Previous Next Contents Index
The syntax checking routines

THE 'SEPARATOR' SUBROUTINE
This small subroutine tests whether the current character is a separator or a quote.
It returns with the Zero flag set if it was a ';', a ',' or a '"'. With the first two
the A register holds the next character of the BASIC line.

2426 SEPARATOR  CP   """                 Return with Zero set if the current
2428            RET  Z                   character is a '"'.
2429            CP   ","
242B            JR   Z,#2430,SEPAR_1     Jump if it's a ','.
242D            CP   ";"
242F            RET  NZ                  Return Zero reset if it isn't a ';'.
2430 SEPAR_1    RST  #28,NEXT_C_ROM      Get the next character.
2431            LD   (#1DEA),A
2434            XOR  A                   Set Zero flag.
2435            LD   A,(#1DEA)
2438            RET

THE 'EVALUATE STRING EXPR.' SUBROUTINE
A call is made to the 'main' ROM 'EXPT_EXP' (class-0A) subroutine, to evaluate a string
expression. During runtime, the parameters of the string (start and length) are
returned in the DE and BC register pairs.

2439 EXPT_STR   RST  #10,CALBAS          Evaluate the string expression.
243A            DEFW #1C8C,EXPT_EXP
243C            RST  #30,SYNTAX_Z
243D            RET  Z                   Return if the syntax is being checked.
243E            PUSH AF                  Save the character following the string
243F            RST  #10,CALBAS          and the Zero flag.
2440            DEFW #2BF1,STK_FETCH     Fetch the string parameters.
2442            POP  AF
2443            RET

THE 'EVAL. MICRODRIVE SYNTAX' SUBROUTINE
This subroutine is entered at 'MD_SYNTAX' or 'MD_SYNTAX1' depending upon whether or
not the character pointer is to be updated to the next character. A single character
string is evaluated, and its ASCII value is stored during runtime. If a separator isn't
present after the single character string, an error will be given.

2444 MD_SYNTAX  RST  #28,NEXT_C_ROM      Next character.
2445 MD_SYNTAX1 CALL #0439,EXPT_STR      Evaluate the string expression.
2448            JR   Z,#245C,MD_SYNT1    Jump if syntax is being checked.
244A            PUSH AF                  Save the character following the
244B            LD   A,C                 string. A holds low byte of string
244C            DEC  A                   length.
244D            OR   B                   Give 'Nonsense in GNOS' error if the
244E            JP   NZ,#2922,REP_1      length of the string isn't one.
2451            LD   A,(DE)              Otherwise fetch the character.
2452            RST  #10,CALBAS          Call 'ALPHA' to see if it's a letter.
2453            DEFW #2C8D,ALPHA
2455            JP   NC,#2922,REP_1      Give error if not a valid one.
2458            LD   (#1E04),A           Store the channel specifier.
245B            POP  AF                  Restore next character.
245C MD_SYNT1   CP   ";"
245E            RET  Z                   Return if it's a semicolon.
245F            CP   ","
2461            RET  Z                   Return if it's a comma.
2462            JP   #2922,REP_1         Otherwise error.

THE 'EVALUATE DEVICE NUMBER' SUBROUTINE
This subroutine is used to evaluate the device number.

2465 EXPT_DEVN  AND  #DF                 Make upper case.
2467            CP   "P"
2469            JR   NZ,#247C,EXPT_DEVN1 Jump if the device isn't 'P'.
246B            RST  #28,NEXT_C_ROM      Get next character.
246C            CALL #0494,EXPT_NUM      Fetch the program number.
246F            RET  Z                   Return if syntax checking.
2470            PUSH AF
2471            LD   A,(#1E01)           Store the program number.
2474            LD   (#1E02),A
2477            CALL #0487,LAST_DRV      Drive is last used drive.
247A            POP  AF
247B            RET

Now a check is made whether the last used drive is wanted.

247C EXPT_DEVN1 RST  #28,NEXT_C_ROM      Update CH_ADD.
247D            CP   "*"
247F            JR   NZ,#2494,EXPT_NUM   Jump if it isn't a '*'.
2481            RST  #30,SYNTAX_Z
2482            CALL NZ,#0487,LAST_DRV   Store last drive number during runtime.
2485            RST  #28,NEXT_C_ROM      Next character.
2486            RET

THE 'SET LAST DRIVE' SUBROUTINE
This subroutine is used whenever the last used drive is to be used again.

2487 LAST_DRV   LD   A,(#1DDA)           Fetch current control port status.
248A            AND  #01                 Keep only drive select.
248C            ADD  A,#01               A holds 1 for drive 2, 2 for drive 1.
248E            XOR  #03                 1 becomes 2, 2 becomes 1.
2490            LD   (#1E01),A           Store drive number.
2493            RET

THE 'EVALUATE NUMERIC EXPR.' SUBROUTINE
This subroutine is used to evaluate a single numeric expression. The result is returned
during runtime into the BC register pair and into UFIA1.

2494 EXPT_NUM   RST  #10,CALBAS          Evaluate the expression by calling
2495            DEFW #1C82,EXPT_1NUM     'EXPT_1NUM' in the 'main' ROM.
2497            RST  #30,SYNTAX_Z
2498            RET  Z                   Return if syntax is being checked.
2499            PUSH AF
249A            RST  #10,CALBAS          Fetch the value from the calculator
249B            DEFW #1E99,FIND_INT2     stack.
249D            LD   A,C
249E            LD   (#1E01),A           Store it in UFIA1.
24A1            POP  AF
24A2            RET

THE 'EVALUATE 2ND FILENAME' SUBROUTINE
This routine evaluates the second filename of a BASIC command. Because 'EXP_F_NAME'
stores the filename in UFIA1, both UFIAs are swapped first, then 'EXP_F_NAME' is
called and an exit is made via 'SWAP_UFIAS' to get the UFIAs in the right order again.

24A3 EXP_F_NAM2 CALL #04A9,SWAP_UFIAS    Swap UFIA1 and 2.
24A6            CALL #04C1,EXP_F_NAME    Evaluate filename.
                                         Exit via 'SWAP_UFIAS'.

THE 'SWAP UFIAS' SUBROUTINE
This subroutine swaps the contents of UFIA1 and UFIA2 in the DFCA.

24A9 SWAP_UFIAS PUSH BC
24AA            PUSH DE
24AB            PUSH HL
24AC            LD   B,24                An UFIA is 24 bytes long.
24AE            LD   DE,#1E01            Start of UFIA1.
24B1            LD   HL,#1E1A            Start of UFIA2.
24B4 SWAP_LOOP  LD   A,(DE)              Exchange the contents.
24B5            LD   C,(HL)
24B6            EX   DE,HL
24B7            LD   (DE),A
24B8            LD   (HL),C
24B9            INC  DE
24BA            INC  HL
24BB            DJNZ #24B4,SWAP_LOOP     Repeat for all 24 bytes.
24BD            POP  HL
24BE            POP  DE
24BF            POP  BC
24C0            RET

THE 'EVALUATE A FILENAME' SUBROUTINE
A string expression is evaluated and, provided that the length is within the range
1..10 characters, stored in UFIA1.

24C1 EXP_F_NAME CALL #0439,EXPT_STR      Evaluate the string.
24C4            RET  Z                   Return if checking syntax.
24C5            PUSH AF
24C6            LD   A,C
24C7            OR   B                   Give 'Invalid FILE NAME' error with a
24C8            JP   Z,#2930,REP_8       null string.
24CB            LD   HL,10
24CE            SBC  HL,BC
24D0            JP   C,#2930,REP_8       Also with string length > 10.
24D3            LD   HL,#1E05            Clear the filename and the directory
24D6            LD   A,11                description of UFIA1.
24D8 CLR_FNAME  LD   (HL)," "
24DA            INC  HL
24DB            DEC  A
24DC            JR   NZ,#24D8,CLR_FNAME  Repeat for all 11 bytes.
24DE            LD   HL,#1E06            Copy the filename into UFIA1.
24E1            EX   DE,HL
24E2            LDIR
24E4            POP  AF
24E5            RET

THE 'CHECK STATION NUMBER' SUBROUTINE
A return to the calling routine is made only if DEV_NUM1 holds a valid station number,
i.e. in the range 0..63.

24E6 TEST_STAT  LD   A,(#1E01)           Fetch (DEV_NUM1).
24E9            INC  A                   Give 'Invalid STATION' error if it
24EA            JP   Z,#2932,REP_9       holds #FF, no station number has been
                                         evaluated.
24ED            SUB  64                  Give the error again if the value is
24EF            JP   NC,#2932,REP_9      greater than or equal to 64.
24F2            RET

THE 'EVALUATE PARAMETERS' SUBROUTINE
This very important subroutine is called to evaluate the syntax of the PUPIL's 'SAVE',
'LOAD', 'MERGE' and 'VERIFY' commands. The routine is entered with CH_ADD pointing to
the command; on exit during runtime UFIA1 is filled with the proper values.

24F3 EXPT_PARMS CALL #0403,TEST_SERV     Return if serving the network, the
24F6            RET  NZ                  parameters have been evaluated already
                                         by the master station.
24F7            RST  #28,NEXT_C_ROM      Get next character from BASIC line.
24F8            CP   " "                 Give 'Nonsense in GNOS' error with
24FA            JP   C,#2922,REP_1       codes below 32, i.e. colour codes, etc.
24FD            LD   (#1E04),A           Store the character in DEV_TYPE1.
2500            CP   "*"                 If it was an '*' evaluate microdrive
2502            CALL Z,#0444,MD_SYNTAX   syntax by calling 'MD_SYNTAX'.
2505            CALL #0465,EXPT_DEVN     Evaluate device or program number.
2508            CALL #0426,SEPARATOR     Test for a separator.
250B            PUSH AF
250C            RST  #30,SYNTAX_Z
250D            JR   Z,#252F,FILENAME    Jump if syntax checking.
250F            LD   A,(#1E04)           Fetch device descriptor.
2512            AND  #DF                 Make capital.
2514            CP   "D"
2516            JR   Z,#252A,NOT_NET     Jump if device is disk.
2518            CP   "M"
251A            JR   Z,#252A,NOT_NET     Or disk with Microdrive syntax.
251C            CP   "P"
251E            JR   Z,#2534,PARAMS      Jump with program.
2520            CP   "N"                 Give 'Invalid DEVICE' error with
2522            JP   NZ,#2934,REP_10     unknown devices.
2525            CALL #03E5,SIGN_NET      Device is network, signal 'networking'.
2528            JR   #2534,PARAMS        Jump to evaluate paremeters.

252A NOT_NET    POP  AF                  Give 'Nonsense in GNOS' error if no
252B            JP   NZ,#2922,REP_1      separator or quote found.
252E            PUSH AF                  Balance the 'POP AF' below.
252F FILENAME   POP  AF
2530            CALL Z,#04C1,EXP_F_NAME  Evaluate filename if necessary.
2533            PUSH AF                  Balance next instruction.
2534 PARAMS     POP  AF
2535            CP   13
2537            JR   Z,#2571,NO_PARAMS   Jump with ENTER.
2539            CP   ":"
253B            JR   Z,#2571,NO_PARAMS   Jump with a colon.
253D            CP   170
253F            JP   Z,#05A7,SCREEN$     Jump with 'SCREEN$'.
2542            CP   175
2544            JP   Z,#05C2,CODE        Jump with 'CODE'.
2547            CP   228
2549            JP   Z,#061C,DATA        Jump with 'DATA'.
254C            CP   202
254E            JR   Z,#2561,LINE        Jump with 'LINE'.
2550            AND  #DF                 Only capitals.
2552            CP   83                  Give 'Statement END error' error if it
2554            JP   NZ,#2924,REP_2      isn't 'S'.
2557            RST  #28,NEXT_C_ROM      Next character.
2558            CALL #0155,ST_END_ROM    Confirm end of statement and exit if
                                         syntax checking.
255B            LD   A,5                 Signal '48K Snapshot' ??
255D            LD   (#1E05),A           Could it be possible ?
2560            RET                      Finished.

Now deal with LINE.

2561 LINE       RST  #28,NEXT_C_ROM      Advance CH_ADD.
2562            RST  #10,CALBAS          Evaluate autostart line number by
2563            DEFW #1C82,EXPT_1NUM     calling 'EXPT_1NUM' in the 'main' ROM.
2565            CALL #0155,ST_END_ROM    Confirm end of statement and exit if
                                         syntax checking.
2568            RST  #10,CALBAS          Fetch the autostart line number.
2569            DEFW #1E99,FIND_INT2
256B            LD   (#1E17),BC          Store it in AUTOSTART1.
256F            JR   #2574,PROG

If there are no parameters, as with a BASIC program the syntax checking ends here.

2571 NO_PARAMS  CALL #0155,ST_END_ROM    Confirm end of statement and exit
                                         during syntax checking.
2574 PROG       LD   A,(#1E04)
2577            AND  #DF                 Only capitals.
2579            CP   "P"                 Jump if the device isn't "P", i.e. no
257B            JR   NZ,#2584,PROG_1     program number was specified.
257D            CALL #0417,TEST_SAVE     'SAVE pn' is not supported, so exit if
2580            RET  Z                   not SAVEing.
2581            JP   #2922,REP_1         Otherwise 'Nonsense in GNOS'.

2584 PROG_1     XOR  A                   File type is 'BASIC'.
2585            LD   (#1E10),A
2588            LD   A,1                 Signal 'BASIC file'.
258A            LD   (#1E05),A
258D            LD   HL,(23641)          Fetch (E_LINE), the first location past
                                         the variables area.
2590            LD   DE,(23635)          Fetch (PROG), the 'start' of the BASIC
2594            LD   (#1E13),DE          program and store it in FILE_ADDR1.
2598            SCF                      Calculate ((E_LINE)-(PROG)-1), i.e. the
2599            SBC  HL,DE               length of the program and its
259B            LD   (#1E11),HL          variables. Store it into LENGTH1_1.
259E            LD   HL,(23627)          Fetch (VARS) and calculate
25A1            SBC  HL,DE               ((VARS)-(PROG)), i.e. the length of the
                                         program without its variables.
25A3            LD   (#1E15),HL          Store it into LENGTH1_2.
25A6            RET                      Finished.

If the token is SCREEN$, the parameters are entered directly into the file header in
UFIA1.

25A7 SCREEN$    RST  #28,NEXT_C_ROM      Get the next character.
25A8            CALL #0155,ST_END_ROM    Confirm end of statement and exit
                                         during syntax checking.
25AB            LD   HL,6912             The size of the display file is stored
25AE            LD   (#1E11),HL          into LENGTH1_1.
25B1            LD   HL,16384            The startaddress is stored into
25B4            LD   (#1E13),HL          FILE_ADDR1.
25B7            LD   A,3                 File type is 'CODE'.
25B9            LD   (#1E10),A
25BC            LD   A,7                 Signal 'SCREEN$'.
25BE            LD   (#1E05),A
25C1            RET                      Finished.

Now deal with CODE, three parameters are needed: "start", "length" and "execute address".
With LOAD there may be none to three parameters, but with SAVE at least two parameters
must be present.

25C2 CODE       RST  #28,NEXT_C_ROM      Update CH_ADD.
25C3            CP   13                  If there are no further parameters,
25C5            JR   Z,#25CB,CODE_1      jump to use '0' as default value.
25C7            CP   ":"                 Jump if there are parameters to be
25C9            JR   NZ,#25D6,CODE_2     evaluated (i.e. the next character
                                         isn't a colon).
25CB CODE_1     CALL #0417,TEST_SAVE     With SAVE there must be at least two
25CE            JP   NZ,#293E,REP_15     parameters, give 'CODE error' if none
                                         present.
25D1            RST  #10,CALBAS          A call to the 'main' ROM routine
25D2            DEFW #1CE6,USE_ZERO      'USE_ZERO' is made to use a value of
25D4            JR   #25DE,CODE_3        zero as default.

Now the routine evaluates the first parameter, if present.

25D6 CODE_2     RST  #10,CALBAS          Use the 'main' ROM routine to evaluate
25D7            DEFW #1C82,EXPT_1NUM     the first parameter.
25D9            CALL #0426,SEPARATOR
25DC            JR   Z,#25E9,CODE_4      Jump if a separator is present.
25DE CODE_3     CALL #0417,TEST_SAVE     With SAVE a second parameter is needed,
25E1            JP   NZ,#293E,REP_15     so again 'CODE error' if not present.
25E4            RST  #10,CALBAS          Use zero as default again if not
25E5            DEFW #1CE6,USE_ZERO      SAVEing.
25E7            JR   #25F1,CODE_5

Evaluate the second parameter.

25E9 CODE_4     RST  #10,CALBAS
25EA            DEFW #1C82,EXPT_1NUM
25EC            CALL #0426,SEPARATOR     Jump if a second separator is found,
25EF            JR   Z,#25F6,CODE_6      i.e. there is a third parameter.
25F1 CODE_5     RST  #10,CALBAS          Otherwise again a zero is used as
25F2            DEFW #1CE6,USE_ZERO      default.
25F4            JR   #25F9,CODE_7

Evaluate the third parameter.

25F6 CODE_6     RST  #10,CALBAS
25F7            DEFW #1C82,EXPT_1NUM
25F9 CODE_7     CALL #0155,ST_END_ROM    Confirm end of statement end exit
                                         during syntax checking.
25FC            RST  #10,CALBAS          Fetch the "autoexecute" address from
25FD            DEFW #1E99,FIND_INT2     the calculator stack and store it into
25FF            LD   (#1E17),BC          AUTOSTART1.
2603            RST  #10,CALBAS          Fetch the "length".
2604            DEFW #1E99,FIND_INT2
2606            LD   (#1E11),BC          Store it into LENGTH1_1.
260A            RST  #10,CALBAS          Fetch the "start".
260B            DEFW #1E99,FIND_INT2
260D            LD   (#1E13),BC          Store it into FILE_ADDR1.
2611            LD   A,3                 File type is 'CODE'.
2613            LD   (#1E10),A
2616            LD   A,4                 Signal 'CODE file'.
2618            LD   (#1E05),A
261B            RET                      Finished.

Finally the routine to evaluate DATA parameters.

261C DATA       CALL #041C,TEST_MERGE    Give 'MERGE error' error if trying to
261F            JP   NZ,#293C,REP_14     merge an array.
2622            RST  #28,NEXT_C_ROM      Next character.
2623            RST  #10,CALBAS          Call 'LOOK_VARS' to look for the array
2624            DEFW #28B2,LOOK_VARS     name.
2626            SET  7,C
2628            JR   NC,#2635,DATA_1     Jump if handling an existing array or
                                         if checking syntax.
262A            LD   HL,#0000            Signal 'using new array'.
262D            CALL #0412,TEST_LOAD
2630            JR   NZ,#2650,DATA_3     Jump if LOADing the array.
2632            JP   #2936,REP_11        Otherwise 'VARIABLE not found'.

2635 DATA_1     JP   NZ,#2922,REP_1      Give 'Nonsense in GNOS' if not an array
                                         variable.

NOTE: This test fails to exclude simple strings, but the 'bug' (present in the 'main' ROM) is corrected at #0640.

2638            RST  #30,SYNTAX_Z
2639            JR   Z,#2662,DATA_5      Jump if syntax is being checked.
263B            CALL #0417,TEST_SAVE
263E            JR   Z,#2645,DATA_2      Jump if not SAVEing.
2640            BIT  7,(HL)              Error 'Nonsense in GNOS' if trying to
2642            JP   Z,#2922,REP_1       SAVE a simple string.
2645 DATA_2     INC  HL                  Point to the 'length' of the array.
2646            LD   A,(HL)              Store it into LENGTH1_1.
2647            LD   (#1E11),A
264A            INC  HL
264B            LD   A,(HL)
264C            LD   (#1E12),A
264F            INC  HL                  Advance to the start of the array.
2650 DATA_3     LD   A,C                 Store the array name into the MSB of
2651            LD   (#1E15),A           LENGTH1_2.
2654            LD   A,1                 File type is 'NUM ARRAY'.
2656            BIT  6,C
2658            JR   Z,#265B,DATA_4      Jump if really a numeric array.
265A            INC  A                   Otherwise file type is 'STR ARRAY'.
265B DATA_4     LD   (#1E10),A           Store the file type into FILE_TYPE1.
265E            INC  A                   Signal: (A=2) 'Numeric array', or
265F            LD   (#1E05),A                   (A=3) 'String array'.
2662 DATA_5     EX   DE,HL               DE holds 'start' of the array (or #0000
                                         with a 'new' array to be LOADed).
2663            RST  #28,NEXT_C_ROM      Next character.
2664            CP   41                  Check that the ')' is present.
2666            JP   NZ,#2922,REP_1      If not 'Nonsense in GNOS'.
2669            RST  #28,NEXT_C_ROM      Next character.
266A            CALL #0155,ST_END_ROM    Confirm end of statement and exit while
                                         syntax checking.
266D            LD   (#1E13),DE          Store "start" of the array into
2671            RET                      FILE_ADDR1 and exit.
Previous Next Contents Index