Tektronix Keithley FOR-16 User's Manual (FORTRAN Driver) User manual

F0.R - 16
MANUAL
c COPYRIGHT 1985 BY METRABYTE CORPORATION
0
WARRANTY
All products manufactured by MetraByte are warranted against defective materials and workmanship for a period of One Year from the date of delivery to the original purchaser. Any product found to be defective within the warranty period will, at the option of MetraByte, be repaired or replaced. This warranty does not apply to
products which have been damaged by improper use.
MetraByte Corporation assumes no liability for damages consequent to the use of this product. This product is not designed with components of a level of reliability suitable for use in life support of other extremely critical systems.
********************************************************************
MetraByte Corporation
440 Myles Standish Boulevard.
Taunton, MA. 02780 U.S.A.
Phone: (508) 880-3000 Telex: 503989
TABLE OF CONTENTS
CHAPTER
1.00
1.10
1.11
2.00
DESCRIPTION
INTRODUCTION
-----------------------------
PAGE
1
SOFTWARE INSTALLATION AND BACKUP ----------- 1 USING THE LIBRARY _--_____-___________------ 2
DASH-16 FORTRAN SUBROUTINE LIBRARY DESCRIPTIONS ___________________-___________ 3
ADINIT ADCONV
D16FIX DMASTA
DMAOFF DAOUT
DIGOUT DIGIN CNTMIn CNTMOn
INPB INPW
OUTB OUTW
PEEKB PEEKW
BASADR, DMALEV, INTLEV, RTNFLG ) -- 4 MODE, SCH, FCH, DATIN(n), RTNFLG ) DATAX, CHANX )
--------------------
RTNSTATUS ) ____________-----______ g
--__________-_-____------------------ 10
I DACn, DAOUT(m), ( ,,ATO"T ) _-____________-__---------
( DATIN )
-__________________________ 13
RTNFLG ) ---------- 11
12
( MODE ) ___-_--_-__--_____-_________ 14 ( MODE, DATOUT ) -------------------- 15
( PORT ) --_________-________-------- 18 ( PORT ) ---____________--_-_________ 19
( PORT, DATOUT )
( PORT, DATO”T ) _____-____________-_ 21 ( MSEG, MOFF ) ________-__-_-_-------
( MSEG, MOFF )
--------------------
---______-____________
20 22
22
i?
POKEB ( MSEG, MOFF, DATOB ) --------------- 23 POKEW
LOCATE CLRSCN
( MSEG, MOFF, DATOW ) --------------- 23 ( ROW, COL ) ______-_________________
( FG, BG ) --------__________________
24 25
3.00
4.00
APPENDIX A
LIBRARY MEMORY MAP ( GLOBALS ) ------------- 26
SERVICE PERFORMANCE REPORT ----------------- 27
SAMPLE PROGRAM FOR A/D MODES ---------- 29
1
1.0
INTRODUCTION
1.10
The MetraByte DASH-16 Data Acquisition Fortran
library is a
comprehensive set of A/D and D/A driver Functions / Subroutines used to extend the Fortran compiler. The DASH-
16 FortranLibrary also contains a set of general purpose I/O functions (INP, OUT,
PEEK & POKE) to Write and read
bytes or words to or from a user defined I/O port or memory
location over the entire 8088/86 address range of 0 to (2-16
- 1). I/O devices e.g.
This allows the user to directly drive other MetraByte
the PIO-12 Parallel I/O board directly for a variety of control applications and also allows memory mapped devices to be used with Fortran. The DASH - 16 Library follows the linking
format as required by the Microsoft Fortran Compiler Version 3.2, and is outlined in the following sections.
SOFTWARE INSTALLATION AND BACKUP
The installation of the DASH-16 interface board is outlined in the DASH-16 manual chapter 2. The selection of the BASE address and Interrupt and DMA levels are internally set as noted in chapter 1. programmable).
DEVELOPMENT AND THE MASTER DISK STORED IN
A BACKUP COPY SHOULD BE USED FOR PROGRAU
(Base Address = Hex 300, DMA = 1, INT =
A
SAFE PLACE.
The disk format is Single Side Double Density DOS 1.10 format and is read compatible for all versions of PC-DOS. Chapter 5 of the DASH-16 manual shows the hookup of the counter/timers for external trigger of the A/D.
The DAS16FOR.LIB will support DOS 1.10 through DOS 3.00 Fortran compiler versions from 3.0 to 3.2.
Programmers should use
and MS
the MS LINK.EXE which is supplied with your Fortran Compiler to obtain upward compatibility.
Do not
use the LINK.EXE supplied with DOS as several revisions and adjustments have been made in the linker program.
1.11 The DASH-16 Fortran library is used at the linker level as
most libraries. compiled according to the Fortran users guide the linker is ready to produce an run-time EXE file. The Linker will automatically search the Fortran
the standard functions. the user will respond with DAS16FOR.LIB to the question of
LIBRARY: when asked. The session would be as follows.
A>LINK
Microsoft linker version XX . . . . . .
Object modules [.OBJ] filespec Run File [ FILESPEC.EXE 1: <return> List Map [NUL.MAP]: <return> Libraries [.LIB]: DAS16FOR
The DAS16FOR.LIB library should be the last library linked during
the link session. are labeled DATA and not
still link without error< since the DGROUP combines all data segments labeled DGROUP under one segment. See linker manual.
USING THE LIBRARY
Once the users Fortran program has been
libraries required to link
In order to link the DASH-16 library
The data segments used in the DAS16FOR library
DATA as in MS Fortran 3.30. This Will
At this point all will be automatic. as needed by the Fortran program. When the prompt displays the program may be run by typing the name. The following sections
will explain the library functions and the,Fortran format.
A>FILESPEC
This will execute the
.EXE file and run the program
The library will be loaded
2
2.0
DASH-16 FORTRAN SUBROUTINE LIBRARY DESCRIPTIONS
All the following DASH-16 subroutines follow the Standard Fortran functions/subroutines and may be nested up to the
limits of the compiler.
part of
the Fortran
function/subroutine names become
be used as labels.
The variable names used for the DASH-16
library functions are considered variables and must be adhered to or else strange will occur.
Using these function names as labels will
introduce bizarre run and linking errors. consists of two types of functions,
Since the following library becomes
library
RESERVED
INTEGER*2
the
following
names and may not
type for all
errors
The library
the unique DASH - 16 functions and the general purpose I/O type functions. The following is incorporated in the library.
a
list of the functions/subroutines
The page numbers have been
added to this section also for the convenience of the user.
*****eta*** DASH _
SUBROUTINE AND FORMAT
ADINIT ADCONV
D16FIX DMASTA DUAOFF DAOUT DIGOUT DIGIN CNTMIn CNTUOn
********* GENERAL PURPOSE IO FUNCTIONS *********
INPB
INPW
OUTB
OUTW
PEERB
PEEKW
POKEB
POKEW LOCATE CLRSCN
16 UNIQUE SUBROUTINES/FUNCTIONS **********
PAGE NO.
( BASADR, DMALEV, INTLEV, RTNFLG ) --------------- 4
( MODE, SCH, FCH, NOS, DATIN(n), RTNFLG ) -------- 5 ( DATAX, CHANX ) ( RTNSTATUS )
---------------_-_-_____________________---------­( DACn, DAOUT(n),
( DA--,-OUT ) --------______-________________________
---------------------------------
-----------------------------------­10
RTNFLG ) ____--_____-___-------- 11
12
( DATAIN ) --------------_------------------------ 1-j ( MODE ) -----------_-_-_-_______________________- 14
( MODE, DATOUT ) ______________---___------------- I5
( PORT ) ----------_-------______________________- 18 ( PORT j ----------------------------------------- 19
( PORT, DATOUT )
( PORT, DAT~UT ) --------_________________________ ( MSEG, MOFF ) __-___-_---___-_-__----------------
( MSEG, MOFF ) ( MSEG, MOFF, DATOB )
( MSEG, MOFF, DATOW )
---------------------------------
-----------------__________________ _____________-______--------
___________________-________ 23
20 21 22 22 23
( ROW, COL ) --____-____--____-___________________ 24 ( FG, BG ) --------------------------------------- 25
8 9
3
DASH-16
FORTRAN LIBRARY DESCRIPTION OF LIBRARY SUBROQTINES
ADINIT ( BASADR, DMALEV, INTLBV, RTNFLG )
This function initializes parameters in order for the
the DASH-16 identification
library functions to
be
used. The function does not have to be executed within a Fortran module since the library has default values.
If other than the default values are used then this function must be executed.
The ADINIT function also allows the user to setup a second board for communications with the system, however only one board is allowed to be operational at a time. If the user wishes to run more than one board in the system, this command should be run for all the boards in the system first. The parameter limits are as follows. names are
BASADR
INTEGER*2
type (2 Bytes length).
= Base Address of DASH - 16 board (OlOOH to 03FOH)
This address range is
checked before further
All variable
execution.
DHALEV
= DMA Channel number of DASH - 16 board ( 1 or 3 )
Only channel 1 or 3 is allowed.
INTLEV
= INTERRUPT Level of DASH - 16 board ( 2 to 7 )
This level is also checked for range.
RTNFLG
= Flag Return Code for current selected function.
EXAMPLE: C
** SETUP BOARD PARAMETERS AS INTEGER * 2 TYPE **
C
INTEGER*2 BASADR,DMALEV,INTLEV,FLGRTN BASADR = t300 DMALEV = #3
INTLEV = #2 FLGRTN = #0
C C
******* EXECUTE FUNCTION CALL *******
C
CALL ADINIT ( BASADR, DMALEV, INTLEV, FLGRTN )
IF (FLGRTN .NE.
C C
10
. . . . . . USER CONTINUES PROGRAM . . . . . . .
----- USER ERROR HANDLER, CHECK RTNFLG FOR ERRORS
END
0000H = function successful. continue normally. 000lH
0003H 0004H
0005H
= System already in use. can't continue. = BASADR variable range error, <lOOH,>3FOH = INTLEV variable range error, <2 or >7. = DMALEV variable range error, not 1 or 3
#o)
GOTO 10
4
DASH-16 FORTRAN LIBRARY
ADCONV 1 MODE, SCH, FCH, NOS, DATIN(n), RTNFLG )
This function allows the user to collect data via the A/D converter using one of five modes. The user also selects the number of channels Start to Final, and the Number Of Scans
for data collection.
to the Final Channel (SCH to FCH). If the Start Channel
(SCH) = 0, and the Final Channel (FCH) = 7, then one scan would collect 8 channels of data into the array DATIN(n). The array size must be large enough to receive the data, at
least ( NOS*(FCH-SCH +l) 1. If SCH = FCH then the Number Of
Scans (NOS) will be the actual number of conversions for that channel.
If 100 conversions are required on channel 3
then, SCH = FCH = 3, and NOS = 100, The array must be at
least DATIN(100)
statement. typing
In MODES 1, 2,
ESC
key
next Fortran statement after the ADCONV statement. This will allow termination of data collection with out re- booting the system. All data previously collected before was pressed
will be valid and the return flag code will be
HEX 1000. (#lOOO).
DESCRIPTION OF LIBRARY SUBROUTINES
A Scan is defined as the Start Channel
[ INTEGER*2 type ] in a DIMENSION
3 and 4 (external trigger modes)
will terminate the run and execute the
Esc key
MODE =
Data
0 =
1=
2 =
3 =
Collection Mode A/D only
Internal start of conversion (start on entry)
Immediate start of conversion by software and collect the specified number of conversions to the specified array.
This routine is
program control only (NO DMA). External trigger for each conversion.
Transfer data to the specified array under program control. The A/D starts with the external trigger for each conversion. The number of conversions is determined by the NOS and the number of channels. This mode is also program control data transfer (NO DMA).
External trigger for each block (SCH-FCH) of channels (NO DMA) under program control. An error code will be returned if the limits are exceeded.
External trigger for each conversion (DMA). This routine collects the data after each external trigger and transfers the data to
the array via DMA. The user
remains in this routine until all the specified conversions are completed.
The user may interrupt the
5
DASH-16 FORTRAN LIBRARY DESCRIPTION OF LIBRARY SUBROUTINES
data collection by pressing the
Esc key.
4 = External trigger for each block (SCH-FCH) of
channels using DMA.
An error code will be returned if the limits are exceeded. Although DMA transfer,
this mode can only be driven at
interrupt rates.
5 = External Trigger Background DMA Data
Transfer.
This mode allows the user to
collect data in the background while running
a secondary program in the foreground. Background
data
collection
runs at the
The
maximum transfer rate of the A/D converter or the rate of the external trigger. 'It is the users responsibility to insure the variable data
array is not
collection.
changed during
The user may check the status of
data
the data transfer at any time by the DMASTA
function which returns the current number of
conversions and the current DASH-16 board
status.
The user may terminate the data collection before the normal end of transfer by the DMAOFF function.
6 = External Trigger DMA mode Auto-Initialize.
This mode allows the user to collect data into the specified
background.
The data is collected until a
array
continuously in the
DMAOFF function is executed. It is the users responsibility to disable the DMA operation
when data collection is no longer required.
NOTE:
The output of counter 2 may be internally connected to the A/D trigger input (IPO) by adding 16 decimal (#lo hex) to the mode.
EXAMPLE:
MODE = 4t16 Will be mode 4 and counter 2 output will be the Trigger for the A/D converter.
SCH = Start Channel ( 0 - 15 Single Ended ) ( 0 - 7
Diff.) This channel is automatically reloaded when
the FCH (final channel) is reached in the
register.
An error code will be returned if the
MUX
scan
limits are exceeded.
PCH =
Final Channel ( 0 - 15 Single Ended ) ( 0 - 7 Diff.). when the SCH (start channel) reloads the
This channel is automatically reloaded
MUX
scan
6
DASH-16 FORTRAN LIBRARY
register. An error code will be returned if the
limits are exceeded.
DESCRIPTION OF LIBRARY SUBROUTINES
NOS =
RTNFLG
= Flag Return code for status of function selected.
HEX CODE 0
DATIN(n) =
Number Of Scans for each group of channels
specified by SCH and
FCH. NOC (number of
conversions) is defined by the equation, NOC = NOS
* ( FCH - SCH + 1 ).
The number of conversions must be with in the range of NOC max = 32760, NOC min = 1. An error code will be returned if the
limits are exceeded.
=
Transfer ok
=
1
SCH, FCH
channel limits exceeded for
Differential
=
2
SCH, FCH channel limits exceeded for Single Ended
3 4
5
6
100
1000
NOC Limit error
A/D DMA mode or Board Busy Time out. No EOC from convertor DMA Vector level range error DMA / Data collection hardware error Function Terminated by Esc key sequence
Data Transfer variable
< 1 or > 32760
INTEGER*2
type Only. !!I This variable is used for data transfer and may be a single variable if only a single channel is to be converted.
length less than or equal to 32760
conversion.
lb bits and a
DATIN(~) may be an array of max
for the data
This is due to the fact of segments Of
lb
byte boundary constraint. The
variable must be a word (2 bytes) type integer.
The size n = NOS*(FCH-SCH+l) minimum.
EXAMPLE: C
**** INITIALIZE VARIABLE'S TYPE FOR USE WITH FUNCTION **** INTEGER*2 MODE, SCH, FCH, NOS, RTNFLG DATIN
C C
**** DIMENSION DATA ARRAY FOR (FCH7-SCHO+l)*lOO = 800
C
DIMENSION DATIN (800)
C
C
***** INITIALIZE VARIABLES ******
C
MODE0 = 0
SCHO = 0 FCH7 = 7
NOSlOO = 100
7
Loading...
+ 25 hidden pages