2  !   OUTPUT 2 USING "#,K";"<lf>INDENT<cr>REN 2,2<cr><lf>RE-STORE ""/RAMBO/DEMO/SGEN_EXAM""<cr>"
4     !
6     END
8     !
10    ! PAGE -> 
12    !***********************************************************************
14 Appl_appl:SUB Appl_appl
16    ! Called when program is first run ("poweron")
18    ! All COM declarations specific to this application are defined here
20      COM /Appl_data/ Data_buffer(1:16,0:4095),Data_header(1:16,1:10)
22      COM /Appl_buf_info/ Disp_choices$(1:2,1:63)[16],Input_labels$(1:63)[16],Num_inputs
24      ! A larger icode program may require you to increase the size of these
26      COM /Exam_block_info/ Icode_info$(0:127)[40],Source$(0:100)[80],INTEGER Compiled(0:255),Icode_compiled,Icode_id,Source_size
28      COM /Exam_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(1:63)
30      ! The next line is necessary to be able to REDIM to the largest size
32      Source_size=SIZE(Source$,1)
34    SUBEND
36    !
38    ! PAGE -> 
40    !***********************************************************************
42 Appl_start:SUB Appl_start
44    ! Called when a measurement is to be started (restarted)
46    !
48      COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs
50      COM /Appl_data/ Data_buffer(*),Data_header(*)
52      COM /Exam_block_info/ Icode_info$(*),Source$(*),INTEGER Compiled(*),Icode_compiled,Icode_id,Source_size
54      !
56      ! Clear Error queue,Stop Icode,Clear Pending SRQs
58      Hw_dev_clear
60      Hw_cmd("CLR;STA?")
62      !
64      ! Fill info block here for ICODE program
66      CALL Exam_syst_info
68      !
70      ! Setup any SRQ/IRQ masks here such as BAV, FIFO OVERFLOW
72      ! Also send out any global information such as ZOOM ON, SYNC ON,
74      ! CONT/BLK modes, etc.
76      ! Note that if the application will not handle all 63 possible
78      ! input channels, you probably want to set up your own class for
80      ! some of these global commands so unrelated modules don't get a
82      ! 'STRT' command.
84      !
86      Hw_cmd("RQS"&VAL$(FNHw_str_2_stat("MSG|PRG|ERR"))) !HP-IB module
88      !
90      ! If f_thruput instruction is to be used, fill module list(0:2) here
92      !
94      ! Change buff size based on new measurement
96      REDIM Data_buffer(1:2*Num_inputs,0:FNMeas_fftsize-1)
98      !
100     ! Wait for global ready then start the ICODE program
102     Hw_wait_gbl_rdy
104     Hw_cmd("PROG"&VAL$(Icode_id),1)
106     !
108   SUBEND
110   !
112   ! PAGE -> 
114   !***********************************************************************
116 Appl_get_data:SUB Appl_get_data(Got_new_data,Stopped)
118   ! Called to get new data from the module
120   ! If new data is not available, this module should return
122   ! with Got_new_data false.  If there is new data, it should
124   ! update the Data_buffer (and Full_scale array if necessary) and
126   ! return with Got_new_data true.
128   !
130     COM /Appl_data/ Data_buffer(*),Data_header(*)
132     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs
134     COM /Exam_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(*)
136     COM /Exam_block_info/ Icode_info$(*),Source$(*),INTEGER Compiled(*),Icode_compiled,Icode_id,Source_size
138   !
140     Got_new_data=0
142     DISP "Ready for data from HP3565S"
144     IF NOT FNHw_srq THEN SUBEXIT
146     !
148 Got_srq:!
150     Sta=VAL(FNHw_cmd_rsp$("STA?"))
152     IF BINAND(Sta,FNHw_str_2_stat("MESSAGE")) THEN 
154       DISP "Processing message from HP3565S HP-IB interface module"
156       Sig_value=VAL(FNHw_cmd_rsp$("SIG?"))
158       SELECT Sig_value
160       !
162       !Put in your own signal values here, and take appropriate
164       ! action such as reading data, triggering, etc.
166       !
168       CASE 1
170         Window_data=1  !for this demo only, probably want time/freq here
172         Data_type=Window_data!  for this demo only
174         GOSUB Get_info
176         Stopped=1
178         DISP ""
180       END SELECT
182     END IF
184     IF BINAND(Sta,FNHw_str_2_stat("ERROR")) THEN 
186       GOSUB Ck_for_errors
188       LINPUT "<ret> to try to continue",Dummy$
190       Stopped=1
192     END IF
194     SUBEXIT
196 Get_info: !
198     !
200     Got_new_data=1
202     ! Read the data buffer
204     Hw_read_fblk(FNIcode_ext_id("OUTPUT_BUFF",Icode_info$(*)),Data_buffer(*))
206     !
208     ! Incoming data usually needs to be scaled before plotting.
210     ! Hann_fact is Hann window Correction factor
212     ! Corr_fact takes care of the digital filter scaling and 2dB overrange
214     ! These are defined in Appl_powerup
216     Scaler=Hann_fact*Corr_fact
218     Num_plots=FNDisp_num_plots
220     FOR I=1 TO Num_plots
222       Module_label$=Disp_choices$(1,FNDisp_choice(I,1))
224       Range_fact=10^(Range(I)/10)
226       Ovld_bit=BINAND(FNHw_rmst(FNCnfg_get_modnum(Module_label$)),FNInpt_str_2_stat("OVERLOAD"))
228       Data_header(I,1)=0     ! DC Offset
230       Data_header(I,3)=Ovld_bit
232       SELECT Data_type
234       CASE Time_data
236         Data_header(I,2)=2/SQR(Scaler*Range_fact)
238         Data_header(I,4)=0     !Don't do logs
240         Data_header(I,5)=0     !set LOG(0),LOG(-1) to this number
242         Data_header(I,6)=0     !Average_number
244         Data_header(I,7)=0     !Real_time flag
246       CASE Freq_data         !we want dB
248         Data_header(I,2)=1/(Scaler*Range_fact)
250         Data_header(I,4)=10     !for 10 * log, we have mag^2 data
252         !
254         ! Half_lsb is the value in user units which we want to set
256         ! Log(0).  Defined in Appl_powerup
258         Data_header(I,5)=Half_lsb/Scaler
260         Data_header(I,6)=20     !Average_number
262         Data_header(I,7)=1      !Real_time flag
264       CASE Window_data    !for this sample program
266         Data_header(I,2)=1
268         Data_header(I,3)=INT(RND*2)  !random fake overloads
270         Data_header(I,4)=0  !don't log it
272         Data_header(I,6)=20*FNMeas_avg_mode !pretend we did 20 averages
274         Data_header(I,7)=INT(RND*2)  !random fake real time
276       END SELECT
278     NEXT I
280     RETURN 
282 Ck_for_errors:  !
284     ! We don't expect any errors, but if there are some, print 'em out.
286     User_clr_scr
288     BEEP 
290     Errs=FNDiag_chk_errors
292     IF NOT Errs THEN OUTPUT CRT;"No active modules report errors"
294     RETURN 
296   SUBEND
298   !
300   ! PAGE -> 
302   !***********************************************************************
304 Appl_update:SUB Appl_update
306     ! This routine is call whenever the display configuration is changed
308     ! Note that default y-axis limits are set here.
310     COM /Appl_data/ Data_buffer(*),Data_header(*)
312     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs
314     COM /Exam_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(*)
316     !
318     DIM Mod$[50]
320     !
322     Num_plots=FNDisp_num_plots
324     ! Next array maps plot number to location of data in the buffer
326     ALLOCATE Plot_to_buf(1:Num_plots)
328     ! Next array contains labels like "Hz" and "Volts"
330     ALLOCATE X_units$(1:Num_plots)[10],Y_units$(1:Num_plots)[10]
332     ! Next array contains x value of the first data point
334     ALLOCATE Start_x(1:Num_plots),Per_bin_x(1:Num_plots)
336     ! Next array contains bin number to start plotting
338     ALLOCATE Start_bin(1:Num_plots),Num_bins(1:Num_plots)
340     ! Next arrays define Y axis default max/min plot units
342     ALLOCATE Y_def_max(1:Num_plots),Y_def_min(1:Num_plots)
344     ! Next array: if non zero, x axis will be logged
346     ALLOCATE Do_log_x(1:Num_plots)
348     ! Next array: if non zero, y axis grid will be log
350     ALLOCATE Do_log_y(1:Num_plots)
352     ! You can define your own trace titles here
354     ALLOCATE Plot_titles$(1:Num_plots)[45]
356     !
358     Fftsize=FNMeas_fftsize
360     Span=FNMeas_span
362     Cf=FNMeas_cf
364     Hz_per_bin=1.28*Span/Fftsize
366     !
368     MAT Start_bin= (0)
370     MAT Num_bins= (FNMeas_fftsize)
372     !
374     FOR Plot_num=1 TO Num_plots
376       Module_label$=Disp_choices$(1,FNDisp_choice(Plot_num,1))
378       Range(Plot_num)=VAL(FNInpt_rsp$(Module_label$,"RANGE"))
380       SELECT UPC$(Disp_choices$(2,FNDisp_choice(Plot_num,2)))
382       !
384       ! We are looking at the selections defined when the
386       ! Display Spreadsheet was initialized in Appl_init
388       !
390       CASE "PS"
392         Plot_to_buf(Plot_num)=FNDisp_choice(Plot_num,1)  !may change
394         Start_x(Plot_num)=(Cf-(Fftsize*25/64)*Hz_per_bin) !BIN 0 FREQ VALUE
396         Per_bin_x(Plot_num)=(Hz_per_bin)
398         Num_bins(Plot_num)=(Fftsize/1.28+1)               !401 point fft
400         Y_units$(Plot_num)="dB"
402         Y_def_max(Plot_num)=Range(Plot_num)
404         Y_def_min(Plot_num)=Y_def_max(Plot_num)-100
406         IF FNInpt_rsp$(Module_label$,"INPUT MODE")="CHRG" THEN 
408           Plot_titles$(Plot_num)=Module_label$&" PS pCp"
410         ELSE
412           Plot_titles$(Plot_num)=Module_label$&" PS Vp"
414         END IF
416         X_units$(Plot_num)=("Hz")
418         Do_log_x(Plot_num)=0
420         Do_log_y(Plot_num)=0
422       CASE "TIME"
424         !
426         ! These are typical settings for time displays
428         Plot_to_buf(Plot_num)=FNDisp_choice(Plot_num,1)
430         Plot_titles$(Plot_num)=Module_label$&" Time"
432         Y_def_max(Plot_num)=10^(Range(Plot_num)/20)
434         Y_def_min(Plot_num)=-Y_def_max(Plot_num)
436         X_units$(Plot_num)="Secs"
438         Y_units$(Plot_num)="Volt"
440         Start_x(Plot_num)=0
442         Per_bin_x(Plot_num)=.390625/Span
444         Do_log_x(Plot_num)=0
446         Do_log_y(Plot_num)=0
448       CASE "HANN"          !just for this example
450         Plot_to_buf(Plot_num)=(2*(FNDisp_choice(Plot_num,1)-1)+FNDisp_choice(Plot_num,2)-1) MOD 2+1
452         Plot_titles$(Plot_num)=" Hann Window"
454         Y_def_max(Plot_num)=1
456         Y_def_min(Plot_num)=0
458         X_units$(Plot_num)="Bins"
460         Y_units$(Plot_num)="Units"
462         Start_x(Plot_num)=0
464         Per_bin_x(Plot_num)=1
466         Do_log_x(Plot_num)=0
468         Do_log_y(Plot_num)=0
470       CASE "FLAT"          !just for this example
472         Plot_to_buf(Plot_num)=(2*(FNDisp_choice(Plot_num,1)-1)+FNDisp_choice(Plot_num,2)-1) MOD 2+1
474         Plot_titles$(Plot_num)=" Flat Top Window"
476         Y_def_max(Plot_num)=4
478         Y_def_min(Plot_num)=-1
480         X_units$(Plot_num)="Bins"
482         Y_units$(Plot_num)="Units"
484         Start_x(Plot_num)=0
486         Per_bin_x(Plot_num)=1
488         Do_log_x(Plot_num)=0
490         Do_log_y(Plot_num)=0
492       END SELECT
494     NEXT Plot_num
496     !
498     ! Pass above info to the display routine
500     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(*))
502     !
504     ! Must call Disp_plot_set before the next two Calls !!!!
506     Disp_put_titles(Plot_titles$(*))      !define your own trace titles
508     Disp_log_set(Do_log_x(*),Do_log_y(*)) !pass info about log-log plots
510   SUBEND
512   !
514   ! PAGE -> 
516   !***********************************************************************
518 Appl_init:SUB Appl_init
520     ! This routine is called by Appl_main  whenever the configuration
522     ! has changed (and at power on).
524     ! Icode program is assembled and downloaded,
526     ! FFT coefficients are retrieved/generated,
528     ! Display Spreadsheet parameters are defined,
530     ! Number of channels is limited to 16 here.
532     COM /Appl_data/ Data_buffer(*),Data_header(*)
534     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs
536     COM /Exam_block_info/ Icode_info$(*),Source$(*),INTEGER Compiled(*),Icode_compiled,Icode_id,Source_size
538     !
540     Hw_dev_clear              !abort any HP-IB activity
542     Appl_powerup              !pass labels to spreadsheets, init constants
544     Hw_cmd("TRGU;DISA;LSPR 1")! make sure default SP algorithms are loaded
546     !
548     ! Get the available module names from the cnfg module
550     Cnfg_labels("ALL INPUT",Input_labels$(*),Num_inputs)
552     !
554     ! You may want to limit the number of input modules to a specific
556     ! range....
558     IF Num_inputs=0 THEN SUBEXIT
560     Num_inputs=MIN(16,Num_inputs)
562     !
564     CALL Exam_icode_prog       !assembles and downloads the icode program
566                                !allocates blocks
568     ALLOCATE INTEGER Coef(0:4095)
570     Lib_fft_coefs(Coef(*))             !generate FFT coefficient table
572     Hw_write_blk(FNIcode_ext_id("COEF",Icode_info$(*)),Coef(*))
574     DEALLOCATE Coef(*)
576     !
578     !define the display spreadsheet here:
580     Num_cols=2
582     ALLOCATE Disp_titles$(1:Num_cols,1:2)[20]
584     ALLOCATE Disp_prompt$(1:Num_cols)[80]
586     ALLOCATE Disp_width(1:Num_cols)
588     !
590     MAT Disp_titles$= ("")
592     Disp_titles$(1,1)="Module"
594     Disp_titles$(1,2)="Label"
596     Disp_titles$(2,1)="Trace"
598     Disp_titles$(2,2)="Type"
600     Disp_prompt$(1)="Enter module label"
602     ! Next prompt would usually be stuff like TIME,PSD,FREQ etc.
604     Disp_prompt$(2)="Enter trace type: HANN,FLAT"
606     Disp_width(1)=16
608     Disp_width(2)=7
610     !
612     MAT Disp_choices$= ("")
614     FOR Module_index=1 TO Num_inputs
616       Disp_choices$(1,Module_index)=Input_labels$(Module_index)
618     NEXT Module_index
620     !
622     ! Next choices would usually be stuff like TIME,PSD,FREQ etc.
624     Disp_choices$(2,1)="HANN"
626     Disp_choices$(2,2)="FLAT"
628     !
630     ! Setup Disp module with titles
632     Disp_spread_set(Disp_titles$(*),Disp_prompt$(*),Disp_width(*),Disp_choices$(*))
634     !
636     ! The module list is used by the Icode instruction 'f_thruput'
638     ! Here, fill Module_list(2:2+N-1) with address of active input modules
640     ! if the f_thruput instruction is used
642     !
644     ! Let 1st module trigger as a default.  This is done to insure that
646     ! a measurement will begin when program is first run.
648     Inpt_cmd(Input_labels$(1),"TRIGGER MODE","SEND TRIGGER")
650     !
652     DISP ""
654   SUBEND
656   !
658   ! PAGE -> 
660   !***********************************************************************
662 Exam_syst_info:SUB Exam_syst_info
664     ! Called by Appl_start, this routine fills a
666     ! parameter block with info necessary for FFT,
668     ! windows, averaging, display modes, etc., then downloads
670     ! to the Parameter block (in HP-IB module) for use by Icode.
672     !
674     COM /Exam_block_info/ Icode_info$(*),Source$(*),INTEGER Compiled(*),Icode_compiled,Icode_id,Source_size
676     !
678     DISP "Fill parameter block with system information..."
680     ALLOCATE INTEGER Param(0:15)
682     Fftsize=FNMeas_fftsize
684     SELECT UPC$(FNMeas_wind_type$)
686     CASE "RECTANGULAR"
688       Do_window=0
690     CASE "HANN"
692       Do_window=1
694       Wind_type_code=1
696     CASE "FLAT TOP"
698       Do_window=1
700       Wind_type_code=2
702     END SELECT
704     !
706     MAT Param= (0)  !set unused params to 0
708     !
710     ! Following 7 parameters are typical of those required
712     ! for the supplied FFT algorithm
714     !
716     Param(0)=0      !block scaling exponent MSW
718     Param(1)=0      !block scaling exponent LSW
720     Param(2)=PROUND(LOG(Fftsize)/LOG(2),0)   !9,10,11,12
722     Param(3)=0                               !overflow flag
724     Param(4)=Do_window  !SWAP_FLAG
726     Param(5)=Do_window  !WINDOW FLAG
728     Param(6)=2          !Mode   0=output is complex
730                         !       1=do ifft
732                         !       2=output is 32 bit Mag^2
734     !
736     ! Following information is system info for use by the ICODE program
738     !
740     Param(7)=Fftsize
742     ! Next line asks the Meas spreadsheet for window type....
744     ! You probably want to have several other flags, such as
746     ! as Block/Continuous, number of averages, etc.
748     Param(8)=Wind_type_code   !1=hanning, 2=flattop
750     !
752     GOSUB Send_params
754     IF FNHw_io_error THEN !try again, may have been in f_thruput, etc.
756       Hw_dev_clear
758       GOSUB Send_params
760       IF FNHw_io_error THEN  !something is wrong
762         User_clr_scr
764         User_error("Unable to send param block to HP-IB module--I/O timeout")
766       END IF
768     END IF
770     SUBEXIT
772 Send_params:  !
774     Hw_write_blk(FNIcode_ext_id("PARAM",Icode_info$(*)),Param(*),2)
776     RETURN 
778   SUBEND
780   !
782   ! PAGE -> 
784   !***********************************************************************
786 Exam_icode_prog:SUB Exam_icode_prog
788   ! The icode program is here in the form of DATA statements.
790   ! It is here that the Icode assembler & downloader are called
792   ! Icode_info$(*) is required by the Icode assembler,
794   ! Icode_id is the block_id of the Icode program
796   ! Source$(*) is kept around to make the debugger more 'friendly'--
798   !  if memory is scarce, it can be deleted from the COMs
800   ! Compiled(*) is kept around to prevent unnecessary compilation
802   ! Icode_compiled is a flag set if the icode has been compiled
804   ! Note that the size of Icode_info$(*), Source$(*), Compiled$(*),
806   !  and List_array$(*) may need to grow with  your Icode program.
808   !
810     COM /Exam_block_info/ Icode_info$(*),Source$(*),INTEGER Compiled(*),Icode_compiled,Icode_id,Source_size
812     !
814     ! Set Info_info to 1 for downloader block allocation,
816     !Set it to 2 to allow use of the Icode debugger also
818     Info_info=2
820     Do_listing=0  !set this to 1 to fill List_array$(*) with listing
822     IF Do_listing THEN 
824       ALLOCATE List_array$(0:300)[95]
826     ELSE
828       ALLOCATE List_array$(0:1)[95]
830     END IF
832     IF NOT Icode_compiled THEN 
834       REDIM Source$(0:Source_size-1) !inflate to max size
836       I=-1
838       REPEAT
840         I=I+1
842         READ Source$(I)
844       UNTIL POS(Source$(I),"EL_COMPLETO")
846       Assy_errors=FNIcode_assemble(Source$(*),Compiled(*),(Info_info),Icode_info$(*),(Do_listing),List_array$(*))
848       IF Do_listing THEN 
850         DISP "Assembly listing is in 'List_array$(*)'..<CONT> when done"
852       ! For example, OUTPUT 701;List_array$(*) will send
854       ! listing to a local printer at address 701.
856         PAUSE
858       END IF
860       Icode_compiled=NOT Assy_errors
862     END IF
864     IF Icode_compiled THEN 
866       Icode_id=FNIcode_dld(Compiled(*),(Info_info),Icode_info$(*))
868     END IF
870     !
872     SUBEXIT
874     !
876     DATA"!**********************************************************"
878     DATA"! sample ICODE PROGRAM for template.  You'll probably want to"
880     DATA"! delete this and write your own ICODE program."
882     DATA"! This program generates  FFTsized Hann and Flat Top windows,"
884     DATA"! and sends them to the data buffer, for later plotting."
886     DATA"!**********************************************************"
888     DATA""
890     DATA" VAR   FFTSIZE           0   !Size of FFT in Complex words"
892     DATA" VAR   FFTSIZEX4         0   !total # 16 BIT WORDS"
894     DATA" VAR   FFTSIZEX8         0   !"
896     DATA" VAR   BUFF_1            0   !offset of Hann window"
898     DATA" VAR   BUFF_2            0   !offset of Flat Top window"
900     DATA" VAR   WIND_TYPE         0   !0=Uniform,1=Hann, 2=Flat top"
902     DATA""
904     DATA" CONST  DATA_RDY         1 !signal that data is ready"
906     DATA""
908     DATA" DEFBLK_SP     WIND          16384,2"
910     DATA" DEFBLK_SP     COEF           4096,2"
912     DATA" DEFBLK_SP     PARAM           182,2"
914     DATA" DEFBLK_MAIN   OUTPUT_BUFF   65536,2"
916     DATA""
918     DATA""
920     DATA"        V_GET16_INDEXED PARAM,7,FFTSIZE    !512,1024,2048,4096"
922     DATA"        V_MULT          FFTSIZE,4,FFTSIZEX4"
924     DATA"        V_CEQUATE       0,BUFF_1     !offsets in output buffer"
926     DATA"        V_ADD           FFTSIZEX4,BUFF_1,BUFF_2"
928     DATA""
930     DATA"        V_CEQUATE       1,WIND_TYPE  !Hann window"
932     DATA"        C_GOSUB         INIT_W      !initialize window"
934     DATA"        F_MOVE_BLOCK    WIND,0,OUTPUT_BUFF,BUFF_1,FFTSIZEX4"
936     DATA"        V_CEQUATE       2,WIND_TYPE  !Flat top window"
938     DATA"        C_GOSUB         INIT_W      !initialize window"
940     DATA"        F_MOVE_BLOCK    WIND,0,OUTPUT_BUFF,BUFF_2,FFTSIZEX4"
942     DATA""
944     DATA"DONE:   F_WAIT_TO_SIG   DATA_RDY"
946     DATA"        C_END"
948     DATA""
950     DATA"!************************************************************"
952     DATA"! Subroutine INIT_WIND forms a window block in the TMS320 RAM"
954     DATA"!************************************************************"
956     DATA""
958     DATA" INIT_W: C_BEQ HANN,WIND_TYPE,1"
960     DATA"        C_BEQ FLAT_TOP,WIND_TYPE,2"
962     DATA"        C_RTS    ! if no window was selected"
964     DATA" HANN:"
966     DATA"        F_FLOAT_WINGEN WIND,0,FFTSIZE,2,0.499984,-.499984"
968     DATA"        C_RTS"
970     DATA" FLAT_TOP:"
972     DATA""
974     DATA"! The 'normal' flat top coefficients are"
976     DATA"!   0.994484/2,-0.955728,0.539289,-.0915810"
978     DATA"! These are all scaled by here to make the peak at 32767"
980     DATA"        F_FLOAT_WINGEN WIND,0,FFTSIZE,4,  .954423166665"
982     DATA".               -1.8344567519  , 1.03512960516,-.175783678825"
984     DATA"        C_RTS"
986     DATA ""
988     DATA" END:   C_END"
990     DATA"EL_COMPLETO"
992   SUBEND
994   !
996   ! PAGE -> 
998   !***********************************************************************
1000 Appl_main:SUB Appl_main(Init)
1002    !
1004    !  This is the main loop for the application.  It sets up for
1006    !  the measurement, sets up the softkeys, and loops processing
1008    !  key presses, updating the measurement, and calling the
1010    !  measurement loop.
1012    !
1014    COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs
1016    !
1018    GOSUB Appl_main_keys   ! setup softkeys
1020    !
1022    ! First init everything
1024    Hw_dev_clear      !this also aborts old icode program
1026    IF Init THEN 
1028      Appl_init       !Initialize Icode, params etc.
1030    END IF
1032    !
1034    ! The following range check will exit you to SPAM
1036    IF Num_inputs=0 THEN 
1038      User_error("***Sorry, can't run this application w/o input modules ***")
1040      SUBEXIT
1042    END IF
1044    !
1046    ! Initialize flags
1048    Restart_meas=1   !come up running
1050    Display_changed=1
1052    Meas_stopped=0   !can't be stopped if we are running
1054    Axes_not_done=1  !Axes aren't plotted yet
1056    Leave_me=0       !Exit to SPAM if true
1058    !
1060    ! This is the main loop of the whole application
1062    REPEAT
1064      !
1066      ! You can have 2 sets of softkeys
1068      IF Main_keys THEN 
1070        IF Meas_stopped THEN 
1072          DISP "Waiting for START key . . ."
1074          ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
1076        ELSE
1078          ON KEY 7 LABEL FNUser_keylabel$("STOP") CALL User_key7isr
1080        END IF
1082      END IF
1084    !
1086      IF Restart_meas THEN 
1088        Appl_start   !start icode program
1090                     ! and set some flags
1092                     ! You may need to add some other flags
1094        Restart_meas=0
1096        Meas_stopped=0
1098        Display_changed=1
1100        Data_valid=0
1102      END IF
1104      !
1106      IF Display_changed THEN 
1108        Appl_update   ! Get information about current plots
1110        Disp_plot_axis ! and redraw the grid, labels, axis and background
1112        Axes_not_done=FNUser_key_press ! did we finish plotting all axes?
1114      END IF
1116      !
1118      ! Will stay in the next routine until Stopped, or a key
1120      ! is pressed.  Data is plotted here.
1122      Appl_meas_loop(Meas_stopped,Display_changed,Data_valid)
1124      !
1126      WHILE FNUser_key_press
1128        IF Main_keys THEN 
1130          Appl_do_main(Restart_meas,Meas_stopped,Display_changed,Keys_changed,Leave_me,Data_valid,Axes_not_done)
1132        ELSE
1134          Appl_do_other(Restart_meas,Meas_stopped,Display_changed,Keys_changed,Data_valid,Axes_not_done)
1136        END IF
1138      END WHILE
1140      !
1142      IF Keys_changed THEN 
1144        IF Main_keys THEN 
1146          GOSUB Appl_other_keys
1148        ELSE
1150          GOSUB Appl_main_keys
1152        END IF
1154      END IF
1156    UNTIL Leave_me
1158    Hw_dev_clear
1160    ! If you have used any of your own global classes, you may wish
1162    !to clear them here using the 'CLASM' command.
1164    SUBEXIT
1166  !
1168 Appl_dummy: !
1170    BEEP 
1172    RETURN 
1174 !
1176 Appl_main_keys:!
1178    Main_keys=1
1180    Only_one_label=1
1182    ON KEY 0 LABEL "" GOSUB Appl_dummy
1184    ON KEY 1 LABEL FNUser_keylabel$("INPUT SETUP") CALL User_key1isr
1186    ON KEY 2 LABEL FNUser_keylabel$("SOURCE SETUP") CALL User_key2isr
1188    ON KEY 3 LABEL FNUser_keylabel$("DISPLAY SETUP") CALL User_key3isr
1190    ON KEY 4 LABEL FNUser_keylabel$("MEASURE SETUP") CALL User_key4isr
1192    IF Only_one_label THEN 
1194      ON KEY 5 LABEL FNUser_keylabel$("HELP") CALL User_key5isr
1196    ELSE
1198      ON KEY 5 LABEL FNUser_keylabel$("OTHER") CALL User_key5isr
1200    END IF
1202    ON KEY 6 LABEL FNUser_keylabel$("MARKER") CALL User_key6isr
1204    ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
1206    ON KEY 8 LABEL FNUser_keylabel$("EXIT") CALL User_key8isr
1208    ON KEY 9 LABEL "" GOSUB Appl_dummy
1210    RETURN 
1212  !
1214 Appl_other_keys:!
1216    Main_keys=0
1218    ON KEY 0 LABEL "" GOSUB Appl_dummy
1220    ON KEY 1 LABEL FNUser_keylabel$("") CALL User_key1isr
1222    ON KEY 2 LABEL FNUser_keylabel$("") CALL User_key2isr
1224    ON KEY 3 LABEL FNUser_keylabel$("") CALL User_key3isr
1226    ON KEY 4 LABEL FNUser_keylabel$("") CALL User_key4isr
1228    ON KEY 5 LABEL FNUser_keylabel$("MAIN") CALL User_key5isr
1230    ON KEY 6 LABEL FNUser_keylabel$("") CALL User_key6isr
1232    ON KEY 7 LABEL FNUser_keylabel$("") CALL User_key7isr
1234    ON KEY 8 LABEL FNUser_keylabel$("") CALL User_key8isr
1236    ON KEY 9 LABEL "" GOSUB Appl_dummy
1238    RETURN 
1240  !
1242  SUBEND
1244  !
1246  !
1248  ! PAGE -> 
1250  !***********************************************************************
1252 Appl_do_main:SUB Appl_do_main(Restart,Stopped,Disp_modified,Keys_changed,Leave_me,Data_valid,Axes_not_done)
1254    COM /Appl_data/ Data_buffer(*),Data_header(*)
1256    !
1258    !  This routine is called when one of the main softkeys is pressed.
1260    !
1262    Key_num=FNUser_get_key
1264    !
1266    Change_in_hw=0
1268    Only_one_label=1
1270    Keys_changed=0
1272    !
1274    SELECT Key_num
1276    CASE 1
1278      ! Note that we get an 'extra' key by using the key you just
1280      ! pressed to return to MAIN
1282      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key1isr
1284      CALL Inpt_spread(Change_in_hw)
1286      Disp_modified=1
1288      OFF KEY Key_num
1290    CASE 2
1292      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key2isr
1294      CALL Srce_spread(Change_in_hw)
1296      Disp_modified=1
1298      OFF KEY Key_num
1300    CASE 3
1302      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key3isr
1304      CALL Disp_spread(Disp_modified)
1306      Disp_modified=1
1308      OFF KEY Key_num
1310    CASE 4
1312      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key4isr
1314      CALL Meas_spread(Meas_modified)
1316      Disp_modified=1
1318      OFF KEY Key_num
1320    CASE 5
1322      IF Only_one_label THEN 
1324        Appl_help
1326        Disp_modified=1
1328      ELSE
1330        Keys_changed=1
1332      END IF
1334    CASE 6
1336      IF Data_valid THEN        !there is valid data to mark
1338        ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key6isr
1340        IF Axes_not_done OR Disp_modified THEN 
1342          Disp_plot_axis
1344          Axes_not_done=FNUser_key_press ! did we finish ploting axes?
1346          Disp_modified=Axes_not_done    !  "   "   "      "       "
1348        END IF
1350        CALL Disp_do_mkr(Data_buffer(*),Data_header(*),0)
1352        OFF KEY Key_num
1354      ELSE
1356        User_error("*** There is no valid data for marker now ***")
1358        Disp_modified=1
1360      END IF
1362    CASE 7
1364      IF Stopped THEN 
1366        Restart=1
1368        Stopped=0
1370      ELSE
1372        Stopped=1
1374      END IF
1376    CASE 8
1378      Leave_me=1
1380    END SELECT
1382      !
1384    IF Meas_modified OR Change_in_hw THEN 
1386      Stopped=1
1388      Data_valid=0
1390    END IF
1392      !
1394    IF FNUser_key_press THEN 
1396      IF FNUser_check_key=Key_num THEN Key_num=FNUser_get_key
1398    END IF
1400  SUBEND
1402  !
1404  ! PAGE -> 
1406  !***********************************************************************
1408 Appl_do_other:SUB Appl_do_other(Restart_meas,Meas_stopped,Display_changed,Keys_changed,Data_valid,Axes_not_done)
1410  !
1412  !  This routine gets called when a softkey is pressed when the
1414  !  'Other' set of softkeys is active.  Thus there is another set of 8
1416  !   keys available to the application.  Note that only 8 keys are used for
1418  !   compatability with both series 200 and 300 computers.
1420    Key_num=FNUser_get_key
1422    !
1424    Keys_changed=0
1426    !
1428    SELECT Key_num
1430    CASE 1
1432      BEEP 
1434    CASE 2
1436      BEEP 
1438    CASE 3
1440      BEEP 
1442    CASE 4
1444      BEEP 
1446    CASE 5
1448      Keys_changed=1
1450    CASE 6
1452      BEEP 
1454    CASE 7
1456      BEEP 
1458    CASE 8
1460      BEEP 
1462    END SELECT
1464    !
1466  SUBEND
1468  !
1470  ! PAGE -> 
1472  !***********************************************************************
1474 Appl_meas_loop:SUB Appl_meas_loop(Stopped,Replot,Data_valid)
1476    COM /Appl_data/ Data_buffer(*),Data_header(*)
1478    !
1480    !  This routine is called when no keys are being pressed.  It
1482    !  should not return until a key has been pressed, or the measurement
1484    !  is done.  The plot routine is called here.
1486    !
1488    Replot=Replot AND Data_valid
1490    REPEAT
1492      IF (NOT Stopped) THEN 
1494        Appl_get_data(New_data,Stopped)
1496        Data_valid=Data_valid OR New_data
1498        Replot=New_data
1500      END IF
1502      IF Replot AND NOT FNUser_key_press THEN 
1504        Disp_plot_data(Data_buffer(*),Data_header(*))
1506        Replot=0
1508        IF FNUser_key_press AND FNUser_check_key=7 AND Stopped THEN Swallow=FNUser_get_key
1510      END IF
1512    UNTIL FNUser_key_press OR Stopped
1514    SUBEXIT
1516    !***: note that if the Appl_get_data routine stops the measurement
1518    !(by setting the Stopped flag), the START/STOP key function has changed
1520    !before we can update the label.  Thus, the user sees 'STOP' when in
1522    !fact the key is a START key.  'Swallowing' the keypress allows the
1524    !routine to exit in the 'Stopped' state, as the user expects.
1526  SUBEND
1528  !
1530  !
1532  ! PAGE -> 
1534  !***********************************************************************
1536 Appl_powerup:SUB Appl_powerup
1538    !  Called by Appl_init, This routine defines the MEASUREMENT, INPUT,
1540    !  and SOURCE spreadsheet choices, as well as some system constants,
1542    !  such as digital filter factor, window correction factors etc.
1544    COM /Exam_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(*)
1546    !
1548    DISP "Initialize spreadsheet: INPT"
1550    DIM Setup$(1:10)[20]
1552    !
1554    RESTORE Input_cols
1556    GOSUB Fill_setup
1558    Inpt_init(Setup$(*))
1560 Input_cols:!
1562    DATA 7
1564    DATA "INPUT MODE","COUPLING","GROUNDING","RANGE","TRIG MODE"
1566    DATA "TRIG LEVEL","TRIG SLOPE"
1568    !
1570    DISP "Initialize spreadsheet: SRCE"
1572    RESTORE Source_cols
1574    GOSUB Fill_setup
1576    Srce_init(Setup$(*))
1578 Source_cols:!
1580    DATA 8
1582    DATA "MODE","OFFSET","AMPLITUDE","SINE FREQ","SPAN","CENTER FREQ"
1584    DATA "TRIG","BURST %"
1586    !
1588    DISP "Initialize spreadsheet: MEAS"
1590    Meas_init
1592    !
1594    DISP "Initialize system scaling constants"
1596    ! Define system scaling consants to prevent recalculation later
1598    Two_db_over=(10^.1)                      !+2db overange in input module
1600    Dig_filt_corr=(1/.460657543)             !input filter safe scaling
1602    Twin_sided=2                             !For twin-sided spectrum
1604    Corr_fact=(Dig_filt_corr*Two_db_over*Twin_sided)^2 !total corr fact
1606    Flat_top_fact=4.1762^2                   !flat top window correction
1608    Hann_fact=2^2                            !Hanning Correction
1610    Half_lsb=(.5/65536)^2                    !assign log(0) to this value
1612    DISP ""
1614    !
1616    SUBEXIT
1618 Fill_setup:!
1620    READ Num_cols
1622    REDIM Setup$(1:Num_cols)
1624    FOR I=1 TO Num_cols
1626      READ Setup$(I)
1628    NEXT I
1630    RETURN 
1632  SUBEND
1634  !
1636  ! PAGE -> 
1638  !***********************************************************************
1640 Appl_help:SUB Appl_help
1642    ! This routine has a series of 'help screens' to give the user some
1644    ! quick information about the system...It is NOT meant to be a
1646    ! substitute for other documentation.
1648    DIM A$[160]
1650    RESTORE Page1
1652    GOSUB Show_page
1654    RESTORE Page2
1656    GOSUB Show_page
1658    RESTORE Page3
1660    GOSUB Show_page
1662    RESTORE Page4
1664    GOSUB Show_page
1666    SUBEXIT
1668 Show_page:!
1670    READ A$
1672    User_clr_scr
1674    WHILE A$<>"***END***"
1676      OUTPUT CRT;A$
1678      READ A$
1680    END WHILE
1682    OUTPUT KBD USING "#,K";"ÿ#Yÿ<"
1684    INPUT "Type 'Y' to continue, anything else to leave...",A$
1686    IF UPC$(A$[1;1])<>"Y" THEN SUBEXIT
1688    RETURN 
1690 Page1:   !
1692    DATA "              Help for Template Application"
1694    DATA ""
1696    DATA "This is the Template Application for the HP3565S demo programs."
1698    DATA "Its purpose is to be a 'template' to help you generate your own"
1700    DATA "application using the framework of the demo programs."
1702    DATA ""
1704    DATA "This program does run 'as is', showing you plots of Hann and"
1706    DATA "Flat Top windows for each of the Input Modules you have in your"
1708    DATA "system, to simulate a data gathering operation."
1710    DATA ""
1712    DATA "Keep in mind that in this sample program, some changes made to "
1714    DATA "the spreadsheet entries do not change the plots, since no real"
1716    DATA "measurement is made (You get to write that part!)."
1718    DATA ""
1720    DATA "Also note that the OVLD, RT, and Avg flags are occasionally "
1722    DATA "turned on (try pushing start several times) so you can see what"
1724    DATA "they look like."
1726    DATA "***END***"
1728 Page2:   !
1730    DATA "              Help for Template Application--Page 2"
1732    DATA ""
1734    DATA "There are four keys that are used to set up a measurement:"
1736    DATA "SOURCE SETUP, INPUT SETUP, DISPLAY SETUP, and MEASURE SETUP."
1738    DATA ""
1740    DATA "The SOURCE SETUP key is used to set up source modules."
1742    DATA "When the system is first powered up, all source modules are OFF."
1744    DATA "Source modules not selected as being 'OFF' are started upon"
1746    DATA "leaving the SOURCE SETUP.   However, if the source is in a"
1748    DATA "trigger mode other than off, it may not start until a trigger"
1750    DATA "is received.  Note that the Burst % and Burst time columns are"
1752    DATA "only valid if both source and inputs have the same span and block size"
1754    DATA ""
1756    DATA "The INPUT SETUP key is used to setup input modules."
1758    DATA "When the system powers up, one input module will be in"
1760    DATA "SEND trigger mode, and the others will be in RECEIVE trigger"
1762    DATA "mode.  At least one module (input or source) should normally"
1764    DATA "be in SEND trigger mode, so that the system will trigger."
1766    DATA "***END***"
1768 Page3:   !
1770    DATA "         Help for Template Application - Page 3"
1772    DATA ""
1774    DATA "The inputs start out at range 0 dBVp, and will usually"
1776    DATA "need to have their ranges changed to appropriate levels."
1778    DATA "The Autorange function is useful if the source module is"
1780    DATA "already going, but it takes at least 20 seconds, and will"
1782    DATA "not always work correctly if the source is in a burst or"
1784    DATA "pulse mode."
1786    DATA ""
1788    DATA "The DISPLAY SETUP key is used to change what is displayed"
1790    DATA "on the screen.  Each line in the menu corresponds to a trace"
1792    DATA "which could be plotted.  The trace will not actually be plotted"
1794    DATA "unless it is made active."
1796    DATA ""
1798    DATA "The MEASURE SETUP key is used to change the nature of the"
1800    DATA "measurement that is being made.  Averaging and FFT Window"
1802    DATA "Type, and the frequency span and center frequency can all"
1804    DATA "be set here."
1806    DATA "***END***"
1808 Page4:   !
1810    DATA "         Help for Template Application - Page 4"
1812    DATA ""
1814    DATA "Any of the four menus can be entered without aborting a"
1816    DATA "measurement that is in progress.  However, changing anything"
1818    DATA "in any menu except the DISPLAY SETUP menu will stop the"
1820    DATA "measurement.  Any current data is thrown away unless the"
1822    DATA "change was in the SOURCE SETUP menu.  While you are in any"
1824    DATA "menu, the measurement is temporarily paused."
1826    DATA ""
1828    DATA "Changes can be made in the DISPLAY SETUP menu without affecting"
1830    DATA "a measurement and without destroying any data.  You can do a"
1832    DATA "complete measurement and later decide what data you need to"
1834    DATA "display."
1836    DATA  "***END***"
1838  SUBEND
1840  !
1842  ! page ->
1844  !**********************************************************************
1846 Appl_debug:SUB Appl_debug(INTEGER Debug_mode)
1848  ! This routine enbles the user to call the Icode debugger interactively,
1850  !yet keeps an application's COM blocks separate from the debugger.
1852  !The parameter passed in is defined in the Icode documentation, but
1854  !briefly is as follows:
1856  ! 0:  If Icode paused, then debug, else return
1858  ! 1:  Wait for pause, then debug
1860  ! 2:  Debug
1862    COM /Exam_block_info/ Icode_info$(*),Source$(*),INTEGER Compiled(*),Icode_compiled,Icode_id,Source_size
1864    User_clr_scr !clear screen
1866    Icode_debug(Debug_mode,Icode_info$(*),Source$(*))
1868    User_clr_scr
1870  SUBEND
1872  !
1874  ! PAGE ->
1876  !*************************************************************************
1878 Meas_meas:SUB Meas_meas
1880    ! Contains commons used by the EXAM_MEAS subprograms
1882    ! Calls Meas_powerup
1884    COM /Meas_sprd/ Box$(1:2,1:14)[40],Title$(1:2,0:2)[40],Prompt$(1:14)[80]
1886    COM /Meas_sprd_num/ Col_width(1:2),Modify_col,INTEGER Max_row,Max_col
1888    COM /Meas_mod_labels/ Srce_labels$(1:63)[20],Inpt_labels$(1:63)[20]
1890    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
1892    COM /Meas_cmnd/ Cmnd$(2:5)[20],Def_value$(2:5)[20]
1894    !
1896    ! Probably want to add some of your own rows to this list
1898    !
1900    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
1902    Meas_powerup
1904  SUBEND
1906 Meas_powerup:SUB Meas_powerup
1908    ! Initializes constants, Sets default measurement parameters.
1910    ! Called by Meas_meas.
1912    !
1914    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
1916    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
1918    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
1920    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
1922    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
1924    !
1926    ! There are (at least) 2 kinds of rows in the measurement
1928    ! spreadsheet:  Command rows, such as Span, Center Frequency, etc.
1930    ! which map directly into commands to modules, and Info rows,
1932    ! such as number of averages, Window type, etc., which just
1934    ! need to be available for other routines to use.  These
1936    ! 2 kinds of rows are handled slightly differently below.
1938    !
1940    Cmnd_start=2  !Only FFTsize right now
1942    Cmnd_stop=2
1944    Info_start=3
1946    Av_r=3        !Average row
1948    Wind_r=4      !Window row
1950    Info_stop=5   !Demo row
1952    !
1954    Max_col=2
1956    Modify_col=2
1958    Max_row=Info_stop
1960    REDIM Box$(1:2,1:Max_row)
1962    MAT Box$= ("")
1964    MAT Title$= ("")
1966    !
1968    RESTORE Meas_data  !so we can read in the spreadsheet's contents
1970    FOR Row=Cmnd_start TO Cmnd_stop
1972      READ Cmnd$(Row),Def_value$(Row),Box$(1,Row),Prompt$(Row)
1974    NEXT Row
1976    FOR Row=Info_start TO Info_stop
1978      READ Box$(2,Row),Box$(1,Row),Prompt$(Row)
1980    NEXT Row
1982    !
1984    Current_inpt=1
1986    Title$(1,0)="MEASUREMENT SETUP"
1988    Title$(1,1)="Item"
1990    Title$(2,1)="Value"
1992    Col_width(1)=40
1994    Col_width(2)=20
1996    !
1998    Row=2              !reset cursor to top row for 1st time thru
2000    SUBEXIT
2002 Meas_data:!
2004    !
2006    !COMMAND ROWS
2008    ! Data is in the form:
2010    ! Command,default value,spreadsheet label,prompt
2012    DATA "FFT SIZE",         "512",   "Complex FFT Size        ->"
2014    DATA "Enter Complex FFT size  (512, 1024, 2048, or 4096)"
2016    !
2018    !INFO ROWS  (No Command)
2020    ! Data is in the form:
2022    ! default value,spreadsheet label,prompt
2024    !
2026    DATA "ON",    "Averaging               ->"
2028    DATA "Enter Averaging mode (ON,OFF)"
2030    !
2032    DATA "Hann",   "Window                  ->"
2034    DATA "Enter Window Type (Hann, Flat top, Rectangular)"
2036    !
2038    DATA "One choice",   "Define your own labels  ->"
2040    DATA "You can define the spreadsheet entries"
2042    !
2044  SUBEND
2046 Meas_init:SUB Meas_init
2048    ! Gets input labels from the config module,
2050    ! Sets input modules to the states shown in  measurement spreadsheet
2052    ! Called at poweron and After reloding state from a file
2054    !
2056    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2058    COM /Meas_mod_labels/ Srce_labels$(*),Inpt_labels$(*)
2060    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2062    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
2064    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
2066    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2068    !
2070    REDIM Box$(1:2,1:Max_row)
2072    ! Get Input labels
2074    !
2076    Cnfg_labels("ALL INPUT",Inpt_labels$(*),Inpt_count)
2078    IF Inpt_count=0 THEN SUBEXIT
2080    !
2082    ! Setup Inputs, then read back from current input
2084    ! Since block_size=2*fft_size, hoops must be jumped
2086    !  through here.  Also, the FFTsize is limited by the
2088    !  number of modules.
2090    Inpt_cmd("ALL INPUT","ZOOM","ON")
2092    FOR Row=Cmnd_start TO Cmnd_stop
2094      IF Cmnd$(Row)="FFT SIZE" THEN 
2096        Tmp$="MEASUREMENT SIZE"
2098        Parm$=VAL$(2*VAL(Def_value$(Row)))
2100        Inpt_cmd("ALL INPUT",Tmp$,Parm$)
2102        Inpt_cmd("ALL INPUT","TRANSFER BLOCK SIZE",Parm$)
2104        Box$(2,Row)=TRIM$(VAL$(1/2*VAL(FNInpt_rsp$(Inpt_labels$(Current_inpt),Tmp$))))
2106      ELSE
2108        Inpt_cmd("ALL INPUT",Cmnd$(Row),Def_value$(Row))
2110        Box$(2,Row)=TRIM$(FNInpt_rsp$(Inpt_labels$(Current_inpt),Cmnd$(Row)))
2112      END IF
2114    NEXT Row
2116    Row=2  !Cursor starts at top initially
2118    !
2120  SUBEND
2122 Meas_spread:SUB Meas_spread(Changed)
2124    ! This is where the user interacts with the Measurement spreadsheet.
2126    ! Valid New entries are put into the spreadsheet, Next/Prev keys
2128    ! are handled.  Changes in the Command rows are sent directly to
2130    ! modules, while changes in Info row are stored in COM in Box$(*),
2132    ! for later retrieval.
2134    !
2136    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2138    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2140    COM /Meas_mod_labels/ Srce_labels$(*),Inpt_labels$(*)
2142    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
2144    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
2146    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2148    DIM New_entry$[160],Choices$(0:20)[80]
2150    INTEGER Done,Dummy,I,Found_it
2152    Changed=0
2154    !
2156    ! Define softkeys.  Keys 1 through 4 are 'firmkeys'
2158    !
2160    ON KEY 5 LABEL "" CALL User_key5isr
2162    ON KEY 6 LABEL "" CALL User_key6isr
2164    ON KEY 7 LABEL FNUser_keylabel$("Prev") CALL User_key7isr
2166    ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
2168    !
2170    User_clr_scr
2172    !
2174    ! Now call spreadsheet.
2176    !
2178    Col=2
2180    Start_row=1
2182    Done=0
2184    REPEAT
2186      User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
2188      SELECT FNUser_check_key
2190      CASE 0
2192        GOSUB Meas_new_entry
2194      CASE 5,6
2196        BEEP 
2198        Dummy=FNUser_get_key
2200      CASE 7     ! Prev
2202        Dummy=FNUser_get_key
2204        GOSUB Meas_prev
2206      CASE 8     ! Next
2208        Dummy=FNUser_get_key
2210        GOSUB Meas_next
2212      CASE ELSE  ! A softkey, but not one of mine.
2214        Done=1
2216      END SELECT
2218    UNTIL Done
2220    User_clr_scr
2222    SUBEXIT
2224    !
2226 Meas_new_entry:!Handle keyboard entries
2228    SELECT Row
2230    CASE Cmnd_start    !   It's the BLOCK SIZE command
2232      Changed=1
2234      ON ERROR GOTO Meas_bad_size
2236      New_fft_size=VAL(New_entry$)
2238      IF New_fft_size<512 THEN New_fft_size=512
2240      IF New_fft_size>4096 THEN New_fft_size=4096
2242      GOSUB Update_fft_size
2244 Meas_bad_size:OFF ERROR 
2246    CASE Wind_r             ! Select window type
2248      Changed=1
2250      ON ERROR GOTO Meas_bad_wind
2252      REDIM Choices$(1:3)
2254      Choices$(1)="Hann"
2256      Choices$(2)="Flat top"
2258      Choices$(3)="Rectangular"
2260      GOSUB Meas_match_it
2262 Meas_bad_wind:OFF ERROR 
2264    CASE Av_r
2266      Changed=1
2268      ON ERROR GOTO Meas_bad_av
2270      REDIM Choices$(1:2)
2272      Choices$(1)="ON"
2274      Choices$(2)="OFF"
2276      GOSUB Meas_match_it
2278 Meas_bad_av:OFF ERROR 
2280    CASE Wind_r+1
2282      ON ERROR GOTO Oh_well
2284      REDIM Choices$(1:2)
2286      Choices$(1)="One Choice"
2288      Choices$(2)="Another Choice"
2290      GOSUB Meas_match_it
2292 Oh_well:OFF ERROR 
2294    END SELECT
2296    RETURN 
2298    !
2300 Meas_match_it:!
2302    Lib_match1(New_entry$,Choices$(*),Found,Choice_num)
2304    IF Found THEN 
2306      Changed=1
2308      Box$(2,Row)=Choices$(Choice_num)
2310    END IF
2312    RETURN 
2314    !
2316 Meas_prev:!Handle 'Previous' key
2318    SELECT Row
2320    CASE Av_r,Wind_r+1
2322      GOSUB Meas_toggle
2324    CASE Cmnd_start
2326      Changed=1
2328      Old_fft_size=VAL(Box$(2,Row))
2330      New_fft_size=Old_fft_size/2
2332      IF New_fft_size<512 THEN New_fft_size=4096
2334      GOSUB Update_fft_size
2336    CASE Wind_r
2338      Changed=1
2340      SELECT UPC$(Box$(2,Row))
2342      CASE "HANN"
2344        Box$(2,Row)="Rectangular"
2346      CASE "FLAT TOP"
2348        Box$(2,Row)="Hann"
2350      CASE "RECTANGULAR"
2352        Box$(2,Row)="Flat Top"
2354      END SELECT
2356    END SELECT
2358    RETURN 
2360    !
2362 Meas_next:!Handle 'Next' Key
2364    SELECT Row
2366    CASE Av_r,Wind_r+1
2368      GOSUB Meas_toggle
2370    CASE Cmnd_start
2372      Changed=1
2374      Old_fft_size=VAL(Box$(2,Row))
2376      New_fft_size=2*Old_fft_size
2378      IF New_fft_size>4096 THEN New_fft_size=512
2380      GOSUB Update_fft_size
2382    CASE Wind_r
2384      Changed=1
2386      SELECT UPC$(Box$(2,Row))
2388      CASE "HANN"
2390        Box$(2,Row)="Flat Top"
2392      CASE "FLAT TOP"
2394        Box$(2,Row)="Rectangular"
2396      CASE "RECTANGULAR"
2398        Box$(2,Row)="Hann"
2400      END SELECT
2402    END SELECT
2404    RETURN 
2406    !
2408 Meas_toggle:!
2410    SELECT Row
2412    CASE Av_r                  ! Toggle average mode on or off
2414      Changed=1
2416      IF Box$(2,Row)="ON" THEN 
2418        Box$(2,Row)="OFF"
2420      ELSE
2422        Box$(2,Row)="ON"
2424      END IF
2426    CASE Wind_r+1              ! Toggle whimsical choices
2428      Changed=1
2430      IF Box$(2,Row)="One choice" THEN 
2432        Box$(2,Row)="Another choice"
2434      ELSE
2436        Box$(2,Row)="One choice"
2438      END IF
2440    END SELECT
2442    RETURN 
2444 !
2446 Update_fft_size:!The block-size is usually 2*fftsize with zoom on
2448    Size$=VAL$(2*New_fft_size)
2450    Inpt_cmd("ALL INPUT","BLOCK SIZE",Size$)
2452    Inpt_cmd("ALL INPUT","TRANSFER BLOCK SIZE",Size$)
2454    Box$(2,Row)=TRIM$(VAL$(1/2*VAL(FNInpt_rsp$(Inpt_labels$(1),"BLOCK SIZE"))))
2456    RETURN 
2458  SUBEND
2460  !************************************************************************
2462  !
2464  !     Now some routines for the application to use
2466  ! These generally 'look' into Box$(*) and return what's there
2468  !************************************************************************
2470 Meas_span:DEF FNMeas_span
2472  ! Returns the Inpt span in Hz from the Measurement spreadsheet
2474  !
2476    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2478    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2480    ! Probably want to change this to something like:
2482    !  RETURN VAL(Box$(2,SPAN_ROW))
2484    RETURN 51200  ! for now
2486  FNEND
2488  !
2490 Meas_cf:DEF FNMeas_cf
2492  ! Returns the Inpt center freq in Hz from the Measurement spreadsheet
2494    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2496    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2498    ! Probably want to change this to something like:
2500    ! RETURN VAL(Box$(2,Cf_row))
2502    RETURN 25600   ! for now
2504  FNEND
2506  !
2508 Meas_fftsize:DEF FNMeas_fftsize
2510  ! Returns the Complex FFTsize from the Measurement Spreadsheet
2512    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2514    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2516    IF POS(Box$(1,Cmnd_start),"FFT") THEN 
2518      RETURN VAL(Box$(2,Cmnd_start))
2520    ELSE
2522      RETURN 2*VAL(Box$(2,Cmnd_start))
2524    END IF
2526  FNEND
2528  !
2530 Meas_wind_type:DEF FNMeas_wind_type$
2532  ! Returns the window type selected in the Measurement Spreadsheet
2534    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2536    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2538    RETURN Box$(2,Wind_r)
2540  FNEND
2542  !
2544 Meas_avg_mode:DEF FNMeas_avg_mode
2546    ! Returns 1 if averages are on, 0 if averaging is off
2548    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2550    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Av_r,Wind_r,Row
2552    IF POS(UPC$(Box$(2,Av_r)),"ON") THEN RETURN 1
2554    RETURN 0
2556  FNEND
2558 !
2560 Meas_save:SUB Meas_save(@File,Ok)
2562  !Called by the FILE module to save the state of the
2564  !measurement spreadsheet into file @File.
2566  !
2568    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2570    !
2572    File_format_rev=2621
2574    OUTPUT @File;File_format_rev
2576    !
2578    CALL File_save_s(@File,Box$(*))
2580    Ok=1
2582    !
2584  SUBEND
2586  !************************************************************************
2588 Meas_load:SUB Meas_load(@File,Ok)
2590  !Called by the FILE module to load the state of the meas spreadsheet
2592  !from file @File.  Meas_init must be called to init modules
2594  !
2596    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2598    !
2600    ENTER @File;File_format_rev
2602    SELECT File_format_rev
2604    CASE 2621
2606    !
2608      CALL File_load_s(@File,Box$(*))
2610    CASE ELSE  !unknown rev
2612      CALL User_error("ERROR Incompatible display file format in Disp_load.")
2614      Ok=0
2616      SUBEXIT
2618    END SELECT
2620    !
2622    CALL Meas_init
2624    Ok=1
2626    !
2628  SUBEND
2630  ! PAGE -> 
2632  !************************************************************************