2  !   OUTPUT 2 USING "#,K";"<lf>INDENT<cr><lf>RE-STORE ""FRF""<cr>"
4     !
6     END
8     !
10    ! PAGE -> 
12    !***********************************************************************
14 Appl_appl:SUB Appl_appl
16    !
18    !**********************************************************************
20    !
22    !
24    !                        FRF file
26    !
28    ! This is the FRF application file.  It can make frequency response
30    ! measurements using the HP3565S system.  It can make your life better,
32    ! and more meaningful.  Trust it.  The FRF application uses most of the
34    ! support files (such as the CNFG and INPT files) plus the FRF_MEAS
36    ! file.  There is an ICODE program that is used to do much of the
38    ! computation for the FRF application.  The source for this ICODE program
40    ! is included here (in subprogram Appl_icode_src); this source is
42    ! assembled the first time the FRF application is initialized.
44    !
46    ! Appl_appl should be called once after the application is loaded, to
48    ! initialize some constants.  It also contains all the common
50    ! declarations used by this file.
52    !
54      COM /Appl_ref_input/ INTEGER Current_inpt
56      COM /Appl_buf_info/ Disp_choices$(1:4,1:63)[30]
58      COM /Appl_convert/ Inputs$(1:63)[20],INTEGER Num_inputs
60      COM /Appl_data/ Data_buffer(1:16,0:2047),Data_header(1:16,1:10)
62      COM /Appl_block_id1/ Icode_id,Input_buff_id,Module_list_id
64      COM /Appl_block_id2/ Output_buff_id,Sp_coef_id,Sp_param_id
66      COM /Appl_disp_info/ Inpm$(1:63)[4],INTEGER Range(1:63)
68      COM /Appl_data_ptr/ INTEGER Block_num,First_third,Second_third
70      COM /Appl_mydata/ Tdata(1:46,0:400),Pdata(1:24,0:400),Cdata(1:23,0:400)
72      COM /Appl_no_data/ INTEGER No_data
74      COM /Appl_num/ Corr_fact,Hann_fact,Flat_top_fact,Half_lsb,Tpi,Pidiv2
76      COM /Appl_trig/ INTEGER Awaiting_trig,Message_disp
78      COM /Appl_time/ Start_time
80      COM /Appl_datasize/ INTEGER Datasize,Fftsize
82      COM /Appl_av_count/ INTEGER Av_count,Numav,Trig_count
84      COM /Appl_ovld/ INTEGER Ovld_array(1:63),Current_ovld(1:63)
86      COM /Appl_av_type/ INTEGER Each_av
88      COM /Appl_object/ Info$(0:150)[40],INTEGER Assembled,Object(0:1023)
90      !
92      ! Current_inpt is the reference input number.
94      ! Disp_choices$ is an array of the possible choices for each column
96      !    in the display spreadsheet.
98      ! Inputs$ is an array of the input labels.
100     ! Num_inputs is the number of inputs.
102     ! Data_buffer is an array of data for the diplay routines to plot.
104     ! Data_header contains information about how to plot the data in
106     !    Data_buffer.
108     ! Icode_id through Sp_param_id are the block id numbers returned by
110     !    the HP-IB module for various blocks.
112     ! Inpm$ is an array of the input modes of the inputs in the system.
114     ! Range is an array of the ranges of the inputs in the system.
116     ! Block_num, First_third, and Second_third are used to keep track
118     !    of how much data the HP-IB has already sent to this program.
120     ! Tdata, Pdata, and Cdata are the data that the HP-IB module
122     !    sends to this program.
124     ! No_data is a flag.  When set, there is no data to plot.
126     ! Corr_fact through Pidiv2 are constants calculated in Appl_powerup.
128     ! Awaiting_trig is a flag.  When set, we're waiting for the inputs
130     !    to trigger.
132     ! Message_disp is a flag.  When set, we have already displayed our
134     !    'Inputs Triggered' message.
136     ! Start_time is the time when we first noticed that the inputs haven't
138     !    yet triggered.
140     ! Datasize is the number of numbers in a complex data record.
142     ! Fftsize is half of Datasize - it's the number of complex numbers in
144     !    a data record.
146     ! Av_count is the current average number that we're displaying on
148     !    the plots on the screen.
150     ! Numav is the number of averages to do.
152     ! Trig_count is the current trigger number that has just been done.
154     ! Ovld_array is an array of overload flags for the input modules.
156     ! Current_ovld is the most recent version of Ovld_array that can be
158     !    used for displaying overload information on plots.
160     ! Each_av is a flag.  When set, we display every average.
162     ! Info$ is information for the ICODE assembler.
164     ! Assembled is a flag that is set to one when the ICODE is assembled.
166     ! Object is the assembled ICODE.
168     !
170     Appl_powerup
172   SUBEND
174 Appl_powerup:SUB Appl_powerup
176     !
178     ! This is called only by Appl_appl.  It initializes some constants.
180     !
182     COM /Appl_num/ Corr_fact,Hann_fact,Flat_top_fact,Half_lsb,Tpi,Pidiv2
184     Two_db_over=10.^.2
186     Dig_filt_corr=1./(.460657543*.460657543)
188     Twin_sided=2.*2.
190     Corr_fact=Dig_filt_corr*Two_db_over*Twin_sided
192     Flat_top_fact=4.1762*4.1762
194     Hann_fact=2.*2.
196     Half_lsb=.5*.5/(65536.*65536.)
198     Tpi=2.*PI
200     Pidiv2=PI*.5
202   SUBEND
204 Appl_init:SUB Appl_init
206     !
208     ! This is called when the application is first run and when the
210     ! configuration has changed.  It initializes the source and input
212     ! spreadsheets to have the necessary columns.  It assembles the
214     ! ICODE program if necessary.  It also initializes a few things
216     ! like the Inputs$ array.
218     !
220     COM /Appl_data/ Data_buffer(*),Data_header(*)
222     COM /Appl_block_id1/ Icode_id,Input_buff_id,Module_list_id
224     COM /Appl_block_id2/ Output_buff_id,Sp_coef_id,Sp_param_id
226     COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
228     COM /Appl_buf_info/ Disp_choices$(*)
230     COM /Appl_ovld/ INTEGER Ovld_array(*),Current_ovld(*)
232     COM /Appl_disp_info/ Inpm$(*),INTEGER Range(*)
234     COM /Appl_datasize/ INTEGER Datasize,Fftsize
236     DIM Setup$(1:7)[20]
238     INTEGER I,In_a_hurry
240     !
242     ! Get Input labels from Configuration module and create trace labels.
244     ! Restrict number of inputs to 24 maximum (ignore others).
246     !
248     Cnfg_labels("ALL INPUT",Inputs$(*),Temp)
250     Num_inputs=Temp
252     IF Num_inputs<=0 THEN SUBEXIT
254     IF Num_inputs>24 THEN Num_inputs=24
256     !
258     RAD
260     Hw_cmd("CLR;DISA;TRGU")
262     !
264     Setup$(1)="INPUT MODE"
266     Setup$(2)="COUPLING"
268     Setup$(3)="GROUNDING"
270     Setup$(4)="RANGE"
272     Setup$(5)="TRIG MODE"
274     Setup$(6)="TRIG LEVEL"
276     Setup$(7)="TRIG SLOPE"
278     Inpt_init(Setup$(*))
280     REDIM Setup$(1:6)
282     Setup$(1)="MODE"
284     Setup$(2)="OFFSET"
286     Setup$(3)="AMPLITUDE"
288     Setup$(4)="SINE FREQ"
290     Setup$(5)="TRIG"
292     Setup$(6)="BURST %"
294     Srce_init(Setup$(*))
296     !
298     Meas_init
300     !
302     Fftsize=FNMeas_block_size
304     Datasize=Fftsize*.78125+1
306     !
308     REDIM Inpm$(1:Num_inputs),Range(1:Num_inputs)
310     REDIM Ovld_array(1:Num_inputs),Current_ovld(1:Num_inputs)
312     REDIM Inputs$(1:Num_inputs)
314     !
316     Appl_new_labels
318     !
320     Hw_cmd("LSPR 1")                 ! Load correct SP progs
322     !
324     ! Set up ICODE stuff
326     !
328     Appl_icode
330     !
332     In_a_hurry=1
334     IF In_a_hurry THEN 
336       ALLOCATE INTEGER Coef(0:4095)
338       Lib_fft_coefs(Coef(*))
340       Hw_write_blk(Sp_coef_id,Coef(*))
342       DEALLOCATE Coef(*)
344     ELSE
346       Hw_cmd("COEF "&VAL$(Sp_coef_id))    ! Generate FFT coefficient table
348     END IF
350     !
352     MAT Data_buffer= (-300)
354     MAT Data_header= (0)
356     !
358     ! Initializes data to -300 (dB or Deg or whatever)
360     ! Initializes offset to 0
362     ! Initializes scale factor to 0
364     ! Initializes to no overloads
366     ! Initializes log to not done
368     ! Initializes log-of-zero value to 0
370     ! Initializes averaging to off
372     !
374   SUBEND
376 Appl_main:SUB Appl_main(Init)
378     !
380     !  This is the main loop for the application.  It sets up for
382     !  the measurement, sets up the softkeys, and loops processing
384     !  key presses, updating the measurement, and calling the
386     !  measurement loop.  The Init parameter says whether to
388     !  re-initialize the application or just go for it.
390     !
392     COM /Appl_no_data/ INTEGER No_data
394     COM /Appl_trig/ INTEGER Awaiting_trig,Message_disp
396     COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
398     DIM Dummy$[16]
400     !
402     ! Setup up initial softkeys
404     GOSUB Appl_main_keys
406     !
408     ! First init everything
410     Hw_dev_clear
412     IF Init THEN CALL Appl_init
414     !
416     IF Num_inputs<1 THEN 
418       User_error("Can't run FRF with no input modules.")
420       SUBEXIT
422     END IF
424     !
426     Hw_change=1
428     Disp_change=1
430     Calc_data=1
432     Screen_cleared=1
434     Leave_me=0
436     Restart=Num_inputs>1
438     Meas_stopped=NOT Restart
440     No_data=1
442     Awaiting_trig=0
444     Update=1
446     REPEAT
448       !
450       IF Meas_stopped THEN 
452         ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
454         Awaiting_trig=0
456       ELSE
458         ON KEY 7 LABEL FNUser_keylabel$("STOP") CALL User_key7isr
460       END IF
462       !
464       IF Update THEN 
466         Appl_rng_inpm
468         Appl_update
470       END IF
472       !
474       IF Disp_change AND NOT Restart THEN 
476         IF NOT Update THEN CALL Appl_update
478         IF NOT No_data AND Calc_data THEN CALL Appl_calc_data
480       END IF
482       !
484       Axis_only=Restart OR No_data
486       Plot_axis=Screen_cleared OR Restart
488       !
490       IF Restart THEN 
492         Appl_start
494         Appl_update
496         Restart=0
498       END IF
500       !
502       Appl_meas_loop(Plot_axis,Axis_only,Meas_stopped)
504       !
506       Hw_change=0
508       Disp_change=0
510       Calc_data=0
512       Update=0
514       Screen_cleared=Plot_axis ! if axes not done, screen is still cleared
516       REPEAT
518         Appl_do_main(Hw_change,Disp_change,Meas_stopped,Screen_cleared,Leave_me,Restart,Update,Calc_data)
520       UNTIL NOT FNUser_key_press
522     UNTIL Leave_me
524     Cnfg_cmd("ALL","CLASM 50") ! Clean up classes defined by FRF
526     Hw_dev_clear
528     SUBEXIT
530     !
532 Appl_dummy:BEEP 
534     RETURN 
536     !
538 Appl_main_keys:!
540     ON KEY 0 LABEL "" GOSUB Appl_dummy
542     ON KEY 1 LABEL FNUser_keylabel$("INPUT SETUP") CALL User_key1isr
544     ON KEY 2 LABEL FNUser_keylabel$("SOURCE SETUP") CALL User_key2isr
546     ON KEY 3 LABEL FNUser_keylabel$("DISPLAY SETUP") CALL User_key3isr
548     ON KEY 4 LABEL FNUser_keylabel$("MEASURE SETUP") CALL User_key4isr
550     ON KEY 5 LABEL FNUser_keylabel$("HELP") CALL User_key5isr
552     ON KEY 6 LABEL FNUser_keylabel$("MARKER") CALL User_key6isr
554     ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
556     ON KEY 8 LABEL FNUser_keylabel$("EXIT") CALL User_key8isr
558     ON KEY 9 LABEL "" GOSUB Appl_dummy
560     RETURN 
562     !
564   SUBEND
566   !
568   !
570   ! PAGE -> 
572   !***********************************************************************
574 Appl_start:SUB Appl_start
576     !
578     ! This is called when a measurement is started.  It sets up the
580     ! module list and parameter blocks for the ICODE program, then
582     ! starts the modules, and finally, starts the ICODE program.
584     !
586     COM /Appl_data/ Data_buffer(*),Data_header(*)
588     COM /Appl_ref_input/ INTEGER Current_inpt
590     COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
592     COM /Appl_block_id1/ Icode_id,Input_buff_id,Module_list_id
594     COM /Appl_block_id2/ Output_buff_id,Sp_coef_id,Sp_param_id
596     COM /Appl_disp_info/ Inpm$(*),INTEGER Range(*)
598     COM /Appl_data_ptr/ INTEGER Block_num,First_third,Second_third
600     COM /Appl_mydata/ Tdata(*),Pdata(*),Cdata(*)
602     COM /Appl_datasize/ INTEGER Datasize,Fftsize
604     COM /Appl_av_count/ INTEGER Av_count,Numav,Trig_count
606     COM /Appl_ovld/ INTEGER Ovld_array(*),Current_ovld(*)
608     COM /Appl_av_type/ INTEGER Each_av
610     INTEGER I
612     !
614     Fftsize=FNMeas_block_size
616     Datasize=Fftsize*.78125+1
618     !
620     Hw_dev_clear
622     Hw_cmd("CLR;STA?")
624     Inpt_cmd("ALL INPUT","CLEAR ERRORS")
626     !
628     ALLOCATE INTEGER Temp_list(0:Num_inputs+2)
630     Temp_list(0)=Fftsize*2
632     Temp_list(1)=1
634     Temp_list(2)=Num_inputs
636     Temp_list(3)=FNCnfg_get_modnum(Inputs$(Current_inpt))
638     Counter=4
640     FOR I=1 TO Num_inputs
642       IF I<>Current_inpt THEN 
644         Temp_list(Counter)=FNCnfg_get_modnum(Inputs$(I))
646         Counter=Counter+1
648       END IF
650     NEXT I
652     Hw_write_blk(Module_list_id,Temp_list(*))
654     DEALLOCATE Temp_list(*)
656     !
658     ! Setup the FFT parameter block
660     !
662     Appl_set_param(Sp_param_id)
664     !
666     Trig_count=0
668     Numav=FNMeas_numav
670     Av_type$=FNMeas_av_type$
672     Each_av=(UPC$(Av_type$[1;1])="E")
674     Av_count=Numav
676     MAT Ovld_array= (0)              ! Clear overload array
678     Block_num=0
680     First_third=1
682     Second_third=0
684     IF Num_inputs>1 THEN 
686       REDIM Tdata(1:Num_inputs-1,0:Datasize*2-1)
688       REDIM Pdata(1:Num_inputs,0:Datasize-1)
690       REDIM Cdata(1:Num_inputs-1,0:Datasize-1)
692     END IF
694     !
696     Appl_rng_inpm
698     !
700     ! Start all modules, syncced up
702     !
704     Hw_gbl_cmd(50,"SYNC ON;STRT")    ! Start the modules we're using
706     DISP "Waiting for modules to start"
708     Hw_wait_gbl_rdy
710     Hw_cmd("SYNC")
712     DISP "Waiting for modules to sync"
714     !
716     ! Wait for everyone to be ready, then start ICODE program
718     !
720     Hw_wait_gbl_rdy
722     DISP 
724     ! Setup HP-IB module for SRQ on MSG,IRQ,PRG, or ERR
726     Hw_cmd("RQS "&VAL$(FNHw_str_2_stat("MSG,IRQ,PRG,ERR")))
728     Hw_cmd("PROG "&VAL$(Icode_id))
730     !
732   SUBEND
734   !
736   ! PAGE -> 
738   !***********************************************************************
740 Appl_update:SUB Appl_update
742     !
744     ! Called when the display has changed in some way.  This subprogram
746     ! sets up the bounds, units, and titles for the plots.
748     !
750     COM /Appl_buf_info/ Disp_choices$(*)
752     COM /Appl_data/ Data_buffer(*),Data_header(*)
754     COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
756     COM /Appl_ref_input/ INTEGER Current_inpt
758     COM /Appl_disp_info/ Inpm$(*),INTEGER Range(*)
760     COM /Appl_num/ Corr_fact,Hann_fact,Flat_top_fact,Half_lsb,Tpi,Pidiv2
762     COM /Appl_datasize/ INTEGER Datasize,Fftsize
764     COM /Appl_av_type/ INTEGER Each_av
766     DIM Def_units$[10],Units$[10],Window_type$[20],Av_type$[20],Func$[30]
768     DIM Type$[20],Temp$[80],Mid$[5]
770     INTEGER I,Def_range,Rng,Numav
772     !
774     Num_plots=FNDisp_num_plots
776     ALLOCATE Plot_to_buf(1:Num_plots)
778     ALLOCATE X_units$(1:Num_plots)[10],Y_units$(1:Num_plots)[10]
780     ALLOCATE Start_x(1:Num_plots),Per_bin_x(1:Num_plots)
782     ALLOCATE Start_bin(1:Num_plots),Num_bins(1:Num_plots)
784     ALLOCATE Y_def_max(1:Num_plots),Y_def_min(1:Num_plots)
786     ALLOCATE Do_log_x(1:Num_plots)
788     ALLOCATE Title$(1:Num_plots)[45]
790     !
792     Def_range=Range(Current_inpt)
794     Def_units$=Inpm$(Current_inpt)
796     Window_type$=FNMeas_window$
798     Wind_fact=Corr_fact
800     Av_type$=FNMeas_av_type$
802     Numav=FNMeas_numav
804     IF Each_av THEN Numav=0                 ! Displaying every average
806     IF Numav<=1 THEN Numav=0                ! No averaging
808     IF UPC$(Window_type$[1;1])="H" THEN Wind_fact=Hann_fact*Corr_fact
810     IF UPC$(Window_type$[1;1])="F" THEN Wind_fact=Flat_top_fact*Corr_fact
812     IF Def_units$[1;2]<>"CH" THEN Def_units$="VOLT"
814     FOR I=1 TO Num_plots
816       Plot_to_buf(I)=I
818       Input_used=FNDisp_choice((I),1)
820       Rng=Range(Input_used)
822       Units$=Inpm$(Input_used)
824       IF Units$[1;2]<>"CH" THEN Units$="VOLT"
826       Data_header(I,1)=0     ! No offset
828       Func$=Disp_choices$(3,FNDisp_choice((I),3))
830       Type$=Disp_choices$(4,FNDisp_choice((I),4))
832       Title$(I)=Inputs$(Input_used)
834       IF Func$="Pwr Spect" THEN 
836         Title$(I)=Title$(I)&"  "&Func$&" "&Type$
838       ELSE
840         Mid$=" / "
842         IF Func$="Cros Spct" THEN Mid$=" * "
844         IF LEN(Title$(I))+LEN(Inputs$(Current_inpt))>24 THEN 
846           Temp$=Title$(I)[1;12]&Mid$&Inputs$(Current_inpt)[1;12]&"  "&Func$&" "&Type$
848         ELSE
850           Temp$=Title$(I)&Mid$&Inputs$(Current_inpt)&"  "&Func$&" "&Type$
852         END IF
854         Title$(I)=Temp$[1;45]
856       END IF
858       SELECT Type$
860       CASE "Phase"
862         Y_units$(I)="Deg"
864         Y_def_min(I)=-180
866         Y_def_max(I)=180
868         Data_header(I,2)=.0174532925199      ! PI/180
870         Data_header(I,4)=0
872       CASE "Mag"
874         SELECT Func$
876         CASE "Freq Resp"
878           Y_def_min(I)=-60+Rng-Def_range
880           Y_def_max(I)=20+Rng-Def_range
882           Data_header(I,2)=10^((Def_range-Rng)*.1)
884           Data_header(I,4)=10
886           Data_header(I,5)=Half_lsb
888           IF Units$=Def_units$ THEN 
890             Y_units$(I)="dB"
892           ELSE
894             IF Units$[1;2]="CH" THEN 
896               Y_units$(I)="dB pC/V"
898             ELSE
900               Y_units$(I)="dB V/pC"
902             END IF
904           END IF
906         CASE "Cros Spct"
908           Y_def_min(I)=-60+(Rng+Def_range)*.5
910           Y_def_max(I)=20+(Rng+Def_range)*.5
912           IF Input_used<>Current_inpt THEN 
914             Scaler=1/(Wind_fact*Wind_fact*10^((Def_range+Rng)*.1))
916             Data_header(I,4)=5
918             Data_header(I,5)=Half_lsb*Half_lsb/(Wind_fact*Wind_fact)
920           ELSE
922             ! This is the same as Power Spectrum
924             Scaler=1/(Wind_fact*10^(Rng*.1))
926             Data_header(I,4)=10
928             Data_header(I,5)=Half_lsb/Wind_fact
930           END IF
932           Data_header(I,2)=Scaler
934           IF Def_units$=Units$ THEN 
936             IF Def_units$[1;2]<>"CH" THEN 
938               Y_units$(I)="dBVp"
940             ELSE
942               Y_units$(I)="dBpCp"
944             END IF
946           ELSE
948             Y_units$(I)="dB V*pC"
950           END IF
952         CASE "Coherence"
954           Y_def_max(I)=0
956           Y_def_min(I)=-20
958           Data_header(I,2)=1
960           Data_header(I,4)=20
962           Data_header(I,5)=Half_lsb
964           Y_units$(I)="dB"
966         CASE "Pwr Spect"
968           Y_def_max(I)=Rng+2
970           Y_def_min(I)=Rng-78
972           Scaler=1/(Wind_fact*10^(Rng*.1))
974           Data_header(I,2)=Scaler
976           Data_header(I,4)=10
978           Data_header(I,5)=Half_lsb/Wind_fact
980           IF Units$[1;2]<>"CH" THEN 
982             Y_units$(I)="dBVp"
984           ELSE
986             Y_units$(I)="dBpCp"
988           END IF
990         CASE ELSE
992           User_stop("Error in Appl_update CASE statement")
994         END SELECT
996       CASE "Real","Imag","Lin Mag"
998         SELECT Func$
1000        CASE "Freq Resp"
1002          IF Type$="Lin Mag" THEN 
1004            Y_def_min(I)=0
1006          ELSE
1008            Y_def_min(I)=-4
1010          END IF
1012          Y_def_max(I)=4
1014          Data_header(I,2)=10^((Def_range-Rng)*.05)
1016          Data_header(I,4)=0
1018          IF Units$=Def_units$ THEN 
1020            Y_units$(I)="V/V"
1022          ELSE
1024            IF Units$[1;2]="CH" THEN 
1026              Y_units$(I)="pC/V"
1028            ELSE
1030              Y_units$(I)="V/pC"
1032            END IF
1034          END IF
1036        CASE "Coherence"
1038          Y_def_min(I)=0
1040          Y_def_max(I)=1
1042          Data_header(I,2)=1
1044          Data_header(I,4)=0
1046          Y_units$(I)=" "
1048        CASE "Cros Spct"
1050          IF Type$="Lin Mag" THEN 
1052            Y_def_min(I)=0
1054          ELSE
1056            Y_def_min(I)=-4
1058          END IF
1060          Y_def_max(I)=4
1062          Data_header(I,2)=1/(Wind_fact*10^((Rng+Def_range)*.05))
1064          Data_header(I,4)=0
1066          IF Units$=Def_units$ THEN 
1068            IF Units$[1;2]<>"CH" THEN 
1070              Y_units$(I)="Vp"
1072            ELSE
1074              Y_units$(I)="pCp"
1076            END IF
1078          ELSE
1080            Y_units$(I)="V*pC"
1082          END IF
1084        CASE "Pwr Spect"
1086          Y_def_min(I)=0
1088          Y_def_max(I)=4
1090          Data_header(I,2)=1/(Wind_fact*10^(Rng*.1))
1092          Data_header(I,4)=0
1094          IF Units$[1;2]<>"CH" THEN 
1096            Y_units$(I)="Vp"
1098          ELSE
1100            Y_units$(I)="pCp"
1102          END IF
1104        CASE ELSE
1106          User_stop("Error in Appl_update CASE statement")
1108        END SELECT
1110      CASE ELSE
1112        User_stop("Error in Appl_update CASE statement")
1114      END SELECT
1116    NEXT I
1118    !
1120    MAT X_units$= ("Hz")
1122    MAT Start_x= (FNMeas_cf-(FNMeas_span*.5))
1124    MAT Per_bin_x= (FNMeas_span*1.28/Fftsize)
1126    MAT Start_bin= (0)  ! Use fftsize*7/64 if all FFT points used
1128    MAT Num_bins= (Datasize)
1130    MAT Do_log_x= (FNMeas_log_freq)
1132    !
1134    Disp_plot_set(Plot_to_buf(*),X_units$(*),Y_units$(*),Start_x(*),Per_bin_x(*),Start_bin(*),Num_bins(*),Y_def_max(*),Y_def_min(*))
1136    Disp_put_titles(Title$(*))    ! I want to set my own titles for plots
1138    Disp_log_set(Do_log_x(*))     ! Set up log or linear frequency
1140    !
1142  SUBEND
1144  !
1146  ! PAGE -> 
1148  !***********************************************************************
1150 Appl_do_main:SUB Appl_do_main(Hw_change,Disp_change,Meas_stopped,Screen_cleared,Leave_me,Restart,Update,Calc_data)
1152    !
1154    ! Once a softkey or firmkey has been pressed, the measurement loop is
1156    ! exited and this subprogram is called to process the key.  It calls
1158    ! the appropriate spreadsheet programs, or the marker program, or
1160    ! whatever.  Hw_change is set if there is a change in the source or
1162    ! input spreadsheets.  Disp_change is set if there is a change in
1164    ! the display spreadsheet or if the frequency axis is changed from
1166    ! linear to log or log to linear.  Meas_stopped says whether or not
1168    ! a measurement is stopped.  Screen_cleared is set if the screen gets
1170    ! cleared for any reason (like a spreadsheet).  Leave_me is set if
1172    ! the FRF application should be exited.  Restart is set if it is time
1174    ! to start a measurement.  Update is set if the Appl_update subprogram
1176    ! needs to be called.  Calc_data is set if Disp_change is set but the
1178    ! change in the display is minor and we don't need to re-calculate
1180    ! all our data.
1182    !
1184    COM /Appl_data/ Data_buffer(*),Data_header(*)
1186    COM /Appl_ref_input/ INTEGER Current_inpt
1188    COM /Appl_convert/ Inputs$(1:63)[20],INTEGER Num_inputs
1190    COM /Appl_no_data/ INTEGER No_data
1192    DIM Dummy$[20]
1194    INTEGER Key_num
1196    !
1198    Key_num=FNUser_get_key
1200    New_ref=0
1202    SELECT Key_num
1204    CASE 1
1206      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key1isr
1208      Temp=0
1210      CALL Inpt_spread(Temp)
1212      Inpt_change=Inpt_change OR Temp
1214      OFF KEY Key_num
1216      Screen_cleared=1
1218    CASE 2
1220      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key2isr
1222      Temp=0
1224      CALL Srce_spread(Temp)
1226      Srce_change=Srce_change OR Temp
1228      OFF KEY Key_num
1230      Screen_cleared=1
1232    CASE 3
1234      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key3isr
1236      Temp=0
1238      Temp2=0
1240      CALL Disp_spread(Temp,Temp2)
1242      Disp_change=Disp_change OR Temp
1244      Calc_data=Calc_data OR Temp2
1246      OFF KEY Key_num
1248      Screen_cleared=1
1250    CASE 4
1252      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key4isr
1254      Temp=0
1256      Temp2=0
1258      Temp3=0
1260      CALL Meas_spread(Temp,Temp2,Temp3)
1262      Meas_change=Meas_change OR Temp
1264      New_ref=New_ref OR Temp2
1266      Disp_change=Disp_change OR Temp3
1268      OFF KEY Key_num
1270      Screen_cleared=1
1272    CASE 5
1274      Appl_help
1276      Screen_cleared=1
1278    CASE 6
1280      IF NOT No_data THEN 
1282        ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key6isr
1284        IF Screen_cleared THEN 
1286          Disp_plot_axis
1288          Screen_cleared=FNUser_key_press ! If key pressed, axes not done
1290        END IF
1292        CALL Disp_do_mkr(Data_buffer(*),Data_header(*),0)
1294        OFF KEY Key_num
1296      ELSE
1298        User_error("There is no data to look at!")
1300      END IF
1302    CASE 7
1304      IF Meas_stopped THEN 
1306        IF Num_inputs>1 THEN 
1308          Restart=1
1310          Meas_stopped=0
1312          No_data=1
1314        ELSE
1316          User_error("Can't make measurements with less than two inputs.")
1318        END IF
1320      ELSE
1322        Meas_stopped=1
1324        Restart=0
1326      END IF
1328    CASE 8
1330      Leave_me=1
1332    END SELECT
1334    !
1336    IF New_ref THEN 
1338      Appl_new_labels
1340    END IF
1342    !
1344    IF Inpt_change OR Srce_change THEN Hw_change=1
1346    !
1348    IF Inpt_change OR Meas_change THEN 
1350      Update=1
1352      No_data=1
1354    END IF
1356    !
1358    IF Hw_change OR Meas_change THEN 
1360      Meas_stopped=1
1362      Restart=0
1364    END IF
1366    !
1368    IF FNUser_key_press THEN 
1370      IF FNUser_check_key=Key_num THEN Key_num=FNUser_get_key
1372    END IF
1374  SUBEND
1376  !
1378  ! PAGE -> 
1380  !***********************************************************************
1382 Appl_meas_loop:SUB Appl_meas_loop(Plot_axis,Axis_only,Meas_stopped)
1384    !
1386    !  This routine is called when no keys are being pressed.  It
1388    !  should not return until a key has been pressed, or the measurement
1390    !  is done.  Plot_axis says whether or not to plot the axis (which
1392    !  should only be necessary after the screen is cleared).  If Axis_only
1394    !  is one, then no data should be plotted until new data shows up
1396    !  from the HP-IB module.  Meas_stopped says whether or not
1398    !  the measurement has stopped.
1400    !
1402    COM /Appl_data/ Data_buffer(*),Data_header(*)
1404    COM /Appl_trig/ INTEGER Awaiting_trig,Message_disp
1406    INTEGER Plot_data,Now_stopped
1408    !
1410    Now_stopped=Meas_stopped
1412    Plot_data=Plot_axis AND NOT Axis_only
1414    REPEAT
1416      IF NOT Meas_stopped THEN 
1418        Appl_get_data(New_data,Meas_stopped)
1420        Plot_data=Plot_data OR New_data
1422      ELSE
1424        DISP "Waiting for START key"
1426      END IF
1428      IF Awaiting_trig THEN CALL Appl_trigger
1430      IF Plot_axis THEN 
1432        Disp_plot_axis
1434        Plot_axis=FNUser_key_press ! if a key was pressed, axes not done
1436      END IF
1438      IF Plot_data THEN 
1440        IF NOT Plot_axis THEN 
1442          Disp_plot_data(Data_buffer(*),Data_header(*))
1444          Plot_data=0
1446        END IF
1448      END IF
1450    UNTIL FNUser_key_press OR Now_stopped<>Meas_stopped
1452  SUBEND
1454  !
1456  !
1458  ! PAGE -> 
1460  !***********************************************************************
1462 Appl_get_data:SUB Appl_get_data(Got_new_data,Meas_stopped)
1464    !
1466    ! Called to get new data from the HP-IB module.
1468    ! If new data is not available, this subprogram should return
1470    ! with Got_new_data false.  If there is new data, it should
1472    ! update the Tdata, Pdata, and Cdata arrays, and return.  When
1474    ! Tdata, Pdata, and Cdata are full, Got_new_data is returned as true.
1476    ! If there is an error in any module, this routine should call the
1478    ! error check routine so an error message can be displayed.
1480    !
1482    COM /Appl_data/ Data_buffer(*),Data_header(*)
1484    COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
1486    COM /Appl_block_id1/ Icode_id,Input_buff_id,Module_list_id
1488    COM /Appl_block_id2/ Output_buff_id,Sp_coef_id,Sp_param_id
1490    COM /Appl_data_ptr/ INTEGER Block_num,First_third,Second_third
1492    COM /Appl_mydata/ Tdata(*),Pdata(*),Cdata(*)
1494    COM /Appl_datasize/ INTEGER Datasize,Fftsize
1496    COM /Appl_av_count/ INTEGER Av_count,Numav,Trig_count
1498    COM /Appl_av_type/ INTEGER Each_av
1500    COM /Appl_ovld/ INTEGER Ovld_array(1:63),Current_ovld(1:63)
1502    !
1504    ! Tdata is an array of transfer function data.  It is complex data,
1506    ! with the real part first and then the imaginary.  There are
1508    ! (Num_inputs - 1) data records in this array, since there's one
1510    ! reference input.
1512    !
1514    ! Pdata is an array of power spectrum data.  It is real data.  There
1516    ! are Num_inputs data records in this array.
1518    !
1520    ! Cdata is an array of coherence data.  It is complex, with the real
1522    ! part first and the imaginary second.  There are (Num_inputs - 1)
1524    ! data records in this array.
1526    !
1528    INTEGER A,Sta,K,I,Stop_flag,Err,Msg,Irq
1530    DIM Av_type$[20]
1532    Got_new_data=0
1534    IF NOT FNHw_srq THEN SUBEXIT
1536    !
1538    !Err=PROUND(LOG(FNHw_str_2_stat("ERROR"))/LOG(2),0)
1540    !Msg=PROUND(LOG(FNHw_str_2_stat("MSG"))/LOG(2),0)
1542    !Irq=PROUND(LOG(FNHw_str_2_stat("IRQ"))/LOG(2),0)
1544    Err=5
1546    Msg=7
1548    Irq=9
1550    Stop_flag=0
1552    REPEAT
1554      Sta=VAL(FNHw_cmd_rsp$("STA?"))
1556      !
1558      IF BIT(Sta,Err) THEN 
1560        User_stop("HP-IB module error: "&FNHw_get_errstr$(VAL(FNHw_cmd_rsp$("ERR?"))))
1562      END IF
1564      IF BIT(Sta,Msg) THEN 
1566        A=VAL(FNHw_cmd_rsp$("SIG?"))
1568        SELECT A
1570        CASE 1                 ! HP-IB module has data for us
1572          IF First_third THEN  ! Complex data, which is bigger
1574            ALLOCATE Data_in_block(0:Datasize*2-1)
1576          ELSE                 ! Mag-squared data or Coherence data
1578            ALLOCATE Data_in_block(0:Datasize-1)
1580          END IF
1582          Hw_read_fblk(Output_buff_id,Data_in_block(*))
1584          Hw_cmd("CONT")       ! Continue ICODE program
1586          Block_num=Block_num+1
1588          ! Now load Data_in_block into Tdata, Pdata, or Cdata
1590          IF First_third THEN 
1592            FOR I=0 TO 2*Datasize-1
1594              Tdata(Block_num,I)=Data_in_block(I)
1596            NEXT I
1598          ELSE
1600            IF Second_third THEN 
1602              FOR I=0 TO Datasize-1
1604                Pdata(Block_num,I)=Data_in_block(I)
1606              NEXT I
1608            ELSE
1610              FOR I=0 TO Datasize-1
1612                Cdata(Block_num,I)=Data_in_block(I)
1614              NEXT I
1616            END IF
1618          END IF
1620          DEALLOCATE Data_in_block(*)
1622          IF First_third AND Block_num=Num_inputs-1 THEN 
1624            Block_num=0
1626            First_third=0
1628            Second_third=1
1630          END IF
1632          IF Second_third AND Block_num=Num_inputs THEN 
1634            Block_num=0
1636            Second_third=0
1638          END IF
1640          IF NOT First_third AND NOT Second_third AND Block_num=Num_inputs-1 THEN 
1642            Block_num=0
1644            First_third=1
1646            MAT Current_ovld= Ovld_array   ! Set up current overload array
1648            IF Numav>1 AND Each_av THEN Av_count=(Av_count MOD Numav)+1
1650            IF Av_count=Numav THEN 
1652              IF FNMeas_restart THEN 
1654                MAT Ovld_array= (0)        ! Clear next overload array
1656                Appl_trigger
1658              ELSE
1660                Meas_stopped=1
1662              END IF
1664            ELSE
1666              Appl_trigger
1668            END IF
1670            Appl_calc_data
1672            Got_new_data=1
1674          END IF
1676        CASE 2             ! Measurement crash
1678          User_error("Sorry, Measurement crashed!")
1680          !Appl_chk_errors
1682          Meas_stopped=1
1684        CASE 4             ! Ready to trigger
1686          Appl_trigger
1688        END SELECT
1690      END IF
1692      IF BIT(Sta,Irq) THEN CALL Appl_chk_errors
1694    UNTIL NOT FNHw_srq OR Got_new_data
1696  SUBEND
1698  !
1700  !***********************************************************************
1702 Appl_new_labels:SUB Appl_new_labels
1704    !
1706    ! Sets up Disp_choices$ and other arrays for the display spreadsheet.
1708    !
1710    COM /Appl_buf_info/ Disp_choices$(*)
1712    COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
1714    COM /Appl_ref_input/ INTEGER Current_inpt
1716    DIM Ref$[20]
1718    !
1720    ! Map input labels into meaningful titles for disp
1722    !
1724    Ref$=FNMeas_ref_input$(Current_inpt)
1726    !
1728    ! Define display spreadsheet application dependent columns
1730    !
1732    Num_cols=4
1734    ALLOCATE Disp_titles$(1:Num_cols,1:2)[20]
1736    ALLOCATE Disp_prompt$(1:Num_cols)[80]
1738    ALLOCATE Disp_width(1:Num_cols)
1740    !
1742    Disp_titles$(1,1)="Module"
1744    Disp_titles$(1,2)="Label"
1746    Disp_titles$(2,1)="Reference"
1748    Disp_titles$(2,2)="Module"
1750    Disp_titles$(3,1)="Trace"
1752    Disp_titles$(3,2)="Function"
1754    Disp_titles$(4,1)="Trace"
1756    Disp_titles$(4,2)="Type"
1758    Disp_prompt$(1)="Enter module label"
1760    Disp_prompt$(2)="Reference Input - to change go to MEASURE SETUP"
1762    Disp_prompt$(3)="Enter trace function: Freq Resp, Coherence, Pwr Spect, Cros Spct"
1764    Disp_prompt$(4)="Enter trace type: Mag, Phase, Real, Imag, Lin Mag"
1766    Disp_width(1)=16
1768    Disp_width(2)=13
1770    Disp_width(3)=9
1772    Disp_width(4)=7
1774    MAT Disp_choices$= ("")
1776    !
1778    FOR Module_index=1 TO Num_inputs
1780      Disp_choices$(1,Module_index)=Inputs$(Module_index)
1782    NEXT Module_index
1784    !
1786    Disp_choices$(2,1)=Inputs$(Current_inpt)
1788    !
1790    Disp_choices$(3,1)="Freq Resp"
1792    Disp_choices$(3,2)="Coherence"
1794    Disp_choices$(3,3)="Pwr Spect"
1796    Disp_choices$(3,4)="Cros Spct"
1798    !
1800    Disp_choices$(4,1)="Mag"
1802    Disp_choices$(4,2)="Phase"
1804    Disp_choices$(4,3)="Real"
1806    Disp_choices$(4,4)="Imag"
1808    Disp_choices$(4,5)="Lin Mag"
1810    !
1812    ! Setup Disp module with titles
1814    !
1816    Disp_spread_set(Disp_titles$(*),Disp_prompt$(*),Disp_width(*),Disp_choices$(*))
1818    !
1820  SUBEND
1822  !
1824 Appl_set_param:SUB Appl_set_param(Param_id)
1826    !
1828    ! Sets up the parameter block for the ICODE program.  This parameter
1830    ! block is used to pass in information about averaging, windowing,
1832    ! FFT size, and whether to restart when done.  The Param_id parameter
1834    ! is the block id for the parameter block.
1836    !
1838    COM /Appl_datasize/ INTEGER Datasize,Fftsize
1840    DIM Wind$[20],Av_type$[20]
1842    INTEGER Do_window,Param(0:10)
1844    Wind$=UPC$(FNMeas_window$)
1846    Do_window=Wind$[1;1]<>"R"
1848    Wind_type=Wind$[1;1]<>"H"
1850    Av_type$=FNMeas_av_type$
1852    Param(0)=0
1854    Param(1)=0
1856    Param(2)=PROUND(LOG(Fftsize)/LOG(2),0)
1858    Param(3)=0
1860    Param(4)=Do_window       ! Swap flag - makes FFT better if windowing
1862    Param(5)=Do_window       ! Window flag
1864    Param(6)=0               ! Normal FFT, no mag-squared results
1866    Param(7)=FNMeas_numav    ! Pass in number of averages
1868    Param(8)=Wind_type       ! Pass in type of window (0=Hann, 1=Flat-top)
1870    Param(9)=FNMeas_restart  ! 1=Restart, 0=Stop when done
1872    Param(10)=(UPC$(Av_type$[1;1])="E") ! Display Each average
1874    Hw_write_blk(Param_id,Param(*))
1876  SUBEND
1878  !
1880 Appl_chk_errors:SUB Appl_chk_errors
1882    !
1884    ! Calls Diag_chk_errors to display error messages for all the modules.
1886    ! Then uses a POLM and and POL to pick out modules to display status
1888    ! messages for.
1890    !
1892    INTEGER Temp,Polm,Polm_bit,Pol,Pol_bit,Mod_num
1894    Temp=FNDiag_chk_errors
1896    Polm=VAL(FNHw_cmd_rsp$("POLM"))
1898    FOR Polm_bit=0 TO 7
1900      IF BIT(Polm,Polm_bit) THEN 
1902        Pol=VAL(FNHw_cmd_rsp$("POL "&VAL$(Polm_bit)))
1904        FOR Pol_bit=0 TO 7
1906          IF BIT(Pol,Pol_bit) THEN 
1908            Mod_num=Polm_bit*8+Pol_bit
1910            Diag_chk_status(FNCnfg_get_label$((Mod_num)))
1912          END IF
1914        NEXT Pol_bit
1916      END IF
1918    NEXT Polm_bit
1920  SUBEND
1922 Appl_trigger:SUB Appl_trigger
1924    !
1926    ! Checks to see if a trigger has occurred.  If not, it displays a
1928    ! message, sets a flag, and returns.  After long enough with no
1930    ! trigger, the message changes to hint that maybe an input needs to be
1932    ! in SEND trigger mode.  If a trigger has occurred, a flag is set, the
1934    ! 'Waiting for trigger' message is erased, and overloads are checked
1936    ! if it is time to look for overloads.  The ICODE program is then
1938    ! continued.
1940    !
1942    COM /Appl_convert/ Inputs$(1:63)[20],INTEGER Num_inputs
1944    COM /Appl_ref_input/ INTEGER Current_inpt
1946    COM /Appl_trig/ INTEGER Awaiting_trig,Message_disp
1948    COM /Appl_time/ Start_time
1950    COM /Appl_av_count/ INTEGER Av_count,Numav,Trig_count
1952    COM /Appl_av_type/ INTEGER Each_av
1954    IF BIT(VAL(FNHw_cmd_rsp$("STC?")),8) THEN ! BAV SRQ already occurred
1956      Appl_message
1958      IF Numav>1 THEN Trig_count=(Trig_count MOD Numav)+1
1960      IF Numav<=1 OR Each_av OR Trig_count=Numav THEN CALL Appl_do_ovld
1962      Hw_cmd("CONT")
1964      Awaiting_trig=0
1966      Message_disp=0
1968    ELSE
1970      IF NOT Message_disp THEN 
1972        IF NOT Awaiting_trig THEN 
1974          Start_time=TIMEDATE
1976          DISP "Waiting for inputs to trigger"
1978          Awaiting_trig=1
1980        ELSE
1982          IF TIMEDATE-Start_time>.25 THEN 
1984            IF VAL(FNInpt_rsp$(Inputs$(Current_inpt),"MODULE STATE"))<9 THEN 
1986              IF TIMEDATE-Start_time>10 THEN 
1988                DISP "Waiting for inputs to trigger - Try putting an Input in Send Trigger Mode"
1990              ELSE
1992                DISP "Waiting for inputs to trigger"
1994              END IF
1996            ELSE
1998              Appl_message
2000            END IF
2002          ELSE
2004            DISP "Waiting for inputs to trigger"
2006          END IF
2008        END IF
2010      END IF
2012    END IF
2014  SUBEND
2016 Appl_calc_data:SUB Appl_calc_data
2018    !
2020    ! This is called once a full set of data has been received from
2022    ! the HP-IB module.  This subprogram looks at what needs to
2024    ! be plotted, and does the necessary calculations to get that.
2026    ! This plot data is put in the Data_buffer, for the plot routines
2028    ! to use.
2030    !
2032    COM /Appl_buf_info/ Disp_choices$(*)
2034    COM /Appl_ref_input/ INTEGER Current_inpt
2036    COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
2038    COM /Appl_data/ Data_buffer(*),Data_header(*)
2040    COM /Appl_mydata/ Tdata(*),Pdata(*),Cdata(*)
2042    COM /Appl_no_data/ INTEGER No_data
2044    COM /Appl_num/ Corr_fact,Hann_fact,Flat_top_fact,Half_lsb,Tpi,Pidiv2
2046    COM /Appl_datasize/ INTEGER Datasize,Fftsize
2048    COM /Appl_av_count/ INTEGER Av_count,Numav,Trig_count
2050    COM /Appl_ovld/ INTEGER Ovld_array(*),Current_ovld(*)
2052    DIM Type$[20],Func$[30]
2054    INTEGER I,J,K,Input_used,No_ref,Datasizex2,Datasizem1
2056    INTEGER Ovld,Ref_ovld
2058    Datasizex2=Datasize*2
2060    Datasizem1=Datasize-1
2062    Ref_ovld=Current_ovld(Current_inpt)
2064    No_data=0
2066    FOR I=1 TO FNDisp_num_plots
2068      Data_header(I,6)=Av_count
2070      Input_used=FNDisp_choice((I),1)
2072      Ovld=Current_ovld(Input_used)
2074      Data_header(I,3)=Ovld OR Ref_ovld
2076      No_ref=Input_used
2077      SELECT No_ref
2078      CASE >Current_inpt
2079         With_ref=No_ref
2080         No_ref=No_ref-1
2081      CASE Current_inpt
2082         With_ref=1
2083      CASE <Current_inpt
2084         With_ref=No_ref+1
2085      END SELECT
2088      Func$=Disp_choices$(3,FNDisp_choice((I),3))
2089      Type$=Disp_choices$(4,FNDisp_choice((I),4))
2090      IF Input_used=Current_inpt AND Func$="Cros Spct" THEN Func$="Pwr Spect"
2091      IF Func$="Cros Spct" AND Type$="Phase" THEN Func$="Freq Resp"
2092      IF Input_used=Current_inpt AND Func$<>"Pwr Spect" THEN 
2094        K=(Type$="Mag" OR Type$="Real" OR Type$="Lin Mag")
2096        FOR J=0 TO Datasizem1
2098          Data_buffer(I,J)=K
2100        NEXT J
2102      ELSE
2104        SELECT Func$
2106        CASE "Freq Resp"
2108          SELECT Type$
2110          CASE "Phase"
2112            FOR J=0 TO Datasizem1
2114              K=J*2
2116              IF Tdata(No_ref,K)<>0 THEN 
2118                Temp=ATN(Tdata(No_ref,K+1)/Tdata(No_ref,K))
2120                IF Tdata(No_ref,K)<0 THEN 
2122                  Temp=Temp+PI
2124                  IF Temp>PI THEN Temp=Temp-Tpi
2126                END IF
2128                Data_buffer(I,J)=Temp
2130              ELSE
2132                IF Tdata(No_ref,K+1)>0 THEN 
2134                  Data_buffer(I,J)=Pidiv2
2136                ELSE
2138                  Data_buffer(I,J)=-Pidiv2
2140                END IF
2142              END IF
2144            NEXT J
2146          CASE "Mag"
2148            FOR J=0 TO Datasizem1
2150              K=J*2
2152              Data_buffer(I,J)=Tdata(No_ref,K)*Tdata(No_ref,K)+Tdata(No_ref,K+1)*Tdata(No_ref,K+1)
2154            NEXT J
2156          CASE "Real"
2158            FOR J=0 TO Datasizem1
2160              Data_buffer(I,J)=Tdata(No_ref,J*2)
2162            NEXT J
2164          CASE "Imag"
2166            FOR J=0 TO Datasizem1
2168              Data_buffer(I,J)=Tdata(No_ref,J*2+1)
2170            NEXT J
2172          CASE "Lin Mag"
2174            FOR J=0 TO Datasizem1
2176              K=J*2
2178              Data_buffer(I,J)=SQR(Tdata(No_ref,K)*Tdata(No_ref,K)+Tdata(No_ref,K+1)*Tdata(No_ref,K+1))
2180            NEXT J
2182          CASE ELSE
2184            User_stop("Error is appl_calc_data FRF CASE statement")
2186          END SELECT
2188        CASE "Coherence"
2190          SELECT Type$
2192          CASE "Lin Mag","Real","Mag"
2194            FOR J=0 TO Datasizem1
2196              Data_buffer(I,J)=Cdata(No_ref,J)
2198            NEXT J
2200          CASE "Imag","Phase"
2202            FOR J=0 TO Datasizem1
2204              Data_buffer(I,J)=0
2206            NEXT J
2208          CASE ELSE
2210            User_stop("Error in appl_calc_data Coherence CASE statement")
2212          END SELECT
2214        CASE "Pwr Spect"
2216          Data_header(I,3)=Ovld      ! Ref_ovld doesn't matter here
2218          SELECT Type$
2220          CASE "Lin Mag","Real","Mag"
2222            FOR J=0 TO Datasizem1
2224              Data_buffer(I,J)=Pdata(With_ref,J)
2226            NEXT J
2228          CASE "Imag","Phase"
2230            FOR J=0 TO Datasizem1
2232              Data_buffer(I,J)=0
2234            NEXT J
2236          CASE ELSE
2238            User_stop("Error in appl_calc_data Coherence CASE statement")
2240          END SELECT
2242        CASE "Cros Spct"
2244          SELECT Type$
2246          CASE "Mag"
2248            FOR J=0 TO Datasizem1
2250              Data_buffer(I,J)=Pdata(1,J)*Pdata(1,J)*(Tdata(No_ref,J*2)*Tdata(No_ref,J*2)+Tdata(No_ref,J*2+1)*Tdata(No_ref,J*2+1))
2252            NEXT J
2254          CASE "Phase"
2256            ! Not needed - used "Freq Resp" phase since it's the same
2258          CASE "Real"
2260            FOR J=0 TO Datasizem1
2262              Data_buffer(I,J)=Tdata(No_ref,J*2)*Pdata(1,J)
2264            NEXT J
2266          CASE "Imag"
2268            FOR J=0 TO Datasizem1
2270              Data_buffer(I,J)=Tdata(No_ref,J*2+1)*Pdata(1,J)
2272            NEXT J
2274          CASE "Lin Mag"
2276            FOR J=0 TO Datasizem1
2278              Data_buffer(I,J)=Pdata(1,J)*SQR((Tdata(No_ref,J*2)*Tdata(No_ref,J*2)+Tdata(No_ref,J*2+1)*Tdata(No_ref,J*2+1)))
2280            NEXT J
2282          CASE ELSE
2284            User_stop("Error in appl_calc_data Cros Spct CASE statement")
2286          END SELECT
2288        CASE ELSE
2290          User_stop("Error in appl_calc_data function CASE statement")
2292        END SELECT
2294      END IF
2296    NEXT I
2298  SUBEND
2300 Appl_message:SUB Appl_message
2302    !
2304    ! This is called by Appl_trigger to display the message that the
2306    ! inputs have triggered, and to display the average number that
2308    ! we're on.
2310    !
2312    COM /Appl_av_count/ INTEGER Av_count,Numav,Trig_count
2314    COM /Appl_trig/ INTEGER Awaiting_trig,Message_disp
2316    DISP "Inputs Triggered";
2318    IF Numav>1 THEN 
2320      DISP " - Average Number ";(Trig_count MOD Numav)+1
2322    ELSE
2324      DISP 
2326    END IF
2328    Message_disp=1
2330  SUBEND
2332 Appl_do_ovld:SUB Appl_do_ovld
2334    !
2336    ! This is called by Appl_trigger if overloads need to be checked.
2338    ! If we're in the middle of an average, where each average is
2340    ! displayed, we need one overload array to update while another one
2342    ! is used for the plots.  Current_ovld is the one used for plots,
2344    ! and Ovld_array is used for updating.
2346    !
2348    COM /Appl_ref_input/ INTEGER Current_inpt
2350    COM /Appl_convert/ Inputs$(*),INTEGER Num_inputs
2352    COM /Appl_ovld/ INTEGER Ovld_array(*),Current_ovld(*)
2354    INTEGER I
2356    FOR I=1 TO Num_inputs
2358      IF NOT Ovld_array(I) THEN Ovld_array(I)=BIT(FNCnfg_rmst(Inputs$(I)),7)
2360    NEXT I
2362    Inpt_cmd("ALL INPUT","STA?")      ! Clear overload bits
2364    Hw_wait_gbl_rdy                   ! Wait for STA? processed
2366  SUBEND
2368 Appl_rng_inpm:SUB Appl_rng_inpm
2370    !
2372    ! Finds out the ranges and input modes of the inputs and stores them
2374    ! in arrays.
2376    !
2378    COM /Appl_convert/ Inputs$(1:63)[20],INTEGER Num_inputs
2380    COM /Appl_disp_info/ Inpm$(1:63)[4],INTEGER Range(1:63)
2382    INTEGER I
2384    !
2386    ! Do some module queries now, since they only need to be done once
2388    !
2390    FOR I=1 TO Num_inputs
2392      Range(I)=VAL(FNInpt_rsp$(Inputs$(I),"RANGE"))
2394      Inpm$(I)=FNInpt_rsp$(Inputs$(I),"INPUT MODE")
2396    NEXT I
2398  SUBEND
2400 Appl_icode:SUB Appl_icode
2402    !
2404    ! Loads, assembles, and downloads the ICODE program.
2406    ! (Doesn't actually do the load and assemble if they have already
2408    ! been done.)  If the variable Enable_list is set to one instead
2410    ! of zero, a listing of the assembled ICODE program will be sent to
2412    ! file "FRF_ICDLST" in the current directory.
2414    !
2416    COM /Appl_block_id1/ Icode_id,Input_buff_id,Module_list_id
2418    COM /Appl_block_id2/ Output_buff_id,Sp_coef_id,Sp_param_id
2420    COM /Appl_object/ Info$(*),INTEGER Assembled,Object(*)
2422    DIM Source$(0:512)[80]
2424    INTEGER Info_info,Enable_list
2426    !
2428    ! Clear out HP-IB module
2430    !
2432    Hw_cmd("CLR;DISA")
2434    !
2436    ! Set up things for the icode assembler
2438    !
2440    Info_info=1      ! At least 1 since I use DEFBLK_SP and DEFBLK_MAIN
2442    IF Info_info=0 THEN REDIM Info$(0:0)
2444    IF Info_info=1 THEN REDIM Info$(0:40)
2446    IF Info_info=2 THEN REDIM Info$(0:150)
2448    IF NOT Assembled THEN 
2450      Enable_list=0    ! REAL programmers don't need listings
2452      IF Enable_list THEN 
2454        ALLOCATE List$(0:1024)[95]
2456      ELSE
2458        ALLOCATE List$(0:0)[1]
2460      END IF
2462      !
2464      ! Get the ICODE source
2466      !
2468      Appl_icode_src(Source$(*))
2470      !
2472      ! Assemble it
2474      !
2476      Error_count=FNIcode_assemble(Source$(*),Object(*),Info_info,Info$(*),Enable_list,List$(*))
2478      Assembled=1
2480      IF Error_count<>0 THEN 
2482        User_stop("ICODE assembler found errors in the ICODE program")
2484      END IF
2486      !
2488      ! Maybe list it
2490      !
2492      IF Enable_list THEN 
2494        DISP "Listing ICODE to file 'FRF_ICDLST'"
2496        ON ERROR GOTO Appl_purged
2498        PURGE "FRF_ICDLST"
2500 Appl_purged:OFF ERROR 
2502        CREATE ASCII "FRF_ICDLST",100
2504        ASSIGN @Listing TO "FRF_ICDLST"
2506        OUTPUT @Listing;List$(*)
2508        ASSIGN @Listing TO *
2510        DISP 
2512      END IF
2514    END IF
2516    !
2518    ! Download and get some block id's
2520    !
2522    Icode_id=FNIcode_dld(Object(*),1,Info$(*))
2524    Input_buff_id=FNIcode_ext_id("INPUT_BUFF",Info$(*))
2526    Module_list_id=FNIcode_ext_id("MOD_LIST",Info$(*))
2528    Output_buff_id=FNIcode_ext_id("OUTPUT_BUFF",Info$(*))
2530    Sp_coef_id=FNIcode_ext_id("COEF",Info$(*))
2532    Sp_param_id=FNIcode_ext_id("PARAM",Info$(*))
2534    !
2536  SUBEND
2538 Appl_icode_src:SUB Appl_icode_src(Source$(*))
2540    !
2542    ! This is the actual ICODE source used by FRF.  All this subprogram
2544    ! does is read it into an array.
2546    !
2548    I=-1
2550    RESTORE Frf_icode
2552    REPEAT
2554      I=I+1
2556      READ Source$(I)
2558    UNTIL Source$(I)="EL_COMPLETO"
2560    IF I>0 THEN REDIM Source$(0:I)
2562    SUBEXIT
2564    !
2566    !******************************************************************
2568    ! Actual ICODE source for FRF data gathering and signal processing.
2570    !******************************************************************
2572    !
2574 Frf_icode: !
2576    DATA "VAR A 0                 ! General purpose temp var"
2578    DATA "VAR NUM_AVGS 0          ! Number of averages requested"
2580    DATA "VAR AVG_NUM 0           ! Current average number"
2582    DATA "VAR WIND_TYPE 0         ! Type of windowing to use"
2584    DATA "VAR RESTART 0           ! Restart after done?"
2586    DATA "VAR DISP_ALL 0          ! Display each average?"
2588    DATA "VAR ZERO 0              ! Zero variable"
2590    DATA "VAR VALID_LOOPS 0       ! Used by ready ram"
2592    DATA "VAR LOOP_COUNT 1        ! Total loops requested"
2594    DATA "VAR NUM_MODS 2          ! Number of input modules"
2596    DATA "VAR NUM_MODSM1 1        ! Number of input modules minus one"
2598    DATA "VAR NUM_MODSM2 0        ! Number of input modules minus two"
2600    DATA "VAR MOD_NUM 0           ! Current input module"
2602    DATA "VAR BSIZ 1024           ! Transfer size from input modules"
2604    DATA "VAR FFTSIZE 512         ! Number of complex words"
2606    DATA "VAR DATASIZE 401        ! Actual data to look at"
2608    DATA "VAR FLT_BUFSIZE 1024    ! Number of entries in floating average"
2610    DATA "VAR INT_BUFSIZE 2048    ! Number of entries in int fast average"
2612    DATA "VAR DATAOFFSET 112      ! Starting point in complex freq array"
2614    DATA "VAR DATASIZEP1 402      ! Used when swapping sides of FFT output"
2616    DATA "VAR DATASIZEM1 400      ! Used when swapping sides of FFT output"
2618    DATA "VAR DATASIZEX2 1024     ! Number of points in complex freq array"
2620    DATA "VAR DATASIZEX4 2048     ! For when there are no averages"
2622    DATA "VAR DATASIZEX5 2560     ! For fast average array"
2624    DATA "VAR DATASIZEX8 4096     ! For floating average array"
2626    DATA "VAR OFFSET 0            ! General Purpose Pointer"
2628    DATA "VAR OFFSET1 0           ! General Purpose Pointer"
2630    DATA "VAR OFFSET2 0           ! General Purpose Pointer"
2632    DATA "VAR SPWORK_EXP 0        ! Used by DO_MOD to remember an exponent"
2634    DATA "VAR BASE_EXP -27        ! Fast avg init base exp"
2636    !
2638    DATA "CONST FFT 4032          ! Start address of fft operation"
2640    DATA "CONST MAGSQ 4038        ! Start address of mag-square operation"
2642    !
2644    DATA "DEFBLK_MAIN INPUT_BUFF    24576,2 ! Time data from input modules"
2646    DATA "DEFBLK_MAIN MOD_LIST        128,2 ! Module list"
2648    DATA "DEFBLK_MAIN OUTPUT_BUFF   16384,2 ! Floating point output data"
2650    DATA "DEFBLK_SP   BIG_WIND       8192,2 ! Window if loaded externally"
2652    DATA "DEFBLK_SP   WIND           8192,2 ! Actual window"
2654    DATA "DEFBLK_SP   FFT_INPUT      8192,2 ! Input to FFT (time data)"
2656    DATA "DEFBLK_SP   FREQ           8192,2 ! Output of FFT (freq data)"
2658    DATA "DEFBLK_SP   COEF           4096,2 ! Coefficients for FFT"
2660    DATA "DEFBLK_SP   PARAM           128,2 ! Parameters for TMS320 stuff"
2662    DATA "DEFBLK_SP   SPWORK         8192,2 ! TMS320 Work block"
2664    DATA "DEFBLK_SP   SPWORK2        8192,2 ! Another TMS320 work block"
2666    DATA "DEFBLK_MAIN FLT_AVG_ARRAY 94208,2 ! 11 ch. 1K cross spectrum"
2668    DATA "DEFBLK_MAIN INT_AVG_ARRAY 61440,2 ! 12 ch. 1K power spectrum"
2670    DATA "DEFBLK_MAIN TEMP          16384,2 ! Work block for 68000"
2672    !
2674    ! Make ICODE fast (ICODE won't suspend except on waiting type commands)
2676    !
2678    DATA "      F_EXEC 0"
2680    !
2682    ! Initialize a bunch of variables
2684    !
2686    DATA "      V_GET16_INDEXED MOD_LIST,0,BSIZ"
2688    DATA "      V_GET16_INDEXED MOD_LIST,1,LOOP_COUNT"
2690    DATA "      V_GET16_INDEXED MOD_LIST,2,NUM_MODS ! Number of inputs"
2692    DATA "      V_GET16_INDEXED PARAM,7,NUM_AVGS    ! Number of averages"
2694    DATA "      V_GET16_INDEXED PARAM,8,WIND_TYPE   ! Type of windowing"
2696    DATA "      V_GET16_INDEXED PARAM,9,RESTART     ! Restart when done?"
2698    DATA "      V_GET16_INDEXED PARAM,10,DISP_ALL   ! Display each average?"
2700    !
2702    ! We only use about 1/1.28 of the points in an FFT (401 out of 512).
2704    ! Therefore, there's no point in doing calculations on the unused
2706    ! part of the data.  If you want to use the full FFT then DATASIZE
2708    ! should be set equal to FFTSIZE and DATAOFFSET should be set equal
2710    ! to 0
2712    !
2714    DATA "      V_DIV BSIZ,2,FFTSIZE"
2716    DATA "      V_DIV FFTSIZE,128,A"
2718    DATA "      V_MULT A,28,DATAOFFSET"
2720    DATA "      V_MULT A,100,A"
2722    DATA "      V_ADD A,1,DATASIZE"
2724    !
2726    DATA "      V_MULT DATASIZE,2,DATASIZEX2"
2728    DATA "      V_MULT DATASIZE,4,DATASIZEX4"
2730    DATA "      V_MULT DATASIZE,5,DATASIZEX5"
2732    DATA "      V_MULT DATASIZE,8,DATASIZEX8"
2734    DATA "      V_ADD DATASIZE,1,DATASIZEP1"
2736    DATA "      V_SUB DATASIZE,1,DATASIZEM1"
2738    DATA "      V_MULT DATASIZE,NUM_MODS,INT_BUFSIZE"
2740    DATA "      V_SUB NUM_MODS,1,NUM_MODSM1"
2742    DATA "      V_SUB NUM_MODS,2,NUM_MODSM2"
2744    DATA "      V_MULT NUM_MODSM1,DATASIZEX2,FLT_BUFSIZE"
2746    !
2748    DATA "      C_GOSUB INIT_W                       ! Initialize window"
2750    !
2752    ! Get ready for thruput
2754    !
2756    DATA "      F_READY_RAM 1,INPUT_BUFF,0,MOD_LIST,0,VALID_LOOPS"
2758    DATA "      F_KEEP_READY_RAM"
2760    !
2762    ! Start looping forever, doing thruput and then FFTs
2764    !
2766    DATA "      C_BLE ONE_AVG,NUM_AVGS,1  ! If no averaging, jump elsewhere"
2768    !
2770    ! INT_AVG_ARRAY is initialized to 1*2^<base exponent> so that the
2772    ! power spectrum will not be exactly zero at any point.  This is
2774    ! because later we'll be dividing by the power spectrum.  The number
2776    ! it's initialized to is the smallest bit in the average buffer.
2778    !
2780 Start: !
2782    DATA "START:"
2784    DATA "      F_FAST_AVG_INIT INT_AVG_ARRAY,0,INT_BUFSIZE,1,BASE_EXP,BASE_EXP"
2786    DATA "      F_FLOAT_CONST FLT_AVG_ARRAY,0,FLT_BUFSIZE,0"
2788    DATA "      V_CEQUATE 0,AVG_NUM                    ! Average Number 0"
2790    DATA "DO_AVG:"
2792    DATA "      C_GOSUB THPT                          ! Do one average"
2794    DATA "      V_CEQUATE 0,MOD_NUM                    ! Mod_num = 0"
2796    DATA "LOOP:  C_GOSUB DO_MOD                         ! Do a Module"
2798    !
2800    ! MOD_NUM is incremented inside DO_MOD, so don't do it here.
2802    !
2804    DATA "      C_BLE LOOP,MOD_NUM,NUM_MODSM1          ! Loop if not done"
2806    !
2808    DATA "      V_ADD 1,AVG_NUM,AVG_NUM                ! Increment Avg_num"
2810    DATA "      C_BEQ GOT_DATA,DISP_ALL,1              ! If disp_all, jump"
2812    DATA "      C_BLT DO_AVG,AVG_NUM,NUM_AVGS          ! Loop if not done"
2814    !
2816    ! All data is now taken, so set up the Input Buffer as a work block.
2818    !
2820 Got_data: !
2822    DATA "GOT_DATA: F_FAST_AVG_DIV INT_AVG_ARRAY,0,OUTPUT_BUFF,0,DATASIZE,1"
2824    DATA "      F_FLOAT_CONST TEMP,0,DATASIZE,1"
2826    DATA "      F_FLOAT_DIV TEMP,0,OUTPUT_BUFF,0,OUTPUT_BUFF,0,DATASIZE"
2828    DATA "      F_FLOAT_INTRLVE OUTPUT_BUFF,0,OUTPUT_BUFF,0,INPUT_BUFF,0,DATASIZE"
2830    !
2832    ! Work Block (= Input Buffer) is now set up!
2834    ! So, start sending out data.
2836    !
2838    DATA "      C_GOSUB OUT_CMPLX    ! Send out complex spectrums"
2840    !
2842    ! Now send out power spectrums
2844    !
2846    DATA "      V_CEQUATE 0,MOD_NUM"
2848 Pwr: !
2850    DATA "PWR:   V_MULT MOD_NUM,DATASIZEX5,OFFSET"
2852    DATA "      F_FAST_AVG_DIV INT_AVG_ARRAY,OFFSET,OUTPUT_BUFF,0,DATASIZE,AVG_NUM"
2854    DATA "      F_SIGNAL 1                             ! Still more data"
2856    DATA "      F_PAUSE"
2858    DATA "      V_ADD MOD_NUM,1,MOD_NUM"
2860    DATA "      C_BLE PWR,MOD_NUM,NUM_MODSM1"
2862    !
2864    ! Now send out coherence functions
2866    !
2868    DATA "      F_FLOAT_DINTRLVE INPUT_BUFF,0,INPUT_BUFF,0,TEMP,0,DATASIZE"
2870    !
2872    ! Data in TEMP is not used, we just needed a place to put it.
2874    !
2876    DATA "      V_CEQUATE 0,MOD_NUM"
2878 Coh: !
2880    DATA "COH:   V_MULT MOD_NUM,DATASIZEX8,OFFSET"
2882    !
2884    !DATA "      F_FLOAT_TO_SHORT FLT_AVG_ARRAY,OFFSET,FREQ,0,DATASIZEX2"
2886    !DATA "      V_GET32_INDEXED ^FREQ,0,A"
2888    !DATA        V_PUT32_INDEXED,PARAM,0,A
2890    !DATA        C_GOSUB,DO_MAGSQ  ! FREQ in => SPWORK out, inc MOD_NUM
2892    !DATA        F_INT_TO_FLOAT,SPWORK,0,TEMP,0,DATASIZE
2894    !
2896    DATA "      F_FLOAT_CONJ FLT_AVG_ARRAY,OFFSET,TEMP,0,DATASIZE"
2898    DATA "      F_FLOAT_CMULT FLT_AVG_ARRAY,OFFSET,TEMP,0,TEMP,0,DATASIZE"
2900    DATA "      F_FLOAT_DINTRLVE TEMP,0,TEMP,0,OUTPUT_BUFF,0,DATASIZE"
2902    !
2904    ! Data in OUTPUT_BUFF is not used, we just had to put it somewhere.
2906    !
2908    DATA "      F_FLOAT_MULT TEMP,0,INPUT_BUFF,0,TEMP,0,DATASIZE"
2910    DATA "      V_ADD MOD_NUM,1,MOD_NUM"
2912    DATA "      V_MULT MOD_NUM,DATASIZEX5,OFFSET"
2914    DATA "      F_FAST_AVG_DIV INT_AVG_ARRAY,OFFSET,OUTPUT_BUFF,0,DATASIZE,1"
2916    DATA "      F_FLOAT_DIV TEMP,0,OUTPUT_BUFF,0,OUTPUT_BUFF,0,DATASIZE"
2918    DATA "      F_SIGNAL 1                             ! Data ready"
2920    DATA "      F_PAUSE"
2922    DATA "      C_BLE COH,MOD_NUM,NUM_MODSM2"
2924    !
2926    ! Loop if we're displaying each average and we're not done averaging.
2928    !
2930    DATA "      C_BLT DO_AVG,AVG_NUM,NUM_AVGS"
2932    !
2934    ! Loop if we're supposed to restart
2936    !
2938    DATA "      C_BNE START,RESTART,0"
2940    DATA "      C_END"
2942    !
2944    !
2946    ! End of main loop
2948    !
2950 Not_val: !
2952    DATA "NOT_VAL:                      ! Valid loops wan't big enough"
2954    DATA "      F_SIGNAL 2"
2956    DATA "      C_END"
2958    !
2960    !
2962    !*********************************************************************
2964    ! ONE_AVG is the routine used if there is no averaging to be done.
2966    ! The loop is speeded up considerably since there is no need to set
2968    ! up an average buffer and later divide it by the number of averages.
2970    !*********************************************************************
2972    !
2974 One_avg: !
2976    DATA "ONE_AVG: C_GOSUB THPT"
2978    DATA "      V_CEQUATE 0,MOD_NUM                    ! Mod_num = 1"
2980    DATA "LOOP1: C_GOSUB DO_MOD1                        ! Do a Module"
2982    !
2984    ! MOD_NUM was incremented in DO_MOD1, so don't increment here.
2986    !
2988    DATA "      C_BLE LOOP1,MOD_NUM,NUM_MODSM1         ! Loop if not done"
2990    !
2992    ! All data is now taken, so set up the Input Buffer as a work block.
2994    !
2996    DATA "      F_FLOAT_CONST OUTPUT_BUFF,0,DATASIZE,1E-30"
2998    DATA "      F_FLOAT_ADD INT_AVG_ARRAY,0,OUTPUT_BUFF,0,OUTPUT_BUFF,0,DATASIZE"
3000    DATA "      F_FLOAT_CONST TEMP,0,DATASIZE,1"
3002    DATA "      F_FLOAT_DIV TEMP,0,OUTPUT_BUFF,0,OUTPUT_BUFF,0,DATASIZE"
3004    DATA "      F_FLOAT_INTRLVE OUTPUT_BUFF,0,OUTPUT_BUFF,0,INPUT_BUFF,0,DATASIZE"
3006    !
3008    ! Work block (= Input Buffer) is now set up.
3010    ! So, start sending out data.
3012    !
3014    DATA "      C_GOSUB OUT_CMPLX           ! Send out complex spectrums"
3016    !
3018    ! Now send out power spectrums
3020    !
3022    DATA "      V_CEQUATE 0,MOD_NUM"
3024 Pwr1: !
3026    DATA "PWR1:  V_MULT MOD_NUM,DATASIZEX4,OFFSET"
3028    DATA "      F_MOVE_BLOCK INT_AVG_ARRAY,OFFSET,OUTPUT_BUFF,0,DATASIZEX4"
3030    DATA "      F_SIGNAL 1                             ! More data ready"
3032    DATA "      F_PAUSE"
3034    DATA "      V_ADD MOD_NUM,1,MOD_NUM"
3036    DATA "      C_BLE PWR1,MOD_NUM,NUM_MODSM1"
3038    !
3040    ! Now send out coherence functions
3042    !
3044    DATA "      F_FLOAT_DINTRLVE INPUT_BUFF,0,INPUT_BUFF,0,TEMP,0,DATASIZE"
3046    DATA "      F_FLOAT_CONST SPWORK,0,DATASIZE,1E-30"
3048    !
3050    ! Data in TEMP is not used, we just needed a place to put it.
3052    !
3054    DATA "      V_CEQUATE 0,MOD_NUM"
3056 Coh1: !
3058    DATA "COH1:  V_MULT MOD_NUM,DATASIZEX8,OFFSET"
3060    !
3062    !DATA "      F_FLOAT_TO_SHORT FLT_AVG_ARRAY,OFFSET,FREQ,0,DATASIZEX2"
3064    !DATA        V_GET32_INDEXED,^FREQ,0,A
3066    !DATA        V_PUT32_INDEXED,PARAM,0,A
3068    !DATA        C_GOSUB,DO_MAGSQ  ! FREQ in => SPWORK out, inc MOD_NUM
3070    !DATA        F_INT_TO_FLOAT,SPWORK,0,TEMP,0,DATASIZE
3072    !
3074    DATA  "     F_FLOAT_CONJ FLT_AVG_ARRAY,OFFSET,TEMP,0,DATASIZE"
3076    DATA  "     F_FLOAT_CMULT FLT_AVG_ARRAY,OFFSET,TEMP,0,TEMP,0,DATASIZE"
3078    DATA "      F_FLOAT_DINTRLVE TEMP,0,TEMP,0,OUTPUT_BUFF,0,DATASIZE"
3080    !
3082    ! Data in OUTPUT_BUFF is not used, we just had to put it somewhere.
3084    !
3086    DATA "      F_FLOAT_MULT TEMP,0,INPUT_BUFF,0,TEMP,0,DATASIZE"
3088    DATA "      V_ADD MOD_NUM,1,MOD_NUM"
3090    DATA "      V_MULT MOD_NUM,DATASIZEX4,OFFSET"
3092    DATA "      F_FLOAT_ADD INT_AVG_ARRAY,OFFSET,SPWORK,0,OUTPUT_BUFF,0,DATASIZE"
3094    DATA "      F_FLOAT_DIV TEMP,0,OUTPUT_BUFF,0,OUTPUT_BUFF,0,DATASIZE"
3096    DATA "      F_SIGNAL 1                             ! Data ready"
3098    DATA "      F_PAUSE"
3100    DATA "      C_BLE COH1,MOD_NUM,NUM_MODSM2"
3102    !
3104    ! Loop if we're supposed to restart
3106    !
3108    DATA "      C_BNE ONE_AVG,RESTART,0"
3110    DATA "      C_END"
3112    !
3114    !
3116    !*********************************************************************
3118    ! Thpt does the thruput for one average.
3120    !*********************************************************************
3122    !
3124 Thpt: !
3126    DATA "THPT:  F_SIGNAL 4                             ! Ready to TRIG"
3128    DATA "      F_PAUSE"
3130    DATA "      F_THRUPUT 0,1                          ! Do Thruput"
3132    DATA "      C_BNE NOT_VAL,VALID_LOOPS,LOOP_COUNT   ! Branch if error"
3134    DATA "      C_RTS"
3136    !
3138    !
3140    !********************************************************************
3142    ! Subroutine DO_MOD finds data for the module & does ffts of it.
3144    ! This routine is used only if averaging is being done.
3146    !********************************************************************
3148    !
3150 Do_mod: !
3152    DATA "DO_MOD: V_MULT MOD_NUM,BSIZ,A           !start building pointer"
3154    DATA "      V_MULT A,LOOP_COUNT,OFFSET       !have pointer to the data"
3156    DATA "      F_MOVE_BLOCK INPUT_BUFF,OFFSET,FFT_INPUT,0,BSIZ"
3158    DATA "      C_GOSUB DO_FFT                   ! ==> FREQ"
3160    !
3162    ! In DO_FFT, OFFSET and OFFSET2 were calculated.  Also,
3164    ! if the MOD_NUM is 0, a short-to-float was done into OUTPUT_BUFF
3166    !
3168    DATA "      C_GOSUB DO_MAGSQ                 ! ==> SPWORK"
3170    !
3172    ! In DO_MAGSQ, the MOD_NUM was incremented
3174    !
3176    DATA "      V_GET32_INDEXED PARAM,0,SPWORK_EXP"
3178    !
3180    DATA "      F_FAST_AVG_ADD SPWORK,DATAOFFSET,INT_AVG_ARRAY,OFFSET,DATASIZE,SPWORK_EXP"
3182    !
3184    DATA "      C_BEQ REF,MOD_NUM,1 ! Since Mod_num was already incremented"
3186    DATA "      F_SHORT_TO_FLOAT FREQ,DATAOFFSET,TEMP,0,DATASIZEX2"
3188    DATA "      F_FLOAT_CMULT TEMP,0,OUTPUT_BUFF,0,TEMP,0,DATASIZE"
3190    DATA "      F_FLOAT_ADD TEMP,0,FLT_AVG_ARRAY,OFFSET2,FLT_AVG_ARRAY,OFFSET2,DATASIZEX2"
3192    DATA "      C_RTS"
3194    !
3196    DATA "REF:   F_SHORT_CONJ FREQ,DATAOFFSET,TEMP,0,DATASIZE"
3198    !
3200    ! There should be a short-to-float TEMP ==> OUTPUT_BUFF, but it's
3202    ! done in DO_FFT instead, to make things a little faster.
3204    !
3206    DATA "      C_RTS"
3208    !
3210    !
3212    !********************************************************************
3214    ! Subroutine DO_MOD1 finds data for the module & does ffts of it.
3216    ! This routine is used instead of DO_MOD if NO averaging is being done.
3218    !********************************************************************
3220    !
3222 Do_mod1: !
3224    DATA "DO_MOD1: V_MULT MOD_NUM,BSIZ,A          !start building pointer"
3226    DATA "      V_MULT A,LOOP_COUNT,OFFSET       !have pointer to the data"
3228    DATA "      F_MOVE_BLOCK INPUT_BUFF,OFFSET,FFT_INPUT,0,BSIZ"
3230    DATA "      C_GOSUB DO_FFT                   ! ==> FREQ,DATAOFFSET"
3232    !
3234    ! In DO_FFT, OFFSET and OFFSET2 were calculated.  Also,
3236    ! if the MOD_NUM is 0, a short-to-float was done into OUTPUT_BUFF
3238    !
3240    DATA "      C_GOSUB DO_MAGSQ                 ! ==> SPWORK,DATAOFFSET"
3242    !
3244    ! In DO_MAGSQ, MOD_NUM was incremented
3246    !
3248    DATA "      F_INT_TO_FLOAT SPWORK,DATAOFFSET,INT_AVG_ARRAY,OFFSET1,DATASIZE"
3250    !
3252    DATA "      C_BEQ REF,MOD_NUM,1 ! Since Mod_num was already incremented"
3254    DATA "      F_SHORT_TO_FLOAT FREQ,DATAOFFSET,TEMP,0,DATASIZEX2"
3256    DATA "      F_FLOAT_CMULT TEMP,0,OUTPUT_BUFF,0,FLT_AVG_ARRAY,OFFSET2,DATASIZE"
3258    DATA "      C_RTS"
3260    !
3262    DATA "REF:   F_SHORT_CONJ FREQ,DATAOFFSET,TEMP,0,DATASIZE"
3264    !
3266    ! There should be a short-to-float TEMP ==> OUTPUT_BUFF, but it's
3268    ! done in DO_FFT instead, to make things a little faster.
3270    !
3272    DATA "      C_RTS"
3274    !
3276    !
3278    !*********************************************************************
3280    !DO FFT SUBROUTINE, normal output selected
3282    !*********************************************************************
3284    !
3286    !the next line reinitializes the time exponent (is overwritten by
3288    ! the FFT/magsq operation
3290    !
3292 Do_fft: !
3294    DATA "DO_FFT: V_PUT32_INDEXED PARAM,0,ZERO"
3296    DATA "      F_SIG_PROC FFT,0,5,PARAM,0,COEF,0,WIND,0,FFT_INPUT,0,SPWORK,0"
3298    !
3300    ! Try to do a little parallel processing here.
3302    !
3304    DATA "      V_MULT MOD_NUM,DATASIZEX5,OFFSET  ! For averaging"
3306    DATA "      V_MULT MOD_NUM,DATASIZEX4,OFFSET1 ! For no averaging"
3308    DATA "      V_SUB MOD_NUM,1,A"
3310    DATA "      V_MULT A,DATASIZEX8,OFFSET2       ! Used by both"
3312    DATA "      C_BNE FFT_W,MOD_NUM,1             ! Jump if MOD_NUM<>1"
3314    DATA "      F_SHORT_TO_FLOAT TEMP,0,OUTPUT_BUFF,0,DATASIZEX2"
3316    !
3318    ! We may have some more time, but there's not much to do
3320    !
3322    DATA "FFT_W: C_SP_BEQ FFT_W,2"
3324    DATA "      F_MOVE_BLOCK SPWORK,0,FREQ,FFTSIZE,DATASIZEP1 ! Swap FFT"
3326    DATA "      V_ADD FFTSIZE,DATAOFFSET,A"
3328    DATA "      F_MOVE_BLOCK SPWORK,A,FREQ,DATAOFFSET,DATASIZEM1 !"
3330    DATA "      V_GET32_INDEXED PARAM,0,A       !get block exp"
3332    DATA "      V_PUT32_INDEXED ^FREQ,0,A    !save block exp"
3334    DATA "      C_RTS"
3336    !
3338    !
3340    !*******************************************************************
3342    ! DO_MAGSQ - Do a Magnitude Squared on the FREQ output of the FFT.
3344    !            Output goes to SPWORK2.
3346    !*******************************************************************
3348    !
3350 Do_magsq: !
3352    DATA "DO_MAGSQ: F_SIG_PROC MAGSQ,0,3,PARAM,0,FREQ,0,SPWORK,0"
3354    !
3356    ! Do some parallel processing - increment MOD_NUM
3358    !
3360    DATA "      V_ADD MOD_NUM,1,MOD_NUM"
3362    !
3364    DATA "MAGSQ_W: C_SP_BEQ MAGSQ_W,2"
3366    DATA "      V_GET32_INDEXED PARAM,0,A"
3368    DATA "      V_PUT32_INDEXED ^SPWORK,0,A"
3370    DATA "      C_RTS"
3372    !
3374    !
3376    !********************************************************************
3378    ! OUT_CMPLX sends out complex frequency spectrum data.  It assumes
3380    ! that the cross-spectrum is available in FLT_AVG_ARRAY and that
3382    ! INPUT_BUFF holds 1/<reference power spectrum>.
3384    ! There is a frequency spectrum for all inputs except the reference
3386    ! input - therefore, this loops NUM_MODS-1 times.
3388    !********************************************************************
3390    !
3392 Out_cmplx: !
3394    DATA "OUT_CMPLX: V_CEQUATE 0,MOD_NUM                ! Modnum=0"
3396    DATA "CMPLX: V_MULT MOD_NUM,DATASIZEX8,OFFSET"
3398    DATA "      F_FLOAT_MULT FLT_AVG_ARRAY,OFFSET,INPUT_BUFF,0,OUTPUT_BUFF,0,DATASIZEX2"
3400    DATA "      F_SIGNAL 1                             ! Data is ready"
3402    DATA "      F_PAUSE"
3404    DATA "      V_ADD MOD_NUM,1,MOD_NUM                ! Increment modnum"
3406    DATA "      C_BLE CMPLX,MOD_NUM,NUM_MODSM2"
3408    DATA "      C_RTS"
3410    !
3412    !
3414    !*******************************************************************
3416    ! Subroutine INIT_WIND forms the correctly sized window on the
3418    ! tms320 ram by sampling an 8k window block in the 68000 ram
3420    !*******************************************************************
3422    !
3424    DATA "INIT_W: C_BEQ FLAT_TOP,WIND_TYPE,1"
3426    !
3428    DATA "      F_FLOAT_WINGEN INPUT_BUFF,0,FFTSIZE,2,0.499984,-.499984"
3430    DATA "      C_GOTO W_CONT"
3432    DATA "FLAT_TOP: F_FLOAT_WINGEN INPUT_BUFF,0,FFTSIZE,4"
3434    !
3436    ! Normal flat-top coefficients are:
3438    !       0.994484 / 2, -0.955728, 0.539289, -0.0915810
3440    ! We have to normalize so that the maximum point is 32767
3442    !
3444    DATA ".     0.954423166665,-1.8344567519,1.03512960516,-0.175783678825"
3446    DATA "W_CONT: F_FLOAT_TO_SHORT INPUT_BUFF,0,OUTPUT_BUFF,0,FFTSIZE"
3448    DATA "      F_SHORT_INTRLVE OUTPUT_BUFF,0,OUTPUT_BUFF,0,WIND,0,FFTSIZE"
3450    DATA "      C_RTS"
3452    !
3454    !
3456    DATA "      V_DIV 8192,FFTSIZE,A               !A=8192/FFTSIZE"
3458    DATA "      F_SAMPLE BIG_WIND,0,WIND,0,BSIZ,2,A"
3460    DATA "      C_RTS"
3462    !
3464    DATA "END:   C_END"
3466    DATA       "EL_COMPLETO"
3468    !
3470  SUBEND
3472 Appl_help:SUB Appl_help
3474    !
3476    ! This is a help routine that can be called while the user is
3478    ! running the FRF application.
3480    !
3482    DIM A$[160]
3484    RESTORE Appl_help_page1
3486    GOSUB Appl_show_page
3488    RESTORE Appl_help_page2
3490    GOSUB Appl_show_page
3492    RESTORE Appl_help_page3
3494    GOSUB Appl_show_page
3496    RESTORE Appl_help_page4
3498    GOSUB Appl_show_page
3500    RESTORE Appl_help_page5
3502    GOSUB Appl_show_page
3504    SUBEXIT
3506 Appl_show_page:READ A$
3508    User_clr_scr
3510    WHILE A$<>"***END***"
3512      OUTPUT CRT;A$
3514      READ A$
3516    END WHILE
3518    OUTPUT KBD USING "#,K";"ÿ#Yÿ<"
3520    INPUT "Type 'Y' to continue, anything else to leave...",A$
3522    IF UPC$(A$[1;1])<>"Y" THEN SUBEXIT
3524    RETURN 
3526 Appl_help_page1: !
3528    DATA "              Help for FRF Application"
3530    DATA ""
3532    DATA "This is the Frequency Response Application for the HP3565"
3534    DATA "system.  In it you can display the Transfer Function between"
3536    DATA "any input module and a specified reference input module.  You"
3538    DATA "can also display the Coherence associated with a transfer"
3540    DATA "function, the Cross Spectrum between an input and the"
3542    DATA "reference, and you can display the Power Spectrum of a single"
3544    DATA "input module."
3546    DATA ""
3548    DATA "This application assumes that the Configuration Menu has"
3550    DATA "already been used to assign labels to the modules in your"
3552    DATA "system, and to specify which modules will be active.  If you"
3554    DATA "haven't done this, and you want to, use the EXIT key and then"
3556    DATA "the CONFIG key to enter the Configuration Menu.  Modules that"
3558    DATA "are inactive are treated as though they are not in the system"
3560    DATA "at all."
3562    DATA "***END***"
3564 Appl_help_page2: !
3566    DATA "         Help for FRF Application - Page 2"
3568    DATA ""
3570    DATA "There are four keys that are used to set up a Frequency"
3572    DATA "Response measurement - SOURCE SETUP, INPUT SETUP, DISPLAY"
3574    DATA "SETUP, and MEASURE SETUP."
3576    DATA ""
3578    DATA "The SOURCE SETUP key is used to set up source modules."
3580    DATA "When the system is first powered up, one source module will"
3582    DATA "start out in RANDOM mode and the rest will be OFF.  Any"
3584    DATA "source in RANDOM or BURST RANDOM mode will automatically track"
3586    DATA "the center frequency and frequency span of the input modules"
3588    DATA "in the system.  At powerup, all sources start at minimum"
3590    DATA "amplitude (-58 dBVp).  It will normally be necessary to"
3592    DATA "increase this amplitude to an appropriate level.  When the"
3594    DATA "SOURCE SETUP menu is exited, the source module is started."
3596    DATA "However, if the source is in a trigger mode other than off,"
3598    DATA "it may not start until a trigger is received."
3600    DATA "***END***"
3602 Appl_help_page3: !
3604    DATA "         Help for FRF Application - Page 3"
3606    DATA ""
3608    DATA "The INPUT SETUP key is used to setup input modules."
3610    DATA "When the system powers up, one input module will be in"
3612    DATA "SEND trigger mode, and the others will be in RECEIVE trigger"
3614    DATA "mode.  At least one module (input or source) should normally"
3616    DATA "be in SEND trigger mode, so that the system will trigger."
3618    DATA "The inputs start out at range 0 dBVp, and will usually"
3620    DATA "need to have their ranges changed to appropriate levels."
3622    DATA "The Autorange function is useful if the source module is"
3624    DATA "already going, but it takes at least 20 seconds, and will"
3626    DATA "not always work correctly if the source is in a burst or"
3628    DATA "pulse mode."
3630    DATA "***END***"
3632 Appl_help_page4: !
3634    DATA "         Help for FRF Application - Page 4"
3636    DATA ""
3638    DATA "The DISPLAY SETUP key is used to change what is displayed"
3640    DATA "on the screen.  Each line in the menu corresponds to a trace"
3642    DATA "which could be plotted.  The trace will not actually be plotted"
3644    DATA "unless it is made active.  There are four possible trace"
3646    DATA "functions which can be plotted - Frequency Response, Power"
3648    DATA "Spectrum, Coherence, and Cross Spectrum.  All of these"
3650    DATA "functions except 'Power Spectrum' require two channels, and"
3652    DATA "use the reference input for the second channel.  The 'Reference"
3654    DATA "Input' column is in the menu to remind you of which channel is"
3656    DATA "the reference.  To change the reference input, use the MEASURE"
3658    DATA "SETUP menu."
3660    DATA ""
3662    DATA "Trace type 'Mag' always means Log Magnitude.  'Lin Mag',"
3664    DATA "'Real', and 'Imag' are always on a linear scale."
3666    DATA "***END***"
3668 Appl_help_page5: !
3670    DATA "         Help for FRF Application - Page 5"
3672    DATA ""
3674    DATA "The MEASURE SETUP key is used to change the nature of the"
3676    DATA "measurement that is being made.  Averaging and FFT Window"
3678    DATA "Type, and the frequency span and center frequency can all"
3680    DATA "be set here."
3682    DATA ""
3684    DATA "Any of the four menus can be entered without aborting a"
3686    DATA "measurement that is in progress.  However, changing anything"
3688    DATA "in any menu except the DISPLAY SETUP menu will stop the"
3690    DATA "measurement.  Any current data is thrown away unless the"
3692    DATA "change was in the SOURCE SETUP menu.  While you are in any"
3694    DATA "menu, the measurement is temporarily paused."
3696    DATA ""
3698    DATA "Changes can be made in the DISPLAY SETUP menu without affecting"
3700    DATA "a measurement and without destroying any data.  You can do a"
3702    DATA "complete measurement and later decide what data you need to"
3704    DATA "display."
3706    DATA "***END***"
3708  SUBEND
3710 Meas_meas:SUB Meas_meas
3712    !
3714    ! This is called once, after this file is loaded.  It contains
3716    ! common declarations, and initializes variables that never
3718    ! change.
3720    !
3722    COM /Meas_sprd/ Box$(1:2,1:14)[40],Title$(1:2,0:2)[40],Prompt$(1:14)[80]
3724    COM /Meas_sprd_num/ Col_width(1:2),Modify_col,INTEGER Max_row,Max_col
3726    COM /Meas_mod_labels/ Inpt_labels$(1:63)[20]
3728    COM /Meas_mod_counts/ INTEGER Inpt_count,Current_inpt
3730    COM /Meas_cmnd/ Cmnd$(2:5)[20],Def_value$(2:5)[20]
3732    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
3734    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
3736    COM /Meas_rowcol/ Row,Col,Start_row
3738    COM /Meas_bsiz_limit/ INTEGER Bsiz_limit
3740    COM /Meas_choices/ Choices$(1:4,1:5)[20]
3742    !
3744    ! Box$ is the array of boxes for the measurement spreadsheet.
3746    ! Title$ is the array of titles for the columns in the spreadsheet.
3748    ! Prompt$ is the array of prompts for the columns in the spreadsheet.
3750    ! Col_width is the array of column widths for the spreadsheet.
3752    ! Modify_col is the first column in the spreadsheet that the user can
3754    !    modify.
3756    ! Max_row and Max_col indicate the size of the spreadsheet.
3758    ! Inpt_labels$ is an array of the legal input labels.
3760    ! Inpt_count is the number of inputs available.
3762    ! Current_inpt is the currently selected reference input.
3764    ! Cmnd$ is an array of input commands that correspond to some of the
3766    !    rows in the spreadsheet.
3768    ! Def_value$ is an array of the reset values for the commands in the
3770    !    Cmnd$ array.
3772    ! Cmnd_start through Inpt_r are names for the various rows in the
3774    !    spreadsheet.
3776    ! Row, Col, and Start_row define the cursor position in the
3778    !    spreadsheet.
3780    ! Bsiz_limit is the maximum value for the complex FFT size, given
3782    !    the number of input modules and the limitations of memory in
3784    !    the HP-IB module.
3786    ! Choices$ is a list of the legal choices to go in the boxes in
3788    !    some of the rows of the spreadsheet.
3790    !
3792    Meas_powerup
3794  SUBEND
3796 Meas_powerup:SUB Meas_powerup
3798    !
3800    ! This is called only by Meas_meas, and only once after this file
3802    ! is loaded.  It initializes some of the spreadsheet, but not all
3804    ! of it (the rest is done in Meas_init or Meas_reset).
3806    !
3808    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3810    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
3812    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
3814    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
3816    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
3818    COM /Meas_choices/ Choices$(*)
3820    INTEGER Row,Counter
3822    !
3824    Cmnd_start=2                    !  2
3826    Cmnd_stop=Cmnd_start+3          !  5
3828    Av_r=Cmnd_stop+3                !  8
3830    Numav_r=Av_r+1                  !  9
3832    Av_type_r=Numav_r+1             ! 10
3834    Restart_r=Av_type_r+1           ! 11
3836    Window_r=Restart_r+1            ! 12
3838    Log_freq_r=Window_r+1           ! 13
3840    Inpt_r=Log_freq_r+1             ! 14
3842    !
3844    RESTORE Meas_data
3846    FOR Row=Cmnd_start TO Cmnd_stop
3848      READ Cmnd$(Row),Def_value$(Row),Box$(1,Row),Prompt$(Row)
3850    NEXT Row
3852    !
3854    REDIM Choices$(Av_type_r:Log_freq_r,1:5)
3856    RESTORE Meas_data2
3858    FOR Row=Av_type_r TO Log_freq_r
3860      Counter=0
3862      REPEAT
3864        Counter=Counter+1
3866        READ Choices$(Row,Counter)
3868      UNTIL Choices$(Row,Counter)="" OR Counter=5
3870    NEXT Row
3872    !
3874    Max_col=2
3876    Modify_col=2
3878    Max_row=Inpt_r
3880    Title$(1,1)="Item"
3882    Title$(1,2)=""
3884    Title$(2,1)="Value"
3886    Title$(2,2)=""
3888    Title$(1,0)="Measurement Setup"
3890    Col_width(1)=40
3892    Col_width(2)=20
3894    !
3896    Box$(1,1)="****** Setups For All Inputs ******"
3898    Box$(1,Cmnd_stop+1)=""
3900    Box$(1,Cmnd_stop+2)="******  Measurement  Setups  ******"
3902    Box$(1,Av_r)="Averaging  (off/on)     ->"
3904    Box$(1,Numav_r)="Number Of Averages      ->"
3906    Box$(1,Av_type_r)="Average Display Mode    ->"
3908    Box$(1,Restart_r)="Restart Mode            ->"
3910    Box$(1,Window_r)="Window Type             ->"
3912    Box$(1,Log_freq_r)="Frequency Axis          ->"
3914    Box$(1,Inpt_r)="Reference Input         ->"
3916    !
3918    Box$(2,1)=""
3920    Box$(2,Cmnd_stop+1)=""
3922    Box$(2,Cmnd_stop+2)=""
3924    !
3926    Prompt$(1)=""
3928    Prompt$(Cmnd_stop+1)=""
3930    Prompt$(Cmnd_stop+2)=""
3932    Prompt$(Av_r)="Average Mode: OFf, ON"
3934    Prompt$(Numav_r)="Enter Number of Averages"
3936    Prompt$(Av_type_r)="Average Type: Last average, Every average"
3938    Prompt$(Restart_r)="Restart Mode: Restart when done, Stop when done"
3940    Prompt$(Window_r)="FFT window type: Hann, Flat top, Rectangular"
3942    Prompt$(Log_freq_r)="Frequency Axis: Linear Frequency, Log Frequency"
3944    Prompt$(Inpt_r)="Enter Label of Reference Input"
3946    !
3948 Meas_data:!
3950    DATA "BLOCK SIZE",       "512",   "Complex FFT Size        ->"
3952    DATA "Enter Complex FFT Size"
3954    DATA "SPAN",             "51200", "Frequency Span (Hz)     ->"
3956    DATA "Enter Span in Hz"
3958    DATA "CENTER FREQUENCY", "25600", "Center Frequency (Hz)   ->"
3960    DATA "Enter Center Frequency in Hz"
3962    DATA "TRIGGER DELAY",    "0",     "Trigger Delay (samples) ->"
3964    DATA "Enter Trigger Delay in Number of Samples"
3966    !
3968 Meas_data2:!
3970    DATA "Last Average", "Every Average"
3972    DATA ""
3974    DATA "Restart When Done", "Stop When Done"
3976    DATA ""
3978    DATA "Hann", "Flat Top", "Rectangular"
3980    DATA ""
3982    DATA "Linear Frequency", "Log Frequency"
3984    DATA ""
3986  SUBEND
3988 Meas_init:SUB Meas_init
3990    !
3992    ! This is called to initialize the measurement spreadsheet,
3994    ! after a configuration change or when the FRF application
3996    ! starts.  It also sets up the inputs and sources to interrupt
3998    ! or SRQ on various events.
4000    !
4002    COM /Meas_mod_labels/ Inpt_labels$(*)
4004    COM /Meas_mod_counts/ INTEGER Inpt_count,Current_inpt
4006    COM /Meas_rowcol/ Row,Col,Start_row
4008    COM /Meas_bsiz_limit/ INTEGER Bsiz_limit
4010    COM /Meas_choices/ Choices$(*)
4012    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4014    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
4016    INTEGER I
4018    REDIM Choices$(Av_type_r:Log_freq_r,1:5)
4020    !
4022    ! Get Input labels
4024    !
4026    Cnfg_labels("ALL INPUT",Inpt_labels$(*),Temp)
4028    Inpt_count=Temp
4030    IF Inpt_count>24 THEN Inpt_count=24
4032    !
4034    ! Initialize upper limit on block size
4036    !
4038    Bsiz_limit=2048
4040    IF Inpt_count>6 THEN Bsiz_limit=1024
4042    IF Inpt_count>12 THEN Bsiz_limit=512
4044    !
4046    Meas_reset
4048    !
4050    ALLOCATE Srce_labels$(1:63)[20]
4052    Cnfg_labels("ALL SOURCE",Srce_labels$(*),Srce_count)
4054    !
4056    ! Setup Inputs (and Sources)
4058    !
4060    Inpt_cmd("ALL INPUT","ZOOM","ON")
4062    Inpt_cmd("ALL INPUT","TRANSFER MODE","BLOCK")
4064    !
4066    Inpt_cmd("ALL INPUT","SRQ MASK","0")
4068    Inpt_cmd("ALL INPUT","INTR MASK","0")
4070    Inpt_cmd("ALL INPUT","CLASM","50")
4072    FOR I=1 TO Inpt_count
4074      Inpt_cmd(Inpt_labels$(I),"CLASP","50")
4076    NEXT I
4078    ! SRQ on Block Available from input.
4080    ! INTR on ERR, FSFAST, or FIFOOVR from input.
4082    Srq$=VAL$(FNInpt_str_2_stat("BAV"))
4084    Intr$=VAL$(FNInpt_str_2_stat("ERROR,FSFAST,FIFOOVR"))
4086    Hw_gbl_cmd(50,"RQS "&Srq$)
4088    Hw_gbl_cmd(50,"INTR "&Intr$)
4090    !
4092    Inpt_cmd(Inpt_labels$(Current_inpt),"TRIG MODE","SEND")
4094    IF Srce_count>0 THEN 
4096      Srce_cmd("ALL SOURCE","CLASP","50")
4098      ! Interrupt on ISHT, ERR, OVLD, MSHT, or FSFAST from a source
4100      Srce_cmd("ALL SOURCE","INTR MASK",VAL$(FNSrce_str_2_stat("ISHT,ERROR,OVLD,MSHT,FSFAST")))
4102      Srce_cmd("ALL SOURCE","RAMP","4096")
4104      Srce_cmd(Srce_labels$(1),"OUTPUT MODE","RANDOM")
4106    END IF
4108    DEALLOCATE Srce_labels$(*)
4110    !
4112    ! Initialize Spreadsheet position
4114    !
4116    Row=2
4118    Col=2
4120    Start_row=1
4122    !
4124  SUBEND
4126 Meas_spread:SUB Meas_spread(Changed,New_ref,Disp_change)
4128    !
4130    ! This brings up the measurement spreadsheet.  The spreadsheet
4132    ! is used to set: FFT size, frequency span, center frequency,
4134    ! trigger delay, averaging mode, restart mode, window type,
4136    ! linear or log frequency, and the reference input.
4138    ! The spreadsheet is exited when one of the four firmkeys
4140    ! is pressed.  If the spreadsheet has changed in any way,
4142    ! the source modules will be started when the spreadsheet
4144    ! is exited.  The parameter Changed is set to one if anything
4146    ! in the spreadsheet changed except the Linear/Log Frequency Row.
4148    ! The parameter New_ref is set to one if the reference module
4150    ! selected is changed.  The parameter Disp_change is set to one
4152    ! if the Linear/Log Frequency Row is changed.
4154    !
4156    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4158    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
4160    COM /Meas_mod_labels/ Inpt_labels$(*)
4162    COM /Meas_mod_counts/ INTEGER Inpt_count,Current_inpt
4164    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
4166    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4168    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
4170    COM /Meas_rowcol/ Row,Col,Start_row
4172    COM /Meas_bsiz_limit/ INTEGER Bsiz_limit
4174    COM /Meas_choices/ Choices$(*)
4176    DIM New_entry$[160]
4178    INTEGER Done,Dummy,I
4180    Changed=0
4182    New_ref=0
4184    Disp_change=0
4186    !
4188    ! Define softkeys.  Keys 1 through 4 are 'firmkeys'
4190    !
4192    ON KEY 5 LABEL FNUser_keylabel$("Reset") CALL User_key5isr
4194    ON KEY 6 LABEL "" CALL User_key6isr
4196    ON KEY 7 LABEL FNUser_keylabel$("Prev") CALL User_key7isr
4198    ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
4200    !
4202    User_clr_scr
4204    !
4206    ! Now call spreadsheet.
4208    !
4210    Done=0
4212    REPEAT
4214      User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
4216      SELECT FNUser_check_key
4218      CASE 0
4220        GOSUB Meas_new_entry
4222      CASE 5
4224        Dummy=FNUser_get_key
4226        Meas_reset
4228        GOSUB Meas_chk_change
4230        New_ref=1
4232      CASE 6
4234        BEEP 
4236        Dummy=FNUser_get_key
4238      CASE 7     ! Prev
4240        Dummy=FNUser_get_key
4242        GOSUB Meas_prev
4244      CASE 8     ! Next
4246        Dummy=FNUser_get_key
4248        GOSUB Meas_next
4250      CASE ELSE  ! A softkey, but not one of mine.
4252        IF Changed THEN 
4254          Srce_cmd("ALL SOURCE","SYNC","OFF")
4256          Srce_cmd("ALL SOURCE","START")
4258        END IF
4260        Done=1
4262      END SELECT
4264    UNTIL Done
4266    User_clr_scr
4268    SUBEXIT
4270    !
4272 Meas_new_entry:!
4274    New_entry$=UPC$(TRIM$(New_entry$))
4276    SELECT Row
4278    CASE Cmnd_start                   ! It's a global BLOCK SIZE command
4280      ON ERROR GOTO Meas_bad_bsiz
4282      IF VAL(New_entry$)<257 THEN New_entry$="512"
4284      IF VAL(New_entry$)>Bsiz_limit THEN New_entry$=VAL$(Bsiz_limit)
4286      OFF ERROR 
4288      GOSUB Meas_chk_change
4290      New_entry$=VAL$(VAL(New_entry$)*2)
4292      Inpt_cmd("ALL INPUT","TBLK",New_entry$)
4294      Inpt_cmd("ALL INPUT",Cmnd$(Row),New_entry$)
4296      Srce_cmd("ALL SOURCE",Cmnd$(Row),New_entry$)
4298      Box$(2,Row)=VAL$(VAL(FNInpt_rsp$(Box$(2,Inpt_r),Cmnd$(Row))) DIV 2)
4300      Temp=VAL(Box$(2,Cmnd_stop))     ! Get Trigger Delay
4302      IF Temp<0 AND ABS(Temp)>=VAL(Box$(2,Row))*2 THEN 
4304        Inpt_cmd("ALL INPUT",Cmnd$(Cmnd_stop),VAL$(-VAL(Box$(2,Row))*2+2))
4306        Box$(2,Cmnd_stop)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),Cmnd$(Cmnd_stop)))
4308      END IF
4310 Meas_bad_bsiz:OFF ERROR 
4312    CASE Cmnd_start+1                 ! SPAN
4314      ON ERROR GOTO Meas_bad_span
4316      IF VAL(New_entry$)>102400.0 THEN New_entry$="102400.0"
4318      IF VAL(New_entry$)<.3 THEN New_entry$=".3"
4320      OFF ERROR 
4322      GOSUB Meas_chk_change
4324      Inpt_cmd("ALL INPUT","SPAN",New_entry$)
4326      Srce_cmd("ALL SOURCE","SPAN",New_entry$)
4328      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),"SPAN"))
4330 Meas_bad_span:OFF ERROR 
4332    CASE Cmnd_start+2                 ! CF
4334      GOSUB Meas_chk_change
4336      Inpt_cmd("ALL INPUT",Cmnd$(Row),New_entry$)
4338      Srce_cmd("ALL SOURCE",Cmnd$(Row),New_entry$)
4340      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),Cmnd$(Row)))
4342    CASE Cmnd_stop                    ! TRIGGER DELAY
4344      GOSUB Meas_chk_change
4346      ON ERROR GOTO Meas_bad_tdly
4348      Temp=VAL(New_entry$)
4350      OFF ERROR 
4352      IF Temp<0 AND ABS(Temp)>=VAL(Box$(2,Cmnd_start))*2 THEN 
4354        Temp=-VAL(Box$(2,Cmnd_start))*2+2   ! Limit trigger delay to < BSIZ
4356      END IF
4358      New_entry$=VAL$((Temp DIV 2)*2)
4360      Inpt_cmd("ALL INPUT",Cmnd$(Row),New_entry$)
4362      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),Cmnd$(Row)))
4364 Meas_bad_tdly:OFF ERROR 
4366    CASE Av_r                         ! Set averaging on or off
4368      IF New_entry$[1;2]="ON" THEN 
4370        Box$(2,Row)="ON"
4372        GOSUB Meas_chk_change
4374      ELSE
4376        IF New_entry$[1;2]="OF" THEN 
4378          Box$(2,Row)="OFF"
4380          GOSUB Meas_chk_change
4382        ELSE
4384          BEEP 
4386        END IF
4388      END IF
4390    CASE Numav_r                 ! Set Number of averages
4392      ON ERROR GOTO Meas_no_number
4394      Temp=VAL(New_entry$)
4396      OFF ERROR 
4398      IF Temp<1 THEN Temp=1
4400      IF Temp>32767 THEN Temp=32767
4402      Box$(2,Row)=VAL$(PROUND(Temp,0))
4404      GOSUB Meas_chk_change
4406 Meas_no_number:OFF ERROR 
4408    CASE Av_type_r TO Log_freq_r ! Set window, Restart, Avg type, Freq axis
4410      Lib_match2(New_entry$,Choices$(*),(Row),Found,Choice_num)
4412      IF Found THEN 
4414        Box$(2,Row)=Choices$(Row,Choice_num)
4416        IF Row<>Log_freq_r THEN 
4418          GOSUB Meas_chk_change
4420        ELSE
4422          Disp_change=1     ! axis change doesn't need to stop measurements
4424        END IF
4426      ELSE
4428        BEEP 
4430      END IF
4432    CASE Inpt_r                  ! Set a new reference input
4434      Lib_match1(New_entry$,Inpt_labels$(*),Found,Choice_num)
4436      IF Found THEN 
4438        IF Current_inpt<>Choice_num THEN 
4440          Box$(2,Row)=Inpt_labels$(Choice_num)
4442          Current_inpt=Choice_num
4444          New_ref=1
4446          GOSUB Meas_chk_change
4448        END IF
4450      ELSE
4452        BEEP 
4454      END IF
4456    CASE ELSE
4458      BEEP 
4460    END SELECT
4462    RETURN 
4464    !
4466 Meas_prev:!
4468    SELECT Row
4470    CASE Av_r
4472      GOSUB Meas_toggle        ! Toggle average mode or arm mode
4474    CASE Inpt_r                ! Go to next input
4476      Current_inpt=(Current_inpt-2+Inpt_count) MOD Inpt_count+1
4478      Box$(2,Inpt_r)=Inpt_labels$(Current_inpt)
4480      New_ref=1
4482      GOSUB Meas_chk_change
4484    CASE Numav_r
4486      Box$(2,Row)=VAL$(MAX(VAL(Box$(2,Row))-1,1))
4488      GOSUB Meas_chk_change
4490    CASE Av_type_r TO Log_freq_r
4492      I=1
4494      WHILE Box$(2,Row)<>Choices$(Row,I)
4496        I=I+1
4498      END WHILE
4500      I=((I+3) MOD 5)+1     ! Subtract 1, but convert 0 to 5
4502      WHILE Choices$(Row,I)=""
4504        I=I-1
4506      END WHILE
4508      Box$(2,Row)=Choices$(Row,I)
4510      IF Row<>Log_freq_r THEN 
4512        GOSUB Meas_chk_change
4514      ELSE
4516        Disp_change=1
4518      END IF
4520    CASE Cmnd_start            ! Block size command
4522      Dummy=VAL(Box$(2,Row))
4524      IF Dummy<=512 THEN 
4526        Dummy=Bsiz_limit
4528      ELSE
4530        Dummy=Dummy DIV 2
4532      END IF
4534      Dummy=Dummy*2
4536      GOSUB Meas_chk_change
4538      Inpt_cmd("ALL INPUT","BLOCK SIZE",VAL$(Dummy))
4540      Inpt_cmd("ALL INPUT","TBLK",VAL$(Dummy))
4542      Srce_cmd("ALL SOURCE","BLOCK SIZE",VAL$(Dummy))
4544      Box$(2,Row)=VAL$(VAL(FNInpt_rsp$(Box$(2,Inpt_r),"BLOCK SIZE")) DIV 2)
4546      Temp=VAL(Box$(2,Cmnd_stop))
4548      IF Temp<0 AND ABS(Temp)>=VAL(Box$(2,Row))*2 THEN 
4550        Inpt_cmd("ALL INPUT",Cmnd$(Cmnd_stop),VAL$(-VAL(Box$(2,Row))*2+2))
4552        Box$(2,Cmnd_stop)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),Cmnd$(Cmnd_stop)))
4554      END IF
4556    CASE Cmnd_start+1          ! Span command
4558      Real_dummy=VAL(Box$(2,Row))
4560      IF Real_dummy>102400.0 THEN Real_dummy=102400.0
4562      IF Real_dummy<.4 THEN Real_dummy=204800.0
4564      GOSUB Meas_chk_change
4566      Inpt_cmd("ALL INPUT","SPAN",VAL$(Real_dummy/2.))
4568      Srce_cmd("ALL SOURCE","SPAN",VAL$(Real_dummy/2.))
4570      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),"SPAN"))
4572    CASE Cmnd_stop             ! Trigger Delay command
4574      Real_dummy=VAL(Box$(2,Row))
4576      GOSUB Meas_chk_change
4578      Real_dummy=Real_dummy-2
4580      IF Real_dummy<0 AND ABS(Real_dummy)>=VAL(Box$(2,Cmnd_start))*2 THEN 
4582        Real_dummy=-VAL(Box$(2,Cmnd_start))*2+2
4584      END IF
4586      Inpt_cmd("ALL INPUT","TRIGGER DELAY",VAL$(Real_dummy))
4588      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),"TRIGGER DELAY"))
4590    END SELECT
4592    RETURN 
4594    !
4596 Meas_next:!
4598    SELECT Row
4600    CASE Av_r
4602      GOSUB Meas_toggle        ! Toggle average mode or arm mode
4604    CASE Inpt_r                ! Go to next input
4606      Current_inpt=Current_inpt MOD Inpt_count+1
4608      Box$(2,Inpt_r)=Inpt_labels$(Current_inpt)
4610      New_ref=1
4612      GOSUB Meas_chk_change
4614    CASE Numav_r
4616      Box$(2,Row)=VAL$(MIN(VAL(Box$(2,Row))+1.,32767))
4618      GOSUB Meas_chk_change
4620    CASE Av_type_r TO Log_freq_r
4622      I=1
4624      WHILE Box$(2,Row)<>Choices$(Row,I)
4626        I=I+1
4628      END WHILE
4630      I=(I MOD 5)+1     ! Add 1, but convert 6 to 1
4632      IF Choices$(Row,I)="" THEN I=1
4634      Box$(2,Row)=Choices$(Row,I)
4636      IF Row<>Log_freq_r THEN 
4638        GOSUB Meas_chk_change
4640      ELSE
4642        Disp_change=1
4644      END IF
4646    CASE Cmnd_start            ! Block size command
4648      Dummy=VAL(Box$(2,Row))
4650      IF Dummy>=Bsiz_limit THEN 
4652        Dummy=512
4654      ELSE
4656        Dummy=Dummy*2
4658      END IF
4660      Dummy=Dummy*2
4662      GOSUB Meas_chk_change
4664      Inpt_cmd("ALL INPUT","BLOCK SIZE",VAL$(Dummy))
4666      Inpt_cmd("ALL INPUT","TBLK",VAL$(Dummy))
4668      Srce_cmd("ALL SOURCE","BLOCK SIZE",VAL$(Dummy))
4670      Box$(2,Row)=VAL$(VAL(FNInpt_rsp$(Box$(2,Inpt_r),"BLOCK SIZE")) DIV 2)
4672      Temp=VAL(Box$(2,Cmnd_stop))
4674      IF Temp<0 AND ABS(Temp)>=VAL(Box$(2,Row))*2 THEN 
4676        Inpt_cmd("ALL INPUT",Cmnd$(Cmnd_stop),VAL$(-VAL(Box$(2,Row))*2+2))
4678        Box$(2,Cmnd_stop)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),Cmnd$(Cmnd_stop)))
4680      END IF
4682    CASE Cmnd_start+1          ! Span command
4684      Real_dummy=VAL(Box$(2,Row))
4686      IF Real_dummy>51200.0 THEN Real_dummy=.15
4688      GOSUB Meas_chk_change
4690      Inpt_cmd("ALL INPUT","SPAN",VAL$(Real_dummy*2.))
4692      Srce_cmd("ALL SOURCE","SPAN",VAL$(Real_dummy*2.))
4694      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),"SPAN"))
4696    CASE Cmnd_stop             ! Trigger Delay command
4698      Real_dummy=VAL(Box$(2,Row))
4700      GOSUB Meas_chk_change
4702      Real_dummy=Real_dummy+2
4704      IF Real_dummy<0 AND ABS(Real_dummy)>=VAL(Box$(2,Cmnd_start))*2 THEN 
4706        Real_dummy=-VAL(Box$(2,Cmnd_start))*2+2
4708      END IF
4710      Inpt_cmd("ALL INPUT","TRIGGER DELAY",VAL$(Real_dummy))
4712      Box$(2,Row)=TRIM$(FNInpt_rsp$(Box$(2,Inpt_r),"TRIGGER DELAY"))
4714    END SELECT
4716    RETURN 
4718    !
4720 Meas_toggle:! Toggle average mode on or off
4722    IF Box$(2,Row)="ON" THEN 
4724      Box$(2,Row)="OFF"
4726    ELSE
4728      Box$(2,Row)="ON"
4730    END IF
4732    GOSUB Meas_chk_change
4734    RETURN 
4736    !
4738 Meas_chk_change:!
4740    IF NOT Changed THEN 
4742      Changed=1
4744      Hw_dev_clear
4746    END IF
4748    RETURN 
4750    !
4752  SUBEND
4754  !************************************************************************
4756  !
4758  !     Now some routines for the application to use
4760  !
4762  !************************************************************************
4764 Meas_ref_input:DEF FNMeas_ref_input$(INTEGER Current)
4766    !
4768    ! This function returns the label of the reference input that
4770    ! is currently selected.  The parameter Current is set to the
4772    ! input number that is the reference input.  This input number
4774    ! is NOT the address of the reference input.  It is the
4776    ! position of the reference input in the array of input labels
4778    ! that the configuration module provides.
4780    !
4782    COM /Meas_mod_labels/ Inpt_labels$(*)
4784    COM /Meas_mod_counts/ INTEGER Inpt_count,Current_inpt
4786    Current=Current_inpt
4788    RETURN Inpt_labels$(Current_inpt)
4790  FNEND
4792 Meas_span:DEF FNMeas_span
4794    !
4796    ! This function returns the current span that the input and
4798    ! source modules are set to.
4800    !
4802    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4804    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4806    RETURN VAL(Box$(2,Cmnd_start+1))
4808  FNEND
4810 Meas_cf:DEF FNMeas_cf
4812    !
4814    ! This function returns the current center frequency the input
4816    ! and source modules are set to.
4818    !
4820    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4822    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4824    RETURN VAL(Box$(2,Cmnd_start+2))
4826  FNEND
4828 Meas_block_size:DEF FNMeas_block_size
4830    !
4832    ! This function returns the current complex FFT size.  This
4834    ! input modules have a block size set to TWICE this value,
4836    ! since the input block size refers to the number of words
4838    ! rather than complex words in a block.  The source block
4840    ! size is set equal to this.
4842    !
4844    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4846    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4848    RETURN VAL(Box$(2,Cmnd_start))
4850  FNEND
4852 Meas_numav:DEF FNMeas_numav
4854    !
4856    ! This function returns the number of averages to do.  If
4858    ! averaging is off or the number of averages is one or less,
4860    ! the function returns zero.
4862    !
4864    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4866    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4868    IF Box$(2,Av_r)="ON" THEN 
4870      IF VAL(Box$(2,Numav_r))>1 THEN RETURN VAL(Box$(2,Numav_r))
4872    END IF
4874    RETURN 0
4876  FNEND
4878 Meas_window:DEF FNMeas_window$
4880    !
4882    ! This function returns the current window type selected, in
4884    ! a string.
4886    !
4888    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4890    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
4892    RETURN Box$(2,Window_r)
4894  FNEND
4896 Meas_av_type:DEF FNMeas_av_type$
4898    !
4900    ! This function returns the current average type (display only
4902    ! the last average or display every average).
4904    !
4906    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4908    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4910    RETURN Box$(2,Av_type_r)
4912  FNEND
4914 Meas_restart:DEF FNMeas_restart
4916    !
4918    ! This function returns the restart mode (restart when done or
4920    ! stop when done.
4922    !
4924    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4926    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
4928    RETURN UPC$(Box$(2,Restart_r)[1;1])="R"
4930  FNEND
4932  !*********************************************************************
4934  !
4936  !     Save and load routines for the Measurement module.
4938  !
4940  !*********************************************************************
4942 Meas_save:SUB Meas_save(@File,Ok)
4944    !
4946    ! This is used to save the current measurement setup in a file.
4948    !
4950    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4952    INTEGER File_format_rev
4954    File_format_rev=2620
4956    OUTPUT @File;File_format_rev
4958    File_save_s(@File,Box$(*))
4960    Ok=1
4962  SUBEND
4964 Meas_load:SUB Meas_load(@File,Ok)
4966    !
4968    ! This is used to load a previously saved measurement setup from
4970    ! a file.
4972    !
4974    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
4976    COM /Meas_mod_counts/ INTEGER Inpt_count,Current_inpt
4978    COM /Meas_mod_labels/ Inpt_labels$(*)
4980    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
4982    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
4984    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
4986    INTEGER File_format_rev,Row,Value,I
4988    DIM Value$[20]
4990    ENTER @File;File_format_rev
4992    SELECT File_format_rev
4994    CASE 2620
4996      File_load_s(@File,Box$(*))
4998      FOR Row=Cmnd_start TO Cmnd_stop
5000        SELECT Row
5002        CASE Cmnd_start
5004          Value$=VAL$(VAL(Box$(2,Row))*2)
5006          Inpt_cmd("ALL INPUT","TBLK",Value$)
5008          Inpt_cmd("ALL INPUT",Cmnd$(Row),Value$)
5010          Srce_cmd("ALL SOURCE",Cmnd$(Row),Value$)
5012        CASE Cmnd_stop
5014          Inpt_cmd("ALL INPUT",Cmnd$(Row),Box$(2,Row))
5016        CASE ELSE
5018          Inpt_cmd("ALL INPUT",Cmnd$(Row),Box$(2,Row))
5020          Srce_cmd("ALL SOURCE",Cmnd$(Row),Box$(2,Row))
5022        END SELECT
5024      NEXT Row
5026      Inpt_cmd("ALL INPUT","CLEAR")
5028      Srce_cmd("ALL SOURCE","CLEAR")
5030      FOR I=1 TO Inpt_count
5032        IF TRIM$(UPC$(Inpt_labels$(I)))=TRIM$(UPC$(Box$(2,Inpt_r))) THEN 
5034          Current_inpt=I
5036        END IF
5038      NEXT I
5040      Appl_new_labels
5042      Ok=1
5044    CASE ELSE
5046      User_error("ERROR - Incompatible file format in Meas_load.")
5048      Ok=0
5050    END SELECT
5052  SUBEND
5054 Meas_reset:SUB Meas_reset
5056    !
5058    ! This is used to reset all the boxes in the spreadsheet to the
5060    ! state they start in.  This is called by Meas_init and by Meas_spread
5062    ! when the 'Reset' key is pressed.
5064    !
5066    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
5068    COM /Meas_rows/ INTEGER Cmnd_start,Cmnd_stop,Av_r,Numav_r,Av_type_r
5070    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
5072    COM /Meas_mod_labels/ Inpt_labels$(*)
5074    COM /Meas_choices/ Choices$(*)
5076    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
5078    COM /Meas_mod_counts/ INTEGER Inpt_count,Current_inpt
5080    INTEGER R
5082    DIM Temp$[20]
5084    !
5086    Box$(2,Av_r)="ON"
5088    Box$(2,Numav_r)="4"
5090    Box$(2,Av_type_r)=Choices$(Av_type_r,1)
5092    Box$(2,Restart_r)=Choices$(Restart_r,1)
5094    Box$(2,Window_r)=Choices$(Window_r,1)
5096    Box$(2,Log_freq_r)=Choices$(Log_freq_r,1)
5098    Current_inpt=MIN(2,Inpt_count)
5100    Box$(2,Inpt_r)=Inpt_labels$(Current_inpt)
5102    !
5104    FOR R=Cmnd_start TO Cmnd_stop
5106      IF Cmnd$(R)="BLOCK SIZE" THEN 
5108        Temp$=VAL$(VAL(Def_value$(R))*2)
5110        Inpt_cmd("ALL INPUT","BLOCK SIZE",Temp$)
5112        Srce_cmd("ALL SOURCE","BLOCK SIZE",Temp$)
5114        Inpt_cmd("ALL INPUT","TBLK",Temp$)
5116        Box$(2,R)=VAL$(VAL(FNInpt_rsp$(Inpt_labels$(Current_inpt),Cmnd$(R)))/2)
5118      ELSE
5120        Inpt_cmd("ALL INPUT",Cmnd$(R),Def_value$(R))
5122        IF R<>Cmnd_stop THEN 
5124          Srce_cmd("ALL SOURCE",Cmnd$(R),Def_value$(R))
5126        END IF
5128        Box$(2,R)=TRIM$(FNInpt_rsp$(Inpt_labels$(Current_inpt),Cmnd$(R)))
5130      END IF
5132    NEXT R
5134  SUBEND
5136 Meas_log_freq:DEF FNMeas_log_freq
5138    !
5140    ! This function returns a one if plots should be displayed with
5142    ! a log frequency axis rather than a linear frequency axis.
5144    !
5146    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
5148    COM /Meas_rows2/ INTEGER Restart_r,Window_r,Log_freq_r,Inpt_r
5150    COM /Meas_choices/ Choices$(*)
5152    RETURN Box$(2,Log_freq_r)=Choices$(Log_freq_r,2)
5154  FNEND