10!  OUTPUT 2 USING "#,K";"<lf>REN<cr>INDENT<cr>RE-STORE ""INPT_H""<cr>"
20!
30  !*************************************************************************
40  !
50  !
60  !                          INPT file
70  !
80  ! This is the INPT file.  It contains subprograms used to setup and control
90  ! the input modules in an HP3565S system.  Only 'active' input modules,
100 ! as defined by the CNFG file, are controlled, since 'inactive' inputs are
110 ! treated as though they don't exist.  This file has some subprograms that
120 ! are used to directly send commands and get responses from an input module.
130 ! It also contains a spreadsheet subprogram that provides a convenient way
140 ! to display and change the setup of the input modules.  Finally, this file
150 ! provides some routines useful for interpreting error messages and status
160 ! bits that can be sent out by a input module.  The following is a
170 ! discription of some of the subprograms in this file.  These are the only
180 ! subprograms that should need to be called from other files or
190 ! applications.  Additional documentation is included in-line with each
200 ! subprogram.
210 !
220 !
230 !        Subprograms available to the user :
240 !
250 !  Inpt_inpt
260 !
270 !                   Poweron Initialization.
280 !
290 !  Inpt_init(OPTIONAL Passed_setup$(1:Num_columns))
300 !
310 !                   Should be called after any change in the inpt
320 !                   configuration or after the Inpt_inpt subprogram
330 !                   is called.  The optional parameter can be used to
340 !                   reinitialize the columns of the input spread sheet.
350 !                   Passed_setup$ contains a list of spread sheet columns
360 !                   to be displayed.  See the spread sheet column table
370 !                   below to determine list of possible column names.
380 !
390 !  Inpt_spread(Changed)
400 !
410 !                   Subprogram to display and allow modification of the
420 !                   input spreadsheet.  The Changed parameter returns true
430 !                   if any change has occurred to an input module.
440 !                   When the Inpt_spread subprogram is exited all errors
450 !                   are cleared.
460 !
470 !  Inpt_cmd(Module_label$,Command$,OPTIONAL Parameter$)
480 !
490 !                   Subprogram to send a command to an input module. The
500 !                   command string is one of the commands in the table
510 !                   at the label "Inpt_commands", and the parameter
520 !                   is one of the parameters for that command.
530 !                   In general, Command$ and Parameter$ can be written out
540 !                   as verbosely as you want, and this subprogram will do
550 !                   its best to interpret them.
560 !
570 !  FNInpt_rsp$(Module_label$,Command$)
580 !
590 !                   Function to query a module for what state its been
600 !                   set to.  Command$ is the command to query.  Returns
610 !                   a string from the module.  Again, the Command$ can be
620 !                   typed out verbosely, and will be interpreted by the
630 !                   subprogram.  NOTE: This routine will not query the
640 !                   the module if the value is already in the
650 !                   spreadsheet.  The spreadsheet value can be different
660 !                   if an ICODE program sends commands to the module
670 !                   changing the setup, or if the CNFG file subprograms
680 !                   are used to change an input module's setup.
690 !
700 !  Inpt_reset(Module_label$)
710 !
720 !                   Subprogram to set the specified module(s) to a known
730 !                   state.  This subprogram only sets the parameters that
740 !                   are in the spreadsheet to known values.  To reset ALL
750 !                   parameters of the module, use:
760 !                     Inpt_cmd(Module_label$,"RESET").
770 !
780 !  FNInpt_stat_2_str$(stat)
790 !
800 !                   This subprogram returns a string containing the
810 !                   mnemonics for each of the status bits set in the
820 !                   passed in word.
830 !
840 !
850 !  FNInpt_str_2_stat(A$)
860 !
870 !                   This subroutine returns a number which represents the
880 !                   status of the Input module if the status bits indicated
890 !                   by A$ are set.  Bit mnemonics may be separated by "," or
900 !                   "|".  This is the inverse of subprogram
910 !                   FNInpt_stat_2_str$(stat).
920 !
930 !  FNInpt_get_errstr$(Error_num)
940 !
950 !                   This subprogram returns a string containing the error
960 !                   message corresponding to the input error number
970 !                   that is passed to it.
980 !
990 !  Inpt_save(@File,Ok)
1000!
1010!                   This subprogram saves the current input setups in
1020!                   the file specified by @File, and returns Ok=1 if
1030!                   it successfully saves the setups.
1040!
1050!  Inpt_load(@File,Ok)
1060!
1070!                  This subprogram loads the input setups from file
1080!                  @File, and returns Ok=1 if the load is successful.
1090!
1100!  Inpt_autorng(Module_label$)
1110!                   Subprogram to autorange the specified module(s).  This
1120!                   waits until the autorange(s) has finished.
1130!
1140!  Inpt_df_resp(Response(*),Span_f,Zoom)
1150!                   Subprogram generates the digital filter response given
1160!                   the span (assumes 262144 hz sample rate) and if zooming
1170!                   or not.  The digital filter response is returned in the
1180!                   Response(*) array and can be used to divide into the
1190!                   FFT'ed spectrum of an input channel.  The array returned
1200!                   is a floating point, complex array of numbers.
1210!
1220!  Inpt_get_spread(OPTIONAL Module$)
1230!
1240!                   This routine querys all the active modules in the system
1250!                   for the needed parameters to fill in the spreadsheet.
1260!
1270!      Spreadsheet configuration column names
1280!
1290!     Name
1300!    -----------------------
1310!    INPUT MODE    -  Sets input mode (volt,icp, or charge)
1320!    COUPLING      -  Sets AC/DC coupling
1330!    GROUNDING     -  Sets floating/grounded mode
1340!    SPAN          -  Sets span frequency
1350!    CENTER        -  Sets center frequency
1360!    BLOCKSIZE     -  Sets measurement blocksize
1370!    TRIG MODE     -  Sets trigger mode (send/recieve)
1380!    TRIG SOURCE   -  Sets trigger source (Same as TRIG MODE, but with
1390!                      all options available)
1400!    TRIG TYPE     -  Sets trigger type (level/magnitude)
1410!    TRIG SLOPE    -  Sets trigger slope (positive/negative)
1420!    TRIG DELAY    -  Sets trigger delay
1430!    TRIG LEVEL    -  Sets trigger level (for level mode)
1440!    UPPER LEVEL   -  Sets upper trigger level (also for level mode too)
1450!    LOWER LEVEL   -  Sets lower trigger level
1460!
1470!*************************************************************************
1480!               TEST CODE
1490!
1500 Testcode:!
1510!LOADSUB ALL FROM "USER"
1520!LOADSUB ALL FROM "HW"
1530!LOADSUB ALL FROM "CNFG"
1540!LOADSUB ALL FROM "LIB"
1550!DELSUB USER_USER   TO END
1560!
1570  FOR I=0 TO 9
1580    ON KEY I LABEL "" GOSUB Dummy
1590  NEXT I
1600  !
1610  User_user
1620  Hw_hw
1630  Cnfg_cnfg
1640  Inpt_inpt
1650  Cnfg_spread(Junk)
1660  Inpt_init
1670  !
1680  REDIM Small_test$(1:2)
1690  Small_test$(1)="INPUT MODE"
1700  Small_test$(2)="RANGE"
1710  LOOP
1720    Inpt_spread(Changed)
1730    Dummy=FNUser_get_key
1740    Inpt_init(Small_test$(*))
1750    Inpt_spread(Changed)
1760    Dummy=FNUser_get_key
1770    Inpt_init
1780  END LOOP
1790  !
1800  STOP
1810  !
1820 Dummy: !
1830  RETURN 
1840  END
1850  ! PAGE -> 
1860  !************************************************************************
1870 Inpt_inpt:SUB Inpt_inpt
1880    !
1890    ! Inpt_inpt should be called the first time this file is run after
1900    ! it is loaded.  It sets up the data used to convert a verbose command
1910    ! into the real input command.  It also has a copy of every common
1920    ! declaration in the INPT file.
1930    !
1940    COM /Inpt_sprd_posn/ Row,Col,Start_row
1950    COM /Inpt_sprd_box/ Box$(1:20,1:63)[16]
1960    COM /Inpt_sprd_title/ Title$(1:20,0:2)[20]
1970    COM /Inpt_sprd_tog/ Toggle$(1:20)[40]
1980    COM /Inpt_sprd_cmnd/ Cmnd_code$(1:20)[20]
1990    COM /Inpt_sprd_prmpt/ Prompt$(1:20)[60]
2000    COM /Inpt_sprd_other/ Col_width(1:20),Max_col,Max_row,Modify_col
2010    COM /Inpt_sprd_reset/ Reset_parms$(1:20)[20]
2020    !
2030    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(1:50)[60],Cnv_mod_cmnd$(1:50)[5]
2040    COM /Inpt_parm_cnv/ Convert_parm$(1:50,0:5)[45]
2050    !
2060    ! Row, Col, and Start_row determine the cursor position in the input
2070    ! spreadsheet.  They are in common so that if the spreadsheet is
2080    ! exited and then re-entered, the cursor will remember where it was.
2090    !
2100    ! Box$ is the array of boxes in the input spreadsheet.
2110    !
2120    ! Title$ is the array of titles for the top of each column of the
2130    ! spreadsheet.
2140    !
2150    ! Toggle$ is an array of strings.  Each string contains the list of
2160    ! values to step through as the 'prev' or 'next' softkey is pushed.
2170    !
2180    ! Cmnd_code$ is an array of the source commands that goes with
2190    ! each column of the spreadsheet.
2200    !
2210    ! Prompt$ is an array of the prompts for each column of the
2220    ! spreadsheet.
2230    !
2240    ! Reset_parms$ is an array of the reset values for each column
2250    ! of the spreadsheet.  This is the value that the input module
2260    ! will start with after Inpt_init is called, and this is also the
2270    ! value that the input module will have after Inpt_reset is called.
2280    !
2290    ! Column_width is an array of the column widths for each column
2300    ! of the spreadsheet.  Max_col and Max_row define the size of the
2310    ! spreadsheet.  Modify_col is the first column that the user can
2320    ! modify.
2330    !
2340    ! Cnv_cmnd_code$ and Cnv_mod_cmnd are arrays of conversion data for
2350    ! converting verbose input commands into the actual command string
2360    ! that the input module expects.  Each element of Cnv_cmnd_code is a
2370    ! list of possible strings, separated by vertical bars, which will be
2380    ! mapped into the actual input command found in Cnv_mod_cmnd$
2390    !
2400    ! Convert_parm$ is used to map verbose parameters of commands into
2410    ! the actual parameters that the input module expects.  It is a 2
2420    ! dimensional array.  The first dimension determines which input
2430    ! command the parameter goes with.  The second determines which
2440    ! parameter for that command.  Each element is a list of verbose
2450    ! parameters separated by vertical bars.
2460    !
2470    !
2480    DIM Temp_code$[55],Dummy$[200]
2490    DIM Setup_array$(1:20)[20],Setup_name$[20]
2500    !
2510    !
2520    Max_col=1
2530    Max_row=1
2540    REDIM Box$(1:Max_col,1:Max_row)
2550    !
2560    ! Read the command code and parameter conversion data into arrays
2570    !
2580    RESTORE Inpt_cnv_data
2590    C=0
2600    Rmax=SIZE(Convert_parm$,2)-1
2610    REPEAT
2620      READ Temp_code$
2630      Temp_code$=UPC$(Temp_code$)
2640      IF Temp_code$<>"NO MORE" THEN 
2650        C=C+1
2660        READ Cnv_mod_cmnd$(C)
2670        Cnv_cmnd_code$(C)=Temp_code$&"|"&Cnv_mod_cmnd$(C)
2680        R=0
2690        Null_found=0
2700        REPEAT
2710          READ Convert_parm$(C,R)
2720          R=R+1
2730          IF Convert_parm$(C,R-1)="" THEN 
2740            Null_found=1
2750            WHILE R<=Rmax
2760              Convert_parm$(C,R)=""
2770              R=R+1
2780            END WHILE
2790          END IF
2800        UNTIL R>Rmax
2810        IF NOT Null_found THEN 
2820          READ Dummy$
2830          IF Dummy$<>"" THEN 
2840            DISP "ERROR : "&Temp_code$&" table command has no null parm string"
2850            PAUSE
2860          END IF
2870        END IF
2880      END IF
2890    UNTIL Temp_code$="NO MORE"
2900    !
2910 Inpt_commands:!
2920    !
2930    ! Command conversion data can be interpreted as follows.  First, there
2940    ! is a string that contains all the possible verbose commands,
2950    ! separated by vertical bars.  The next string is the actual command
2960    ! that will be sent to the input module if one of the verbose commands
2970    ! is specified.  The next strings, until a null string is found, are
2980    ! used to convert verbose parameters to the command.  They are in
2990    ! order, and each string contains the possible verbose parameters
3000    ! separated by vertical bars.  The end of the data is signalled by
3010    ! the string "NO MORE".
3020    !
3030 Inpt_cnv_data:   !
3040    ! This command has no parameters
3050    DATA  "RESET|RESET MODULE"  ! Verbose versions
3060    DATA    "RST"               ! Actual command to input module
3070    DATA    ""                  ! No parameters
3080    ! This command has parameters
3090    DATA  "INPUT MODE|MODE"     ! Verbose versions
3100    DATA    "INPM"              ! Actual command to input module
3110    DATA    "VOLT|VOLTAGE|V"    ! Verbose forms of parameter #0
3120    DATA    "ICP|I"             !   "       "   "      "     #1
3130    DATA    "CHRG|CHARGE|C"     !   "       "   "      "     #2
3140    DATA    ""                  ! No more parameters
3150    DATA  "START|START MODULE|START MEASUREMENT"
3160    DATA    "STRT",""
3170    DATA  "STOP MODULE|STOP MEASUREMENT"
3180    DATA    "STOP",""
3190    DATA  "GROUNDING|INPUT GROUNDING|GNDING"
3200    DATA    "IGND"
3210    DATA    "FLOAT|FLOATING|DIFF|DIFFERENTIAL|F|D"
3220    DATA    "GNDED|GND|GROUND|GROUNDED|G",""
3230    DATA  "COUPLING|INPUT COUPLING"
3240    DATA    "CPL"
3250    DATA    "DC|D","AC|A",""
3260    DATA  "RANGE|INPUT RANGE"
3270    DATA    "RNG",""
3280    DATA  "CENTER|CENTER FREQ|CENTER FREQUENCY"
3290    DATA    "CF",""
3300    DATA  "SPAN|SPAN FREQ|SPAN FREQUENCY"
3310    DATA    "SP",""
3320    DATA  "ZOOM|ZOOM MODE"
3330    DATA    "ZOOM"
3340    DATA    "OFF|OF","ON",""
3350    DATA  "BLOCKSIZE|BLOCK SIZE|MEASUREMENT SIZE"
3360    DATA    "BSIZ",""
3370    DATA  "TRIG|TRIG MODE|TRIGGER MODE|TRIG SOURCE|TRIGGER SOURCE"
3380    DATA    "TSRC"
3390    DATA    "IGNR|LOCAL FREERUN|IGNORE|IGNORE TRIGGER|I"
3400    DATA     "LINP|LOCAL INPUT|LOCAL INPUT TRIGGER|L"
3410    DATA     "MAN|MANUAL|MANUAL TRIGGER|M"
3420    DATA     "FREE|FREERUN|SYSTEM FREE|SYSTEM FREERUN|F"
3430    DATA     "SEND|SYSTEM INPUT|SEND TRIGGER|S"
3440    DATA     "RCVE|RECEIVE|SYSTEM|RECEIVE TRIGGER|R",""
3450    DATA  "TRIG TYPE|TRIGGER TYPE"
3460    DATA    "TRGM"
3470    DATA    "LVL|LEVEL|SLOPE|L","MAG|MAGNITUDE|BOUNDED|M",""
3480    DATA  "UPPER LEVEL|MAIN LEVEL|TRIG LEVEL"
3490    DATA    "TLVL",""
3500    DATA  "LOWER LEVEL|ALTERNATE LEVEL"
3510    DATA    "TMLV",""
3520    DATA  "TRIG DELAY|TRIGGER DELAY"
3530    DATA    "TDLY",""
3540    DATA  "TRIG SLOPE|TRIGGER SLOPE|SLOPE"
3550    DATA    "TSLP"
3560    DATA    "+|POS|POSITIVE|P","-|NEG|NEGATIVE|N",""
3570    DATA  "TRANSFER MODE|DATA MODE|DATA TRANSFER MODE"
3580    DATA    "TRNM"
3590    DATA    "BLOCK|B","CONTINUOUS|CONT|C",""
3600    DATA  "TRANSFER SIZE|TRANSFER BLOCK SIZE"
3610    DATA    "TBLK",""
3620    DATA  "OVERLOADS|NUMBER OF OVERLOADS"
3630    DATA    "RNOV",""
3640    DATA  "OVERLOAD INFO|OVERLOAD TYPES|OVERLOAD INFORMATION"
3650    DATA    "OVRI",""
3660    !
3670    DATA  "CLEAR|CLEAR ERRORS"
3680    DATA    "CLR",""
3690    DATA  "SRQ MASK|SRQ"
3700    DATA    "RQS",""
3710    DATA  "INTR MASK|INTERRUPT MASK|INTERRUPT"
3720    DATA    "INTR",""
3730    DATA  "SHUT MASK|SHUTDOWN MASK|SHUTDOWN"
3740    DATA    "SHUT",""
3750    DATA  "ERROR|ERROR QUEUE"
3760    DATA    "ERR",""
3770    DATA  "STATUS|GET STATUS"
3780    DATA    "STA",""
3790    DATA  "CHECK STATUS"
3800    DATA    "STC",""
3810    DATA  "STATE|MODULE STATE|MEASUREMENT STATE"
3820    DATA    "MS",""
3830    !
3840    DATA  "CAL|CAL BUS MODE|CAL MODE|CAL BUS"
3850    DATA    "ICAL"
3860    DATA    "OFF|OF|O","FRONTEND|FRONT END|INPUT|F"
3870    DATA    "A/D|A/D CONVERTER|CONVERTER|A"
3880    DATA    ""
3890    DATA  "PHASE|START PHASE|LO PHASE"
3900    DATA    "LOPH",""
3910    DATA  "FILTER PHASE|DIGITAL FILTER PHASE"
3920    DATA    "DFPC",""
3930    DATA  "ARM MODE"
3940    DATA    "ARM"
3950    DATA    "AUTO|FREERUN|FREE RUN|A"
3960    DATA    "MANUAL|M",""
3970    DATA  "MAN ARM|MANUAL ARM|ARM MEASUREMENT"
3980    DATA    "MARM",""
3990    !
4000    DATA  "OVERLAP|OVERLAP AMOUNT|OVERLAP SIZE"
4010    DATA    "OLAP",""
4020    DATA  "AUTORANGE|AUTO-RANGE|AUTO RANGE|AUTORNG"
4030    DATA    "SARG",""
4040    DATA  "AUTOZERO|AUTO-ZERO|AUTO ZERO|SINGLE AUTOZERO"
4050    DATA    "SAZ",""
4060    DATA  "TRIGGER|TRIGGER MODULE"
4070    DATA    "TRG",""
4080    DATA  "SYNC MODE"
4090    DATA    "SYNC","OFF|OF","ON",""
4100    DATA  "OVERHEAD|AUTORANGE OVERHEAD"
4110    DATA    "AROV",""
4120    DATA  "AUTORANGE TIME|AUTORNG TIME"
4130    DATA    "ART",""
4140    DATA  "AUTORANGE TIME MODE|AUTORNG TIME MODE"
4150    DATA    "ARIT"
4160    DATA    "OFF|OF","ON",""
4170    DATA  "AUTOZERO TIME"
4180    DATA    "AZT",""
4190    DATA  "AUTOZERO TIME MODE"
4200    DATA    "AZIT"
4210    DATA    "OFF|OF","ON",""
4220    DATA  "AUTOZERO MODE|ZERO MODE"
4230    DATA    "AZM"
4240    DATA    "ZERO|Z","ALL|ALL RANGES|A",
4250    DATA    "OFFSET|DC OFFSET|O"
4260    DATA    "SINGLE INPUT|SINGLE OFFSET|S","INPUT|INPUT OFFSET|I"
4270    DATA    ""
4280    DATA  "AUTOZERO SINGLE MODE"
4290    DATA    "AZSM"
4300    DATA    "OFF|OF","ON",""
4310    DATA  "OFFSET|ZERO OFFSET|AUTOZERO OFFSET"
4320    DATA    "OAZ",""
4330    DATA  "SETTLING|ENABLE SETTLING"
4340    DATA    "DSET",
4350    DATA    "ON","OFF|OF",""
4360    DATA  "INV INPUT|INVERT|INVERSION|INVERT INPUT|I"
4370    DATA    "DS_H"
4380    DATA    "+|POS|POSITIVE|P","-|NEG|NEGATIVE|N",""
4390    DATA  "MAXIMUM OVERLOADS"
4400    DATA    "NOVR",""
4410    DATA  "NO MORE"
4420    !
4430    !
4440  SUBEND
4450  ! PAGE -> 
4460  !************************************************************************
4470 Inpt_setup:SUB Inpt_setup(OPTIONAL Passed_setup$(*))
4480    !
4490    ! Inpt_setup is used to specify the columns that will show up in the
4500    ! input spreadsheet.  The Passed_setup$ parameter is an array of
4510    ! strings, each specifying one column of the spreadsheet.  If the
4520    ! parameter is not there, default columns are used.
4530    !
4540    COM /Inpt_sprd_posn/ Row,Col,Start_row
4550    COM /Inpt_sprd_box/ Box$(*)
4560    COM /Inpt_sprd_title/ Title$(*)
4570    COM /Inpt_sprd_tog/ Toggle$(*)
4580    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
4590    COM /Inpt_sprd_prmpt/ Prompt$(*)
4600    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
4610    COM /Inpt_sprd_reset/ Reset_parms$(*)
4620    !
4630    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
4640    COM /Inpt_parm_cnv/ Convert_parm$(*)
4650    !
4660    DIM Temp_code$[55],Dummy$[200]
4670    DIM Setup_array$(1:20)[20],Setup_name$[20]
4680    !
4690    RESTORE Inpt_def_setup
4700    READ Setup_size
4710    REDIM Setup_array$(1:Setup_size)
4720    READ Setup_array$(*)
4730    IF NPAR>0 THEN MAT Setup_array$= Passed_setup$
4740    Setup_size=SIZE(Setup_array$,1)
4750    !
4760    Max_col=Setup_size+1
4770    Max_row=63
4780    Modify_col=2
4790    !
4800    REDIM Title$(1:Max_col,0:2),Cmnd_code$(1:Max_col)
4810    REDIM Prompt$(1:Max_col),Col_width(1:Max_col)
4820    !
4830    Row=1
4840    Col=2
4850    Start_row=1
4860    !
4870    ! Setup the first column
4880    !
4890    Col_width(1)=16
4900    Title$(1,1)="Channel"
4910    Title$(1,2)="Name"
4920    Cmnd_code$(1)=""
4930    Prompt$(1)=""
4940    Title$(1,0)="Input Spreadsheet"
4950    !
4960    ! Read the column data into arrays
4970    !
4980    Total_width=Col_width(1)+2
4990    FOR C=2 TO Max_col
5000      RESTORE Inpt_data
5010      REPEAT
5020        READ Setup_name$
5030        IF UPC$(Setup_name$)="NO MORE" THEN 
5040          User_error("Illegal setup parm. to Inpt_inpt: "&Setup_array$(C-1))
5050        END IF
5060        This_is_it=(UPC$(Setup_name$)=UPC$(Setup_array$(C-1)))
5070        READ Toggle$(C),Reset_parms$(C),Col_width(C),Title$(C,1),Title$(C,2),Prompt$(C)
5080        Cmnd_code$(C)=Cnv_mod_cmnd$(FNInpt_get_code(Setup_name$))
5090        IF This_is_it THEN Total_width=Total_width+1+Col_width(C)
5100      UNTIL This_is_it
5110    NEXT C
5120    IF Total_width>FNLib_crt_width THEN 
5130      User_stop("Illegal Setup_array in Inpt_Inpt, too many chars: "&VAL$(Total_width))
5140    END IF
5150    C=1
5160    Loop_cnt=0
5170    WHILE (Total_width<FNLib_crt_width) AND (Loop_cnt<>2)
5180      Col_width(C)=Col_width(C)+1
5190      C=C+1
5200      IF C>Max_col THEN 
5210        C=1
5220        Loop_cnt=Loop_cnt+1
5230      END IF
5240      Total_width=Total_width+1
5250    END WHILE
5260    !
5270    !
5280    ! The data statements at the end of this subprogram define the
5290    ! possible columns for the input spreadsheet.  For each column, there
5300    ! is an associated input command, a list of the parameters to send to
5310    ! the module as the prev and next keys are used, a default (reset)
5320    ! value for the command, a column width, two column title strings, and
5330    ! a prompt string.  This data for each column is loaded into arrays for
5340    ! the spreadsheet to use.
5350    !
5360    !
5370    !   command code         toggle codes              reset parm
5380    !   ----------------     ------------------------  ----------
5390    !     col_width  title1         title2       Prompt
5400    !     ---------  ----------     ----------   --------------------
5410 Inpt_data:!
5420    DATA    "INPUT MODE",    "VOLT|ICP|CHRG",          "VOLT"
5430    DATA      4,     "Inpt ",       "Mode ",     "Input mode: Volt, ICP, or Chrg"
5440    DATA    "GROUNDING",     "GND|FLOAT",              "GND"
5450    DATA      6,     "Input",       "Gnding",    "Input grounding: Ground, or Float"
5460    DATA    "COUPLING",      "DC|AC",                  "DC"
5470    DATA      4,     "Cplg ",       "",          "Coupling: AC, DC"
5480    DATA    "RANGE",         "",                       "0"
5490    DATA      5,     "Range",       "(dB) ",     "Full scale Range in dBVp or dBpCp"
5500    DATA    "SPAN",          "",                       "51200"
5510    DATA      9,     "Span ",       "(Hz) ",     "Span frequency in Hz"
5520    DATA    "CENTER",        "",                       "25600"
5530    DATA      9,     "Center ",     "Freq (Hz)", "Center frequency in Hz"
5540    DATA    "BLOCKSIZE",     "",                       "1024"
5550    DATA      4,     "Blk",         "Size",      "Block size"
5560    DATA    "TRIG MODE",     "SEND|RCVE",              "RCVE"
5570    DATA      4,     "Trig ",       "Mode ",     "Trigger mode: Send, or Rcve"
5580    DATA    "TRIG SOURCE",   "FREE|LINP|MAN|IMM|SEND|RCVE", "RCVE"
5590    DATA      6,     "Trig ",       "Source ",   "Trigger source: Free, Linp, Man, Imm, Send, or Rcve"
5600    DATA    "TRIG TYPE",     "LVL|MAG",                "LVL"
5610    DATA      4,     "Trig ",       "Type ",     "Trigger type: LVL, MAG"
5620    DATA    "TRIG LEVEL",    "",                       "0"
5630    DATA      7,     "Trigger",     "Level",     "Trigger level in % of full scale"
5640    DATA    "UPPER LEVEL",   "",                       "50"
5650    DATA      7,     "Upper",       "Level",     "Upper/Slope trigger level in % of full scale"
5660    DATA    "LOWER LEVEL",   "",                       "-50"
5670    DATA      7,     "Lower",       "Level",     "Lower trigger level in % of full scale"
5680    DATA    "TRIG DELAY",    "",                       "0"
5690    DATA      7,     "Trig ",       "Delay",     "Trigger delay in filtered samples"
5700    DATA    "TRIG SLOPE",    "+|-",                    "+"
5710    DATA      5,     "Trig ",       "Slope",     "Trigger slope: + OR -"
5720    DATA    "INV INPUT",     "+|-",                    "+"
5730    DATA      6,     "Invert",      "Input ",    "Input inversion: + OR -, (+ for non inverting)"
5740    DATA    "NO MORE"
5750    !
5760    !
5770    ! The following defines the columns to be used in the input
5780    ! spreadsheet if no columns are specified.
5790    !
5800 Inpt_def_setup:   !
5810    DATA 9
5820    DATA "INPUT MODE","COUPLING","GROUNDING","RANGE","CENTER","TRIG MODE"
5830    DATA "TRIG LEVEL","TRIG DELAY","TRIG SLOPE"
5840    !
5850    !
5860  SUBEND
5870  ! PAGE -> 
5880  !************************************************************************
5890 Inpt_init:SUB Inpt_init(OPTIONAL Passed_setup$(*))
5900    !
5910    ! Should be called after any change in the inpt
5920    ! configuration or after the Inpt_inpt subprogram
5930    ! is called.  The optional parameter can be used to
5940    ! reinitialize the columns of the input spread sheet.
5950    ! Passed_setup$ contains a list of spread sheet columns
5960    ! to be displayed.  This subprogram also loads up Box$
5970    ! with correct values.
5980    !
5990    COM /Inpt_sprd_box/ Box$(*)
6000    COM /Inpt_sprd_title/ Title$(*)
6010    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
6020    COM /Inpt_sprd_prmpt/ Prompt$(*)
6030    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
6040    !
6050    IF NPAR>0 THEN 
6060      Inpt_setup(Passed_setup$(*))
6070    ELSE
6080      Inpt_setup
6090    END IF
6100    !
6110    ALLOCATE Inpt_labels$(1:63)[16]
6120    Cnfg_labels("ALL INPUT",Inpt_labels$(*),Num_inputs)
6130    !
6140    REDIM Box$(1:Max_col,1:(1+Num_inputs))
6150    Max_row=Num_inputs+1
6160    Box$(1,1)="All Input"
6170    FOR Col=2 TO SIZE(Box$,1)
6180      Box$(Col,1)=""
6190    NEXT Col
6200    !
6210    FOR Row=1 TO Num_inputs
6220      Box$(1,Row+1)=TRIM$(Inpt_labels$(Row))
6230    NEXT Row
6240    !
6250    DEALLOCATE Inpt_labels$(*)
6260    !
6270    Inpt_reset("ALL INPUT")
6280    !
6290  SUBEND
6300  ! PAGE -> 
6310  !************************************************************************
6320 Inpt_spread:SUB Inpt_spread(Changed)
6330    !
6340    ! Subprogram to display and allow modification of the
6350    ! input spreadsheet.  The Changed parameter returns true
6360    ! if any change has occurred to an input module.
6370    ! When the Inpt_spread subprogram is exited with Changed true,
6380    ! all errors are cleared on all the inputs.
6390    !
6400    COM /Inpt_sprd_posn/ Row,Col,Start_row
6410    COM /Inpt_sprd_box/ Box$(*)
6420    COM /Inpt_sprd_title/ Title$(*)
6430    COM /Inpt_sprd_tog/ Toggle$(*)
6440    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
6450    COM /Inpt_sprd_prmpt/ Prompt$(*)
6460    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
6470    !
6480    DIM New_entry$[160],Module_label$[16],Tog_temp$[200],Box_temp$[100]
6490    !
6500    !Define softkeys.  Keys 1 to 4 are reserved for "hardkeys"
6510    ON KEY 5 LABEL FNUser_keylabel$("Reset") CALL User_key5isr
6520    ON KEY 6 LABEL FNUser_keylabel$("Autorange") CALL User_key6isr
6530    ON KEY 7 LABEL FNUser_keylabel$("Previous") CALL User_key7isr
6540    ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
6550    !
6560    CALL User_clr_scr
6570    !
6580    Changed=0
6590    !
6600    !Now call spread sheet.  It returns with New_entry$ and Row and Col
6610    Done=0
6620    REPEAT
6630      !
6640      CALL User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
6650      !
6660      IF Row=1 THEN 
6670        Module_label$="ALL INPUT"
6680      ELSE
6690        Module_label$=Box$(1,Row)
6700      END IF
6710      !
6720      SELECT FNUser_check_key
6730      CASE 0   !no key pressed, must be a New_entry$ for Box
6740        GOSUB Inpt_chk_change
6750        GOSUB Inpt_new_entry
6760      CASE 5
6770        GOSUB Inpt_chk_change
6780        Dummy=FNUser_get_key  !to clear the key
6790        DISP "Resetting Modules"
6800        Inpt_reset(Module_label$)
6810      CASE 6
6820        GOSUB Inpt_chk_change
6830        Dummy=FNUser_get_key
6840        DISP "Autoranging"
6850        Inpt_cmd(Module_label$,"CLEAR")
6860        Inpt_autorng(Module_label$)
6870        IF Row=1 THEN 
6880          Strt_r=2
6890          Stop_r=Max_row
6900        ELSE
6910          Strt_r=Row
6920          Stop_r=Row
6930        END IF
6940        Beeped=0
6950        FOR R=Strt_r TO Stop_r
6960          IF NOT Beeped THEN 
6970            IF POS(FNInpt_stat_2_str$(FNCnfg_rmst(Box$(1,R))),"ERR")<>0 THEN 
6980              BEEP 
6990              Beeped=1
7000            END IF
7010          END IF
7020        NEXT R
7030      CASE 7
7040        GOSUB Inpt_chk_change
7050        Dummy=FNUser_get_key
7060        Previous=1
7070        GOSUB Inpt_next_prev
7080      CASE 8
7090        Dummy=FNUser_get_key
7100        GOSUB Inpt_chk_change
7110        Previous=0
7120        GOSUB Inpt_next_prev
7130      CASE ELSE   !a softkey but not one of mine, so exit
7140        Done=1
7150      END SELECT
7160    UNTIL Done
7170    IF Changed THEN 
7180      Inpt_cmd("ALL INPUT","CLEAR")
7190    END IF
7200    CALL User_clr_scr
7210    SUBEXIT
7220    !
7230    !
7240 Inpt_chk_change:!
7250    IF NOT Changed THEN 
7260      Hw_dev_clear
7270      Inpt_cmd("ALL INPUT","STOP")
7280      Changed=1
7290    END IF
7300    RETURN 
7310    !
7320 Inpt_new_entry:!
7330   !acts on new_entry from spread_sheet
7340    IF TRIM$(New_entry$)<>"" THEN 
7350      Cnfg_cmd(Module_label$,"CLR")
7360      !  The following line changes the module and updates Box$
7370      Inpt_cmd(Module_label$,Cmnd_code$(Col),New_entry$)
7380      IF Row<>1 THEN 
7390        IF POS(FNInpt_stat_2_str$(FNCnfg_rmst(Module_label$)),"ERR")<>0 THEN 
7400          User_error("Value not understood")
7410        END IF
7420      ELSE
7430        IF Max_row>1 THEN 
7440          IF POS(FNInpt_stat_2_str$(FNCnfg_rmst(Box$(1,2))),"ERR")<>0 THEN 
7450            User_error("Value not understood")
7460          END IF
7470        END IF
7480      END IF
7490      DISP 
7500    END IF
7510    RETURN 
7520    !
7530 Inpt_next_prev:   !
7540    Tog_temp$=Toggle$(Col)
7550    IF Tog_temp$<>"" THEN 
7560      IF Row=1 THEN 
7570        IF Max_row=1 THEN RETURN 
7580        Strt_row=2
7590        Stop_row=Max_row
7600      ELSE
7610        Strt_row=Row
7620        Stop_row=Row
7630      END IF
7640      Box_temp$=Box$(Col,Strt_row)
7650      GOSUB Inpt_find_it
7660      FOR R=Strt_row TO Stop_row
7670        Inpt_cmd(Box$(1,R),Cmnd_code$(Col),Box_temp$)
7680      NEXT R
7690    END IF
7700    RETURN 
7710    !
7720    !  This finds the current parameter in the Tog_temp$ string
7730    !  and finds the previous/next parameter in that string.
7740 Inpt_find_it:       !
7750    IF Previous THEN 
7760      Tog_ptr=POS("|"&Tog_temp$&"|","|"&Box_temp$&"|")
7770      Stop_ptr=Tog_ptr-2
7780      IF Tog_ptr<2 THEN Stop_ptr=LEN(Tog_temp$)
7790      Tog_ptr=LEN(Tog_temp$)-Stop_ptr+1
7800      Tog_temp$=REV$(Tog_temp$)
7810      Strt_ptr=POS(Tog_temp$[Tog_ptr]&"|","|")
7820      IF Strt_ptr<>0 THEN 
7830        Strt_ptr=LEN(Tog_temp$)-Tog_ptr-Strt_ptr+3
7840      ELSE
7850        Strt_ptr=1
7860      END IF
7870      Tog_temp$=REV$(Tog_temp$)
7880    ELSE
7890      Tog_ptr=POS("|"&Tog_temp$&"|","|"&Box_temp$&"|")
7900      IF Tog_ptr=0 THEN Tog_ptr=1
7910      Strt_ptr=POS(Tog_temp$[Tog_ptr],"|")+Tog_ptr
7920      IF Strt_ptr<=Tog_ptr THEN Strt_ptr=1
7930      Stop_ptr=POS(Tog_temp$[Strt_ptr],"|")-2+Strt_ptr
7940      IF Stop_ptr<Strt_ptr THEN Stop_ptr=LEN(Tog_temp$)
7950    END IF
7960    Box_temp$=Tog_temp$[Strt_ptr,Stop_ptr]
7970    RETURN 
7980    !
7990  SUBEND
8000  !
8010  ! PAGE -> 
8020  !************************************************************************
8030 Inpt_get_all:SUB Inpt_get_all(Box$(*),Cmnd$,Col)
8040    !
8050    ! Fills column Col of Box$ with values read from the input modules.
8060    ! Cmnd_code$ is the command string corresponding to column Col.
8070    ! This string is sent out to all input modules.  Then each is
8080    ! read from and the value (converted to verbose form) is put in Box$.
8090    !
8100    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
8110    !
8120    Cmnd_num=FNInpt_get_code(Cmnd$)
8130    IF Cmnd$<>"DS_H" THEN 
8140      Cnfg_cmd("ALL INPUT",Cnv_mod_cmnd$(Cmnd_num)&"?")
8150    !
8160      FOR R=2 TO SIZE(Box$,2)
8170        Cnfg_wait_rdy(Box$(1,R))
8180        Box$(Col,R)=FNInpt_cnvt_in$(FNCnfg_rsp$(Box$(1,R)),Cmnd_num)
8190      NEXT R
8200    ELSE
8210      FOR R=2 TO SIZE(Box$,2)
8220        Box$(Col,R)=FNDisp_sc_sign$(R)
8230      NEXT R
8240    END IF
8250    SUBEXIT
8260  SUBEND
8270  ! PAGE -> 
8280  !************************************************************************
8290 Inpt_rsp:DEF FNInpt_rsp$(Module$,Cmnd$)
8300    !
8310    ! Function to query a module for what state it has been
8320    ! set to.  Command$ is the command to query.  The function returns
8330    ! a string from the module.  The Command$ can be typed out verbosely,
8340    ! and will be interpreted by the subprogram.  NOTE: This routine
8350    ! will not query the module if the value is already in the spreadsheet.
8360    ! The spreadsheet value can be different if an ICODE program sends
8370    ! commands to the module changing the setup, or if the CNFG file
8380    ! subprograms are used to change an input module's setup.
8390    !
8400    COM /Inpt_sprd_box/ Box$(*)
8410    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
8420    COM /Inpt_parm_cnv/ Convert_parm$(*)
8430    DIM Temp$[256],Actual_cmnd$[10]
8440    !
8450    Temp$=Cmnd$
8460    IF Temp$="" THEN RETURN ""
8470    IF Temp$="DS_H" THEN RETURN FNDisp_sc_sign$(FNInpt_get_row(Module$))
8480    !
8490    ! Strip off question mark if there - it'll be added back later.
8500    !
8510    IF (Temp$[LEN(Temp$)]="?") AND (LEN(Temp$)>1) THEN 
8520      Temp$=Temp$[1;LEN(Temp$)-1]
8530    END IF
8540    !
8550    Cmnd_code=FNInpt_get_code(Temp$)
8560    IF Cmnd_code=0 THEN 
8570      RETURN FNCnfg_cmd_rsp$(Module$,Temp$&"?")
8580    ELSE
8590      Actual_cmnd$=Cnv_mod_cmnd$(Cmnd_code)
8600      Col=FNInpt_get_col(Actual_cmnd$)
8610      IF Col<>0 THEN 
8620        Row=FNInpt_get_row(Module$)
8630        IF Row=1 THEN 
8640          User_stop("Bad global call to FNInpt_rsp$")
8650          RETURN ""
8660        ELSE
8670          RETURN Box$(Col,Row)
8680        END IF
8690      ELSE
8700        Temp$=FNCnfg_cmd_rsp$(Module$,Actual_cmnd$&"?")
8710        RETURN FNInpt_cnvt_in$(Temp$,Cmnd_code)
8720      END IF
8730    END IF
8740    !
8750  FNEND
8760  ! PAGE -> 
8770  !************************************************************************
8780 Inpt_cmd:SUB Inpt_cmd(Module$,Cmnd$,OPTIONAL Parm$)
8790    !
8800    ! Subprogram to send a command to a input module.
8810    ! Module$ is the name of the module to send to.  Cmnd$ is the
8820    ! command to send.  Parm_$, if specified, is the parameter to
8830    ! send with the command.  In general, Cmnd$ and Parm_$ can be
8840    ! written out as verbosely as you want, and this subprogram
8850    ! will do its best to interpret them.
8860    !
8870    COM /Inpt_sprd_box/ Box$(*)
8880    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
8890    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
8900    COM /Inpt_parm_cnv/ Convert_parm$(*)
8910    COM /Inpt_sprd_other/ Col_width(1:20),Max_col,Max_row,Modify_col
8920    DIM C_parm$[256],Temp_parm$[256],Temp$[100],Actual_cmnd$[10]
8930    !
8940    Cmnd_code=FNInpt_get_code(Cmnd$)
8950    C_parm$=""
8960    IF NPAR=3 THEN C_parm$=TRIM$(Parm$)
8970    !
8980    IF (Cmnd_code=0) THEN 
8990      Cnfg_cmd(Module$,Cmnd$&" "&C_parm$)
9000    ELSE
9010      IF C_parm$<>"" THEN 
9020        C=0
9030        Maxc=SIZE(Convert_parm$,2)-1
9040        C_parm$="|"&UPC$(Parm$)&"|"
9050        WHILE (C<Maxc) AND (POS("|"&Convert_parm$(Cmnd_code,C)&"|",C_parm$)=0)
9060          C=C+1
9070        END WHILE
9080        IF POS("|"&Convert_parm$(Cmnd_code,C)&"|",C_parm$)=0 THEN 
9090          Temp_parm$=Parm$
9100        ELSE
9110          Temp_parm$=VAL$(C)
9120        END IF
9130        !
9140      ELSE
9150        Temp_parm$=""
9160      END IF
9170      Row=FNInpt_get_row(Module$)
9180      Actual_cmnd$=Cnv_mod_cmnd$(Cmnd_code)
9190      IF Cmnd$<>"DS_H" THEN 
9200        Cnfg_cmd(Module$,Actual_cmnd$&" "&Temp_parm$)
9210      ELSE
9220        Disp_sc_sign(Temp_parm$,Row)
9230      END IF
9240      !
9250      ! The reset command ('RST') is sort of a special case.  After it
9260      ! is sent, the whole spreadsheet must be updated, not just one
9270      ! column.
9280      !
9290      IF Actual_cmnd$="RST" THEN 
9300        Inpt_get_spread(Module$)
9310      ELSE
9320        Col=FNInpt_get_col(Actual_cmnd$)
9330        IF Col<>0 THEN 
9340          IF Row=1 THEN 
9350            Inpt_get_all(Box$(*),Actual_cmnd$,Col)
9360          ELSE
9370            IF Cmnd$<>"DS_H" THEN 
9380              Temp$=FNCnfg_cmd_rsp$(Module$,Actual_cmnd$&"?")
9390              Box$(Col,Row)=FNInpt_cnvt_in$(Temp$,Cmnd_code)
9400            ELSE
9410              Box$(Col,Row)=FNDisp_sc_sign$(Row)
9420            END IF
9430          END IF
9440        END IF
9450      END IF
9460    END IF
9470    !
9480  SUBEND
9490  ! PAGE -> 
9500  !************************************************************************
9510 Inpt_get_code:DEF FNInpt_get_code(Cmnd$)
9520    !
9530    ! Converts Cmnd_code$, which is a verbose command string, into
9540    ! a number representing the position of that command in the
9550    ! array of possible commands.  This number can then be used to
9560    ! index into the array of actual commands to send to a module.
9570    !
9580    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
9590    DIM In_code$[256]
9600    !
9610    In_code$="|"&UPC$(TRIM$(Cmnd$))&"|"
9620    FOR Cmnd_code=1 TO SIZE(Cnv_cmnd_code$,1)
9630      IF POS("|"&Cnv_cmnd_code$(Cmnd_code)&"|",In_code$)<>0 THEN 
9640        RETURN Cmnd_code
9650      END IF
9660    NEXT Cmnd_code
9670    RETURN 0
9680  FNEND
9690  ! PAGE -> 
9700  !************************************************************************
9710 Inpt_cnvt_in:DEF FNInpt_cnvt_in$(Response$,Cmnd_code)
9720    !
9730    ! Response$ is a response from a input module.  Cmnd_code is the
9740    ! number corresponding to the command which generated the response.
9750    ! This function returns the verbose form of the response.
9760    !
9770    COM /Inpt_parm_cnv/ Convert_parm$(*)
9780    DIM Temp_r$[256]
9790    !
9800    IF Cmnd_code=0 THEN RETURN Response$
9810    IF Convert_parm$(Cmnd_code,1)="" THEN RETURN Response$
9820    !
9830    Response=VAL(Response$)
9840    Temp_r$=Convert_parm$(Cmnd_code,Response)
9850    End_pos=POS(Temp_r$,"|")-1
9860    IF End_pos>0 THEN Temp_r$=Temp_r$[1;End_pos]
9870    RETURN Temp_r$
9880  FNEND
9890  ! PAGE -> 
9900  !************************************************************************
9910 Inpt_autorng:SUB Inpt_autorng(Module_label$)
9920    !
9930    ! This routine autoranges the specified module(s), and updates the
9940    ! spreadsheet when the autorange is completed.
9950    !
9960    COM /Inpt_sprd_box/ Box$(*)
9970    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
9980    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
9990    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
10000   Col=FNInpt_get_col("RNG")
10010   Cnfg_cmd(Module_label$,"SARG")
10020   Hw_wait_gbl_rdy
10030   IF Col=0 THEN SUBEXIT
10040   Row=FNInpt_get_row(Module_label$)
10050   IF Row=1 THEN 
10060     Inpt_get_all(Box$(*),"RANGE",Col)
10070   ELSE
10080     Cmnd_num=FNInpt_get_code("RANGE")
10090     Box$(Col,Row)=FNInpt_cnvt_in$(FNCnfg_cmd_rsp$(Module_label$,Cnv_mod_cmnd$(Cmnd_num)&"?"),Cmnd_num)
10100   END IF
10110 SUBEND
10120 ! PAGE -> 
10130 !************************************************************************
10140 Inpt_reset:SUB Inpt_reset(Module_label$)
10150   !
10160   ! Subprogram to set the specified module(s) to a known
10170   ! state.  This subprogram only resets the parameters that
10180   ! are in the spreadsheet to known values.  It also clears
10190   ! shutdown if the module was shut down.  To reset ALL
10200   ! parameters of the module, use:
10210   !   Inpt_cmd(Module_label$,"RESET").
10220   !
10230   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
10240   COM /Inpt_sprd_tog/ Toggle$(*)
10250   COM /Inpt_sprd_reset/ Reset_parms$(*)
10260   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
10270   !
10280   FOR Col=2 TO Max_col
10290     IF Cmnd$(Col)<>"DS_H" THEN 
10300       Inpt_cmd(Module_label$,Cmnd_code$(Col),Reset_parms$(Col))
10310     ELSE
10320       Disp_sc_sign("0",0)  ! 0= ALL ROWS
10330     END IF
10340   NEXT Col
10350 SUBEND
10360 ! PAGE -> 
10370 !************************************************************************
10380 Inpt_get_row:DEF FNInpt_get_row(Module_label$)
10390   !
10400   ! Returns the row in Box$ that input label Module_label$ refers to.
10410   ! Since every label used should be somewhere in Box$, no error checking
10420   ! is done.  This will return 0 if Module_label$ isn't found.
10430   !
10440   COM /Inpt_sprd_box/ Box$(*)
10450   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
10460   DIM Temp_label$[16]
10470   Temp_label$=UPC$(TRIM$(Module_label$))
10480   FOR Row=1 TO Max_row
10490     IF TRIM$(UPC$(Box$(1,Row)))=Temp_label$ THEN RETURN Row
10500   NEXT Row
10510   RETURN 0
10520 FNEND
10530 ! PAGE -> 
10540 !************************************************************************
10550 Inpt_stat_2_str:DEF FNInpt_stat_2_str$(Stat)
10560   !
10570   ! This subprogram returns a string containing the
10580   ! mnemonics for each of the status bits set in the
10590   ! passed in status number.
10600   !
10610   DIM Ret_str$[100]
10620   !
10630   Ret_str$=""
10640   RESTORE Inpt_stat_data
10650   !
10660   FOR Bitnum=0 TO 14
10670     READ Bit_name$
10680     IF BIT(Stat,Bitnum) THEN Ret_str$=Ret_str$&Bit_name$&"|"
10690   NEXT Bitnum
10700   !
10710   IF Ret_str$="" THEN Ret_str$=Ret_str$&"|"
10720   RETURN TRIM$(Ret_str$[1,LEN(Ret_str$)-1])
10730   !
10740 Inpt_stat_data:  !
10750   DATA    "INTRG","BIT1","TRGRDY","ARMRDY"
10760   DATA    "RDY","ERR","BIT6","OVLD"
10770   DATA    "RQS","INTR","SHUT","BAV"
10780   DATA    "FSFAST","FIFOOVR","PON","???"
10790 FNEND
10800 ! PAGE -> 
10810 !************************************************************************
10820 Inpt_get_errstr:DEF FNInpt_get_errstr$(Error_num)
10830   !
10840   ! This subprogram returns a string containing the error
10850   ! message corresponding to the input error number
10860   ! that is passed to it.
10870   !
10880   DIM Msg$[100]
10890   INTEGER Current_err
10900   ON ERROR GOTO Not_found
10910   REPEAT
10920     READ Current_err,Msg$
10930   UNTIL Current_err=Error_num
10940   OFF ERROR 
10950   RETURN Msg$
10960   STOP
10970 Not_found:OFF ERROR 
10980   RETURN VAL$(Error_num)
10990   STOP
11000   DATA -100,"Illegal command"
11010   DATA -101,"Invalid parameter"
11020   DATA 111,"Start Must Be Received Before Marm"
11030   DATA 112,"Marm Not Valid In Auto Arm Mode"
11040   DATA 113,"Start Must Be Received Before Trg"
11050   DATA 131,"Invalid SET length"
11060   DATA 132,"Invalid SET id"
11070   DATA 133,"Invalid SET parameter or syntax"
11080   DATA 140,"Response buffer overflow"
11090   DATA 150,"Global CLAS or CLASM attempt to clear class"
11100   DATA 160,"Invalid parameter for TST command"
11110   DATA 161,"Invalid block length for TST command parm"
11120   DATA 301,"Invalid range for input mode"
11130   DATA 302,"Invalid coupling or input mode for OFS mode"
11140   DATA 303,"Autozero offset too big for range"
11150   DATA 304,"Illegal span/zoom combination"
11160   DATA 305,"Illegal number of words in zoom mode"
11170   DATA 310,"Can't autorange with current setup"
11180   DATA 320,"Bad INPM mode during test"
11190   DATA 330,"Pretrigger size > data record"
11200   DATA 331,"transfer size > data record"
11210   DATA 332,"overlap size >= data record"
11220   DATA 501,"Command buffer overflow"
11230   DATA 502,"Response buffer underflow"
11240   DATA 504,"Data Register Overread"
11250   DATA 510,"Bad global class from FB controller"
11260   DATA 601,"too much power in charge amp"
11270   DATA 602,"Processor went OTL, module restarted"
11280   DATA 610,"ROM test failures"
11290   DATA 620,"RAM fails self test"
11300   DATA 630,"read error in novram"
11310   DATA 640,"Internal Fs broke"
11320   DATA 651,"FB data reg. overflow"
11330   DATA 661,"Trigger PTA error"
11340   DATA 662,"System trigger error"
11350   DATA 663,"Can't load trigger levels"
11360   DATA 670,"LO GA out to lunch"
11370   DATA 671,"LO programming bad"
11380   DATA 672,"Local Oscillator sample rate too fast"
11390   DATA 680,"Digital Filter GA out to lunch"
11400   DATA 681,"DF programming bad, plug it in"
11410   DATA 682,"Digital Filter sample rate too fast"
11420   DATA 690,"FIFO GA out to lunch"
11430   DATA 691,"FIFO programming bad"
11440   DATA 692,"FIFO GA over write"
11450   DATA 693,"FIFO GA got a premature trigger"
11460   DATA 694,"FIFO GA didn't get emptied"
11470   DATA 695,"FIFO didn't get block available"
11480   DATA 700,"FE programming error"
11490   DATA 701,"dac railed during autozero"
11500   DATA 702,"overload during autozero"
11510   DATA 703,"can't autozero in specified number of passes"
11520 FNEND
11530 ! PAGE -> 
11540 !************************************************************************
11550 Inpt_save:SUB Inpt_save(@File,Ok)
11560   !
11570   ! This subprogram saves the current input setups (Box$) in
11580   ! the file specified by @File, and returns Ok=1 if
11590   ! it successfully saves the setups.
11600   !
11610   COM /Inpt_sprd_box/ Box$(*)
11620   !
11630   !
11640   File_format_rev=2620
11650   OUTPUT @File;File_format_rev
11660   !
11670   CALL File_save_s(@File,Box$(*))
11680   Ok=1
11690   !
11700 SUBEND
11710 ! PAGE -> 
11720 !************************************************************************
11730 Inpt_load:SUB Inpt_load(@File,Ok)
11740   !
11750   ! This subprogram loads the input setups from file
11760   ! @File, and returns Ok=1 if the load is successful.
11770   !
11780   COM /Inpt_sprd_box/ Box$(*)
11790   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
11800   COM /Inpt_sprd_other/ Col_width(1:20),Max_col,Max_row,Modify_col
11810   !
11820   !
11830   ENTER @File;File_format_rev
11840   SELECT File_format_rev
11850   CASE 2620
11860     CALL File_load_s(@File,Box$(*))
11870     !
11880     Inpt_cmd("ALL INPUT","CLR")
11890     !
11900     FOR Col=2 TO Max_col
11910       FOR Row=2 TO Max_row
11920         Inpt_cmd(Box$(1,Row),Cmnd_code$(Col),Box$(Col,Row))
11930       NEXT Row
11940     NEXT Col
11950     !
11960     Cnfg_cmd("ALL INPUT","ERR?")
11970     FOR Row=2 TO Max_row
11980       IF VAL(FNCnfg_rsp$(Box$(1,Row)))<>0 THEN 
11990         User_error("Unable to setup module "&Box$(1,Row)&" when recalling state.")
12000       END IF
12010     NEXT Row
12020   !
12030   CASE ELSE  !unknown rev
12040     CALL User_error("ERROR Incompatible display file format in Inpt_load.")
12050     Ok=0
12060     SUBEXIT
12070   END SELECT
12080   !
12090   Ok=1
12100   !
12110 SUBEND
12120 !************************************************************************
12130 Inpt_get_col:DEF FNInpt_get_col(Actual_cmnd$)
12140   !
12150   ! Returns the column number in Box$ corresponding to the input
12160   ! command Actual_cmnd$.  If no column in Box$ uses Actual_cmnd$,
12170   ! zero is returned.
12180   !
12190   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
12200   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
12210   !
12220   FOR Col=2 TO Max_col
12230     IF Cmnd_code$(Col)=Actual_cmnd$ THEN RETURN Col
12240   NEXT Col
12250   RETURN 0
12260 FNEND
12270 !************************************************************************
12280 Inpt_str_2_stat:DEF FNInpt_str_2_stat(A$)
12290   !
12300   ! This subroutine returns a number which represents the status
12310   ! of the Input module if the status bits indicated by A$ are set.
12320   ! Bit mnemonics may be separated by "," or "|".  This is the
12330   ! inverse of subprogram FNInpt_stat_2_str$(stat).
12340   !
12350   ALLOCATE Temp$[255],Bit$[40]
12360   Temp$=TRIM$(UPC$(A$))
12370   Stat=0
12380   WHILE POS(Temp$,",")
12390     Temp$[POS(Temp$,",");1]="|"
12400   END WHILE
12410   WHILE POS(Temp$,"|")
12420     Bit$=Temp$[1,POS(Temp$,"|")-1]
12430     GOSUB Add_bit_value
12440     Temp$=Temp$[POS(Temp$,"|")+1]
12450   END WHILE
12460   IF Temp$<>"" THEN 
12470     Bit$=Temp$
12480     GOSUB Add_bit_value
12490   END IF
12500   RETURN Stat
12510 Add_bit_value:!
12520   SELECT Bit$
12530   CASE "INTRG","INPUT TRIGGERED"
12540     Stat=Stat+1        !bit 0
12550   CASE "BIT1"
12560     Stat=Stat+2        !bit 1
12570   CASE "TRGRDY","READY FOR TRIG","READY FOR TRIGGER","RDY FOR TRG"
12580     Stat=Stat+4        !bit 2
12590   CASE "ARMRDY","READY FOR ARM","RDY FOR ARM"
12600     Stat=Stat+8        !bit 3
12610   CASE "RDY","READY"
12620     Stat=Stat+16       !bit 4
12630   CASE "ERR","ERROR"
12640     Stat=Stat+32       !bit 5
12650   CASE "BIT6"
12660     Stat=Stat+64       !bit 6
12670   CASE "OVLD","OVERLOAD"
12680     Stat=Stat+128      !bit 7
12690   CASE "RQS"
12700     Stat=Stat+256      !bit 8
12710   CASE "INTR"
12720     Stat=Stat+512      !bit 9
12730   CASE "SHT","SHUT","SHUTDOWN"
12740     Stat=Stat+1024     !bit 10
12750   CASE "BAV","BLOCK AVAILABLE"
12760     Stat=Stat+2048     !bit 11
12770   CASE "FSFAST"
12780     Stat=Stat+4096     !BIT 12
12790   CASE "FIFOOVR","FIFO OVERFLOW"
12800     Stat=Stat+8192     !bit 13
12810   CASE "PON","POWER ON"
12820     Stat=Stat+16384    !bit 14
12830   CASE ELSE
12840     User_error("*** Couldn't recognize "&Bit$&" in FNINPT_str_2_stat***")
12850   END SELECT
12860   RETURN 
12870 FNEND
12880 !
12890 !************************************************************************
12900 Inpt_get_spread:SUB Inpt_get_spread(OPTIONAL Pmodule$)
12910 !
12920 !  This routine querys all the active modules in the system
12930 !  for the needed parameters to fill in the spreadsheet.
12940 !
12950   COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
12960   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
12970   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
12980   DIM Temp$[10],Module$[16]
12990   Module$="ALL INPUT"
13000   IF NPAR>0 THEN Module$=Pmodule$
13010   Row=FNInpt_get_row(Module$)
13020   FOR Col=2 TO Max_col
13030     Cmnd_code=FNInpt_get_code(Cmnd_code$(Col))
13040     IF Row=1 THEN 
13050       Inpt_get_all(Box$(*),Cnv_mod_cmnd$(Cmnd_code),Col)
13060     ELSE
13070       Temp$=FNCnfg_cmd_rsp$(Module$,Cnv_mod_cmnd$(Cmnd_code)&"?")
13080       Box$(Col,Row)=FNInpt_cnvt_in$(Temp$,Cmnd_code)
13090     END IF
13100   NEXT Col
13110 SUBEND