1  !   OUTPUT 2 USING "#,K";"<lf>INDENT<cr><lf>RE-STORE ""DS_H""<cr>"
2     !
3     END
4     !
5     ! PAGE -> 
6     !***********************************************************************
7 Appl_appl:SUB Appl_appl
8      !***********************************************************************
9      !* This subroutine is called when the digital scope application is first
10     !* run.  It sets up application specific common variables.
11     !***********************************************************************
12      COM /Appl_buf_info/ Disp_choices$(1:3,1:63)[20],Input_labels$(1:63)[20]
13      COM /Ds_data/ Data_header(1:63,1:10),INTEGER Ovld_buffer(1:63)
14      COM /Ds_data2/ INTEGER Compute_buf(1:63)
15      COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
16      COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$[50]
17      COM /Ds_input_info2/ REAL Ranges(1:63),Trigger_delays(1:63),Input_modes$(1:63)[10]
18      COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
19      COM /Ds_meas_flags/ INTEGER Blk_in_progress
20      COM /Ds_icode_code/ Source$(0:100)[80],INTEGER Object(0:100)
21      COM /Ds_icode_info/ Info$(0:20)[40],INTEGER Assembled
22      COM /Ds_error/ INTEGER Errored,No_inputs
23      COM /Ds_key5/ INTEGER Key5_pressed
24     !
25      Assembled=0
26      SUBEXIT
27     !
28    SUBEND
29 !
30 Appl_common:SUB Appl_common
31     !************************************************************************
32     !* This subroutine provides access to common variables.  To do this,
33     !* type in 'CALL APPL_COMMON' from the keyboard.  When through, press
34     !* continue.  Some local variables are provided for convenience.
35     !* Since this subroutine provides no functionality, it can be deleted
36     !* once program debugging is complete.
37     !************************************************************************
38      COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
39      COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
40      COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
41      COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$[50]
42      COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
43      COM /Ds_input_info2/ REAL Ranges(*),Trigger_delays(*),Input_modes$(*)
44      COM /Ds_icode_code/ Source$(*),INTEGER Object(*)
45      COM /Ds_icode_info/ Info$(*),INTEGER Assembled
46      COM /Ds_error/ INTEGER Errored,No_inputs
47      COM /Ds_key5/ INTEGER Key5_pressed
48      INTEGER I,J,K,L,M,N
49      REAL A,B,C,D,E,F
50      DIM A$[200],B$[200],C$[200]
51     !
52      PAUSE
53      SUBEXIT
54    SUBEND
55 !
56 Appl_init_sprd:SUB Appl_init_sprd
57     !**********************************************************************
58     !* This subroutine set up the input and source spreadsheet selections
59     !* for the digital scope function.
60     !**********************************************************************
61      DIM Setup$(1:7)[20]
62     !
63     !Input spreadsheet setup:
64      REDIM Setup$(1:6)
65      Setup$(1)="INPUT MODE"
66      Setup$(2)="COUPLING"
67      Setup$(3)="GROUNDING"
68      Setup$(4)="RANGE"
69      Setup$(5)="TRIG DELAY"
70      Setup$(6)="INV INPUT"
71      Inpt_init(Setup$(*))
72     !
73     !Source spreadsheet setup:
74      REDIM Setup$(1:7)
75      Setup$(1)="MODE"
76      Setup$(2)="OFFSET"
77      Setup$(3)="AMPLITUDE"
78      Setup$(4)="SPAN"
79      Setup$(5)="CENTER FREQ"
80      Setup$(6)="SINE FREQ"
81      Setup$(7)="BURST %"
82      Srce_init(Setup$(*))
83     !
84      SUBEXIT
85    SUBEND
86 !
87 Appl_init:SUB Appl_init
88     !***********************************************************************
89     !* This routine initializes the system for the digital scope function.
90     !* It should be called when first entering the application, and
91     !* whenever the system configuration has changed (CNFG spreadsheet).
92     !***********************************************************************
93      COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
94      COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
95      COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
96      COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
97      DIM Temp$[255]
98     !
99     !Initialize spread sheets:
100     Appl_init_sprd
101     Meas_init
102    !
103    !Initialize and assemble ICODE program:
104     Ds_init_icode
105    !Initialize input modules:
106     Ds_init_inputs
107    !Get number of input modules and their names:
108     Ds_input_labels
109     Appl_new_labels
110    !
111     SUBEXIT
112   SUBEND
113!
114 Appl_main:SUB Appl_main(Init)
115    !***********************************************************************
116    !* This routine is the entry point for the digital scope function.
117    !* It sequences through the various digital scope functions: setting up
118    !* the hardware, allocating memory, setting up the plots, starting
119    !* measurements, collecting data, doing plots, accessing the various
120    !* spreadsheets, and error handling.
121    !***********************************************************************
122     COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_lab
el$
123     COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
124     COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
125     COM /Ds_error/ INTEGER Errored,No_inputs
126     INTEGER Meas_stopped,Restart_meas,Leave_me,Buf_allocated,Keys_changed
127     INTEGER Display_changed,Replot,Plot_erased,Valid_data
128     INTEGER Errored_key,Main_keys,Axs_interruptus
129     INTEGER K
130    !
131     DISP "Setting up for digital scope . . ."
132     Buf_allocated=0
133    !
134    !Clear the 35651 module and abort any running ICODE:
135     Ds_attention
136    !
137    !Setup up initial softkeys:
138     GOSUB Appl_main_keys
139     Ds_clear_key5
140    !
141    !First init everything:
142     IF Init THEN CALL Appl_init
143    !
144     Restart_meas=1
145     Display_changed=1
146     Meas_stopped=0
147     Leave_me=0
148     Replot=0
149     Valid_data=0
150     Plot_erased=0
151     Errored=No_inputs
152     Errored_key=0
153     Axs_interruptus=0
154    !
155    !Allocate some dummy buffers:
156     ALLOCATE INTEGER Input_buffer(1:1,0:0)
157     ALLOCATE REAL Data_buffer(1:1,0:0)
158     Buf_allocated=1
159    !
160     REPEAT
161       IF Main_keys THEN 
162         ON KEY 7 LABEL "" GOSUB Appl_dummy
163       END IF
164      !
165       Single_mode=FNMeas_single
166       IF Restart_meas AND NOT No_inputs THEN 
167         DISP "Re-starting . . ."
168         Errored=0
169        !Clear the 35651 module and abort any running ICODE:
170         Ds_attention
171        !
172        !Get axis up as soon as possible:
173         Ds_setup_info2
174         Appl_update
175         Disp_plot_axis
176         Axs_interruptus=FNUser_key_press
177         Display_changed=0
178        !
179        !Start the measurement:
180         Appl_start
181         Restart_meas=0
182         Meas_stopped=0
183         Valid_data=0
184         Plot_erased=0
185        !
186         IF NOT Errored THEN 
187          !Allocate enough memory to upload the thruput block from the 35651:
188           DISP "Allocating memory . . ."
189           IF Buf_allocated THEN !Deallocate memory if previously allocated:
190             DEALLOCATE Input_buffer(*)
191             DEALLOCATE Data_buffer(*)
192             Buf_allocated=0
193           END IF
194           ALLOCATE INTEGER Input_buffer(1:Num_inputs,0:MAX(0,Power2_blk_size
-1))
195           ALLOCATE REAL Data_buffer(1:7,0:MAX(0,Power2_blk_size-1))
196           FOR K=1 TO Power2_blk_size-1
197             Data_buffer(7,K)=0
198           NEXT K
199           Buf_allocated=1
200           REDIM Ovld_buffer(1:Num_inputs)
201          !OUTPUT 701;"Available memory = "&VAL$(PROUND((VAL(SYSTEM$("AVAILABLE MEMORY"))/1.E+6),-6))&" megabytes."
202         END IF
203         DISP ""
204       END IF
205      !
206      !Re-plot grids if changed in any of the spreadsheets:
207       IF Display_changed OR Plot_erased OR Axs_interruptus THEN 
208         IF Display_changed THEN CALL Appl_update
209         Disp_plot_axis
210         Axs_interruptus=FNUser_key_press
211         Display_changed=0
212       END IF
213      !
214      !Re-plot old data if returning from a spreadsheet:
215      !(but only if valid data is available):
216       Replot=Plot_erased AND Valid_data
217      !
218       IF Main_keys THEN 
219         IF Errored THEN 
220           ON KEY 7 LABEL FNUser_keylabel$("RE-START") CALL User_key7isr
221           Errored_key=1
222         ELSE
223           Errored_key=0
224           IF Single_mode THEN 
225             IF Meas_stopped THEN 
226               ON KEY 7 LABEL FNUser_keylabel$("START") CALL User_key7isr
227             ELSE
228               ON KEY 7 LABEL FNUser_keylabel$("STOP") CALL User_key7isr
229             END IF
230           ELSE
231             IF Meas_stopped THEN 
232               ON KEY 7 LABEL FNUser_keylabel$("CONTINUE") CALL User_key7isr
233             ELSE
234               ON KEY 7 LABEL FNUser_keylabel$("PAUSE") CALL User_key7isr
235             END IF
236           END IF
237         END IF
238       END IF
239      !
240       Appl_meas_loop(Meas_stopped,Replot,Valid_data,Axs_interruptus,Input_buffer(*),Data_buffer(*))
241      !
242       WHILE FNUser_key_press
243         Ds_log_key5
244         IF Main_keys THEN 
245           Appl_do_main(Restart_meas,Meas_stopped,Display_changed,Keys_changed,Plot_erased,Leave_me,Valid_data,Axs_interruptus,Errored_key,Data_buffer(*))
246         ELSE
247           Appl_do_other(Restart_meas,Meas_stopped,Display_changed,Keys_changed,Plot_erased,Data_buffer(*))
248         END IF
249       END WHILE
250      !
251       IF Keys_changed THEN 
252         IF Main_keys THEN 
253           GOSUB Appl_other_keys
254         ELSE
255           GOSUB Appl_main_keys
256         END IF
257       END IF
258     UNTIL Leave_me
259     SUBEXIT
260    !
261 Appl_dummy:!
262     RETURN 
263    !
264 Appl_main_keys:!
265     Main_keys=1
266     ON KEY 0 LABEL "" GOSUB Appl_dummy
267     ON KEY 1 LABEL FNUser_keylabel$("INPUT SETUP") CALL User_key1isr
268     ON KEY 2 LABEL FNUser_keylabel$("SOURCE SETUP") CALL User_key2isr
269     ON KEY 3 LABEL FNUser_keylabel$("DISPLAY SETUP") CALL User_key3isr
270     ON KEY 4 LABEL FNUser_keylabel$("MEASURE SETUP") CALL User_key4isr
271     ON KEY 5 LABEL FNUser_keylabel$("OTHER") CALL Ds_key5isr
272     ON KEY 6 LABEL FNUser_keylabel$("ADVANCED OSC") CALL User_key6isr
273     ON KEY 7 LABEL "" GOSUB Appl_dummy
274     ON KEY 8 LABEL FNUser_keylabel$("EXIT") CALL User_key8isr
275     ON KEY 9 LABEL "" GOSUB Appl_dummy
276     Keys_changed=0
277     RETURN 
278     !
279 Appl_other_keys: !
280     Main_keys=0
281     ON KEY 0 LABEL "" GOSUB Appl_dummy
282     ON KEY 1 LABEL FNUser_keylabel$("HELP") CALL User_key1isr
283     ON KEY 2 LABEL FNUser_keylabel$("") CALL User_key2isr
284     ON KEY 3 LABEL FNUser_keylabel$("Think Jet") CALL User_key3isr
285     ON KEY 4 LABEL FNUser_keylabel$("Plot") CALL User_key4isr
286     ON KEY 5 LABEL FNUser_keylabel$("MAIN") CALL Ds_key5isr
287     ON KEY 6 LABEL FNUser_keylabel$("DACQ300") CALL User_key6isr
288     ON KEY 7 LABEL FNUser_keylabel$("HARD RESTART") CALL User_key7isr
289     ON KEY 8 LABEL FNUser_keylabel$("") CALL User_key8isr
290     ON KEY 9 LABEL "" GOSUB Appl_dummy
291     Keys_changed=0
292     RETURN 
293     !
294   SUBEND
295!
296 Appl_start:SUB Appl_start
297    !*********************************************************************
298    !* This subroutine starts a digital scope measurement.
299    !* The sequence of events are:
300    !*    1) Initialize and download ICODE blocks
301    !*    2) Set up the input modules
302    !*    3) Start input modules
303    !*    4) Wait for all ready
304    !*    5) Synchronize input modules
305    !*    6) Start ICODE
306    !*    7) Start the ICODE data collection process (by continuing the
307    !*       ICODE program)
308    !*    8) If in a non-triggered mode, force a system trigger
309    !*********************************************************************
310     COM /Ds_meas_flags/ INTEGER Blk_in_progress
311     COM /Ds_error/ INTEGER Errored,No_inputs
312    !
313    !Initialize, download ICODE blocks (finds Max_tdly_label$):
314     Ds_init_blocks
315     IF Errored THEN SUBEXIT
316    !
317    !Setup inputs (needs Max_tdly_label$):
318     Ds_setup_inputs
319    !
320    !Hold off triggers, start and synchronize the inputs:
321     Hw_cmd("TRGA")
322     Inpt_cmd("ALL INPUT","STRT")
323     DISP "Waiting for hardware ready . . ."
324     Hw_wait_gbl_rdy
325     DISP ""
326     Hw_cmd("SYNC")
327    !
328    !Start ICODE:
329     Ds_start_icode
330    !
331    !Collect the first block so it will be ready:
332     Hw_cmd("CONT;TRGU")
333     Blk_in_progress=1
334    !
335    !Did everything start without errors?
336     DISP "Checking for errors . . ."
337     IF BIT(VAL(FNHw_cmd_rsp$("STC?")),9) THEN 
338       IF FNDiag_chk_errors THEN 
339         Errored=1
340         User_error("Error when starting measurement.")
341       END IF
342     END IF
343     DISP ""
344    !
345     SUBEXIT
346   SUBEND
347  !
348 Appl_update:SUB Appl_update
349   !***********************************************************************
350   !* This subroutine initializes the grids for the plot routines.  It is
351   !* called whenever the axis might have changed; for example, a range,
352   !* blocksize, or trigger delay change on one of the input modules.
353   !***********************************************************************
354     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
355     COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
356     COM /Ds_data2/ INTEGER Compute_buf(*)
357     COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
358     COM /Ds_input_info2/ REAL Ranges(*),Trigger_delays(*),Input_modes$(*)
359     COM /Ds_error/ INTEGER Errored,No_inputs
360     REAL Range,Y_min_max,Full_scale,Two_db_over,Dig_filt_corr
361     INTEGER I,Num_plots,Buf_num,Disp_c1,Disp_c2,Disp_c3
362     DIM Scale_sign(1:16)
363    !
364    !Special case if no inputs:
365     IF No_inputs THEN 
366       Ranges(1)=0.
367       Trigger_delays(1)=0.
368       Input_modes$(1)="VOLT"
369     END IF
370    !
371    !Scaling factors:
372     Two_db_over=10.^(-2./20.)       !Two dB overhead in front ends.
373     Dig_filt_corr=15094.3657/32768.   !Digital filter safe-scaling factor.
374     Full_scale=Two_db_over*Dig_filt_corr*32768.
375    !
376     Num_plots=FNDisp_num_plots
377     ALLOCATE Plot_to_buf(1:Num_plots)
378     ALLOCATE X_units$(1:Num_plots)[10],Y_units$(1:Num_plots)[10]
379     ALLOCATE Start_x(1:Num_plots),Per_bin_x(1:Num_plots)
380     ALLOCATE Start_bin(1:Num_plots),Num_bins(1:Num_plots)
381     ALLOCATE Y_def_max(1:Num_plots),Y_def_min(1:Num_plots)
382    !
383     MAT Data_header= (0)
384     MAT Scale_sign= (1)
385     MAT Compute_buf= (0)
386     MAT X_units$= ("SEC")
387     MAT Per_bin_x= (1./(FNMeas_fs))  !Seconds per point = 1/(sample rate).
388     MAT Start_bin= (0.)      !Start plotting at bin 0.
389     MAT Num_bins= (FNMeas_num_samp)
390    !
392     Disp_exp_done
393     Disp_set_auto_c(1)
394     Disp_set_curs(0,0)
396    !
397     FOR I=1 TO Num_plots
398       Disp_c1=FNDisp_choice((I),1)
399       Disp_c2=FNDisp_choice((I),2)
400       Disp_c3=FNDisp_choice((I),3)
401       SELECT Disp_c3
402       CASE 1   ! SINGLE INPUT
403         Plot_to_buf(I)=Disp_c1
404       CASE 2   ! DIFFERENTIAL INPUT
405         Plot_to_buf(I)=Disp_c1+Disp_c2+1
406         IF Disp_c1=Disp_c2 THEN 
407           Plot_to_buf(I)=7
408         END IF
409         IF Disp_c1>Disp_c2 THEN 
410           Scale_sign(I)=-1
411         END IF
412       CASE 3   ! INPUT VERSUS INPUT
413         Plot_to_buf(I)=Disp_c2  ! Allways 'Input 1' in this world
414       CASE 4   ! DOUBLE INPUT
415         Compute_buf(1)=1        ! Make sure 'Input 1' will be computed
416         Plot_to_buf(I)=Disp_c1
417       CASE ELSE
418       END SELECT
419     !
420     !
421       IF Disp_c3>2 THEN   ! We must make 2  Y buffers (This is the VS or the DOUBLE case)
422         Buf_num=Disp_c1
423         IF Disp_c3=4 THEN Buf_num=1   ! CASE 'double input' => 'Input 1' must be computed
424         Compute_buf(Buf_num)=1
425         Range=Ranges(Buf_num)
426         IF Input_modes$(Buf_num)[1;2]="CH" THEN 
427           IF Disp_c3=3 THEN X_units$(I)="C"     ! Only VS case
428           Y_min_max=(10.^(Range/20.))*1.E-12 !Ranges are in dBpC peak.
429           Y_def_min(I)=-1.*Y_min_max
430           Y_def_max(I)=Y_min_max
431         ELSE
432           IF Disp_c3=3 THEN X_units$(I)="V"     ! Only VS case
433           Y_min_max=10.^(Range/20.)          !Ranges are in dBV peak.
434           Y_def_min(I)=-1.*Y_min_max
435           Y_def_max(I)=Y_min_max
436         END IF
437         IF Disp_c3=3 THEN 
438           Start_x(I)=Y_def_min(I)
439           Per_bin_x(I)=2.*Y_min_max/Num_bins(I)
440         END IF
441         Data_header(Buf_num,1)=0         !Data offset.
442         Data_header(Buf_num,2)=Full_scale/Y_min_max !Data scale factor.
443       END IF
444       Buf_num=Plot_to_buf(I)
445       Compute_buf(Buf_num)=1
446       Range=Ranges(Buf_num)
447       IF Input_modes$(Buf_num)[1;2]="CH" THEN 
448         Y_units$(I)="C"
449         Y_min_max=(10.^(Range/20.))*1.E-12   !Ranges are in dBpC peak.
450         Y_def_min(I)=-1.*Y_min_max
451         Y_def_max(I)=Y_min_max
452       ELSE
453         Y_units$(I)="V"
454         Y_min_max=10.^(Range/20.)            !Ranges are in dBV peak.
455         Y_def_min(I)=-1.*Y_min_max
456         Y_def_max(I)=Y_min_max
457       END IF
458       Data_header(Buf_num,1)=0           !Data offset.
459       Data_header(Buf_num,2)=Full_scale/Y_min_max   !Data scale factor.
460      !Starting time for each channel is pre/post trigger delay divided
461      !by the effective sample rate:
462       IF Disp_c3<>3 THEN Start_x(I)=Trigger_delays(Buf_num)/FNMeas_fs
463     NEXT I
464    !
465     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(*))
466    !
467     SUBEXIT
468   SUBEND
469!
470 Appl_do_main:SUB Appl_do_main(INTEGER Restart,Stopped,Disp_modified,Keys_changed,Plot_erased,Leave_me,Valid_data,Axs_interruptus,E_key,REAL Data_buffer(*))
471    !*********************************************************************
472    !* This subroutine handles the main softkeys.
473    !*
474    !* The following variables are inputs to this routine:
475    !*               E_key: true if errored keys active.
476    !*          Valid_data: true if Data_buffer(*) contains valid data.
477    !*      Data_buffer(*): array of data points for marker routine.
478    !*     Axs_interruptus: true if a softkey interrupted axis generation.
479    !*
480    !* The following variables are returned:
481    !*             Restart: true if a spreadsheet change requires a restart.
482    !*             Stopped: true if measurement is to be stopped.
483    !*       Disp_modified: true if a change requires a different display.
484    !*        Keys_changed: true if the alternate softkeys are selected.
485    !*         Plot_erased: true if plots were erased by a spreadsheet or ?.
486    !*            Leave_me: true if exit key pressed.
487    !*          valid_data: false if a spreadsheet change invalidates data.
488    !*     Axs_interruptus: true if a softkey interrupted axis generation.
489    !*********************************************************************
490     COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
491     COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
492     COM /Ds_meas_flags/ INTEGER Blk_in_progress
493     REAL Change_in_hw,Dummy
494     INTEGER Small_change
495    !
496     Key_num=FNUser_get_key
497    !
498     Change_in_hw=0
499     Plot_erased=0
500    !
501     SELECT Key_num
502     CASE 1
503       IF FNDisp_sv_tr_clr THEN 
505         ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key1isr
506         CALL Inpt_spread(Change_in_hw)
507         OFF KEY Key_num
508         Plot_erased=1
509       ELSE
510         Disp_user_mess("Sorry, can't change INPUT SETUP while SAVE TRACE is active.",3)
511         Disp_user_mess("Erase trace first ...",1)
512       END IF
514     CASE 2
515       ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key2isr
516       CALL Srce_spread(Change_in_hw)
517       OFF KEY Key_num
518       Plot_erased=1
519     CASE 3
520       ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key3isr
521       CALL Disp_spread(Dummy)
522       OFF KEY Key_num
523       Disp_modified=Dummy
524       Plot_erased=1
525     CASE 4
526       ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key4isr
527       CALL Meas_spread(Change_in_hw,Dummy)
528       OFF KEY Key_num
529       Small_change=Dummy
530       IF Small_change THEN Valid_data=0
531       Plot_erased=1
532     CASE 5
533       Keys_changed=1
534     CASE 6
535       IF Valid_data THEN 
536         ON KEY Key_num LABEL FNUser_keylabel$("MAIN") CALL User_key6isr
537         IF Axs_interruptus THEN 
538          !Axis not finished; try again:
539           Disp_plot_axis
540           Axs_interruptus=FNUser_key_press
541         END IF
542         IF FNDisp_in_ds_h THEN 
543           CALL Disp_h_mkr(Data_buffer(*),Data_header(*),0)
544         ELSE
545           CALL Disp_do_mkr(Data_buffer(*),Data_header(*),0)
546         END IF
547         OFF KEY Key_num
548         Plot_erased=1  ! Really it's not, but we want a replot.
549       ELSE
550         User_error("There is no valid data for the marker function.")
551       END IF
552     CASE 7
553       IF E_key THEN 
554         Restart=1
555       ELSE
556         IF Stopped THEN 
557           Stopped=0
558        !
559        !If single_mode, then collect another block:
560           IF Single_mode THEN 
561             Hw_wait_gbl_rdy
562             Hw_cmd("CONT;TRGU")
563             Blk_in_progress=1
564           END IF
565         ELSE
566           Stopped=1
567           IF Single_mode AND Blk_in_progress THEN 
568            !User stopped in the middle of the measurement; special case:
569             DISP "Single mode measurement aborted; recovering . . ."
570             Ds_soft_start
571             DISP ""
572           END IF
573         END IF
574       END IF
575     CASE 8
576       Leave_me=1
577     END SELECT
578       !
579     IF Change_in_hw THEN 
580       Restart=1
581       Disp_modified=1
582     END IF
583       !
584     IF FNUser_key_press THEN 
585       IF FNUser_check_key=Key_num THEN Key_num=FNUser_get_key
586     END IF
587     SUBEXIT
588    !
589   SUBEND
590!
591 Appl_do_other:SUB Appl_do_other(INTEGER Restart,Stopped,Disp_modified,Keys_changed,Plot_erased,REAL Buf(*))
592    !*********************************************************************
593    !* This subroutine handles the secondary softkeys.
594    !*
595    !* The following variables are returned:
596    !*             Restart: true if user requested a hard restart.
597    !*             Stopped: true if measurement is to be stopped.
598    !*       Disp_modified: true if a change requires a different display.
599    !*        Keys_changed: true if the alternate softkeys are selected.
600    !*         Plot_erased: true if plots were erased for any reason.
601    !*********************************************************************
602     INTEGER Key_num
603    !
604     Key_num=FNUser_get_key
605     Plot_erased=0
606    !
607     SELECT Key_num
608     CASE 1
609       Ds_help
610       Plot_erased=1
611       Keys_changed=1  ! Return to main keys
612     CASE 2
613  !    Ds_store_tr
614       Keys_changed=1
615     CASE 3
616       Ds_think_jet
617       Keys_changed=1
618     CASE 4
619       Ds_plot(Buf(*))
620       Plot_erased=1
621       Keys_changed=1
622     CASE 5
623       Keys_changed=1
624     CASE 6
625       Ds_dacq300
626     CASE 7
627       Restart=1
628       Keys_changed=1
629     CASE 8
630     END SELECT
631     !
632   SUBEND
633!
634 Appl_meas_loop:SUB Appl_meas_loop(INTEGER Stopped,Replot,Valid_data,Axs_interruptus,INTEGER Input_buffer(*),REAL Data_buffer(*))
635    !**********************************************************************
636    !* This subroutine get new measurement data when it is available and
637    !* plots it.  The subroutine is exited when a key is pressed or when
638    !* one measurement is complete in the single mode.
639    !**********************************************************************
640     COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
641     COM /Ds_data2/ INTEGER Compute_buf(*)
642     COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
643     COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
644     COM /Ds_error/ INTEGER Errored,No_inputs
645     INTEGER New_data
646     REAL Start_time,Display_time
647    !
648     Display_time=2.       !Wait time before displaying status line.
649     Start_time=TIMEDATE
650    !If measurement is not running  put up the old data:
651     REPEAT
652       New_data=0
653       IF NOT Stopped AND NOT Errored THEN 
654         Appl_get_data(New_data,Input_buffer(*))
655         IF Errored THEN 
656           Valid_data=0
657           SUBEXIT
658         END IF
659         IF New_data THEN Valid_data=1
660       END IF
661       IF (New_data OR Replot) AND NOT Axs_interruptus THEN 
662   !     MAT Data_buffer= Input_buffer    , is the 'DS'-way ...
663   !
664   !  And now the 'DS_H'-way :
665   !
666         FOR I=1 TO 3
667           IF Compute_buf(I) THEN 
668             Weight_factor=FNDisp_kn_scaled(I)
669             FOR X=0 TO Power2_blk_size-1
670               Data_buffer(I,X)=Input_buffer(I,X)*Weight_factor
671             NEXT X
672           END IF
673         NEXT I
674         IF Compute_buf(4) THEN 
675           FOR X=0 TO Power2_blk_size-1
676             Data_buffer(4,X)=Input_buffer(2,X)-Input_buffer(1,X)
677           NEXT X
678         END IF
679         IF Compute_buf(5) THEN 
680           FOR X=0 TO Power2_blk_size-1
681             Data_buffer(5,X)=Input_buffer(3,X)-Input_buffer(1,X)
682           NEXT X
683         END IF
684         IF Compute_buf(6) THEN        ! Won't ever occur
685           FOR X=0 TO Power2_blk_size-1
686             Data_buffer(6,X)=Input_buffer(3,X)-Input_buffer(2,X)
687           NEXT X
688         END IF
689         Disp_plot_data(Data_buffer(*),Data_header(*))
690         Replot=0
691       ELSE
692         IF (TIMEDATE-Start_time)>Display_time THEN 
693          !While waiting, give the user some status information:
694           DISP FNDs_meas_state$(Max_tdly_label$,Stopped)
695         END IF
696       END IF
697       Ds_log_key5
698     UNTIL FNUser_key_press OR (Single_mode AND New_data)
699    !
700    !If single mode, stop measurement if new data was acquired:
701     IF Single_mode AND New_data THEN Stopped=1
702    !
703    !Clear status display line on exit:
704     DISP ""
705    !
706     SUBEXIT
707   SUBEND
708!
709 Appl_get_data:SUB Appl_get_data(INTEGER Got_new_data,INTEGER Input_buffer(*))
710    !**********************************************************************
711    !* This subroutine checks to see if a new block of data is available
712    !* from the 35651.  If so, it gets the block and returns it in
713    !* Input_buffer and returns the Got_new_data flag true.
714    !* If block is not available yet, the Got_new_data flag is returned
715    !* false and Input_buffer is unchanged.
716    !* The 35651 signals that data is avaliable by SRQ'ing on ICODE message.
717    !**********************************************************************
718     COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
719     COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
720     COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
721     COM /Ds_meas_flags/ INTEGER Blk_in_progress
722     COM /Ds_error/ INTEGER Errored,No_inputs
723     INTEGER Status,Signal,Dummy
724    !
725     Got_new_data=0
726     IF NOT FNHw_srq THEN SUBEXIT
727    !
728     Signal=VAL(FNHw_cmd_rsp$("SIG?"))
729     Status=VAL(FNHw_cmd_rsp$("STA?"))
730     IF BIT(Status,5) THEN 
731       User_error("35651 error occurred when waiting for ICODE block ready.")
732       Dummy=FNDiag_chk_moderr("HP-IB")
733     END IF
734     IF NOT BIT(Status,7) THEN SUBEXIT     !No ICODE message.
735    !
736    !Clear overload bit in inputs in preparation for next block:
737     Hw_gbl_cmd(109,"STA?")
738    !
739     IF Signal<>2 THEN 
740       IF Signal=3 THEN 
741         User_error("Interrupt occurred when getting block.")
742       ELSE
743         User_error("Problem with ICODE block ready.")
744       END IF
745       Dummy=FNDiag_chk_errors
746       Errored=1
747       SUBEXIT
748     END IF
749    !
750    !A block is available; get it:
751     Hw_read_blk(Input_buffer_id,Input_buffer(*))
752     Got_new_data=1
753     Blk_in_progress=0
754    !
755    !Check for overloads:
756     Ds_do_overload
757    !
758    !If continous mode, then collect another block while plotting:
759     IF NOT Single_mode THEN 
760       Hw_wait_gbl_rdy
761       Hw_cmd("CONT;TRGU")
762       Blk_in_progress=1
763     END IF
764    !
765     SUBEXIT
766   SUBEND
767 !
768 Appl_new_labels:SUB Appl_new_labels
769   !***********************************************************************
770   !* This subroutine gets the trace titles ready for the plot routine.
771   !***********************************************************************
772     COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
773    !
774    !Setup display routines with input labels:
775    !
776     Num_cols=3
777     ALLOCATE Disp_titles$(1:Num_cols,1:2)[20]
778     ALLOCATE Disp_prompt$(1:Num_cols)[80]
779     ALLOCATE Disp_width(1:Num_cols)
780    !
781     MAT Disp_titles$= ("")
782     Disp_titles$(1,1)="Module"
783     Disp_titles$(1,2)="Label"
784     Disp_titles$(2,1)="Reference"
785     Disp_titles$(2,2)="Module"
786     Disp_titles$(3,1)="Display"
787     Disp_titles$(3,2)="Type"
788     Disp_prompt$(1)="Enter module label"
789     Disp_prompt$(2)="Not possible to alter"
790     Disp_prompt$(3)="Enter display type"
791     Disp_width(1)=20
792     Disp_width(2)=20
793     Disp_width(3)=20
794     MAT Disp_choices$= ("")
795    !
796     FOR Module_index=1 TO SIZE(Input_labels$,1)
797       Disp_choices$(1,Module_index)=Input_labels$(Module_index)
798     NEXT Module_index
799     Disp_choices$(2,1)="Ref."&Input_labels$(1)
800     Disp_choices$(3,1)="Single Input"
801     Disp_choices$(3,2)="Differential Input"
802     Disp_choices$(3,3)="Input vs Input"
803     Disp_choices$(3,4)="Double Input"
804    !
805    !
806    !Setup display spreadsheet with titles:
807     Disp_spread_set(Disp_titles$(*),Disp_prompt$(*),Disp_width(*),Disp_choices$(*))
808     !
809     SUBEXIT
810   SUBEND
811 !
812 Ds_setup_inputs:SUB Ds_setup_inputs
813    !**********************************************************************
814    !* This subroutine sets up all the active input modules.  Some setups
815    !* are changed to accomodate the digital scope function.  Other setups
816    !* are left as is; they will be either their default values or whatever
817    !* has been selected in the input spreadsheet.
818    !**********************************************************************
819     COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
820     DIM String$[500],Trg_source_name$[20]
821    !
822    !Input setup string; some explanatory notes:
823    !     RQS 0      Only one input ('slowest') will SRQ to start thruput.
824    !     TSRC SYS   Trigger from system, except for trigger sourcing inputs.
825    !     SP ______  Span determined by 'effective sample rate' selection.
826    !     BSIZ ____  Determined from record size and pretrigger selection.
827    !     TDLY 0     Trigger delay not allowed if non-triggered mode.
828    !     TDLY ____  Trigger delay from spreadsheet in triggered mode.
829     String$="STOP;CLR;RQS 0;TSRC SYS"
830     String$=String$&";SP "&VAL$(FNMeas_span)
831     String$=String$&";BSIZ "&VAL$(Power2_blk_size)
832    !
833    !The input modules are set up slightly differently in the triggered mode.
834     IF NOT FNMeas_trigger_on THEN 
835       String$=String$&";TDLY 0"
836     END IF
837    !
838     Inpt_cmd("ALL INPUT",String$)
839    !
840    !Get all the source modules off the trigger line (Note that this won't
841    !stop their outputs):
842     Srce_cmd("ALL SOURCE","TRIGGER MODE","IGNORE TRIGGER")
843    !Disable sources from interrupting or SRQ'ing:
844     Srce_cmd("ALL SOURCE","INTR 0;RQS 0")
845    !
846    !If this is to be a triggered measurement, set up the triggering module:
847     IF FNMeas_trigger_on THEN 
848       Trg_source_name$=FNMeas_trg_source$
849       IF FNMeas_trig_input THEN 
850         Inpt_cmd(Trg_source_name$,"TRIGGER MODE","SEND TRIGGER")
851       ELSE
852         IF UPC$(FNCnfg_type$(Trg_source_name$))="SOURCE" THEN 
853           Srce_cmd(Trg_source_name$,"TRIGGER MODE","SEND TRIGGER")
854           Srce_cmd(Trg_source_name$,"START")
855          !Allow this source to interrupt on error:
856           Srce_cmd(Trg_source_name$,"INTR 32")
857         END IF
858       END IF
859     ELSE
860      !Not in triggered mode; trigger immediately from one of the inputs:
861       Inpt_cmd(Max_tdly_label$,"TSRC FREE")
862     END IF
863    !
864    !Select input with longest data collection time to generate SRQ on
865    !BAV (block available) to start thruput:
866     Inpt_cmd(Max_tdly_label$,"RQS 2048")
867    !
868    !Send record length to source spreadsheet so it can figure out burst %:
869     Srce_cmd("ALL SOURCE","BLOCK SIZE",VAL$(FNMeas_num_samp))
870    !
871     SUBEXIT
872   SUBEND
873 !
874 Ds_start_icode:SUB Ds_start_icode
875    !**********************************************************************
876    !* This subroutine start the previously downloaded ICODE program in
877    !* the 35651.  The ICODE will signal if it has started properly.  If it
878    !* hasn't, an error condition is flagged.
879    !**********************************************************************
880     COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
881     COM /Ds_error/ INTEGER Errored,No_inputs
882     INTEGER Status,Signal
883    !
884    !Set 35651 to SRQ on ICODE message;Start ICODE:
885     Hw_cmd("RQS 128;PROG "&VAL$(Icode_id))
886    !
887    !Wait for ICODE started:
888     DISP "Waiting for ICODE started."
889     Hw_wait_srq
890     DISP ""
891    !
892     Signal=VAL(FNHw_cmd_rsp$("SIG?"))
893     Status=VAL(FNHw_cmd_rsp$("STA?"))
894     IF BIT(Status,5)<>0 THEN PRINT "35651 error occurred when starting ICODE."
895     IF Signal<>1 THEN 
896       User_error("ICODE not started properly.")
897       Errored=1
898     END IF
899    !
900     SUBEXIT
901   SUBEND
902  !
903 Ds_do_overload:SUB Ds_do_overload
904    !**********************************************************************
905    !* This subroutine checks the currently plotted inputs to see if any
906    !* are overloaded.  If so, set the overload flag in the data header so
907    !* that the plot routine knows to display the OVLD message.
908    !**********************************************************************
909     COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
910     COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
911     INTEGER Plot_num,Num_plots,Buffer_num
912    !
913    !Get overload status block from the 35651:
914     Hw_read_blk(Ovld_buffer_id,Ovld_buffer(*))
915    !
916    !Setup data header with overload information:
917     Num_plots=FNDisp_num_plots
918     FOR Plot_num=1 TO Num_plots
919       Buffer_num=FNDisp_choice((Plot_num),1)
920       Data_header(Buffer_num,3)=BIT(Ovld_buffer(Buffer_num),7)
921     NEXT Plot_num
922    !
923     SUBEXIT
924   SUBEND
925 !
926 Ds_init_icode:SUB Ds_init_icode
927    !**********************************************************************
928    !* This subroutine sets up the ICODE program for the digital scope
929    !* function.  The ICODE is read in from DATA statements, assembled
930    !* and then downloaded to the 35651.
931    !*
932    !*   Signal values:  1   ICODE is started and ready for thruput.
933    !*                   2   A data block is available for uploading.
934    !*                   3   Thruput failed; data unavailable; ICODE aborted.
935    !**********************************************************************
936     COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
937     COM /Ds_icode_code/ Source$(*),INTEGER Object(*)
938     COM /Ds_icode_info/ Info$(*),INTEGER Assembled
939     COM /Ds_error/ INTEGER Errored,No_inputs
940     DIM Listing$(1:1)[1]
941     INTEGER Info_info,Enable_listing
942    !
943    !Don't re-assemble ICODE if commons are intact:
944     IF Assembled THEN SUBEXIT
945    !
946     Info_info=1
947     Enable_listing=0
948    !
949     RESTORE Ds_icode_prog
950     I=0
951     LOOP
952       READ Source$(I)
953     EXIT IF UPC$(Source$(I))="EL_COMPLETO"
954       I=I+1
955     END LOOP
956    !
957     Num_errors=FNIcode_assemble(Source$(*),Object(*),Info_info,Info$(*),(Enable_listing),Listing$(*))
958    !
959     IF Num_errors>0 THEN 
960       User_error("Error in ICODE program assemble.")
961       Errored=1
962     ELSE
963       Assembled=1
964     END IF
965    !
966     SUBEXIT
967    !
968 Ds_icode_prog:   !
969    !Define variables:
970     DATA "VAR VALID_LOOPS 0       !Counts successful thruput loops."
971     DATA "VAR NUM_MODULES 0       !Holds number of modules for thruput."
972     DATA "VAR MODULE_NUM 0        !Index variable for overload read loop."
973     DATA "VAR POINTER 0           !Block addressing pointer."
974     DATA "VAR MODULE_ADR 0        !Holds a module address."
975     DATA "VAR STATUS 0            !Temporary variable."
976    !
977    !Define arrays (blocks):
978     DATA "DEFBLK_EXT  MODULE_LIST      !Contains setup for thruput."
979     DATA "DEFBLK_EXT  INPUT_BUFFER     !Time data from 35652s goes here."
980     DATA "DEFBLK_EXT  OVLD_STATUS      !Status data from 35652s goes here."
981    !
982    !Start of executable ICODE.
983    !Setup for thruput to RAM:
984     DATA "      F_READY_RAM 1,INPUT_BUFFER,0,MODULE_LIST,0,VALID_LOOPS"
985     DATA "      F_KEEP_READY_RAM    !Save thruput setup for multiple uses."
986    !
987    !Signal to host computer that ICODE has started:
988     DATA "      F_SIGNAL 1"
989     DATA "      F_PAUSE             !Wait for host computer."
990    !
991    !Wait for SRQ indicating that Input modules have a block available:
992     DATA "AGAIN:          "
993     DATA "      F_WAIT_SRQ"
994     DATA "      F_ASSERT_TRIG       !Hold off further triggering."
995    !
996    !Thruput the time data:
997     DATA "      F_THRUPUT 0,1       !Thruput; no wait-for-SRQ; abort on IRQ."
998    !
999    !Read the module status of the input modules to get overload info:
1000    DATA "      V_GET16_INDEXED MODULE_LIST,2,NUM_MODULES"
1001    DATA "      V_CEQUATE 0,MODULE_NUM"
1002    DATA "O_LOOP:     "
1003    DATA "      V_ADD 3,MODULE_NUM,POINTER"
1004    DATA "      V_GET16_INDEXED MODULE_LIST,POINTER,MODULE_ADR"
1005    DATA "      F_GET_STATUS MODULE_ADR,STATUS"
1006    DATA "      V_PUT16_INDEXED OVLD_STATUS,MODULE_NUM,STATUS"
1007    DATA "      V_ADD 1,MODULE_NUM,MODULE_NUM"
1008    DATA "      C_BLT O_LOOP,MODULE_NUM,NUM_MODULES"
1009   !
1010   !Check for successful thruput:
1011    DATA "      C_BEQ NO_VAL,VALID_LOOPS,0  !If VALID_LOOPS=0 goto NO_VAL."
1012   !Signal block available, pause; do it again when continued.
1013    DATA "      F_SIGNAL 2"
1014    DATA "      F_PAUSE"
1015    DATA "      C_GOTO AGAIN"
1016   !
1017   !Jump here on error:
1018    DATA "NO_VAL:         "
1019    DATA "      F_SIGNAL 3"
1020    DATA "      C_END"
1021   !
1022    DATA "EL_COMPLETO"
1023   !
1024  SUBEND
1025!
1026 Ds_init_blocks:SUB Ds_init_blocks
1027   !**********************************************************************
1028   !* This subroutine initializes the ICODE blocks and downloads the
1029   !* ICODE and module list blocks needed for thruput.  This routine should
1030   !* be called before starting the ICODE program the first time.  It
1031   !* should also be called if the measurement parameters have been
1032   !* changed, as there could be new blocksizes and a different module list.
1033   !**********************************************************************
1034    COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
1035    COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
1036    COM /Ds_icode_code/ Source$(*),INTEGER Object(*)
1037    COM /Ds_icode_info/ Info$(*),INTEGER Assembled
1038    COM /Ds_error/ INTEGER Errored,No_inputs
1039   !
1040    REAL Block_id,Input_buf_size
1041    REAL Required_words,Available_words
1042    INTEGER Module_list(0:99)
1043   !
1044   !Allocate blocks and get some block_id's from the 35651:
1045   !Set up the module list first so that input buffer size is known:
1046    Ds_module_list(Module_list(*))
1047    Input_buf_size=Num_inputs*Power2_blk_size
1048   !
1049   !Allocate blocks and get some block_id's from the 35651:
1050    Module_list_id=FNIcode_def_ext("MODULE_LIST",(1),(SIZE(Module_list,1)),(0),(0),Info$(*))
1051    Ovld_buffer_id=FNIcode_def_ext("OVLD_STATUS",(1),(Num_inputs),(0),(0),Info$(*))
1052   !
1053   !Check that 35651 has enough memory for requested measurement:
1054    Required_words=Input_buf_size+SIZE(Object,1)+2
1055    Available_words=FNHw_mainblk_aval
1056    IF Required_words>Available_words THEN 
1057      User_error("Requested measurement will overflow 35651 RAM space by "&VAL$(DROUND(((100.*(Required_words/Available_words))-100.),3))&"%")
1058      Errored=1
1059      SUBEXIT
1060    END IF
1061   !
1062    Input_buffer_id=FNIcode_def_ext("INPUT_BUFFER",(1),(Input_buf_size),(0),(0),Info$(*))
1063   !
1064   !Download ICODE program to 35651:
1065    Icode_id=FNIcode_dld(Object(*),(1),Info$(*))
1066   !
1067   !Download the module list to the 35651:
1068    Hw_write_blk(Module_list_id,Module_list(*))
1069   !
1070    SUBEXIT
1071  SUBEND
1072!
1073 Ds_module_list:SUB Ds_module_list(INTEGER Module_list(*))
1074   !***********************************************************************
1075   !* This subroutine sets up the thruput module list for thruput to RAM.
1076   !* The 35651 module needs this list to execute the thruput ICODE command.
1077   !* The list includes the thruput block size, the number of thruput loops
1078   !* (the number of times to read data from each of the modules; for the
1079   !* digital scope function, this is always one), the number of input
1080   !* modules to read data from, and the module address for each.  This
1081   !* routine also finds the input module that has the longest data
1082   !* collection time (biggest trigger delay); it will be this module that
1083   !* SRQ's on block available to initiate block transfers.
1084   !***********************************************************************
1085    COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
1086    COM /Ds_block_ids/ REAL Icode_id,Input_buffer_id,Module_list_id,Ovld_buffer_id
1087    COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
1088    INTEGER Input_number
1089    REAL Block_size,Radix2,Max_trig_delay,Min_trig_delay
1090   !
1091    Module_list(1)=1        !Number of thruput loops per thruput command.
1092    Module_list(2)=Num_inputs
1093    Max_trig_delay=-MINREAL
1094    Min_trig_delay=MAXREAL
1095    Max_tdly_label$=Input_labels$(1)
1096    FOR Input_number=1 TO Num_inputs
1097      Module_list(Input_number+2)=FNCnfg_get_modnum(Input_labels$(Input_number))
1098      Trigger_delay=VAL(FNInpt_rsp$(Input_labels$(Input_number),"TRIGGER DELAY"))
1099      Min_trig_delay=MIN(Min_trig_delay,Trigger_delay)
1100      IF Trigger_delay>Max_trig_delay THEN 
1101        Max_trig_delay=Trigger_delay
1102        Max_tdly_label$=Input_labels$(Input_number)
1103      END IF
1104    NEXT Input_number
1105   !
1106    Block_size=FNMeas_num_samp
1107    Radix2=LOG(Block_size)/LOG(2.)
1108    IF FRACT(Radix2)<1.E-5 THEN 
1109      Power2_blk_size=2^(INT(Radix2))   !Block_size is already a power of 2.
1110    ELSE
1111      Power2_blk_size=2^(INT(Radix2)+1)    !Pick next largest power of 2.
1112    END IF
1113   !
1114   !Power2_block_size must be > ABS(Min_trig_delay) if pretriggering:
1115    IF Min_trig_delay<0 THEN 
1116      Radix2=LOG(ABS(Min_trig_delay))/LOG(2.)
1117     !Pick next largest power of 2:
1118      Power2_blk_size=MAX(Power2_blk_size,2^(INT(Radix2)+1))
1119    END IF
1120   !
1121   !Finally, module list can be completed:
1122    Module_list(0)=Power2_blk_size
1123   !
1124    SUBEXIT
1125  SUBEND
1126 !
1127 Ds_meas_state:DEF FNDs_meas_state$(Input_label$,INTEGER Stopped)
1128   !***********************************************************************
1129   !* This function returns the state of the measurement in a format
1130   !* suitable for a display line message.
1131   !***********************************************************************
1132    COM /Ds_meas_info/ INTEGER Triggered_mode,Single_mode
1133    COM /Ds_error/ INTEGER Errored,No_inputs
1134    INTEGER State
1135    DIM State$[80]
1136   !
1137    IF Errored THEN 
1138      IF No_inputs THEN 
1139        State$="No active input modules; EXIT and change configuration."
1140      ELSE
1141        State$="Paused in an error state; change setup or press RESTART."
1142      END IF
1143      RETURN "Digital Scope: "&State$
1144    END IF
1145   !
1146    IF Stopped THEN 
1147      IF Single_mode THEN 
1148        State$="Single mode; press START for another measurement."
1149      ELSE
1150        State$="Paused; press CONTINUE for new data."
1151      END IF
1152      RETURN "Digital Scope: "&State$
1153    ELSE
1154      State=VAL(FNInpt_rsp$(Input_label$,"MS?"))
1155      SELECT State
1156      CASE 0
1157        State$="not started."
1158      CASE 1
1159        State$="initializing hardware."
1160      CASE 2
1161        State$="doing an autozero."
1162      CASE 3
1163        State$="waiting for SYNC."
1164      CASE 4
1165        State$="waiting for filters to settle."
1166      CASE 5
1167        State$="taking pretrigger data."
1168      CASE 6
1169        State$="waiting to be armed."
1170      CASE 7
1171        State$="waiting for system to be armed."
1172      CASE 8
1173        State$="waiting for trigger."
1174      CASE 9
1175        State$="taking data."
1176      CASE 10
1177        State$="doing a single autozero."
1178      CASE 11
1179        State$="doing a single autorange."
1180      CASE ELSE
1181        State$="doing some unknown thing."
1182      END SELECT
1183   !
1184      RETURN "Digital Scope: Input '"&Input_label$&"' is "&State$
1185    END IF
1186   !
1187  FNEND
1188!
1189 Ds_input_labels:SUB Ds_input_labels
1190   !***********************************************************************
1191   !* This subroutine sets up the Input_labels$ array with the names of all
1192   !* the active input channels as set up in the configuration spreadsheet.
1193   !* Num_inputs is set to the number of active inputs.
1194   !***********************************************************************
1195    COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
1196    COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
1197    COM /Ds_error/ INTEGER Errored,No_inputs
1198    INTEGER Dummy
1199   !
1200   !Get number of input modules and their names:
1201    Cnfg_labels("ALL INPUT",Input_labels$(*),Num_inputs)
1202    Dummy=Num_inputs
1203    No_inputs=(Dummy<1)
1204    IF No_inputs THEN 
1205      REDIM Input_labels$(1:1)
1206      Input_labels$(1)="Input 0"
1207    ELSE
1208      REDIM Input_labels$(1:Num_inputs)
1209    END IF
1210   !
1211    SUBEXIT
1212  SUBEND
1213!
1214 Ds_soft_start:SUB Ds_soft_start
1215   !*********************************************************************
1216   !* This subroutine does a 'soft' start on the input modules.  It aborts
1217   !* pending HP-IB activity, stops ICODE, and stops the input modules.
1218   !* It then restarts the input modules and the ICODE program.  This
1219   !* subroutine is called to clear out data in the measurement pipeline
1220   !* when a measurement is aborted.  Note that this subroutine is not
1221   !* suitable for re-starting if the measurement setup has changed.
1222   !*********************************************************************
1223    COM /Ds_meas_flags/ INTEGER Blk_in_progress
1224   !
1225    Hw_dev_clear
1226    Inpt_cmd("ALL INPUT","STOP")
1227   !
1228   !Hold off triggers, start and synchronize the inputs:
1229    Hw_cmd("TRGA")
1230    Inpt_cmd("ALL INPUT","STRT")
1231    Hw_wait_gbl_rdy
1232    Hw_cmd("SYNC")
1233   !
1234   !Start ICODE:
1235    Ds_start_icode
1236   !
1237    Blk_in_progress=0
1238   !
1239    SUBEXIT
1240  SUBEND
1241!
1242 Ds_init_inputs:SUB Ds_init_inputs
1243   !**********************************************************************
1244   !* This subroutine initializes all the active input modules for the
1245   !* digital scope function.  Some setups are changed.  Other
1246   !* setups are left as is; they will be either their default values or
1247   !* whatever they have been set to in the input spreadsheet.  This
1248   !* subroutine should be called on entry to digital scope if the config-
1249   !* uration has changed and the first time digital scope is entered.
1250   !* The inputs setups that are initialized in this subroutine are common
1251   !* to all digital scope measurements and need not be called for a
1252   !* measurement setup change.
1253   !**********************************************************************
1254    DIM String$[500]
1255   !
1256   !Input setup string; some explanatory notes:
1257   !     ZOOM OFF   Digital scope doesn't support complex time records.
1258   !     INTR 32    Any module can interrupt on error (data reg over-read).
1259   !     SYNC ON    Synced so digital filters produce simultaneous samples.
1260   !     TRNM BLK   Block transfers only; continuous records not supported.
1261    String$="ARM AUTO;AZM ZERO;AZSM ON;DSET ON;FINT OFF;FSHT OFF;FSRQ OFF;ICAL OFF;INTR 32;NOVR 0;OVRM NBR;SYNC ON;TRNM BLK;ZOOM OFF"
1262   !
1263   !Send to all active input modules:
1264    Inpt_cmd("ALL INPUT",String$)
1265   !
1266    SUBEXIT
1267  SUBEND
1268!
1269 Ds_setup_info2:SUB Ds_setup_info2
1270   !*********************************************************************
1271   !* This subroutine gets ranges, trigger delays, and input modes for
1272   !* all the active input modules.  It should be called before starting
1273   !* if the measurement setup might have changed.
1274   !*********************************************************************
1275    COM /Appl_buf_info/ Disp_choices$(*),Input_labels$(*)
1276    COM /Ds_input_info/ REAL Num_inputs,INTEGER Power2_blk_size,Max_tdly_label$
1277    COM /Ds_input_info2/ REAL Ranges(*),Trigger_delays(*),Input_modes$(*)
1278    INTEGER Input_num
1279    DIM Input_name$[20]
1280   !
1281   !Get ranges, trigger delays, and input modes for active input modules:
1282    FOR Input_num=1 TO Num_inputs
1283      Input_name$=Input_labels$(Input_num)
1284      Ranges(Input_num)=VAL(FNInpt_rsp$(Input_name$,"RANGE"))
1285      Trigger_delays(Input_num)=VAL(FNInpt_rsp$(Input_name$,"TRIGGER DELAY"))
1286      Input_modes$(Input_num)=FNInpt_rsp$(Input_name$,"INPUT MODE")
1287    NEXT Input_num
1288   !
1289    SUBEXIT
1290  SUBEND
1291!
1292 Ds_attention:SUB Ds_attention
1293   !*********************************************************************
1294   !* This subroutine gets the 35651's undivided attention.  It aborts
1295   !* any pending HP-IB activity, aborts any running ICODE program,
1296   !* clears any errors, and de-allocates any block assignments.
1297   !*********************************************************************
1298   !
1299    Hw_dev_clear
1300   !Abort any running ICODE, clear errors, and clear all block assignments:
1301    Hw_cmd("ABRT;CLR;DISA")
1302   !
1303    SUBEXIT
1304  SUBEND
1305!
1306 Ds_key5isr:SUB Ds_key5isr
1307   !*********************************************************************
1308   !* This subroutine is the interrupt service routine for softkey K5.
1309   !* It is handled differently from the other softkeys.  This key is
1310   !* handled only after plots or axis have finished to avoid partially
1311   !* drawn displays.
1312   !*********************************************************************
1313    COM /Ds_key5/ INTEGER Key5_pressed
1314   !
1315    Key5_pressed=1
1316   !
1317    SUBEXIT
1318  SUBEND
1319!
1320 Ds_log_key5:SUB Ds_log_key5
1321   !*********************************************************************
1322   !* This subroutine logs softkey K5 presses by calling User_key5isr.
1323   !* This provides a means for delaying the effect of K5 presses until
1324   !* they can be handled more easily.
1325   !*********************************************************************
1326    COM /Ds_key5/ INTEGER Key5_pressed
1327   !
1328    IF Key5_pressed THEN 
1329      User_key5isr
1330    END IF
1331    Key5_pressed=0
1332   !
1333    SUBEXIT
1334  SUBEND
1335!
1336 Ds_clear_key5:SUB Ds_clear_key5
1337   !*********************************************************************
1338   !* This subroutine clears any softkey K5 presses.
1339   !*********************************************************************
1340    COM /Ds_key5/ INTEGER Key5_pressed
1341   !
1342    Key5_pressed=0
1343   !
1344    SUBEXIT
1345  SUBEND
1346!
1347 Ds_do_naught:SUB Ds_do_naught
1348   !*********************************************************************
1349   !* This subroutine is self-documenting.
1350   !*********************************************************************
1351    SUBEXIT
1352  SUBEND
1353!
1354 Ds_help:SUB Ds_help
1355   !*********************************************************************
1356   !* This subroutine prints out the 'help' message for Digital Scope.
1357   !*********************************************************************
1358   !
1359    DIM A$[160]
1360    RESTORE Ds_help_page1
1361    GOSUB Ds_show_page
1362    RESTORE Ds_help_page2
1363    GOSUB Ds_show_page
1364    RESTORE Ds_help_page3
1365    GOSUB Ds_show_page
1366    RESTORE Ds_help_page4
1367    GOSUB Ds_show_page
1368    RESTORE Ds_help_page5
1369    GOSUB Ds_show_page
1370    RESTORE Ds_help_page6
1371    GOSUB Ds_show_page
1372    RESTORE Ds_help_page7
1373    GOSUB Ds_show_page
1374    RESTORE Ds_help_page8
1375    GOSUB Ds_show_page
1376    RESTORE Ds_help_page9
1377    GOSUB Ds_show_page
1378    RESTORE Ds_help_page10
1379    GOSUB Ds_show_page
1380    SUBEXIT
1381 Ds_show_page:READ A$
1382    User_clr_scr
1383    WHILE A$<>"***END***"
1384      OUTPUT CRT;A$
1385      READ A$
1386    END WHILE
1387    OUTPUT KBD USING "#,K";"ÿ#Yÿ<"
1388    INPUT "Type 'Y' to continue, anything else to leave...",A$
1389    IF UPC$(A$[1;1])<>"Y" THEN SUBEXIT
1390    RETURN 
1391 Ds_help_page1: !
1392    DATA "            Help for Digital Scope Application"
1393    DATA ""
1394    DATA "The Digital Scope application will display time records from any of"
1395    DATA "the active input modules in a 3565S system.  When first started, the"
1396    DATA "application comes up running in a default setup.  The measurement is"
1397    DATA "tailored to specific needs through the use of spreadsheets that are"
1398    DATA "accessed via softkeys.  From the main, or plot, level of Digital"
1399    DATA "Scope, the following softkeys are accessible:"
1400    DATA ""
1401    DATA "   INPUT SETUP  calls up the spreadheet for the input channels"
1402    DATA "   SOURCE SETUP  calls up the spreadsheet for the sources"
1403    DATA "   DISPLAY SETUP  calls up the spreadsheet to select plots"
1404    DATA "   MEASURE SETUP  calls up the Digital Scope spreadsheet"
1405    DATA "   OTHER  calls up an alternate set of softkey functions"
1406    DATA "   MARKER  enters a mode that allows reading plot data values"
1407    DATA "   PAUSE, CONTINUE, START, or STOP  measurement control keys"
1408    DATA "   EXIT  leaves Digital Scope"
1409    DATA ""
1410    DATA "***END***"
1411 Ds_help_page2: !
1412    DATA "       Help for Digital Scope Application - Page 2"
1413    DATA ""
1414    DATA "INPUT softkey and spreadsheet:"
1415    DATA "   MAIN  returns to plot level of Digital Scope"
1416    DATA "   RESET  sets input setups to their defaults"
1417    DATA "   AUTORANGE  inputs try to pick 'best' range for signals present"
1418    DATA "   PREV, NEXT  can be used instead of keyboard entry"
1419    DATA ""
1420    DATA "The following input setups can be changed on an individual basis:"
1421    DATA "   INPUT MODE  voltage input, charge input, or voltage with ICP current"
1422    DATA "   COUPLING  ac or dc"
1423    DATA "   INPUT GROUNDING grounded or floating to break ground loops"
1424    DATA "   RANGE  sensitivity of input channels"
1425    DATA "   TRIGGER DELAY  in samples; this sets up pre/post triggering"
1426    DATA ""
1427    DATA "Note: Negative trigger delay is pre-triggering.  For example, with a"
1428    DATA "trigger delay of -100 and a block size ('number of samples captured'"
1429    DATA "in MEASURE spreadsheet) of 200, the trigger point will be mid-plot."
1430    DATA "***END***"
1431 Ds_help_page3: !
1432    DATA "       Help for Digital Scope Application - Page 3"
1433    DATA ""
1434    DATA "SOURCE softkey and spreadsheet:"
1435    DATA "   MAIN  returns to plot level of Digital Scope"
1436    DATA "   RESET  sets source setups to their defaults"
1437    DATA "   CLEAR SHUTDOWN  if source's shutdown BNC input is tripped"
1438    DATA "   PREV, NEXT  can be used instead of keyboard entry"
1439    DATA ""
1440    DATA "The following source setups can be changed on an individual basis:"
1441    DATA "   SOURCE MODE  random, sine, burst, etc"
1442    DATA "   DC OFFSET"
1443    DATA "   AMPLITUDE  peak source output amplitude"
1444    DATA "   SPAN, CENTER FREQUENCY  for band-translated noise"
1445    DATA "   SINE FREQUENCY  for the sine and burst sine modes"
1446    DATA "   BURST %  percentage of the time record that a burst is 'on'"
1447    DATA ""
1448    DATA "Note: burst % will be correct only if source span is the same as"
1449    DATA "the measurement spans (about 40% of the effective sample rate)."
1450    DATA "***END***"
1451 Ds_help_page4: !
1452    DATA "       Help for Digital Scope Application - Page 4"
1453    DATA ""
1454    DATA "DISPLAY softkey and spreadsheet:"
1455    DATA "   RESET  sets plot selections and scaling to their defaults"
1456    DATA "   PREV, NEXT  can be used instead of keyboard entry"
1457    DATA ""
1458    DATA "This spreadsheet allows the number of plots and plot scaling"
1459    DATA "to be changed for the Digital Scope time displays."
1460    DATA "   MODULE LABEL  label of input channel data to plot"
1461    DATA "   Y AXIS MIN, MAX  allows changes in Y axis scaling"
1462    DATA "   RECALL TRACE 1,2  recalls stored traces (see MARKER softkey)"
1463    DATA ""
1464    DATA "The input channels are referred to by a label.  To change the"
1465    DATA "default label assigments, press the EXIT softkey and press the"
1466    DATA "CNFG softkey to bring up the configuration spreadsheet."
1467    DATA "***END***"
1468 Ds_help_page5: !
1469    DATA "       Help for Digital Scope Application - Page 5"
1470    DATA ""
1471    DATA "MEASURE SETUP softkey and spreadsheet:"
1472    DATA "   RESET  sets Digital Scope measurement setups to their defaults"
1473    DATA "   PREV, NEXT  can be used instead of keyboard entry"
1474    DATA ""
1475    DATA "   EFFECTIVE SAMPLE RATE  seconds per sample point"
1476    DATA "     <bandwidth>  frequencies above this value will be attenuated"
1477    DATA "   NUMBER OF SAMPLES  in each time record plot"
1478    DATA "     <total time>  total length of captured time record"
1479    DATA "   WAIT FOR TRIGGER  off: capture immediately; on: triggered"
1480    DATA "   CONTINUOUS/SINGLE  continous mode uses pipelined data; there"
1481    DATA "     will be a delay from signal changes to display changes."
1482    DATA "     Single mode collects new data only after the START softkey"
1483    DATA "     is pressed; use single mode to guarantee fresh data."
1484    DATA "   TRIGGER SETUP  see next page"
1485    DATA "***END***"
1486 Ds_help_page6: !
1487    DATA "       Help for Digital Scope Application - Page 6"
1488    DATA ""
1489    DATA "TRIGGER SETUP:"
1490    DATA "When in the 'wait-for-trigger' mode, data is captured relative to a "
1491    DATA "system trigger.  The TRIGGER SOURCE entry area of the MEASURE SETUP"
1492    DATA "spreadsheet specifies the triggering module for the system."
1493    DATA ""
1494    DATA "   Triggering from source modules: select the label of the desired"
1495    DATA "source.  This is useful when triggering relative to a source burst."
1496    DATA""
1497    DATA "   Triggering from input channels: select the label of the input channel"
1498    DATA "desired.  Two types of triggering are supported: level and magnitude."
1499    DATA "Use level to trigger on a signal crossing a level.  Use magnitude to"
1500    DATA "trigger on a signal excursion outside of a bounded region.  All levels are"
1501    DATA "in +-% of full scale; these levels correspond to % of default plot scaling."
1502    DATA""
1503    DATA "Note: use TRIGGER DELAY in INPUT SETUP to position the trigger"
1504    DATA "point in the time record."
1505    DATA "***END***"
1506 Ds_help_page7: !
1507    DATA "       Help for Digital Scope Application - Page 7"
1508    DATA ""
1509    DATA "OTHER softkey:"
1510    DATA "This softkey calls up an alternate set of softkeys.  All these"
1511    DATA "softkeys bump back to the plot level softkeys."
1512    DATA""
1513    DATA "   HELP  that's how you got here!"
1514    DATA "   MAIN  returns to plot level of Digital Scope"
1515    DATA "   HARD RESET  starts a measurement over"
1516    DATA "***END***"
1517 Ds_help_page8: !
1518    DATA "       Help for Digital Scope Application - Page 8"
1519    DATA ""
1520    DATA "MARKER softkey:"
1521    DATA "This softkeys puts a cursor up on the plots allowing the "
1522    DATA "direct readout of plot data values.  It also calls up another"
1523    DATA "set of softkeys:"
1524    DATA ""
1525    DATA "   MARKER TO X  enter the x-axis value of the cursor"
1526    DATA "   MARKER TO MIN  puts the cursor on the smallest Y value"
1527    DATA "   MARKER TO MAX  puts the cursor on the largest Y value"
1528    DATA "   STORE TRACE  stores the trace the cursor is on to a file"
1529    DATA "      (Recall them with the DISPLAY SETUP spreadsheet)"
1530    DATA "   MAIN  returns to plot level of Digital Scope"
1531    DATA "   PREVIOUS, NEXT TRACE  moves cursor to the desired trace"
1532    DATA ""
1533    DATA "Use the arrow keys, knob or mouse to move the cursor around."
1534    DATA "***END***"
1535 Ds_help_page9: !
1536    DATA "       Help for Digital Scope Application - Page 9"
1537    DATA ""
1538    DATA "PAUSE, CONTINUE, START, or STOP softkeys:"
1539    DATA "These softkeys control the measurement.  The PAUSE/CONTINUE"
1540    DATA "softkeys are used in the continuous mode.  Press PAUSE to get"
1541    DATA "a better look at a changing display.  Press CONTINUE to resume"
1542    DATA "the measurement.  Note that the continuous mode uses a data"
1543    DATA "pipeline that is not cleared out when paused; the next data"
1544    DATA "that appears after a CONTINUE will be old data from before the"
1545    DATA "PAUSE."
1546    DATA ""
1547    DATA "The START/STOP softkeys are used in the single mode.  Press "
1548    DATA "START to collect a brand new block of data from all the input"
1549    DATA "channels.  Press STOP to abort a long single-mode measurement."
1550    DATA "***END***"
1551 Ds_help_page10: !
1552    DATA "       Help for Digital Scope Application - Page 10"
1553    DATA ""
1554    DATA "EXIT softkey:"
1555    DATA "Use this softkey to leave the Digital Scope Application before"
1556    DATA "running another application."
1557    DATA ""
1558    DATA "Also, use this softkey to gain access to the CNFG spreadsheet to"
1559    DATA "change the labels associated with any of the hardware modules."
1560    DATA "***END***"
1561  SUBEND
1562!
1563 Meas_meas:SUB Meas_meas
1564   !*********************************************************************
1565   !* This subroutine contains all the common variables used for the
1566   !* measurement spreadsheet for the digital scope function.  It is
1567   !* by the application loader to initialize common assignments.
1568   !*********************************************************************
1569    COM /Meas_row_col/ REAL Row,Col
1570    COM /Meas_sprd/ Box$(1:2,1:15)[40],Title$(1:2,0:2)[60],Prompt$(1:15)[80]
1571    COM /Meas_old_box/ Old_box$(1:2,1:15)[40]
1572    COM /Meas_sprd_num/ Col_width(1:2),Modify_col,INTEGER Max_row,Max_col
1573    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
1574    COM /Meas_trig_info/ Trg_source_name$[20],INTEGER Trig_is_input
1575   !
1576    Meas_defaults
1577    SUBEXIT
1578  SUBEND
1579!
1580 Meas_common:SUB Meas_common
1581   !*********************************************************************
1582   !* This subroutine contains all the common variables used in the
1583   !* measurement spreadsheet for the digital scope function.  It exists
1584   !* to aid in program debugging.  Since it provides no functionality,
1585   !* it can be deleted when program debugging is complete.
1586   !*********************************************************************
1587    COM /Meas_row_col/ REAL Row,Col
1588    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
1589    COM /Meas_old_box/ Old_box$(1:2,1:15)[40]
1590    COM /Meas_sprd_num/ Col_width(1:2),Modify_col,INTEGER Max_row,Max_col
1591    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
1592    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
1593   !
1594    PAUSE
1595    SUBEXIT
1596  SUBEND
1597!
1598 Meas_defaults:SUB Meas_defaults
1599   !*********************************************************************
1600   !* This subroutine sets the measurement spreadsheet boxes to their
1601   !* default values.  It should be called before the measurement spread-
1602   !* sheet is first entered.
1603   !*********************************************************************
1604    COM /Meas_row_col/ REAL Row,Col
1605    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
1606    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
1607    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
1608    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
1609    DIM Label$(1:63)[20]
1610    REAL Num_labels
1611   !
1612    Max_col=2
1613    Max_row=7
1614    Modify_col=2
1615    Row=2
1616    Col=2
1617   !
1618   !Assign spreadsheet rows:
1619    Fs_row=2
1620    Nsc_row=3
1621    Wft_row=6
1622    Cs_row=7
1623    Ts_row=10
1624    Tm_row=11
1625    Tsl_row=99
1626    Tl1_row=99
1627    Tl2_row=99
1628   !
1629    Title$(1,0)="Digital Scope MEASUREMENT SETUP Spreadsheet"
1630    Title$(1,1)="Item"
1631    Title$(1,2)=""
1632    Title$(2,1)="Value"
1633    Title$(2,2)=""
1634    Prompt$(1)=""
1635    Prompt$(2)="Enter New Value"
1636    Col_width(1)=40
1637    Col_width(2)=30
1638   !
1639   !Set up default spreadsheet:
1640    REDIM Box$(1:2,1:Cs_row)
1641    Box$(1,1)="****** Setups For All Inputs ******"
1642    Box$(1,Fs_row)="Effective Sample Rate <bandwidth>"
1643    Box$(1,Nsc_row)="Number of Samples Captured <total time>"
1644    Box$(1,4)=""
1645    Box$(1,5)="******  Measurement Control  ******"
1646    Box$(1,Wft_row)="Wait for Trigger"
1647    Box$(1,Cs_row)="Continuous/Single"
1648   !
1649   !Set up prompts:
1650    Prompt$(1)=""
1651    Prompt$(Fs_row)="Enter Samples per Second"
1652    Prompt$(Nsc_row)="Enter Number of Samples to Capture"
1653    Prompt$(4)=""
1654    Prompt$(5)=""
1655    Prompt$(Wft_row)="Triggered Mode Off or On"
1656    Prompt$(Cs_row)="Continuous or Single Measurement"
1657    Prompt$(8)=""
1658    Prompt$(9)=""
1659    Prompt$(Ts_row)="Select Channel Name to use as Trigger Source"
1660    Prompt$(Tm_row)="Level (level/slope) or Magnitude (bounded) Trigger"
1661   !
1662    Box$(2,1)=""
1663    Box$(2,Fs_row)=FNMeas_find_fs$(262144.,"SAME")
1664    Box$(2,Nsc_row)=FNMeas_find_ns$(256.,262144.,"SAME")
1665    Box$(2,4)=""
1666    Box$(2,5)=""
1667    Box$(2,Wft_row)="Off"
1668    Box$(2,Cs_row)="Continuous"
1669   !
1670    SUBEXIT
1671  SUBEND
1672!
1673 Meas_init:SUB Meas_init
1674   !*********************************************************************
1675   !* This subroutine must be called when starting up an application.
1676   !* The previously set up measurement spreadsheet values will not be
1677   !* changed, assuming common has not been scratched.   Use Meas_defaults
1678   !* to initialize the measurement spreadsheet values to their defaults.
1679   !* The reason that this subroutine must be called on application startup
1680   !* even though common is intact is that on rerun BASIC will REDIM all
1681   !* arrays in common to their maximum sizes.
1682   !* This routine must also be called after a configuration change.  If
1683   !* the current trigger source module is no longer a valid name, a
1684   !* valid trigger source module is assigned.
1685   !*********************************************************************
1686    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
1687    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
1688    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
1689    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
1690    DIM Label$(1:63)[20]
1691    REAL Num_labels
1692   !
1693    REDIM Box$(1:Max_col,1:Max_row)
1694   !
1695    IF FNCnfg_good_label(Trg_source_name$) THEN 
1696      Trig_is_input=(UPC$(FNCnfg_type$(Trg_source_name$))="INPUT")
1697     !Use the same capitals and smalls as the in configuration:
1698      Trg_source_name$=FNCnfg_get_label$(FNCnfg_get_modnum(Trg_source_name$))
1699    ELSE
1700     !Get default for Trg_source_name$:
1701      Cnfg_labels("ALL INPUT",Label$(*),Num_labels)
1702      IF Num_labels>0 THEN 
1703        Trg_source_name$=Label$(1)
1704        Trig_is_input=1
1705      ELSE
1706        User_error("Warning: No active input modules found; Digital Scope needs at least one.")
1707        Trig_is_input=0
1708        Cnfg_labels("ALL",Label$(*),Num_labels)
1709        IF Num_labels>0 THEN 
1710          Trg_source_name$=Label$(1)
1711        ELSE
1712          Trg_source_name$=""
1713        END IF
1714      END IF
1715    END IF
1716   !
1717   !Trigger source module could have changed; re-do spreadsheet:
1718    Meas_respread
1719   !
1720    SUBEXIT
1721  SUBEND
1722!
1723 Meas_spread:SUB Meas_spread(Changed,Small_change)
1724   !*********************************************************************
1725   !* This subroutine is the entry point for the measurment spreadsheet
1726   !* for the digital scope function.  It calls the generic spreadsheet
1727   !* with the measurement spreadsheet boxes and handles measurement setup
1728   !* changes.  It checks that any requested measurment setup change is
1729   !* valid before accepting it.
1730   !*********************************************************************
1731    COM /Meas_row_col/ REAL Row,Col
1732    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
1733    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
1734    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
1735    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
1736    DIM New_entry$[160],Toggle_type$[10],Inp_label$(1:63)[20],Src_label$(1:63)[20],Trigger_choices$(1:63)[20]
1737    INTEGER Done,Dummy,Unknown_entry,Num_labels,Label_num,Found
1738    REAL Fs,Ns,Num_inp_labels,Num_src_labels,Tlv,Tlv_increment
1739    REAL Dummy_found,Dummy_label_num
1740   !
1741    Changed=0
1742    Small_change=0
1743    Tlv_increment=15.
1744   !
1745   ! Define softkeys.  Keys 1 through 4 are 'firmkeys'
1746    ON KEY 5 LABEL FNUser_keylabel$("RESET") CALL User_key5isr
1747    ON KEY 6 LABEL "" CALL User_key6isr
1748    ON KEY 7 LABEL FNUser_keylabel$("Prev") CALL User_key7isr
1749    ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
1750   !
1751    User_clr_scr
1752   !
1753   !Set up table for trigger source selections:
1754    Cnfg_labels("ALL INPUT",Inp_label$(*),Num_inp_labels)
1755    Cnfg_labels("ALL SOURCE",Src_label$(*),Num_src_labels)
1756    Num_labels=Num_inp_labels+Num_src_labels
1757    REDIM Trigger_choices$(1:MAX(1,Num_labels))
1758    Trigger_choices$(1)="None Available"
1759    IF Num_inp_labels>0 THEN 
1760      FOR Label_num=1 TO Num_inp_labels
1761        Trigger_choices$(Label_num)=Inp_label$(Label_num)
1762      NEXT Label_num
1763    END IF
1764    IF Num_src_labels>0 THEN 
1765      FOR Label_num=1 TO Num_src_labels
1766        Trigger_choices$(Num_inp_labels+Label_num)=Src_label$(Label_num)
1767      NEXT Label_num
1768    END IF
1769   !Find out which label number corresponds to current trigger source name:
1770    Lib_match1(Trg_source_name$,Trigger_choices$(*),Dummy_found,Dummy_label_num)
1771    Found=Dummy_found
1772    Label_num=Dummy_label_num
1773    IF Found THEN 
1774      Trg_source_name$=Trigger_choices$(Label_num)
1775      Trig_is_input=(Label_num<=Num_inp_labels)
1776    ELSE
1777      Trg_source_name$=""
1778      Trig_is_input=0
1779    END IF
1780   !
1781   ! Now call spreadsheet.
1782    Start_row=1
1783    Done=0
1784    REPEAT
1785      User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
1786      SELECT FNUser_check_key
1787      CASE 0
1788        GOSUB Meas_new_entry
1789      CASE 5
1790       !Reset spreadsheet to power-on defaults:
1791        Dummy=FNUser_get_key
1792        Meas_defaults
1793        Changed=1
1794        Trg_source_name$=""
1795        User_clr_scr
1796        Meas_init      !Meas_init does a Meas_respread.
1797      CASE 6
1798        Dummy=FNUser_get_key
1799      CASE 7     ! Prev
1800        Dummy=FNUser_get_key
1801        Toggle_type$="PREV"
1802        GOSUB Meas_toggle
1803      CASE 8     ! Next
1804        Dummy=FNUser_get_key
1805        Toggle_type$="NEXT"
1806        GOSUB Meas_toggle
1807      CASE ELSE  ! A softkey, but not one of mine.
1808        Done=1
1809      END SELECT
1810    UNTIL Done
1811    User_clr_scr
1812    SUBEXIT
1813    !
1814 Meas_new_entry:!
1815    New_entry$=UPC$(TRIM$(New_entry$))
1816    IF LEN(New_entry$)<1 THEN RETURN      !No entry; no action.
1817    Unknown_entry=0
1818    SELECT Row
1819    CASE Fs_row       !New sample rate entry.
1820      ON ERROR GOTO Meas_bad_entry
1821      Fs=VAL(New_entry$)
1822      OFF ERROR 
1823      Box$(2,Row)=FNMeas_find_fs$(Fs,"SAME")
1824     !Update total time box, too:
1825      Ns=VAL(Box$(2,Nsc_row))
1826      Fs=VAL(Box$(2,Fs_row))
1827      Box$(2,Nsc_row)=FNMeas_find_ns$(Ns,Fs,"SAME")
1828      Changed=1
1829    CASE Nsc_row    !Find number of samples entry.
1830      ON ERROR GOTO Meas_bad_entry
1831      Ns=VAL(New_entry$)
1832      OFF ERROR 
1833      Fs=VAL(Box$(2,Fs_row))   !Need sample rate to compute time.
1834      Box$(2,Row)=FNMeas_find_ns$(Ns,Fs,"SAME")
1835      Changed=1
1836    CASE Wft_row
1837      New_entry$=New_entry$&"_"    !In case New_entry$ is < 1 char.
1838      IF New_entry$[1;2]="ON" OR New_entry$[1;1]="Y" OR New_entry$[1;1]="1" THEN 
1839        Box$(2,Row)="On"
1840        Changed=1
1841        Meas_respread
1842      ELSE
1843        IF New_entry$[1;2]="OF" OR New_entry$[1;1]="N" OR New_entry$[1;1]="0" THEN 
1844          Box$(2,Row)="Off"
1845          Changed=1
1846          Meas_respread
1847        ELSE
1848          Unknown_entry=1
1849        END IF
1850      END IF
1851    CASE Cs_row
1852      SELECT New_entry$[1;1]
1853      CASE "C","0"
1854        Box$(2,Row)="Continuous"
1855        Changed=1
1856      CASE "S","1"
1857        Box$(2,Row)="Single"
1858        Changed=1
1859      CASE ELSE
1860        Unknown_entry=1
1861      END SELECT
1862    CASE Ts_row
1863      Lib_match1(New_entry$,Trigger_choices$(*),Dummy_found,Dummy_label_num)
1864      Found=Dummy_found
1865      Label_num=Dummy_label_num
1866      IF Found THEN 
1867        Trg_source_name$=Trigger_choices$(Label_num)
1868        Trig_is_input=(Label_num<=Num_inp_labels)
1869        Changed=1
1870        Meas_respread
1871      ELSE
1872        Unknown_entry=1
1873      END IF
1874    CASE Tlv_row,Tl1_row,Tl2_row
1875      ON ERROR GOTO Meas_bad_entry
1876      Tlv=VAL(New_entry$)
1877      OFF ERROR 
1878      IF Tlv>125.83 THEN Tlv=125.83
1879      IF Tlv<-125.86 THEN Tlv=-125.86
1880      SELECT Row
1881      CASE Tlv_row
1882        Inpt_cmd(Trg_source_name$,"TRIG LEVEL",VAL$(Tlv))
1883      CASE Tl1_row
1884        Inpt_cmd(Trg_source_name$,"UPPER LEVEL",VAL$(Tlv))
1885      CASE Tl2_row
1886        Inpt_cmd(Trg_source_name$,"LOWER LEVEL",VAL$(Tlv))
1887      END SELECT
1888      Small_change=1
1889      Meas_respread
1890    CASE Tsl_row
1891      SELECT New_entry$[1;1]
1892      CASE "+","P","R","0"    !Positive, Rising edge.
1893        Inpt_cmd(Trg_source_name$,"TRIGGER SLOPE","+")
1894        Small_change=1
1895        Meas_respread
1896      CASE "-","N","F","1"    !Negative, Falling edge.
1897        Inpt_cmd(Trg_source_name$,"TRIGGER SLOPE","-")
1898        Small_change=1
1899        Meas_respread
1900      CASE ELSE
1901        Unknown_entry=1
1902      END SELECT
1903    CASE Tm_row
1904      SELECT New_entry$[1;1]
1905      CASE "L","S","E","0"    !Level, slope, edge trigger.
1906        Inpt_cmd(Trg_source_name$,"TRIGGER TYPE","LEVEL")
1907        Small_change=1
1908        Meas_respread
1909      CASE "M","B","1"    !Magnitude, bounded trigger.
1910        Inpt_cmd(Trg_source_name$,"TRIGGER TYPE","MAGNITUDE")
1911        Small_change=1
1912        Meas_respread
1913      CASE ELSE
1914        Unknown_entry=1
1915      END SELECT
1916    END SELECT
1917    IF Unknown_entry THEN CALL User_error("Unknown entry")
1918    RETURN 
1919   !
1920 Meas_bad_entry:  !
1921    OFF ERROR 
1922    User_error("Expected a number")
1923    RETURN 
1924    !
1925 Meas_toggle:!
1926    SELECT Row
1927    CASE Fs_row    !Find prev/next sample rate:
1928      Fs=VAL(Box$(2,Row))
1929      Box$(2,Row)=FNMeas_find_fs$(Fs,Toggle_type$)
1930     !Update total time box, too:
1931      Ns=VAL(Box$(2,Nsc_row))
1932      Fs=VAL(Box$(2,Fs_row))
1933      Box$(2,Nsc_row)=FNMeas_find_ns$(Ns,Fs,"SAME")
1934      Changed=1
1935    CASE Wft_row
1936      IF UPC$(Box$(2,Row))="OFF" THEN 
1937        Box$(2,Row)="On"
1938      ELSE
1939        Box$(2,Row)="Off"
1940      END IF
1941      Changed=1
1942      Meas_respread
1943    CASE Ts_row
1944      IF Num_labels>1 THEN 
1945        IF UPC$(Toggle_type$)="PREV" THEN 
1946          Label_num=Label_num-1
1947          IF Label_num<1 THEN Label_num=Num_labels
1948        ELSE
1949          Label_num=Label_num+1
1950          IF Label_num>Num_labels THEN Label_num=1
1951        END IF
1952        Trig_is_input=(Label_num<=Num_inp_labels)
1953        Trg_source_name$=Trigger_choices$(Label_num)
1954        Changed=1
1955        Meas_respread
1956      END IF
1957    CASE Cs_row
1958      IF UPC$(Box$(2,Row))="CONTINUOUS" THEN 
1959        Box$(2,Row)="Single"
1960      ELSE
1961        Box$(2,Row)="Continuous"
1962      END IF
1963      Changed=1
1964    CASE Nsc_row    !Find next/prev number of samples.
1965      Ns=VAL(Box$(2,Row))
1966      Fs=VAL(Box$(2,Fs_row))   !Need sample rate to compute time.
1967      Box$(2,Row)=FNMeas_find_ns$(Ns,Fs,Toggle_type$)
1968      Changed=1
1969    CASE Tlv_row,Tl1_row,Tl2_row
1970      Tlv=VAL(Box$(2,Row))/Tlv_increment
1971      Tlv=PROUND(Tlv,0)*Tlv_increment
1972      IF Toggle_type$="PREV" THEN 
1973        Tlv=Tlv-Tlv_increment
1974      ELSE
1975        Tlv=Tlv+Tlv_increment
1976      END IF
1977      IF Tlv>125.83 THEN Tlv=125.83
1978      IF Tlv<-125.86 THEN Tlv=-125.86
1979      SELECT Row
1980      CASE Tlv_row
1981        Inpt_cmd(Trg_source_name$,"TRIG LEVEL",VAL$(Tlv))
1982      CASE Tl1_row
1983        Inpt_cmd(Trg_source_name$,"UPPER LEVEL",VAL$(Tlv))
1984      CASE Tl2_row
1985        Inpt_cmd(Trg_source_name$,"LOWER LEVEL",VAL$(Tlv))
1986      END SELECT
1987      Small_change=1
1988      Meas_respread
1989    CASE Tm_row
1990      IF UPC$(Box$(2,Row))="LEVEL" THEN 
1991        Inpt_cmd(Trg_source_name$,"TRIGGER TYPE","MAGNITUDE")
1992      ELSE
1993        Inpt_cmd(Trg_source_name$,"TRIGGER TYPE","LEVEL")
1994      END IF
1995      Small_change=1
1996      Meas_respread
1997    CASE Tsl_row
1998      IF Box$(2,Row)="+" THEN 
1999        Inpt_cmd(Trg_source_name$,"TRIGGER SLOPE","-")
2000      ELSE
2001        Inpt_cmd(Trg_source_name$,"TRIGGER SLOPE","+")
2002      END IF
2003      Small_change=1
2004      Meas_respread
2005    END SELECT
2006    RETURN 
2007   !
2008  SUBEND
2009!
2010 Meas_find_fs:DEF FNMeas_find_fs$(REAL Fs,Toggle_type$)
2011  !************************************************************************
2012  !* This subroutine changes a given sample rate into the proper format
2013  !* for the measurement setup spreadsheet.  The sample rate is checked
2014  !* to make sure it is valid.
2015  !*  Inputs: Fs (real)  sample rate
2016  !*          Toggle_type$  (ascii)
2017  !*                       ="NEXT" selects the next valid sample rate
2018  !*                       ="PREV" selects the previous "   "      "
2019  !*                       = else  selects present sample rate
2020  !*  Output: Formatted$  (ascii)  formatted output
2021  !************************************************************************
2022    INTEGER N,Max_n
2023    REAL Max_fs,Min_fs,X,Max_bandwidth,Aa_bandwidth
2024    DIM Formatted$[40]
2025   !
2026    Max_fs=262144.         !Hz; maximum system sample rate.
2027    Max_n=19               !Maximum divide-by-2's on maximum sample rate.
2028    Max_bandwidth=51200.   !Maximum bandwidth associated with sample rate.
2029    Aa_bandwidth=50000.    !Anti-alias filter bandwidth.
2030   !
2031    Min_fs=Max_fs/(2.^Max_n)
2032   !Make sure that Fs is within bounds:
2033    IF Fs>Max_fs THEN Fs=Max_fs
2034    IF Fs<Min_fs THEN Fs=Min_fs
2035   !
2036   !Round to the nearest valid sample rate:
2037    N=LOG(Max_fs/Fs)/LOG(2.)
2038   !
2039   !Find the desired Fs:
2040    SELECT UPC$(Toggle_type$)
2041    CASE "PREV"
2042      N=N+1
2043      IF N>Max_n THEN N=0
2044    CASE "NEXT"
2045      N=N-1
2046      IF N<0 THEN N=Max_n
2047    END SELECT
2048    Fs=Max_fs/(2.^N)
2049   !
2050   !Find the associated bandwidth:
2051    IF N=0 OR N=1 THEN 
2052      Bandwidth=DROUND(Aa_bandwidth,3)
2053    ELSE
2054      Bandwidth=DROUND((Max_bandwidth/(2^(N-1))),3)
2055    END IF
2056   !
2057   !Format the output string:
2058    SELECT Bandwidth
2059    CASE >=1000.
2060      Formatted$=VAL$(Bandwidth/1000.)&" KHz"
2061    CASE ELSE
2062      Formatted$=VAL$(Bandwidth)&" Hz"
2063    END SELECT
2064    Formatted$=VAL$(Fs)&" Hz  <"&Formatted$&">"
2065   !
2066    RETURN Formatted$
2067  FNEND
2068!
2069 Meas_find_ns:DEF FNMeas_find_ns$(REAL Ns,Fs,Toggle_type$)
2070  !************************************************************************
2071  !* This subroutine changes a given number of samples into the proper
2072  !* format for the measurement setup spreadsheet.  The number of samples
2073  !* is checked to make sure it is valid.
2074  !*  Inputs: Ns (real)  number of samples
2075  !*          Fs (real)  sample rate
2076  !*          Toggle_type$  (ascii)
2077  !*                       ="NEXT" selects the next ^2 number of samples
2078  !*                       ="PREV" selects the previous " "   "     "
2079  !*                       = else  selects present sample rate
2080  !*  Output: Formatted$  (ascii)  formatted output
2081  !************************************************************************
2082    INTEGER Min_ns,Max_ns,Num_samples,N
2083    REAL Total_time
2084    DIM Formatted$[40]
2085   !
2086    Min_ns=16              !Mininum of 16 samples (esthetics limit).
2087    Max_ns=8192            !Maximum of 8192 samples (35652 limit).
2088   !
2089   !Make sure that Number of samples is within bounds:
2090    SELECT Ns
2091    CASE <Min_ns
2092      Num_samples=Min_ns
2093    CASE >Max_ns
2094      Num_samples=Max_ns
2095    CASE ELSE
2096      Num_samples=Ns         !Round to an integer.
2097    END SELECT
2098   !
2099   !Find the nearest power of two number of samples:
2100    N=LOG(Num_samples)/LOG(2.)
2101   !
2102   !Find the desired record size:
2103    SELECT UPC$(Toggle_type$)
2104    CASE "PREV"
2105      Num_samples=2.^(N-1)
2106      IF Num_samples<Min_ns THEN Num_samples=Max_ns
2107    CASE "NEXT"
2108      Num_samples=2.^(N+1)
2109      IF Num_samples>Max_ns THEN Num_samples=Min_ns
2110    END SELECT
2111   !
2112   !Find the associated total time:
2113    Total_time=DROUND(Num_samples/Fs,3)
2114   !
2115   !Format the output string:
2116    SELECT Total_time
2117    CASE 1.E+6 TO 1.E+9
2118      Formatted$=VAL$(Total_time*1.E-6)&" MSEC"
2119    CASE 1.E+3 TO 1.E+6
2120      Formatted$=VAL$(Total_time*1.E-3)&" KSEC"
2121    CASE 1. TO 1.E+3
2122      Formatted$=VAL$(Total_time)&" SEC"
2123    CASE 1.E-3 TO 1.
2124      Formatted$=VAL$(Total_time*1.E+3)&" mSEC"
2125    CASE 1.E-6 TO 1.E-3
2126      Formatted$=VAL$(Total_time*1.E+6)&" uSEC"
2127    CASE ELSE
2128      Formatted$=VAL$(Total_time)&" SEC"
2129    END SELECT
2130    Formatted$=VAL$(Num_samples)&" Samples  <"&Formatted$&">"
2131   !
2132    RETURN Formatted$
2133  FNEND
2134!
2135 Meas_lvl_spread:SUB Meas_lvl_spread
2136   !*********************************************************************
2137   !* This subroutine sets up a spreadsheet for level triggering from a
2138   !* 35652 input module.
2139   !*********************************************************************
2140    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2141    COM /Meas_old_box/ Old_box$(*)
2142    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2143    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2144    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2145    INTEGER Row
2146   !
2147   !Assign spreadsheet rows:
2148    Ts_row=10
2149    Tm_row=11
2150    Tlv_row=12
2151    Tsl_row=13
2152    Tl1_row=99
2153    Tl2_row=99
2154   !
2155   !Save old values before changing spreadsheet:
2156    REDIM Old_box$(1:2,1:SIZE(Box$,2))
2157    MAT Old_box$= Box$
2158    REDIM Box$(1:2,1:Tsl_row)
2159    Max_row=Tsl_row
2160   !
2161   !Setup new rows:
2162    Box$(1,Ts_row-2)=""
2163    Box$(1,Ts_row-1)="******     Trigger Setup     ******"
2164    Box$(1,Ts_row)="Trigger Source"
2165    Box$(1,Tm_row)="Trigger Mode"
2166    Box$(1,Tlv_row)="Trigger Level"
2167    Box$(1,Tsl_row)="Trigger Slope"
2168   !
2169   !Set up prompts:
2170    Prompt$(Tlv_row)="Trigger Level in % of full scale"
2171    Prompt$(Tsl_row)="Trigger Slope (+ or -)"
2172   !
2173   !Set up entry boxes:
2174    Box$(2,Ts_row-2)=""
2175    Box$(2,Ts_row-1)=""
2176    Box$(2,Ts_row)=Trg_source_name$&" (an Input)"
2177    Box$(2,Tm_row)="Level"
2178    Box$(2,Tlv_row)=FNInpt_rsp$(Trg_source_name$,"TRIG LEVEL")&" %"
2179    Box$(2,Tsl_row)=FNInpt_rsp$(Trg_source_name$,"TRIG SLOPE")
2180   !
2181   !Restore box values:
2182    FOR Row=1 TO Cs_row
2183      Box$(1,Row)=Old_box$(1,Row)
2184      Box$(2,Row)=Old_box$(2,Row)
2185    NEXT Row
2186   !
2187    SUBEXIT
2188  SUBEND
2189!
2190 Meas_respread:SUB Meas_respread
2191   !************************************************************************
2192   !* This subroutine figures out which spreadsheet to setup.  It should be
2193   !* called whenever a measurement setup change might require a new
2194   !* spreadsheet format.
2195   !************************************************************************
2196    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2197    COM /Meas_old_box/ Old_box$(*)
2198    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2199    INTEGER Line_number
2200   !
2201    IF FNMeas_trigger_on THEN 
2202      IF Trig_is_input THEN 
2203        IF FNInpt_rsp$(Trg_source_name$,"TRIG TYPE")="MAG" THEN 
2204          Meas_mag_spread
2205        ELSE
2206          Meas_lvl_spread
2207        END IF
2208      ELSE
2209        Meas_oth_spread
2210      END IF
2211    ELSE
2212      Meas_non_spread
2213    END IF
2214   !
2215   !Clear spreadsheet lines if spreadsheet has shrunk:
2216    IF SIZE(Box$,2)<SIZE(Old_box$,2) THEN 
2217      FOR Line_number=(SIZE(Old_box$,2)+1) TO (SIZE(Box$,2)+2) STEP -1
2218        PRINT TABXY(1,Line_number+2),RPT$(" ",80)
2219      NEXT Line_number
2220    END IF
2221   !
2222    SUBEXIT
2223  SUBEND
2224 Meas_non_spread:SUB Meas_non_spread
2225   !*********************************************************************
2226   !* This subroutine sets up a spreadsheet for the untriggerred mode.
2227   !*********************************************************************
2228    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2229    COM /Meas_old_box/ Old_box$(*)
2230    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2231    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2232    INTEGER Row
2233   !
2234   !Assign spreadsheet rows:
2235    Ts_row=99
2236    Tm_row=99
2237    Tlv_row=99
2238    Tsl_row=99
2239    Tl1_row=99
2240    Tl2_row=99
2241   !
2242   !Save old values before changing spreadsheet:
2243    REDIM Old_box$(1:2,1:SIZE(Box$,2))
2244    MAT Old_box$= Box$
2245    REDIM Box$(1:2,1:Cs_row)
2246    Max_row=Cs_row
2247   !
2248   !Restore box values:
2249    FOR Row=1 TO Cs_row
2250      Box$(1,Row)=Old_box$(1,Row)
2251      Box$(2,Row)=Old_box$(2,Row)
2252    NEXT Row
2253   !
2254    SUBEXIT
2255  SUBEND
2256!
2257 Meas_mag_spread:SUB Meas_mag_spread
2258   !*********************************************************************
2259   !* This subroutine sets up a spreadsheet for magnitude triggerring
2260   !* from a 35652 input module.
2261   !*********************************************************************
2262    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2263    COM /Meas_old_box/ Old_box$(*)
2264    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2265    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2266    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2267    INTEGER Row
2268   !
2269   !Assign spreadsheet rows:
2270    Ts_row=10
2271    Tm_row=11
2272    Tlv_row=99
2273    Tsl_row=99
2274    Tl1_row=12
2275    Tl2_row=13
2276   !
2277   !Save old values before changing spreadsheet:
2278    REDIM Old_box$(1:2,1:SIZE(Box$,2))
2279    MAT Old_box$= Box$
2280    REDIM Box$(1:2,1:Tl2_row)
2281    Max_row=Tl2_row
2282   !
2283   !Setup new rows:
2284    Box$(1,Ts_row-2)=""
2285    Box$(1,Ts_row-1)="******     Trigger Setup     ******"
2286    Box$(1,Ts_row)="Trigger Source"
2287    Box$(1,Tm_row)="Trigger Mode"
2288    Box$(1,Tl1_row)="Trigger Bound 1"
2289    Box$(1,Tl2_row)="Trigger Bound 2"
2290   !
2291   !Set up prompts:
2292    Prompt$(Tl1_row)="Trigger Bound 1 in % of full scale"
2293    Prompt$(Tl2_row)="Trigger Bound 2 in % of full scale"
2294   !
2295   !Set up entry boxes:
2296    Box$(2,Ts_row-2)=""
2297    Box$(2,Ts_row-1)=""
2298    Box$(2,Ts_row)=Trg_source_name$&" (an Input)"
2299    Box$(2,Tm_row)="Magnitude"
2300    Box$(2,Tl1_row)=FNInpt_rsp$(Trg_source_name$,"UPPER LEVEL")&" %"
2301    Box$(2,Tl2_row)=FNInpt_rsp$(Trg_source_name$,"LOWER LEVEL")&" %"
2302   !
2303   !Restore box values:
2304    FOR Row=1 TO Cs_row
2305      Box$(1,Row)=Old_box$(1,Row)
2306      Box$(2,Row)=Old_box$(2,Row)
2307    NEXT Row
2308   !
2309    SUBEXIT
2310  SUBEND
2311 Meas_oth_spread:SUB Meas_oth_spread
2312   !*********************************************************************
2313   !* This subroutine sets up a spreadsheet for triggerring from
2314   !* something other than a 35652 input module.
2315   !*********************************************************************
2316    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2317    COM /Meas_old_box/ Old_box$(*)
2318    COM /Meas_sprd_num/ Col_width(*),Modify_col,INTEGER Max_row,Max_col
2319    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2320    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2321    INTEGER Row
2322   !
2323   !Assign spreadsheet rows:
2324    Ts_row=10
2325    Tm_row=99
2326    Tlv_row=99
2327    Tsl_row=99
2328    Tl1_row=99
2329    Tl2_row=99
2330   !
2331   !Save old values before changing spreadsheet:
2332    REDIM Old_box$(1:2,1:SIZE(Box$,2))
2333    MAT Old_box$= Box$
2334    REDIM Box$(1:2,1:Ts_row)
2335    Max_row=Ts_row
2336   !
2337   !Setup new rows:
2338    Box$(1,Ts_row-2)=""
2339    Box$(1,Ts_row-1)="******     Trigger Setup     ******"
2340    Box$(1,Ts_row)="Trigger Source"
2341   !
2342   !Set up entry boxes:
2343    Box$(2,Ts_row-2)=""
2344    Box$(2,Ts_row-1)=""
2345    Box$(2,Ts_row)=Trg_source_name$
2346    IF FNCnfg_good_label(Trg_source_name$) THEN 
2347      IF (UPC$(FNCnfg_type$((Trg_source_name$)))="SOURCE") THEN Box$(2,Ts_row)=Box$(2,Ts_row)&" (a Source)"
2348    END IF
2349   !
2350   !Restore box values:
2351    FOR Row=1 TO Cs_row
2352      Box$(1,Row)=Old_box$(1,Row)
2353      Box$(2,Row)=Old_box$(2,Row)
2354    NEXT Row
2355   !
2356    SUBEXIT
2357  SUBEND
2358!
2359 Dummy:SUB Dummy
2360  SUBEND
2361 Dummy:SUB Dummy
2362  SUBEND
2363 Dummy:SUB Dummy
2364  SUBEND
2365!
2366 Meas_fs:DEF FNMeas_fs
2367  !************************************************************************
2368  !* The following collection of routines provides a means for the digital
2369  !* scope function to access the measurement setup as defined in the
2370  !* measurement spreadsheet.
2371  !************************************************************************
2372  !************************************************************************
2373  !* This function returns the current sample rate for digital scope.
2374  !************************************************************************
2375    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2376    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2377    RETURN VAL(Box$(2,Fs_row))
2378  FNEND
2379!
2380 Meas_span:DEF FNMeas_span
2381  !************************************************************************
2382  !* This function returns the current span for digital scope.
2383  !************************************************************************
2384    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2385    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2386   !
2387    RETURN VAL(Box$(2,Fs_row))/2.56
2388  FNEND
2389!
2390 Meas_trigger_on:DEF FNMeas_trigger_on
2391  !************************************************************************
2392  !* This function returns logical true/false for 'Wait for Trigger'.
2393  !************************************************************************
2394    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2395    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2396    INTEGER Trigger_on
2397   !
2398    Trigger_on=(UPC$(Box$(2,Wft_row))="ON")
2399    RETURN Trigger_on
2400  FNEND
2401!
2402 Meas_num_samp:DEF FNMeas_num_samp
2403  !************************************************************************
2404  !* This function returns the number of samples per trace for dig scope.
2405  !************************************************************************
2406    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2407    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2408   !
2409    RETURN VAL(Box$(2,Nsc_row))
2410  FNEND
2411!
2412 Meas_single:DEF FNMeas_single
2413  !************************************************************************
2414  !* This function returns logical true/false for 'Single Measurement'.
2415  !************************************************************************
2416    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2417    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2418    INTEGER Single
2419   !
2420    Single=(UPC$(Box$(2,Cs_row))="SINGLE")
2421    RETURN Single
2422  FNEND
2423!
2424 Meas_trg_source:DEF FNMeas_trg_source$
2425  !************************************************************************
2426  !* This function returns the name of the module currently selected to
2427  !* trigger the measurement.
2428  !************************************************************************
2429    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2430   !
2431    RETURN Trg_source_name$
2432  FNEND
2433!
2434 Meas_time:DEF FNMeas_time
2435  !************************************************************************
2436  !* This function returns the captured time length in seconds.
2437  !************************************************************************
2438    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2439    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2440   !
2441    RETURN VAL(Box$(2,Nsc_row))/VAL(Box$(2,Fs_row))
2442  FNEND
2443!
2444 Meas_trig_input:DEF FNMeas_trig_input
2445  !************************************************************************
2446  !* This function returns true if the module currently selected to trigger
2447  !* the measurement is an input module.
2448  !************************************************************************
2449    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2450   !
2451    RETURN Trig_is_input
2452  FNEND
2453!
2454  !************************************************************************
2455  !     End of routines for the application to use.
2456  !************************************************************************
2457!
2458 Meas_save:SUB Meas_save(@File,REAL Ok)
2459  !************************************************************************
2460  !*    Save recall routines.
2461  !************************************************************************
2462  !************************************************************************
2463  !* This subroutine appends the current digital scope setup to @File by
2464  !* saving Box$(*) and some other variables.  A revision code is written
2465  !* to the file to reject incompatible data on recall.
2466  !************************************************************************
2467    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2468    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2469    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2470    INTEGER File_format_rev
2471   !
2472    File_format_rev=2620
2473    OUTPUT @File;File_format_rev
2474    OUTPUT @File;Trg_source_name$
2475    OUTPUT @File;Trig_is_input
2476    OUTPUT @File;Tm_row
2477    OUTPUT @File;Tsl_row
2478    OUTPUT @File;Tlv_row
2479    OUTPUT @File;Tl1_row
2480    OUTPUT @File;Tl2_row
2481    File_save_s(@File,Box$(*))
2482    Ok=1
2483   !
2484    SUBEXIT
2485  SUBEND
2486!
2487 Meas_load:SUB Meas_load(@File,REAL Ok)
2488  !************************************************************************
2489  !* This subroutine gets a digital scope setup from @File by loading Box$
2490  !* and some other variables.
2491  !* The revision code is read from the file to reject incompatible data.
2492  !************************************************************************
2493    COM /Meas_sprd/ Box$(*),Title$(*),Prompt$(*)
2494    COM /Meas_rows/ INTEGER Fs_row,Wft_row,Ts_row,Cs_row,Nsc_row,Tm_row,Tlv_row,Tsl_row,Tl1_row,Tl2_row
2495    COM /Meas_trig_info/ Trg_source_name$,INTEGER Trig_is_input
2496    DIM Temp$[40]
2497    INTEGER File_format_rev
2498   !
2499    ENTER @File;File_format_rev
2500    SELECT File_format_rev
2501    CASE 2620
2502      ENTER @File;Trg_source_name$
2503      ENTER @File;Trig_is_input
2504      ENTER @File;Tm_row
2505      ENTER @File;Tsl_row
2506      ENTER @File;Tlv_row
2507      ENTER @File;Tl1_row
2508      ENTER @File;Tl2_row
2509      File_load_s(@File,Box$(*))
2510     !
2511     !Set up trigger module if trigger from an input:
2512      IF FNMeas_trigger_on AND Trig_is_input THEN 
2513        Temp$=UPC$(TRIM$(Box$(2,Tm_row)))
2514        IF Temp$[1;1]="L" THEN 
2515          Inpt_cmd(Trg_source_name$,"TRIGGER TYPE","LEVEL")
2516          Temp$=TRIM$(Box$(2,Tsl_row))
2517          Inpt_cmd(Trg_source_name$,"TRIGGER SLOPE",Temp$)
2518          Temp$=VAL$(VAL(Box$(2,Tlv_row)))
2519          Inpt_cmd(Trg_source_name$,"TRIG LEVEL",Temp$)
2520        ELSE
2521          Inpt_cmd(Trg_source_name$,"TRIGGER TYPE","MAGNITUDE")
2522          Temp$=VAL$(VAL(Box$(2,Tl1_row)))
2523          Inpt_cmd(Trg_source_name$,"UPPER LEVEL",Temp$)
2524          Temp$=VAL$(VAL(Box$(2,Tl2_row)))
2525          Inpt_cmd(Trg_source_name$,"LOWER LEVEL",Temp$)
2526        END IF
2527       !
2528       !Clear any errors these module setup commands may have caused:
2529        Inpt_cmd("ALL INPUT","CLEAR")
2530        Srce_cmd("ALL SOURCE","CLEAR")
2531      END IF
2532      Meas_respread
2533      Ok=1
2534    CASE ELSE
2535      User_error("Load ERROR - Incompatible file format for Digital Scope spreadsheet.")
2536      Ok=0
2537    END SELECT
2538    SUBEXIT
2539  SUBEND
2540!
2541 Ds_store_tr:SUB Ds_store_tr
2542   !*********************************************************************
2543   !*
2544   !*********************************************************************
2545    Disp_user_mess("Ds_store_tr",2)
2546    SUBEXIT
2547  SUBEND
2548 Ds_think_jet:SUB Ds_think_jet
2549   !*********************************************************************
2550   !*
2551   !*********************************************************************
2552    OUTPUT 2 USING "K,#";CHR$(255)&CHR$(124)
2553    PRINTER IS 701
2554    DUMP DEVICE IS 701
2555    PRINT CHR$(27)&"*r1280S";       !  HI DENSITY GRAPH MODE, 1280 pixels
2556    PRINT CHR$(27)&"*rA";           !  ACTIVATE
2570    DUMP GRAPHICS                   !  DUMP IT
2571    PRINT CHR$(27)&"*r640S";        !  LOW DENSITY GRAPH MODE, 640 pixels
2572    PRINT CHR$(27)&"*rB";           !  DE-ACTIVATE
2573    PRINTER IS CRT
2574    OUTPUT 2 USING "K,#";CHR$(255)&CHR$(124)
2575    SUBEXIT
2576  SUBEND
2577 Ds_plot:SUB Ds_plot(Buf(*))
2578   !*********************************************************************
2579   !*  Ds_plot sets the external plotter active, plots all traces there and
2580   !*  re-initiates the CRT as PLOTTER again.
2581   !*********************************************************************
2582    COM /Ds_data/ REAL Data_header(*),INTEGER Ovld_buffer(*)
2583    PLOTTER IS 705,"HPGL"
2584    Disp_plot_axis
2585    Disp_plot_data(Buf(*),Data_header(*))
2586    Plot_plot                       ! Re-initiate
2587    SUBEXIT
2588  SUBEND
2589 Ds_dacq300:SUB Ds_dacq300
2590   !*********************************************************************
2591   !*
2592   !*********************************************************************
2593    Disp_user_mess("  ***  DACQ300 utility not implemented yet ***",10)
2594    SUBEXIT
2595  SUBEND