1 !    OUTPUT 2 USING "#,K";"<lf>INDENT<cr>REN 1,1<cr><lf>RE-STORE ""SPAM_GEN_H""<cr>"
2     Load_loader(1)
3     STOP
4     !
5 Load_gen_con:    !
6     Load_loader(0)
7     STOP
8     !
9 Load_delend:  !
10 !   OUTPUT 2 USING "#,K";"<lf>INDENT<cr>REN 1,1<cr><lf>RE-STORE ""SPAM_H""<cr>"
11    !
12    !                      SPAM file
13    !
14    !     This file contains the Signal Processing Application Manager.
15    !     It consists of a spreadsheet that is used to load and run the
16    !     various demo programs available.  The list of demo programs
17    !     available is read from the file SPAM_SETUP when this program
18    !     is first run.  The SPAM_SETUP file should be an ASCII type file
19    !     with the format shown below:
20    !
21    !     <first line>    10  !  <Description of first demo program>
22    !                     20  !  <Filename of first demo program>
23    !                     30  !  <Description of second demo program>
24    !                     40  !  <Filename of second demo program>
25    !                              .
26    !                              .
27    !                              .
28    !                     ??? !  <Description of last demo program>
29    !     <last line>     ??? !  <Filename of last demo program>
30    !
31    !
32    !     The above format is easily obtained by simply editing a file
33    !     with the BASIC editor, and 'SAVE'ing the result in SPAM_SETUP.
34    !
35    Main_main(0)
36    STOP
37    !
38    !  This entry point is used when loading a demo program.
39 Main_from_load:   !
40    Main_main(1)
41    STOP
42    !
43    END
44    !
45    ! PAGE -> 
46    !***********************************************************************
47 Main_main:SUB Main_main(From_load)
48      !
49      !  This is the subprogram that is first called after a run is given
50      !  for the Signal Processing Application Manager.  The From_load
51      !  parameter indicates the program is in the process of loading
52      !  a demo program.  This subprogram initializes the system based
53      !  on if its loading an application program, its the first time
54      !  this program was run after being loaded, or the program was
55      !  just loaded and run.  The later two cases are distinguished by
56      !  the Skip_init_flag that is kept in common.
57      !
58      COM /Main_spread/ Row,Col,Start_row
59      COM /Main_boxes/ Box$(1:2,1:18)[40]
60      COM /Main_title/ Title$(1:2,0:2)[40]
61      COM /Main_prompt/ Prompt$(1:2)[80]
62      COM /Main_width/ Col_width(1:2)
63      COM /Main_max/ Max_col,Max_row,Modify_col
64      COM /Main_file/ Appl_file$(1:18)[120],Appl_loaded
65      COM /Main_init/ Skip_init_flag
66      !
67      FOR Keynum=0 TO 9
68        ON KEY Keynum LABEL "" GOSUB Main_main_dum
69      NEXT Keynum
70      !
71      IF Skip_init_flag THEN 
72        !  Run at least once before since being loaded, only need to
73        !  initialize the Cnfg, Diag, and Appl files.
74        !
75        DISP "Initializing hardware configuration . . ."
76        Cnfg_init
77        Diag_init
78        IF (NOT From_load) AND (Appl_loaded<>0) THEN 
79          Main_appl_init
80        END IF
81      END IF
82      !
83      IF NOT Skip_init_flag THEN 
84        ! First time run after being loaded, initialize all files.
85        !
86        DISP "Initializing . . ."
87        Main_initall
88        DISP "Initializing hardware configuration . . ."
89        Cnfg_init
90        Diag_init
91        DISP "Initializing SPAM"
92        Main_init
93        Skip_init_flag=1
94      END IF
95      DISP ""
96      !
97      IF From_load THEN 
98        !  If in process of loading a demo program, call the loader.
99        !
100       IF NOT FNMain_load_appl("") THEN 
101         Appl_loaded=0
102       END IF
103     END IF
104     !
105     !  Startup the Signal Processing Application Manager spreadsheet.
106     !
107     Main_spread(From_load)
108     !
109     SUBEXIT
110     !
111 Main_main_dum:    !
112     BEEP 
113     RETURN 
114     !
115   SUBEND
116   ! PAGE -> 
117   !***********************************************************************
118 Load_loader:SUB Load_loader(Init)
119     !
120     !  This subprogram is used to generate the SPAM file.  It loads the
121     !  available files into memory, and then deletes itself and prompts
122     !  the user to save the resulting SPAM file.  This subprogram uses
123     !  the keyboard buffer to load the files because BASIC doesn't allow
124     !  loading subprograms with new common blocks into an already running
125     !  program.  The user should not touch the computer until the loading
126     !  of the various files is complete.  The Init flag indicates to
127     !  start the loading process from the beginning.
128     !
129     COM /Appl_loader/ Pass$[20],File_list$(0:49)[100],File_ptr,Save_file$[100]
130     DIM Temp$(1:1)[80],Filename$[100],Temp_file$[100]
131     !
132     IF Init THEN Pass$=""
133     !
134     REPEAT
135       SELECT Pass$
136       CASE ""
137         GOSUB Load_startup
138         Pass$="START LOADING"
139         OUTPUT KBD USING "#,K";"<cr>ÿ#DEL 1,LOAD_GEN_CON<cr>RUN<cr>"
140         STOP
141       CASE "START LOADING"
142         Init_flag=1
143         RESTORE Load_data
144         File_ptr=0
145         DISP "GETTING MODULES"
146         REPEAT
147           READ Temp_file$
148           File_list$(File_ptr)=Temp_file$
149           IF Temp_file$<>"*" THEN File_ptr=File_ptr+1
150           !
151         UNTIL Temp_file$="*"
152         File_ptr=0
153         Save_file$=""
154         Pass$="LOAD THEM"
155       CASE "LOAD THEM"
156         Init_flag=1
157         Must_have=1
158         !
159         IF Save_file$<>"" THEN 
160           Filename$=Save_file$
161           Save_file$=""
162         ELSE
163           Save_file$=""
164           Filename$=File_list$(File_ptr)
165           File_ptr=File_ptr+1
166           !
167           Pnd_pos=POS(Filename$,"#")
168           IF Pnd_pos<>0 THEN 
169             Save_file$=Filename$
170             Must_have=0
171             IF Pnd_pos=1 THEN 
172               Save_file$=Save_file$[2]
173               Filename$=SYSTEM$("VERSION:BASIC")&Save_file$
174             ELSE
175               Filename$=Save_file$[1;Pnd_pos-1]&SYSTEM$("VERSION:BASIC")&Save_file$[Pnd_pos+1]
176               Save_file$=Save_file$[1;Pnd_pos-1]&Save_file$[Pnd_pos+1]
177             END IF
178             Dot_posn=POS(Filename$,".")
179             IF Dot_posn<>0 THEN Filename$[Dot_posn;1]="_"
180           END IF
181         END IF
182         !
183         IF Filename$<>"*" THEN 
184           GOSUB Load_chk_file
185           IF File_ok THEN ! Skip if not found and not needed
186             DISP "LOADING FROM FILE "&Filename$
187             OUTPUT KBD USING "#,K";"ÿ#<cr><cr>REN 1,1<cr>LOADSUB ALL FROM """&Filename$&"""<cr>RUN<cr>"
188             STOP
189           END IF
190         ELSE
191           Pass$="LOADED"
192         END IF
193       CASE "LOADED"
194         OUTPUT CRT;CHR$(12)
195         OUTPUT CRT;RPT$(CHR$(10),5)
196         OUTPUT CRT;"     SPAM is finished being generated!!"
197         OUTPUT CRT
198         OUTPUT CRT;"     When the prompt appears, store this program for future use."
199         OUTPUT CRT;"     Also COPY the ""SPAM_SETUP"" and ""FFT_COEFS"" files to the same media."
200         DISP ""
201         OUTPUT KBD USING "#,K";"ÿ#<cr>DEL 1,LOAD_DELEND<cr>DELSUB LOAD_LOADER<cr>REN 1,1<cr><lf><cr>DISP""Modify this line and store program""<cr>RE-STORE ""SPAM_H""ÿ<"
202         STOP
203       END SELECT
204     UNTIL 1=0
205     DISP ""
206     SUBEXIT
207     !
208 Load_data:  ! 'DISP' is modified for Hasselblad DS application. New name: 'DISP_H'.
209             ! 'PLOT' is modified for Hasselblad DS application. New name: 'PLOT_H'.
210             ! 'INPT' is modified for Hasselblad DS application. New name: 'INPT_H'.
211     DATA FILE,INPT_H,SRCE,DISP_H,DIAG,CNFG,PLOT_H#,USER,HW,ICODE,LIB,*
212       !
213       !
214 Load_startup:!
215     OUTPUT CRT;CHR$(12)
216     OUTPUT CRT;RPT$(CHR$(10),4)
217     OUTPUT CRT;"  Generating the Signal Processing Application Manger"
218     OUTPUT CRT;"            for  Victor  Hasselblad  AB"
219     OUTPUT CRT
220     OUTPUT CRT;"     This will take a few minutes to complete"
221     OUTPUT CRT
222     OUTPUT CRT;"     DO NOT attempt to stop this loading process!!"
223     RETURN 
224       !
225       !
226 Load_chk_file:!
227     REPEAT
228       File_ok=1
229       ON ERROR GOTO Load_ignore
230       Temp$(1)=""
231       CAT Filename$ TO Temp$(*)
232 Load_ignore:    !
233       OFF ERROR 
234       IF Temp$(1)="" THEN 
235         File_ok=0
236         IF NOT Must_have THEN RETURN 
237         DISP "Can't find file "&Filename$&", place in default MSI and press <CONTINUE>"
238         BEEP 
239         PAUSE
240       END IF
241     UNTIL File_ok
242     RETURN 
243   SUBEND
244   !
245   ! PAGE -> 
246   !***********************************************************************
247 Main_initall:SUB Main_initall
248     !
249     !  This subprogram initializes all the files.
250     !
251     Lib_lib
252     Icode_icode
253     Hw_hw
254     User_user
255     Plot_plot
256     !
257     Main_marquee
258     Cnfg_cnfg
259     !
260     Disp_disp
261     Srce_srce
262     Inpt_inpt
263     !
264     Diag_diag
265     File_file
266     !
267   SUBEND
268   !
269   ! PAGE -> 
270   !***********************************************************************
271 Main_init:SUB Main_init
272     !
273     !  This subprogram initializes the SPAM spreadsheet.
274     !
275     COM /Main_spread/ Row,Col,Start_row
276     COM /Main_boxes/ Box$(*)
277     COM /Main_title/ Title$(*)
278     COM /Main_prompt/ Prompt$(*)
279     COM /Main_width/ Col_width(*)
280     COM /Main_max/ Max_col,Max_row,Modify_col
281     COM /Main_file/ Appl_file$(*),Appl_loaded
282     !
283     DIM New_line$[160]
284     !
285     Max_col=2
286     Modify_col=2
287     Row=1
288     Col=2
289     Start_row=1
290     Max_row=0
291     Title$(1,0)="Signal Processing Application Manager"
292     !
293     RESTORE Main_sprd_data
294     FOR Col=1 TO Max_col
295       READ Col_width(Col),Title$(Col,1),Title$(Col,2),Prompt$(Col)
296     NEXT Col
297     !
298     ON ERROR GOTO Main_bad_file
299     ASSIGN @Spam_file TO "SPAM_SETUP"
300     OFF ERROR 
301     Spam_linecnt=0
302     !
303     ON ERROR GOTO Main_spam_bad
304     LOOP
305       ON END @Spam_file GOTO Main_spam_eof
306       ENTER @Spam_file;New_line$
307       Spam_linecnt=Spam_linecnt+1
308       Box$(1,Max_row+1)=TRIM$(New_line$[POS(New_line$,"!")+1])
309       Box$(2,Max_row+1)=""
310       ON END @Spam_file GOTO Main_spam_bad
311       ENTER @Spam_file;New_line$
312       Spam_linecnt=Spam_linecnt+1
313       Appl_file$(Max_row+1)=TRIM$(New_line$[POS(New_line$,"!")+1])
314       Max_row=Max_row+1
315     END LOOP
316     !
317 Main_spam_eof:    !
318     ASSIGN @Spam_file TO *
319     OFF ERROR 
320     !
321     SUBEXIT
322     !
323 Main_spam_bad:    !
324     User_clr_scr
325     PRINT "Error in SPAM_SETUP file near line #"&VAL$(Spam_linecnt)
326     PRINT "Fix error and re-run"
327     STOP
328     !
329 Main_bad_file:    !
330     User_clr_scr
331     PRINT "Unable to open SPAM_SETUP file under default directory"
332     PRINT "Fix error and re-run"
333     STOP
334     !
335 Main_sprd_data:    !
336     DATA 40,  "Application",  "", ""
337     DATA 11,  "Currently",    "Loaded",       "Waiting for softkey"
338   SUBEND
339   ! PAGE -> 
340   !************************************************************************
341 Main_spread:SUB Main_spread(From_load)
342     !
343     !  This subprogram displays the SPAM spreadsheet, and allows the user
344     !  to load and run demo programs.
345     !
346     COM /Main_spread/ Row,Col,Start_row       !keep these in com for memory
347     COM /Main_boxes/ Box$(*)
348     COM /Main_title/ Title$(*)
349     COM /Main_prompt/ Prompt$(*)
350     COM /Main_width/ Col_width(*)
351     COM /Main_max/ Max_col,Max_row,Modify_col
352     COM /Main_file/ Appl_file$(*),Appl_loaded
353     DIM New_entry$[400]
354     !
355     REDIM Box$(1:2,1:(Max_row)),Appl_file$(1:(Max_row))
356     !
357     GOSUB Main_sprd_keys
358     !
359     User_clr_scr
360     Dummy=FNUser_get_key
361     !
362     !  Set loaded flag in spreadsheet if an application loaded
363     IF Appl_loaded=0 THEN 
364       FOR R=1 TO Max_row
365         Box$(2,R)=""
366       NEXT R
367     ELSE
368       Box$(2,Appl_loaded)="*"
369     END IF
370     !
371     !Now call spread sheet.  It returns with New_entry$ and Row and Col
372     Done=0
373     REPEAT
374       CALL User_spread(Box$(*),Title$(*),Prompt$(*),New_entry$,Col_width(*),Modify_col,Col,Row,Start_row)
375       !
376       SELECT FNUser_check_key
377       !
378       CASE 0   !no key pressed, must be a New_entry$ for Box
379         BEEP 
380         !
381       CASE 1 ! Load application
382         Dummy=FNUser_get_key  !to clear the key
383         IF Row<>Appl_loaded THEN 
384           GOSUB Main_clr_keys
385           User_clr_scr
386           IF Appl_loaded<>0 THEN Box$(2,Appl_loaded)=""
387           Appl_loaded=Row
388           IF FNMain_load_appl(Appl_file$(Row)) THEN 
389           END IF
390           ! Returns only if an error
391           GOSUB Main_sprd_keys
392           Appl_loaded=0
393         END IF
394         !
395       CASE 2 ! Start loaded
396         Dummy=FNUser_get_key
397         IF Appl_loaded<>0 THEN 
398           GOSUB Main_clr_keys
399           User_clr_scr
400           Appl_main(0)
401           User_clr_scr
402           GOSUB Main_sprd_keys
403         ELSE
404           BEEP 
405         END IF
406         !
407       CASE 3 ! Save configuration
408         Dummy=FNUser_get_key
409         IF Appl_loaded<>0 THEN 
410           Main_save(Appl_file$(Appl_loaded),Ok)
411         ELSE
412           BEEP 
413         END IF
414         !
415       CASE 4 ! Get configuration
416         Dummy=FNUser_get_key
417         IF Appl_loaded<>0 THEN 
418           Main_recall(Appl_file$(Appl_loaded),Ok)
419         ELSE
420           BEEP 
421         END IF
422         !
423       CASE 6 ! Configuration
424         Dummy=FNUser_get_key
425         GOSUB Main_clr_keys
426         User_clr_scr
427         Cnfg_spread(Changed)
428         User_clr_scr
429         Diag_init
430         IF Changed AND (Appl_loaded<>0) THEN 
431           Main_appl_init
432         END IF
433         GOSUB Main_sprd_keys
434         !
435       CASE 8 ! Diagnostics
436         Dummy=FNUser_get_key
437         GOSUB Main_clr_keys
438         User_clr_scr
439         Diag_main
440         !
441         Cnfg_init
442         Diag_init
443         IF Appl_loaded<>0 THEN 
444           Main_appl_init
445         END IF
446         User_clr_scr
447         GOSUB Main_sprd_keys
448         !
449       CASE ELSE   !a softkey but not one of mine, so exit
450         Dummy=FNUser_get_key
451         BEEP 
452       END SELECT
453     UNTIL 1=0
454     CALL User_clr_scr
455     SUBEXIT
456     !
457 Main_dummy:    !
458     BEEP 
459     RETURN 
460     !
461 Main_sprd_keys: !
462     !define softkeys
463     ON KEY 0 LABEL "" GOSUB Main_dummy
464     ON KEY 1 LABEL FNUser_keylabel$("LOAD APPL.") CALL User_key1isr
465     ON KEY 2 LABEL "" GOSUB Main_dummy
466     ON KEY 3 LABEL "" GOSUB Main_dummy
467     ON KEY 4 LABEL "" GOSUB Main_dummy
468     IF Appl_loaded<>0 THEN 
469       ON KEY 2 LABEL FNUser_keylabel$("RUN LOADED") CALL User_key2isr
470       ON KEY 3 LABEL FNUser_keylabel$("SAVE SETUP") CALL User_key3isr
471       ON KEY 4 LABEL FNUser_keylabel$("GET SETUP") CALL User_key4isr
472     END IF
473     ON KEY 5 LABEL "" GOSUB Main_dummy
474     ON KEY 6 LABEL FNUser_keylabel$("CONFIG") CALL User_key6isr
475     ON KEY 7 LABEL "" GOSUB Main_dummy
476     ON KEY 8 LABEL FNUser_keylabel$("HARDWARE DIAG") CALL User_key8isr
477     ON KEY 9 LABEL "" GOSUB Main_dummy
478     RETURN 
479     !
480 Main_clr_keys:    !
481     FOR Keynum=0 TO 9
482       ON KEY Keynum LABEL "" GOSUB Main_dummy
483     NEXT Keynum
484     RETURN 
485     !
486   SUBEND
487   ! PAGE -> 
488   !************************************************************************
489 Main_appl_init:SUB Main_appl_init
490     COM /Main_file/ Appl_file$(*),Appl_loaded
491     COM /Main_init/ Skip_init_flag
492   !
493     DISP "Initializing Application . . ."
494     ON ERROR GOTO Main_no_appl
495     Appl_init
496     OFF ERROR 
497     SUBEXIT
498     !
499 Main_no_appl: !
500     OFF ERROR 
501     Skip_init_flag=0
502     Appl_loaded=0
503   !
504   SUBEND
505   ! PAGE -> 
506   !************************************************************************
507 Main_load_appl:DEF FNMain_load_appl(Appl_filename$)
508     !
509     !  This subprogram loads a demo file.  It first looks for the demo
510     !  file to load.  If the demo file is found, it deletes any previously
511     !  loaded demo program, then stops the program and restarts it to
512     !  clear out any common blocks from a previously loaded program,
513     !  and then loads the selected demo program.  Appl_filename$ is the
514     !  filename for the selected demo program.
515     !
516     COM /Main_load_appl/ Loading_file$[120],Fileloaded
517     !
518     DIM Temp$(1)[80]
519     !
520     Deleted_subs=0
521     Do_quick_load=0
522     !
523     IF Appl_filename$<>"" THEN 
524       DISP "Looking for application . . ."
525       Loading_file$=FNLib_full_path$(Appl_filename$)
526       ON ERROR GOTO Main_err_ignore
527       CAT Loading_file$ TO Temp$(*)
528 Main_err_ignore:!
529       OFF ERROR 
530       !
531       IF Temp$(1)<>"" THEN 
532         ON ERROR GOTO Main_ignr_del
533         DELSUB Appl_appl TO END
534         Deleted_subs=1
535 Main_ignr_del:!
536         OFF ERROR 
537         Fileloaded=0
538         !
539         Do_quick_load=1
540         IF Deleted_subs THEN 
541           DISP "Loading application . . ."
542           OUTPUT KBD USING "#,K";"ÿ#<cr>RUN MAIN_FROM_LOAD<cr>"
543           STOP
544         END IF
545       END IF
546     END IF
547     !
548     IF (Appl_filename$="") OR Do_quick_load THEN 
549       IF NOT Fileloaded THEN 
550         Fileloaded=1
551         DISP "Loading application . . ."
552         OUTPUT KBD USING "#,K";"ÿ#<cr>LOADSUB ALL FROM """&Loading_file$&"""<cr>RUN MAIN_FROM_LOAD<cr>"
553         STOP
554       ELSE
555         Fileloaded=0
556         DISP "Initializing application . ."
557         ON ERROR GOTO Main_not_loaded
558         Meas_meas
559         Appl_appl
560         Main_appl_init
561         Fileloaded=1
562 Main_not_loaded:!
563         OFF ERROR 
564       END IF
565     END IF
566     !
567     IF NOT Fileloaded THEN 
568       User_error(Appl_filename$&" file not found.  Unable to load application")
569     END IF
570     !
571     RETURN Fileloaded
572   !
573   FNEND
574   !
575 Main_save:SUB Main_save(Current_appl$,Ok)
576     !
577     !  This subprogram saves the current state of the various spreadsheets
578     !  for the currently loaded application.
579     !
580     ON ERROR GOTO Main_sv_badfile
581     Ok=1
582     CALL File_save_open(@File,Ok)
583     IF NOT Ok THEN GOTO Main_sv_badfile
584     !
585     ON ERROR GOTO Main_sv_bad
586     !
587     OUTPUT @File;Current_appl$
588     !
589     IF Ok THEN 
590       DISP "Saving configuration setup"
591       CALL Cnfg_save(@File,Ok)
592     END IF
593     IF Ok THEN 
594       DISP "Saving input setup"
595       CALL Inpt_save(@File,Ok)
596     END IF
597     IF Ok THEN 
598       DISP "Saving source setup"
599       CALL Srce_save(@File,Ok)
600     END IF
601     IF Ok THEN 
602       DISP "Saving measurement setup"
603       CALL Meas_save(@File,Ok)
604     END IF
605     IF Ok THEN 
606       DISP "Saving display setup"
607       CALL Disp_save(@File,Ok)
608     END IF
609     ASSIGN @File TO *
610     OFF ERROR 
611     IF Ok THEN 
612       DISP "Save done."
613       WAIT .5
614     ELSE
615       User_error("Save failed.")
616     END IF
617     SUBEXIT
618 Main_sv_bad:!
619     OFF ERROR 
620     CALL User_error("Save failed: "&ERRM$)
621     SUBEXIT
622 Main_sv_badfile:!
623     OFF ERROR 
624     SUBEXIT
625   SUBEND
626   !
627 Main_recall:SUB Main_recall(Current_appl$,Ok)
628     !
629     !  This subprogram recalls a saved save state.  The state must
630     !  match the currently loaded application.  If an error occurrs
631     !  during the recall, the recall is aborted and the state is reset.
632     !
633     DIM Recall_appl$[100]
634     !
635     ON ERROR RECOVER Main_ld_badfile
636     CALL File_load_open(@File,Ok)
637     IF NOT Ok THEN GOTO Main_ld_badfile
638     !
639     ON ERROR GOTO Main_ld_bad
640     !
641     ENTER @File;Recall_appl$
642     IF NOT (Current_appl$=Recall_appl$) THEN 
643       User_error("Load failed: File not saved from "&Current_appl$&".")
644       ASSIGN @File TO *
645       SUBEXIT
646     END IF
647     !
648     IF Ok THEN 
649       DISP "Recalling configuration setup"
650       CALL Cnfg_load(@File,Ok)
651     END IF
652     !
653     Main_appl_init
654     !
655     IF Ok THEN 
656       DISP "Recalling input setup"
657       CALL Inpt_load(@File,Ok)
658     END IF
659     IF Ok THEN 
660       DISP "Recalling source setup"
661       CALL Srce_load(@File,Ok)
662     END IF
663     IF Ok THEN 
664       DISP "Recalling measurement setup"
665       CALL Meas_load(@File,Ok)
666     END IF
667     IF Ok THEN 
668       DISP "Recalling display setup"
669       CALL Disp_load(@File,Ok)
670     END IF
671     ASSIGN @File TO *
672     IF Ok THEN 
673       DISP "Load done."
674       WAIT .5
675     ELSE
676       User_error("Load failed.")
677     END IF
678     SUBEXIT
679 Main_ld_bad:!
680     OFF ERROR 
681     CALL User_error("Load failed: "&ERRM$)
682     DISP "Initializing system"
683     Cnfg_cnfg
684     Cnfg_init
685     Diag_init
686     Main_appl_init  ! Reinitialize system
687     SUBEXIT
688 Main_ld_badfile:!
689     OFF ERROR 
690     SUBEXIT
691   SUBEND
692   ! PAGE -> 
693   !************************************************************************
694 Main_marquee:SUB Main_marquee
695     !
696     !  This subprogram puts up the pretty picture when SPAM is first run.
697     !
698     CALL User_clr_scr
699     GRAPHICS ON
700     INTEGER A(0:5)
701     GESCAPE CRT,3;A(*)       !gets CRT pixel size in A(*)
702     X_pixels=A(2)
703     IF X_pixels>1000 THEN 
704       Char_size=8*FNPlot_good_csize
705     ELSE
706       Char_size=4*FNPlot_good_csize
707     END IF
708     Plot_set_viewp(1,1,0,0,16)
709     CALL Plot_background
710     WINDOW 0,1,0,1
711     LORG 4
712     PEN 2
713     MOVE .5,.7
714     CALL Plot_bold_label(Char_size,"HP3565S")
715     MOVE .5,.55
716     CALL Plot_bold_label(Char_size,"S P A M")
717     LORG 4
718     PEN 5
719     MOVE .5,.35
720     CALL Plot_bold_label(Char_size/3,"Digital Scope")
721     CALL Plot_bold_label(Char_size/3,"Frequency Response")
722     CALL Plot_bold_label(Char_size/3,"Power Spectral Density")
723     CALL Plot_bold_label(Char_size/3,"Throughput")
724     LORG 4
725     PEN 6
726     MOVE .68,.37
727     CALL Plot_bold_label(Char_size/3,"*")
728     LORG 4
729     PEN 6
730     MOVE .37,.05
731     CALL Plot_bold_label(Char_size/4,"* Enhanced")
732     !
733     ! now plot fancy frame
734     PEN 1
735     FOR I=0 TO 3
736       Plot_set_viewp(1,1,0,0,I)
737       FRAME
738     NEXT I
739     PEN 2     !red
740     FOR I=4 TO 7
741       Plot_set_viewp(1,1,0,0,I)
742       FRAME
743     NEXT I
744     PEN 6  !brick red
745     FOR I=8 TO 11
746       Plot_set_viewp(1,1,0,0,I)
747       FRAME
748     NEXT I
749     PEN 1
750   SUBEND
751   ! PAGE -> 
752   !************************************************************************