URL
https://opencores.org/ocsvn/a-z80/a-z80/trunk
Subversion Repositories a-z80
[/] [a-z80/] [trunk/] [host/] [zxspectrum_de1/] [rom/] [zxspectrum_rom.asm] - Rev 13
Go to most recent revision | Compare with Previous | Blame | View Log
;************************************************************************
;** An Assembly File Listing to generate a 16K ROM for the ZX Spectrum **
;************************************************************************
;
; 03-13-2016:
; Add custom NMI handler and a function to enter game pokes after pressing the NMI button
;
; 11-10-2014:
; This version has been updated to correctly handle the NMI jump.
;
; -------------------------
; Last updated: 13-DEC-2004
; -------------------------
; TASM cross-assembler directives.
; ( comment out, perhaps, for other assemblers - see Notes at end.)
#define DEFB .BYTE
#define DEFW .WORD
#define DEFM .TEXT
#define ORG .ORG
#define EQU .EQU
#define equ .EQU
; It is always a good idea to anchor, using ORGs, important sections such as
; the character bitmaps so that they don't move as code is added and removed.
; Generally most approaches try to maintain main entry points as they are
; often used by third-party software.
ORG 0000
;*****************************************
;** Part 1. RESTART ROUTINES AND TABLES **
;*****************************************
; -----------
; THE 'START'
; -----------
; At switch on, the Z80 chip is in Interrupt Mode 0.
; The Spectrum uses Interrupt Mode 1.
; This location can also be 'called' to reset the machine.
; Typically with PRINT USR 0.
;; START
L0000: DI ; Disable Interrupts.
XOR A ; Signal coming from START.
LD DE,$FFFF ; Set pointer to top of possible physical RAM.
JP L11CB ; Jump forward to common code at START-NEW.
; -------------------
; THE 'ERROR' RESTART
; -------------------
; The error pointer is made to point to the position of the error to enable
; the editor to highlight the error position if it occurred during syntax
; checking. It is used at 37 places in the program. An instruction fetch
; on address $0008 may page in a peripheral ROM such as the Sinclair
; Interface 1 or Disciple Disk Interface. This was not an original design
; concept and not all errors pass through here.
;; ERROR-1
L0008: LD HL,($5C5D) ; Fetch the character address from CH_ADD.
LD ($5C5F),HL ; Copy it to the error pointer X_PTR.
JR L0053 ; Forward to continue at ERROR-2.
; -----------------------------
; THE 'PRINT CHARACTER' RESTART
; -----------------------------
; The A register holds the code of the character that is to be sent to
; the output stream of the current channel. The alternate register set is
; used to output a character in the A register so there is no need to
; preserve any of the current main registers (HL, DE, BC).
; This restart is used 21 times.
;; PRINT-A
L0010: JP L15F2 ; Jump forward to continue at PRINT-A-2.
; ---
DEFB $FF, $FF, $FF ; Five unused locations.
DEFB $FF, $FF ;
; -------------------------------
; THE 'COLLECT CHARACTER' RESTART
; -------------------------------
; The contents of the location currently addressed by CH_ADD are fetched.
; A return is made if the value represents a character that has
; relevance to the BASIC parser. Otherwise CH_ADD is incremented and the
; tests repeated. CH_ADD will be addressing somewhere -
; 1) in the BASIC program area during line execution.
; 2) in workspace if evaluating, for example, a string expression.
; 3) in the edit buffer if parsing a direct command or a new BASIC line.
; 4) in workspace if accepting input but not that from INPUT LINE.
;; GET-CHAR
L0018: LD HL,($5C5D) ; fetch the address from CH_ADD.
LD A,(HL) ; use it to pick up current character.
;; TEST-CHAR
L001C: CALL L007D ; routine SKIP-OVER tests if the character is
; relevant.
RET NC ; Return if it is significant.
; ------------------------------------
; THE 'COLLECT NEXT CHARACTER' RESTART
; ------------------------------------
; As the BASIC commands and expressions are interpreted, this routine is
; called repeatedly to step along the line. It is used 83 times.
;; NEXT-CHAR
L0020: CALL L0074 ; routine CH-ADD+1 fetches the next immediate
; character.
JR L001C ; jump back to TEST-CHAR until a valid
; character is found.
; ---
DEFB $FF, $FF, $FF ; unused
; -----------------------
; THE 'CALCULATE' RESTART
; -----------------------
; This restart enters the Spectrum's internal, floating-point, stack-based,
; FORTH-like language.
; It is further used recursively from within the calculator.
; It is used on 77 occasions.
;; FP-CALC
L0028: JP L335B ; jump forward to the CALCULATE routine.
; ---
DEFB $FF, $FF, $FF ; spare - note that on the ZX81, space being a
DEFB $FF, $FF ; little cramped, these same locations were
; used for the five-byte end-calc literal.
; ------------------------------
; THE 'CREATE BC SPACES' RESTART
; ------------------------------
; This restart is used on only 12 occasions to create BC spaces
; between workspace and the calculator stack.
;; BC-SPACES
L0030: PUSH BC ; Save number of spaces.
LD HL,($5C61) ; Fetch WORKSP.
PUSH HL ; Save address of workspace.
JP L169E ; Jump forward to continuation code RESERVE.
; --------------------------------
; THE 'MASKABLE INTERRUPT' ROUTINE
; --------------------------------
; This routine increments the Spectrum's three-byte FRAMES counter fifty
; times a second (sixty times a second in the USA ).
; Both this routine and the called KEYBOARD subroutine use the IY register
; to access system variables and flags so a user-written program must
; disable interrupts to make use of the IY register.
;; MASK-INT
L0038: PUSH AF ; Save the registers that will be used but not
PUSH HL ; the IY register unfortunately.
LD HL,($5C78) ; Fetch the first two bytes at FRAMES1.
INC HL ; Increment lowest two bytes of counter.
LD ($5C78),HL ; Place back in FRAMES1.
LD A,H ; Test if the result was zero.
OR L ;
JR NZ,L0048 ; Forward, if not, to KEY-INT
INC (IY+$40) ; otherwise increment FRAMES3 the third byte.
; Now save the rest of the main registers and read and decode the keyboard.
;; KEY-INT
L0048: PUSH BC ; Save the other main registers.
PUSH DE ;
CALL L02BF ; Routine KEYBOARD executes a stage in the
; process of reading a key-press.
POP DE ;
POP BC ; Restore registers.
POP HL ;
POP AF ;
EI ; Enable Interrupts.
RET ; Return.
; ---------------------
; THE 'ERROR-2' ROUTINE
; ---------------------
; A continuation of the code at 0008.
; The error code is stored and after clearing down stacks, an indirect jump
; is made to MAIN-4, etc. to handle the error.
;; ERROR-2
L0053: POP HL ; drop the return address - the location
; after the RST 08H instruction.
LD L,(HL) ; fetch the error code that follows.
; (nice to see this instruction used.)
; Note. this entry point is used when out of memory at REPORT-4.
; The L register has been loaded with the report code but X-PTR is not
; updated.
;; ERROR-3
L0055: LD (IY+$00),L ; Store it in the system variable ERR_NR.
LD SP,($5C3D) ; ERR_SP points to an error handler on the
; machine stack. There may be a hierarchy
; of routines.
; To MAIN-4 initially at base.
; or REPORT-G on line entry.
; or ED-ERROR when editing.
; or ED-FULL during ed-enter.
; or IN-VAR-1 during runtime input etc.
JP L16C5 ; Jump to SET-STK to clear the calculator stack
; and reset MEM to usual place in the systems
; variables area and then indirectly to MAIN-4,
; etc.
; ---
DEFB $FF, $FF, $FF ; Unused locations
DEFB $FF, $FF, $FF ; before the fixed-position
DEFB $FF ; NMI routine.
; ------------------------------------
; THE 'NON-MASKABLE INTERRUPT' ROUTINE
; ------------------------------------
;
; There is no NMI switch on the standard Spectrum or its peripherals.
; When the NMI line is held low, then no matter what the Z80 was doing at
; the time, it will now execute the code at 66 Hex.
; This Interrupt Service Routine will jump to location zero if the contents
; of the system variable NMIADD are zero or return if the location holds a
; non-zero address. So attaching a simple switch to the NMI as in the book
; "Spectrum Hardware Manual" causes a reset. The logic was obviously
; intended to work the other way. Sinclair Research said that, since they
; had never advertised the NMI, they had no plans to fix the error "until
; the opportunity arose".
;
; Note. The location NMIADD was, in fact, later used by Sinclair Research
; to enhance the text channel on the ZX Interface 1.
; On later Amstrad-made Spectrums, and the Brazilian Spectrum, the logic of
; this routine was indeed reversed but not as at first intended.
;
; It can be deduced by looking elsewhere in this ROM that the NMIADD system
; variable pointed to L121C and that this enabled a Warm Restart to be
; performed at any time, even while playing machine code games, or while
; another Spectrum has been allowed to gain control of this one.
;
; Software houses would have been able to protect their games from attack by
; placing two zeros in the NMIADD system variable.
;; RESET
L0066: PUSH AF ; save the
PUSH HL ; registers.
; LD HL,($5CB0) ; fetch the system variable NMIADD.
LD HL, nmi_handler ; Custom NMI handler
LD A,H ; test address
OR L ; for zero.
; JR NZ,L0070 ; skip to NO-RESET if NOT ZERO
JR Z,L0070 ; **FIXED**
JP (HL) ; jump to routine ( i.e. L0000 )
;; NO-RESET
L0070: POP HL ; restore the
POP AF ; registers.
RETN ; return to previous interrupt state.
; ---------------------------
; THE 'CH ADD + 1' SUBROUTINE
; ---------------------------
; This subroutine is called from RST 20, and three times from elsewhere
; to fetch the next immediate character following the current valid character
; address and update the associated system variable.
; The entry point TEMP-PTR1 is used from the SCANNING routine.
; Both TEMP-PTR1 and TEMP-PTR2 are used by the READ command routine.
;; CH-ADD+1
L0074: LD HL,($5C5D) ; fetch address from CH_ADD.
;; TEMP-PTR1
L0077: INC HL ; increase the character address by one.
;; TEMP-PTR2
L0078: LD ($5C5D),HL ; update CH_ADD with character address.
X007B: LD A,(HL) ; load character to A from HL.
RET ; and return.
; --------------------------
; THE 'SKIP OVER' SUBROUTINE
; --------------------------
; This subroutine is called once from RST 18 to skip over white-space and
; other characters irrelevant to the parsing of a BASIC line etc. .
; Initially the A register holds the character to be considered
; and HL holds its address which will not be within quoted text
; when a BASIC line is parsed.
; Although the 'tab' and 'at' characters will not appear in a BASIC line,
; they could be present in a string expression, and in other situations.
; Note. although white-space is usually placed in a program to indent loops
; and make it more readable, it can also be used for the opposite effect and
; spaces may appear in variable names although the parser never sees them.
; It is this routine that helps make the variables 'Anum bEr5 3BUS' and
; 'a number 53 bus' appear the same to the parser.
;; SKIP-OVER
L007D: CP $21 ; test if higher than space.
RET NC ; return with carry clear if so.
CP $0D ; carriage return ?
RET Z ; return also with carry clear if so.
; all other characters have no relevance
; to the parser and must be returned with
; carry set.
CP $10 ; test if 0-15d
RET C ; return, if so, with carry set.
CP $18 ; test if 24-32d
CCF ; complement carry flag.
RET C ; return with carry set if so.
; now leaves 16d-23d
INC HL ; all above have at least one extra character
; to be stepped over.
CP $16 ; controls 22d ('at') and 23d ('tab') have two.
JR C,L0090 ; forward to SKIPS with ink, paper, flash,
; bright, inverse or over controls.
; Note. the high byte of tab is for RS232 only.
; it has no relevance on this machine.
INC HL ; step over the second character of 'at'/'tab'.
;; SKIPS
L0090: SCF ; set the carry flag
LD ($5C5D),HL ; update the CH_ADD system variable.
RET ; return with carry set.
; ------------------
; THE 'TOKEN' TABLES
; ------------------
; The tokenized characters 134d (RND) to 255d (COPY) are expanded using
; this table. The last byte of a token is inverted to denote the end of
; the word. The first is an inverted step-over byte.
;; TKN-TABLE
L0095: DEFB '?'+$80
DEFM "RN"
DEFB 'D'+$80
DEFM "INKEY"
DEFB '$'+$80
DEFB 'P','I'+$80
DEFB 'F','N'+$80
DEFM "POIN"
DEFB 'T'+$80
DEFM "SCREEN"
DEFB '$'+$80
DEFM "ATT"
DEFB 'R'+$80
DEFB 'A','T'+$80
DEFM "TA"
DEFB 'B'+$80
DEFM "VAL"
DEFB '$'+$80
DEFM "COD"
DEFB 'E'+$80
DEFM "VA"
DEFB 'L'+$80
DEFM "LE"
DEFB 'N'+$80
DEFM "SI"
DEFB 'N'+$80
DEFM "CO"
DEFB 'S'+$80
DEFM "TA"
DEFB 'N'+$80
DEFM "AS"
DEFB 'N'+$80
DEFM "AC"
DEFB 'S'+$80
DEFM "AT"
DEFB 'N'+$80
DEFB 'L','N'+$80
DEFM "EX"
DEFB 'P'+$80
DEFM "IN"
DEFB 'T'+$80
DEFM "SQ"
DEFB 'R'+$80
DEFM "SG"
DEFB 'N'+$80
DEFM "AB"
DEFB 'S'+$80
DEFM "PEE"
DEFB 'K'+$80
DEFB 'I','N'+$80
DEFM "US"
DEFB 'R'+$80
DEFM "STR"
DEFB '$'+$80
DEFM "CHR"
DEFB '$'+$80
DEFM "NO"
DEFB 'T'+$80
DEFM "BI"
DEFB 'N'+$80
; The previous 32 function-type words are printed without a leading space
; The following have a leading space if they begin with a letter
DEFB 'O','R'+$80
DEFM "AN"
DEFB 'D'+$80
DEFB $3C,'='+$80 ; <=
DEFB $3E,'='+$80 ; >=
DEFB $3C,$3E+$80 ; <>
DEFM "LIN"
DEFB 'E'+$80
DEFM "THE"
DEFB 'N'+$80
DEFB 'T','O'+$80
DEFM "STE"
DEFB 'P'+$80
DEFM "DEF F"
DEFB 'N'+$80
DEFM "CA"
DEFB 'T'+$80
DEFM "FORMA"
DEFB 'T'+$80
DEFM "MOV"
DEFB 'E'+$80
DEFM "ERAS"
DEFB 'E'+$80
DEFM "OPEN "
DEFB '#'+$80
DEFM "CLOSE "
DEFB '#'+$80
DEFM "MERG"
DEFB 'E'+$80
DEFM "VERIF"
DEFB 'Y'+$80
DEFM "BEE"
DEFB 'P'+$80
DEFM "CIRCL"
DEFB 'E'+$80
DEFM "IN"
DEFB 'K'+$80
DEFM "PAPE"
DEFB 'R'+$80
DEFM "FLAS"
DEFB 'H'+$80
DEFM "BRIGH"
DEFB 'T'+$80
DEFM "INVERS"
DEFB 'E'+$80
DEFM "OVE"
DEFB 'R'+$80
DEFM "OU"
DEFB 'T'+$80
DEFM "LPRIN"
DEFB 'T'+$80
DEFM "LLIS"
DEFB 'T'+$80
DEFM "STO"
DEFB 'P'+$80
DEFM "REA"
DEFB 'D'+$80
DEFM "DAT"
DEFB 'A'+$80
DEFM "RESTOR"
DEFB 'E'+$80
DEFM "NE"
DEFB 'W'+$80
DEFM "BORDE"
DEFB 'R'+$80
DEFM "CONTINU"
DEFB 'E'+$80
DEFM "DI"
DEFB 'M'+$80
DEFM "RE"
DEFB 'M'+$80
DEFM "FO"
DEFB 'R'+$80
DEFM "GO T"
DEFB 'O'+$80
DEFM "GO SU"
DEFB 'B'+$80
DEFM "INPU"
DEFB 'T'+$80
DEFM "LOA"
DEFB 'D'+$80
DEFM "LIS"
DEFB 'T'+$80
DEFM "LE"
DEFB 'T'+$80
DEFM "PAUS"
DEFB 'E'+$80
DEFM "NEX"
DEFB 'T'+$80
DEFM "POK"
DEFB 'E'+$80
DEFM "PRIN"
DEFB 'T'+$80
DEFM "PLO"
DEFB 'T'+$80
DEFM "RU"
DEFB 'N'+$80
DEFM "SAV"
DEFB 'E'+$80
DEFM "RANDOMIZ"
DEFB 'E'+$80
DEFB 'I','F'+$80
DEFM "CL"
DEFB 'S'+$80
DEFM "DRA"
DEFB 'W'+$80
DEFM "CLEA"
DEFB 'R'+$80
DEFM "RETUR"
DEFB 'N'+$80
DEFM "COP"
DEFB 'Y'+$80
; ----------------
; THE 'KEY' TABLES
; ----------------
; These six look-up tables are used by the keyboard reading routine
; to decode the key values.
;
; The first table contains the maps for the 39 keys of the standard
; 40-key Spectrum keyboard. The remaining key [SHIFT $27] is read directly.
; The keys consist of the 26 upper-case alphabetic characters, the 10 digit
; keys and the space, ENTER and symbol shift key.
; Unshifted alphabetic keys have $20 added to the value.
; The keywords for the main alphabetic keys are obtained by adding $A5 to
; the values obtained from this table.
;; MAIN-KEYS
L0205: DEFB $42 ; B
DEFB $48 ; H
DEFB $59 ; Y
DEFB $36 ; 6
DEFB $35 ; 5
DEFB $54 ; T
DEFB $47 ; G
DEFB $56 ; V
DEFB $4E ; N
DEFB $4A ; J
DEFB $55 ; U
DEFB $37 ; 7
DEFB $34 ; 4
DEFB $52 ; R
DEFB $46 ; F
DEFB $43 ; C
DEFB $4D ; M
DEFB $4B ; K
DEFB $49 ; I
DEFB $38 ; 8
DEFB $33 ; 3
DEFB $45 ; E
DEFB $44 ; D
DEFB $58 ; X
DEFB $0E ; SYMBOL SHIFT
DEFB $4C ; L
DEFB $4F ; O
DEFB $39 ; 9
DEFB $32 ; 2
DEFB $57 ; W
DEFB $53 ; S
DEFB $5A ; Z
DEFB $20 ; SPACE
DEFB $0D ; ENTER
DEFB $50 ; P
DEFB $30 ; 0
DEFB $31 ; 1
DEFB $51 ; Q
DEFB $41 ; A
;; E-UNSHIFT
; The 26 unshifted extended mode keys for the alphabetic characters.
; The green keywords on the original keyboard.
L022C: DEFB $E3 ; READ
DEFB $C4 ; BIN
DEFB $E0 ; LPRINT
DEFB $E4 ; DATA
DEFB $B4 ; TAN
DEFB $BC ; SGN
DEFB $BD ; ABS
DEFB $BB ; SQR
DEFB $AF ; CODE
DEFB $B0 ; VAL
DEFB $B1 ; LEN
DEFB $C0 ; USR
DEFB $A7 ; PI
DEFB $A6 ; INKEY$
DEFB $BE ; PEEK
DEFB $AD ; TAB
DEFB $B2 ; SIN
DEFB $BA ; INT
DEFB $E5 ; RESTORE
DEFB $A5 ; RND
DEFB $C2 ; CHR$
DEFB $E1 ; LLIST
DEFB $B3 ; COS
DEFB $B9 ; EXP
DEFB $C1 ; STR$
DEFB $B8 ; LN
;; EXT-SHIFT
; The 26 shifted extended mode keys for the alphabetic characters.
; The red keywords below keys on the original keyboard.
L0246: DEFB $7E ; ~
DEFB $DC ; BRIGHT
DEFB $DA ; PAPER
DEFB $5C ; \
DEFB $B7 ; ATN
DEFB $7B ; {
DEFB $7D ; }
DEFB $D8 ; CIRCLE
DEFB $BF ; IN
DEFB $AE ; VAL$
DEFB $AA ; SCREEN$
DEFB $AB ; ATTR
DEFB $DD ; INVERSE
DEFB $DE ; OVER
DEFB $DF ; OUT
DEFB $7F ; (Copyright character)
DEFB $B5 ; ASN
DEFB $D6 ; VERIFY
DEFB $7C ; |
DEFB $D5 ; MERGE
DEFB $5D ; ]
DEFB $DB ; FLASH
DEFB $B6 ; ACS
DEFB $D9 ; INK
DEFB $5B ; [
DEFB $D7 ; BEEP
;; CTL-CODES
; The ten control codes assigned to the top line of digits when the shift
; key is pressed.
L0260: DEFB $0C ; DELETE
DEFB $07 ; EDIT
DEFB $06 ; CAPS LOCK
DEFB $04 ; TRUE VIDEO
DEFB $05 ; INVERSE VIDEO
DEFB $08 ; CURSOR LEFT
DEFB $0A ; CURSOR DOWN
DEFB $0B ; CURSOR UP
DEFB $09 ; CURSOR RIGHT
DEFB $0F ; GRAPHICS
;; SYM-CODES
; The 26 red symbols assigned to the alphabetic characters of the keyboard.
; The ten single-character digit symbols are converted without the aid of
; a table using subtraction and minor manipulation.
L026A: DEFB $E2 ; STOP
DEFB $2A ; *
DEFB $3F ; ?
DEFB $CD ; STEP
DEFB $C8 ; >=
DEFB $CC ; TO
DEFB $CB ; THEN
DEFB $5E ; ^
DEFB $AC ; AT
DEFB $2D ; -
DEFB $2B ; +
DEFB $3D ; =
DEFB $2E ; .
DEFB $2C ; ,
DEFB $3B ; ;
DEFB $22 ; "
DEFB $C7 ; <=
DEFB $3C ; <
DEFB $C3 ; NOT
DEFB $3E ; >
DEFB $C5 ; OR
DEFB $2F ; /
DEFB $C9 ; <>
DEFB $60 ; pound
DEFB $C6 ; AND
DEFB $3A ; :
;; E-DIGITS
; The ten keywords assigned to the digits in extended mode.
; The remaining red keywords below the keys.
L0284: DEFB $D0 ; FORMAT
DEFB $CE ; DEF FN
DEFB $A8 ; FN
DEFB $CA ; LINE
DEFB $D3 ; OPEN #
DEFB $D4 ; CLOSE #
DEFB $D1 ; MOVE
DEFB $D2 ; ERASE
DEFB $A9 ; POINT
DEFB $CF ; CAT
;*******************************
;** Part 2. KEYBOARD ROUTINES **
;*******************************
; Using shift keys and a combination of modes the Spectrum 40-key keyboard
; can be mapped to 256 input characters
; ---------------------------------------------------------------------------
;
; 0 1 2 3 4 -Bits- 4 3 2 1 0
; PORT PORT
;
; F7FE [ 1 ] [ 2 ] [ 3 ] [ 4 ] [ 5 ] | [ 6 ] [ 7 ] [ 8 ] [ 9 ] [ 0 ] EFFE
; ^ | v
; FBFE [ Q ] [ W ] [ E ] [ R ] [ T ] | [ Y ] [ U ] [ I ] [ O ] [ P ] DFFE
; ^ | v
; FDFE [ A ] [ S ] [ D ] [ F ] [ G ] | [ H ] [ J ] [ K ] [ L ] [ ENT ] BFFE
; ^ | v
; FEFE [SHI] [ Z ] [ X ] [ C ] [ V ] | [ B ] [ N ] [ M ] [sym] [ SPC ] 7FFE
; ^ $27 $18 v
; Start End
; 00100111 00011000
;
; ---------------------------------------------------------------------------
; The above map may help in reading.
; The neat arrangement of ports means that the B register need only be
; rotated left to work up the left hand side and then down the right
; hand side of the keyboard. When the reset bit drops into the carry
; then all 8 half-rows have been read. Shift is the first key to be
; read. The lower six bits of the shifts are unambiguous.
; -------------------------------
; THE 'KEYBOARD SCANNING' ROUTINE
; -------------------------------
; From keyboard and s-inkey$
; Returns 1 or 2 keys in DE, most significant shift first if any
; key values 0-39 else 255
;; KEY-SCAN
L028E: LD L,$2F ; initial key value
; valid values are obtained by subtracting
; eight five times.
LD DE,$FFFF ; a buffer to receive 2 keys.
LD BC,$FEFE ; the commencing port address
; B holds 11111110 initially and is also
; used to count the 8 half-rows
;; KEY-LINE
L0296: IN A,(C) ; read the port to A - bits will be reset
; if a key is pressed else set.
CPL ; complement - pressed key-bits are now set
AND $1F ; apply 00011111 mask to pick up the
; relevant set bits.
JR Z,L02AB ; forward to KEY-DONE if zero and therefore
; no keys pressed in row at all.
LD H,A ; transfer row bits to H
LD A,L ; load the initial key value to A
;; KEY-3KEYS
L029F: INC D ; now test the key buffer
RET NZ ; if we have collected 2 keys already
; then too many so quit.
;; KEY-BITS
L02A1: SUB $08 ; subtract 8 from the key value
; cycling through key values (top = $27)
; e.g. 2F> 27>1F>17>0F>07
; 2E> 26>1E>16>0E>06
SRL H ; shift key bits right into carry.
JR NC,L02A1 ; back to KEY-BITS if not pressed
; but if pressed we have a value (0-39d)
LD D,E ; transfer a possible previous key to D
LD E,A ; transfer the new key to E
JR NZ,L029F ; back to KEY-3KEYS if there were more
; set bits - H was not yet zero.
;; KEY-DONE
L02AB: DEC L ; cycles 2F>2E>2D>2C>2B>2A>29>28 for
; each half-row.
RLC B ; form next port address e.g. FEFE > FDFE
JR C,L0296 ; back to KEY-LINE if still more rows to do.
LD A,D ; now test if D is still FF ?
INC A ; if it is zero we have at most 1 key
; range now $01-$28 (1-40d)
RET Z ; return if one key or no key.
CP $28 ; is it capsshift (was $27) ?
RET Z ; return if so.
CP $19 ; is it symbol shift (was $18) ?
RET Z ; return also
LD A,E ; now test E
LD E,D ; but first switch
LD D,A ; the two keys.
CP $18 ; is it symbol shift ?
RET ; return (with zero set if it was).
; but with symbol shift now in D
; ----------------------
; THE 'KEYBOARD' ROUTINE
; ----------------------
; Called from the interrupt 50 times a second.
;
;; KEYBOARD
L02BF: CALL L028E ; routine KEY-SCAN
RET NZ ; return if invalid combinations
; then decrease the counters within the two key-state maps
; as this could cause one to become free.
; if the keyboard has not been pressed during the last five interrupts
; then both sets will be free.
LD HL,$5C00 ; point to KSTATE-0
;; K-ST-LOOP
L02C6: BIT 7,(HL) ; is it free ? (i.e. $FF)
JR NZ,L02D1 ; forward to K-CH-SET if so
INC HL ; address the 5-counter
DEC (HL) ; decrease the counter
DEC HL ; step back
JR NZ,L02D1 ; forward to K-CH-SET if not at end of count
LD (HL),$FF ; else mark this particular map free.
;; K-CH-SET
L02D1: LD A,L ; make a copy of the low address byte.
LD HL,$5C04 ; point to KSTATE-4
; (ld l,$04 would do)
CP L ; have both sets been considered ?
JR NZ,L02C6 ; back to K-ST-LOOP to consider this 2nd set
; now the raw key (0-38d) is converted to a main key (uppercase).
CALL L031E ; routine K-TEST to get main key in A
RET NC ; return if just a single shift
LD HL,$5C00 ; point to KSTATE-0
CP (HL) ; does the main key code match ?
JR Z,L0310 ; forward to K-REPEAT if so
; if not consider the second key map.
EX DE,HL ; save kstate-0 in de
LD HL,$5C04 ; point to KSTATE-4
CP (HL) ; does the main key code match ?
JR Z,L0310 ; forward to K-REPEAT if so
; having excluded a repeating key we can now consider a new key.
; the second set is always examined before the first.
BIT 7,(HL) ; is the key map free ?
JR NZ,L02F1 ; forward to K-NEW if so.
EX DE,HL ; bring back KSTATE-0
BIT 7,(HL) ; is it free ?
RET Z ; return if not.
; as we have a key but nowhere to put it yet.
; continue or jump to here if one of the buffers was free.
;; K-NEW
L02F1: LD E,A ; store key in E
LD (HL),A ; place in free location
INC HL ; advance to the interrupt counter
LD (HL),$05 ; and initialize counter to 5
INC HL ; advance to the delay
LD A,($5C09) ; pick up the system variable REPDEL
LD (HL),A ; and insert that for first repeat delay.
INC HL ; advance to last location of state map.
LD C,(IY+$07) ; pick up MODE (3 bytes)
LD D,(IY+$01) ; pick up FLAGS (3 bytes)
PUSH HL ; save state map location
; Note. could now have used, to avoid IY,
; ld l,$41; ld c,(hl); ld l,$3B; ld d,(hl).
; six and two threes of course.
CALL L0333 ; routine K-DECODE
POP HL ; restore map pointer
LD (HL),A ; put the decoded key in last location of map.
;; K-END
L0308: LD ($5C08),A ; update LASTK system variable.
SET 5,(IY+$01) ; update FLAGS - signal a new key.
RET ; return to interrupt routine.
; -----------------------
; THE 'REPEAT KEY' BRANCH
; -----------------------
; A possible repeat has been identified. HL addresses the raw key.
; The last location of the key map holds the decoded key from the first
; context. This could be a keyword and, with the exception of NOT a repeat
; is syntactically incorrect and not really desirable.
;; K-REPEAT
L0310: INC HL ; increment the map pointer to second location.
LD (HL),$05 ; maintain interrupt counter at 5.
INC HL ; now point to third location.
DEC (HL) ; decrease the REPDEL value which is used to
; time the delay of a repeat key.
RET NZ ; return if not yet zero.
LD A,($5C0A) ; fetch the system variable value REPPER.
LD (HL),A ; for subsequent repeats REPPER will be used.
INC HL ; advance
;
LD A,(HL) ; pick up the key decoded possibly in another
; context.
; Note. should compare with $A5 (RND) and make
; a simple return if this is a keyword.
; e.g. cp $a5; ret nc; (3 extra bytes)
JR L0308 ; back to K-END
; ----------------------
; THE 'KEY-TEST' ROUTINE
; ----------------------
; also called from s-inkey$
; begin by testing for a shift with no other.
;; K-TEST
L031E: LD B,D ; load most significant key to B
; will be $FF if not shift.
LD D,$00 ; and reset D to index into main table
LD A,E ; load least significant key from E
CP $27 ; is it higher than 39d i.e. FF
RET NC ; return with just a shift (in B now)
CP $18 ; is it symbol shift ?
JR NZ,L032C ; forward to K-MAIN if not
; but we could have just symbol shift and no other
BIT 7,B ; is other key $FF (ie not shift)
RET NZ ; return with solitary symbol shift
;; K-MAIN
L032C: LD HL,L0205 ; address: MAIN-KEYS
ADD HL,DE ; add offset 0-38
LD A,(HL) ; pick up main key value
SCF ; set carry flag
RET ; return (B has other key still)
; ----------------------------------
; THE 'KEYBOARD DECODING' SUBROUTINE
; ----------------------------------
; also called from s-inkey$
;; K-DECODE
L0333: LD A,E ; pick up the stored main key
CP $3A ; an arbitrary point between digits and letters
JR C,L0367 ; forward to K-DIGIT with digits, space, enter.
DEC C ; decrease MODE ( 0='KLC', 1='E', 2='G')
JP M,L034F ; to K-KLC-LET if was zero
JR Z,L0341 ; to K-E-LET if was 1 for extended letters.
; proceed with graphic codes.
; Note. should selectively drop return address if code > 'U' ($55).
; i.e. abort the KEYBOARD call.
; e.g. cp 'V'; jr c,addit; pop af ;pop af ;;addit etc. (6 extra bytes).
; (s-inkey$ never gets into graphics mode.)
;; addit
ADD A,$4F ; add offset to augment 'A' to graphics A say.
RET ; return.
; Note. ( but [GRAPH] V gives RND, etc ).
; ---
; the jump was to here with extended mode with uppercase A-Z.
;; K-E-LET
L0341: LD HL,L022C-$41 ; base address of E-UNSHIFT L022c.
; ( $01EB in standard ROM ).
INC B ; test B is it empty i.e. not a shift.
JR Z,L034A ; forward to K-LOOK-UP if neither shift.
LD HL,L0246-$41 ; Address: $0205 L0246-$41 EXT-SHIFT base
;; K-LOOK-UP
L034A: LD D,$00 ; prepare to index.
ADD HL,DE ; add the main key value.
LD A,(HL) ; pick up other mode value.
RET ; return.
; ---
; the jump was here with mode = 0
;; K-KLC-LET
L034F: LD HL,L026A-$41 ; prepare base of sym-codes
BIT 0,B ; shift=$27 sym-shift=$18
JR Z,L034A ; back to K-LOOK-UP with symbol-shift
BIT 3,D ; test FLAGS is it 'K' mode (from OUT-CURS)
JR Z,L0364 ; skip to K-TOKENS if so
BIT 3,(IY+$30) ; test FLAGS2 - consider CAPS LOCK ?
RET NZ ; return if so with main code.
INC B ; is shift being pressed ?
; result zero if not
RET NZ ; return if shift pressed.
ADD A,$20 ; else convert the code to lower case.
RET ; return.
; ---
; the jump was here for tokens
;; K-TOKENS
L0364: ADD A,$A5 ; add offset to main code so that 'A'
; becomes 'NEW' etc.
RET ; return.
; ---
; the jump was here with digits, space, enter and symbol shift (< $xx)
;; K-DIGIT
L0367: CP $30 ; is it '0' or higher ?
RET C ; return with space, enter and symbol-shift
DEC C ; test MODE (was 0='KLC', 1='E', 2='G')
JP M,L039D ; jump to K-KLC-DGT if was 0.
JR NZ,L0389 ; forward to K-GRA-DGT if mode was 2.
; continue with extended digits 0-9.
LD HL,L0284-$30 ; $0254 - base of E-DIGITS
BIT 5,B ; test - shift=$27 sym-shift=$18
JR Z,L034A ; to K-LOOK-UP if sym-shift
CP $38 ; is character '8' ?
JR NC,L0382 ; to K-8-&-9 if greater than '7'
SUB $20 ; reduce to ink range $10-$17
INC B ; shift ?
RET Z ; return if not.
ADD A,$08 ; add 8 to give paper range $18 - $1F
RET ; return
; ---
; 89
;; K-8-&-9
L0382: SUB $36 ; reduce to 02 and 03 bright codes
INC B ; test if shift pressed.
RET Z ; return if not.
ADD A,$FE ; subtract 2 setting carry
RET ; to give 0 and 1 flash codes.
; ---
; graphics mode with digits
;; K-GRA-DGT
L0389: LD HL,L0260-$30 ; $0230 base address of CTL-CODES
CP $39 ; is key '9' ?
JR Z,L034A ; back to K-LOOK-UP - changed to $0F, GRAPHICS.
CP $30 ; is key '0' ?
JR Z,L034A ; back to K-LOOK-UP - changed to $0C, delete.
; for keys '0' - '7' we assign a mosaic character depending on shift.
AND $07 ; convert character to number. 0 - 7.
ADD A,$80 ; add offset - they start at $80
INC B ; destructively test for shift
RET Z ; and return if not pressed.
XOR $0F ; toggle bits becomes range $88-$8F
RET ; return.
; ---
; now digits in 'KLC' mode
;; K-KLC-DGT
L039D: INC B ; return with digit codes if neither
RET Z ; shift key pressed.
BIT 5,B ; test for caps shift.
LD HL,L0260-$30 ; prepare base of table CTL-CODES.
JR NZ,L034A ; back to K-LOOK-UP if shift pressed.
; must have been symbol shift
SUB $10 ; for ASCII most will now be correct
; on a standard typewriter.
CP $22 ; but '@' is not - see below.
JR Z,L03B2 ; forward to K-@-CHAR if so
CP $20 ; '_' is the other one that fails
RET NZ ; return if not.
LD A,$5F ; substitute ASCII '_'
RET ; return.
; ---
;; K-@-CHAR
L03B2: LD A,$40 ; substitute ASCII '@'
RET ; return.
; ------------------------------------------------------------------------
; The Spectrum Input character keys. One or two are abbreviated.
; From $00 Flash 0 to $FF COPY. The routine above has decoded all these.
; | 00 Fl0| 01 Fl1| 02 Br0| 03 Br1| 04 In0| 05 In1| 06 CAP| 07 EDT|
; | 08 LFT| 09 RIG| 0A DWN| 0B UP | 0C DEL| 0D ENT| 0E SYM| 0F GRA|
; | 10 Ik0| 11 Ik1| 12 Ik2| 13 Ik3| 14 Ik4| 15 Ik5| 16 Ik6| 17 Ik7|
; | 18 Pa0| 19 Pa1| 1A Pa2| 1B Pa3| 1C Pa4| 1D Pa5| 1E Pa6| 1F Pa7|
; | 20 SP | 21 ! | 22 " | 23 # | 24 $ | 25 % | 26 & | 27 ' |
; | 28 ( | 29 ) | 2A * | 2B + | 2C , | 2D - | 2E . | 2F / |
; | 30 0 | 31 1 | 32 2 | 33 3 | 34 4 | 35 5 | 36 6 | 37 7 |
; | 38 8 | 39 9 | 3A : | 3B ; | 3C < | 3D = | 3E > | 3F ? |
; | 40 @ | 41 A | 42 B | 43 C | 44 D | 45 E | 46 F | 47 G |
; | 48 H | 49 I | 4A J | 4B K | 4C L | 4D M | 4E N | 4F O |
; | 50 P | 51 Q | 52 R | 53 S | 54 T | 55 U | 56 V | 57 W |
; | 58 X | 59 Y | 5A Z | 5B [ | 5C \ | 5D ] | 5E ^ | 5F _ |
; | 60 £ | 61 a | 62 b | 63 c | 64 d | 65 e | 66 f | 67 g |
; | 68 h | 69 i | 6A j | 6B k | 6C l | 6D m | 6E n | 6F o |
; | 70 p | 71 q | 72 r | 73 s | 74 t | 75 u | 76 v | 77 w |
; | 78 x | 79 y | 7A z | 7B { | 7C | | 7D } | 7E ~ | 7F © |
; | 80 128| 81 129| 82 130| 83 131| 84 132| 85 133| 86 134| 87 135|
; | 88 136| 89 137| 8A 138| 8B 139| 8C 140| 8D 141| 8E 142| 8F 143|
; | 90 [A]| 91 [B]| 92 [C]| 93 [D]| 94 [E]| 95 [F]| 96 [G]| 97 [H]|
; | 98 [I]| 99 [J]| 9A [K]| 9B [L]| 9C [M]| 9D [N]| 9E [O]| 9F [P]|
; | A0 [Q]| A1 [R]| A2 [S]| A3 [T]| A4 [U]| A5 RND| A6 IK$| A7 PI |
; | A8 FN | A9 PNT| AA SC$| AB ATT| AC AT | AD TAB| AE VL$| AF COD|
; | B0 VAL| B1 LEN| B2 SIN| B3 COS| B4 TAN| B5 ASN| B6 ACS| B7 ATN|
; | B8 LN | B9 EXP| BA INT| BB SQR| BC SGN| BD ABS| BE PEK| BF IN |
; | C0 USR| C1 ST$| C2 CH$| C3 NOT| C4 BIN| C5 OR | C6 AND| C7 <= |
; | C8 >= | C9 <> | CA LIN| CB THN| CC TO | CD STP| CE DEF| CF CAT|
; | D0 FMT| D1 MOV| D2 ERS| D3 OPN| D4 CLO| D5 MRG| D6 VFY| D7 BEP|
; | D8 CIR| D9 INK| DA PAP| DB FLA| DC BRI| DD INV| DE OVR| DF OUT|
; | E0 LPR| E1 LLI| E2 STP| E3 REA| E4 DAT| E5 RES| E6 NEW| E7 BDR|
; | E8 CON| E9 DIM| EA REM| EB FOR| EC GTO| ED GSB| EE INP| EF LOA|
; | F0 LIS| F1 LET| F2 PAU| F3 NXT| F4 POK| F5 PRI| F6 PLO| F7 RUN|
; | F8 SAV| F9 RAN| FA IF | FB CLS| FC DRW| FD CLR| FE RET| FF CPY|
; Note that for simplicity, Sinclair have located all the control codes
; below the space character.
; ASCII DEL, $7F, has been made a copyright symbol.
; Also $60, '`', not used in BASIC but used in other languages, has been
; allocated the local currency symbol for the relevant country -
; £ in most Spectrums.
; ------------------------------------------------------------------------
;**********************************
;** Part 3. LOUDSPEAKER ROUTINES **
;**********************************
; Documented by Alvin Albrecht.
; ------------------------------
; Routine to control loudspeaker
; ------------------------------
; Outputs a square wave of given duration and frequency
; to the loudspeaker.
; Enter with: DE = #cycles - 1
; HL = tone period as described next
;
; The tone period is measured in T states and consists of
; three parts: a coarse part (H register), a medium part
; (bits 7..2 of L) and a fine part (bits 1..0 of L) which
; contribute to the waveform timing as follows:
;
; coarse medium fine
; duration of low = 118 + 1024*H + 16*(L>>2) + 4*(L&0x3)
; duration of hi = 118 + 1024*H + 16*(L>>2) + 4*(L&0x3)
; Tp = tone period = 236 + 2048*H + 32*(L>>2) + 8*(L&0x3)
; = 236 + 2048*H + 8*L = 236 + 8*HL
;
; As an example, to output five seconds of middle C (261.624 Hz):
; (a) Tone period = 1/261.624 = 3.822ms
; (b) Tone period in T-States = 3.822ms*fCPU = 13378
; where fCPU = clock frequency of the CPU = 3.5MHz
; © Find H and L for desired tone period:
; HL = (Tp - 236) / 8 = (13378 - 236) / 8 = 1643 = 0x066B
; (d) Tone duration in cycles = 5s/3.822ms = 1308 cycles
; DE = 1308 - 1 = 0x051B
;
; The resulting waveform has a duty ratio of exactly 50%.
;
;
;; BEEPER
L03B5: DI ; Disable Interrupts so they don't disturb timing
LD A,L ;
SRL L ;
SRL L ; L = medium part of tone period
CPL ;
AND $03 ; A = 3 - fine part of tone period
LD C,A ;
LD B,$00 ;
LD IX,L03D1 ; Address: BE-IX+3
ADD IX,BC ; IX holds address of entry into the loop
; the loop will contain 0-3 NOPs, implementing
; the fine part of the tone period.
LD A,($5C48) ; BORDCR
AND $38 ; bits 5..3 contain border colour
RRCA ; border colour bits moved to 2..0
RRCA ; to match border bits on port #FE
RRCA ;
OR $08 ; bit 3 set (tape output bit on port #FE)
; for loud sound output
;; BE-IX+3
L03D1: NOP ;(4) ; optionally executed NOPs for small
; adjustments to tone period
;; BE-IX+2
L03D2: NOP ;(4) ;
;; BE-IX+1
L03D3: NOP ;(4) ;
;; BE-IX+0
L03D4: INC B ;(4) ;
INC C ;(4) ;
;; BE-H&L-LP
L03D6: DEC C ;(4) ; timing loop for duration of
JR NZ,L03D6 ;(12/7); high or low pulse of waveform
LD C,$3F ;(7) ;
DEC B ;(4) ;
JP NZ,L03D6 ;(10) ; to BE-H&L-LP
XOR $10 ;(7) ; toggle output beep bit
OUT ($FE),A ;(11) ; output pulse
LD B,H ;(4) ; B = coarse part of tone period
LD C,A ;(4) ; save port #FE output byte
BIT 4,A ;(8) ; if new output bit is high, go
JR NZ,L03F2 ;(12/7); to BE-AGAIN
LD A,D ;(4) ; one cycle of waveform has completed
OR E ;(4) ; (low->low). if cycle countdown = 0
JR Z,L03F6 ;(12/7); go to BE-END
LD A,C ;(4) ; restore output byte for port #FE
LD C,L ;(4) ; C = medium part of tone period
DEC DE ;(6) ; decrement cycle count
JP (IX) ;(8) ; do another cycle
;; BE-AGAIN ; halfway through cycle
L03F2: LD C,L ;(4) ; C = medium part of tone period
INC C ;(4) ; adds 16 cycles to make duration of high = duration of low
JP (IX) ;(8) ; do high pulse of tone
;; BE-END
L03F6: EI ; Enable Interrupts
RET ;
; ------------------
; THE 'BEEP' COMMAND
; ------------------
; BASIC interface to BEEPER subroutine.
; Invoked in BASIC with:
; BEEP dur, pitch
; where dur = duration in seconds
; pitch = # of semitones above/below middle C
;
; Enter with: pitch on top of calculator stack
; duration next on calculator stack
;
;; beep
L03F8: RST 28H ;; FP-CALC
DEFB $31 ;;duplicate ; duplicate pitch
DEFB $27 ;;int ; convert to integer
DEFB $C0 ;;st-mem-0 ; store integer pitch to memory 0
DEFB $03 ;;subtract ; calculate fractional part of pitch = fp_pitch - int_pitch
DEFB $34 ;;stk-data ; push constant
DEFB $EC ;;Exponent: $7C, Bytes: 4 ; constant = 0.05762265
DEFB $6C,$98,$1F,$F5 ;;($6C,$98,$1F,$F5)
DEFB $04 ;;multiply ; compute:
DEFB $A1 ;;stk-one ; 1 + 0.05762265 * fraction_part(pitch)
DEFB $0F ;;addition
DEFB $38 ;;end-calc ; leave on calc stack
LD HL,$5C92 ; MEM-0: number stored here is in 16 bit integer format (pitch)
; 0, 0/FF (pos/neg), LSB, MSB, 0
; LSB/MSB is stored in two's complement
; In the following, the pitch is checked if it is in the range -128<=p<=127
LD A,(HL) ; First byte must be zero, otherwise
AND A ; error in integer conversion
JR NZ,L046C ; to REPORT-B
INC HL ;
LD C,(HL) ; C = pos/neg flag = 0/FF
INC HL ;
LD B,(HL) ; B = LSB, two's complement
LD A,B ;
RLA ;
SBC A,A ; A = 0/FF if B is pos/neg
CP C ; must be the same as C if the pitch is -128<=p<=127
JR NZ,L046C ; if no, error REPORT-B
INC HL ; if -128<=p<=127, MSB will be 0/FF if B is pos/neg
CP (HL) ; verify this
JR NZ,L046C ; if no, error REPORT-B
; now we know -128<=p<=127
LD A,B ; A = pitch + 60
ADD A,$3C ; if -60<=pitch<=67,
JP P,L0425 ; goto BE-i-OK
JP PO,L046C ; if pitch <= 67 goto REPORT-B
; lower bound of pitch set at -60
;; BE-I-OK ; here, -60<=pitch<=127
; and A=pitch+60 -> 0<=A<=187
L0425: LD B,$FA ; 6 octaves below middle C
;; BE-OCTAVE ; A=# semitones above 5 octaves below middle C
L0427: INC B ; increment octave
SUB $0C ; 12 semitones = one octave
JR NC,L0427 ; to BE-OCTAVE
ADD A,$0C ; A = # semitones above C (0-11)
PUSH BC ; B = octave displacement from middle C, 2's complement: -5<=B<=10
LD HL,L046E ; Address: semi-tone
CALL L3406 ; routine LOC-MEM
; HL = 5*A + $046E
CALL L33B4 ; routine STACK-NUM
; read FP value (freq) from semitone table (HL) and push onto calc stack
RST 28H ;; FP-CALC
DEFB $04 ;;multiply mult freq by 1 + 0.0576 * fraction_part(pitch) stacked earlier
;; thus taking into account fractional part of pitch.
;; the number 0.0576*frequency is the distance in Hz to the next
;; note (verify with the frequencies recorded in the semitone
;; table below) so that the fraction_part of the pitch does
;; indeed represent a fractional distance to the next note.
DEFB $38 ;;end-calc HL points to first byte of fp num on stack = middle frequency to generate
POP AF ; A = octave displacement from middle C, 2's complement: -5<=A<=10
ADD A,(HL) ; increase exponent by A (equivalent to multiplying by 2^A)
LD (HL),A ;
RST 28H ;; FP-CALC
DEFB $C0 ;;st-mem-0 ; store frequency in memory 0
DEFB $02 ;;delete ; remove from calc stack
DEFB $31 ;;duplicate ; duplicate duration (seconds)
DEFB $38 ;;end-calc
CALL L1E94 ; routine FIND-INT1 ; FP duration to A
CP $0B ; if dur > 10 seconds,
JR NC,L046C ; goto REPORT-B
;;; The following calculation finds the tone period for HL and the cycle count
;;; for DE expected in the BEEPER subroutine. From the example in the BEEPER comments,
;;;
;;; HL = ((fCPU / f) - 236) / 8 = fCPU/8/f - 236/8 = 437500/f -29.5
;;; DE = duration * frequency - 1
;;;
;;; Note the different constant (30.125) used in the calculation of HL
;;; below. This is probably an error.
RST 28H ;; FP-CALC
DEFB $E0 ;;get-mem-0 ; push frequency
DEFB $04 ;;multiply ; result1: #cycles = duration * frequency
DEFB $E0 ;;get-mem-0 ; push frequency
DEFB $34 ;;stk-data ; push constant
DEFB $80 ;;Exponent $93, Bytes: 3 ; constant = 437500
DEFB $43,$55,$9F,$80 ;;($55,$9F,$80,$00)
DEFB $01 ;;exchange ; frequency on top
DEFB $05 ;;division ; 437500 / frequency
DEFB $34 ;;stk-data ; push constant
DEFB $35 ;;Exponent: $85, Bytes: 1 ; constant = 30.125
DEFB $71 ;;($71,$00,$00,$00)
DEFB $03 ;;subtract ; result2: tone_period(HL) = 437500 / freq - 30.125
DEFB $38 ;;end-calc
CALL L1E99 ; routine FIND-INT2
PUSH BC ; BC = tone_period(HL)
CALL L1E99 ; routine FIND-INT2, BC = #cycles to generate
POP HL ; HL = tone period
LD D,B ;
LD E,C ; DE = #cycles
LD A,D ;
OR E ;
RET Z ; if duration = 0, skip BEEP and avoid 65536 cycle
; boondoggle that would occur next
DEC DE ; DE = #cycles - 1
JP L03B5 ; to BEEPER
; ---
;; REPORT-B
L046C: RST 08H ; ERROR-1
DEFB $0A ; Error Report: Integer out of range
; ---------------------
; THE 'SEMI-TONE' TABLE
; ---------------------
;
; Holds frequencies corresponding to semitones in middle octave.
; To move n octaves higher or lower, frequencies are multiplied by 2^n.
;; semi-tone five byte fp decimal freq note (middle)
L046E: DEFB $89, $02, $D0, $12, $86; 261.625565290 C
DEFB $89, $0A, $97, $60, $75; 277.182631135 C#
DEFB $89, $12, $D5, $17, $1F; 293.664768100 D
DEFB $89, $1B, $90, $41, $02; 311.126983881 D#
DEFB $89, $24, $D0, $53, $CA; 329.627557039 E
DEFB $89, $2E, $9D, $36, $B1; 349.228231549 F
DEFB $89, $38, $FF, $49, $3E; 369.994422674 F#
DEFB $89, $43, $FF, $6A, $73; 391.995436072 G
DEFB $89, $4F, $A7, $00, $54; 415.304697513 G#
DEFB $89, $5C, $00, $00, $00; 440.000000000 A
DEFB $89, $69, $14, $F6, $24; 466.163761616 A#
DEFB $89, $76, $F1, $10, $05; 493.883301378 B
; "Music is the hidden mathematical endeavour of a soul unconscious it
; is calculating" - Gottfried Wilhelm Liebnitz 1646 - 1716
;****************************************
;** Part 4. CASSETTE HANDLING ROUTINES **
;****************************************
; These routines begin with the service routines followed by a single
; command entry point.
; The first of these service routines is a curiosity.
; -----------------------
; THE 'ZX81 NAME' ROUTINE
; -----------------------
; This routine fetches a filename in ZX81 format and is not used by the
; cassette handling routines in this ROM.
;; zx81-name
L04AA: CALL L24FB ; routine SCANNING to evaluate expression.
LD A,($5C3B) ; fetch system variable FLAGS.
ADD A,A ; test bit 7 - syntax, bit 6 - result type.
JP M,L1C8A ; to REPORT-C if not string result
; 'Nonsense in BASIC'.
POP HL ; drop return address.
RET NC ; return early if checking syntax.
PUSH HL ; re-save return address.
CALL L2BF1 ; routine STK-FETCH fetches string parameters.
LD H,D ; transfer start of filename
LD L,E ; to the HL register.
DEC C ; adjust to point to last character and
RET M ; return if the null string.
; or multiple of 256!
ADD HL,BC ; find last character of the filename.
; and also clear carry.
SET 7,(HL) ; invert it.
RET ; return.
; =========================================
;
; PORT 254 ($FE)
;
; spk mic { border }
; ___ ___ ___ ___ ___ ___ ___ ___
; PORT | | | | | | | | |
; 254 | | | | | | | | |
; $FE |___|___|___|___|___|___|___|___|
; 7 6 5 4 3 2 1 0
;
; ----------------------------------
; Save header and program/data bytes
; ----------------------------------
; This routine saves a section of data. It is called from SA-CTRL to save the
; seventeen bytes of header data. It is also the exit route from that routine
; when it is set up to save the actual data.
; On entry -
; HL points to start of data.
; IX points to descriptor.
; The accumulator is set to $00 for a header, $FF for data.
;; SA-BYTES
L04C2: LD HL,L053F ; address: SA/LD-RET
PUSH HL ; is pushed as common exit route.
; however there is only one non-terminal exit
; point.
LD HL,$1F80 ; a timing constant H=$1F, L=$80
; inner and outer loop counters
; a five second lead-in is used for a header.
BIT 7,A ; test one bit of accumulator.
; (AND A ?)
JR Z,L04D0 ; skip to SA-FLAG if a header is being saved.
; else is data bytes and a shorter lead-in is used.
LD HL,$0C98 ; another timing value H=$0C, L=$98.
; a two second lead-in is used for the data.
;; SA-FLAG
L04D0: EX AF,AF' ; save flag
INC DE ; increase length by one.
DEC IX ; decrease start.
DI ; disable interrupts
LD A,$02 ; select red for border, microphone bit on.
LD B,A ; also does as an initial slight counter value.
;; SA-LEADER
L04D8: DJNZ L04D8 ; self loop to SA-LEADER for delay.
; after initial loop, count is $A4 (or $A3)
OUT ($FE),A ; output byte $02/$0D to tape port.
XOR $0F ; switch from RED (mic on) to CYAN (mic off).
LD B,$A4 ; hold count. also timed instruction.
DEC L ; originally $80 or $98.
; but subsequently cycles 256 times.
JR NZ,L04D8 ; back to SA-LEADER until L is zero.
; the outer loop is counted by H
DEC B ; decrement count
DEC H ; originally twelve or thirty-one.
JP P,L04D8 ; back to SA-LEADER until H becomes $FF
; now send a sync pulse. At this stage mic is off and A holds value
; for mic on.
; A sync pulse is much shorter than the steady pulses of the lead-in.
LD B,$2F ; another short timed delay.
;; SA-SYNC-1
L04EA: DJNZ L04EA ; self loop to SA-SYNC-1
OUT ($FE),A ; switch to mic on and red.
LD A,$0D ; prepare mic off - cyan
LD B,$37 ; another short timed delay.
;; SA-SYNC-2
L04F2: DJNZ L04F2 ; self loop to SA-SYNC-2
OUT ($FE),A ; output mic off, cyan border.
LD BC,$3B0E ; B=$3B time(*), C=$0E, YELLOW, MIC OFF.
;
EX AF,AF' ; restore saved flag
; which is 1st byte to be saved.
LD L,A ; and transfer to L.
; the initial parity is A, $FF or $00.
JP L0507 ; JUMP forward to SA-START ->
; the mid entry point of loop.
; -------------------------
; During the save loop a parity byte is maintained in H.
; the save loop begins by testing if reduced length is zero and if so
; the final parity byte is saved reducing count to $FFFF.
;; SA-LOOP
L04FE: LD A,D ; fetch high byte
OR E ; test against low byte.
JR Z,L050E ; forward to SA-PARITY if zero.
LD L,(IX+$00) ; load currently addressed byte to L.
;; SA-LOOP-P
L0505: LD A,H ; fetch parity byte.
XOR L ; exclusive or with new byte.
; -> the mid entry point of loop.
;; SA-START
L0507: LD H,A ; put parity byte in H.
LD A,$01 ; prepare blue, mic=on.
SCF ; set carry flag ready to rotate in.
JP L0525 ; JUMP forward to SA-8-BITS -8->
; ---
;; SA-PARITY
L050E: LD L,H ; transfer the running parity byte to L and
JR L0505 ; back to SA-LOOP-P
; to output that byte before quitting normally.
; ---
; The entry point to save yellow part of bit.
; A bit consists of a period with mic on and blue border followed by
; a period of mic off with yellow border.
; Note. since the DJNZ instruction does not affect flags, the zero flag is
; used to indicate which of the two passes is in effect and the carry
; maintains the state of the bit to be saved.
;; SA-BIT-2
L0511: LD A,C ; fetch 'mic on and yellow' which is
; held permanently in C.
BIT 7,B ; set the zero flag. B holds $3E.
; The entry point to save 1 entire bit. For first bit B holds $3B(*).
; Carry is set if saved bit is 1. zero is reset NZ on entry.
;; SA-BIT-1
L0514: DJNZ L0514 ; self loop for delay to SA-BIT-1
JR NC,L051C ; forward to SA-OUT if bit is 0.
; but if bit is 1 then the mic state is held for longer.
LD B,$42 ; set timed delay. (66 decimal)
;; SA-SET
L051A: DJNZ L051A ; self loop to SA-SET
; (roughly an extra 66*13 clock cycles)
;; SA-OUT
L051C: OUT ($FE),A ; blue and mic on OR yellow and mic off.
LD B,$3E ; set up delay
JR NZ,L0511 ; back to SA-BIT-2 if zero reset NZ (first pass)
; proceed when the blue and yellow bands have been output.
DEC B ; change value $3E to $3D.
XOR A ; clear carry flag (ready to rotate in).
INC A ; reset zero flag i.e. NZ.
; -8->
;; SA-8-BITS
L0525: RL L ; rotate left through carry
; C<76543210<C
JP NZ,L0514 ; JUMP back to SA-BIT-1
; until all 8 bits done.
; when the initial set carry is passed out again then a byte is complete.
DEC DE ; decrease length
INC IX ; increase byte pointer
LD B,$31 ; set up timing.
LD A,$7F ; test the space key and
IN A,($FE) ; return to common exit (to restore border)
RRA ; if a space is pressed
RET NC ; return to SA/LD-RET. - - >
; now test if byte counter has reached $FFFF.
LD A,D ; fetch high byte
INC A ; increment.
JP NZ,L04FE ; JUMP to SA-LOOP if more bytes.
LD B,$3B ; a final delay.
;; SA-DELAY
L053C: DJNZ L053C ; self loop to SA-DELAY
RET ; return - - >
; ------------------------------
; THE 'SAVE/LOAD RETURN' ROUTINE
; ------------------------------
; The address of this routine is pushed on the stack prior to any load/save
; operation and it handles normal completion with the restoration of the
; border and also abnormal termination when the break key, or to be more
; precise the space key is pressed during a tape operation.
;
; - - >
;; SA/LD-RET
L053F: PUSH AF ; preserve accumulator throughout.
LD A,($5C48) ; fetch border colour from BORDCR.
AND $38 ; mask off paper bits.
RRCA ; rotate
RRCA ; to the
RRCA ; range 0-7.
OUT ($FE),A ; change the border colour.
LD A,$7F ; read from port address $7FFE the
IN A,($FE) ; row with the space key at outside.
RRA ; test for space key pressed.
EI ; enable interrupts
JR C,L0554 ; forward to SA/LD-END if not
;; REPORT-Da
L0552: RST 08H ; ERROR-1
DEFB $0C ; Error Report: BREAK - CONT repeats
; ---
;; SA/LD-END
L0554: POP AF ; restore the accumulator.
RET ; return.
; ------------------------------------
; Load header or block of information
; ------------------------------------
; This routine is used to load bytes and on entry A is set to $00 for a
; header or to $FF for data. IX points to the start of receiving location
; and DE holds the length of bytes to be loaded. If, on entry the carry flag
; is set then data is loaded, if reset then it is verified.
;; LD-BYTES
L0556: INC D ; reset the zero flag without disturbing carry.
EX AF,AF' ; preserve entry flags.
DEC D ; restore high byte of length.
DI ; disable interrupts
LD A,$0F ; make the border white and mic off.
OUT ($FE),A ; output to port.
LD HL,L053F ; Address: SA/LD-RET
PUSH HL ; is saved on stack as terminating routine.
; the reading of the EAR bit (D6) will always be preceded by a test of the
; space key (D0), so store the initial post-test state.
IN A,($FE) ; read the ear state - bit 6.
RRA ; rotate to bit 5.
AND $20 ; isolate this bit.
OR $02 ; combine with red border colour.
LD C,A ; and store initial state long-term in C.
CP A ; set the zero flag.
;
;; LD-BREAK
L056B: RET NZ ; return if at any time space is pressed.
;; LD-START
L056C: CALL L05E7 ; routine LD-EDGE-1
JR NC,L056B ; back to LD-BREAK with time out and no
; edge present on tape.
; but continue when a transition is found on tape.
LD HL,$0415 ; set up 16-bit outer loop counter for
; approx 1 second delay.
;; LD-WAIT
L0574: DJNZ L0574 ; self loop to LD-WAIT (for 256 times)
DEC HL ; decrease outer loop counter.
LD A,H ; test for
OR L ; zero.
JR NZ,L0574 ; back to LD-WAIT, if not zero, with zero in B.
; continue after delay with H holding zero and B also.
; sample 256 edges to check that we are in the middle of a lead-in section.
CALL L05E3 ; routine LD-EDGE-2
JR NC,L056B ; back to LD-BREAK
; if no edges at all.
;; LD-LEADER
L0580: LD B,$9C ; set timing value.
CALL L05E3 ; routine LD-EDGE-2
JR NC,L056B ; back to LD-BREAK if time-out
LD A,$C6 ; two edges must be spaced apart.
CP B ; compare
JR NC,L056C ; back to LD-START if too close together for a
; lead-in.
INC H ; proceed to test 256 edged sample.
JR NZ,L0580 ; back to LD-LEADER while more to do.
; sample indicates we are in the middle of a two or five second lead-in.
; Now test every edge looking for the terminal sync signal.
;; LD-SYNC
L058F: LD B,$C9 ; initial timing value in B.
CALL L05E7 ; routine LD-EDGE-1
JR NC,L056B ; back to LD-BREAK with time-out.
LD A,B ; fetch augmented timing value from B.
CP $D4 ; compare
JR NC,L058F ; back to LD-SYNC if gap too big, that is,
; a normal lead-in edge gap.
; but a short gap will be the sync pulse.
; in which case another edge should appear before B rises to $FF
CALL L05E7 ; routine LD-EDGE-1
RET NC ; return with time-out.
; proceed when the sync at the end of the lead-in is found.
; We are about to load data so change the border colours.
LD A,C ; fetch long-term mask from C
XOR $03 ; and make blue/yellow.
LD C,A ; store the new long-term byte.
LD H,$00 ; set up parity byte as zero.
LD B,$B0 ; timing.
JR L05C8 ; forward to LD-MARKER
; the loop mid entry point with the alternate
; zero flag reset to indicate first byte
; is discarded.
; --------------
; the loading loop loads each byte and is entered at the mid point.
;; LD-LOOP
L05A9: EX AF,AF' ; restore entry flags and type in A.
JR NZ,L05B3 ; forward to LD-FLAG if awaiting initial flag
; which is to be discarded.
JR NC,L05BD ; forward to LD-VERIFY if not to be loaded.
LD (IX+$00),L ; place loaded byte at memory location.
JR L05C2 ; forward to LD-NEXT
; ---
;; LD-FLAG
L05B3: RL C ; preserve carry (verify) flag in long-term
; state byte. Bit 7 can be lost.
XOR L ; compare type in A with first byte in L.
RET NZ ; return if no match e.g. CODE vs. DATA.
; continue when data type matches.
LD A,C ; fetch byte with stored carry
RRA ; rotate it to carry flag again
LD C,A ; restore long-term port state.
INC DE ; increment length ??
JR L05C4 ; forward to LD-DEC.
; but why not to location after ?
; ---
; for verification the byte read from tape is compared with that in memory.
;; LD-VERIFY
L05BD: LD A,(IX+$00) ; fetch byte from memory.
XOR L ; compare with that on tape
RET NZ ; return if not zero.
;; LD-NEXT
L05C2: INC IX ; increment byte pointer.
;; LD-DEC
L05C4: DEC DE ; decrement length.
EX AF,AF' ; store the flags.
LD B,$B2 ; timing.
; when starting to read 8 bits the receiving byte is marked with bit at right.
; when this is rotated out again then 8 bits have been read.
;; LD-MARKER
L05C8: LD L,$01 ; initialize as %00000001
;; LD-8-BITS
L05CA: CALL L05E3 ; routine LD-EDGE-2 increments B relative to
; gap between 2 edges.
RET NC ; return with time-out.
LD A,$CB ; the comparison byte.
CP B ; compare to incremented value of B.
; if B is higher then bit on tape was set.
; if <= then bit on tape is reset.
RL L ; rotate the carry bit into L.
LD B,$B0 ; reset the B timer byte.
JP NC,L05CA ; JUMP back to LD-8-BITS
; when carry set then marker bit has been passed out and byte is complete.
LD A,H ; fetch the running parity byte.
XOR L ; include the new byte.
LD H,A ; and store back in parity register.
LD A,D ; check length of
OR E ; expected bytes.
JR NZ,L05A9 ; back to LD-LOOP
; while there are more.
; when all bytes loaded then parity byte should be zero.
LD A,H ; fetch parity byte.
CP $01 ; set carry if zero.
RET ; return
; in no carry then error as checksum disagrees.
; -------------------------
; Check signal being loaded
; -------------------------
; An edge is a transition from one mic state to another.
; More specifically a change in bit 6 of value input from port $FE.
; Graphically it is a change of border colour, say, blue to yellow.
; The first entry point looks for two adjacent edges. The second entry point
; is used to find a single edge.
; The B register holds a count, up to 256, within which the edge (or edges)
; must be found. The gap between two edges will be more for a '1' than a '0'
; so the value of B denotes the state of the bit (two edges) read from tape.
; ->
;; LD-EDGE-2
L05E3: CALL L05E7 ; call routine LD-EDGE-1 below.
RET NC ; return if space pressed or time-out.
; else continue and look for another adjacent
; edge which together represent a bit on the
; tape.
; ->
; this entry point is used to find a single edge from above but also
; when detecting a read-in signal on the tape.
;; LD-EDGE-1
L05E7: LD A,$16 ; a delay value of twenty two.
;; LD-DELAY
L05E9: DEC A ; decrement counter
JR NZ,L05E9 ; loop back to LD-DELAY 22 times.
AND A ; clear carry.
;; LD-SAMPLE
L05ED: INC B ; increment the time-out counter.
RET Z ; return with failure when $FF passed.
LD A,$7F ; prepare to read keyboard and EAR port
IN A,($FE) ; row $7FFE. bit 6 is EAR, bit 0 is SPACE key.
RRA ; test outer key the space. (bit 6 moves to 5)
RET NC ; return if space pressed. >>>
XOR C ; compare with initial long-term state.
AND $20 ; isolate bit 5
JR Z,L05ED ; back to LD-SAMPLE if no edge.
; but an edge, a transition of the EAR bit, has been found so switch the
; long-term comparison byte containing both border colour and EAR bit.
LD A,C ; fetch comparison value.
CPL ; switch the bits
LD C,A ; and put back in C for long-term.
AND $07 ; isolate new colour bits.
OR $08 ; set bit 3 - MIC off.
OUT ($FE),A ; send to port to effect the change of colour.
SCF ; set carry flag signaling edge found within
; time allowed.
RET ; return.
; ---------------------------------
; Entry point for all tape commands
; ---------------------------------
; This is the single entry point for the four tape commands.
; The routine first determines in what context it has been called by examining
; the low byte of the Syntax table entry which was stored in T_ADDR.
; Subtracting $EO (the present arrangement) gives a value of
; $00 - SAVE
; $01 - LOAD
; $02 - VERIFY
; $03 - MERGE
; As with all commands the address STMT-RET is on the stack.
;; SAVE-ETC
L0605: POP AF ; discard address STMT-RET.
LD A,($5C74) ; fetch T_ADDR
; Now reduce the low byte of the Syntax table entry to give command.
; Note. For ZASM use SUB $E0 as next instruction.
L0609: SUB L1ADF + 1 % 256 ; subtract the known offset.
; ( is SUB $E0 in standard ROM )
LD ($5C74),A ; and put back in T_ADDR as 0,1,2, or 3
; for future reference.
CALL L1C8C ; routine EXPT-EXP checks that a string
; expression follows and stacks the
; parameters in run-time.
CALL L2530 ; routine SYNTAX-Z
JR Z,L0652 ; forward to SA-DATA if checking syntax.
LD BC,$0011 ; presume seventeen bytes for a header.
LD A,($5C74) ; fetch command from T_ADDR.
AND A ; test for zero - SAVE.
JR Z,L0621 ; forward to SA-SPACE if so.
LD C,$22 ; else double length to thirty four.
;; SA-SPACE
L0621: RST 30H ; BC-SPACES creates 17/34 bytes in workspace.
PUSH DE ; transfer the start of new space to
POP IX ; the available index register.
; ten spaces are required for the default filename but it is simpler to
; overwrite the first file-type indicator byte as well.
LD B,$0B ; set counter to eleven.
LD A,$20 ; prepare a space.
;; SA-BLANK
L0629: LD (DE),A ; set workspace location to space.
INC DE ; next location.
DJNZ L0629 ; loop back to SA-BLANK till all eleven done.
LD (IX+$01),$FF ; set first byte of ten character filename
; to $FF as a default to signal null string.
CALL L2BF1 ; routine STK-FETCH fetches the filename
; parameters from the calculator stack.
; length of string in BC.
; start of string in DE.
LD HL,$FFF6 ; prepare the value minus ten.
DEC BC ; decrement length.
; ten becomes nine, zero becomes $FFFF.
ADD HL,BC ; trial addition.
INC BC ; restore true length.
JR NC,L064B ; forward to SA-NAME if length is one to ten.
; the filename is more than ten characters in length or the null string.
LD A,($5C74) ; fetch command from T_ADDR.
AND A ; test for zero - SAVE.
JR NZ,L0644 ; forward to SA-NULL if not the SAVE command.
; but no more than ten characters are allowed for SAVE.
; The first ten characters of any other command parameter are acceptable.
; Weird, but necessary, if saving to sectors.
; Note. the golden rule that there are no restriction on anything is broken.
;; REPORT-Fa
L0642: RST 08H ; ERROR-1
DEFB $0E ; Error Report: Invalid file name
; continue with LOAD, MERGE, VERIFY and also SAVE within ten character limit.
;; SA-NULL
L0644: LD A,B ; test length of filename
OR C ; for zero.
JR Z,L0652 ; forward to SA-DATA if so using the 255
; indicator followed by spaces.
LD BC,$000A ; else trim length to ten.
; other paths rejoin here with BC holding length in range 1 - 10.
;; SA-NAME
L064B: PUSH IX ; push start of file descriptor.
POP HL ; and pop into HL.
INC HL ; HL now addresses first byte of filename.
EX DE,HL ; transfer destination address to DE, start
; of string in command to HL.
LDIR ; copy up to ten bytes
; if less than ten then trailing spaces follow.
; the case for the null string rejoins here.
;; SA-DATA
L0652: RST 18H ; GET-CHAR
CP $E4 ; is character after filename the token 'DATA' ?
JR NZ,L06A0 ; forward to SA-SCR$ to consider SCREEN$ if
; not.
; continue to consider DATA.
LD A,($5C74) ; fetch command from T_ADDR
CP $03 ; is it 'VERIFY' ?
JP Z,L1C8A ; jump forward to REPORT-C if so.
; 'Nonsense in BASIC'
; VERIFY "d" DATA is not allowed.
; continue with SAVE, LOAD, MERGE of DATA.
RST 20H ; NEXT-CHAR
CALL L28B2 ; routine LOOK-VARS searches variables area
; returning with carry reset if found or
; checking syntax.
SET 7,C ; this converts a simple string to a
; string array. The test for an array or string
; comes later.
JR NC,L0672 ; forward to SA-V-OLD if variable found.
LD HL,$0000 ; set destination to zero as not fixed.
LD A,($5C74) ; fetch command from T_ADDR
DEC A ; test for 1 - LOAD
JR Z,L0685 ; forward to SA-V-NEW with LOAD DATA.
; to load a new array.
; otherwise the variable was not found in run-time with SAVE/MERGE.
;; REPORT-2a
L0670: RST 08H ; ERROR-1
DEFB $01 ; Error Report: Variable not found
; continue with SAVE/LOAD DATA
;; SA-V-OLD
L0672: JP NZ,L1C8A ; to REPORT-C if not an array variable.
; or erroneously a simple string.
; 'Nonsense in BASIC'
CALL L2530 ; routine SYNTAX-Z
JR Z,L0692 ; forward to SA-DATA-1 if checking syntax.
INC HL ; step past single character variable name.
LD A,(HL) ; fetch low byte of length.
LD (IX+$0B),A ; place in descriptor.
INC HL ; point to high byte.
LD A,(HL) ; and transfer that
LD (IX+$0C),A ; to descriptor.
INC HL ; increase pointer within variable.
;; SA-V-NEW
L0685: LD (IX+$0E),C ; place character array name in header.
LD A,$01 ; default to type numeric.
BIT 6,C ; test result from look-vars.
JR Z,L068F ; forward to SA-V-TYPE if numeric.
INC A ; set type to 2 - string array.
;; SA-V-TYPE
L068F: LD (IX+$00),A ; place type 0, 1 or 2 in descriptor.
;; SA-DATA-1
L0692: EX DE,HL ; save var pointer in DE
RST 20H ; NEXT-CHAR
CP $29 ; is character ')' ?
JR NZ,L0672 ; back if not to SA-V-OLD to report
; 'Nonsense in BASIC'
RST 20H ; NEXT-CHAR advances character address.
CALL L1BEE ; routine CHECK-END errors if not end of
; the statement.
EX DE,HL ; bring back variables data pointer.
JP L075A ; jump forward to SA-ALL
; ---
; the branch was here to consider a 'SCREEN$', the display file.
;; SA-SCR$
L06A0: CP $AA ; is character the token 'SCREEN$' ?
JR NZ,L06C3 ; forward to SA-CODE if not.
LD A,($5C74) ; fetch command from T_ADDR
CP $03 ; is it MERGE ?
JP Z,L1C8A ; jump to REPORT-C if so.
; 'Nonsense in BASIC'
; continue with SAVE/LOAD/VERIFY SCREEN$.
RST 20H ; NEXT-CHAR
CALL L1BEE ; routine CHECK-END errors if not at end of
; statement.
; continue in runtime.
LD (IX+$0B),$00 ; set descriptor length
LD (IX+$0C),$1B ; to $1b00 to include bitmaps and attributes.
LD HL,$4000 ; set start to display file start.
LD (IX+$0D),L ; place start in
LD (IX+$0E),H ; the descriptor.
JR L0710 ; forward to SA-TYPE-3
; ---
; the branch was here to consider CODE.
;; SA-CODE
L06C3: CP $AF ; is character the token 'CODE' ?
JR NZ,L0716 ; forward if not to SA-LINE to consider an
; auto-started BASIC program.
LD A,($5C74) ; fetch command from T_ADDR
CP $03 ; is it MERGE ?
JP Z,L1C8A ; jump forward to REPORT-C if so.
; 'Nonsense in BASIC'
RST 20H ; NEXT-CHAR advances character address.
CALL L2048 ; routine PR-ST-END checks if a carriage
; return or ':' follows.
JR NZ,L06E1 ; forward to SA-CODE-1 if there are parameters.
LD A,($5C74) ; else fetch the command from T_ADDR.
AND A ; test for zero - SAVE without a specification.
JP Z,L1C8A ; jump to REPORT-C if so.
; 'Nonsense in BASIC'
; for LOAD/VERIFY put zero on stack to signify handle at location saved from.