Classic Computer Magazine Archive COMPUTE! ISSUE 64 / SEPTEMBER 1985 / PAGE 113

128
Sound
And Music

Part 2

Philip I. Nelson
Assistant Editor


The second installment of this two-part article explores the Commodore 128's FILTER, SOUND, and PLAY commands and includes three short demonstration programs.


In Part 1 (COMPUTE!, August 1985), we discussed the Commodore 128's VOL, TEMPO, and ENVELOPE commands as well as the basics of sound envelopes and waveforms. This month we'll examine the three remaining sound commands: FILTER, SOUND, and PLAY. Since your 128 User's Guide explains the fundamentals, we'll focus on less obvious features and note how these complex commands interact with one another.

FILTER Needs PLAY
Like the ENVELOPE command (see Part 1), FILTER does nothing noticeable until you turn the filter on with a PLAY statement. Insert X1 inside the PLAY string wherever you want to turn the filter on, and X0 where you want to turn it off. If you leave out the X parameter, PLAY ignores preceding FILTER commands (the filter remains off). In the simplest case (a FILTER command followed by PLAY"X1"), the filter affects all three voices. However, you can also filter each voice individually:

FILTER 1000,1,0,0,15
PLAY "V1 X1 V2 X0 V3 X0

    These statements turn the lowpass filter on for voice 1 and turn it off for voices 2 and 3. The 128 remembers which voice to filter when it executes subsequent PLAY statements (more about multivoice music is explained below). However, you can use only one filter setting at a time. For instance, you can't use a low-pass filter for voice 1 and a band-pass filter for voice 2. Whenever X1 appears in a PLAY string, the 128 uses the most recent FILTER setting. If no FILTER command has been executed, this may result in silence.

A FILTER Editor
As with other sound effects, the best way to learn is to listen and experiment; Program 1 below, "128 FILTER Editor," lets you do just that. It's self-prompting, so you need only type it in, save a copy, and run it. The menu screen displays all the current filter parameters and lets you change whatever you like. To select any option, press a number key from 0 to 9 and follow the prompts. The program begins with no filtering (all filters off) for comparison.
    Option 9 switches you to the display screen, plays an ascending musical scale with whatever filtering you've selected, and displays the FILTER statement currently in effect. Once you find a filter setting you like, write down the FILTER statement displayed on the screen and use it in your own programs. From this screen the number keys 1-6 select different octaves for the scale. Press the space bar to return to the main screen.
    Option 7 lets you select any of the 128's ten predefined instrument envelopes, and option 8 controls the tempo at which the scale is played. Note that some of the predefined envelopes don't work well at fast tempos: The note ends before the sound envelope can complete its natural cycle. Use a slower tempo to slow things down and study a particular effect.
    The SID filter is a bit notorious. While it works fine on some machines (my old 64 has a great one), its performance may vary from one SID chip to the next. The manual for our preproduction 128 notes that filtering "cannot be counted on," suggesting that nothing was done to improve the 128's filter. With practice you should be able to achieve satisfactory effects on your own machine, though they might sound somewhat different on another computer.

The SOUND Command
SOUND is a very powerful command intended for sound effects rather than music. Unlike PLAY (which defaults to maximum volume), SOUND has a default volume setting of zero. Thus, you must turn the volume up with VOL before the first SOUND statement in a program. And whereas PLAY delays the rest of your program until it completes the current PLAY string, SOUND statements play "in the background" while the program continues. To demonstrate, enter NEW and press RUN/STOP-RESTORE (to clear the SID chip), then type in and run the following two-line program:

10 VOL15:SOUND 1,5000,200:SOUN
   D 2,4000,200:SOUND 3,3000,2
   00
20 FORJ=1T010:PRINT"PROGRAM CO
   NTINUING":NEXT:PRINT"DONE"

    Notice how the three-voice sound continues even after this program ends and returns the computer to READY mode.
    The first number in a SOUND statement (1, 2, or 3) picks one of the 128's three voices. By using dif ferent voice numbers, you can play up to three sounds at once. However, the 128 ordinarily waits until a voice has finished the current SOUND statement before starting a new SOUND statement for that voice. To illustrate, in line 10 of the above program, change the 2 and 3 to 1; then run it again. Now voice 1 plays three notes in sequence.
    In most cases SOUND'S background-playing ability is desirable: Sound effects don't slow down the rest of your program. However, in other cases you might want to interrupt a sound immediately (if, for example, the user wants to exit the program). Fortunately, this is easy to do: SOUND statements with zero duration take effect immediately, whether or not preceding sounds have finished. Thus, SOUND 1,0,0 silences voice 1; use FOR J=1 TO 3: SOUND J,0,0: NEXT to silence all three voices.
    Since variables can be used for any SOUND parameter, you can create more dynamic, integrated ef fects by incorporating other program variables in SOUND commands. For example, say that your game uses the variable X to represent a spaceship's screen position. To make a cruising sound, you might substitute something like X*1000 for the frequency number in a SOUND command.

A SOUND Editor
"128 SOUND Editor," listed below, lets you experiment with SOUND commands and design sound effects for your own programs using up to three voices at once. Type in and save Program 2, then run it. The first thing you'll hear are three complex, multivoice sound effects (don't worry if they're not exactly to your taste-you'll soon know enough about SOUND to replace them with your own). Next, the editing screen appears, displaying ten options and all the current SOUND parameters (your User's Guide explains the meaning of each parameter). To choose an option, press a number key from 0 to 9. The program instructs you how to proceed and does not let you enter inappropriate values.
    Option 1 lets you switch from one voice to another. Option 9 switches you to the display screen, which plays the current sound and displays the SOUND statements that create it. It's fun to experiment with 128 SOUND Editor, and it can save a lot of programming time. Use it to design exactly the sound you want, then copy the SOUND statements from the display screen and use them in your programs. (Though the program can play sounds with one, two, or three voices at once, it's not necessary to use multiple voices. Zero-duration SOUND statements produce no sound and may be ignored.)

The PLAY Command
Designed for real music-making, PLAY is the most versatile of all the 128's sound commands. As outlined in the User's Guide, PLAY works much like the familiar PRINT statement. Each PLAY command is followed by a string containing special control characters. The letters A-F are interpreted as notes; thus, the statement PLAY"C D E F" plays the four notes C-D-EF. In the last example PLAY was followed by a string of characters enclosed in quotation marks. However, PLAY can also handle string variables (A$ = "C D E F": PLAY A$).
    To see this method at work, type in and save Program 3, "128 PLAY Demonstrator." It plays a short, Bach-like tune with several different instrument envelopes. Note that all of the music control characters are stored in DATA statements. Line 50 READS each line of data into a string named A$, and the subroutine at line 20 PRINTs each music string just before it is PLAYed.
    Like other strings, PLAY strings can be concatenated (combined) with the + operator, and manipulated with any of the stringrelated functions: MID$, LEFT$, RIGHT$, LEN, VAL, CHR$, ASC, and STR$. Program 1 contains several different examples.
    For complex music you might want to store PLAY strings in a string array. For instance, the following statement stores 100 elements of music data in a string array named M$( ): FOR J=1 TO 100: READ M$(J): NEXT. Once the music array is created, you can quickly access any string it contains: PLAY M$(3) plays the third music string held in M$( ), and so on. This is very helpful for repeating certain passages. You may also find it useful to create separate arrays for different purposes (one to store notes, another for duration characters, and so forth).

Multivoice Music
Since the SID chip has three voices, PLAY can play up to three notes simultaneously. The V control character (followed by 1, 2, or 3) determines which voice is affected. Thus, the statement PLAY "V1 C V2 E V3 G" plays a simple three-note chord. After processing V1 C, the 128 "looks ahead" to see whether it should play other notes at the same time; however, the computer looks ahead only as far as the next note. Thus, the statement PLAY "V1 CDE V2 CDE" does not play the notes C-D-E simultaneously with two voices. Instead, it plays two sequential notes (C-D) with voice 1, then two simultaneous notes (E and C) with voices 1 and 2, followed by two sequential notes (D-E) with voice 2.
    When all voices play notes of the same duration, multivoice music is not particularly difficult to write: Insert V1 before each note for voice 1, V2 before each voice 2 note, and so forth (concatenations like A$="V1"+A$ can help condense the otherwise cumbersome code). However, when different voices play notes of different durations, you must make sure that all the durations add up.
    For instance, you might want voice 1 to hold a long whole note while voice 2 plays a series of six teenth notes. To keep the timing straight, you should not let voice 1 play another note until voice 2 has finished the equivalent of a whole note (16 sixteenths or whatever). Similarly, the timing may be thrown off if voice 2 plays more than 16 sixteenths before voice 1 gets back in the act. The M control character supposedly tells the 128 to wait until all voices finish the current measure before moving ahead. But M is just an adjuster. It can't magically repair music that doesn't add up in the first place.

Interactions
As noted throughout this article, certain 128 sound commands work with certain others. The VOL command, for instance, is needed only for SOUND statements (PLAY sets volume independently with the U control character). TEMPO, FILTER, and ENVELOPE, on the other hand, seem designed to work with PLAY. TEMPO is irrelevant to SOUND (which sets its own duration and so on); ENVELOPE and FILTER have no effect until activated by PLAY.
    However, other interactions are possible (at least on our 128, admittedly a preproduction model). For instance, though the SOUND statement provides no way to turn on the filter, SOUNDS can be affected by "leftover" filter settings. If the 128 executes a FILTER statement followed by PLAY"X1", the filter remains on and affects subsequent SOUND statements. PLAY"X0" turns the filter off for SOUND as well as for PLAY.
    This interaction can be viewed either as an advantage-filtering is otherwise unavailable with SOUND-or as a pitfall for unwary programmers. To prevent unwanted interactive effects, begin sound and music programs by setting all sound parameters at zero or default values. Commodore 64 programmers often clear the SID chip with FOR J=54272 TO 54296: POKE J,0: NEXT. Though this statement does clear the 128's SID chip, it doesn't necessarily change the 128's sound settings, which are recorded elsewhere in memory.

For instructions on entering these listings,
please refer to "COMPUTE!'s Guide to Typing
In Programs" published bimonthly in COMPUTE!.

Program 1: 128 FILTER
Editor


100 GOSUB570:GOTO310
110 FORD=1TO3:SOUNDJ,0,0:NEXT:
    FILTER0,0,0,0,0:RETURN
120 PLAY A$:RETURN
130 LP$=" OFF":IFLP=1THENLP$="
     {RVS}ON {OFF}"
140 RETURN
150 BP$=" OFF":IFBP=ITHENBP$="
     {RVS}ON {OFF}"
160 RETURN
170 HP$=" OFF":IFHP=1THENHP$="
     {RVS}ON {OFF}"
180 RETURN
190 PRINTD$"SET CUTOFF FREQUEN
    CY (0-2047)"
200 INPUTA:IFA<0ORA>2047THENGO
    SUB550:GOTO190
210 FQ=A:RETURN
220 LP=ABS(LP=0):RETURN
230 BP=ABS(BP=0):RETURN
240 HP=ABS(HP=0):RETURN
250 PRINTD$"SET FILTER RESONAN
    CE (0-15)":INPUTA:IFA<0ORA
    >15THENGOSUB550:GOTO250
260 RE=A:RETURN
270 PRINTD$"CHOOSE SOUND ENVEL
    OPE (0-9)":INPUTA:IFA<0ORA
    >9THENGOSUB550:GOTO270
280 WV$="T"+CHR$(A+48):RETURN
290 PRINTD$"CHOOSE TEMPO (1-25
    5)":INPUTA:IFA<1ORA>255THE
    NGOSUB550:GOTO290
300 TM=A:RETURN
310 PRINT"{CLR}{RVS} 128 FILTE
    R EDITOR ":PRINT
320 PRINT"1 {RVS} FREQUENCY
    {OFF}"FQ"{LEFT}{4 SPACES}"
330 PRINT"2 {RVS} LOW
    {2 SPACES}PASS {OFF)";:GOS
    UB130:PRINTLP$
340 PRINT"3 {RVS} BAND PASS
    {OFF}";:GOSUB150:PRINTBP$
350 PRINT"4 {RVS} HIGH PASS
    {OFF}";:GOSUB170:PRINTHP$
360 PRINT"5 {RVS} RESONANCE
    {OFF}";RE"{LEFT} ":PRINT"
    {2 SPACES}(RVS)-----------
    {OFF}"
370 PRINT"7 {RVS} ENVELOPE
    {2 SPACES}(OFF} "MID$(WV$,
    2)T$(VAL(MID$(V;V$,2)))
380 PRINT"8 (RVS) TEMPO
    {5 SPACES}{OFF}"TM"{LEFT}
    {2 SPACES}":PRINT"9 {RVS}
    {SPACE}PLAY{6 SPACES}{OFF}
    ":PRINT"0 {RVS} QUIT
    {6 SPACES}{OFF}{DOWN}"
390 PRINT"{RVS}ENTER YOUR CHOI
    CE (0-9)":PRINT"(3 SPACES)
    {UP}"
400 GETKEYA$:IFA$<"0"ORA$>"9"O
    RA$="6"THENPRINT:GOSUB550:
    PRINT:GOTO390
410 IFA$="9"THEN440
420 IFA$="0"THENEND
430 ONVAL(A$)GOSUB190,220,230,
    240,250,250,270,290:PRINTE
    $:GOTO320
440 PRINTCHR$(147)"OCTAVE "MID
    $(OC$,2)CHR$(13)
450 PRINT"LOW{2 SPACES}PASS "L
    P$:PRINT"BAND PASS "BP$:PR
    INT"HIGH PASS "HP$:PRINT
460 PRINT"{RVS}CURRENT FILTER
    {SPACE}STATEMENT:":PRINT:P
    RINT"FILTER ";
470 PRINTMID$(STR$(FQ),2)","MI
    D$(STR$(LP),2)","MID$(STR$
    (BP),2)","
480 PRINTMID$(STR$(HP),2)","MI
    D$(STR$(RE),2):PRINT:FILTE
    R FQ,LP,BP,HP,RE
490 PRINT"PRESS {RVS} 1 - 6
    {OFF} FOR OCTAVE"CHR$(13)S
    PC(6)"{RVS} SPACE {OFF} TO
     EXIT"
500 F$="X0 ":IFLP=1ORBP=1ORHP=
    1THENF$="X1 "
510 A$=F$+WV$+"S":GOSUB120:TEM
    PO TM
520 GET B$:IFB$=CHR$(32)THENGO
    SUB110:GOTO310
530 IFB$=>"1"ANDB$<="6"THENOC$
    ="O"+CHR$(VAL(B$)+48):PRIN
    T"{HOME}"SPC(6)VAL(B$)
540 A$=OC$+"CDEFGAB":GOSUB120:
    GOTO520
550 GOSUB110:FORJ=1TO3:SOUNDJ,
    1000+J*500,15,0,0,0,2,J*10
    00:NEXT
560 PRINT"(UP}{RVS)INAPPROPRIA
    TE":SLEEP1:PRINT"{UP}
    {13 SPACES}{3 UP}":RETURN
570 PRINTCHR$(14)CHR$(8):FORJ=
    54272TO54296:POKEJ,0:NEXT:
    VOL15:D$=CHR$(19)
580 FORJ=1TO15:D$=D$+CHR$(17):
    NEXT:FQ=1000:LP=0:BP=0:HP=
    0:RE=15:WV$="T7":TM=55
590 FORJ=1TO35:X$=X$+CHR$(32):
    NEXT:E$=D$+X$+CHR$(13)+X$+
    CHR$(19)+CHR$(13)
600 FORJ=0TO9:READX$:T$(J)="
    {2 SPACES}"+X$:NEXT:OC$="O
    3":GOSUB110:RETURN
610 DATA"PIANO(6 SPACES}","ACC
    ORDION{2 SPACES}","CALLIOP
    E{3 SPACES}","DRUM
    {7 SPACES}","FUTE
    {6 SPACES}"
620 DATA"GUITAR{5 SPACES}","HA
    RPSICHORD","ORGAN
    {6 SPACES}","TRUMPET
    {4 SPACES}","XYLOPHONE
    {2 SPACES}"


Program 2: 128 SOUND
Editor


10 GOSUB30:GOSUB570:GOTO320
20 PRINT"{CLR}{RVS}128 SOUND E
   DITOR":PRINT:RETURN
30 FORJ=ITO3:SOUNDJ,0,0:NEXT:R
   ETURN
40 PRINTD$"CHOOSE VOICE (1-3)"
   :INPUTA:IFA<1ORA>3THENGOSUB
   550:GOTO40
50 VC=A:RETURN
60 PRINTD$"CHOOSE FREQUENCY (0
   -65535)"
70 INPUTA:IFA<0ORA>65535THENGO
   SUB550:GOTO60
80 FQ(VC)=A:RETURN
90 PRINTD$"CHOOSE DURATION (60
   0=10 SECONDS)"
100 INPUTA:IFA<0THENGOSUB550:G
    OTO90
110 DU(VC)=A:RETURN
120 PRINTD$"CHOOSE DIRECTION O
    F SOUND SWEEP"
130 PRINT"0=UP{2 SPACES}1=DOWN
    {2 SPACES}2=OSCILLATE":INP
    UTA:IFA<0ORA>2THENGOSUB550
    :GOTO120
140 DI(VC)=A:RETURN
150 PRINTD$"CHOOSE MINIMUM FRE
    QUENCY FOR"
160 PRINT"SOUND SWEEP (0-65535
    )":INPUTA:IFA<0ORA>65535TH
    ENGOSUB550:GOTO150
170 IFA=>FQ(VC)THENGOSUB550:GO
    TO150
180 MI(VC)=A:RETURN
190 PRINTD$"CHOOSE STEP VALUE
    {SPACE}FOR SOUND SWEEP"
200 PRINT"(LESSER OF 32767 OR"
    FQ(VC)-MI(VC)+1"{LEFT})"
210 INPUTA:IFA<0ORA>32767THENG
    OSUB550:GOTO190
220 IFA>(FQ(VC)-MI(VC))THENGOS
    UB550:GOTO190
230 SV(VC)=A:RETURN
240 PRINTD$"CHOOSE WAVEFORM
    {SHIFT-SPACE}(5 SPACES}0=T
    RIANGLE"
250 PRINT"1=SAWTOOTH{2 SPACES}
    2=PULSE{2 SPACES}3=WHITE N
    OISE"
260 INPUTA:IFA<0ORA>3THENGOSUB
    550:GOTO240
270 WV(VC)=A:RETURN
280 PRINTD$"CHOOSE PULSE WIDTH
    "
290 PRINT"(0-4095)":INPUTA:IFA
    <0ORA>4095THENGOSUB550:GOT
    O280
300 PW(VC)=A:RETURN
310 GOSUB20
320 PRINT-1 {RVS} VOICE
    {6 SPACES}{OFF}"VC:PRINT"2
     {RVS} FREQUENCY{2 SPACES}
    {OFF}"FQ(VC)"{LEFT}
    {4 SPACES}"
330 PRINT"3 {RVS} DURATION
    {3 SPACES}{OFF}"DU(VC)"
    {LEFT}{4 SPACES}"
340 PRINT"4 {RVS} DIRECTION
    {2 SPACES}{OFF}"DI(VC)DI$(
    DI(VC))
350 PRINT"5 {RVS} MINIMUM
    {4 SPACES}{OFF}"MI(VC)"
    {LEFT}{4 SPACES}":PRINT"6
    {SPACE}{RVS} STEP VALUE
    {OFF}"SV(VC)"{LEFT}
    {4 SPACES}"
360 PRINT"7 {RVS} WAVEFORM
    {3 SPACES}{OFF}"WV(VC)WV$(
    WV(VC))
370 PRINT"8 {RVS} PULSEWIDTH
    {OFF}"PW(VC)"{LEFT}
    {4 SPACES}"
380 PRINT"9 {RVS} HEAR SOUND
    {OFF}":PRINT"0 {RVS} QUIT
    {7 SPACES}{OFF}":PRINT
390 PRINT"{RVS}ENTER YOUR CHOI
    CE (0-9)":PRINT"{3 SPACES}
    {UP}"
400 GETKEYA$:IFA$<"0"ORA$>"9"T
    HENPRINT:GOSUB550:PRINT:GO
    TO390
410 IFA$="9"THEN440
420 IFA$="0"THENGOSUB30:END
430 ONVAL(A$)GOSUB40,60,90,120
    ,150,190,240,280:PRINTE$:G
    OTO320
440 PRINT"{CLR}THE FOLLOWING S
    OUND STATEMENTS":PRINT"
    {2 SPACES}CREATE THE SOUND
    S YOU HEAR."
450 PRINT"ZERO-DURATION SOUNDS
     ARE SILENT."
460 FORJ=ITO3:SOUNDJ,FQ(J),DU(
    J),DI(J),MI(J),SV(J),WV(J)
    ,PW(J):NEXT
470 FORJ=1TO3:PRINT:PRINT"SOUN
    D ";
480 PRINTMID$(STR$(J),2)","MID
    $(STR$(FQ(J)),2)","MID$(ST
    R$(DU(J)),2)",";
490 PRINTMID$(STR$(DI(J)),2)",
    "MID$(STR$(MI(J)),2)","MID
    $(STR$(SV(J)),2)",";
500 PRINTMID$(STR$(WV(J)),2)",
    "MID$(STR$(PW(J)),2):NEXT
510 PRINT:PRINT"PRESS (RVS)RET
    URN{OFF} TO E(IT":PRINTSPC
    (6)"{RVS}SPACE {OFF} TO RE
    PEAT"
520 GETKEYA$:IFA$=CHR$(13)THEN
    GOSUB30:GOTO310
530 IFA$=CHR$(32)THENGOSUB30:G
    OTO440
540 GOTO520
550 GOSUB30:FORJ=1TO3:SOUNDJ,1
    000+J*500,15,0,0,0,2,J*100
    0:NEXT
560 PRINT"{UP}{RVS)INAPPROPRIA
    TE":SLEEP1:PRINT"{UP}
    {13 SPACES}{3 UP}":RETURN
570 PRINTCHR$(14):D$=CHR$(19):
    FORJ=54272TO54296:POKEJ,0:
    NEXT:FORJ=1TO15
580 D$=D$+CHR$(17):NEXT:GOSUB2
    0:VOL15:FORJ=1TO38:X$=X$+C
    HR$(32):NEXT
590 VC=1:E$=D$+X$+CHR$(13)+X$+
    CHR$(13)+X$+CHR$(19)+CHR$(
    13)
600 FORK=2000TO4000STEP220:FOR
    J=1T03:SOUNDJ,K*2+J*20,45,
    2,K,K/3,2,4095-K
610 NEXTJ,K:FORJ=45TOlSTEP-5:S
    OUND1,J*1000,5,1,J*100,J*2
    80,2,2300
620 SOUND2,3200-J*20,5,0,0,0,2
    ,1500:SOUND3,J*1200,5,1,J*
    120,J*300,2,3000
630 NEXT:FORJ=1TO3:SOUNDJ,1000
    0,200,1,J*2000,J*400,2,230
    0:NEXT:FORJ=1TO3
640 READFQ(J),DU(J),DI(J),MI(J
    ),SV(J),WV(J),PW(J):NEXT:F
    ORJ=0TO3:READA$
650 WV$(J)="--- "+A$:NEXT:FORJ
    =0TO2:READA$:DI$(J)="--- "
    +A$:NEXT:RETURN
660 DATA10000,260,2,2000,60,2,
    2000,0,0,0,0,0,0,2000,0,0,
    0,0,0,0,2000
670 DATA"TRIANGLE","SAWTOOTH",
    "PULSE{3 SPACES}","NOISE
    {3 SPACES}"
680 DATA"UPWARD{3 SPACES}","DO
    WNWARD ","OSCILLATE"


Program 3: 128 PLAY
Demonstrator


10 GOTO30
20 PRINTA$:PLAYA$:RETURN
30 PRINTCHR$(147)CHR$(14)SPC(3
   )CHR$(18)"128 PLAY DEMONSTR
   ATOR"CHR$(13)
40 FORJ=54272TO54296:POKEJ,0:N
   EXT:FILTER0,0,0,0:FORJ=1TO3
   :SOUNDJ,0,0:NEXT
50 READA$:IFA$<>"Z"THENGOSUB20
   :GOTO50
60 PRINT:PRINTSPC(2)CHR$(18)"P
   RESS P TO PLAY AGAIN, Q TO
   {SPACE}QUIT"
70 GETKEYG$:IFG$="P"THENRUN
80 IFG$<>"Q"THEN70
90 END
100 DATA U15 X0 V1 S
110 DATA T7 O5 C O4 B O5 IC SO
    4 GRERGR
120 DATA T6 CDC O3 B O4 IC SO3
     GRERGR
130 DATA T7 CGDGEGDGC
140 DATA O4 C O3 BAGFEDC
150 DATA O5 C O4 BAGFED
160 DATA T6 CGDGEGFGEGDG
170 DATA CG O3 #A O4 G O3 A O4
     G O3 G O4 G
180 DATA O3 F R O5 FE I F S DR
      O4 BR O5 DR
190 DATA T2 G O6 G O5 A O6 G O
    5 B O6 G C O6 GDGFG
200 DATA ERDCDGC O5 B
210 DATA T4 ERDCDGC O4 B
220 DATA T6 ERDCDGC O3 B
230 DATA TO ERDCDGC O2 BC
240 DATA T7 O3 CDEFGABC
250 DATA O4 CDEFGABC
260 DATA O5 CDEFGAB
270 DATA O6 CR O5 CR 1 O3 CR
50000 DATA Z