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 Zero flag set if it was a ";", "," or a """, with the first two A holds
the next character.

0A1E SEPARATOR  CP   ","
0A20            JR   Z,#0A29,SEPAR_1     Jump if current character is a comma.
0A22            CP   ";"
0A24            JR   Z,#0A29,SEPAR_1     Jump if it is a semicolon.
0A26            CP   """
0A28            RET                      Return with Zero set if it's a quote.
0A29 SEPAR_1    RST  #28,NEXT_C_RAM      Get next character.
0A2A            LD   (#1DEA),A
0A2D            XOR  A                   Set Zero flag.
0A2E            LD   A,(#1DEA)
0A31            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.

0A32 EXPT_STR   RST  #10,CALBAS          Evaluate the string expression.
0A33            DEFW #1C8C,EXPT_EXP
0A35            RST  #30,SYNTAX_Z
0A36            RET  Z                   Return if syntax is being checked.
0A37            PUSH AF                  Save the character following the string
0A38            RST  #10,CALBAS          and the zero flag.
0A39            DEFW #2BF1,STK_FETCH     Fetch the string parameters.
0A3B            POP  AF
0A3C            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 is given.

0A3D MD_SYNTAX  RST  #28,NEXT_C_RAM      Next character.
0A3E MD_SYNTAX1 CALL #0A32,EXPT_STR
0A41            JR   Z,#0A55,MD_SYNT_1   Jump if syntax is being checked.
0A43            PUSH AF                  Save the character following the
0A44            LD   A,C                 string. A holds string length low byte.
0A45            DEC  A
0A46            OR   B                   Give an error if there isn't exactly
0A47            JP   NZ,#2934,REP_10     one character in the string.
0A4A            LD   A,(DE)              Fetch the channel specifier.
0A4B            RST  #10,CALBAS          Call 'ALPHA' to see if it's a valid
0A4C            DEFW #2C8D,ALPHA         letter.
0A4E            JP   NC,#2934,REP_10     Give error if not a valid letter.
0A51            LD   (#1E04),A           Store the specifier in the UFIA.
0A54            POP  AF                  Restore next character.
0A55 MD_SYNT_1  CP   ";"
0A57            RET  Z                   Return if it's a semicolon.
0A58            CP   ","
0A5A            RET  Z                   Return if it's a comma.
0A5B            JP   #2920,REP_0         Otherwise give error.

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

0A5E EXPT_DEVN  AND  #DF                 Make upper case.
0A60            CP   "P"
0A62            JR   NZ,#0A75,EXPT_DEVN1 Jump if the device wasn't "P".
0A64            RST  #28,NEXT_C_RAM      Next character.
0A65            CALL #0A8D,EXPT_NUM      Get the program number.
0A68            RET  Z                   Return if syntax checking.
0A69            PUSH AF
0A6A            LD   A,(#1E01)           Store program number.
0A6D            LD   (#1E02),A
0A70            CALL #0A80,LAST_DRV      Drive is last drive.
0A73            POP  AF
0A74            RET

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

0A75 EXPT_DEVN1 RST  #28,NEXT_C_RAM      Get next character.
0A76 EXPT_DEVN2 CP   "*"
0A78            JR   NZ,#0A8D,EXPT_NUM   Jump if it wasn't a "*".
0A7A            RST  #30,SYNTAX_Z
0A7B            CALL NZ,#0A80,LAST_DRV   Store last drive number during runtime.
0A7E            RST  #28,NEXT_C_RAM      Next character.
0A7F            RET

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

0A80 LAST_DRV   LD   A,(#1DDA)           Fetch current control port status.
0A83            AND  #01                 Keep only drive select.
0A85            ADD  A,1                 A holds 1 for drive 2, 2 for drive 1.
0A87            XOR  #03                 1 becomes 2, 2 becomes 1.
0A89            LD   (#1E01),A           Store drive number.
0A8C            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.

0A8D EXPT_NUM   RST  #10,CALBAS          Evaluate the expression by calling
0A8E            DEFW #1C82,EXPT_1NUM     'EXPT_1NUM' in the 'main' ROM.
0A90            RST  #30,SYNTAX_Z
0A91            RET  Z                   Return if syntax is being checked.
0A92            PUSH AF
0A93            RST  #10,CALBAS          Fetch the value from the calculator
0A94            DEFW #1E99,FIND_INT2     stack.
0A96            LD   A,C
0A97            LD   (#1E01),A           Store it in UFIA1.
0A9A            POP  AF
0A9B            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 UFIA's in the right place again.

0A9C EXP_F_NAM2 CALL #0AA2,SWAP_UFIAS    Swap UFIA1 and 2.
0A9F            CALL #0ABC,EXP_F_NAME    Evaluate filename.
                                         Exit via 'SWAP_UFIAS'.

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

0AA2 SWAP_UFIAS PUSH AF
0AA3            PUSH BC
0AA4            PUSH DE
0AA5            PUSH HL
0AA6            LD   B,24                An UFIA is 24 bytes long.
0AA8            LD   DE,#1E01            Start of UFIA1.
0AAB            LD   HL,#1E1A            Start of UFIA2.
0AAE SWAP_LOOP  LD   A,(DE)              Exchange the contents.
0AAF            LD   C,(HL)
0AB0            EX   DE,HL
0AB1            LD   (DE),A
0AB2            LD   (HL),C
0AB3            INC  DE
0AB4            INC  HL
0AB5            DJNZ #0AAE,SWAP_LOOP     Repeat for all 24 bytes.
0AB7            POP  HL
0AB8            POP  DE
0AB9            POP  BC
0ABA            POP  AF
0ABB            RET

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

0ABC EXP_F_NAME CALL #0A32,EXPT_STR      Evaluate the string.
0ABF            RET  Z                   Return if checking syntax.
0AC0            PUSH AF
0AC1            LD   A,C
0AC2            OR   B
0AC3            JP   Z,#2930,REP_8       Give error with null string.
0AC6            LD   HL,10
0AC9            SBC  HL,BC
0ACB            JP   C,#2930,REP_8       Give error with string length > 10.
0ACE            LD   HL,#1E05            Clear the filename and the directory
0AD1            LD   A,11                description of UFIA1.
0AD3 CLR_FNAME  LD   (HL)," "
0AD5            INC  HL
0AD6            DEC  A
0AD7            JR   NZ,#0AD3,CLR_FNAME  Repeat for all 11 bytes.
0AD9            LD   HL,#1E06            Copy the filename into UFIA1.
0ADC            EX   DE,HL
0ADD            LDIR
0ADF            POP  AF
0AE0            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.

0AE1 TEST_STAT  LD   A,(#1E01)           Fetch DEV_NUM1.
0AE4            INC  A                   Give an error if it holds #FF, no
0AE5            JP   Z,#2932,REP_9       station number has been evaluated.
0AE8            DEC  A                   Balance the 'INC'.
0AE9            SUB  64                  Return only if the value isn't greater
0AEB            RET  C                   than 63.
0AEC            JP   #2932,REP_9         Give error.

THE 'EVALUATE PARAMETERS' SUBROUTINE
This very important subroutine is called to evaluate the syntax of the DISCiPLE'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.

0AEF EXPT_PARMS CALL #09FB,TEST_SERV     Return when serving the network, the
0AF2            RET  NZ                  parameters have been evaluated already
                                         by the station requesting service.
0AF3            RST  #28,NEXT_C_RAM      Get next character from BASIC line.
0AF4            CP   " "                 Give an error with character codes
0AF6            JP   C,#2920,REP_0       below 32, i.e. colour codes, etc.
0AF9            CP   170
0AFB            JP   Z,#161E,DUMP_SCR$   Jump with 'SCREEN$'.
0AFE            LD   (#1E04),A           Otherwise store it in DEV_TYPE1.
0B01            CP   "@"
0B03            JR   NZ,#0B3C,NOT_@      Jump if not a '@'.

Now deal with @.

0B05            CALL #0A5E,EXPT_DEVN     Evaluate drive number.
0B08            CALL #0A1E,SEPARATOR
0B0B            JP   NZ,#2924,REP_2      Give error if no separator was found.
0B0E            RST  #10,CALBAS          Call 'EXPT_1NUM' to evaluate the track
0B0F            DEFW #1C82,EXPT_1NUM     number.
0B11            CALL #0A1E,SEPARATOR     Test for another separator and give an
0B14            JP   NZ,#2924,REP_2      error if none found.
0B17            RST  #10,CALBAS          Evaluate sector number.
0B18            DEFW #1C82,EXPT_1NUM
0B1A            CALL #0A1E,SEPARATOR     Again a separator has to be found.
0B1D            JP   NZ,#2924,REP_2
0B20            RST  #10,CALBAS          Evaluate address.
0B21            DEFW #1C82,EXPT_1NUM
0B23            CALL #0409,ST_END_RAM    Confirm end of statement, and exit
                                         during syntax checking.
0B26            RST  #10,CALBAS          Fetch the address from the calculator
0B27            DEFW #1E99,FIND_INT2     stack.
0B29            LD   (#1E15),BC          Store it in LENGTH1_2
0B2D            RST  #10,CALBAS          Fetch sector.
0B2E            DEFW #1E99,FIND_INT2
0B30            LD   (#1E13),BC          Store it in FILE_ADDR1
0B34            RST  #10,CALBAS          Fetch track.
0B35            DEFW #1E99,FIND_INT2
0B37            LD   (#1E11),BC          Store it in LENGTH1_1
0B3A            RET                      Exit.

0B3C NOT_@      CP   "*"                 Call 'MD_SYNTAX' if it was a "*".
0B3E            CALL Z,#0A3D,MD_SYNTAX
0B41            CALL #0A5E,EXPT_DEVN     Fetch device or program number.
0B44            CALL #0A1E,SEPARATOR     Test for a separator.
0B47            PUSH AF
0B48            RST  #30,SYNTAX_Z
0B49            JR   Z,#0B7F,FILENAME    Jump if syntax checking.
0B4B            LD   A,(#1E04)           Fetch device descriptor.
0B4E            AND  #DF                 Only capitals.
0B50            CP   "D"
0B52            JR   Z,#0B7A,NOT_NET     Jump if device is disk.
0B54            CP   "M"
0B56            JR   Z,#0B7A,NOT_NET     Or disk with Microdrive syntax.
0B58            CP   "P"
0B5A            JR   Z,#0B84,PARAMS      Jump with program.
0B5C            CP   "F"
0B5E            JR   NZ,#0B68,NETWORKING Jump if not stealing or forcing.
0B60            CALL #09D8,SIGN_STEAL    Signal 'stealing from or forcing to a
0B63            LD   A,"N"               pupil'. Device is network.
0B65            LD   (#1E04),A
0B68 NETWORKING CP   "N"
0B6A            JP   NZ,#2934,REP_10     Give error with unknown device.
0B6D            LD   A,(#029C)
0B70            CP   0
0B72            JP   Z,#294A,REP_21      Give error if network is off.
0B75            CALL #09DD,SIGN_NET      Signal 'networking'.
0B78            JR   #0B84,PARAMS        Evaluate parameters.

0B7A NOT_NET    POP  AF                  Give error if no separator or quote
0B7B            JP   NZ,#2920,REP_0      found with devices "D" and "M".
0B7E            PUSH AF                  Balance 'POP AF' below.
0B7F FILENAME   POP  AF
0B80            CALL Z,#0ABC,EXP_F_NAME  Evaluate filename if necessary.
0B83            PUSH AF                  Balance next instruction.
0B84 PARAMS     POP  AF
0B85            CP   13
0B87            JP   Z,#0C18,NO_PARAMS   Jump with ENTER.
0B8A            CP   ":"
0B8C            JP   Z,#0C18,NO_PARAMS   Jump with colon.
0B8F            CP   204
0B91            JP   Z,#0702,TO          Jump with 'TO'.
0B94            CP   170
0B96            JP   Z,#0C4E,SCREEN$     Jump with 'SCREEN$'.
0B99            CP   175
0B9B            JP   Z,#0C69,CODE        Jump with 'CODE'.
0B9E            CP   228
0BA0            JP   Z,#0CC3,DATA        Jump with 'DATA'.
0BA3            CP   202
0BA5            JP   Z,#0C08,LINE        Jump with 'LINE'.
0BA8            AND  #DF                 Only capitals.
0BAA            CP   "S"
0BAC            JR   NZ,#0BB8,NOT_S      Jump with other than 'S'.
0BAE            RST  #28,NEXT_C_RAM      Next character.
0BAF            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0BB2            LD   A,5                 Signal '48K Snapshot'.
0BB4            LD   (#1E05),A
0BB7            RET                      Finished.

0BB8 NOT_S      CP   "K"
0BBA            JR   NZ,#0BC6,NOT_K      Jump with other than 'K'.
0BBC            RST  #28,NEXT_C_RAM      Next character.
0BBD            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0BC0            LD   A,9                 Signal '128K Snapshot'.
0BC2            LD   (#1E05),A
0BC5            RET                      Finished.

0BC6 NOT_K      CP   "X"
0BC8            JP   NZ,#2920,REP_0      Give error with other than 'X'.
0BCB            RST  #28,NEXT_C_RAM      Next character.
0BCC            CALL #0A1E,SEPARATOR     Jump if a separator found, there is
0BCF            JR   Z,#0BDF,X_FILE_1    more.
0BD1            CALL #0A0F,TEST_SAVE     There must follow a address if SAVEing.
0BD4            JP   NZ,#2924,REP_2      Give error if SAVEing.
0BD7            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0BDA            LD   BC,#1BD6            Load address of execute file.
0BDD            JR   #0BE8,X_FILE_2      Jump forward.

A separator has been found, so there should follow an address.

0BDF X_FILE_1   RST  #10,CALBAS          Evaluate address.
0BE0            DEFW #1C82,EXPT_1NUM
0BE2            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0BE5            RST  #10,CALBAS          Fetch the address.
0BE6            DEFW #1E99,FIND_INT2
0BE8 X_FILE_2   LD   (#1E13),BC          Store it in FILE_ADDR1
0BEC            LD   BC,510              Length of execute file on double
0BEF            LD   A,(#1DDA)           density disks.
0BF2            AND  #04
0BF4            JR   Z,#0BF9,X_FILE_3    Jump if double density selected.
0BF6            LD   BC,254              Otherwise this is the length of the
                                         execute file.
0BF9 X_FILE_3   LD   (#1E11),BC          Store length in LENGTH1_1.
0BFD            LD   A,3                 File type is 'CODE'.
0BFF            LD   (#1E10),A           Store it in FILE_TYPE1.
0C02            LD   A,11                Signal 'Execute file'.
0C04            LD   (#1E05),A           Store in DIR_DESCR1
0C07            RET                      Finished.

Now deal with LINE. The DISCiPLE allows LOAD, VERIFY and MERGE .. LINE to be entered as
a command but the LINE is completely ignored.

0C08 LINE       RST  #28,NEXT_C_RAM      Advance CH_ADD.
0C09            RST  #10,CALBAS          Evaluate autostart line number by
0C0A            DEFW #1C82,EXPT_1NUM     calling 'EXPT_1NUM' in the 'main' ROM.
0C0C            CALL #0409,ST_END_RAM    Confirm end of statement, and exit
                                         during syntax checking.
0C0F            RST  #10,CALBAS          Fetch the autostart line number.
0C10            DEFW #1E99,FIND_INT2
0C12            LD   (#1E17),BC          Store it in AUTOSTART1.
0C16            JR   #0C1B,PROG

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

0C18 NO_PARAMS  CALL #0409,ST_END_RAM    Confirm end of statement, exit when
                                         syntax checking.
0C1B PROG       LD   A,(#1E04)
0C1E            AND  #DF                 Only capitals.
0C20            CP   "P"                 Jump if the device wasn't "P", i.e. no
0C22            JR   NZ,#0C2B,PROG_1     program number was specified.
0C24            CALL #0A0F,TEST_SAVE     'SAVE pn' is not supported, so give an
0C27            RET  Z                   error if saving, otherwise return.
0C28            JP   #2920,REP_0

0C2B PROG_1     XOR  A                   File type is 'BASIC'.
0C2C            LD   (#1E10),A
0C2F            LD   A,1                 Signal 'BASIC file'.
0C31            LD   (#1E05),A
0C34            LD   HL,(23641)          Fetch (E_LINE), the first location past
                                         the variables area.
0C37            LD   DE,(23635)          Fetch (PROG), the 'start' of the BASIC
0C3B            LD   (#1E13),DE          program and store it in FILE_ADDR1
0C3F            SCF                      Calculate ((E_LINE)-(PROG)-1), i.e. the
0C40            SBC  HL,DE               length of the program and its
0C42            LD   (#1E11),HL          variables. Store it in LENGTH1_1.
0C45            LD   HL,(23627)          Fetch (VARS) and calculate
0C48            SBC  HL,DE               (VARS)-(PROG), i.e. the length of the
                                         program without its variables.
0C4A            LD   (#1E15),HL          Store it into LENGTH1_2.
0C4D            RET                      Finished.

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

0C4E SCREEN$    RST  #28,NEXT_C_RAM      Get the next character.
0C4F            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0C52            LD   HL,6912             The size of the display file is stored
0C55            LD   (#1E11),HL          into LENGTH1_1.
0C58            LD   HL,16384            The startaddress is stored into
0C5B            LD   (#1E13),HL          FILE_ADDR1
0C5E            LD   A,3                 File type is 'CODE'.
0C60            LD   (#1E10),A
0C63            LD   A,7                 Signal 'SCREEN$'.
0C65            LD   (#1E05),A
0C68            RET

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

0C69 CODE       RST  #28,NEXT_C_RAM      Update CH_ADD.
0C6A            CP   13                  If there are no further parameters,
0C6C            JR   Z,#0C72,CODE_1      jump to use '0' as default value.
0C6E            CP   ":"                 Jump if there are parameters to be
0C70            JR   NZ,#0C7D,CODE_2     evaluated (i.e. the next character is
                                         not a colon).
0C72 CODE_1     CALL #0A0F,TEST_SAVE     'SAVE .. CODE' has to be followed by at
0C75            JP   NZ,#2924,REP_2      least two numbers, so give an error if
                                         none present.
0C78            RST  #10,CALBAS          A call to the 'main' ROM routine
0C79            DEFW #1CE6,USE_ZERO      'USE_ZERO' is made to use a value of
0C7B            JR   #0C85,CODE_3        zero as default.

It's likely that an address follows.

0C7D CODE_2     RST  #10,CALBAS          Use the 'main' ROM routine to evaluate
0C7E            DEFW #1C82,EXPT_1NUM     the first parameter.
0C80            CALL #0A1E,SEPARATOR
0C83            JR   Z,#0C90,CODE_4      Jump if a separator is present.
0C85 CODE_3     CALL #0A0F,TEST_SAVE     Give an error if there isn't a second
0C88            JP   NZ,#2924,REP_2      number with 'SAVE .. CODE'.
0C8B            RST  #10,CALBAS          Otherwise use zero as default.
0C8C            DEFW #1CE6,USE_ZERO
0C8E            JR   #0C98,CODE_5

The length seems to be present also.

0C90 CODE_4     RST  #10,CALBAS          Evaluate the second parameter.
0C91            DEFW #1C82,EXPT_1NUM
0C93            CALL #0A1E,SEPARATOR     Jump if a second separator is found.
0C96            JR   Z,#0C9D,CODE_6
0C98 CODE_5     RST  #10,CALBAS          Otherwise zero is default.
0C99            DEFW #1CE6,USE_ZERO
0C9B            JR   #0CA0,CODE_7

There's even an execute address.

0C9D CODE_6     RST  #10,CALBAS          Evaluate the third parameter.
0C9E            DEFW #1C82,EXPT_1NUM
0CA0 CODE_7     CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0CA3            RST  #10,CALBAS          Fetch the "autoexecute" address from
0CA4            DEFW #1E99,FIND_INT2     the calculator stack and store it into
0CA6            LD   (#1E17),BC          AUTOSTART1
0CAA            RST  #10,CALBAS          Fetch the "length".
0CAB            DEFW #1E99,FIND_INT2
0CAD            LD   (#1E11),BC          Store it into LENGTH1_1
0CB1            RST  #10,CALBAS          Fetch the "start".
0CB2            DEFW #1E99,FIND_INT2
0CB4            LD   (#1E13),BC          Store it into FILE_ADDR1
0CB8            LD   A,3                 File type is 'CODE'.
0CBA            LD   (#1E10),A
0CBD            LD   A,4                 Signal 'CODE file'.
0CBF            LD   (#1E05),A
0CC2            RET                      Finished.

Finally the routine to evaluate DATA parameters.

0CC3 DATA       CALL #0A14,TEST_MERGE    Give an error if attempting to MERGE an
0CC6            JP   NZ,#293C,REP_14     array.
0CC9            RST  #28,NEXT_C_RAM      Next character.
0CCA            RST  #10,CALBAS          Call LOOK_VARS to look for the array
0CCB            DEFW #28B2,LOOK_VARS     name.
0CCD            SET  7,C
0CCF            JR   NC,#0CDC,DATA_1     Jump if handling an existing array or
                                         if syntax checking.
0CD1            LD   HL,#0000            Signal 'using a new array'.
0CD4            CALL #0A0A,TEST_LOAD
0CD7            JR   NZ,#0CF7,DATA_3     Jump if LOADing the array.
0CD9            JP   #2936,REP_11        Otherwise give error 'Variable not
                                         found'.
0CDC DATA_1     JP   NZ,#2920,REP_0      Give error if not an array variable.

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

0CDF            RST  #30,SYNTAX_Z
0CE0            JR   Z,#0D09,DATA_5      Jump if syntax is being checked.
0CE2            CALL #0A0F,TEST_SAVE
0CE5            JR   Z,#0CEC,DATA_2      Jump if LOADing.
0CE7            BIT  7,(HL)              Give an error if trying to SAVE a
0CE9            JP   Z,#2920,REP_0       simple string.
0CEC DATA_2     INC  HL                  Point to the 'length' of the array.
0CED            LD   A,(HL)              Store the length into LENGTH1_1.
0CEE            LD   (#1E11),A
0CF1            INC  HL
0CF2            LD   A,(HL)
0CF3            LD   (#1E12),A
0CF6            INC  HL                  Advance to the start of the array.
0CF7 DATA_3     LD   A,C                 Store array name into LSB of LENGTH1_2.
0CF8            LD   (#1E15),A
0CFB            LD   A,1                 File type is 'NUM ARRAY'.
0CFD            BIT  6,C
0CFF            JR   Z,#0D02,DATA_4      Jump if really a numeric array.
0D01            INC  A                   File type is 'STR ARRAY'.
0D02 DATA_4     LD   (#1E10),A           Store file type into FILE_TYPE1.
0D05            INC  A                   Signal: (A=2) 'Numeric array',
0D06            LD   (#1E05),A                   (A=3) 'String array'.
0D09 DATA_5     EX   DE,HL               DE holds 'start' of the array (or #0000
                                         with a 'new' array to be LOADed).
0D0A            RST  #28,NEXT_C_RAM      Next character.
0D0B            CP   ")"                 Check that the ')' does exist.
0D0D            JP   NZ,#2924,REP_2      Report an error if not.
0D10            RST  #28,NEXT_C_RAM      Next character.
0D11            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
0D14            LD   (#1E13),DE          Store "start" of the array into
0D18            RET                      FILE_ADDR1 and exit.
Previous Next Contents Index