1 ! RE-STORE "DISP_H"
2     ! NÎdfil ihopslÌngd av SNO 87-01-19.
3     !
4     ! Motsvarar DISP.
5     !
6     ! ØNDRINGAR INFÚRDA I DISP_RESET      87-01-23
7     ! ØNDRINGAR INFÚRDA I DISP_PLOT_DATA  87-01-24
8     ! ØNDRINGAR INFÚRDA I DISP_PLOT_SET   87-01-24
9     ! ØNDRINGAR INFÚRDA I DISP_DISP       87-01-24
10    ! ØNDRINGAR INFÚRDA I DISP_PLOT_AXIS  87-02-06
11    ! ØNDRINGAR INFÚRDA I DISP_DO_MKR     87-02-06
12    !
13    ! NY FUNKTION :     FNDISP_IN_DS_H    87-01-24
14    ! NY FUNKTION :     FNDISP_VS_XMAG    87-01-24
15    ! NY FUNKTION :     FNDISP_VS_XMIN    87-01-24
16    ! NY FUNKTION :     FNDISP_VS_XMAX    87-01-24
17    ! NY FUNKTION :     FNDISP_EXP_START  87-02-06
18    ! NY FUNKTION :     FNDISP_EXP_STOP   87-02-06
19    ! NY FUNKTION :     FNDISP_EXP_ZERO   87-02-06
20    ! NY FUNKTION :     FNDISP_VS_START   87-02-06
21    ! NY FUNKTION :     FNDISP_VS_STOP    87-02-06
23    ! NY FUNKTION :     FNDISP_KN_SCALED  87-02-26
24    ! NY FUNKTION :     FNDISP_ST_TR_FULL 87-02-26
25    ! NY FUNKTION :     FNDISP_SC_SIGN$   87-02-26
26    ! NY FUNKTION :     FNDISP_PLOT_SV_TR 87-02-26
27    ! NY FUNKTION :     FNDISP_OFFS0      87-02-26
28    ! NY FUNKTION :     FNDISP_GET_ROW    87-02-26
29    ! NY FUNKTION :     FNDISP_AUTO_C     87-02-26
30    ! NY FUNKTION :     FNDISP_DATA_MOVE  87-02-26
31    ! NY FUNKTION :     FNDISP_GET_CURS   87-02-26
32    ! NY FUNKTION :     FNDISP_GET_SUB    87-02-26
33    ! NY FUNKTION :     FNDISP_SV_TR_CLR  87-02-26
34    !
35    ! NY RUTIN    :     DISP_EXP_TR       87-02-06
36    ! NY RUTIN    :     DISP_EXP_MIN      87-02-06
37    ! NY RUTIN    :     DISP_EXP_MAX      87-02-06
38    ! NY RUTIN    :     DISP_EXP_ZERO     87-02-06
39    ! NY RUTIN    :     DISP_EXP_FORGET   87-02-06
40    ! NY RUTIN    :     DISP_USER_MESS    87-02-06
41    ! NY RUTIN    :     DISP_SET_OFFS0    87-02-26
42    ! NY RUTIN    :     DISP_SET_SCALE    87-02-26
43    ! NY RUTIN    :     DISP_ACT_KNOB     87-02-26
44    ! NY RUTIN    :     DISP_SET_SC_SIGN  87-02-26
45    ! NY RUTIN    :     DISP_SET_SV_TR    87-02-26
46    ! NY RUTIN    :     DISP_GET_SV_TR    87-02-26
47    ! NY RUTIN    :     DISP_DEL_SV_TR    87-02-26
48    ! NY RUTIN    :     DISP_H_MKR        87-02-26
57    ! NY RUTIN    :     DISP_EXP_DONE     87-02-06
58    ! NY RUTIN    :     DISP_SET_D_MOVE   87-02-26
59    ! NY RUTIN    :     DISP_SET_CURS     87-02-26
60    ! NY RUTIN    :     DISP_SET_SUB      87-02-06
61    !
62 Disp_disp:SUB Disp_disp
63      !This subprogram defines and initializes all common used by the DISP
64      !file subprograms.  The size of the recalled trace buffer is defined
65      !here and can be modified to suit application or memory requirements.
66      !
67      !These common blocks give the display spread sheet memory:
68      COM /Disp_spread1/ Box$(1:10,1:17)[45],Row,Col,Start_row
69      COM /Disp_spread2/ Title$(1:10,0:2)[45],Prompt$(1:10)[80],Col_width(1:10)
70      COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
71      COM /Disp_spread4/ Choices$(1:6,1:64)[45],Num_choices(1:6)
72      COM /Disp_choice/ Plot_choice(1:16,1:6)
73      !
74      !
75      !These common blocks "store" plot setups.  Values are set by subprograms
76      !like Disp_plot_set, and used by subprograms like Disp_plot_axis.
77      COM /Disp_num_plots/ Num_live_plots,Num_r_plots
78      COM /Disp_titles/ Plot_titles$(1:16)[45]
79      COM /Disp_y/ Y_max$(1:16)[20],Y_min$(1:16)[20]
80      COM /Disp_buf/ Plot_to_buf(1:16),Start_bin(1:16),Num_bins(1:16)
81      COM /Disp_units/ X_units$(1:16)[10],Y_units$(1:16)[10]
82      COM /Disp_window/ X_min(1:16),X_max(1:16),Y_min(1:16),Y_max(1:16)
83      COM /Disp_log/ Do_log_x(1:16),Do_log_y(1:16)
84      COM /Disp_mkr/ Mkr_plot,INTEGER Saved_tr,INTEGER Reference_tr
85      COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
86      !
87      !
88      !The size of the Recall_buf can be changed here. This determines
89      !the number of traces that can be recalled and their maximum size.
90      COM /Disp_recall/ Recall_buf(1:2,1:4096),Recall_head(1:2,1:10)  !2 big ones
91    ! COM /Disp_recall/ Recall_buf(1:1,1:1024),Recall_head(1:1,1:10)  !smaller one
92      !
93      !These common blocks store other recalled trace info and should not
94      !be changed.
95      COM /Disp_recall1/ R_x_units$(1:16)[10],R_y_units$(1:16)[10],R_num_bins(1:16)
96      COM /Disp_recall2/ R_x_min(1:16),R_x_max(1:16),R_y_def_min(1:16),R_y_def_max(1:16)
97      COM /Disp_recall3/ R_do_log_x(1:16),R_do_log_y(1:16)
98      COM /Disp_recall4/ Plot_to_r_buf(1:16)
99      !
100     COM /Disp_exp/ INTEGER Start_binx,Stop_binx,Zero_binx,INTEGER New_plot,Old_start_bin,Old_stop_bin
101     COM /Disp_knob_scale/ Scale_factor,Scale_sign(1:3),INTEGER Activated
102     Scale_factor=1
103     MAT Scale_sign= (1.0)
104     Activated=0
105     COM /Disp_offs0/ Offset0_x,Offset0_y,Offset0_y_abs
106     Offset0_x=0
107     Offset0_y=0
108     COM /Disp_sub/ Sub_active(1:16,0:1,0:1)
109     MAT Sub_active= (0)
110     COM /Disp_curs/ Offset_x,Offset_y
111     Offset_x=0
112     Offset_y=0
113     COM /Disp_auto/ INTEGER Auto_center_on,REAL Data_move_offs(1:16,0:1,0:1)
114     MAT Data_move_offs= (0)
115     COM /Disp_sv_tr/ Sv_trace(1:4,0:8191),INTEGER Trace_saved(1:16,0:1),INTEGER Arr_size(1:4)
116     !
117     MAT Trace_saved= (0)
118     !C_plot_array is saved in common to avoid re-computing the x axis.
119     COM /Disp_plot_array/ C_plot_array(1:1024,1:2),C_p_size
120     C_p_size=1024
121     !
122     Num_recall_rows=SIZE(Recall_buf,1)   !for spread sheet
123     !
124     ! Init /Disp_exp/
125     Start_binx=-99
126     Stop_binx=-99
127     Zero_binx=-99
128   SUBEND
129   !************************************************************************
130 Disp_spread_set:SUB Disp_spread_set(Ex_title$(*),Ex_prompt$(*),Ex_col_width(*),Ex_choices$(*))
131   !This sub sets up the display spread sheet.  It should be called
132   !before Disp_spread and whenever there is a configuration change.
133   !It defines the spread sheet titles, etc which are stored in COM.
134   !Columns for "Active" "Y min" and "Y max" are standard, from 1 to 6
135   !other columns are defined by by the calling program.  Passed arrays
136   !in should be dimensioned to the number of columns needed, up to 6.
137 !       Ex_title$(1:6,1:2)[45]  Two lines of titles for the columns.
138 !       Ex_prompt$(1:6)[80] Prompts for the columns.
139 !       Ex_col_width(1:6) Width of the columns.
140 !       Ex_choices$(1:6,1:64)[45] An array of possible choices for each
141 !                      column.
142   !
143     COM /Disp_spread1/ Box$(*),Row,Col,Start_row
144     COM /Disp_spread2/ Title$(*),Prompt$(*),Col_width(*)
145     COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
146     COM /Disp_spread4/ Choices$(*),Num_choices(*)
147  !
148     Num_categories=SIZE(Ex_title$,1)  !number of externally defined columns
149     Max_col=Num_categories+4       !4 for num, active, y min, y max
150     !
151     !
152     !For each category, count the number of choices
153     REDIM Num_choices(1:Num_categories)
154     FOR Category_num=1 TO Num_categories
155       Choice_num=0
156       REPEAT
157         Choice_num=Choice_num+1
158       UNTIL (Ex_choices$(Category_num,Choice_num)="") OR (Choice_num=SIZE(Ex_choices$,2))
159       IF Ex_choices$(Category_num,Choice_num)="" THEN Choice_num=Choice_num-1
160       Num_choices(Category_num)=Choice_num
161     NEXT Category_num
162     !
163     !copy list of choices into common
164     REDIM Choices$(1:Num_categories,1:MAX(Num_choices(*)))
165     FOR Category_num=1 TO Num_categories
166       FOR Choice_num=1 TO Num_choices(Category_num)
167         Choices$(Category_num,Choice_num)=Ex_choices$(Category_num,Choice_num)
168       NEXT Choice_num
169     NEXT Category_num
170     !
171     !figure out how many rows of live (not recalled) traces should be displayed
172     Num_live_rows=1
173     FOR Category_num=1 TO Num_categories
174       Num_live_rows=Num_live_rows*Num_choices(Category_num)
175     NEXT Category_num
176     Num_live_rows=MIN(Num_live_rows,16)
177     Max_row=1+Num_live_rows+Num_recall_rows    !+1 for "All" line
178     REDIM Box$(1:Max_col,1:Max_row)
179     !
180     !define constants for other columns
181     Active_col=2
182     Y_min_col=3+Num_categories
183     Y_max_col=4+Num_categories
184     !
185     !re-DIM arrays in common so they can be indexed by column instead
186     !of category_num
187     REDIM Num_choices(3:2+Num_categories)
188     REDIM Choices$(3:2+Num_categories,1:MAX(Num_choices(*)))
189  !
190  ! These data statements define the setup and titles for each column
191  !
192  !   col_width  title1         title2      Prompt
193  !   ---------  ----------     ----------  --------------------
194     DATA    5,     "Trace",    "Num",     ""
195     DATA    4,     "Act-",     "ive",     "Trace active: (Yes or No)"
196   !externally defined columns show up here
197     DATA    9,     "Y Axis",     "Min",      "Y Axis minimum: (value or ""Default"")"
198     DATA    9,     "Y Axis",     "Max",      "Y Axis maximum: (value or ""Default"")"
199  !
200  !
201  !read spread sheet setup into arrays
202     MAT Col_width= (0)
203     Title$(1,0)="DISPLAY SETUP"
204     FOR C=1 TO 2
205       READ Col_width(C),Title$(C,1),Title$(C,2),Prompt$(C)
206     NEXT C
207     FOR C=3 TO 2+Num_categories
208       Col_width(C)=Ex_col_width(C-2)
209       Title$(C,1)=Ex_title$(C-2,1)
210       Title$(C,2)=Ex_title$(C-2,2)
211       Prompt$(C)=Ex_prompt$(C-2)
212     NEXT C
213     FOR C=Num_categories+3 TO Max_col
214       READ Col_width(C),Title$(C,1),Title$(C,2),Prompt$(C)
215     NEXT C
216     !
217     !set rows to initial values
218     CALL Disp_reset
219     !
220     !copy Box$ to other common blocks
221     CALL Disp_update_com
222     !
223   SUBEND
224   ! PAGE -> 
225   !************************************************************************
226 Disp_spread:SUB Disp_spread(Modified,OPTIONAL Major_mod)
227   !This subprogram is the display spread sheet, called when the
228   !DISPLAY SETUP softkey is pressed.  For up to 16 "live" traces, it allows 
the
229   !user to make the trace active, change Y axis scaling, or change one
230   !or more application-dependent items.  It also allows the user to recall
231   !a previously stored trace into one of the recall buffers.  <Modified> is
232   !is set to 1 if any changes were made.  <Major_mod> is set to 1 if
233   !any changes were made to any of the spread sheet columns
234   !other than Y axis scaling.
235     COM /Disp_spread1/ Box$(*),Row,Col,Start_row
236     COM /Disp_spread2/ Title$(*),Prompt$(*),Col_width(*)
237     COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
238     COM /Disp_spread4/ Choices$(*),Num_choices(*)
239  !
240     DIM New_entry$[160]
241     Max_row=SIZE(Box$,2)
242  !
243     GOSUB Label_keys
244     CALL User_clr_scr
245  !Now call spread sheet.  It returns with New_entry$ and Row and Col
246     Done=0
247     Modified=0
248     Major_mod1=0
249     REPEAT
250       CALL User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),2,Col,Row,Start_row)
251       SELECT FNUser_check_key
252       CASE 0   !no key pressed, must be a New_entry$ for Box
253         GOSUB New_entry
254       CASE 5         !the Reset key
255         Dummy=FNUser_get_key
256         CALL Disp_reset
257         Modified=1
258         Major_mod1=1
259       CASE 6         !"Color" softkey
260         Dummy=FNUser_get_key
261         IF FNPlot_have_color THEN 
262           CALL Plot_set_color(NOT FNPlot_use_color)
263           GOSUB Label_keys
264         ELSE
265           BEEP 651,.03
266         END IF
267       CASE 7         !Prev
268         Dummy=FNUser_get_key
269         GOSUB Prev_choice
270       CASE 8         !next
271         Dummy=FNUser_get_key
272         GOSUB Next_choice
273       CASE ELSE      !a softkey but not one of mine, so exit
274         Done=1
275       END SELECT
276     UNTIL Done
277     CALL User_clr_scr
278     IF Modified THEN CALL Disp_update_com
279     IF NPAR>1 THEN Major_mod=Major_mod1
280     SUBEXIT
281 New_entry:          !------------------------------------------------
282    !acts on new_entry from spread_sheet
283     New_entry$=UPC$(TRIM$(New_entry$))
284     IF New_entry$[1,1]="""" THEN New_entry$=TRIM$(New_entry$[2]) !delete "
285     IF New_entry$<>"" THEN 
286       SELECT Col
287       CASE Active_col
288         Modified=1
289         Major_mod1=1
290         SELECT New_entry$[1,1]
291         CASE "Y","*"
292           SELECT Row
293           CASE 1    !All row
294             FOR R=2 TO Num_live_rows+1
295               Box$(Col,R)="*"
296             NEXT R
297           CASE <=Num_live_rows+1
298             Box$(Col,Row)="*"
299           CASE >Num_live_rows+1    !recalled trace
300             GOSUB Recall_trace
301           END SELECT
302         CASE "N"
303           SELECT Row
304           CASE 1
305             FOR R=2 TO Max_row
306               Box$(Col,R)=""
307             NEXT R
308             FOR R=Num_live_rows+2 TO Max_row
309               Box$(Active_col+1,R)="Recall trace "&VAL$(R-Num_live_rows-1)
310             NEXT R
311           CASE <=Num_live_rows+1
312             Box$(Col,Row)=""
313           CASE >Num_live_rows+1    !recalled trace
314             GOSUB Cancel_recall
315           END SELECT
316         CASE ELSE
317           BEEP 200,.1
318         END SELECT
319       CASE Active_col+1 TO Y_min_col-1  !application dependent cols
320         Modified=1
321         Major_mod1=1
322         IF Row<=Num_live_rows+1 THEN 
323           CALL Lib_match2(New_entry$,Choices$(*),Col,Found,Choice_num)
324           IF Found THEN 
325             IF Row=1 THEN 
326               FOR R=2 TO Num_live_rows+1
327                 Box$(Col,R)=Choices$(Col,Choice_num)
328               NEXT R
329             ELSE
330               Box$(Col,Row)=Choices$(Col,Choice_num)
331             END IF
332           ELSE
333             BEEP 200,.1
334           END IF
335         ELSE   !row is recalled traces
336           CALL User_error("Sorry, you can not modify this box on recalled traces.")
337         END IF
338       CASE Y_min_col,Y_max_col
339         Modified=1
340         IF New_entry$[1,1]="D" THEN 
341           IF Row=1 THEN 
342             FOR R=2 TO Max_row
343               Box$(Col,R)="Default"
344             NEXT R
345           ELSE
346             Box$(Col,Row)="Default"
347           END IF
348         ELSE
349           ON ERROR GOTO Not_a_number
350           Dummy=VAL(New_entry$)
351           IF Row=1 THEN 
352             FOR R=2 TO Max_row
353               Box$(Col,R)=New_entry$
354             NEXT R
355           ELSE
356             Box$(Col,Row)=New_entry$
357           END IF
358           OFF ERROR 
359           GOTO Ok
360 Not_a_number:OFF ERROR 
361           DISP ERRM$
362           BEEP 200,.1
363           WAIT 2
364           DISP 
365 Ok:         !
366         END IF
367       END SELECT
368     END IF
369     RETURN 
370 Prev_choice:   !--------------------------------------------------
371     SELECT Col
372     CASE Active_col
373       Modified=1
374       Major_mod1=1
375       GOSUB Toggle
376     CASE Active_col+1 TO Y_min_col-1  !application dependent columns
377       IF (Num_choices(Col)>1) AND (Row<=Num_live_rows+1) THEN 
378         Modified=1
379         Major_mod1=1
380         !find the choice_num of the current selection and decrement
381         IF Row=1 THEN  !first row is "all"
382           CALL Lib_match2(Box$(Col,2),Choices$(*),Col,Found,Choice_num)
383         ELSE
384           CALL Lib_match2(Box$(Col,Row),Choices$(*),Col,Found,Choice_num)
385         END IF
386         Choice_num=Choice_num-1
387         IF Choice_num<1 THEN Choice_num=Num_choices(Col)
388         IF Row=1 THEN 
389           FOR R=2 TO Num_live_rows+1
390             Box$(Col,R)=Choices$(Col,Choice_num)
391           NEXT R
392         ELSE
393           Box$(Col,Row)=Choices$(Col,Choice_num)
394         END IF
395       ELSE
396         BEEP 651,.03
397       END IF
398     CASE ELSE                !other column
399       BEEP 651,.03
400     END SELECT
401     RETURN 
402 Next_choice:    !-------------------------------------------------
403     SELECT Col
404     CASE Active_col
405       Modified=1
406       Major_mod1=1
407       GOSUB Toggle
408     CASE Active_col+1 TO Y_min_col-1  !application dependent columns
409       IF (Num_choices(Col)>1) AND (Row<=Num_live_rows+1) THEN 
410         Modified=1
411         Major_mod1=1
412         !find the choice_num of the current selection and increment
413         IF Row=1 THEN  !first row is "all"
414           CALL Lib_match2(Box$(Col,2),Choices$(*),Col,Found,Choice_num)
415         ELSE
416           CALL Lib_match2(Box$(Col,Row),Choices$(*),Col,Found,Choice_num)
417         END IF
418         Choice_num=Choice_num+1
419         IF Choice_num>Num_choices(Col) THEN Choice_num=1
420         IF Row=1 THEN     !ALL rows
421           FOR R=2 TO Num_live_rows+1
422             Box$(Col,R)=Choices$(Col,Choice_num)
423           NEXT R
424         ELSE
425           Box$(Col,Row)=Choices$(Col,Choice_num)
426         END IF
427       ELSE
428         BEEP 651,.03
429       END IF
430     CASE ELSE                !other column
431       BEEP 651,.03
432     END SELECT
433     RETURN 
434 Toggle:        !--------------------------------------------------
435     IF Row=1 THEN         !ALL rows
436       IF Box$(Col,2)="*" THEN 
437         FOR R=2 TO Max_row
438           Box$(Col,R)=""
439         NEXT R
440         FOR R=Num_live_rows+2 TO Max_row
441           Box$(Active_col+1,R)="Recall trace "&VAL$(R-Num_live_rows-1)
442         NEXT R
443       ELSE
444         FOR R=2 TO Num_live_rows+1
445           Box$(Col,R)="*"
446         NEXT R
447       END IF
448     ELSE
449       IF Box$(Col,Row)="*" THEN 
450         IF Row<=Num_live_rows+1 THEN     !live traces
451           Box$(Col,Row)=""
452         ELSE
453           GOSUB Cancel_recall
454         END IF
455       ELSE
456         IF Row<=Num_live_rows+1 THEN     !live traces
457           Box$(Col,Row)="*"
458         ELSE
459           GOSUB Recall_trace
460         END IF
461       END IF
462     END IF
463     RETURN 
464 Recall_trace:   !-----------------------------------------------------
465     CALL Disp_recall_tr(Row-Num_live_rows-1,Box$(Active_col+1,Row),Ok)
466     IF Ok THEN 
467       Box$(Active_col,Row)="*"
468     ELSE
469       GOSUB Cancel_recall
470     END IF
471     RETURN 
472 Cancel_recall:  !-----------------------------------------------------
473     Box$(Active_col,Row)=""
474     Box$(Active_col+1,Row)="Recall trace "&VAL$(Row-Num_live_rows-1)
475     RETURN 
476 Label_keys:     !------------------------------------------------------
477  ! Overwrite unused softkeys
478     ON KEY 5 LABEL FNUser_keylabel$("Reset") CALL User_key5isr
479     IF FNPlot_have_color THEN 
480       IF FNPlot_use_color THEN 
481         ON KEY 6 LABEL FNUser_keylabel$("Color *") CALL User_key6isr
482       ELSE
483         ON KEY 6 LABEL FNUser_keylabel$("Color") CALL User_key6isr
484       END IF
485     ELSE
486       ON KEY 6 LABEL "" CALL User_key6isr
487     END IF
488     ON KEY 7 LABEL FNUser_keylabel$("Previous") CALL User_key7isr
489     ON KEY 8 LABEL FNUser_keylabel$("Next") CALL User_key8isr
490     RETURN 
491   SUBEND
492   ! PAGE -> 
493   !************************************************************************
494 Disp_plot_set:SUB 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(*))
495     !Called to "program" the plot setup.  Must be called by the application
496     !before Disp_plot_data is called, and whenever hardware or the display
497     !changes.  This sub just "stores" the passed info in common for use
498     !by other Disp_ subprograms such as Disp_plot_axis.
499     !
500 !       Plot_to_buf(1:num_plots)  Array of buffer numbers, one for each
501 !                      plot.  Passed to Disp_plot_set so it knows
502 !                      which buffer to get each plot out of.
503 !       X_units$(1:num_plots)  like "Hz" or "Sec" for each plot.
504 !                      A "" means don't label the x axis. 10 chars max.
505 !       Y_units$(1:num_plots) like "V" or "dBVp".  A "" means don't
506 !                      label the Y axis. 10 chars max.
507 !       Start_x(1:num_plots) The X axis value of Data_buffer(plot_num,0)
508 !                      in real world units.
509 !       Per_bin_x(1:num_plots) The value of one x bin in real world
510 !                      units.
511 !       Start_bin(1:num_plots) Which element of Data_buffer to start plotting.
512 !       Num_bins(1:num_plots) Number of points to plot.
513 !       Y_def_max(1:num_plots), Y_def_min(*):  Y axis values to use when
514 !                      when "default" scaling is selected.
515  !
516     COM /Disp_num_plots/ Num_live_plots,Num_r_plots
517     COM /Disp_y/ Y_max$(*),Y_min$(*)
518     COM /Disp_buf/ Plot_to_buf_c(*),Start_bin_c(*),Num_bins_c(*)
519     COM /Disp_units/ X_units_c$(*),Y_units_c$(*)
520     COM /Disp_window/ X_min(*),X_max(*),Y_min(*),Y_max(*)
521     COM /Disp_log/ Do_log_x(*),Do_log_y(*)
522     COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
523     !
524     COM /Disp_recall1/ R_x_units$(*),R_y_units$(*),R_num_bins(*)
525     COM /Disp_recall2/ R_x_min(*),R_x_max(*),R_y_def_min(*),R_y_def_max(*)
526     COM /Disp_recall3/ R_do_log_x(*),R_do_log_y(*)
527     COM /Disp_recall4/ Plot_to_r_buf(*)
528     !
529     !
530     IF Num_live_plots>SIZE(Plot_to_buf,1) THEN CALL User_stop("Size of Plot_to_buf < num_plots in Disp_plot_data")
531     Plots_done=0
532     R_plots_done=0
533     MAT Do_log_x= (0)
534     MAT Do_log_y= (0)
535     FOR P=1 TO Num_live_plots
536       GOSUB Do_live_plot
537     NEXT P
538     IF Num_r_plots>0 THEN !do recalled plots with info in common
539       FOR P=Num_live_plots+1 TO Num_live_plots+Num_r_plots
540         GOSUB Do_recall_plot
541       NEXT P
542     END IF
543     SUBEXIT
544 Do_live_plot:      !-----------------------------------------------------
545     Plot_to_buf_c(P)=Plot_to_buf(P)
546     X_units_c$(P)=X_units$(P)
547     Y_units_c$(P)=Y_units$(P)
548     Start_bin(P)=MAX(0,Start_bin(P))
549     Start_bin_c(P)=Start_bin(P)
550     Num_bins_c(P)=Num_bins(P)
551     IF Num_bins(P)<1 THEN CALL User_stop("ERROR: Num_bins <1 (Disp_plot_set)")
552     IF Per_bin_x(P)<=0 THEN CALL User_stop("ERROR: Per_bin_x<=0 (Disp_plot_set)")
553     X_min(P)=Start_x(P)+Start_bin(P)*Per_bin_x(P)
554     X_max(P)=Start_x(P)+(Start_bin(P)+Num_bins(P)-1)*Per_bin_x(P)
555     Y_min(P)=Y_def_min(P)
556     IF Y_min$(P)<>"Default" THEN Y_min(P)=VAL(Y_min$(P))
557     Y_max(P)=Y_def_max(P)
558     IF Y_max$(P)<>"Default" THEN Y_max(P)=VAL(Y_max$(P))
559     IF Y_max(P)<=Y_min(P) THEN Y_max(P)=Y_min(P)+1
560    ! Special test for 'DS_H' when in 'Input vs ...'
561     IF (FNDisp_in_ds_h AND (FNDisp_choice(P,3)=3)) THEN 
562       X_max(P)=FNDisp_vs_xmax
563       X_min(P)=FNDisp_vs_xmin
564       Per_bin_x(P)=(X_max(P)-X_min_(P))/Num_bins(P)
565     END IF
566     RETURN 
567 Do_recall_plot:      !------------------------------------------------
568     Do_log_x(P)=R_do_log_x(Plot_to_r_buf(P))
569     Do_log_y(P)=R_do_log_y(Plot_to_r_buf(P))
570     X_units_c$(P)=R_x_units$(Plot_to_r_buf(P))
571     Y_units_c$(P)=R_y_units$(Plot_to_r_buf(P))
572     Start_bin_c(P)=1
573     Num_bins_c(P)=R_num_bins(Plot_to_r_buf(P))
574     X_min(P)=R_x_min(Plot_to_r_buf(P))
575     X_max(P)=R_x_max(Plot_to_r_buf(P))
576     Y_min(P)=R_y_def_min(Plot_to_r_buf(P))
577     IF Y_min$(P)<>"Default" THEN Y_min(P)=VAL(Y_min$(P))
578     Y_max(P)=R_y_def_max(Plot_to_r_buf(P))
579     IF Y_max$(P)<>"Default" THEN Y_max(P)=VAL(Y_max$(P))
580     IF Y_max(P)<=Y_min(P) THEN Y_max(P)=Y_min(P)+1
581     IF Do_log_y(P) AND (Y_max(P)<=0) THEN Y_max(P)=1    !aviod LOG(0)
582     IF Do_log_y(P) AND (Y_min(P)<=0) THEN Y_min(P)=Y_max(P)/1000
583     RETURN 
584   SUBEND
585   ! PAGE -> 
586   !************************************************************************
587 Disp_plot_axis:SUB Disp_plot_axis
588    !This subprogram plots grids and labels the axis for all the plots.
589     COM /Disp_titles/ Plot_titles$(*)
590     COM /Disp_units/ X_units$(*),Y_units$(*)
591     COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
592     COM /Disp_log/ Do_log_x(*),Do_log_y(*)
593     COM /Disp_num_plots/ Num_live_plots,Num_r_plots
594     COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
595     COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
596     !
597     DIM X_min(1:16),X_max(1:16)
598     DIM Start_bin(1:16),Num_bins(1:16)
599     !
600     CSIZE FNPlot_good_csize
601     Plots_done=0
602     R_plots_done=0
603     CALL User_clr_scr
604     MAT Start_bin= Start_bin_c
605     MAT Num_bins= Num_bins_c
606     MAT X_min= X_min_c
607     MAT X_max= X_max_c
608     !first figure Y_units_len, how many characters of room to leave
609     !at the left of the plot for the y axis labels.
610     !One value is used for all plots for atheistics.
611     Y_units_len=0
612     Total_num_plots=Num_live_plots+Num_r_plots
613     FOR P=1 TO Total_num_plots
614       L=LEN(Y_units$(P))
615       IF L<>0 THEN 
616         L=MAX(5,L)          !4 for numbers +1 for prefix
617       END IF
618       Y_units_len=MAX(Y_units_len,L+1)    !+1 space
619       Do_vs=(FNDisp_in_ds_h AND (FNDisp_choice(P,3)=3))
620       IF FNDisp_in_ds_h THEN 
621         Start_bin(P)=MAX(Start_bin_c(P),FNDisp_exp_start)
622         Num_bins(P)=MIN(Num_bins_c(P),(FNDisp_exp_stop+1-Start_bin(P)))
623         IF Num_bins(P)<0 THEN Num_bins(P)=Num_bins_c(P)
624         IF NOT Do_vs THEN 
625             ! And now into real world units ...
626           X_min(P)=X_min_c(P)+Start_bin(P)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
627           X_max(P)=X_min_c(P)+(Start_bin(P)+Num_bins(P)-1)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
628         END IF
629       END IF
630       Stop_bin=Start_bin(P)+Num_bins(P)-1
631     NEXT P
632     !
633     !now draw axis, background  and grid for each plot
634     FOR P=1 TO Total_num_plots
635       IF FNUser_key_press THEN SUBEXIT
636       CALL Plot_set_viewp(Total_num_plots,P,X_label_length,Y_units_len,0)
637       CALL Plot_do_axes(Plot_titles$(P),X_units$(P),Y_units$(P),X_min(P),X_max(P),Y_min(P),Y_max(P),X_label_length)
638       !now change viewport to 1 pixel inside axes
639       CALL Plot_set_viewp(Total_num_plots,P,X_label_length,Y_units_len,1)
640       CALL Plot_background
641       IF FNPlot_x_pixel<1/130 THEN !if there is enough resolution
642         CALL Plot_grid(X_min(P),X_max(P),Y_min(P),Y_max(P),Do_log_x(P),Do_log_y(P))
643       END IF
644     NEXT P
645   SUBEND
646   ! PAGE -> 
647   !************************************************************************
648 Disp_plot_data:SUB Disp_plot_data(Buf(*),Head(*))
649    !This subprogram draws the data for the plot.
650    !New trace data is passed in, Trace selection info and
651    !plot scaling info should be left in COM from previous calls to
652    !Disp_put_trace and Disp_plot_set.  Plot titles and axis labels
653    !should be left on the screen by a previous call to Disp_plot_axis.
654    !
655    !For each plot, Plot_make_x and Plot_make_y are called to make
656    !the Plot_array(*) which is passed to Plot_do_data.
657     COM /Disp_num_plots/ Num_live_plots,Num_r_plots
658     COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
659     COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
660     COM /Disp_log/ Do_log_x(*),Do_log_y(*)
661     COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
662     COM /Disp_recall/ Recall_buf(*),Recall_head(*)
663     COM /Disp_recall4/ Plot_to_r_buf(*)
664     COM /Disp_plot_array/ C_plot_array(*),C_p_size
665     COM /Disp_vs_scale/ Sc_start_bin,Sc_stop_bin
666     DIM Message$[100]
667     INTEGER Do_vs,Rf_tr,Sv_tr
668     DIM X_min(1:16),X_max(1:16)
669     DIM Start_bin(1:16),Num_bins(1:16)
670     CSIZE FNPlot_good_csize
671     Plots_done=0
672     MAT Start_bin= Start_bin_c
673     MAT Num_bins= Num_bins_c
674     MAT X_min= X_min_c
675     MAT X_max= X_max_c
676    !There are 2 possibilities for Plot_array(*):
677    !   C_plot_array(*) is used if it is big enough, since Plot_make_x
678    !               is smart enough to not re-compute x if not needed.
679    !   A_plot_array(*) is used if C_plot_array is not big enough.
680    !
681     IF MAX(Num_bins(*))>C_p_size THEN  !need to allocate
682       ALLOCATE A_plot_array(1:MAX(Num_bins(*)),1:2)  !matrix PLOT array
683       Use_a=1
684     ELSE                          !use array in common
685       Use_a=0
686     END IF
687     Total_num_plots=Num_live_plots+Num_r_plots
688     ALLOCATE D_plot_array(1:MAX(Num_bins(*)),1:2)
689     GOSUB Do_data
690     IF (Num_r_plots>0) AND NOT R_plots_done THEN 
691       GOSUB Do_recall_data
692       R_plots_done=1
693     END IF
694     Plots_done=1
695     DEALLOCATE D_plot_array(*)
696     SUBEXIT
697 Do_data:   !-----------------------------------------------------------
698     FOR P=1 TO Num_live_plots
699       IF FNUser_key_press THEN 
700         !leave early, unless its the marker key
701         IF FNUser_check_key<>6 THEN SUBEXIT
702       END IF
703       IF Do_log_y(P) THEN !y axis is displayed logarithmically
704         IF Head(Plot_to_buf(P),4)<>0 THEN 
705           CALL User_error("Can not do double LOG of Y axis")
706         END IF
707       END IF
708       IF Head(Plot_to_buf(P),2)=0 THEN 
709         CALL User_stop("Data_header Scale factor is zero")
710         Head(Plot_to_buf(P),2)=1
711       END IF
712       Do_vs=(FNDisp_in_ds_h AND (FNDisp_choice(P,3)=3))
713       IF FNDisp_in_ds_h THEN 
714         Start_bin(P)=MAX(Start_bin_c(P),FNDisp_exp_start)
715         Num_bins(P)=MIN(Num_bins_c(P),(FNDisp_exp_stop+1-Start_bin(P)))
716         IF Num_bins(P)<0 THEN Num_bins(P)=Num_bins_c(P)
717         IF NOT Do_vs THEN 
718             ! And now into real world units ...
719           X_min(P)=X_min_c(P)+Start_bin(P)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
720           X_max(P)=X_min_c(P)+(Start_bin(P)+Num_bins(P)-1)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
721           Sc_start_bin=Start_bin(P)
722           Sc_stop_bin=Sc_start_bin+Num_bins(P)-1
723         ELSE
724           Sc_start_bin=Start_bin_c(P)
725           Sc_stop_bin=Sc_start_bin+Num_bins_c(P)-1
726         END IF
727       END IF
728       Stop_bin=Start_bin(P)+Num_bins(P)-1
729       Stop_bin=MIN(Stop_bin,SIZE(Buf,2)-1) ! Just hope nothing changes in DS_H case
730       Stop_bin_c=Start_bin_c(P)+Num_bins_c(P)-1
731       Overload=Head(Plot_to_buf(P),3)
732       Average=Head(Plot_to_buf(P),6)
733       Real_time=Head(Plot_to_buf(P),7)
734       !
735       Message$=""
736       IF Real_time THEN Message$="RT "
737       IF Average THEN Message$=Message$&"Avg "&VAL$(Average)
738       !get plot_array ready before clearing old plot
739       REDIM D_plot_array(Start_bin(P):Stop_bin,1:2)
740       IF Use_a THEN 
741         REDIM A_plot_array(Start_bin(P):Stop_bin,1:2)
742         CALL Plot_make_y(Buf(*),Head(*),A_plot_array(*),Plot_to_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
743         IF Do_vs THEN       ! Put the reference Inupt in X vector
744           Scaleor=(Stop_bin_c-Start_bin_c(P)+1)/(Scale_factor*FNDisp_vs_xmag)
745           Move_bins=FNDisp_vs_xmin/FNDisp_vs_xmag*(Stop_bin_c-Start_bin_c(P)+1)
746           FOR X=Start_bin(P) TO Stop_bin
747             A_plot_array(X,1)=A_plot_array(X,2)*Scaleor-Move_bins
748           NEXT X
749           CALL Plot_make_y(Buf(*),Head(*),A_plot_array(*),FNDisp_choice(P,1),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
750         ELSE
751           CALL Plot_make_x(A_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
752         END IF
753       ELSE
754         REDIM C_plot_array(Start_bin(P):Stop_bin,1:2)
755         CALL Plot_make_y(Buf(*),Head(*),C_plot_array(*),Plot_to_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
756         IF Do_vs THEN       ! Put the reference Inupt in X vector
757           Scaleor=(Stop_bin_c-Start_bin_c(P)+1)/(Scale_factor*FNDisp_vs_xmag)
758           Move_bins=FNDisp_vs_xmin/FNDisp_vs_xmag*(Stop_bin_c-Start_bin_c(P)+1)
759           FOR X=Start_bin(P) TO Stop_bin
760             C_plot_array(X,1)=C_plot_array(X,2)*Scaleor-Move_bins
761           NEXT X
762           CALL Plot_make_y(Buf(*),Head(*),C_plot_array(*),FNDisp_choice(P,1),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
763         ELSE
764           CALL Plot_make_x(C_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
765         END IF
766       END IF
767       !
768       !clear old plot
769       CALL Plot_set_viewp(Total_num_plots,P,0,Y_units_len,1)
770       CALL Plot_background
771       IF FNPlot_x_pixel<1/130 THEN !if there is enough resolution
772         CALL Plot_grid(X_min(P),X_max(P),Y_min(P),Y_max(P),Do_log_x(P),Do_log_y(P))
773       END IF
774       !
775       !plot new data
776       Rf_tr=0       ! This is not a reference trace
777       Sv_tr=0       ! this is a live trace (not "saved")
778       Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
779             IF Dummy<>0 THEN Message$="DM "&Message$
780      !  Subtract  activ  .... ?
781       GOSUB Do_subtract
782       Offset_temp=Offset-Dummy*Scale_factor
783      !
784       IF Use_a THEN 
785         CALL Plot_do_data(A_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P))
786       ELSE
787         CALL Plot_do_data(C_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P))
788       END IF
789       !plot 2nd, 3rd and 4th trace if required ...
790       IF FNDisp_in_ds_h THEN 
791       !
792         St_index=FNDisp_plot_sv_tr(P,Rf_tr)
793         IF St_index<>0 THEN      ! Write Save_trace
794           Sv_tr=1
795           Message$="SV "&Message$
796           IF Use_a THEN 
797             CALL Disp_get_sv_tr(A_plot_array(*),Dummy,St_index)
798             CALL Plot_make_x(A_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
799             Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
800             IF Dummy<>0 THEN Message$="DM "&Message$
801             GOSUB Do_subtract
802             Offset_temp=Offset-Dummy*Scale_factor
803             CALL Plot_do_data(A_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P),5)
804           ELSE
805             CALL Disp_get_sv_tr(C_plot_array(*),Dummy,St_index)
806             CALL Plot_make_x(C_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
807             Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
808             IF Dummy<>0 THEN Message$="DM "&Message$
809             GOSUB Do_subtract
810             Offset_temp=Offset-Dummy*Scale_factor
811             CALL Plot_do_data(C_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P),5)
812           END IF
813         END IF   ! Save_tr
814       !
815         IF FNDisp_choice(P,3)=4 THEN  ! Write double
816           Rf_tr=1
817           Sv_tr=0
818           IF Use_a THEN 
819             CALL Plot_make_y(Buf(*),Head(*),A_plot_array(*),1,Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
820             CALL Plot_make_x(A_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
821             Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
822             IF Dummy<>0 THEN Message$="DM "&Message$
823             GOSUB Do_subtract
824             Offset_temp=Offset-Dummy*Scale_factor
825             CALL Plot_do_data(A_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P),6)
826           ELSE
827             CALL Plot_make_y(Buf(*),Head(*),C_plot_array(*),1,Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
828             CALL Plot_make_x(C_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
829             Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
830             IF Dummy<>0 THEN Message$="DM "&Message$
831             GOSUB Do_subtract
832             Offset_temp=Offset-Dummy*Scale_factor
833             CALL Plot_do_data(C_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P),6)
834           END IF
835           St_index=FNDisp_plot_sv_tr(P,1)
836           IF St_index<>0 THEN    ! Write Save_trace for double
837             Sv_tr=1
838             Message$="SV "&Message$
839             IF Use_a THEN 
840               CALL Disp_get_sv_tr(A_plot_array(*),Dummy,St_index)
841               CALL Plot_make_x(A_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
842               Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
843               IF Dummy<>0 THEN Message$="DM "&Message$
844               GOSUB Do_subtract
845               Offset_temp=Offset-Dummy*Scale_factor
846               CALL Plot_do_data(A_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P),4)
847             ELSE
848               CALL Disp_get_sv_tr(C_plot_array(*),Dummy,St_index)
849               CALL Plot_make_x(C_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
850               Dummy=FNDisp_data_move(P,Rf_tr,Sv_tr)
851               GOSUB Do_subtract
852               Offset_temp=Offset-Dummy*Scale_factor
853               CALL Plot_do_data(C_plot_array(*),Overload,Message$,Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P),4)
854             END IF
855           END IF ! Save_tr for double
856         END IF   ! Double
857       !
858       END IF     ! In_ds_h
859     NEXT P
860     RETURN 
861 Do_subtract:    !-----------------------------------------------------------------
862     MAT D_plot_array= (0)
863     IF FNDisp_get_sub(P,Rf_tr,Sv_tr) THEN 
864       Message$="SUB "&Message$
865       IF NOT Sv_tr THEN    ! GET THE SAVED TRACE
866         St_index=FNDisp_plot_sv_tr(P,Rf_tr)
867         IF St_index<>0 THEN 
868           Disp_get_sv_tr(D_plot_array(*),Num_of_bins,St_index)
869         END IF
870       ELSE          ! GET LIVE TRACE
871         IF Rf_tr THEN 
872           Choice_num=2     ! GET THE REFERENCE LIVE TRACE
873         ELSE
874           Choice_num=1
875         END IF
876         CALL Plot_make_y(Buf(*),Head(*),D_plot_array(*),FNDisp_choice(P,Choice_num),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
877       END IF
878      !
879       FOR K=Start_bin(P) TO Stop_bin
880         IF Use_a THEN 
881           A_plot_array(K,2)=A_plot_array(K,2)-D_plot_array(K,2)
882         ELSE
883           C_plot_array(K,2)=C_plot_array(K,2)-D_plot_array(K,2)
884         END IF
885       NEXT K
886     END IF
887     RETURN 
888 Do_recall_data:   !-----------------------------------------------------------
889     FOR P=Num_live_plots+1 TO Num_live_plots+Num_r_plots
890       IF FNUser_key_press THEN 
891         !leave early, unless its the marker key
892         IF FNUser_check_key<>6 THEN SUBEXIT
893       END IF
894       Stop_bin=Start_bin(P)+Num_bins(P)-1
895       Overload=Recall_head(Plot_to_r_buf(P),3)
896       !get plot_array ready before clearing old plot
897       IF Use_a THEN 
898         REDIM A_plot_array(Start_bin(P):Stop_bin,1:2)
899         CALL Plot_make_y(Recall_buf(*),Recall_head(*),A_plot_array(*),Plot_to_r_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
900         CALL Plot_make_x(A_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
901       ELSE
902         REDIM C_plot_array(Start_bin(P):Stop_bin,1:2)
903         CALL Plot_make_y(Recall_buf(*),Recall_head(*),C_plot_array(*),Plot_to_r_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
904         CALL Plot_make_x(C_plot_array(*),Do_log_x(P),X_min(P),X_max(P))
905       END IF
906       !
907       !clear old plot
908       CALL Plot_set_viewp(Total_num_plots,P,0,Y_units_len,1)
909       CALL Plot_background
910       IF FNPlot_x_pixel<1/130 THEN !if there is enough resolution
911         CALL Plot_grid(X_min(P),X_max(P),Y_min(P),Y_max(P),Do_log_x(P),Do_log_y(P))
912       END IF
913       !
914       !plot new data
915       IF Use_a THEN 
916         CALL Plot_do_data(A_plot_array(*),Overload,"Recalled",Y_min(P),Y_max(P),Offset,Scale_factor,Do_log_y(P))
917       ELSE
918         CALL Plot_do_data(C_plot_array(*),Overload,"Recalled",Y_min(P),Y_max(P),Offset,Scale_factor,Do_log_y(P))
919       END IF
920     NEXT P
921     RETURN 
922   SUBEND
923   ! PAGE -> 
924   !************************************************************************
925 Disp_do_mkr:SUB Disp_do_mkr(Buf(*),Head(*),Redraw)
926     !This subprogram handles the marker.  It Does not return
927     !until an unknown softkey is pressed.  It sets up softkeys to do
928     !marker functions and store traces in disc files.
929     COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
930     COM /Disp_units/ X_units$(*),Y_units$(*)
931     COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
932     COM /Disp_log/ Do_log_x(*),Do_log_y(*)
933     COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
934     COM /Disp_recall/ Recall_buf(*),Recall_head(*)
935     COM /Disp_recall4/ Plot_to_r_buf(*)
936     COM /Disp_mkr/ Mkr_plot,INTEGER Saved_tr,INTEGER Reference_tr
937     COM /Disp_num_plots/ Num_live_plots,Num_r_plots
938     !
939     DIM X_min(1:16),X_max(1:16)
940     DIM Start_bin(1:16),Num_bins(1:16)
941     INTEGER In_vs
942     !
943     MAT Start_bin= Start_bin_c
944     MAT Num_bins= Num_bins_c
945     MAT X_min= X_min_c
946     MAT X_max= X_max_c
947     !
948     Total_num_plots=Num_live_plots+Num_r_plots
949     IF Redraw THEN CALL Disp_plot_axis
950     IF Redraw OR NOT Plots_done THEN CALL Disp_plot_data(Buf(*),Head(*))
951     ALLOCATE Plot_array(1:MAX(Num_bins(*),SIZE(Recall_buf,2)),1:2)  !matrix PLOT array
952     IF FNUser_key_press THEN SUBEXIT
953     ON KEY 1 LABEL FNUser_keylabel$("Marker to X") CALL User_key1isr
954     ON KEY 2 LABEL FNUser_keylabel$("Marker to Min") CALL User_key2isr
955     ON KEY 3 LABEL FNUser_keylabel$("Marker to Max") CALL User_key3isr
956     ON KEY 4 LABEL FNUser_keylabel$("Store Trace") CALL User_key4isr
957     ON KEY 5 LABEL FNUser_keylabel$("EXPAND") CALL User_key5isr
958     ! 6 will be "MAIN"
959     ON KEY 7 LABEL FNUser_keylabel$("Previous Trace") CALL User_key7isr
960     ON KEY 8 LABEL FNUser_keylabel$("Next Trace") CALL User_key8isr
961     Done=0
962     GOSUB New_mkr_plot
963     REPEAT
964       CALL Plot_set_viewp(Total_num_plots,P,0,Y_units_len,1)
965       CALL Plot_do_mkr(Plot_array(*),X_units$(P),Y_units$(P),X_min(P),X_max(P),Y_min(P),Y_max(P),Offset,Scale_factor,Do_log_y(P))
966       SELECT FNUser_check_key
967       CASE 1     !move marker
968         Dummy=FNUser_get_key      !to clear the key
969         Plot_move_mkr(Plot_array(*),X_units$(P),X_min(P),X_max(P),"X")
970       CASE 2   !move marker to min
971         Dummy=FNUser_get_key      !to clear the key
972         Plot_move_mkr(Plot_array(*),X_units$(P),X_min(P),X_max(P),"MIN")
973       CASE 3     !move marker to max
974         Dummy=FNUser_get_key      !to clear the key
975         Plot_move_mkr(Plot_array(*),X_units$(P),X_min(P),X_max(P),"MAX")
976       CASE 4     !store
977         Dummy=FNUser_get_key      !to clear the key
978         CALL Disp_store_tr(Plot_array(*),P,Overload,Offset,Scale_factor)
979       CASE 5     !EXPAND
980         Dummy=FNUser_get_key      !to clear the key
981         CALL Disp_exp_tr(Buf(*),Head(*))
982         Dummy=FNUser_get_key      !to clear the key
983       CASE 7    !prev
984         Dummy=FNUser_get_key      !to clear the key
985         REPEAT
986           Mkr_plot=Mkr_plot-1
987           IF Mkr_plot=0 THEN Mkr_plot=Total_num_plots
988           IF FNDisp_in_ds_h THEN 
989             In_vs=(FNDisp_choice(Mkr_plot,3)=3)
990           ELSE
991             In_vs=0
992           END IF
993         UNTIL NOT In_vs
994         GOSUB New_mkr_plot
995       CASE 8    !next
996         Dummy=FNUser_get_key
997         REPEAT
998           Mkr_plot=Mkr_plot+1
999           IF Mkr_plot>Total_num_plots THEN Mkr_plot=1
1000          In_vs=(FNDisp_in_ds_h AND (FNDisp_choice(Mkr_plot,3)=3))
1001          IF FNDisp_in_ds_h THEN 
1002            In_vs=(FNDisp_choice(Mkr_plot,3)=3)
1003          ELSE
1004            In_vs=0
1005          END IF
1006        UNTIL NOT In_vs
1007        GOSUB New_mkr_plot
1008      CASE ELSE
1009        Done=1
1010      END SELECT
1011    UNTIL Done
1012    SUBEXIT
1013 New_mkr_plot:    !----------------------------------------------------
1014    Mkr_plot=MAX(1,MIN(Total_num_plots,Mkr_plot))
1015    P=Mkr_plot      ! Use shorter variable name
1016    Do_vs=(FNDisp_in_ds_h AND (FNDisp_choice(P,3)=3))
1017    IF FNDisp_in_ds_h THEN 
1018      Start_bin(P)=MAX(Start_bin_c(P),FNDisp_exp_start)
1019      Num_bins(P)=MIN(Num_bins_c(P),(FNDisp_exp_stop+1-Start_bin(P)))
1020      IF Num_bins(P)<0 THEN Num_bins(P)=Num_bins_c(P)
1021      IF NOT Do_vs THEN 
1022            ! And now into real world units ...
1023        X_min(P)=X_min_c(P)+Start_bin(P)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
1024        X_max(P)=X_min_c(P)+(Start_bin(P)+Num_bins(P)-1)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
1025      END IF
1026    END IF
1027    Stop_bin=Start_bin(P)+Num_bins(P)-1
1028    IF P>Num_live_plots THEN    !recalled trace, get from Recall_buf(*)
1029      REDIM Plot_array(Start_bin(P):Stop_bin,1:2)
1030      CALL Plot_make_y(Recall_buf(*),Recall_head(*),Plot_array(*),Plot_to_r_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
1031      CALL Plot_make_x(Plot_array(*),Do_log_x(P),X_min(P),X_max(P))
1032      Overload=Recall_head(Plot_to_r_buf(P),3)
1033    ELSE                    !not recalled, get Plot_array from Buf(*)
1034      Stop_bin=MIN(Stop_bin,SIZE(Buf,2)-1)
1035      REDIM Plot_array(Start_bin(P):Stop_bin,1:2)
1036      CALL Plot_make_y(Buf(*),Head(*),Plot_array(*),Plot_to_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
1037      CALL Plot_make_x(Plot_array(*),Do_log_x(P),X_min(P),X_max(P))
1038      Overload=Head(Plot_to_buf(P),3)
1039    END IF
1040    RETURN 
1041  SUBEND
1042  ! PAGE -> 
1043  !************************************************************************
1044 Disp_choice:DEF FNDisp_choice(Plot_num,Category_num)
1045  !This function returns the current selection of an application
1046  !dependent column of the display spread sheet.  It returns an index
1047  !into the array Choices$(*), given the plot number and category number.
1048    COM /Disp_choice/ Plot_choice(*)
1049    RETURN Plot_choice(Plot_num,Category_num)
1050  FNEND
1051  !************************************************************************
1052 Disp_num_plots:DEF FNDisp_num_plots
1053    !This function returns the number of plots, not counting recalled traces.
1054    COM /Disp_num_plots/ Num_live_plots,Num_r_plots
1055    RETURN Num_live_plots
1056  FNEND
1057  ! PAGE -> 
1058  !************************************************************************
1059 Disp_update_com:SUB Disp_update_com
1060  !This subprogram is called before exiting Disp_spread to translate
1061  !from spreadsheet form to plot form.
1062    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1063    COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
1064    COM /Disp_spread4/ Choices$(*),Num_choices(*)
1065    COM /Disp_choice/ Plot_choice(*)
1066    COM /Disp_recall4/ Plot_to_r_buf(1:16)
1067    ALLOCATE Plot_titles$(1:16)[45],Y_max$(1:16)[20],Y_min$(1:16)[20]
1068    DIM Title$[255],Temp$[40]
1069    !copy Box$ info into  arrays for passing to Disp_put_traces
1070    Max_row=SIZE(Box$,2)
1071    Num_live_plots=0
1072    Num_r_plots=0
1073    FOR R=2 TO Num_live_rows+1        !for each live row, check for active t
race
1074      IF Box$(Active_col,R)="*" THEN 
1075        GOSUB Do_the_row
1076      END IF
1077    NEXT R
1078    IF Num_live_plots<1 THEN 
1079      R=2
1080      Box$(Active_col,R)="*"    !make first one active
1081      GOSUB Do_the_row
1082      CALL User_error("You must have at least one active trace")
1083    END IF
1084    FOR R=Num_live_rows+2 TO Max_row        !for each recall row, check for active trace
1085      IF Box$(Active_col,R)="*" THEN 
1086        GOSUB Do_the_row
1087      END IF
1088    NEXT R
1089    CALL Disp_put_traces(Num_live_plots,Num_r_plots,Y_max$(*),Y_min$(*))
1090    CALL Disp_put_titles(Plot_titles$(*))
1091    SUBEXIT
1092 Do_the_row:  !-------------------------------------------------------
1093    !processes row R  of the spread sheet data
1094    IF Num_live_plots+Num_r_plots<16 THEN 
1095      IF R<=Num_live_rows+1 THEN 
1096        Num_live_plots=Num_live_plots+1
1097      ELSE        !recalled plots
1098        Num_r_plots=Num_r_plots+1
1099      END IF
1100      Plot_num=Num_live_plots+Num_r_plots
1101      !
1102      !built title out of application dependent cols
1103      Title$=""
1104      FOR C=Active_col+1 TO Y_min_col-1
1105        Title$=Title$&Box$(C,R)&" "
1106      NEXT C
1107      Title$=TRIM$(Title$)
1108      IF LEN(Title$)<45 THEN 
1109        Plot_titles$(Plot_num)=Title$
1110      ELSE
1111        Plot_titles$(Plot_num)=Title$[1,45]
1112      END IF
1113      !
1114      !check for swapped min/max
1115      IF Box$(Y_min_col,R)<>"Default" AND Box$(Y_max_col,R)<>"Default" THEN 
1116        IF VAL(Box$(Y_min_col,R))>VAL(Box$(Y_max_col,R)) THEN     !min>max ?
1117          Temp$=Box$(Y_min_col,R)
1118          Box$(Y_min_col,R)=Box$(Y_max_col,R)
1119          Box$(Y_max_col,R)=Temp$
1120        END IF
1121      END IF
1122      Y_min$(Plot_num)=Box$(Y_min_col,R)
1123      Y_max$(Plot_num)=Box$(Y_max_col,R)
1124      !
1125      IF R<=Num_live_rows+1 THEN              !live trace
1126        !encode application dependent stuff
1127        FOR C=Active_col+1 TO Y_min_col-1!for each appl dependent col
1128          CALL Lib_match2(Box$(C,R),Choices$(*),C,Found,Choice_num)
1129          IF Found THEN 
1130            Plot_choice(Plot_num,C-Active_col)=Choice_num
1131          ELSE
1132            CALL User_stop("match failed")
1133          END IF
1134        NEXT C
1135      ELSE                                    !recalled trace
1136        Plot_to_r_buf(Plot_num)=R-Num_live_rows-1
1137      END IF
1138    END IF     !plots<=16
1139    RETURN 
1140  SUBEND
1141  ! PAGE -> 
1142  !************************************************************************
1143 Disp_reset:SUB Disp_reset
1144  !This subprogram resets the display spread sheet to its initial state.
1145  !The initial state defines up to 16 plots unique plots using all
1146  !combinations of Choices$() for each application dependent column.
1147  !Y axis scaling is set to "Default", and several plots are set active.
1148  !
1149    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1150    COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
1151    COM /Disp_spread4/ Choices$(*),Num_choices(*)
1152    INTEGER A(0:5),In_ds_h,More
1153    GESCAPE CRT,3;A(*)   !get CRT pixel size in A(*)
1154    IF A(2)>1000 THEN    !if CRT is high resolution then
1155      Max_active=9       !display up to 9 traces as default
1156    ELSE
1157      Max_active=4
1158    END IF
1159  !
1160    IF FNDisp_in_ds_h THEN Max_active=4
1161    MAT Box$= ("")
1162    Max_row=SIZE(Box$,2)
1163    !
1164    !set up "All" row
1165    Box$(1,1)="All"
1166    ALLOCATE Current_choice(3:3+Num_categories)
1167    !Current_choice has an element for each column (category) to be varied.
1168    !The values are the choice numbers and are incremented in a ripple
1169    !counter like fashion.
1170    MAT Current_choice= (1)  !first row is first choice for all categories.
1171    FOR R=2 TO Num_live_rows+1
1172      Box$(1,R)=VAL$(R-1)
1173      IF (R-1)<=Max_active THEN Box$(Active_col,R)="*"
1174      FOR C=3 TO 2+Num_categories
1175        Box$(C,R)=Choices$(C,Current_choice(C))
1176      NEXT C
1177      Box$(Y_min_col,R)="Default"
1178      Box$(Y_max_col,R)="Default"
1179      !
1180      !increment current_choice array
1181      REPEAT
1182        Current_choice(3)=Current_choice(3)+1!increment choice in left most col
1183        FOR C=3 TO 2+Num_categories          !check each col for wrap
1184          IF Current_choice(C)>Num_choices(C) THEN !need to "carry"
1185            Current_choice(C)=1
1186            Current_choice(C+1)=Current_choice(C+1)+1
1187          END IF
1188        NEXT C
1189        IF FNDisp_in_ds_h THEN 
1190          More=(Current_choice(5)<>1) AND (Current_choice(4)=Current_choice(3))
1191        ELSE
1192          More=0
1193        END IF
1194      UNTIL NOT More
1195    !
1196    NEXT R
1197    FOR R=Num_live_rows+2 TO Max_row
1198      Box$(1,R)="R "&VAL$(R-Num_live_rows-1)
1199      Box$(Active_col,R)=""
1200      Box$(Y_min_col,R)="Default"
1201      Box$(Y_max_col,R)="Default"
1202      Box$(Active_col+1,R)="Recall trace "&VAL$(R-Num_live_rows-1)
1203    NEXT R
1204  SUBEND
1205  ! PAGE -> 
1206  !************************************************************************
1207 Disp_save:SUB Disp_save(@File,Ok)
1208  !This subprogram saves the state of the display spreadsheet
1209  !into file @File.
1210  !
1211    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1212    !
1213    !
1214    File_format_rev=2621
1215    OUTPUT @File;File_format_rev
1216    !
1217    CALL File_save_s(@File,Box$(*))
1218    Ok=1
1219    !
1220  SUBEND
1221  !************************************************************************
1222 Disp_load:SUB Disp_load(@File,Ok)
1223  !This subprogram loads the state of the display spreadsheet
1224  !from file @File.  Disp_put_traces must be called by the application
1225  !to update other items.
1226  !
1227    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1228    COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
1229    !
1230    !
1231    ENTER @File;File_format_rev
1232    SELECT File_format_rev
1233    CASE 2621
1234      CALL File_load_s(@File,Box$(*))
1235    !
1236    CASE ELSE  !unknown rev
1237      CALL User_error("ERROR Incompatible display file format in Disp_load.")
1238      Ok=0
1239      SUBEXIT
1240    END SELECT
1241    !
1242    !Turn off recall traces
1243    FOR R=2 TO SIZE(Box$,2)
1244      IF POS(Box$(1,R),"R") THEN 
1245        Box$(Active_col,R)=""
1246        Box$(Active_col+1,R)="Recall trace "&VAL$(R-Num_live_rows-1)
1247      END IF
1248    NEXT R
1249    !
1250    CALL Disp_update_com
1251    Ok=1
1252    !
1253  SUBEND
1254  ! PAGE -> 
1255  !************************************************************************
1256 Disp_store_tr:SUB Disp_store_tr(Plot_array(*),P,Overload,Offset,Scale_factor)
1257  !This subprogram outputs the trace to an ASCII file.  The format is
1258  !HP's implementation of the Neutral File format.
1259  !---------------------------------------------------------------------
1260    COM /Disp_titles/ Plot_titles$(*)
1261    COM /Disp_units/ X_units$(*),Y_units$(*)
1262    COM /Disp_window/ X_min(*),X_max(*),Y_min(*),Y_max(*)
1263    COM /Disp_log/ Do_log_x(*),Do_log_y(*)
1264    DIM File_name$[160]
1265    File_size=(12*40+SIZE(Plot_array,1)*25.0)/256
1266    LINPUT "Name of file for trace store ?",File_name$
1267    IF TRIM$(File_name$)="" THEN SUBEXIT
1268    ON ERROR GOTO Create_failed
1269    CREATE ASCII File_name$,File_size
1270    OFF ERROR 
1271    GOTO Created
1272 Create_failed:OFF ERROR 
1273    IF ERRN=54 THEN !duplicate file name
1274      IF NOT FNUser_yes("File already exists. OK to overwrite ? (Y or N)",1) THEN 
1275        CALL User_error("Trace Store Aborted.")
1276        SUBEXIT
1277      END IF
1278    ELSE
1279      CALL User_error("Store failed: "&ERRM$)
1280      SUBEXIT
1281    END IF
1282    ON ERROR GOTO Store_failed
1283    PURGE File_name$
1284    CREATE ASCII File_name$,File_size
1285 Created: !
1286    ON ERROR GOTO Store_failed
1287    ASSIGN @File TO File_name$
1288    GOSUB Write_heading
1289    GOSUB Write_data
1290    DISP "Store done"
1291    WAIT 3
1292    SUBEXIT
1293 Write_heading:   !-----------------------------------------------
1294    DISP "Storing ";Plot_titles$(P);" in file ";File_name$;" ."
1295    OUTPUT @File;"SPAMHDR("
1296    OUTPUT @File;"  XUNI:"&FNDisp_zap$(X_units$(P))&","
1297    OUTPUT @File;"  YUNI:"&FNDisp_zap$(Y_units$(P))&","
1298    OUTPUT @File;"  XMIN:"&VAL$(X_min(P))&","
1299    OUTPUT @File;"  XMAX:"&VAL$(X_max(P))&","
1300    OUTPUT @File;"  XLOG:"&VAL$(Do_log_x(P))&","
1301    OUTPUT @File;"  YLOG:"&VAL$(Do_log_y(P))&","
1302    OUTPUT @File;"  YDMI:"&VAL$(Y_min(P))&","
1303    OUTPUT @File;"  YDMA:"&VAL$(Y_max(P))&","
1304    OUTPUT @File;");"
1305    RETURN 
1306 Write_data:      !-----------------------------------------------
1307    DISP "Storing ";Plot_titles$(P);" in file ";File_name$;" .."
1308    INTEGER I,N
1309    N=SIZE(Plot_array,1)
1310    ALLOCATE Y(1:N),Y$(1:N)[21],Mask(1:2)
1311    Mask(1)=0  !ignore X of x,y point
1312    Mask(2)=1  !use Y
1313    MAT Y= Plot_array*Mask
1314    MAT Y= Y-(Offset)
1315    MAT Y= Y/(Scale_factor)
1316    !now do format to string array to avoid SRM limitations with USING.
1317    IF Do_log_y(P) THEN !need to un-log
1318      FOR I=1 TO N-1
1319        OUTPUT Y$(I) USING "#,MD.12DESZZZ,A";10^(Y(I)),","
1320      NEXT I
1321    ELSE
1322      FOR I=1 TO N-1
1323        OUTPUT Y$(I) USING "#,MD.12DESZZZ,A";Y(I),","
1324      NEXT I
1325    END IF
1326    OUTPUT Y$(N) USING "#,MD.12DESZZZ,A";Y(N)," "
1327    DISP "Storing ";Plot_titles$(P);" in file ";File_name$;" ..."
1328    OUTPUT @File;"DATAHDR("
1329    OUTPUT @File;"  LBL:"&FNDisp_zap$(Plot_titles$(P))&","
1330    OUTPUT @File;"  DATE:"&DATE$(TIMEDATE)&","
1331    OUTPUT @File;"  OVLD:"&VAL$(Overload)&","
1332    OUTPUT @File;"  DATA#ASCI,20,"&VAL$(SIZE(Plot_array,1))&":"
1333    OUTPUT @File;Y$(*)
1334    OUTPUT @File;");"
1335    RETURN 
1336 Store_failed:    !-------------------------------------------------
1337    CALL User_error("Store failed: "&ERRM$)
1338    WAIT 1
1339  SUBEND
1340  ! PAGE -> 
1341  !************************************************************************
1342 Disp_recall_tr:SUB Disp_recall_tr(R_buf_num,R_title$,Ok)
1343  !This subprogram reads a trace from a file.  The format is
1344  !HP's implementation of the Neutral File format.  The trace data is
1345  !stored in a buffer of the Recall_buf(*) array.
1346  !---------------------------------------------------------------------
1347    COM /Disp_recall/ Recall_buf(*),Recall_head(*)
1348    COM /Disp_recall1/ R_x_units$(*),R_y_units$(*),R_num_bins(*)
1349    COM /Disp_recall2/ R_x_min(*),R_x_max(*),R_y_def_min(*),R_y_def_max(*)
1350    COM /Disp_recall3/ R_do_log_x(*),R_do_log_y(*)
1351    !
1352    DIM File_name$[160],Line$[256]
1353    Ok=1
1354    Got_data=0
1355    ON ERROR GOTO Recall_failed
1356    LINPUT "Name of file for trace recall ?",File_name$
1357    IF TRIM$(File_name$)="" THEN 
1358      Ok=0
1359      SUBEXIT
1360    END IF
1361    ASSIGN @File TO File_name$
1362    GOSUB Set_defaults
1363    ON END @File GOTO Eof
1364    GOSUB Read_file
1365 Eof:DISP 
1366    IF NOT Got_data THEN Ok=0
1367    SUBEXIT
1368 Set_defaults:   !-----------------------------------------------
1369    R_x_units$(R_buf_num)=""
1370    R_y_units$(R_buf_num)=" "
1371    R_x_min(R_buf_num)=0
1372    R_x_max(R_buf_num)=1
1373    R_y_def_min(R_buf_num)=-1
1374    R_y_def_max(R_buf_num)=1
1375    R_do_log_x(R_buf_num)=0
1376    R_do_log_y(R_buf_num)=0
1377    R_num_bins(R_buf_num)=0
1378    R_title$="Recall trace "&VAL$(R_buf_num)
1379    Recall_head(R_buf_num,1)=0       !offset
1380    Recall_head(R_buf_num,2)=1       !scale factor
1381    Recall_head(R_buf_num,3)=0       !overload
1382    RETURN 
1383 Read_file:      !-----------------------------------------------
1384    DISP "Recalling from file ";File_name$;" ."
1385    WHILE Ok
1386      ENTER @File;Line$
1387      Line$=TRIM$(Line$)
1388      IF LEN(Line$)>5 THEN 
1389        IF Line$[LEN(Line$)]="," THEN Line$=Line$[1,LEN(Line$)-1]!delete ,
1390        SELECT UPC$(Line$[1,4])
1391        CASE "XUNI"
1392          R_x_units$(R_buf_num)=Line$[6]
1393        CASE "YUNI"
1394          R_y_units$(R_buf_num)=Line$[6]
1395        CASE "XMIN"
1396          R_x_min(R_buf_num)=VAL(Line$[6])
1397        CASE "XMAX"
1398          R_x_max(R_buf_num)=VAL(Line$[6])
1399        CASE "XLOG"
1400          R_do_log_x(R_buf_num)=VAL(Line$[6])
1401        CASE "YLOG"
1402          R_do_log_y(R_buf_num)=VAL(Line$[6])
1403        CASE "YDMI"
1404          R_y_def_min(R_buf_num)=VAL(Line$[6])
1405        CASE "YDMA"
1406          R_y_def_max(R_buf_num)=VAL(Line$[6])
1407        CASE "LBL:"
1408          R_title$=Line$[5]
1409        CASE "OVLD"
1410          Recall_head(R_buf_num,3)=VAL(Line$[6])
1411        CASE "DATA"
1412          IF POS(Line$,"DATA#ASCI") THEN GOSUB Read_data
1413        END SELECT
1414      END IF
1415    END WHILE
1416    RETURN 
1417 Read_data:      !-----------------------------------------------
1418    !comes here when Line$ is "DATA#ASCI,<bytes per items>,<num items>:"
1419    INTEGER I,N
1420    Line$=Line$[11]  !delete "DATA#ASCI,"
1421    ENTER Line$;Dummy,N
1422    R_num_bins(R_buf_num)=N
1423    IF N>SIZE(Recall_buf,2) THEN 
1424      CALL User_error("Recall failed:  Recall_buf(*) array is too small.")
1425      !size of array is defined in SUB Disp_disp
1426      Ok=0
1427    ELSE
1428      ALLOCATE Y(1:N)
1429      DISP "Recalling from file ";File_name$;" .."
1430      ENTER @File;Y(*)
1431      DISP "Recalling from file ";File_name$;" ..."
1432      FOR I=1 TO N
1433        Recall_buf(R_buf_num,I)=Y(I)
1434      NEXT I
1435      Got_data=1
1436    END IF
1437    RETURN 
1438 Recall_failed:    !-------------------------------------------------
1439    Ok=0
1440    CALL User_error("Recall failed: "&ERRM$)
1441    WAIT 1
1442  SUBEND
1443  ! PAGE -> 
1444  !************************************************************************
1445 Disp_zap:DEF FNDisp_zap$(S$)
1446   !This function changes illegal characters to spaces.
1447    DIM R$[256]
1448    INTEGER I
1449    R$=""
1450    IF LEN(S$)>0 THEN 
1451      FOR I=1 TO LEN(S$)
1452        SELECT NUM(S$[I;1])
1453        CASE <32,>125,35,40,41,44,58,59!   < ,>},#,(,),,,:,;
1454          R$=R$&" "
1455        CASE ELSE                     !ok
1456          R$=R$&S$[I;1]
1457        END SELECT
1458      NEXT I
1459    END IF
1460    RETURN R$
1461  FNEND
1462  ! PAGE -> 
1463  !************************************************************************
1464 Disp_put_traces:SUB Disp_put_traces(Num_live_plots,Num_r_plots,Y_max$(*),Y_min$(*))
1465    !This subprogram is called from Disp_spread or a non-interactive program to
1466    !define the plots.
1467    COM /Disp_y/ Y_max_c$(*),Y_min_c$(*)
1468    COM /Disp_num_plots/ Num_live_plotsc,Num_r_plots_c
1469    COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
1470    Num_live_plotsc=Num_live_plots
1471    Num_r_plots_c=Num_r_plots
1472    MAT Y_max_c$= Y_max$
1473    MAT Y_min_c$= Y_min$
1474  SUBEND
1475  ! PAGE -> 
1476  !************************************************************************
1477 Disp_put_titles:SUB Disp_put_titles(Plot_titles$(*))
1478    !This subprogram is called from Disp_spread or a non-interactive program to
1479    !define the plot titles.
1480    COM /Disp_titles/ Plot_titles_c$(*)
1481    FOR I=1 TO SIZE(Plot_titles$,1)
1482      IF LEN(Plot_titles$(I))>45 THEN 
1483        Plot_titles_c$(I)=Plot_titles$(I)[1,45]
1484      ELSE
1485        Plot_titles_c$(I)=Plot_titles$(I)
1486      END IF
1487    NEXT I
1488  SUBEND
1489  ! PAGE -> 
1490  !************************************************************************
1491 Disp_log_set:SUB Disp_log_set(Do_log_x(*),OPTIONAL Do_log_y(*))
1492    !This subprogram may be called to change plot axis to logarithmic.
1493    !It must be called
1494    !after Disp_plot_set since Disp_plot_set resets
1495    !all plots to linear.
1496    !Setting Do_log_y produces the same trace shape as setting
1497    !Data_header(*,4)=1.0  However, Do_log_y produces a log grid and
1498    !the marker is not logged.
1499!       Do_log_x(1:num_plots) Array of flags, one for each plot.
1500!                      0= linear X axis,  non-zero = log X axis.
1501!       Do_log_y(1:num_plots) Array of flags, one for each plot.
1502    !
1503    COM /Disp_num_plots/ Num_live_plots,Num_r_plots
1504    COM /Disp_buf/ Plot_to_buf(*),Start_bin(*),Num_bins(*)
1505    COM /Disp_window/ X_min(*),X_max(*),Y_min(*),Y_max(*)
1506    COM /Disp_log/ Do_log_x_c(*),Do_log_y_c(*)
1507    !
1508    FOR P=1 TO Num_live_plots
1509      Do_log_x_c(P)=0
1510      IF Do_log_x(P) THEN 
1511        IF X_max(P)>0 THEN 
1512          IF X_min(P)>0 THEN   !all ok as is
1513            Do_log_x_c(P)=1
1514          ELSE                 !need to change start_bin to avoid negative x
1515            Per_bin_x=(X_max(P)-X_min(P))/(Num_bins(P)-1)
1516            Bins=INT(-X_min(P)/Per_bin_x+1)
1517            Start_bin(P)=Start_bin(P)+Bins
1518            Num_bins(P)=Num_bins(P)-Bins
1519            X_min(P)=X_min(P)+Per_bin_x*Bins
1520            Do_log_x_c(P)=1
1521          END IF
1522        ELSE  !x_max<0
1523          CALL User_error("NOTE: Can't do LOG of negative X-axis")
1524        END IF
1525      END IF
1526    NEXT P
1527    IF NPAR>1 THEN 
1528      FOR P=1 TO Num_live_plots
1529        Do_log_y_c(P)=0
1530        IF Do_log_y(P) THEN 
1531          IF Y_max(P)>0 THEN 
1532            IF Y_min(P)>0 THEN !all ok as is
1533              Do_log_y_c(P)=1
1534            ELSE               !need to change Y_min
1535              Y_min(P)=Y_max(P)/1000
1536              Do_log_y_c(P)=1
1537            END IF
1538          ELSE!x_max<0
1539            CALL User_error("NOTE: Can't do LOG of negative Y-axis")
1540          END IF
1541        END IF
1542      NEXT P
1543    END IF
1544  SUBEND
1545  ! PAGE -> 
1546  !************************************************************************
1547 Disp_reset_y:SUB Disp_reset_y
1548   !This subprogram may be called to reset the Y axis scaling of the
1549   !display spread sheet to "Default" for all the live rows.
1550    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1551    COM /Disp_spread3/ Active_col,Y_max_col,Y_min_col,Num_categories,Num_live_rows,Num_recall_rows
1552    FOR R=2 TO Num_live_rows+1
1553      Box$(Y_max_col,R)="Default"
1554      Box$(Y_min_col,R)="Default"
1555    NEXT R
1556    CALL Disp_update_com
1557  SUBEND
1558  !************************************************************************
1559 Disp_in_ds_h:DEF FNDisp_in_ds_h
1560  !This function returns a logical 1 if the current APPL is DS_H else 0
1561    COM /Disp_spread4/ Choices$(*),Num_choices(*)
1562    IF SIZE(Choices$,1)>2 THEN 
1563      RETURN (Choices$(5,3)="Input vs Input")   ! Who could possibly write this sentence, except DS_H ...?
1564    ELSE
1565      RETURN 0
1566    END IF
1567  FNEND
1568  !************************************************************************
1569 Disp_vs_xmag:DEF FNDisp_vs_xmag
1570  !This function returns the magnitude of X scale for DS_H 'Input vs Input'
1571  ! which is always the same as Y first line i Box$.
1572    IF FNDisp_in_ds_h THEN 
1573      RETURN FNDisp_vs_xmax-FNDisp_vs_xmin
1574    ELSE
1575      RETURN 2.
1576    END IF
1577  FNEND
1578  !************************************************************************
1579 Disp_vs_xmin:DEF FNDisp_vs_xmin
1580   !This function returns the X_min value for 'Input vs Input' in DS_H
1581   ! that is the same as Y_min 1st line in Box$
1582    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1583    IF Box$(6,2)="Default" THEN 
1584      RETURN -1.
1585    ELSE
1586      RETURN VAL(Box$(6,2))
1587    END IF
1588  FNEND
1589  !************************************************************************
1590 Disp_vs_xmax:DEF FNDisp_vs_xmax
1591   !This function returns the X_max value for 'Input vs Input' in DS_H
1592   ! that is the same as Y_max 1st line in Box$
1593    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
1594    IF Box$(7,2)="Default" THEN 
1595      RETURN 1.
1596    ELSE
1597      RETURN VAL(Box$(7,2))
1598    END IF
1599  FNEND
1600  !************************************************************************
1601 Disp_exp_tr:SUB Disp_exp_tr(Buf(*),Head(*))
1602    !This subprogram handles the ...
1603    COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
1604    COM /Disp_units/ X_units$(*),Y_units$(*)
1605    COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
1606    COM /Disp_log/ Do_log_x(*),Do_log_y(*)
1607    COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
1608    COM /Disp_recall/ Recall_buf(*),Recall_head(*)
1609    COM /Disp_recall4/ Plot_to_r_buf(*)
1610    COM /Disp_mkr/ Mkr_plot,INTEGER Saved_tr,INTEGER Reference_tr
1611    COM /Disp_num_plots/ Num_live_plots,Num_r_plots
1612    !
1613    DIM X_min(1:16),X_max(1:16)
1614    DIM Start_bin(1:16),Num_bins(1:16)
1615    !
1616    MAT Start_bin= Start_bin_c
1617    MAT Num_bins= Num_bins_c
1618    MAT X_min= X_min_c
1619    MAT X_max= X_max_c
1620    ALLOCATE Plot_array(1:MAX(Num_bins(*),SIZE(Recall_buf,2)),1:2)  !matrix PLOT array
1621    IF FNUser_key_press THEN SUBEXIT
1622    IF NOT FNDisp_in_ds_h THEN CALL User_error("*** Only for DS_H use ***")
1623    IF NOT FNDisp_in_ds_h THEN SUBEXIT
1624    Total_num_plots=Num_live_plots+Num_r_plots
1625    ON KEY 1 LABEL FNUser_keylabel$("Set Min") CALL User_key1isr
1626    ON KEY 2 LABEL FNUser_keylabel$("MAIN") CALL User_key2isr
1627    ON KEY 3 LABEL FNUser_keylabel$("Set Max") CALL User_key3isr
1628    ON KEY 4 LABEL FNUser_keylabel$("FORGET") CALL User_key4isr
1629    ON KEY 5 LABEL "" CALL Disp_do_naught
1630    ON KEY 6 LABEL "" CALL Disp_do_naught
1631    ON KEY 7 LABEL "" CALL Disp_do_naught
1632    ON KEY 8 LABEL "" CALL Disp_do_naught
1633    Done=0
1634    GOSUB New_mkr_plot
1635    REPEAT
1636      CALL Plot_set_viewp(Total_num_plots,P,0,Y_units_len,1)
1637      Offset_temp=Offset-FNDisp_data_move(P,Reference_tr,Saved_tr)*Scale_factor
1638      CALL Plot_do_mkr(Plot_array(*),X_units$(P),Y_units$(P),X_min(P),X_max(P),Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P))
1639      SELECT FNUser_check_key
1640      CASE 1     ! Set min
1641        Dummy=FNUser_get_key      !to clear the key
1642        Disp_exp_min(P)
1643    ! CASE 2   !MAIN
1644      CASE 3     ! Set max
1645        Dummy=FNUser_get_key      !to clear the key
1646        CALL Disp_exp_max(P)
1647      CASE 4   ! FORGET
1648        Dummy=FNUser_get_key      !to clear the key
1649        CALL Disp_exp_forget(1)
1650        Done=1
1651      CASE ELSE
1652        Done=1
1653      END SELECT
1654    UNTIL Done
1655    ON KEY 1 LABEL FNUser_keylabel$("SAVE") CALL User_key1isr
1656    ON KEY 2 LABEL FNUser_keylabel$("EXPAND") CALL User_key2isr
1657    ON KEY 3 LABEL FNUser_keylabel$("SELECT") CALL User_key3isr
1658    ON KEY 4 LABEL FNUser_keylabel$("RESET CURSOR") CALL User_key4isr
1659    ON KEY 5 LABEL FNUser_keylabel$("AUTO C OFF") CALL User_key5isr
1660    ON KEY 6 LABEL FNUser_keylabel$("MAIN") CALL User_key6isr
1661    ON KEY 7 LABEL FNUser_keylabel$("DATA MOVE") CALL User_key7isr
1662    ON KEY 8 LABEL FNUser_keylabel$("SUBTRACT") CALL User_key8isr
1663    CALL Disp_exp_done
1664    SUBEXIT
1665 New_mkr_plot:    !----------------------------------------------------
1666    Mkr_plot=MAX(1,MIN(Total_num_plots,Mkr_plot))
1667    P=Mkr_plot      !shorter variable name
1668    Do_vs=(FNDisp_in_ds_h AND (FNDisp_choice(P,3)=3))
1669    Start_bin(P)=MAX(Start_bin_c(P),FNDisp_exp_start)
1670    Num_bins(P)=MIN(Num_bins_c(P),(FNDisp_exp_stop+1-Start_bin(P)))
1671    IF Num_bins(P)<0 THEN Num_bins(P)=Num_bins_c(P)
1672    IF NOT Do_vs THEN 
1673            ! And now into real world units ...
1674      X_min(P)=X_min_c(P)+Start_bin(P)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
1675      X_max(P)=X_min_c(P)+(Start_bin(P)+Num_bins(P)-1)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
1676    END IF
1677    Stop_bin=Start_bin(P)+Num_bins(P)-1
1678    IF P>Num_live_plots THEN    !recalled trace, get from Recall_buf(*)
1679      REDIM Plot_array(Start_bin(P):Stop_bin,1:2)
1680      CALL Plot_make_y(Recall_buf(*),Recall_head(*),Plot_array(*),Plot_to_r_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
1681      CALL Plot_make_x(Plot_array(*),Do_log_x(P),X_min(P),X_max(P))
1682      Overload=Recall_head(Plot_to_r_buf(P),3)
1683    ELSE                    !not recalled, get Plot_array from Buf(*)
1684      Stop_bin=MIN(Stop_bin,SIZE(Buf,2)-1)
1685      REDIM Plot_array(Start_bin(P):Stop_bin,1:2)
1686      CALL Plot_make_y(Buf(*),Head(*),Plot_array(*),Plot_to_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
1687      CALL Plot_make_x(Plot_array(*),Do_log_x(P),X_min(P),X_max(P))
1688      Overload=Head(Plot_to_buf(P),3)
1689    END IF
1690    RETURN 
1691  SUBEND
1692 Disp_do_naught:SUB Disp_do_naught
1693   !*********************************************************************
1694   !* This subroutine is self-documenting.
1695   !*********************************************************************
1696    SUBEXIT
1697  SUBEND
1698   !*********************************************************************
1699 Disp_exp_min:SUB Disp_exp_min(Plot_num)
1700    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1701    COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
1702    COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
1703    I=Plot_num                   ! Shorter name ....
1704    IF Start_bin<0 THEN Start_bin=Start_bin_c(I)
1705    IF Stop_bin<0 THEN Stop_bin=Num_bins_c(I)-Start_bin_c(I)-1
1706   !
1707    IF New_plot THEN 
1708      Old_start_bin=Start_bin
1709      Old_stop_bin=Stop_bin
1710    END IF
1711    IF NOT New_plot THEN ! Erase old line
1712      IF FNPlot_use_color THEN 
1713        PEN 7
1714      ELSE
1715        PEN -1
1716      END IF
1717      PLOT Start_bin,Y_min(I)
1718      PLOT Start_bin,Y_max(I)
1719      PENUP
1720    END IF
1721    Start_bin=FNPlot_mkr_bin             ! GET NEW DATA
1722   ! Plot new line
1723    PEN 3
1724    PLOT Start_bin,Y_min(I)
1725    PLOT Start_bin,Y_max(I)
1726    PENUP
1727    New_plot=0
1728    SUBEXIT
1729  SUBEND
1730   !*********************************************************************
1731 Disp_exp_max:SUB Disp_exp_max(Plot_num)
1732    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1733    COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
1734    COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
1735    I=Plot_num                   ! Shorter name ....
1736    IF Start_bin<0 THEN Start_bin=Start_bin_c(I)
1737    IF Stop_bin<0 THEN Stop_bin=1+Num_bin_c(I)-Start_bin_c(I)
1738   !
1739    IF New_plot THEN 
1740      Old_start_bin=Start_bin
1741      Old_stop_bin=Stop_bin
1742    END IF
1743    IF NOT New_plot THEN ! Erase old line
1744      IF FNPlot_use_color THEN 
1745        PEN 7
1746      ELSE
1747        PEN 1
1748      END IF
1749      PLOT Stop_bin,Y_min(I)
1750      PLOT Stop_bin,Y_max(I)
1751      PENUP
1752    END IF
1753    Stop_bin=FNPlot_mkr_bin
1754   ! Plot new line
1755    PEN 3
1756    PLOT Stop_bin,Y_min(I)
1757    PLOT Stop_bin,Y_max(I)
1758    PENUP
1759    SUBEXIT
1760  SUBEND
1761   !*********************************************************************
1762 Disp_exp_forget:SUB Disp_exp_forget(INTEGER Do_beep)
1763    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1764    Disp_user_mess("Expand Set Initial Limits",.5,Do_beep)
1765    Start_bin=-99
1766    Stop_bin=-99
1767    SUBEXIT
1768  SUBEND
1769   !*********************************************************************
1770 Disp_exp_zero:SUB Disp_exp_zero
1771    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1772    Disp_user_mess("THIS IS ZERO",.5)
1773    Zero_bin=FNPlot_mkr_bin
1774    SUBEXIT
1775  SUBEND
1776   !*********************************************************************
1777 Disp_exp_start:DEF FNDisp_exp_start
1778    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1779    RETURN Start_bin
1780  FNEND
1781   !*********************************************************************
1782 Disp_exp_stop:DEF FNDisp_exp_stop
1783    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1784    RETURN Stop_bin
1785  FNEND
1786   !*********************************************************************
1787 Disp_exp_zero:DEF FNDisp_exp_zero
1788    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
1789    RETURN Zero_bin
1790  FNEND
1791   !*********************************************************************
1792 Disp_vs_start:DEF FNDisp_vs_start
1793    COM /Disp_vs_scale/ Sc_start_bin,Sc_stop_bin
1794    RETURN Sc_start_bin
1795  FNEND
1796   !*********************************************************************
1797 Disp_vs_stop:DEF FNDisp_vs_stop
1798    COM /Disp_vs_scale/ Sc_start_bin,Sc_stop_bin
1799    RETURN Sc_stop_bin
1800  FNEND
1801   !*********************************************************************
1802 Disp_user_mess:SUB Disp_user_mess(Aline$,Wait_time,OPTIONAL INTEGER Do_beep)
1803   !This subprogram reports messages to the user using the DISP line,
1804   !beeps, waits 'Wait_time' sec, and exits.
1805    IF NPAR=3 THEN 
1806      IF Do_beep THEN BEEP 100,.5
1807    END IF
1808    DISP Aline$
1809    WAIT Wait_time
1810    DISP 
1811  SUBEND
1812   !*********************************************************************
1813 Disp_offs0:DEF FNDisp_offs0(I$)
1814    COM /Disp_offs0/ Offset0_x,Offset0_y,Offset0_y_abs
1815    SELECT I$
1816      CASE "X"
1817      RETURN Offset0_x
1818      CASE "Y"
1819      RETURN Offset0_y
1820      CASE ELSE
1821      RETURN Offset0_y_abs
1822    END SELECT
1823  FNEND
1824   !*********************************************************************
1825 Disp_kn_scaled:DEF FNDisp_kn_scaled(Inp_num)
1826    COM /Disp_knob_scale/ Scale_factor,Scale_sign(*),INTEGER Activated
1827    Scale_factor=1
1828    IF Activated THEN 
1829      RETURN Scale_sign(Inp_num)*Scale_factor
1830    ELSE
1831      RETURN Scale_sign(Inp_num)
1832    END IF
1833  FNEND
1834   !*********************************************************************
1835 Disp_sc_sign:DEF FNDisp_sc_sign$(Row)
1836    COM /Disp_knob_scale/ Scale_factor,Scale_sign(*),INTEGER Activated
1837    IF Scale_sign(Row-1)=-1.0 THEN 
1838      RETURN "-"
1839    ELSE
1840      RETURN "+"
1841    END IF
1842  FNEND
1843   !*********************************************************************
1844 Disp_set_offs0:SUB Disp_set_offs0(Offset,I$)
1845    COM /Disp_offs0/ Offset0_x,Offset0_y,Offset0_y_abs
1846    SELECT I$
1847      CASE "X"
1848      Offset0_x=Offset
1849      CASE "Y"
1850      Offset0_y=Offset
1851      CASE ELSE
1852      Offset0_y_abs=Offset
1853    END SELECT
1854    SUBEXIT
1855  SUBEND
1856   !*********************************************************************
1857 Disp_set_scale:SUB Disp_set_scale(Sc_change)
1858    COM /Disp_knob_scale/ Scale_factor,Scale_sign(*),INTEGER Activated
1859    IF Activated THEN 
1860      Scale_factor=Scale_factor+Sc_change
1861    END IF
1862    SUBEXIT
1863  SUBEND
1864   !*********************************************************************
1865 Disp_sc_sign:SUB Disp_sc_sign(Sc_sign$,Row)
1866    COM /Disp_knob_scale/ Scale_factor,Scale_sign(*),INTEGER Activated
1867    IF Row=1 THEN ! ALL INPUTS
1868      FOR I=1 TO SIZE(Scale_sign,1)
1869        IF Sc_sign$="1" THEN 
1870          Scale_sign(I)=-1.0
1871        ELSE
1872          Scale_sign(I)=1.0
1873        END IF
1874      NEXT I
1875    ELSE
1876      IF Sc_sign$="1" THEN 
1877        Scale_sign(Row-1)=-1.0
1878      ELSE
1879        Scale_sign(Row-1)=1.0
1880      END IF
1881    END IF
1882    SUBEXIT
1883  SUBEND
1884   !*********************************************************************
1885 Disp_set_sv_tr:SUB Disp_set_sv_tr(Array(*),Plot_number,INTEGER Reference_tr,INTEGER Ok)
1886    COM /Disp_sv_tr/ Sv_trace(*),INTEGER Trace_saved(*),INTEGER Arr_size(*)
1887    Ok=0                       ! Murphy's law ...
1888    Last=MAX(Trace_saved(*))
1889    IF Last>3 THEN 
1890      User_error(" *** Can't have more than four STORE TRACES (Delete one first) ***")
1891    ELSE
1892      Start_bin=BASE(Array,1)
1893      IF Start_bin<>0 THEN 
1894        Disp_user_mess(" Surly you don't want to SAVE this small part. (FORGET EXPAND first)",3)
1895      ELSE
1896        New_index=Last+1
1897        Stop_bin=SIZE(Array,1)-1+Start_bin
1898        Num_bins=1+Stop_bin-Start_bin
1899        Trace_saved(FNDisp_get_row(Plot_number),Reference_tr)=New_index
1900     !
1901     ! Store new data:
1902        Arr_size(New_index)=Num_bins
1903        FOR J=Start_bin TO Stop_bin           ! Copying ...
1904          Sv_trace(New_index,J)=Array(J,2)
1905        NEXT J
1906        Ok=1       ! Even Murphy could fail !!
1907      END IF
1908    END IF
1909    SUBEXIT
1910  SUBEND
1911   !*********************************************************************
1912 Disp_del_sv_tr:SUB Disp_del_sv_tr(Plot_number,INTEGER Reference_tr)
1913  !
1914  ! Deletes one saved trace and packs Sv_trace.
1915  !
1916  !
1917    COM /Disp_sv_tr/ Sv_trace(*),INTEGER Trace_saved(*),INTEGER Arr_size(*)
1918    INTEGER I,Empty_pl
1919    Row=FNDisp_get_row(Plot_number)              ! This is the row number in Disp spread sheet
1920    IF Row<1 THEN 
1921      User_stop("Trace not found. Re-run program. (Disp_del_sv_tr)")
1922    ELSE
1923      Empty_pl=Trace_saved(Row,Reference_tr)
1924      Last_pl=MAX(Trace_saved(*))
1925      Last_pl=MIN(4,Last_pl)
1926      Trace_saved(Row,Reference_tr)=0
1927      GOSUB Pack_sv_tr
1928    END IF
1929    SUBEXIT
1930 Pack_sv_tr:  !----------------------------------------------------------
1931    FOR I=1 TO 16
1932      FOR K=0 TO 1
1933        IF Trace_saved(I,K)>Empty_pl-1 THEN Trace_saved(I,K)=Trace_saved(I,K)-1
1934      NEXT K
1935    NEXT I
1936   !
1937    FOR I=Empty_pl TO Last_pl-1
1938      Arr_size(I)=Arr_size(I+1)
1939     ! Now copy data ...
1940      FOR J=0 TO Arr_size(I)-1
1941        Sv_trace(I,J)=Sv_trace(I+1,J)
1942      NEXT J
1943    NEXT I
1944    RETURN 
1945  SUBEND
1946   !*********************************************************************
1947 Disp_act_knob:SUB Disp_act_knob(Flag)
1948    COM /Disp_knob_scale/ Scale_factor,Scale_sign(*),INTEGER Activated
1949    Activated=Flag
1950    SUBEXIT
1951  SUBEND
1952  !************************************************************************
1953 Disp_h_mkr:SUB Disp_h_mkr(Buf(*),Head(*),Redraw)
1954    !This subprogram handles the marker in the DS_H case.  It Does not return
1955    !until an unknown softkey is pressed.  It sets up softkeys to do
1956    !marker functions.
1957    COM /Disp_buf/ Plot_to_buf(*),Start_bin_c(*),Num_bins_c(*)
1958    COM /Disp_units/ X_units$(*),Y_units$(*)
1959    COM /Disp_window/ X_min_c(*),X_max_c(*),Y_min(*),Y_max(*)
1960    COM /Disp_log/ Do_log_x(*),Do_log_y(*)
1961    COM /Disp_misc/ Y_units_len,Plots_done,R_plots_done
1962    COM /Disp_recall/ Recall_buf(*),Recall_head(*)
1963    COM /Disp_recall4/ Plot_to_r_buf(*)
1964    COM /Disp_mkr/ Mkr_plot,INTEGER Saved_tr,INTEGER Reference_tr
1965    COM /Disp_num_plots/ Num_live_plots,Num_r_plots
1966    !
1967    DIM X_min(1:16),X_max(1:16)
1968    DIM Start_bin(1:16),Num_bins(1:16)
1969    INTEGER Do_vs,Mkr_ok,Rf_ok,Sv_ok,Save_ok
1970    !
1971    MAT Start_bin= Start_bin_c
1972    MAT Num_bins= Num_bins_c
1973    MAT X_min= X_min_c
1974    MAT X_max= X_max_c
1975    !
1976    Total_num_plots=Num_live_plots+Num_r_plots
1977    IF Redraw THEN CALL Disp_plot_axis
1978    IF Redraw OR NOT Plots_done THEN CALL Disp_plot_data(Buf(*),Head(*))
1979    ALLOCATE Plot_array(1:MAX(Num_bins(*),SIZE(Recall_buf,2)),1:2)      !matrix PLOT array
1980    ALLOCATE D_plot_array(0:MAX(Num_bins(*),SIZE(Recall_buf,2))-1,1:2)  !matrix PLOT array, for subtract
1981    IF FNUser_key_press THEN SUBEXIT
1982    ON KEY 1 LABEL FNUser_keylabel$("SAVE UNSAVE") CALL User_key1isr
1983    ON KEY 2 LABEL FNUser_keylabel$("EXPAND") CALL User_key2isr
1984    ON KEY 3 LABEL FNUser_keylabel$("SELECT") CALL User_key3isr
1985    ON KEY 4 LABEL FNUser_keylabel$("RESET CURSOR") CALL User_key4isr
1986        IF FNDisp_auto_c THEN 
1987          Ltext$="AUTO C OFF"
1988        ELSE
1989          Ltext$="AUTO C ON"
1990        END IF
1991    ON KEY 5 LABEL FNUser_keylabel$(Ltext$) CALL User_key5isr
1992    ! 6 will be "MAIN"
1993    ON KEY 7 LABEL FNUser_keylabel$("DATA MOVE") CALL User_key7isr
1994    ON KEY 8 LABEL FNUser_keylabel$("SUBTRACT") CALL User_key8isr
1995    Done=0
1996    GOSUB New_mkr_plot_h
1997    REPEAT
1998      CALL Plot_set_viewp(Total_num_plots,P,0,Y_units_len,1)
1999      IF Do_vs THEN 
2000        REPEAT
2001        UNTIL FNUser_key_press
2002      ELSE
2003        Offset_temp=Offset-FNDisp_data_move(P,Reference_tr,Saved_tr)*Scale_factor
2004        GOSUB Ch_subtract
2005        CALL Plot_do_mkr(Plot_array(*),X_units$(P),Y_units$(P),X_min(P),X_max(P),Y_min(P),Y_max(P),Offset_temp,Scale_factor,Do_log_y(P))       ! PLOT_DO_MKR WON'T EXIT UNTIL A KEY IS PRESSED  ...
2006      END IF
2007      SELECT FNUser_check_key
2008      CASE 1     ! SAVE (and UNSAVE)
2009        Dummy=FNUser_get_key      !to clear the key
2010        IF Saved_tr THEN 
2011          IF FNUser_yes("Do you want to erase this trace",0) THEN 
2012            Disp_del_sv_tr(P,Reference_tr)
2013            Disp_user_mess("  Trace erased",1)
2014            Saved_tr=0
2015          END IF
2016        ELSE
2017          IF FNDisp_plot_sv_tr(P,Reference_tr) THEN 
2018            Disp_user_mess("Allready saved.",2)
2019          ELSE
2020            Disp_set_sv_tr(Plot_array(*),P,Reference_tr,Save_ok)
2021            IF Save_ok THEN 
2022              Saved_tr=1
2023              Disp_user_mess("Trace saved",1)
2024            END IF
2025          END IF
2026        END IF
2027      CASE 2   ! EXPAND
2028        Dummy=FNUser_get_key      !to clear the key
2029        CALL Disp_exp_tr(Buf(*),Head(*))
2030        Dummy=FNUser_get_key      !to clear the key
2031        Done=1
2032      CASE 3     ! SELECT
2033        Dummy=FNUser_get_key      !to clear the key
2034        REPEAT
2035          IF Saved_tr AND Reference_tr THEN Mkr_plot=Mkr_plot+1
2036          IF Mkr_plot>Total_num_plots THEN Mkr_plot=1
2037          IF Saved_tr THEN Reference_tr=NOT Reference_tr
2038          Saved_tr=NOT Saved_tr
2039         !
2040          Mkr_ok=FNDisp_choice(Mkr_plot,3)<>3                              ! OK when not in "VS"-plot
2041          Rf_ok=(NOT Reference_tr) OR (FNDisp_choice(Mkr_plot,3)=4)        ! OK when not "REF" or one really exists
2042          Sv_ok=(NOT Saved_tr) OR FNDisp_plot_sv_tr(Mkr_plot,Reference_tr) ! OK when not "SV" or one really exists
2043        UNTIL Mkr_ok AND Rf_ok AND Sv_ok
2044        GOSUB New_mkr_plot_h
2045      CASE 4     ! RESET CURSOR
2046        Dummy=FNUser_get_key      !to clear the key
2047        IF FNDisp_get_curs("X")=0 AND FNDisp_get_curs("Y")=0 THEN 
2048          Disp_user_mess("Cursor position set.",2)
2049          Disp_set_curs(FNDisp_offs0("X"),FNDisp_offs0("Y_ABS"))
2050        ELSE
2051          Disp_user_mess("Cursor position reset.",2)
2052          Disp_set_curs((0),(0))
2053        END IF
2054  !     CALL Disp_store_tr(Plot_array(*),P,Overload,Offset,Scale_factor)
2055      CASE 5     ! EXPAND
2056        Dummy=FNUser_get_key      !to clear the key
2057        IF FNDisp_auto_c THEN 
2058          Disp_set_auto_c(0)
2059          Ltext$="AUTO C ON"
2060        ELSE
2061          Disp_set_auto_c(1)
2062          Ltext$="AUTO C OFF"
2063        END IF
2064        ON KEY 5 LABEL FNUser_keylabel$(Ltext$) CALL User_key5isr
2065      CASE 7    ! DATA MOVE
2066        Dummy=FNUser_get_key      !to clear the key
2067        IF FNDisp_data_move(P,Reference_tr,Saved_tr)=0 THEN 
2068          Disp_set_d_move(P,Reference_tr,Saved_tr,FNDisp_offs0("Y"))
2069        ELSE
2070          Disp_set_d_move(P,Reference_tr,Saved_tr,0)
2071          Disp_user_mess("Data move erased.",1)
2072        END IF
2073        Done=1
2074      CASE 8    ! SUBTRACT
2075        Dummy=FNUser_get_key
2076        IF FNDisp_get_sub(P,Reference_tr,Saved_tr) THEN 
2077          Disp_set_sub(P,Reference_tr,Saved_tr,0)
2078          Disp_user_mess("SUBTRACT deactivated.",3)
2079        ELSE
2080          Disp_set_sub(P,Reference_tr,Saved_tr,1)
2081          Disp_user_mess("SUBTRACT activated.",3)
2082        END IF
2083      CASE ELSE
2084        Done=1
2085      END SELECT
2086    UNTIL Done
2087    SET ECHO -80000.0,0.   ! Outside clip limits
2088    SUBEXIT
2089 New_mkr_plot_h:    !----------------------------------------------------
2090    Mkr_plot=MAX(1,MIN(Total_num_plots,Mkr_plot))
2091    P=Mkr_plot      ! Use shorter variable name
2092    Do_vs=(FNDisp_choice(P,3)=3)
2093    Start_bin(P)=MAX(Start_bin_c(P),FNDisp_exp_start)
2094    Num_bins(P)=MIN(Num_bins_c(P),(FNDisp_exp_stop+1-Start_bin(P)))
2095    IF Num_bins(P)<0 THEN Num_bins(P)=Num_bins_c(P)
2096    IF NOT Do_vs THEN 
2097            ! And now into real world units ...
2098      X_min(P)=X_min_c(P)+Start_bin(P)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
2099      X_max(P)=X_min_c(P)+(Start_bin(P)+Num_bins(P)-1)*(X_max_c(P)-X_min_c(P))/Num_bins_c(P)
2100    END IF
2101    Stop_bin=Start_bin(P)+Num_bins(P)-1
2102   !
2103    IF P>Num_live_plots THEN    !recalled trace, get from Recall_buf(*)
2104      REDIM Plot_array(Start_bin(P):Stop_bin,1:2)
2105      CALL Plot_make_y(Recall_buf(*),Recall_head(*),Plot_array(*),Plot_to_r_buf(P),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
2106      CALL Plot_make_x(Plot_array(*),Do_log_x(P),X_min(P),X_max(P))
2107      Overload=Recall_head(Plot_to_r_buf(P),3)
2108    ELSE                    !not recalled, get Plot_array from Buf(*)
2109      Stop_bin=MIN(Stop_bin,SIZE(Buf,2)-1)
2110      REDIM Plot_array(Start_bin(P):Stop_bin,1:2)
2111      IF Reference_tr THEN 
2112        Plot_buffer=1
2113      ELSE
2114        Plot_buffer=Plot_to_buf(P)
2115      END IF
2116      CALL Plot_make_y(Buf(*),Head(*),Plot_array(*),Plot_buffer,Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
2117      IF Saved_tr THEN 
2118        Disp_get_sv_tr(Plot_array(*),Dummy,FNDisp_plot_sv_tr(P,Reference_tr))
2119        IF Dummy-1<>Stop_bin-Start_bin(P) THEN 
2120          Disp_user_mess(" *** WARNING: Different number of bins in LIVE and SAVE trace (DISP_H_MKR) ***",5)
2121        END IF
2122      END IF
2123      CALL Plot_make_x(Plot_array(*),Do_log_x(P),X_min(P),X_max(P))
2124      Overload=Head(Plot_to_buf(P),3)
2125    END IF
2126    RETURN 
2127 Ch_subtract:   !-----------------------------------------------------------
------
2128    MAT D_plot_array= (0)
2129    IF FNDisp_get_sub(P,Reference_tr,Saved_tr) THEN 
2131      IF NOT Saved_tr THEN    ! GET THE SAVED TRACE
2132        St_index=FNDisp_plot_sv_tr(P,Reference_tr)
2133        IF St_index<>0 THEN 
2134          Disp_get_sv_tr(D_plot_array(*),Num_of_bins,St_index)
2135        END IF
2136      ELSE          ! GET LIVE TRACE
2137        IF Reference_tr THEN 
2138          Choice_num=2     ! GET THE REFERENCE LIVE TRACE
2139        ELSE
2140          Choice_num=1
2141        END IF
2142        CALL Plot_make_y(Buf(*),Head(*),D_plot_array(*),FNDisp_choice(P,Choice_num),Start_bin(P),Stop_bin,Do_log_y(P),Offset,Scale_factor)
2143      END IF
2144     !
2145      FOR K=Start_bin(P) TO Stop_bin
2149          Plot_array(K,2)=Plot_array(K,2)-D_plot_array(K,2)
2151      NEXT K
2152    END IF
2153    RETURN 
2154  SUBEND
2155  !********************************************************************************
2156 Disp_get_sv_tr:SUB Disp_get_sv_tr(Array(*),Num_bins,Sv_index)
2157  ! IN:  SV_index
2158  ! OUT: Array, Num_bins
2159  !
2160    COM /Disp_sv_tr/ Sv_trace(*),INTEGER Trace_saved(*),INTEGER Arr_size(*)
2161    Sv_index=MAX(MIN(4,Sv_index),1)     ! Sv_index must be in the intervall 1:4
2162    Start_bin=BASE(Array,1)
2163    Stop_bin=MIN((SIZE(Array,1)-1),(Arr_size(Sv_index)-1))+Start_bin
2164    Num_bins=1+Stop_bin-Start_bin
2165    FOR J=Start_bin TO Stop_bin               ! Copying ...
2166      Array(J,2)=Sv_trace(Sv_index,J)
2167    NEXT J
2168    SUBEXIT
2169  SUBEND
2170  !************************************************************************
2171 Disp_plot_sv_tr:DEF FNDisp_plot_sv_tr(Plot_number,INTEGER Reference_plot)
2172  !This function returns the index number of the trace stored in Sv_trace  for plot "Plot_number"
2173  !
2174  ! IN: Plot_number    - the live plots, starting at 1 for the first
2175  !     Reference_plot - LOGICAL, 0= not reference    1= reference
2176  !
2177  ! Return: Index in Sv_trace(*) for this plot
2178  !
2179    COM /Disp_sv_tr/ Sv_trace(*),INTEGER Trace_saved(*),INTEGER Arr_size(*)
2180    Row=FNDisp_get_row(Plot_number)
2181    IF Row=0 THEN 
2182      User_error(" *** ERROR : Trace not found  (Disp_plot_sv_tr) ***")
2183      RETURN 0
2184    ELSE
2185      RETURN Trace_saved(Row,Reference_plot)
2186    END IF
2187  FNEND
2188  !************************************************************************
2189 Disp_get_row:DEF FNDisp_get_row(Plot_number)
2190  !
2191  ! This function returns row number in the Disp spread sheet of "Plot_num"
2192  !
2193  ! IN: Plot_number    - the live plots, starting at 1 for the first
2194  !
2195  !
2196    COM /Disp_spread1/ Box$(*),Row,Col,Start_row
2197  !
2198  ! Initialization
2199    I=0
2200    Count=MAX(1,Plot_number)    ! Must not destroy "Plot_number"
2201    Activate_col=2              ! The activation col is the 2nd leftmost
2202    Row=0
2203  !
2204    REPEAT
2205      I=I+1
2206      IF Box$(Activate_col,I)="*" THEN 
2207        Count=Count-1
2208        IF Count=0 THEN Row=I
2209      END IF
2210    UNTIL Row<>0 OR I=16
2211  !     That was it ...
2212    RETURN Row
2213  FNEND
2214   !*********************************************************************
2215 Disp_exp_done:SUB Disp_exp_done
2216    COM /Disp_exp/ INTEGER Start_bin,Stop_bin,Zero_bin,INTEGER New_plot,Old_start_bin,Old_stop_bin
2217    New_plot=1
2218    SUBEXIT
2219  SUBEND
2220   !*********************************************************************
2221 Disp_set_auto_c:SUB Disp_set_auto_c(INTEGER Toggle)
2222    COM /Disp_auto/ INTEGER Auto_center_on,REAL Data_move_offs(*)
2223    Auto_center_on=Toggle
2224    SUBEXIT
2225  SUBEND
2226   !*********************************************************************
2227 Disp_auto_c:DEF FNDisp_auto_c
2228  !
2229    COM /Disp_auto/ INTEGER Auto_center_on,REAL Data_move_offs(*)
2230    RETURN Auto_center_on
2231  FNEND
2232   !*********************************************************************
2233 Disp_data_move:DEF FNDisp_data_move(Plot_num,INTEGER Ref_tr,INTEGER Sv_tr)
2234  !
2235    COM /Disp_auto/ INTEGER Auto_center_on,REAL Data_move_offs(*)
2236    RETURN Data_move_offs(Plot_num,Ref_tr,Sv_tr)
2237  FNEND
2238   !*********************************************************************
2239 Disp_set_d_move:SUB Disp_set_d_move(Plot_num,INTEGER Ref_tr,INTEGER Sv_tr,REAL Data_value)
2240    COM /Disp_auto/ INTEGER Auto_center_on,REAL Data_move_offs(*)
2241    Data_move_offs(Plot_num,Ref_tr,Sv_tr)=Data_value
2242    SUBEXIT
2243  SUBEND
2244   !*********************************************************************
2245 Disp_get_curs:DEF FNDisp_get_curs(I$)
2246    COM /Disp_curs/ Offset_x,Offset_y
2247    IF I$="X" THEN 
2248      RETURN Offset_x
2249    ELSE
2250      RETURN Offset_y
2251    END IF
2252  FNEND
2253   !*********************************************************************
2254 Disp_set_curs:SUB Disp_set_curs(X,Y)
2255    COM /Disp_curs/ Offset_x,Offset_y
2256    Offset_x=X
2257    Offset_y=Y
2258    SUBEXIT
2259  SUBEND
2260   !*********************************************************************
2261 Disp_get_sub:DEF FNDisp_get_sub(P,INTEGER Rf_tr,INTEGER Sv_tr)
2262    COM /Disp_sub/ Sub_active(1:16,0:1,0:1)
2263    RETURN Sub_active(P,Rf_tr,Sv_tr)
2264  FNEND
2265   !*********************************************************************
2266 Disp_set_sub:SUB Disp_set_sub(P,INTEGER Rf_tr,INTEGER Sv_tr,INTEGER Flag_value)
2267    COM /Disp_sub/ Sub_active(1:16,0:1,0:1)
2268    Sub_active(P,Rf_tr,Sv_tr)=Flag_value
2269    SUBEXIT
2270  SUBEND
2271   !*********************************************************************
2272 Disp_sv_tr_clr:DEF FNDisp_sv_tr_clr
2273    COM /Disp_sv_tr/ Sv_trace(*),INTEGER Trace_saved(*),INTEGER Arr_size(*)
2274    RETURN NOT MAX(Trace_saved(*))
2275  FNEND