2  !   OUTPUT 2 USING "#,K";"<lf>INDENT<cr>REN 2,2<cr><lf>RE-STORE ""/RAMBO/DEMO/SGEN_TMS""<cr>"
4     !
6     END
8     !
10    ! PAGE -> 
12    !***********************************************************************
14 Appl_appl:SUB Appl_appl
16    ! Called when program is first run ("poweron")
18      ! All commons used in TMS 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:3,1:63)[16],Input_labels$(1:63)[16],Num_inputs,Output_labels$(1:63)[16],Num_outputs
24      COM /Tms_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(1:63)
26      COM /Tms_block_info/ Icode_info$(0:127)[40],Icode_id,Source$(0:300)[80]
28    SUBEND
30    !
32    ! PAGE -> 
34    !***********************************************************************
36 Appl_start:SUB Appl_start
38    ! Called when a measurement is to be started (restarted)
40    ! Calls other subs to pass info to ICODE program,
42    ! Sends some global commands to input modules,
44    ! Starts the icode program.
46    !
48      COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
50      COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs,Output_labels$(*),Num_outputs
52      COM /Appl_data/ Data_buffer(*),Data_header(*)
54      !
56      DIM A$[255]
58      !
60      !Clear Error queue,Stop Icode,Clear Pending SRQs
62      Hw_cmd("CLR;ABRT;STA?")
64      !
66      DISP "Filling and downloading parameter block"
68      CALL Tms_params
70      Inpt_cmd("ALL INPUT","LMAN")   !turn off unrelated input modules
72      Inpt_cmd("ALL INPUT","CLR;RQS 0;INTR 0;CLASM 50") !clear all modules
74      !
76      DISP "Initializing Input module to take data"
78      Module_label$=Disp_choices$(1,FNDisp_choice(1,1))
80      Mask$=VAL$(FNInpt_str_2_stat("BLOCK AVAILABLE"))
82      I_mask$=VAL$(FNInpt_str_2_stat("ERROR|FIFO OVERFLOW"))
84      Inpt_cmd(Module_label$,"CLASP 50;RQS",Mask$)
86      Inpt_cmd(Module_label$,"INTR",I_mask$)
88      Inpt_cmd(Module_label$,"TRANSFER MODE","BLOCK")
90      Inpt_cmd(Module_label$,"SYNC ON")
92      !
94      DISP "FILLING MODULE LIST"
96      ALLOCATE INTEGER Temp_list(0:2)
98      Temp_list(0)=FNMeas_fftsize*2  ! Allow for filter settling
100     Temp_list(1)=1                 ! Loop count
102     Temp_list(2)=Num_inputs        ! module count
104     Hw_write_blk(FNIcode_ext_id("MOD_LIST",Icode_info$(*)),Temp_list(*))
106     DEALLOCATE Temp_list(*)
108     !
110     REDIM Data_buffer(1:4,0:FNMeas_fftsize-1)
112     !
114     ! SETUP HP-IB MODULE  FOR SRQ ON MSG,PRG,OR ERROR
116     Mask$=VAL$(FNHw_str_2_stat("MESSAGE|ERROR|PRG"))
118     Hw_cmd("RQS "&Mask$)
120     !
122     DISP "Starting the measurement"
124     Hw_wait_gbl_rdy
126     Hw_cmd("PROG "&VAL$(Icode_id))
128     !
130   SUBEND
132   !
134   ! PAGE -> 
136   !***********************************************************************
138 Appl_get_data:SUB Appl_get_data(Got_new_data,Stopped)
140   ! Called to get new data from the module
142   ! If new data is not available, this module should return
144   ! with Got_new_data false.  If there is new data, it should
146   ! update the Data_buffer (and Full_scale array if necessary) and
148   ! return with Got_new_data true.
150   !
152     COM /Appl_data/ Data_buffer(*),Data_header(*)
154     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs,Output_labels$(*),Num_outputs
156     COM /Tms_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(*)
158     COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
160   !
162     Got_new_data=0
164     IF NOT FNHw_srq THEN SUBEXIT
166     !
168 Got_srq:!
170     Sta=VAL(FNHw_cmd_rsp$("STA?"))
172     IF BINAND(Sta,FNHw_str_2_stat("MESSAGE")) THEN 
174       Sig_value=VAL(FNHw_cmd_rsp$("SIG?"))
176       SELECT Sig_value
178       CASE <=0
180         DISP "Doing average number ";ABS(Sig_value)+1
182         SUBEXIT
184       CASE 2
186         User_error("FOR SOME REASON, MEASUREMENT CRASHED....sorry...TRY AGAIN")
188         Stopped=1
190       CASE 4      !synchronize Basic and Icode
192         Hw_cmd("CONT")
194         SUBEXIT
196       CASE 5
198         DISP "reading data from HP3565S"
200         Average_number=FNMeas_avg_mode*FNMeas_num_avg
202         GOSUB Fill_hdr
204         Stopped=1
206         DISP ""
208         SUBEXIT
210       CASE ELSE
212         User_error("Unknown message in appl_get data: "&VAL$(Sig_value))
214       END SELECT
216     END IF
218     IF BINAND(Sta,FNHw_str_2_stat("ERROR")) THEN 
220       User_error("HP3565S HP-IB module reports error #"&FNHw_cmd_rsp$("ERR?"))
222     END IF
224     SUBEXIT
226 Fill_hdr: !
228     Hw_read_fblk(FNIcode_ext_id("OUTPUT_BUFF",Icode_info$(*)),Data_buffer(*))
230     Got_new_data=1
232     SELECT UPC$(FNMeas_wind_type$)
234     CASE "HANN"
236       Scaler=Corr_fact*Hann_fact
238     CASE "FLAT TOP"
240       Scaler=Corr_fact*Flat_top_fact
242     CASE "RECTANGULAR"
244       Scaler=Corr_fact
246     END SELECT
248         !
250     Module_label$=Disp_choices$(1,FNDisp_choice(1,1))
252     Ovld_bit=BINAND(FNCnfg_rmst(Module_label$),FNInpt_str_2_stat("OVERLOAD"))
254     FOR I=1 TO 3 STEP 2   !TIME ARRAYS
256       Range_fact=10^(Range(I)/10)
258       Data_header(I,1)=0          !   Offset
260       Data_header(I,2)=2/(SQR(Corr_fact*Range_fact))
262       Data_header(I,3)=Ovld_bit
264       Data_header(I,4)=0   !linear plot
266       Data_header(I,6)=0
268     NEXT I
270     FOR I=2 TO 4 STEP 2   !LOG ARRAYS
272       Range_fact=10^(Range(I)/10)
274       Data_header(I,1)=0          !   Offset
276       Data_header(I,2)=1/(Scaler*Range_fact)
278       Data_header(I,3)=Ovld_bit
280       Data_header(I,4)=10   !MULT LOGS BY 10
282       Data_header(I,5)=Half_lsb/Scaler
284       Data_header(I,6)=Average_number
286     NEXT I
288     RETURN 
290   SUBEND
292   !
294   ! PAGE -> 
296   !***********************************************************************
298 Appl_update:SUB Appl_update
300     ! This routine is call whenever the display configuration is changed
302     ! The default y-axis limits are defined here.
304     !
306     COM /Appl_data/ Data_buffer(*),Data_header(*)
308     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs,Output_labels$(*),Num_outputs
310     COM /Tms_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(*)
312     !
314     Num_plots=FNDisp_num_plots
316     ALLOCATE Plot_to_buf(1:Num_plots)
318     ALLOCATE X_units$(1:Num_plots)[10],Y_units$(1:Num_plots)[10]
320     ALLOCATE Start_x(1:Num_plots),Per_bin_x(1:Num_plots)
322     ALLOCATE Start_bin(1:Num_plots),Num_bins(1:Num_plots)
324     ALLOCATE Y_def_max(1:Num_plots),Y_def_min(1:Num_plots)
326     !
328     !
330     ! Get the available module names from the cnfg module
332     !
334     Fftsize=FNMeas_fftsize
336     Span=FNMeas_span
338     Hz_per_bin=2.56*Span/Fftsize  !with zoom off
340     !
342     MAT Start_bin= (0)
344     MAT Num_bins= (Fftsize)
346     !
348     Module_label$=Disp_choices$(1,FNDisp_choice(1,1))
350     FOR Plot_num=1 TO Num_plots
352       Plot_to_buf(Plot_num)=4*(FNDisp_choice(Plot_num,1)-1)+2*(FNDisp_choice(Plot_num,2)-1)+FNDisp_choice(Plot_num,3)
354       Range(Plot_num)=VAL(FNInpt_rsp$(Module_label$,"RANGE"))
356       SELECT UPC$(Disp_choices$(3,FNDisp_choice(Plot_num,3))[1,4])
358       CASE "FREQ"
360         X_units$(Plot_num)=("Hz")
362         Start_x(Plot_num)=0 !BIN 0 FREQ VALUE
364         Per_bin_x(Plot_num)=(Hz_per_bin)
366         Num_bins(Plot_num)=(Fftsize/2.56+1)            !201 point fft
368         IF FNInpt_rsp$(Module_label$,"INPUT MODE")="CHRG" THEN 
370           Y_units$(Plot_num)="dBpCp"
372         ELSE
374           Y_units$(Plot_num)=("dBVp")
376         END IF
378         Y_def_max(Plot_num)=Range(Plot_num)
380         Y_def_min(Plot_num)=Y_def_max(Plot_num)-(100) ! 100 dB dynamic rng
382       CASE "TIME"
384         Y_def_max(Plot_num)=10^(Range(Plot_num)/20)
386         Y_def_min(Plot_num)=-Y_def_max(Plot_num)
388         X_units$(Plot_num)="Secs"
390         IF FNInpt_rsp$(Module_label$,"INPUT MODE")="CHRG" THEN 
392           Y_units$(Plot_num)="pC"
394         ELSE
396           Y_units$(Plot_num)="V"
398         END IF
400         Start_x(Plot_num)=0
402         Per_bin_x(Plot_num)=.390625/Span
404       END SELECT
406     NEXT Plot_num
408     !
410     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(*))
412   SUBEND
414   !
416   ! PAGE -> 
418   !***********************************************************************
420 Appl_init:SUB Appl_init
422     !
424     ! This routine is called whenever a the configuration has changed
426     ! (Called by Appl_main.)  The Icode program is assembled and
428     ! Spreadsheets are initialized etc.
430     COM /Appl_data/ Data_buffer(*),Data_header(*)
432     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs,Output_labels$(*),Num_outputs
434     COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
436     DIM Dummy$[256]
438     !
440     Hw_dev_clear
442     Appl_powerup               ! Initialize spreadsheets
444     Hw_cmd("TRGU;ABRT;DISA;LSPR 1") !LOAD CORRECT SP PROGS
446     !
448     ! Get the available module names from the cnfg module
450     Cnfg_labels("ALL INPUT",Input_labels$(*),Num_inputs)
452     IF Num_inputs=0 THEN SUBEXIT
454     Num_inputs=1                    !NO MORE THAN 1 INPUT CHANNEL ALLOWED
456     !
458     Tms_do_icode               !assembles and downloads the icode program
460     Tms_fft_coefs              ! download fft coefficients
462     Tms_320_prog               ! download tms320 program
464     User_clr_scr
466     !
468     Inpt_cmd(Input_labels$(1),"TRIGGER MODE","SEND")
470     Cnfg_labels("ALL SOURCE",Output_labels$(*),Num_outputs)
472     IF Num_outputs<1 THEN 
474       User_error(" Before continuing, connect a signal source to "&Input_labels$(1))
476     ELSE
478       User_error(" Before continuing, connect "&Output_labels$(1)&" to "&Input_labels$(1))
480       Srce_cmd(Output_labels$(1),"RESET MODULE")
482       Srce_cmd(Output_labels$(1),"OUTPUT MODE","RANDOM")
484       Srce_cmd(Output_labels$(1),"AMPLITUDE","0")
486       Srce_cmd(Output_labels$(1),"START")
488     END IF
490     User_clr_scr
492     !
494     Num_cols=3
496     ALLOCATE Disp_titles$(1:Num_cols,1:2)[20]
498     ALLOCATE Disp_prompt$(1:Num_cols)[80]
500     ALLOCATE Disp_width(1:Num_cols)
502     !
504     MAT Disp_titles$= ("")
506     Disp_titles$(1,1)="Module"
508     Disp_titles$(1,2)="Label"
510     Disp_titles$(2,1)="Trace"
512     Disp_titles$(2,2)="Type"
514     Disp_titles$(3,2)="Domain"
516     Disp_prompt$(1)="Enter module label"
518     Disp_prompt$(2)="Enter trace type: FILTered, UNFiltered"
520     Disp_prompt$(3)="Enter trace type: TIME, FREQ"
522     Disp_width(1)=16
524     Disp_width(2)=7
526     Disp_width(3)=7
528     MAT Disp_choices$= ("")
530     !
532     Disp_choices$(1,1)=Input_labels$(1)
534     !
536     Disp_choices$(2,1)="UNF"
538     Disp_choices$(2,2)="FILT"
540     Disp_choices$(3,1)="TIME"
542     Disp_choices$(3,2)="FREQ"
544     !
546     ! Setup Disp module with titles
548     Disp_spread_set(Disp_titles$(*),Disp_prompt$(*),Disp_width(*),Disp_choices$(*))
550     !
552     ! Module list contains info needed by 'f_thruput' instruction
554     DISP "Filling module list"
556     ALLOCATE INTEGER Module_list(0:Num_inputs+2)
558     Module_list(0)=Num_inputs
560     Module_list(3)=FNCnfg_get_modnum(Input_labels$(1))
562     Hw_write_blk(FNIcode_ext_id("MOD_LIST",Icode_info$(*)),Module_list(*))
564     !
566     ! Initialize data arrays, assume default 512 fftsize
568     REDIM Data_buffer(1:4,0:511)
570     DISP ""
572   SUBEND
574   !
576   ! PAGE -> 
578   !***********************************************************************
580 Tms_params:SUB Tms_params
582     ! This routine asks the Measurement spreadsheet for information
584     ! about windows, FFTsize, Averaging, etc., and passes it to
586     ! the ICODE program.
588     COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
590     !
592     ALLOCATE INTEGER Param(0:15)
594     Fftsize=FNMeas_fftsize
596     SELECT UPC$(FNMeas_wind_type$)
598     CASE "RECTANGULAR"
600       Do_window=0
602     CASE "HANN"
604       Do_window=1
606       Wind_type_code=1
608     CASE "FLAT TOP"
610       Do_window=1
612       Wind_type_code=2
614     END SELECT
616     !
618     Param(0)=0      !block scaling exponent MSW
620     Param(1)=0      !block scaling exponent LSW
622     Param(2)=PROUND(LOG(Fftsize)/LOG(2),0)   !9,10,11,12
624     Param(3)=0                               !overflow flag
626     Param(4)=Do_window  !SWAP_FLAG
628     Param(5)=Do_window  !WINDOW FLAG
630     Param(6)=2          !OUTPUT IS MAG^2
632     !
634     ! System info for ICODE program use
636     Param(7)=Fftsize
638     Param(8)=FNMeas_num_avg
640     Param(9)=Wind_type_code   !1=hanning, 2=flattop
642     Param(10)=0               !Not used
644     Param(11)=FNMeas_avg_mode !0=OFF, 1=ON
646     Param(12)=0               !Not used
648     Param(13)=0               !not used
650     Param(14)=0               !not used
652     Param(15)=FNMeas_fftsize*2
654     !
656     GOSUB Send_params
658     IF FNHw_io_error THEN 
660       Hw_dev_clear
662       GOSUB Send_params
664       IF FNHw_io_error THEN 
666         User_stop("Couldn't recover from i/o error...try cycling power/check HP-IB cables etc.")
668       END IF
670     END IF
672     Subext
674 Send_params: !
676     Hw_write_blk(FNIcode_ext_id("PARAM",Icode_info$(*)),Param(*),2)
678   SUBEND
680   !
682   ! PAGE -> 
684   !***********************************************************************
686 Tms_do_icode:SUB Tms_do_icode
688   !
690   ! assembles and downloads the  the icode program
692   !
694     COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
696     Info_info=2 !downloader allocates blocks, debugging allowed
698     ALLOCATE INTEGER Compiled(0:1024),List_array$(0:1)[8]
700     I=0
702     LOOP
704       READ Source$(I)
706     EXIT IF POS(Source$(I),"EL_COMPLETO")
708       I=I+1
710     END LOOP
712 Private_idaho:  !
714     REDIM Source$(0:I)
716     Do_listing=0
718     Assy_errors=FNIcode_assemble(Source$(*),Compiled(*),(Info_info),Icode_info$(*),(Do_listing),List_array$(*))
720     IF NOT Assy_errors THEN 
722       Icode_id=FNIcode_dld(Compiled(*),(Info_info),Icode_info$(*))
724     ELSE
726       User_stop("Too many errors when assembling Icode...")
728     END IF
730     SUBEXIT
732 Tms_icode: !
734     DATA""
736     DATA"!**********************************************************"
738     DATA"! ICODE PROGRAM TO TAKE DATA FOR TMS320 DEMO PROGRAM"
740     DATA"!   ALSO DOES THE SIGNAL PROCESSING"
742     DATA"!**********************************************************"
744     DATA""
746     DATA" VAR   A                 0   !gen purpose temp var"
748     DATA" VAR   NUM_AVGS          0   !# averages requested"
750     DATA" VAR   AVG_NUM           0   !current average number"
752     DATA" VAR   BSIZ              0   !xfer size from input modules"
754     DATA" VAR   VALID_LOOPS       0   !used by ready ram"
756     DATA" VAR   MF_MOD            0   !current input module"
758     DATA" VAR   P_INP             0   !pointer into input buffer"
760     DATA" VAR   FFTSIZE         512   !#complex words"
762     DATA" VAR   FFTSIZEX2      1024   !total # 16 BIT WORDS"
764     DATA" VAR   FFTSIZEX3      1536   !"
766     DATA" VAR   FFTSIZEX4      2048   !for floating point records"
768     DATA" VAR   BUFF_1            0   !offset of unfiltered time"
770     DATA" VAR   BUFF_2            0   !offset of unfiltered freq data"
772     DATA" VAR   BUFF_3            0   !offset of filtered time data"
774     DATA" VAR   BUFF_4            0   !offset of filtered freq data"
776     DATA" VAR   FFT_KEEP          0   !for 201 line resolution"
778     DATA" VAR   FFT_KEEPX2        0   !"
780     DATA" VAR   FFT_KEEPX4        0   ! for floating point records"
782     DATA" VAR   FFT_KEEPX5        0   ! for fast average records"
784     DATA" VAR   OFFSET            0   !gp pointer"
786     DATA" VAR   FREQ_EXP          0   !block scaling exp of mag^2 freq"
788     DATA" VAR   TEMP              0"
790     DATA" VAR   I                 0   !loop counter"
792     DATA" VAR   WIND_TYPE         0   !0=Uniform,1=Hann, 2=Flat top"
794     DATA""
796     DATA"! Variables which  don't change!!!"
798     DATA" VAR   ZERO              0   ! var always = 0"
800     DATA" VAR   BASE_EXP        -24   !initial exp of avg array block"
802     DATA" VAR   MINUS1           -1   !will always be -1,but must be a var"
804     DATA" VAR   FIFTEEN          15   ! for a v_put32_indexed"
806     DATA""
808     DATA" CONST  FFT           4032 !start address of fft operation"
810     DATA" CONST  FILT_ADDR       64 !start addr of filter program"
812     DATA" CONST  INTLV_OFFS   16384 !offset of zeroes for interleaving"
814     DATA" CONST  FILT_OFFS     8192 !offset of filtered time"
816     DATA""
818     DATA" DEFBLK_MAIN   INPUT_BUFF    32768,2"
820     DATA" DEFBLK_MAIN   MOD_LIST        128,2"
822     DATA" DEFBLK_SP     WIND           8192,2"
824     DATA" DEFBLK_SP     SP_INPUT       8192,2"
826     DATA" DEFBLK_SP     SP_OUTPUT      8192,2"
828     DATA" DEFBLK_SP     COEF           4096,2"
830     DATA" DEFBLK_SP     PARAM           182,2"
832     DATA" DEFBLK_SP     SP_WORK        8192,2"
834     DATA" DEFBLK_MAIN   OUTPUT_BUFF   65536,2"
836     DATA" DEFBLK_MAIN   AVG_ARRAY     65536,2"
838     DATA" DEFBLK_MAIN   SP_PROG         128,2"
840     DATA""
842 Tms_icode_start: !
844     DATA""
846     DATA"        V_GET16_INDEXED PARAM,7,FFTSIZE    !512,1024,2048,4096"
848     DATA"        V_MULT          FFTSIZE,2,FFTSIZEX2"
850     DATA"        V_MULT          FFTSIZE,3,FFTSIZEX3"
852     DATA"        V_MULT          FFTSIZE,4,FFTSIZEX4"
854     DATA"        V_CEQUATE       0,BUFF_1     !offsets in output buffer"
856     DATA"        V_ADD           FFTSIZEX4,BUFF_1,BUFF_2"
858     DATA"        V_ADD           FFTSIZEX4,BUFF_2,BUFF_3"
860     DATA"        V_ADD           FFTSIZEX4,BUFF_3,BUFF_4"
862     DATA""
864     DATA"! We are in unzoomed mode, so 201/512 lines are useful"
866     DATA"        V_MULT          FFTSIZE,200,A"
868     DATA"        V_DIV           A,512,A"
870     DATA"        V_ADD           1,A,FFT_KEEP        !in data points"
872     DATA"        V_MULT          FFT_KEEP,2,FFT_KEEPX2"
874     DATA"        V_MULT          FFT_KEEP,4,FFT_KEEPX4"
876     DATA"        V_MULT          FFT_KEEP, 5,FFT_KEEPX5"
878     DATA""
880     DATA"        V_ADD            FILT_OFFS,FFTSIZE,P_INP"
882     DATA"        V_GET16_INDEXED PARAM,8,NUM_AVGS    !1 to N"
884     DATA"        V_GET16_INDEXED PARAM,9,WIND_TYPE   !1=HANNING, 2=FLATTOP"
886     DATA"        V_GET16_INDEXED MOD_LIST,3,MF_MOD"
888     DATA""
890     DATA"        C_GOSUB         INIT_W      !initialize window"
892     DATA""
894     DATA"! Initialize input buffer array"
896     DATA"        F_READY_RAM     1,INPUT_BUFF,0,MOD_LIST,0,VALID_LOOPS"
898     DATA"        F_KEEP_READY_RAM"
900     DATA"        F_SHORT_CONST   INPUT_BUFF,INTLV_OFFS,8192,0,0"
902     DATA""
904     DATA"! Intitialize fast average array"
906     DATA"        F_FAST_AVG_INIT AVG_ARRAY,0,FFTSIZEX2,0,0,BASE_EXP"
908     DATA"        V_CEQUATE       0,AVG_NUM"
910     DATA""
912     DATA"!-----------Take data------------------------------------"
914     DATA""
916     DATA"! Start modules, let basic trigger them"
918     DATA"        F_MOD_COMMAND   MF_MOD,'STRT'"
920     DATA"        F_WAIT_TO_SIG   4          !wait for Basic to catch up"
922     DATA"        F_PAUSE"
924     DATA"        C_GOSUB         WAIT_RDY"
926     DATA"        F_SYNC"
928     DATA"! Begin loop"
930     DATA" L1:    F_THRUPUT        1,1"
932     DATA"        C_BEQ            OOPS,VALID_LOOPS,0"
934     DATA""
936     DATA"! Let Basic know what average we are doing"
938     DATA"        V_MULT           AVG_NUM,MINUS1,TEMP"
940     DATA"        F_SIGNAL         TEMP"
942     DATA""
944     DATA"!----Now do FFT of unfiltered data, and save to avg array-----"
946     DATA""
948     DATA"! Since we are in Baseband mode, need to interleave with zeroes"
950     DATA"       F_SHORT_INTRLVE   INPUT_BUFF,FFTSIZE,INPUT_BUFF,INTLV_OFFS"
952     DATA".                        SP_INPUT,0,FFTSIZE"
954     DATA"        C_GOSUB          DO_FFT"
956     DATA"        F_FAST_AVG_ADD   SP_OUTPUT,0,AVG_ARRAY,0,FFT_KEEP,FREQ_EXP"
958     DATA""
960     DATA"!---------Now do filtering -------------------------------------"
962     DATA""
964     DATA"        F_LOAD_PROG      SP_PROG,0     ! Load filter algorithm"
966     DATA"        F_MOVE_BLOCK     INPUT_BUFF,0,SP_INPUT,0,FFTSIZEX2"
968     DATA""
970     DATA"! PARAM(15) has 2*fftsize in it"
972     DATA"        F_SIG_PROC       FILT_ADDR,0,3,PARAM,15"
974     DATA".                        SP_INPUT,0,SP_OUTPUT,0"
976     DATA" FILT0: C_SP_BEQ         FILT0,2"
978     DATA""
980     DATA"! Save filtered time data, toss settling time, interleave for FFT"
982     DATA"        F_MOVE_BLOCK     SP_OUTPUT,0,INPUT_BUFF"
984     DATA".                        FILT_OFFS,FFTSIZEX2"
986     DATA"        F_SHORT_TO_FLOAT INPUT_BUFF,P_INP,OUTPUT_BUFF,BUFF_3"
988     DATA".                        FFTSIZE"
990     DATA"        F_SHORT_INTRLVE  INPUT_BUFF,P_INP,INPUT_BUFF,INTLV_OFFS"
992     DATA".                        SP_INPUT,0,FFTSIZE"
994     DATA"        C_GOSUB          DO_FFT  !of filtered time data"
996     DATA"        F_FAST_AVG_ADD   SP_OUTPUT,0,AVG_ARRAY"
998     DATA".                        FFT_KEEPX5,FFT_KEEP,FREQ_EXP"
1000    DATA""
1002    DATA"        V_ADD  1,AVG_NUM,AVG_NUM"
1004    DATA"        C_BLT  L1,AVG_NUM,NUM_AVGS"
1006    DATA""
1008    DATA"        F_FAST_AVG_DIV  AVG_ARRAY,0"
1010    DATA".                       AVG_ARRAY,0,FFT_KEEPX2,NUM_AVGS"
1012    DATA"        F_MOVE_BLOCK  AVG_ARRAY,0,OUTPUT_BUFF,BUFF_2,FFT_KEEPX4"
1014    DATA"        F_MOVE_BLOCK  AVG_ARRAY,FFT_KEEPX4"
1016    DATA".                     OUTPUT_BUFF,BUFF_4,FFT_KEEPX4"
1018    DATA""
1020    DATA"! Send unfiltered time data to output buffer"
1022    DATA"      F_SHORT_TO_FLOAT INPUT_BUFF,FFTSIZE"
1024    DATA".                      OUTPUT_BUFF,BUFF_1,FFTSIZE"
1026    DATA""
1028    DATA"! Signal Processing Completed, show results"
1030    DATA"         F_WAIT_TO_SIG 5"
1032    DATA"         C_END"
1034    DATA""
1036    DATA" OOPS:  F_WAIT_TO_SIG 2    !crashed !"
1038    DATA"        C_END"
1040    DATA""
1042    DATA""
1044    DATA"!***********************************************************"
1046    DATA"! Subroutine WAIT_RDY waits for global ready"
1048    DATA"!***********************************************************"
1050    DATA" WAIT_RDY:"
1052    DATA"          F_GET_GLB_STA A"
1054    DATA"          V_NOT A,A"
1056    DATA"          C_BITSET WAIT_RDY,A,4   !loop until ready"
1058    DATA"          C_RTS"
1060    DATA""
1062    DATA"!***********************************************************"
1064    DATA"! subroutine DO_FFT loads the FFT algorithm, initializes the"
1066    DATA"! time block scaling-exponent to zero, does an fft, (output"
1068    DATA"! has been set to be magnitude^2 by the parameter block) and"
1070    DATA"! stores the resultant block scaling exponent in the variable"
1072    DATA"! 'A'"
1074    DATA"!***********************************************************"
1076    DATA" DO_FFT:"
1078    DATA"         V_PUT32_INDEXED PARAM,0,ZERO"
1080    DATA"         F_LOAD_SP_ALGS 1"
1082    DATA"   F_SIG_PROC FFT,0,5,PARAM,0,COEF,0,WIND,0,SP_INPUT,0,SP_OUTPUT,0"
1084    DATA" FFT0:   C_SP_BEQ FFT0,2"
1086    DATA"         V_GET32_INDEXED PARAM,0,FREQ_EXP !get block exp"
1088    DATA"         C_RTS"
1090    DATA""
1092    DATA"!************************************************************"
1094    DATA"! Subroutine INIT_WIND forms a window block in the TMS320 RAM"
1096    DATA"!************************************************************"
1098    DATA""
1100    DATA" INIT_W: C_BEQ HANN,WIND_TYPE,1"
1102    DATA"        C_BEQ FLAT_TOP,WIND_TYPE,2"
1104    DATA"        C_RTS    ! if no window was selected"
1106    DATA" HANN:"
1108    DATA"        F_FLOAT_WINGEN INPUT_BUFF,0,FFTSIZE,2,0.499984,-.499984"
1110    DATA"        C_GOTO CONT_WIND"
1112    DATA" FLAT_TOP:"
1114    DATA""
1116    DATA"! The 'normal' flat top coefficients are"
1118    DATA"!   0.994484/2,-0.955728,0.539289,-.0915810"
1120    DATA"! These are all scaled by here to make the peak at 32767"
1122    DATA"        F_FLOAT_WINGEN INPUT_BUFF,0,FFTSIZE,4,  .954423166665"
1124    DATA".               -1.8344567519  , 1.03512960516,-.175783678825"
1126    DATA" CONT_WIND:"
1128    DATA"        F_FLOAT_TO_SHORT INPUT_BUFF,0,OUTPUT_BUFF,0,FFTSIZE"
1130    DATA"        F_SHORT_INTRLVE OUTPUT_BUFF,0,OUTPUT_BUFF,0,WIND,0,FFTSIZE"
1132    DATA"        C_RTS"
1134    DATA""
1136    DATA"!----------------------------------------------------------"
1138    DATA" END:   C_END"
1140    DATA"        EL_COMPLETO"
1142    DATA"!----------------------------------------------------------"
1144  SUBEND
1146  !
1148  ! PAGE -> 
1150  !***********************************************************************
1152 Appl_main:SUB Appl_main(Init)
1154    !
1156    !  This is the main loop for the application.  It sets up for
1158    !  the measurement, sets up the softkeys, and loops processing
1160    !  key presses, updating the measurement, and calling the
1162    !  measurement loop.
1164    !
1166    COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*),Num_inputs,Output_labels$(*),Num_outputs
1168    !
1170    GOSUB Appl_main_keys  !to setup softkeys
1172    !
1174    Hw_dev_clear      !clear Interface module to known state
1176    IF Init THEN      !init everything, assemble icode, etc.
1178      Appl_init
1180    END IF
1182    !
1184    IF Num_inputs=0 THEN 
1186      User_error("Sorry, but this program requires an input module for proper operation.")
1188      SUBEXIT
1190    END IF
1192      !
1194    Restart_meas=1   !come up running
1196    Display_changed=1
1198    Meas_stopped=0   !can't be stopped if we are running
1200    Axes_not_done=0
1202    Leave_me=0
1204    REPEAT
1206      !
1208      IF Meas_stopped THEN 
1210        DISP "Waiting for START key. . ."
1212        ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
1214      ELSE
1216        ON KEY 7 LABEL FNUser_keylabel$("STOP") CALL User_key7isr
1218      END IF
1220    !
1222      IF Restart_meas THEN 
1224        Appl_start
1226        Restart_meas=0
1228        Meas_stopped=0
1230        Display_changed=1
1232        Data_valid=0
1234      END IF
1236      !
1238      IF Display_changed THEN 
1240        Appl_update
1242        Disp_plot_axis !a keypress will exit this immediately
1244        Axes_not_done=FNUser_key_press !are all axes up?
1246      END IF
1248      !
1250      Appl_meas_loop(Meas_stopped,Display_changed,Data_valid)
1252      !
1254      WHILE FNUser_key_press
1256        Appl_do_main(Restart_meas,Meas_stopped,Display_changed,Leave_me,Data_valid,Axes_not_done)
1258      END WHILE
1260      !
1262    UNTIL Leave_me
1264    Hw_dev_clear
1266    Cnfg_cmd("ALL","CLASM 50")
1268    SUBEXIT
1270  !
1272 Appl_dummy: !
1274    BEEP 
1276    RETURN 
1278 !
1280 Appl_main_keys:!
1282    ON KEY 0 LABEL "" GOSUB Appl_dummy
1284    ON KEY 1 LABEL FNUser_keylabel$("INPUT SETUP") CALL User_key1isr
1286    ON KEY 2 LABEL FNUser_keylabel$("SOURCE SETUP") CALL User_key2isr
1288    ON KEY 3 LABEL FNUser_keylabel$("DISPLAY SETUP") CALL User_key3isr
1290    ON KEY 4 LABEL FNUser_keylabel$("MEASURE SETUP") CALL User_key4isr
1292    ON KEY 5 LABEL FNUser_keylabel$("HELP") CALL User_key5isr
1294    ON KEY 6 LABEL FNUser_keylabel$("MARKER") CALL User_key6isr
1296    ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
1298    ON KEY 8 LABEL FNUser_keylabel$("EXIT") CALL User_key8isr
1300    ON KEY 9 LABEL "" GOSUB Appl_dummy
1302    RETURN 
1304  !
1306  SUBEND
1308  !
1310  ! PAGE -> 
1312  !***********************************************************************
1314 Appl_do_main:SUB Appl_do_main(Restart,Stopped,Disp_modified,Leave_me,Data_valid,Axes_not_done)
1316    !
1318    !  This routine is called when one of the main softkeys is pressed.
1320    !
1322    COM /Appl_data/ Data_buffer(*),Data_header(*)
1324    Key_num=FNUser_get_key
1326    !
1328    Change_in_hw=0
1330    !
1332    SELECT Key_num
1334    CASE 1
1336      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key1isr
1338      CALL Inpt_spread(Change_in_hw)
1340      Disp_modified=1
1342      OFF KEY Key_num
1344    CASE 2
1346      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key2isr
1348      CALL Srce_spread(Change_in_hw)
1350      Disp_modified=1
1352      OFF KEY Key_num
1354    CASE 3
1356      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key3isr
1358      CALL Disp_spread(Disp_modified)
1360      Disp_modified=1
1362      OFF KEY Key_num
1364    CASE 4
1366      ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key4isr
1368      CALL Meas_spread(Meas_modified)
1370      Disp_modified=1
1372      OFF KEY Key_num
1374    CASE 5
1376      Appl_help
1378      Disp_modified=1
1380    CASE 6
1382      IF Data_valid THEN        !there is valid data to mark
1384        ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key6isr
1386        IF Axes_not_done OR Disp_modified THEN 
1388          Disp_plot_axis
1390          Axes_not_done=FNUser_key_press
1392          Disp_modified=Axes_not_done
1394        END IF
1396        CALL Disp_do_mkr(Data_buffer(*),Data_header(*),0)
1398        OFF KEY Key_num
1400      ELSE
1402        Disp_modified=1
1404        User_error("*** There is no valid data for marker now ***")
1406      END IF
1408    CASE 7
1410      IF Stopped THEN 
1412        Restart=1
1414        Stopped=0
1416      ELSE
1418        Stopped=1
1420      END IF
1422    CASE 8
1424      Leave_me=1
1426    END SELECT
1428      !
1430    IF Meas_modified THEN  !automatically restart
1432      Stopped=0
1434      Data_valid=0
1436      Restart=1
1438    END IF
1440      !
1442    IF Change_in_hw THEN 
1444      Stopped=1
1446      Disp_modified=1
1448      Data_valid=0
1450    END IF
1452      !
1454    IF FNUser_key_press THEN 
1456      IF FNUser_check_key=Key_num THEN Key_num=FNUser_get_key
1458    END IF
1460  SUBEND
1462  !
1464  ! PAGE -> 
1466  !***********************************************************************
1468 Appl_meas_loop:SUB Appl_meas_loop(Stopped,Replot,Data_valid)
1470    !
1472    !  This routine is called when no keys are being pressed.  It
1474    !  should not return until a key has been pressed, or the measurement
1476    !  is done.
1478    !
1480    COM /Appl_data/ Data_buffer(*),Data_header(*)
1482    REPEAT
1484      IF (NOT Stopped) THEN 
1486        Appl_get_data(New_data,Stopped)
1488        Data_valid=New_data OR Data_valid
1490        Replot=Data_valid
1492      END IF
1494      IF Replot AND NOT FNUser_key_press THEN 
1496        Disp_plot_data(Data_buffer(*),Data_header(*))
1498        Replot=0
1500        IF FNUser_key_press AND FNUser_check_key=7 AND Stopped THEN Swallow=FNUser_get_key  !see *** below
1502      END IF
1504    UNTIL FNUser_key_press OR Stopped
1506    SUBEXIT
1508    !***: note that if the Appl_get_data routine stops the measurement
1510    !(by setting the Stopped flag), the START/STOP key function has changed
1512    !before we can update the label.  Thus, the user sees 'STOP' when in
1514    !fact the key is a START key.  'Swallowing' the keypress allows the
1516    !routine to exit in the 'Stopped' state, as the user expects.
1518  SUBEND
1520  !
1522  ! PAGE -> 
1524  !***********************************************************************
1526 Appl_powerup:SUB Appl_powerup
1528   ! The column headings for the Input and Source spreadsheets are defined
1530   ! here, as well as system correction constants, such as digital filter
1532   ! correction, window factors, etc.
1534    COM /Tms_scale_info/ Half_lsb,Corr_fact,Flat_top_fact,Hann_fact,Range(*)
1536    DISP "Initialize spreadsheet: INPT"
1538    DIM Setup$(1:10)[20]
1540    !
1542    RESTORE Input_cols
1544    GOSUB Fill_setup
1546    Inpt_init(Setup$(*))
1548 Input_cols:!
1550    DATA 7
1552    DATA "INPUT MODE","COUPLING","GROUNDING","RANGE","TRIG MODE"
1554    DATA "TRIG LEVEL","TRIG SLOPE"
1556    !
1558    DISP "Initialize spreadsheet: SRCE"
1560    RESTORE Source_cols
1562    GOSUB Fill_setup
1564    Srce_init(Setup$(*))
1566 Source_cols:!
1568    DATA 8
1570    DATA "MODE","OFFSET","AMPLITUDE","SINE FREQ","SPAN","CENTER FREQ"
1572    DATA "TRIG","BURST %"
1574    !
1576    DISP "Initialize spreadsheet: MEAS"
1578    Meas_init
1580    !
1582    DISP "Initialize system scaling constants"
1584    ! Define system scaling consants to prevent recalculation later
1586    Two_db_over=(10^.1)                      !+2db overange in input module
1588    Dig_filt_corr=(1/.460657543)             !filter correction in inp mod
1590    Twin_sided=2                             !For twin-sided spectrum
1592    Corr_fact=(Dig_filt_corr*Two_db_over*Twin_sided)^2 !total corr fact
1594    Flat_top_fact=4.1762^2                   !flat top window correction
1596    Hann_fact=2^2                            !Hanning Correction
1598    Half_lsb=(.5/65536)^2                    !assign log(0) to this value
1600    DISP ""
1602    !
1604    SUBEXIT
1606 Fill_setup:!
1608    READ Num_cols
1610    REDIM Setup$(1:Num_cols)
1612    FOR I=1 TO Num_cols
1614      READ Setup$(I)
1616    NEXT I
1618    RETURN 
1620  SUBEND
1622  !
1624  ! PAGE -> 
1626  !***********************************************************************
1628 Tms_assy_list:SUB Tms_assy_list
1630    ! An assembly listing of the TMS320 demo program appears here as
1632    ! comments.  Not called by anything, just here for perusal.
1634    !                      1 "TMS320"
1636    !                      3 ***********************************************
1638    !                      4 *  The following program is adapted from the TI
1640    !                      5 *   1983 TMS32010 User's Guide, page 4-4.
1642    !                      6 *  It implements a 17 tap FIR filter, to show
1644    !                      7 *   how to download TMS320 programs.
1646    !                      8 *  The filter input format is N 16-bit real pts
1648    !                      9 *  The Icode call for this program should be
1650    !                     10 *  F_SIG_PROC,addr,0,3,PARAM_ID,INP_ID,OUT_ID
1652    !                     11 *  The parameter block is defined as follows:
1654    !                     12 *       PARAM(0) = Number of real data points
1656    !                     13 **********************************************
1658    !                     14
1660    !                     15 *** Define global labels ***
1662    !                     16
1664    !                     17         GLB      DEMO_START
1666    !                     18         GLB      DEMO_END
1668    !                     19
1670    !                     20 *** Reserve storage for state variables ***
1672    !                     21
1674    !                     22
1676    !           <0000>    23 XR1     EQU    0
1678    !           <0010>    24 XR17    EQU    XR1+16
1680    !                     25
1682    !                     26 *** Now for the impulse responses ***
1684    !                     27
1686    !           <0011>    28 CX1    EQU    XR17+1
1688    !           <0021>    29 CX17   EQU    CX1+16
1690    !                     30
1692    !                     31 ****  Now define pointers etc  ****
1694    !                     32
1696    !           <0022>    33 YR      EQU     CX17+1   ;real output word
1698    !           <0023>    34 MINUS1  EQU     YR+1     ; Holds -1
1700    !           <0024>    35 ZERO    EQU     MINUS1+1 ; Holds  0
1702    !           <0025>    36 ONE     EQU     ZERO+1   ; Holds  1
1704    !           <0026>    37 TWO     EQU     ONE+1    ; Holds  2
1706    !           <0027>    38 TEMP0   EQU     TWO+1
1708    !           <0028>    39 TEMP1   EQU     TEMP0+1
1710    !           <0029>    40 INDEX   EQU     TEMP1+1  ; Loop index
1712    !           <002A>    41 PTR_PARAM EQU   INDEX+1  ; Ptr to param block
1714    !           <002B>    42 PTR_INP EQU   PTR_PARAM+1; Ptr to input buffer
1716    !           <002C>    43 PTR_OUT EQU     PTR_INP+1; Ptr to output buff
1718    !           <002D>    44 NUM_WORDS EQU   PTR_OUT+1;  # words to filter
1720    !                     45
1722    !                     46
1724    !                     47 **** Define Page 1 of cache ****
1726    !                     48
1728    !           <0009>    49 INTS_COPY EQU   9  ;Copy of TMS320 status word
1730    !                     50
1732    !                     51 **** Define I/O ports ****
1734    !                     52
1736    !           <0000>    53 PA_RDAT EQU     PA0    ; I/O, RAM data
1738    !           <0001>    54 PA_RADD EQU     PA1    ; I/O, RAM addr
1740    !           <0002>    55 PA_FFT  EQU     PA2    ; I/O-FFT status/cont
1742    !           <0003>    56 PA_INTS EQU     PA3    ; I/O, TMS320 int/stat
1744    !                     57
1746    !                     58 **** Now begin the program ****
1748    !                     59
1750    !                     60         RORG
1752    !  0000 F9000013      61         B       DEMO_START
1754    !  0002               62 COEF_TBL
1756    !  0002 E287          63         DW     -7545  ;These coefficients
1758    !  0003 13F5          64         DW      5109  ;  are in Q15 format.
1760    !  0004 1C4F          65         DW      7247  ;The 'real' value can
1762    !  0005 0E53          66         DW      3667  ; be found by dividing
1764    !  0006 F19B          67         DW     -3685  ; by 32768.
1766    !  0007 ECFC          68         DW     -4868  ;Note that these coefs
1768    !  0008 1A33          69         DW      6707  ; result in a dc
1770    !  0009 5ED7          70         DW     24279  ; gain of about 3,
1772    !  000A 7FFF          71         DW     32767  ; so they will be re-
1774    !  000B 5ED7          72         DW     24279  ; scaled before use.
1776    !  000C 1A33          73         DW      6707
1778    !  000D ECFC          74         DW     -4868
1780    !  000E F19B          75         DW     -3685
1782    !  000F 0E53          76         DW      3667
1784    !  0010 1C4F          77         DW      7247
1786    !  0011 13F5          78         DW      5109
1788    !  0012 E287          79         DW     -7545
1790    !                     80
1792    !  0013               81 DEMO_START  ;These lines are specific to
1794    !  0013 7F8B          82         SOVM    ;HP3565S
1796    !  0014 7F82          83         EINT
1798    !  0015 6E01          84         LDPK    1
1800    !  0016 7E00          85         LACK    0
1802    !  0017 5009          86         SACL    INTS_COPY  ;Always save a copy
1804    !  0018 4B09          87         OUT     INTS_COPY,PA_INTS
1806    !  0019 F500001B      88         BV      CLROVF
1808    !  001B 6E00          89 CLROVF  LDPK    0
1810    !  001C 5027          90         SACL    TEMP0
1812    !  001D 4A27          91         OUT     TEMP0,PA_FFT
1814    !                     92         ;Above line stopped HW addr chip
1816    !                     93 *** Now begin application ***
1818    !                     94
1820    !  001E 7F89          95         ZAC            ; Define constants
1822    !  001F 5024          96         SACL    ZERO
1824    !  0020 7E01          97         LACK    1
1826    !  0021 5025          98         SACL    ONE
1828    !  0022 7F89          99         ZAC
1830    !  0023 1025         100         SUB     ONE
1832    !  0024 5023         101         SACL    MINUS1
1834    !  0025 2125         102         LAC     ONE,1
1836    !  0026 5026         103         SACL    TWO
1838    !                    104
1840    !                    105 ****  Now read in the coefficients  ****
1842    !                    106
1844    !  0027 6A25         107         LT      ONE
1846    !  0028 8000         108         MPYK    COEF_TBL
1848    !  0029 7F8E         109         PAC
1850    !  002A 7010         110         LARK    AR0,16
1852    !  002B 7111         111         LARK    AR1,CX1
1854    !  002C 6881         112 RCONST  LARP    1
1856    !  002D 67A0         113         TBLR    *+,AR0
1858    !  002E 0025         114         ADD     ONE
1860    !  002F F400002C     115         BANZ    RCONST
1862    !                    116
1864    !                    117 **** Now get ptrs to i/o buffers ****
1866    !                    118
1868    !  0031 4924         119         OUT     ZERO,PA_RADD
1870    !  0032 402A         120         IN      PTR_PARAM,PA_RDAT
1872    !  0033 4925         121         OUT     ONE,PA_RADD
1874    !  0034 402B         122         IN      PTR_INP,PA_RDAT
1876    !  0035 4926         123         OUT     TWO,PA_RADD
1878    !  0036 402C         124         IN      PTR_OUT,PA_RDAT
1880    !                    125
1882    !                    126 **** Now get number of words to filter ****
1884    !                    127
1886    !  0037 492A         128         OUT     PTR_PARAM,PA_RADD
1888    !  0038 402D         129         IN      NUM_WORDS,PA_RDAT
1890    !                    130
1892    !                    131 **** Now initialize loop index to zero ****
1894    !                    132
1896    !  0039 7F89         133         ZAC
1898    !  003A 5029         134         SACL    INDEX
1900    !  003B 6880         135         LARP    0         ;use AR0 first
1902    !                    136
1904    !                    137 **** Now process real points ****
1906    !                    138
1908    !                    139        ;get next point
1910    !  003C 492B         140 NXTRPT  OUT     PTR_INP,PA_RADD
1912    !  003D 4000         141         IN      XR1,PA_RDAT
1914    !                    142
1916    !  003E 7010         143         LARK    AR0,XR17
1918    !  003F 7121         144         LARK    AR1,CX17
1920    !  0040 7F89         145         ZAC
1922    !  0041 6A91         146         LT      *-,AR1
1924    !  0042 6D90         147         MPY     *-,AR0
1926    !  0043 6B81         148 RLOOP   LTD     *,AR1
1928    !  0044 6D90         149         MPY     *-,AR0
1930    !  0045 F4000043     150         BANZ    RLOOP
1932    !  0047 7F8F         151         APAC
1934    !  0048 0E25         152         ADD     ONE,14 ;always round up
1936    !  0049 5922         153         SACH    YR,1
1938    !  004A 492C         154         OUT     PTR_OUT,PA_RADD
1940    !  004B 4822         155         OUT     YR,PA_RDAT   ;save result
1942    !                    156
1944    !  004C 202B         157         LAC     PTR_INP ;increment I/O ptrs
1946    !  004D 0025         158         ADD     ONE
1948    !  004E 502B         159         SACL    PTR_INP
1950    !  004F 202C         160         LAC     PTR_OUT
1952    !  0050 0025         161         ADD     ONE
1954    !  0051 502C         162         SACL    PTR_OUT
1956    !  0052 2029         163         LAC     INDEX
1958    !  0053 0025         164         ADD     ONE  ;incr loop index
1960    !  0054 5029         165         SACL    INDEX
1962    !  0055 102D         166         SUB     NUM_WORDS ; Loop test
1964    !  0056 FA00003C     167         BLZ     NXTRPT ;branch if not done
1966    !                    168
1968    !                    169
1970    !                    170 **** Now signal 68000 that we are done ****
1972    !                    171
1974    !  0058 2225         172         LAC     ONE,2           ;4
1976    !  0059 6E01         173         LDPK    1  ;switch to high cache
1978    !  005A 5009         174         SACL    INTS_COPY  ;keep a copy
1980    !  005B 4B09         175         OUT     INTS_COPY,PA_INTS ;done bit
1982    !  005C 7F80         176         NOP                ;for timing
1984    !  005D F900005D     177 DEMO_END B DEMO_END
1986  SUBEND
1988  !
1990  ! PAGE -> 
1992  !***********************************************************************
1994 Tms_320_prog:SUB Tms_320_prog
1996  ! This routine handles the details of downloading the TMS320 demo
1998  ! program.  Note that the program is stored here in DATA
2000  ! statements.  Also note that the filter coefficients are scaled
2002  ! here for a nominal DC gain of 1.
2004  !
2006    COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
2008    ALLOCATE INTEGER Object_code(0:97)
2010    DIM Dummy$[256]
2012    GOSUB Demo_data   !Fill object code array
2014    !
2016    ! The coefficients in the TI example give a DC gain of 3, so....
2018    ! scale 'em  for  x1 dc gain
2020    FOR I=4 TO 20   !these are the coefficients
2022      Object_code(I)=INT((1.0*Object_code(I))/2.888+.5)
2024    NEXT I
2026    ! Download into a block (MUST be on the 68000 board)
2028    Hw_write_blk(FNIcode_ext_id("SP_PROG",Icode_info$(*)),Object_code(*))
2030    SUBEXIT
2032 !
2034 Demo_data:!
2036!
2038! Subroutine fills the object code array with:
2040! Object code(0)=TMS320 start address (64)
2042! Object_code(1)=TMS320 prog length   (96)
2044! Object_code(2,...,97)=TMS320 object code
2046! See subprogram "TMS_ASSY_LIST" for assembly listing
2048    RESTORE Demo_data
2050    FOR I=0 TO 97
2052      READ Object_code(I)
2054    NEXT I
2056    RETURN 
2058    DATA      64    !start address
2060    DATA      96    !prog length
2062    DATA    -1792,     83,  -7545,  5109   !BEGIN PROGRAM
2064    DATA     7247,   3667,  -3685,  -4868
2066    DATA     6707,  24279,  32767,  24279
2068    DATA     6707,  -4868,  -3685,  3667
2070    DATA     7247,   5109,  -7545,  32651
2072    DATA    32642,  28161,  32256,  20489
2074    DATA    19209,  -2816,     91,  28160
2076    DATA    20519,  18983,  32649,  20516
2078    DATA    32257,  20517,  32649,   4133
2080    DATA    20515,   8485,  20518,  27173
2082    DATA   -32702,  32654,  28688,  28945
2084    DATA    26753,  26528,     37,  -3072
2086    DATA      108,  18724,  16426,  18725
2088    DATA    16427,  18726,  16428,  18730
2090    DATA    16429,  32649,  20521,  26752
2092    DATA    18731,  16384,  28688,  28961
2094    DATA    32649,  27281,  28048,  27521
2096    DATA    28048,  -3072,    131,  32655
2098    DATA     3621,  22818,  18732,  18466
2100    DATA     8235,     37,  20523,   8236
2102    DATA       37,  20524,   8233,     37
2104    DATA    20521,   4141,  -1536,    124
2106    DATA     8741,  28161,  20489,  19209
2108    DATA    32640,  -1792,    157,    255
2110  SUBEND
2112  !
2114  ! PAGE -> 
2116  !***********************************************************************
2118 Tms_fft_coefs:SUB Tms_fft_coefs
2120  !
2122  !--This routine handles the details of downloading the fft coefficients
2124  !
2126    COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
2128    ALLOCATE INTEGER Coef(0:4095)
2130    Lib_fft_coefs(Coef(*))             !generate FFT coefficient table
2132    DISP "Downloading fft coefficients"
2134    Hw_write_blk(FNIcode_ext_id("COEF",Icode_info$(*)),Coef(*))
2136  SUBEND
2138  !
2140  ! PAGE -> 
2142  !***********************************************************************
2144 Appl_help:SUB Appl_help
2146  ! This routine is the 'help' routine:  several screens of information
2148  ! are available.
2150    DIM Line$[256]
2152    User_clr_scr
2154    RESTORE Msg0
2156    GOSUB Show_page
2158    RESTORE Msg1
2160    GOSUB Show_page
2162    RESTORE Msg2
2164    GOSUB Show_page
2166    RESTORE Msg3
2168    GOSUB Show_page
2170    RESTORE Msg4
2172    GOSUB Show_page
2174    SUBEXIT
2176 Show_page:   !
2178    READ Line$
2180    WHILE Line$<>"***END***"
2182      OUTPUT CRT;Line$
2184      READ Line$
2186    END WHILE
2188    OUTPUT KBD USING "#,K";"˙#Y˙<"
2190    INPUT "Type 'Y' to continue, anything else to leave...",A$
2192    IF UPC$(A$[1;1])<>"Y" THEN SUBEXIT
2194    User_clr_scr
2196    RETURN 
2198 Msg0:!
2200    DATA""
2202    DATA"                       TMS320 DEMO PROGRAM"
2204    DATA""
2206    DATA"  This demo describes the steps necessary to download and run a user generated"
2208    DATA"TMS320 program, using as an example a 17-tap FIR filter similar to a program"
2210    DATA"in the 1983 TI TMS320 users guide, page 4-4."
2212    DATA""
2214    DATA"  Although no attempt is made to teach TMS320 assembly language programming,"
2216    DATA"details specific to the HP3565S system will be noted."
2218    DATA""
2220    DATA"  First, the TMS320 source code is generated and assembled on a development"
2222    DATA "system such as the HP64000."
2224    DATA ""
2226    DATA"  Next, some simple header information needs to be added to the"
2228    DATA"beginning of the object code:"
2230    DATA""
2232    DATA"    Word(0) = the start address (decimal) of the TMS320 program, 64 in this case"
2234    DATA"    Word(1) = the length (in words) of the TMS320 program, 96 in this case"
2236    DATA"    Word(2,...,N) = the object code (decimal)"
2238    DATA"***END***"
2240 Msg1:   !
2242    DATA""
2244    DATA"  After assembling the source code and adding header information, the"
2246    DATA"TMS320 program needs to be stored in a file or array for downloading"
2248    DATA"to a data block in Main (not SP) RAM.  For this demo, the TMS320 program"
2250    DATA"is stored in DATA statements in the subroutine 'Tms_320_prog'."
2252    DATA""
2254    DATA"  The TMS320 program can be downloaded using the 'WBLD' HP-IB instruction."
2256    DATA"Once downloaded, the Icode operation 'f_load_prog' moves the program to the"
2258    DATA"TMS320 program space, possibly overwriting any previous program (FFT etc)."
2260    DATA""
2262    DATA"  The TMS320 program is started using the 'f_sig_proc' or 'EXSP' instruction."
2264    DATA""
2266    DATA"  Note that cycling power, pushing the reset button, 'RST','HRST','LSPR 1',"
2268    DATA"and 'f_load_sp_algs,1' all reload the default TMS320 algorithms."
2270    DATA""
2272    DATA"  The subprogram 'Tms_assy_list€' is a (surprise!) listing of the TMS320"
2274    DATA"demo filter program."
2276    DATA "***END***"
2278    !
2280 Msg2:!
2282    DATA"Thus to use your own TMS320 program :"
2284    DATA"1) Assemble the program"
2286    DATA"2) Add the following header to the beginning of the object code"
2288    DATA"           TMS320 start address (64,..,4095)"
2290    DATA"           program length (# of 16-bit words)."
2292    DATA"3) Allocate a data block on the 68000 board (NOT the TMS320 board)"
2294    DATA"4) Download the header/object code to the block."
2296    DATA"5) To load the program, use one of the the following instructions:"
2298    DATA"           'f_load_prog' (Icode)"
2300    DATA"           'WSPM'        (HP-IB)"
2302    DATA"6) To run the program, use one of the following instructions:"
2304    DATA"           'f_sig_proc'  (Icode)"
2306    DATA"           'EXSP'        (HP-IB)"
2308    DATA"7) Be sure to reload the default algorithms before attempting to use them:"
2310    DATA"           'f_load_sp_algs' (Icode)"
2312    DATA"           'LSPR'           (HP-IB)"
2314    DATA"(Default algorithms are automatically loaded at power on, 'HRST' & 'RST'.)"
2316    DATA "***END***"
2318 Msg3: !
2320    DATA" Some details of TMS320 programs specific to HP3565S:"
2322    DATA""
2324    DATA"  *) Interrupts must always be enabled (do not use 'DINT' opcode)"
2326    DATA""
2328    DATA"  *) Page 1 of the TMS320 cache is reserved for system use."
2330    DATA""
2332    DATA"  *) The TMS320 signals 'done' by setting a bit in its status/"
2334    DATA"     interrupt register, PA3  (byte-wide).  A copy of any byte written"
2336    DATA"     to PA3 MUST be kept in page 1 of cache, in location 9.  Failure"
2338    DATA"     to observe this convention will cause inconsistent operation upon"
2340    DATA"     returning from interrupts, generating Error #547."
2342    DATA""
2344    DATA"  *) The hardware address generator MUST be initialized before a TMS320"
2346    DATA"     program uses data ram.  This can be done by writing a zero to PA2."
2348    DATA""
2350    DATA "***END***"
2352 Msg4: !
2354    DATA"  A typical TMS320 program skeleton is as follows:"
2356    DATA""
2358    DATA"BEGIN           EINT             ;must always be enabled"
2360    DATA"                LDPK 0           ;page 1 is reserved"
2362    DATA"                ZAC              ;clear accumulator"
2364    DATA"                SACL TEMP        ;assumes TEMP has been declared"
2366    DATA"                OUT  TEMP,PA2    ;turn off hardware addressing"
2368    DATA"                OUT  TEMP,PA3    ;signal 'not done yet' "
2370    DATA"                ;***do operations here***"
2372    DATA"                LAC  ONE,2       ;assumes ONE contains '1'"
2374    DATA"                LDPK 1           ;to save a copy of the done bit"
2376    DATA"                SACL 9           ;ALWAYS save a copy"
2378    DATA"                OUT  9,PA3       ;output a done bit"
2380    DATA"HERE            B    HERE        ;and do nothing"
2382    DATA""
2384    DATA" Note that the the ICODE instruction 'c_sp_beq' is used to examine"
2386    DATA"a specified bit of PA3, a byte-wide register. The supplied algorithms"
2388    DATA"set bit 2 to indicate 'done'."
2390    DATA "***END***"
2392  SUBEND
2394  !
2396  ! PAGE -> 
2398  !***********************************************************************
2400 Appl_debug:SUB Appl_debug(INTEGER Debug_mode)
2402  ! This routine enbles the user to call the Icode debugger interactively,
2404  !yet keeps an application's COM blocks separate from the debugger.
2406  !The parameter passed in is defined in the Icode documentation, but
2408  !briefly is as follows:
2410  ! 0:  If Icode paused, then debug, else return
2412  ! 1:  Wait for pause, then debug
2414  ! 2:  Debug
2416    COM /Tms_block_info/ Icode_info$(*),Icode_id,Source$(*)
2418    User_clr_scr
2420    CALL Icode_debug(Debug_mode,Icode_info$(*),Source$(*))
2422    User_clr_scr
2424  SUBEND
2426  !
2428  ! PAGE ->
2430  !*************************************************************************
2432 Meas_meas:SUB Meas_meas
2434    ! COMmons are defined here, Meas_powerup is called
2436    COM /Meas_sprd/ Box$(1:2,1:14)[40],Title$(1:2,0:2)[40],Prompt$(1:14)[80]
2438    COM /Meas_sprd_num/ Col_width(1:2),Modify_col,INTEGER Max_row,Max_col
2440    COM /Meas_mod_labels/ Srce_labels$(1:63)[20],Inpt_labels$(1:63)[20]
2442    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
2444    COM /Meas_cmnd/ Cmnd$(2:5)[20],Def_value$(2:5)[20]
2446    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
2448    Meas_powerup
2450  SUBEND
2452 Meas_powerup:SUB Meas_powerup
2454    ! Defines default measurement setup parameters so we can come up
2456    ! running.
2458    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2460    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2462    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
2464    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
2466    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
2468    !
2470    Cmnd_start=2
2472    Cmnd_stop=3
2474    Av_r=6
2476    Numav_r=7
2478    Wind_r=8
2480    !
2482    Max_col=2
2484    Modify_col=2
2486    Max_row=8
2488    REDIM Box$(1:2,1:Max_row)
2490    MAT Box$= ("")
2492    MAT Title$= ("")
2494    !
2496    RESTORE Meas_data
2498    FOR Row=Cmnd_start TO Cmnd_stop
2500      READ Cmnd$(Row),Def_value$(Row),Box$(1,Row),Prompt$(Row)
2502    NEXT Row
2504    FOR Row=Av_r TO Wind_r
2506      READ Box$(2,Row),Box$(1,Row),Prompt$(Row)
2508    NEXT Row
2510    Row=2      !reset cursor to top row
2512    !
2514    Current_inpt=1
2516    Title$(1,0)="Measurement Setup"
2518    Title$(1,1)="Item"
2520    Title$(2,1)="Value"
2522    Col_width(1)=40
2524    Col_width(2)=20
2526    !
2528    !
2530    Box$(1,1)="****** Setups For All Inputs ******"
2532    Box$(1,5)="*** Averaging & Window Selection ***"
2534    SUBEXIT
2536 Meas_data:!
2538    !COMMAND ROWS
2540    DATA "FFT SIZE",          "512",   "Complex FFT Size        ->"
2542    DATA "Enter Complex FFT size  (512, 1024, 2048, or 4096)"
2544    !
2546    DATA "SPAN",             "51200", "Frequency Span          ->"
2548    DATA "Enter Span in Hz (0.195,0.39,...,100,200,...,51200)"
2550    !
2552    ! INFO ROWS  (No Command)
2554    DATA "ON" ,    "Averaging               ->"
2556    DATA "Enter Averaging mode (ON,OFF)"
2558    DATA "25",    "Number of Averages      ->"
2560    DATA "Enter Number of averages (1,...,32767)"
2562    DATA "Hann",   "Window                  ->"
2564    DATA "Enter Window Type (Hann, Flat top, Rectangular)"
2566  SUBEND
2568 Meas_init:SUB Meas_init
2570    ! This routine makes sure the state of the input modules
2572    ! matches the items in the spreadsheet after Meas_powerup
2574    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2576    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2578    COM /Meas_mod_labels/ Srce_labels$(*),Inpt_labels$(*)
2580    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
2582    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
2584    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
2586    !
2588    REDIM Box$(1:2,1:Max_row) !reset dim of BOX$
2590    !
2592    ! Get Input labels
2594    !
2596    Cnfg_labels("ALL INPUT",Inpt_labels$(*),Inpt_count)
2598    IF Inpt_count=0 THEN SUBEXIT
2600    Inpt_count=1 !Only one input for this application
2602    !
2604    ! Setup Inputs, then read back from current input
2606    ! Since block_size=2*fft_size, hoops must be jumped
2608    !  through here.
2610    Inpt_cmd("ALL INPUT","ZOOM","OFF")
2612    FOR Row=Cmnd_start TO Cmnd_stop
2614      IF Cmnd$(Row)="FFT SIZE" THEN 
2616        Tmp$="BLOCK SIZE"
2618        Parm$=VAL$(2*VAL(Def_value$(Row)))
2620        Inpt_cmd("ALL INPUT",Tmp$,Parm$)
2622        Inpt_cmd("ALL INPUT","TRANSFER BLOCK SIZE",Parm$)
2624        Box$(2,Row)=TRIM$(VAL$(1/2*VAL(FNInpt_rsp$(Inpt_labels$(Current_inpt),Tmp$))))
2626      ELSE
2628        Inpt_cmd("ALL INPUT",Cmnd$(Row),Def_value$(Row))
2630        Box$(2,Row)=TRIM$(FNInpt_rsp$(Inpt_labels$(Current_inpt),Cmnd$(Row)))
2632      END IF
2634    NEXT Row
2636    Row=2  !initialize cursor row
2638    !
2640  SUBEND
2642 Meas_spread:SUB Meas_spread(Changed)
2644  ! This is the interactive portion of the measurement spreadsheet.
2646  ! New entries are compared against lists of valid entries,
2648  ! Next/previous keys are handled, etc.
2650  !
2652    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2654    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2656    COM /Meas_mod_labels/ Srce_labels$(*),Inpt_labels$(*)
2658    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
2660    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
2662    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
2664    DIM New_entry$[160]
2666    INTEGER Done,Dummy,I,Found_it
2668    Changed=0
2670    !
2672    ! Define softkeys.  Keys 1 through 4 are 'firmkeys'
2674    !
2676    ON KEY 5 LABEL "" CALL User_key5isr
2678    ON KEY 6 LABEL "" CALL User_key6isr
2680    ON KEY 7 LABEL FNUser_keylabel$("Prev") CALL User_key7isr
2682    ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
2684    !
2686    User_clr_scr
2688    !
2690    ! Now call spreadsheet.
2692    !
2694    Col=2
2696    Start_row=1
2698    Done=0
2700    REPEAT
2702      User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
2704      SELECT FNUser_check_key
2706      CASE 0
2708        GOSUB Meas_new_entry
2710      CASE 5,6
2712        BEEP 
2714        Dummy=FNUser_get_key
2716      CASE 7     ! Prev
2718        Dummy=FNUser_get_key
2720        GOSUB Meas_prev
2722      CASE 8     ! Next
2724        Dummy=FNUser_get_key
2726        GOSUB Meas_next
2728      CASE ELSE  ! A softkey, but not one of mine.
2730        Done=1
2732      END SELECT
2734    UNTIL Done
2736    User_clr_scr
2738    SUBEXIT
2740    !
2742 Meas_new_entry: !
2744    SELECT Row
2746    CASE Cmnd_start TO Cmnd_stop ! It's a global input setup command
2748      Changed=1
2750      IF Row=Cmnd_start THEN ! It's the BLOCK SIZE command
2752        ON ERROR GOTO Meas_bad_bsiz
2754        New_fftsize=VAL(New_entry$)
2756        IF New_fftsize<512 THEN New_fftsize=512
2758        IF New_fftsize>4096 THEN New_fftsize=4096
2760        GOSUB Update_fftsize
2762      ELSE
2764        New_entry$=VAL$(MIN(50000,VAL(New_entry$))) !limit span to 51200
2766        Inpt_cmd("ALL INPUT",Cmnd$(Row),New_entry$)
2768        Box$(2,Row)=TRIM$(FNInpt_rsp$(Inpt_labels$(1),Cmnd$(Row)))
2770 Meas_bad_bsiz: !
2772        OFF ERROR 
2774      END IF
2776    CASE Av_r            ! Set average on or off
2778      Changed=1
2780      IF UPC$(New_entry$[1;2])="ON" THEN 
2782        Box$(2,Row)="ON"
2784        Changed=1
2786      ELSE
2788        IF UPC$(New_entry$[1;2])="OF" THEN 
2790          Box$(2,Row)="OFF"
2792          Changed=1
2794        ELSE
2796          BEEP 
2798        END IF
2800      END IF
2802    CASE Numav_r                 ! Set Number of averages
2804      Changed=1
2806      ON ERROR GOTO Meas_no_number
2808      Temp=VAL(New_entry$)
2810      IF Temp<1 THEN Temp=1
2812      IF Temp>32767 THEN Temp=32767
2814      Box$(2,Row)=VAL$(PROUND(Temp,0))
2816      Changed=1
2818 Meas_no_number:OFF ERROR 
2820    CASE Wind_r             ! Select window type
2822      Changed=1
2824      ON ERROR GOTO Meas_bad_wind
2826      SELECT TRIM$(UPC$(New_entry$[1,1]))
2828      CASE "H"
2830        Box$(2,Row)="Hann"
2832      CASE "F"
2834        Box$(2,Row)="Flat top"
2836      CASE "R"
2838        Box$(2,Row)="Rectangular"
2840      END SELECT
2842      Changed=1
2844 Meas_bad_wind:OFF ERROR 
2846    CASE ELSE
2848      BEEP 
2850    END SELECT
2852    RETURN 
2854    !
2856 Meas_prev: !
2858    Changed=1
2860    SELECT Row
2862    CASE Av_r
2864      GOSUB Meas_toggle        ! Toggle average  or free run
2866    CASE Cmnd_start
2868      SELECT VAL(Box$(2,Row))
2870      CASE 1024,2048,4096
2872        New_fftsize=.5*VAL(Box$(2,Row))
2874      CASE 512
2876        New_fftsize=4096
2878      END SELECT
2880      GOSUB Update_fftsize
2882    CASE Cmnd_start+1          !SPAN ROW
2884      IF VAL(Box$(2,Row))<.2 THEN Box$(2,Row)="100000" !GO TO 51200
2886      Inpt_cmd("ALL INPUT","SPAN",VAL$(.4*VAL(Box$(2,Row))))
2888      Box$(2,Row)=TRIM$(FNInpt_rsp$(Inpt_labels$(1),"SPAN"))
2890    CASE Wind_r
2892      IF UPC$(Box$(2,Row))="HANN" THEN 
2894        Box$(2,Row)="Flat Top"
2896      ELSE
2898        IF UPC$(Box$(2,Row))="FLAT TOP" THEN 
2900          Box$(2,Row)="Rectangular"
2902        ELSE
2904          IF UPC$(Box$(2,Row))="RECTANGULAR" THEN 
2906            Box$(2,Row)="Hann"
2908          END IF
2910        END IF
2912      END IF
2914    END SELECT
2916    RETURN 
2918    !
2920 Meas_next: !
2922    Changed=1
2924    SELECT Row
2926    CASE Av_r
2928      GOSUB Meas_toggle        ! Toggle average or free run
2930    CASE Cmnd_start
2932      SELECT VAL(Box$(2,Row))
2934      CASE 512,1024,2048
2936        New_fftsize=2*VAL(Box$(2,Row))
2938      CASE 4096
2940        New_fftsize=512
2942      END SELECT
2944      GOSUB Update_fftsize
2946    CASE Cmnd_start+1          !SPAN ROW
2948      IF VAL(Box$(2,Row))>100000 THEN Box$(2,Row)="0.1"   !go to .195Hz
2950      Inpt_cmd("ALL INPUT","SPAN",VAL$(1.5*VAL(Box$(2,Row))))
2952      Box$(2,Row)=TRIM$(FNInpt_rsp$(Inpt_labels$(1),"SPAN"))
2954    CASE Wind_r
2956      IF UPC$(Box$(2,Row))="HANN" THEN 
2958        Box$(2,Row)="Rectangular"
2960      ELSE
2962        IF UPC$(Box$(2,Row))="FLAT TOP" THEN 
2964          Box$(2,Row)="Hann"
2966        ELSE
2968          IF UPC$(Box$(2,Row))="RECTANGULAR" THEN 
2970            Box$(2,Row)="Flat Top"
2972          END IF
2974        END IF
2976      END IF
2978    END SELECT
2980    RETURN 
2982    !
2984 Meas_toggle: !
2986    Changed=1
2988    SELECT Row
2990    CASE Av_r                  ! Toggle average mode on or off
2992      IF Box$(2,Row)="ON" THEN 
2994        Box$(2,Row)="OFF"
2996      ELSE
2998        Box$(2,Row)="ON"
3000      END IF
3002      Changed=1
3004    END SELECT
3006    RETURN 
3008 Update_fftsize: !
3010    Size$=VAL$(2*New_fftsize)
3012    Inpt_cmd("ALL INPUT","BLOCK SIZE",Size$)
3014    Inpt_cmd("ALL INPUT","TRANSFER BLOCK SIZE",Size$)
3016    Box$(2,Row)=TRIM$(VAL$(1/2*VAL(FNInpt_rsp$(Inpt_labels$(1),"BLOCK SIZE"))))
3018    RETURN 
3020  SUBEND
3022  !************************************************************************
3024  !
3026  !     Now some routines for the application to use
3028  !
3030  !************************************************************************
3032 Meas_span:DEF FNMeas_span
3034    ! Looks into a box in meas spreadsheet, returns span
3036    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3038    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3040    RETURN VAL(Box$(2,Cmnd_start+1))
3042  FNEND
3044 Meas_fftsize:DEF FNMeas_fftsize
3046    ! Looks into a box in meas spreadsheet, returns fftsize
3048    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3050    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3052    RETURN VAL(Box$(2,Cmnd_start))
3054  FNEND
3056  !
3058 Meas_wind_type:DEF FNMeas_wind_type$
3060    ! Looks into a box in meas spreadsheet, returns window type
3062    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3064    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3066    RETURN Box$(2,Wind_r)
3068  FNEND
3070  !
3072 Meas_num_avg:DEF FNMeas_num_avg
3074    ! Looks into a box in meas spreadsheet, returns #avgs if avg is on
3076    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3078    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3080    IF FNMeas_avg_mode THEN RETURN VAL(Box$(2,Numav_r))
3082    RETURN 1
3084  FNEND
3086  !
3088 Meas_avg_mode:DEF FNMeas_avg_mode
3090    ! Returns 1 if averages are on, 0 if averaging is off
3092    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3094    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3096    IF POS(UPC$(Box$(2,Av_r)),"ON") THEN RETURN 1
3098    RETURN 0
3100  FNEND
3102 !
3104 Meas_save:SUB Meas_save(@File,Ok)
3106  !Called by the FILE module to save the state of the
3108  !measurement spreadsheet into file @File.
3110  !
3112    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3114    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
3116    COM /Meas_mod_labels/ Srce_labels$(*),Inpt_labels$(*)
3118    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
3120    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
3122    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3124    !
3126    !
3128    File_format_rev=2621
3130    OUTPUT @File;File_format_rev
3132    !
3134    CALL File_save_s(@File,Box$(*))
3136    Ok=1
3138    !
3140  SUBEND
3142  !************************************************************************
3144 Meas_load:SUB Meas_load(@File,Ok)
3146  !Called by the FILE module to load the state of the meas spreadsheet
3148  !from file @File.  Meas_init is called to update the modules
3150  !to update other items.
3152  !
3154    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
3156    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
3158    COM /Meas_mod_labels/ Srce_labels$(*),Inpt_labels$(*)
3160    COM /Meas_mod_counts/ Srce_count,Inpt_count,Current_srce,Current_inpt
3162    COM /Meas_cmnd/ Cmnd$(*),Def_value$(*)
3164    COM /Meas_rows/ Cmnd_start,Cmnd_stop,Inpt_r,Srce_r,Av_r,Numav_r,Wind_r,Row
3166    !
3168    !
3170    ENTER @File;File_format_rev
3172    SELECT File_format_rev
3174    CASE 2621
3176    !
3178      CALL File_load_s(@File,Box$(*))
3180    CASE ELSE  !unknown rev
3182      CALL User_error("ERROR Incompatible display file format in Meas_load.")
3184      Ok=0
3186      SUBEXIT
3188    END SELECT
3190    !
3192    CALL Meas_init !Let modules know what was in the boxes
3194    Ok=1
3196    !
3198  SUBEND
3200  ! PAGE -> 
3202  !************************************************************************