CPU-Z80-Disassembler

 view release on metacpan or  search on metacpan

t/data/zx48.asm  view on Meta::CPAN


        CALL    L15D4           ; routine WAIT-KEY - input address is KEY-NEXT
                                ; but is reset to KEY-INPUT
        LD      E,A             ; save first in E

;; ED-CONTR
L0F6C:  CALL    L15D4           ; routine WAIT-KEY for control.
                                ; input address will be key-next.

        PUSH    DE              ; saved code/parameters
        LD      HL,($5C5B)      ; fetch address of keyboard cursor from K_CUR
        RES     0,(IY+$07)      ; set MODE to 'L'

        CALL    L1655           ; routine MAKE-ROOM makes 2/3 spaces at cursor

        POP     BC              ; restore code/parameters
        INC     HL              ; address first location
        LD      (HL),B          ; place code (ink etc.)
        INC     HL              ; address next
        LD      (HL),C          ; place possible parameter. If only one
                                ; then DE points to this location also.
        JR      L0F8B           ; forward to ADD-CH-1

; ------------------------
; Add code to current line
; ------------------------
; this is the branch used to add normal non-control characters
; with ED-LOOP as the stacked return address.
; it is also the OUTPUT service routine for system channel 'R'.

;; ADD-CHAR
L0F81:  RES     0,(IY+$07)      ; set MODE to 'L'

X0F85:  LD      HL,($5C5B)      ; fetch address of keyboard cursor from K_CUR

        CALL    L1652           ; routine ONE-SPACE creates one space.

; either a continuation of above or from ED-CONTR with ED-LOOP on stack.

;; ADD-CH-1
L0F8B:  LD      (DE),A          ; load current character to last new location.
        INC     DE              ; address next
        LD      ($5C5B),DE      ; and update K_CUR system variable.
        RET                     ; return - either a simple return

t/data/zx48.asm  view on Meta::CPAN

; using a look-up table.

;; ED-KEYS
L0F92:  LD      E,A             ; character to E.
        LD      D,$00           ; prepare to add.
        LD      HL,L0FA0 - 7    ; base address of editing keys table. $0F99
        ADD     HL,DE           ; add E
        LD      E,(HL)          ; fetch offset to E
        ADD     HL,DE           ; add offset for address of handling routine.
        PUSH    HL              ; push the address on machine stack.
        LD      HL,($5C5B)      ; load address of cursor from K_CUR.
        RET                     ; Make an indirect jump forward to routine.

; ------------------
; Editing keys table
; ------------------
; For each code in the range $07 to $0F this table contains a
; single offset byte to the routine that services that code.
; Note. for what was intended there should also have been an
; entry for chr$ 6 with offset to ed-symbol.

t/data/zx48.asm  view on Meta::CPAN

        CALL    L196E           ; routine LINE-ADDR to find address of line
                                ; or following line if it doesn't exist.
        CALL    L1695           ; routine LINE-NO will get line number from
                                ; address or previous line if at end-marker.
        LD      A,D             ; if there is no program then DE will
        OR      E               ; contain zero so test for this.
        JP      Z,L1097         ; jump to CLEAR-SP if so.

; Note. at this point we have a validated line number, not just an
; approximation and it would be best to update E_PPC with the true
; cursor line value which would enable the line cursor to be suppressed
; in all situations - see shortly.

        PUSH    HL              ; save address of line.
        INC     HL              ; address low byte of length.
        LD      C,(HL)          ; transfer to C
        INC     HL              ; next to high byte
        LD      B,(HL)          ; transfer to B.
        LD      HL,$000A        ; an overhead of ten bytes
        ADD     HL,BC           ; is added to length.
        LD      B,H             ; transfer adjusted value

t/data/zx48.asm  view on Meta::CPAN

        CALL    L1097           ; routine CLEAR-SP clears editing area.
        LD      HL,($5C51)      ; address CURCHL
        EX      (SP),HL         ; swap with line address on stack
        PUSH    HL              ; save line address underneath

        LD      A,$FF           ; select system channel 'R'
        CALL    L1601           ; routine CHAN-OPEN opens it

        POP     HL              ; drop line address
        DEC     HL              ; make it point to first byte of line num.
        DEC     (IY+$0F)        ; decrease E_PPC_lo to suppress line cursor.
                                ; Note. ineffective when E_PPC is one
                                ; greater than last line of program perhaps
                                ; as a result of a delete.
                                ; credit. Paul Harrison 1982.

        CALL    L1855           ; routine OUT-LINE outputs the BASIC line
                                ; to the editing area.
        INC     (IY+$0F)        ; restore E_PPC_lo to the previous value.
        LD      HL,($5C59)      ; address E_LINE in editing area.
        INC     HL              ; advance

t/data/zx48.asm  view on Meta::CPAN

        LD      ($5C5B),HL      ; update K_CUR to address start of BASIC.
        POP     HL              ; restore the address of CURCHL.
        CALL    L1615           ; routine CHAN-FLAG sets flags for it.

        RET                     ; RETURN to ED-LOOP.

; -------------------
; Cursor down editing
; -------------------
;   The BASIC lines are displayed at the top of the screen and the user
;   wishes to move the cursor down one line in edit mode.
;   With INPUT LINE, this key must be used instead of entering STOP.

;; ED-DOWN
L0FF3:  BIT     5,(IY+$37)      ; test FLAGX  - Input Mode ?
        JR      NZ,L1001        ; skip to ED-STOP if so

        LD      HL,$5C49        ; address E_PPC - 'current line'
        CALL    L190F           ; routine LN-FETCH fetches number of next
                                ; line or same if at end of program.
        JR      L106E           ; forward to ED-LIST to produce an

t/data/zx48.asm  view on Meta::CPAN


; ---

;; ED-STOP
L1001:  LD      (IY+$00),$10    ; set ERR_NR to 'STOP in INPUT' code
        JR      L1024           ; forward to ED-ENTER to produce error.

; -------------------
; Cursor left editing
; -------------------
; This acts on the cursor in the lower section of the screen in both
; editing and input mode.

;; ED-LEFT
L1007:  CALL    L1031           ; routine ED-EDGE moves left if possible
        JR      L1011           ; forward to ED-CUR to update K-CUR
                                ; and return to ED-LOOP.

; --------------------
; Cursor right editing
; --------------------
; This acts on the cursor in the lower screen in both editing and input
; mode and moves it to the right.

;; ED-RIGHT
L100C:  LD      A,(HL)          ; fetch addressed character.
        CP      $0D             ; is it carriage return ?
        RET     Z               ; return if so to ED-LOOP

        INC     HL              ; address next character

;; ED-CUR
L1011:  LD      ($5C5B),HL      ; update K_CUR system variable
        RET                     ; return to ED-LOOP

; --------------
; DELETE editing
; --------------
; This acts on the lower screen and deletes the character to left of
; cursor. If control characters are present these are deleted first
; leaving the naked parameter (0-7) which appears as a '?' except in the
; case of chr$ 6 which is the comma control character. It is not mandatory
; to delete these second characters.

;; ED-DELETE
L1015:  CALL    L1031           ; routine ED-EDGE moves cursor to left.
        LD      BC,$0001        ; of character to be deleted.
        JP      L19E8           ; to RECLAIM-2 reclaim the character.

; ------------------------------------------
; Ignore next 2 codes from key-input routine
; ------------------------------------------
; Since AT and TAB cannot be entered this point is never reached
; from the keyboard. If inputting from a tape device or network then
; the control and two following characters are ignored and processing
; continues as if a carriage return had been received.

t/data/zx48.asm  view on Meta::CPAN

;; ED-END
L1026:  POP     HL              ; the previous value of ERR_SP
        LD      ($5C3D),HL      ; is restored to ERR_SP system variable
        BIT     7,(IY+$00)      ; is ERR_NR $FF (= 'OK') ?
        RET     NZ              ; return if so

        LD      SP,HL           ; else put error routine on stack
        RET                     ; and make an indirect jump to it.

; -----------------------------
; Move cursor left when editing
; -----------------------------
; This routine moves the cursor left. The complication is that it must
; not position the cursor between control codes and their parameters.
; It is further complicated in that it deals with TAB and AT characters
; which are never present from the keyboard.
; The method is to advance from the beginning of the line each time,
; jumping one, two, or three characters as necessary saving the original
; position at each jump in DE. Once it arrives at the cursor then the next
; legitimate leftmost position is in DE.

;; ED-EDGE
L1031:  SCF                     ; carry flag must be set to call the nested
        CALL    L1195           ; subroutine SET-DE.
                                ; if input   then DE=WORKSP
                                ; if editing then DE=E_LINE
        SBC     HL,DE           ; subtract address from start of line
        ADD     HL,DE           ; and add back.
        INC     HL              ; adjust for carry.
        POP     BC              ; drop return address
        RET     C               ; return to ED-LOOP if already at left
                                ; of line.

        PUSH    BC              ; resave return address - ED-LOOP.
        LD      B,H             ; transfer HL - cursor address
        LD      C,L             ; to BC register pair.
                                ; at this point DE addresses start of line.

;; ED-EDGE-1
L103E:  LD      H,D             ; transfer DE - leftmost pointer
        LD      L,E             ; to HL
        INC     HL              ; address next leftmost character to
                                ; advance position each time.
        LD      A,(DE)          ; pick up previous in A
        AND     $F0             ; lose the low bits

t/data/zx48.asm  view on Meta::CPAN

        LD      A,(DE)          ; reload leftmost character
        SUB     $17             ; decimal 23 ('tab')
        ADC     A,$00           ; will be 0 for 'tab' and 'at'.
        JR      NZ,L1051        ; forward to ED-EDGE-2 if not
                                ; HL has been incremented twice

        INC     HL              ; increment a third time for 'at'/'tab'

;; ED-EDGE-2
L1051:  AND     A               ; prepare for true subtraction
        SBC     HL,BC           ; subtract cursor address from pointer
        ADD     HL,BC           ; and add back
                                ; Note when HL matches the cursor position BC,
                                ; there is no carry and the previous
                                ; position is in DE.
        EX      DE,HL           ; transfer result to DE if looping again.
                                ; transfer DE to HL to be used as K-CUR
                                ; if exiting loop.
        JR      C,L103E         ; back to ED-EDGE-1 if cursor not matched.

        RET                     ; return.

; -----------------
; Cursor up editing
; -----------------
; The main screen displays part of the BASIC program and the user wishes
; to move up one line scrolling if necessary.
; This has no alternative use in input mode.

t/data/zx48.asm  view on Meta::CPAN


;; KEY-DONE2
L111B:  SCF                     ; set carry flag to show a key has been found
        RET                     ; and return.

; --------------------
; Lower screen copying
; --------------------
; This subroutine is called whenever the line in the editing area or
; input workspace is required to be printed to the lower screen.
; It is by calling this routine after any change that the cursor, for
; instance, appears to move to the left.
; Remember the edit line will contain characters and tokens
; e.g. "1000 LET a=1" is 8 characters.

;; ED-COPY
L111D:  CALL    L0D4D           ; routine TEMPS sets temporary attributes.
        RES     3,(IY+$02)      ; update TV_FLAG  - signal no change in mode
        RES     5,(IY+$02)      ; update TV_FLAG  - signal don't clear lower
                                ; screen.
        LD      HL,($5C8A)      ; fetch SPOSNL

t/data/zx48.asm  view on Meta::CPAN

        CALL    L1195           ; call routine SET-DE
                                ; if in input DE = WORKSP
                                ; if in edit  DE = E_LINE
        EX      DE,HL           ; start address to HL

        CALL    L187D           ; routine OUT-LINE2 outputs entire line up to
                                ; carriage return including initial
                                ; characterized line number when present.
        EX      DE,HL           ; transfer new address to DE
        CALL    L18E1           ; routine OUT-CURS considers a
                                ; terminating cursor.

        LD      HL,($5C8A)      ; fetch updated SPOSNL
        EX      (SP),HL         ; exchange with ECHO_E on stack
        EX      DE,HL           ; transfer ECHO_E to DE
        CALL    L0D4D           ; routine TEMPS to re-set attributes
                                ; if altered.

; the lower screen was not cleared, at the outset, so if deleting then old
; text from a previous print may follow this line and requires blanking.

t/data/zx48.asm  view on Meta::CPAN

; This routine uses HL only and returns with that register holding
; WORKSP/STKBOT/STKEND though no use is made of this. The routines also
; reset MEM to its usual place in the systems variable area should it
; have been relocated to a FOR-NEXT variable. The main entry point
; SET-MIN is called at the start of the MAIN-EXEC loop and prior to
; displaying an error.

;; SET-MIN
L16B0:  LD      HL,($5C59)      ; fetch E_LINE
        LD      (HL),$0D        ; insert carriage return
        LD      ($5C5B),HL      ; make K_CUR keyboard cursor point there.
        INC     HL              ; next location
        LD      (HL),$80        ; holds end-marker $80
        INC     HL              ; next location becomes
        LD      ($5C61),HL      ; start of WORKSP

; This entry point is used prior to input and prior to the execution,
; or parsing, of each statement.

;; SET-WORK
L16BF:  LD      HL,($5C61)      ; fetch WORKSP value

t/data/zx48.asm  view on Meta::CPAN

; Print a whole BASIC line
; ------------------------
; This routine prints a whole BASIC line and it is called
; from LIST-ALL to output the line to current channel
; and from ED-EDIT to 'sprint' the line to the edit buffer.

;; OUT-LINE
L1855:  LD      BC,($5C49)      ; fetch E_PPC the current line which may be
                                ; unchecked and not exist.
        CALL    L1980           ; routine CP-LINES finds match or line after.
        LD      D,$3E           ; prepare cursor '>' in D.
        JR      Z,L1865         ; to OUT-LINE1 if matched or line after.

        LD      DE,$0000        ; put zero in D, to suppress line cursor.
        RL      E               ; pick up carry in E if line before current
                                ; leave E zero if same or after.

;; OUT-LINE1
L1865:  LD      (IY+$2D),E      ; save flag in BREG which is spare.
        LD      A,(HL)          ; get high byte of line number.
        CP      $40             ; is it too high ($2F is maximum possible) ?
        POP     BC              ; drop the return address and
        RET     NC              ; make an early return if so >>>

        PUSH    BC              ; save return address
        CALL    L1A28           ; routine OUT-NUM-2 to print addressed number
                                ; with leading space.
        INC     HL              ; skip low number byte.
        INC     HL              ; and the two
        INC     HL              ; length bytes.
        RES     0,(IY+$01)      ; update FLAGS - signal leading space required.
        LD      A,D             ; fetch the cursor.
        AND     A               ; test for zero.
        JR      Z,L1881         ; to OUT-LINE3 if zero.


        RST     10H             ; PRINT-A prints '>' the current line cursor.

; this entry point is called from ED-COPY

;; OUT-LINE2
L187D:  SET     0,(IY+$01)      ; update FLAGS - suppress leading space.

;; OUT-LINE3
L1881:  PUSH    DE              ; save flag E for a return value.
        EX      DE,HL           ; save HL address in DE.
        RES     2,(IY+$30)      ; update FLAGS2 - signal NOT in QUOTES.

t/data/zx48.asm  view on Meta::CPAN

L1894:  LD      HL,($5C5F)      ; fetch X_PTR - possibly the error pointer
                                ; address.
        AND     A               ; clear the carry flag.
        SBC     HL,DE           ; test if an error address has been reached.
        JR      NZ,L18A1        ; forward to OUT-LINE5 if not.

        LD      A,$3F           ; load A with '?' the error marker.
        CALL    L18C1           ; routine OUT-FLASH to print flashing marker.

;; OUT-LINE5
L18A1:  CALL    L18E1           ; routine OUT-CURS will print the cursor if
                                ; this is the right position.
        EX      DE,HL           ; restore address pointer to HL.
        LD      A,(HL)          ; fetch the addressed character.
        CALL    L18B6           ; routine NUMBER skips a hidden floating 
                                ; point number if present.
        INC     HL              ; now increment the pointer.
        CP      $0D             ; is character end-of-line ?
        JR      Z,L18B4         ; to OUT-LINE6, if so, as line is finished.

        EX      DE,HL           ; save the pointer in DE.

t/data/zx48.asm  view on Meta::CPAN

        INC     HL              ;
        INC     HL              ;
        INC     HL              ;
        LD      A,(HL)          ; fetch the following character
        RET                     ; for return value.

; --------------------------
; Print a flashing character
; --------------------------
; This subroutine is called from OUT-LINE to print a flashing error
; marker '?' or from the next routine to print a flashing cursor e.g. 'L'.
; However, this only gets called from OUT-LINE when printing the edit line
; or the input buffer to the lower screen so a direct call to $09F4 can
; be used, even though out-line outputs to other streams.
; In fact the alternate set is used for the whole routine.

;; OUT-FLASH
L18C1:  EXX                     ; switch in alternate set

        LD      HL,($5C8F)      ; fetch L = ATTR_T, H = MASK-T
        PUSH    HL              ; save masks.

t/data/zx48.asm  view on Meta::CPAN


        POP     HL              ; pop P_FLAG to H.
        LD      (IY+$57),H      ; and restore system variable P_FLAG.
        POP     HL              ; restore temporary masks
        LD      ($5C8F),HL      ; and restore system variables ATTR_T/MASK_T

        EXX                     ; switch back to main set
        RET                     ; return

; ----------------
; Print the cursor
; ----------------
; This routine is called before any character is output while outputting
; a BASIC line or the input buffer. This includes listing to a printer
; or screen, copying a BASIC line to the edit buffer and printing the
; input buffer or edit buffer to the lower screen. It is only in the
; latter two cases that it has any relevance and in the last case it
; performs another very important function also.

;; OUT-CURS
L18E1:  LD      HL,($5C5B)      ; fetch K_CUR the current cursor address
        AND     A               ; prepare for true subtraction.
        SBC     HL,DE           ; test against pointer address in DE and
        RET     NZ              ; return if not at exact position.

; the value of MODE, maintained by KEY-INPUT, is tested and if non-zero
; then this value 'E' or 'G' will take precedence.

        LD      A,($5C41)       ; fetch MODE  0='KLC', 1='E', 2='G'.
        RLC     A               ; double the value and set flags.
        JR      Z,L18F3         ; to OUT-C-1 if still zero ('KLC').

        ADD     A,$43           ; add 'C' - will become 'E' if originally 1
                                ; or 'G' if originally 2.
        JR      L1909           ; forward to OUT-C-2 to print.

; ---

; If mode was zero then, while printing a BASIC line, bit 2 of flags has been
; set if 'THEN' or ':' was encountered as a main character and reset otherwise.
; This is now used to determine if the 'K' cursor is to be printed but this
; transient state is also now transferred permanently to bit 3 of FLAGS
; to let the interrupt routine know how to decode the next key.

;; OUT-C-1
L18F3:  LD      HL,$5C3B        ; Address FLAGS
        RES     3,(HL)          ; signal 'K' mode initially.
        LD      A,$4B           ; prepare letter 'K'.
        BIT     2,(HL)          ; test FLAGS - was the
                                ; previous main character ':' or 'THEN' ?
        JR      Z,L1909         ; forward to OUT-C-2 if so to print.

t/data/zx48.asm  view on Meta::CPAN

L195A:  CP      $22             ; is it quote character '"'  ?
        JR      NZ,L1968        ; to OUT-CH-2 with others to set 'L' mode.

        PUSH    AF              ; save character.
        LD      A,($5C6A)       ; fetch FLAGS2.
        XOR     $04             ; toggle the quotes flag.
        LD      ($5C6A),A       ; update FLAGS2
        POP     AF              ; and restore character.

;; OUT-CH-2
L1968:  SET     2,(IY+$01)      ; update FLAGS - signal L mode if the cursor
                                ; is next.

;; OUT-CH-3
L196C:  RST     10H             ; PRINT-A vectors the character to
                                ; channel 'S', 'K', 'R' or 'P'.
        RET                     ; return.

; -------------------------------------------
; Get starting address of line, or line after
; -------------------------------------------

t/data/zx48.asm  view on Meta::CPAN

        RRCA                    ; lose bit 0.
        RRCA                    ; test if quotes required.
        JR      NC,L2129        ; forward to IN-PR-3 if not.

        LD      A,$22           ; load the '"' character
        LD      (DE),A          ; place quote in first new location at DE.
        DEC     HL              ; decrease HL - from carriage return.
        LD      (HL),A          ; and place a quote in second location.

;; IN-PR-3
L2129:  LD      ($5C5B),HL      ; set keyboard cursor K_CUR to HL
        BIT     7,(IY+$37)      ; test FLAGX  - is this INPUT LINE ??
        JR      NZ,L215E        ; forward to IN-VAR-3 if so as input will
                                ; be accepted without checking its syntax.

        LD      HL,($5C5D)      ; fetch CH_ADD
        PUSH    HL              ; and save on stack.
        LD      HL,($5C3D)      ; fetch ERR_SP
        PUSH    HL              ; and save on stack

;; IN-VAR-1

t/data/zx48.asm  view on Meta::CPAN

; the jump was to here when using INPUT LINE.

;; IN-VAR-3
L215E:  CALL    L0F2C           ; routine EDITOR is called for input

; when ENTER received rejoin other route but with no syntax check.

; INPUT and INPUT LINE converge here.

;; IN-VAR-4
L2161:  LD      (IY+$22),$00    ; set K_CUR_hi to a low value so that the cursor
                                ; no longer appears in the input line.

        CALL    L21D6           ; routine IN-CHAN-K tests if the keyboard
                                ; is being used for input.
        JR      NZ,L2174        ; forward to IN-VAR-5 if using another input 
                                ; channel.

; continue here if using the keyboard.

        CALL    L111D           ; routine ED-COPY overprints the edit line
                                ; to the lower screen. The only visible
                                ; affect is that the cursor disappears.
                                ; if you're inputting more than one item in
                                ; a statement then that becomes apparent.

        LD      BC,($5C82)      ; fetch line and column from ECHO_E
        CALL    L0DD9           ; routine CL-SET sets S-POSNL to those
                                ; values.

; if using another input channel rejoin here.

;; IN-VAR-5

t/data/zx48_base.asm  view on Meta::CPAN

        call WAIT_KEY           ; routine WAIT-KEY - input address is KEY-NEXT
                                ; but is reset to KEY-INPUT
        ld e,a                  ; save first in E

;; ED-CONTR
ED_CONTR:
        call WAIT_KEY           ; routine WAIT-KEY for control.
                                ; input address will be key-next.

        push de                 ; saved code/parameters
        ld hl,(0x5C5B)          ; fetch address of keyboard cursor from K_CUR
        res 0,(iy+0x07)         ; set MODE to 'L'

        call MAKE_ROOM          ; routine MAKE-ROOM makes 2/3 spaces at cursor

        pop bc                  ; restore code/parameters
        inc hl                  ; address first location
        ld (hl),b               ; place code (ink etc.)
        inc hl                  ; address next
        ld (hl),c               ; place possible parameter. If only one
                                ; then DE points to this location also.
        jr ADD_CH_1             ; forward to ADD-CH-1

; ------------------------

t/data/zx48_base.asm  view on Meta::CPAN

; ------------------------
; this is the branch used to add normal non-control characters
; with ED-LOOP as the stacked return address.
; it is also the OUTPUT service routine for system channel 'R'.

;; ADD-CHAR
ADD_CHAR:
        res 0,(iy+0x07)         ; set MODE to 'L'

X0F85:
        ld hl,(0x5C5B)          ; fetch address of keyboard cursor from K_CUR

        call ONE_SPACE          ; routine ONE-SPACE creates one space.

; either a continuation of above or from ED-CONTR with ED-LOOP on stack.

;; ADD-CH-1
ADD_CH_1:
        ld (de),a               ; load current character to last new location.
        inc de                  ; address next
        ld (0x5C5B),de          ; and update K_CUR system variable.

t/data/zx48_base.asm  view on Meta::CPAN


;; ED-KEYS
ED_KEYS:
        ld e,a                  ; character to E.
        ld d,0x00               ; prepare to add.
        ld hl,ed_keys_t - 7     ; base address of editing keys table. $0F99
        add hl,de               ; add E
        ld e,(hl)               ; fetch offset to E
        add hl,de               ; add offset for address of handling routine.
        push hl                 ; push the address on machine stack.
        ld hl,(0x5C5B)          ; load address of cursor from K_CUR.
        ret                     ; Make an indirect jump forward to routine.

; ------------------
; Editing keys table
; ------------------
; For each code in the range $07 to $0F this table contains a
; single offset byte to the routine that services that code.
; Note. for what was intended there should also have been an
; entry for chr$ 6 with offset to ed-symbol.

t/data/zx48_base.asm  view on Meta::CPAN

        call LINE_ADDR          ; routine LINE-ADDR to find address of line
                                ; or following line if it doesn't exist.
        call LINE_NO            ; routine LINE-NO will get line number from
                                ; address or previous line if at end-marker.
        ld a,d                  ; if there is no program then DE will
        or e                    ; contain zero so test for this.
        jp z,CLEAR_SP           ; jump to CLEAR-SP if so.

; Note. at this point we have a validated line number, not just an
; approximation and it would be best to update E_PPC with the true
; cursor line value which would enable the line cursor to be suppressed
; in all situations - see shortly.

        push hl                 ; save address of line.
        inc hl                  ; address low byte of length.
        ld c,(hl)               ; transfer to C
        inc hl                  ; next to high byte
        ld b,(hl)               ; transfer to B.
        ld hl,0x000A            ; an overhead of ten bytes
        add hl,bc               ; is added to length.
        ld b,h                  ; transfer adjusted value

t/data/zx48_base.asm  view on Meta::CPAN

        call CLEAR_SP           ; routine CLEAR-SP clears editing area.
        ld hl,(0x5C51)          ; address CURCHL
        ex (sp),hl              ; swap with line address on stack
        push hl                 ; save line address underneath

        ld a,0xFF               ; select system channel 'R'
        call CHAN_OPEN          ; routine CHAN-OPEN opens it

        pop hl                  ; drop line address
        dec hl                  ; make it point to first byte of line num.
        dec (iy+0x0F)           ; decrease E_PPC_lo to suppress line cursor.
                                ; Note. ineffective when E_PPC is one
                                ; greater than last line of program perhaps
                                ; as a result of a delete.
                                ; credit. Paul Harrison 1982.

        call OUT_LINE           ; routine OUT-LINE outputs the BASIC line
                                ; to the editing area.
        inc (iy+0x0F)           ; restore E_PPC_lo to the previous value.
        ld hl,(0x5C59)          ; address E_LINE in editing area.
        inc hl                  ; advance

t/data/zx48_base.asm  view on Meta::CPAN

        ld (0x5C5B),hl          ; update K_CUR to address start of BASIC.
        pop hl                  ; restore the address of CURCHL.
        call CHAN_FLAG          ; routine CHAN-FLAG sets flags for it.

        ret                     ; RETURN to ED-LOOP.

; -------------------
; Cursor down editing
; -------------------
;   The BASIC lines are displayed at the top of the screen and the user
;   wishes to move the cursor down one line in edit mode.
;   With INPUT LINE, this key must be used instead of entering STOP.

;; ED-DOWN
ED_DOWN:
        bit 5,(iy+0x37)         ; test FLAGX  - Input Mode ?
        jr nz,ED_STOP           ; skip to ED-STOP if so

        ld hl,0x5C49            ; address E_PPC - 'current line'
        call LN_FETCH           ; routine LN-FETCH fetches number of next
                                ; line or same if at end of program.

t/data/zx48_base.asm  view on Meta::CPAN

; ---

;; ED-STOP
ED_STOP:
        ld (iy+0x00),0x10       ; set ERR_NR to 'STOP in INPUT' code
        jr ED_ENTER             ; forward to ED-ENTER to produce error.

; -------------------
; Cursor left editing
; -------------------
; This acts on the cursor in the lower section of the screen in both
; editing and input mode.

;; ED-LEFT
ED_LEFT:
        call ED_EDGE            ; routine ED-EDGE moves left if possible
        jr ED_CUR               ; forward to ED-CUR to update K-CUR
                                ; and return to ED-LOOP.

; --------------------
; Cursor right editing
; --------------------
; This acts on the cursor in the lower screen in both editing and input
; mode and moves it to the right.

;; ED-RIGHT
ED_RIGHT:
        ld a,(hl)               ; fetch addressed character.
        cp 0x0D                 ; is it carriage return ?
        ret z                   ; return if so to ED-LOOP

        inc hl                  ; address next character

;; ED-CUR
ED_CUR:
        ld (0x5C5B),hl          ; update K_CUR system variable
        ret                     ; return to ED-LOOP

; --------------
; DELETE editing
; --------------
; This acts on the lower screen and deletes the character to left of
; cursor. If control characters are present these are deleted first
; leaving the naked parameter (0-7) which appears as a '?' except in the
; case of chr$ 6 which is the comma control character. It is not mandatory
; to delete these second characters.

;; ED-DELETE
ED_DELETE:
        call ED_EDGE            ; routine ED-EDGE moves cursor to left.
        ld bc,0x0001            ; of character to be deleted.
        jp RECLAIM_2            ; to RECLAIM-2 reclaim the character.

; ------------------------------------------
; Ignore next 2 codes from key-input routine
; ------------------------------------------
; Since AT and TAB cannot be entered this point is never reached
; from the keyboard. If inputting from a tape device or network then
; the control and two following characters are ignored and processing
; continues as if a carriage return had been received.

t/data/zx48_base.asm  view on Meta::CPAN

ED_END:
        pop hl                  ; the previous value of ERR_SP
        ld (0x5C3D),hl          ; is restored to ERR_SP system variable
        bit 7,(iy+0x00)         ; is ERR_NR $FF (= 'OK') ?
        ret nz                  ; return if so

        ld sp,hl                ; else put error routine on stack
        ret                     ; and make an indirect jump to it.

; -----------------------------
; Move cursor left when editing
; -----------------------------
; This routine moves the cursor left. The complication is that it must
; not position the cursor between control codes and their parameters.
; It is further complicated in that it deals with TAB and AT characters
; which are never present from the keyboard.
; The method is to advance from the beginning of the line each time,
; jumping one, two, or three characters as necessary saving the original
; position at each jump in DE. Once it arrives at the cursor then the next
; legitimate leftmost position is in DE.

;; ED-EDGE
ED_EDGE:
        scf                     ; carry flag must be set to call the nested
        call SET_DE             ; subroutine SET-DE.
                                ; if input   then DE=WORKSP
                                ; if editing then DE=E_LINE
        sbc hl,de               ; subtract address from start of line
        add hl,de               ; and add back.
        inc hl                  ; adjust for carry.
        pop bc                  ; drop return address
        ret c                   ; return to ED-LOOP if already at left
                                ; of line.

        push bc                 ; resave return address - ED-LOOP.
        ld b,h                  ; transfer HL - cursor address
        ld c,l                  ; to BC register pair.
                                ; at this point DE addresses start of line.

;; ED-EDGE-1
ED_EDGE_1:
        ld h,d                  ; transfer DE - leftmost pointer
        ld l,e                  ; to HL
        inc hl                  ; address next leftmost character to
                                ; advance position each time.
        ld a,(de)               ; pick up previous in A

t/data/zx48_base.asm  view on Meta::CPAN

        sub 0x17                ; decimal 23 ('tab')
        adc a,0x00              ; will be 0 for 'tab' and 'at'.
        jr nz,ED_EDGE_2         ; forward to ED-EDGE-2 if not
                                ; HL has been incremented twice

        inc hl                  ; increment a third time for 'at'/'tab'

;; ED-EDGE-2
ED_EDGE_2:
        and a                   ; prepare for true subtraction
        sbc hl,bc               ; subtract cursor address from pointer
        add hl,bc               ; and add back
                                ; Note when HL matches the cursor position BC,
                                ; there is no carry and the previous
                                ; position is in DE.
        ex de,hl                ; transfer result to DE if looping again.
                                ; transfer DE to HL to be used as K-CUR
                                ; if exiting loop.
        jr c,ED_EDGE_1          ; back to ED-EDGE-1 if cursor not matched.

        ret                     ; return.

; -----------------
; Cursor up editing
; -----------------
; The main screen displays part of the BASIC program and the user wishes
; to move up one line scrolling if necessary.
; This has no alternative use in input mode.

t/data/zx48_base.asm  view on Meta::CPAN

;; KEY-DONE2
KEY_DONE2:
        scf                     ; set carry flag to show a key has been found
        ret                     ; and return.

; --------------------
; Lower screen copying
; --------------------
; This subroutine is called whenever the line in the editing area or
; input workspace is required to be printed to the lower screen.
; It is by calling this routine after any change that the cursor, for
; instance, appears to move to the left.
; Remember the edit line will contain characters and tokens
; e.g. "1000 LET a=1" is 8 characters.

;; ED-COPY
ED_COPY:
        call TEMPS              ; routine TEMPS sets temporary attributes.
        res 3,(iy+0x02)         ; update TV_FLAG  - signal no change in mode
        res 5,(iy+0x02)         ; update TV_FLAG  - signal don't clear lower
                                ; screen.

t/data/zx48_base.asm  view on Meta::CPAN

        call SET_DE             ; call routine SET-DE
                                ; if in input DE = WORKSP
                                ; if in edit  DE = E_LINE
        ex de,hl                ; start address to HL

        call OUT_LINE2          ; routine OUT-LINE2 outputs entire line up to
                                ; carriage return including initial
                                ; characterized line number when present.
        ex de,hl                ; transfer new address to DE
        call OUT_CURS           ; routine OUT-CURS considers a
                                ; terminating cursor.

        ld hl,(0x5C8A)          ; fetch updated SPOSNL
        ex (sp),hl              ; exchange with ECHO_E on stack
        ex de,hl                ; transfer ECHO_E to DE
        call TEMPS              ; routine TEMPS to re-set attributes
                                ; if altered.

; the lower screen was not cleared, at the outset, so if deleting then old
; text from a previous print may follow this line and requires blanking.

t/data/zx48_base.asm  view on Meta::CPAN

; WORKSP/STKBOT/STKEND though no use is made of this. The routines also
; reset MEM to its usual place in the systems variable area should it
; have been relocated to a FOR-NEXT variable. The main entry point
; SET-MIN is called at the start of the MAIN-EXEC loop and prior to
; displaying an error.

;; SET-MIN
SET_MIN:
        ld hl,(0x5C59)          ; fetch E_LINE
        ld (hl),0x0D            ; insert carriage return
        ld (0x5C5B),hl          ; make K_CUR keyboard cursor point there.
        inc hl                  ; next location
        ld (hl),0x80            ; holds end-marker $80
        inc hl                  ; next location becomes
        ld (0x5C61),hl          ; start of WORKSP

; This entry point is used prior to input and prior to the execution,
; or parsing, of each statement.

;; SET-WORK
SET_WORK:

t/data/zx48_base.asm  view on Meta::CPAN

; ------------------------
; This routine prints a whole BASIC line and it is called
; from LIST-ALL to output the line to current channel
; and from ED-EDIT to 'sprint' the line to the edit buffer.

;; OUT-LINE
OUT_LINE:
        ld bc,(0x5C49)          ; fetch E_PPC the current line which may be
                                ; unchecked and not exist.
        call CP_LINES           ; routine CP-LINES finds match or line after.
        ld d,0x3E               ; prepare cursor '>' in D.
        jr z,OUT_LINE1          ; to OUT-LINE1 if matched or line after.

        ld de,0x0000            ; put zero in D, to suppress line cursor.
        rl e                    ; pick up carry in E if line before current
                                ; leave E zero if same or after.

;; OUT-LINE1
OUT_LINE1:
        ld (iy+0x2D),e          ; save flag in BREG which is spare.
        ld a,(hl)               ; get high byte of line number.
        cp 0x40                 ; is it too high ($2F is maximum possible) ?
        pop bc                  ; drop the return address and
        ret nc                  ; make an early return if so >>>

        push bc                 ; save return address
        call OUT_NUM_2          ; routine OUT-NUM-2 to print addressed number
                                ; with leading space.
        inc hl                  ; skip low number byte.
        inc hl                  ; and the two
        inc hl                  ; length bytes.
        res 0,(iy+0x01)         ; update FLAGS - signal leading space required.
        ld a,d                  ; fetch the cursor.
        and a                   ; test for zero.
        jr z,OUT_LINE3          ; to OUT-LINE3 if zero.


        rst 0x10                ; PRINT-A prints '>' the current line cursor.

; this entry point is called from ED-COPY

;; OUT-LINE2
OUT_LINE2:
        set 0,(iy+0x01)         ; update FLAGS - suppress leading space.

;; OUT-LINE3
OUT_LINE3:
        push de                 ; save flag E for a return value.

t/data/zx48_base.asm  view on Meta::CPAN

                                ; address.
        and a                   ; clear the carry flag.
        sbc hl,de               ; test if an error address has been reached.
        jr nz,OUT_LINE5         ; forward to OUT-LINE5 if not.

        ld a,0x3F               ; load A with '?' the error marker.
        call OUT_FLASH          ; routine OUT-FLASH to print flashing marker.

;; OUT-LINE5
OUT_LINE5:
        call OUT_CURS           ; routine OUT-CURS will print the cursor if
                                ; this is the right position.
        ex de,hl                ; restore address pointer to HL.
        ld a,(hl)               ; fetch the addressed character.
        call NUMBER             ; routine NUMBER skips a hidden floating
                                ; point number if present.
        inc hl                  ; now increment the pointer.
        cp 0x0D                 ; is character end-of-line ?
        jr z,OUT_LINE6          ; to OUT-LINE6, if so, as line is finished.

        ex de,hl                ; save the pointer in DE.

t/data/zx48_base.asm  view on Meta::CPAN

        inc hl
        inc hl
        inc hl
        ld a,(hl)               ; fetch the following character
        ret                     ; for return value.

; --------------------------
; Print a flashing character
; --------------------------
; This subroutine is called from OUT-LINE to print a flashing error
; marker '?' or from the next routine to print a flashing cursor e.g. 'L'.
; However, this only gets called from OUT-LINE when printing the edit line
; or the input buffer to the lower screen so a direct call to $09F4 can
; be used, even though out-line outputs to other streams.
; In fact the alternate set is used for the whole routine.

;; OUT-FLASH
OUT_FLASH:
        exx                     ; switch in alternate set

        ld hl,(0x5C8F)          ; fetch L = ATTR_T, H = MASK-T

t/data/zx48_base.asm  view on Meta::CPAN


        pop hl                  ; pop P_FLAG to H.
        ld (iy+0x57),h          ; and restore system variable P_FLAG.
        pop hl                  ; restore temporary masks
        ld (0x5C8F),hl          ; and restore system variables ATTR_T/MASK_T

        exx                     ; switch back to main set
        ret                     ; return

; ----------------
; Print the cursor
; ----------------
; This routine is called before any character is output while outputting
; a BASIC line or the input buffer. This includes listing to a printer
; or screen, copying a BASIC line to the edit buffer and printing the
; input buffer or edit buffer to the lower screen. It is only in the
; latter two cases that it has any relevance and in the last case it
; performs another very important function also.

;; OUT-CURS
OUT_CURS:
        ld hl,(0x5C5B)          ; fetch K_CUR the current cursor address
        and a                   ; prepare for true subtraction.
        sbc hl,de               ; test against pointer address in DE and
        ret nz                  ; return if not at exact position.

; the value of MODE, maintained by KEY-INPUT, is tested and if non-zero
; then this value 'E' or 'G' will take precedence.

        ld a,(0x5C41)           ; fetch MODE  0='KLC', 1='E', 2='G'.
        rlc a                   ; double the value and set flags.
        jr z,OUT_C_1            ; to OUT-C-1 if still zero ('KLC').

        add a,0x43              ; add 'C' - will become 'E' if originally 1
                                ; or 'G' if originally 2.
        jr OUT_C_2              ; forward to OUT-C-2 to print.

; ---

; If mode was zero then, while printing a BASIC line, bit 2 of flags has been
; set if 'THEN' or ':' was encountered as a main character and reset otherwise.
; This is now used to determine if the 'K' cursor is to be printed but this
; transient state is also now transferred permanently to bit 3 of FLAGS
; to let the interrupt routine know how to decode the next key.

;; OUT-C-1
OUT_C_1:
        ld hl,0x5C3B            ; Address FLAGS
        res 3,(hl)              ; signal 'K' mode initially.
        ld a,0x4B               ; prepare letter 'K'.
        bit 2,(hl)              ; test FLAGS - was the
                                ; previous main character ':' or 'THEN' ?

t/data/zx48_base.asm  view on Meta::CPAN

        jr nz,OUT_CH_2          ; to OUT-CH-2 with others to set 'L' mode.

        push af                 ; save character.
        ld a,(0x5C6A)           ; fetch FLAGS2.
        xor 0x04                ; toggle the quotes flag.
        ld (0x5C6A),a           ; update FLAGS2
        pop af                  ; and restore character.

;; OUT-CH-2
OUT_CH_2:
        set 2,(iy+0x01)         ; update FLAGS - signal L mode if the cursor
                                ; is next.

;; OUT-CH-3
OUT_CH_3:
        rst 0x10                ; PRINT-A vectors the character to
                                ; channel 'S', 'K', 'R' or 'P'.
        ret                     ; return.

; -------------------------------------------
; Get starting address of line, or line after

t/data/zx48_base.asm  view on Meta::CPAN

        rrca                    ; test if quotes required.
        jr nc,IN_PR_3           ; forward to IN-PR-3 if not.

        ld a,0x22               ; load the '"' character
        ld (de),a               ; place quote in first new location at DE.
        dec hl                  ; decrease HL - from carriage return.
        ld (hl),a               ; and place a quote in second location.

;; IN-PR-3
IN_PR_3:
        ld (0x5C5B),hl          ; set keyboard cursor K_CUR to HL
        bit 7,(iy+0x37)         ; test FLAGX  - is this INPUT LINE ??
        jr nz,IN_VAR_3          ; forward to IN-VAR-3 if so as input will
                                ; be accepted without checking its syntax.

        ld hl,(0x5C5D)          ; fetch CH_ADD
        push hl                 ; and save on stack.
        ld hl,(0x5C3D)          ; fetch ERR_SP
        push hl                 ; and save on stack

;; IN-VAR-1

t/data/zx48_base.asm  view on Meta::CPAN

;; IN-VAR-3
IN_VAR_3:
        call EDITOR             ; routine EDITOR is called for input

; when ENTER received rejoin other route but with no syntax check.

; INPUT and INPUT LINE converge here.

;; IN-VAR-4
IN_VAR_4:
        ld (iy+0x22),0x00       ; set K_CUR_hi to a low value so that the cursor
                                ; no longer appears in the input line.

        call IN_CHAN_K          ; routine IN-CHAN-K tests if the keyboard
                                ; is being used for input.
        jr nz,IN_VAR_5          ; forward to IN-VAR-5 if using another input
                                ; channel.

; continue here if using the keyboard.

        call ED_COPY            ; routine ED-COPY overprints the edit line
                                ; to the lower screen. The only visible
                                ; affect is that the cursor disappears.
                                ; if you're inputting more than one item in
                                ; a statement then that becomes apparent.

        ld bc,(0x5C82)          ; fetch line and column from ECHO_E
        call CL_SET             ; routine CL-SET sets S-POSNL to those
                                ; values.

; if using another input channel rejoin here.

;; IN-VAR-5

t/data/zx48_benchmark.asm  view on Meta::CPAN

                                ; own in RAM and make CHARS point to it.
RASP          equ $5C38         ; Length of warning buzz.
PIP           equ $5C39         ; Length of keyboard click.
ERR_NR        equ $5C3A         ; 1 less than the report code. Starts off at 255 (for 1)
                                ; so PEEK 23610 gives 255.
FLAGS         equ $5C3B         ; Various flags to control the BASIC system.
TV_FLAG       equ $5C3C         ; Flags associated with the television.
ERR_SP        equ $5C3D         ; Address of item on machine stack to be used as
                                ; error return.
LIST_SP       equ $5C3F         ; Address of return address from automatic listing.
MODE          equ $5C41         ; Specifies K, L, C. E or G cursor.
NEWPPC        equ $5C42         ; Line to be jumped to.
NSPPC         equ $5C44         ; Statement number in line to be jumped to. Poking
                                ; first NEWPPC and then NSPPC forces a jump to
                                ; a specified statement in a line.
PPC           equ $5C45         ; Line number of statement currently being executed.
SUBPPC        equ $5C47         ; Number within line of statement being executed.
BORDCR        equ $5C48         ; Border colour * 8; also contains the attributes
                                ; normally used for the lower half of the screen.
E_PPC         equ $5C49         ; Number of current line (with program cursor).
VARS          equ $5C4B         ; Address of variables.
DEST          equ $5C4D         ; Address of variable in assignment.
CHANS         equ $5C4F         ; Address of channel data.
CURCHL        equ $5C51         ; Address of information currently being used for
                                ; input and output.
PROG          equ $5C53         ; Address of BASIC program.
NXTLIN        equ $5C55         ; Address of next line in program.
DATADD        equ $5C57         ; Address of terminator of last DATA item.
E_LINE        equ $5C59         ; Address of command being typed in.
K_CUR         equ $5C5B         ; Address of cursor.
CH_ADD        equ $5C5D         ; Address of the next character to be interpreted:
                                ; the character after the argument of PEEK, or
                                ; the NEWLINE at the end of a POKE statement.
X_PTR         equ $5C5F         ; Address of the character after the ? marker.
WORKSP        equ $5C61         ; Address of temporary work space.
STKBOT        equ $5C63         ; Address of bottom of calculator stack.
STKEND        equ $5C65         ; Address of start of spare space.
BREG          equ $5C67         ; Calculator's b register.
MEM           equ $5C68         ; Address of area used for calculator's memory.
                                ; (Usually MEMBOT, but not always.)

t/data/zx48_benchmark.asm  view on Meta::CPAN

                                ; but is reset to KEY-INPUT
        ld e, a                 ; save first in E

;; ED-CONTR

ED_CONTR:
        call WAIT_KEY           ; routine WAIT-KEY for control.
                                ; input address will be key-next.

        push de                 ; saved code/parameters
        ld hl, (K_CUR)          ; fetch address of keyboard cursor from K_CUR
        res 0, (iy+MODE-IY0)    ; set MODE to 'L'

        call MAKE_ROOM          ; routine MAKE-ROOM makes 2/3 spaces at cursor

        pop bc                  ; restore code/parameters
        inc hl                  ; address first location
        ldi (hl), b             ; place code (ink etc.)
                                ; address next
        ld (hl), c              ; place possible parameter. If only one
                                ; then DE points to this location also.
        jr ADD_CH_1             ; forward to ADD-CH-1


t/data/zx48_benchmark.asm  view on Meta::CPAN

; with ED-LOOP as the stacked return address.
; it is also the OUTPUT service routine for system channel 'R'.

;; ADD-CHAR

ADD_CHAR:
        res 0, (iy+MODE-IY0)    ; set MODE to 'L'


X0F85:
        ld hl, (K_CUR)          ; fetch address of keyboard cursor from K_CUR

        call ONE_SPACE          ; routine ONE-SPACE creates one space.

; either a continuation of above or from ED-CONTR with ED-LOOP on stack.

;; ADD-CH-1

ADD_CH_1:
        ldi (de), a             ; load current character to last new location.
                                ; address next

t/data/zx48_benchmark.asm  view on Meta::CPAN

;; ED-KEYS

ED_KEYS:
        ld e, a                 ; character to E.
        ld d, $00               ; prepare to add.
        ld hl, ed_keys_t-$07    ; base address of editing keys table. $0F99
        add hl, de              ; add E
        ld e, (hl)              ; fetch offset to E
        add hl, de              ; add offset for address of handling routine.
        push hl                 ; push the address on machine stack.
        ld hl, (K_CUR)          ; load address of cursor from K_CUR.
        ret                     ; Make an indirect jump forward to routine.


; ------------------
; Editing keys table
; ------------------
; For each code in the range $07 to $0F this table contains a
; single offset byte to the routine that services that code.
; Note. for what was intended there should also have been an
; entry for chr$ 6 with offset to ed-symbol.

t/data/zx48_benchmark.asm  view on Meta::CPAN

        call LINE_ADDR          ; routine LINE-ADDR to find address of line
                                ; or following line if it doesn't exist.
        call LINE_NO            ; routine LINE-NO will get line number from
                                ; address or previous line if at end-marker.
        ld a, d                 ; if there is no program then DE will
        or e                    ; contain zero so test for this.
        jp z, CLEAR_SP          ; jump to CLEAR-SP if so.

; Note. at this point we have a validated line number, not just an
; approximation and it would be best to update E_PPC with the true
; cursor line value which would enable the line cursor to be suppressed
; in all situations - see shortly.

        push hl                 ; save address of line.
        inc hl                  ; address low byte of length.
        ldi c, (hl)             ; transfer to C
                                ; next to high byte
        ld b, (hl)              ; transfer to B.
        ld hl, $000A            ; an overhead of ten bytes
        add hl, bc              ; is added to length.
        ld bc, hl               ; transfer adjusted value

t/data/zx48_benchmark.asm  view on Meta::CPAN

        call CLEAR_SP           ; routine CLEAR-SP clears editing area.
        ld hl, (CURCHL)         ; address CURCHL
        ex (sp), hl             ; swap with line address on stack
        push hl                 ; save line address underneath

        ld a, $FF               ; select system channel 'R'
        call CHAN_OPEN          ; routine CHAN-OPEN opens it

        pop hl                  ; drop line address
        dec hl                  ; make it point to first byte of line num.
        dec (iy+E_PPC-IY0)      ; decrease E_PPC_lo to suppress line cursor.
                                ; Note. ineffective when E_PPC is one
                                ; greater than last line of program perhaps
                                ; as a result of a delete.
                                ; credit. Paul Harrison 1982.

        call OUT_LINE           ; routine OUT-LINE outputs the BASIC line
                                ; to the editing area.
        inc (iy+E_PPC-IY0)      ; restore E_PPC_lo to the previous value.
        ld hl, (E_LINE)         ; address E_LINE in editing area.
        inc hl                  ; advance

t/data/zx48_benchmark.asm  view on Meta::CPAN

        pop hl                  ; restore the address of CURCHL.
        call CHAN_FLAG          ; routine CHAN-FLAG sets flags for it.

        ret                     ; RETURN to ED-LOOP.


; -------------------
; Cursor down editing
; -------------------
;   The BASIC lines are displayed at the top of the screen and the user
;   wishes to move the cursor down one line in edit mode.
;   With INPUT LINE, this key must be used instead of entering STOP.

;; ED-DOWN

ED_DOWN:
        bit 5, (iy+FLAGX-IY0)   ; test FLAGX  - Input Mode ?
        jr nz, ED_STOP          ; skip to ED-STOP if so

        ld hl, E_PPC            ; address E_PPC - 'current line'
        call LN_FETCH           ; routine LN-FETCH fetches number of next

t/data/zx48_benchmark.asm  view on Meta::CPAN

;; ED-STOP

ED_STOP:
        ld (iy+ERR_NR-IY0), $10 ; set ERR_NR to 'STOP in INPUT' code
        jr ED_ENTER             ; forward to ED-ENTER to produce error.


; -------------------
; Cursor left editing
; -------------------
; This acts on the cursor in the lower section of the screen in both
; editing and input mode.

;; ED-LEFT

ED_LEFT:
        call ED_EDGE            ; routine ED-EDGE moves left if possible
        jr ED_CUR               ; forward to ED-CUR to update K-CUR
                                ; and return to ED-LOOP.


; --------------------
; Cursor right editing
; --------------------
; This acts on the cursor in the lower screen in both editing and input
; mode and moves it to the right.

;; ED-RIGHT

ED_RIGHT:
        ld a, (hl)              ; fetch addressed character.
        cp $0D                  ; is it carriage return ?
        ret z                   ; return if so to ED-LOOP

        inc hl                  ; address next character

t/data/zx48_benchmark.asm  view on Meta::CPAN


ED_CUR:
        ld (K_CUR), hl          ; update K_CUR system variable
        ret                     ; return to ED-LOOP


; --------------
; DELETE editing
; --------------
; This acts on the lower screen and deletes the character to left of
; cursor. If control characters are present these are deleted first
; leaving the naked parameter (0-7) which appears as a '?' except in the
; case of chr$ 6 which is the comma control character. It is not mandatory
; to delete these second characters.

;; ED-DELETE

ED_DELETE:
        call ED_EDGE            ; routine ED-EDGE moves cursor to left.
        ld bc, $0001            ; of character to be deleted.
        jp RECLAIM_2            ; to RECLAIM-2 reclaim the character.


; ------------------------------------------
; Ignore next 2 codes from key-input routine
; ------------------------------------------
; Since AT and TAB cannot be entered this point is never reached
; from the keyboard. If inputting from a tape device or network then
; the control and two following characters are ignored and processing

t/data/zx48_benchmark.asm  view on Meta::CPAN

        pop hl                  ; the previous value of ERR_SP
        ld (ERR_SP), hl         ; is restored to ERR_SP system variable
        bit 7, (iy+ERR_NR-IY0)  ; is ERR_NR $FF (= 'OK') ?
        ret nz                  ; return if so

        ld sp, hl               ; else put error routine on stack
        ret                     ; and make an indirect jump to it.


; -----------------------------
; Move cursor left when editing
; -----------------------------
; This routine moves the cursor left. The complication is that it must
; not position the cursor between control codes and their parameters.
; It is further complicated in that it deals with TAB and AT characters
; which are never present from the keyboard.
; The method is to advance from the beginning of the line each time,
; jumping one, two, or three characters as necessary saving the original
; position at each jump in DE. Once it arrives at the cursor then the next
; legitimate leftmost position is in DE.

;; ED-EDGE

ED_EDGE:
        scf                     ; carry flag must be set to call the nested
        call SET_DE             ; subroutine SET-DE.
                                ; if input   then DE=WORKSP
                                ; if editing then DE=E_LINE
        sbc hl, de              ; subtract address from start of line
        add hl, de              ; and add back.
        inc hl                  ; adjust for carry.
        pop bc                  ; drop return address
        ret c                   ; return to ED-LOOP if already at left
                                ; of line.

        push bc                 ; resave return address - ED-LOOP.
        ld bc, hl               ; transfer HL - cursor address
                                ; to BC register pair.
                                ; at this point DE addresses start of line.

;; ED-EDGE-1

ED_EDGE_1:
        ld hl, de               ; transfer DE - leftmost pointer
                                ; to HL
        inc hl                  ; address next leftmost character to
                                ; advance position each time.

t/data/zx48_benchmark.asm  view on Meta::CPAN

        adc a, $00              ; will be 0 for 'tab' and 'at'.
        jr nz, ED_EDGE_2        ; forward to ED-EDGE-2 if not
                                ; HL has been incremented twice

        inc hl                  ; increment a third time for 'at'/'tab'

;; ED-EDGE-2

ED_EDGE_2:
        and a                   ; prepare for true subtraction
        sbc hl, bc              ; subtract cursor address from pointer
        add hl, bc              ; and add back
                                ; Note when HL matches the cursor position BC,
                                ; there is no carry and the previous
                                ; position is in DE.
        ex de, hl               ; transfer result to DE if looping again.
                                ; transfer DE to HL to be used as K-CUR
                                ; if exiting loop.
        jr c, ED_EDGE_1         ; back to ED-EDGE-1 if cursor not matched.

        ret                     ; return.


; -----------------
; Cursor up editing
; -----------------
; The main screen displays part of the BASIC program and the user wishes
; to move up one line scrolling if necessary.
; This has no alternative use in input mode.

t/data/zx48_benchmark.asm  view on Meta::CPAN

KEY_DONE2:
        scf                     ; set carry flag to show a key has been found
        ret                     ; and return.


; --------------------
; Lower screen copying
; --------------------
; This subroutine is called whenever the line in the editing area or
; input workspace is required to be printed to the lower screen.
; It is by calling this routine after any change that the cursor, for
; instance, appears to move to the left.
; Remember the edit line will contain characters and tokens
; e.g. "1000 LET a=1" is 8 characters.

;; ED-COPY

ED_COPY:
        call TEMPS              ; routine TEMPS sets temporary attributes.
        res 3, (iy+TV_FLAG-IY0) ; update TV_FLAG  - signal no change in mode
        res 5, (iy+TV_FLAG-IY0) ; update TV_FLAG  - signal don't clear lower

t/data/zx48_benchmark.asm  view on Meta::CPAN

        call SET_DE             ; call routine SET-DE
                                ; if in input DE = WORKSP
                                ; if in edit  DE = E_LINE
        ex de, hl               ; start address to HL

        call OUT_LINE2          ; routine OUT-LINE2 outputs entire line up to
                                ; carriage return including initial
                                ; characterized line number when present.
        ex de, hl               ; transfer new address to DE
        call OUT_CURS           ; routine OUT-CURS considers a
                                ; terminating cursor.

        ld hl, (SPOSNL)         ; fetch updated SPOSNL
        ex (sp), hl             ; exchange with ECHO_E on stack
        ex de, hl               ; transfer ECHO_E to DE
        call TEMPS              ; routine TEMPS to re-set attributes
                                ; if altered.

; the lower screen was not cleared, at the outset, so if deleting then old
; text from a previous print may follow this line and requires blanking.

t/data/zx48_benchmark.asm  view on Meta::CPAN

; reset MEM to its usual place in the systems variable area should it
; have been relocated to a FOR-NEXT variable. The main entry point
; SET-MIN is called at the start of the MAIN-EXEC loop and prior to
; displaying an error.

;; SET-MIN

SET_MIN:
        ld hl, (E_LINE)         ; fetch E_LINE
        ld (hl), $0D            ; insert carriage return
        ld (K_CUR), hl          ; make K_CUR keyboard cursor point there.
        inc hl                  ; next location
        ldi (hl), $80           ; holds end-marker $80
                                ; next location becomes
        ld (WORKSP), hl         ; start of WORKSP

; This entry point is used prior to input and prior to the execution,
; or parsing, of each statement.

;; SET-WORK

t/data/zx48_benchmark.asm  view on Meta::CPAN

; This routine prints a whole BASIC line and it is called
; from LIST-ALL to output the line to current channel
; and from ED-EDIT to 'sprint' the line to the edit buffer.

;; OUT-LINE

OUT_LINE:
        ld bc, (E_PPC)          ; fetch E_PPC the current line which may be
                                ; unchecked and not exist.
        call CP_LINES           ; routine CP-LINES finds match or line after.
        ld d, $3E               ; prepare cursor '>' in D.
        jr z, OUT_LINE1         ; to OUT-LINE1 if matched or line after.

        ld de, $0000            ; put zero in D, to suppress line cursor.
        rl e                    ; pick up carry in E if line before current
                                ; leave E zero if same or after.

;; OUT-LINE1

OUT_LINE1:
        ld (iy+BREG-IY0), e     ; save flag in BREG which is spare.
        ld a, (hl)              ; get high byte of line number.
        cp $40                  ; is it too high ($2F is maximum possible) ?
        pop bc                  ; drop the return address and
        ret nc                  ; make an early return if so >>>

        push bc                 ; save return address
        call OUT_NUM_2          ; routine OUT-NUM-2 to print addressed number
                                ; with leading space.
        inc hl                  ; skip low number byte.
        inc hl                  ; and the two
        inc hl                  ; length bytes.
        res 0, (iy+FLAGS-IY0)   ; update FLAGS - signal leading space required.
        ld a, d                 ; fetch the cursor.
        and a                   ; test for zero.
        jr z, OUT_LINE3         ; to OUT-LINE3 if zero.


        rst $10                 ; PRINT-A prints '>' the current line cursor.

; this entry point is called from ED-COPY

;; OUT-LINE2

OUT_LINE2:
        set 0, (iy+FLAGS-IY0)   ; update FLAGS - suppress leading space.

;; OUT-LINE3

t/data/zx48_benchmark.asm  view on Meta::CPAN

        and a                   ; clear the carry flag.
        sbc hl, de              ; test if an error address has been reached.
        jr nz, OUT_LINE5        ; forward to OUT-LINE5 if not.

        ld a, $3F               ; load A with '?' the error marker.
        call OUT_FLASH          ; routine OUT-FLASH to print flashing marker.

;; OUT-LINE5

OUT_LINE5:
        call OUT_CURS           ; routine OUT-CURS will print the cursor if
                                ; this is the right position.
        ex de, hl               ; restore address pointer to HL.
        ld a, (hl)              ; fetch the addressed character.
        call NUMBER             ; routine NUMBER skips a hidden floating
                                ; point number if present.
        inc hl                  ; now increment the pointer.
        cp $0D                  ; is character end-of-line ?
        jr z, OUT_LINE6         ; to OUT-LINE6, if so, as line is finished.

        ex de, hl               ; save the pointer in DE.

t/data/zx48_benchmark.asm  view on Meta::CPAN

        inc hl
        inc hl
        ld a, (hl)              ; fetch the following character
        ret                     ; for return value.


; --------------------------
; Print a flashing character
; --------------------------
; This subroutine is called from OUT-LINE to print a flashing error
; marker '?' or from the next routine to print a flashing cursor e.g. 'L'.
; However, this only gets called from OUT-LINE when printing the edit line
; or the input buffer to the lower screen so a direct call to $09F4 can
; be used, even though out-line outputs to other streams.
; In fact the alternate set is used for the whole routine.

;; OUT-FLASH

OUT_FLASH:
        exx                     ; switch in alternate set

t/data/zx48_benchmark.asm  view on Meta::CPAN

        pop hl                  ; pop P_FLAG to H.
        ld (iy+P_FLAG-IY0), h   ; and restore system variable P_FLAG.
        pop hl                  ; restore temporary masks
        ld (ATTR_T), hl         ; and restore system variables ATTR_T/MASK_T

        exx                     ; switch back to main set
        ret                     ; return


; ----------------
; Print the cursor
; ----------------
; This routine is called before any character is output while outputting
; a BASIC line or the input buffer. This includes listing to a printer
; or screen, copying a BASIC line to the edit buffer and printing the
; input buffer or edit buffer to the lower screen. It is only in the
; latter two cases that it has any relevance and in the last case it
; performs another very important function also.

;; OUT-CURS

OUT_CURS:
        ld hl, (K_CUR)          ; fetch K_CUR the current cursor address
        and a                   ; prepare for true subtraction.
        sbc hl, de              ; test against pointer address in DE and
        ret nz                  ; return if not at exact position.

; the value of MODE, maintained by KEY-INPUT, is tested and if non-zero
; then this value 'E' or 'G' will take precedence.

        ld a, (MODE)            ; fetch MODE  0='KLC', 1='E', 2='G'.
        rlc a                   ; double the value and set flags.
        jr z, OUT_C_1           ; to OUT-C-1 if still zero ('KLC').

        add a, $43              ; add 'C' - will become 'E' if originally 1
                                ; or 'G' if originally 2.
        jr OUT_C_2              ; forward to OUT-C-2 to print.


; ---

; If mode was zero then, while printing a BASIC line, bit 2 of flags has been
; set if 'THEN' or ':' was encountered as a main character and reset otherwise.
; This is now used to determine if the 'K' cursor is to be printed but this
; transient state is also now transferred permanently to bit 3 of FLAGS
; to let the interrupt routine know how to decode the next key.

;; OUT-C-1

OUT_C_1:
        ld hl, FLAGS            ; Address FLAGS
        res 3, (hl)             ; signal 'K' mode initially.
        ld a, $4B               ; prepare letter 'K'.
        bit 2, (hl)             ; test FLAGS - was the

t/data/zx48_benchmark.asm  view on Meta::CPAN


        push af                 ; save character.
        ld a, (FLAGS2)          ; fetch FLAGS2.
        xor $04                 ; toggle the quotes flag.
        ld (FLAGS2), a          ; update FLAGS2
        pop af                  ; and restore character.

;; OUT-CH-2

OUT_CH_2:
        set 2, (iy+FLAGS-IY0)   ; update FLAGS - signal L mode if the cursor
                                ; is next.

;; OUT-CH-3

OUT_CH_3:
        rst $10                 ; PRINT-A vectors the character to
                                ; channel 'S', 'K', 'R' or 'P'.
        ret                     ; return.


t/data/zx48_benchmark.asm  view on Meta::CPAN

        jr nc, IN_PR_3          ; forward to IN-PR-3 if not.

        ld a, $22               ; load the '"' character
        ld (de), a              ; place quote in first new location at DE.
        dec hl                  ; decrease HL - from carriage return.
        ld (hl), a              ; and place a quote in second location.

;; IN-PR-3

IN_PR_3:
        ld (K_CUR), hl          ; set keyboard cursor K_CUR to HL
        bit 7, (iy+FLAGX-IY0)   ; test FLAGX  - is this INPUT LINE ??
        jr nz, IN_VAR_3         ; forward to IN-VAR-3 if so as input will
                                ; be accepted without checking its syntax.

        ld hl, (CH_ADD)         ; fetch CH_ADD
        push hl                 ; and save on stack.
        ld hl, (ERR_SP)         ; fetch ERR_SP
        push hl                 ; and save on stack

;; IN-VAR-1

t/data/zx48_benchmark.asm  view on Meta::CPAN

IN_VAR_3:
        call EDITOR             ; routine EDITOR is called for input

; when ENTER received rejoin other route but with no syntax check.

; INPUT and INPUT LINE converge here.

;; IN-VAR-4

IN_VAR_4:
        ld (iy+$22), $00        ; set K_CUR_hi to a low value so that the cursor
                                ; no longer appears in the input line.

        call IN_CHAN_K          ; routine IN-CHAN-K tests if the keyboard
                                ; is being used for input.
        jr nz, IN_VAR_5         ; forward to IN-VAR-5 if using another input
                                ; channel.

; continue here if using the keyboard.

        call ED_COPY            ; routine ED-COPY overprints the edit line
                                ; to the lower screen. The only visible
                                ; affect is that the cursor disappears.
                                ; if you're inputting more than one item in
                                ; a statement then that becomes apparent.

        ld bc, (ECHO_E)         ; fetch line and column from ECHO_E
        call CL_SET             ; routine CL-SET sets S-POSNL to those
                                ; values.

; if using another input channel rejoin here.

;; IN-VAR-5

t/data/zx81.asm  view on Meta::CPAN



; ======================
; ZX-81 SYSTEM VARIABLES
; ======================

ERR_NR        equ $4000         ; N1   Current report code minus one
FLAGS         equ $4001         ; N1   Various flags
ERR_SP        equ $4002         ; N2   Address of top of GOSUB stack
RAMTOP        equ $4004         ; N2   Address of reserved area (not wiped out by NEW)
MODE          equ $4006         ; N1   Current cursor mode
PPC           equ $4007         ; N2   Line number of line being executed
VERSN         equ $4009         ; N1   First system variable to be SAVEd
E_PPC         equ $400A         ; N2   Line number of line with cursor
D_FILE        equ $400C         ; N2   Address of start of display file
DF_CC         equ $400E         ; N2   Address of print position within display file
VARS          equ $4010         ; N2   Address of start of variables area
DEST          equ $4012         ; N2   Address of variable being assigned
E_LINE        equ $4014         ; N2   Address of start of edit line
CH_ADD        equ $4016         ; N2   Address of the next character to interpret
X_PTR         equ $4018         ; N2   Address of char. preceding syntax error marker
STKBOT        equ $401A         ; N2   Address of calculator stack
STKEND        equ $401C         ; N2   Address of end of calculator stack
BERG          equ $401E         ; N1   Used by floating point calculator

t/data/zx81.asm  view on Meta::CPAN

                                ; 
                                ; ---
                                ; 

        defb $FF                ; unused location.
                                ; 
; ---------------------------------
; THE 'COLLECT A CHARACTER' RESTART
; ---------------------------------
; The character addressed by the system variable CH_ADD is fetched and if it
; is a non-space, non-cursor character it is returned else CH_ADD is
; incremented and the new addressed character tested until it is not a space.

;; GET-CHAR

GET_CHAR:
        ld hl, (CH_ADD)         ; set HL to character address CH_ADD.
        ld a, (hl)              ; fetch addressed character to A.
                                ; 
;; TEST-SP

t/data/zx81.asm  view on Meta::CPAN

        and a                   ; test for space.
        ret nz                  ; return if not a space
                                ; 
        nop                     ; else trickle through
        nop                     ; to the next routine.
                                ; 
; ------------------------------------
; THE 'COLLECT NEXT CHARACTER' RESTART
; ------------------------------------
; The character address in incremented and the new addressed character is
; returned if not a space, or cursor, else the process is repeated.

;; NEXT-CHAR

NEXT_CHAR:
        call CH_ADD_1           ; routine CH-ADD+1 gets next immediate
                                ; character.
        jr TEST_SP              ; back to TEST-SP.
                                ; 

; ---

t/data/zx81.asm  view on Meta::CPAN

;   generated by the HALT that cause the Refresh value to rise from $E0 to $FF,
;   triggering an Interrupt on the next transition.
;   This works happily for all display lines between these extremes and the
;   generation of the 32 character, 1 pixel high, line will always take 128
;   clock cycles.

; ---------------------------------
; THE 'INCREMENT CH-ADD' SUBROUTINE
; ---------------------------------
; This is the subroutine that increments the character address system variable
; and returns if it is not the cursor character. The ZX81 has an actual
; character at the cursor position rather than a pointer system variable
; as is the case with prior and subsequent ZX computers.

;; CH-ADD+1

CH_ADD_1:
        ld hl, (CH_ADD)         ; fetch character address to CH_ADD.
                                ; 
;; TEMP-PTR1

TEMP_PTR1:
        inc hl                  ; address next immediate location.
                                ; 
;; TEMP-PTR2

TEMP_PTR2:
        ld (CH_ADD), hl         ; update system variable CH_ADD.
                                ; 
        ld a, (hl)              ; fetch the character.
        cp $7F                  ; compare to cursor character.
        ret nz                  ; return if not the cursor.
                                ; 
        jr TEMP_PTR1            ; back for next character to TEMP-PTR1.
                                ; 

; --------------------
; THE 'ERROR-2' BRANCH
; --------------------
; This is a continuation of the error restart.
; If the error occurred in runtime then the error stack pointer will probably
; lead to an error report being printed unless it occurred during input.

t/data/zx81.asm  view on Meta::CPAN

        defb $E2                ; LLIST
        defb $C0                ; ""
        defb $D9                ; OR
        defb $E0                ; STEP
        defb $DB                ; <=
        defb $DD                ; <>
        defb $75                ; EDIT
        defb $DA                ; AND
        defb $DE                ; THEN
        defb $DF                ; TO
        defb $72                ; cursor-left
        defb $77                ; RUBOUT
        defb $74                ; GRAPHICS
        defb $73                ; cursor-right
        defb $70                ; cursor-up
        defb $71                ; cursor-down
        defb $0B                ; "
        defb $11                ; )
        defb $10                ; (
        defb $0D                ; $
        defb $DC                ; >=
        defb $79                ; FUNCTION
        defb $14                ; =
        defb $15                ; +
        defb $16                ; -
        defb $D8                ; **

t/data/zx81.asm  view on Meta::CPAN

                                ; 
        ld (VARS), hl           ; set system variable VARS to next location
                                ; 
        call CLEAR              ; routine CLEAR sets $80 end-marker and the
                                ; dynamic memory pointers E_LINE, STKBOT and
                                ; STKEND.
                                ; 
;; N/L-ONLY

N_L_ONLY:
        call CURSOR_IN          ; routine CURSOR-IN inserts the cursor and
                                ; end-marker in the Edit Line also setting
                                ; size of lower display to two lines.
                                ; 
        call SLOW_FAST          ; routine SLOW/FAST selects COMPUTE and DISPLAY
                                ; 
; ---------------------------
; THE 'BASIC LISTING' SECTION
; ---------------------------
;
;

t/data/zx81.asm  view on Meta::CPAN

                                ; 
        ld (hl), d              ; 
        dec hl                  ; 
        ld (hl), e              ; 
        jr UPPER                ; to UPPER
                                ; 

; ----------------------------
; THE 'EDIT LINE COPY' SECTION
; ----------------------------
; This routine sets the edit line to just the cursor when
; 1) There is not enough memory to edit a BASIC line.
; 2) The edit key is used during input.
; The entry point LOWER


;; EDIT-INP

EDIT_INP:
        call CURSOR_IN          ; routine CURSOR-IN sets cursor only edit line.
                                ; 
; ->

;; LOWER

LOWER:
        ld hl, (E_LINE)         ; fetch edit line start from E_LINE.
                                ; 
;; EACH-CHAR

t/data/zx81.asm  view on Meta::CPAN

;; END-LINE

END_LINE:
        cp $76                  ; 
        inc hl                  ; 
        jr nz, EACH_CHAR        ; to EACH-CHAR
                                ; 
;; EDIT-LINE

EDIT_LINE:
        call CURSOR             ; routine CURSOR sets cursor K or L.
                                ; 
;; EDIT-ROOM

EDIT_ROOM:
        call LINE_ENDS          ; routine LINE-ENDS
        ld hl, (E_LINE)         ; sv E_LINE_lo
        ld (iy+ERR_NR-IY0), $FF ; sv ERR_NR
        call COPY_LINE          ; routine COPY-LINE
        bit 7, (iy+ERR_NR-IY0)  ; sv ERR_NR
        jr nz, DISPLAY_6        ; to DISPLAY-6

t/data/zx81.asm  view on Meta::CPAN

        ld hl, EDIT_INP         ; Address: EDIT-INP
        push hl                 ; ** is pushed as an error looping address.
                                ; 
        bit 5, (iy+FLAGX-IY0)   ; test FLAGX
        ret nz                  ; indirect jump if in input mode
                                ; to L046F, EDIT-INP (begin again).
                                ; 
;

        ld hl, (E_LINE)         ; fetch E_LINE
        ld (DF_CC), hl          ; and use to update the screen cursor DF_CC
                                ; 
; so now RST $10 will print the line numbers to the edit line instead of screen.
; first make sure that no newline/out of screen can occur while sprinting the
; line numbers to the edit line.

        ld hl, $1821            ; prepare line 0, column 0.
        ld (S_POSN), hl         ; update S_POSN with these dummy values.
                                ; 
        ld hl, (E_PPC)          ; fetch current line from E_PPC may be a
                                ; non-existent line e.g. last line deleted.

t/data/zx81.asm  view on Meta::CPAN

                                ; 
        dec hl                  ; point to high byte.
        call OUT_NO             ; routine OUT-NO writes number to edit line.
                                ; 
        inc hl                  ; point to length bytes.
        ld c, (hl)              ; low byte to C.
        inc hl                  ; 
        ld b, (hl)              ; high byte to B.
                                ; 
        inc hl                  ; point to first character in line.
        ld de, (DF_CC)          ; fetch display file cursor DF_CC
                                ; 
        ld a, $7F               ; prepare the cursor character.
        ld (de), a              ; and insert in edit line.
        inc de                  ; increment intended destination.
                                ; 
        push hl                 ; * save start of BASIC.
                                ; 
        ld hl, $001D            ; set an overhead of 29 bytes.
        add hl, de              ; add in the address of cursor.
        add hl, bc              ; add the length of the line.
        sbc hl, sp              ; subtract the stack pointer.
                                ; 
        pop hl                  ; * restore pointer to start of BASIC.
                                ; 
        ret nc                  ; return if not enough room to L046F EDIT-INP.
                                ; the edit key appears not to work.
                                ; 
        ldir                    ; else copy bytes from program to edit line.
                                ; Note. hidden floating point forms are also

t/data/zx81.asm  view on Meta::CPAN

        rst $10                 ; PRINT-A
        jr MORE_LINE            ; to MORE-LINE
                                ; 

; ---

;; OUT-CURS

OUT_CURS:
        ld a, (MODE)            ; Fetch value of system variable MODE
        ld b, $AB               ; Prepare an inverse [F] for function cursor.
                                ; 
        and a                   ; Test for zero -
        jr nz, FLAGS_2          ; forward if not to FLAGS-2
                                ; 
        ld a, (FLAGS)           ; Fetch system variable FLAGS.
        ld b, $B0               ; Prepare an inverse [K] for keyword cursor.
                                ; 
;; FLAGS-2

FLAGS_2:
        rra                     ; 00000?00 -> 000000?0
        rra                     ; 000000?0 -> 0000000?
        and $01                 ; 0000000?    0000000x
                                ; 
        add a, b                ; Possibly [F] -> [G]  or  [K] -> [L]
                                ; 

t/data/zx81.asm  view on Meta::CPAN


;; SET-STK-E

SET_STK_E:
        ld (STKEND), hl         ; sv STKEND
        ret                     ; 

; -----------------------
; THE 'CURSOR-IN' ROUTINE
; -----------------------
; This routine is called to set the edit line to the minimum cursor/newline
; and to set STKEND, the start of free space, at the next position.

;; CURSOR-IN

CURSOR_IN:
        ld hl, (E_LINE)         ; fetch start of edit line from E_LINE
        ld (hl), $7F            ; insert cursor character
                                ; 
        inc hl                  ; point to next location.
        ld (hl), $76            ; insert NEWLINE character
        inc hl                  ; point to next free location.
                                ; 
        ld (iy+DF_SZ-IY0), $02  ; set lower screen display file size DF_SZ
                                ; 
        jr SET_STK_B            ; exit via SET-STK-B above
                                ; 

t/data/zx81.ctl  view on Meta::CPAN

0017:B
0017-0017 FF	:B
	:; unused location.
	:;

0018:C
	:#; ---------------------------------
	:#; THE 'COLLECT A CHARACTER' RESTART
	:#; ---------------------------------
	:#; The character addressed by the system variable CH_ADD is fetched and if it
	:#; is a non-space, non-cursor character it is returned else CH_ADD is 
	:#; incremented and the new addressed character tested until it is not a space.
	:#
	:#;; GET-CHAR
0018 2A1640     ld hl, ($4016)	:C GET_CHAR
	:; set HL to character address CH_ADD.

001B:C
001B 7E         ld a, (hl)	:C
	:; fetch addressed character to A.
	:;

t/data/zx81.ctl  view on Meta::CPAN

001F:C
001F 00         nop	:C
	:; to the next routine.
	:;

0020:C
	:#; ------------------------------------
	:#; THE 'COLLECT NEXT CHARACTER' RESTART
	:#; ------------------------------------
	:#; The character address in incremented and the new addressed character is 
	:#; returned if not a space, or cursor, else the process is repeated.
	:#
	:#;; NEXT-CHAR
0020 CD4900     call $0049	:C NEXT_CHAR
	:; routine CH-ADD+1 gets next immediate
	:; character.

0023:C
0023 18F7       jr $001C	:C
	:; back to TEST-SP.
	:;

t/data/zx81.ctl  view on Meta::CPAN

	:#;   generated by the HALT that cause the Refresh value to rise from $E0 to $FF,
	:#;   triggering an Interrupt on the next transition.
	:#;   This works happily for all display lines between these extremes and the 
	:#;   generation of the 32 character, 1 pixel high, line will always take 128 
	:#;   clock cycles.
	:#
	:#; ---------------------------------
	:#; THE 'INCREMENT CH-ADD' SUBROUTINE
	:#; ---------------------------------
	:#; This is the subroutine that increments the character address system variable
	:#; and returns if it is not the cursor character. The ZX81 has an actual 
	:#; character at the cursor position rather than a pointer system variable
	:#; as is the case with prior and subsequent ZX computers.
	:#
	:#;; CH-ADD+1
0049 2A1640     ld hl, ($4016)	:C CH_ADD_1
	:; fetch character address to CH_ADD.
	:;

004C:C
	:#;; TEMP-PTR1
004C 23         inc hl	:C TEMP_PTR1

t/data/zx81.ctl  view on Meta::CPAN

004D 221640     ld ($4016), hl	:C TEMP_PTR2
	:; update system variable CH_ADD.
	:;

0050:C
0050 7E         ld a, (hl)	:C
	:; fetch the character.

0051:C
0051 FE7F       cp $7F	:C
	:; compare to cursor character.

0053:C
0053 C0         ret nz	:C
	:; return if not the cursor.
	:;

0054:C
0054 18F6       jr $004C	:C
	:; back for next character to TEMP-PTR1.
	:;

0056:C
	:#; --------------------
	:#; THE 'ERROR-2' BRANCH

t/data/zx81.ctl  view on Meta::CPAN

00B5:B
00B5-00B5 DE	:B
	:; THEN

00B6:B
00B6-00B6 DF	:B
	:; TO

00B7:B
00B7-00B7 72	:B
	:; cursor-left

00B8:B
00B8-00B8 77	:B
	:; RUBOUT

00B9:B
00B9-00B9 74	:B
	:; GRAPHICS

00BA:B
00BA-00BA 73	:B
	:; cursor-right

00BB:B
00BB-00BB 70	:B
	:; cursor-up

00BC:B
00BC-00BC 71	:B
	:; cursor-down

00BD:B
00BD-00BD 0B	:B
	:; "

00BE:B
00BE-00BE 11	:B
	:; )

00BF:B

t/data/zx81.ctl  view on Meta::CPAN

0410:C
0410 CD9A14     call $149A	:C
	:; routine CLEAR sets $80 end-marker and the 
	:; dynamic memory pointers E_LINE, STKBOT and
	:; STKEND.
	:;

0413:C
	:#;; N/L-ONLY
0413 CDAD14     call $14AD	:C N_L_ONLY
	:; routine CURSOR-IN inserts the cursor and 
	:; end-marker in the Edit Line also setting
	:; size of lower display to two lines.
	:;

0416:C
0416 CD0702     call $0207	:C
	:; routine SLOW/FAST selects COMPUTE and DISPLAY
	:;

0419:C

t/data/zx81.ctl  view on Meta::CPAN


046D:C
046D 18AA       jr $0419	:C
	:; to UPPER
	:;

046F:C
	:#; ----------------------------
	:#; THE 'EDIT LINE COPY' SECTION
	:#; ----------------------------
	:#; This routine sets the edit line to just the cursor when
	:#; 1) There is not enough memory to edit a BASIC line.
	:#; 2) The edit key is used during input.
	:#; The entry point LOWER
	:#
	:#
	:#;; EDIT-INP
046F CDAD14     call $14AD	:C EDIT_INP
	:; routine CURSOR-IN sets cursor only edit line.
	:;

0472:C
	:#; ->
	:#
	:#;; LOWER
0472 2A1440     ld hl, ($4014)	:C LOWER
	:; fetch edit line start from E_LINE.
	:;

t/data/zx81.ctl  view on Meta::CPAN

	:;

0485:C
0485 20EE       jr nz, $0475	:C
	:; to EACH-CHAR
	:;

0487:C
	:#;; EDIT-LINE
0487 CD3705     call $0537	:C EDIT_LINE
	:; routine CURSOR sets cursor K or L.
	:;

048A:C
	:#;; EDIT-ROOM
048A CD1F0A     call $0A1F	:C EDIT_ROOM
	:; routine LINE-ENDS

048D:C
048D 2A1440     ld hl, ($4014)	:C
	:; sv E_LINE_lo

t/data/zx81.ctl  view on Meta::CPAN

	:;

05D0:C
	:#;
	:#
05D0 2A1440     ld hl, ($4014)	:C
	:; fetch E_LINE

05D3:C
05D3 220E40     ld ($400E), hl	:C
	:; and use to update the screen cursor DF_CC
	:;

05D6:C
	:#; so now RST $10 will print the line numbers to the edit line instead of screen.
	:#; first make sure that no newline/out of screen can occur while sprinting the
	:#; line numbers to the edit line.
	:#
05D6 212118     ld hl, $1821	:C
	:; prepare line 0, column 0.

t/data/zx81.ctl  view on Meta::CPAN

05EF 46         ld b, (hl)	:C
	:; high byte to B.
	:;

05F0:C
05F0 23         inc hl	:C
	:; point to first character in line.

05F1:C
05F1 ED5B0E40   ld de, ($400E)	:C
	:; fetch display file cursor DF_CC
	:;

05F5:C
05F5 3E7F       ld a, $7F	:C
	:; prepare the cursor character.

05F7:C
05F7 12         ld (de), a	:C
	:; and insert in edit line.

05F8:C
05F8 13         inc de	:C
	:; increment intended destination.
	:;

t/data/zx81.ctl  view on Meta::CPAN

05F9 E5         push hl	:C
	:; * save start of BASIC.
	:;

05FA:C
05FA 211D00     ld hl, $001D	:C
	:; set an overhead of 29 bytes.

05FD:C
05FD 19         add hl, de	:C
	:; add in the address of cursor.

05FE:C
05FE 09         add hl, bc	:C
	:; add the length of the line.

05FF:C
05FF ED72       sbc hl, sp	:C
	:; subtract the stack pointer.
	:;

t/data/zx81.ctl  view on Meta::CPAN


079D:C
	:#; ---
	:#
	:#;; OUT-CURS
079D 3A0640     ld a, ($4006)	:C OUT_CURS
	:; Fetch value of system variable MODE

07A0:C
07A0 06AB       ld b, $AB	:C
	:; Prepare an inverse [F] for function cursor.
	:;

07A2:C
07A2 A7         and a	:C
	:; Test for zero -

07A3:C
07A3 2005       jr nz, $07AA	:C
	:; forward if not to FLAGS-2
	:;

07A5:C
07A5 3A0140     ld a, ($4001)	:C
	:; Fetch system variable FLAGS.

07A8:C
07A8 06B0       ld b, $B0	:C
	:; Prepare an inverse [K] for keyword cursor.
	:;

07AA:C
	:#;; FLAGS-2
07AA 1F         rra	:C FLAGS_2
	:; 00000?00 -> 000000?0

07AB:C
07AB 1F         rra	:C
	:; 000000?0 -> 0000000?

t/data/zx81.ctl  view on Meta::CPAN


14AC:C
14AC C9         ret	:C
	:;
	:;

14AD:C
	:#; -----------------------
	:#; THE 'CURSOR-IN' ROUTINE
	:#; -----------------------
	:#; This routine is called to set the edit line to the minimum cursor/newline
	:#; and to set STKEND, the start of free space, at the next position.
	:#
	:#;; CURSOR-IN
14AD 2A1440     ld hl, ($4014)	:C CURSOR_IN
	:; fetch start of edit line from E_LINE

14B0:C
14B0 367F       ld (hl), $7F	:C
	:; insert cursor character
	:;

14B2:C
14B2 23         inc hl	:C
	:; point to next location.

14B3:C
14B3 3676       ld (hl), $76	:C
	:; insert NEWLINE character

t/data/zx81_sysvars.ctl  view on Meta::CPAN

		:<; ======================
		:<
		:<

4000	:IY

4000	:=	ERR_NR 			; N1   Current report code minus one
4001	:=	FLAGS  			; N1   Various flags
4002	:=	ERR_SP 			; N2   Address of top of GOSUB stack
4004	:=	RAMTOP 			; N2   Address of reserved area (not wiped out by NEW)
4006	:=	MODE   			; N1   Current cursor mode
4007	:=	PPC    			; N2   Line number of line being executed
4009	:=	VERSN  			; N1   First system variable to be SAVEd
400A	:=	E_PPC  			; N2   Line number of line with cursor
400C	:=	D_FILE 			; N2   Address of start of display file
400E	:=	DF_CC  			; N2   Address of print position within display file
4010	:=	VARS   			; N2   Address of start of variables area
4012	:=	DEST   			; N2   Address of variable being assigned
4014	:=	E_LINE 			; N2   Address of start of edit line
4016	:=	CH_ADD 			; N2   Address of the next character to interpret
4018	:=	X_PTR  			; N2   Address of char. preceding syntax error marker
401A	:=	STKBOT 			; N2   Address of calculator stack
401C	:=	STKEND 			; N2   Address of end of calculator stack
401E	:=	BERG   			; N1   Used by floating point calculator

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

        JP      L07F5           ; jump forward to PRINT-SP.

 ; ---

        DEFB    $FF             ; unused location.

; ---------------------------------
; THE 'COLLECT A CHARACTER' RESTART
; ---------------------------------
; The character addressed by the system variable CH_ADD is fetched and if it
; is a non-space, non-cursor character it is returned else CH_ADD is 
; incremented and the new addressed character tested until it is not a space.

;; GET-CHAR
L0018:  LD      HL,($4016)      ; set HL to character address CH_ADD.
        LD      A,(HL)          ; fetch addressed character to A.

;; TEST-SP
L001C:  AND     A               ; test for space.
        RET     NZ              ; return if not a space

        NOP                     ; else trickle through
        NOP                     ; to the next routine.

; ------------------------------------
; THE 'COLLECT NEXT CHARACTER' RESTART
; ------------------------------------
; The character address in incremented and the new addressed character is 
; returned if not a space, or cursor, else the process is repeated.

;; NEXT-CHAR
L0020:  CALL    L0049           ; routine CH-ADD+1 gets next immediate
                                ; character.
        JR      L001C           ; back to TEST-SP.

; ---

        DEFB    $FF, $FF, $FF   ; unused locations.

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

;   generated by the HALT that cause the Refresh value to rise from $E0 to $FF,
;   triggering an Interrupt on the next transition.
;   This works happily for all display lines between these extremes and the 
;   generation of the 32 character, 1 pixel high, line will always take 128 
;   clock cycles.

; ---------------------------------
; THE 'INCREMENT CH-ADD' SUBROUTINE
; ---------------------------------
; This is the subroutine that increments the character address system variable
; and returns if it is not the cursor character. The ZX81 has an actual 
; character at the cursor position rather than a pointer system variable
; as is the case with prior and subsequent ZX computers.

;; CH-ADD+1
L0049:  LD      HL,($4016)      ; fetch character address to CH_ADD.

;; TEMP-PTR1
L004C:  INC     HL              ; address next immediate location.

;; TEMP-PTR2
L004D:  LD      ($4016),HL      ; update system variable CH_ADD.

        LD      A,(HL)          ; fetch the character.
        CP      $7F             ; compare to cursor character.
        RET     NZ              ; return if not the cursor.

        JR      L004C           ; back for next character to TEMP-PTR1.

; --------------------
; THE 'ERROR-2' BRANCH
; --------------------
; This is a continuation of the error restart.
; If the error occurred in runtime then the error stack pointer will probably
; lead to an error report being printed unless it occurred during input.
; If the error occurred when checking syntax then the error stack pointer

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

        DEFB    $E2             ; LLIST
        DEFB    $C0             ; ""
        DEFB    $D9             ; OR
        DEFB    $E0             ; STEP
        DEFB    $DB             ; <=
        DEFB    $DD             ; <>
        DEFB    $75             ; EDIT
        DEFB    $DA             ; AND
        DEFB    $DE             ; THEN
        DEFB    $DF             ; TO
        DEFB    $72             ; cursor-left
        DEFB    $77             ; RUBOUT
        DEFB    $74             ; GRAPHICS
        DEFB    $73             ; cursor-right
        DEFB    $70             ; cursor-up
        DEFB    $71             ; cursor-down
        DEFB    $0B             ; "
        DEFB    $11             ; )
        DEFB    $10             ; (
        DEFB    $0D             ; $
        DEFB    $DC             ; >=
        DEFB    $79             ; FUNCTION
        DEFB    $14             ; =
        DEFB    $15             ; +
        DEFB    $16             ; -
        DEFB    $D8             ; **

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

        INC     HL              ; point to next location.
        DJNZ    L0408           ; loop back for all twenty five to LINE

        LD      ($4010),HL      ; set system variable VARS to next location

        CALL    L149A           ; routine CLEAR sets $80 end-marker and the 
                                ; dynamic memory pointers E_LINE, STKBOT and
                                ; STKEND.

;; N/L-ONLY
L0413:  CALL    L14AD           ; routine CURSOR-IN inserts the cursor and 
                                ; end-marker in the Edit Line also setting
                                ; size of lower display to two lines.

        CALL    L0207           ; routine SLOW/FAST selects COMPUTE and DISPLAY

; ---------------------------
; THE 'BASIC LISTING' SECTION
; ---------------------------
;
;

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

        JR      NZ,L0472        ; forward to LOWER

        LD      (HL),D          ;
        DEC     HL              ;
        LD      (HL),E          ;
        JR      L0419           ; to UPPER

; ----------------------------
; THE 'EDIT LINE COPY' SECTION
; ----------------------------
; This routine sets the edit line to just the cursor when
; 1) There is not enough memory to edit a BASIC line.
; 2) The edit key is used during input.
; The entry point LOWER


;; EDIT-INP
L046F:  CALL    L14AD           ; routine CURSOR-IN sets cursor only edit line.

; ->

;; LOWER
L0472:  LD      HL,($4014)      ; fetch edit line start from E_LINE.

;; EACH-CHAR
L0475:  LD      A,(HL)          ; fetch a character from edit line.
        CP      $7E             ; compare to the number marker.
        JR      NZ,L0482        ; forward if not to END-LINE

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

        JR      L0475           ; back to EACH-CHAR

; ---

;; END-LINE
L0482:  CP      $76             ;
        INC     HL              ;
        JR      NZ,L0475        ; to EACH-CHAR

;; EDIT-LINE
L0487:  CALL    L0537           ; routine CURSOR sets cursor K or L.

;; EDIT-ROOM
L048A:  CALL    L0A1F           ; routine LINE-ENDS
        LD      HL,($4014)      ; sv E_LINE_lo
        LD      (IY+$00),$FF    ; sv ERR_NR
        CALL    L0766           ; routine COPY-LINE
        BIT     7,(IY+$00)      ; sv ERR_NR
        JR      NZ,L04C1        ; to DISPLAY-6

        LD      A,($4022)       ; sv DF_SZ

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN

        LD      HL,L046F        ; Address: EDIT-INP
        PUSH    HL              ; ** is pushed as an error looping address.

        BIT     5,(IY+$2D)      ; test FLAGX
        RET     NZ              ; indirect jump if in input mode
                                ; to L046F, EDIT-INP (begin again).

;

        LD      HL,($4014)      ; fetch E_LINE
        LD      ($400E),HL      ; and use to update the screen cursor DF_CC

; so now RST $10 will print the line numbers to the edit line instead of screen.
; first make sure that no newline/out of screen can occur while sprinting the
; line numbers to the edit line.

        LD      HL,$1821        ; prepare line 0, column 0.
        LD      ($4039),HL      ; update S_POSN with these dummy values.

        LD      HL,($400A)      ; fetch current line from E_PPC may be a 
                                ; non-existent line e.g. last line deleted.

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN


        DEC     HL              ; point to high byte.
        CALL    L0AA5           ; routine OUT-NO writes number to edit line.

        INC     HL              ; point to length bytes.
        LD      C,(HL)          ; low byte to C.
        INC     HL              ;
        LD      B,(HL)          ; high byte to B.

        INC     HL              ; point to first character in line.
        LD      DE,($400E)      ; fetch display file cursor DF_CC

        LD      A,$7F           ; prepare the cursor character.
        LD      (DE),A          ; and insert in edit line.
        INC     DE              ; increment intended destination.

        PUSH    HL              ; * save start of BASIC.

        LD      HL,$001D        ; set an overhead of 29 bytes.
        ADD     HL,DE           ; add in the address of cursor.
        ADD     HL,BC           ; add the length of the line.
        SBC     HL,SP           ; subtract the stack pointer.

        POP     HL              ; * restore pointer to start of BASIC.

        RET     NC              ; return if not enough room to L046F EDIT-INP.
                                ; the edit key appears not to work.

        LDIR                    ; else copy bytes from program to edit line.
                                ; Note. hidden floating point forms are also

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN



;; NOT-TOKEN
L079A:  RST     10H             ; PRINT-A
        JR      L076D           ; to MORE-LINE

; ---

;; OUT-CURS
L079D:  LD      A,($4006)       ; Fetch value of system variable MODE
        LD      B,$AB           ; Prepare an inverse [F] for function cursor.

        AND     A               ; Test for zero -
        JR      NZ,L07AA        ; forward if not to FLAGS-2

        LD      A,($4001)       ; Fetch system variable FLAGS.
        LD      B,$B0           ; Prepare an inverse [K] for keyword cursor.

;; FLAGS-2
L07AA:  RRA                     ; 00000?00 -> 000000?0
        RRA                     ; 000000?0 -> 0000000?
        AND     $01             ; 0000000?    0000000x

        ADD     A,B             ; Possibly [F] -> [G]  or  [K] -> [L]

        CALL    L07F5           ; routine PRINT-SP prints character 
        JR      L076D           ; back to MORE-LINE

t/data/zx81_version_2_rom_source.asm  view on Meta::CPAN


;

;; SET-STK-E
L14A9:  LD      ($401C),HL      ; sv STKEND
        RET                     ;

; -----------------------
; THE 'CURSOR-IN' ROUTINE
; -----------------------
; This routine is called to set the edit line to the minimum cursor/newline
; and to set STKEND, the start of free space, at the next position.

;; CURSOR-IN
L14AD:  LD      HL,($4014)      ; fetch start of edit line from E_LINE
        LD      (HL),$7F        ; insert cursor character

        INC     HL              ; point to next location.
        LD      (HL),$76        ; insert NEWLINE character
        INC     HL              ; point to next free location.

        LD      (IY+$22),$02    ; set lower screen display file size DF_SZ

        JR      L14A6           ; exit via SET-STK-B above

; ------------------------

t/dis_zx48.t  view on Meta::CPAN

													  "own in RAM and make CHARS point to it.");
	$self->labels->add(0x5C38, 'RASP'      )->comment("Length of warning buzz.");
	$self->labels->add(0x5C39, 'PIP'       )->comment("Length of keyboard click.");
	$self->labels->add(0x5C3A, 'ERR_NR'    )->comment("1 less than the report code. Starts off at 255 (for 1)\n".
													  "so PEEK 23610 gives 255.");
	$self->labels->add(0x5C3B, 'FLAGS'     )->comment("Various flags to control the BASIC system.");
	$self->labels->add(0x5C3C, 'TV_FLAG'   )->comment("Flags associated with the television.");
	$self->labels->add(0x5C3D, 'ERR_SP'    )->comment("Address of item on machine stack to be used as\n".
													  "error return.");
	$self->labels->add(0x5C3F, 'LIST_SP'   )->comment("Address of return address from automatic listing.");
	$self->labels->add(0x5C41, 'MODE'      )->comment("Specifies K, L, C. E or G cursor.");
	$self->labels->add(0x5C42, 'NEWPPC'    )->comment("Line to be jumped to.");
	$self->labels->add(0x5C44, 'NSPPC'     )->comment("Statement number in line to be jumped to. Poking\n".
													  "first NEWPPC and then NSPPC forces a jump to\n".
													  "a specified statement in a line.");
	$self->labels->add(0x5C45, 'PPC'       )->comment("Line number of statement currently being executed.");
	$self->labels->add(0x5C47, 'SUBPPC'    )->comment("Number within line of statement being executed.");
	$self->labels->add(0x5C48, 'BORDCR'    )->comment("Border colour * 8; also contains the attributes\n".
													  "normally used for the lower half of the screen.");
	$self->labels->add(0x5C49, 'E_PPC'     )->comment("Number of current line (with program cursor).");
	$self->labels->add(0x5C4B, 'VARS'      )->comment("Address of variables.");
	$self->labels->add(0x5C4D, 'DEST'      )->comment("Address of variable in assignment.");
	$self->labels->add(0x5C4F, 'CHANS'     )->comment("Address of channel data.");
	$self->labels->add(0x5C51, 'CURCHL'    )->comment("Address of information currently being used for\n".
													  "input and output.");
	$self->labels->add(0x5C53, 'PROG'      )->comment("Address of BASIC program.");
	$self->labels->add(0x5C55, 'NXTLIN'    )->comment("Address of next line in program.");
	$self->labels->add(0x5C57, 'DATADD'    )->comment("Address of terminator of last DATA item.");
	$self->labels->add(0x5C59, 'E_LINE'    )->comment("Address of command being typed in.");
	$self->labels->add(0x5C5B, 'K_CUR'     )->comment("Address of cursor.");
	$self->labels->add(0x5C5D, 'CH_ADD'    )->comment("Address of the next character to be interpreted:\n".
													  "the character after the argument of PEEK, or\n".
													  "the NEWLINE at the end of a POKE statement.");
	$self->labels->add(0x5C5F, 'X_PTR'     )->comment("Address of the character after the ? marker.");
	$self->labels->add(0x5C61, 'WORKSP'    )->comment("Address of temporary work space.");
	$self->labels->add(0x5C63, 'STKBOT'    )->comment("Address of bottom of calculator stack.");
	$self->labels->add(0x5C65, 'STKEND'    )->comment("Address of start of spare space.");
	$self->labels->add(0x5C67, 'BREG'      )->comment("Calculator's b register.");
	$self->labels->add(0x5C68, 'MEM'       )->comment("Address of area used for calculator's memory.\n".
													  "(Usually MEMBOT, but not always.)");



( run in 0.335 second using v1.01-cache-2.11-cpan-4d50c553e7e )