HTBasic Help
×
Menu
Index

Example: Function Generator

 
10     ! *********************************************************************
20     ! Example: Function Generator
30     !
40     ! This program shows how a panel, menu, and pushbuttons can be
50     ! used to construct a front panel for a function generator.
60     !
70     ! *********************************************************************
80     !
90     ! This part of the program creates a panel with one menu selection.
100   ! Four menu buttons are put into the menu. When any of these menu
110   ! items is selected, an appropriate subroutine is called.
120   !
130   DIM Attr$(3)[15],Attr(3)
140   COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
150   ASSIGN @Fgen_panel TO WIDGET "PANEL";SET ("TITLE":" Example: Function Generator","X":150,"Y":80,"WIDTH":240,"HEIGHT":200,"MAXIMIZABLE":0,"RESIZABLE":0)
160   CONTROL @Fgen_panel;SET ("SYSTEM MENU":"Quit")
170   ON EVENT @Fgen_panel,"SYSTEM MENU" GOTO Finis
180   !
190   ASSIGN @Fgen_main TO WIDGET "PULLDOWN MENU";SET ("LABEL":"Control Menu"),PARENT @Fgen_panel
200   ASSIGN @Frequency TO WIDGET "MENU BUTTON";SET ("LABEL":"Frequency"),PARENT @Fgen_main
210   ASSIGN @Amplitude TO WIDGET "MENU BUTTON";SET ("LABEL":"Amplitude"),PARENT @Fgen_main
220   ASSIGN @Dc_offset TO WIDGET "MENU BUTTON";SET ("LABEL":"DC Offset"),PARENT @Fgen_main
230   ASSIGN @Function TO WIDGET "MENU BUTTON";SET ("LABEL":"Function"),PARENT @Fgen_main
240   ASSIGN @Modulation TO WIDGET "CASCADE MENU";SET ("LABEL":"Modulation"),PARENT @Fgen_main
250   ASSIGN @Am TO WIDGET "MENU TOGGLE";SET ("LABEL":"AM"),PARENT @Modulation
260   ASSIGN @Pm TO WIDGET "MENU TOGGLE";SET ("LABEL":"PM"),PARENT @Modulation
270   !
280   !  Initial values for the controls
290   !
300   Freq=1000
310   Ampl=.001
320   Ampl_unit=0
330   Offset=0
340   Func=0
350   !
360   ! Displays for the values of the controls. The displays are actually
370   ! pushbuttons and the label for each button is used to display its
380   ! current value.
390   !
400   Attr$(0)="X"
410   Attr$(1)="Y"
420   Attr$(2)="WIDTH"
430   Attr$(3)="HEIGHT"
440   Attr(0)=30                   ! X position
450   Attr(1)=8                    ! Y position
460   Attr(2)=178                  ! width
470   Attr(3)=33                   ! height
480   !
490   ASSIGN @Freq_disp TO WIDGET "PUSHBUTTON";SET (Attr$(*):Attr(*),"LABEL":VAL$(Freq)&" Hz"),PARENT @Fgen_panel
500   Attr(1)=Attr(1)+Attr(3)
510   ASSIGN @Ampl_disp TO WIDGET "PUSHBUTTON";SET (Attr$(*):Attr(*),"LABEL":VAL$(Ampl)&" V p-p"),PARENT @Fgen_panel
520   Attr(1)=Attr(1)+Attr(3)
530   ASSIGN @Offs_disp TO WIDGET "PUSHBUTTON";SET (Attr$(*):Attr(*),"LABEL":VAL$(Offset)&" V offset"),PARENT @Fgen_panel
540   Attr(1)=Attr(1)+Attr(3)
550   ASSIGN @Func_disp TO WIDGET "PUSHBUTTON";SET (Attr$(*):Attr(*),"LABEL":"SINE"),PARENT @Fgen_panel
560   !
570   ! When either the menu is pulled down, or the display is clicked, call
580   ! a routine to change that control.
590   !
600   ON EVENT @Frequency,"ACTIVATED",1 CALL Set_frequency
610   ON EVENT @Function,"ACTIVATED",1 CALL Set_function
620   ON EVENT @Amplitude,"ACTIVATED",1 CALL Set_amplitude
630   ON EVENT @Dc_offset,"ACTIVATED",1 CALL Set_offset
640   ON EVENT @Freq_disp,"ACTIVATED",1 CALL Set_frequency
650   ON EVENT @Func_disp,"ACTIVATED",1 CALL Set_function
660   ON EVENT @Ampl_disp,"ACTIVATED",1 CALL Set_amplitude
670   ON EVENT @Offs_disp,"ACTIVATED",1 CALL Set_offset
680   !
690   ! Event handling for modulation toggles in the menu
700   !
710   ON EVENT @Am,"CHANGED",1 CALL Toggle_am
720   ON EVENT @Pm,"CHANGED",1 CALL Toggle_pm
730   !
740   LOOP
750     WAIT FOR EVENT
760   END LOOP
770 Finis: END
780   SUB Set_frequency
790   !
800   ! This routine sets the value of frequency.
810   !
820     COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
830     !
840     ! The user is allowed to enter the new frequency in any of three units.
850     ! A cancel button is included in case the user makes a mistake.
860     !
870     DIM Btn$(3)[6],Freq$[20]
880     Btn$(0)="Hz"
890     Btn$(1)="kHz"
900     Btn$(2)="MHz"
910     Btn$(3)="Cancel"
920     !
930     ! Use a STRING dialog to get the new frequency. This dialog returns
940     ! a string so a conversion must be done.
950     !
960     DIALOG "STRING","",Btn;SET ("VALUE":VAL$(Freq),"TITLE":"Enter Frequency","DIALOG BUTTONS":Btn$(*),"DEFAULT BUTTON":0),RETURN ("VALUE":Freq$)
970     !
980     IF Btn=3 THEN SUBEXIT              ! Cancel was clicked
990     ON ERROR GOTO Cant_convert
1000    Freq=VAL(Freq$)                    ! convert to a number
1010    OFF ERROR
1020    !
1030    ! The value is checked for validity. The valid range might depend on
1040    ! function, but that case is not handled.
1050    !
1060    Freq=DROUND(Freq*10^(3*Btn),11)    ! apply the suffix and round
1070    IF Freq>2.0E+7 THEN Frequ=2.0E+7
1080    CONTROL @Freq_disp;SET ("LABEL":VAL$(Freq)&" Hz")
1090    !
1100    ! If actual instruments were being controlled, the OUTPUT statement
1110    ! would be here.
1120    !
1130    SUBEXIT
1140 Cant_convert:   !
1150    !
1160    ! The string could not be converted to a number. Display an error
1170    ! message and ask again.
1180    !
1190    DIALOG "ERROR",Freq$&CHR$(10)&"is not recognizable as a number.";SET ("TITLE":"Can't convert to a number")
1200    OFF ERROR
1210    GOTO 960
1220  SUBEND
1230  SUB Set_function
1240    COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
1250    DIM Func$(5)[10]
1260    Func$(0)="SINE"
1270    Func$(1)="SQUARE"
1280    Func$(2)="TRIANGLE"
1290    Func$(3)="POS RAMP"
1300    Func$(4)="NEG RAMP"
1310    Func$(5)="DC only"
1320    !
1330    ! The button value is placed in a temporary variable in case Cancel
1340    ! is clicked. Only if OK is clicked is the value transferred to
1350    ! the actual variable which contains the function.
1360    !
1370    DIALOG "LIST","",Btn;SET ("TITLE":"Select Function","ITEMS":Func$(*),"SELECTION":Func,"DEFAULT BUTTON":0),RETURN ("SELECTION":A)
1380    IF Btn=1 THEN SUBEXIT
1390    Func=A
1400    CONTROL @Func_disp;SET ("LABEL":Func$(Func))
1410    !
1420    ! If DC only function is selected then the amplitude control has
1430    ! no effect.  The button and menu are deactivated.
1440    !
1450    IF Func=5 THEN
1460      CONTROL @Ampl_disp;SET ("SENSITIVE":0)
1470      CONTROL @Amplitude;SET ("SENSITIVE":0)
1480    ELSE
1490      CONTROL @Ampl_disp;SET ("SENSITIVE":1)
1500      CONTROL @Amplitude;SET ("SENSITIVE":1)
1510    END IF
1520  SUBEND
1530  SUB Set_amplitude
1540    COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
1550    DIM Btn$(5)[7],Ampl$[20]
1560    Btn$(0)=" V p-p"
1570    Btn$(1)=" mV p-p"
1580    Btn$(2)=" V RMS"
1590    Btn$(3)=" mV RMS"
1600    Btn$(4)=" dBm"
1610    Btn$(5)="Cancel"
1620    DIALOG "STRING","",Btn;SET ("VALUE":VAL$(Ampl),"TITLE":"Enter Amplitude","DIALOG BUTTONS":Btn$(*),"DEFAULT BUTTON":0),RETURN ("VALUE":Ampl$)
1630    IF Btn=5 THEN SUBEXIT             ! Cancel was clicked
1640    ON ERROR GOTO Cant_convert
1650    Ampl=VAL(Ampl$)
1660    OFF ERROR
1670    Ampl_unit=Btn
1680    IF Btn=1 OR Btn=3 THEN
1690      Ampl=Ampl*.001                  ! A mV button was selected
1700      Ampl_unit=Ampl_unit-1           ! Change to V unit
1710    END IF
1720    IF Btn<4 THEN
1730      !
1740      ! A volt button was used. Round and check for limits. The limit
1750      ! might also depend on the dc offset.
1760      !
1770      Ampl=ABS(PROUND(Ampl,-3))
1780      IF Ampl>5 THEN Ampl=5
1790    ELSE
1800      !
1810      ! dBm was selected. Round and check for limits.
1820      !
1830      Ampl=PROUND(Ampl,-2)
1840      IF Ampl>13 THEN Ampl=13
1850      IF Ampl<-60 THEN Ampl=-60
1860    END IF
1870    CONTROL @Ampl_disp;SET ("LABEL":VAL$(Ampl)&Btn$(Ampl_unit))
1880    SUBEXIT
1890 Cant_convert:   !
1900    DIALOG "ERROR",Ampl$&CHR$(10)&"is not recognizable as a number.";SET ("TITLE":"Can't convert to a number")
1910    GOTO 1620
1920  SUBEND
1930  SUB Set_offset
1940    COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
1950    DIM Btn$(2)[6],Offs$[20]
1960    Btn$(0)=" V"
1970    Btn$(1)=" mV"
1980    Btn$(2)="Cancel"
1990    DIALOG "STRING","",Btn;SET ("VALUE":VAL$(Offset),"TITLE":"Enter DC Offset","DIALOG BUTTONS":Btn$(*),"DEFAULT BUTTON":0),RETURN ("VALUE":Offs$)
2000    IF Btn=2 THEN SUBEXIT  ! Cancel was selected
2010    ON ERROR GOTO Cant_convert
2020    Offset=VAL(Offs$)
2030    OFF ERROR
2040    IF Btn=1 THEN Offset=Offset*.001            ! mV button
2050    Offset=PROUND(Offset,-3)                    ! Round to 3 digits
2060    !
2070    IF ABS(Offset)>5 THEN Offset=SGN(Offset)*5  ! no more than 5 V offset
2080    CONTROL @Offs_disp;SET ("LABEL":VAL$(Offset)&" V offset")
2090    SUBEXIT
2100 Cant_convert:   !
2110    DIALOG "ERROR",Offs$&CHR$(10)&"is not recognizable as a number.";SET ("TITLE":"Can't convert to a number")
2120    GOTO 1990
2130  SUBEND
2140  SUB Toggle_am
2150    COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
2160  !
2170  ! The menu widgets handle displaying whether modulation is on or
2180  ! off automatically. This routine determines what the state is and
2190  ! does the appropriate I/O.
2200  !
2210    STATUS @Am;RETURN ("VALUE":State)
2220    IF State THEN
2230  !
2240  ! Send the command to turn AM on
2250  !
2260    ELSE
2270  !
2280  ! Send the command to turn AM off
2290  !
2300    END IF
2310  SUBEND
2320  SUB Toggle_pm
2330    COM /Fgen/Freq,Ampl,Ampl_unit,Func,Offset,@Freq_disp,@Ampl_disp,@Offs_disp,@Func_disp,@Amplitude,@Am,@Pm
2340  !
2350  ! The menu widgets handle displaying whether modulation is on or
2360  ! off automatically. This routine determines what the state is and
2370  ! then does the appropriate I/O.
2380  !
2390    STATUS @Pm;RETURN ("VALUE":State)
2400    IF State THEN
2410  !
2420  ! Send the command to turn PM on
2430  !
2440    ELSE
2450  !
2460  ! Send the command to turn PM off
2470  !
2480    END IF
2490  SUBEND