10!  OUTPUT 2 USING "#,K";"<lf>REN<cr>INDENT<cr>RE-STORE ""INPT""<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  "MAXIMUM OVERLOADS"
4370    DATA    "NOVR",""
4380    DATA  "NO MORE"
4390    !
4400    !
4410  SUBEND
4420  ! PAGE -> 
4430  !************************************************************************
4440 Inpt_setup:SUB Inpt_setup(OPTIONAL Passed_setup$(*))
4450    !
4460    ! Inpt_setup is used to specify the columns that will show up in the
4470    ! input spreadsheet.  The Passed_setup$ parameter is an array of
4480    ! strings, each specifying one column of the spreadsheet.  If the
4490    ! parameter is not there, default columns are used.
4500    !
4510    COM /Inpt_sprd_posn/ Row,Col,Start_row
4520    COM /Inpt_sprd_box/ Box$(*)
4530    COM /Inpt_sprd_title/ Title$(*)
4540    COM /Inpt_sprd_tog/ Toggle$(*)
4550    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
4560    COM /Inpt_sprd_prmpt/ Prompt$(*)
4570    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
4580    COM /Inpt_sprd_reset/ Reset_parms$(*)
4590    !
4600    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
4610    COM /Inpt_parm_cnv/ Convert_parm$(*)
4620    !
4630    DIM Temp_code$[55],Dummy$[200]
4640    DIM Setup_array$(1:20)[20],Setup_name$[20]
4650    !
4660    RESTORE Inpt_def_setup
4670    READ Setup_size
4680    REDIM Setup_array$(1:Setup_size)
4690    READ Setup_array$(*)
4700    IF NPAR>0 THEN MAT Setup_array$= Passed_setup$
4710    Setup_size=SIZE(Setup_array$,1)
4720    !
4730    Max_col=Setup_size+1
4740    Max_row=63
4750    Modify_col=2
4760    !
4770    REDIM Title$(1:Max_col,0:2),Cmnd_code$(1:Max_col)
4780    REDIM Prompt$(1:Max_col),Col_width(1:Max_col)
4790    !
4800    Row=1
4810    Col=2
4820    Start_row=1
4830    !
4840    ! Setup the first column
4850    !
4860    Col_width(1)=16
4870    Title$(1,1)="Channel"
4880    Title$(1,2)="Name"
4890    Cmnd_code$(1)=""
4900    Prompt$(1)=""
4910    Title$(1,0)="Input Spreadsheet"
4920    !
4930    ! Read the column data into arrays
4940    !
4950    Total_width=Col_width(1)+2
4960    FOR C=2 TO Max_col
4970      RESTORE Inpt_data
4980      REPEAT
4990        READ Setup_name$
5000        IF UPC$(Setup_name$)="NO MORE" THEN 
5010          User_error("Illegal setup parm. to Inpt_inpt: "&Setup_array$(C-1))
5020        END IF
5030        This_is_it=(UPC$(Setup_name$)=UPC$(Setup_array$(C-1)))
5040        READ Toggle$(C),Reset_parms$(C),Col_width(C),Title$(C,1),Title$(C,2),Prompt$(C)
5050        Cmnd_code$(C)=Cnv_mod_cmnd$(FNInpt_get_code(Setup_name$))
5060        IF This_is_it THEN Total_width=Total_width+1+Col_width(C)
5070      UNTIL This_is_it
5080    NEXT C
5090    IF Total_width>FNLib_crt_width THEN 
5100      User_stop("Illegal Setup_array in Inpt_Inpt, too many chars: "&VAL$(Total_width))
5110    END IF
5120    C=1
5130    Loop_cnt=0
5140    WHILE (Total_width<FNLib_crt_width) AND (Loop_cnt<>2)
5150      Col_width(C)=Col_width(C)+1
5160      C=C+1
5170      IF C>Max_col THEN 
5180        C=1
5190        Loop_cnt=Loop_cnt+1
5200      END IF
5210      Total_width=Total_width+1
5220    END WHILE
5230    !
5240    !
5250    ! The data statements at the end of this subprogram define the
5260    ! possible columns for the input spreadsheet.  For each column, there
5270    ! is an associated input command, a list of the parameters to send to
5280    ! the module as the prev and next keys are used, a default (reset)
5290    ! value for the command, a column width, two column title strings, and
5300    ! a prompt string.  This data for each column is loaded into arrays for
5310    ! the spreadsheet to use.
5320    !
5330    !
5340    !   command code         toggle codes              reset parm
5350    !   ----------------     ------------------------  ----------
5360    !     col_width  title1         title2       Prompt
5370    !     ---------  ----------     ----------   --------------------
5380 Inpt_data:!
5390    DATA    "INPUT MODE",    "VOLT|ICP|CHRG",          "VOLT"
5400    DATA      4,     "Inpt ",       "Mode ",     "Input mode: Volt, ICP, or Chrg"
5410    DATA    "GROUNDING",     "GND|FLOAT",              "GND"
5420    DATA      6,     "Input",       "Gnding",    "Input grounding: Ground, or Float"
5430    DATA    "COUPLING",      "DC|AC",                  "DC"
5440    DATA      4,     "Cplg ",       "",          "Coupling: AC, DC"
5450    DATA    "RANGE",         "",                       "0"
5460    DATA      5,     "Range",       "(dB) ",     "Full scale Range in dBVp or dBpCp"
5470    DATA    "SPAN",          "",                       "51200"
5480    DATA      9,     "Span ",       "(Hz) ",     "Span frequency in Hz"
5490    DATA    "CENTER",        "",                       "25600"
5500    DATA      9,     "Center ",     "Freq (Hz)", "Center frequency in Hz"
5510    DATA    "BLOCKSIZE",     "",                       "1024"
5520    DATA      4,     "Blk",         "Size",      "Block size"
5530    DATA    "TRIG MODE",     "SEND|RCVE",              "RCVE"
5540    DATA      4,     "Trig ",       "Mode ",     "Trigger mode: Send, or Rcve"
5550    DATA    "TRIG SOURCE",   "FREE|LINP|MAN|IMM|SEND|RCVE", "RCVE"
5560    DATA      6,     "Trig ",       "Source ",   "Trigger source: Free, Linp, Man, Imm, Send, or Rcve"
5570    DATA    "TRIG TYPE",     "LVL|MAG",                "LVL"
5580    DATA      4,     "Trig ",       "Type ",     "Trigger type: LVL, MAG"
5590    DATA    "TRIG LEVEL",    "",                       "0"
5600    DATA      7,     "Trigger",     "Level",     "Trigger level in % of full scale"
5610    DATA    "UPPER LEVEL",   "",                       "50"
5620    DATA      7,     "Upper",       "Level",     "Upper/Slope trigger level in % of full scale"
5630    DATA    "LOWER LEVEL",   "",                       "-50"
5640    DATA      7,     "Lower",       "Level",     "Lower trigger level in % of full scale"
5650    DATA    "TRIG DELAY",    "",                       "0"
5660    DATA      7,     "Trig ",       "Delay",     "Trigger delay in filtered samples"
5670    DATA    "TRIG SLOPE",    "+|-",                    "+"
5680    DATA      5,     "Trig ",       "Slope",     "Trigger slope: + OR -"
5690    DATA    "NO MORE"
5700    !
5710    !
5720    ! The following defines the columns to be used in the input
5730    ! spreadsheet if no columns are specified.
5740    !
5750 Inpt_def_setup:   !
5760    DATA 9
5770    DATA "INPUT MODE","COUPLING","GROUNDING","RANGE","CENTER","TRIG MODE"
5780    DATA "TRIG LEVEL","TRIG DELAY","TRIG SLOPE"
5790    !
5800    !
5810  SUBEND
5820  ! PAGE -> 
5830  !************************************************************************
5840 Inpt_init:SUB Inpt_init(OPTIONAL Passed_setup$(*))
5850    !
5860    ! Should be called after any change in the inpt
5870    ! configuration or after the Inpt_inpt subprogram
5880    ! is called.  The optional parameter can be used to
5890    ! reinitialize the columns of the input spread sheet.
5900    ! Passed_setup$ contains a list of spread sheet columns
5910    ! to be displayed.  This subprogram also loads up Box$
5920    ! with correct values.
5930    !
5940    COM /Inpt_sprd_box/ Box$(*)
5950    COM /Inpt_sprd_title/ Title$(*)
5960    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
5970    COM /Inpt_sprd_prmpt/ Prompt$(*)
5980    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
5990    !
6000    IF NPAR>0 THEN 
6010      Inpt_setup(Passed_setup$(*))
6020    ELSE
6030      Inpt_setup
6040    END IF
6050    !
6060    ALLOCATE Inpt_labels$(1:63)[16]
6070    Cnfg_labels("ALL INPUT",Inpt_labels$(*),Num_inputs)
6080    !
6090    REDIM Box$(1:Max_col,1:(1+Num_inputs))
6100    Max_row=Num_inputs+1
6110    Box$(1,1)="All Input"
6120    FOR Col=2 TO SIZE(Box$,1)
6130      Box$(Col,1)=""
6140    NEXT Col
6150    !
6160    FOR Row=1 TO Num_inputs
6170      Box$(1,Row+1)=TRIM$(Inpt_labels$(Row))
6180    NEXT Row
6190    !
6200    DEALLOCATE Inpt_labels$(*)
6210    !
6220    Inpt_reset("ALL INPUT")
6230    !
6240  SUBEND
6250  ! PAGE -> 
6260  !************************************************************************
6270 Inpt_spread:SUB Inpt_spread(Changed)
6280    !
6290    ! Subprogram to display and allow modification of the
6300    ! input spreadsheet.  The Changed parameter returns true
6310    ! if any change has occurred to an input module.
6320    ! When the Inpt_spread subprogram is exited with Changed true,
6330    ! all errors are cleared on all the inputs.
6340    !
6350    COM /Inpt_sprd_posn/ Row,Col,Start_row
6360    COM /Inpt_sprd_box/ Box$(*)
6370    COM /Inpt_sprd_title/ Title$(*)
6380    COM /Inpt_sprd_tog/ Toggle$(*)
6390    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
6400    COM /Inpt_sprd_prmpt/ Prompt$(*)
6410    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
6420    !
6430    DIM New_entry$[160],Module_label$[16],Tog_temp$[200],Box_temp$[100]
6440    !
6450    !Define softkeys.  Keys 1 to 4 are reserved for "hardkeys"
6460    ON KEY 5 LABEL FNUser_keylabel$("Reset") CALL User_key5isr
6470    ON KEY 6 LABEL FNUser_keylabel$("Autorange") CALL User_key6isr
6480    ON KEY 7 LABEL FNUser_keylabel$("Previous") CALL User_key7isr
6490    ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
6500    !
6510    CALL User_clr_scr
6520    !
6530    Changed=0
6540    !
6550    !Now call spread sheet.  It returns with New_entry$ and Row and Col
6560    Done=0
6570    REPEAT
6580      !
6590      CALL User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
6600      !
6610      IF Row=1 THEN 
6620        Module_label$="ALL INPUT"
6630      ELSE
6640        Module_label$=Box$(1,Row)
6650      END IF
6660      !
6670      SELECT FNUser_check_key
6680      CASE 0   !no key pressed, must be a New_entry$ for Box
6690        GOSUB Inpt_chk_change
6700        GOSUB Inpt_new_entry
6710      CASE 5
6720        GOSUB Inpt_chk_change
6730        Dummy=FNUser_get_key  !to clear the key
6740        DISP "Resetting Modules"
6750        Inpt_reset(Module_label$)
6760      CASE 6
6770        GOSUB Inpt_chk_change
6780        Dummy=FNUser_get_key
6790        DISP "Autoranging"
6800        Inpt_cmd(Module_label$,"CLEAR")
6810        Inpt_autorng(Module_label$)
6820        IF Row=1 THEN 
6830          Strt_r=2
6840          Stop_r=Max_row
6850        ELSE
6860          Strt_r=Row
6870          Stop_r=Row
6880        END IF
6890        Beeped=0
6900        FOR R=Strt_r TO Stop_r
6910          IF NOT Beeped THEN 
6920            IF POS(FNInpt_stat_2_str$(FNCnfg_rmst(Box$(1,R))),"ERR")<>0 THEN 
6930              BEEP 
6940              Beeped=1
6950            END IF
6960          END IF
6970        NEXT R
6980      CASE 7
6990        GOSUB Inpt_chk_change
7000        Dummy=FNUser_get_key
7010        Previous=1
7020        GOSUB Inpt_next_prev
7030      CASE 8
7040        Dummy=FNUser_get_key
7050        GOSUB Inpt_chk_change
7060        Previous=0
7070        GOSUB Inpt_next_prev
7080      CASE ELSE   !a softkey but not one of mine, so exit
7090        Done=1
7100      END SELECT
7110    UNTIL Done
7120    IF Changed THEN 
7130      Inpt_cmd("ALL INPUT","CLEAR")
7140    END IF
7150    CALL User_clr_scr
7160    SUBEXIT
7170    !
7180    !
7190 Inpt_chk_change:!
7200    IF NOT Changed THEN 
7210      Hw_dev_clear
7220      Inpt_cmd("ALL INPUT","STOP")
7230      Changed=1
7240    END IF
7250    RETURN 
7260    !
7270 Inpt_new_entry:!
7280   !acts on new_entry from spread_sheet
7290    IF TRIM$(New_entry$)<>"" THEN 
7300      Cnfg_cmd(Module_label$,"CLR")
7310      !  The following line changes the module and updates Box$
7320      Inpt_cmd(Module_label$,Cmnd_code$(Col),New_entry$)
7330      IF Row<>1 THEN 
7340        IF POS(FNInpt_stat_2_str$(FNCnfg_rmst(Module_label$)),"ERR")<>0 THEN 
7350          User_error("Value not understood")
7360        END IF
7370      ELSE
7380        IF Max_row>1 THEN 
7390          IF POS(FNInpt_stat_2_str$(FNCnfg_rmst(Box$(1,2))),"ERR")<>0 THEN 
7400            User_error("Value not understood")
7410          END IF
7420        END IF
7430      END IF
7440      DISP 
7450    END IF
7460    RETURN 
7470    !
7480 Inpt_next_prev:   !
7490    Tog_temp$=Toggle$(Col)
7500    IF Tog_temp$<>"" THEN 
7510      IF Row=1 THEN 
7520        IF Max_row=1 THEN RETURN 
7530        Strt_row=2
7540        Stop_row=Max_row
7550      ELSE
7560        Strt_row=Row
7570        Stop_row=Row
7580      END IF
7590      Box_temp$=Box$(Col,Strt_row)
7600      GOSUB Inpt_find_it
7610      FOR R=Strt_row TO Stop_row
7620        Inpt_cmd(Box$(1,R),Cmnd_code$(Col),Box_temp$)
7630      NEXT R
7640    END IF
7650    RETURN 
7660    !
7670    !  This finds the current parameter in the Tog_temp$ string
7680    !  and finds the previous/next parameter in that string.
7690 Inpt_find_it:       !
7700    IF Previous THEN 
7710      Tog_ptr=POS("|"&Tog_temp$&"|","|"&Box_temp$&"|")
7720      Stop_ptr=Tog_ptr-2
7730      IF Tog_ptr<2 THEN Stop_ptr=LEN(Tog_temp$)
7740      Tog_ptr=LEN(Tog_temp$)-Stop_ptr+1
7750      Tog_temp$=REV$(Tog_temp$)
7760      Strt_ptr=POS(Tog_temp$[Tog_ptr]&"|","|")
7770      IF Strt_ptr<>0 THEN 
7780        Strt_ptr=LEN(Tog_temp$)-Tog_ptr-Strt_ptr+3
7790      ELSE
7800        Strt_ptr=1
7810      END IF
7820      Tog_temp$=REV$(Tog_temp$)
7830    ELSE
7840      Tog_ptr=POS("|"&Tog_temp$&"|","|"&Box_temp$&"|")
7850      IF Tog_ptr=0 THEN Tog_ptr=1
7860      Strt_ptr=POS(Tog_temp$[Tog_ptr],"|")+Tog_ptr
7870      IF Strt_ptr<=Tog_ptr THEN Strt_ptr=1
7880      Stop_ptr=POS(Tog_temp$[Strt_ptr],"|")-2+Strt_ptr
7890      IF Stop_ptr<Strt_ptr THEN Stop_ptr=LEN(Tog_temp$)
7900    END IF
7910    Box_temp$=Tog_temp$[Strt_ptr,Stop_ptr]
7920    RETURN 
7930    !
7940  SUBEND
7950  !
7960  ! PAGE -> 
7970  !************************************************************************
7980 Inpt_get_all:SUB Inpt_get_all(Box$(*),Cmnd$,Col)
7990    !
8000    ! Fills column Col of Box$ with values read from the input modules.
8010    ! Cmnd_code$ is the command string corresponding to column Col.
8020    ! This string is sent out to all input modules.  Then each is
8030    ! read from and the value (converted to verbose form) is put in Box$.
8040    !
8050    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
8060    !
8070    Cmnd_num=FNInpt_get_code(Cmnd$)
8080    Cnfg_cmd("ALL INPUT",Cnv_mod_cmnd$(Cmnd_num)&"?")
8090    !
8100    FOR R=2 TO SIZE(Box$,2)
8110      Cnfg_wait_rdy(Box$(1,R))
8120      Box$(Col,R)=FNInpt_cnvt_in$(FNCnfg_rsp$(Box$(1,R)),Cmnd_num)
8130    NEXT R
8140    SUBEXIT
8150  SUBEND
8160  ! PAGE -> 
8170  !************************************************************************
8180 Inpt_rsp:DEF FNInpt_rsp$(Module$,Cmnd$)
8190    !
8200    ! Function to query a module for what state it has been
8210    ! set to.  Command$ is the command to query.  The function returns
8220    ! a string from the module.  The Command$ can be typed out verbosely,
8230    ! and will be interpreted by the subprogram.  NOTE: This routine
8240    ! will not query the module if the value is already in the spreadsheet.
8250    ! The spreadsheet value can be different if an ICODE program sends
8260    ! commands to the module changing the setup, or if the CNFG file
8270    ! subprograms are used to change an input module's setup.
8280    !
8290    COM /Inpt_sprd_box/ Box$(*)
8300    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
8310    COM /Inpt_parm_cnv/ Convert_parm$(*)
8320    DIM Temp$[256],Actual_cmnd$[10]
8330    !
8340    Temp$=Cmnd$
8350    IF Temp$="" THEN RETURN ""
8360    !
8370    ! Strip off question mark if there - it'll be added back later.
8380    !
8390    IF (Temp$[LEN(Temp$)]="?") AND (LEN(Temp$)>1) THEN 
8400      Temp$=Temp$[1;LEN(Temp$)-1]
8410    END IF
8420    !
8430    Cmnd_code=FNInpt_get_code(Temp$)
8440    IF Cmnd_code=0 THEN 
8450      RETURN FNCnfg_cmd_rsp$(Module$,Temp$&"?")
8460    ELSE
8470      Actual_cmnd$=Cnv_mod_cmnd$(Cmnd_code)
8480      Col=FNInpt_get_col(Actual_cmnd$)
8490      IF Col<>0 THEN 
8500        Row=FNInpt_get_row(Module$)
8510        IF Row=1 THEN 
8520          User_stop("Bad global call to FNInpt_rsp$")
8530          RETURN ""
8540        ELSE
8550          RETURN Box$(Col,Row)
8560        END IF
8570      ELSE
8580        Temp$=FNCnfg_cmd_rsp$(Module$,Actual_cmnd$&"?")
8590        RETURN FNInpt_cnvt_in$(Temp$,Cmnd_code)
8600      END IF
8610    END IF
8620    !
8630  FNEND
8640  ! PAGE -> 
8650  !************************************************************************
8660 Inpt_cmd:SUB Inpt_cmd(Module$,Cmnd$,OPTIONAL Parm$)
8670    !
8680    ! Subprogram to send a command to a input module.
8690    ! Module$ is the name of the module to send to.  Cmnd$ is the
8700    ! command to send.  Parm_$, if specified, is the parameter to
8710    ! send with the command.  In general, Cmnd$ and Parm_$ can be
8720    ! written out as verbosely as you want, and this subprogram
8730    ! will do its best to interpret them.
8740    !
8750    COM /Inpt_sprd_box/ Box$(*)
8760    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
8770    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
8780    COM /Inpt_parm_cnv/ Convert_parm$(*)
8790    COM /Inpt_sprd_other/ Col_width(1:20),Max_col,Max_row,Modify_col
8800    DIM C_parm$[256],Temp_parm$[256],Temp$[100],Actual_cmnd$[10]
8810    !
8820    Cmnd_code=FNInpt_get_code(Cmnd$)
8830    C_parm$=""
8840    IF NPAR=3 THEN C_parm$=TRIM$(Parm$)
8850    !
8860    IF (Cmnd_code=0) THEN 
8870      Cnfg_cmd(Module$,Cmnd$&" "&C_parm$)
8880    ELSE
8890      IF C_parm$<>"" THEN 
8900        C=0
8910        Maxc=SIZE(Convert_parm$,2)-1
8920        C_parm$="|"&UPC$(Parm$)&"|"
8930        WHILE (C<Maxc) AND (POS("|"&Convert_parm$(Cmnd_code,C)&"|",C_parm$)=0)
8940          C=C+1
8950        END WHILE
8960        IF POS("|"&Convert_parm$(Cmnd_code,C)&"|",C_parm$)=0 THEN 
8970          Temp_parm$=Parm$
8980        ELSE
8990          Temp_parm$=VAL$(C)
9000        END IF
9010        !
9020      ELSE
9030        Temp_parm$=""
9040      END IF
9050      Actual_cmnd$=Cnv_mod_cmnd$(Cmnd_code)
9060      Cnfg_cmd(Module$,Actual_cmnd$&" "&Temp_parm$)
9070      Row=FNInpt_get_row(Module$)
9080      !
9090      ! The reset command ('RST') is sort of a special case.  After it
9100      ! is sent, the whole spreadsheet must be updated, not just one
9110      ! column.
9120      !
9130      IF Actual_cmnd$="RST" THEN 
9140        Inpt_get_spread(Module$)
9150      ELSE
9160        Col=FNInpt_get_col(Actual_cmnd$)
9170        IF Col<>0 THEN 
9180          IF Row=1 THEN 
9190            Inpt_get_all(Box$(*),Actual_cmnd$,Col)
9200          ELSE
9210            Temp$=FNCnfg_cmd_rsp$(Module$,Actual_cmnd$&"?")
9220            Box$(Col,Row)=FNInpt_cnvt_in$(Temp$,Cmnd_code)
9230          END IF
9240        END IF
9250      END IF
9260    END IF
9270    !
9280  SUBEND
9290  ! PAGE -> 
9300  !************************************************************************
9310 Inpt_get_code:DEF FNInpt_get_code(Cmnd$)
9320    !
9330    ! Converts Cmnd_code$, which is a verbose command string, into
9340    ! a number representing the position of that command in the
9350    ! array of possible commands.  This number can then be used to
9360    ! index into the array of actual commands to send to a module.
9370    !
9380    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
9390    DIM In_code$[256]
9400    !
9410    In_code$="|"&UPC$(TRIM$(Cmnd$))&"|"
9420    FOR Cmnd_code=1 TO SIZE(Cnv_cmnd_code$,1)
9430      IF POS("|"&Cnv_cmnd_code$(Cmnd_code)&"|",In_code$)<>0 THEN 
9440        RETURN Cmnd_code
9450      END IF
9460    NEXT Cmnd_code
9470    RETURN 0
9480  FNEND
9490  ! PAGE -> 
9500  !************************************************************************
9510 Inpt_cnvt_in:DEF FNInpt_cnvt_in$(Response$,Cmnd_code)
9520    !
9530    ! Response$ is a response from a input module.  Cmnd_code is the
9540    ! number corresponding to the command which generated the response.
9550    ! This function returns the verbose form of the response.
9560    !
9570    COM /Inpt_parm_cnv/ Convert_parm$(*)
9580    DIM Temp_r$[256]
9590    !
9600    IF Cmnd_code=0 THEN RETURN Response$
9610    IF Convert_parm$(Cmnd_code,1)="" THEN RETURN Response$
9620    !
9630    Response=VAL(Response$)
9640    Temp_r$=Convert_parm$(Cmnd_code,Response)
9650    End_pos=POS(Temp_r$,"|")-1
9660    IF End_pos>0 THEN Temp_r$=Temp_r$[1;End_pos]
9670    RETURN Temp_r$
9680  FNEND
9690  ! PAGE -> 
9700  !************************************************************************
9710 Inpt_autorng:SUB Inpt_autorng(Module_label$)
9720    !
9730    ! This routine autoranges the specified module(s), and updates the
9740    ! spreadsheet when the autorange is completed.
9750    !
9760    COM /Inpt_sprd_box/ Box$(*)
9770    COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
9780    COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
9790    COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
9800    Col=FNInpt_get_col("RNG")
9810    Cnfg_cmd(Module_label$,"SARG")
9820    Hw_wait_gbl_rdy
9830    IF Col=0 THEN SUBEXIT
9840    Row=FNInpt_get_row(Module_label$)
9850    IF Row=1 THEN 
9860      Inpt_get_all(Box$(*),"RANGE",Col)
9870    ELSE
9880      Cmnd_num=FNInpt_get_code("RANGE")
9890      Box$(Col,Row)=FNInpt_cnvt_in$(FNCnfg_cmd_rsp$(Module_label$,Cnv_mod_cmnd$(Cmnd_num)&"?"),Cmnd_num)
9900    END IF
9910  SUBEND
9920  ! PAGE -> 
9930  !************************************************************************
9940 Inpt_reset:SUB Inpt_reset(Module_label$)
9950    !
9960    ! Subprogram to set the specified module(s) to a known
9970    ! state.  This subprogram only resets the parameters that
9980    ! are in the spreadsheet to known values.  It also clears
9990    ! shutdown if the module was shut down.  To reset ALL
10000   ! parameters of the module, use:
10010   !   Inpt_cmd(Module_label$,"RESET").
10020   !
10030   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
10040   COM /Inpt_sprd_tog/ Toggle$(*)
10050   COM /Inpt_sprd_reset/ Reset_parms$(*)
10060   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
10070   !
10080   FOR Col=2 TO Max_col
10090     Inpt_cmd(Module_label$,Cmnd_code$(Col),Reset_parms$(Col))
10100   NEXT Col
10110 SUBEND
10120 ! PAGE -> 
10130 !************************************************************************
10140 Inpt_get_row:DEF FNInpt_get_row(Module_label$)
10150   !
10160   ! Returns the row in Box$ that input label Module_label$ refers to.
10170   ! Since every label used should be somewhere in Box$, no error checking
10180   ! is done.  This will return 0 if Module_label$ isn't found.
10190   !
10200   COM /Inpt_sprd_box/ Box$(*)
10210   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
10220   DIM Temp_label$[16]
10230   Temp_label$=UPC$(TRIM$(Module_label$))
10240   FOR Row=1 TO Max_row
10250     IF TRIM$(UPC$(Box$(1,Row)))=Temp_label$ THEN RETURN Row
10260   NEXT Row
10270   RETURN 0
10280 FNEND
10290 ! PAGE -> 
10300 !************************************************************************
10310 Inpt_stat_2_str:DEF FNInpt_stat_2_str$(Stat)
10320   !
10330   ! This subprogram returns a string containing the
10340   ! mnemonics for each of the status bits set in the
10350   ! passed in status number.
10360   !
10370   DIM Ret_str$[100]
10380   !
10390   Ret_str$=""
10400   RESTORE Inpt_stat_data
10410   !
10420   FOR Bitnum=0 TO 14
10430     READ Bit_name$
10440     IF BIT(Stat,Bitnum) THEN Ret_str$=Ret_str$&Bit_name$&"|"
10450   NEXT Bitnum
10460   !
10470   IF Ret_str$="" THEN Ret_str$=Ret_str$&"|"
10480   RETURN TRIM$(Ret_str$[1,LEN(Ret_str$)-1])
10490   !
10500 Inpt_stat_data:  !
10510   DATA    "INTRG","BIT1","TRGRDY","ARMRDY"
10520   DATA    "RDY","ERR","BIT6","OVLD"
10530   DATA    "RQS","INTR","SHUT","BAV"
10540   DATA    "FSFAST","FIFOOVR","PON","???"
10550 FNEND
10560 ! PAGE -> 
10570 !************************************************************************
10580 Inpt_get_errstr:DEF FNInpt_get_errstr$(Error_num)
10590   !
10600   ! This subprogram returns a string containing the error
10610   ! message corresponding to the input error number
10620   ! that is passed to it.
10630   !
10640   DIM Msg$[100]
10650   INTEGER Current_err
10660   ON ERROR GOTO Not_found
10670   REPEAT
10680     READ Current_err,Msg$
10690   UNTIL Current_err=Error_num
10700   OFF ERROR 
10710   RETURN Msg$
10720   STOP
10730 Not_found:OFF ERROR 
10740   RETURN VAL$(Error_num)
10750   STOP
10760   DATA -100,"Illegal command"
10770   DATA -101,"Invalid parameter"
10780   DATA 111,"Start Must Be Received Before Marm"
10790   DATA 112,"Marm Not Valid In Auto Arm Mode"
10800   DATA 113,"Start Must Be Received Before Trg"
10810   DATA 131,"Invalid SET length"
10820   DATA 132,"Invalid SET id"
10830   DATA 133,"Invalid SET parameter or syntax"
10840   DATA 140,"Response buffer overflow"
10850   DATA 150,"Global CLAS or CLASM attempt to clear class"
10860   DATA 160,"Invalid parameter for TST command"
10870   DATA 161,"Invalid block length for TST command parm"
10880   DATA 301,"Invalid range for input mode"
10890   DATA 302,"Invalid coupling or input mode for OFS mode"
10900   DATA 303,"Autozero offset too big for range"
10910   DATA 304,"Illegal span/zoom combination"
10920   DATA 305,"Illegal number of words in zoom mode"
10930   DATA 310,"Can't autorange with current setup"
10940   DATA 320,"Bad INPM mode during test"
10950   DATA 330,"Pretrigger size > data record"
10960   DATA 331,"transfer size > data record"
10970   DATA 332,"overlap size >= data record"
10980   DATA 501,"Command buffer overflow"
10990   DATA 502,"Response buffer underflow"
11000   DATA 504,"Data Register Overread"
11010   DATA 510,"Bad global class from FB controller"
11020   DATA 601,"too much power in charge amp"
11030   DATA 602,"Processor went OTL, module restarted"
11040   DATA 610,"ROM test failures"
11050   DATA 620,"RAM fails self test"
11060   DATA 630,"read error in novram"
11070   DATA 640,"Internal Fs broke"
11080   DATA 651,"FB data reg. overflow"
11090   DATA 661,"Trigger PTA error"
11100   DATA 662,"System trigger error"
11110   DATA 663,"Can't load trigger levels"
11120   DATA 670,"LO GA out to lunch"
11130   DATA 671,"LO programming bad"
11140   DATA 672,"Local Oscillator sample rate too fast"
11150   DATA 680,"Digital Filter GA out to lunch"
11160   DATA 681,"DF programming bad, plug it in"
11170   DATA 682,"Digital Filter sample rate too fast"
11180   DATA 690,"FIFO GA out to lunch"
11190   DATA 691,"FIFO programming bad"
11200   DATA 692,"FIFO GA over write"
11210   DATA 693,"FIFO GA got a premature trigger"
11220   DATA 694,"FIFO GA didn't get emptied"
11230   DATA 695,"FIFO didn't get block available"
11240   DATA 700,"FE programming error"
11250   DATA 701,"dac railed during autozero"
11260   DATA 702,"overload during autozero"
11270   DATA 703,"can't autozero in specified number of passes"
11280 FNEND
11290 ! PAGE -> 
11300 !************************************************************************
11310 Inpt_save:SUB Inpt_save(@File,Ok)
11320   !
11330   ! This subprogram saves the current input setups (Box$) in
11340   ! the file specified by @File, and returns Ok=1 if
11350   ! it successfully saves the setups.
11360   !
11370   COM /Inpt_sprd_box/ Box$(*)
11380   !
11390   !
11400   File_format_rev=2620
11410   OUTPUT @File;File_format_rev
11420   !
11430   CALL File_save_s(@File,Box$(*))
11440   Ok=1
11450   !
11460 SUBEND
11470 ! PAGE -> 
11480 !************************************************************************
11490 Inpt_load:SUB Inpt_load(@File,Ok)
11500   !
11510   ! This subprogram loads the input setups from file
11520   ! @File, and returns Ok=1 if the load is successful.
11530   !
11540   COM /Inpt_sprd_box/ Box$(*)
11550   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
11560   COM /Inpt_sprd_other/ Col_width(1:20),Max_col,Max_row,Modify_col
11570   !
11580   !
11590   ENTER @File;File_format_rev
11600   SELECT File_format_rev
11610   CASE 2620
11620     CALL File_load_s(@File,Box$(*))
11630     !
11640     Inpt_cmd("ALL INPUT","CLR")
11650     !
11660     FOR Col=2 TO Max_col
11670       FOR Row=2 TO Max_row
11680         Inpt_cmd(Box$(1,Row),Cmnd_code$(Col),Box$(Col,Row))
11690       NEXT Row
11700     NEXT Col
11710     !
11720     Cnfg_cmd("ALL INPUT","ERR?")
11730     FOR Row=2 TO Max_row
11740       IF VAL(FNCnfg_rsp$(Box$(1,Row)))<>0 THEN 
11750         User_error("Unable to setup module "&Box$(1,Row)&" when recalling state.")
11760       END IF
11770     NEXT Row
11780   !
11790   CASE ELSE  !unknown rev
11800     CALL User_error("ERROR Incompatible display file format in Inpt_load.")
11810     Ok=0
11820     SUBEXIT
11830   END SELECT
11840   !
11850   Ok=1
11860   !
11870 SUBEND
11880 !************************************************************************
11890 Inpt_get_col:DEF FNInpt_get_col(Actual_cmnd$)
11900   !
11910   ! Returns the column number in Box$ corresponding to the input
11920   ! command Actual_cmnd$.  If no column in Box$ uses Actual_cmnd$,
11930   ! zero is returned.
11940   !
11950   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
11960   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
11970   !
11980   FOR Col=2 TO Max_col
11990     IF Cmnd_code$(Col)=Actual_cmnd$ THEN RETURN Col
12000   NEXT Col
12010   RETURN 0
12020 FNEND
12030 !************************************************************************
12040 Inpt_str_2_stat:DEF FNInpt_str_2_stat(A$)
12050   !
12060   ! This subroutine returns a number which represents the status
12070   ! of the Input module if the status bits indicated by A$ are set.
12080   ! Bit mnemonics may be separated by "," or "|".  This is the
12090   ! inverse of subprogram FNInpt_stat_2_str$(stat).
12100   !
12110   ALLOCATE Temp$[255],Bit$[40]
12120   Temp$=TRIM$(UPC$(A$))
12130   Stat=0
12140   WHILE POS(Temp$,",")
12150     Temp$[POS(Temp$,",");1]="|"
12160   END WHILE
12170   WHILE POS(Temp$,"|")
12180     Bit$=Temp$[1,POS(Temp$,"|")-1]
12190     GOSUB Add_bit_value
12200     Temp$=Temp$[POS(Temp$,"|")+1]
12210   END WHILE
12220   IF Temp$<>"" THEN 
12230     Bit$=Temp$
12240     GOSUB Add_bit_value
12250   END IF
12260   RETURN Stat
12270 Add_bit_value:!
12280   SELECT Bit$
12290   CASE "INTRG","INPUT TRIGGERED"
12300     Stat=Stat+1        !bit 0
12310   CASE "BIT1"
12320     Stat=Stat+2        !bit 1
12330   CASE "TRGRDY","READY FOR TRIG","READY FOR TRIGGER","RDY FOR TRG"
12340     Stat=Stat+4        !bit 2
12350   CASE "ARMRDY","READY FOR ARM","RDY FOR ARM"
12360     Stat=Stat+8        !bit 3
12370   CASE "RDY","READY"
12380     Stat=Stat+16       !bit 4
12390   CASE "ERR","ERROR"
12400     Stat=Stat+32       !bit 5
12410   CASE "BIT6"
12420     Stat=Stat+64       !bit 6
12430   CASE "OVLD","OVERLOAD"
12440     Stat=Stat+128      !bit 7
12450   CASE "RQS"
12460     Stat=Stat+256      !bit 8
12470   CASE "INTR"
12480     Stat=Stat+512      !bit 9
12490   CASE "SHT","SHUT","SHUTDOWN"
12500     Stat=Stat+1024     !bit 10
12510   CASE "BAV","BLOCK AVAILABLE"
12520     Stat=Stat+2048     !bit 11
12530   CASE "FSFAST"
12540     Stat=Stat+4096     !BIT 12
12550   CASE "FIFOOVR","FIFO OVERFLOW"
12560     Stat=Stat+8192     !bit 13
12570   CASE "PON","POWER ON"
12580     Stat=Stat+16384    !bit 14
12590   CASE ELSE
12600     User_error("*** Couldn't recognize "&Bit$&" in FNINPT_str_2_stat***")
12610   END SELECT
12620   RETURN 
12630 FNEND
12640 !
12650 !************************************************************************
12660 Inpt_get_spread:SUB Inpt_get_spread(OPTIONAL Pmodule$)
12670 !
12680 !  This routine querys all the active modules in the system
12690 !  for the needed parameters to fill in the spreadsheet.
12700 !
12710   COM /Inpt_cmnd_cnv/ Cnv_cmnd_code$(*),Cnv_mod_cmnd$(*)
12720   COM /Inpt_sprd_cmnd/ Cmnd_code$(*)
12730   COM /Inpt_sprd_other/ Col_width(*),Max_col,Max_row,Modify_col
12740   DIM Temp$[10],Module$[16]
12750   Module$="ALL INPUT"
12760   IF NPAR>0 THEN Module$=Pmodule$
12770   Row=FNInpt_get_row(Module$)
12780   FOR Col=2 TO Max_col
12790     Cmnd_code=FNInpt_get_code(Cmnd_code$(Col))
12800     IF Row=1 THEN 
12810       Inpt_get_all(Box$(*),Cnv_mod_cmnd$(Cmnd_code),Col)
12820     ELSE
12830       Temp$=FNCnfg_cmd_rsp$(Module$,Cnv_mod_cmnd$(Cmnd_code)&"?")
12840       Box$(Col,Row)=FNInpt_cnvt_in$(Temp$,Cmnd_code)
12850     END IF
12860   NEXT Col
12870 SUBEND