Subversion Repositories pentevo

Rev

Rev 596 | Go to most recent revision | Blame | Compare with Previous | Last modification | View Log | Download | RSS feed

  1.  
  2. ;www.fruitcake.plus.com
  3.  
  4. ;LAST UPDATE: 08.07.2014 savelij
  5.  
  6.                 include ../../define.a80
  7.  
  8. TAP_EMU_BORDER  EQU 0
  9.  
  10. ; **************************************
  11. ; *** SPECTRUM 128 ROM 1 DISASSEMBLY ***
  12. ; **************************************
  13.  
  14. ; The Spectrum ROMs are copyright Amstrad, who have kindly given permission
  15. ; to reverse engineer and publish ROM disassemblies.
  16.  
  17.  
  18. ; =====
  19. ; NOTES
  20. ; =====
  21.  
  22. ; ------------
  23. ; Release Date
  24. ; ------------
  25. ; 23rd May 2009
  26.  
  27.  
  28. ; =================
  29. ; ASSEMBLER DEFINES
  30. ; =================
  31.  
  32. ;TASM directives:
  33.  
  34. ;#define DB .BYTE      
  35. ;#define DEFW .WORD
  36. ;#define DEFM .TEXT
  37. ;#DEFINE DEFS .FILL
  38. ;#define END  .END
  39. ;#define EQU  .EQU
  40. ;#define ORG  .ORG
  41.  
  42. ; The Sinclair Interface1 ROM written by Dr. Ian Logan calls numerous
  43. ; routines in this ROM. Non-standard entry points have a label beginning
  44. ; with X.
  45.  
  46.         ORG     $0000
  47.  
  48. ;*****************************************
  49. ;** Part 1. RESTART ROUTINES AND TABLES **
  50. ;*****************************************
  51.  
  52. ; -----------
  53. ; THE 'START'
  54. ; -----------
  55. ; At switch on, the Z80 chip is in interrupt mode 0.
  56. ; This location can also be 'called' to reset the machine.
  57. ; Typically with PRINT USR 0.
  58.  
  59. ;; START
  60. L0000:  DI                      ; disable interrupts.
  61.         XOR     A               ; signal coming from START.
  62.         LD      DE,$FFFF        ; top of possible physical RAM.
  63.         JP      L11CB           ; jump forward to common code at START-NEW.
  64.  
  65. ; -------------------
  66. ; THE 'ERROR' RESTART
  67. ; -------------------
  68. ; The error pointer is made to point to the position of the error to enable
  69. ; the editor to show the error if it occurred during syntax checking.
  70. ; It is used at 37 places in the program.
  71. ; An instruction fetch on address $0008 may page in a peripheral ROM
  72. ; such as the Sinclair Interface 1 or Disciple Disk Interface.
  73. ; This was not however an original design concept and not all errors pass
  74. ; through here.
  75.  
  76. ;; ERROR-1
  77. L0008           NOP
  78.                 JP RST8_CMP
  79.  
  80. ;               LD HL,($5C5D)           ; fetch the character address from CH_ADD.
  81. ;               LD ($5C5F),HL           ; copy it to the error pointer X_PTR.
  82. ;               JR L0053                ; forward to continue at ERROR-2.
  83.  
  84. ; -----------------------------
  85. ; THE 'PRINT CHARACTER' RESTART
  86. ; -----------------------------
  87. ; The A register holds the code of the character that is to be sent to
  88. ; the output stream of the current channel.
  89. ; The alternate register set is used to output a character in the A register
  90. ; so there is no need to preserve any of the current registers (HL,DE,BC).
  91. ; This restart is used 21 times.
  92.  
  93.                 DUPL 0X0010-$,0XFF
  94. ;; PRINT-A
  95. L0010:  JP      L15F2           ; jump forward to continue at PRINT-A-2.
  96.  
  97. ; ---
  98.  
  99.                 DUPL ADR_SEL_ROM-$,0XFF
  100. L0014           OUT (C),A
  101.                 NOP
  102.                 RET
  103.  
  104.                 DUPL 0X0018-$,0XFF
  105.  
  106. ;        DB    $FF             ; this byte is used by the SPECTRUM command in
  107.                                 ; ROM 0 to generate an error report "0 OK".
  108. ;        DB    $FF, $FF        ; four unused locations.
  109. ;        DB    $FF, $FF        ;
  110.  
  111. ; -------------------------------
  112. ; THE 'COLLECT CHARACTER' RESTART
  113. ; -------------------------------
  114. ; The contents of the location currently addressed by CH_ADD are fetched.
  115. ; A return is made if the value represents a character that has
  116. ; relevance to the BASIC parser. Otherwise CH_ADD is incremented and the
  117. ; tests repeated. CH_ADD will be addressing somewhere -
  118. ; 1) in the BASIC program area during line execution.
  119. ; 2) in workspace if evaluating, for example, a string expression.
  120. ; 3) in the edit buffer if parsing a direct command or a new BASIC line.
  121. ; 4) in workspace if accepting input but not that from INPUT LINE.
  122.  
  123. ;; GET-CHAR
  124. L0018:  LD      HL,($5C5D)      ; fetch the address from CH_ADD.
  125.         LD      A,(HL)          ; use it to pick up current character.
  126.  
  127. ;; TEST-CHAR
  128. L001C:  CALL    L007D           ; routine SKIP-OVER tests if the character
  129.         RET     NC              ; is relevant. Return if it is so.
  130.  
  131. ; ------------------------------------
  132. ; THE 'COLLECT NEXT CHARACTER' RESTART
  133. ; ------------------------------------
  134. ; As the BASIC commands and expressions are interpreted, this routine is
  135. ; called repeatedly to step along the line. It is used 83 times.
  136.  
  137. ;; NEXT-CHAR
  138. L0020:  CALL    L0074           ; routine CH-ADD+1 fetches the next immediate
  139.                                 ; character.
  140.         JR      L001C           ; jump back to TEST-CHAR until a valid
  141.                                 ; character is found.
  142.  
  143. ; ---
  144.  
  145.         DB    $FF, $FF, $FF   ; unused
  146.  
  147. ; -----------------------
  148. ; THE 'CALCULATE' RESTART
  149. ; -----------------------
  150. ; This restart enters the Spectrum's internal, floating-point,
  151. ; stack-based, FORTH-like language.
  152. ; It is further used recursively from within the calculator.
  153. ; It is used on 77 occasions.
  154.  
  155. ;; FP-CALC
  156. L0028:  JP      L335B           ; jump forward to the CALCULATE routine.
  157.  
  158. ; ---
  159.  
  160.         DB    $FF, $FF, $FF   ; spare - note that on the ZX81, space being a
  161.         DB    $FF, $FF        ; little cramped, these same locations were
  162.                                 ; used for the five-byte end-calc literal.
  163.  
  164. ; ------------------------------
  165. ; THE 'CREATE BC SPACES' RESTART
  166. ; ------------------------------
  167. ; This restart is used on only 12 occasions to create BC spaces
  168. ; between workspace and the calculator stack.
  169.  
  170. ;; BC-SPACES
  171. L0030:  PUSH    BC              ; save number of spaces.
  172.         LD      HL,($5C61)      ; fetch WORKSP.
  173.         PUSH    HL              ; save address of workspace.
  174.         JP      L169E           ; jump forward to continuation code RESERVE.
  175.  
  176. ; --------------------------------
  177. ; THE 'MASKABLE INTERRUPT' ROUTINE
  178. ; --------------------------------
  179. ; This routine increments the Spectrum's three-byte FRAMES counter
  180. ; fifty times a second (sixty times a second in the USA ).
  181. ; Both this routine and the called KEYBOARD subroutine use
  182. ; the IY register to access system variables and flags so a user-written
  183. ; program must disable interrupts to make use of the IY register.
  184.  
  185. ;; MASK-INT
  186. L0038:  PUSH    AF              ; save the registers.
  187.         PUSH    HL              ; but not IY unfortunately.
  188.         LD      HL,($5C78)      ; fetch two bytes at FRAMES1.
  189.         INC     HL              ; increment lowest two bytes of counter.
  190.         LD      ($5C78),HL      ; place back in FRAMES1.
  191.         LD      A,H             ; test if the result
  192.         OR      L               ; was zero.
  193.         JR      NZ,L0048        ; forward to KEY-INT if not.
  194.  
  195.         INC     (IY+$40)        ; otherwise increment FRAMES3 the third byte.
  196.  
  197. ; now save the rest of the main registers and read and decode the keyboard.
  198.  
  199. ;; KEY-INT
  200. L0048:  PUSH    BC              ; save the other
  201.         PUSH    DE              ; main registers.
  202.  
  203.                 IF BAS48_ONLY=1
  204.                 CALL L02BF
  205.                 ELSE
  206.                 CALL L386E              ; Spectrum 128 patch: read the keypad and keyboard
  207.                                         ; in the process of reading a key-press.
  208.                 ENDIF
  209.  
  210. L004D:  POP     DE              ;
  211.         POP     BC              ; restore registers.
  212.  
  213.         POP     HL              ;
  214.         POP     AF              ;
  215.         EI                      ; enable interrupts.
  216.         RET                     ; return.
  217.  
  218. ; ---------------------
  219. ; THE 'ERROR-2' ROUTINE
  220. ; ---------------------
  221. ; A continuation of the code at 0008.
  222. ; The error code is stored and after clearing down stacks,
  223. ; an indirect jump is made to MAIN-4, etc. to handle the error.
  224.  
  225. ;; ERROR-2
  226. L0053:  POP     HL              ; drop the return address - the location
  227.                                 ; after the RST 08H instruction.
  228.         LD      L,(HL)          ; fetch the error code that follows.
  229.                                 ; (nice to see this instruction used.)
  230.  
  231. ; Note. this entry point is used when out of memory at REPORT-4.
  232. ; The L register has been loaded with the report code but X-PTR is not
  233. ; updated.
  234.  
  235. ;; ERROR-3
  236. L0055:  LD      (IY+$00),L      ; store it in the system variable ERR_NR.
  237.         LD      SP,($5C3D)      ; ERR_SP points to an error handler on the
  238.                                 ; machine stack. There may be a hierarchy
  239.                                 ; of routines.
  240.                                 ; to MAIN-4 initially at base.
  241.                                 ; or REPORT-G on line entry.
  242.                                 ; or  ED-ERROR when editing.
  243.                                 ; or   ED-FULL during ed-enter.
  244.                                 ; or  IN-VAR-1 during runtime input etc.
  245.  
  246.         JP      L16C5           ; jump to SET-STK to clear the calculator
  247.                                 ; stack and reset MEM to usual place in the
  248.                                 ; systems variables area.
  249.                                 ; and then indirectly to MAIN-4, etc.
  250.  
  251. ; ---
  252.  
  253.         DB    $FF, $FF, $FF   ; unused locations
  254.         DB    $FF, $FF, $FF   ; before the fixed-position
  255.         DB    $FF             ; NMI routine.
  256.  
  257. ; ------------------------------------
  258. ; THE 'NON-MASKABLE INTERRUPT' ROUTINE
  259. ; ------------------------------------
  260. ; There is no NMI switch on the standard Spectrum.
  261. ; When activated, a location in the system variables is tested
  262. ; and if the contents are zero a jump made to that location else
  263. ; a return is made. Perhaps a disabled development feature but
  264. ; if the logic was reversed, no program would be safe from
  265. ; copy-protection and the Spectrum would have had no software base.
  266. ; The location NMIADD was later used by Interface 1 for other purposes.
  267. ; On later Spectrums, and the Brazilian Spectrum, the logic of this
  268. ; routine was reversed.
  269.  
  270. ;; RESET
  271.                 DUPL 0X0066-$,0XFF
  272. L0066           NOP
  273. ;               PUSH AF         ; save the
  274.                 PUSH HL         ; registers.
  275.                 LD HL,($5CB0)   ; fetch the system variable NMIADD.
  276.                 LD A,H          ; test address
  277.                 OR L            ; for zero.
  278. ;               JR NZ,L0070     ; skip to NO-RESET if NOT ZERO
  279.                 JR Z,L0070
  280.                 JP (HL)         ; jump to routine ( i.e. L0000 )
  281.  
  282. ;; NO-RESET
  283. L0070           POP HL          ; restore the
  284.                 POP AF          ; registers.
  285.                 RETN            ; return to previous interrupt state.
  286.  
  287. ; ---------------------------
  288. ; THE 'CH ADD + 1' SUBROUTINE
  289. ; ---------------------------
  290. ; This subroutine is called from RST 20, and three times from elsewhere
  291. ; to fetch the next immediate character following the current valid character
  292. ; address and update the associated system variable.
  293. ; The entry point TEMP-PTR1 is used from the SCANNING routine.
  294. ; Both TEMP-PTR1 and TEMP-PTR2 are used by the READ command routine.
  295.  
  296. ;; CH-ADD+1
  297. L0074:  LD      HL,($5C5D)      ; fetch address from CH_ADD.
  298.  
  299. ;; TEMP-PTR1
  300. L0077:  INC     HL              ; increase the character address by one.
  301.  
  302. ;; TEMP-PTR2
  303. L0078:  LD      ($5C5D),HL      ; update CH_ADD with character address.
  304.  
  305. X007B:  LD      A,(HL)          ; load character to A from HL.
  306.         RET                     ; and return.
  307.  
  308. ; --------------------------
  309. ; THE 'SKIP OVER' SUBROUTINE
  310. ; --------------------------
  311. ; This subroutine is called once from RST 18 to skip over white-space and
  312. ; other characters irrelevant to the parsing of a BASIC line etc. .
  313. ; Initially the A register holds the character to be considered
  314. ; and HL holds its address which will not be within quoted text
  315. ; when a BASIC line is parsed.
  316. ; Although the 'tab' and 'at' characters will not appear in a BASIC line,
  317. ; they could be present in a string expression, and in other situations.
  318. ; Note. although white-space is usually placed in a program to indent loops
  319. ; and make it more readable, it can also be used for the opposite effect and
  320. ; spaces may appear in variable names although the parser never sees them.
  321. ; It is this routine that helps make the variables 'Anum bEr5 3BUS' and
  322. ; 'a number 53 bus' appear the same to the parser.
  323.  
  324. ;; SKIP-OVER
  325. L007D:  CP      $21             ; test if higher than space.
  326.         RET     NC              ; return with carry clear if so.
  327.  
  328.         CP      $0D             ; carriage return ?
  329.         RET     Z               ; return also with carry clear if so.
  330.  
  331.                                 ; all other characters have no relevance
  332.                                 ; to the parser and must be returned with
  333.                                 ; carry set.
  334.  
  335.         CP      $10             ; test if 0-15d
  336.         RET     C               ; return, if so, with carry set.
  337.  
  338.         CP      $18             ; test if 24-32d
  339.         CCF                     ; complement carry flag.
  340.         RET     C               ; return with carry set if so.
  341.  
  342.                                 ; now leaves 16d-23d
  343.  
  344.         INC     HL              ; all above have at least one extra character
  345.                                 ; to be stepped over.
  346.  
  347.         CP      $16             ; controls 22d ('at') and 23d ('tab') have two.
  348.         JR      C,L0090         ; forward to SKIPS with ink, paper, flash,
  349.                                 ; bright, inverse or over controls.
  350.                                 ; Note. the high byte of tab is for RS232 only.
  351.                                 ; it has no relevance on this machine.
  352.  
  353.         INC     HL              ; step over the second character of 'at'/'tab'.
  354.  
  355. ;; SKIPS
  356. L0090:  SCF                     ; set the carry flag
  357.         LD      ($5C5D),HL      ; update the CH_ADD system variable.
  358.         RET                     ; return with carry set.
  359.  
  360.  
  361. ; ------------------
  362. ; THE 'TOKEN TABLES'
  363. ; ------------------
  364. ; The tokenized characters 134d (RND) to 255d (COPY) are expanded using
  365. ; this table. The last byte of a token is inverted to denote the end of
  366. ; the word. The first is an inverted step-over byte.
  367.  
  368. ;; TKN-TABLE
  369. L0095           DC "?"          ;DB    '?'+$80
  370.                 DC "RND"        ;DEFM    "RN"
  371.                                 ;DB    'D'+$80
  372.                 DC "INKEY$"     ;DEFM    "INKEY"
  373.                                 ;DB    '$'+$80
  374.                 DC "PI"         ;DB    'P','I'+$80
  375.                 DC "FN"         ;DB    'F','N'+$80
  376.                 DC "POINT"      ;DEFM    "POIN"
  377.                                 ;DB    'T'+$80
  378.                 DC "SCREEN$"    ;DEFM    "SCREEN"
  379.                                 ;DB    '$'+$80
  380.                 DC "ATTR"       ;DEFM    "ATT"
  381.                                 ;DB    'R'+$80
  382.                 DC "AT"         ;DB    'A','T'+$80
  383.                 DC "TAB"        ;DEFM    "TA"
  384.                                 ;DB    'B'+$80
  385.                 DC "VAL$"       ;DEFM    "VAL"
  386.                                 ;DB    '$'+$80
  387.                 DC "CODE"       ;DEFM    "COD"
  388.                                 ;DB    'E'+$80
  389.                 DC "VAL"        ;DEFM    "VA"
  390.                                 ;DB    'L'+$80
  391.                 DC "LEN"        ;DEFM    "LE"
  392.                                 ;DB    'N'+$80
  393.                 DC "SIN"        ;DEFM    "SI"
  394.                                 ;DB    'N'+$80
  395.                 DC "COS"        ;DEFM    "CO"
  396.                                 ;DB    'S'+$80
  397.                 DC "TAN"        ;DEFM    "TA"
  398.                                 ;DB    'N'+$80
  399.                 DC "ASN"        ;DEFM    "AS"
  400.                                 ;DB    'N'+$80
  401.                 DC "ACS"        ;DEFM    "AC"
  402.                                 ;DB    'S'+$80
  403.                 DC "ATN"        ;DEFM    "AT"
  404.                                 ;DB    'N'+$80
  405.                 DC "LN"         ;DB    'L','N'+$80
  406.                 DC "EXP"        ;DEFM    "EX"
  407.                                 ;DB    'P'+$80
  408.                 DC "INT"        ;DEFM    "IN"
  409.                                 ;DB    'T'+$80
  410.                 DC "SQR"        ;DEFM    "SQ"
  411.                                 ;DB    'R'+$80
  412.                 DC "SGN"        ;DEFM    "SG"
  413.                                 ;DB    'N'+$80
  414.                 DC "ABS"        ;DEFM    "AB"
  415.                                 ;DB    'S'+$80
  416.                 DC "PEEK"       ;DEFM    "PEE"
  417.                                 ;DB    'K'+$80
  418.                 DC "IN"         ;DB    'I','N'+$80
  419.                 DC "USR"        ;DEFM    "US"
  420.                                 ;DB    'R'+$80
  421.                 DC "STR$"       ;DEFM    "STR"
  422.                                 ;DB    '$'+$80
  423.                 DC "CHR$"       ;DEFM    "CHR"
  424.                                 ;DB    '$'+$80
  425.                 DC "NOT"        ;DEFM    "NO"
  426.                                 ;DB    'T'+$80
  427.                 DC "BIN"        ;DEFM    "BI"
  428.                                 ;DB    'N'+$80
  429.  
  430. ;   The previous 32 function-type words are printed without a leading space
  431. ;   The following have a leading space if they begin with a letter
  432.  
  433.                 DC "OR"         ;DB    'O','R'+$80
  434.                 DC "AND"        ;DEFM    "AN"
  435.                                 ;DB    'D'+$80
  436.                 DC "<="         ;DB    $3C,'='+$80             ; <=
  437.                 DC ">="         ;DB    $3E,'='+$80             ; >=
  438.                 DC "<>"         ;DB    $3C,$3E+$80             ; <>
  439.                 DC "LINE"       ;DEFM    "LIN"
  440.                                 ;DB    'E'+$80
  441.                 DC "THEN"       ;DEFM    "THE"
  442.                                 ;DB    'N'+$80
  443.                 DC "TO"         ;DB    'T','O'+$80
  444.                 DC "STEP"       ;DEFM    "STE"
  445.                                 ;DB    'P'+$80
  446.                 DC "DEF FN"     ;DEFM    "DEF F"
  447.                                 ;DB    'N'+$80
  448.                 DC "CAT"        ;DEFM    "CA"
  449.                                 ;DB    'T'+$80
  450.                 DC "FORMAT"     ;DEFM    "FORMA"
  451.                                 ;DB    'T'+$80
  452.                 DC "MOVE"       ;DEFM    "MOV"
  453.                                 ;DB    'E'+$80
  454.                 DC "ERASE"      ;DEFM    "ERAS"
  455.                                 ;DB    'E'+$80
  456.                 DC "OPEN #"     ;DEFM    "OPEN "
  457.                                 ;DB    '#'+$80
  458.                 DC "CLOSE #"    ;DEFM    "CLOSE "
  459.                                 ;DB    '#'+$80
  460.                 DC "MERGE"      ;DEFM    "MERG"
  461.                                 ;DB    'E'+$80
  462.                 DC "VERIFY"     ;DEFM    "VERIF"
  463.                                 ;DB    'Y'+$80
  464.                 DC "BEEP"       ;DEFM    "BEE"
  465.                                 ;DB    'P'+$80
  466.                 DC "CIRCLE"     ;DEFM    "CIRCL"
  467.                                 ;DB    'E'+$80
  468.                 DC "INK"        ;DEFM    "IN"
  469.                                 ;DB    'K'+$80
  470.                 DC "PAPER"      ;DEFM    "PAPE"
  471.                                 ;DB    'R'+$80
  472.                 DC "FLASH"      ;DEFM    "FLAS"
  473.                                 ;DB    'H'+$80
  474.                 DC "BRIGHT"     ;DEFM    "BRIGH"
  475.                                 ;DB    'T'+$80
  476.                 DC "INVERSE"    ;DEFM    "INVERS"
  477.                                 ;DB    'E'+$80
  478.                 DC "OVER"       ;DEFM    "OVE"
  479.                                 ;DB    'R'+$80
  480.                 DC "OUT"        ;DEFM    "OU"
  481.                                 ;DB    'T'+$80
  482.                 DC "LPRINT"     ;DEFM    "LPRIN"
  483.                                 ;DB    'T'+$80
  484.                 DC "LLIST"      ;DEFM    "LLIS"
  485.                                 ;DB    'T'+$80
  486.                 DC "STOP"       ;DEFM    "STO"
  487.                                 ;DB    'P'+$80
  488.                 DC "READ"       ;DEFM    "REA"
  489.                                 ;DB    'D'+$80
  490.                 DC "DATA"       ;DEFM    "DAT"
  491.                                 ;DB    'A'+$80
  492.                 DC "RESTORE"    ;DEFM    "RESTOR"
  493.                                 ;DB    'E'+$80
  494.                 DC "NEW"        ;DEFM    "NE"
  495.                                 ;DB    'W'+$80
  496.                 DC "BORDER"     ;DEFM    "BORDE"
  497.                                 ;DB    'R'+$80
  498.                 DC "CONTINUE"   ;DEFM    "CONTINU"
  499.                                 ;DB    'E'+$80
  500.                 DC "DIM"        ;DEFM    "DI"
  501.                                 ;DB    'M'+$80
  502.                 DC "REM"        ;DEFM    "RE"
  503.                                 ;DB    'M'+$80
  504.                 DC "FOR"        ;DEFM    "FO"
  505.                                 ;DB    'R'+$80
  506.                 DC "GO TO"      ;DEFM    "GO T"
  507.                                 ;DB    'O'+$80
  508.                 DC "GO SUB"     ;DEFM    "GO SU"
  509.                                 ;DB    'B'+$80
  510.                 DC "INPUT"      ;DEFM    "INPU"
  511.                                 ;DB    'T'+$80
  512.                 DC "LOAD"       ;DEFM    "LOA"
  513.                                 ;DB    'D'+$80
  514.                 DC "LIST"       ;DEFM    "LIS"
  515.                                 ;DB    'T'+$80
  516.                 DC "LET"        ;DEFM    "LE"
  517.                                 ;DB    'T'+$80
  518.                 DC "PAUSE"      ;DEFM    "PAUS"
  519.                                 ;DB    'E'+$80
  520.                 DC "NEXT"       ;DEFM    "NEX"
  521.                                 ;DB    'T'+$80
  522.                 DC "POKE"       ;DEFM    "POK"
  523.                                 ;DB    'E'+$80
  524.                 DC "PRINT"      ;DEFM    "PRIN"
  525.                                 ;DB    'T'+$80
  526.                 DC "PLOT"       ;DEFM    "PLO"
  527.                                 ;DB    'T'+$80
  528.                 DC "RUN"        ;DEFM    "RU"
  529.                                 ;DB    'N'+$80
  530.                 DC "SAVE"       ;DEFM    "SAV"
  531.                                 ;DB    'E'+$80
  532.                 DC "RANDOMIZE"  ;DEFM    "RANDOMIZ"
  533.                                 ;DB    'E'+$80
  534.                 DC "IF"         ;DB    'I','F'+$80
  535.                 DC "CLS"        ;DEFM    "CL"
  536.                                 ;DB    'S'+$80
  537.                 DC "DRAW"       ;DEFM    "DRA"
  538.                                 ;DB    'W'+$80
  539.                 DC "CLEAR"      ;DEFM    "CLEA"
  540.                                 ;DB    'R'+$80
  541.                 DC "RETURN"     ;DEFM    "RETUR"
  542.                                 ;DB    'N'+$80
  543.                 DC "COPY"       ;DEFM    "COP"
  544.                                 ;DB    'Y'+$80
  545.  
  546. ; ----------------
  547. ; THE 'KEY' TABLES
  548. ; ----------------
  549. ; These six look-up tables are used by the keyboard reading routine
  550. ; to decode the key values.
  551.  
  552. ; The first table contains the maps for the 39 keys of the standard
  553. ; 40-key Spectrum keyboard. The remaining key [SHIFT $27] is read directly.
  554. ; The keys consist of the 26 upper-case alphabetic characters, the 10 digit
  555. ; keys and the space, ENTER and symbol shift key.
  556. ; Unshifted alphabetic keys have $20 added to the value.
  557. ; The keywords for the main alphabetic keys are obtained by adding $A5 to
  558. ; the values obtained from this table.
  559.  
  560. ;; MAIN-KEYS
  561. L0205:  DB    $42             ; B
  562.         DB    $48             ; H
  563.         DB    $59             ; Y
  564.         DB    $36             ; 6
  565.         DB    $35             ; 5
  566.         DB    $54             ; T
  567.         DB    $47             ; G
  568.         DB    $56             ; V
  569.         DB    $4E             ; N
  570.         DB    $4A             ; J
  571.         DB    $55             ; U
  572.         DB    $37             ; 7
  573.         DB    $34             ; 4
  574.         DB    $52             ; R
  575.         DB    $46             ; F
  576.         DB    $43             ; C
  577.         DB    $4D             ; M
  578.         DB    $4B             ; K
  579.         DB    $49             ; I
  580.         DB    $38             ; 8
  581.         DB    $33             ; 3
  582.         DB    $45             ; E
  583.         DB    $44             ; D
  584.         DB    $58             ; X
  585.         DB    $0E             ; SYMBOL SHIFT
  586.         DB    $4C             ; L
  587.         DB    $4F             ; O
  588.         DB    $39             ; 9
  589.         DB    $32             ; 2
  590.         DB    $57             ; W
  591.         DB    $53             ; S
  592.         DB    $5A             ; Z
  593.         DB    $20             ; SPACE
  594.         DB    $0D             ; ENTER
  595.         DB    $50             ; P
  596.         DB    $30             ; 0
  597.         DB    $31             ; 1
  598.         DB    $51             ; Q
  599.         DB    $41             ; A
  600.  
  601.  
  602. ;; E-UNSHIFT
  603. ;  The 26 unshifted extended mode keys for the alphabetic characters.
  604. ;  The green keywords on the original keyboard.
  605. L022C:  DB    $E3             ; READ
  606.         DB    $C4             ; BIN
  607.         DB    $E0             ; LPRINT
  608.         DB    $E4             ; DATA
  609.         DB    $B4             ; TAN
  610.         DB    $BC             ; SGN
  611.         DB    $BD             ; ABS
  612.         DB    $BB             ; SQR
  613.         DB    $AF             ; CODE
  614.         DB    $B0             ; VAL
  615.         DB    $B1             ; LEN
  616.         DB    $C0             ; USR
  617.         DB    $A7             ; PI
  618.         DB    $A6             ; INKEY$
  619.         DB    $BE             ; PEEK
  620.         DB    $AD             ; TAB
  621.         DB    $B2             ; SIN
  622.         DB    $BA             ; INT
  623.         DB    $E5             ; RESTORE
  624.         DB    $A5             ; RND
  625.         DB    $C2             ; CHR$
  626.         DB    $E1             ; LLIST
  627.         DB    $B3             ; COS
  628.         DB    $B9             ; EXP
  629.         DB    $C1             ; STR$
  630.         DB    $B8             ; LN
  631.  
  632.  
  633. ;; EXT-SHIFT
  634. ;  The 26 shifted extended mode keys for the alphabetic characters.
  635. ;  The red keywords below keys on the original keyboard.
  636. L0246:  DB    $7E             ; ~
  637.         DB    $DC             ; BRIGHT
  638.         DB    $DA             ; PAPER
  639.         DB    $5C             ;
  640.         DB    $B7             ; ATN
  641.         DB    $7B             ; {
  642.         DB    $7D             ; }
  643.         DB    $D8             ; CIRCLE
  644.         DB    $BF             ; IN
  645.         DB    $AE             ; VAL$
  646.         DB    $AA             ; SCREEN$
  647.         DB    $AB             ; ATTR
  648.         DB    $DD             ; INVERSE
  649.         DB    $DE             ; OVER
  650.         DB    $DF             ; OUT
  651.         DB    $7F             ; (Copyright character)
  652.         DB    $B5             ; ASN
  653.         DB    $D6             ; VERIFY
  654.         DB    $7C             ; |
  655.         DB    $D5             ; MERGE
  656.         DB    $5D             ; ]
  657.         DB    $DB             ; FLASH
  658.         DB    $B6             ; ACS
  659.         DB    $D9             ; INK
  660.         DB    $5B             ; [
  661.         DB    $D7             ; BEEP
  662.  
  663.  
  664. ;; CTL-CODES
  665. ;  The ten control codes assigned to the top line of digits when the shift
  666. ;  key is pressed.
  667. L0260:  DB    $0C             ; DELETE
  668.         DB    $07             ; EDIT
  669.         DB    $06             ; CAPS LOCK
  670.         DB    $04             ; TRUE VIDEO
  671.         DB    $05             ; INVERSE VIDEO
  672.         DB    $08             ; CURSOR LEFT
  673.         DB    $0A             ; CURSOR DOWN
  674.         DB    $0B             ; CURSOR UP
  675.         DB    $09             ; CURSOR RIGHT
  676.         DB    $0F             ; GRAPHICS
  677.  
  678.  
  679. ;; SYM-CODES
  680. ;  The 26 red symbols assigned to the alphabetic characters of the keyboard.
  681. ;  The ten single-character digit symbols are converted without the aid of
  682. ;  a table using subtraction and minor manipulation.
  683. L026A:  DB    $E2             ; STOP
  684.         DB    $2A             ; *
  685.         DB    $3F             ; ?
  686.         DB    $CD             ; STEP
  687.         DB    $C8             ; >=
  688.         DB    $CC             ; TO
  689.         DB    $CB             ; THEN
  690.         DB    $5E             ; ^
  691.         DB    $AC             ; AT
  692.         DB    $2D             ; -
  693.         DB    $2B             ; +
  694.         DB    $3D             ; =
  695.         DB    $2E             ; .
  696.         DB    $2C             ; ,
  697.         DB    $3B             ; ;
  698.         DB    $22             ; "
  699.         DB    $C7             ; <=
  700.         DB    $3C             ; <
  701.         DB    $C3             ; NOT
  702.         DB    $3E             ; >
  703.         DB    $C5             ; OR
  704.         DB    $2F             ; /
  705.         DB    $C9             ; <>
  706.         DB    $60             ; pound
  707.         DB    $C6             ; AND
  708.         DB    $3A             ; :
  709.  
  710. ;; E-DIGITS
  711. ;  The ten keywords assigned to the digits in extended mode.
  712. ;  The remaining red keywords below the keys.
  713. L0284:  DB    $D0             ; FORMAT
  714.         DB    $CE             ; DEF FN
  715.         DB    $A8             ; FN
  716.         DB    $CA             ; LINE
  717.         DB    $D3             ; OPEN#
  718.         DB    $D4             ; CLOSE#
  719.         DB    $D1             ; MOVE
  720.         DB    $D2             ; ERASE
  721.         DB    $A9             ; POINT
  722.         DB    $CF             ; CAT
  723.  
  724.  
  725. ;*******************************
  726. ;** Part 2. KEYBOARD ROUTINES **
  727. ;*******************************
  728.  
  729. ; Using shift keys and a combination of modes the Spectrum 40-key keyboard
  730. ; can be mapped to 256 input characters
  731.  
  732. ; ---------------------------------------------------------------------------
  733. ;
  734. ;         0     1     2     3     4 -Bits-  4     3     2     1     0
  735. ; PORT                                                                    PORT
  736. ;
  737. ; F7FE  [ 1 ] [ 2 ] [ 3 ] [ 4 ] [ 5 ]  |  [ 6 ] [ 7 ] [ 8 ] [ 9 ] [ 0 ]   EFFE
  738. ;  ^                                   |                                   v
  739. ; FBFE  [ Q ] [ W ] [ E ] [ R ] [ T ]  |  [ Y ] [ U ] [ I ] [ O ] [ P ]   DFFE
  740. ;  ^                                   |                                   v
  741. ; FDFE  [ A ] [ S ] [ D ] [ F ] [ G ]  |  [ H ] [ J ] [ K ] [ L ] [ ENT ] BFFE
  742. ;  ^                                   |                                   v
  743. ; FEFE  [SHI] [ Z ] [ X ] [ C ] [ V ]  |  [ B ] [ N ] [ M ] [sym] [ SPC ] 7FFE
  744. ;  ^     $27                                                 $18           v
  745. ; Start                                                                   End
  746. ;        00100111                                            00011000
  747. ;
  748. ; ---------------------------------------------------------------------------
  749. ; The above map may help in reading.
  750. ; The neat arrangement of ports means that the B register need only be
  751. ; rotated left to work up the left hand side and then down the right
  752. ; hand side of the keyboard. When the reset bit drops into the carry
  753. ; then all 8 half-rows have been read. Shift is the first key to be
  754. ; read. The lower six bits of the shifts are unambiguous.
  755.  
  756. ; -------------------------------
  757. ; THE 'KEYBOARD SCANNING' ROUTINE
  758. ; -------------------------------
  759. ; from keyboard and s-inkey$
  760. ; returns 1 or 2 keys in DE, most significant shift first if any
  761. ; key values 0-39 else 255
  762.  
  763. ;; KEY-SCAN
  764. L028E:  LD      L,$2F           ; initial key value
  765.                                 ; valid values are obtained by subtracting
  766.                                 ; eight five times.
  767.         LD      DE,$FFFF        ; a buffer to receive 2 keys.
  768.  
  769.         LD      BC,$FEFE        ; the commencing port address
  770.                                 ; B holds 11111110 initially and is also
  771.                                 ; used to count the 8 half-rows
  772. ;; KEY-LINE
  773. L0296:  IN      A,(C)           ; read the port to A - bits will be reset
  774.                                 ; if a key is pressed else set.
  775.         CPL                     ; complement - pressed key-bits are now set
  776.         AND     $1F             ; apply 00011111 mask to pick up the
  777.                                 ; relevant set bits.
  778.  
  779.         JR      Z,L02AB         ; forward to KEY-DONE if zero and therefore
  780.                                 ; no keys pressed in row at all.
  781.  
  782.         LD      H,A             ; transfer row bits to H
  783.         LD      A,L             ; load the initial key value to A
  784.  
  785. ;; KEY-3KEYS
  786. L029F:  INC     D               ; now test the key buffer
  787.         RET     NZ              ; if we have collected 2 keys already
  788.                                 ; then too many so quit.
  789.  
  790. ;; KEY-BITS
  791. L02A1:  SUB     $08             ; subtract 8 from the key value
  792.                                 ; cycling through key values (top = $27)
  793.                                 ; e.g. 2F>   27>1F>17>0F>07
  794.                                 ;      2E>   26>1E>16>0E>06
  795.         SRL     H               ; shift key bits right into carry.
  796.         JR      NC,L02A1        ; back to KEY-BITS if not pressed
  797.                                 ; but if pressed we have a value (0-39d)
  798.  
  799.         LD      D,E             ; transfer a possible previous key to D
  800.         LD      E,A             ; transfer the new key to E
  801.         JR      NZ,L029F        ; back to KEY-3KEYS if there were more
  802.                                 ; set bits - H was not yet zero.
  803.  
  804. ;; KEY-DONE
  805. L02AB:  DEC     L               ; cycles 2F>2E>2D>2C>2B>2A>29>28 for
  806.                                 ; each half-row.
  807.         RLC     B               ; form next port address e.g. FEFE > FDFE
  808.         JR      C,L0296         ; back to KEY-LINE if still more rows to do.
  809.  
  810.         LD      A,D             ; now test if D is still FF ?
  811.         INC     A               ; if it is zero we have at most 1 key
  812.                                 ; range now $01-$28  (1-40d)
  813.         RET     Z               ; return if one key or no key.
  814.  
  815.         CP      $28             ; is it capsshift (was $27) ?
  816.         RET     Z               ; return if so.
  817.  
  818.         CP      $19             ; is it symbol shift (was $18) ?
  819.         RET     Z               ; return also
  820.  
  821.         LD      A,E             ; now test E
  822.         LD      E,D             ; but first switch
  823.         LD      D,A             ; the two keys.
  824.         CP      $18             ; is it symbol shift ?
  825.         RET                     ; return (with zero set if it was).
  826.                                 ; but with symbol shift now in D
  827.  
  828. ; ------------------------------
  829. ; Scan keyboard and decode value
  830. ; ------------------------------
  831. ; from interrupt 50 times a second
  832. ;
  833.  
  834. ;; KEYBOARD
  835. L02BF:  CALL    L028E           ; routine KEY-SCAN
  836.         RET     NZ              ; return if invalid combinations
  837.  
  838. ; then decrease the counters within the two key-state maps
  839. ; as this could cause one to become free.
  840. ; if the keyboard has not been pressed during the last five interrupts
  841. ; then both sets will be free.
  842.  
  843.  
  844.         LD      HL,$5C00        ; point to KSTATE-0
  845.  
  846. ;; K-ST-LOOP
  847. L02C6:  BIT     7,(HL)          ; is it free ?  ($FF)
  848.         JR      NZ,L02D1        ; forward to K-CH-SET if so
  849.  
  850.         INC     HL              ; address 5-counter
  851.         DEC     (HL)            ; decrease counter
  852.         DEC     HL              ; step back
  853.         JR      NZ,L02D1        ; forward to K-CH-SET if not at end of count
  854.  
  855.         LD      (HL),$FF        ; else mark it free.
  856.  
  857. ;; K-CH-SET
  858. L02D1:  LD      A,L             ; store low address byte.
  859.         LD      HL,$5C04        ; point to KSTATE-4
  860.                                 ; (ld l, $04)
  861.         CP      L               ; have 2 been done ?
  862.         JR      NZ,L02C6        ; back to K-ST-LOOP to consider this 2nd set
  863.  
  864. ; now the raw key (0-38) is converted to a main key (uppercase).
  865.  
  866.         CALL    L031E           ; routine K-TEST to get main key in A
  867.         RET     NC              ; return if single shift
  868.  
  869.         LD      HL,$5C00        ; point to KSTATE-0
  870.         CP      (HL)            ; does it match ?
  871.         JR      Z,L0310         ; forward to K-REPEAT if so
  872.  
  873. ; if not consider the second key map.
  874.  
  875.         EX      DE,HL           ; save kstate-0 in de
  876.         LD      HL,$5C04        ; point to KSTATE-4
  877.         CP      (HL)            ; does it match ?
  878.         JR      Z,L0310         ; forward to K-REPEAT if so
  879.  
  880. ; having excluded a repeating key we can now consider a new key.
  881. ; the second set is always examined before the first.
  882.  
  883.         BIT     7,(HL)          ; is it free ?
  884.         JR      NZ,L02F1        ; forward to K-NEW if so.
  885.  
  886.         EX      DE,HL           ; bring back kstate-0
  887.         BIT     7,(HL)          ; is it free ?
  888.         RET     Z               ; return if not.
  889.                                 ; as we have a key but nowhere to put it yet.
  890.  
  891. ; continue or jump to here if one of the buffers was free.
  892.  
  893. ;; K-NEW
  894. L02F1:  LD      E,A             ; store key in E
  895.         LD      (HL),A          ; place in free location
  896.         INC     HL              ; advance to interrupt counter
  897.         LD      (HL),$05        ; and initialize to 5
  898.         INC     HL              ; advance to delay
  899.         LD      A,($5C09)       ; pick up system variable REPDEL
  900.         LD      (HL),A          ; and insert that for first repeat delay.
  901.         INC     HL              ; advance to last location of state map.
  902.  
  903.         LD      C,(IY+$07)      ; pick up MODE  (3 bytes)
  904.         LD      D,(IY+$01)      ; pick up FLAGS (3 bytes)
  905.         PUSH    HL              ; save state map location
  906.                                 ; Note. could now have used.
  907.                                 ; ld l,$41; ld c,(hl); ld l,$3B; ld d,(hl).
  908.                                 ; six and two threes of course.
  909.         CALL    L0333           ; routine K-DECODE
  910.         POP     HL              ; restore map pointer
  911.         LD      (HL),A          ; put decoded key in last location of map.
  912.  
  913. ;; K-END
  914. L0308:  LD      ($5C08),A       ; update LASTK system variable.
  915.         SET     5,(IY+$01)      ; update FLAGS  - signal new key.
  916.         RET                     ; done
  917.  
  918. ; ---------------------------
  919. ; THE 'REPEAT KEY' SUBROUTINE
  920. ; ---------------------------
  921. ; A possible repeat has been identified. HL addresses the raw (main) key.
  922. ; The last location holds the decoded key (from the first context).
  923.  
  924. ;; K-REPEAT
  925. L0310:  INC     HL              ; advance
  926.         LD      (HL),$05        ; maintain interrupt counter at 5
  927.         INC     HL              ; advance
  928.         DEC     (HL)            ; decrease REPDEL value.
  929.         RET     NZ              ; return if not yet zero.
  930.  
  931.         LD      A,($5C0A)       ; REPPER
  932.         LD      (HL),A          ; but for subsequent repeats REPPER will be used.
  933.         INC     HL              ; advance
  934.                                 ;
  935.         LD      A,(HL)          ; pick up the key decoded possibly in another
  936.                                 ; context.
  937.         JR      L0308           ; back to K-END
  938.  
  939. ; --------------
  940. ; Test key value
  941. ; --------------
  942. ; also called from s-inkey$
  943. ; begin by testing for a shift with no other.
  944.  
  945. ;; K-TEST
  946. L031E:  LD      B,D             ; load most significant key to B
  947.                                 ; will be $FF if not shift.
  948.         LD      D,$00           ; and reset D to index into main table
  949.         LD      A,E             ; load least significant key from E
  950.         CP      $27             ; is it higher than 39d   i.e. FF
  951.         RET     NC              ; return with just a shift (in B now)
  952.  
  953.         CP      $18             ; is it symbol shift ?
  954.         JR      NZ,L032C        ; forward to K-MAIN if not
  955.  
  956. ; but we could have just symbol shift and no other
  957.  
  958.         BIT     7,B             ; is other key $FF (ie not shift)
  959.         RET     NZ              ; return with solitary symbol shift
  960.  
  961.  
  962. ;; K-MAIN
  963. L032C:  LD      HL,L0205        ; address: MAIN-KEYS
  964.         ADD     HL,DE           ; add offset 0-38
  965.         LD      A,(HL)          ; pick up main key value
  966.         SCF                     ; set carry flag
  967.         RET                     ; return    (B has other key still)
  968.  
  969. ; -----------------
  970. ; Keyboard decoding
  971. ; -----------------
  972. ; also called from s-inkey$
  973.  
  974. ;; K-DECODE
  975. L0333:  LD      A,E             ; pick up the stored main key
  976.         CP      $3A             ; an arbitrary point between digits and letters
  977.         JR      C,L0367         ; forward to K-DIGIT with digits, space, enter.
  978.  
  979.         DEC     C               ; decrease MODE ( 0='KLC', 1='E', 2='G')
  980.  
  981.         JP      M,L034F         ; to K-KLC-LET if was zero
  982.  
  983.         JR      Z,L0341         ; to K-E-LET if was 1 for extended letters.
  984.  
  985. ; proceed with graphic codes.
  986. ; Note. should selectively drop return address if code > 'U' ($55).
  987. ; i.e. abort the KEYBOARD call.
  988. ; e.g. cp 'V'; jr c addit; pop af; ;;addit etc. (5 bytes of instruction).
  989. ; (s-inkey$ never gets into graphics mode.)
  990.  
  991. ;; addit
  992.         ADD     A,$4F           ; add offset to augment 'A' to graphics A say.
  993.         RET                     ; return.
  994.                                 ; Note. ( but [GRAPH] V gives RND, etc ).
  995.  
  996. ; ---
  997.  
  998. ; the jump was to here with extended mode with uppercase A-Z.
  999.  
  1000. ;; K-E-LET
  1001. L0341:  LD      HL,L022C-$41    ; base address of E-UNSHIFT L022c
  1002.                                 ; ( $01EB in standard ROM )
  1003.         INC     B               ; test B is it empty i.e. not a shift
  1004.         JR      Z,L034A         ; forward to K-LOOK-UP if neither shift
  1005.  
  1006.         LD      HL,L0246-$41    ; Address: $0205 L0246-$41 EXT-SHIFT base
  1007.  
  1008. ;; K-LOOK-UP
  1009. L034A:  LD      D,$00           ; prepare to index
  1010.         ADD     HL,DE           ; add the main key value
  1011.         LD      A,(HL)          ; pick up other mode value
  1012.         RET                     ; return
  1013.  
  1014. ; ---
  1015.  
  1016. ; the jump was here with mode = 0
  1017.  
  1018. ;; K-KLC-LET
  1019. L034F:  LD      HL,L026A-$41    ; prepare base of sym-codes
  1020.         BIT     0,B             ; shift=$27 sym-shift=$18
  1021.         JR      Z,L034A         ; back to K-LOOK-UP with symbol-shift
  1022.  
  1023.         BIT     3,D             ; test FLAGS is it 'K' mode (from OUT-CURS)
  1024.         JR      Z,L0364         ; skip to K-TOKENS if so
  1025.  
  1026.         BIT     3,(IY+$30)      ; test FLAGS2 - consider CAPS LOCK ?
  1027.         RET     NZ              ; return if so with main code.
  1028.  
  1029.         INC     B               ; is shift being pressed ?
  1030.                                 ; result zero if not
  1031.         RET     NZ              ; return if shift pressed.
  1032.  
  1033.         ADD     A,$20           ; else convert the code to lower case.
  1034.         RET                     ; return.
  1035.  
  1036. ; ---
  1037.  
  1038. ; the jump was here for tokens
  1039.  
  1040. ;; K-TOKENS
  1041. L0364:  ADD     A,$A5           ; add offset to main code so that 'A'
  1042.                                 ; becomes 'NEW' etc.
  1043.         RET                     ; return
  1044.  
  1045. ; ---
  1046.  
  1047. ; the jump was here with digits, space, enter and symbol shift (< $xx)
  1048.  
  1049. ;; K-DIGIT
  1050. L0367:  CP      $30             ; is it '0' or higher ?
  1051.         RET     C               ; return with space, enter and symbol-shift
  1052.  
  1053.         DEC     C               ; test MODE (was 0='KLC', 1='E', 2='G')
  1054.         JP      M,L039D         ; jump to K-KLC-DGT if was 0.
  1055.  
  1056.         JR      NZ,L0389        ; forward to K-GRA-DGT if mode was 2.
  1057.  
  1058. ; continue with extended digits 0-9.
  1059.  
  1060.         LD      HL,L0284-$30    ; $0254 - base of E-DIGITS
  1061.         BIT     5,B             ; test - shift=$27 sym-shift=$18
  1062.         JR      Z,L034A         ; to K-LOOK-UP if sym-shift
  1063.  
  1064.         CP      $38             ; is character '8' ?
  1065.         JR      NC,L0382        ; to K-8-&-9 if greater than '7'
  1066.  
  1067.         SUB     $20             ; reduce to ink range $10-$17
  1068.         INC     B               ; shift ?
  1069.         RET     Z               ; return if not.
  1070.  
  1071.         ADD     A,$08           ; add 8 to give paper range $18 - $1F
  1072.         RET                     ; return
  1073.  
  1074. ; ---
  1075.  
  1076. ; 89
  1077.  
  1078. ;; K-8-&-9
  1079. L0382:  SUB     $36             ; reduce to 02 and 03  bright codes
  1080.         INC     B               ; test if shift pressed.
  1081.         RET     Z               ; return if not.
  1082.  
  1083.         ADD     A,$FE           ; subtract 2 setting carry
  1084.         RET                     ; to give 0 and 1    flash codes.
  1085.  
  1086. ; ---
  1087.  
  1088. ;  graphics mode with digits
  1089.  
  1090. ;; K-GRA-DGT
  1091. L0389:  LD      HL,L0260-$30    ; $0230 base address of CTL-CODES
  1092.  
  1093.         CP      $39             ; is key '9' ?
  1094.         JR      Z,L034A         ; back to K-LOOK-UP - changed to $0F, GRAPHICS.
  1095.  
  1096.         CP      $30             ; is key '0' ?
  1097.         JR      Z,L034A         ; back to K-LOOK-UP - changed to $0C, delete.
  1098.  
  1099. ; for keys '0' - '7' we assign a mosaic character depending on shift.
  1100.  
  1101.         AND     $07             ; convert character to number. 0 - 7.
  1102.         ADD     A,$80           ; add offset - they start at $80
  1103.  
  1104.         INC     B               ; destructively test for shift
  1105.         RET     Z               ; and return if not pressed.
  1106.  
  1107.         XOR     $0F             ; toggle bits becomes range $88-$8F
  1108.         RET                     ; return.
  1109.  
  1110. ; ---
  1111.  
  1112. ; now digits in 'KLC' mode
  1113.  
  1114. ;; K-KLC-DGT
  1115. L039D:  INC     B               ; return with digit codes if neither
  1116.         RET     Z               ; shift key pressed.
  1117.  
  1118.         BIT     5,B             ; test for caps shift.
  1119.  
  1120.         LD      HL,L0260-$30    ; prepare base of table CTL-CODES.
  1121.         JR      NZ,L034A        ; back to K-LOOK-UP if shift pressed.
  1122.  
  1123. ; must have been symbol shift
  1124.  
  1125.         SUB     $10             ; for ASCII most will now be correct
  1126.                                 ; on a standard typewriter.
  1127.         CP      $22             ; but '@' is not - see below.
  1128.         JR      Z,L03B2         ; forward to to K-@-CHAR if so
  1129.  
  1130.         CP      $20             ; '_' is the other one that fails
  1131.         RET     NZ              ; return if not.
  1132.  
  1133.         LD      A,$5F           ; substitute ASCII '_'
  1134.         RET                     ; return.
  1135.  
  1136. ; ---
  1137.  
  1138. ;; K-@-CHAR
  1139. L03B2:  LD      A,$40           ; substitute ASCII '@'
  1140.         RET                     ; return.
  1141.  
  1142.  
  1143. ; ------------------------------------------------------------------------
  1144. ; The Spectrum Input character keys. One or two are abbreviated.
  1145. ; From $00 Flash 0 to $FF COPY. The routine above has decoded all these.
  1146.  
  1147. ;  | 00 Fl0| 01 Fl1| 02 Br0| 03 Br1| 04 In0| 05 In1| 06 CAP| 07 EDT|
  1148. ;  | 08 LFT| 09 RIG| 0A DWN| 0B UP | 0C DEL| 0D ENT| 0E SYM| 0F GRA|
  1149. ;  | 10 Ik0| 11 Ik1| 12 Ik2| 13 Ik3| 14 Ik4| 15 Ik5| 16 Ik6| 17 Ik7|
  1150. ;  | 18 Pa0| 19 Pa1| 1A Pa2| 1B Pa3| 1C Pa4| 1D Pa5| 1E Pa6| 1F Pa7|
  1151. ;  | 20 SP | 21  ! | 22  " | 23  # | 24  $ | 25  % | 26  & | 27  ' |
  1152. ;  | 28  ( | 29  ) | 2A  * | 2B  + | 2C  , | 2D  - | 2E  . | 2F  / |
  1153. ;  | 30  0 | 31  1 | 32  2 | 33  3 | 34  4 | 35  5 | 36  6 | 37  7 |
  1154. ;  | 38  8 | 39  9 | 3A  : | 3B  ; | 3C  < | 3D  = | 3E  > | 3F  ? |
  1155. ;  | 40  @ | 41  A | 42  B | 43  C | 44  D | 45  E | 46  F | 47  G |
  1156. ;  | 48  H | 49  I | 4A  J | 4B  K | 4C  L | 4D  M | 4E  N | 4F  O |
  1157. ;  | 50  P | 51  Q | 52  R | 53  S | 54  T | 55  U | 56  V | 57  W |
  1158. ;  | 58  X | 59  Y | 5A  Z | 5B  [ | 5C  \ | 5D  ] | 5E  ^ | 5F  _ |
  1159. ;  | 60 ukp| 61  a | 62  b | 63  c | 64  d | 65  e | 66  f | 67  g |
  1160. ;  | 68  h | 69  i | 6A  j | 6B  k | 6C  l | 6D  m | 6E  n | 6F  o |
  1161. ;  | 70  p | 71  q | 72  r | 73  s | 74  t | 75  u | 76  v | 77  w |
  1162. ;  | 78  x | 79  y | 7A  z | 7B  { | 7C  | | 7D  } | 7E  ~ | 7F (c)|
  1163. ;  | 80 128| 81 129| 82 130| 83 131| 84 132| 85 133| 86 134| 87 135|
  1164. ;  | 88 136| 89 137| 8A 138| 8B 139| 8C 140| 8D 141| 8E 142| 8F 143|
  1165. ;  | 90 [A]| 91 [B]| 92 [C]| 93 [D]| 94 [E]| 95 [F]| 96 [G]| 97 [H]|
  1166. ;  | 98 [I]| 99 [J]| 9A [K]| 9B [L]| 9C [M]| 9D [N]| 9E [O]| 9F [P]|
  1167. ;  | A0 [Q]| A1 [R]| A2 [S]| A3 [T]| A4 [U]| A5 RND| A6 IK$| A7 PI |
  1168. ;  | A8 FN | A9 PNT| AA SC$| AB ATT| AC AT | AD TAB| AE VL$| AF COD|
  1169. ;  | B0 VAL| B1 LEN| B2 SIN| B3 COS| B4 TAN| B5 ASN| B6 ACS| B7 ATN|
  1170. ;  | B8 LN | B9 EXP| BA INT| BB SQR| BC SGN| BD ABS| BE PEK| BF IN |
  1171. ;  | C0 USR| C1 ST$| C2 CH$| C3 NOT| C4 BIN| C5 OR | C6 AND| C7 <= |
  1172. ;  | C8 >= | C9 <> | CA LIN| CB THN| CC TO | CD STP| CE DEF| CF CAT|
  1173. ;  | D0 FMT| D1 MOV| D2 ERS| D3 OPN| D4 CLO| D5 MRG| D6 VFY| D7 BEP|
  1174. ;  | D8 CIR| D9 INK| DA PAP| DB FLA| DC BRI| DD INV| DE OVR| DF OUT|
  1175. ;  | E0 LPR| E1 LLI| E2 STP| E3 REA| E4 DAT| E5 RES| E6 NEW| E7 BDR|
  1176. ;  | E8 CON| E9 DIM| EA REM| EB FOR| EC GTO| ED GSB| EE INP| EF LOA|
  1177. ;  | F0 LIS| F1 LET| F2 PAU| F3 NXT| F4 POK| F5 PRI| F6 PLO| F7 RUN|
  1178. ;  | F8 SAV| F9 RAN| FA IF | FB CLS| FC DRW| FD CLR| FE RET| FF CPY|
  1179.  
  1180. ; Note that for simplicity, Sinclair have located all the control codes
  1181. ; below the space character.
  1182. ; ASCII DEL, $7F, has been made a copyright symbol.
  1183. ; Also $60, '`', not used in BASIC but used in other languages, has been
  1184. ; allocated the local currency symbol for the relevant country -
  1185. ; ukp in most Spectrums.
  1186.  
  1187. ; ------------------------------------------------------------------------
  1188.  
  1189. ;**********************************
  1190. ;** Part 3. LOUDSPEAKER ROUTINES **
  1191. ;**********************************
  1192.  
  1193.  
  1194. ; Documented by Alvin Albrecht.
  1195.  
  1196.  
  1197. ; ------------------------------
  1198. ; Routine to control loudspeaker
  1199. ; ------------------------------
  1200. ; Outputs a square wave of given duration and frequency
  1201. ; to the loudspeaker.
  1202. ;   Enter with: DE = #cycles - 1
  1203. ;               HL = tone period as described next
  1204. ;
  1205. ; The tone period is measured in T states and consists of
  1206. ; three parts: a coarse part (H register), a medium part
  1207. ; (bits 7..2 of L) and a fine part (bits 1..0 of L) which
  1208. ; contribute to the waveform timing as follows:
  1209. ;
  1210. ;                          coarse    medium       fine
  1211. ; duration of low  = 118 + 1024*H + 16*(L>>2) + 4*(L&0x3)
  1212. ; duration of hi   = 118 + 1024*H + 16*(L>>2) + 4*(L&0x3)
  1213. ; Tp = tone period = 236 + 2048*H + 32*(L>>2) + 8*(L&0x3)
  1214. ;                  = 236 + 2048*H + 8*L = 236 + 8*HL
  1215. ;
  1216. ; As an example, to output five seconds of middle C (261.624 Hz):
  1217. ;   (a) Tone period = 1/261.624 = 3.822ms
  1218. ;   (b) Tone period in T-States = 3.822ms*fCPU = 13378
  1219. ;         where fCPU = clock frequency of the CPU = 3.5MHz
  1220. ;   (c) Find H and L for desired tone period:
  1221. ;         HL = (Tp - 236) / 8 = (13378 - 236) / 8 = 1643 = 0x066B
  1222. ;   (d) Tone duration in cycles = 5s/3.822ms = 1308 cycles
  1223. ;         DE = 1308 - 1 = 0x051B
  1224. ;
  1225. ; The resulting waveform has a duty ratio of exactly 50%.
  1226. ;
  1227. ;
  1228. ;; BEEPER
  1229. L03B5:  DI                      ; Disable Interrupts so they don't disturb timing
  1230.         LD      A,L             ;
  1231.         SRL     L               ;
  1232.         SRL     L               ; L = medium part of tone period
  1233.         CPL                     ;
  1234.         AND     $03             ; A = 3 - fine part of tone period
  1235.         LD      C,A             ;
  1236.         LD      B,$00           ;
  1237.         LD      IX,L03D1        ; Address: BE-IX+3
  1238.         ADD     IX,BC           ;   IX holds address of entry into the loop
  1239.                                 ;   the loop will contain 0-3 NOPs, implementing
  1240.                                 ;   the fine part of the tone period.
  1241.         LD      A,($5C48)       ; BORDCR
  1242.         AND     $38             ; bits 5..3 contain border colour
  1243.         RRCA                    ; border colour bits moved to 2..0
  1244.         RRCA                    ;   to match border bits on port #FE
  1245.         RRCA                    ;
  1246.         OR       $08            ; bit 3 set (tape output bit on port #FE)
  1247.                                 ;   for loud sound output
  1248. ;; BE-IX+3
  1249. L03D1:  NOP              ;(4)   ; optionally executed NOPs for small
  1250.                                 ;   adjustments to tone period
  1251. ;; BE-IX+2
  1252. L03D2:  NOP              ;(4)   ;
  1253.  
  1254. ;; BE-IX+1
  1255. L03D3:  NOP              ;(4)   ;
  1256.  
  1257. ;; BE-IX+0
  1258. L03D4:  INC     B        ;(4)   ;
  1259.         INC     C        ;(4)   ;
  1260.  
  1261. ;; BE-H&L-LP
  1262. L03D6:  DEC     C        ;(4)   ; timing loop for duration of
  1263.         JR      NZ,L03D6 ;(12/7);   high or low pulse of waveform
  1264.  
  1265.         LD      C,$3F    ;(7)   ;
  1266.         DEC     B        ;(4)   ;
  1267.         JP      NZ,L03D6 ;(10)  ; to BE-H&L-LP
  1268.  
  1269.         XOR     $10      ;(7)   ; toggle output beep bit
  1270.         OUT     ($FE),A  ;(11)  ; output pulse
  1271.         LD      B,H      ;(4)   ; B = coarse part of tone period
  1272.         LD      C,A      ;(4)   ; save port #FE output byte
  1273.         BIT     4,A      ;(8)   ; if new output bit is high, go
  1274.         JR      NZ,L03F2 ;(12/7);   to BE-AGAIN
  1275.  
  1276.         LD      A,D      ;(4)   ; one cycle of waveform has completed
  1277.         OR      E        ;(4)   ;   (low->low). if cycle countdown = 0
  1278.         JR      Z,L03F6  ;(12/7);   go to BE-END
  1279.  
  1280.         LD      A,C      ;(4)   ; restore output byte for port #FE
  1281.         LD      C,L      ;(4)   ; C = medium part of tone period
  1282.         DEC     DE       ;(6)   ; decrement cycle count
  1283.         JP      (IX)     ;(8)   ; do another cycle
  1284.  
  1285. ;; BE-AGAIN                     ; halfway through cycle
  1286. L03F2:  LD      C,L      ;(4)   ; C = medium part of tone period
  1287.         INC     C        ;(4)   ; adds 16 cycles to make duration of high = duration of low
  1288.         JP      (IX)     ;(8)   ; do high pulse of tone
  1289.  
  1290. ;; BE-END
  1291. L03F6:  EI                      ; Enable Interrupts
  1292.         RET                     ;
  1293.  
  1294.  
  1295. ; -------------------
  1296. ; Handle BEEP command
  1297. ; -------------------
  1298. ; BASIC interface to BEEPER subroutine.
  1299. ; Invoked in BASIC with:
  1300. ;   BEEP dur, pitch
  1301. ;   where dur   = duration in seconds
  1302. ;         pitch = # of semitones above/below middle C
  1303. ;
  1304. ; Enter with: pitch on top of calculator stack
  1305. ;             duration next on calculator stack
  1306. ;
  1307. ;; beep
  1308. L03F8:  RST     28H             ;; FP-CALC
  1309.         DB    $31             ;;duplicate                  ; duplicate pitch
  1310.         DB    $27             ;;int                        ; convert to integer
  1311.         DB    $C0             ;;st-mem-0                   ; store integer pitch to memory 0
  1312.         DB    $03             ;;subtract                   ; calculate fractional part of pitch = fp_pitch - int_pitch
  1313.         DB    $34             ;;stk-data                   ; push constant
  1314.         DB    $EC             ;;Exponent: $7C, Bytes: 4    ; constant = 0.05762265
  1315.         DB    $6C,$98,$1F,$F5 ;;($6C,$98,$1F,$F5)
  1316.         DB    $04             ;;multiply                   ; compute:
  1317.         DB    $A1             ;;stk-one                    ; 1 + 0.05762265 * fraction_part(pitch)
  1318.         DB    $0F             ;;addition
  1319.         DB    $38             ;;end-calc                   ; leave on calc stack
  1320.  
  1321.         LD      HL,$5C92        ; MEM-0: number stored here is in 16 bit integer format (pitch)
  1322.                                 ;   0, 0/FF (pos/neg), LSB, MSB, 0
  1323.                                 ;   LSB/MSB is stored in two's complement
  1324.                                 ; In the following, the pitch is checked if it is in the range -128<=p<=127
  1325.         LD      A,(HL)          ; First byte must be zero, otherwise
  1326.         AND     A               ;   error in integer conversion
  1327.         JR      NZ,L046C        ; to REPORT-B
  1328.  
  1329.         INC     HL              ;
  1330.         LD      C,(HL)          ; C = pos/neg flag = 0/FF
  1331.         INC     HL              ;
  1332.         LD      B,(HL)          ; B = LSB, two's complement
  1333.         LD      A,B             ;
  1334.         RLA                     ;
  1335.         SBC     A,A             ; A = 0/FF if B is pos/neg
  1336.         CP      C               ; must be the same as C if the pitch is -128<=p<=127
  1337.         JR      NZ,L046C        ; if no, error REPORT-B
  1338.  
  1339.         INC     HL              ; if -128<=p<=127, MSB will be 0/FF if B is pos/neg
  1340.         CP      (HL)            ; verify this
  1341.         JR      NZ,L046C        ; if no, error REPORT-B
  1342.                                 ; now we know -128<=p<=127
  1343.         LD      A,B             ; A = pitch + 60
  1344.         ADD     A,$3C           ; if -60<=pitch<=67,
  1345.         JP      P,L0425         ;   goto BE-i-OK
  1346.  
  1347.         JP      PO,L046C        ; if pitch <= 67 goto REPORT-B
  1348.                                 ;   lower bound of pitch set at -60
  1349.  
  1350. ;; BE-I-OK                      ; here, -60<=pitch<=127
  1351.                                 ; and A=pitch+60 -> 0<=A<=187
  1352.  
  1353. L0425:  LD      B,$FA           ; 6 octaves below middle C
  1354.  
  1355. ;; BE-OCTAVE                    ; A=# semitones above 5 octaves below middle C
  1356. L0427:  INC     B               ; increment octave
  1357.         SUB     $0C             ; 12 semitones = one octave
  1358.         JR      NC,L0427        ; to BE-OCTAVE
  1359.  
  1360.         ADD     A,$0C           ; A = # semitones above C (0-11)
  1361.         PUSH    BC              ; B = octave displacement from middle C, 2's complement: -5<=B<=10
  1362.         LD      HL,L046E        ; Address: semi-tone
  1363.         CALL    L3406           ; routine LOC-MEM
  1364.                                 ;   HL = 5*A + $046E
  1365.         CALL    L33B4           ; routine STACK-NUM
  1366.                                 ;   read FP value (freq) from semitone table (HL) and push onto calc stack
  1367.  
  1368.         RST     28H             ;; FP-CALC
  1369.         DB    $04             ;;multiply   mult freq by 1 + 0.0576 * fraction_part(pitch) stacked earlier
  1370.                                 ;;             thus taking into account fractional part of pitch.
  1371.                                 ;;           the number 0.0576*frequency is the distance in Hz to the next
  1372.                                 ;;             note (verify with the frequencies recorded in the semitone
  1373.                                 ;;             table below) so that the fraction_part of the pitch does
  1374.                                 ;;             indeed represent a fractional distance to the next note.
  1375.         DB    $38             ;;end-calc   HL points to first byte of fp num on stack = middle frequency to generate
  1376.  
  1377.         POP     AF              ; A = octave displacement from middle C, 2's complement: -5<=A<=10
  1378.         ADD     A,(HL)          ; increase exponent by A (equivalent to multiplying by 2^A)
  1379.         LD      (HL),A          ;
  1380.  
  1381.         RST     28H             ;; FP-CALC
  1382.         DB    $C0             ;;st-mem-0          ; store frequency in memory 0
  1383.         DB    $02             ;;delete            ; remove from calc stack
  1384.         DB    $31             ;;duplicate         ; duplicate duration (seconds)
  1385.         DB    $38             ;;end-calc
  1386.  
  1387.         CALL    L1E94           ; routine FIND-INT1 ; FP duration to A
  1388.         CP      $0B             ; if dur > 10 seconds,
  1389.         JR      NC,L046C        ;   goto REPORT-B
  1390.  
  1391.         ;;; The following calculation finds the tone period for HL and the cycle count
  1392.         ;;; for DE expected in the BEEPER subroutine.  From the example in the BEEPER comments,
  1393.         ;;;
  1394.         ;;; HL = ((fCPU / f) - 236) / 8 = fCPU/8/f - 236/8 = 437500/f -29.5
  1395.         ;;; DE = duration * frequency - 1
  1396.         ;;;
  1397.         ;;; Note the different constant (30.125) used in the calculation of HL
  1398.         ;;; below.  This is probably an error.
  1399.  
  1400.         RST     28H             ;; FP-CALC
  1401.         DB    $E0             ;;get-mem-0                 ; push frequency
  1402.         DB    $04             ;;multiply                  ; result1: #cycles = duration * frequency
  1403.         DB    $E0             ;;get-mem-0                 ; push frequency
  1404.         DB    $34             ;;stk-data                  ; push constant
  1405.         DB    $80             ;;Exponent $93, Bytes: 3    ; constant = 437500
  1406.         DB    $43,$55,$9F,$80 ;;($55,$9F,$80,$00)
  1407.         DB    $01             ;;exchange                  ; frequency on top
  1408.         DB    $05             ;;division                  ; 437500 / frequency
  1409.         DB    $34             ;;stk-data                  ; push constant
  1410.         DB    $35             ;;Exponent: $85, Bytes: 1   ; constant = 30.125
  1411.         DB    $71             ;;($71,$00,$00,$00)
  1412.         DB    $03             ;;subtract                  ; result2: tone_period(HL) = 437500 / freq - 30.125
  1413.         DB    $38             ;;end-calc
  1414.  
  1415.         CALL    L1E99           ; routine FIND-INT2
  1416.         PUSH    BC              ;   BC = tone_period(HL)
  1417.         CALL    L1E99           ; routine FIND-INT2, BC = #cycles to generate
  1418.         POP     HL              ; HL = tone period
  1419.         LD      D,B             ;
  1420.         LD      E,C             ; DE = #cycles
  1421.         LD      A,D             ;
  1422.         OR      E               ;
  1423.         RET     Z               ; if duration = 0, skip BEEP and avoid 65536 cycle
  1424.                                 ;   boondoggle that would occur next
  1425.         DEC     DE              ; DE = #cycles - 1
  1426.         JP      L03B5           ; to BEEPER
  1427.  
  1428. ; ---
  1429.  
  1430.  
  1431. ;; REPORT-B
  1432. L046C:  RST     08H             ; ERROR-1
  1433.         DB    $0A             ; Error Report: Integer out of range
  1434.  
  1435.  
  1436.  
  1437. ; ---------------
  1438. ; Semi-tone table
  1439. ; ---------------
  1440. ;
  1441. ; Holds frequencies corresponding to semitones in middle octave.
  1442. ; To move n octaves higher or lower, frequencies are multiplied by 2^n.
  1443.  
  1444. ;; semi-tone         five byte fp         decimal freq     note (middle)
  1445. L046E:  DB    $89, $02, $D0, $12, $86;  261.625565290         C
  1446.         DB    $89, $0A, $97, $60, $75;  277.182631135         C#
  1447.         DB    $89, $12, $D5, $17, $1F;  293.664768100         D
  1448.         DB    $89, $1B, $90, $41, $02;  311.126983881         D#
  1449.         DB    $89, $24, $D0, $53, $CA;  329.627557039         E
  1450.         DB    $89, $2E, $9D, $36, $B1;  349.228231549         F
  1451.         DB    $89, $38, $FF, $49, $3E;  369.994422674         F#
  1452.         DB    $89, $43, $FF, $6A, $73;  391.995436072         G
  1453.         DB    $89, $4F, $A7, $00, $54;  415.304697513         G#
  1454.         DB    $89, $5C, $00, $00, $00;  440.000000000         A
  1455.         DB    $89, $69, $14, $F6, $24;  466.163761616         A#
  1456.         DB    $89, $76, $F1, $10, $05;  493.883301378         B
  1457.  
  1458.  
  1459. ;****************************************
  1460. ;** Part 4. CASSETTE HANDLING ROUTINES **
  1461. ;****************************************
  1462.  
  1463. ; These routines begin with the service routines followed by a single
  1464. ; command entry point.
  1465. ; The first of these service routines is a curiosity.
  1466.  
  1467. ; -----------------------
  1468. ; THE 'ZX81 NAME' ROUTINE
  1469. ; -----------------------
  1470. ;   This routine fetches a filename in ZX81 format and is not used by the
  1471. ;   cassette handling routines in this ROM.
  1472.  
  1473. ;; zx81-name
  1474. L04AA:  CALL    L24FB           ; routine SCANNING to evaluate expression.
  1475.         LD      A,($5C3B)       ; fetch system variable FLAGS.
  1476.         ADD     A,A             ; test bit 7 - syntax, bit 6 - result type.
  1477.         JP      M,L1C8A         ; to REPORT-C if not string result
  1478.                                 ; 'Nonsense in BASIC'.
  1479.  
  1480.         POP     HL              ; drop return address.
  1481.         RET     NC              ; return early if checking syntax.
  1482.  
  1483.         PUSH    HL              ; re-save return address.
  1484.         CALL    L2BF1           ; routine STK-FETCH fetches string parameters.
  1485.         LD      H,D             ; transfer start of filename
  1486.         LD      L,E             ; to the HL register.
  1487.         DEC     C               ; adjust to point to last character and
  1488.         RET     M               ; return if the null string.
  1489.                                 ; or multiple of 256!
  1490.  
  1491.         ADD     HL,BC           ; find last character of the filename.
  1492.                                 ; and also clear carry.
  1493.         SET     7,(HL)          ; invert it.
  1494.         RET                     ; return.
  1495.  
  1496. ; =========================================
  1497. ;
  1498. ; PORT 254 ($FE)
  1499. ;
  1500. ;                      spk mic { border  }  
  1501. ;          ___ ___ ___ ___ ___ ___ ___ ___
  1502. ; PORT    |   |   |   |   |   |   |   |   |
  1503. ; 254     |   |   |   |   |   |   |   |   |
  1504. ; $FE     |___|___|___|___|___|___|___|___|
  1505. ;           7   6   5   4   3   2   1   0
  1506. ;
  1507.  
  1508. ; ----------------------------------
  1509. ; Save header and program/data bytes
  1510. ; ----------------------------------
  1511. ; This routine saves a section of data. It is called from SA-CTRL to save the
  1512. ; seventeen bytes of header data. It is also the exit route from that routine
  1513. ; when it is set up to save the actual data.
  1514. ; On entry -
  1515. ; HL points to start of data.
  1516. ; IX points to descriptor.
  1517. ; The accumulator is set to  $00 for a header, $FF for data.
  1518.  
  1519. ;; SA-BYTES
  1520. L04C2:  LD      HL,L053F        ; address: SA/LD-RET
  1521.         PUSH    HL              ; is pushed as common exit route.
  1522.                                 ; however there is only one non-terminal exit
  1523.                                 ; point.
  1524.  
  1525.         LD      HL,$1F80        ; a timing constant H=$1F, L=$80
  1526.                                 ; inner and outer loop counters
  1527.                                 ; a five second lead-in is used for a header.
  1528.  
  1529.         BIT     7,A             ; test one bit of accumulator.
  1530.                                 ; (AND A ?)
  1531.         JR      Z,L04D0         ; skip to SA-FLAG if a header is being saved.
  1532.  
  1533. ; else is data bytes and a shorter lead-in is used.
  1534.  
  1535.         LD      HL,$0C98        ; another timing value H=$0C, L=$98.
  1536.                                 ; a two second lead-in is used for the data.
  1537.  
  1538.  
  1539. ;; SA-FLAG
  1540. L04D0:  EX      AF,AF'          ; save flag
  1541.        INC     DE              ; increase length by one.
  1542.        DEC     IX              ; decrease start.
  1543.  
  1544.        DI                      ; disable interrupts
  1545.  
  1546.        LD      A,$02           ; select red for border, microphone bit on.
  1547.        LD      B,A             ; also does as an initial slight counter value.
  1548.  
  1549. ;; SA-LEADER
  1550. L04D8:  DJNZ    L04D8           ; self loop to SA-LEADER for delay.
  1551.                                ; after initial loop, count is $A4 (or $A3)
  1552.  
  1553.        OUT     ($FE),A         ; output byte $02/$0D to tape port.
  1554.  
  1555.        XOR     $0F             ; switch from RED (mic on) to CYAN (mic off).
  1556.  
  1557.        LD      B,$A4           ; hold count. also timed instruction.
  1558.  
  1559.        DEC     L               ; originally $80 or $98.
  1560.                                ; but subsequently cycles 256 times.
  1561.        JR      NZ,L04D8        ; back to SA-LEADER until L is zero.
  1562.  
  1563. ; the outer loop is counted by H
  1564.  
  1565.        DEC     B               ; decrement count
  1566.        DEC     H               ; originally  twelve or thirty-one.
  1567.        JP      P,L04D8         ; back to SA-LEADER until H becomes $FF
  1568.  
  1569. ; now send a synch pulse. At this stage mic is off and A holds value
  1570. ; for mic on.
  1571. ; A synch pulse is much shorter than the steady pulses of the lead-in.
  1572.  
  1573.        LD      B,$2F           ; another short timed delay.
  1574.  
  1575. ;; SA-SYNC-1
  1576. L04EA:  DJNZ    L04EA           ; self loop to SA-SYNC-1
  1577.  
  1578.        OUT     ($FE),A         ; switch to mic on and red.
  1579.        LD      A,$0D           ; prepare mic off - cyan
  1580.        LD      B,$37           ; another short timed delay.
  1581.  
  1582. ;; SA-SYNC-2
  1583. L04F2:  DJNZ    L04F2           ; self loop to SA-SYNC-2
  1584.  
  1585.        OUT     ($FE),A         ; output mic off, cyan border.
  1586.        LD      BC,$3B0E        ; B=$3B time(*), C=$0E, YELLOW, MIC OFF.
  1587.  
  1588. ;
  1589.  
  1590.        EX      AF,AF'          ; restore saved flag
  1591.                                 ; which is 1st byte to be saved.
  1592.  
  1593.         LD      L,A             ; and transfer to L.
  1594.                                 ; the initial parity is A, $FF or $00.
  1595.         JP      L0507           ; JUMP forward to SA-START     ->
  1596.                                 ; the mid entry point of loop.
  1597.  
  1598. ; -------------------------
  1599. ; During the save loop a parity byte is maintained in H.
  1600. ; the save loop begins by testing if reduced length is zero and if so
  1601. ; the final parity byte is saved reducing count to $FFFF.
  1602.  
  1603. ;; SA-LOOP
  1604. L04FE:  LD      A,D             ; fetch high byte
  1605.         OR      E               ; test against low byte.
  1606.         JR      Z,L050E         ; forward to SA-PARITY if zero.
  1607.  
  1608.         LD      L,(IX+$00)      ; load currently addressed byte to L.
  1609.  
  1610. ;; SA-LOOP-P
  1611. L0505:  LD      A,H             ; fetch parity byte.
  1612.         XOR     L               ; exclusive or with new byte.
  1613.  
  1614. ; -> the mid entry point of loop.
  1615.  
  1616. ;; SA-START
  1617. L0507:  LD      H,A             ; put parity byte in H.
  1618.         LD      A,$01           ; prepare blue, mic=on.
  1619.         SCF                     ; set carry flag ready to rotate in.
  1620.         JP      L0525           ; JUMP forward to SA-8-BITS            -8->
  1621.  
  1622. ; ---
  1623.  
  1624. ;; SA-PARITY
  1625. L050E:  LD      L,H             ; transfer the running parity byte to L and
  1626.         JR      L0505           ; back to SA-LOOP-P
  1627.                                 ; to output that byte before quitting normally.
  1628.  
  1629. ; ---
  1630.  
  1631. ; entry point to save yellow part of bit.
  1632. ; a bit consists of a period with mic on and blue border followed by
  1633. ; a period of mic off with yellow border.
  1634. ; Note. since the DJNZ instruction does not affect flags, the zero flag is used
  1635. ; to indicate which of the two passes is in effect and the carry maintains the
  1636. ; state of the bit to be saved.
  1637.  
  1638. ;; SA-BIT-2
  1639. L0511:  LD      A,C             ; fetch 'mic on and yellow' which is
  1640.                                 ; held permanently in C.
  1641.         BIT     7,B             ; set the zero flag. B holds $3E.
  1642.  
  1643. ; entry point to save 1 entire bit. For first bit B holds $3B(*).
  1644. ; Carry is set if saved bit is 1. zero is reset NZ on entry.
  1645.  
  1646. ;; SA-BIT-1
  1647. L0514:  DJNZ    L0514           ; self loop for delay to SA-BIT-1
  1648.  
  1649.         JR      NC,L051C        ; forward to SA-OUT if bit is 0.
  1650.  
  1651. ; but if bit is 1 then the mic state is held for longer.
  1652.  
  1653.         LD      B,$42           ; set timed delay. (66 decimal)
  1654.  
  1655. ;; SA-SET
  1656. L051A:  DJNZ    L051A           ; self loop to SA-SET
  1657.                                 ; (roughly an extra 66*13 clock cycles)
  1658.  
  1659. ;; SA-OUT
  1660. L051C:  OUT     ($FE),A         ; blue and mic on OR  yellow and mic off.
  1661.  
  1662.         LD      B,$3E           ; set up delay
  1663.         JR      NZ,L0511        ; back to SA-BIT-2 if zero reset NZ (first pass)
  1664.  
  1665. ; proceed when the blue and yellow bands have been output.
  1666.  
  1667.         DEC     B               ; change value $3E to $3D.
  1668.         XOR     A               ; clear carry flag (ready to rotate in).
  1669.         INC     A               ; reset zero flag ie. NZ.
  1670.  
  1671. ; -8->
  1672.  
  1673. ;; SA-8-BITS
  1674. L0525:  RL      L               ; rotate left through carry
  1675.                                 ; C<76543210<C  
  1676.         JP      NZ,L0514        ; JUMP back to SA-BIT-1
  1677.                                 ; until all 8 bits done.
  1678.  
  1679. ; when the initial set carry is passed out again then a byte is complete.
  1680.  
  1681.         DEC     DE              ; decrease length
  1682.         INC     IX              ; increase byte pointer
  1683.         LD      B,$31           ; set up timing.
  1684.  
  1685.         LD      A,$7F           ; test the space key and
  1686.         IN      A,($FE)         ; return to common exit (to restore border)
  1687.         RRA                     ; if a space is pressed
  1688.         RET     NC              ; return to SA/LD-RET.   - - >
  1689.  
  1690. ; now test if byte counter has reached $FFFF.
  1691.  
  1692.         LD      A,D             ; fetch high byte
  1693.         INC     A               ; increment.
  1694.         JP      NZ,L04FE        ; JUMP to SA-LOOP if more bytes.
  1695.  
  1696.         LD      B,$3B           ; a final delay.
  1697.  
  1698. ;; SA-DELAY
  1699. L053C:  DJNZ    L053C           ; self loop to SA-DELAY
  1700.  
  1701.         RET                     ; return - - >
  1702.  
  1703. ; --------------------------------------------------
  1704. ; Reset border and check BREAK key for LOAD and SAVE
  1705. ; --------------------------------------------------
  1706. ; the address of this routine is pushed on the stack prior to any load/save
  1707. ; operation and it handles normal completion with the restoration of the
  1708. ; border and also abnormal termination when the break key, or to be more
  1709. ; precise the space key is pressed during a tape operation.
  1710. ; - - >
  1711.  
  1712. ;; SA/LD-RET
  1713. L053F:  PUSH    AF              ; preserve accumulator throughout.
  1714.         LD      A,($5C48)       ; fetch border colour from BORDCR.
  1715.         AND     $38             ; mask off paper bits.
  1716.         RRCA                    ; rotate
  1717.         RRCA                    ; to the
  1718.         RRCA                    ; range 0-7.
  1719.  
  1720. ;===============================
  1721.                 IF TAP_EMU_BORDER=1
  1722.                 DB 0,0
  1723.                 ELSE
  1724.                 OUT ($FE),A     ; change the border colour.
  1725.                 ENDIF
  1726. ;===============================
  1727.  
  1728.         LD      A,$7F           ; read from port address $7FFE the
  1729.         IN      A,($FE)         ; row with the space key at outside.
  1730.  
  1731.         RRA                     ; test for space key pressed.
  1732.         EI                      ; enable interrupts
  1733.         JR      C,L0554         ; forward to SA/LD-END if not
  1734.  
  1735.  
  1736. ;; REPORT-Da
  1737. L0552:  RST     08H             ; ERROR-1
  1738.         DB    $0C             ; Error Report: BREAK - CONT repeats
  1739.  
  1740. ; ---
  1741.  
  1742. ;; SA/LD-END
  1743. L0554:  POP     AF              ; restore the accumulator.
  1744.         RET                     ; return.
  1745.  
  1746. ; ------------------------------------
  1747. ; Load header or block of information
  1748. ; ------------------------------------
  1749. ; This routine is used to load bytes and on entry A is set to $00 for a
  1750. ; header or to $FF for data.  IX points to the start of receiving location
  1751. ; and DE holds the length of bytes to be loaded. If, on entry the carry flag
  1752. ; is set then data is loaded, if reset then it is verified.
  1753.  
  1754. ;; LD-BYTES
  1755. L0556:  INC     D               ; reset the zero flag without disturbing carry.
  1756.         EX      AF,AF'          ; preserve entry flags.
  1757.        DEC     D               ; restore high byte of length.
  1758.  
  1759.        DI                      ; disable interrupts
  1760.  
  1761.        LD      A,$0F           ; make the border white and mic off.
  1762.  
  1763. ;===============================
  1764.                 IF TAP_EMU_BORDER=1
  1765.                 DB 0,0
  1766.                 ELSE
  1767.                 OUT ($FE),A     ; output to port.
  1768.                 ENDIF
  1769. ;===============================
  1770.  
  1771.        LD      HL,L053F        ; Address: SA/LD-RET
  1772.        PUSH    HL              ; is saved on stack as terminating routine.
  1773.  
  1774. ; the reading of the EAR bit (D6) will always be preceded by a test of the
  1775. ; space key (D0), so store the initial post-test state.
  1776.  
  1777.        IN      A,($FE)         ; read the ear state - bit 6.
  1778.        RRA                     ; rotate to bit 5.
  1779.        AND     $20             ; isolate this bit.
  1780.        OR      $02             ; combine with red border colour.
  1781.  
  1782. ;===============================
  1783.                 RST 8
  1784.                 DB _TAPE_EMUL
  1785. ;               LD C,A          ; and store initial state long-term in C.
  1786. ;               CP A            ; set the zero flag.
  1787. ;===============================
  1788.  
  1789. ;; LD-BREAK
  1790. L056B:  RET     NZ              ; return if at any time space is pressed.
  1791.  
  1792. ;; LD-START
  1793. L056C:  CALL    L05E7           ; routine LD-EDGE-1
  1794.        JR      NC,L056B        ; back to LD-BREAK with time out and no
  1795.                                ; edge present on tape.
  1796.  
  1797. ; but continue when a transition is found on tape.
  1798.  
  1799.        LD      HL,$0415        ; set up 16-bit outer loop counter for
  1800.                                ; approx 1 second delay.
  1801.  
  1802. ;; LD-WAIT
  1803. L0574:  DJNZ    L0574           ; self loop to LD-WAIT (for 256 times)
  1804.  
  1805.        DEC     HL              ; decrease outer loop counter.
  1806.        LD      A,H             ; test for
  1807.        OR      L               ; zero.
  1808.        JR      NZ,L0574        ; back to LD-WAIT, if not zero, with zero in B.
  1809.  
  1810. ; continue after delay with H holding zero and B also.
  1811. ; sample 256 edges to check that we are in the middle of a lead-in section.
  1812.  
  1813.        CALL    L05E3           ; routine LD-EDGE-2
  1814.        JR      NC,L056B        ; back to LD-BREAK
  1815.                                ; if no edges at all.
  1816.  
  1817. ;; LD-LEADER
  1818. L0580:  LD      B,$9C           ; set timing value.
  1819.        CALL    L05E3           ; routine LD-EDGE-2
  1820.        JR      NC,L056B        ; back to LD-BREAK if time-out
  1821.  
  1822.        LD      A,$C6           ; two edges must be spaced apart.
  1823.        CP      B               ; compare
  1824.        JR      NC,L056C        ; back to LD-START if too close together for a
  1825.                                ; lead-in.
  1826.  
  1827.        INC     H               ; proceed to test 256 edged sample.
  1828.        JR      NZ,L0580        ; back to LD-LEADER while more to do.
  1829.  
  1830. ; sample indicates we are in the middle of a two or five second lead-in.
  1831. ; Now test every edge looking for the terminal synch signal.
  1832.  
  1833. ;; LD-SYNC
  1834. L058F:  LD      B,$C9           ; initial timing value in B.
  1835.        CALL    L05E7           ; routine LD-EDGE-1
  1836.        JR      NC,L056B        ; back to LD-BREAK with time-out.
  1837.  
  1838.        LD      A,B             ; fetch augmented timing value from B.
  1839.        CP      $D4             ; compare
  1840.        JR      NC,L058F        ; back to LD-SYNC if gap too big, that is,
  1841.                                ; a normal lead-in edge gap.
  1842.  
  1843. ; but a short gap will be the synch pulse.
  1844. ; in which case another edge should appear before B rises to $FF
  1845.  
  1846.        CALL    L05E7           ; routine LD-EDGE-1
  1847.        RET     NC              ; return with time-out.
  1848.  
  1849. ; proceed when the synch at the end of the lead-in is found.
  1850. ; We are about to load data so change the border colours.
  1851.  
  1852.        LD      A,C             ; fetch long-term mask from C
  1853.        XOR     $03             ; and make blue/yellow.
  1854.  
  1855.        LD      C,A             ; store the new long-term byte.
  1856.  
  1857.        LD      H,$00           ; set up parity byte as zero.
  1858.        LD      B,$B0           ; timing.
  1859.        JR      L05C8           ; forward to LD-MARKER
  1860.                                ; the loop mid entry point with the alternate
  1861.                                ; zero flag reset to indicate first byte
  1862.                                ; is discarded.
  1863.  
  1864. ; --------------
  1865. ; the loading loop loads each byte and is entered at the mid point.
  1866.  
  1867. ;; LD-LOOP
  1868. L05A9:  EX      AF,AF'          ; restore entry flags and type in A.
  1869.         JR      NZ,L05B3        ; forward to LD-FLAG if awaiting initial flag
  1870.                                 ; which is to be discarded.
  1871.  
  1872.         JR      NC,L05BD        ; forward to LD-VERIFY if not to be loaded.
  1873.  
  1874.         LD      (IX+$00),L      ; place loaded byte at memory location.
  1875.         JR      L05C2           ; forward to LD-NEXT
  1876.  
  1877. ; ---
  1878.  
  1879. ;; LD-FLAG
  1880. L05B3:  RL      C               ; preserve carry (verify) flag in long-term
  1881.                                 ; state byte. Bit 7 can be lost.
  1882.  
  1883.         XOR     L               ; compare type in A with first byte in L.
  1884.         RET     NZ              ; return if no match e.g. CODE vs DATA.
  1885.  
  1886. ; continue when data type matches.
  1887.  
  1888.         LD      A,C             ; fetch byte with stored carry
  1889.         RRA                     ; rotate it to carry flag again
  1890.         LD      C,A             ; restore long-term port state.
  1891.  
  1892.         INC     DE              ; increment length ??
  1893.         JR      L05C4           ; forward to LD-DEC.
  1894.                                 ; but why not to location after ?
  1895.  
  1896. ; ---
  1897. ; for verification the byte read from tape is compared with that in memory.
  1898.  
  1899. ;; LD-VERIFY
  1900. L05BD:  LD      A,(IX+$00)      ; fetch byte from memory.
  1901.         XOR     L               ; compare with that on tape
  1902.         RET     NZ              ; return if not zero.
  1903.  
  1904. ;; LD-NEXT
  1905. L05C2:  INC     IX              ; increment byte pointer.
  1906.  
  1907. ;; LD-DEC
  1908. L05C4:  DEC     DE              ; decrement length.
  1909.         EX      AF,AF'          ; store the flags.
  1910.        LD      B,$B2           ; timing.
  1911.  
  1912. ; when starting to read 8 bits the receiving byte is marked with bit at right.
  1913. ; when this is rotated out again then 8 bits have been read.
  1914.  
  1915. ;; LD-MARKER
  1916. L05C8:  LD      L,$01           ; initialize as %00000001
  1917.  
  1918. ;; LD-8-BITS
  1919. L05CA:  CALL    L05E3           ; routine LD-EDGE-2 increments B relative to
  1920.                                ; gap between 2 edges.
  1921.        RET     NC              ; return with time-out.
  1922.  
  1923.        LD      A,$CB           ; the comparison byte.
  1924.        CP      B               ; compare to incremented value of B.
  1925.                                ; if B is higher then bit on tape was set.
  1926.                                ; if <= then bit on tape is reset.
  1927.  
  1928.        RL      L               ; rotate the carry bit into L.
  1929.  
  1930.        LD      B,$B0           ; reset the B timer byte.
  1931.        JP      NC,L05CA        ; JUMP back to LD-8-BITS
  1932.  
  1933. ; when carry set then marker bit has been passed out and byte is complete.
  1934.  
  1935.        LD      A,H             ; fetch the running parity byte.
  1936.        XOR     L               ; include the new byte.
  1937.        LD      H,A             ; and store back in parity register.
  1938.  
  1939.        LD      A,D             ; check length of
  1940.        OR      E               ; expected bytes.
  1941.        JR      NZ,L05A9        ; back to LD-LOOP
  1942.                                ; while there are more.
  1943.  
  1944. ; when all bytes loaded then parity byte should be zero.
  1945.  
  1946.        LD      A,H             ; fetch parity byte.
  1947.        CP      $01             ; set carry if zero.
  1948.        RET                     ; return
  1949.                                ; in no carry then error as checksum disagrees.
  1950.  
  1951. ; -------------------------
  1952. ; Check signal being loaded
  1953. ; -------------------------
  1954. ; An edge is a transition from one mic state to another.
  1955. ; More specifically a change in bit 6 of value input from port $FE.
  1956. ; Graphically it is a change of border colour, say, blue to yellow.
  1957. ; The first entry point looks for two adjacent edges. The second entry point
  1958. ; is used to find a single edge.
  1959. ; The B register holds a count, up to 256, within which the edge (or edges)
  1960. ; must be found. The gap between two edges will be more for a '1' than a '0'
  1961. ; so the value of B denotes the state of the bit (two edges) read from tape.
  1962.  
  1963. ; ->
  1964.  
  1965. ;; LD-EDGE-2
  1966. L05E3:  CALL    L05E7           ; call routine LD-EDGE-1 below.
  1967.        RET     NC              ; return if space pressed or time-out.
  1968.                                ; else continue and look for another adjacent
  1969.                                ; edge which together represent a bit on the
  1970.                                ; tape.
  1971.  
  1972. ; ->
  1973. ; this entry point is used to find a single edge from above but also
  1974. ; when detecting a read-in signal on the tape.
  1975.  
  1976. ;; LD-EDGE-1
  1977. L05E7:  LD      A,$16           ; a delay value of twenty two.
  1978.  
  1979. ;; LD-DELAY
  1980. L05E9:  DEC     A               ; decrement counter
  1981.        JR      NZ,L05E9        ; loop back to LD-DELAY 22 times.
  1982.  
  1983.        AND      A              ; clear carry.
  1984.  
  1985. ;; LD-SAMPLE
  1986. L05ED:  INC     B               ; increment the time-out counter.
  1987.        RET     Z               ; return with failure when $FF passed.
  1988.  
  1989.        LD      A,$7F           ; prepare to read keyboard and EAR port
  1990.        IN      A,($FE)         ; row $7FFE. bit 6 is EAR, bit 0 is SPACE key.
  1991.        RRA                     ; test outer key the space. (bit 6 moves to 5)
  1992.        RET     NC              ; return if space pressed.  >>>
  1993.  
  1994.        XOR     C               ; compare with initial long-term state.
  1995.        AND     $20             ; isolate bit 5
  1996.        JR      Z,L05ED         ; back to LD-SAMPLE if no edge.
  1997.  
  1998. ; but an edge, a transition of the EAR bit, has been found so switch the
  1999. ; long-term comparison byte containing both border colour and EAR bit.
  2000.  
  2001.        LD      A,C             ; fetch comparison value.
  2002.        CPL                     ; switch the bits
  2003.        LD      C,A             ; and put back in C for long-term.
  2004.  
  2005.        AND     $07             ; isolate new colour bits.
  2006.        OR      $08             ; set bit 3 - MIC off.
  2007.        OUT     ($FE),A         ; send to port to effect change of colour.
  2008.  
  2009.        SCF                     ; set carry flag signaling edge found within
  2010.                                ; time allowed.
  2011.        RET                     ; return.
  2012.  
  2013. ; ---------------------------------
  2014. ; Entry point for all tape commands
  2015. ; ---------------------------------
  2016. ; This is the single entry point for the four tape commands.
  2017. ; The routine first determines in what context it has been called by examining
  2018. ; the low byte of the Syntax table entry which was stored in T_ADDR.
  2019. ; Subtracting $EO (the present arrangement) gives a value of
  2020. ; $00 - SAVE
  2021. ; $01 - LOAD
  2022. ; $02 - VERIFY
  2023. ; $03 - MERGE
  2024. ; As with all commands the address STMT-RET is on the stack.
  2025.  
  2026. ;; SAVE-ETC
  2027. L0605:  POP     AF              ; discard address STMT-RET.
  2028.        LD      A,($5C74)       ; fetch T_ADDR
  2029.  
  2030. ; Now reduce the low byte of the Syntax table entry to give command.
  2031. ; Note. For ZASM use SUB $E0 as next instruction.
  2032.  
  2033. L0609           SUB LOW (L1ADF)+1       ; subtract the known offset.
  2034.                                ; ( is SUB $E0 in standard ROM )
  2035.  
  2036.        LD      ($5C74),A       ; and put back in T_ADDR as 0,1,2, or 3
  2037.                                ; for future reference.
  2038.  
  2039.        CALL    L1C8C           ; routine EXPT-EXP checks that a string
  2040.                                ; expression follows and stacks the
  2041.                                ; parameters in run-time.
  2042.  
  2043.        CALL    L2530           ; routine SYNTAX-Z
  2044.        JR      Z,L0652         ; forward to SA-DATA if checking syntax.
  2045.  
  2046.        LD      BC,$0011        ; presume seventeen bytes for a header.
  2047.        LD      A,($5C74)       ; fetch command from T_ADDR.
  2048.        AND     A               ; test for zero - SAVE.
  2049.        JR      Z,L0621         ; forward to SA-SPACE if so.
  2050.  
  2051.        LD      C,$22           ; else double length to thirty four.
  2052.  
  2053. ;; SA-SPACE
  2054. L0621:  RST     30H             ; BC-SPACES creates 17/34 bytes in workspace.
  2055.  
  2056.        PUSH    DE              ; transfer the start of new space to
  2057.        POP     IX              ; the available index register.
  2058.  
  2059. ; ten spaces are required for the default filename but it is simpler to
  2060. ; overwrite the first file-type indicator byte as well.
  2061.  
  2062.        LD      B,$0B           ; set counter to eleven.
  2063.        LD      A,$20           ; prepare a space.
  2064.  
  2065. ;; SA-BLANK
  2066. L0629:  LD      (DE),A          ; set workspace location to space.
  2067.        INC     DE              ; next location.
  2068.        DJNZ    L0629           ; loop back to SA-BLANK till all eleven done.
  2069.  
  2070.        LD      (IX+$01),$FF    ; set first byte of ten character filename
  2071.                                ; to $FF as a default to signal null string.
  2072.  
  2073.        CALL    L2BF1           ; routine STK-FETCH fetches the filename
  2074.                                ; parameters from the calculator stack.
  2075.                                ; length of string in BC.
  2076.                                ; start of string in DE.
  2077.  
  2078.        LD      HL,$FFF6        ; prepare the value minus ten.
  2079.        DEC     BC              ; decrement length.
  2080.                                ; ten becomes nine, zero becomes $FFFF.
  2081.        ADD     HL,BC           ; trial addition.
  2082.        INC     BC              ; restore true length.
  2083.        JR      NC,L064B        ; forward to SA-NAME if length is one to ten.
  2084.  
  2085. ; the filename is more than ten characters in length or the null string.
  2086.  
  2087.        LD      A,($5C74)       ; fetch command from T_ADDR.
  2088.        AND     A               ; test for zero - SAVE.
  2089.        JR      NZ,L0644        ; forward to SA-NULL if not the SAVE command.
  2090.  
  2091. ; but no more than ten characters are allowed for SAVE.
  2092. ; The first ten characters of any other command parameter are acceptable.
  2093. ; Weird, but necessary, if saving to sectors.
  2094. ; Note. the golden rule that there are no restriction on anything is broken.
  2095.  
  2096. ;; REPORT-Fa
  2097. L0642:  RST     08H             ; ERROR-1
  2098.        DB    $0E             ; Error Report: Invalid file name
  2099.  
  2100. ; continue with LOAD, MERGE, VERIFY and also SAVE within ten character limit.
  2101.  
  2102. ;; SA-NULL
  2103. L0644:  LD      A,B             ; test length of filename
  2104.        OR      C               ; for zero.
  2105.        JR      Z,L0652         ; forward to SA-DATA if so using the 255
  2106.                                ; indicator followed by spaces.
  2107.  
  2108.        LD      BC,$000A        ; else trim length to ten.
  2109.  
  2110. ; other paths rejoin here with BC holding length in range 1 - 10.
  2111.  
  2112. ;; SA-NAME
  2113. L064B:  PUSH    IX              ; push start of file descriptor.
  2114.        POP     HL              ; and pop into HL.
  2115.  
  2116.        INC     HL              ; HL now addresses first byte of filename.
  2117.        EX      DE,HL           ; transfer destination address to DE, start
  2118.                                ; of string in command to HL.
  2119.        LDIR                    ; copy up to ten bytes
  2120.                                ; if less than ten then trailing spaces follow.
  2121.  
  2122. ; the case for the null string rejoins here.
  2123.  
  2124. ;; SA-DATA
  2125. L0652:  RST     18H             ; GET-CHAR
  2126.        CP      $E4             ; is character after filename the token 'DATA' ?
  2127.        JR      NZ,L06A0        ; forward to SA-SCR$ to consider SCREEN$ if
  2128.                                ; not.
  2129.  
  2130. ; continue to consider DATA.
  2131.  
  2132.        LD      A,($5C74)       ; fetch command from T_ADDR
  2133.        CP      $03             ; is it 'VERIFY' ?
  2134.        JP      Z,L1C8A         ; jump forward to REPORT-C if so.
  2135.                                ; 'Nonsense in BASIC'
  2136.                                ; VERIFY "d" DATA is not allowed.
  2137.  
  2138. ; continue with SAVE, LOAD, MERGE of DATA.
  2139.  
  2140.        RST     20H             ; NEXT-CHAR
  2141.        CALL    L28B2           ; routine LOOK-VARS searches variables area
  2142.                                ; returning with carry reset if found or
  2143.                                ; checking syntax.
  2144.        SET     7,C             ; this converts a simple string to a
  2145.                                ; string array. The test for an array or string
  2146.                                ; comes later.
  2147.        JR      NC,L0672        ; forward to SA-V-OLD if variable found.
  2148.  
  2149.        LD      HL,$0000        ; set destination to zero as not fixed.
  2150.        LD      A,($5C74)       ; fetch command from T_ADDR
  2151.        DEC     A               ; test for 1 - LOAD
  2152.        JR      Z,L0685         ; forward to SA-V-NEW with LOAD DATA.
  2153.                                ; to load a new array.
  2154.  
  2155. ; otherwise the variable was not found in run-time with SAVE/MERGE.
  2156.  
  2157. ;; REPORT-2a
  2158. L0670:  RST     08H             ; ERROR-1
  2159.        DB    $01             ; Error Report: Variable not found
  2160.  
  2161. ; continue with SAVE/LOAD  DATA
  2162.  
  2163. ;; SA-V-OLD
  2164. L0672:  JP      NZ,L1C8A        ; to REPORT-C if not an array variable.
  2165.                                ; or erroneously a simple string.
  2166.                                ; 'Nonsense in BASIC'
  2167.  
  2168.  
  2169.        CALL    L2530           ; routine SYNTAX-Z
  2170.        JR      Z,L0692         ; forward to SA-DATA-1 if checking syntax.
  2171.  
  2172.        INC     HL              ; step past single character variable name.
  2173.        LD      A,(HL)          ; fetch low byte of length.
  2174.        LD      (IX+$0B),A      ; place in descriptor.
  2175.        INC     HL              ; point to high byte.
  2176.        LD      A,(HL)          ; and transfer that
  2177.        LD      (IX+$0C),A      ; to descriptor.
  2178.        INC     HL              ; increase pointer within variable.
  2179.  
  2180. ;; SA-V-NEW
  2181. L0685:  LD      (IX+$0E),C      ; place character array name in  header.
  2182.        LD      A,$01           ; default to type numeric.
  2183.        BIT     6,C             ; test result from look-vars.
  2184.        JR      Z,L068F         ; forward to SA-V-TYPE if numeric.
  2185.  
  2186.        INC     A               ; set type to 2 - string array.
  2187.  
  2188. ;; SA-V-TYPE
  2189. L068F:  LD      (IX+$00),A      ; place type 0, 1 or 2 in descriptor.
  2190.  
  2191. ;; SA-DATA-1
  2192. L0692:  EX      DE,HL           ; save var pointer in DE
  2193.  
  2194.        RST     20H             ; NEXT-CHAR
  2195.        CP      $29             ; is character ')' ?
  2196.        JR      NZ,L0672        ; back if not to SA-V-OLD to report
  2197.                                ; 'Nonsense in BASIC'
  2198.  
  2199.        RST     20H             ; NEXT-CHAR advances character address.
  2200.        CALL    L1BEE           ; routine CHECK-END errors if not end of
  2201.                                ; the statement.
  2202.  
  2203.        EX      DE,HL           ; bring back variables data pointer.
  2204.        JP      L075A           ; jump forward to SA-ALL
  2205.  
  2206. ; ---
  2207. ; the branch was here to consider a 'SCREEN$', the display file.
  2208.  
  2209. ;; SA-SCR$
  2210. L06A0:  CP      $AA             ; is character the token 'SCREEN$' ?
  2211.        JR      NZ,L06C3        ; forward to SA-CODE if not.
  2212.  
  2213.        LD      A,($5C74)       ; fetch command from T_ADDR
  2214.        CP      $03             ; is it MERGE ?
  2215.        JP       Z,L1C8A        ; jump to REPORT-C if so.
  2216.                                ; 'Nonsense in BASIC'
  2217.  
  2218. ; continue with SAVE/LOAD/VERIFY SCREEN$.
  2219.  
  2220.        RST     20H             ; NEXT-CHAR
  2221.        CALL    L1BEE           ; routine CHECK-END errors if not at end of
  2222.                                ; statement.
  2223.  
  2224. ; continue in runtime.
  2225.  
  2226.        LD      (IX+$0B),$00    ; set descriptor length
  2227.        LD      (IX+$0C),$1B    ; to $1b00 to include bitmaps and attributes.
  2228.  
  2229.        LD      HL,$4000        ; set start to display file start.
  2230.        LD      (IX+$0D),L      ; place start in
  2231.        LD      (IX+$0E),H      ; the descriptor.
  2232.        JR      L0710           ; forward to SA-TYPE-3
  2233.  
  2234. ; ---
  2235. ; the branch was here to consider CODE.
  2236.  
  2237. ;; SA-CODE
  2238. L06C3:  CP      $AF             ; is character the token 'CODE' ?
  2239.        JR      NZ,L0716        ; forward if not to SA-LINE to consider an
  2240.                                ; auto-started BASIC program.
  2241.  
  2242.        LD      A,($5C74)       ; fetch command from T_ADDR
  2243.        CP      $03             ; is it MERGE ?
  2244.        JP      Z,L1C8A         ; jump forward to REPORT-C if so.
  2245.                                ; 'Nonsense in BASIC'
  2246.  
  2247.  
  2248.        RST     20H             ; NEXT-CHAR advances character address.
  2249.        CALL    L2048           ; routine PR-ST-END checks if a carriage
  2250.                                ; return or ':' follows.
  2251.        JR      NZ,L06E1        ; forward to SA-CODE-1 if there are parameters.
  2252.  
  2253.        LD      A,($5C74)       ; else fetch the command from T_ADDR.
  2254.        AND     A               ; test for zero - SAVE without a specification.
  2255.        JP      Z,L1C8A         ; jump to REPORT-C if so.
  2256.                                ; 'Nonsense in BASIC'
  2257.  
  2258. ; for LOAD/VERIFY put zero on stack to signify handle at location saved from.
  2259.  
  2260.        CALL    L1CE6           ; routine USE-ZERO
  2261.        JR      L06F0           ; forward to SA-CODE-2
  2262.  
  2263. ; ---
  2264. ; if there are more characters after CODE expect start and possibly length.
  2265.  
  2266. ;; SA-CODE-1
  2267. L06E1:  CALL    L1C82           ; routine EXPT-1NUM checks for numeric
  2268.                                ; expression and stacks it in run-time.
  2269.  
  2270.        RST     18H             ; GET-CHAR
  2271.        CP      $2C             ; does a comma follow ?
  2272.        JR      Z,L06F5         ; forward if so to SA-CODE-3
  2273.  
  2274. ; else allow saved code to be loaded to a specified address.
  2275.  
  2276.        LD      A,($5C74)       ; fetch command from T_ADDR.
  2277.        AND     A               ; is the command SAVE which requires length ?
  2278.        JP      Z,L1C8A         ; jump to REPORT-C if so.
  2279.                                ; 'Nonsense in BASIC'
  2280.  
  2281. ; the command LOAD code may rejoin here with zero stacked as start.
  2282.  
  2283. ;; SA-CODE-2
  2284. L06F0:  CALL    L1CE6           ; routine USE-ZERO stacks zero for length.
  2285.        JR      L06F9           ; forward to SA-CODE-4
  2286.  
  2287. ; ---
  2288. ; the branch was here with SAVE CODE start,
  2289.  
  2290. ;; SA-CODE-3
  2291. L06F5:  RST     20H             ; NEXT-CHAR advances character address.
  2292.        CALL    L1C82           ; routine EXPT-1NUM checks for expression
  2293.                                ; and stacks in run-time.
  2294.  
  2295. ; paths converge here and nothing must follow.
  2296.  
  2297. ;; SA-CODE-4
  2298. L06F9:  CALL    L1BEE           ; routine CHECK-END errors with extraneous
  2299.                                ; characters and quits if checking syntax.
  2300.  
  2301. ; in run-time there are two 16-bit parameters on the calculator stack.
  2302.  
  2303.        CALL    L1E99           ; routine FIND-INT2 gets length.
  2304.        LD      (IX+$0B),C      ; place length
  2305.        LD      (IX+$0C),B      ; in descriptor.
  2306.        CALL    L1E99           ; routine FIND-INT2 gets start.
  2307.        LD      (IX+$0D),C      ; place start
  2308.        LD      (IX+$0E),B      ; in descriptor.
  2309.        LD      H,B             ; transfer the
  2310.        LD      L,C             ; start to HL also.
  2311.  
  2312. ;; SA-TYPE-3
  2313. L0710:  LD      (IX+$00),$03    ; place type 3 - code in descriptor.
  2314.        JR      L075A           ; forward to SA-ALL.
  2315.  
  2316. ; ---
  2317. ; the branch was here with BASIC to consider an optional auto-start line
  2318. ; number.
  2319.  
  2320. ;; SA-LINE
  2321. L0716:  CP      $CA             ; is character the token 'LINE' ?
  2322.        JR      Z,L0723         ; forward to SA-LINE-1 if so.
  2323.  
  2324. ; else all possibilities have been considered and nothing must follow.
  2325.  
  2326.        CALL    L1BEE           ; routine CHECK-END
  2327.  
  2328. ; continue in run-time to save BASIC without auto-start.
  2329.  
  2330.        LD      (IX+$0E),$80    ; place high line number in descriptor to
  2331.                                ; disable auto-start.
  2332.        JR      L073A           ; forward to SA-TYPE-0 to save program.
  2333.  
  2334. ; ---
  2335. ; the branch was here to consider auto-start.
  2336.  
  2337. ;; SA-LINE-1
  2338. L0723:  LD      A,($5C74)       ; fetch command from T_ADDR
  2339.        AND     A               ; test for SAVE.
  2340.        JP      NZ,L1C8A        ; jump forward to REPORT-C with anything else.
  2341.                                ; 'Nonsense in BASIC'
  2342.  
  2343. ;
  2344.  
  2345.        RST     20H             ; NEXT-CHAR
  2346.        CALL    L1C82           ; routine EXPT-1NUM checks for numeric
  2347.                                ; expression and stacks in run-time.
  2348.        CALL    L1BEE           ; routine CHECK-END quits if syntax path.
  2349.        CALL    L1E99           ; routine FIND-INT2 fetches the numeric
  2350.                                ; expression.
  2351.        LD      (IX+$0D),C      ; place the auto-start
  2352.        LD      (IX+$0E),B      ; line number in the descriptor.
  2353.  
  2354. ; Note. this isn't checked, but is subsequently handled by the system.
  2355. ; If the user typed 40000 instead of 4000 then it won't auto-start
  2356. ; at line 4000, or indeed, at all.
  2357.  
  2358. ; continue to save program and any variables.
  2359.  
  2360. ;; SA-TYPE-0
  2361. L073A:  LD      (IX+$00),$00    ; place type zero - program in descriptor.
  2362.         LD      HL,($5C59)      ; fetch E_LINE to HL.
  2363.         LD      DE,($5C53)      ; fetch PROG to DE.
  2364.         SCF                     ; set carry flag to calculate from end of
  2365.                                 ; variables E_LINE -1.
  2366.         SBC     HL,DE           ; subtract to give total length.
  2367.  
  2368.         LD      (IX+$0B),L      ; place total length
  2369.         LD      (IX+$0C),H      ; in descriptor.
  2370.         LD      HL,($5C4B)      ; load HL from system variable VARS
  2371.         SBC     HL,DE           ; subtract to give program length.
  2372.         LD      (IX+$0F),L      ; place length of program
  2373.         LD      (IX+$10),H      ; in the descriptor.
  2374.         EX      DE,HL           ; start to HL, length to DE.
  2375.  
  2376. ;; SA-ALL
  2377. L075A:  LD      A,($5C74)       ; fetch command from T_ADDR
  2378.         AND     A               ; test for zero - SAVE.
  2379.         JP      Z,L0970         ; jump forward to SA-CONTRL with SAVE  ->
  2380.  
  2381. ; ---
  2382. ; continue with LOAD, MERGE and VERIFY.
  2383.  
  2384.         PUSH    HL              ; save start.
  2385.         LD      BC,$0011        ; prepare to add seventeen
  2386.         ADD     IX,BC           ; to point IX at second descriptor.
  2387.  
  2388. ;; LD-LOOK-H
  2389. L0767:  PUSH    IX              ; save IX
  2390.         LD      DE,$0011        ; seventeen bytes
  2391.         XOR     A               ; reset zero flag
  2392.         SCF                     ; set carry flag
  2393.         CALL    L0556           ; routine LD-BYTES loads a header from tape
  2394.                                 ; to second descriptor.
  2395.         POP     IX              ; restore IX.
  2396.         JR      NC,L0767        ; loop back to LD-LOOK-H until header found.
  2397.  
  2398.         LD      A,$FE           ; select system channel 'S'
  2399.         CALL    L1601           ; routine CHAN-OPEN opens it.
  2400.  
  2401.         LD      (IY+$52),$03    ; set SCR_CT to 3 lines.
  2402.  
  2403.         LD      C,$80           ; C has bit 7 set to indicate type mismatch as
  2404.                                 ; a default startpoint.
  2405.  
  2406.         LD      A,(IX+$00)      ; fetch loaded header type to A
  2407.         CP      (IX-$11)        ; compare with expected type.
  2408.         JR      NZ,L078A        ; forward to LD-TYPE with mis-match.
  2409.  
  2410.         LD      C,$F6           ; set C to minus ten - will count characters
  2411.                                 ; up to zero.
  2412.  
  2413. ;; LD-TYPE
  2414. L078A:  CP      $04             ; check if type in acceptable range 0 - 3.
  2415.         JR      NC,L0767        ; back to LD-LOOK-H with 4 and over.
  2416.  
  2417. ; else A indicates type 0-3.
  2418.  
  2419.         LD      DE,L09C0        ; address base of last 4 tape messages
  2420.         PUSH    BC              ; save BC
  2421.         CALL    L0C0A           ; routine PO-MSG outputs relevant message.
  2422.                                 ; Note. all messages have a leading newline.
  2423.         POP     BC              ; restore BC
  2424.  
  2425.         PUSH    IX              ; transfer IX,
  2426.         POP     DE              ; the 2nd descriptor, to DE.
  2427.         LD      HL,$FFF0        ; prepare minus seventeen.
  2428.         ADD     HL,DE           ; add to point HL to 1st descriptor.
  2429.         LD      B,$0A           ; the count will be ten characters for the
  2430.                                 ; filename.
  2431.  
  2432.         LD      A,(HL)          ; fetch first character and test for
  2433.         INC     A               ; value 255.
  2434.         JR      NZ,L07A6        ; forward to LD-NAME if not the wildcard.
  2435.  
  2436. ; but if it is the wildcard, then add ten to C which is minus ten for a type
  2437. ; match or -128 for a type mismatch. Although characters have to be counted
  2438. ; bit 7 of C will not alter from state set here.
  2439.  
  2440.         LD      A,C             ; transfer $F6 or $80 to A
  2441.         ADD     A,B             ; add $0A
  2442.         LD      C,A             ; place result, zero or -118, in C.
  2443.  
  2444. ; At this point we have either a type mismatch, a wildcard match or ten
  2445. ; characters to be counted. The characters must be shown on the screen.
  2446.  
  2447. ;; LD-NAME
  2448. L07A6:  INC     DE              ; address next input character
  2449.         LD      A,(DE)          ; fetch character
  2450.         CP      (HL)            ; compare to expected
  2451.         INC     HL              ; address next expected character
  2452.         JR      NZ,L07AD        ; forward to LD-CH-PR with mismatch
  2453.  
  2454.         INC     C               ; increment matched character count
  2455.  
  2456. ;; LD-CH-PR
  2457. L07AD:  RST     10H             ; PRINT-A prints character
  2458.         DJNZ    L07A6           ; loop back to LD-NAME for ten characters.
  2459.  
  2460. ; if ten characters matched and the types previously matched then C will
  2461. ; now hold zero.
  2462.  
  2463.         BIT     7,C             ; test if all matched
  2464.         JR      NZ,L0767        ; back to LD-LOOK-H if not
  2465.  
  2466. ; else print a terminal carriage return.
  2467.  
  2468.         LD      A,$0D           ; prepare carriage return.
  2469.         RST     10H             ; PRINT-A outputs it.
  2470.  
  2471. ; The various control routines for LOAD, VERIFY and MERGE are executed
  2472. ; during the one-second gap following the header on tape.
  2473.  
  2474.         POP     HL              ; restore xx
  2475.         LD      A,(IX+$00)      ; fetch incoming type
  2476.         CP      $03             ; compare with CODE
  2477.         JR      Z,L07CB         ; forward to VR-CONTROL if it is CODE.
  2478.  
  2479. ;  type is a program or an array.
  2480.  
  2481.         LD      A,($5C74)       ; fetch command from T_ADDR
  2482.         DEC     A               ; was it LOAD ?
  2483.         JP      Z,L0808         ; JUMP forward to LD-CONTRL if so to
  2484.                                 ; load BASIC or variables.
  2485.  
  2486.         CP      $02             ; was command MERGE ?
  2487.         JP      Z,L08B6         ; jump forward to ME-CONTRL if so.
  2488.  
  2489. ; else continue into VERIFY control routine to verify.
  2490.  
  2491. ; ---------------------
  2492. ; Handle VERIFY control
  2493. ; ---------------------
  2494. ; There are two branches to this routine.
  2495. ; 1) From above to verify a program or array
  2496. ; 2) from earlier with no carry to load or verify code.
  2497.  
  2498. ;; VR-CONTROL
  2499. L07CB:  PUSH    HL              ; save pointer to data.
  2500.         LD      L,(IX-$06)      ; fetch length of old data
  2501.         LD      H,(IX-$05)      ; to HL.
  2502.         LD      E,(IX+$0B)      ; fetch length of new data
  2503.         LD      D,(IX+$0C)      ; to DE.
  2504.         LD      A,H             ; check length of old
  2505.         OR      L               ; for zero.
  2506.         JR      Z,L07E9         ; forward to VR-CONT-1 if length unspecified
  2507.                                 ; e.g LOAD "x" CODE
  2508.  
  2509. ; as opposed to, say, LOAD 'x' CODE 32768,300.
  2510.  
  2511.         SBC     HL,DE           ; subtract the two lengths.
  2512.         JR      C,L0806         ; forward to REPORT-R if the length on tape is
  2513.                                 ; larger than that specified in command.
  2514.                                 ; 'Tape loading error'
  2515.  
  2516.         JR      Z,L07E9         ; forward to VR-CONT-1 if lengths match.
  2517.  
  2518. ; a length on tape shorter than expected is not allowed for CODE
  2519.  
  2520.         LD      A,(IX+$00)      ; else fetch type from tape.
  2521.         CP      $03             ; is it CODE ?
  2522.         JR      NZ,L0806        ; forward to REPORT-R if so
  2523.                                 ; 'Tape loading error'
  2524.  
  2525. ;; VR-CONT-1
  2526. L07E9:  POP     HL              ; pop pointer to data
  2527.         LD      A,H             ; test for zero
  2528.         OR      L               ; e.g. LOAD 'x' CODE
  2529.         JR      NZ,L07F4        ; forward to VR-CONT-2 if destination specified.
  2530.  
  2531.         LD      L,(IX+$0D)      ; else use the destination in the header
  2532.         LD      H,(IX+$0E)      ; and load code at address saved from.
  2533.  
  2534. ;; VR-CONT-2
  2535. L07F4:  PUSH    HL              ; push pointer to start of data block.
  2536.         POP     IX              ; transfer to IX.
  2537.         LD      A,($5C74)       ; fetch reduced command from T_ADDR
  2538.         CP      $02             ; is it VERIFY ?
  2539.         SCF                     ; prepare a set carry flag
  2540.         JR      NZ,L0800        ; skip to VR-CONT-3 if not
  2541.  
  2542.         AND     A               ; clear carry flag for VERIFY so that
  2543.                                 ; data is not loaded.
  2544.  
  2545. ;; VR-CONT-3
  2546. L0800:  LD      A,$FF           ; signal data block to be loaded
  2547.  
  2548. ; -----------------
  2549. ; Load a data block
  2550. ; -----------------
  2551. ; This routine is called from 3 places other than above to load a data block.
  2552. ; In all cases the accumulator is first set to $FF so the routine could be
  2553. ; called at the previous instruction.
  2554.  
  2555. ;; LD-BLOCK
  2556. L0802:  CALL    L0556           ; routine LD-BYTES
  2557.         RET     C               ; return if successful.
  2558.  
  2559.  
  2560. ;; REPORT-R
  2561. L0806:  RST     08H             ; ERROR-1
  2562.         DB    $1A             ; Error Report: Tape loading error
  2563.  
  2564. ; -------------------
  2565. ; Handle LOAD control
  2566. ; -------------------
  2567. ; This branch is taken when the command is LOAD with type 0, 1 or 2.
  2568.  
  2569. ;; LD-CONTRL
  2570. L0808:  LD      E,(IX+$0B)      ; fetch length of found data block
  2571.         LD      D,(IX+$0C)      ; from 2nd descriptor.
  2572.         PUSH    HL              ; save destination
  2573.         LD      A,H             ; test for zero
  2574.         OR      L               ;
  2575.         JR      NZ,L0819        ; forward if not to LD-CONT-1
  2576.  
  2577.         INC     DE              ; increase length
  2578.         INC     DE              ; for letter name
  2579.         INC     DE              ; and 16-bit length
  2580.         EX      DE,HL           ; length to HL,
  2581.         JR      L0825           ; forward to LD-CONT-2
  2582.  
  2583. ; ---
  2584.  
  2585. ;; LD-CONT-1
  2586. L0819:  LD      L,(IX-$06)      ; fetch length from
  2587.         LD      H,(IX-$05)      ; the first header.
  2588.         EX      DE,HL           ;
  2589.         SCF                     ; set carry flag
  2590.         SBC     HL,DE           ;
  2591.         JR      C,L082E         ; to LD-DATA
  2592.  
  2593. ;; LD-CONT-2
  2594. L0825:  LD      DE,$0005        ; allow overhead of five bytes.
  2595.         ADD     HL,DE           ; add in the difference in data lengths.
  2596.         LD      B,H             ; transfer to
  2597.         LD      C,L             ; the BC register pair
  2598.         CALL    L1F05           ; routine TEST-ROOM fails if not enough room.
  2599.  
  2600. ;; LD-DATA
  2601. L082E:  POP     HL              ; pop destination
  2602.         LD      A,(IX+$00)      ; fetch type 0, 1 or 2.
  2603.         AND     A               ; test for program and variables.
  2604.         JR      Z,L0873         ; forward if so to LD-PROG
  2605.  
  2606. ; the type is a numeric or string array.
  2607.  
  2608.         LD      A,H             ; test the destination for zero
  2609.         OR      L               ; indicating variable does not already exist.
  2610.         JR      Z,L084C         ; forward if so to LD-DATA-1
  2611.  
  2612. ; else the destination is the first dimension within the array structure
  2613.  
  2614.         DEC     HL              ; address high byte of total length
  2615.         LD      B,(HL)          ; transfer to B.
  2616.         DEC     HL              ; address low byte of total length.
  2617.         LD      C,(HL)          ; transfer to C.
  2618.         DEC     HL              ; point to letter of variable.
  2619.         INC     BC              ; adjust length to
  2620.         INC     BC              ; include these
  2621.         INC     BC              ; three bytes also.
  2622.         LD      ($5C5F),IX      ; save header pointer in X_PTR.
  2623.         CALL    L19E8           ; routine RECLAIM-2 reclaims the old variable
  2624.                                 ; sliding workspace including the two headers
  2625.                                 ; downwards.
  2626.         LD      IX,($5C5F)      ; reload IX from X_PTR which will have been
  2627.                                 ; adjusted down by POINTERS routine.
  2628.  
  2629. ;; LD-DATA-1
  2630. L084C:  LD      HL,($5C59)      ; address E_LINE
  2631.         DEC     HL              ; now point to the $80 variables end-marker.
  2632.         LD      C,(IX+$0B)      ; fetch new data length
  2633.         LD      B,(IX+$0C)      ; from 2nd header.
  2634.         PUSH    BC              ; * save it.
  2635.         INC     BC              ; adjust the
  2636.         INC     BC              ; length to include
  2637.         INC     BC              ; letter name and total length.
  2638.         LD      A,(IX-$03)      ; fetch letter name from old header.
  2639.         PUSH    AF              ; preserve accumulator though not corrupted.
  2640.  
  2641.         CALL    L1655           ; routine MAKE-ROOM creates space for variable
  2642.                                 ; sliding workspace up. IX no longer addresses
  2643.                                 ; anywhere meaningful.
  2644.         INC     HL              ; point to first new location.
  2645.  
  2646.         POP     AF              ; fetch back the letter name.
  2647.         LD      (HL),A          ; place in first new location.
  2648.         POP     DE              ; * pop the data length.
  2649.         INC     HL              ; address 2nd location
  2650.         LD      (HL),E          ; store low byte of length.
  2651.         INC     HL              ; address next.
  2652.         LD      (HL),D          ; store high byte.
  2653.         INC     HL              ; address start of data.
  2654.         PUSH    HL              ; transfer address
  2655.         POP     IX              ; to IX register pair.
  2656.         SCF                     ; set carry flag indicating load not verify.
  2657.         LD      A,$FF           ; signal data not header.
  2658.         JP      L0802           ; JUMP back to LD-BLOCK
  2659.  
  2660. ; -----------------
  2661. ; the branch is here when a program as opposed to an array is to be loaded.
  2662.  
  2663. ;; LD-PROG
  2664. L0873:  EX      DE,HL           ; transfer dest to DE.
  2665.         LD      HL,($5C59)      ; address E_LINE
  2666.         DEC     HL              ; now variables end-marker.
  2667.         LD      ($5C5F),IX      ; place the IX header pointer in X_PTR
  2668.         LD      C,(IX+$0B)      ; get new length
  2669.         LD      B,(IX+$0C)      ; from 2nd header
  2670.         PUSH    BC              ; and save it.
  2671.  
  2672.         CALL    L19E5           ; routine RECLAIM-1 reclaims program and vars.
  2673.                                 ; adjusting X-PTR.
  2674.  
  2675.         POP     BC              ; restore new length.
  2676.         PUSH    HL              ; * save start
  2677.         PUSH    BC              ; ** and length.
  2678.  
  2679.         CALL    L1655           ; routine MAKE-ROOM creates the space.
  2680.  
  2681.         LD      IX,($5C5F)      ; reload IX from adjusted X_PTR
  2682.         INC     HL              ; point to start of new area.
  2683.         LD      C,(IX+$0F)      ; fetch length of BASIC on tape
  2684.         LD      B,(IX+$10)      ; from 2nd descriptor
  2685.         ADD     HL,BC           ; add to address the start of variables.
  2686.         LD      ($5C4B),HL      ; set system variable VARS
  2687.  
  2688.         LD      H,(IX+$0E)      ; fetch high byte of autostart line number.
  2689.         LD      A,H             ; transfer to A
  2690.         AND     $C0             ; test if greater than $3F.
  2691.         JR      NZ,L08AD        ; forward to LD-PROG-1 if so with no autostart.
  2692.  
  2693.         LD      L,(IX+$0D)      ; else fetch the low byte.
  2694.         LD      ($5C42),HL      ; set sytem variable to line number NEWPPC
  2695.         LD      (IY+$0A),$00    ; set statement NSPPC to zero.
  2696.  
  2697. ;; LD-PROG-1
  2698. L08AD:  POP     DE              ; ** pop the length
  2699.         POP     IX              ; * and start.
  2700.         SCF                     ; set carry flag
  2701.         LD      A,$FF           ; signal data as opposed to a header.
  2702.         JP      L0802           ; jump back to LD-BLOCK
  2703.  
  2704. ; --------------------
  2705. ; Handle MERGE control
  2706. ; --------------------
  2707. ; the branch was here to merge a program and its variables or an array.
  2708. ;
  2709.  
  2710. ;; ME-CONTRL
  2711. L08B6:  LD      C,(IX+$0B)      ; fetch length
  2712.         LD      B,(IX+$0C)      ; of data block on tape.
  2713.         PUSH    BC              ; save it.
  2714.         INC     BC              ; one for the pot.
  2715.  
  2716.         RST     30H             ; BC-SPACES creates room in workspace.
  2717.                                 ; HL addresses last new location.
  2718.         LD      (HL),$80        ; place end-marker at end.
  2719.         EX      DE,HL           ; transfer first location to HL.
  2720.         POP     DE              ; restore length to DE.
  2721.         PUSH    HL              ; save start.
  2722.  
  2723.         PUSH    HL              ; and transfer it
  2724.         POP     IX              ; to IX register.
  2725.         SCF                     ; set carry flag to load data on tape.
  2726.         LD      A,$FF           ; signal data not a header.
  2727.         CALL    L0802           ; routine LD-BLOCK loads to workspace.
  2728.         POP     HL              ; restore first location in workspace to HL.
  2729. X08CE   LD      DE,($5C53)      ; set DE from system variable PROG.
  2730.  
  2731. ; now enter a loop to merge the data block in workspace with the program and
  2732. ; variables.
  2733.  
  2734. ;; ME-NEW-LP
  2735. L08D2:  LD      A,(HL)          ; fetch next byte from workspace.
  2736.         AND     $C0             ; compare with $3F.
  2737.         JR      NZ,L08F0        ; forward to ME-VAR-LP if a variable or
  2738.                                 ; end-marker.
  2739.  
  2740. ; continue when HL addresses a BASIC line number.
  2741.  
  2742. ;; ME-OLD-LP
  2743. L08D7:  LD      A,(DE)          ; fetch high byte from program area.
  2744.         INC     DE              ; bump prog address.
  2745.         CP      (HL)            ; compare with that in workspace.
  2746.         INC     HL              ; bump workspace address.
  2747.         JR      NZ,L08DF        ; forward to ME-OLD-L1 if high bytes don't match
  2748.  
  2749.         LD      A,(DE)          ; fetch the low byte of program line number.
  2750.         CP      (HL)            ; compare with that in workspace.
  2751.  
  2752. ;; ME-OLD-L1
  2753. L08DF:  DEC     DE              ; point to start of
  2754.         DEC     HL              ; respective lines again.
  2755.         JR      NC,L08EB        ; forward to ME-NEW-L2 if line number in
  2756.                                 ; workspace is less than or equal to current
  2757.                                 ; program line as has to be added to program.
  2758.  
  2759.         PUSH    HL              ; else save workspace pointer.
  2760.         EX      DE,HL           ; transfer prog pointer to HL
  2761.         CALL    L19B8           ; routine NEXT-ONE finds next line in DE.
  2762.         POP     HL              ; restore workspace pointer
  2763.         JR      L08D7           ; back to ME-OLD-LP until destination position
  2764.                                 ; in program area found.
  2765.  
  2766. ; ---
  2767. ; the branch was here with an insertion or replacement point.
  2768.  
  2769. ;; ME-NEW-L2
  2770. L08EB:  CALL    L092C           ; routine ME-ENTER enters the line
  2771.         JR      L08D2           ; loop back to ME-NEW-LP.
  2772.  
  2773. ; ---
  2774. ; the branch was here when the location in workspace held a variable.
  2775.  
  2776. ;; ME-VAR-LP
  2777. L08F0:  LD      A,(HL)          ; fetch first byte of workspace variable.
  2778.         LD      C,A             ; copy to C also.
  2779.         CP      $80             ; is it the end-marker ?
  2780.         RET     Z               ; return if so as complete.  >>>>>
  2781.  
  2782.         PUSH    HL              ; save workspace area pointer.
  2783.         LD      HL,($5C4B)      ; load HL with VARS - start of variables area.
  2784.  
  2785. ;; ME-OLD-VP
  2786. L08F9:  LD      A,(HL)          ; fetch first byte.
  2787.         CP      $80             ; is it the end-marker ?
  2788.         JR      Z,L0923         ; forward if so to ME-VAR-L2 to add
  2789.                                 ; variable at end of variables area.
  2790.  
  2791.         CP      C               ; compare with variable in workspace area.
  2792.         JR      Z,L0909         ; forward to ME-OLD-V2 if a match to replace.
  2793.  
  2794. ; else entire variables area has to be searched.
  2795.  
  2796. ;; ME-OLD-V1
  2797. L0901:  PUSH    BC              ; save character in C.
  2798.         CALL    L19B8           ; routine NEXT-ONE gets following variable
  2799.                                 ; address in DE.
  2800.         POP     BC              ; restore character in C
  2801.         EX      DE,HL           ; transfer next address to HL.
  2802.         JR      L08F9           ; loop back to ME-OLD-VP
  2803.  
  2804. ; ---
  2805. ; the branch was here when first characters of name matched.
  2806.  
  2807. ;; ME-OLD-V2
  2808. L0909:  AND     $E0             ; keep bits 11100000
  2809.         CP      $A0             ; compare   10100000 - a long-named variable.
  2810.  
  2811.         JR      NZ,L0921        ; forward to ME-VAR-L1 if just one-character.
  2812.  
  2813. ; but long-named variables have to be matched character by character.
  2814.  
  2815.         POP     DE              ; fetch workspace 1st character pointer
  2816.         PUSH    DE              ; and save it on the stack again.
  2817.         PUSH    HL              ; save variables area pointer on stack.
  2818.  
  2819. ;; ME-OLD-V3
  2820. L0912:  INC     HL              ; address next character in vars area.
  2821.         INC     DE              ; address next character in workspace area.
  2822.         LD      A,(DE)          ; fetch workspace character.
  2823.         CP      (HL)            ; compare to variables character.
  2824.         JR      NZ,L091E        ; forward to ME-OLD-V4 with a mismatch.
  2825.  
  2826.         RLA                     ; test if the terminal inverted character.
  2827.         JR      NC,L0912        ; loop back to ME-OLD-V3 if more to test.
  2828.  
  2829. ; otherwise the long name matches in its entirety.
  2830.  
  2831.         POP     HL              ; restore pointer to first character of variable
  2832.         JR      L0921           ; forward to ME-VAR-L1
  2833.  
  2834. ; ---
  2835. ; the branch is here when two characters don't match
  2836.  
  2837. ;; ME-OLD-V4
  2838. L091E:  POP     HL              ; restore the prog/vars pointer.
  2839.         JR      L0901           ; back to ME-OLD-V1 to resume search.
  2840.  
  2841. ; ---
  2842. ; branch here when variable is to replace an existing one
  2843.  
  2844. ;; ME-VAR-L1
  2845. L0921:  LD      A,$FF           ; indicate a replacement.
  2846.  
  2847. ; this entry point is when A holds $80 indicating a new variable.
  2848.  
  2849. ;; ME-VAR-L2
  2850. L0923:  POP     DE              ; pop workspace pointer.
  2851.         EX      DE,HL           ; now make HL workspace pointer, DE vars pointer
  2852.         INC     A               ; zero flag set if replacement.
  2853.         SCF                     ; set carry flag indicating a variable not a
  2854.                                 ; program line.
  2855.         CALL    L092C           ; routine ME-ENTER copies variable in.
  2856.         JR      L08F0           ; loop back to ME-VAR-LP
  2857.  
  2858. ; ------------------------
  2859. ; Merge a Line or Variable
  2860. ; ------------------------
  2861. ; A BASIC line or variable is inserted at the current point. If the line numbers
  2862. ; or variable names match (zero flag set) then a replacement takes place.
  2863.  
  2864. ;; ME-ENTER
  2865. L092C:  JR      NZ,L093E        ; forward to ME-ENT-1 for insertion only.
  2866.  
  2867. ; but the program line or variable matches so old one is reclaimed.
  2868.  
  2869.         EX      AF,AF'          ; save flag??
  2870.        LD      ($5C5F),HL      ; preserve workspace pointer in dynamic X_PTR
  2871.        EX      DE,HL           ; transfer program dest pointer to HL.
  2872.        CALL    L19B8           ; routine NEXT-ONE finds following location
  2873.                                ; in program or variables area.
  2874.        CALL    L19E8           ; routine RECLAIM-2 reclaims the space between.
  2875.        EX      DE,HL           ; transfer program dest pointer back to DE.
  2876.        LD      HL,($5C5F)      ; fetch adjusted workspace pointer from X_PTR
  2877.        EX      AF,AF'          ; restore flags.
  2878.  
  2879. ; now the new line or variable is entered.
  2880.  
  2881. ;; ME-ENT-1
  2882. L093E:  EX      AF,AF'          ; save or re-save flags.
  2883.        PUSH    DE              ; save dest pointer in prog/vars area.
  2884.        CALL    L19B8           ; routine NEXT-ONE finds next in workspace.
  2885.                                ; gets next in DE, difference in BC.
  2886.                                ; prev addr in HL
  2887.        LD      ($5C5F),HL      ; store pointer in X_PTR
  2888.        LD      HL,($5C53)      ; load HL from system variable PROG
  2889.        EX      (SP),HL         ; swap with prog/vars pointer on stack.
  2890.        PUSH    BC              ; ** save length of new program line/variable.
  2891.        EX      AF,AF'          ; fetch flags back.
  2892.         JR      C,L0955         ; skip to ME-ENT-2 if variable
  2893.  
  2894.         DEC     HL              ; address location before pointer
  2895.         CALL    L1655           ; routine MAKE-ROOM creates room for BASIC line
  2896.         INC     HL              ; address next.
  2897.         JR      L0958           ; forward to ME-ENT-3
  2898.  
  2899. ; ---
  2900.  
  2901. ;; ME-ENT-2
  2902. L0955:  CALL    L1655           ; routine MAKE-ROOM creates room for variable.
  2903.  
  2904. ;; ME-ENT-3
  2905. L0958:  INC     HL              ; address next?
  2906.  
  2907.         POP     BC              ; ** pop length
  2908.         POP     DE              ; * pop value for PROG which may have been
  2909.                                 ; altered by POINTERS if first line.
  2910.         LD      ($5C53),DE      ; set PROG to original value.
  2911.         LD      DE,($5C5F)      ; fetch adjusted workspace pointer from X_PTR
  2912.         PUSH    BC              ; save length
  2913.         PUSH    DE              ; and workspace pointer
  2914.         EX      DE,HL           ; make workspace pointer source, prog/vars
  2915.                                 ; pointer the destination
  2916.         LDIR                    ; copy bytes of line or variable into new area.
  2917.         POP     HL              ; restore workspace pointer.
  2918.         POP     BC              ; restore length.
  2919.         PUSH    DE              ; save new prog/vars pointer.
  2920.         CALL    L19E8           ; routine RECLAIM-2 reclaims the space used
  2921.                                 ; by the line or variable in workspace block
  2922.                                 ; as no longer required and space could be
  2923.                                 ; useful for adding more lines.
  2924.         POP     DE              ; restore the prog/vars pointer
  2925.         RET                     ; return.
  2926.  
  2927. ; -------------------
  2928. ; Handle SAVE control
  2929. ; -------------------
  2930. ; A branch from the main SAVE-ETC routine at SAVE-ALL.
  2931. ; First the header data is saved. Then after a wait of 1 second
  2932. ; the data itself is saved.
  2933. ; HL points to start of data.
  2934. ; IX points to start of descriptor.
  2935.  
  2936. ;; SA-CONTRL
  2937. L0970:  PUSH    HL              ; save start of data
  2938.  
  2939.         LD      A,$FD           ; select system channel 'S'
  2940.         CALL    L1601           ; routine CHAN-OPEN
  2941.  
  2942.         XOR     A               ; clear to address table directly
  2943.         LD      DE,L09A1        ; address: tape-msgs
  2944.         CALL    L0C0A           ; routine PO-MSG -
  2945.                                 ; 'Start tape then press any key.'
  2946.  
  2947.         SET     5,(IY+$02)      ; TV_FLAG  - Signal lower screen requires
  2948.                                 ; clearing
  2949.         CALL    L15D4           ; routine WAIT-KEY
  2950.  
  2951.         PUSH    IX              ; save pointer to descriptor.
  2952.         LD      DE,$0011        ; there are seventeen bytes.
  2953.         XOR     A               ; signal a header.
  2954.         CALL    L04C2           ; routine SA-BYTES
  2955.  
  2956.         POP     IX              ; restore descriptor pointer.
  2957.  
  2958.         LD      B,$32           ; wait for a second - 50 interrupts.
  2959.  
  2960. ;; SA-1-SEC
  2961. L0991:  HALT                    ; wait for interrupt
  2962.         DJNZ    L0991           ; back to SA-1-SEC until pause complete.
  2963.  
  2964.         LD      E,(IX+$0B)      ; fetch length of bytes from the
  2965.         LD      D,(IX+$0C)      ; descriptor.
  2966.  
  2967.         LD      A,$FF           ; signal data bytes.
  2968.  
  2969.         POP     IX              ; retrieve pointer to start
  2970.         JP      L04C2           ; jump back to SA-BYTES
  2971.  
  2972.  
  2973. ; Arrangement of two headers in workspace.
  2974. ; Originally IX addresses first location and only one header is required
  2975. ; when saving.
  2976. ;
  2977. ;   OLD     NEW         PROG   DATA  DATA  CODE
  2978. ;   HEADER  HEADER             num   chr          NOTES.
  2979. ;   ------  ------      ----   ----  ----  ----   -----------------------------
  2980. ;   IX-$11  IX+$00      0      1     2     3      Type.
  2981. ;   IX-$10  IX+$01      x      x     x     x      F  ($FF if filename is null).
  2982. ;   IX-$0F  IX+$02      x      x     x     x      i
  2983. ;   IX-$0E  IX+$03      x      x     x     x      l
  2984. ;   IX-$0D  IX+$04      x      x     x     x      e
  2985. ;   IX-$0C  IX+$05      x      x     x     x      n
  2986. ;   IX-$0B  IX+$06      x      x     x     x      a
  2987. ;   IX-$0A  IX+$07      x      x     x     x      m
  2988. ;   IX-$09  IX+$08      x      x     x     x      e
  2989. ;   IX-$08  IX+$09      x      x     x     x      .
  2990. ;   IX-$07  IX+$0A      x      x     x     x      (terminal spaces).
  2991. ;   IX-$06  IX+$0B      lo     lo    lo    lo     Total  
  2992. ;   IX-$05  IX+$0C      hi     hi    hi    hi     Length of datablock.
  2993. ;   IX-$04  IX+$0D      Auto   -     -     Start  Various
  2994. ;   IX-$03  IX+$0E      Start  a-z   a-z   addr   ($80 if no autostart).
  2995. ;   IX-$02  IX+$0F      lo     -     -     -      Length of Program
  2996. ;   IX-$01  IX+$10      hi     -     -     -      only i.e. without variables.
  2997. ;
  2998.  
  2999.  
  3000. ; ------------------------
  3001. ; Canned cassette messages
  3002. ; ------------------------
  3003. ; The last-character-inverted Cassette messages.
  3004. ; Starts with normal initial step-over byte.
  3005.  
  3006. ;; tape-msgs
  3007. L09A1           DB $80
  3008.                 DC "Start tape, then press any key."    ;DEFM    "Start tape, then press any key"
  3009. L09C0           EQU $-1                                 ;DB    '.'+$80
  3010.                 DB $0D
  3011.                 DC "Program: "                          ;DEFM    "Program:"
  3012.                                                         ;DB    ' '+$80
  3013.                 DB $0D
  3014.                 DC "Number array: "                     ;DEFM    "Number array:"
  3015.                                                         ;DB    ' '+$80
  3016.                 DB $0D
  3017.                 DC "Character array: "                  ;DEFM    "Character array:"
  3018.                                                         ;DB    ' '+$80
  3019.                 DB $0D
  3020.                 DC "Bytes: "                            ;DEFM    "Bytes:"
  3021.                                                         ;DB    ' '+$80
  3022. ;               DB    ' '+$80
  3023.  
  3024.  
  3025. ;**************************************************
  3026. ;** Part 5. SCREEN AND PRINTER HANDLING ROUTINES **
  3027. ;**************************************************
  3028.  
  3029. ; ---------------------
  3030. ; General PRINT routine
  3031. ; ---------------------
  3032. ; This is the routine most often used by the RST 10 restart although the
  3033. ; subroutine is on two occasions called directly when it is known that
  3034. ; output will definitely be to the lower screen.
  3035.  
  3036. ;; PRINT-OUT
  3037. L09F4:  CALL    L0B03           ; routine PO-FETCH fetches print position
  3038.                                 ; to HL register pair.
  3039.         CP      $20             ; is character a space or higher ?
  3040.         JP      NC,L0AD9        ; jump forward to PO-ABLE if so.
  3041.  
  3042.         CP      $06             ; is character in range 00-05 ?
  3043.         JR      C,L0A69         ; to PO-QUEST to print '?' if so.
  3044.  
  3045.         CP      $18             ; is character in range 24d - 31d ?
  3046.         JR      NC,L0A69        ; to PO-QUEST to also print '?' if so.
  3047.  
  3048.         LD      HL,L0A11 - 6    ; address 0A0B - the base address of control
  3049.                                 ; character table - where zero would be.
  3050.         LD      E,A             ; control character 06 - 23d
  3051.         LD      D,$00           ; is transferred to DE.
  3052.  
  3053.         ADD     HL,DE           ; index into table.
  3054.  
  3055.         LD      E,(HL)          ; fetch the offset to routine.
  3056.         ADD     HL,DE           ; add to make HL the address.
  3057.         PUSH    HL              ; push the address.
  3058.         JP      L0B03           ; to PO-FETCH, as the screen/printer position
  3059.                                 ; has been disturbed, and indirectly to
  3060.                                 ; routine on stack.
  3061.  
  3062. ; -----------------------
  3063. ; Control character table
  3064. ; -----------------------
  3065. ; For control characters in the range 6 - 23d the following table
  3066. ; is indexed to provide an offset to the handling routine that
  3067. ; follows the table.
  3068.  
  3069. ;; ctlchrtab
  3070. L0A11:  DB    L0A5F - $       ; 06d offset $4E to Address: PO-COMMA
  3071.         DB    L0A69 - $       ; 07d offset $57 to Address: PO-QUEST
  3072.         DB    L0A23 - $       ; 08d offset $10 to Address: PO-BACK-1
  3073.         DB    L0A3D - $       ; 09d offset $29 to Address: PO-RIGHT
  3074.         DB    L0A69 - $       ; 10d offset $54 to Address: PO-QUEST
  3075.         DB    L0A69 - $       ; 11d offset $53 to Address: PO-QUEST
  3076.         DB    L0A69 - $       ; 12d offset $52 to Address: PO-QUEST
  3077.         DB    L0A4F - $       ; 13d offset $37 to Address: PO-ENTER
  3078.         DB    L0A69 - $       ; 14d offset $50 to Address: PO-QUEST
  3079.         DB    L0A69 - $       ; 15d offset $4F to Address: PO-QUEST
  3080.         DB    L0A7A - $       ; 16d offset $5F to Address: PO-1-OPER
  3081.         DB    L0A7A - $       ; 17d offset $5E to Address: PO-1-OPER
  3082.         DB    L0A7A - $       ; 18d offset $5D to Address: PO-1-OPER
  3083.         DB    L0A7A - $       ; 19d offset $5C to Address: PO-1-OPER
  3084.         DB    L0A7A - $       ; 20d offset $5B to Address: PO-1-OPER
  3085.         DB    L0A7A - $       ; 21d offset $5A to Address: PO-1-OPER
  3086.         DB    L0A75 - $       ; 22d offset $54 to Address: PO-2-OPER
  3087.         DB    L0A75 - $       ; 23d offset $53 to Address: PO-2-OPER
  3088.  
  3089.  
  3090. ; -------------------
  3091. ; Cursor left routine
  3092. ; -------------------
  3093. ; Backspace and up a line if that action is from the left of screen.
  3094. ; For ZX printer backspace up to first column but not beyond.
  3095.  
  3096. ;; PO-BACK-1
  3097. L0A23:  INC     C               ; move left one column.
  3098.         LD      A,$22           ; value $21 is leftmost column.
  3099.         CP      C               ; have we passed ?
  3100.         JR      NZ,L0A3A        ; to PO-BACK-3 if not and store new position.
  3101.  
  3102.         BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  3103.         JR      NZ,L0A38        ; to PO-BACK-2 if so, as we are unable to
  3104.                                 ; backspace from the leftmost position.
  3105.  
  3106.  
  3107.         INC     B               ; move up one screen line
  3108.         LD      C,$02           ; the rightmost column position.
  3109.         LD      A,$18           ; Note. This should be $19
  3110.                                 ; credit. Dr. Frank O'Hara, 1982
  3111.  
  3112.         CP      B               ; has position moved past top of screen ?
  3113.         JR      NZ,L0A3A        ; to PO-BACK-3 if not and store new position.
  3114.  
  3115.         DEC     B               ; else back to $18.
  3116.  
  3117. ;; PO-BACK-2
  3118. L0A38:  LD      C,$21           ; the leftmost column position.
  3119.  
  3120. ;; PO-BACK-3
  3121. L0A3A:  JP      L0DD9           ; to CL-SET and PO-STORE to save new
  3122.                                 ; position in system variables.
  3123.  
  3124. ; --------------------
  3125. ; Cursor right routine
  3126. ; --------------------
  3127. ; This moves the print position to the right leaving a trail in the
  3128. ; current background colour.
  3129. ; "However the programmer has failed to store the new print position
  3130. ;  so CHR$ 9 will only work if the next print position is at a newly
  3131. ;  defined place.
  3132. ;   e.g. PRINT PAPER 2; CHR$ 9; AT 4,0;
  3133. ;  does work but is not very helpful"
  3134. ; - Dr. Ian Logan, Understanding Your Spectrum, 1982.
  3135.  
  3136. ;; PO-RIGHT
  3137. L0A3D:  LD      A,($5C91)       ; fetch P_FLAG value
  3138.         PUSH    AF              ; and save it on stack.
  3139.  
  3140.         LD      (IY+$57),$01    ; temporarily set P_FLAG 'OVER 1'.
  3141.         LD      A,$20           ; prepare a space.
  3142.         CALL    L0B65           ; routine PO-CHAR to print it.
  3143.                                 ; Note. could be PO-ABLE which would update
  3144.                                 ; the column position.
  3145.  
  3146.         POP     AF              ; restore the permanent flag.
  3147.         LD      ($5C91),A       ; and restore system variable P_FLAG
  3148.  
  3149.         RET                     ; return without updating column position
  3150.  
  3151. ; -----------------------
  3152. ; Perform carriage return
  3153. ; -----------------------
  3154. ; A carriage return is 'printed' to screen or printer buffer.
  3155.  
  3156. ;; PO-ENTER
  3157. L0A4F:  BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  3158.         JP      NZ,L0ECD        ; to COPY-BUFF if so, to flush buffer and reset
  3159.                                 ; the print position.
  3160.  
  3161.         LD      C,$21           ; the leftmost column position.
  3162.         CALL    L0C55           ; routine PO-SCR handles any scrolling required.
  3163.         DEC     B               ; to next screen line.
  3164.         JP      L0DD9           ; jump forward to CL-SET to store new position.
  3165.  
  3166. ; -----------
  3167. ; Print comma
  3168. ; -----------
  3169. ; The comma control character. The 32 column screen has two 16 character
  3170. ; tabstops.  The routine is only reached via the control character table.
  3171.  
  3172. ;; PO-COMMA
  3173. L0A5F:  CALL    L0B03           ; routine PO-FETCH - seems unnecessary.
  3174.  
  3175.         LD      A,C             ; the column position. $21-$01
  3176.         DEC     A               ; move right. $20-$00
  3177.         DEC     A               ; and again   $1F-$00 or $FF if trailing
  3178.         AND     $10             ; will be $00 or $10.
  3179.         JR      L0AC3           ; forward to PO-FILL
  3180.  
  3181. ; -------------------
  3182. ; Print question mark
  3183. ; -------------------
  3184. ; This routine prints a question mark which is commonly
  3185. ; used to print an unassigned control character in range 0-31d.
  3186. ; there are a surprising number yet to be assigned.
  3187.  
  3188. ;; PO-QUEST
  3189. L0A69:  LD      A,$3F           ; prepare the character '?'.
  3190.         JR      L0AD9           ; forward to PO-ABLE.
  3191.  
  3192. ; --------------------------------
  3193. ; Control characters with operands
  3194. ; --------------------------------
  3195. ; Certain control characters are followed by 1 or 2 operands.
  3196. ; The entry points from control character table are PO-2-OPER and PO-1-OPER.
  3197. ; The routines alter the output address of the current channel so that
  3198. ; subsequent RST $10 instructions take the appropriate action
  3199. ; before finally resetting the output address back to PRINT-OUT.
  3200.  
  3201. ;; PO-TV-2
  3202. L0A6D:  LD      DE,L0A87        ; address: PO-CONT will be next output routine
  3203.         LD      ($5C0F),A       ; store first operand in TVDATA-hi
  3204.         JR      L0A80           ; forward to PO-CHANGE >>
  3205.  
  3206. ; ---
  3207.  
  3208. ; -> This initial entry point deals with two operands - AT or TAB.
  3209.  
  3210. ;; PO-2-OPER
  3211. L0A75:  LD      DE,L0A6D        ; address: PO-TV-2 will be next output routine
  3212.         JR      L0A7D           ; forward to PO-TV-1
  3213.  
  3214. ; ---
  3215.  
  3216. ; -> This initial entry point deals with one operand INK to OVER.
  3217.  
  3218. ;; PO-1-OPER
  3219. L0A7A:  LD      DE,L0A87        ; address: PO-CONT will be next output routine
  3220.  
  3221. ;; PO-TV-1
  3222. L0A7D:  LD      ($5C0E),A       ; store control code in TVDATA-lo
  3223.  
  3224. ;; PO-CHANGE
  3225. L0A80:  LD      HL,($5C51)      ; use CURCHL to find current output channel.
  3226.         LD      (HL),E          ; make it
  3227.         INC     HL              ; the supplied
  3228.         LD      (HL),D          ; address from DE.
  3229.         RET                     ; return.
  3230.  
  3231. ; ---
  3232.  
  3233. ;; PO-CONT
  3234. L0A87:  LD      DE,L09F4        ; Address: PRINT-OUT
  3235.         CALL    L0A80           ; routine PO-CHANGE to restore normal channel.
  3236.         LD      HL,($5C0E)      ; TVDATA gives control code and possible
  3237.                                 ; subsequent character
  3238.         LD      D,A             ; save current character
  3239.         LD      A,L             ; the stored control code
  3240.         CP      $16             ; was it INK to OVER (1 operand) ?
  3241.         JP      C,L2211         ; to CO-TEMP-5
  3242.  
  3243.         JR      NZ,L0AC2        ; to PO-TAB if not 22d i.e. 23d TAB.
  3244.  
  3245.                                 ; else must have been 22d AT.
  3246.         LD      B,H             ; line to H   (0-23d)
  3247.         LD      C,D             ; column to C (0-31d)
  3248.         LD      A,$1F           ; the value 31d
  3249.         SUB     C               ; reverse the column number.
  3250.         JR      C,L0AAC         ; to PO-AT-ERR if C was greater than 31d.
  3251.  
  3252.         ADD     A,$02           ; transform to system range $02-$21
  3253.         LD      C,A             ; and place in column register.
  3254.  
  3255.         BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  3256.         JR      NZ,L0ABF        ; to PO-AT-SET as line can be ignored.
  3257.  
  3258.         LD      A,$16           ; 22 decimal
  3259.         SUB     B               ; subtract line number to reverse
  3260.                                 ; 0 - 22 becomes 22 - 0.
  3261.  
  3262. ;; PO-AT-ERR
  3263. L0AAC:  JP      C,L1E9F         ; to REPORT-B if higher than 22 decimal
  3264.                                 ; Integer out of range.
  3265.  
  3266.         INC     A               ; adjust for system range $01-$17
  3267.         LD      B,A             ; place in line register
  3268.         INC     B               ; adjust to system range  $02-$18
  3269.         BIT     0,(IY+$02)      ; TV_FLAG  - Lower screen in use ?
  3270.         JP      NZ,L0C55        ; exit to PO-SCR to test for scrolling
  3271.  
  3272.         CP      (IY+$31)        ; Compare against DF_SZ
  3273.         JP      C,L0C86         ; to REPORT-5 if too low
  3274.                                 ; Out of screen.
  3275.  
  3276. ;; PO-AT-SET
  3277. L0ABF:  JP      L0DD9           ; print position is valid so exit via CL-SET
  3278.  
  3279. ; Continue here when dealing with TAB.
  3280. ; Note. In BASIC, TAB is followed by a 16-bit number and was initially
  3281. ; designed to work with any output device.
  3282.  
  3283. ;; PO-TAB
  3284. L0AC2:  LD      A,H             ; transfer parameter to A
  3285.                                 ; Losing current character -
  3286.                                 ; High byte of TAB parameter.
  3287.  
  3288.  
  3289. ;; PO-FILL
  3290. L0AC3:  CALL    L0B03           ; routine PO-FETCH, HL-addr, BC=line/column.
  3291.                                 ; column 1 (right), $21 (left)
  3292.         ADD     A,C             ; add operand to current column
  3293.         DEC     A               ; range 0 - 31+
  3294.         AND     $1F             ; make range 0 - 31d
  3295.         RET     Z               ; return if result zero
  3296.  
  3297.         LD      D,A             ; Counter to D
  3298.         SET     0,(IY+$01)      ; update FLAGS  - signal suppress leading space.
  3299.  
  3300. ;; PO-SPACE
  3301. L0AD0:  LD      A,$20           ; space character.
  3302.         CALL    L0C3B           ; routine PO-SAVE prints the character
  3303.                                 ; using alternate set (normal output routine)
  3304.         DEC     D               ; decrement counter.
  3305.         JR      NZ,L0AD0        ; to PO-SPACE until done
  3306.  
  3307.         RET                     ; return
  3308.  
  3309. ; ----------------------
  3310. ; Printable character(s)
  3311. ; ----------------------
  3312. ; This routine prints printable characters and continues into
  3313. ; the position store routine
  3314.  
  3315. ;; PO-ABLE
  3316. L0AD9:  CALL    L0B24           ; routine PO-ANY
  3317.                                 ; and continue into position store routine.
  3318.  
  3319. ; -------------------------------------
  3320. ; Store line, column, and pixel address
  3321. ; -------------------------------------
  3322. ; This routine updates the system variables associated with
  3323. ; The main screen, lower screen/input buffer or ZX printer.
  3324.  
  3325. ;; PO-STORE
  3326. L0ADC:  BIT     1,(IY+$01)      ; test FLAGS  - Is printer in use ?
  3327.         JR      NZ,L0AFC        ; to PO-ST-PR if so
  3328.  
  3329.         BIT     0,(IY+$02)      ; TV_FLAG  - Lower screen in use ?
  3330.         JR      NZ,L0AF0        ; to PO-ST-E if so
  3331.  
  3332.         LD      ($5C88),BC      ; S_POSN line/column upper screen
  3333.         LD      ($5C84),HL      ; DF_CC  display file address
  3334.         RET                     ;
  3335.  
  3336. ; ---
  3337.  
  3338. ;; PO-ST-E
  3339. L0AF0:  LD      ($5C8A),BC      ; SPOSNL line/column lower screen
  3340.         LD      ($5C82),BC      ; ECHO_E line/column input buffer
  3341.         LD      ($5C86),HL      ; DFCCL  lower screen memory address
  3342.         RET                     ;
  3343.  
  3344. ; ---
  3345.  
  3346. ;; PO-ST-PR
  3347. L0AFC:  LD      (IY+$45),C      ; P_POSN column position printer
  3348.         LD      ($5C80),HL      ; PR_CC  full printer buffer memory address
  3349.         RET                     ;
  3350.  
  3351. ; -------------------------
  3352. ; Fetch position parameters
  3353. ; -------------------------
  3354. ; This routine fetches the line/column and display file address
  3355. ; of the upper and lower screen or, if the printer is in use,
  3356. ; the column position and absolute memory address.
  3357. ; Note. that PR-CC-hi (23681) is used by this routine and the one above
  3358. ; and if, in accordance with the manual (that says this is unused), the
  3359. ; location has been used for other purposes, then subsequent output
  3360. ; to the printer buffer could corrupt a 256-byte section of memory.
  3361.  
  3362. ;; PO-FETCH
  3363. L0B03:  BIT     1,(IY+$01)      ; test FLAGS  - Is printer in use
  3364.         JR      NZ,L0B1D        ; to PO-F-PR if so
  3365.  
  3366.                                 ; assume upper screen
  3367.         LD      BC,($5C88)      ; S_POSN
  3368.         LD      HL,($5C84)      ; DF_CC display file address
  3369.         BIT     0,(IY+$02)      ; TV_FLAG  - Lower screen in use ?
  3370.         RET     Z               ; return if upper screen
  3371.  
  3372.                                 ; ah well, was lower screen
  3373.         LD      BC,($5C8A)      ; SPOSNL
  3374.         LD      HL,($5C86)      ; DFCCL
  3375.         RET                     ; return
  3376.  
  3377. ; ---
  3378.  
  3379. ;; PO-F-PR
  3380. L0B1D:  LD      C,(IY+$45)      ; P_POSN column only
  3381.         LD      HL,($5C80)      ; PR_CC printer buffer address
  3382.         RET                     ; return
  3383.  
  3384. ; -------------------
  3385. ; Print any character
  3386. ; -------------------
  3387. ; This routine is used to print any character in range 32d - 255d
  3388. ; It is only called from PO-ABLE which continues into PO-STORE
  3389.  
  3390. ;; PO-ANY
  3391. L0B24:  CP      $80             ; ASCII ?
  3392.         JR      C,L0B65         ; to PO-CHAR is so.
  3393.  
  3394.         CP      $90             ; test if a block graphic character.
  3395.         JR      NC,L0B52        ; to PO-T&UDG to print tokens and udg's
  3396.  
  3397. ; The 16 2*2 mosaic characters 128-143 decimal are formed from
  3398. ; bits 0-3 of the character.
  3399.  
  3400.         LD      B,A             ; save character
  3401.         CALL    L0B38           ; routine PO-GR-1 to construct top half
  3402.                                 ; then bottom half.
  3403.         CALL    L0B03           ; routine PO-FETCH fetches print position.
  3404.         LD      DE,$5C92        ; MEM-0 is location of 8 bytes of character
  3405.         JR      L0B7F           ; to PR-ALL to print to screen or printer
  3406.  
  3407. ; ---
  3408.  
  3409. ;; PO-GR-1
  3410. L0B38:  LD      HL,$5C92        ; address MEM-0 - a temporary buffer in
  3411.                                 ; systems variables which is normally used
  3412.                                 ; by the calculator.
  3413.         CALL    L0B3E           ; routine PO-GR-2 to construct top half
  3414.                                 ; and continue into routine to construct
  3415.                                 ; bottom half.
  3416.  
  3417. ;; PO-GR-2
  3418. L0B3E:  RR      B               ; rotate bit 0/2 to carry
  3419.         SBC     A,A             ; result $00 or $FF
  3420.         AND     $0F             ; mask off right hand side
  3421.         LD      C,A             ; store part in C
  3422.         RR      B               ; rotate bit 1/3 of original chr to carry
  3423.         SBC     A,A             ; result $00 or $FF
  3424.         AND     $F0             ; mask off left hand side
  3425.         OR      C               ; combine with stored pattern
  3426.         LD      C,$04           ; four bytes for top/bottom half
  3427.  
  3428. ;; PO-GR-3
  3429. L0B4C:  LD      (HL),A          ; store bit patterns in temporary buffer
  3430.         INC     HL              ; next address
  3431.         DEC     C               ; jump back to
  3432.         JR      NZ,L0B4C        ; to PO-GR-3 until byte is stored 4 times
  3433.  
  3434.         RET                     ; return
  3435.  
  3436. ; ---
  3437.  
  3438. ; Tokens and User defined graphics are now separated.
  3439.  
  3440. ;; PO-T&UDG
  3441. L0B52           IF BAS48_ONLY=1
  3442.                 SUB 0XA5
  3443.                 JR NC,L0B5F
  3444.                 ELSE
  3445.                 JP L3B9F                ;Spectrum 128 patch
  3446.                 NOP
  3447.                 ENDIF
  3448.  
  3449. L0B56:  ADD     A,$15           ; add 21d to restore to 0 - 20
  3450.         PUSH    BC              ; save current print position
  3451.         LD      BC,($5C7B)      ; fetch UDG to address bit patterns
  3452.         JR      L0B6A           ; to PO-CHAR-2 - common code to lay down
  3453.                                 ; a bit patterned character
  3454.  
  3455. ; ---
  3456.  
  3457. ;; PO-T
  3458. L0B5F:  CALL    L0C10           ; routine PO-TOKENS prints tokens
  3459.         JP      L0B03           ; exit via a JUMP to PO-FETCH as this routine
  3460.                                 ; must continue into PO-STORE.
  3461.                                 ; A JR instruction could be used.
  3462.  
  3463. ; This point is used to print ASCII characters  32d - 127d.
  3464.  
  3465. ;; PO-CHAR
  3466. L0B65:  PUSH    BC              ; save print position
  3467.         LD      BC,($5C36)      ; address CHARS
  3468.  
  3469. ; This common code is used to transfer the character bytes to memory.
  3470.  
  3471. ;; PO-CHAR-2
  3472. L0B6A:  EX      DE,HL           ; transfer destination address to DE
  3473.         LD      HL,$5C3B        ; point to FLAGS
  3474.         RES     0,(HL)          ; allow for leading space
  3475.         CP      $20             ; is it a space ?
  3476.         JR      NZ,L0B76        ; to PO-CHAR-3 if not
  3477.  
  3478.         SET     0,(HL)          ; signal no leading space to FLAGS
  3479.  
  3480. ;; PO-CHAR-3
  3481. L0B76:  LD      H,$00           ; set high byte to 0
  3482.         LD      L,A             ; character to A
  3483.                                 ; 0-21 UDG or 32-127 ASCII.
  3484.         ADD     HL,HL           ; multiply
  3485.         ADD     HL,HL           ; by
  3486.         ADD     HL,HL           ; eight
  3487.         ADD     HL,BC           ; HL now points to first byte of character
  3488.         POP     BC              ; the source address CHARS or UDG
  3489.         EX      DE,HL           ; character address to DE
  3490.  
  3491. ; --------------------
  3492. ; Print all characters
  3493. ; --------------------
  3494. ; This entry point entered from above to print ASCII and UDGs
  3495. ; but also from earlier to print mosaic characters.
  3496. ; HL=destination
  3497. ; DE=character source
  3498. ; BC=line/column
  3499.  
  3500. ;; PR-ALL
  3501. L0B7F:  LD      A,C             ; column to A
  3502.         DEC     A               ; move right
  3503.         LD      A,$21           ; pre-load with leftmost position
  3504.         JR      NZ,L0B93        ; but if not zero to PR-ALL-1
  3505.  
  3506.         DEC     B               ; down one line
  3507.         LD      C,A             ; load C with $21
  3508.         BIT     1,(IY+$01)      ; test FLAGS  - Is printer in use
  3509.         JR      Z,L0B93         ; to PR-ALL-1 if not
  3510.  
  3511.         PUSH    DE              ; save source address
  3512.         CALL    L0ECD           ; routine COPY-BUFF outputs line to printer
  3513.         POP     DE              ; restore character source address
  3514.         LD      A,C             ; the new column number ($21) to C
  3515.  
  3516. ;; PR-ALL-1
  3517. L0B93:  CP      C               ; this test is really for screen - new line ?
  3518.         PUSH    DE              ; save source
  3519.  
  3520.         CALL    Z,L0C55         ; routine PO-SCR considers scrolling
  3521.  
  3522.         POP     DE              ; restore source
  3523.         PUSH    BC              ; save line/column
  3524.         PUSH    HL              ; and destination
  3525.         LD      A,($5C91)       ; fetch P_FLAG to accumulator
  3526.         LD      B,$FF           ; prepare OVER mask in B.
  3527.         RRA                     ; bit 0 set if OVER 1
  3528.         JR      C,L0BA4         ; to PR-ALL-2
  3529.  
  3530.         INC     B               ; set OVER mask to 0
  3531.  
  3532. ;; PR-ALL-2
  3533. L0BA4:  RRA                     ; skip bit 1 of P_FLAG
  3534.         RRA                     ; bit 2 is INVERSE
  3535.         SBC     A,A             ; will be FF for INVERSE 1 else zero
  3536.         LD      C,A             ; transfer INVERSE mask to C
  3537.         LD      A,$08           ; prepare to count 8 bytes
  3538.         AND     A               ; clear carry to signal screen
  3539.         BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  3540.         JR      Z,L0BB6         ; to PR-ALL-3 if screen
  3541.  
  3542.         SET     1,(IY+$30)      ; update FLAGS2  - signal printer buffer has
  3543.                                 ; been used.
  3544.         SCF                     ; set carry flag to signal printer.
  3545.  
  3546. ;; PR-ALL-3
  3547. L0BB6:  EX      DE,HL           ; now HL=source, DE=destination
  3548.  
  3549. ;; PR-ALL-4
  3550. L0BB7:  EX      AF,AF'          ; save printer/screen flag
  3551.        LD      A,(DE)          ; fetch existing destination byte
  3552.        AND     B               ; consider OVER
  3553.        XOR     (HL)            ; now XOR with source
  3554.        XOR     C               ; now with INVERSE MASK
  3555.        LD      (DE),A          ; update screen/printer
  3556.        EX      AF,AF'          ; restore flag
  3557.         JR      C,L0BD3         ; to PR-ALL-6 - printer address update
  3558.  
  3559.         INC     D               ; gives next pixel line down screen
  3560.  
  3561. ;; PR-ALL-5
  3562. L0BC1:  INC     HL              ; address next character byte
  3563.         DEC     A               ; the byte count is decremented
  3564.         JR      NZ,L0BB7        ; back to PR-ALL-4 for all 8 bytes
  3565.  
  3566.         EX      DE,HL           ; destination to HL
  3567.         DEC     H               ; bring back to last updated screen position
  3568.         BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  3569.         CALL    Z,L0BDB         ; if not, call routine PO-ATTR to update
  3570.                                 ; corresponding colour attribute.
  3571.         POP     HL              ; restore original screen/printer position
  3572.         POP     BC              ; and line column
  3573.         DEC     C               ; move column to right
  3574.         INC     HL              ; increase screen/printer position
  3575.         RET                     ; return and continue into PO-STORE
  3576.                                 ; within PO-ABLE
  3577.  
  3578. ; ---
  3579.  
  3580. ; This branch is used to update the printer position by 32 places
  3581. ; Note. The high byte of the address D remains constant (which it should).
  3582.  
  3583. ;; PR-ALL-6
  3584. L0BD3:  EX      AF,AF'          ; save the flag
  3585.        LD      A,$20           ; load A with 32 decimal
  3586.        ADD     A,E             ; add this to E
  3587.        LD      E,A             ; and store result in E
  3588.        EX      AF,AF'          ; fetch the flag
  3589.         JR      L0BC1           ; back to PR-ALL-5
  3590.  
  3591. ; -------------
  3592. ; Set attribute
  3593. ; -------------
  3594. ; This routine is entered with the HL register holding the last screen
  3595. ; address to be updated by PRINT or PLOT.
  3596. ; The Spectrum screen arrangement leads to the L register holding
  3597. ; the correct value for the attribute file and it is only necessary
  3598. ; to manipulate H to form the correct colour attribute address.
  3599.  
  3600. ;; PO-ATTR
  3601. L0BDB:  LD       A,H            ; fetch high byte $40 - $57
  3602.         RRCA                    ; shift
  3603.         RRCA                    ; bits 3 and 4
  3604.         RRCA                    ; to right.
  3605.         AND     $03             ; range is now 0 - 2
  3606.         OR      $58             ; form correct high byte for third of screen
  3607.         LD      H,A             ; HL is now correct
  3608.         LD      DE,($5C8F)      ; make D hold ATTR_T, E hold MASK-T
  3609.         LD      A,(HL)          ; fetch existing attribute
  3610.         XOR     E               ; apply masks
  3611.         AND     D               ;
  3612.         XOR     E               ;
  3613.         BIT     6,(IY+$57)      ; test P_FLAG  - is this PAPER 9 ??
  3614.         JR      Z,L0BFA         ; skip to PO-ATTR-1 if not.
  3615.  
  3616.         AND     $C7             ; set paper
  3617.         BIT     2,A             ; to contrast with ink
  3618.         JR      NZ,L0BFA        ; skip to PO-ATTR-1
  3619.  
  3620.         XOR     $38             ;
  3621.  
  3622. ;; PO-ATTR-1
  3623. L0BFA:  BIT     4,(IY+$57)      ; test P_FLAG  - Is this INK 9 ??
  3624.         JR      Z,L0C08         ; skip to PO-ATTR-2 if not
  3625.  
  3626.         AND     $F8             ; make ink
  3627.         BIT     5,A             ; contrast with paper.
  3628.         JR      NZ,L0C08        ; to PO-ATTR-2
  3629.  
  3630.         XOR     $07             ;
  3631.  
  3632. ;; PO-ATTR-2
  3633. L0C08:  LD      (HL),A          ; save the new attribute.
  3634.         RET                     ; return.
  3635.  
  3636. ; ----------------
  3637. ; Message printing
  3638. ; ----------------
  3639. ; This entry point is used to print tape, boot-up, scroll? and error messages
  3640. ; On entry the DE register points to an initial step-over byte or
  3641. ; the inverted end-marker of the previous entry in the table.
  3642. ; A contains the message number, often zero to print first message.
  3643. ; (HL has nothing important usually P_FLAG)
  3644.  
  3645. ;; PO-MSG
  3646. L0C0A:  PUSH    HL              ; put hi-byte zero on stack to suppress
  3647.         LD      H,$00           ; trailing spaces
  3648.         EX      (SP),HL         ; ld h,0; push hl would have done ?.
  3649.         JR      L0C14           ; forward to PO-TABLE.
  3650.  
  3651. ; ---
  3652.  
  3653. ; This entry point prints the BASIC keywords, '<>' etc. from alt set
  3654.  
  3655. ;; PO-TOKENS
  3656. L0C10:  LD      DE,L0095        ; address: TKN-TABLE
  3657.         PUSH    AF              ; save the token number to control
  3658.                                 ; trailing spaces - see later *
  3659.  
  3660. ;; PO-TABLE
  3661. L0C14:  CALL    L0C41           ; routine PO-SEARCH will set carry for
  3662.                                 ; all messages and function words.
  3663. L0C17:  JR      C,L0C22         ; forward to PO-EACH if not a command,
  3664.                                 ; '<>' etc.
  3665.  
  3666.         LD      A,$20           ; prepare leading space
  3667.         BIT     0,(IY+$01)      ; test FLAGS  - leading space if not set
  3668.         CALL    Z,L0C3B         ; routine PO-SAVE to print a space
  3669.                                 ; without disturbing registers
  3670.  
  3671. ;; PO-EACH
  3672. L0C22:  LD      A,(DE)          ; fetch character
  3673.         AND     $7F             ; remove any inverted bit
  3674.         CALL    L0C3B           ; routine PO-SAVE to print using alternate
  3675.                                 ; set of registers.
  3676.         LD      A,(DE)          ; re-fetch character.
  3677.         INC     DE              ; address next
  3678.         ADD     A,A             ; was character inverted ?
  3679.                                 ; (this also doubles character)
  3680.         JR      NC,L0C22        ; back to PO-EACH if not
  3681.  
  3682.         POP     DE              ; * re-fetch trailing space flag to D (was A)
  3683.         CP      $48             ; was last character '$' ($24*2)
  3684.         JR      Z,L0C35         ; forward to PO-TR-SP to consider trailing
  3685.                                 ; space if so.
  3686.  
  3687.         CP      $82             ; was it < 'A' i.e. '#','>','=' from tokens
  3688.                                 ; or ' ','.' (from tape) or '?' from scroll
  3689.         RET     C               ; no trailing space
  3690.  
  3691. ;; PO-TR-SP
  3692. L0C35:  LD      A,D             ; the trailing space flag (zero if an error msg)
  3693.         CP      $03             ; test against RND, INKEY$ and PI
  3694.                                 ; which have no parameters and
  3695.         RET     C               ; therefore no trailing space so return.
  3696.  
  3697.         LD      A,$20           ; else continue and print a trailing space.
  3698.  
  3699. ; -------------------------
  3700. ; Handle recursive printing
  3701. ; -------------------------
  3702. ; This routine which is part of PRINT-OUT allows RST $10 to be
  3703. ; used recursively to print tokens and the spaces associated with them.
  3704.  
  3705. ;; PO-SAVE
  3706. L0C3B:  PUSH    DE              ; save DE as CALL-SUB doesn't.
  3707.         EXX                     ; switch in main set
  3708.  
  3709.         RST     10H             ; PRINT-A prints using this alternate set.
  3710.  
  3711.         EXX                     ; back to this alternate set.
  3712.         POP     DE              ; restore initial DE.
  3713.         RET                     ; return.
  3714.  
  3715. ; ------------
  3716. ; Table search
  3717. ; ------------
  3718. ; This subroutine searches a message or the token table for the
  3719. ; message number held in A. DE holds the address of the table.
  3720.  
  3721. ;; PO-SEARCH
  3722. L0C41:  PUSH    AF              ; save the message/token number
  3723.         EX      DE,HL           ; transfer DE to HL
  3724.         INC     A               ; adjust for initial step-over byte
  3725.  
  3726. ;; PO-STEP
  3727. L0C44:  BIT     7,(HL)          ; is character inverted ?
  3728.         INC     HL              ; address next
  3729.         JR      Z,L0C44         ; back to PO-STEP if not inverted.
  3730.  
  3731.         DEC     A               ; decrease counter
  3732.         JR      NZ,L0C44        ; back to PO-STEP if not zero
  3733.  
  3734.         EX      DE,HL           ; transfer address to DE
  3735.         POP     AF              ; restore message/token number
  3736.         CP      $20             ; return with carry set
  3737.         RET     C               ; for all messages and function tokens
  3738.  
  3739.         LD      A,(DE)          ; test first character of token
  3740.         SUB     $41             ; and return with carry set
  3741.         RET                     ; if it is less that 'A'
  3742.                                 ; i.e. '<>', '<=', '>='
  3743.  
  3744. ; ---------------
  3745. ; Test for scroll
  3746. ; ---------------
  3747. ; This test routine is called when printing carriage return, when considering
  3748. ; PRINT AT and from the general PRINT ALL characters routine to test if
  3749. ; scrolling is required, prompting the user if necessary.
  3750. ; This is therefore using the alternate set.
  3751. ; The B register holds the current line.
  3752.  
  3753. ;; PO-SCR
  3754. L0C55:  BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  3755.         RET     NZ              ; return immediately if so.
  3756.  
  3757.         LD      DE,L0DD9        ; set DE to address: CL-SET
  3758.         PUSH    DE              ; and push for return address.
  3759.         LD      A,B             ; transfer the line to A.
  3760.         BIT     0,(IY+$02)      ; test TV_FLAG  - Lower screen in use ?
  3761.         JP      NZ,L0D02        ; jump forward to PO-SCR-4 if so.
  3762.  
  3763.         CP      (IY+$31)        ; greater than DF_SZ display file size ?
  3764.         JR      C,L0C86         ; forward to REPORT-5 if less.
  3765.                                 ; 'Out of screen'
  3766.  
  3767.         RET     NZ              ; return (via CL-SET) if greater
  3768.  
  3769.         BIT     4,(IY+$02)      ; test TV_FLAG  - Automatic listing ?
  3770.         JR      Z,L0C88         ; forward to PO-SCR-2 if not.
  3771.  
  3772.         LD      E,(IY+$2D)      ; fetch BREG - the count of scroll lines to E.
  3773.         DEC     E               ; decrease and jump
  3774.         JR      Z,L0CD2         ; to PO-SCR-3 if zero and scrolling required.
  3775.  
  3776.         LD      A,$00           ; explicit - select channel zero.
  3777.         CALL    L1601           ; routine CHAN-OPEN opens it.
  3778.  
  3779.         LD      SP,($5C3F)      ; set stack pointer to LIST_SP
  3780.  
  3781.         RES     4,(IY+$02)      ; reset TV_FLAG  - signal auto listing finished.
  3782.         RET                     ; return ignoring pushed value, CL-SET
  3783.                                 ; to MAIN or EDITOR without updating
  3784.                                 ; print position                         ->
  3785.  
  3786. ; ---
  3787.  
  3788.  
  3789. ;; REPORT-5
  3790. L0C86:  RST     08H             ; ERROR-1
  3791.         DB    $04             ; Error Report: Out of screen
  3792.  
  3793. ; continue here if not an automatic listing.
  3794.  
  3795. ;; PO-SCR-2
  3796. L0C88:  DEC     (IY+$52)        ; decrease SCR_CT
  3797.         JR      NZ,L0CD2        ; forward to PO-SCR-3 to scroll display if
  3798.                                 ; result not zero.
  3799.  
  3800. ; now produce prompt.
  3801.  
  3802.         LD      A,$18           ; reset
  3803.         SUB     B               ; the
  3804.         LD      ($5C8C),A       ; SCR_CT scroll count
  3805.         LD      HL,($5C8F)      ; L=ATTR_T, H=MASK_T
  3806.         PUSH    HL              ; save on stack
  3807.         LD      A,($5C91)       ; P_FLAG
  3808.         PUSH    AF              ; save on stack to prevent lower screen
  3809.                                 ; attributes (BORDCR etc.) being applied.
  3810.         LD      A,$FD           ; select system channel 'K'
  3811.         CALL    L1601           ; routine CHAN-OPEN opens it
  3812.         XOR     A               ; clear to address message directly
  3813.         LD      DE,L0CF8        ; make DE address: scrl-mssg
  3814.         CALL    L0C0A           ; routine PO-MSG prints to lower screen
  3815.         SET     5,(IY+$02)      ; set TV_FLAG  - signal lower screen requires
  3816.                                 ; clearing
  3817.         LD      HL,$5C3B        ; make HL address FLAGS
  3818.         SET     3,(HL)          ; signal 'L' mode.
  3819.         RES     5,(HL)          ; signal 'no new key'.
  3820.         EXX                     ; switch to main set.
  3821.                                 ; as calling chr input from alternative set.
  3822.         CALL    L15D4           ; routine WAIT-KEY waits for new key
  3823.                                 ; Note. this is the right routine but the
  3824.                                 ; stream in use is unsatisfactory. From the
  3825.                                 ; choices available, it is however the best.
  3826.  
  3827.         EXX                     ; switch back to alternate set.
  3828.         CP      $20             ; space is considered as BREAK
  3829.         JR      Z,L0D00         ; forward to REPORT-D if so
  3830.                                 ; 'BREAK - CONT repeats'
  3831.  
  3832.         CP      $E2             ; is character 'STOP' ?
  3833.         JR      Z,L0D00         ; forward to REPORT-D if so
  3834.  
  3835.         OR      $20             ; convert to lower-case
  3836.         CP      $6E             ; is character 'n' ?
  3837.         JR      Z,L0D00         ; forward to REPORT-D if so else scroll.
  3838.  
  3839.         LD      A,$FE           ; select system channel 'S'
  3840.         CALL    L1601           ; routine CHAN-OPEN
  3841.         POP     AF              ; restore original P_FLAG
  3842.         LD      ($5C91),A       ; and save in P_FLAG.
  3843.         POP     HL              ; restore original ATTR_T, MASK_T
  3844.         LD      ($5C8F),HL      ; and reset ATTR_T, MASK-T as 'scroll?' has
  3845.                                 ; been printed.
  3846.  
  3847. ;; PO-SCR-3
  3848. L0CD2:  CALL    L0DFE           ; routine CL-SC-ALL to scroll whole display
  3849.         LD      B,(IY+$31)      ; fetch DF_SZ to B
  3850.         INC     B               ; increase to address last line of display
  3851.         LD      C,$21           ; set C to $21 (was $21 from above routine)
  3852.         PUSH    BC              ; save the line and column in BC.
  3853.  
  3854.         CALL    L0E9B           ; routine CL-ADDR finds display address.
  3855.  
  3856.         LD      A,H             ; now find the corresponding attribute byte
  3857.         RRCA                    ; (this code sequence is used twice
  3858.         RRCA                    ; elsewhere and is a candidate for
  3859.         RRCA                    ; a subroutine.)
  3860.         AND     $03             ;
  3861.         OR      $58             ;
  3862.         LD      H,A             ;
  3863.  
  3864.         LD      DE,$5AE0        ; start of last 'line' of attribute area
  3865.         LD      A,(DE)          ; get attribute for last line
  3866.         LD      C,(HL)          ; transfer to base line of upper part
  3867.         LD      B,$20           ; there are thirty two bytes
  3868.         EX      DE,HL           ; swap the pointers.
  3869.  
  3870. ;; PO-SCR-3A
  3871. L0CF0:  LD      (DE),A          ; transfer
  3872.         LD      (HL),C          ; attributes.
  3873.         INC     DE              ; address next.
  3874.         INC     HL              ; address next.
  3875.         DJNZ    L0CF0           ; loop back to PO-SCR-3A for all adjacent
  3876.                                 ; attribute lines.
  3877.  
  3878.         POP     BC              ; restore the line/column.
  3879.         RET                     ; return via CL-SET (was pushed on stack).
  3880.  
  3881. ; ---
  3882.  
  3883. ; The message 'scroll?' appears here with last byte inverted.
  3884.  
  3885. ;; scrl-mssg
  3886. L0CF8           DB $80             ; initial step-over byte.
  3887.                 DC "scroll?"    ;DEFM    "scroll"
  3888.                                 ;DB    '?'+$80
  3889.  
  3890. ;; REPORT-D
  3891. L0D00:  RST     08H             ; ERROR-1
  3892.         DB    $0C             ; Error Report: BREAK - CONT repeats
  3893.  
  3894. ; continue here if using lower display - A holds line number.
  3895.  
  3896. ;; PO-SCR-4
  3897. L0D02:  CP      $02             ; is line number less than 2 ?
  3898.         JR      C,L0C86         ; to REPORT-5 if so
  3899.                                 ; 'Out of Screen'.
  3900.  
  3901.         ADD     A,(IY+$31)      ; add DF_SZ
  3902.         SUB     $19             ;
  3903.         RET     NC              ; return if scrolling unnecessary
  3904.  
  3905.         NEG                     ; Negate to give number of scrolls required.
  3906.         PUSH    BC              ; save line/column
  3907.         LD      B,A             ; count to B
  3908.         LD      HL,($5C8F)      ; fetch current ATTR_T, MASK_T to HL.
  3909.         PUSH    HL              ; and save
  3910.         LD      HL,($5C91)      ; fetch P_FLAG
  3911.         PUSH    HL              ; and save.
  3912.                                 ; to prevent corruption by input AT
  3913.  
  3914.         CALL    L0D4D           ; routine TEMPS sets to BORDCR etc
  3915.         LD      A,B             ; transfer scroll number to A.
  3916.  
  3917. ;; PO-SCR-4A
  3918. L0D1C:  PUSH    AF              ; save scroll number.
  3919.         LD      HL,$5C6B        ; address DF_SZ
  3920.         LD      B,(HL)          ; fetch old value
  3921.         LD      A,B             ; transfer to A
  3922.         INC     A               ; and increment
  3923.         LD      (HL),A          ; then put back.
  3924.         LD      HL,$5C89        ; address S_POSN_hi - line
  3925.         CP      (HL)            ; compare
  3926.         JR      C,L0D2D         ; forward to PO-SCR-4B if scrolling required
  3927.  
  3928.         INC     (HL)            ; else increment S_POSN_hi
  3929.         LD      B,$18           ; set count to whole display ??
  3930.                                 ; Note. should be $17 and the top line
  3931.                                 ; will be scrolled into the ROM which
  3932.                                 ; is harmless on the standard set up.
  3933.  
  3934. ;; PO-SCR-4B
  3935. L0D2D:  CALL    L0E00           ; routine CL-SCROLL scrolls B lines
  3936.         POP     AF              ; restore scroll counter.
  3937.         DEC     A               ; decrease
  3938.         JR      NZ,L0D1C        ; back to to PO-SCR-4A until done
  3939.  
  3940.         POP     HL              ; restore original P_FLAG.
  3941.         LD      (IY+$57),L      ; and overwrite system variable P_FLAG.
  3942.  
  3943.         POP     HL              ; restore original ATTR_T/MASK_T.
  3944.         LD      ($5C8F),HL      ; and update system variables.
  3945.  
  3946.         LD      BC,($5C88)      ; fetch S_POSN to BC.
  3947.         RES     0,(IY+$02)      ; signal to TV_FLAG  - main screen in use.
  3948.         CALL    L0DD9           ; call routine CL-SET for upper display.
  3949.  
  3950.         SET     0,(IY+$02)      ; signal to TV_FLAG  - lower screen in use.
  3951.         POP     BC              ; restore line/column
  3952.         RET                     ; return via CL-SET for lower display.
  3953.  
  3954. ; ----------------------
  3955. ; Temporary colour items
  3956. ; ----------------------
  3957. ; This subroutine is called 11 times to copy the permanent colour items
  3958. ; to the temporary ones.
  3959.  
  3960. ;; TEMPS
  3961. L0D4D:  XOR     A               ; clear the accumulator
  3962.         LD      HL,($5C8D)      ; fetch L=ATTR_P and H=MASK_P
  3963.         BIT     0,(IY+$02)      ; test TV_FLAG  - is lower screen in use ?
  3964.         JR      Z,L0D5B         ; skip to TEMPS-1 if not
  3965.  
  3966.         LD      H,A             ; set H, MASK P, to 00000000.
  3967.         LD      L,(IY+$0E)      ; fetch BORDCR to L which is used for lower
  3968.                                 ; screen.
  3969.  
  3970. ;; TEMPS-1
  3971. L0D5B:  LD      ($5C8F),HL      ; transfer values to ATTR_T and MASK_T
  3972.  
  3973. ; for the print flag the permanent values are odd bits, temporary even bits.
  3974.  
  3975.         LD      HL,$5C91        ; address P_FLAG.
  3976.         JR      NZ,L0D65        ; skip to TEMPS-2 if lower screen using A=0.
  3977.  
  3978.         LD      A,(HL)          ; else pick up flag bits.
  3979.         RRCA                    ; rotate permanent bits to temporary bits.
  3980.  
  3981. ;; TEMPS-2
  3982. L0D65:  XOR     (HL)            ;
  3983.         AND     $55             ; BIN 01010101
  3984.         XOR     (HL)            ; permanent now as original
  3985.         LD      (HL),A          ; apply permanent bits to temporary bits.
  3986.         RET                     ; and return.
  3987.  
  3988. ; ------------------
  3989. ; Handle CLS command
  3990. ; ------------------
  3991. ; clears the display.
  3992. ; if it's difficult to write it should be difficult to read.
  3993.  
  3994. ;; CLS
  3995. L0D6B:  CALL    L0DAF           ; routine CL-ALL  clears display and
  3996.                                 ; resets attributes to permanent.
  3997.                                 ; re-attaches it to this computer.
  3998.  
  3999. ; this routine called from INPUT, **
  4000.  
  4001. ;; CLS-LOWER
  4002. L0D6E:  LD      HL,$5C3C        ; address System Variable TV_FLAG.
  4003.         RES     5,(HL)          ; TV_FLAG - signal do not clear lower screen.
  4004.         SET     0,(HL)          ; TV_FLAG - signal lower screen in use.
  4005.         CALL    L0D4D           ; routine TEMPS picks up temporary colours.
  4006.         LD      B,(IY+$31)      ; fetch lower screen DF_SZ
  4007.         CALL    L0E44           ; routine CL-LINE clears lower part
  4008.                                 ; and sets permanent attributes.
  4009.  
  4010.         LD      HL,$5AC0        ; fetch attribute address leftmost cell,
  4011.                                 ; second line up.
  4012.         LD      A,($5C8D)       ; fetch permanent attribute from ATTR_P.
  4013.         DEC     B               ; decrement lower screen display file size
  4014.         JR      L0D8E           ; forward to CLS-3 ->
  4015.  
  4016. ; ---
  4017.  
  4018. ;; CLS-1
  4019. L0D87:  LD      C,$20           ; set counter to 32 characters per line
  4020.  
  4021. ;; CLS-2
  4022. L0D89:  DEC     HL              ; decrease attribute address.
  4023.         LD      (HL),A          ; and place attributes in next line up.
  4024.         DEC     C               ; decrease 32 counter.
  4025.         JR      NZ,L0D89        ; loop back to CLS-2 until all 32 done.
  4026.  
  4027. ;; CLS-3
  4028. L0D8E:  DJNZ    L0D87           ; decrease B counter and back to CLS-1
  4029.                                 ; if not zero.
  4030.  
  4031.         LD      (IY+$31),$02    ; set DF_SZ lower screen to 2
  4032.  
  4033. ; This entry point is called from CL-ALL below to
  4034. ; reset the system channel input and output addresses to normal.
  4035.  
  4036. ;; CL-CHAN
  4037. L0D94:  LD      A,$FD           ; select system channel 'K'
  4038.         CALL    L1601           ; routine CHAN-OPEN opens it.
  4039.         LD      HL,($5C51)      ; fetch CURCHL to HL to address current channel
  4040.         LD      DE,L09F4        ; set address to PRINT-OUT for first pass.
  4041.         AND     A               ; clear carry for first pass.
  4042.  
  4043. ;; CL-CHAN-A
  4044. L0DA0:  LD      (HL),E          ; insert output address first pass.
  4045.         INC     HL              ; or input address on second pass.
  4046.         LD      (HL),D          ;
  4047.         INC     HL              ;
  4048.         LD      DE,L10A8        ; fetch address KEY-INPUT for second pass
  4049.         CCF                     ; complement carry flag - will set on pass 1.
  4050.  
  4051.         JR      C,L0DA0         ; back to CL-CHAN-A if first pass else done.
  4052.  
  4053.         LD      BC,$1721        ; line 23 for lower screen
  4054.         JR      L0DD9           ; exit via CL-SET to set column
  4055.                                 ; for lower display
  4056.  
  4057. ; ---------------------------
  4058. ; Clearing whole display area
  4059. ; ---------------------------
  4060. ; This subroutine called from CLS, AUTO-LIST and MAIN-3
  4061. ; clears 24 lines of the display and resets the relevant system variables
  4062. ; and system channels.
  4063.  
  4064. ;; CL-ALL
  4065. L0DAF:  LD      HL,$0000        ; initialize plot coordinates.
  4066.         LD      ($5C7D),HL      ; set COORDS to 0,0.
  4067.         RES     0,(IY+$30)      ; update FLAGS2  - signal main screen is clear.
  4068.  
  4069.         CALL    L0D94           ; routine CL-CHAN makes channel 'K' 'normal'.
  4070.  
  4071.         LD      A,$FE           ; select system channel 'S'
  4072.         CALL    L1601           ; routine CHAN-OPEN opens it
  4073.         CALL    L0D4D           ; routine TEMPS picks up permanent values.
  4074.         LD      B,$18           ; There are 24 lines.
  4075.         CALL    L0E44           ; routine CL-LINE clears 24 text lines
  4076.                                 ; (and sets BC to $1821)
  4077.  
  4078.         LD      HL,($5C51)      ; fetch CURCHL make HL address current
  4079.                                 ; channel 'S'
  4080.         LD      DE,L09F4        ; address: PRINT-OUT
  4081.         LD      (HL),E          ; is made
  4082.         INC     HL              ; the normal
  4083.         LD      (HL),D          ; output address.
  4084.  
  4085.         LD      (IY+$52),$01    ; set SCR_CT - scroll count is set to default.
  4086.                                 ; Note. BC already contains $1821.
  4087.         LD      BC,$1821        ; reset column and line to 0,0
  4088.                                 ; and continue into CL-SET, below, exiting
  4089.                                 ; via PO-STORE (for upper screen).
  4090.  
  4091. ; ---------------------------
  4092. ; Set line and column numbers
  4093. ; ---------------------------
  4094. ; This important subroutine is used to calculate the character output
  4095. ; address for screens or printer based on the line/column for screens
  4096. ; or the column for printer.
  4097.  
  4098. ;; CL-SET
  4099. L0DD9:  LD      HL,$5B00        ; the base address of printer buffer
  4100.         BIT     1,(IY+$01)      ; test FLAGS  - is printer in use ?
  4101.         JR      NZ,L0DF4        ; forward to CL-SET-2 if so.
  4102.  
  4103.         LD      A,B             ; transfer line to A.
  4104.         BIT     0,(IY+$02)      ; test TV_FLAG  - lower screen in use ?
  4105.         JR      Z,L0DEE         ; skip to CL-SET-1 if handling upper part
  4106.  
  4107.         ADD     A,(IY+$31)      ; add DF_SZ for lower screen
  4108.         SUB     $18             ; and adjust.
  4109.  
  4110. ;; CL-SET-1
  4111. L0DEE:  PUSH    BC              ; save the line/column.
  4112.         LD      B,A             ; transfer line to B
  4113.                                 ; (adjusted if lower screen)
  4114.  
  4115.         CALL    L0E9B           ; routine CL-ADDR calculates address at left
  4116.                                 ; of screen.
  4117.         POP     BC              ; restore the line/column.
  4118.  
  4119. ;; CL-SET-2
  4120. L0DF4:  LD      A,$21           ; the column $1-$21 is reversed
  4121.         SUB     C               ; to range $00 - $20
  4122.         LD      E,A             ; now transfer to DE
  4123.         LD      D,$00           ; prepare for addition
  4124.         ADD     HL,DE           ; and add to base address
  4125.         JP      L0ADC           ; exit via PO-STORE to update relevant
  4126.                                 ; system variables.
  4127. ; ----------------
  4128. ; Handle scrolling
  4129. ; ----------------
  4130. ; The routine CL-SC-ALL is called once from PO to scroll all the display
  4131. ; and from the routine CL-SCROLL, once, to scroll part of the display.
  4132.  
  4133. ;; CL-SC-ALL
  4134. L0DFE:  LD      B,$17           ; scroll 23 lines, after 'scroll?'.
  4135.  
  4136. ;; CL-SCROLL
  4137. L0E00:  CALL    L0E9B           ; routine CL-ADDR gets screen address in HL.
  4138.         LD      C,$08           ; there are 8 pixel lines to scroll.
  4139.  
  4140. ;; CL-SCR-1
  4141. L0E05:  PUSH    BC              ; save counters.
  4142.         PUSH    HL              ; and initial address.
  4143.         LD      A,B             ; get line count.
  4144.         AND     $07             ; will set zero if all third to be scrolled.
  4145.         LD      A,B             ; re-fetch the line count.
  4146.         JR      NZ,L0E19        ; forward to CL-SCR-3 if partial scroll.
  4147.  
  4148. ; HL points to top line of third and must be copied to bottom of previous 3rd.
  4149. ; ( so HL = $4800 or $5000 ) ( but also sometimes $4000 )
  4150.  
  4151. ;; CL-SCR-2
  4152. L0E0D:  EX      DE,HL           ; copy HL to DE.
  4153.         LD      HL,$F8E0        ; subtract $08 from H and add $E0 to L -
  4154.         ADD     HL,DE           ; to make destination bottom line of previous
  4155.                                 ; third.
  4156.         EX      DE,HL           ; restore the source and destination.
  4157.         LD      BC,$0020        ; thirty-two bytes are to be copied.
  4158.         DEC     A               ; decrement the line count.
  4159.         LDIR                    ; copy a pixel line to previous third.
  4160.  
  4161. ;; CL-SCR-3
  4162. L0E19:  EX      DE,HL           ; save source in DE.
  4163.         LD      HL,$FFE0        ; load the value -32.
  4164.         ADD     HL,DE           ; add to form destination in HL.
  4165.         EX      DE,HL           ; switch source and destination
  4166.         LD      B,A             ; save the count in B.
  4167.         AND     $07             ; mask to find count applicable to current
  4168.         RRCA                    ; third and
  4169.         RRCA                    ; multiply by
  4170.         RRCA                    ; thirty two (same as 5 RLCAs)
  4171.  
  4172.         LD      C,A             ; transfer byte count to C ($E0 at most)
  4173.         LD      A,B             ; store line count to A
  4174.         LD      B,$00           ; make B zero
  4175.         LDIR                    ; copy bytes (BC=0, H incremented, L=0)
  4176.         LD      B,$07           ; set B to 7, C is zero.
  4177.         ADD     HL,BC           ; add 7 to H to address next third.
  4178.         AND     $F8             ; has last third been done ?
  4179.         JR      NZ,L0E0D        ; back to CL-SCR-2 if not
  4180.  
  4181.         POP     HL              ; restore topmost address.
  4182.         INC     H               ; next pixel line down.
  4183.         POP     BC              ; restore counts.
  4184.         DEC     C               ; reduce pixel line count.
  4185.         JR      NZ,L0E05        ; back to CL-SCR-1 if all eight not done.
  4186.  
  4187.         CALL    L0E88           ; routine CL-ATTR gets address in attributes
  4188.                                 ; from current 'ninth line', count in BC.
  4189.         LD      HL,$FFE0        ; set HL to the 16-bit value -32.
  4190.         ADD     HL,DE           ; and add to form destination address.
  4191.         EX      DE,HL           ; swap source and destination addresses.
  4192.         LDIR                    ; copy bytes scrolling the linear attributes.
  4193.         LD      B,$01           ; continue to clear the bottom line.
  4194.  
  4195. ; ---------------------------
  4196. ; Clear text lines of display
  4197. ; ---------------------------
  4198. ; This subroutine, called from CL-ALL, CLS-LOWER and AUTO-LIST and above,
  4199. ; clears text lines at bottom of display.
  4200. ; The B register holds on entry the number of lines to be cleared 1-24.
  4201.  
  4202. ;; CL-LINE
  4203. L0E44:  PUSH    BC              ; save line count
  4204.         CALL    L0E9B           ; routine CL-ADDR gets top address
  4205.         LD      C,$08           ; there are eight screen lines to a text line.
  4206.  
  4207. ;; CL-LINE-1
  4208. L0E4A:  PUSH    BC              ; save pixel line count
  4209.         PUSH    HL              ; and save the address
  4210.         LD      A,B             ; transfer the line to A (1-24).
  4211.  
  4212. ;; CL-LINE-2
  4213. L0E4D:  AND     $07             ; mask 0-7 to consider thirds at a time
  4214.         RRCA                    ; multiply
  4215.         RRCA                    ; by 32  (same as five RLCA instructions)
  4216.         RRCA                    ; now 32 - 256(0)
  4217.         LD      C,A             ; store result in C
  4218.         LD      A,B             ; save line in A (1-24)
  4219.         LD      B,$00           ; set high byte to 0, prepare for ldir.
  4220.         DEC     C               ; decrement count 31-255.
  4221.         LD      D,H             ; copy HL
  4222.         LD      E,L             ; to DE.
  4223.         LD      (HL),$00        ; blank the first byte.
  4224.         INC     DE              ; make DE point to next byte.
  4225.         LDIR                    ; ldir will clear lines.
  4226.         LD      DE,$0701        ; now address next third adjusting
  4227.         ADD     HL,DE           ; register E to address left hand side
  4228.         DEC     A               ; decrease the line count.
  4229.         AND     $F8             ; will be 16, 8 or 0  (AND $18 will do).
  4230.         LD      B,A             ; transfer count to B.
  4231.         JR      NZ,L0E4D        ; back to CL-LINE-2 if 16 or 8 to do
  4232.                                 ; the next third.
  4233.  
  4234.         POP     HL              ; restore start address.
  4235.         INC     H               ; address next line down.
  4236.         POP     BC              ; fetch counts.
  4237.         DEC     C               ; decrement pixel line count
  4238.         JR      NZ,L0E4A        ; back to CL-LINE-1 till all done.
  4239.  
  4240.         CALL    L0E88           ; routine CL-ATTR gets attribute address
  4241.                                 ; in DE and B * 32 in BC.
  4242.         LD      H,D             ; transfer the address
  4243.         LD      L,E             ; to HL.
  4244.  
  4245.         INC     DE              ; make DE point to next location.
  4246.  
  4247.         LD      A,($5C8D)       ; fetch ATTR_P - permanent attributes
  4248.         BIT     0,(IY+$02)      ; test TV_FLAG  - lower screen in use ?
  4249.         JR      Z,L0E80         ; skip to CL-LINE-3 if not.
  4250.  
  4251.         LD      A,($5C48)       ; else lower screen uses BORDCR as attribute.
  4252.  
  4253. ;; CL-LINE-3
  4254. L0E80:  LD      (HL),A          ; put attribute in first byte.
  4255.         DEC     BC              ; decrement the counter.
  4256.         LDIR                    ; copy bytes to set all attributes.
  4257.         POP     BC              ; restore the line $01-$24.
  4258.         LD      C,$21           ; make column $21. (No use is made of this)
  4259.         RET                     ; return to the calling routine.
  4260.  
  4261. ; ------------------
  4262. ; Attribute handling
  4263. ; ------------------
  4264. ; This subroutine is called from CL-LINE or CL-SCROLL with the HL register
  4265. ; pointing to the 'ninth' line and H needs to be decremented before or after
  4266. ; the division. Had it been done first then either present code or that used
  4267. ; at the start of PO-ATTR could have been used.
  4268. ; The Spectrum screen arrangement leads to the L register holding already
  4269. ; the correct value for the attribute file and it is only necessary
  4270. ; to manipulate H to form the correct colour attribute address.
  4271.  
  4272. ;; CL-ATTR
  4273. L0E88:  LD      A,H             ; fetch H to A - $48, $50, or $58.
  4274.         RRCA                    ; divide by
  4275.         RRCA                    ; eight.
  4276.         RRCA                    ; $09, $0A or $0B.
  4277.         DEC     A               ; $08, $09 or $0A.
  4278.         OR      $50             ; $58, $59 or $5A.
  4279.         LD      H,A             ; save high byte of attributes.
  4280.  
  4281.         EX      DE,HL           ; transfer attribute address to DE
  4282.         LD      H,C             ; set H to zero - from last LDIR.
  4283.         LD      L,B             ; load L with the line from B.
  4284.         ADD     HL,HL           ; multiply
  4285.         ADD     HL,HL           ; by
  4286.         ADD     HL,HL           ; thirty two
  4287.         ADD     HL,HL           ; to give count of attribute
  4288.         ADD     HL,HL           ; cells to end of display.
  4289.  
  4290.         LD      B,H             ; transfer result
  4291.         LD      C,L             ; to register BC.
  4292.  
  4293.         RET                     ; and return.
  4294.  
  4295. ; -------------------------------
  4296. ; Handle display with line number
  4297. ; -------------------------------
  4298. ; This subroutine is called from four places to calculate the address
  4299. ; of the start of a screen character line which is supplied in B.
  4300.  
  4301. ;; CL-ADDR
  4302. L0E9B:  LD      A,$18           ; reverse the line number
  4303.         SUB     B               ; to range $00 - $17.
  4304.         LD      D,A             ; save line in D for later.
  4305.         RRCA                    ; multiply
  4306.         RRCA                    ; by
  4307.         RRCA                    ; thirty-two.
  4308.  
  4309.         AND     $E0             ; mask off low bits to make
  4310.         LD      L,A             ; L a multiple of 32.
  4311.  
  4312.         LD      A,D             ; bring back the line to A.
  4313.  
  4314.         AND     $18             ; now $00, $08 or $10.
  4315.  
  4316.         OR      $40             ; add the base address of screen.
  4317.  
  4318.         LD      H,A             ; HL now has the correct address.
  4319.         RET                     ; return.
  4320.  
  4321. ; -------------------
  4322. ; Handle COPY command
  4323. ; -------------------
  4324. ; This command copies the top 176 lines to the ZX Printer
  4325. ; It is popular to call this from machine code at point
  4326. ; L0EAF with B holding 192 (and interrupts disabled) for a full-screen
  4327. ; copy. This particularly applies to 16K Spectrums as time-critical
  4328. ; machine code routines cannot be written in the first 16K of RAM as
  4329. ; it is shared with the ULA which has precedence over the Z80 chip.
  4330.  
  4331. ;; COPY
  4332.  
  4333. L0EAC:  DI                      ; disable interrupts as this is time-critical.
  4334. ;===============================
  4335.                 RST 8
  4336.                 DB _AY_PRN_SCR
  4337. ;               LD B,$B0                ; top 176 lines.
  4338. ;===============================
  4339.  
  4340. L0EAF           LD HL,$4000             ; address start of the display file.
  4341.  
  4342. ; now enter a loop to handle each pixel line.
  4343.  
  4344. ;; COPY-1
  4345. L0EB2:  PUSH    HL              ; save the screen address.
  4346.         PUSH    BC              ; and the line counter.
  4347.  
  4348.         CALL    L0EF4           ; routine COPY-LINE outputs one line.
  4349.  
  4350.         POP     BC              ; restore the line counter.
  4351.         POP     HL              ; and display address.
  4352.         INC     H               ; next line down screen within 'thirds'.
  4353.         LD      A,H             ; high byte to A.
  4354.         AND     $07             ; result will be zero if we have left third.
  4355.         JR      NZ,L0EC9        ; forward to COPY-2 if not to continue loop.
  4356.  
  4357.         LD      A,L             ; consider low byte first.
  4358.         ADD     A,$20           ; increase by 32 - sets carry if back to zero.
  4359.         LD      L,A             ; will be next group of 8.
  4360.         CCF                     ; complement - carry set if more lines in
  4361.                                 ; the previous third.
  4362.         SBC     A,A             ; will be FF, if more, else 00.
  4363.         AND     $F8             ; will be F8 (-8) or 00.
  4364.         ADD     A,H             ; that is subtract 8, if more to do in third.
  4365.         LD      H,A             ; and reset address.
  4366.  
  4367. ;; COPY-2
  4368. L0EC9:  DJNZ    L0EB2           ; back to COPY-1 for all lines.
  4369.  
  4370.         JR      L0EDA           ; forward to COPY-END to switch off the printer
  4371.                                 ; motor and enable interrupts.
  4372.                                 ; Note. Nothing else required.
  4373.  
  4374. ; ------------------------------
  4375. ; Pass printer buffer to printer
  4376. ; ------------------------------
  4377. ; This routine is used to copy 8 text lines from the printer buffer
  4378. ; to the ZX Printer. These text lines are mapped linearly so HL does
  4379. ; not need to be adjusted at the end of each line.
  4380.  
  4381. ;; COPY-BUFF
  4382. L0ECD:  DI                      ; disable interrupts
  4383.         LD      HL,$5B00        ; the base address of the Printer Buffer.
  4384.         LD      B,$08           ; set count to 8 lines of 32 bytes.
  4385.  
  4386. ;; COPY-3
  4387. L0ED3:  PUSH    BC              ; save counter.
  4388.         CALL    L0EF4           ; routine COPY-LINE outputs 32 bytes
  4389.         POP     BC              ; restore counter.
  4390.         DJNZ    L0ED3           ; loop back to COPY-3 for all 8 lines.
  4391.                                 ; then stop motor and clear buffer.
  4392.  
  4393. ; Note. the COPY command rejoins here, essentially to execute the next
  4394. ; three instructions.
  4395.  
  4396. ;; COPY-END
  4397. L0EDA           LD A,$04                ; output value 4 to port
  4398.                 OUT ($FB),A             ; to stop the slowed printer motor.
  4399. L0EDE           EI                      ; enable interrupts.
  4400.  
  4401. ; --------------------
  4402. ; Clear Printer Buffer
  4403. ; --------------------
  4404. ; This routine clears an arbitrary 256 bytes of memory.
  4405. ; Note. The routine seems designed to clear a buffer that follows the
  4406. ; system variables.
  4407. ; The routine should check a flag or HL address and simply return if COPY
  4408. ; is in use.
  4409. ; (T-ADDR-lo would work for the system but not if COPY called externally.)
  4410. ; As a consequence of this omission the buffer will needlessly
  4411. ; be cleared when COPY is used and the screen/printer position may be set to
  4412. ; the start of the buffer and the line number to 0 (B)
  4413. ; giving an 'Out of Screen' error.
  4414. ; There seems to have been an unsuccessful attempt to circumvent the use
  4415. ; of PR_CC_hi.
  4416.  
  4417. ;; CLEAR-PRB
  4418. L0EDF:  LD      HL,$5B00        ; the location of the buffer.
  4419.         LD      (IY+$46),L      ; update PR_CC_lo - set to zero - superfluous.
  4420.         XOR     A               ; clear the accumulator.
  4421.         LD      B,A             ; set count to 256 bytes.
  4422.  
  4423. ;; PRB-BYTES
  4424. L0EE7:  LD      (HL),A          ; set addressed location to zero.
  4425.         INC     HL              ; address next byte - Note. not INC L.
  4426.         DJNZ    L0EE7           ; back to PRB-BYTES. repeat for 256 bytes.
  4427.  
  4428.         RES     1,(IY+$30)      ; set FLAGS2 - signal printer buffer is clear.
  4429.         LD      C,$21           ; set the column position .
  4430.         JP      L0DD9           ; exit via CL-SET and then PO-STORE.
  4431.  
  4432. ; -----------------
  4433. ; Copy line routine
  4434. ; -----------------
  4435. ; This routine is called from COPY and COPY-BUFF to output a line of
  4436. ; 32 bytes to the ZX Printer.
  4437. ; Output to port $FB -
  4438. ; bit 7 set - activate stylus.
  4439. ; bit 7 low - deactivate stylus.
  4440. ; bit 2 set - stops printer.
  4441. ; bit 2 reset - starts printer
  4442. ; bit 1 set - slows printer.
  4443. ; bit 1 reset - normal speed.
  4444.  
  4445. ;; COPY-LINE
  4446. ;===============================
  4447. L0EF4          
  4448.                 LD A,(HL)
  4449.                 RST 8
  4450.                 DB _AY_PRN_A_
  4451.                 RET
  4452. ;               LD A,B                  ; fetch the counter 1-8 or 1-176
  4453. ;               CP $03                  ; is it 01 or 02 ?.
  4454. ;               SBC A,A                 ; result is $FF if so else $00.
  4455. ;===============================
  4456.                 AND $02                 ; result is 02 now else 00.
  4457.                                         ; bit 1 set slows the printer.
  4458.                 OUT ($FB),A             ; slow the printer for the
  4459.                                         ; last two lines.
  4460.         LD      D,A             ; save the mask to control the printer later.
  4461.  
  4462. ;; COPY-L-1
  4463. L0EFD:  CALL    L1F54           ; call BREAK-KEY to read keyboard immediately.
  4464.         JR      C,L0F0C         ; forward to COPY-L-2 if 'break' not pressed.
  4465.  
  4466.         LD      A,$04           ; else stop the
  4467.         OUT     ($FB),A         ; printer motor.
  4468.         EI                      ; enable interrupts.
  4469.         CALL    L0EDF           ; call routine CLEAR-PRB.
  4470.                                 ; Note. should not be cleared if COPY in use.
  4471.  
  4472. ;; REPORT-Dc
  4473. L0F0A:  RST     08H             ; ERROR-1
  4474.         DB      $0C             ; Error Report: BREAK - CONT repeats
  4475.  
  4476. ;; COPY-L-2
  4477. L0F0C:  IN      A,($FB)         ; test now to see if
  4478.         ADD     A,A             ; a printer is attached.
  4479.         RET     M               ; return if not - but continue with parent
  4480.                                 ; command.
  4481.  
  4482.         JR      NC,L0EFD        ; back to COPY-L-1 if stylus of printer not
  4483.                                 ; in position.
  4484.  
  4485.         LD      C,$20           ; set count to 32 bytes.
  4486.  
  4487. ;; COPY-L-3
  4488. L0F14:  LD      E,(HL)          ; fetch a byte from line.
  4489.         INC     HL              ; address next location. Note. not INC L.
  4490.         LD      B,$08           ; count the bits.
  4491.  
  4492. ;; COPY-L-4
  4493. L0F18:  RL      D               ; prepare mask to receive bit.
  4494.         RL      E               ; rotate leftmost print bit to carry
  4495.         RR      D               ; and back to bit 7 of D restoring bit 1
  4496.  
  4497. ;; COPY-L-5
  4498. L0F1E:  IN      A,($FB)         ; read the port.
  4499.         RRA                     ; bit 0 to carry.
  4500.         JR      NC,L0F1E        ; back to COPY-L-5 if stylus not in position.
  4501.  
  4502.         LD      A,D             ; transfer command bits to A.
  4503.         OUT     ($FB),A         ; and output to port.
  4504.         DJNZ    L0F18           ; loop back to COPY-L-4 for all 8 bits.
  4505.  
  4506.         DEC     C               ; decrease the byte count.
  4507.         JR      NZ,L0F14        ; back to COPY-L-3 until 256 bits done.
  4508.  
  4509.         RET                     ; return to calling routine COPY/COPY-BUFF.
  4510.  
  4511. ; ----------------------------------
  4512. ; Editor routine for BASIC and INPUT
  4513. ; ----------------------------------
  4514. ; The editor is called to prepare or edit a BASIC line.
  4515. ; It is also called from INPUT to input a numeric or string expression.
  4516. ; The behaviour and options are quite different in the various modes
  4517. ; and distinguished by bit 5 of FLAGX.
  4518. ;
  4519. ; This is a compact and highly versatile routine.
  4520.  
  4521. ;; EDITOR
  4522. L0F2C:  LD      HL,($5C3D)      ; fetch ERR_SP
  4523.         PUSH    HL              ; save on stack
  4524.  
  4525. ;; ED-AGAIN
  4526. L0F30:  LD      HL,L107F        ; address: ED-ERROR
  4527.         PUSH    HL              ; save address on stack and
  4528.         LD      ($5C3D),SP      ; make ERR_SP point to it.
  4529.  
  4530. ; Note. While in editing/input mode should an error occur then RST 08 will
  4531. ; update X_PTR to the location reached by CH_ADD and jump to ED-ERROR
  4532. ; where the error will be cancelled and the loop begin again from ED-AGAIN
  4533. ; above. The position of the error will be apparent when the lower screen is
  4534. ; reprinted. If no error then the re-iteration is to ED-LOOP below when
  4535. ; input is arriving from the keyboard.
  4536.  
  4537. ;; ED-LOOP
  4538. L0F38:  CALL    L15D4           ; routine WAIT-KEY gets key possibly
  4539.                                 ; changing the mode.
  4540.         PUSH    AF              ; save key.
  4541.         LD      D,$00           ; and give a short click based
  4542.         LD      E,(IY-$01)      ; on PIP value for duration.
  4543.         LD      HL,$00C8        ; and pitch.
  4544.         CALL    L03B5           ; routine BEEPER gives click - effective
  4545.                                 ; with rubber keyboard.
  4546.         POP     AF              ; get saved key value.
  4547.         LD      HL,L0F38        ; address: ED-LOOP is loaded to HL.
  4548.         PUSH    HL              ; and pushed onto stack.
  4549.  
  4550. ; At this point there is a looping return address on the stack, an error
  4551. ; handler and an input stream set up to supply characters.
  4552. ; The character that has been received can now be processed.
  4553.  
  4554.         CP      $18             ; range 24 to 255 ?
  4555.         JR      NC,L0F81        ; forward to ADD-CHAR if so.
  4556.  
  4557.         CP      $07             ; lower than 7 ?
  4558.         JR      C,L0F81         ; forward to ADD-CHAR also.
  4559.                                 ; Note. This is a 'bug' and chr$ 6, the comma
  4560.                                 ; control character, should have had an
  4561.                                 ; entry in the ED-KEYS table.
  4562.                                 ; Steven Vickers, 1984, Pitman.
  4563.  
  4564.         CP      $10             ; less than 16 ?
  4565.         JR      C,L0F92         ; forward to ED-KEYS if editing control
  4566.                                 ; range 7 to 15 dealt with by a table
  4567.  
  4568.         LD      BC,$0002        ; prepare for ink/paper etc.
  4569.         LD      D,A             ; save character in D
  4570.         CP      $16             ; is it ink/paper/bright etc. ?
  4571.         JR      C,L0F6C         ; forward to ED-CONTR if so
  4572.  
  4573.                                 ; leaves 22d AT and 23d TAB
  4574.                                 ; which can't be entered via KEY-INPUT.
  4575.                                 ; so this code is never normally executed
  4576.                                 ; when the keyboard is used for input.
  4577.  
  4578.         INC     BC              ; if it was AT/TAB - 3 locations required
  4579.         BIT     7,(IY+$37)      ; test FLAGX  - Is this INPUT LINE ?
  4580.         JP      Z,L101E         ; jump to ED-IGNORE if not, else
  4581.  
  4582.         CALL    L15D4           ; routine WAIT-KEY - input address is KEY-NEXT
  4583.                                 ; but is reset to KEY-INPUT
  4584.         LD      E,A             ; save first in E
  4585.  
  4586. ;; ED-CONTR
  4587. L0F6C:  CALL    L15D4           ; routine WAIT-KEY for control.
  4588.                                 ; input address will be key-next.
  4589.  
  4590.         PUSH    DE              ; saved code/parameters
  4591.         LD      HL,($5C5B)      ; fetch address of keyboard cursor from K_CUR
  4592.         RES     0,(IY+$07)      ; set MODE to 'L'
  4593.  
  4594.         CALL    L1655           ; routine MAKE-ROOM makes 2/3 spaces at cursor
  4595.  
  4596.         POP     BC              ; restore code/parameters
  4597.         INC     HL              ; address first location
  4598.         LD      (HL),B          ; place code (ink etc.)
  4599.         INC     HL              ; address next
  4600.         LD      (HL),C          ; place possible parameter. If only one
  4601.                                 ; then DE points to this location also.
  4602.         JR      L0F8B           ; forward to ADD-CH-1
  4603.  
  4604. ; ------------------------
  4605. ; Add code to current line
  4606. ; ------------------------
  4607. ; this is the branch used to add normal non-control characters
  4608. ; with ED-LOOP as the stacked return address.
  4609. ; it is also the OUTPUT service routine for system channel 'R'.
  4610.  
  4611. ;; ADD-CHAR
  4612. L0F81:  RES     0,(IY+$07)      ; set MODE to 'L'
  4613.  
  4614. X0F85:  LD      HL,($5C5B)      ; fetch address of keyboard cursor from K_CUR
  4615.         CALL    L1652           ; routine ONE-SPACE creates one space.
  4616.  
  4617. ; either a continuation of above or from ED-CONTR with ED-LOOP on stack.
  4618.  
  4619. ;; ADD-CH-1
  4620. L0F8B:  LD      (DE),A          ; load current character to last new location.
  4621.         INC     DE              ; address next
  4622.         LD      ($5C5B),DE      ; and update K_CUR system variable.
  4623.         RET                     ; return - either a simple return
  4624.                                 ; from ADD-CHAR or to ED-LOOP on stack.
  4625.  
  4626. ; ---
  4627.  
  4628. ; a branch of the editing loop to deal with control characters
  4629. ; using a look-up table.
  4630.  
  4631. ;; ED-KEYS
  4632. L0F92:  LD      E,A             ; character to E.
  4633.         LD      D,$00           ; prepare to add.
  4634.         LD      HL,L0FA0 - 7    ; base address of editing keys table. $0F99
  4635.         ADD     HL,DE           ; add E
  4636.         LD      E,(HL)          ; fetch offset to E
  4637.         ADD     HL,DE           ; add offset for address of handling routine.
  4638.         PUSH    HL              ; push the address on machine stack.
  4639.         LD      HL,($5C5B)      ; load address of cursor from K_CUR.
  4640.         RET                     ; an make an indirect jump forward to routine.
  4641.  
  4642. ; ------------------
  4643. ; Editing keys table
  4644. ; ------------------
  4645. ; For each code in the range $07 to $0F this table contains a
  4646. ; single offset byte to the routine that services that code.
  4647. ; Note. for what was intended there should also have been an
  4648. ; entry for chr$ 6 with offset to ed-symbol.
  4649.  
  4650. ;; ed-keys-t
  4651. L0FA0:  DB    L0FA9 - $  ; 07d offset $09 to Address: ED-EDIT
  4652.         DB    L1007 - $  ; 08d offset $66 to Address: ED-LEFT
  4653.         DB    L100C - $  ; 09d offset $6A to Address: ED-RIGHT
  4654.         DB    L0FF3 - $  ; 10d offset $50 to Address: ED-DOWN
  4655.         DB    L1059 - $  ; 11d offset $B5 to Address: ED-UP
  4656.         DB    L1015 - $  ; 12d offset $70 to Address: ED-DELETE
  4657.         DB    L1024 - $  ; 13d offset $7E to Address: ED-ENTER
  4658.         DB    L1076 - $  ; 14d offset $CF to Address: ED-SYMBOL
  4659.         DB    L107C - $  ; 15d offset $D4 to Address: ED-GRAPH
  4660.  
  4661. ; ---------------
  4662. ; Handle EDIT key
  4663. ; ---------------
  4664. ; The user has pressed SHIFT 1 to bring edit line down to bottom of screen.
  4665. ; Alternatively the user wishes to clear the input buffer and start again.
  4666. ; Alternatively ...
  4667.  
  4668. ;; ED-EDIT
  4669. L0FA9:  LD      HL,($5C49)      ; fetch E_PPC the last line number entered.
  4670.                                 ; Note. may not exist and may follow program.
  4671.         BIT     5,(IY+$37)      ; test FLAGX  - input mode ?
  4672.         JP      NZ,L1097        ; jump forward to CLEAR-SP if not in editor.
  4673.  
  4674.         CALL    L196E           ; routine LINE-ADDR to find address of line
  4675.                                 ; or following line if it doesn't exist.
  4676.         CALL    L1695           ; routine LINE-NO will get line number from
  4677.                                 ; address or previous line if at end-marker.
  4678.         LD      A,D             ; if there is no program then DE will
  4679.         OR      E               ; contain zero so test for this.
  4680.         JP      Z,L1097         ; jump to to CLEAR-SP if so.
  4681.  
  4682. ; Note. at this point we have a validated line number, not just an
  4683. ; approximation and it would be best to update E_PPC with the true
  4684. ; cursor line value which would enable the line cursor to be suppressed
  4685. ; in all situations - see shortly.
  4686.  
  4687.         PUSH    HL              ; save address of line.
  4688.         INC     HL              ; address low byte of length.
  4689.         LD      C,(HL)          ; transfer to C
  4690.         INC     HL              ; next to high byte
  4691.         LD      B,(HL)          ; transfer to B.
  4692.         LD      HL,$000A        ; an overhead of ten bytes
  4693.         ADD     HL,BC           ; is added to length.
  4694.         LD      B,H             ; transfer adjusted value
  4695.         LD      C,L             ; to BC register.
  4696.         CALL    L1F05           ; routine TEST-ROOM checks free memory.
  4697.         CALL    L1097           ; routine CLEAR-SP clears editing area.
  4698.         LD      HL,($5C51)      ; address CURCHL
  4699.         EX      (SP),HL         ; swap with line address on stack
  4700.         PUSH    HL              ; save line address underneath
  4701.  
  4702.         LD      A,$FF           ; select system channel 'R'
  4703.         CALL    L1601           ; routine CHAN-OPEN opens it
  4704.  
  4705.         POP     HL              ; drop line address
  4706.         DEC     HL              ; make it point to first byte of line num.
  4707.         DEC     (IY+$0F)        ; decrease E_PPC_lo to suppress line cursor.
  4708.                                 ; Note. ineffective when E_PPC is one
  4709.                                 ; greater than last line of program perhaps
  4710.                                 ; as a result of a delete.
  4711.                                 ; credit. Paul Harrison 1982.
  4712.  
  4713.         CALL    L1855           ; routine OUT-LINE outputs the BASIC line
  4714.                                 ; to the editing area.
  4715.         INC     (IY+$0F)        ; restore E_PPC_lo to the previous value.
  4716.         LD      HL,($5C59)      ; address E_LINE in editing area.
  4717.         INC     HL              ; advance
  4718.         INC     HL              ; past space
  4719.         INC     HL              ; and digit characters
  4720.         INC     HL              ; of line number.
  4721.  
  4722.         LD      ($5C5B),HL      ; update K_CUR to address start of BASIC.
  4723.         POP     HL              ; restore the address of CURCHL.
  4724.         CALL    L1615           ; routine CHAN-FLAG sets flags for it.
  4725.         RET                     ; RETURN to ED-LOOP.
  4726.  
  4727. ; -------------------
  4728. ; Cursor down editing
  4729. ; -------------------
  4730. ; The BASIC lines are displayed at the top of the screen and the user
  4731. ; wishes to move the cursor down one line in edit mode.
  4732. ; In input mode this key can be used as an alternative to entering STOP.
  4733.  
  4734. ;; ED-DOWN
  4735. L0FF3:  BIT     5,(IY+$37)      ; test FLAGX  - Input Mode ?
  4736.         JR      NZ,L1001        ; skip to ED-STOP if so
  4737.  
  4738.         LD      HL,$5C49        ; address E_PPC - 'current line'
  4739.         CALL    L190F           ; routine LN-FETCH fetches number of next
  4740.                                 ; line or same if at end of program.
  4741.         JR      L106E           ; forward to ED-LIST to produce an
  4742.                                 ; automatic listing.
  4743.  
  4744. ; ---
  4745.  
  4746. ;; ED-STOP
  4747. L1001:  LD      (IY+$00),$10    ; set ERR_NR to 'STOP in INPUT' code
  4748.         JR      L1024           ; forward to ED-ENTER to produce error.
  4749.  
  4750. ; -------------------
  4751. ; Cursor left editing
  4752. ; -------------------
  4753. ; This acts on the cursor in the lower section of the screen in both
  4754. ; editing and input mode.
  4755.  
  4756. ;; ED-LEFT
  4757. L1007:  CALL    L1031           ; routine ED-EDGE moves left if possible
  4758.         JR      L1011           ; forward to ED-CUR to update K-CUR
  4759.                                 ; and return to ED-LOOP.
  4760.  
  4761. ; --------------------
  4762. ; Cursor right editing
  4763. ; --------------------
  4764. ; This acts on the cursor in the lower screen in both editing and input
  4765. ; mode and moves it to the right.
  4766.  
  4767. ;; ED-RIGHT
  4768. L100C:  LD      A,(HL)          ; fetch addressed character.
  4769.         CP      $0D             ; is it carriage return ?
  4770.         RET     Z               ; return if so to ED-LOOP
  4771.  
  4772.         INC     HL              ; address next character
  4773.  
  4774. ;; ED-CUR
  4775. L1011:  LD      ($5C5B),HL      ; update K_CUR system variable
  4776.         RET                     ; return to ED-LOOP
  4777.  
  4778. ; --------------
  4779. ; DELETE editing
  4780. ; --------------
  4781. ; This acts on the lower screen and deletes the character to left of
  4782. ; cursor. If control characters are present these are deleted first
  4783. ; leaving the naked parameter (0-7) which appears as a '?' except in the
  4784. ; case of chr$ 6 which is the comma control character. It is not mandatory
  4785. ; to delete these second characters.
  4786.  
  4787. ;; ED-DELETE
  4788. L1015:  CALL    L1031           ; routine ED-EDGE moves cursor to left.
  4789.         LD      BC,$0001        ; of character to be deleted.
  4790.         JP      L19E8           ; to RECLAIM-2 reclaim the character.
  4791.  
  4792. ; ------------------------------------------
  4793. ; Ignore next 2 codes from key-input routine
  4794. ; ------------------------------------------
  4795. ; Since AT and TAB cannot be entered this point is never reached
  4796. ; from the keyboard. If inputting from a tape device or network then
  4797. ; the control and two following characters are ignored and processing
  4798. ; continues as if a carriage return had been received.
  4799. ; Here, perhaps, another Spectrum has said print #15; AT 0,0; "This is yellow"
  4800. ; and this one is interpreting input #15; a$.
  4801.  
  4802. ;; ED-IGNORE
  4803. L101E:  CALL    L15D4           ; routine WAIT-KEY to ignore keystroke.
  4804.         CALL    L15D4           ; routine WAIT-KEY to ignore next key.
  4805.  
  4806. ; -------------
  4807. ; Enter/newline
  4808. ; -------------
  4809. ; The enter key has been pressed to have BASIC line or input accepted.
  4810.  
  4811. ;; ED-ENTER
  4812. L1024:  POP     HL              ; discard address ED-LOOP
  4813.         POP     HL              ; drop address ED-ERROR
  4814.  
  4815. ;; ED-END
  4816. L1026:  POP     HL              ; the previous value of ERR_SP
  4817.         LD      ($5C3D),HL      ; is restored to ERR_SP system variable
  4818.         BIT     7,(IY+$00)      ; is ERR_NR $FF (= 'OK') ?
  4819.         RET     NZ              ; return if so
  4820.  
  4821.         LD      SP,HL           ; else put error routine on stack
  4822.         RET                     ; and make an indirect jump to it.
  4823.  
  4824. ; -----------------------------
  4825. ; Move cursor left when editing
  4826. ; -----------------------------
  4827. ; This routine moves the cursor left. The complication is that it must
  4828. ; not position the cursor between control codes and their parameters.
  4829. ; It is further complicated in that it deals with TAB and AT characters
  4830. ; which are never present from the keyboard.
  4831. ; The method is to advance from the beginning of the line each time,
  4832. ; jumping one, two, or three characters as necessary saving the original
  4833. ; position at each jump in DE. Once it arrives at the cursor then the next
  4834. ; legitimate leftmost position is in DE.
  4835.  
  4836. ;; ED-EDGE
  4837. L1031:  SCF                     ; carry flag must be set to call the nested
  4838.         CALL    L1195           ; subroutine SET-DE.
  4839.                                 ; if input   then DE=WORKSP
  4840.                                 ; if editing then DE=E_LINE
  4841.         SBC     HL,DE           ; subtract address from start of line
  4842.         ADD     HL,DE           ; and add back.
  4843.         INC     HL              ; adjust for carry.
  4844.         POP     BC              ; drop return address
  4845.         RET     C               ; return to ED-LOOP if already at left
  4846.                                 ; of line.
  4847.  
  4848.         PUSH    BC              ; resave return address - ED-LOOP.
  4849.         LD      B,H             ; transfer HL - cursor address
  4850.         LD      C,L             ; to BC register pair.
  4851.                                 ; at this point DE addresses start of line.
  4852.  
  4853. ;; ED-EDGE-1
  4854. L103E:  LD      H,D             ; transfer DE - leftmost pointer
  4855.         LD      L,E             ; to HL
  4856.         INC     HL              ; address next leftmost character to
  4857.                                 ; advance position each time.
  4858.         LD      A,(DE)          ; pick up previous in A
  4859.         AND     $F0             ; lose the low bits
  4860.         CP      $10             ; is it INK to TAB $10-$1F ?
  4861.                                 ; that is, is it followed by a parameter ?
  4862.         JR      NZ,L1051        ; to ED-EDGE-2 if not
  4863.                                 ; HL has been incremented once
  4864.  
  4865.         INC     HL              ; address next as at least one parameter.
  4866.  
  4867. ; in fact since 'tab' and 'at' cannot be entered the next section seems
  4868. ; superfluous.
  4869. ; The test will always fail and the jump to ED-EDGE-2 will be taken.
  4870.  
  4871.         LD      A,(DE)          ; reload leftmost character
  4872.         SUB     $17             ; decimal 23 ('tab')
  4873.         ADC     A,$00           ; will be 0 for 'tab' and 'at'.
  4874.         JR      NZ,L1051        ; forward to ED-EDGE-2 if not
  4875.                                 ; HL has been incremented twice
  4876.  
  4877.         INC     HL              ; increment a third time for 'at'/'tab'
  4878.  
  4879. ;; ED-EDGE-2
  4880. L1051:  AND     A               ; prepare for true subtraction
  4881.         SBC     HL,BC           ; subtract cursor address from pointer
  4882.         ADD     HL,BC           ; and add back
  4883.                                 ; Note when HL matches the cursor position BC,
  4884.                                 ; there is no carry and the previous
  4885.                                 ; position is in DE.
  4886.         EX      DE,HL           ; transfer result to DE if looping again.
  4887.                                 ; transfer DE to HL to be used as K-CUR
  4888.                                 ; if exiting loop.
  4889.         JR      C,L103E         ; back to ED-EDGE-1 if cursor not matched.
  4890.  
  4891.         RET                     ; return.
  4892.  
  4893. ; -----------------
  4894. ; Cursor up editing
  4895. ; -----------------
  4896. ; The main screen displays part of the BASIC program and the user wishes
  4897. ; to move up one line scrolling if necessary.
  4898. ; This has no alternative use in input mode.
  4899.  
  4900. ;; ED-UP
  4901. L1059:  BIT     5,(IY+$37)      ; test FLAGX  - input mode ?
  4902.         RET     NZ              ; return if not in editor - to ED-LOOP.
  4903.  
  4904.         LD      HL,($5C49)      ; get current line from E_PPC
  4905.         CALL    L196E           ; routine LINE-ADDR gets address
  4906.         EX      DE,HL           ; and previous in DE
  4907.         CALL    L1695           ; routine LINE-NO gets prev line number
  4908.         LD      HL,$5C4A        ; set HL to E_PPC_hi as next routine stores
  4909.                                 ; top first.
  4910.         CALL    L191C           ; routine LN-STORE loads DE value to HL
  4911.                                 ; high byte first - E_PPC_lo takes E
  4912.  
  4913. ; this branch is also taken from ed-down.
  4914.  
  4915. ;; ED-LIST
  4916. L106E:  CALL    L1795           ; routine AUTO-LIST lists to upper screen
  4917.                                 ; including adjusted current line.
  4918.         LD      A,$00           ; select lower screen again
  4919.         JP      L1601           ; exit via CHAN-OPEN to ED-LOOP
  4920.  
  4921. ; --------------------------------
  4922. ; Use of symbol and graphics codes
  4923. ; --------------------------------
  4924. ; These will not be encountered with the keyboard but would be handled
  4925. ; otherwise as follows.
  4926. ; As noted earlier, Vickers says there should have been an entry in
  4927. ; the KEYS table for chr$ 6 which also pointed here.
  4928. ; If, for simplicity, two Spectrums were both using #15 as a bi-directional
  4929. ; channel connected to each other:-
  4930. ; then when the other Spectrum has said PRINT #15; x, y
  4931. ; input #15; i ; j  would treat the comma control as a newline and the
  4932. ; control would skip to input j.
  4933. ; You can get round the missing chr$ 6 handler by sending multiple print
  4934. ; items separated by a newline '.
  4935.  
  4936. ; chr$14 would have the same functionality.
  4937.  
  4938. ; This is chr$ 14.
  4939. ;; ED-SYMBOL
  4940. L1076:  BIT     7,(IY+$37)      ; test FLAGX - is this INPUT LINE ?
  4941.         JR      Z,L1024         ; back to ED-ENTER if not to treat as if
  4942.                                 ; enter had been pressed.
  4943.                                 ; else continue and add code to buffer.
  4944.  
  4945. ; Next is chr$ 15
  4946. ; Note that ADD-CHAR precedes the table so we can't offset to it directly.
  4947.  
  4948. ;; ED-GRAPH
  4949. L107C:  JP      L0F81           ; jump back to ADD-CHAR
  4950.  
  4951. ; --------------------
  4952. ; Editor error routine
  4953. ; --------------------
  4954. ; If an error occurs while editing, or inputting, then ERR_SP
  4955. ; points to the stack location holding address ED_ERROR.
  4956.  
  4957. ;; ED-ERROR
  4958. L107F:  BIT     4,(IY+$30)      ; test FLAGS2  - is K channel in use ?
  4959.         JR      Z,L1026         ; back to ED-END if not.
  4960.  
  4961. ; but as long as we're editing lines or inputting from the keyboard, then
  4962. ; we've run out of memory so give a short rasp.
  4963.  
  4964.         LD      (IY+$00),$FF    ; reset ERR_NR to 'OK'.
  4965.         LD      D,$00           ; prepare for beeper.
  4966.         LD      E,(IY-$02)      ; use RASP value.
  4967.         LD      HL,$1A90        ; set a duration.
  4968.         CALL    L03B5           ; routine BEEPER emits a warning rasp.
  4969.         JP      L0F30           ; to ED-AGAIN to re-stack address of
  4970.                                 ; this routine and make ERR_SP point to it.
  4971.  
  4972. ; ---------------------
  4973. ; Clear edit/work space
  4974. ; ---------------------
  4975. ; The editing area or workspace is cleared depending on context.
  4976. ; This is called from ED-EDIT to clear workspace if edit key is
  4977. ; used during input, to clear editing area if no program exists
  4978. ; and to clear editing area prior to copying the edit line to it.
  4979. ; It is also used by the error routine to clear the respective
  4980. ; area depending on FLAGX.
  4981.  
  4982. ;; CLEAR-SP
  4983. L1097:  PUSH    HL              ; preserve HL
  4984.         CALL    L1190           ; routine SET-HL
  4985.                                 ; if in edit   HL = WORKSP-1, DE = E_LINE
  4986.                                 ; if in input  HL = STKBOT,   DE = WORKSP
  4987.         DEC     HL              ; adjust
  4988.         CALL    L19E5           ; routine RECLAIM-1 reclaims space
  4989.         LD      ($5C5B),HL      ; set K_CUR to start of empty area
  4990.         LD      (IY+$07),$00    ; set MODE to 'KLC'
  4991.         POP     HL              ; restore HL.
  4992.         RET                     ; return.
  4993.  
  4994. ; ---------------------
  4995. ; Handle keyboard input
  4996. ; ---------------------
  4997. ; This is the service routine for the input stream of the keyboard
  4998. ; channel 'K'.
  4999.  
  5000. ;; KEY-INPUT
  5001. L10A8:  BIT     3,(IY+$02)      ; test TV_FLAG  - has a key been pressed in
  5002.                                 ; editor ?
  5003.         CALL    NZ,L111D        ; routine ED-COPY if so to reprint the lower
  5004.                                 ; screen at every keystroke.
  5005.         AND     A               ; clear carry - required exit condition.
  5006.         BIT     5,(IY+$01)      ; test FLAGS  - has a new key been pressed ?
  5007.         RET     Z               ; return if not.
  5008.  
  5009.         LD      A,($5C08)       ; system variable LASTK will hold last key -
  5010.                                 ; from the interrupt routine.
  5011.         RES     5,(IY+$01)      ; update FLAGS  - reset the new key flag.
  5012.         PUSH    AF              ; save the input character.
  5013.         BIT     5,(IY+$02)      ; test TV_FLAG  - clear lower screen ?
  5014.         CALL    NZ,L0D6E        ; routine CLS-LOWER if so.
  5015.  
  5016.         POP     AF              ; restore the character code.
  5017.         CP      $20             ; if space or higher then
  5018.         JR      NC,L111B        ; forward to KEY-DONE2 and return with carry
  5019.                                 ; set to signal key-found.
  5020.  
  5021.         CP      $10             ; with 16d INK and higher skip
  5022.         JR      NC,L10FA        ; forward to KEY-CONTR.
  5023.  
  5024.         CP      $06             ; for 6 - 15d
  5025.         JR      NC,L10DB        ; skip forward to KEY-M-CL to handle Modes
  5026.                                 ; and CapsLock.
  5027.  
  5028. ; that only leaves 0-5, the flash bright inverse switches.
  5029.  
  5030.         LD      B,A             ; save character in B
  5031.         AND     $01             ; isolate the embedded parameter (0/1).
  5032.         LD      C,A             ; and store in C
  5033.         LD      A,B             ; re-fetch copy (0-5)
  5034.         RRA                     ; halve it 0, 1 or 2.
  5035.         ADD     A,$12           ; add 18d gives 'flash', 'bright'
  5036.                                 ; and 'inverse'.
  5037.         JR      L1105           ; forward to KEY-DATA with the
  5038.                                 ; parameter (0/1) in C.
  5039.  
  5040. ; ---
  5041.  
  5042. ; Now separate capslock 06 from modes 7-15.
  5043.  
  5044. ;; KEY-M-CL
  5045. L10DB:  JR      NZ,L10E6        ; forward to KEY-MODE if not 06 (capslock)
  5046.  
  5047.         LD      HL,$5C6A        ; point to FLAGS2
  5048.         LD      A,$08           ; value 00000100
  5049.         XOR     (HL)            ; toggle BIT 2 of FLAGS2 the capslock bit
  5050.         LD      (HL),A          ; and store result in FLAGS2 again.
  5051.         JR      L10F4           ; forward to KEY-FLAG to signal no-key.
  5052.  
  5053. ; ---
  5054.  
  5055. ;; KEY-MODE
  5056. L10E6:  CP      $0E             ; compare with chr 14d
  5057.         RET     C               ; return with carry set "key found" for
  5058.                                 ; codes 7 - 13d leaving 14d and 15d
  5059.                                 ; which are converted to mode codes.
  5060.  
  5061.         SUB     $0D             ; subtract 13d leaving 1 and 2
  5062.                                 ; 1 is 'E' mode, 2 is 'G' mode.
  5063.         LD      HL,$5C41        ; address the MODE system variable.
  5064.         CP      (HL)            ; compare with existing value before
  5065.         LD      (HL),A          ; inserting the new value.
  5066.         JR      NZ,L10F4        ; forward to KEY-FLAG if it has changed.
  5067.  
  5068.         LD      (HL),$00        ; else make MODE zero - KLC mode
  5069.                                 ; Note. while in Extended/Graphics mode,
  5070.                                 ; the Extended Mode/Graphics key is pressed
  5071.                                 ; again to get out.
  5072.  
  5073. ;; KEY-FLAG
  5074. L10F4:  SET     3,(IY+$02)      ; update TV_FLAG  - show key state has changed
  5075.         CP      A               ; clear carry and reset zero flags -
  5076.                                 ; no actual key returned.
  5077.         RET                     ; make the return.
  5078.  
  5079. ; ---
  5080.  
  5081. ; now deal with colour controls - 16-23 ink, 24-31 paper
  5082.  
  5083. ;; KEY-CONTR
  5084. L10FA:  LD      B,A             ; make a copy of character.
  5085.         AND     $07             ; mask to leave bits 0-7
  5086.         LD      C,A             ; and store in C.
  5087.         LD      A,$10           ; initialize to 16d - INK.
  5088.         BIT     3,B             ; was it paper ?
  5089.         JR      NZ,L1105        ; forward to KEY-DATA with INK 16d and
  5090.                                 ; colour in C.
  5091.  
  5092.         INC     A               ; else change from INK to PAPER (17d) if so.
  5093.  
  5094. ;; KEY-DATA
  5095. L1105:  LD      (IY-$2D),C      ; put the colour (0-7)/state(0/1) in KDATA
  5096.         LD      DE,L110D        ; address: KEY-NEXT will be next input stream
  5097.         JR      L1113           ; forward to KEY-CHAN to change it ...
  5098.  
  5099. ; ---
  5100.  
  5101. ; ... so that INPUT_AD directs control to here at next call to WAIT-KEY
  5102.  
  5103. ;; KEY-NEXT
  5104. L110D:  LD      A,($5C0D)       ; pick up the parameter stored in KDATA.
  5105.         LD      DE,L10A8        ; address: KEY-INPUT will be next input stream
  5106.                                 ; continue to restore default channel and
  5107.                                 ; make a return with the control code.
  5108.  
  5109. ;; KEY-CHAN
  5110. L1113:  LD      HL,($5C4F)      ; address start of CHANNELS area using CHANS
  5111.                                 ; system variable.
  5112.                                 ; Note. One might have expected CURCHL to
  5113.                                 ; have been used.
  5114.         INC     HL              ; step over the
  5115.         INC     HL              ; output address
  5116.         LD      (HL),E          ; and update the input
  5117.         INC     HL              ; routine address for
  5118.         LD      (HL),D          ; the next call to WAIT-KEY.
  5119.  
  5120. ;; KEY-DONE2
  5121. L111B:  SCF                     ; set carry flag to show a key has been found
  5122.         RET                     ; and return.
  5123.  
  5124. ; --------------------
  5125. ; Lower screen copying
  5126. ; --------------------
  5127. ; This subroutine is called whenever the line in the editing area or
  5128. ; input workspace is required to be printed to the lower screen.
  5129. ; It is by calling this routine after any change that the cursor, for
  5130. ; instance, appears to move to the left.
  5131. ; Remember the edit line will contain characters and tokens
  5132. ; e.g. "1000 LET a = 1" is 12 characters.
  5133.  
  5134. ;; ED-COPY
  5135. L111D:  CALL    L0D4D           ; routine TEMPS sets temporary attributes.
  5136.         RES     3,(IY+$02)      ; update TV_FLAG  - signal no change in mode
  5137.         RES     5,(IY+$02)      ; update TV_FLAG  - signal don't clear lower
  5138.                                 ; screen.
  5139.         LD      HL,($5C8A)      ; fetch SPOSNL
  5140.         PUSH    HL              ; and save on stack.
  5141.  
  5142.         LD      HL,($5C3D)      ; fetch ERR_SP
  5143.         PUSH    HL              ; and save also
  5144.         LD      HL,L1167        ; address: ED-FULL
  5145.         PUSH    HL              ; is pushed as the error routine
  5146.         LD      ($5C3D),SP      ; and ERR_SP made to point to it.
  5147.  
  5148.         LD      HL,($5C82)      ; fetch ECHO_E
  5149.         PUSH    HL              ; and push also
  5150.  
  5151.         SCF                     ; set carry flag to control SET-DE
  5152.         CALL    L1195           ; call routine SET-DE
  5153.                                 ; if in input DE = WORKSP
  5154.                                 ; if in edit  DE = E_LINE
  5155.         EX      DE,HL           ; start address to HL
  5156.  
  5157.         CALL    L187D           ; routine OUT-LINE2 outputs entire line up to
  5158.                                 ; carriage return including initial
  5159.                                 ; characterized line number when present.
  5160.         EX      DE,HL           ; transfer new address to DE
  5161.         CALL    L18E1           ; routine OUT-CURS considers a
  5162.                                 ; terminating cursor.
  5163.  
  5164.         LD      HL,($5C8A)      ; fetch updated SPOSNL
  5165.         EX      (SP),HL         ; exchange with ECHO_E on stack
  5166.         EX      DE,HL           ; transfer ECHO_E to DE
  5167.         CALL    L0D4D           ; routine TEMPS to re-set attributes
  5168.                                 ; if altered.
  5169.  
  5170. ; the lower screen was not cleared, at the outset, so if deleting then old
  5171. ; text from a previous print may follow this line and requires blanking.
  5172.  
  5173. ;; ED-BLANK
  5174. L1150:  LD      A,($5C8B)       ; fetch SPOSNL_hi is current line
  5175.         SUB     D               ; compare with old
  5176.         JR      C,L117C         ; forward to ED-C-DONE if no blanking
  5177.  
  5178.         JR      NZ,L115E        ; forward to ED-SPACES if line has changed
  5179.  
  5180.         LD      A,E             ; old column to A
  5181.         SUB     (IY+$50)        ; subtract new in SPOSNL_lo
  5182.         JR      NC,L117C        ; forward to ED-C-DONE if no backfilling.
  5183.  
  5184. ;; ED-SPACES
  5185. L115E:  LD      A,$20           ; prepare a space.
  5186.         PUSH    DE              ; save old line/column.
  5187.         CALL    L09F4           ; routine PRINT-OUT prints a space over
  5188.                                 ; any text from previous print.
  5189.                                 ; Note. Since the blanking only occurs when
  5190.                                 ; using $09F4 to print to the lower screen,
  5191.                                 ; there is no need to vector via a RST 10
  5192.                                 ; and we can use this alternate set.
  5193.         POP     DE              ; restore the old line column.
  5194.         JR      L1150           ; back to ED-BLANK until all old text blanked.
  5195.  
  5196. ; -------
  5197. ; ED-FULL
  5198. ; -------
  5199. ; this is the error routine addressed by ERR_SP. This is not for the out of
  5200. ; memory situation as we're just printing. The pitch and duration are exactly
  5201. ; the same as used by ED-ERROR from which this has been augmented. The
  5202. ; situation is that the lower screen is full and a rasp is given to suggest
  5203. ; that this is perhaps not the best idea you've had that day.
  5204.  
  5205. ;; ED-FULL
  5206. L1167:  LD      D,$00           ; prepare to moan.
  5207.         LD      E,(IY-$02)      ; fetch RASP value.
  5208.         LD      HL,$1A90        ; set duration.
  5209.         CALL    L03B5           ; routine BEEPER.
  5210.         LD      (IY+$00),$FF    ; clear ERR_NR.
  5211.         LD      DE,($5C8A)      ; fetch SPOSNL.
  5212.         JR      L117E           ; forward to ED-C-END
  5213.  
  5214. ; -------
  5215.  
  5216. ; the exit point from line printing continues here.
  5217.  
  5218. ;; ED-C-DONE
  5219. L117C:  POP     DE              ; fetch new line/column.
  5220.         POP     HL              ; fetch the error address.
  5221.  
  5222. ; the error path rejoins here.
  5223.  
  5224. ;; ED-C-END
  5225. L117E:  POP     HL              ; restore the old value of ERR_SP.
  5226.         LD      ($5C3D),HL      ; update the system variable ERR_SP
  5227.         POP     BC              ; old value of SPOSN_L
  5228.         PUSH    DE              ; save new value
  5229.         CALL    L0DD9           ; routine CL-SET and PO-STORE
  5230.                                 ; update ECHO_E and SPOSN_L from BC
  5231.         POP     HL              ; restore new value
  5232.         LD      ($5C82),HL      ; and update ECHO_E
  5233.         LD      (IY+$26),$00    ; make error pointer X_PTR_hi out of bounds
  5234.         RET                     ; return
  5235.  
  5236. ; -----------------------------------------------
  5237. ; Point to first and last locations of work space
  5238. ; -----------------------------------------------
  5239. ; These two nested routines ensure that the appropriate pointers are
  5240. ; selected for the editing area or workspace. The routines that call
  5241. ; these routines are designed to work on either area.
  5242.  
  5243. ; this routine is called once
  5244. ;; SET-HL
  5245. L1190:  LD      HL,($5C61)      ; fetch WORKSP to HL.
  5246.         DEC     HL              ; point to last location of editing area.
  5247.         AND     A               ; clear carry to limit exit points to first
  5248.                                 ; or last.
  5249.  
  5250. ; this routine is called with carry set and exits at a conditional return.
  5251.  
  5252. ;; SET-DE
  5253. L1195:  LD      DE,($5C59)      ; fetch E_LINE to DE
  5254.         BIT     5,(IY+$37)      ; test FLAGX  - Input Mode ?
  5255.         RET     Z               ; return now if in editing mode
  5256.  
  5257.         LD      DE,($5C61)      ; fetch WORKSP to DE
  5258.         RET     C               ; return if carry set ( entry = set-de)
  5259.  
  5260.         LD      HL,($5C63)      ; fetch STKBOT to HL as well
  5261.         RET                     ; and return  (entry = set-hl (in input))
  5262.  
  5263. ; -------------------------------
  5264. ; Remove floating point from line
  5265. ; -------------------------------
  5266. ; When a BASIC LINE or the INPUT BUFFER is parsed any numbers will have
  5267. ; an invisible chr 14d inserted after them and the 5-byte integer or
  5268. ; floating point form inserted after that. Similar invisible value holders
  5269. ; are also created after the numeric and string variables in a DEF FN list.
  5270. ; This routine removes these 'compiled' numbers from the edit line or
  5271. ; input workspace.
  5272.  
  5273. ;; REMOVE-FP
  5274. L11A7:  LD      A,(HL)          ; fetch character
  5275.         CP      $0E             ; is it the number marker ?
  5276.         LD      BC,$0006        ; prepare for six bytes
  5277.         CALL    Z,L19E8         ; routine RECLAIM-2 reclaims space if $0E
  5278.         LD      A,(HL)          ; reload next (or same) character
  5279.         INC     HL              ; and advance address
  5280.         CP      $0D             ; end of line or input buffer ?
  5281.         JR      NZ,L11A7        ; back to REMOVE-FP until entire line done.
  5282.  
  5283.         RET                     ; return
  5284.  
  5285.  
  5286. ;*********************************
  5287. ;** Part 6. EXECUTIVE ROUTINES  **
  5288. ;*********************************
  5289.  
  5290.  
  5291. ; The memory.
  5292. ;
  5293. ; +---------+-----------+------------+--------------+-------------+--
  5294. ; | BASIC   |  Display  | Attributes | ZX Printer   |    System   |
  5295. ; |  ROM    |   File    |    File    |   Buffer     |  Variables  |
  5296. ; +---------+-----------+------------+--------------+-------------+--
  5297. ; ^         ^           ^            ^              ^             ^
  5298. ; $0000   $4000       $5800        $5B00          $5C00         $5CB6 = CHANS
  5299. ;
  5300. ;
  5301. ;  --+----------+---+---------+-----------+---+------------+--+---+--
  5302. ;    | Channel  |$80|  BASIC  | Variables |$80| Edit Line  |NL|$80|
  5303. ;    |   Info   |   | Program |   Area    |   | or Command |  |   |
  5304. ;  --+----------+---+---------+-----------+---+------------+--+---+--
  5305. ;    ^              ^         ^               ^                   ^
  5306. ;  CHANS           PROG      VARS           E_LINE              WORKSP
  5307. ;
  5308. ;
  5309. ;                             ---5-->         <---2---  <--3---
  5310. ;  --+-------+--+------------+-------+-------+---------+-------+-+---+------+
  5311. ;    | INPUT |NL| Temporary  | Calc. | Spare | Machine | GOSUB |?|$3E| UDGs |
  5312. ;    | data  |  | Work Space | Stack |       |  Stack  | Stack | |   |      |
  5313. ;  --+-------+--+------------+-------+-------+---------+-------+-+---+------+
  5314. ;    ^                       ^       ^       ^                   ^   ^      ^
  5315. ;  WORKSP                  STKBOT  STKEND   sp               RAMTOP UDG  P_RAMT
  5316. ;                                                                        
  5317.  
  5318. ; -------------------
  5319. ; Handle NEW command
  5320. ; -------------------
  5321. ; The NEW command is about to set all RAM below RAMTOP to zero and
  5322. ; then re-initialize the system. All RAM above RAMTOP should, and will be,
  5323. ; preserved.
  5324. ; There is nowhere to store values in RAM or on the stack which becomes
  5325. ; inoperable. Similarly PUSH and CALL instructions cannot be used to
  5326. ; store values or section common code. The alternate register set is the only
  5327. ; place available to store 3 persistent 16-bit system variables.
  5328.  
  5329. ;; NEW
  5330. L11B7:  DI                      ; disable interrupts - machine stack will be
  5331.                                 ; cleared.
  5332.         LD      A,$FF           ; flag coming from NEW.
  5333.         LD      DE,($5CB2)      ; fetch RAMTOP as top value.
  5334.         EXX                     ; switch in alternate set.
  5335.         LD      BC,($5CB4)      ; fetch P-RAMT differs on 16K/48K machines.
  5336.         LD      DE,($5C38)      ; fetch RASP/PIP.
  5337.         LD      HL,($5C7B)      ; fetch UDG    differs on 16K/48K machines.
  5338.         EXX                     ; switch back to main set and continue into...
  5339.  
  5340. ; ---------------------------
  5341. ; Main entry (initialization)
  5342. ; ---------------------------
  5343. ; This common code tests ram and sets it to zero re-initializing
  5344. ; all the non-zero system variables and channel information.
  5345. ; The A register tells if coming from START or NEW
  5346.  
  5347. ;; START-NEW
  5348. L11CB:  LD      B,A             ; save the flag for later branching.
  5349.  
  5350.         LD      A,$07           ; select a white border
  5351.         OUT     ($FE),A         ; and set it now.
  5352.  
  5353.         LD      A,$3F           ; load accumulator with last page in ROM.
  5354.         LD      I,A             ; set the I register - this remains constant
  5355.                                 ; and can't be in range $40 - $7F as 'snow'
  5356.                                 ; appears on the screen.
  5357.         NOP                     ; these seem unnecessary.
  5358.         NOP                     ;
  5359.         NOP                     ;
  5360.         NOP                     ;
  5361. ;        NOP                     ;
  5362. ;        NOP                     ;
  5363.                 RST 8
  5364.                 DB _TAPE_INIT
  5365.  
  5366. ; ------------
  5367. ; Check RAM
  5368. ; ------------
  5369. ; Typically a Spectrum will have 16K or 48K of Ram and this code will
  5370. ; test it all till it finds an unpopulated location or, less likely, a
  5371. ; faulty location. Usually it stops when it reaches the top $FFFF or
  5372. ; in the case of NEW the supplied top value. The entire screen turns
  5373. ; black with sometimes red stripes on black paper visible.
  5374.  
  5375. ;; ram-check
  5376. L11DA:  LD      H,D             ; transfer the top value to
  5377.         LD      L,E             ; the HL register pair.
  5378.  
  5379. ;; RAM-FILL
  5380. L11DC:  LD      (HL),$02        ; load with 2 - red ink on black paper
  5381.         DEC     HL              ; next lower
  5382.         CP      H               ; have we reached ROM - $3F ?
  5383.         JR      NZ,L11DC        ; back to RAM-FILL if not.
  5384.  
  5385. ;; RAM-READ
  5386. L11E2:  AND     A               ; clear carry - prepare to subtract
  5387.         SBC     HL,DE           ; subtract and add back setting
  5388.         ADD     HL,DE           ; carry when back at start.
  5389.         INC     HL              ; and increment for next iteration.
  5390.         JR      NC,L11EF        ; forward to RAM-DONE if we've got back to
  5391.                                 ; starting point with no errors.
  5392.  
  5393.         DEC     (HL)            ; decrement to 1.
  5394.         JR      Z,L11EF         ; forward to RAM-DONE if faulty.
  5395.  
  5396.         DEC     (HL)            ; decrement to zero.
  5397.         JR      Z,L11E2         ; back to RAM-READ if zero flag was set.
  5398.  
  5399. ;; RAM-DONE
  5400. L11EF:  DEC     HL              ; step back to last valid location.
  5401.         EXX                     ; regardless of state, set up possibly
  5402.                                 ; stored system variables in case from NEW.
  5403.         LD      ($5CB4),BC      ; insert P-RAMT.
  5404.         LD      ($5C38),DE      ; insert RASP/PIP.
  5405.         LD      ($5C7B),HL      ; insert UDG.
  5406.         EXX                     ; switch in main set.
  5407.         INC     B               ; now test if we arrived here from NEW.
  5408.         JR      Z,L1219         ; forward to RAM-SET if we did.
  5409.  
  5410. ; this section applies to START only.
  5411.  
  5412.         LD      ($5CB4),HL      ; set P-RAMT to the highest working RAM
  5413.                                 ; address.
  5414.         LD      DE,$3EAF        ; address of last byte of 'U' bitmap in ROM.
  5415.         LD      BC,$00A8        ; there are 21 user defined graphics.
  5416.         EX      DE,HL           ; switch pointers and make the UDGs a
  5417.         LDDR                    ; copy of the standard characters A - U.
  5418.         EX      DE,HL           ; switch the pointer to HL.
  5419.         INC     HL              ; update to start of 'A' in RAM.
  5420.         LD      ($5C7B),HL      ; make UDG system variable address the first
  5421.                                 ; bitmap.
  5422.         DEC     HL              ; point at RAMTOP again.
  5423.  
  5424.         LD      BC,$0040        ; set the values of
  5425.         LD      ($5C38),BC      ; the PIP and RASP system variables.
  5426.  
  5427. ; the NEW command path rejoins here.
  5428.  
  5429. ;; RAM-SET
  5430. L1219:  LD      ($5CB2),HL      ; set system variable RAMTOP to HL.
  5431.  
  5432.                 LD HL,CHARS-0X100       ;$3C00        ; a strange place to set the pointer to the
  5433.         LD      ($5C36),HL      ; character set, CHARS - as no printing yet.
  5434.  
  5435.         LD      HL,($5CB2)      ; fetch RAMTOP to HL again as we've lost it.
  5436.  
  5437.         LD      (HL),$3E        ; top of user ram holds GOSUB end marker
  5438.                                 ; an impossible line number - see RETURN.
  5439.                                 ; no significance in the number $3E. It has
  5440.                                 ; been traditional since the ZX80.
  5441.  
  5442.         DEC     HL              ; followed by empty byte (not important).
  5443.         LD      SP,HL           ; set up the machine stack pointer.
  5444.         DEC     HL              ;
  5445.         DEC     HL              ;
  5446.         LD      ($5C3D),HL      ; ERR_SP is where the error pointer is
  5447.                                 ; at moment empty - will take address MAIN-4
  5448.                                 ; at the call preceding that address,
  5449.                                 ; although interrupts and calls will make use
  5450.                                 ; of this location in meantime.
  5451.  
  5452.         IM      1               ; select interrupt mode 1.
  5453.         LD      IY,$5C3A        ; set IY to ERR_NR. IY can reach all standard
  5454.                                 ; system variables but shadow ROM system
  5455.                                 ; variables will be mostly out of range.
  5456.  
  5457.         EI                      ; enable interrupts now that we have a stack.
  5458.  
  5459.         LD      HL,$5CB6        ; the address of the channels - initially
  5460.                                 ; following system variables.
  5461.         LD      ($5C4F),HL      ; set the CHANS system variable.
  5462.  
  5463.         LD      DE,L15AF        ; address: init-chan in ROM.
  5464.         LD      BC,$0015        ; there are 21 bytes of initial data in ROM.
  5465.         EX      DE,HL           ; swap the pointers.
  5466.         LDIR                    ; copy the bytes to RAM.
  5467.  
  5468.         EX      DE,HL           ; swap pointers. HL points to program area.
  5469.         DEC     HL              ; decrement address.
  5470.         LD      ($5C57),HL      ; set DATADD to location before program area.
  5471.         INC     HL              ; increment again.
  5472.  
  5473.         LD      ($5C53),HL      ; set PROG the location where BASIC starts.
  5474.         LD      ($5C4B),HL      ; set VARS to same location with a
  5475.         LD      (HL),$80        ; variables end-marker.
  5476.         INC     HL              ; advance address.
  5477.         LD      ($5C59),HL      ; set E_LINE, where the edit line
  5478.                                 ; will be created.
  5479.                                 ; Note. it is not strictly necessary to
  5480.                                 ; execute the next fifteen bytes of code
  5481.                                 ; as this will be done by the call to SET-MIN.
  5482.                                 ; --
  5483.         LD      (HL),$0D        ; initially just has a carriage return
  5484.         INC     HL              ; followed by
  5485.         LD      (HL),$80        ; an end-marker.
  5486.         INC     HL              ; address the next location.
  5487.         LD      ($5C61),HL      ; set WORKSP - empty workspace.
  5488.         LD      ($5C63),HL      ; set STKBOT - bottom of the empty stack.
  5489.         LD      ($5C65),HL      ; set STKEND to the end of the empty stack.
  5490.                                 ; --
  5491.         LD      A,$38           ; the colour system is set to white paper,
  5492.                                 ; black ink, no flash or bright.
  5493.         LD      ($5C8D),A       ; set ATTR_P permanent colour attributes.
  5494.         LD      ($5C8F),A       ; set ATTR_T temporary colour attributes.
  5495.         LD      ($5C48),A       ; set BORDCR the border colour/lower screen
  5496.                                 ; attributes.
  5497.  
  5498.         LD      HL,$0523        ; The keyboard repeat and delay values
  5499.         LD      ($5C09),HL      ; are loaded to REPDEL and REPPER.
  5500.  
  5501.         DEC     (IY-$3A)        ; set KSTATE-0 to $FF.
  5502.         DEC     (IY-$36)        ; set KSTATE-4 to $FF.
  5503.                                 ; thereby marking both available.
  5504.  
  5505.         LD      HL,L15C6        ; set source to ROM Address: init-strm
  5506.         LD      DE,$5C10        ; set destination to system variable STRMS-FD
  5507.         LD      BC,$000E        ; copy the 14 bytes of initial 7 streams data
  5508.         LDIR                    ; from ROM to RAM.
  5509.  
  5510.         SET     1,(IY+$01)      ; update FLAGS  - signal printer in use.
  5511.  
  5512. ;===============================
  5513.                 CALL PRINTER_INITER
  5514. ;               CALL L0EDF                      ; call routine CLEAR-PRB to initialize system
  5515.                                                 ; variables associated with printer.
  5516. ;===============================
  5517.  
  5518.         LD      (IY+$31),$02    ; set DF_SZ the lower screen display size to
  5519.                                 ; two lines
  5520.         CALL    L0D6B           ; call routine CLS to set up system
  5521.                                 ; variables associated with screen and clear
  5522.                                 ; the screen and set attributes.
  5523.         XOR     A               ; clear accumulator so that we can address
  5524.         LD      DE,L1539 - 1    ; the message table directly.
  5525.         CALL    L0C0A           ; routine PO-MSG puts
  5526.                                 ; '(c) 1982 Sinclair Research Ltd'
  5527.                                 ; at bottom of display.
  5528.         SET     5,(IY+$02)      ; update TV_FLAG  - signal lower screen will
  5529.                                 ; require clearing.
  5530.  
  5531.         JR      L12A9           ; forward to MAIN-1
  5532.  
  5533. ; -------------------
  5534. ; Main execution loop
  5535. ; -------------------
  5536. ;
  5537. ;
  5538.  
  5539. ;; MAIN-EXEC
  5540. L12A2:  LD      (IY+$31),$02    ; set DF_SZ lower screen display file
  5541.                                 ; size to 2 lines.
  5542.         CALL    L1795           ; routine AUTO-LIST
  5543.  
  5544. ;; MAIN-1
  5545. L12A9:  CALL    L16B0           ; routine SET-MIN clears work areas.
  5546.  
  5547. ;; MAIN-2
  5548. L12AC:  LD      A,$00           ; select channel 'K' the keyboard
  5549.         CALL    L1601           ; routine CHAN-OPEN opens it
  5550.         CALL    L0F2C           ; routine EDITOR is called.
  5551.                                 ; Note the above routine is where the Spectrum
  5552.                                 ; waits for user-interaction. Perhaps the
  5553.                                 ; most common input at this stage
  5554.                                 ; is LOAD "".
  5555.         CALL    L1B17           ; routine LINE-SCAN scans the input.
  5556.         BIT     7,(IY+$00)      ; test ERR_NR - will be $FF if syntax
  5557.                                 ; is correct.
  5558.         JR      NZ,L12CF        ; forward, if correct, to MAIN-3.
  5559.  
  5560. ;
  5561.  
  5562.         BIT     4,(IY+$30)      ; test FLAGS2 - K channel in use ?
  5563.         JR      Z,L1303         ; forward to MAIN-4 if not.
  5564.  
  5565. ;
  5566.  
  5567.         LD      HL,($5C59)      ; an editing error so address E_LINE.
  5568.         CALL    L11A7           ; routine REMOVE-FP removes the hidden
  5569.                                 ; floating-point forms.
  5570.         LD      (IY+$00),$FF    ; system variable ERR_NR is reset to 'OK'.
  5571.         JR      L12AC           ; back to MAIN-2 to allow user to correct.
  5572.  
  5573. ; ---
  5574.  
  5575. ; the branch was here if syntax has passed test.
  5576.  
  5577. ;; MAIN-3
  5578. L12CF:  LD      HL,($5C59)      ; fetch the edit line address from E_LINE.
  5579.         LD      ($5C5D),HL      ; system variable CH_ADD is set to first
  5580.                                 ; character of edit line.
  5581.                                 ; Note. the above two instructions are a little
  5582.                                 ; inadequate.
  5583.                                 ; They are repeated with a subtle difference
  5584.                                 ; at the start of the next subroutine and are
  5585.                                 ; therefore not required above.
  5586.  
  5587.         CALL    L19FB           ; routine E-LINE-NO will fetch any line
  5588.                                 ; number to BC if this is a program line.
  5589.  
  5590.         LD      A,B             ; test if the number of
  5591.         OR      C               ; the line is non-zero.
  5592.         JP      NZ,L155D        ; jump forward to MAIN-ADD if so to add the
  5593.                                 ; line to the BASIC program.
  5594.  
  5595. ; Has the user just pressed the ENTER key ?
  5596.  
  5597.         RST     18H             ; GET-CHAR gets character addressed by CH_ADD.
  5598.         CP      $0D             ; is it a carriage return ?
  5599.         JR      Z,L12A2         ; back to MAIN-EXEC if so for an automatic
  5600.                                 ; listing.
  5601.  
  5602. ; this must be a direct command.
  5603.  
  5604.         BIT     0,(IY+$30)      ; test FLAGS2 - clear the main screen ?
  5605.         CALL    NZ,L0DAF        ; routine CL-ALL, if so, e.g. after listing.
  5606.         CALL    L0D6E           ; routine CLS-LOWER anyway.
  5607.         LD      A,$19           ; compute scroll count to 25 minus
  5608.         SUB     (IY+$4F)        ; value of S_POSN_hi.
  5609.         LD      ($5C8C),A       ; update SCR_CT system variable.
  5610.         SET     7,(IY+$01)      ; update FLAGS - signal running program.
  5611.         LD      (IY+$00),$FF    ; set ERR_NR to 'OK'.
  5612.         LD      (IY+$0A),$01    ; set NSPPC to one for first statement.
  5613.         CALL    L1B8A           ; call routine LINE-RUN to run the line.
  5614.                                 ; sysvar ERR_SP therefore addresses MAIN-4
  5615.  
  5616. ; Examples of direct commands are RUN, CLS, LOAD "", PRINT USR 40000,
  5617. ; LPRINT "A"; etc..
  5618. ; If a user written machine-code program disables interrupts then it
  5619. ; must enable them to pass the next step. We also jumped to here if the
  5620. ; keyboard was not being used.
  5621.  
  5622. ;; MAIN-4
  5623. L1303:  HALT                    ; wait for interrupt.
  5624.  
  5625.         RES     5,(IY+$01)      ; update FLAGS - signal no new key.
  5626.         BIT     1,(IY+$30)      ; test FLAGS2 - is printer buffer clear ?
  5627.         CALL    NZ,L0ECD        ; call routine COPY-BUFF if not.
  5628.                                 ; Note. the programmer has neglected
  5629.                                 ; to set bit 1 of FLAGS first.
  5630.  
  5631.         LD      A,($5C3A)       ; fetch ERR_NR
  5632.         INC     A               ; increment to give true code.
  5633.  
  5634. ; Now deal with a runtime error as opposed to an editing error.
  5635. ; However if the error code is now zero then the OK message will be printed.
  5636.  
  5637. ;; MAIN-G
  5638. L1313:  PUSH    AF              ; save the error number.
  5639.  
  5640.         LD      HL,$0000        ; prepare to clear some system variables.
  5641.         LD      (IY+$37),H      ; clear all the bits of FLAGX.
  5642.         LD      (IY+$26),H      ; blank X_PTR_hi to suppress error marker.
  5643.         LD      ($5C0B),HL      ; blank DEFADD to signal that no defined
  5644.                                 ; function is currently being evaluated.
  5645.  
  5646.         LD      HL,$0001        ; explicit - inc hl would do.
  5647.         LD      ($5C16),HL      ; ensure STRMS-00 is keyboard.
  5648.  
  5649.         CALL    L16B0           ; routine SET-MIN clears workspace etc.
  5650.         RES     5,(IY+$37)      ; update FLAGX - signal in EDIT not INPUT mode.
  5651.                                 ; Note. all the bits were reset earlier.
  5652.  
  5653.         CALL    L0D6E           ; call routine CLS-LOWER.
  5654.         SET     5,(IY+$02)      ; update TV_FLAG - signal lower screen
  5655.                                 ; requires clearing.
  5656.  
  5657.         POP     AF              ; bring back the error number
  5658.         LD      B,A             ; and make a copy in B.
  5659.         CP      $0A             ; is it a print-ready digit ?
  5660.         JR      C,L133C         ; forward to MAIN-5 if so.
  5661.  
  5662.         ADD     A,$07           ; add ASCII offset to letters.
  5663.  
  5664. ;; MAIN-5
  5665. L133C:  CALL    L15EF           ; call routine OUT-CODE to print the code.
  5666.  
  5667.         LD      A,$20           ; followed by a space.
  5668.         RST     10H             ; PRINT-A
  5669.  
  5670.         LD      A,B             ; fetch stored report code.
  5671.         LD      DE,L1391        ; address: rpt-mesgs.
  5672.         CALL    L0C0A           ; call routine PO-MSG to print.
  5673.  
  5674. X1349
  5675.                 IF BAS48_ONLY=1
  5676.                 XOR A
  5677.                 LD DE,L1536
  5678.                 ELSE
  5679.                 CALL L3B3B              ; Spectrum 128 patch
  5680.                 NOP
  5681.                 ENDIF
  5682.  
  5683. L134D:  CALL    L0C0A           ; routine PO-MSG prints them although it would
  5684.                                 ; be more succinct to use RST $10.
  5685.  
  5686.         LD      BC,($5C45)      ; fetch PPC the current line number.
  5687.         CALL    L1A1B           ; routine OUT-NUM-1 will print that
  5688.         LD      A,$3A           ; then a ':'.
  5689.         RST     10H             ; PRINT-A
  5690.  
  5691.         LD      C,(IY+$0D)      ; then SUBPPC for statement
  5692.         LD      B,$00           ; limited to 127
  5693.         CALL    L1A1B           ; routine OUT-NUM-1
  5694.  
  5695.         CALL    L1097           ; routine CLEAR-SP clears editing area.
  5696.                                 ; which probably contained 'RUN'.
  5697.         LD      A,($5C3A)       ; fetch ERR_NR again
  5698.         INC     A               ; test for no error originally $FF.
  5699.         JR      Z,L1386         ; forward to MAIN-9 if no error.
  5700.  
  5701.         CP      $09             ; is code Report 9 STOP ?
  5702.         JR      Z,L1373         ; forward to MAIN-6 if so
  5703.  
  5704.         CP      $15             ; is code Report L Break ?
  5705.         JR      NZ,L1376        ; forward to MAIN-7 if not
  5706.  
  5707. ; Stop or Break was encountered so consider CONTINUE.
  5708.  
  5709. ;; MAIN-6
  5710. L1373:  INC     (IY+$0D)        ; increment SUBPPC to next statement.
  5711.  
  5712. ;; MAIN-7
  5713. L1376:  LD      BC,$0003        ; prepare to copy 3 system variables to
  5714.         LD      DE,$5C70        ; address OSPPC - statement for CONTINUE.
  5715.                                 ; also updating OLDPPC line number below.
  5716.  
  5717.         LD      HL,$5C44        ; set source top to NSPPC next statement.
  5718.         BIT     7,(HL)          ; did BREAK occur before the jump ?
  5719.                                 ; e.g. between GO TO and next statement.
  5720.         JR      Z,L1384         ; skip forward to MAIN-8, if not, as setup
  5721.                                 ; is correct.
  5722.  
  5723.         ADD     HL,BC           ; set source to SUBPPC number of current
  5724.                                 ; statement/line which will be repeated.
  5725.  
  5726. ;; MAIN-8
  5727. L1384:  LDDR                    ; copy PPC to OLDPPC and SUBPPC to OSPCC
  5728.                                 ; or NSPPC to OLDPPC and NEWPPC to OSPCC
  5729.  
  5730. ;; MAIN-9
  5731. L1386:  LD      (IY+$0A),$FF    ; update NSPPC - signal 'no jump'.
  5732.         RES     3,(IY+$01)      ; update FLAGS  - signal use 'K' mode for
  5733.                                 ; the first character in the editor and
  5734.         JP      L12AC           ; jump back to MAIN-2.
  5735.  
  5736.  
  5737. ; ----------------------
  5738. ; Canned report messages
  5739. ; ----------------------
  5740. ; The Error reports with the last byte inverted. The first entry
  5741. ; is a dummy entry. The last, which begins with $7F, the Spectrum
  5742. ; character for copyright symbol, is placed here for convenience
  5743. ; as is the preceding comma and space.
  5744. ; The report line must accommodate a 4-digit line number and a 3-digit
  5745. ; statement number which limits the length of the message text to twenty
  5746. ; characters.
  5747. ; e.g.  "B Integer out of range, 1000:127"
  5748.  
  5749. ;; rpt-mesgs
  5750. L1391           DB $80
  5751.                 DC "OK"                         ;DB    'O','K'+$80              ; 0
  5752.                 DC "NEXT without FOR"           ;DEFM    "NEXT without FO"
  5753.                                                 ;DB    'R'+$80          ; 1
  5754.                 DC "Variable not found"         ;DEFM    "Variable not foun"
  5755.                                                 ;DB    'd'+$80          ; 2
  5756.                 DC "Subscript wrong"            ;DEFM    "Subscript wron"
  5757.                                                 ;DB    'g'+$80          ; 3
  5758.                 DC "Out of memory"              ;DEFM    "Out of memor"
  5759.                                                 ;DB    'y'+$80          ; 4
  5760.                 DC "Out of screen"              ;DEFM    "Out of scree"
  5761.                                                 ;DB    'n'+$80          ; 5
  5762.                 DC "Number too big"             ;DEFM    "Number too bi"
  5763.                                                 ;DB    'g'+$80          ; 6
  5764.                 DC "RETURN without GOSUB"       ;DEFM    "RETURN without GOSU"
  5765.                                                 ;DB    'B'+$80          ; 7
  5766.                 DC "End of file"                ;DEFM    "End of fil"
  5767.                                                 ;DB    'e'+$80          ; 8
  5768.                 DC "STOP statement"             ;DEFM    "STOP statemen"
  5769.                                                 ;DB    't'+$80          ; 9
  5770.                 DC "Invalid argument"           ;DEFM    "Invalid argumen"
  5771.                                                 ;DB    't'+$80          ; A
  5772.                 DC "Integer out of range"       ;DEFM    "Integer out of rang"
  5773.                                                 ;DB    'e'+$80          ; B
  5774.                 DC "Nonsense in BASIC"          ;DEFM    "Nonsense in BASI"
  5775.                                                 ;DB    'C'+$80          ; C
  5776.                 DC "BREAK - CONT repeats"       ;DEFM    "BREAK - CONT repeat"
  5777.                                                 ;DB    's'+$80          ; D
  5778.                 DC "Out of DATA"                ;DEFM    "Out of DAT"
  5779.                                                 ;DB    'A'+$80          ; E
  5780.                 DC "Invalid file name"          ;DEFM    "Invalid file nam"
  5781.                                                 ;DB    'e'+$80          ; F
  5782.                 DC "No room for line"           ;DEFM    "No room for lin"
  5783.                                                 ;DB    'e'+$80          ; G
  5784.                 DC "STOP in INPUT"              ;DEFM    "STOP in INPU"
  5785.                                                 ;DB    'T'+$80          ; H
  5786.                 DC "FOR without NEXT"           ;DEFM    "FOR without NEX"
  5787.                                                 ;DB    'T'+$80          ; I
  5788.                 DC "Invalid I/O device"         ;DEFM    "Invalid I/O devic"
  5789.                                                 ;DB    'e'+$80          ; J
  5790.                 DC "Invalid colour"             ;DEFM    "Invalid colou"
  5791.                                                 ;DB    'r'+$80          ; K
  5792.                 DC "BREAK into program"         ;DEFM    "BREAK into progra"
  5793.                                                 ;DB    'm'+$80          ; L
  5794.                 DC "RAMTOP no good"             ;DEFM    "RAMTOP no goo"
  5795.                                                 ;DB    'd'+$80          ; M
  5796.                 DC "Statement lost"             ;DEFM    "Statement los"
  5797.                                                 ;DB    't'+$80          ; N
  5798.                 DC "Invalid stream"             ;DEFM    "Invalid strea"
  5799.                                                 ;DB    'm'+$80          ; O
  5800.                 DC "FN without DEF"             ;DEFM    "FN without DE"
  5801.                                                 ;DB    'F'+$80          ; P
  5802.                 DC "Parameter error"            ;DEFM    "Parameter erro"
  5803.                                                 ;DB    'r'+$80          ; Q
  5804.                 DC "Tape loading error"         ;DEFM    "Tape loading erro"
  5805.                                                 ;DB    'r'+$80          ; R
  5806. L1536           EQU $-1
  5807. ;; comma-sp  
  5808. L1537           DC ", "                         ;DB    ',',' '+$80              ; used in report line.
  5809. ;; copyright
  5810. L1539           DB $7F                          ; copyright
  5811.                 DC " 1982 Sinclair Research Ltd"        ;DEFM    " 1982 Sinclair Research Lt"
  5812.                                                         ;DB    'd'+$80
  5813.  
  5814.  
  5815. ; -------------
  5816. ; REPORT-G
  5817. ; -------------
  5818. ; Note ERR_SP points here during line entry which allows the
  5819. ; normal 'Out of Memory' report to be augmented to the more
  5820. ; precise 'No Room for line' report.
  5821.  
  5822. ;; REPORT-G
  5823. ; No Room for line
  5824. L1555:  LD      A,$10           ; i.e. 'G' -$30 -$07
  5825.         LD      BC,$0000        ; this seems unnecessary.
  5826.         JP      L1313           ; jump back to MAIN-G
  5827.  
  5828. ; -----------------------------
  5829. ; Handle addition of BASIC line
  5830. ; -----------------------------
  5831. ; Note this is not a subroutine but a branch of the main execution loop.
  5832. ; System variable ERR_SP still points to editing error handler.
  5833. ; A new line is added to the BASIC program at the appropriate place.
  5834. ; An existing line with same number is deleted first.
  5835. ; Entering an existing line number deletes that line.
  5836. ; Entering a non-existent line allows the subsequent line to be edited next.
  5837.  
  5838. ;; MAIN-ADD
  5839. L155D:  LD      ($5C49),BC      ; set E_PPC to extracted line number.
  5840.         LD      HL,($5C5D)      ; fetch CH_ADD - points to location after the
  5841.                                 ; initial digits (set in E_LINE_NO).
  5842.         EX      DE,HL           ; save start of BASIC in DE.
  5843.  
  5844.         LD      HL,L1555        ; Address: REPORT-G
  5845.         PUSH    HL              ; is pushed on stack and addressed by ERR_SP.
  5846.                                 ; the only error that can occur is
  5847.                                 ; 'Out of memory'.
  5848.  
  5849.         LD      HL,($5C61)      ; fetch WORKSP - end of line.
  5850.         SCF                     ; prepare for true subtraction.
  5851.         SBC     HL,DE           ; find length of BASIC and
  5852.         PUSH    HL              ; save it on stack.
  5853.         LD      H,B             ; transfer line number
  5854.         LD      L,C             ; to HL register.
  5855.         CALL    L196E           ; routine LINE-ADDR will see if
  5856.                                 ; a line with the same number exists.
  5857.         JR      NZ,L157D        ; forward if no existing line to MAIN-ADD1.
  5858.  
  5859.         CALL    L19B8           ; routine NEXT-ONE finds the existing line.
  5860.         CALL    L19E8           ; routine RECLAIM-2 reclaims it.
  5861.  
  5862. ;; MAIN-ADD1
  5863. L157D:  POP     BC              ; retrieve the length of the new line.
  5864.         LD      A,C             ; and test if carriage return only
  5865.         DEC     A               ; i.e. one byte long.
  5866.         OR      B               ; result would be zero.
  5867.         JR      Z,L15AB         ; forward to MAIN-ADD2 is so.
  5868.  
  5869.         PUSH    BC              ; save the length again.
  5870.         INC     BC              ; adjust for inclusion
  5871.         INC     BC              ; of line number (two bytes)
  5872.         INC     BC              ; and line length
  5873.         INC     BC              ; (two bytes).
  5874.         DEC     HL              ; HL points to location before the destination
  5875.  
  5876.         LD      DE,($5C53)      ; fetch the address of PROG
  5877.         PUSH    DE              ; and save it on the stack
  5878.         CALL    L1655           ; routine MAKE-ROOM creates BC spaces in
  5879.                                 ; program area and updates pointers.
  5880.         POP     HL              ; restore old program pointer.
  5881.         LD      ($5C53),HL      ; and put back in PROG as it may have been
  5882.                                 ; altered by the POINTERS routine.
  5883.  
  5884.         POP     BC              ; retrieve BASIC length
  5885.         PUSH    BC              ; and save again.
  5886.  
  5887.         INC     DE              ; points to end of new area.
  5888.         LD      HL,($5C61)      ; set HL to WORKSP - location after edit line.
  5889.         DEC     HL              ; decrement to address end marker.
  5890.         DEC     HL              ; decrement to address carriage return.
  5891.         LDDR                    ; copy the BASIC line back to initial command.
  5892.  
  5893.         LD      HL,($5C49)      ; fetch E_PPC - line number.
  5894.         EX      DE,HL           ; swap it to DE, HL points to last of
  5895.                                 ; four locations.
  5896.         POP     BC              ; retrieve length of line.
  5897.         LD      (HL),B          ; high byte last.
  5898.         DEC     HL              ;
  5899.         LD      (HL),C          ; then low byte of length.
  5900.         DEC     HL              ;
  5901.         LD      (HL),E          ; then low byte of line number.
  5902.         DEC     HL              ;
  5903.         LD      (HL),D          ; then high byte range $0 - $27 (1-9999).
  5904.  
  5905. ;; MAIN-ADD2
  5906. L15AB:  POP     AF              ; drop the address of Report G
  5907.         JP      L12A2           ; and back to MAIN-EXEC producing a listing
  5908.                                 ; and to reset ERR_SP in EDITOR.
  5909.  
  5910.  
  5911. ; ---------------------------
  5912. ; Initial channel information
  5913. ; ---------------------------
  5914. ; This initial channel information is copied from ROM to RAM,
  5915. ; during initialization. It's new location is after the system
  5916. ; variables and is addressed by the system variable CHANS
  5917. ; which means that it can slide up and down in memory.
  5918. ; The table is never searched and the last character which could be anything
  5919. ; other than a comma provides a convenient resting place for DATADD.
  5920.  
  5921. ;; init-chan
  5922. L15AF           DW L09F4                ; PRINT-OUT
  5923.                 DW L10A8                ; KEY-INPUT
  5924.                 DB "K"
  5925.                 DW L09F4                ; PRINT-OUT
  5926.                 DW L15C4                ; REPORT-J
  5927.                 DB "S"
  5928.                 DW L0F81                ; ADD-CHAR
  5929.                 DW L15C4                ; REPORT-J
  5930.                 DB "R"
  5931. ;=======================================
  5932.                 DW PRN_TOKEN
  5933. ;               DW L09F4                ; PRINT-OUT
  5934. ;=======================================
  5935.                 DW L15C4                ; REPORT-J
  5936.                 DB "P"
  5937.  
  5938.         DB    $80             ; End Marker
  5939.  
  5940. ;; REPORT-J
  5941. L15C4:  RST     08H             ; ERROR-1
  5942.         DB    $12             ; Error Report: Invalid I/O device
  5943.  
  5944.  
  5945. ; -------------------
  5946. ; Initial stream data
  5947. ; -------------------
  5948. ; This is the initial stream data for the seven streams $FD - $03 that is
  5949. ; copied from ROM to the STRMS system variables area during initialization.
  5950. ; There are reserved locations there for another 12 streams.
  5951. ; Each location contains an offset to the second byte of a channel.
  5952. ; The first byte of a channel can't be used as that would result in an
  5953. ; offset of zero for some and zero is used to denote that a stream is closed.
  5954.  
  5955. ;; init-strm
  5956. L15C6:  DB    $01, $00        ; stream $FD offset to channel 'K'
  5957.         DB    $06, $00        ; stream $FE offset to channel 'S'
  5958.         DB    $0B, $00        ; stream $FF offset to channel 'R'
  5959.  
  5960.         DB    $01, $00        ; stream $00 offset to channel 'K'
  5961.         DB    $01, $00        ; stream $01 offset to channel 'K'
  5962.         DB    $06, $00        ; stream $02 offset to channel 'S'
  5963.         DB    $10, $00        ; stream $03 offset to channel 'P'
  5964.  
  5965. ; ----------------------------
  5966. ; Control for input subroutine
  5967. ; ----------------------------
  5968. ;
  5969.  
  5970. ;; WAIT-KEY
  5971. L15D4:  BIT     5,(IY+$02)      ; test TV_FLAG - clear lower screen ?
  5972.         JR      NZ,L15DE        ; forward to WAIT-KEY1 if so.
  5973.  
  5974.         SET     3,(IY+$02)      ; update TV_FLAG - signal reprint the edit
  5975.                                 ; line to the lower screen.
  5976.  
  5977. ;; WAIT-KEY1
  5978. L15DE:  CALL    L15E6           ; routine INPUT-AD is called.
  5979.         RET     C               ; return with acceptable keys.
  5980.  
  5981.         JR      Z,L15DE         ; back to WAIT-KEY1 if no key is pressed
  5982.                                 ; or it has been handled within INPUT-AD.
  5983.  
  5984. ; Note. When inputting from the keyboard all characters are returned with
  5985. ; above conditions so this path is never taken.
  5986.  
  5987. ;; REPORT-8
  5988. L15E4:  RST     08H             ; ERROR-1
  5989.         DB    $07             ; Error Report: End of file
  5990.  
  5991. ; ------------------------------
  5992. ; Make HL point to input address
  5993. ; ------------------------------
  5994. ; This routine fetches the address of the input stream from the current
  5995. ; channel area using system variable CURCHL.
  5996.  
  5997. ;; INPUT-AD
  5998. L15E6:  EXX                     ; switch in alternate set.
  5999.         PUSH    HL              ; save HL register
  6000.         LD      HL,($5C51)      ; fetch address of CURCHL - current channel.
  6001.         INC     HL              ; step over output routine
  6002.         INC     HL              ; to point to low byte of input routine.
  6003.         JR      L15F7           ; forward to CALL-SUB.
  6004.  
  6005. ; -------------------
  6006. ; Main Output Routine
  6007. ; -------------------
  6008. ; The entry point OUT-CODE is called on five occasions to print
  6009. ; the ASCII equivalent of a value 0-9.
  6010. ;
  6011. ; PRINT-A-2 is a continuation of the RST 10 to print any character.
  6012. ; Both print to the current channel and the printing of control codes
  6013. ; may alter that channel to divert subsequent RST 10 instructions
  6014. ; to temporary routines. The normal channel is $09F4.
  6015.  
  6016. ;; OUT-CODE
  6017. L15EF:  LD      E,$30           ; add 48 decimal to give ASCII
  6018.         ADD     A,E             ; character '0' to '9'.
  6019.  
  6020. ;; PRINT-A-2
  6021. L15F2:  EXX                     ; switch in alternate set
  6022.         PUSH    HL              ; save HL register
  6023.         LD      HL,($5C51)      ; fetch CURCHL the current channel.
  6024.  
  6025. ; input-ad rejoins here also.
  6026.  
  6027. ;; CALL-SUB
  6028. L15F7:  LD      E,(HL)          ; put the low byte in E.
  6029.         INC     HL              ; advance address.
  6030.         LD      D,(HL)          ; put the high byte to D.
  6031.         EX      DE,HL           ; transfer the stream to HL.
  6032.         CALL    L162C           ; use routine CALL-JUMP.
  6033.                                 ; in effect CALL (HL).
  6034.  
  6035.         POP     HL              ; restore saved HL register.
  6036.         EXX                     ; switch back to the main set and
  6037.         RET                     ; return.
  6038.  
  6039. ; ------------
  6040. ; Open channel
  6041. ; ------------
  6042. ; This subroutine is used by the ROM to open a channel 'K', 'S', 'R' or 'P'.
  6043. ; This is either for its own use or in response to a user's request, for
  6044. ; example, when '#' is encountered with output - PRINT, LIST etc.
  6045. ; or with input - INPUT, INKEY$ etc.
  6046. ; it is entered with a system stream $FD - $FF, or a user stream $00 - $0F
  6047. ; in the accumulator.
  6048.  
  6049. ;; CHAN-OPEN
  6050. L1601:  ADD     A,A             ; double the stream ($FF will become $FE etc.)
  6051.         ADD     A,$16           ; add the offset to stream 0 from $5C00
  6052.         LD      L,A             ; result to L
  6053.         LD      H,$5C           ; now form the address in STRMS area.
  6054.         LD      E,(HL)          ; fetch low byte of CHANS offset
  6055.         INC     HL              ; address next
  6056.         LD      D,(HL)          ; fetch high byte of offset
  6057.         LD      A,D             ; test that the stream is open.
  6058.         OR      E               ; zero if closed.
  6059.         JR      NZ,L1610        ; forward to CHAN-OP-1 if open.
  6060.  
  6061. ;; REPORT-Oa
  6062. L160E:  RST     08H             ; ERROR-1
  6063.         DB    $17             ; Error Report: Invalid stream
  6064.  
  6065. ; continue here if stream was open. Note that the offset is from CHANS
  6066. ; to the second byte of the channel.
  6067.  
  6068. ;; CHAN-OP-1
  6069. L1610:  DEC     DE              ; reduce offset so it points to the channel.
  6070.         LD      HL,($5C4F)      ; fetch CHANS the location of the base of
  6071.                                 ; the channel information area
  6072.         ADD     HL,DE           ; and add the offset to address the channel.
  6073.                                 ; and continue to set flags.
  6074.  
  6075. ; -----------------
  6076. ; Set channel flags
  6077. ; -----------------
  6078. ; This subroutine is used from ED-EDIT, str$ and read-in to reset the
  6079. ; current channel when it has been temporarily altered.
  6080.  
  6081. ;; CHAN-FLAG
  6082. L1615:  LD      ($5C51),HL      ; set CURCHL system variable to the
  6083.                                 ; address in HL
  6084.         RES     4,(IY+$30)      ; update FLAGS2  - signal K channel not in use.
  6085.                                 ; Note. provide a default for channel 'R'.
  6086.         INC     HL              ; advance past
  6087.         INC     HL              ; output routine.
  6088.         INC     HL              ; advance past
  6089.         INC     HL              ; input routine.
  6090.         LD      C,(HL)          ; pick up the letter.
  6091.         LD      HL,L162D        ; address: chn-cd-lu
  6092.         CALL    L16DC           ; routine INDEXER finds offset to a
  6093.                                 ; flag-setting routine.
  6094.  
  6095.         RET     NC              ; but if the letter wasn't found in the
  6096.                                 ; table just return now. - channel 'R'.
  6097.  
  6098.         LD      D,$00           ; prepare to add
  6099.         LD      E,(HL)          ; offset to E
  6100.         ADD     HL,DE           ; add offset to location of offset to form
  6101.                                 ; address of routine
  6102.  
  6103. ;; CALL-JUMP
  6104. L162C:  JP      (HL)            ; jump to the routine
  6105.  
  6106. ; Footnote. calling any location that holds JP (HL) is the equivalent to
  6107. ; a pseudo Z80 instruction CALL (HL). The ROM uses the instruction above.
  6108.  
  6109. ; --------------------------
  6110. ; Channel code look-up table
  6111. ; --------------------------
  6112. ; This table is used by the routine above to find one of the three
  6113. ; flag setting routines below it.
  6114. ; A zero end-marker is required as channel 'R' is not present.
  6115.  
  6116. ;; chn-cd-lu
  6117. L162D:  DB    'K', L1634-$-1  ; offset $06 to CHAN-K
  6118.         DB    'S', L1642-$-1  ; offset $12 to CHAN-S
  6119.         DB    'P', L164D-$-1  ; offset $1B to CHAN-P
  6120.  
  6121.         DB    $00             ; end marker.
  6122.  
  6123. ; --------------
  6124. ; Channel K flag
  6125. ; --------------
  6126. ; routine to set flags for lower screen/keyboard channel.
  6127.  
  6128. ;; CHAN-K
  6129. L1634:  SET     0,(IY+$02)      ; update TV_FLAG  - signal lower screen in use
  6130.         RES     5,(IY+$01)      ; update FLAGS    - signal no new key
  6131.         SET     4,(IY+$30)      ; update FLAGS2   - signal K channel in use
  6132.         JR      L1646           ; forward to CHAN-S-1 for indirect exit
  6133.  
  6134. ; --------------
  6135. ; Channel S flag
  6136. ; --------------
  6137. ; routine to set flags for upper screen channel.
  6138.  
  6139. ;; CHAN-S
  6140. L1642:  RES     0,(IY+$02)      ; TV_FLAG  - signal main screen in use
  6141.  
  6142. ;; CHAN-S-1
  6143. L1646:  RES     1,(IY+$01)      ; update FLAGS  - signal printer not in use
  6144.         JP      L0D4D           ; jump back to TEMPS and exit via that
  6145.                                 ; routine after setting temporary attributes.
  6146. ; --------------
  6147. ; Channel P flag
  6148. ; --------------
  6149. ; This routine sets a flag so that subsequent print related commands
  6150. ; print to printer or update the relevant system variables.
  6151. ; This status remains in force until reset by the routine above.
  6152.  
  6153. ;; CHAN-P
  6154. L164D:  SET     1,(IY+$01)      ; update FLAGS  - signal printer in use
  6155.         RET                     ; return
  6156.  
  6157. ; -----------------------
  6158. ; Just one space required
  6159. ; -----------------------
  6160. ; This routine is called once only to create a single space
  6161. ; in workspace by ADD-CHAR. It is slightly quicker than using a RST $30.
  6162. ; There are several instances in the calculator where the sequence
  6163. ; ld bc, 1; rst $30 could be replaced by a call to this routine but it
  6164. ; only gives a saving of one byte each time.
  6165.  
  6166. ;; ONE-SPACE
  6167. L1652:  LD      BC,$0001        ; create space for a single character.
  6168.  
  6169. ; ---------
  6170. ; Make Room
  6171. ; ---------
  6172. ; This entry point is used to create BC spaces in various areas such as
  6173. ; program area, variables area, workspace etc..
  6174. ; The entire free RAM is available to each BASIC statement.
  6175. ; On entry, HL addresses where the first location is to be created.
  6176. ; Afterwards, HL will point to the location before this.
  6177.  
  6178. ;; MAKE-ROOM
  6179. L1655:  PUSH    HL              ; save the address pointer.
  6180.         CALL    L1F05           ; routine TEST-ROOM checks if room
  6181.                                 ; exists and generates an error if not.
  6182.         POP     HL              ; restore the address pointer.
  6183.         CALL    L1664           ; routine POINTERS updates the
  6184.                                 ; dynamic memory location pointers.
  6185.                                 ; DE now holds the old value of STKEND.
  6186.         LD      HL,($5C65)      ; fetch new STKEND the top destination.
  6187.  
  6188.         EX      DE,HL           ; HL now addresses the top of the area to
  6189.                                 ; be moved up - old STKEND.
  6190.         LDDR                    ; the program, variables, etc are moved up.
  6191.         RET                     ; return with new area ready to be populated.
  6192.                                 ; HL points to location before new area,
  6193.                                 ; and DE to last of new locations.
  6194.  
  6195. ; -----------------------------------------------
  6196. ; Adjust pointers before making or reclaiming room
  6197. ; -----------------------------------------------
  6198. ; This routine is called by MAKE-ROOM to adjust upwards and by RECLAIM to
  6199. ; adjust downwards the pointers within dynamic memory.
  6200. ; The fourteen pointers to dynamic memory, starting with VARS and ending
  6201. ; with STKEND, are updated adding BC if they are higher than the position
  6202. ; in HL.  
  6203. ; The system variables are in no particular order except that STKEND, the first
  6204. ; free location after dynamic memory must be the last encountered.
  6205.  
  6206. ;; POINTERS
  6207. L1664:  PUSH    AF              ; preserve accumulator.
  6208.         PUSH    HL              ; put pos pointer on stack.
  6209.         LD      HL,$5C4B        ; address VARS the first of the
  6210.         LD      A,$0E           ; fourteen variables to consider.
  6211.  
  6212. ;; PTR-NEXT
  6213. L166B:  LD      E,(HL)          ; fetch the low byte of the system variable.
  6214.         INC     HL              ; advance address.
  6215.         LD      D,(HL)          ; fetch high byte of the system variable.
  6216.         EX      (SP),HL         ; swap pointer on stack with the variable
  6217.                                 ; pointer.
  6218.         AND     A               ; prepare to subtract.
  6219.         SBC     HL,DE           ; subtract variable address
  6220.         ADD     HL,DE           ; and add back
  6221.         EX      (SP),HL         ; swap pos with system variable pointer
  6222.         JR      NC,L167F        ; forward to PTR-DONE if var before pos
  6223.  
  6224.         PUSH    DE              ; save system variable address.
  6225.         EX      DE,HL           ; transfer to HL
  6226.         ADD     HL,BC           ; add the offset
  6227.         EX      DE,HL           ; back to DE
  6228.         LD      (HL),D          ; load high byte
  6229.         DEC     HL              ; move back
  6230.         LD      (HL),E          ; load low byte
  6231.         INC     HL              ; advance to high byte
  6232.         POP     DE              ; restore old system variable address.
  6233.  
  6234. ;; PTR-DONE
  6235. L167F:  INC     HL              ; address next system variable.
  6236.         DEC     A               ; decrease counter.
  6237.         JR      NZ,L166B        ; back to PTR-NEXT if more.
  6238.         EX      DE,HL           ; transfer old value of STKEND to HL.
  6239.                                 ; Note. this has always been updated.
  6240.         POP     DE              ; pop the address of the position.
  6241.  
  6242.         POP     AF              ; pop preserved accumulator.
  6243.         AND     A               ; clear carry flag preparing to subtract.
  6244.  
  6245.         SBC     HL,DE           ; subtract position from old stkend
  6246.         LD      B,H             ; to give number of data bytes
  6247.         LD      C,L             ; to be moved.
  6248.         INC     BC              ; increment as we also copy byte at old STKEND.
  6249.         ADD     HL,DE           ; recompute old stkend.
  6250.         EX      DE,HL           ; transfer to DE.
  6251.         RET                     ; return.
  6252.  
  6253.  
  6254.  
  6255. ; -------------------
  6256. ; Collect line number
  6257. ; -------------------
  6258. ; This routine extracts a line number, at an address that has previously
  6259. ; been found using LINE-ADDR, and it is entered at LINE-NO. If it encounters
  6260. ; the program 'end-marker' then the previous line is used and if that
  6261. ; should also be unacceptable then zero is used as it must be a direct
  6262. ; command. The program end-marker is the variables end-marker $80, or
  6263. ; if variables exist, then the first character of any variable name.
  6264.  
  6265. ;; LINE-ZERO
  6266. L168F:  DB    $00, $00        ; dummy line number used for direct commands
  6267.  
  6268.  
  6269. ;; LINE-NO-A
  6270. L1691:  EX      DE,HL           ; fetch the previous line to HL and set
  6271.         LD      DE,$168F        ; DE to LINE-ZERO should HL also fail.
  6272.  
  6273. ; -> The Entry Point.
  6274.  
  6275. ;; LINE-NO
  6276. L1695:  LD      A,(HL)          ; fetch the high byte - max $2F
  6277.         AND     $C0             ; mask off the invalid bits.
  6278.         JR      NZ,L1691        ; to LINE-NO-A if an end-marker.
  6279.  
  6280.         LD      D,(HL)          ; reload the high byte.
  6281.         INC     HL              ; advance address.
  6282.         LD      E,(HL)          ; pick up the low byte.
  6283.         RET                     ; return from here.
  6284.  
  6285. ; -------------------
  6286. ; Handle reserve room
  6287. ; -------------------
  6288. ; This is a continuation of the restart BC-SPACES
  6289.  
  6290. ;; RESERVE
  6291. L169E:  LD      HL,($5C63)      ; STKBOT first location of calculator stack
  6292.         DEC     HL              ; make one less than new location
  6293.         CALL    L1655           ; routine MAKE-ROOM creates the room.
  6294.         INC     HL              ; address the first new location
  6295.         INC     HL              ; advance to second
  6296.         POP     BC              ; restore old WORKSP
  6297.         LD      ($5C61),BC      ; system variable WORKSP was perhaps
  6298.                                 ; changed by POINTERS routine.
  6299.         POP     BC              ; restore count for return value.
  6300.         EX      DE,HL           ; switch. DE = location after first new space
  6301.         INC     HL              ; HL now location after new space
  6302.         RET                     ; return.
  6303.  
  6304. ; ---------------------------
  6305. ; Clear various editing areas
  6306. ; ---------------------------
  6307. ; This routine sets the editing area, workspace and calculator stack
  6308. ; to their minimum configurations as at initialization and indeed this
  6309. ; routine could have been relied on to perform that task.
  6310. ; This routine uses HL only and returns with that register holding
  6311. ; WORKSP/STKBOT/STKEND though no use is made of this. The routines also
  6312. ; reset MEM to its usual place in the systems variable area should it
  6313. ; have been relocated to a FOR-NEXT variable. The main entry point
  6314. ; SET-MIN is called at the start of the MAIN-EXEC loop and prior to
  6315. ; displaying an error.
  6316.  
  6317. ;; SET-MIN
  6318. L16B0:  LD      HL,($5C59)      ; fetch E_LINE
  6319.         LD      (HL),$0D        ; insert carriage return
  6320.         LD      ($5C5B),HL      ; make K_CUR keyboard cursor point there.
  6321.         INC     HL              ; next location
  6322.         LD      (HL),$80        ; holds end-marker $80
  6323.         INC     HL              ; next location becomes
  6324.         LD      ($5C61),HL      ; start of WORKSP
  6325.  
  6326. ; This entry point is used prior to input and prior to the execution,
  6327. ; or parsing, of each statement.
  6328.  
  6329. ;; SET-WORK
  6330. L16BF:  LD      HL,($5C61)      ; fetch WORKSP value
  6331.         LD      ($5C63),HL      ; and place in STKBOT
  6332.  
  6333. ; This entry point is used to move the stack back to its normal place
  6334. ; after temporary relocation during line entry and also from ERROR-3
  6335.  
  6336. ;; SET-STK
  6337. L16C5:  LD      HL,($5C63)      ; fetch STKBOT value
  6338.         LD      ($5C65),HL      ; and place in STKEND.
  6339.  
  6340.         PUSH    HL              ; perhaps an obsolete entry point.
  6341.         LD      HL,$5C92        ; normal location of MEM-0
  6342.         LD      ($5C68),HL      ; is restored to system variable MEM.
  6343.         POP     HL              ; saved value not required.
  6344.         RET                     ; return.
  6345.  
  6346. ; ------------------
  6347. ; Reclaim edit-line?
  6348. ; ------------------
  6349. ; This seems to be legacy code from the ZX80/ZX81 as it is
  6350. ; not used in this ROM.
  6351. ; That task, in fact, is performed here by the dual-area routine CLEAR-SP.
  6352. ; This routine is designed to deal with something that is known to be in the
  6353. ; edit buffer and not workspace.
  6354. ; On entry, HL must point to the end of the something to be deleted.
  6355.  
  6356. ;; REC-EDIT
  6357. L16D4:  LD      DE,($5C59)      ; fetch start of edit line from E_LINE.
  6358.         JP      L19E5           ; jump forward to RECLAIM-1.
  6359.  
  6360. ; --------------------------
  6361. ; The Table INDEXING routine
  6362. ; --------------------------
  6363. ; This routine is used to search two-byte hash tables for a character
  6364. ; held in C, returning the address of the following offset byte.
  6365. ; if it is known that the character is in the table e.g. for priorities,
  6366. ; then the table requires no zero end-marker. If this is not known at the
  6367. ; outset then a zero end-marker is required and carry is set to signal
  6368. ; success.
  6369.  
  6370. ;; INDEXER-1
  6371. L16DB:  INC     HL              ; address the next pair of values.
  6372.  
  6373. ; -> The Entry Point.
  6374.  
  6375. ;; INDEXER
  6376. L16DC:  LD      A,(HL)          ; fetch the first byte of pair
  6377.         AND     A               ; is it the end-marker ?
  6378.         RET     Z               ; return with carry reset if so.
  6379.  
  6380.         CP      C               ; is it the required character ?
  6381.         INC     HL              ; address next location.
  6382.         JR      NZ,L16DB        ; back to INDEXER-1 if no match.
  6383.  
  6384.         SCF                     ; else set the carry flag.
  6385.         RET                     ; return with carry set
  6386.  
  6387. ; --------------------------------
  6388. ; The Channel and Streams Routines
  6389. ; --------------------------------
  6390. ; A channel is an input/output route to a hardware device
  6391. ; and is identified to the system by a single letter e.g. 'K' for
  6392. ; the keyboard. A channel can have an input and output route
  6393. ; associated with it in which case it is bi-directional like
  6394. ; the keyboard. Others like the upper screen 'S' are output
  6395. ; only and the input routine usually points to a report message.
  6396. ; Channels 'K' and 'S' are system channels and it would be inappropriate
  6397. ; to close the associated streams so a mechanism is provided to
  6398. ; re-attach them. When the re-attachment is no longer required, then
  6399. ; closing these streams resets them as at initialization.
  6400. ; The same also would have applied to channel 'R', the RS232 channel
  6401. ; as that is used by the system. It's input stream seems to have been
  6402. ; removed and it is not available to the user. However the channel could
  6403. ; not be removed entirely as its output routine was used by the system.
  6404. ; As a result of removing this channel, channel 'P', the printer is
  6405. ; erroneously treated as a system channel.
  6406. ; Ironically the tape streamer is not accessed through streams and
  6407. ; channels.
  6408. ; Early demonstrations of the Spectrum showed a single microdrive being
  6409. ; controlled by this ROM. Adverts also said that the network and RS232
  6410. ; were in this ROM. Channels 'M' and 'N' are user channels and have been
  6411. ; removed successfully if, as seems vaguely possible, they existed.
  6412.  
  6413. ; ---------------------
  6414. ; Handle CLOSE# command
  6415. ; ---------------------
  6416. ; This command allows streams to be closed after use.
  6417. ; Any temporary memory areas used by the stream would be reclaimed and
  6418. ; finally flags set or reset if necessary.
  6419.  
  6420. ;; CLOSE
  6421. L16E5:  CALL    L171E           ; routine STR-DATA fetches parameter
  6422.                                 ; from calculator stack and gets the
  6423.                                 ; existing STRMS data pointer address in HL
  6424.                                 ; and stream offset from CHANS in BC.
  6425.  
  6426.                                 ; Note. this offset could be zero if the
  6427.                                 ; stream is already closed. A check for this
  6428.                                 ; should occur now and an error should be
  6429.                                 ; generated, for example,
  6430.                                 ; Report S 'Stream already closed'.
  6431.  
  6432.         CALL    L1701           ; routine CLOSE-2 would perform any actions
  6433.                                 ; peculiar to that stream without disturbing
  6434.                                 ; data pointer to STRMS entry in HL.
  6435.  
  6436.         LD      BC,$0000        ; the stream is to be blanked.
  6437.         LD      DE,$A3E2        ; the number of bytes from stream 4, $5C1E,
  6438.                                 ; to $10000
  6439.         EX      DE,HL           ; transfer offset to HL, STRMS data pointer
  6440.                                 ; to DE.
  6441.         ADD     HL,DE           ; add the offset to the data pointer.  
  6442.         JR      C,L16FC         ; forward to CLOSE-1 if a non-system stream.
  6443.                                 ; i.e. higher than 3.
  6444.  
  6445. ; proceed with a negative result.
  6446.  
  6447.         LD      BC,L15C6 + 14   ; prepare the address of the byte after
  6448.                                 ; the initial stream data in ROM. ($15D4)
  6449.         ADD     HL,BC           ; index into the data table with negative value.
  6450.         LD      C,(HL)          ; low byte to C
  6451.         INC     HL              ; address next.
  6452.         LD      B,(HL)          ; high byte to B.
  6453.  
  6454. ; and for streams 0 - 3 just enter the initial data back into the STRMS entry
  6455. ; streams 0 - 2 can't be closed as they are shared by the operating system.
  6456. ; -> for streams 4 - 15 then blank the entry.
  6457.  
  6458. ;; CLOSE-1
  6459. L16FC:  EX      DE,HL           ; address of stream to HL.
  6460.         LD      (HL),C          ; place zero (or low byte).
  6461.         INC     HL              ; next address.
  6462.         LD      (HL),B          ; place zero (or high byte).
  6463.         RET                     ; return.
  6464.  
  6465. ; ------------------
  6466. ; CLOSE-2 Subroutine
  6467. ; ------------------
  6468. ; There is not much point in coming here.
  6469. ; The purpose was once to find the offset to a special closing routine,
  6470. ; in this ROM and within 256 bytes of the close stream look up table that
  6471. ; would reclaim any buffers associated with a stream. At least one has been
  6472. ; removed.
  6473.  
  6474. ;; CLOSE-2
  6475. L1701:  PUSH    HL              ; * save address of stream data pointer
  6476.                                 ; in STRMS on the machine stack.
  6477.         LD      HL,($5C4F)      ; fetch CHANS address to HL
  6478.         ADD     HL,BC           ; add the offset to address the second
  6479.                                 ; byte of the output routine hopefully.
  6480.         INC     HL              ; step past
  6481.         INC     HL              ; the input routine.
  6482.         INC     HL              ; to address channel's letter
  6483.         LD      C,(HL)          ; pick it up in C.
  6484.                                 ; Note. but if stream is already closed we
  6485.                                 ; get the value $10 (the byte preceding 'K').
  6486.         EX      DE,HL           ; save the pointer to the letter in DE.
  6487.         LD      HL,L1716        ; address: cl-str-lu in ROM.
  6488.         CALL    L16DC           ; routine INDEXER uses the code to get
  6489.                                 ; the 8-bit offset from the current point to
  6490.                                 ; the address of the closing routine in ROM.
  6491.                                 ; Note. it won't find $10 there!
  6492.         LD      C,(HL)          ; transfer the offset to C.
  6493.         LD      B,$00           ; prepare to add.
  6494.         ADD     HL,BC           ; add offset to point to the address of the
  6495.                                 ; routine that closes the stream.
  6496.                                 ; (and presumably removes any buffers that
  6497.                                 ; are associated with it.)
  6498.         JP      (HL)            ; jump to that routine.
  6499.  
  6500. ; --------------------------
  6501. ; CLOSE stream look-up table
  6502. ; --------------------------
  6503. ; This table contains an entry for a letter found in the CHANS area.
  6504. ; followed by an 8-bit displacement, from that byte's address in the
  6505. ; table to the routine that performs any ancillary actions associated
  6506. ; with closing the stream of that channel.
  6507. ; The table doesn't require a zero end-marker as the letter has been
  6508. ; picked up from a channel that has an open stream.
  6509.  
  6510. ;; cl-str-lu
  6511. L1716:  DB    'K', L171C-$-1  ; offset 5 to CLOSE-STR
  6512.         DB    'S', L171C-$-1  ; offset 3 to CLOSE-STR
  6513.         DB    'P', L171C-$-1  ; offset 1 to CLOSE-STR
  6514.  
  6515.  
  6516. ; ------------------------
  6517. ; Close Stream Subroutines
  6518. ; ------------------------
  6519. ; The close stream routines in fact have no ancillary actions to perform
  6520. ; which is not surprising with regard to 'K' and 'S'.
  6521.  
  6522. ;; CLOSE-STR                    
  6523. L171C:  POP     HL              ; * now just restore the stream data pointer
  6524.         RET                     ; in STRMS and return.
  6525.  
  6526. ; -----------
  6527. ; Stream data
  6528. ; -----------
  6529. ; This routine finds the data entry in the STRMS area for the specified
  6530. ; stream which is passed on the calculator stack. It returns with HL
  6531. ; pointing to this system variable and BC holding a displacement from
  6532. ; the CHANS area to the second byte of the stream's channel. If BC holds
  6533. ; zero, then that signifies that the stream is closed.
  6534.  
  6535. ;; STR-DATA
  6536. L171E:  CALL    L1E94           ; routine FIND-INT1 fetches parameter to A
  6537.         CP      $10             ; is it less than 16d ?
  6538.         JR      C,L1727         ; skip forward to STR-DATA1 if so.
  6539.  
  6540. ;; REPORT-Ob
  6541. L1725:  RST     08H             ; ERROR-1
  6542.         DB    $17             ; Error Report: Invalid stream
  6543.  
  6544. ;; STR-DATA1
  6545. L1727:  ADD     A,$03           ; add the offset for 3 system streams.
  6546.                                 ; range 00 - 15d becomes 3 - 18d.
  6547.         RLCA                    ; double as there are two bytes per
  6548.                                 ; stream - now 06 - 36d
  6549.         LD      HL,$5C10        ; address STRMS - the start of the streams
  6550.                                 ; data area in system variables.
  6551.         LD      C,A             ; transfer the low byte to A.
  6552.         LD      B,$00           ; prepare to add offset.
  6553.         ADD     HL,BC           ; add to address the data entry in STRMS.
  6554.  
  6555. ; the data entry itself contains an offset from CHANS to the address of the
  6556. ; stream
  6557.  
  6558.         LD      C,(HL)          ; low byte of displacement to C.
  6559.         INC     HL              ; address next.
  6560.         LD      B,(HL)          ; high byte of displacement to B.
  6561.         DEC     HL              ; step back to leave HL pointing to STRMS
  6562.                                 ; data entry.
  6563.         RET                     ; return with CHANS displacement in BC
  6564.                                 ; and address of stream data entry in HL.
  6565.  
  6566. ; --------------------
  6567. ; Handle OPEN# command
  6568. ; --------------------
  6569. ; Command syntax example: OPEN #5,"s"
  6570. ; On entry the channel code entry is on the calculator stack with the next
  6571. ; value containing the stream identifier. They have to swapped.
  6572.  
  6573. ;; OPEN
  6574. L1736:  RST     28H             ;; FP-CALC    ;s,c.
  6575.         DB    $01             ;;exchange    ;c,s.
  6576.         DB    $38             ;;end-calc
  6577.  
  6578.         CALL    L171E           ; routine STR-DATA fetches the stream off
  6579.                                 ; the stack and returns with the CHANS
  6580.                                 ; displacement in BC and HL addressing
  6581.                                 ; the STRMS data entry.
  6582.         LD      A,B             ; test for zero which
  6583.         OR      C               ; indicates the stream is closed.
  6584.         JR      Z,L1756         ; skip forward to OPEN-1 if so.
  6585.  
  6586. ; if it is a system channel then it can re-attached.
  6587.  
  6588.         EX      DE,HL           ; save STRMS address in DE.
  6589.         LD      HL,($5C4F)      ; fetch CHANS.
  6590.         ADD     HL,BC           ; add the offset to address the second
  6591.                                 ; byte of the channel.
  6592.         INC     HL              ; skip over the
  6593.         INC     HL              ; input routine.
  6594.         INC     HL              ; and address the letter.
  6595.         LD      A,(HL)          ; pick up the letter.
  6596.         EX      DE,HL           ; save letter pointer and bring back
  6597.                                 ; the STRMS pointer.
  6598.  
  6599.         CP      $4B             ; is it 'K' ?
  6600.         JR      Z,L1756         ; forward to OPEN-1 if so
  6601.  
  6602.         CP      $53             ; is it 'S' ?
  6603.         JR      Z,L1756         ; forward to OPEN-1 if so
  6604.  
  6605.         CP      $50             ; is it 'P' ?
  6606.         JR      NZ,L1725        ; back to REPORT-Ob if not.
  6607.                                 ; to report 'Invalid stream'.
  6608.  
  6609. ; continue if one of the upper-case letters was found.
  6610. ; and rejoin here from above if stream was closed.
  6611.  
  6612. ;; OPEN-1
  6613. L1756:  CALL    L175D           ; routine OPEN-2 opens the stream.
  6614.  
  6615. ; it now remains to update the STRMS variable.
  6616.  
  6617.         LD      (HL),E          ; insert or overwrite the low byte.
  6618.         INC     HL              ; address high byte in STRMS.
  6619.         LD      (HL),D          ; insert or overwrite the high byte.
  6620.         RET                     ; return.
  6621.  
  6622. ; -----------------
  6623. ; OPEN-2 Subroutine
  6624. ; -----------------
  6625. ; There is some point in coming here as, as well as once creating buffers,
  6626. ; this routine also sets flags.
  6627.  
  6628. ;; OPEN-2
  6629. L175D:  PUSH    HL              ; * save the STRMS data entry pointer.
  6630.         CALL    L2BF1           ; routine STK-FETCH now fetches the
  6631.                                 ; parameters of the channel string.
  6632.                                 ; start in DE, length in BC.
  6633.  
  6634.         LD      A,B             ; test that it is not
  6635.         OR      C               ; the null string.
  6636.         JR      NZ,L1767        ; skip forward to OPEN-3 with 1 character
  6637.                                 ; or more!
  6638.  
  6639. ;; REPORT-Fb
  6640. L1765:  RST     08H             ; ERROR-1
  6641.         DB    $0E             ; Error Report: Invalid file name
  6642.  
  6643. ;; OPEN-3
  6644. L1767:  PUSH    BC              ; save the length of the string.
  6645.         LD      A,(DE)          ; pick up the first character.
  6646.                                 ; Note. if the second character is used to
  6647.                                 ; distinguish between a binary or text
  6648.                                 ; channel then it will be simply a matter
  6649.                                 ; of setting bit 7 of FLAGX.
  6650.         AND     $DF             ; make it upper-case.
  6651.         LD      C,A             ; place it in C.
  6652.         LD      HL,L177A        ; address: op-str-lu is loaded.
  6653.         CALL    L16DC           ; routine INDEXER will search for letter.
  6654.         JR      NC,L1765        ; back to REPORT-F if not found
  6655.                                 ; 'Invalid filename'
  6656.  
  6657.         LD      C,(HL)          ; fetch the displacement to opening routine.
  6658.         LD      B,$00           ; prepare to add.
  6659.         ADD     HL,BC           ; now form address of opening routine.
  6660.         POP     BC              ; restore the length of string.
  6661.         JP      (HL)            ; now jump forward to the relevant routine.
  6662.  
  6663. ; -------------------------
  6664. ; OPEN stream look-up table
  6665. ; -------------------------
  6666. ; The open stream look-up table consists of matched pairs.
  6667. ; The channel letter is followed by an 8-bit displacement to the
  6668. ; associated stream-opening routine in this ROM.
  6669. ; The table requires a zero end-marker as the letter has been
  6670. ; provided by the user and not the operating system.
  6671.  
  6672. ;; op-str-lu
  6673. L177A:  DB    'K', L1781-$-1  ; $06 offset to OPEN-K
  6674.         DB    'S', L1785-$-1  ; $08 offset to OPEN-S
  6675.         DB    'P', L1789-$-1  ; $0A offset to OPEN-P
  6676.  
  6677.         DB    $00             ; end-marker.
  6678.  
  6679. ; ----------------------------
  6680. ; The Stream Opening Routines.
  6681. ; ----------------------------
  6682. ; These routines would have opened any buffers associated with the stream
  6683. ; before jumping forward to to OPEN-END with the displacement value in E
  6684. ; and perhaps a modified value in BC. The strange pathing does seem to
  6685. ; provide for flexibility in this respect.
  6686. ;
  6687. ; There is no need to open the printer buffer as it is there already
  6688. ; even if you are still saving up for a ZX Printer or have moved onto
  6689. ; something bigger. In any case it would have to be created after
  6690. ; the system variables but apart from that it is a simple task
  6691. ; and all but one of the ROM routines can handle a buffer in that position.
  6692. ; (PR-ALL-6 would require an extra 3 bytes of code).
  6693. ; However it wouldn't be wise to have two streams attached to the ZX Printer
  6694. ; as you can now, so one assumes that if PR_CC_hi was non-zero then
  6695. ; the OPEN-P routine would have refused to attach a stream if another
  6696. ; stream was attached.
  6697.  
  6698. ; Something of significance is being passed to these ghost routines in the
  6699. ; second character. Strings 'RB', 'RT' perhaps or a drive/station number.
  6700. ; The routine would have to deal with that and exit to OPEN_END with BC
  6701. ; containing $0001 or more likely there would be an exit within the routine.
  6702. ; Anyway doesn't matter, these routines are long gone.
  6703.  
  6704. ; -----------------
  6705. ; OPEN-K Subroutine
  6706. ; -----------------
  6707. ; Open Keyboard stream.
  6708.  
  6709. ;; OPEN-K
  6710. L1781:  LD      E,$01           ; 01 is offset to second byte of channel 'K'.
  6711.         JR      L178B           ; forward to OPEN-END
  6712.  
  6713. ; -----------------
  6714. ; OPEN-S Subroutine
  6715. ; -----------------
  6716. ; Open Screen stream.
  6717.  
  6718. ;; OPEN-S
  6719. L1785:  LD      E,$06           ; 06 is offset to 2nd byte of channel 'S'
  6720.         JR      L178B           ; to OPEN-END
  6721.  
  6722. ; -----------------
  6723. ; OPEN-P Subroutine
  6724. ; -----------------
  6725. ; Open Printer stream.
  6726.  
  6727. ;; OPEN-P
  6728. L1789:  LD      E,$10           ; 16d is offset to 2nd byte of channel 'P'
  6729.  
  6730. ;; OPEN-END
  6731. L178B:  DEC     BC              ; the stored length of 'K','S','P' or
  6732.                                 ; whatever is now tested. ??
  6733.         LD      A,B             ; test now if initial or residual length
  6734.         OR      C               ; is one character.
  6735.         JR      NZ,L1765        ; to REPORT-Fb 'Invalid file name' if not.
  6736.  
  6737.         LD      D,A             ; load D with zero to form the displacement
  6738.                                 ; in the DE register.
  6739.         POP     HL              ; * restore the saved STRMS pointer.
  6740.         RET                     ; return to update STRMS entry thereby
  6741.                                 ; signaling stream is open.
  6742.  
  6743. ; ----------------------------------------
  6744. ; Handle CAT, ERASE, FORMAT, MOVE commands
  6745. ; ----------------------------------------
  6746. ; These just generate an error report as the ROM is 'incomplete'.
  6747. ;
  6748. ; Luckily this provides a mechanism for extending these in a shadow ROM
  6749. ; but without the powerful mechanisms set up in this ROM.
  6750. ; An instruction fetch on $0008 may page in a peripheral ROM,
  6751. ; e.g. the Sinclair Interface 1 ROM, to handle these commands.
  6752. ; However that wasn't the plan.
  6753. ; Development of this ROM continued for another three months until the cost
  6754. ; of replacing it and the manual became unfeasible.
  6755. ; The ultimate power of channels and streams died at birth.
  6756.  
  6757. ;; CAT-ETC
  6758. L1793:  JR      L1725           ; to REPORT-Ob
  6759.  
  6760. ; -----------------
  6761. ; Perform AUTO-LIST
  6762. ; -----------------
  6763. ; This produces an automatic listing in the upper screen.
  6764.  
  6765. ;; AUTO-LIST
  6766. L1795:  LD      ($5C3F),SP      ; save stack pointer in LIST_SP
  6767.         LD      (IY+$02),$10    ; update TV_FLAG set bit 3
  6768.         CALL    L0DAF           ; routine CL-ALL.
  6769.         SET     0,(IY+$02)      ; update TV_FLAG  - signal lower screen in use
  6770.  
  6771.         LD      B,(IY+$31)      ; fetch DF_SZ to B.
  6772.         CALL    L0E44           ; routine CL-LINE clears lower display
  6773.                                 ; preserving B.
  6774.         RES     0,(IY+$02)      ; update TV_FLAG  - signal main screen in use
  6775.         SET     0,(IY+$30)      ; update FLAGS2  - signal unnecessary to
  6776.                                 ; clear main screen.
  6777.         LD      HL,($5C49)      ; fetch E_PPC current edit line to HL.
  6778.         LD      DE,($5C6C)      ; fetch S_TOP to DE, the current top line
  6779.                                 ; (initially zero)
  6780.         AND     A               ; prepare for true subtraction.
  6781.         SBC     HL,DE           ; subtract and
  6782.         ADD     HL,DE           ; add back.
  6783.         JR      C,L17E1         ; to AUTO-L-2 if S_TOP higher than E_PPC
  6784.                                 ; to set S_TOP to E_PPC
  6785.  
  6786.         PUSH    DE              ; save the top line number.
  6787.         CALL    L196E           ; routine LINE-ADDR gets address of E_PPC.
  6788.         LD      DE,$02C0        ; prepare known number of characters in
  6789.                                 ; the default upper screen.
  6790.         EX      DE,HL           ; offset to HL, program address to DE.
  6791.         SBC     HL,DE           ; subtract high value from low to obtain
  6792.                                 ; negated result used in addition.
  6793.         EX      (SP),HL         ; swap result with top line number on stack.
  6794.         CALL    L196E           ; routine LINE-ADDR  gets address of that
  6795.                                 ; top line in HL and next line in DE.
  6796.         POP     BC              ; restore the result to balance stack.
  6797.  
  6798. ;; AUTO-L-1
  6799. L17CE:  PUSH    BC              ; save the result.
  6800.         CALL    L19B8           ; routine NEXT-ONE gets address in HL of
  6801.                                 ; line after auto-line (in DE).
  6802.         POP     BC              ; restore result.
  6803.         ADD     HL,BC           ; compute back.
  6804.         JR      C,L17E4         ; to AUTO-L-3 if line 'should' appear
  6805.  
  6806.         EX      DE,HL           ; address of next line to HL.
  6807.         LD      D,(HL)          ; get line
  6808.         INC     HL              ; number
  6809.         LD      E,(HL)          ; in DE.
  6810.         DEC     HL              ; adjust back to start.
  6811.         LD      ($5C6C),DE      ; update S_TOP.
  6812.         JR      L17CE           ; to AUTO-L-1 until estimate reached.
  6813.  
  6814. ; ---
  6815.  
  6816. ; the jump was to here if S_TOP was greater than E_PPC
  6817.  
  6818. ;; AUTO-L-2
  6819. L17E1:  LD      ($5C6C),HL      ; make S_TOP the same as E_PPC.
  6820.  
  6821. ; continue here with valid starting point from above or good estimate
  6822. ; from computation
  6823.  
  6824. ;; AUTO-L-3
  6825. L17E4:  LD      HL,($5C6C)      ; fetch S_TOP line number to HL.
  6826.         CALL    L196E           ; routine LINE-ADDR gets address in HL.
  6827.                                 ; address of next in DE.
  6828.         JR      Z,L17ED         ; to AUTO-L-4 if line exists.
  6829.  
  6830.         EX      DE,HL           ; else use address of next line.
  6831.  
  6832. ;; AUTO-L-4
  6833. L17ED:  CALL    L1833           ; routine LIST-ALL                >>>
  6834.  
  6835. ; The return will be to here if no scrolling occurred
  6836.  
  6837.         RES     4,(IY+$02)      ; update TV_FLAG  - signal no auto listing.
  6838.         RET                     ; return.
  6839.  
  6840. ; ------------
  6841. ; Handle LLIST
  6842. ; ------------
  6843. ; A short form of LIST #3. The listing goes to stream 3 - default printer.
  6844.  
  6845. ;; LLIST
  6846. L17F5:  LD      A,$03           ; the usual stream for ZX Printer
  6847.         JR      L17FB           ; forward to LIST-1
  6848.  
  6849. ; -----------
  6850. ; Handle LIST
  6851. ; -----------
  6852. ; List to any stream.
  6853. ; Note. While a starting line can be specified it is
  6854. ; not possible to specify an end line.
  6855. ; Just listing a line makes it the current edit line.
  6856.  
  6857. ;; LIST
  6858. L17F9:  LD      A,$02           ; default is stream 2 - the upper screen.
  6859.  
  6860. ;; LIST-1
  6861. L17FB:  LD      (IY+$02),$00    ; the TV_FLAG is initialized with bit 0 reset
  6862.                                 ; indicating upper screen in use.
  6863.         CALL    L2530           ; routine SYNTAX-Z - checking syntax ?
  6864.         CALL    NZ,L1601        ; routine CHAN-OPEN if in run-time.
  6865.  
  6866.         RST     18H             ; GET-CHAR
  6867.         CALL    L2070           ; routine STR-ALTER will alter if '#'.
  6868.         JR      C,L181F         ; forward to LIST-4 not a '#' .
  6869.  
  6870.  
  6871.         RST     18H             ; GET-CHAR
  6872.         CP      $3B             ; is it ';' ?
  6873.         JR      Z,L1814         ; skip to LIST-2 if so.
  6874.  
  6875.         CP      $2C             ; is it ',' ?
  6876.         JR      NZ,L181A        ; forward to LIST-3 if neither separator.
  6877.  
  6878. ; we have, say,  LIST #15, and a number must follow the separator.
  6879.  
  6880. ;; LIST-2
  6881. L1814:  RST     20H             ; NEXT-CHAR
  6882.         CALL    L1C82           ; routine EXPT-1NUM
  6883.         JR      L1822           ; forward to LIST-5
  6884.  
  6885. ; ---
  6886.  
  6887. ; the branch was here with just LIST #3 etc.
  6888.  
  6889. ;; LIST-3
  6890. L181A:  CALL    L1CE6           ; routine USE-ZERO
  6891.         JR      L1822           ; forward to LIST-5
  6892.  
  6893. ; ---
  6894.  
  6895. ; the branch was here with LIST
  6896.  
  6897. ;; LIST-4
  6898. L181F:  CALL    L1CDE           ; routine FETCH-NUM checks if a number
  6899.                                 ; follows else uses zero.
  6900.  
  6901. ;; LIST-5
  6902. L1822:  CALL    L1BEE           ; routine CHECK-END quits if syntax OK >>>
  6903.  
  6904.         CALL    L1E99           ; routine FIND-INT2 fetches the number
  6905.                                 ; from the calculator stack in run-time.
  6906.         LD      A,B             ; fetch high byte of line number and
  6907.         AND     $3F             ; make less than $40 so that NEXT-ONE
  6908.                                 ; (from LINE-ADDR) doesn't lose context.
  6909.                                 ; Note. this is not satisfactory and the typo
  6910.                                 ; LIST 20000 will list an entirely different
  6911.                                 ; section than LIST 2000. Such typos are not
  6912.                                 ; available for checking if they are direct
  6913.                                 ; commands.
  6914.  
  6915.         LD      H,A             ; transfer the modified
  6916.         LD      L,C             ; line number to HL.
  6917.         LD      ($5C49),HL      ; update E_PPC to new line number.
  6918.         CALL    L196E           ; routine LINE-ADDR gets the address of the
  6919.                                 ; line.
  6920.  
  6921. ; This routine is called from AUTO-LIST
  6922.  
  6923. ;; LIST-ALL
  6924. L1833:  LD      E,$01           ; signal current line not yet printed
  6925.  
  6926. ;; LIST-ALL-2
  6927. L1835:  CALL    L1855           ; routine OUT-LINE outputs a BASIC line
  6928.                                 ; using PRINT-OUT and makes an early return
  6929.                                 ; when no more lines to print. >>>
  6930.  
  6931.         RST     10H             ; PRINT-A prints the carriage return (in A)
  6932.  
  6933.         BIT     4,(IY+$02)      ; test TV_FLAG  - automatic listing ?
  6934.         JR      Z,L1835         ; back to LIST-ALL-2 if not
  6935.                                 ; (loop exit is via OUT-LINE)
  6936.  
  6937. ; continue here if an automatic listing required.
  6938.  
  6939.         LD      A,($5C6B)       ; fetch DF_SZ lower display file size.
  6940.         SUB     (IY+$4F)        ; subtract S_POSN_hi ithe current line number.
  6941.         JR      NZ,L1835        ; back to LIST-ALL-2 if upper screen not full.
  6942.  
  6943.         XOR     E               ; A contains zero, E contains one if the
  6944.                                 ; current edit line has not been printed
  6945.                                 ; or zero if it has (from OUT-LINE).
  6946.         RET     Z               ; return if the screen is full and the line
  6947.                                 ; has been printed.
  6948.  
  6949. ; continue with automatic listings if the screen is full and the current
  6950. ; edit line is missing. OUT-LINE will scroll automatically.
  6951.  
  6952.         PUSH    HL              ; save the pointer address.
  6953.         PUSH    DE              ; save the E flag.
  6954.         LD      HL,$5C6C        ; fetch S_TOP the rough estimate.
  6955.         CALL    L190F           ; routine LN-FETCH updates S_TOP with
  6956.                                 ; the number of the next line.
  6957.         POP     DE              ; restore the E flag.
  6958.         POP     HL              ; restore the address of the next line.
  6959.         JR      L1835           ; back to LIST-ALL-2.
  6960.  
  6961. ; ------------------------
  6962. ; Print a whole BASIC line
  6963. ; ------------------------
  6964. ; This routine prints a whole BASIC line and it is called
  6965. ; from LIST-ALL to output the line to current channel
  6966. ; and from ED-EDIT to 'sprint' the line to the edit buffer.
  6967.  
  6968. ;; OUT-LINE
  6969. L1855:  LD      BC,($5C49)      ; fetch E_PPC the current line which may be
  6970.                                 ; unchecked and not exist.
  6971.         CALL    L1980           ; routine CP-LINES finds match or line after.
  6972.         LD      D,$3E           ; prepare cursor '>' in D.
  6973.         JR      Z,L1865         ; to OUT-LINE1 if matched or line after.
  6974.  
  6975.         LD      DE,$0000        ; put zero in D, to suppress line cursor.
  6976.         RL      E               ; pick up carry in E if line before current
  6977.                                 ; leave E zero if same or after.
  6978.  
  6979. ;; OUT-LINE1
  6980. L1865:  LD      (IY+$2D),E      ; save flag in BREG which is spare.
  6981.         LD      A,(HL)          ; get high byte of line number.
  6982.         CP      $40             ; is it too high ($2F is maximum possible) ?
  6983.         POP     BC              ; drop the return address and
  6984.         RET     NC              ; make an early return if so >>>
  6985.  
  6986.         PUSH    BC              ; save return address
  6987.         CALL    L1A28           ; routine OUT-NUM-2 to print addressed number
  6988.                                 ; with leading space.
  6989.         INC     HL              ; skip low number byte.
  6990.         INC     HL              ; and the two
  6991.         INC     HL              ; length bytes.
  6992.         RES     0,(IY+$01)      ; update FLAGS - signal leading space required.
  6993.         LD      A,D             ; fetch the cursor.
  6994.         AND     A               ; test for zero.
  6995.         JR      Z,L1881         ; to OUT-LINE3 if zero.
  6996.  
  6997.  
  6998.         RST     10H             ; PRINT-A prints '>' the current line cursor.
  6999.  
  7000. ; this entry point is called from ED-COPY
  7001.  
  7002. ;; OUT-LINE2
  7003. L187D:  SET     0,(IY+$01)      ; update FLAGS - suppress leading space.
  7004.  
  7005. ;; OUT-LINE3
  7006. L1881:  PUSH    DE              ; save flag E for a return value.
  7007.         EX      DE,HL           ; save HL address in DE.
  7008.         RES     2,(IY+$30)      ; update FLAGS2 - signal NOT in QUOTES.
  7009.  
  7010.         LD      HL,$5C3B        ; point to FLAGS.
  7011.         RES     2,(HL)          ; signal 'K' mode. (starts before keyword)
  7012.         BIT     5,(IY+$37)      ; test FLAGX - input mode ?
  7013.         JR      Z,L1894         ; forward to OUT-LINE4 if not.
  7014.  
  7015.         SET     2,(HL)          ; signal 'L' mode. (used for input)
  7016.  
  7017. ;; OUT-LINE4
  7018. L1894:  LD      HL,($5C5F)      ; fetch X_PTR - possibly the error pointer
  7019.                                 ; address.
  7020.         AND     A               ; clear the carry flag.
  7021.         SBC     HL,DE           ; test if an error address has been reached.
  7022.         JR      NZ,L18A1        ; forward to OUT-LINE5 if not.
  7023.  
  7024.         LD      A,$3F           ; load A with '?' the error marker.
  7025.         CALL    L18C1           ; routine OUT-FLASH to print flashing marker.
  7026.  
  7027. ;; OUT-LINE5
  7028. L18A1:  CALL    L18E1           ; routine OUT-CURS will print the cursor if
  7029.                                 ; this is the right position.
  7030.         EX      DE,HL           ; restore address pointer to HL.
  7031.         LD      A,(HL)          ; fetch the addressed character.
  7032.         CALL    L18B6           ; routine NUMBER skips a hidden floating
  7033.                                 ; point number if present.
  7034.         INC     HL              ; now increment the pointer.
  7035.         CP      $0D             ; is character end-of-line ?
  7036.         JR      Z,L18B4         ; to OUT-LINE6, if so, as line is finished.
  7037.  
  7038.         EX      DE,HL           ; save the pointer in DE.
  7039.         CALL    L1937           ; routine OUT-CHAR to output character/token.
  7040.  
  7041.         JR      L1894           ; back to OUT-LINE4 until entire line is done.
  7042.  
  7043. ; ---
  7044.  
  7045. ;; OUT-LINE6
  7046. L18B4:  POP     DE              ; bring back the flag E, zero if current
  7047.                                 ; line printed else 1 if still to print.
  7048.         RET                     ; return with A holding $0D
  7049.  
  7050. ; -------------------------
  7051. ; Check for a number marker
  7052. ; -------------------------
  7053. ; this subroutine is called from two processes. while outputting BASIC lines
  7054. ; and while searching statements within a BASIC line.
  7055. ; during both, this routine will pass over an invisible number indicator
  7056. ; and the five bytes floating-point number that follows it.
  7057. ; Note that this causes floating point numbers to be stripped from
  7058. ; the BASIC line when it is fetched to the edit buffer by OUT_LINE.
  7059. ; the number marker also appears after the arguments of a DEF FN statement
  7060. ; and may mask old 5-byte string parameters.
  7061.  
  7062. ;; NUMBER
  7063. L18B6:  CP      $0E             ; character fourteen ?
  7064.         RET     NZ              ; return if not.
  7065.  
  7066.         INC     HL              ; skip the character
  7067.         INC     HL              ; and five bytes
  7068.         INC     HL              ; following.
  7069.         INC     HL              ;
  7070.         INC     HL              ;
  7071.         INC     HL              ;
  7072.         LD      A,(HL)          ; fetch the following character
  7073.         RET                     ; for return value.
  7074.  
  7075. ; --------------------------
  7076. ; Print a flashing character
  7077. ; --------------------------
  7078. ; This subroutine is called from OUT-LINE to print a flashing error
  7079. ; marker '?' or from the next routine to print a flashing cursor e.g. 'L'.
  7080. ; However, this only gets called from OUT-LINE when printing the edit line
  7081. ; or the input buffer to the lower screen so a direct call to $09F4 can
  7082. ; be used, even though out-line outputs to other streams.
  7083. ; In fact the alternate set is used for the whole routine.
  7084.  
  7085. ;; OUT-FLASH
  7086. L18C1:  EXX                     ; switch in alternate set
  7087.  
  7088.         LD      HL,($5C8F)      ; fetch L = ATTR_T, H = MASK-T
  7089.         PUSH    HL              ; save masks.
  7090.         RES     7,H             ; reset flash mask bit so active.
  7091.         SET     7,L             ; make attribute FLASH.
  7092.         LD      ($5C8F),HL      ; resave ATTR_T and MASK-T
  7093.  
  7094.         LD      HL,$5C91        ; address P_FLAG
  7095.         LD      D,(HL)          ; fetch to D
  7096.         PUSH    DE              ; and save.
  7097.         LD      (HL),$00        ; clear inverse, over, ink/paper 9
  7098.  
  7099.         CALL    L09F4           ; routine PRINT-OUT outputs character
  7100.                                 ; without the need to vector via RST 10.
  7101.  
  7102.         POP     HL              ; pop P_FLAG to H.
  7103.         LD      (IY+$57),H      ; and restore system variable P_FLAG.
  7104.         POP     HL              ; restore temporary masks
  7105.         LD      ($5C8F),HL      ; and restore system variables ATTR_T/MASK_T
  7106.  
  7107.         EXX                     ; switch back to main set
  7108.         RET                     ; return
  7109.  
  7110. ; ----------------
  7111. ; Print the cursor
  7112. ; ----------------
  7113. ; This routine is called before any character is output while outputting
  7114. ; a BASIC line or the input buffer. This includes listing to a printer
  7115. ; or screen, copying a BASIC line to the edit buffer and printing the
  7116. ; input buffer or edit buffer to the lower screen. It is only in the
  7117. ; latter two cases that it has any relevance and in the last case it
  7118. ; performs another very important function also.
  7119.  
  7120. ;; OUT-CURS
  7121. L18E1:  LD      HL,($5C5B)      ; fetch K_CUR the current cursor address
  7122.         AND     A               ; prepare for true subtraction.
  7123.         SBC     HL,DE           ; test against pointer address in DE and
  7124.         RET     NZ              ; return if not at exact position.
  7125.  
  7126. ; the value of MODE, maintained by KEY-INPUT, is tested and if non-zero
  7127. ; then this value 'E' or 'G' will take precedence.
  7128.  
  7129.         LD      A,($5C41)       ; fetch MODE  0='KLC', 1='E', 2='G'.
  7130.                 DB 0XCB
  7131.                 RLCA               ; double the value and set flags.
  7132.         JR      Z,L18F3         ; to OUT-C-1 if still zero ('KLC').
  7133.  
  7134.         ADD     A,$43           ; add 'C' - will become 'E' if originally 1
  7135.                                 ; or 'G' if originally 2.
  7136.         JR      L1909           ; forward to OUT-C-2 to print.
  7137.  
  7138. ; ---
  7139.  
  7140. ; If mode was zero then, while printing a BASIC line, bit 2 of flags has been
  7141. ; set if 'THEN' or ':' was encountered as a main character and reset otherwise.
  7142. ; This is now used to determine if the 'K' cursor is to be printed but this
  7143. ; transient state is also now transferred permanently to bit 3 of FLAGS
  7144. ; to let the interrupt routine know how to decode the next key.
  7145.  
  7146. ;; OUT-C-1
  7147. L18F3:  LD      HL,$5C3B        ; Address FLAGS
  7148.         RES     3,(HL)          ; signal 'K' mode initially.
  7149.         LD      A,$4B           ; prepare letter 'K'.
  7150.         BIT     2,(HL)          ; test FLAGS - was the
  7151.                                 ; previous main character ':' or 'THEN' ?
  7152.         JR      Z,L1909         ; forward to OUT-C-2 if so to print.
  7153.  
  7154.         SET     3,(HL)          ; signal 'L' mode to interrupt routine.
  7155.                                 ; Note. transient bit has been made permanent.
  7156.         INC     A               ; augment from 'K' to 'L'.
  7157.  
  7158.         BIT     3,(IY+$30)      ; test FLAGS2 - consider caps lock ?
  7159.                                 ; which is maintained by KEY-INPUT.
  7160.         JR      Z,L1909         ; forward to OUT-C-2 if not set to print.
  7161.  
  7162.         LD      A,$43           ; alter 'L' to 'C'.
  7163.  
  7164. ;; OUT-C-2
  7165. L1909:  PUSH    DE              ; save address pointer but OK as OUT-FLASH
  7166.                                 ; uses alternate set without RST 10.
  7167.  
  7168.         CALL    L18C1           ; routine OUT-FLASH to print.
  7169.  
  7170.         POP     DE              ; restore and
  7171.         RET                     ; return.
  7172.  
  7173. ; ----------------------------
  7174. ; Get line number of next line
  7175. ; ----------------------------
  7176. ; These two subroutines are called while editing.
  7177. ; This entry point is from ED-DOWN with HL addressing E_PPC
  7178. ; to fetch the next line number.
  7179. ; Also from AUTO-LIST with HL addressing S_TOP just to update S_TOP
  7180. ; with the value of the next line number. It gets fetched but is discarded.
  7181. ; These routines never get called while the editor is being used for input.
  7182.  
  7183. ;; LN-FETCH
  7184. L190F:  LD      E,(HL)          ; fetch low byte
  7185.         INC     HL              ; address next
  7186.         LD      D,(HL)          ; fetch high byte.
  7187.         PUSH    HL              ; save system variable hi pointer.
  7188.         EX      DE,HL           ; line number to HL,
  7189.         INC     HL              ; increment as a starting point.
  7190.         CALL    L196E           ; routine LINE-ADDR gets address in HL.
  7191.         CALL    L1695           ; routine LINE-NO gets line number in DE.
  7192.         POP     HL              ; restore system variable hi pointer.
  7193.  
  7194. ; This entry point is from the ED-UP with HL addressing E_PPC_hi
  7195.  
  7196. ;; LN-STORE
  7197. L191C:  BIT     5,(IY+$37)      ; test FLAGX - input mode ?
  7198.         RET     NZ              ; return if so.
  7199.                                 ; Note. above already checked by ED-UP/ED-DOWN.
  7200.  
  7201.         LD      (HL),D          ; save high byte of line number.
  7202.         DEC     HL              ; address lower
  7203.         LD      (HL),E          ; save low byte of line number.
  7204.         RET                     ; return.
  7205.  
  7206. ; -----------------------------------------
  7207. ; Outputting numbers at start of BASIC line
  7208. ; -----------------------------------------
  7209. ; This routine entered at OUT-SP-NO is used to compute then output the first
  7210. ; three digits of a 4-digit BASIC line printing a space if necessary.
  7211. ; The line number, or residual part, is held in HL and the BC register
  7212. ; holds a subtraction value -1000, -100 or -10.
  7213. ; Note. for example line number 200 -
  7214. ; space(out_char), 2(out_code), 0(out_char) final number always out-code.
  7215.  
  7216. ;; OUT-SP-2
  7217. L1925:  LD      A,E             ; will be space if OUT-CODE not yet called.
  7218.                                 ; or $FF if spaces are suppressed.
  7219.                                 ; else $30 ('0').
  7220.                                 ; (from the first instruction at OUT-CODE)
  7221.                                 ; this guy is just too clever.
  7222.         AND     A               ; test bit 7 of A.
  7223.         RET     M               ; return if $FF, as leading spaces not
  7224.                                 ; required. This is set when printing line
  7225.                                 ; number and statement in MAIN-5.
  7226.  
  7227.         JR      L1937           ; forward to exit via OUT-CHAR.
  7228.  
  7229. ; ---
  7230.  
  7231. ; -> the single entry point.
  7232.  
  7233. ;; OUT-SP-NO
  7234. L192A:  XOR     A               ; initialize digit to 0
  7235.  
  7236. ;; OUT-SP-1
  7237. L192B:  ADD     HL,BC           ; add negative number to HL.
  7238.         INC     A               ; increment digit
  7239.         JR      C,L192B         ; back to OUT-SP-1 until no carry from
  7240.                                 ; the addition.
  7241.  
  7242.         SBC     HL,BC           ; cancel the last addition
  7243.         DEC     A               ; and decrement the digit.
  7244.         JR      Z,L1925         ; back to OUT-SP-2 if it is zero.
  7245.  
  7246.         JP      L15EF           ; jump back to exit via OUT-CODE.    ->
  7247.  
  7248.  
  7249. ; -------------------------------------
  7250. ; Outputting characters in a BASIC line
  7251. ; -------------------------------------
  7252. ; This subroutine ...
  7253.  
  7254. ;; OUT-CHAR
  7255. L1937:  CALL    L2D1B           ; routine NUMERIC tests if it is a digit ?
  7256.         JR      NC,L196C        ; to OUT-CH-3 to print digit without
  7257.                                 ; changing mode. Will be 'K' mode if digits
  7258.                                 ; are at beginning of edit line.
  7259.  
  7260.         CP      $21             ; less than quote character ?
  7261.         JR      C,L196C         ; to OUT-CH-3 to output controls and space.
  7262.  
  7263.         RES     2,(IY+$01)      ; initialize FLAGS to 'K' mode and leave
  7264.                                 ; unchanged if this character would precede
  7265.                                 ; a keyword.
  7266.  
  7267.         CP      $CB             ; is character 'THEN' token ?
  7268.         JR      Z,L196C         ; to OUT-CH-3 to output if so.
  7269.  
  7270.         CP      $3A             ; is it ':' ?
  7271.         JR      NZ,L195A        ; to OUT-CH-1 if not statement separator
  7272.                                 ; to change mode back to 'L'.
  7273.  
  7274.         BIT     5,(IY+$37)      ; FLAGX  - Input Mode ??
  7275.         JR      NZ,L1968        ; to OUT-CH-2 if in input as no statements.
  7276.                                 ; Note. this check should seemingly be at
  7277.                                 ; the start. Commands seem inappropriate in
  7278.                                 ; INPUT mode and are rejected by the syntax
  7279.                                 ; checker anyway.
  7280.                                 ; unless INPUT LINE is being used.
  7281.  
  7282.         BIT     2,(IY+$30)      ; test FLAGS2 - is the ':' within quotes ?
  7283.         JR      Z,L196C         ; to OUT-CH-3 if ':' is outside quoted text.
  7284.  
  7285.         JR      L1968           ; to OUT-CH-2 as ':' is within quotes
  7286.  
  7287. ; ---
  7288.  
  7289. ;; OUT-CH-1
  7290. L195A:  CP      $22             ; is it quote character '"'  ?
  7291.         JR      NZ,L1968        ; to OUT-CH-2 with others to set 'L' mode.
  7292.  
  7293.         PUSH    AF              ; save character.
  7294.         LD      A,($5C6A)       ; fetch FLAGS2.
  7295.         XOR     $04             ; toggle the quotes flag.
  7296.         LD      ($5C6A),A       ; update FLAGS2
  7297.         POP     AF              ; and restore character.
  7298.  
  7299. ;; OUT-CH-2
  7300. L1968:  SET     2,(IY+$01)      ; update FLAGS - signal L mode if the cursor
  7301.                                 ; is next.
  7302.  
  7303. ;; OUT-CH-3
  7304. L196C:  RST     10H             ; PRINT-A vectors the character to
  7305.                                 ; channel 'S', 'K', 'R' or 'P'.
  7306.         RET                     ; return.
  7307.  
  7308. ; -------------------------------------------
  7309. ; Get starting address of line, or line after
  7310. ; -------------------------------------------
  7311. ; This routine is used often to get the address, in HL, of a BASIC line
  7312. ; number supplied in HL, or failing that the address of the following line
  7313. ; and the address of the previous line in DE.
  7314.  
  7315. ;; LINE-ADDR
  7316. L196E:  PUSH    HL              ; save line number in HL register
  7317.         LD      HL,($5C53)      ; fetch start of program from PROG
  7318.         LD      D,H             ; transfer address to
  7319.         LD      E,L             ; the DE register pair.
  7320.  
  7321. ;; LINE-AD-1
  7322. L1974:  POP     BC              ; restore the line number to BC
  7323.         CALL    L1980           ; routine CP-LINES compares with that
  7324.                                 ; addressed by HL
  7325.         RET     NC              ; return if line has been passed or matched.
  7326.                                 ; if NZ, address of previous is in DE
  7327.  
  7328.         PUSH    BC              ; save the current line number
  7329.         CALL    L19B8           ; routine NEXT-ONE finds address of next
  7330.                                 ; line number in DE, previous in HL.
  7331.         EX      DE,HL           ; switch so next in HL
  7332.         JR      L1974           ; back to LINE-AD-1 for another comparison
  7333.  
  7334. ; --------------------
  7335. ; Compare line numbers
  7336. ; --------------------
  7337. ; This routine compares a line number supplied in BC with an addressed
  7338. ; line number pointed to by HL.
  7339.  
  7340. ;; CP-LINES
  7341. L1980:  LD      A,(HL)          ; Load the high byte of line number and
  7342.         CP      B               ; compare with that of supplied line number.
  7343.         RET     NZ              ; return if yet to match (carry will be set).
  7344.  
  7345.         INC     HL              ; address low byte of
  7346.         LD      A,(HL)          ; number and pick up in A.
  7347.         DEC     HL              ; step back to first position.
  7348.         CP      C               ; now compare.
  7349.         RET                     ; zero set if exact match.
  7350.                                 ; carry set if yet to match.
  7351.                                 ; no carry indicates a match or
  7352.                                 ; next available BASIC line or
  7353.                                 ; program end marker.
  7354.  
  7355. ; -------------------
  7356. ; Find each statement
  7357. ; -------------------
  7358. ; The single entry point EACH-STMT is used to
  7359. ; 1) To find the D'th statement in a line.
  7360. ; 2) To find a token in held E.
  7361.  
  7362. ;; not-used
  7363. L1988:  INC     HL              ;
  7364.         INC     HL              ;
  7365.         INC     HL              ;
  7366.  
  7367. ; -> entry point.
  7368.  
  7369. ;; EACH-STMT
  7370. L198B:  LD      ($5C5D),HL      ; save HL in CH_ADD
  7371.         LD      C,$00           ; initialize quotes flag
  7372.  
  7373. ;; EACH-S-1
  7374. L1990:  DEC     D               ; decrease statement count
  7375.         RET     Z               ; return if zero
  7376.  
  7377.  
  7378.         RST     20H             ; NEXT-CHAR
  7379.         CP      E               ; is it the search token ?
  7380.         JR      NZ,L199A        ; forward to EACH-S-3 if not
  7381.  
  7382.         AND     A               ; clear carry
  7383.         RET                     ; return signalling success.
  7384.  
  7385. ; ---
  7386.  
  7387. ;; EACH-S-2
  7388. L1998:  INC     HL              ; next address
  7389.         LD      A,(HL)          ; next character
  7390.  
  7391. ;; EACH-S-3
  7392. L199A:  CALL    L18B6           ; routine NUMBER skips if number marker
  7393.         LD      ($5C5D),HL      ; save in CH_ADD
  7394.         CP      $22             ; is it quotes '"' ?
  7395.         JR      NZ,L19A5        ; to EACH-S-4 if not
  7396.  
  7397.         DEC     C               ; toggle bit 0 of C
  7398.  
  7399. ;; EACH-S-4
  7400. L19A5:  CP      $3A             ; is it ':'
  7401.         JR      Z,L19AD         ; to EACH-S-5
  7402.  
  7403.         CP      $CB             ; 'THEN'
  7404.         JR      NZ,L19B1        ; to EACH-S-6
  7405.  
  7406. ;; EACH-S-5
  7407. L19AD:  BIT     0,C             ; is it in quotes
  7408.         JR      Z,L1990         ; to EACH-S-1 if not
  7409.  
  7410. ;; EACH-S-6
  7411. L19B1:  CP      $0D             ; end of line ?
  7412.         JR      NZ,L1998        ; to EACH-S-2
  7413.  
  7414.         DEC     D               ; decrease the statement counter
  7415.                                 ; which should be zero else
  7416.                                 ; 'Statement Lost'.
  7417.         SCF                     ; set carry flag - not found
  7418.         RET                     ; return
  7419.  
  7420. ; -----------------------------------------------------------------------
  7421. ; Storage of variables. For full details - see chapter 24.
  7422. ; ZX Spectrum BASIC Programming by Steven Vickers 1982.
  7423. ; It is bits 7-5 of the first character of a variable that allow
  7424. ; the six types to be distinguished. Bits 4-0 are the reduced letter.
  7425. ; So any variable name is higher that $3F and can be distinguished
  7426. ; also from the variables area end-marker $80.
  7427. ;
  7428. ; 76543210 meaning                               brief outline of format.
  7429. ; -------- ------------------------              -----------------------
  7430. ; 010      string variable.                      2 byte length + contents.
  7431. ; 110      string array.                         2 byte length + contents.
  7432. ; 100      array of numbers.                     2 byte length + contents.
  7433. ; 011      simple numeric variable.              5 bytes.
  7434. ; 101      variable length named numeric.        5 bytes.
  7435. ; 111      for-next loop variable.               18 bytes.
  7436. ; 10000000 the variables area end-marker.
  7437. ;
  7438. ; Note. any of the above seven will serve as a program end-marker.
  7439. ;
  7440. ; -----------------------------------------------------------------------
  7441.  
  7442. ; ------------
  7443. ; Get next one
  7444. ; ------------
  7445. ; This versatile routine is used to find the address of the next line
  7446. ; in the program area or the next variable in the variables area.
  7447. ; The reason one routine is made to handle two apparently unrelated tasks
  7448. ; is that it can be called indiscriminately when merging a line or a
  7449. ; variable.
  7450.  
  7451. ;; NEXT-ONE
  7452. L19B8:  PUSH    HL              ; save the pointer address.
  7453.         LD      A,(HL)          ; get first byte.
  7454.         CP      $40             ; compare with upper limit for line numbers.
  7455.         JR      C,L19D5         ; forward to NEXT-O-3 if within BASIC area.
  7456.  
  7457. ; the continuation here is for the next variable unless the supplied
  7458. ; line number was erroneously over 16383. see RESTORE command.
  7459.  
  7460.         BIT     5,A             ; is it a string or an array variable ?
  7461.         JR      Z,L19D6         ; forward to NEXT-O-4 to compute length.
  7462.  
  7463.         ADD     A,A             ; test bit 6 for single-character variables.
  7464.         JP      M,L19C7         ; forward to NEXT-O-1 if so
  7465.  
  7466.         CCF                     ; clear the carry for long-named variables.
  7467.                                 ; it remains set for for-next loop variables.
  7468.  
  7469. ;; NEXT-O-1
  7470. L19C7:  LD      BC,$0005        ; set BC to 5 for floating point number
  7471.         JR      NC,L19CE        ; forward to NEXT-O-2 if not a for/next
  7472.                                 ; variable.
  7473.  
  7474.         LD      C,$12           ; set BC to eighteen locations.
  7475.                                 ; value, limit, step, line and statement.
  7476.  
  7477. ; now deal with long-named variables
  7478.  
  7479. ;; NEXT-O-2
  7480. L19CE:  RLA                     ; test if character inverted. carry will also
  7481.                                 ; be set for single character variables
  7482.         INC     HL              ; address next location.
  7483.         LD      A,(HL)          ; and load character.
  7484.         JR      NC,L19CE        ; back to NEXT-O-2 if not inverted bit.
  7485.                                 ; forward immediately with single character
  7486.                                 ; variable names.
  7487.  
  7488.         JR      L19DB           ; forward to NEXT-O-5 to add length of
  7489.                                 ; floating point number(s etc.).
  7490.  
  7491. ; ---
  7492.  
  7493. ; this branch is for line numbers.
  7494.  
  7495. ;; NEXT-O-3
  7496. L19D5:  INC     HL              ; increment pointer to low byte of line no.
  7497.  
  7498. ; strings and arrays rejoin here
  7499.  
  7500. ;; NEXT-O-4
  7501. L19D6:  INC     HL              ; increment to address the length low byte.
  7502.         LD      C,(HL)          ; transfer to C and
  7503.         INC     HL              ; point to high byte of length.
  7504.         LD      B,(HL)          ; transfer that to B
  7505.         INC     HL              ; point to start of BASIC/variable contents.
  7506.  
  7507. ; the three types of numeric variables rejoin here
  7508.  
  7509. ;; NEXT-O-5
  7510. L19DB:  ADD     HL,BC           ; add the length to give address of next
  7511.                                 ; line/variable in HL.
  7512.         POP     DE              ; restore previous address to DE.
  7513.  
  7514. ; ------------------
  7515. ; Difference routine
  7516. ; ------------------
  7517. ; This routine terminates the above routine and is also called from the
  7518. ; start of the next routine to calculate the length to reclaim.
  7519.  
  7520. ;; DIFFER
  7521. L19DD:  AND     A               ; prepare for true subtraction.
  7522.         SBC     HL,DE           ; subtract the two pointers.
  7523.         LD      B,H             ; transfer result
  7524.         LD      C,L             ; to BC register pair.
  7525.         ADD     HL,DE           ; add back
  7526.         EX      DE,HL           ; and switch pointers
  7527.         RET                     ; return values are the length of area in BC,
  7528.                                 ; low pointer (previous) in HL,
  7529.                                 ; high pointer (next) in DE.
  7530.  
  7531. ; -----------------------
  7532. ; Handle reclaiming space
  7533. ; -----------------------
  7534. ;
  7535.  
  7536. ;; RECLAIM-1
  7537. L19E5:  CALL    L19DD           ; routine DIFFER immediately above
  7538.  
  7539. ;; RECLAIM-2
  7540. L19E8:  PUSH    BC              ;
  7541.  
  7542.         LD      A,B             ;
  7543.         CPL                     ;
  7544.         LD      B,A             ;
  7545.         LD      A,C             ;
  7546.         CPL                     ;
  7547.         LD      C,A             ;
  7548.         INC     BC              ;
  7549.  
  7550.         CALL    L1664           ; routine POINTERS
  7551.         EX      DE,HL           ;
  7552.         POP     HL              ;
  7553.  
  7554.         ADD     HL,DE           ;
  7555.         PUSH    DE              ;
  7556.         LDIR                    ; copy bytes
  7557.  
  7558.         POP     HL              ;
  7559.         RET                     ;
  7560.  
  7561. ; ----------------------------------------
  7562. ; Read line number of line in editing area
  7563. ; ----------------------------------------
  7564. ; This routine reads a line number in the editing area returning the number
  7565. ; in the BC register or zero if no digits exist before commands.
  7566. ; It is called from LINE-SCAN to check the syntax of the digits.
  7567. ; It is called from MAIN-3 to extract the line number in preparation for
  7568. ; inclusion of the line in the BASIC program area.
  7569. ;
  7570. ; Interestingly the calculator stack is moved from its normal place at the
  7571. ; end of dynamic memory to an adequate area within the system variables area.
  7572. ; This ensures that in a low memory situation, that valid line numbers can
  7573. ; be extracted without raising an error and that memory can be reclaimed
  7574. ; by deleting lines. If the stack was in its normal place then a situation
  7575. ; arises whereby the Spectrum becomes locked with no means of reclaiming space.
  7576.  
  7577. ;; E-LINE-NO
  7578. L19FB:  LD      HL,($5C59)      ; load HL from system variable E_LINE.
  7579.  
  7580.         DEC     HL              ; decrease so that NEXT_CHAR can be used
  7581.                                 ; without skipping the first digit.
  7582.  
  7583.         LD      ($5C5D),HL      ; store in the system variable CH_ADD.
  7584.  
  7585.         RST     20H             ; NEXT-CHAR skips any noise and white-space
  7586.                                 ; to point exactly at the first digit.
  7587.  
  7588.         LD      HL,$5C92        ; use MEM-0 as a temporary calculator stack
  7589.                                 ; an overhead of three locations are needed.
  7590.         LD      ($5C65),HL      ; set new STKEND.
  7591.  
  7592.         CALL    L2D3B           ; routine INT-TO-FP will read digits till
  7593.                                 ; a non-digit found.
  7594.         CALL    L2DA2           ; routine FP-TO-BC will retrieve number
  7595.                                 ; from stack at membot.
  7596.         JR      C,L1A15         ; forward to E-L-1 if overflow i.e. > 65535.
  7597.                                 ; 'Nonsense in BASIC'
  7598.  
  7599.         LD      HL,$D8F0        ; load HL with value -9999
  7600.         ADD     HL,BC           ; add to line number in BC
  7601.  
  7602. ;; E-L-1
  7603. L1A15:  JP      C,L1C8A         ; to REPORT-C 'Nonsense in BASIC' if over.
  7604.                                 ; Note. As ERR_SP points to ED_ERROR
  7605.                                 ; the report is never produced although
  7606.                                 ; the RST $08 will update X_PTR leading to
  7607.                                 ; the error marker being displayed when
  7608.                                 ; the ED_LOOP is reiterated.
  7609.                                 ; in fact, since it is immediately
  7610.                                 ; cancelled, any report will do.
  7611.  
  7612. ; a line in the range 0 - 9999 has been entered.
  7613.  
  7614.         JP      L16C5           ; jump back to SET-STK to set the calculator
  7615.                                 ; stack back to its normal place and exit
  7616.                                 ; from there.
  7617.  
  7618. ; ---------------------------------
  7619. ; Report and line number outputting
  7620. ; ---------------------------------
  7621. ; Entry point OUT-NUM-1 is used by the Error Reporting code to print
  7622. ; the line number and later the statement number held in BC.
  7623. ; If the statement was part of a direct command then -2 is used as a
  7624. ; dummy line number so that zero will be printed in the report.
  7625. ; This routine is also used to print the exponent of E-format numbers.
  7626. ;
  7627. ; Entry point OUT-NUM-2 is used from OUT-LINE to output the line number
  7628. ; addressed by HL with leading spaces if necessary.
  7629.  
  7630. ;; OUT-NUM-1
  7631. L1A1B:  PUSH    DE              ; save the
  7632.         PUSH    HL              ; registers.
  7633.         XOR     A               ; set A to zero.
  7634.         BIT     7,B             ; is the line number minus two ?
  7635.         JR      NZ,L1A42        ; forward to OUT-NUM-4 if so to print zero
  7636.                                 ; for a direct command.
  7637.  
  7638.         LD      H,B             ; transfer the
  7639.         LD      L,C             ; number to HL.
  7640.         LD      E,$FF           ; signal 'no leading zeros'.
  7641.         JR      L1A30           ; forward to continue at OUT-NUM-3
  7642.  
  7643. ; ---
  7644.  
  7645. ; from OUT-LINE - HL addresses line number.
  7646.  
  7647. ;; OUT-NUM-2
  7648. L1A28:  PUSH    DE              ; save flags
  7649.         LD      D,(HL)          ; high byte to D
  7650.         INC     HL              ; address next
  7651.         LD      E,(HL)          ; low byte to E
  7652.         PUSH    HL              ; save pointer
  7653.         EX      DE,HL           ; transfer number to HL
  7654.         LD      E,$20           ; signal 'output leading spaces'
  7655.  
  7656. ;; OUT-NUM-3
  7657. L1A30:  LD      BC,$FC18        ; value -1000
  7658.         CALL    L192A           ; routine OUT-SP-NO outputs space or number
  7659.         LD      BC,$FF9C        ; value -100
  7660.         CALL    L192A           ; routine OUT-SP-NO
  7661.         LD      C,$F6           ; value -10 ( B is still $FF )
  7662.         CALL    L192A           ; routine OUT-SP-NO
  7663.         LD      A,L             ; remainder to A.
  7664.  
  7665. ;; OUT-NUM-4
  7666. L1A42:  CALL    L15EF           ; routine OUT-CODE for final digit.
  7667.                                 ; else report code zero wouldn't get
  7668.                                 ; printed.
  7669.         POP     HL              ; restore the
  7670.         POP     DE              ; registers and
  7671.         RET                     ; return.
  7672.  
  7673.  
  7674. ;***************************************************
  7675. ;** Part 7. BASIC LINE AND COMMAND INTERPRETATION **
  7676. ;***************************************************
  7677.  
  7678. ; ----------------
  7679. ; The offset table
  7680. ; ----------------
  7681. ; The BASIC interpreter has found a command code $CE - $FF
  7682. ; which is then reduced to range $00 - $31 and added to the base address
  7683. ; of this table to give the address of an offset which, when added to
  7684. ; the offset therein, gives the location in the following parameter table
  7685. ; where a list of class codes, separators and addresses relevant to the
  7686. ; command exists.
  7687.  
  7688. ;; offst-tbl
  7689. L1A48:  DB    L1AF9 - $       ; B1 offset to Address: P-DEF-FN
  7690.         DB    L1B14 - $       ; CB offset to Address: P-CAT
  7691.         DB    L1B06 - $       ; BC offset to Address: P-FORMAT
  7692.         DB    L1B0A - $       ; BF offset to Address: P-MOVE
  7693.         DB    L1B10 - $       ; C4 offset to Address: P-ERASE
  7694.         DB    L1AFC - $       ; AF offset to Address: P-OPEN
  7695.         DB    L1B02 - $       ; B4 offset to Address: P-CLOSE
  7696.         DB    L1AE2 - $       ; 93 offset to Address: P-MERGE
  7697.         DB    L1AE1 - $       ; 91 offset to Address: P-VERIFY
  7698.         DB    L1AE3 - $       ; 92 offset to Address: P-BEEP
  7699.         DB    L1AE7 - $       ; 95 offset to Address: P-CIRCLE
  7700.         DB    L1AEB - $       ; 98 offset to Address: P-INK
  7701.         DB    L1AEC - $       ; 98 offset to Address: P-PAPER
  7702.         DB    L1AED - $       ; 98 offset to Address: P-FLASH
  7703.         DB    L1AEE - $       ; 98 offset to Address: P-BRIGHT
  7704.         DB    L1AEF - $       ; 98 offset to Address: P-INVERSE
  7705.         DB    L1AF0 - $       ; 98 offset to Address: P-OVER
  7706.         DB    L1AF1 - $       ; 98 offset to Address: P-OUT
  7707.         DB    L1AD9 - $       ; 7F offset to Address: P-LPRINT
  7708.         DB    L1ADC - $       ; 81 offset to Address: P-LLIST
  7709.         DB    L1A8A - $       ; 2E offset to Address: P-STOP
  7710.         DB    L1AC9 - $       ; 6C offset to Address: P-READ
  7711.         DB    L1ACC - $       ; 6E offset to Address: P-DATA
  7712.         DB    L1ACF - $       ; 70 offset to Address: P-RESTORE
  7713.         DB    L1AA8 - $       ; 48 offset to Address: P-NEW
  7714.         DB    L1AF5 - $       ; 94 offset to Address: P-BORDER
  7715.         DB    L1AB8 - $       ; 56 offset to Address: P-CONT
  7716.         DB    L1AA2 - $       ; 3F offset to Address: P-DIM
  7717.         DB    L1AA5 - $       ; 41 offset to Address: P-REM
  7718.         DB    L1A90 - $       ; 2B offset to Address: P-FOR
  7719.         DB    L1A7D - $       ; 17 offset to Address: P-GO-TO
  7720.         DB    L1A86 - $       ; 1F offset to Address: P-GO-SUB
  7721.         DB    L1A9F - $       ; 37 offset to Address: P-INPUT
  7722.         DB    L1AE0 - $       ; 77 offset to Address: P-LOAD
  7723.         DB    L1AAE - $       ; 44 offset to Address: P-LIST
  7724.         DB    L1A7A - $       ; 0F offset to Address: P-LET
  7725.         DB    L1AC5 - $       ; 59 offset to Address: P-PAUSE
  7726.         DB    L1A98 - $       ; 2B offset to Address: P-NEXT
  7727.         DB    L1AB1 - $       ; 43 offset to Address: P-POKE
  7728.         DB    L1A9C - $       ; 2D offset to Address: P-PRINT
  7729.         DB    L1AC1 - $       ; 51 offset to Address: P-PLOT
  7730.         DB    L1AAB - $       ; 3A offset to Address: P-RUN
  7731.         DB    L1ADF - $       ; 6D offset to Address: P-SAVE
  7732.         DB    L1AB5 - $       ; 42 offset to Address: P-RANDOM
  7733.         DB    L1A81 - $       ; 0D offset to Address: P-IF
  7734.         DB    L1ABE - $       ; 49 offset to Address: P-CLS
  7735.         DB    L1AD2 - $       ; 5C offset to Address: P-DRAW
  7736.         DB    L1ABB - $       ; 44 offset to Address: P-CLEAR
  7737.         DB    L1A8D - $       ; 15 offset to Address: P-RETURN
  7738.         DB    L1AD6 - $       ; 5D offset to Address: P-COPY
  7739.  
  7740.  
  7741. ; -------------------------------
  7742. ; The parameter or "Syntax" table
  7743. ; -------------------------------
  7744. ; For each command there exists a variable list of parameters.
  7745. ; If the character is greater than a space it is a required separator.
  7746. ; If less, then it is a command class in the range 00 - 0B.
  7747. ; Note that classes 00, 03 and 05 will fetch the addresses from this table.
  7748. ; Some classes e.g. 07 and 0B have the same address in all invocations
  7749. ; and the command is re-computed from the low-byte of the parameter address.
  7750. ; Some e.g. 02 are only called once so a call to the command is made from
  7751. ; within the class routine rather than holding the address within the table.
  7752. ; Some class routines check syntax entirely and some leave this task for the
  7753. ; command itself.
  7754. ; Others for example CIRCLE (x,y,z) check the first part (x,y) using the
  7755. ; class routine and the final part (,z) within the command.
  7756. ; The last few commands appear to have been added in a rush but their syntax
  7757. ; is rather simple e.g. MOVE "M1","M2"
  7758.  
  7759. ;; P-LET
  7760. L1A7A:  DB    $01             ; Class-01 - A variable is required.
  7761.         DB    $3D             ; Separator:  '='
  7762.         DB    $02             ; Class-02 - An expression, numeric or string,
  7763.                                 ; must follow.
  7764.  
  7765. ;; P-GO-TO
  7766. L1A7D:  DB    $06             ; Class-06 - A numeric expression must follow.
  7767.         DB    $00             ; Class-00 - No further operands.
  7768.         DEFW    L1E67           ; Address: $1E67; Address: GO-TO
  7769.  
  7770. ;; P-IF
  7771. L1A81:  DB    $06             ; Class-06 - A numeric expression must follow.
  7772.         DB    $CB             ; Separator:  'THEN'
  7773.         DB    $05             ; Class-05 - Variable syntax checked
  7774.                                 ; by routine.
  7775.         DEFW    L1CF0           ; Address: $1CF0; Address: IF
  7776.  
  7777. ;; P-GO-SUB
  7778. L1A86:  DB    $06             ; Class-06 - A numeric expression must follow.
  7779.         DB    $00             ; Class-00 - No further operands.
  7780.         DEFW    L1EED           ; Address: $1EED; Address: GO-SUB
  7781.  
  7782. ;; P-STOP
  7783. L1A8A:  DB    $00             ; Class-00 - No further operands.
  7784.         DEFW    L1CEE           ; Address: $1CEE; Address: STOP
  7785.  
  7786. ;; P-RETURN
  7787. L1A8D:  DB    $00             ; Class-00 - No further operands.
  7788.         DEFW    L1F23           ; Address: $1F23; Address: RETURN
  7789.  
  7790. ;; P-FOR
  7791. L1A90:  DB    $04             ; Class-04 - A single character variable must
  7792.                                 ; follow.
  7793.         DB    $3D             ; Separator:  '='
  7794.         DB    $06             ; Class-06 - A numeric expression must follow.
  7795.         DB    $CC             ; Separator:  'TO'
  7796.         DB    $06             ; Class-06 - A numeric expression must follow.
  7797.         DB    $05             ; Class-05 - Variable syntax checked
  7798.                                 ; by routine.
  7799.         DEFW    L1D03           ; Address: $1D03; Address: FOR
  7800.  
  7801. ;; P-NEXT
  7802. L1A98:  DB    $04             ; Class-04 - A single character variable must
  7803.                                 ; follow.
  7804.         DB    $00             ; Class-00 - No further operands.
  7805.         DEFW    L1DAB           ; Address: $1DAB; Address: NEXT
  7806.  
  7807. ;; P-PRINT
  7808. L1A9C:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7809.                                 ; by routine.
  7810.         DEFW    L1FCD           ; Address: $1FCD; Address: PRINT
  7811.  
  7812. ;; P-INPUT
  7813. L1A9F:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7814.                                 ; by routine.
  7815.         DEFW    L2089           ; Address: $2089; Address: INPUT
  7816.  
  7817. ;; P-DIM
  7818. L1AA2:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7819.                                 ; by routine.
  7820.         DEFW    L2C02           ; Address: $2C02; Address: DIM
  7821.  
  7822. ;; P-REM
  7823. L1AA5:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7824.                                 ; by routine.
  7825.         DEFW    L1BB2           ; Address: $1BB2; Address: REM
  7826.  
  7827. ;; P-NEW
  7828. L1AA8:  DB    $00             ; Class-00 - No further operands.
  7829.         DEFW    L11B7           ; Address: $11B7; Address: NEW
  7830.  
  7831. ;; P-RUN
  7832. L1AAB:  DB    $03             ; Class-03 - A numeric expression may follow
  7833.                                 ; else default to zero.
  7834.         DEFW    L1EA1           ; Address: $1EA1; Address: RUN
  7835.  
  7836. ;; P-LIST
  7837. L1AAE:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7838.                                 ; by routine.
  7839.         DEFW    L17F9           ; Address: $17F9; Address: LIST
  7840.  
  7841. ;; P-POKE
  7842. L1AB1:  DB    $08             ; Class-08 - Two comma-separated numeric
  7843.                                 ; expressions required.
  7844.         DB    $00             ; Class-00 - No further operands.
  7845.         DEFW    L1E80           ; Address: $1E80; Address: POKE
  7846.  
  7847. ;; P-RANDOM
  7848. L1AB5:  DB    $03             ; Class-03 - A numeric expression may follow
  7849.                                 ; else default to zero.
  7850.         DEFW    L1E4F           ; Address: $1E4F; Address: RANDOMIZE
  7851.  
  7852. ;; P-CONT
  7853. L1AB8:  DB    $00             ; Class-00 - No further operands.
  7854.         DEFW    L1E5F           ; Address: $1E5F; Address: CONTINUE
  7855.  
  7856. ;; P-CLEAR
  7857. L1ABB:  DB    $03             ; Class-03 - A numeric expression may follow
  7858.                                 ; else default to zero.
  7859.         DEFW    L1EAC           ; Address: $1EAC; Address: CLEAR
  7860.  
  7861. ;; P-CLS
  7862. L1ABE:  DB    $00             ; Class-00 - No further operands.
  7863.         DEFW    L0D6B           ; Address: $0D6B; Address: CLS
  7864.  
  7865. ;; P-PLOT
  7866. L1AC1:  DB    $09             ; Class-09 - Two comma-separated numeric
  7867.                                 ; expressions required with optional colour
  7868.                                 ; items.
  7869.         DB    $00             ; Class-00 - No further operands.
  7870.         DEFW    L22DC           ; Address: $22DC; Address: PLOT
  7871.  
  7872. ;; P-PAUSE
  7873. L1AC5:  DB    $06             ; Class-06 - A numeric expression must follow.
  7874.         DB    $00             ; Class-00 - No further operands.
  7875.         DEFW    L1F3A           ; Address: $1F3A; Address: PAUSE
  7876.  
  7877. ;; P-READ
  7878. L1AC9:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7879.                                 ; by routine.
  7880.         DEFW    L1DED           ; Address: $1DED; Address: READ
  7881.  
  7882. ;; P-DATA
  7883. L1ACC:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7884.                                 ; by routine.
  7885.         DEFW    L1E27           ; Address: $1E27; Address: DATA
  7886.  
  7887. ;; P-RESTORE
  7888. L1ACF:  DB    $03             ; Class-03 - A numeric expression may follow
  7889.                                 ; else default to zero.
  7890.         DEFW    L1E42           ; Address: $1E42; Address: RESTORE
  7891.  
  7892. ;; P-DRAW
  7893. L1AD2:  DB    $09             ; Class-09 - Two comma-separated numeric
  7894.                                 ; expressions required with optional colour
  7895.                                 ; items.
  7896.         DB    $05             ; Class-05 - Variable syntax checked
  7897.                                 ; by routine.
  7898.         DEFW    L2382           ; Address: $2382; Address: DRAW
  7899.  
  7900. ;; P-COPY
  7901. L1AD6:  DB    $00             ; Class-00 - No further operands.
  7902.         DEFW    L0EAC           ; Address: $0EAC; Address: COPY
  7903.  
  7904. ;; P-LPRINT
  7905. L1AD9:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7906.                                 ; by routine.
  7907.         DEFW    L1FC9           ; Address: $1FC9; Address: LPRINT
  7908.  
  7909. ;; P-LLIST
  7910. L1ADC:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7911.                                 ; by routine.
  7912.         DEFW    L17F5           ; Address: $17F5; Address: LLIST
  7913.  
  7914. ;; P-SAVE
  7915. L1ADF:  DB    $0B             ; Class-0B - Offset address converted to tape
  7916.                                 ; command.
  7917.  
  7918. ;; P-LOAD
  7919. L1AE0:  DB    $0B             ; Class-0B - Offset address converted to tape
  7920.                                 ; command.
  7921.  
  7922. ;; P-VERIFY
  7923. L1AE1:  DB    $0B             ; Class-0B - Offset address converted to tape
  7924.                                 ; command.
  7925.  
  7926. ;; P-MERGE
  7927. L1AE2:  DB    $0B             ; Class-0B - Offset address converted to tape
  7928.                                 ; command.
  7929.  
  7930. ;; P-BEEP
  7931. L1AE3:  DB    $08             ; Class-08 - Two comma-separated numeric
  7932.                                 ; expressions required.
  7933.         DB    $00             ; Class-00 - No further operands.
  7934.         DEFW    L03F8           ; Address: $03F8; Address: BEEP
  7935.  
  7936. ;; P-CIRCLE
  7937. L1AE7:  DB    $09             ; Class-09 - Two comma-separated numeric
  7938.                                 ; expressions required with optional colour
  7939.                                 ; items.
  7940.         DB    $05             ; Class-05 - Variable syntax checked
  7941.                                 ; by routine.
  7942.         DEFW    L2320           ; Address: $2320; Address: CIRCLE
  7943.  
  7944. ;; P-INK
  7945. L1AEB:  DB    $07             ; Class-07 - Offset address is converted to
  7946.                                 ; colour code.
  7947.  
  7948. ;; P-PAPER
  7949. L1AEC:  DB    $07             ; Class-07 - Offset address is converted to
  7950.                                 ; colour code.
  7951.  
  7952. ;; P-FLASH
  7953. L1AED:  DB    $07             ; Class-07 - Offset address is converted to
  7954.                                 ; colour code.
  7955.  
  7956. ;; P-BRIGHT
  7957. L1AEE:  DB    $07             ; Class-07 - Offset address is converted to
  7958.                                 ; colour code.
  7959.  
  7960. ;; P-INVERSE
  7961. L1AEF:  DB    $07             ; Class-07 - Offset address is converted to
  7962.                                 ; colour code.
  7963.  
  7964. ;; P-OVER
  7965. L1AF0:  DB    $07             ; Class-07 - Offset address is converted to
  7966.                                 ; colour code.
  7967.  
  7968. ;; P-OUT
  7969. L1AF1:  DB    $08             ; Class-08 - Two comma-separated numeric
  7970.                                 ; expressions required.
  7971.         DB    $00             ; Class-00 - No further operands.
  7972.         DEFW    L1E7A           ; Address: $1E7A; Address: OUT
  7973.  
  7974. ;; P-BORDER
  7975. L1AF5:  DB    $06             ; Class-06 - A numeric expression must follow.
  7976.         DB    $00             ; Class-00 - No further operands.
  7977.         DEFW    L2294           ; Address: $2294; Address: BORDER
  7978.  
  7979. ;; P-DEF-FN
  7980. L1AF9:  DB    $05             ; Class-05 - Variable syntax checked entirely
  7981.                                 ; by routine.
  7982.         DEFW    L1F60           ; Address: $1F60; Address: DEF-FN
  7983.  
  7984. ;; P-OPEN
  7985. L1AFC:  DB    $06             ; Class-06 - A numeric expression must follow.
  7986.         DB    $2C             ; Separator:  ','          see Footnote *
  7987.         DB    $0A             ; Class-0A - A string expression must follow.
  7988.         DB    $00             ; Class-00 - No further operands.
  7989.         DEFW    L1736           ; Address: $1736; Address: OPEN
  7990.  
  7991. ;; P-CLOSE
  7992. L1B02:  DB    $06             ; Class-06 - A numeric expression must follow.
  7993.         DB    $00             ; Class-00 - No further operands.
  7994.         DEFW    L16E5           ; Address: $16E5; Address: CLOSE
  7995.  
  7996. ;; P-FORMAT
  7997. L1B06:  DB    $0A             ; Class-0A - A string expression must follow.
  7998.         DB    $00             ; Class-00 - No further operands.
  7999.         DEFW    L1793           ; Address: $1793; Address: CAT-ETC
  8000.  
  8001. ;; P-MOVE
  8002. L1B0A:  DB    $0A             ; Class-0A - A string expression must follow.
  8003.         DB    $2C             ; Separator:  ','
  8004.         DB    $0A             ; Class-0A - A string expression must follow.
  8005.         DB    $00             ; Class-00 - No further operands.
  8006.         DEFW    L1793           ; Address: $1793; Address: CAT-ETC
  8007.  
  8008. ;; P-ERASE
  8009. L1B10:  DB    $0A             ; Class-0A - A string expression must follow.
  8010.         DB    $00             ; Class-00 - No further operands.
  8011.         DEFW    L1793           ; Address: $1793; Address: CAT-ETC
  8012.  
  8013. ;; P-CAT
  8014. L1B14:  DB    $00             ; Class-00 - No further operands.
  8015.         DEFW    L1793           ; Address: $1793; Address: CAT-ETC
  8016.  
  8017. ; * Note that a comma is required as a separator with the OPEN command
  8018. ; but the Interface 1 programmers relaxed this allowing ';' as an
  8019. ; alternative for their channels creating a confusing mixture of
  8020. ; allowable syntax as it is this ROM which opens or re-opens the
  8021. ; normal channels.
  8022.  
  8023. ; -------------------------------
  8024. ; Main parser (BASIC interpreter)
  8025. ; -------------------------------
  8026. ; This routine is called once from MAIN-2 when the BASIC line is to
  8027. ; be entered or re-entered into the Program area and the syntax
  8028. ; requires checking.
  8029.  
  8030. ;; LINE-SCAN
  8031. L1B17:  RES     7,(IY+$01)      ; update FLAGS - signal checking syntax
  8032.         CALL    L19FB           ; routine E-LINE-NO              >>
  8033.                                 ; fetches the line number if in range.
  8034.  
  8035.         XOR     A               ; clear the accumulator.
  8036.         LD      ($5C47),A       ; set statement number SUBPPC to zero.
  8037.         DEC     A               ; set accumulator to $FF.
  8038.         LD      ($5C3A),A       ; set ERR_NR to 'OK' - 1.
  8039.         JR      L1B29           ; forward to continue at STMT-L-1.
  8040.  
  8041. ; --------------
  8042. ; Statement loop
  8043. ; --------------
  8044. ;
  8045. ;
  8046.  
  8047. ;; STMT-LOOP
  8048. L1B28:  RST     20H             ; NEXT-CHAR
  8049.  
  8050. ; -> the entry point from above or LINE-RUN
  8051. ;; STMT-L-1
  8052. L1B29:  CALL    L16BF           ; routine SET-WORK clears workspace etc.
  8053.  
  8054.         INC     (IY+$0D)        ; increment statement number SUBPPC
  8055.         JP      M,L1C8A         ; to REPORT-C to raise
  8056.                                 ; 'Nonsense in BASIC' if over 127.
  8057.  
  8058.         RST     18H             ; GET-CHAR
  8059.  
  8060.         LD      B,$00           ; set B to zero for later indexing.
  8061.                                 ; early so any other reason ???
  8062.  
  8063.         CP      $0D             ; is character carriage return ?
  8064.                                 ; i.e. an empty statement.
  8065.         JR      Z,L1BB3         ; forward to LINE-END if so.
  8066.  
  8067.         CP      $3A             ; is it statement end marker ':' ?
  8068.                                 ; i.e. another type of empty statement.
  8069.         JR      Z,L1B28         ; back to STMT-LOOP if so.
  8070.  
  8071.         LD      HL,L1B76        ; address: STMT-RET
  8072.         PUSH    HL              ; is now pushed as a return address
  8073.         LD      C,A             ; transfer the current character to C.
  8074.  
  8075. ; advance CH_ADD to a position after command and test if it is a command.
  8076.  
  8077.         RST     20H             ; NEXT-CHAR to advance pointer
  8078.         LD      A,C             ; restore current character
  8079.         SUB     $CE             ; subtract 'DEF FN' - first command
  8080.         JP      C,L1C8A         ; jump to REPORT-C if less than a command
  8081.                                 ; raising
  8082.                                 ; 'Nonsense in BASIC'
  8083.  
  8084.         LD      C,A             ; put the valid command code back in C.
  8085.                                 ; register B is zero.
  8086.         LD      HL,L1A48        ; address: offst-tbl
  8087.         ADD     HL,BC           ; index into table with one of 50 commands.
  8088.         LD      C,(HL)          ; pick up displacement to syntax table entry.
  8089.         ADD     HL,BC           ; add to address the relevant entry.
  8090.         JR      L1B55           ; forward to continue at GET-PARAM
  8091.  
  8092. ; ----------------------
  8093. ; The main scanning loop
  8094. ; ----------------------
  8095. ; not documented properly
  8096. ;
  8097.  
  8098. ;; SCAN-LOOP
  8099. L1B52:  LD      HL,($5C74)      ; fetch temporary address from T_ADDR
  8100.                                 ; during subsequent loops.
  8101.  
  8102. ; -> the initial entry point with HL addressing start of syntax table entry.
  8103.  
  8104. ;; GET-PARAM
  8105. L1B55:  LD      A,(HL)          ; pick up the parameter.
  8106.         INC     HL              ; address next one.
  8107.         LD      ($5C74),HL      ; save pointer in system variable T_ADDR
  8108.  
  8109.         LD      BC,L1B52        ; address: SCAN-LOOP
  8110.         PUSH    BC              ; is now pushed on stack as looping address.
  8111.         LD      C,A             ; store parameter in C.
  8112.         CP      $20             ; is it greater than ' '  ?
  8113.         JR      NC,L1B6F        ; forward to SEPARATOR to check that correct
  8114.                                 ; separator appears in statement if so.
  8115.  
  8116.         LD      HL,L1C01        ; address: class-tbl.
  8117.         LD      B,$00           ; prepare to index into the class table.
  8118.         ADD     HL,BC           ; index to find displacement to routine.
  8119.         LD      C,(HL)          ; displacement to BC
  8120.         ADD     HL,BC           ; add to address the CLASS routine.
  8121.         PUSH    HL              ; push the address on the stack.
  8122.  
  8123.         RST     18H             ; GET-CHAR - HL points to place in statement.
  8124.  
  8125.         DEC     B               ; reset the zero flag - the initial state
  8126.                                 ; for all class routines.
  8127.  
  8128.         RET                     ; and make an indirect jump to routine
  8129.                                 ; and then SCAN-LOOP (also on stack).
  8130.  
  8131. ; Note. one of the class routines will eventually drop the return address
  8132. ; off the stack breaking out of the above seemingly endless loop.
  8133.  
  8134. ; ----------------
  8135. ; Verify separator
  8136. ; ----------------
  8137. ; This routine is called once to verify that the mandatory separator
  8138. ; present in the parameter table is also present in the correct
  8139. ; location following the command. For example, the 'THEN' token after
  8140. ; the 'IF' token and expression.
  8141.  
  8142. ;; SEPARATOR
  8143. L1B6F:  RST     18H             ; GET-CHAR
  8144.         CP      C               ; does it match the character in C ?
  8145.         JP      NZ,L1C8A        ; jump forward to REPORT-C if not
  8146.                                 ; 'Nonsense in BASIC'.
  8147.  
  8148.         RST     20H             ; NEXT-CHAR advance to next character
  8149.         RET                     ; return.
  8150.  
  8151. ; ------------------------------
  8152. ; Come here after interpretation
  8153. ; ------------------------------
  8154. ;
  8155. ;
  8156.  
  8157. ;; STMT-RET
  8158. L1B76:  CALL    L1F54           ; routine BREAK-KEY is tested after every
  8159.                                 ; statement.
  8160.         JR      C,L1B7D         ; step forward to STMT-R-1 if not pressed.
  8161.  
  8162. ;; REPORT-L
  8163. L1B7B:  RST     08H             ; ERROR-1
  8164.         DB    $14             ; Error Report: BREAK into program
  8165.  
  8166. ;; STMT-R-1
  8167. L1B7D           IF BAS48_ONLY=1
  8168.                 BIT 7,(IY+0X0A)
  8169.                 ELSE
  8170.                 CALL L3B4D              ; Spectrum 128 patch
  8171.                 NOP
  8172.                 ENDIF
  8173.  
  8174. L1B81:  JR      NZ,L1BF4        ; forward to STMT-NEXT if a program line.
  8175.  
  8176.         LD      HL,($5C42)      ; fetch line number from NEWPPC
  8177.         BIT     7,H             ; will be set if minus two - direct command(s)
  8178.         JR      Z,L1B9E         ; forward to LINE-NEW if a jump is to be
  8179.                                 ; made to a new program line/statement.
  8180.  
  8181. ; --------------------
  8182. ; Run a direct command
  8183. ; --------------------
  8184. ; A direct command is to be run or, if continuing from above,
  8185. ; the next statement of a direct command is to be considered.
  8186.  
  8187. ;; LINE-RUN
  8188. L1B8A:  LD      HL,$FFFE        ; The dummy value minus two
  8189.         LD      ($5C45),HL      ; is set/reset as line number in PPC.
  8190.         LD      HL,($5C61)      ; point to end of line + 1 - WORKSP.
  8191.         DEC     HL              ; now point to $80 end-marker.
  8192.         LD      DE,($5C59)      ; address the start of line E_LINE.
  8193.         DEC     DE              ; now location before - for GET-CHAR.
  8194.         LD      A,($5C44)       ; load statement to A from NSPPC.
  8195.         JR      L1BD1           ; forward to NEXT-LINE.
  8196.  
  8197. ; ------------------------------
  8198. ; Find start address of new line
  8199. ; ------------------------------
  8200. ; The branch was to here if a jump is to made to a new line number
  8201. ; and statement.
  8202. ; That is the previous statement was a GO TO, GO SUB, RUN, RETURN, NEXT etc..
  8203.  
  8204. ;; LINE-NEW
  8205. L1B9E:  CALL    L196E           ; routine LINE-ADDR gets address of line
  8206.                                 ; returning zero flag set if line found.
  8207.         LD      A,($5C44)       ; fetch new statement from NSPPC
  8208.         JR      Z,L1BBF         ; forward to LINE-USE if line matched.
  8209.  
  8210. ; continue as must be a direct command.
  8211.  
  8212.         AND     A               ; test statement which should be zero
  8213.         JR      NZ,L1BEC        ; forward to REPORT-N if not.
  8214.                                 ; 'Statement lost'
  8215.  
  8216. ;
  8217.  
  8218.         LD      B,A             ; save statement in B. ?
  8219.         LD      A,(HL)          ; fetch high byte of line number.
  8220.         AND     $C0             ; test if using direct command
  8221.                                 ; a program line is less than $3F
  8222.         LD      A,B             ; retrieve statement.
  8223.                                 ; (we can assume it is zero).
  8224.         JR      Z,L1BBF         ; forward to LINE-USE if was a program line
  8225.  
  8226. ; Alternatively a direct statement has finished correctly.
  8227.  
  8228. ;; REPORT-0
  8229. L1BB0:  RST     08H             ; ERROR-1
  8230.         DB    $FF             ; Error Report: OK
  8231.  
  8232. ; ------------------
  8233. ; Handle REM command
  8234. ; ------------------
  8235. ; The REM command routine.
  8236. ; The return address STMT-RET is dropped and the rest of line ignored.
  8237.  
  8238. ;; REM
  8239. L1BB2:  POP     BC              ; drop return address STMT-RET and
  8240.                                 ; continue ignoring rest of line.
  8241.  
  8242. ; ------------
  8243. ; End of line?
  8244. ; ------------
  8245. ;
  8246. ;
  8247.  
  8248. ;; LINE-END
  8249. L1BB3:  CALL    L2530           ; routine SYNTAX-Z  (UNSTACK-Z?)
  8250.         RET     Z               ; return if checking syntax.
  8251.  
  8252.         LD      HL,($5C55)      ; fetch NXTLIN to HL.
  8253.         LD      A,$C0           ; test against the
  8254.         AND     (HL)            ; system limit $3F.
  8255.         RET     NZ              ; return if more as must be
  8256.                                 ; end of program.
  8257.                                 ; (or direct command)
  8258.  
  8259.         XOR     A               ; set statement to zero.
  8260.  
  8261. ; and continue to set up the next following line and then consider this new one.
  8262.  
  8263. ; ---------------------
  8264. ; General line checking
  8265. ; ---------------------
  8266. ; The branch was here from LINE-NEW if BASIC is branching.
  8267. ; or a continuation from above if dealing with a new sequential line.
  8268. ; First make statement zero number one leaving others unaffected.
  8269.  
  8270. ;; LINE-USE
  8271. L1BBF:  CP      $01             ; will set carry if zero.
  8272.         ADC     A,$00           ; add in any carry.
  8273.  
  8274.         LD      D,(HL)          ; high byte of line number to D.
  8275.         INC     HL              ; advance pointer.
  8276.         LD      E,(HL)          ; low byte of line number to E.
  8277.         LD      ($5C45),DE      ; set system variable PPC.
  8278.  
  8279.         INC     HL              ; advance pointer.
  8280.         LD      E,(HL)          ; low byte of line length to E.
  8281.         INC     HL              ; advance pointer.
  8282.         LD      D,(HL)          ; high byte of line length to D.
  8283.  
  8284.         EX      DE,HL           ; swap pointer to DE before
  8285.         ADD     HL,DE           ; adding to address the end of line.
  8286.         INC     HL              ; advance to start of next line.
  8287.  
  8288. ; -----------------------------
  8289. ; Update NEXT LINE but consider
  8290. ; previous line or edit line.
  8291. ; -----------------------------
  8292. ; The pointer will be the next line if continuing from above or to
  8293. ; edit line end-marker ($80) if from LINE-RUN.
  8294.  
  8295. ;; NEXT-LINE
  8296. L1BD1:  LD      ($5C55),HL      ; store pointer in system variable NXTLIN
  8297.  
  8298.         EX      DE,HL           ; bring back pointer to previous or edit line
  8299.         LD      ($5C5D),HL      ; and update CH_ADD with character address.
  8300.  
  8301.         LD      D,A             ; store statement in D.
  8302.         LD      E,$00           ; set E to zero to suppress token searching
  8303.                                 ; if EACH-STMT is to be called.
  8304.         LD      (IY+$0A),$FF    ; set statement NSPPC to $FF signalling
  8305.                                 ; no jump to be made.
  8306.         DEC     D               ; decrement and test statement
  8307.         LD      (IY+$0D),D      ; set SUBPPC to decremented statement number.
  8308.         JP      Z,L1B28         ; to STMT-LOOP if result zero as statement is
  8309.                                 ; at start of line and address is known.
  8310.  
  8311.         INC     D               ; else restore statement.
  8312.         CALL    L198B           ; routine EACH-STMT finds the D'th statement
  8313.                                 ; address as E does not contain a token.
  8314.         JR      Z,L1BF4         ; forward to STMT-NEXT if address found.
  8315.  
  8316. ;; REPORT-N
  8317. L1BEC:  RST     08H             ; ERROR-1
  8318.         DB    $16             ; Error Report: Statement lost
  8319.  
  8320. ; -----------------
  8321. ; End of statement?
  8322. ; -----------------
  8323. ; This combination of routines is called from 20 places when
  8324. ; the end of a statement should have been reached and all preceding
  8325. ; syntax is in order.
  8326.  
  8327. ;; CHECK-END
  8328. L1BEE:  CALL    L2530           ; routine SYNTAX-Z
  8329.         RET     NZ              ; return immediately in runtime
  8330.  
  8331.         POP     BC              ; drop address of calling routine.
  8332.         POP     BC              ; drop address STMT-RET.
  8333.                                 ; and continue to find next statement.
  8334.  
  8335. ; --------------------
  8336. ; Go to next statement
  8337. ; --------------------
  8338. ; Acceptable characters at this point are carriage return and ':'.
  8339. ; If so go to next statement which in the first case will be on next line.
  8340.  
  8341. ;; STMT-NEXT
  8342. L1BF4           IF BAS48_ONLY=1
  8343.                 RST 0X18
  8344.                 CP 0X0D
  8345.                 ELSE
  8346.                 CALL L3B5D              ; Spectrum 128 patch
  8347.                 ENDIF
  8348.  
  8349. L1BF7:  JR      Z,L1BB3         ; back to LINE-END if so.
  8350.  
  8351.         CP      $3A             ; is it ':' ?
  8352.         JP      Z,L1B28         ; jump back to STMT-LOOP to consider
  8353.                                 ; further statements
  8354.  
  8355.         JP      L1C8A           ; jump to REPORT-C with any other character
  8356.                                 ; 'Nonsense in BASIC'.
  8357.  
  8358. ; Note. the two-byte sequence 'rst 08; DB $0b' could replace the above jp.
  8359.  
  8360. ; -------------------
  8361. ; Command class table
  8362. ; -------------------
  8363. ;
  8364.  
  8365. ;; class-tbl
  8366. L1C01:  DB    L1C10 - $       ; 0F offset to Address: CLASS-00
  8367.         DB    L1C1F - $       ; 1D offset to Address: CLASS-01
  8368.         DB    L1C4E - $       ; 4B offset to Address: CLASS-02
  8369.         DB    L1C0D - $       ; 09 offset to Address: CLASS-03
  8370.         DB    L1C6C - $       ; 67 offset to Address: CLASS-04
  8371.         DB    L1C11 - $       ; 0B offset to Address: CLASS-05
  8372.         DB    L1C82 - $       ; 7B offset to Address: CLASS-06
  8373.         DB    L1C96 - $       ; 8E offset to Address: CLASS-07
  8374.         DB    L1C7A - $       ; 71 offset to Address: CLASS-08
  8375.         DB    L1CBE - $       ; B4 offset to Address: CLASS-09
  8376.         DB    L1C8C - $       ; 81 offset to Address: CLASS-0A
  8377.         DB    L1CDB - $       ; CF offset to Address: CLASS-0B
  8378.  
  8379.  
  8380. ; --------------------------------
  8381. ; Command classes---00, 03, and 05
  8382. ; --------------------------------
  8383. ; class-03 e.g RUN or RUN 200   ;  optional operand
  8384. ; class-00 e.g CONTINUE         ;  no operand
  8385. ; class-05 e.g PRINT            ;  variable syntax checked by routine
  8386.  
  8387. ;; CLASS-03
  8388. L1C0D:  CALL    L1CDE           ; routine FETCH-NUM
  8389.  
  8390. ;; CLASS-00
  8391.  
  8392. L1C10:  CP      A               ; reset zero flag.
  8393.  
  8394. ; if entering here then all class routines are entered with zero reset.
  8395.  
  8396. ;; CLASS-05
  8397. L1C11:  POP     BC              ; drop address SCAN-LOOP.
  8398.         CALL    Z,L1BEE         ; if zero set then call routine CHECK-END >>>
  8399.                                 ; as should be no further characters.
  8400.  
  8401.         EX      DE,HL           ; save HL to DE.
  8402.         LD      HL,($5C74)      ; fetch T_ADDR
  8403.         LD      C,(HL)          ; fetch low byte of routine
  8404.         INC     HL              ; address next.
  8405.         LD      B,(HL)          ; fetch high byte of routine.
  8406.         EX      DE,HL           ; restore HL from DE
  8407.         PUSH    BC              ; push the address
  8408.         RET                     ; and make an indirect jump to the command.
  8409.  
  8410. ; --------------------------------
  8411. ; Command classes---01, 02, and 04
  8412. ; --------------------------------
  8413. ; class-01  e.g LET A = 2*3     ; a variable is reqd
  8414.  
  8415. ; This class routine is also called from INPUT and READ to find the
  8416. ; destination variable for an assignment.
  8417.  
  8418. ;; CLASS-01
  8419. L1C1F:  CALL    L28B2           ; routine LOOK-VARS returns carry set if not
  8420.                                 ; found in runtime.
  8421.  
  8422. ; ----------------------
  8423. ; Variable in assignment
  8424. ; ----------------------
  8425. ;
  8426. ;
  8427.  
  8428. ;; VAR-A-1
  8429. L1C22:  LD      (IY+$37),$00    ; set FLAGX to zero
  8430.         JR      NC,L1C30        ; forward to VAR-A-2 if found or checking
  8431.                                 ; syntax.
  8432.  
  8433.         SET     1,(IY+$37)      ; FLAGX  - Signal a new variable
  8434.         JR      NZ,L1C46        ; to VAR-A-3 if not assigning to an array
  8435.                                 ; e.g. LET a$(3,3) = "X"
  8436.  
  8437. ;; REPORT-2
  8438. L1C2E:  RST     08H             ; ERROR-1
  8439.         DB    $01             ; Error Report: Variable not found
  8440.  
  8441. ;; VAR-A-2
  8442. L1C30:  CALL    Z,L2996         ; routine STK-VAR considers a subscript/slice
  8443.         BIT     6,(IY+$01)      ; test FLAGS  - Numeric or string result ?
  8444.         JR      NZ,L1C46        ; to VAR-A-3 if numeric
  8445.  
  8446.         XOR     A               ; default to array/slice - to be retained.
  8447.         CALL    L2530           ; routine SYNTAX-Z
  8448.         CALL    NZ,L2BF1        ; routine STK-FETCH is called in runtime
  8449.                                 ; may overwrite A with 1.
  8450.         LD      HL,$5C71        ; address system variable FLAGX
  8451.         OR      (HL)            ; set bit 0 if simple variable to be reclaimed
  8452.         LD      (HL),A          ; update FLAGX
  8453.         EX      DE,HL           ; start of string/subscript to DE
  8454.  
  8455. ;; VAR-A-3
  8456. L1C46:  LD      ($5C72),BC      ; update STRLEN
  8457.         LD      ($5C4D),HL      ; and DEST of assigned string.
  8458.         RET                     ; return.
  8459.  
  8460. ; -------------------------------------------------
  8461. ; class-02 e.g. LET a = 1 + 1   ; an expression must follow
  8462.  
  8463. ;; CLASS-02
  8464. L1C4E:  POP     BC              ; drop return address SCAN-LOOP
  8465.         CALL    L1C56           ; routine VAL-FET-1 is called to check
  8466.                                 ; expression and assign result in runtime
  8467.         CALL    L1BEE           ; routine CHECK-END checks nothing else
  8468.                                 ; is present in statement.
  8469.         RET                     ; Return
  8470.  
  8471. ; -------------
  8472. ; Fetch a value
  8473. ; -------------
  8474. ;
  8475. ;
  8476.  
  8477. ;; VAL-FET-1
  8478. L1C56:  LD      A,($5C3B)       ; initial FLAGS to A
  8479.  
  8480. ;; VAL-FET-2
  8481. L1C59:  PUSH    AF              ; save A briefly
  8482.         CALL    L24FB           ; routine SCANNING evaluates expression.
  8483.         POP     AF              ; restore A
  8484.         LD      D,(IY+$01)      ; post-SCANNING FLAGS to D
  8485.         XOR     D               ; xor the two sets of flags
  8486.         AND     $40             ; pick up bit 6 of xored FLAGS should be zero
  8487.         JR      NZ,L1C8A        ; forward to REPORT-C if not zero
  8488.                                 ; 'Nonsense in BASIC' - results don't agree.
  8489.  
  8490.         BIT     7,D             ; test FLAGS - is syntax being checked ?
  8491.         JP      NZ,L2AFF        ; jump forward to LET to make the assignment
  8492.                                 ; in runtime.
  8493.  
  8494.         RET                     ; but return from here if checking syntax.
  8495.  
  8496. ; ------------------
  8497. ; Command class---04
  8498. ; ------------------
  8499. ; class-04 e.g. FOR i            ; a single character variable must follow
  8500.  
  8501. ;; CLASS-04
  8502. L1C6C:  CALL    L28B2           ; routine LOOK-VARS
  8503.         PUSH    AF              ; preserve flags.
  8504.         LD      A,C             ; fetch type - should be 011xxxxx
  8505.         OR      $9F             ; combine with 10011111.
  8506.         INC     A               ; test if now $FF by incrementing.
  8507.         JR      NZ,L1C8A        ; forward to REPORT-C if result not zero.
  8508.  
  8509.         POP     AF              ; else restore flags.
  8510.         JR      L1C22           ; back to VAR-A-1
  8511.  
  8512.  
  8513. ; --------------------------------
  8514. ; Expect numeric/string expression
  8515. ; --------------------------------
  8516. ; This routine is used to get the two coordinates of STRING$, ATTR and POINT.
  8517. ; It is also called from PRINT-ITEM to get the two numeric expressions that
  8518. ; follow the AT ( in PRINT AT, INPUT AT).
  8519.  
  8520. ;; NEXT-2NUM
  8521. L1C79:  RST     20H             ; NEXT-CHAR advance past 'AT' or '('.
  8522.  
  8523. ; --------
  8524. ; class-08 e.g POKE 65535,2     ; two numeric expressions separated by comma
  8525. ;; CLASS-08
  8526. ;; EXPT-2NUM
  8527. L1C7A:  CALL    L1C82           ; routine EXPT-1NUM is called for first
  8528.                                 ; numeric expression
  8529.         CP      $2C             ; is character ',' ?
  8530.         JR      NZ,L1C8A        ; to REPORT-C if not required separator.
  8531.                                 ; 'Nonsense in BASIC'.
  8532.  
  8533.         RST     20H             ; NEXT-CHAR
  8534.  
  8535. ; ->
  8536. ;  class-06  e.g. GOTO a*1000   ; a numeric expression must follow
  8537. ;; CLASS-06
  8538. ;; EXPT-1NUM
  8539. L1C82:  CALL    L24FB           ; routine SCANNING
  8540.         BIT     6,(IY+$01)      ; test FLAGS  - Numeric or string result ?
  8541.         RET     NZ              ; return if result is numeric.
  8542.  
  8543. ;; REPORT-C
  8544. L1C8A:  RST     08H             ; ERROR-1
  8545.         DB    $0B             ; Error Report: Nonsense in BASIC
  8546.  
  8547. ; ---------------------------------------------------------------
  8548. ; class-0A e.g. ERASE "????"    ; a string expression must follow.
  8549. ;                               ; these only occur in unimplemented commands
  8550. ;                               ; although the routine expt-exp is called
  8551. ;                               ; from SAVE-ETC
  8552.  
  8553. ;; CLASS-0A
  8554. ;; EXPT-EXP
  8555. L1C8C:  CALL    L24FB           ; routine SCANNING
  8556.         BIT     6,(IY+$01)      ; test FLAGS  - Numeric or string result ?
  8557.         RET     Z               ; return if string result.
  8558.  
  8559.         JR      L1C8A           ; back to REPORT-C if numeric.
  8560.  
  8561. ; ---------------------
  8562. ; Set permanent colours
  8563. ; class 07
  8564. ; ---------------------
  8565. ; class-07 e.g PAPER 6          ; a single class for a collection of
  8566. ;                               ; similar commands. Clever.
  8567. ;
  8568. ; Note. these commands should ensure that current channel is 'S'
  8569.  
  8570. ;; CLASS-07
  8571. L1C96:  BIT     7,(IY+$01)      ; test FLAGS - checking syntax only ?
  8572.         RES     0,(IY+$02)      ; update TV_FLAG - signal main screen in use
  8573.         CALL    NZ,L0D4D        ; routine TEMPS is called in runtime.
  8574.         POP     AF              ; drop return address SCAN-LOOP
  8575.         LD      A,($5C74)       ; T_ADDR_lo to accumulator.
  8576.                                 ; points to '$07' entry + 1
  8577.                                 ; e.g. for INK points to $EC now
  8578.  
  8579. ; Note if you move alter the syntax table next line may have to be altered.
  8580.  
  8581. ; Note. For ZASM assembler replace following expression with SUB $13.
  8582.  
  8583. L1CA5           SUB LOW (L1AEB)-$D8     ; % 256 ; convert $EB to $D8 ('INK') etc.
  8584.                                 ; ( is SUB $13 in standard ROM )
  8585.  
  8586.         CALL    L21FC           ; routine CO-TEMP-4
  8587.         CALL    L1BEE           ; routine CHECK-END check that nothing else
  8588.                                 ; in statement.
  8589.  
  8590. ; return here in runtime.
  8591.  
  8592.         LD      HL,($5C8F)      ; pick up ATTR_T and MASK_T
  8593.         LD      ($5C8D),HL      ; and store in ATTR_P and MASK_P
  8594.         LD      HL,$5C91        ; point to P_FLAG.
  8595.         LD      A,(HL)          ; pick up in A
  8596.         RLCA                    ; rotate to left
  8597.         XOR     (HL)            ; combine with HL
  8598.         AND     $AA             ; 10101010
  8599.         XOR     (HL)            ; only permanent bits affected
  8600.         LD      (HL),A          ; reload into P_FLAG.
  8601.         RET                     ; return.
  8602.  
  8603. ; ------------------
  8604. ; Command class---09
  8605. ; ------------------
  8606. ; e.g. PLOT PAPER 0; 128,88     ; two coordinates preceded by optional
  8607. ;                               ; embedded colour items.
  8608. ;
  8609. ; Note. this command should ensure that current channel is actually 'S'.
  8610.  
  8611. ;; CLASS-09
  8612. L1CBE:  CALL    L2530           ; routine SYNTAX-Z
  8613.         JR      Z,L1CD6         ; forward to CL-09-1 if checking syntax.
  8614.  
  8615.         RES     0,(IY+$02)      ; update TV_FLAG - signal main screen in use
  8616.         CALL    L0D4D           ; routine TEMPS is called.
  8617.         LD      HL,$5C90        ; point to MASK_T
  8618.         LD      A,(HL)          ; fetch mask to accumulator.
  8619.         OR      $F8             ; or with 11111000 paper/bright/flash 8
  8620.         LD      (HL),A          ; mask back to MASK_T system variable.
  8621.         RES     6,(IY+$57)      ; reset P_FLAG  - signal NOT PAPER 9 ?
  8622.  
  8623.         RST     18H             ; GET-CHAR
  8624.  
  8625. ;; CL-09-1
  8626. L1CD6:  CALL    L21E2           ; routine CO-TEMP-2 deals with any embedded
  8627.                                 ; colour items.
  8628.         JR      L1C7A           ; exit via EXPT-2NUM to check for x,y.
  8629.  
  8630. ; Note. if either of the numeric expressions contain STR$ then the flag setting
  8631. ; above will be undone when the channel flags are reset during STR$.
  8632. ; e.g.
  8633. ; 10 BORDER 3 : PLOT VAL STR$ 128, VAL STR$ 100
  8634. ; credit John Elliott.
  8635.  
  8636. ; ------------------
  8637. ; Command class---0B
  8638. ; ------------------
  8639. ; Again a single class for four commands.
  8640. ; This command just jumps back to SAVE-ETC to handle the four tape commands.
  8641. ; The routine itself works out which command has called it by examining the
  8642. ; address in T_ADDR_lo. Note therefore that the syntax table has to be
  8643. ; located where these and other sequential command addresses are not split
  8644. ; over a page boundary.
  8645.  
  8646. ;; CLASS-0B
  8647. L1CDB:  JP      L0605           ; jump way back to SAVE-ETC
  8648.  
  8649. ; --------------
  8650. ; Fetch a number
  8651. ; --------------
  8652. ; This routine is called from CLASS-03 when a command may be followed by
  8653. ; an optional numeric expression e.g. RUN. If the end of statement has
  8654. ; been reached then zero is used as the default.
  8655. ; Also called from LIST-4.
  8656.  
  8657. ;; FETCH-NUM
  8658. L1CDE:  CP      $0D             ; is character a carriage return ?
  8659.         JR      Z,L1CE6         ; forward to USE-ZERO if so
  8660.  
  8661.         CP      $3A             ; is it ':' ?
  8662.         JR      NZ,L1C82        ; forward to EXPT-1NUM if not.
  8663.                                 ; else continue and use zero.
  8664.  
  8665. ; ----------------
  8666. ; Use zero routine
  8667. ; ----------------
  8668. ; This routine is called four times to place the value zero on the
  8669. ; calculator stack as a default value in runtime.
  8670.  
  8671. ;; USE-ZERO
  8672. L1CE6:  CALL    L2530           ; routine SYNTAX-Z  (UNSTACK-Z?)
  8673.         RET     Z               ;
  8674.  
  8675.         RST     28H             ;; FP-CALC
  8676.         DB    $A0             ;;stk-zero       ;0.
  8677.         DB    $38             ;;end-calc
  8678.  
  8679.         RET                     ; return.
  8680.  
  8681. ; -------------------
  8682. ; Handle STOP command
  8683. ; -------------------
  8684. ; Command Syntax: STOP
  8685. ; One of the shortest and least used commands. As with 'OK' not an error.
  8686.  
  8687. ;; REPORT-9
  8688. ;; STOP
  8689. L1CEE:  RST     08H             ; ERROR-1
  8690.         DB    $08             ; Error Report: STOP statement
  8691.  
  8692. ; -----------------
  8693. ; Handle IF command
  8694. ; -----------------
  8695. ; e.g. IF score>100 THEN PRINT "You Win"
  8696. ; The parser has already checked the expression the result of which is on
  8697. ; the calculator stack. The presence of the 'THEN' separator has also been
  8698. ; checked and CH-ADD points to the command after THEN.
  8699. ;
  8700.  
  8701. ;; IF
  8702. L1CF0:  POP     BC              ; drop return address - STMT-RET
  8703.         CALL    L2530           ; routine SYNTAX-Z
  8704.         JR      Z,L1D00         ; forward to IF-1 if checking syntax
  8705.                                 ; to check syntax of PRINT "You Win"
  8706.  
  8707.  
  8708.         RST     28H             ;; FP-CALC    score>100 (1=TRUE 0=FALSE)
  8709.         DB    $02             ;;delete      .
  8710.         DB    $38             ;;end-calc
  8711.  
  8712.         EX      DE,HL           ; make HL point to deleted value
  8713.         CALL    L34E9           ; routine TEST-ZERO
  8714.         JP      C,L1BB3         ; jump to LINE-END if FALSE (0)
  8715.  
  8716. ;; IF-1
  8717. L1D00:  JP      L1B29           ; to STMT-L-1, if true (1) to execute command
  8718.                                 ; after 'THEN' token.
  8719.  
  8720. ; ------------------
  8721. ; Handle FOR command
  8722. ; ------------------
  8723. ; e.g. FOR i = 0 TO 1 STEP 0.1
  8724. ; Using the syntax tables, the parser has already checked for a start and
  8725. ; limit value and also for the intervening separator.
  8726. ; the two values v,l are on the calculator stack.
  8727. ; CLASS-04 has also checked the variable and the name is in STRLEN_lo.
  8728. ; The routine begins by checking for an optional STEP.
  8729.  
  8730. ;; FOR
  8731. L1D03:  CP      $CD             ; is there a 'STEP' ?
  8732.         JR      NZ,L1D10        ; to F-USE-1 if not to use 1 as default.
  8733.  
  8734.         RST     20H             ; NEXT-CHAR
  8735.         CALL    L1C82           ; routine EXPT-1NUM
  8736.         CALL    L1BEE           ; routine CHECK-END
  8737.         JR      L1D16           ; to F-REORDER
  8738.  
  8739. ; ---
  8740.  
  8741. ;; F-USE-1
  8742. L1D10:  CALL    L1BEE           ; routine CHECK-END
  8743.  
  8744.         RST     28H             ;; FP-CALC      v,l.
  8745.         DB    $A1             ;;stk-one       v,l,1=s.
  8746.         DB    $38             ;;end-calc
  8747.  
  8748.  
  8749. ;; F-REORDER
  8750. L1D16:  RST     28H             ;; FP-CALC       v,l,s.
  8751.         DB    $C0             ;;st-mem-0       v,l,s.
  8752.         DB    $02             ;;delete         v,l.
  8753.         DB    $01             ;;exchange       l,v.
  8754.         DB    $E0             ;;get-mem-0      l,v,s.
  8755.         DB    $01             ;;exchange       l,s,v.
  8756.         DB    $38             ;;end-calc
  8757.  
  8758.         CALL    L2AFF           ; routine LET assigns the initial value v to
  8759.                                 ; the variable altering type if necessary.
  8760.         LD      ($5C68),HL      ; The system variable MEM is made to point to
  8761.                                 ; the variable instead of its normal
  8762.                                 ; location MEMBOT
  8763.         DEC     HL              ; point to single-character name
  8764.         LD      A,(HL)          ; fetch name
  8765.         SET     7,(HL)          ; set bit 7 at location
  8766.         LD      BC,$0006        ; add six to HL
  8767.         ADD     HL,BC           ; to address where limit should be.
  8768.         RLCA                    ; test bit 7 of original name.
  8769.         JR      C,L1D34         ; forward to F-L-S if already a FOR/NEXT
  8770.                                 ; variable
  8771.  
  8772.         LD      C,$0D           ; otherwise an additional 13 bytes are needed.
  8773.                                 ; 5 for each value, two for line number and
  8774.                                 ; 1 byte for looping statement.
  8775.         CALL    L1655           ; routine MAKE-ROOM creates them.
  8776.         INC     HL              ; make HL address limit.
  8777.  
  8778. ;; F-L-S
  8779. L1D34:  PUSH    HL              ; save position.
  8780.  
  8781.         RST     28H             ;; FP-CALC         l,s.
  8782.         DB    $02             ;;delete           l.
  8783.         DB    $02             ;;delete           .
  8784.         DB    $38             ;;end-calc
  8785.                                 ; DE points to STKEND, l.
  8786.  
  8787.         POP     HL              ; restore variable position
  8788.         EX      DE,HL           ; swap pointers
  8789.         LD      C,$0A           ; ten bytes to move
  8790.         LDIR                    ; Copy 'deleted' values to variable.
  8791.         LD      HL,($5C45)      ; Load with current line number from PPC
  8792.         EX      DE,HL           ; exchange pointers.
  8793.         LD      (HL),E          ; save the looping line
  8794.         INC     HL              ; in the next
  8795.         LD      (HL),D          ; two locations.
  8796.         LD      D,(IY+$0D)      ; fetch statement from SUBPPC system variable.
  8797.         INC     D               ; increment statement.
  8798.         INC     HL              ; and pointer
  8799.         LD      (HL),D          ; and store the looping statement.
  8800.                                 ;
  8801.         CALL    L1DDA           ; routine NEXT-LOOP considers an initial
  8802.         RET     NC              ; iteration. Return to STMT-RET if a loop is
  8803.                                 ; possible to execute next statement.
  8804.  
  8805. ; no loop is possible so execution continues after the matching 'NEXT'
  8806.  
  8807.         LD      B,(IY+$38)      ; get single-character name from STRLEN_lo
  8808.         LD      HL,($5C45)      ; get the current line from PPC
  8809.         LD      ($5C42),HL      ; and store it in NEWPPC
  8810.         LD      A,($5C47)       ; fetch current statement from SUBPPC
  8811.         NEG                     ; Negate as counter decrements from zero
  8812.                                 ; initially and we are in the middle of a
  8813.                                 ; line.
  8814.         LD      D,A             ; Store result in D.
  8815.         LD      HL,($5C5D)      ; get current address from CH_ADD
  8816.         LD      E,$F3           ; search will be for token 'NEXT'
  8817.  
  8818. ;; F-LOOP
  8819. L1D64:  PUSH    BC              ; save variable name.
  8820.         LD      BC,($5C55)      ; fetch NXTLIN
  8821.         CALL    L1D86           ; routine LOOK-PROG searches for 'NEXT' token.
  8822.         LD      ($5C55),BC      ; update NXTLIN
  8823.         POP     BC              ; and fetch the letter
  8824.         JR      C,L1D84         ; forward to REPORT-I if the end of program
  8825.                                 ; was reached by LOOK-PROG.
  8826.                                 ; 'FOR without NEXT'
  8827.  
  8828.         RST     20H             ; NEXT-CHAR fetches character after NEXT
  8829.         OR      $20             ; ensure it is upper-case.
  8830.         CP      B               ; compare with FOR variable name
  8831.         JR      Z,L1D7C         ; forward to F-FOUND if it matches.
  8832.  
  8833. ; but if no match i.e. nested FOR/NEXT loops then continue search.
  8834.  
  8835.         RST     20H             ; NEXT-CHAR
  8836.         JR      L1D64           ; back to F-LOOP
  8837.  
  8838. ; ---
  8839.  
  8840.  
  8841. ;; F-FOUND
  8842. L1D7C:  RST     20H             ; NEXT-CHAR
  8843.         LD      A,$01           ; subtract the negated counter from 1
  8844.         SUB     D               ; to give the statement after the NEXT
  8845.         LD      ($5C44),A       ; set system variable NSPPC
  8846.         RET                     ; return to STMT-RET to branch to new
  8847.                                 ; line and statement. ->
  8848. ; ---
  8849.  
  8850. ;; REPORT-I
  8851. L1D84:  RST     08H             ; ERROR-1
  8852.         DB    $11             ; Error Report: FOR without NEXT
  8853.  
  8854. ; ---------
  8855. ; LOOK-PROG
  8856. ; ---------
  8857. ; Find DATA, DEF FN or NEXT.
  8858. ; This routine searches the program area for one of the above three keywords.
  8859. ; On entry, HL points to start of search area.
  8860. ; The token is in E, and D holds a statement count, decremented from zero.
  8861.  
  8862. ;; LOOK-PROG
  8863. L1D86:  LD      A,(HL)          ; fetch current character
  8864.         CP      $3A             ; is it ':' a statement separator ?
  8865.         JR      Z,L1DA3         ; forward to LOOK-P-2 if so.
  8866.  
  8867. ; The starting point was PROG - 1 or the end of a line.
  8868.  
  8869. ;; LOOK-P-1
  8870. L1D8B:  INC     HL              ; increment pointer to address
  8871.         LD      A,(HL)          ; the high byte of line number
  8872.         AND     $C0             ; test for program end marker $80 or a
  8873.                                 ; variable
  8874.         SCF                     ; Set Carry Flag
  8875.         RET     NZ              ; return with carry set if at end
  8876.                                 ; of program.           ->
  8877.  
  8878.         LD      B,(HL)          ; high byte of line number to B
  8879.         INC     HL              ;
  8880.         LD      C,(HL)          ; low byte to C.
  8881.         LD      ($5C42),BC      ; set system variable NEWPPC.
  8882.         INC     HL              ;
  8883.         LD      C,(HL)          ; low byte of line length to C.
  8884.         INC     HL              ;
  8885.         LD      B,(HL)          ; high byte to B.
  8886.         PUSH    HL              ; save address
  8887.         ADD     HL,BC           ; add length to position.
  8888.         LD      B,H             ; and save result
  8889.         LD      C,L             ; in BC.
  8890.         POP     HL              ; restore address.
  8891.         LD      D,$00           ; initialize statement counter to zero.
  8892.  
  8893. ;; LOOK-P-2
  8894. L1DA3:  PUSH    BC              ; save address of next line
  8895.         CALL    L198B           ; routine EACH-STMT searches current line.
  8896.         POP     BC              ; restore address.
  8897.         RET     NC              ; return if match was found. ->
  8898.  
  8899.         JR      L1D8B           ; back to LOOK-P-1 for next line.
  8900.  
  8901. ; -------------------
  8902. ; Handle NEXT command
  8903. ; -------------------
  8904. ; e.g. NEXT i
  8905. ; The parameter tables have already evaluated the presence of a variable
  8906.  
  8907. ;; NEXT
  8908. L1DAB:  BIT     1,(IY+$37)      ; test FLAGX - handling a new variable ?
  8909.         JP      NZ,L1C2E        ; jump back to REPORT-2 if so
  8910.                                 ; 'Variable not found'
  8911.  
  8912. ; now test if found variable is a simple variable uninitialized by a FOR.
  8913.  
  8914.         LD      HL,($5C4D)      ; load address of variable from DEST
  8915.         BIT     7,(HL)          ; is it correct type ?
  8916.         JR      Z,L1DD8         ; forward to REPORT-1 if not
  8917.                                 ; 'NEXT without FOR'
  8918.  
  8919.         INC     HL              ; step past variable name
  8920.         LD      ($5C68),HL      ; and set MEM to point to three 5-byte values
  8921.                                 ; value, limit, step.
  8922.  
  8923.         RST     28H             ;; FP-CALC     add step and re-store
  8924.         DB    $E0             ;;get-mem-0    v.
  8925.         DB    $E2             ;;get-mem-2    v,s.
  8926.         DB    $0F             ;;addition     v+s.
  8927.         DB    $C0             ;;st-mem-0     v+s.
  8928.         DB    $02             ;;delete       .
  8929.         DB    $38             ;;end-calc
  8930.  
  8931.         CALL    L1DDA           ; routine NEXT-LOOP tests against limit.
  8932.         RET     C               ; return if no more iterations possible.
  8933.  
  8934.         LD      HL,($5C68)      ; find start of variable contents from MEM.
  8935.         LD      DE,$000F        ; add 3*5 to
  8936.         ADD     HL,DE           ; address the looping line number
  8937.         LD      E,(HL)          ; low byte to E
  8938.         INC     HL              ;
  8939.         LD      D,(HL)          ; high byte to D
  8940.         INC     HL              ; address looping statement
  8941.         LD      H,(HL)          ; and store in H
  8942.         EX      DE,HL           ; swap registers
  8943.         JP      L1E73           ; exit via GO-TO-2 to execute another loop.
  8944.  
  8945. ; ---
  8946.  
  8947. ;; REPORT-1
  8948. L1DD8:  RST     08H             ; ERROR-1
  8949.         DB    $00             ; Error Report: NEXT without FOR
  8950.  
  8951.  
  8952. ; -----------------
  8953. ; Perform NEXT loop
  8954. ; -----------------
  8955. ; This routine is called from the FOR command to test for an initial
  8956. ; iteration and from the NEXT command to test for all subsequent iterations.
  8957. ; the system variable MEM addresses the variable's contents which, in the
  8958. ; latter case, have had the step, possibly negative, added to the value.
  8959.  
  8960. ;; NEXT-LOOP
  8961. L1DDA:  RST     28H             ;; FP-CALC
  8962.         DB    $E1             ;;get-mem-1        l.
  8963.         DB    $E0             ;;get-mem-0        l,v.
  8964.         DB    $E2             ;;get-mem-2        l,v,s.
  8965.         DB    $36             ;;less-0           l,v,(1/0) negative step ?
  8966.         DB    $00             ;;jump-true        l,v.(1/0)
  8967.  
  8968.         DB    $02             ;;to L1DE2, NEXT-1 if step negative
  8969.  
  8970.         DB    $01             ;;exchange         v,l.
  8971.  
  8972. ;; NEXT-1
  8973. L1DE2:  DB    $03             ;;subtract         l-v OR v-l.
  8974.         DB    $37             ;;greater-0        (1/0)
  8975.         DB    $00             ;;jump-true        .
  8976.  
  8977.         DB    $04             ;;to L1DE9, NEXT-2 if no more iterations.
  8978.  
  8979.         DB    $38             ;;end-calc         .
  8980.  
  8981.         AND     A               ; clear carry flag signalling another loop.
  8982.         RET                     ; return
  8983.  
  8984. ; ---
  8985.  
  8986. ;; NEXT-2
  8987. L1DE9:  DB    $38             ;;end-calc         .
  8988.  
  8989.         SCF                     ; set carry flag signalling looping exhausted.
  8990.         RET                     ; return
  8991.  
  8992.  
  8993. ; -------------------
  8994. ; Handle READ command
  8995. ; -------------------
  8996. ; e.g. READ a, b$, c$(1000 TO 3000)
  8997. ; A list of comma-separated variables is assigned from a list of
  8998. ; comma-separated expressions.
  8999. ; As it moves along the first list, the character address CH_ADD is stored
  9000. ; in X_PTR while CH_ADD is used to read the second list.
  9001.  
  9002. ;; READ-3
  9003. L1DEC:  RST     20H             ; NEXT-CHAR
  9004.  
  9005. ; -> Entry point.
  9006. ;; READ
  9007. L1DED:  CALL    L1C1F           ; routine CLASS-01 checks variable.
  9008.         CALL    L2530           ; routine SYNTAX-Z
  9009.         JR      Z,L1E1E         ; forward to READ-2 if checking syntax
  9010.  
  9011.  
  9012.         RST     18H             ; GET-CHAR
  9013.         LD      ($5C5F),HL      ; save character position in X_PTR.
  9014.         LD      HL,($5C57)      ; load HL with Data Address DATADD, which is
  9015.                                 ; the start of the program or the address
  9016.                                 ; after the last expression that was read or
  9017.                                 ; the address of the line number of the
  9018.                                 ; last RESTORE command.
  9019.         LD      A,(HL)          ; fetch character
  9020.         CP      $2C             ; is it a comma ?
  9021.         JR      Z,L1E0A         ; forward to READ-1 if so.
  9022.  
  9023. ; else all data in this statement has been read so look for next DATA token
  9024.  
  9025.         LD      E,$E4           ; token 'DATA'
  9026.         CALL    L1D86           ; routine LOOK-PROG
  9027.         JR      NC,L1E0A        ; forward to READ-1 if DATA found
  9028.  
  9029. ; else report the error.
  9030.  
  9031. ;; REPORT-E
  9032. L1E08:  RST     08H             ; ERROR-1
  9033.         DB    $0D             ; Error Report: Out of DATA
  9034.  
  9035. ;; READ-1
  9036. L1E0A:  CALL    L0077           ; routine TEMP-PTR1 advances updating CH_ADD
  9037.                                 ; with new DATADD position.
  9038.         CALL    L1C56           ; routine VAL-FET-1 assigns value to variable
  9039.                                 ; checking type match and adjusting CH_ADD.
  9040.  
  9041.         RST     18H             ; GET-CHAR fetches adjusted character position
  9042.         LD      ($5C57),HL      ; store back in DATADD
  9043.         LD      HL,($5C5F)      ; fetch X_PTR  the original READ CH_ADD
  9044.         LD      (IY+$26),$00    ; now nullify X_PTR_hi
  9045.         CALL    L0078           ; routine TEMP-PTR2 restores READ CH_ADD
  9046.  
  9047. ;; READ-2
  9048. L1E1E:  RST     18H             ; GET-CHAR
  9049.         CP      $2C             ; is it ',' indicating more variables to read ?
  9050.         JR      Z,L1DEC         ; back to READ-3 if so
  9051.  
  9052.         CALL    L1BEE           ; routine CHECK-END
  9053.         RET                     ; return from here in runtime to STMT-RET.
  9054.  
  9055. ; -------------------
  9056. ; Handle DATA command
  9057. ; -------------------
  9058. ; In runtime this 'command' is passed by but the syntax is checked when such
  9059. ; a statement is found while parsing a line.
  9060. ; e.g. DATA 1, 2, "text", score-1, a$(location, room, object), FN r(49),
  9061. ;         wages - tax, TRUE, The meaning of life
  9062.  
  9063. ;; DATA
  9064. L1E27:  CALL    L2530           ; routine SYNTAX-Z to check status
  9065.         JR      NZ,L1E37        ; forward to DATA-2 if in runtime
  9066.  
  9067. ;; DATA-1
  9068. L1E2C:  CALL    L24FB           ; routine SCANNING to check syntax of
  9069.                                 ; expression
  9070.         CP      $2C             ; is it a comma ?
  9071.         CALL    NZ,L1BEE        ; routine CHECK-END checks that statement
  9072.                                 ; is complete. Will make an early exit if
  9073.                                 ; so. >>>
  9074.         RST     20H             ; NEXT-CHAR
  9075.         JR      L1E2C           ; back to DATA-1
  9076.  
  9077. ; ---
  9078.  
  9079. ;; DATA-2
  9080. L1E37:  LD      A,$E4           ; set token to 'DATA' and continue into
  9081.                                 ; the the PASS-BY routine.
  9082.  
  9083.  
  9084. ; ----------------------------------
  9085. ; Check statement for DATA or DEF FN
  9086. ; ----------------------------------
  9087. ; This routine is used to backtrack to a command token and then
  9088. ; forward to the next statement in runtime.
  9089.  
  9090. ;; PASS-BY
  9091. L1E39:  LD      B,A             ; Give BC enough space to find token.
  9092.         CPDR                    ; Compare decrement and repeat. (Only use).
  9093.                                 ; Work backwards till keyword is found which
  9094.                                 ; is start of statement before any quotes.
  9095.                                 ; HL points to location before keyword.
  9096.         LD      DE,$0200        ; count 1+1 statements, dummy value in E to
  9097.                                 ; inhibit searching for a token.
  9098.         JP      L198B           ; to EACH-STMT to find next statement
  9099.  
  9100. ; -----------------------------------------------------------------------
  9101. ; A General Note on Invalid Line Numbers.
  9102. ; =======================================
  9103. ; One of the revolutionary concepts of Sinclair BASIC was that it supported
  9104. ; virtual line numbers. That is the destination of a GO TO, RESTORE etc. need
  9105. ; not exist. It could be a point before or after an actual line number.
  9106. ; Zero suffices for a before but the after should logically be infinity.
  9107. ; Since the maximum actual line limit is 9999 then the system limit, 16383
  9108. ; when variables kick in, would serve fine as a virtual end point.
  9109. ; However, ironically, only the LOAD command gets it right. It will not
  9110. ; autostart a program that has been saved with a line higher than 16383.
  9111. ; All the other commands deal with the limit unsatisfactorily.
  9112. ; LIST, RUN, GO TO, GO SUB and RESTORE have problems and the latter may
  9113. ; crash the machine when supplied with an inappropriate virtual line number.
  9114. ; This is puzzling as very careful consideration must have been given to
  9115. ; this point when the new variable types were allocated their masks and also
  9116. ; when the routine NEXT-ONE was successfully re-written to reflect this.
  9117. ; An enigma.
  9118. ; -------------------------------------------------------------------------
  9119.  
  9120. ; ----------------------
  9121. ; Handle RESTORE command
  9122. ; ----------------------
  9123. ; The restore command sets the system variable for the data address to
  9124. ; point to the location before the supplied line number or first line
  9125. ; thereafter.
  9126. ; This alters the position where subsequent READ commands look for data.
  9127. ; Note. If supplied with inappropriate high numbers the system may crash
  9128. ; in the LINE-ADDR routine as it will pass the program/variables end-marker
  9129. ; and then lose control of what it is looking for - variable or line number.
  9130. ; - observation, Steven Vickers, 1984, Pitman.
  9131.  
  9132. ;; RESTORE
  9133. L1E42:  CALL    L1E99           ; routine FIND-INT2 puts integer in BC.
  9134.                                 ; Note. B should be checked against limit $3F
  9135.                                 ; and an error generated if higher.
  9136.  
  9137. ; this entry point is used from RUN command with BC holding zero
  9138.  
  9139. ;; REST-RUN
  9140. L1E45:  LD      H,B             ; transfer the line
  9141.         LD      L,C             ; number to the HL register.
  9142.         CALL    L196E           ; routine LINE-ADDR to fetch the address.
  9143.         DEC     HL              ; point to the location before the line.
  9144.         LD      ($5C57),HL      ; update system variable DATADD.
  9145.         RET                     ; return to STMT-RET (or RUN)
  9146.  
  9147. ; ------------------------
  9148. ; Handle RANDOMIZE command
  9149. ; ------------------------
  9150. ; This command sets the SEED for the RND function to a fixed value.
  9151. ; With the parameter zero, a random start point is used depending on
  9152. ; how long the computer has been switched on.
  9153.  
  9154. ;; RANDOMIZE
  9155. L1E4F:  CALL    L1E99           ; routine FIND-INT2 puts parameter in BC.
  9156.         LD      A,B             ; test this
  9157.         OR      C               ; for zero.
  9158.         JR      NZ,L1E5A        ; forward to RAND-1 if not zero.
  9159.  
  9160.         LD      BC,($5C78)      ; use the lower two bytes at FRAMES1.
  9161.  
  9162. ;; RAND-1
  9163. L1E5A:  LD      ($5C76),BC      ; place in SEED system variable.
  9164.         RET                     ; return to STMT-RET
  9165.  
  9166. ; -----------------------
  9167. ; Handle CONTINUE command
  9168. ; -----------------------
  9169. ; The CONTINUE command transfers the OLD (but incremented) values of
  9170. ; line number and statement to the equivalent "NEW VALUE" system variables
  9171. ; by using the last part of GO TO and exits indirectly to STMT-RET.
  9172.  
  9173. ;; CONTINUE
  9174. L1E5F:  LD      HL,($5C6E)      ; fetch OLDPPC line number.
  9175.         LD      D,(IY+$36)      ; fetch OSPPC statement.
  9176.         JR      L1E73           ; forward to GO-TO-2
  9177.  
  9178. ; --------------------
  9179. ; Handle GO TO command
  9180. ; --------------------
  9181. ; The GO TO command routine is also called by GO SUB and RUN routines
  9182. ; to evaluate the parameters of both commands.
  9183. ; It updates the system variables used to fetch the next line/statement.
  9184. ; It is at STMT-RET that the actual change in control takes place.
  9185. ; Unlike some BASICs the line number need not exist.
  9186. ; Note. the high byte of the line number is incorrectly compared with $F0
  9187. ; instead of $3F. This leads to commands with operands greater than 32767
  9188. ; being considered as having been run from the editing area and the
  9189. ; error report 'Statement Lost' is given instead of 'OK'.
  9190. ; - Steven Vickers, 1984.
  9191.  
  9192. ;; GO-TO
  9193. L1E67:  CALL    L1E99           ; routine FIND-INT2 puts operand in BC
  9194.         LD      H,B             ; transfer line
  9195.         LD      L,C             ; number to HL.
  9196.         LD      D,$00           ; set statement to 0 - first.
  9197.         LD      A,H             ; compare high byte only
  9198.         CP      $F0             ; to $F0 i.e. 61439 in full.
  9199.         JR      NC,L1E9F        ; forward to REPORT-B if above.
  9200.  
  9201. ; This call entry point is used to update the system variables e.g. by RETURN.
  9202.  
  9203. ;; GO-TO-2
  9204. L1E73:  LD      ($5C42),HL      ; save line number in NEWPPC
  9205.         LD      (IY+$0A),D      ; and statement in NSPPC
  9206.         RET                     ; to STMT-RET (or GO-SUB command)
  9207.  
  9208. ; ------------------
  9209. ; Handle OUT command
  9210. ; ------------------
  9211. ; Syntax has been checked and the two comma-separated values are on the
  9212. ; calculator stack.
  9213.  
  9214. ;; OUT
  9215. L1E7A:  CALL    L1E85           ; routine TWO-PARAM fetches values
  9216.                                 ; to BC and A.
  9217.         OUT     (C),A           ; perform the operation.
  9218.         RET                     ; return to STMT-RET.
  9219.  
  9220. ; -------------------
  9221. ; Handle POKE command
  9222. ; -------------------
  9223. ; This routine alters a single byte in the 64K address space.
  9224. ; Happily no check is made as to whether ROM or RAM is addressed.
  9225. ; Sinclair BASIC requires no poking of system variables.
  9226.  
  9227. ;; POKE
  9228. L1E80:  CALL    L1E85           ; routine TWO-PARAM fetches values
  9229.                                 ; to BC and A.
  9230.         LD      (BC),A          ; load memory location with A.
  9231.         RET                     ; return to STMT-RET.
  9232.  
  9233. ; ------------------------------------
  9234. ; Fetch two  parameters from calculator stack
  9235. ; ------------------------------------
  9236. ; This routine fetches a byte and word from the calculator stack
  9237. ; producing an error if either is out of range.
  9238.  
  9239. ;; TWO-PARAM
  9240. L1E85:  CALL    L2DD5           ; routine FP-TO-A
  9241.         JR      C,L1E9F         ; forward to REPORT-B if overflow occurred
  9242.  
  9243.         JR      Z,L1E8E         ; forward to TWO-P-1 if positive
  9244.  
  9245.         NEG                     ; negative numbers are made positive
  9246.  
  9247. ;; TWO-P-1
  9248. L1E8E:  PUSH    AF              ; save the value
  9249.         CALL    L1E99           ; routine FIND-INT2 gets integer to BC
  9250.         POP     AF              ; restore the value
  9251.         RET                     ; return
  9252.  
  9253. ; -------------
  9254. ; Find integers
  9255. ; -------------
  9256. ; The first of these routines fetches a 8-bit integer (range 0-255) from the
  9257. ; calculator stack to the accumulator and is used for colours, streams,
  9258. ; durations and coordinates.
  9259. ; The second routine fetches 16-bit integers to the BC register pair
  9260. ; and is used to fetch command and function arguments involving line numbers
  9261. ; or memory addresses and also array subscripts and tab arguments.
  9262. ; ->
  9263.  
  9264. ;; FIND-INT1
  9265. L1E94:  CALL    L2DD5           ; routine FP-TO-A
  9266.         JR      L1E9C           ; forward to FIND-I-1 for common exit routine.
  9267.  
  9268. ; ---
  9269.  
  9270. ; ->
  9271.  
  9272. ;; FIND-INT2
  9273. L1E99:  CALL    L2DA2           ; routine FP-TO-BC
  9274.  
  9275. ;; FIND-I-1
  9276. L1E9C:  JR      C,L1E9F         ; to REPORT-Bb with overflow.
  9277.  
  9278.         RET     Z               ; return if positive.
  9279.  
  9280.  
  9281. ;; REPORT-Bb
  9282. L1E9F:  RST     08H             ; ERROR-1
  9283.         DB    $0A             ; Error Report: Integer out of range
  9284.  
  9285. ; ------------------
  9286. ; Handle RUN command
  9287. ; ------------------
  9288. ; This command runs a program starting at an optional line.
  9289. ; It performs a 'RESTORE 0' then CLEAR
  9290.  
  9291. ;; RUN
  9292. L1EA1:  CALL    L1E67           ; routine GO-TO puts line number in
  9293.                                 ; system variables.
  9294.         LD      BC,$0000        ; prepare to set DATADD to first line.
  9295.         CALL    L1E45           ; routine REST-RUN does the 'restore'.
  9296.                                 ; Note BC still holds zero.
  9297.         JR      L1EAF           ; forward to CLEAR-RUN to clear variables
  9298.                                 ; without disturbing RAMTOP and
  9299.                                 ; exit indirectly to STMT-RET
  9300.  
  9301. ; --------------------
  9302. ; Handle CLEAR command
  9303. ; --------------------
  9304. ; This command reclaims the space used by the variables.
  9305. ; It also clears the screen and the GO SUB stack.
  9306. ; With an integer expression, it sets the uppermost memory
  9307. ; address within the BASIC system.
  9308. ; "Contrary to the manual, CLEAR doesn't execute a RESTORE" -
  9309. ; Steven Vickers, Pitman Pocket Guide to the Spectrum, 1984.
  9310.  
  9311. ;; CLEAR
  9312. L1EAC:  CALL    L1E99           ; routine FIND-INT2 fetches to BC.
  9313.  
  9314. ;; CLEAR-RUN
  9315. L1EAF:  LD      A,B             ; test for
  9316.         OR      C               ; zero.
  9317.         JR      NZ,L1EB7        ; skip to CLEAR-1 if not zero.
  9318.  
  9319.         LD      BC,($5CB2)      ; use the existing value of RAMTOP if zero.
  9320.  
  9321. ;; CLEAR-1
  9322. L1EB7:  PUSH    BC              ; save ramtop value.
  9323.  
  9324.         LD      DE,($5C4B)      ; fetch VARS
  9325.         LD      HL,($5C59)      ; fetch E_LINE
  9326.         DEC     HL              ; adjust to point at variables end-marker.
  9327.         CALL    L19E5           ; routine RECLAIM-1 reclaims the space used by
  9328.                                 ; the variables.
  9329.         CALL    L0D6B           ; routine CLS to clear screen.
  9330.         LD      HL,($5C65)      ; fetch STKEND the start of free memory.
  9331.         LD      DE,$0032        ; allow for another 50 bytes.
  9332.         ADD     HL,DE           ; add the overhead to HL.
  9333.  
  9334.         POP     DE              ; restore the ramtop value.
  9335.         SBC     HL,DE           ; if HL is greater than the value then jump
  9336.         JR      NC,L1EDA        ; forward to REPORT-M
  9337.                                 ; 'RAMTOP no good'
  9338.  
  9339.         LD      HL,($5CB4)      ; now P-RAMT ($7FFF on 16K RAM machine)
  9340.         AND     A               ; exact this time.
  9341.         SBC     HL,DE           ; new ramtop must be lower or the same.
  9342.         JR      NC,L1EDC        ; skip to CLEAR-2 if in actual RAM.
  9343.  
  9344. ;; REPORT-M
  9345. L1EDA:  RST     08H             ; ERROR-1
  9346.         DB    $15             ; Error Report: RAMTOP no good
  9347.  
  9348. ;; CLEAR-2
  9349. L1EDC:  EX      DE,HL           ; transfer ramtop value to HL.
  9350.         LD      ($5CB2),HL      ; update system variable RAMTOP.
  9351.         POP     DE              ; pop the return address STMT-RET.
  9352.         POP     BC              ; pop the Error Address.
  9353.         LD      (HL),$3E        ; now put the GO SUB end-marker at RAMTOP.
  9354.         DEC     HL              ; leave a location beneath it.
  9355.         LD      SP,HL           ; initialize the machine stack pointer.
  9356.         PUSH    BC              ; push the error address.
  9357.         LD      ($5C3D),SP      ; make ERR_SP point to location.
  9358.         EX      DE,HL           ; put STMT-RET in HL.
  9359.         JP      (HL)            ; and go there directly.
  9360.  
  9361. ; ---------------------
  9362. ; Handle GO SUB command
  9363. ; ---------------------
  9364. ; The GO SUB command diverts BASIC control to a new line number
  9365. ; in a very similar manner to GO TO but
  9366. ; the current line number and current statement + 1
  9367. ; are placed on the GO SUB stack as a RETURN point.
  9368.  
  9369. ;; GO-SUB
  9370. L1EED:  POP     DE              ; drop the address STMT-RET
  9371.         LD      H,(IY+$0D)      ; fetch statement from SUBPPC and
  9372.         INC     H               ; increment it
  9373.         EX      (SP),HL         ; swap - error address to HL,
  9374.                                 ; H (statement) at top of stack,
  9375.                                 ; L (unimportant) beneath.
  9376.         INC     SP              ; adjust to overwrite unimportant byte
  9377.         LD      BC,($5C45)      ; fetch the current line number from PPC
  9378.         PUSH    BC              ; and PUSH onto GO SUB stack.
  9379.                                 ; the empty machine-stack can be rebuilt
  9380.         PUSH    HL              ; push the error address.
  9381.         LD      ($5C3D),SP      ; make system variable ERR_SP point to it.
  9382.         PUSH    DE              ; push the address STMT-RET.
  9383.         CALL    L1E67           ; call routine GO-TO to update the system
  9384.                                 ; variables NEWPPC and NSPPC.
  9385.                                 ; then make an indirect exit to STMT-RET via
  9386.         LD      BC,$0014        ; a 20-byte overhead memory check.
  9387.  
  9388. ; ----------------------
  9389. ; Check available memory
  9390. ; ----------------------
  9391. ; This routine is used on many occasions when extending a dynamic area
  9392. ; upwards or the GO SUB stack downwards.
  9393.  
  9394. ;; TEST-ROOM
  9395. L1F05:  LD      HL,($5C65)      ; fetch STKEND
  9396.         ADD     HL,BC           ; add the supplied test value
  9397.         JR      C,L1F15         ; forward to REPORT-4 if over $FFFF
  9398.  
  9399.         EX      DE,HL           ; was less so transfer to DE
  9400.         LD      HL,$0050        ; test against another 80 bytes
  9401.         ADD     HL,DE           ; anyway
  9402.         JR      C,L1F15         ; forward to REPORT-4 if this passes $FFFF
  9403.  
  9404.         SBC     HL,SP           ; if less than the machine stack pointer
  9405.         RET     C               ; then return - OK.
  9406.  
  9407. ;; REPORT-4
  9408. L1F15:  LD      L,$03           ; prepare 'Out of Memory'
  9409.         JP      L0055           ; jump back to ERROR-3 at $0055
  9410.                                 ; Note. this error can't be trapped at $0008
  9411.  
  9412. ; ------------------------------
  9413. ; THE 'FREE MEMORY' USER ROUTINE
  9414. ; ------------------------------
  9415. ; This routine is not used by the ROM but allows users to evaluate
  9416. ; approximate free memory with PRINT 65536 - USR 7962.
  9417.  
  9418. ;; free-mem
  9419. L1F1A:  LD      BC,$0000        ; allow no overhead.
  9420.  
  9421.         CALL    L1F05           ; routine TEST-ROOM.
  9422.  
  9423.         LD      B,H             ; transfer the result
  9424.         LD      C,L             ; to the BC register.
  9425.         RET                     ; the USR function returns value of BC.
  9426.  
  9427. ; --------------------
  9428. ; THE 'RETURN' COMMAND
  9429. ; --------------------
  9430. ; As with any command, there are two values on the machine stack at the time
  9431. ; it is invoked.  The machine stack is below the GOSUB stack.  Both grow
  9432. ; downwards, the machine stack by two bytes, the GOSUB stack by 3 bytes.
  9433. ; The highest location is a statement byte followed by a two-byte line number.
  9434.  
  9435. ;; RETURN
  9436. L1F23:  POP     BC              ; drop the address STMT-RET.
  9437.         POP     HL              ; now the error address.
  9438.         POP     DE              ; now a possible BASIC return line.
  9439.         LD      A,D             ; the high byte $00 - $27 is
  9440.         CP      $3E             ; compared with the traditional end-marker $3E.
  9441.         JR      Z,L1F36         ; forward to REPORT-7 with a match.
  9442.                                 ; 'RETURN without GOSUB'
  9443.  
  9444. ; It was not the end-marker so a single statement byte remains at the base of
  9445. ; the calculator stack. It can't be popped off.
  9446.  
  9447.         DEC     SP              ; adjust stack pointer to create room for two
  9448.                                 ; bytes.
  9449.         EX      (SP),HL         ; statement to H, error address to base of
  9450.                                 ; new machine stack.
  9451.         EX      DE,HL           ; statement to D,  BASIC line number to HL.
  9452.         LD      ($5C3D),SP      ; adjust ERR_SP to point to new stack pointer
  9453.         PUSH    BC              ; now re-stack the address STMT-RET
  9454.         JP      L1E73           ; to GO-TO-2 to update statement and line
  9455.                                 ; system variables and exit indirectly to the
  9456.                                 ; address just pushed on stack.
  9457.  
  9458. ; ---
  9459.  
  9460. ;; REPORT-7
  9461. L1F36:  PUSH    DE              ; replace the end-marker.
  9462.         PUSH    HL              ; now restore the error address
  9463.                                 ; as will be required in a few clock cycles.
  9464.  
  9465.         RST     08H             ; ERROR-1
  9466.         DB    $06             ; Error Report: RETURN without GOSUB
  9467.  
  9468. ; --------------------
  9469. ; Handle PAUSE command
  9470. ; --------------------
  9471. ; The pause command takes as its parameter the number of interrupts
  9472. ; for which to wait. PAUSE 50 pauses for about a second.
  9473. ; PAUSE 0 pauses indefinitely.
  9474. ; Both forms can be finished by pressing a key.
  9475.  
  9476. ;; PAUSE
  9477. L1F3A:  CALL    L1E99           ; routine FIND-INT2 puts value in BC
  9478.  
  9479. ;; PAUSE-1
  9480. L1F3D:  HALT                    ; wait for interrupt.
  9481.         DEC     BC              ; decrease counter.
  9482.         LD      A,B             ; test if
  9483.         OR      C               ; result is zero.
  9484.         JR      Z,L1F4F         ; forward to PAUSE-END if so.
  9485.  
  9486.         LD      A,B             ; test if
  9487.         AND     C               ; now $FFFF
  9488.         INC     A               ; that is, initially zero.
  9489.         JR      NZ,L1F49        ; skip forward to PAUSE-2 if not.
  9490.  
  9491.         INC     BC              ; restore counter to zero.
  9492.  
  9493. ;; PAUSE-2
  9494. L1F49:  BIT     5,(IY+$01)      ; test FLAGS - has a new key been pressed ?
  9495.         JR      Z,L1F3D         ; back to PAUSE-1 if not.
  9496.  
  9497. ;; PAUSE-END
  9498. L1F4F:  RES     5,(IY+$01)      ; update FLAGS - signal no new key
  9499.         RET                     ; and return.
  9500.  
  9501. ; -------------------
  9502. ; Check for BREAK key
  9503. ; -------------------
  9504. ; This routine is called from COPY-LINE, when interrupts are disabled,
  9505. ; to test if BREAK (SHIFT - SPACE) is being pressed.
  9506. ; It is also called at STMT-RET after every statement.
  9507.  
  9508. ;; BREAK-KEY
  9509. L1F54:  LD      A,$7F           ; Input address: $7FFE
  9510.         IN      A,($FE)         ; read lower right keys
  9511.         RRA                     ; rotate bit 0 - SPACE
  9512.         RET     C               ; return if not reset
  9513.  
  9514.         LD      A,$FE           ; Input address: $FEFE
  9515.         IN      A,($FE)         ; read lower left keys
  9516.         RRA                     ; rotate bit 0 - SHIFT
  9517.         RET                     ; carry will be set if not pressed.
  9518.                                 ; return with no carry if both keys
  9519.                                 ; pressed.
  9520.  
  9521. ; ---------------------
  9522. ; Handle DEF FN command
  9523. ; ---------------------
  9524. ; e.g DEF FN r$(a$,a) = a$(a TO )
  9525. ; this 'command' is ignored in runtime but has its syntax checked
  9526. ; during line-entry.
  9527.  
  9528. ;; DEF-FN
  9529. L1F60:  CALL    L2530           ; routine SYNTAX-Z
  9530.         JR      Z,L1F6A         ; forward to DEF-FN-1 if parsing
  9531.  
  9532.         LD      A,$CE           ; else load A with 'DEF FN' and
  9533.         JP      L1E39           ; jump back to PASS-BY
  9534.  
  9535. ; ---
  9536.  
  9537. ; continue here if checking syntax.
  9538.  
  9539. ;; DEF-FN-1
  9540. L1F6A:  SET      6,(IY+$01)     ; set FLAGS  - Assume numeric result
  9541.         CALL    L2C8D           ; call routine ALPHA
  9542.         JR      NC,L1F89        ; if not then to DEF-FN-4 to jump to
  9543.                                 ; 'Nonsense in BASIC'
  9544.  
  9545.  
  9546.         RST     20H             ; NEXT-CHAR
  9547.         CP      $24             ; is it '$' ?
  9548.         JR      NZ,L1F7D        ; to DEF-FN-2 if not as numeric.
  9549.  
  9550.         RES     6,(IY+$01)      ; set FLAGS  - Signal string result
  9551.  
  9552.         RST     20H             ; get NEXT-CHAR
  9553.  
  9554. ;; DEF-FN-2
  9555. L1F7D:  CP      $28             ; is it '(' ?
  9556.         JR      NZ,L1FBD        ; to DEF-FN-7 'Nonsense in BASIC'
  9557.  
  9558.  
  9559.         RST     20H             ; NEXT-CHAR
  9560.         CP      $29             ; is it ')' ?
  9561.         JR      Z,L1FA6         ; to DEF-FN-6 if null argument
  9562.  
  9563. ;; DEF-FN-3
  9564. L1F86:  CALL    L2C8D           ; routine ALPHA checks that it is the expected
  9565.                                 ; alphabetic character.
  9566.  
  9567. ;; DEF-FN-4
  9568. L1F89:  JP      NC,L1C8A        ; to REPORT-C  if not
  9569.                                 ; 'Nonsense in BASIC'.
  9570.  
  9571.         EX      DE,HL           ; save pointer in DE
  9572.  
  9573.         RST     20H             ; NEXT-CHAR re-initializes HL from CH_ADD
  9574.                                 ; and advances.
  9575.         CP      $24             ; '$' ? is it a string argument.
  9576.         JR      NZ,L1F94        ; forward to DEF-FN-5 if not.
  9577.  
  9578.         EX      DE,HL           ; save pointer to '$' in DE
  9579.  
  9580.         RST     20H             ; NEXT-CHAR re-initializes HL and advances
  9581.  
  9582. ;; DEF-FN-5
  9583. L1F94:  EX      DE,HL           ; bring back pointer.
  9584.         LD      BC,$0006        ; the function requires six hidden bytes for
  9585.                                 ; each parameter passed.
  9586.                                 ; The first byte will be $0E
  9587.                                 ; then 5-byte numeric value
  9588.                                 ; or 5-byte string pointer.
  9589.  
  9590.         CALL    L1655           ; routine MAKE-ROOM creates space in program
  9591.                                 ; area.
  9592.  
  9593.         INC     HL              ; adjust HL (set by LDDR)
  9594.         INC     HL              ; to point to first location.
  9595.         LD      (HL),$0E        ; insert the 'hidden' marker.
  9596.  
  9597. ; Note. these invisible storage locations hold nothing meaningful for the
  9598. ; moment. They will be used every time the corresponding function is
  9599. ; evaluated in runtime.
  9600. ; Now consider the following character fetched earlier.
  9601.  
  9602.         CP      $2C             ; is it ',' ? (more than one parameter)
  9603.         JR      NZ,L1FA6        ; to DEF-FN-6 if not
  9604.  
  9605.  
  9606.         RST     20H             ; else NEXT-CHAR
  9607.         JR      L1F86           ; and back to DEF-FN-3
  9608.  
  9609. ; ---
  9610.  
  9611. ;; DEF-FN-6
  9612. L1FA6:  CP      $29             ; should close with a ')'
  9613.         JR      NZ,L1FBD        ; to DEF-FN-7 if not
  9614.                                 ; 'Nonsense in BASIC'
  9615.  
  9616.  
  9617.         RST     20H             ; get NEXT-CHAR
  9618.         CP      $3D             ; is it '=' ?
  9619.         JR      NZ,L1FBD        ; to DEF-FN-7 if not 'Nonsense...'
  9620.  
  9621.  
  9622.         RST     20H             ; address NEXT-CHAR
  9623.         LD      A,($5C3B)       ; get FLAGS which has been set above
  9624.         PUSH    AF              ; and preserve
  9625.  
  9626.         CALL    L24FB           ; routine SCANNING checks syntax of expression
  9627.                                 ; and also sets flags.
  9628.  
  9629.         POP     AF              ; restore previous flags
  9630.         XOR     (IY+$01)        ; xor with FLAGS - bit 6 should be same
  9631.                                 ; therefore will be reset.
  9632.         AND     $40             ; isolate bit 6.
  9633.  
  9634. ;; DEF-FN-7
  9635. L1FBD:  JP      NZ,L1C8A        ; jump back to REPORT-C if the expected result
  9636.                                 ; is not the same type.
  9637.                                 ; 'Nonsense in BASIC'
  9638.  
  9639.         CALL    L1BEE           ; routine CHECK-END will return early if
  9640.                                 ; at end of statement and move onto next
  9641.                                 ; else produce error report. >>>
  9642.  
  9643.                                 ; There will be no return to here.
  9644.  
  9645. ; -------------------------------
  9646. ; Returning early from subroutine
  9647. ; -------------------------------
  9648. ; All routines are capable of being run in two modes - syntax checking mode
  9649. ; and runtime mode.  This routine is called often to allow a routine to return
  9650. ; early if checking syntax.
  9651.  
  9652. ;; UNSTACK-Z
  9653. L1FC3:  CALL    L2530           ; routine SYNTAX-Z sets zero flag if syntax
  9654.                                 ; is being checked.
  9655.  
  9656.         POP     HL              ; drop the return address.
  9657.         RET      Z              ; return to previous call in chain if checking
  9658.                                 ; syntax.
  9659.  
  9660.         JP      (HL)            ; jump to return address as BASIC program is
  9661.                                 ; actually running.
  9662.  
  9663. ; ---------------------
  9664. ; Handle LPRINT command
  9665. ; ---------------------
  9666. ; A simple form of 'PRINT #3' although it can output to 16 streams.
  9667. ; Probably for compatibility with other BASICs particularly ZX81 BASIC.
  9668. ; An extra UDG might have been better.
  9669.  
  9670. ;; LPRINT
  9671. L1FC9:  LD      A,$03           ; the printer channel
  9672.         JR      L1FCF           ; forward to PRINT-1
  9673.  
  9674. ; ---------------------
  9675. ; Handle PRINT commands
  9676. ; ---------------------
  9677. ; The Spectrum's main stream output command.
  9678. ; The default stream is stream 2 which is normally the upper screen
  9679. ; of the computer. However the stream can be altered in range 0 - 15.
  9680.  
  9681. ;; PRINT
  9682. L1FCD:  LD      A,$02           ; the stream for the upper screen.
  9683.  
  9684. ; The LPRINT command joins here.
  9685.  
  9686. ;; PRINT-1
  9687. L1FCF:  CALL    L2530           ; routine SYNTAX-Z checks if program running
  9688.         CALL    NZ,L1601        ; routine CHAN-OPEN if so
  9689.         CALL    L0D4D           ; routine TEMPS sets temporary colours.
  9690.         CALL    L1FDF           ; routine PRINT-2 - the actual item
  9691.         CALL    L1BEE           ; routine CHECK-END gives error if not at end
  9692.                                 ; of statement
  9693.         RET                     ; and return >>>
  9694.  
  9695. ; ------------------------------------
  9696. ; this subroutine is called from above
  9697. ; and also from INPUT.
  9698.  
  9699. ;; PRINT-2
  9700. L1FDF:  RST     18H             ; GET-CHAR gets printable character
  9701.         CALL    L2045           ; routine PR-END-Z checks if more printing
  9702.         JR      Z,L1FF2         ; to PRINT-4 if not     e.g. just 'PRINT :'
  9703.  
  9704. ; This tight loop deals with combinations of positional controls and
  9705. ; print items. An early return can be made from within the loop
  9706. ; if the end of a print sequence is reached.
  9707.  
  9708. ;; PRINT-3
  9709. L1FE5:  CALL    L204E           ; routine PR-POSN-1 returns zero if more
  9710.                                 ; but returns early at this point if
  9711.                                 ; at end of statement!
  9712.                                 ;
  9713.         JR      Z,L1FE5         ; to PRINT-3 if consecutive positioners
  9714.  
  9715.         CALL    L1FFC           ; routine PR-ITEM-1 deals with strings etc.
  9716.         CALL    L204E           ; routine PR-POSN-1 for more position codes
  9717.         JR      Z,L1FE5         ; loop back to PRINT-3 if so
  9718.  
  9719. ;; PRINT-4
  9720. L1FF2:  CP      $29             ; return now if this is ')' from input-item.
  9721.                                 ; (see INPUT.)
  9722.         RET     Z               ; or continue and print carriage return in
  9723.                                 ; runtime
  9724.  
  9725. ; ---------------------
  9726. ; Print carriage return
  9727. ; ---------------------
  9728. ; This routine which continues from above prints a carriage return
  9729. ; in run-time. It is also called once from PRINT-POSN.
  9730.  
  9731. ;; PRINT-CR
  9732. L1FF5:  CALL    L1FC3           ; routine UNSTACK-Z
  9733.  
  9734.         LD      A,$0D           ; prepare a carriage return
  9735.  
  9736.         RST     10H             ; PRINT-A
  9737.         RET                     ; return
  9738.  
  9739.  
  9740. ; -----------
  9741. ; Print items
  9742. ; -----------
  9743. ; This routine deals with print items as in
  9744. ; PRINT AT 10,0;"The value of A is ";a
  9745. ; It returns once a single item has been dealt with as it is part
  9746. ; of a tight loop that considers sequences of positional and print items
  9747.  
  9748. ;; PR-ITEM-1
  9749. L1FFC:  RST     18H             ; GET-CHAR
  9750.         CP      $AC             ; is character 'AT' ?
  9751.         JR      NZ,L200E        ; forward to PR-ITEM-2 if not.
  9752.  
  9753.         CALL    L1C79           ; routine NEXT-2NUM  check for two comma
  9754.                                 ; separated numbers placing them on the
  9755.                                 ; calculator stack in runtime.
  9756.         CALL    L1FC3           ; routine UNSTACK-Z quits if checking syntax.
  9757.  
  9758.         CALL    L2307           ; routine STK-TO-BC get the numbers in B and C.
  9759.         LD      A,$16           ; prepare the 'at' control.
  9760.         JR      L201E           ; forward to PR-AT-TAB to print the sequence.
  9761.  
  9762. ; ---
  9763.  
  9764. ;; PR-ITEM-2
  9765. L200E:  CP      $AD             ; is character 'TAB' ?
  9766.         JR      NZ,L2024        ; to PR-ITEM-3 if not
  9767.  
  9768.  
  9769.         RST     20H             ; NEXT-CHAR to address next character
  9770.         CALL    L1C82           ; routine EXPT-1NUM
  9771.         CALL    L1FC3           ; routine UNSTACK-Z quits if checking syntax.
  9772.  
  9773.         CALL    L1E99           ; routine FIND-INT2 puts integer in BC.
  9774.         LD      A,$17           ; prepare the 'tab' control.
  9775.  
  9776. ;; PR-AT-TAB
  9777. L201E:  RST     10H             ; PRINT-A outputs the control
  9778.  
  9779.         LD      A,C             ; first value to A
  9780.         RST     10H             ; PRINT-A outputs it.
  9781.  
  9782.         LD      A,B             ; second value
  9783.         RST     10H             ; PRINT-A
  9784.  
  9785.         RET                     ; return - item finished >>>
  9786.  
  9787. ; ---
  9788.  
  9789. ; Now consider paper 2; #2; a$
  9790.  
  9791. ;; PR-ITEM-3
  9792. L2024:  CALL    L21F2           ; routine CO-TEMP-3 will print any colour
  9793.         RET     NC              ; items - return if success.
  9794.  
  9795.         CALL    L2070           ; routine STR-ALTER considers new stream
  9796.         RET     NC              ; return if altered.
  9797.  
  9798.         CALL    L24FB           ; routine SCANNING now to evaluate expression
  9799.         CALL    L1FC3           ; routine UNSTACK-Z if not runtime.
  9800.  
  9801.         BIT     6,(IY+$01)      ; test FLAGS  - Numeric or string result ?
  9802.         CALL    Z,L2BF1         ; routine STK-FETCH if string.
  9803.                                 ; note no flags affected.
  9804.         JP      NZ,L2DE3        ; to PRINT-FP to print if numeric >>>
  9805.  
  9806. ; It was a string expression - start in DE, length in BC
  9807. ; Now enter a loop to print it
  9808.  
  9809. ;; PR-STRING
  9810. L203C:  LD      A,B             ; this tests if the
  9811.         OR      C               ; length is zero and sets flag accordingly.
  9812.         DEC     BC              ; this doesn't but decrements counter.
  9813.         RET     Z               ; return if zero.
  9814.  
  9815.         LD      A,(DE)          ; fetch character.
  9816.         INC     DE              ; address next location.
  9817.  
  9818.         RST     10H             ; PRINT-A.
  9819.  
  9820.         JR      L203C           ; loop back to PR-STRING.
  9821.  
  9822. ; ---------------
  9823. ; End of printing
  9824. ; ---------------
  9825. ; This subroutine returns zero if no further printing is required
  9826. ; in the current statement.
  9827. ; The first terminator is found in  escaped input items only,
  9828. ; the others in print_items.
  9829.  
  9830. ;; PR-END-Z
  9831. L2045:  CP      $29             ; is character a ')' ?
  9832.         RET     Z               ; return if so -        e.g. INPUT (p$); a$
  9833.  
  9834. ;; PR-ST-END
  9835. L2048:  CP      $0D             ; is it a carriage return ?
  9836.         RET     Z               ; return also -         e.g. PRINT a
  9837.  
  9838.         CP      $3A             ; is character a ':' ?
  9839.         RET                     ; return - zero flag will be set if so.
  9840.                                 ;                       e.g. PRINT a :
  9841.  
  9842. ; --------------
  9843. ; Print position
  9844. ; --------------
  9845. ; This routine considers a single positional character ';', ',', '''
  9846.  
  9847. ;; PR-POSN-1
  9848. L204E:  RST     18H             ; GET-CHAR
  9849.         CP      $3B             ; is it ';' ?            
  9850.                                 ; i.e. print from last position.
  9851.         JR      Z,L2067         ; forward to PR-POSN-3 if so.
  9852.                                 ; i.e. do nothing.
  9853.  
  9854.         CP      $2C             ; is it ',' ?
  9855.                                 ; i.e. print at next tabstop.
  9856.         JR      NZ,L2061        ; forward to PR-POSN-2 if anything else.
  9857.  
  9858.         CALL    L2530           ; routine SYNTAX-Z
  9859.         JR      Z,L2067         ; forward to PR-POSN-3 if checking syntax.
  9860.  
  9861.         LD      A,$06           ; prepare the 'comma' control character.
  9862.  
  9863.         RST     10H             ; PRINT-A  outputs to current channel in
  9864.                                 ; run-time.
  9865.  
  9866.         JR      L2067           ; skip to PR-POSN-3.
  9867.  
  9868. ; ---
  9869.  
  9870. ; check for newline.
  9871.  
  9872. ;; PR-POSN-2
  9873. L2061:  CP      $27             ; is character a "'" ? (newline)
  9874.         RET     NZ              ; return if no match              >>>
  9875.  
  9876.         CALL    L1FF5           ; routine PRINT-CR outputs a carriage return
  9877.                                 ; in runtime only.
  9878.  
  9879. ;; PR-POSN-3
  9880. L2067:  RST     20H             ; NEXT-CHAR to A.
  9881.         CALL    L2045           ; routine PR-END-Z checks if at end.
  9882.         JR      NZ,L206E        ; to PR-POSN-4 if not.
  9883.  
  9884.         POP     BC              ; drop return address if at end.
  9885.  
  9886. ;; PR-POSN-4
  9887. L206E:  CP      A               ; reset the zero flag.
  9888.         RET                     ; and return to loop or quit.
  9889.  
  9890. ; ------------
  9891. ; Alter stream
  9892. ; ------------
  9893. ; This routine is called from PRINT ITEMS above, and also LIST as in
  9894. ; LIST #15
  9895.  
  9896. ;; STR-ALTER
  9897. L2070:  CP      $23             ; is character '#' ?
  9898.         SCF                     ; set carry flag.
  9899.         RET     NZ              ; return if no match.
  9900.  
  9901.  
  9902.         RST      20H            ; NEXT-CHAR
  9903.         CALL    L1C82           ; routine EXPT-1NUM gets stream number
  9904.         AND     A               ; prepare to exit early with carry reset
  9905.         CALL    L1FC3           ; routine UNSTACK-Z exits early if parsing
  9906.         CALL    L1E94           ; routine FIND-INT1 gets number off stack
  9907.         CP      $10             ; must be range 0 - 15 decimal.
  9908.         JP      NC,L160E        ; jump back to REPORT-Oa if not
  9909.                                 ; 'Invalid stream'.
  9910.  
  9911.         CALL    L1601           ; routine CHAN-OPEN
  9912.         AND     A               ; clear carry - signal item dealt with.
  9913.         RET                     ; return
  9914.  
  9915. ; --------------------
  9916. ; Handle INPUT command
  9917. ; --------------------
  9918. ; This command
  9919. ;
  9920.  
  9921. ;; INPUT
  9922. L2089:  CALL    L2530           ; routine SYNTAX-Z to check if in runtime.
  9923.         JR      Z,L2096         ; forward to INPUT-1 if checking syntax.
  9924.  
  9925.         LD      A,$01           ; select channel 'K' the keyboard for input.
  9926.         CALL    L1601           ; routine CHAN-OPEN opens it.
  9927.         CALL    L0D6E           ; routine CLS-LOWER clears the lower screen
  9928.                                 ; and sets DF_SZ to two.
  9929.  
  9930. ;; INPUT-1
  9931. L2096:  LD      (IY+$02),$01    ; update TV_FLAG - signal lower screen in use
  9932.                                 ; ensuring that the correct set of system
  9933.                                 ; variables are updated and that the border
  9934.                                 ; colour is used.
  9935.  
  9936.         CALL    L20C1           ; routine IN-ITEM-1 to handle the input.
  9937.  
  9938.         CALL    L1BEE           ; routine CHECK-END will make an early exit
  9939.                                 ; if checking syntax. >>>
  9940.  
  9941. ; keyboard input has been made and it remains to adjust the upper
  9942. ; screen in case the lower two lines have been extended upwards.
  9943.  
  9944.         LD      BC,($5C88)      ; fetch S_POSN current line/column of
  9945.                                 ; the upper screen.
  9946.         LD      A,($5C6B)       ; fetch DF_SZ the display file size of
  9947.                                 ; the lower screen.
  9948.         CP      B               ; test that lower screen does not overlap
  9949.         JR      C,L20AD         ; forward to INPUT-2 if not.
  9950.  
  9951. ; the two screens overlap so adjust upper screen.
  9952.  
  9953.         LD      C,$21           ; set column of upper screen to leftmost.
  9954.         LD      B,A             ; and line to one above lower screen.
  9955.                                 ; continue forward to update upper screen
  9956.                                 ; print position.
  9957.  
  9958. ;; INPUT-2
  9959. L20AD:  LD      ($5C88),BC      ; set S_POSN update upper screen line/column.
  9960.         LD      A,$19           ; subtract from twenty five
  9961.         SUB     B               ; the new line number.
  9962.         LD      ($5C8C),A       ; and place result in SCR_CT - scroll count.
  9963.         RES     0,(IY+$02)      ; update TV_FLAG - signal main screen in use.
  9964.         CALL    L0DD9           ; routine CL-SET sets the print position
  9965.                                 ; system variables for the upper screen.
  9966.         JP      L0D6E           ; jump back to CLS-LOWER and make
  9967.                                 ; an indirect exit >>.
  9968.  
  9969. ; ---------------------
  9970. ; INPUT ITEM subroutine
  9971. ; ---------------------
  9972. ; This subroutine deals with the input items and print items.
  9973. ; from  the current input channel.
  9974. ; It is only called from the above INPUT routine but was obviously
  9975. ; once called from somewhere else in another context.
  9976.  
  9977. ;; IN-ITEM-1
  9978. L20C1:  CALL    L204E           ; routine PR-POSN-1 deals with a single
  9979.                                 ; position item at each call.
  9980.         JR      Z,L20C1         ; back to IN-ITEM-1 until no more in a
  9981.                                 ; sequence.
  9982.  
  9983.         CP      $28             ; is character '(' ?
  9984.         JR      NZ,L20D8        ; forward to IN-ITEM-2 if not.
  9985.  
  9986. ; any variables within braces will be treated as part, or all, of the prompt
  9987. ; instead of being used as destination variables.
  9988.  
  9989.         RST     20H             ; NEXT-CHAR
  9990.         CALL    L1FDF           ; routine PRINT-2 to output the dynamic
  9991.                                 ; prompt.
  9992.  
  9993.         RST     18H             ; GET-CHAR
  9994.         CP      $29             ; is character a matching ')' ?
  9995.         JP      NZ,L1C8A        ; jump back to REPORT-C if not.
  9996.                                 ; 'Nonsense in BASIC'.
  9997.  
  9998.         RST     20H             ; NEXT-CHAR
  9999.         JP      L21B2           ; forward to IN-NEXT-2
  10000.  
  10001. ; ---
  10002.  
  10003. ;; IN-ITEM-2
  10004. L20D8:  CP      $CA             ; is the character the token 'LINE' ?
  10005.         JR      NZ,L20ED        ; forward to IN-ITEM-3 if not.
  10006.  
  10007.         RST     20H             ; NEXT-CHAR - variable must come next.
  10008.         CALL    L1C1F           ; routine CLASS-01 returns destination
  10009.                                 ; address of variable to be assigned.
  10010.                                 ; or generates an error if no variable
  10011.                                 ; at this position.
  10012.  
  10013.         SET     7,(IY+$37)      ; update FLAGX  - signal handling INPUT LINE
  10014.         BIT     6,(IY+$01)      ; test FLAGS  - numeric or string result ?
  10015.         JP      NZ,L1C8A        ; jump back to REPORT-C if not string
  10016.                                 ; 'Nonsense in BASIC'.
  10017.  
  10018.         JR      L20FA           ; forward to IN-PROMPT to set up workspace.
  10019.  
  10020. ; ---
  10021.  
  10022. ; the jump was here for other variables.
  10023.  
  10024. ;; IN-ITEM-3
  10025. L20ED:  CALL     L2C8D          ; routine ALPHA checks if character is
  10026.                                 ; a suitable variable name.
  10027.         JP      NC,L21AF        ; forward to IN-NEXT-1 if not
  10028.  
  10029.         CALL    L1C1F           ; routine CLASS-01 returns destination
  10030.                                 ; address of variable to be assigned.
  10031.         RES     7,(IY+$37)      ; update FLAGX  - signal not INPUT LINE.
  10032.  
  10033. ;; IN-PROMPT
  10034. L20FA:  CALL    L2530           ; routine SYNTAX-Z
  10035.         JP      Z,L21B2         ; forward to IN-NEXT-2 if checking syntax.
  10036.  
  10037.         CALL    L16BF           ; routine SET-WORK clears workspace.
  10038.         LD      HL,$5C71        ; point to system variable FLAGX
  10039.         RES     6,(HL)          ; signal string result.
  10040.         SET     5,(HL)          ; signal in Input Mode for editor.
  10041.         LD      BC,$0001        ; initialize space required to one for
  10042.                                 ; the carriage return.
  10043.         BIT     7,(HL)          ; test FLAGX - INPUT LINE in use ?
  10044.         JR      NZ,L211C        ; forward to IN-PR-2 if so as that is
  10045.                                 ; all the space that is required.
  10046.  
  10047.         LD      A,($5C3B)       ; load accumulator from FLAGS
  10048.         AND     $40             ; mask to test BIT 6 of FLAGS and clear
  10049.                                 ; the other bits in A.
  10050.                                 ; numeric result expected ?
  10051.         JR      NZ,L211A        ; forward to IN-PR-1 if so
  10052.  
  10053.         LD      C,$03           ; increase space to three bytes for the
  10054.                                 ; pair of surrounding quotes.
  10055.  
  10056. ;; IN-PR-1
  10057. L211A:  OR      (HL)            ; if numeric result, set bit 6 of FLAGX.
  10058.         LD      (HL),A          ; and update system variable
  10059.  
  10060. ;; IN-PR-2
  10061. L211C:  RST     30H             ; BC-SPACES opens 1 or 3 bytes in workspace
  10062.         LD      (HL),$0D        ; insert carriage return at last new location.
  10063.         LD      A,C             ; fetch the length, one or three.
  10064.         RRCA                    ; lose bit 0.
  10065.         RRCA                    ; test if quotes required.
  10066.         JR      NC,L2129        ; forward to IN-PR-3 if not.
  10067.  
  10068.         LD      A,$22           ; load the '"' character
  10069.         LD      (DE),A          ; place quote in first new location at DE.
  10070.         DEC     HL              ; decrease HL - from carriage return.
  10071.         LD      (HL),A          ; and place a quote in second location.
  10072.  
  10073. ;; IN-PR-3
  10074. L2129:  LD      ($5C5B),HL      ; set keyboard cursor K_CUR to HL
  10075.         BIT     7,(IY+$37)      ; test FLAGX  - is this INPUT LINE ??
  10076.         JR      NZ,L215E        ; forward to IN-VAR-3 if so as input will
  10077.                                 ; be accepted without checking its syntax.
  10078.  
  10079.         LD      HL,($5C5D)      ; fetch CH_ADD
  10080.         PUSH    HL              ; and save on stack.
  10081.         LD      HL,($5C3D)      ; fetch ERR_SP
  10082.         PUSH    HL              ; and save on stack
  10083.  
  10084. ;; IN-VAR-1
  10085. L213A:  LD      HL,L213A        ; address: IN-VAR-1 - this address
  10086.         PUSH    HL              ; is saved on stack to handle errors.
  10087.         BIT     4,(IY+$30)      ; test FLAGS2  - is K channel in use ?
  10088.         JR      Z,L2148         ; forward to IN-VAR-2 if not using the
  10089.                                 ; keyboard for input. (??)
  10090.  
  10091.         LD      ($5C3D),SP      ; set ERR_SP to point to IN-VAR-1 on stack.
  10092.  
  10093. ;; IN-VAR-2
  10094. L2148:  LD      HL,($5C61)      ; set HL to WORKSP - start of workspace.
  10095.         CALL    L11A7           ; routine REMOVE-FP removes floating point
  10096.                                 ; forms when looping in error condition.
  10097.         LD      (IY+$00),$FF    ; set ERR_NR to 'OK' cancelling the error.
  10098.                                 ; but X_PTR causes flashing error marker
  10099.                                 ; to be displayed at each call to the editor.
  10100.         CALL    L0F2C           ; routine EDITOR allows input to be entered
  10101.                                 ; or corrected if this is second time around.
  10102.  
  10103. ; if we pass to next then there are no system errors
  10104.  
  10105.         RES     7,(IY+$01)      ; update FLAGS  - signal checking syntax
  10106.         CALL    L21B9           ; routine IN-ASSIGN checks syntax using
  10107.                                 ; the VAL-FET-2 and powerful SCANNING routines.
  10108.                                 ; any syntax error and its back to IN-VAR-1.
  10109.                                 ; but with the flashing error marker showing
  10110.                                 ; where the error is.
  10111.                                 ; Note. the syntax of string input has to be
  10112.                                 ; checked as the user may have removed the
  10113.                                 ; bounding quotes or escaped them as with
  10114.                                 ; "hat" + "stand" for example.
  10115. ; proceed if syntax passed.
  10116.  
  10117.         JR      L2161           ; jump forward to IN-VAR-4
  10118.  
  10119. ; ---
  10120.  
  10121. ; the jump was to here when using INPUT LINE.
  10122.  
  10123. ;; IN-VAR-3
  10124. L215E:  CALL    L0F2C           ; routine EDITOR is called for input
  10125.  
  10126. ; when ENTER received rejoin other route but with no syntax check.
  10127.  
  10128. ; INPUT and INPUT LINE converge here.
  10129.  
  10130. ;; IN-VAR-4
  10131. L2161:  LD      (IY+$22),$00    ; set K_CUR_hi to a low value so that the cursor
  10132.                                 ; no longer appears in the input line.
  10133.  
  10134.         CALL    L21D6           ; routine IN-CHAN-K tests if the keyboard
  10135.                                 ; is being used for input.
  10136.         JR      NZ,L2174        ; forward to IN-VAR-5 if using another input
  10137.                                 ; channel.
  10138.  
  10139. ; continue here if using the keyboard.
  10140.  
  10141.         CALL    L111D           ; routine ED-COPY overprints the edit line
  10142.                                 ; to the lower screen. The only visible
  10143.                                 ; affect is that the cursor disappears.
  10144.                                 ; if you're inputting more than one item in
  10145.                                 ; a statement then that becomes apparent.
  10146.  
  10147.         LD      BC,($5C82)      ; fetch line and column from ECHO_E
  10148.         CALL    L0DD9           ; routine CL-SET sets S-POSNL to those
  10149.                                 ; values.
  10150.  
  10151. ; if using another input channel rejoin here.
  10152.  
  10153. ;; IN-VAR-5
  10154. L2174:  LD      HL,$5C71        ; point HL to FLAGX
  10155.         RES     5,(HL)          ; signal not in input mode
  10156.         BIT     7,(HL)          ; is this INPUT LINE ?
  10157.         RES     7,(HL)          ; cancel the bit anyway.
  10158.         JR      NZ,L219B        ; forward to IN-VAR-6 if INPUT LINE.
  10159.  
  10160.         POP     HL              ; drop the looping address
  10161.         POP     HL              ; drop the the address of previous
  10162.                                 ; error handler.
  10163.         LD      ($5C3D),HL      ; set ERR_SP to point to it.
  10164.         POP     HL              ; drop original CH_ADD which points to
  10165.                                 ; INPUT command in BASIC line.
  10166.         LD      ($5C5F),HL      ; save in X_PTR while input is assigned.
  10167.         SET     7,(IY+$01)      ; update FLAGS - Signal running program
  10168.         CALL    L21B9           ; routine IN-ASSIGN is called again
  10169.                                 ; this time the variable will be assigned
  10170.                                 ; the input value without error.
  10171.                                 ; Note. the previous example now
  10172.                                 ; becomes "hatstand"
  10173.  
  10174.         LD      HL,($5C5F)      ; fetch stored CH_ADD value from X_PTR.
  10175.         LD      (IY+$26),$00    ; set X_PTR_hi so that iy is no longer relevant.
  10176.         LD      ($5C5D),HL      ; put restored value back in CH_ADD
  10177.         JR      L21B2           ; forward to IN-NEXT-2 to see if anything
  10178.                                 ; more in the INPUT list.
  10179.  
  10180. ; ---
  10181.  
  10182. ; the jump was to here with INPUT LINE only
  10183.  
  10184. ;; IN-VAR-6
  10185. L219B:  LD      HL,($5C63)      ; STKBOT points to the end of the input.
  10186.         LD      DE,($5C61)      ; WORKSP points to the beginning.
  10187.         SCF                     ; prepare for true subtraction.
  10188.         SBC     HL,DE           ; subtract to get length
  10189.         LD      B,H             ; transfer it to
  10190.         LD      C,L             ; the BC register pair.
  10191.         CALL    L2AB2           ; routine STK-STO-$ stores parameters on
  10192.                                 ; the calculator stack.
  10193.         CALL    L2AFF           ; routine LET assigns it to destination.
  10194.         JR      L21B2           ; forward to IN-NEXT-2 as print items
  10195.                                 ; not allowed with INPUT LINE.
  10196.                                 ; Note. that "hat" + "stand" will, for
  10197.                                 ; example, be unchanged as also would
  10198.                                 ; 'PRINT "Iris was here"'.
  10199.  
  10200. ; ---
  10201.  
  10202. ; the jump was to here when ALPHA found more items while looking for
  10203. ; a variable name.
  10204.  
  10205. ;; IN-NEXT-1
  10206. L21AF:  CALL    L1FFC           ; routine PR-ITEM-1 considers further items.
  10207.  
  10208. ;; IN-NEXT-2
  10209. L21B2:  CALL    L204E           ; routine PR-POSN-1 handles a position item.
  10210.         JP      Z,L20C1         ; jump back to IN-ITEM-1 if the zero flag
  10211.                                 ; indicates more items are present.
  10212.  
  10213.         RET                     ; return.
  10214.  
  10215. ; ---------------------------
  10216. ; INPUT ASSIGNMENT Subroutine
  10217. ; ---------------------------
  10218. ; This subroutine is called twice from the INPUT command when normal
  10219. ; keyboard input is assigned. On the first occasion syntax is checked
  10220. ; using SCANNING. The final call with the syntax flag reset is to make
  10221. ; the assignment.
  10222.  
  10223. ;; IN-ASSIGN
  10224. L21B9:  LD      HL,($5C61)      ; fetch WORKSP start of input
  10225.         LD      ($5C5D),HL      ; set CH_ADD to first character
  10226.  
  10227.         RST     18H             ; GET-CHAR ignoring leading white-space.
  10228.         CP      $E2             ; is it 'STOP'
  10229.         JR      Z,L21D0         ; forward to IN-STOP if so.
  10230.  
  10231.         LD      A,($5C71)       ; load accumulator from FLAGX
  10232.         CALL    L1C59           ; routine VAL-FET-2 makes assignment
  10233.                                 ; or goes through the motions if checking
  10234.                                 ; syntax. SCANNING is used.
  10235.  
  10236.         RST     18H             ; GET-CHAR
  10237.         CP      $0D             ; is it carriage return ?
  10238.         RET     Z               ; return if so
  10239.                                 ; either syntax is OK
  10240.                                 ; or assignment has been made.
  10241.  
  10242. ; if another character was found then raise an error.
  10243. ; User doesn't see report but the flashing error marker
  10244. ; appears in the lower screen.
  10245.  
  10246. ;; REPORT-Cb
  10247. L21CE:  RST     08H             ; ERROR-1
  10248.         DB    $0B             ; Error Report: Nonsense in BASIC
  10249.  
  10250. ;; IN-STOP
  10251. L21D0:  CALL    L2530           ; routine SYNTAX-Z (UNSTACK-Z?)
  10252.         RET     Z               ; return if checking syntax
  10253.                                 ; as user wouldn't see error report.
  10254.                                 ; but generate visible error report
  10255.                                 ; on second invocation.
  10256.  
  10257. ;; REPORT-H
  10258. L21D4:  RST     08H             ; ERROR-1
  10259.         DB    $10             ; Error Report: STOP in INPUT
  10260.  
  10261. ; ------------------
  10262. ; Test for channel K
  10263. ; ------------------
  10264. ; This subroutine is called once from the keyboard
  10265. ; INPUT command to check if the input routine in
  10266. ; use is the one for the keyboard.
  10267.  
  10268. ;; IN-CHAN-K
  10269. L21D6:  LD      HL,($5C51)      ; fetch address of current channel CURCHL
  10270.         INC     HL              ;
  10271.         INC     HL              ; advance past
  10272.         INC     HL              ; input and
  10273.         INC     HL              ; output streams
  10274.         LD      A,(HL)          ; fetch the channel identifier.
  10275.         CP      $4B             ; test for 'K'
  10276.         RET                     ; return with zero set if keyboard is use.
  10277.  
  10278. ; --------------------
  10279. ; Colour Item Routines
  10280. ; --------------------
  10281. ;
  10282. ; These routines have 3 entry points -
  10283. ; 1) CO-TEMP-2 to handle a series of embedded Graphic colour items.
  10284. ; 2) CO-TEMP-3 to handle a single embedded print colour item.
  10285. ; 3) CO TEMP-4 to handle a colour command such as FLASH 1
  10286. ;
  10287. ; "Due to a bug, if you bring in a peripheral channel and later use a colour
  10288. ;  statement, colour controls will be sent to it by mistake." - Steven Vickers
  10289. ;  Pitman Pocket Guide, 1984.
  10290. ;
  10291. ; To be fair, this only applies if the last channel was other than 'K', 'S'
  10292. ; or 'P', which are all that are supported by this ROM, but if that last
  10293. ; channel was a microdrive file, network channel etc. then
  10294. ; PAPER 6; CLS will not turn the screen yellow and
  10295. ; CIRCLE INK 2; 128,88,50 will not draw a red circle.
  10296. ;
  10297. ; This bug does not apply to embedded PRINT items as it is quite permissible
  10298. ; to mix stream altering commands and colour items.
  10299. ; The fix therefore would be to ensure that CLASS-07 and CLASS-09 make
  10300. ; channel 'S' the current channel when not checking syntax.
  10301. ; -----------------------------------------------------------------
  10302.  
  10303. ;; CO-TEMP-1
  10304. L21E1:  RST     20H             ; NEXT-CHAR
  10305.  
  10306. ; -> Entry point from CLASS-09. Embedded Graphic colour items.
  10307. ; e.g. PLOT INK 2; PAPER 8; 128,88
  10308. ; Loops till all colour items output, finally addressing the coordinates.
  10309.  
  10310. ;; CO-TEMP-2
  10311. L21E2:  CALL    L21F2           ; routine CO-TEMP-3 to output colour control.
  10312.         RET     C               ; return if nothing more to output. ->
  10313.  
  10314.  
  10315.         RST     18H             ; GET-CHAR
  10316.         CP      $2C             ; is it ',' separator ?
  10317.         JR      Z,L21E1         ; back if so to CO-TEMP-1
  10318.  
  10319.         CP      $3B             ; is it ';' separator ?
  10320.         JR      Z,L21E1         ; back to CO-TEMP-1 for more.
  10321.  
  10322.         JP      L1C8A           ; to REPORT-C (REPORT-Cb is within range)
  10323.                                 ; 'Nonsense in BASIC'
  10324.  
  10325. ; -------------------
  10326. ; CO-TEMP-3
  10327. ; -------------------
  10328. ; -> this routine evaluates and outputs a colour control and parameter.
  10329. ; It is called from above and also from PR-ITEM-3 to handle a single embedded
  10330. ; print item e.g. PRINT PAPER 6; "Hi". In the latter case, the looping for
  10331. ; multiple items is within the PR-ITEM routine.
  10332. ; It is quite permissible to send these to any stream.
  10333.  
  10334. ;; CO-TEMP-3
  10335. L21F2:  CP      $D9             ; is it 'INK' ?
  10336.         RET     C               ; return if less.
  10337.  
  10338.         CP      $DF             ; compare with 'OUT'
  10339.         CCF                     ; Complement Carry Flag
  10340.         RET     C               ; return if greater than 'OVER', $DE.
  10341.  
  10342.         PUSH    AF              ; save the colour token.
  10343.  
  10344.         RST     20H             ; address NEXT-CHAR
  10345.         POP     AF              ; restore token and continue.
  10346.  
  10347. ; -> this entry point used by CLASS-07. e.g. the command PAPER 6.
  10348.  
  10349. ;; CO-TEMP-4
  10350. L21FC:  SUB     $C9             ; reduce to control character $10 (INK)
  10351.                                 ; thru $15 (OVER).
  10352.         PUSH    AF              ; save control.
  10353.         CALL    L1C82           ; routine EXPT-1NUM stacks addressed
  10354.                                 ; parameter on calculator stack.
  10355.         POP     AF              ; restore control.
  10356.         AND     A               ; clear carry
  10357.  
  10358.         CALL    L1FC3           ; routine UNSTACK-Z returns if checking syntax.
  10359.  
  10360.         PUSH    AF              ; save again
  10361.         CALL    L1E94           ; routine FIND-INT1 fetches parameter to A.
  10362.         LD      D,A             ; transfer now to D
  10363.         POP     AF              ; restore control.
  10364.  
  10365.         RST     10H             ; PRINT-A outputs the control to current
  10366.                                 ; channel.
  10367.         LD      A,D             ; transfer parameter to A.
  10368.  
  10369.         RST     10H             ; PRINT-A outputs parameter.
  10370.         RET                     ; return. ->
  10371.  
  10372. ; -------------------------------------------------------------------------
  10373. ;
  10374. ;         {fl}{br}{   paper   }{  ink    }    The temporary colour attributes
  10375. ;          ___ ___ ___ ___ ___ ___ ___ ___    system variable.
  10376. ; ATTR_T  |   |   |   |   |   |   |   |   |
  10377. ;         |   |   |   |   |   |   |   |   |
  10378. ; 23695   |___|___|___|___|___|___|___|___|
  10379. ;           7   6   5   4   3   2   1   0
  10380. ;
  10381. ;
  10382. ;         {fl}{br}{   paper   }{  ink    }    The temporary mask used for
  10383. ;          ___ ___ ___ ___ ___ ___ ___ ___    transparent colours. Any bit
  10384. ; MASK_T  |   |   |   |   |   |   |   |   |   that is 1 shows that the
  10385. ;         |   |   |   |   |   |   |   |   |   corresponding attribute is
  10386. ; 23696   |___|___|___|___|___|___|___|___|   taken not from ATTR-T but from
  10387. ;           7   6   5   4   3   2   1   0     what is already on the screen.
  10388. ;
  10389. ;
  10390. ;         {paper9 }{ ink9 }{ inv1 }{ over1}   The print flags. Even bits are
  10391. ;          ___ ___ ___ ___ ___ ___ ___ ___    temporary flags. The odd bits
  10392. ; P_FLAG  |   |   |   |   |   |   |   |   |   are the permanent flags.
  10393. ;         | p | t | p | t | p | t | p | t |
  10394. ; 23697   |___|___|___|___|___|___|___|___|
  10395. ;           7   6   5   4   3   2   1   0
  10396. ;
  10397. ; -----------------------------------------------------------------------
  10398.  
  10399. ; ------------------------------------
  10400. ;  The colour system variable handler.
  10401. ; ------------------------------------
  10402. ; This is an exit branch from PO-1-OPER, PO-2-OPER
  10403. ; A holds control $10 (INK) to $15 (OVER)
  10404. ; D holds parameter 0-9 for ink/paper 0,1 or 8 for bright/flash,
  10405. ; 0 or 1 for over/inverse.
  10406.  
  10407. ;; CO-TEMP-5
  10408. L2211:  SUB     $11             ; reduce range $FF-$04
  10409.         ADC     A,$00           ; add in carry if INK
  10410.         JR      Z,L2234         ; forward to CO-TEMP-7 with INK and PAPER.
  10411.  
  10412.         SUB     $02             ; reduce range $FF-$02
  10413.         ADC     A,$00           ; add carry if FLASH
  10414.         JR      Z,L2273         ; forward to CO-TEMP-C with FLASH and BRIGHT.
  10415.  
  10416.         CP      $01             ; is it 'INVERSE' ?
  10417.         LD      A,D             ; fetch parameter for INVERSE/OVER
  10418.         LD      B,$01           ; prepare OVER mask setting bit 0.
  10419.         JR      NZ,L2228        ; forward to CO-TEMP-6 if OVER
  10420.  
  10421.         RLCA                    ; shift bit 0
  10422.         RLCA                    ; to bit 2
  10423.         LD      B,$04           ; set bit 2 of mask for inverse.
  10424.  
  10425. ;; CO-TEMP-6
  10426. L2228:  LD      C,A             ; save the A
  10427.         LD      A,D             ; re-fetch parameter
  10428.         CP      $02             ; is it less than 2
  10429.         JR      NC,L2244        ; to REPORT-K if not 0 or 1.
  10430.                                 ; 'Invalid colour'.
  10431.  
  10432.         LD      A,C             ; restore A
  10433.         LD      HL,$5C91        ; address system variable P_FLAG
  10434.         JR      L226C           ; forward to exit via routine CO-CHANGE
  10435.  
  10436. ; ---
  10437.  
  10438. ; the branch was here with INK/PAPER and carry set for INK.
  10439.  
  10440. ;; CO-TEMP-7
  10441. L2234:  LD      A,D             ; fetch parameter
  10442.         LD      B,$07           ; set ink mask 00000111
  10443.         JR      C,L223E         ; forward to CO-TEMP-8 with INK
  10444.  
  10445.         RLCA                    ; shift bits 0-2
  10446.         RLCA                    ; to
  10447.         RLCA                    ; bits 3-5
  10448.         LD      B,$38           ; set paper mask 00111000
  10449.  
  10450. ; both paper and ink rejoin here
  10451.  
  10452. ;; CO-TEMP-8
  10453. L223E:  LD      C,A             ; value to C
  10454.         LD      A,D             ; fetch parameter
  10455.         CP      $0A             ; is it less than 10d ?
  10456.         JR      C,L2246         ; forward to CO-TEMP-9 if so.
  10457.  
  10458. ; ink 10 etc. is not allowed.
  10459.  
  10460. ;; REPORT-K
  10461. L2244:  RST     08H             ; ERROR-1
  10462.         DB    $13             ; Error Report: Invalid colour
  10463.  
  10464. ;; CO-TEMP-9
  10465. L2246:  LD      HL,$5C8F        ; address system variable ATTR_T initially.
  10466.         CP      $08             ; compare with 8
  10467.         JR      C,L2258         ; forward to CO-TEMP-B with 0-7.
  10468.  
  10469.         LD      A,(HL)          ; fetch temporary attribute as no change.
  10470.         JR      Z,L2257         ; forward to CO-TEMP-A with INK/PAPER 8
  10471.  
  10472. ; it is either ink 9 or paper 9 (contrasting)
  10473.  
  10474.         OR      B               ; or with mask to make white
  10475.         CPL                     ; make black and change other to dark
  10476.         AND     $24             ; 00100100
  10477.         JR      Z,L2257         ; forward to CO-TEMP-A if black and
  10478.                                 ; originally light.
  10479.  
  10480.         LD      A,B             ; else just use the mask (white)
  10481.  
  10482. ;; CO-TEMP-A
  10483. L2257:  LD      C,A             ; save A in C
  10484.  
  10485. ;; CO-TEMP-B
  10486. L2258:  LD      A,C             ; load colour to A
  10487.         CALL    L226C           ; routine CO-CHANGE addressing ATTR-T
  10488.  
  10489.         LD      A,$07           ; put 7 in accumulator
  10490.         CP      D               ; compare with parameter
  10491.         SBC     A,A             ; $00 if 0-7, $FF if 8
  10492.         CALL    L226C           ; routine CO-CHANGE addressing MASK-T
  10493.                                 ; mask returned in A.
  10494.  
  10495. ; now consider P-FLAG.
  10496.  
  10497.         RLCA                    ; 01110000 or 00001110
  10498.         RLCA                    ; 11100000 or 00011100
  10499.         AND     $50             ; 01000000 or 00010000  (AND 01010000)
  10500.         LD      B,A             ; transfer to mask
  10501.         LD      A,$08           ; load A with 8
  10502.         CP      D               ; compare with parameter
  10503.         SBC     A,A             ; $FF if was 9,  $00 if 0-8
  10504.                                 ; continue while addressing P-FLAG
  10505.                                 ; setting bit 4 if ink 9
  10506.                                 ; setting bit 6 if paper 9
  10507.  
  10508. ; -----------------------
  10509. ; Handle change of colour
  10510. ; -----------------------
  10511. ; This routine addresses a system variable ATTR_T, MASK_T or P-FLAG in HL.
  10512. ; colour value in A, mask in B.
  10513.  
  10514. ;; CO-CHANGE
  10515. L226C:  XOR     (HL)            ; impress bits specified
  10516.         AND     B               ; by mask
  10517.         XOR     (HL)            ; on system variable.
  10518.         LD      (HL),A          ; update system variable.
  10519.         INC     HL              ; address next location.
  10520.         LD      A,B             ; put current value of mask in A
  10521.         RET                     ; return.
  10522.  
  10523. ; ---
  10524.  
  10525. ; the branch was here with flash and bright
  10526.  
  10527. ;; CO-TEMP-C
  10528. L2273:  SBC     A,A             ; set zero flag for bright.
  10529.         LD      A,D             ; fetch original parameter 0,1 or 8
  10530.         RRCA                    ; rotate bit 0 to bit 7
  10531.         LD      B,$80           ; mask for flash 10000000
  10532.         JR      NZ,L227D        ; forward to CO-TEMP-D if flash
  10533.  
  10534.         RRCA                    ; rotate bit 7 to bit 6
  10535.         LD      B,$40           ; mask for bright 01000000
  10536.  
  10537. ;; CO-TEMP-D
  10538. L227D:  LD      C,A             ; store value in C
  10539.         LD      A,D             ; fetch parameter
  10540.         CP      $08             ; compare with 8
  10541.         JR      Z,L2287         ; forward to CO-TEMP-E if 8
  10542.  
  10543.         CP      $02             ; test if 0 or 1
  10544.         JR      NC,L2244        ; back to REPORT-K if not
  10545.                                 ; 'Invalid colour'
  10546.  
  10547. ;; CO-TEMP-E
  10548. L2287:  LD      A,C             ; value to A
  10549.         LD      HL,$5C8F        ; address ATTR_T
  10550.         CALL    L226C           ; routine CO-CHANGE addressing ATTR_T
  10551.         LD      A,C             ; fetch value
  10552.         RRCA                    ; for flash8/bright8 complete
  10553.         RRCA                    ; rotations to put set bit in
  10554.         RRCA                    ; bit 7 (flash) bit 6 (bright)
  10555.         JR      L226C           ; back to CO-CHANGE addressing MASK_T
  10556.                                 ; and indirect return.
  10557.  
  10558. ; ---------------------
  10559. ; Handle BORDER command
  10560. ; ---------------------
  10561. ; Command syntax example: BORDER 7
  10562. ; This command routine sets the border to one of the eight colours.
  10563. ; The colours used for the lower screen are based on this.
  10564.  
  10565. ;; BORDER
  10566. L2294:  CALL    L1E94           ; routine FIND-INT1
  10567.         CP      $08             ; must be in range 0 (black) to 7 (white)
  10568.         JR      NC,L2244        ; back to REPORT-K if not
  10569.                                 ; 'Invalid colour'.
  10570.  
  10571.         OUT     ($FE),A         ; outputting to port effects an immediate
  10572.                                 ; change.
  10573.         RLCA                    ; shift the colour to
  10574.         RLCA                    ; the paper bits setting the
  10575.         RLCA                    ; ink colour black.
  10576.         BIT     5,A             ; is the number light coloured ?
  10577.                                 ; i.e. in the range green to white.
  10578.         JR      NZ,L22A6        ; skip to BORDER-1 if so
  10579.  
  10580.         XOR     $07             ; make the ink white.
  10581.  
  10582. ;; BORDER-1
  10583. L22A6:  LD      ($5C48),A       ; update BORDCR with new paper/ink
  10584.         RET                     ; return.
  10585.  
  10586. ; -----------------
  10587. ; Get pixel address
  10588. ; -----------------
  10589. ;
  10590. ;
  10591.  
  10592. ;; PIXEL-ADD
  10593. L22AA:  LD      A,$AF           ; load with 175 decimal.
  10594.         SUB     B               ; subtract the y value.
  10595.         JP      C,L24F9         ; jump forward to REPORT-Bc if greater.
  10596.                                 ; 'Integer out of range'
  10597.  
  10598. ; the high byte is derived from Y only.
  10599. ; the first 3 bits are always 010
  10600. ; the next 2 bits denote in which third of the screen the byte is.
  10601. ; the last 3 bits denote in which of the 8 scan lines within a third
  10602. ; the byte is located. There are 24 discrete values.
  10603.  
  10604.  
  10605.         LD      B,A             ; the line number from top of screen to B.
  10606.         AND     A               ; clear carry (already clear)
  10607.         RRA                     ;                     0xxxxxxx
  10608.         SCF                     ; set carry flag
  10609.         RRA                     ;                     10xxxxxx
  10610.         AND     A               ; clear carry flag
  10611.         RRA                     ;                     010xxxxx
  10612.  
  10613.         XOR     B               ;
  10614.         AND     $F8             ; keep the top 5 bits 11111000
  10615.         XOR     B               ;                     010xxbbb
  10616.         LD      H,A             ; transfer high byte to H.
  10617.  
  10618. ; the low byte is derived from both X and Y.
  10619.  
  10620.         LD      A,C             ; the x value 0-255.
  10621.         RLCA                    ;
  10622.         RLCA                    ;
  10623.         RLCA                    ;
  10624.         XOR     B               ; the y value
  10625.         AND     $C7             ; apply mask             11000111
  10626.         XOR     B               ; restore unmasked bits  xxyyyxxx
  10627.         RLCA                    ; rotate to              xyyyxxxx
  10628.         RLCA                    ; required position.     yyyxxxxx
  10629.         LD      L,A             ; low byte to L.
  10630.  
  10631. ; finally form the pixel position in A.
  10632.  
  10633.         LD      A,C             ; x value to A
  10634.         AND     $07             ; mod 8
  10635.         RET                     ; return
  10636.  
  10637. ; ----------------
  10638. ; Point Subroutine
  10639. ; ----------------
  10640. ; The point subroutine is called from s-point via the scanning functions
  10641. ; table.
  10642.  
  10643. ;; POINT-SUB
  10644. L22CB:  CALL    L2307           ; routine STK-TO-BC
  10645.         CALL    L22AA           ; routine PIXEL-ADD finds address of pixel.
  10646.         LD      B,A             ; pixel position to B, 0-7.
  10647.         INC     B               ; increment to give rotation count 1-8.
  10648.         LD      A,(HL)          ; fetch byte from screen.
  10649.  
  10650. ;; POINT-LP
  10651. L22D4:  RLCA                    ; rotate and loop back
  10652.         DJNZ    L22D4           ; to POINT-LP until pixel at right.
  10653.  
  10654.         AND      $01            ; test to give zero or one.
  10655.         JP      L2D28           ; jump forward to STACK-A to save result.
  10656.  
  10657. ; -------------------
  10658. ; Handle PLOT command
  10659. ; -------------------
  10660. ; Command Syntax example: PLOT 128,88
  10661. ;
  10662.  
  10663. ;; PLOT
  10664. L22DC:  CALL    L2307           ; routine STK-TO-BC
  10665.         CALL    L22E5           ; routine PLOT-SUB
  10666.         JP      L0D4D           ; to TEMPS
  10667.  
  10668. ; -------------------
  10669. ; The Plot subroutine
  10670. ; -------------------
  10671. ; A screen byte holds 8 pixels so it is necessary to rotate a mask
  10672. ; into the correct position to leave the other 7 pixels unaffected.
  10673. ; However all 64 pixels in the character cell take any embedded colour
  10674. ; items.
  10675. ; A pixel can be reset (inverse 1), toggled (over 1), or set ( with inverse
  10676. ; and over switches off). With both switches on, the byte is simply put
  10677. ; back on the screen though the colours may change.
  10678.  
  10679. ;; PLOT-SUB
  10680. L22E5:  LD      ($5C7D),BC      ; store new x/y values in COORDS
  10681.         CALL    L22AA           ; routine PIXEL-ADD gets address in HL,
  10682.                                 ; count from left 0-7 in B.
  10683.         LD      B,A             ; transfer count to B.
  10684.         INC     B               ; increase 1-8.
  10685.         LD      A,$FE           ; 11111110 in A.
  10686.  
  10687. ;; PLOT-LOOP
  10688. L22F0:  RRCA                    ; rotate mask.
  10689.         DJNZ    L22F0           ; to PLOT-LOOP until B circular rotations.
  10690.  
  10691.         LD      B,A             ; load mask to B
  10692.         LD      A,(HL)          ; fetch screen byte to A
  10693.  
  10694.         LD      C,(IY+$57)      ; P_FLAG to C
  10695.         BIT     0,C             ; is it to be OVER 1 ?
  10696.         JR      NZ,L22FD        ; forward to PL-TST-IN if so.
  10697.  
  10698. ; was over 0
  10699.  
  10700.         AND     B               ; combine with mask to blank pixel.
  10701.  
  10702. ;; PL-TST-IN
  10703. L22FD:  BIT     2,C             ; is it inverse 1 ?
  10704.         JR      NZ,L2303        ; to PLOT-END if so.
  10705.  
  10706.         XOR     B               ; switch the pixel
  10707.         CPL                     ; restore other 7 bits
  10708.  
  10709. ;; PLOT-END
  10710. L2303:  LD      (HL),A          ; load byte to the screen.
  10711.         JP      L0BDB           ; exit to PO-ATTR to set colours for cell.
  10712.  
  10713. ; ------------------------------
  10714. ; Put two numbers in BC register
  10715. ; ------------------------------
  10716. ;
  10717. ;
  10718.  
  10719. ;; STK-TO-BC
  10720. L2307:  CALL    L2314           ; routine STK-TO-A
  10721.         LD      B,A             ;
  10722.         PUSH    BC              ;
  10723.         CALL    L2314           ; routine STK-TO-A
  10724.         LD      E,C             ;
  10725.         POP     BC              ;
  10726.         LD      D,C             ;
  10727.         LD      C,A             ;
  10728.         RET                     ;
  10729.  
  10730. ; -----------------------
  10731. ; Put stack in A register
  10732. ; -----------------------
  10733. ; This routine puts the last value on the calculator stack into the accumulator
  10734. ; deleting the last value.
  10735.  
  10736. ;; STK-TO-A
  10737. L2314:  CALL    L2DD5           ; routine FP-TO-A compresses last value into
  10738.                                 ; accumulator. e.g. PI would become 3.
  10739.                                 ; zero flag set if positive.
  10740.         JP      C,L24F9         ; jump forward to REPORT-Bc if >= 255.5.
  10741.  
  10742.         LD      C,$01           ; prepare a positive sign byte.
  10743.         RET     Z               ; return if FP-TO-BC indicated positive.
  10744.  
  10745.         LD      C,$FF           ; prepare negative sign byte and
  10746.         RET                     ; return.
  10747.  
  10748.  
  10749. ; ---------------------
  10750. ; Handle CIRCLE command
  10751. ; ---------------------
  10752. ;
  10753. ; syntax has been partly checked using the class for draw command.
  10754.  
  10755. ;; CIRCLE
  10756. L2320:  RST     18H             ; GET-CHAR
  10757.         CP      $2C             ; is it required comma ?
  10758.         JP      NZ,L1C8A        ; jump to REPORT-C if not
  10759.  
  10760.  
  10761.         RST     20H             ; NEXT-CHAR
  10762.         CALL    L1C82           ; routine EXPT-1NUM fetches radius
  10763.         CALL    L1BEE           ; routine CHECK-END will return here if
  10764.                                 ; nothing follows command.
  10765.  
  10766.         RST     28H             ;; FP-CALC
  10767.         DB    $2A             ;;abs           ; make radius positive
  10768.         DB    $3D             ;;re-stack      ; in full floating point form
  10769.         DB    $38             ;;end-calc
  10770.  
  10771.         LD      A,(HL)          ; fetch first floating point byte
  10772.         CP      $81             ; compare to one
  10773.         JR      NC,L233B        ; forward to C-R-GRE-1 if circle radius
  10774.                                 ; is greater than one.
  10775.  
  10776.  
  10777.         RST     28H             ;; FP-CALC
  10778.         DB    $02             ;;delete        ; delete the radius from stack.
  10779.         DB    $38             ;;end-calc
  10780.  
  10781.         JR      L22DC           ; to PLOT to just plot x,y.
  10782.  
  10783. ; ---
  10784.  
  10785.  
  10786. ;; C-R-GRE-1
  10787. L233B:  RST     28H             ;; FP-CALC      ; x, y, r
  10788.         DB    $A3             ;;stk-pi/2      ; x, y, r, pi/2.
  10789.         DB    $38             ;;end-calc
  10790.  
  10791.         LD      (HL),$83        ;               ; x, y, r, 2*PI
  10792.  
  10793.         RST     28H             ;; FP-CALC
  10794.         DB    $C5             ;;st-mem-5      ; store 2*PI in mem-5
  10795.         DB    $02             ;;delete        ; x, y, z.
  10796.         DB    $38             ;;end-calc
  10797.  
  10798.         CALL    L247D           ; routine CD-PRMS1
  10799.         PUSH    BC              ;
  10800.  
  10801.         RST     28H             ;; FP-CALC
  10802.         DB    $31             ;;duplicate
  10803.         DB    $E1             ;;get-mem-1
  10804.         DB    $04             ;;multiply
  10805.         DB    $38             ;;end-calc
  10806.  
  10807.         LD      A,(HL)          ;
  10808.         CP      $80             ;
  10809.         JR      NC,L235A        ; to C-ARC-GE1
  10810.  
  10811.  
  10812.         RST     28H             ;; FP-CALC
  10813.         DB    $02             ;;delete
  10814.         DB    $02             ;;delete
  10815.         DB    $38             ;;end-calc
  10816.  
  10817.         POP     BC              ;
  10818.         JP      L22DC           ; JUMP to PLOT
  10819.  
  10820. ; ---
  10821.  
  10822.  
  10823. ;; C-ARC-GE1
  10824. L235A:  RST     28H             ;; FP-CALC
  10825.         DB    $C2             ;;st-mem-2
  10826.         DB    $01             ;;exchange
  10827.         DB    $C0             ;;st-mem-0
  10828.         DB    $02             ;;delete
  10829.         DB    $03             ;;subtract
  10830.         DB    $01             ;;exchange
  10831.         DB    $E0             ;;get-mem-0
  10832.         DB    $0F             ;;addition
  10833.         DB    $C0             ;;st-mem-0
  10834.         DB    $01             ;;exchange
  10835.         DB    $31             ;;duplicate
  10836.         DB    $E0             ;;get-mem-0
  10837.         DB    $01             ;;exchange
  10838.         DB    $31             ;;duplicate
  10839.         DB    $E0             ;;get-mem-0
  10840.         DB    $A0             ;;stk-zero
  10841.         DB    $C1             ;;st-mem-1
  10842.         DB    $02             ;;delete
  10843.         DB    $38             ;;end-calc
  10844.  
  10845.         INC     (IY+$62)        ; MEM-2-1st
  10846.         CALL     L1E94          ; routine FIND-INT1
  10847.         LD      L,A             ;
  10848.         PUSH    HL              ;
  10849.         CALL    L1E94           ; routine FIND-INT1
  10850.         POP     HL              ;
  10851.         LD      H,A             ;
  10852.         LD      ($5C7D),HL      ; COORDS
  10853.         POP     BC              ;
  10854.         JP      L2420           ; to DRW-STEPS
  10855.  
  10856.  
  10857. ; -------------------
  10858. ; Handle DRAW command
  10859. ; -------------------
  10860. ;
  10861. ;
  10862.  
  10863. ;; DRAW
  10864. L2382:  RST     18H             ; GET-CHAR
  10865.         CP      $2C             ;
  10866.         JR      Z,L238D         ; to DR-3-PRMS
  10867.  
  10868.         CALL    L1BEE           ; routine CHECK-END
  10869.         JP      L2477           ; to LINE-DRAW
  10870.  
  10871. ; ---
  10872.  
  10873. ;; DR-3-PRMS
  10874. L238D:  RST     20H             ; NEXT-CHAR
  10875.         CALL    L1C82           ; routine EXPT-1NUM
  10876.         CALL    L1BEE           ; routine CHECK-END
  10877.  
  10878.         RST     28H             ;; FP-CALC
  10879.         DB    $C5             ;;st-mem-5
  10880.         DB    $A2             ;;stk-half
  10881.         DB    $04             ;;multiply
  10882.         DB    $1F             ;;sin
  10883.         DB    $31             ;;duplicate
  10884.         DB    $30             ;;not
  10885.         DB    $30             ;;not
  10886.         DB    $00             ;;jump-true
  10887.  
  10888.         DB    $06             ;;to L23A3, DR-SIN-NZ
  10889.  
  10890.         DB    $02             ;;delete
  10891.         DB    $38             ;;end-calc
  10892.  
  10893.         JP      L2477           ; to LINE-DRAW
  10894.  
  10895. ; ---
  10896.  
  10897. ;; DR-SIN-NZ
  10898. L23A3:  DB    $C0             ;;st-mem-0
  10899.         DB    $02             ;;delete
  10900.         DB    $C1             ;;st-mem-1
  10901.         DB    $02             ;;delete
  10902.         DB    $31             ;;duplicate
  10903.         DB    $2A             ;;abs
  10904.         DB    $E1             ;;get-mem-1
  10905.         DB    $01             ;;exchange
  10906.         DB    $E1             ;;get-mem-1
  10907.         DB    $2A             ;;abs
  10908.         DB    $0F             ;;addition
  10909.         DB    $E0             ;;get-mem-0
  10910.         DB    $05             ;;division
  10911.         DB    $2A             ;;abs
  10912.         DB    $E0             ;;get-mem-0
  10913.         DB    $01             ;;exchange
  10914.         DB    $3D             ;;re-stack
  10915.         DB    $38             ;;end-calc
  10916.  
  10917.         LD      A,(HL)          ;
  10918.         CP      $81             ;
  10919.         JR      NC,L23C1        ; to DR-PRMS
  10920.  
  10921.  
  10922.         RST     28H             ;; FP-CALC
  10923.         DB    $02             ;;delete
  10924.         DB    $02             ;;delete
  10925.         DB    $38             ;;end-calc
  10926.  
  10927.         JP      L2477           ; to LINE-DRAW
  10928.  
  10929. ; ---
  10930.  
  10931. ;; DR-PRMS
  10932. L23C1:  CALL    L247D           ; routine CD-PRMS1
  10933.         PUSH    BC              ;
  10934.  
  10935.         RST     28H             ;; FP-CALC
  10936.         DB    $02             ;;delete
  10937.         DB    $E1             ;;get-mem-1
  10938.         DB    $01             ;;exchange
  10939.         DB    $05             ;;division
  10940.         DB    $C1             ;;st-mem-1
  10941.         DB    $02             ;;delete
  10942.         DB    $01             ;;exchange
  10943.         DB    $31             ;;duplicate
  10944.         DB    $E1             ;;get-mem-1
  10945.         DB    $04             ;;multiply
  10946.         DB    $C2             ;;st-mem-2
  10947.         DB    $02             ;;delete
  10948.         DB    $01             ;;exchange
  10949.         DB    $31             ;;duplicate
  10950.         DB    $E1             ;;get-mem-1
  10951.         DB    $04             ;;multiply
  10952.         DB    $E2             ;;get-mem-2
  10953.         DB    $E5             ;;get-mem-5
  10954.         DB    $E0             ;;get-mem-0
  10955.         DB    $03             ;;subtract
  10956.         DB    $A2             ;;stk-half
  10957.         DB    $04             ;;multiply
  10958.         DB    $31             ;;duplicate
  10959.         DB    $1F             ;;sin
  10960.         DB    $C5             ;;st-mem-5
  10961.         DB    $02             ;;delete
  10962.         DB    $20             ;;cos
  10963.         DB    $C0             ;;st-mem-0
  10964.         DB    $02             ;;delete
  10965.         DB    $C2             ;;st-mem-2
  10966.         DB    $02             ;;delete
  10967.         DB    $C1             ;;st-mem-1
  10968.         DB    $E5             ;;get-mem-5
  10969.         DB    $04             ;;multiply
  10970.         DB    $E0             ;;get-mem-0
  10971.         DB    $E2             ;;get-mem-2
  10972.         DB    $04             ;;multiply
  10973.         DB    $0F             ;;addition
  10974.         DB    $E1             ;;get-mem-1
  10975.         DB    $01             ;;exchange
  10976.         DB    $C1             ;;st-mem-1
  10977.         DB    $02             ;;delete
  10978.         DB    $E0             ;;get-mem-0
  10979.         DB    $04             ;;multiply
  10980.         DB    $E2             ;;get-mem-2
  10981.         DB    $E5             ;;get-mem-5
  10982.         DB    $04             ;;multiply
  10983.         DB    $03             ;;subtract
  10984.         DB    $C2             ;;st-mem-2
  10985.         DB    $2A             ;;abs
  10986.         DB    $E1             ;;get-mem-1
  10987.         DB    $2A             ;;abs
  10988.         DB    $0F             ;;addition
  10989.         DB    $02             ;;delete
  10990.         DB    $38             ;;end-calc
  10991.  
  10992.         LD      A,(DE)          ;
  10993.         CP       $81            ;
  10994.         POP     BC              ;
  10995.         JP      C,L2477         ; to LINE-DRAW
  10996.  
  10997.         PUSH    BC              ;
  10998.  
  10999.         RST     28H             ;; FP-CALC
  11000.         DB    $01             ;;exchange
  11001.         DB    $38             ;;end-calc
  11002.  
  11003.         LD      A,($5C7D)       ; COORDS-x
  11004.         CALL    L2D28           ; routine STACK-A
  11005.  
  11006.         RST     28H             ;; FP-CALC
  11007.         DB    $C0             ;;st-mem-0
  11008.         DB    $0F             ;;addition
  11009.         DB    $01             ;;exchange
  11010.         DB    $38             ;;end-calc
  11011.  
  11012.         LD      A,($5C7E)       ; COORDS-y
  11013.         CALL    L2D28           ; routine STACK-A
  11014.  
  11015.         RST     28H             ;; FP-CALC
  11016.         DB    $C5             ;;st-mem-5
  11017.         DB    $0F             ;;addition
  11018.         DB    $E0             ;;get-mem-0
  11019.         DB    $E5             ;;get-mem-5
  11020.         DB    $38             ;;end-calc
  11021.  
  11022.         POP     BC              ;
  11023.  
  11024. ;; DRW-STEPS
  11025. L2420:  DEC     B               ;
  11026.         JR      Z,L245F         ; to ARC-END
  11027.  
  11028.         JR      L2439           ; to ARC-START
  11029.  
  11030. ; ---
  11031.  
  11032.  
  11033. ;; ARC-LOOP
  11034. L2425:  RST     28H             ;; FP-CALC
  11035.         DB    $E1             ;;get-mem-1
  11036.         DB    $31             ;;duplicate
  11037.         DB    $E3             ;;get-mem-3
  11038.         DB    $04             ;;multiply
  11039.         DB    $E2             ;;get-mem-2
  11040.         DB    $E4             ;;get-mem-4
  11041.         DB    $04             ;;multiply
  11042.         DB    $03             ;;subtract
  11043.         DB    $C1             ;;st-mem-1
  11044.         DB    $02             ;;delete
  11045.         DB    $E4             ;;get-mem-4
  11046.         DB    $04             ;;multiply
  11047.         DB    $E2             ;;get-mem-2
  11048.         DB    $E3             ;;get-mem-3
  11049.         DB    $04             ;;multiply
  11050.         DB    $0F             ;;addition
  11051.         DB    $C2             ;;st-mem-2
  11052.         DB    $02             ;;delete
  11053.         DB    $38             ;;end-calc
  11054.  
  11055. ;; ARC-START
  11056. L2439:  PUSH    BC              ;
  11057.  
  11058.         RST     28H             ;; FP-CALC
  11059.         DB    $C0             ;;st-mem-0
  11060.         DB    $02             ;;delete
  11061.         DB    $E1             ;;get-mem-1
  11062.         DB    $0F             ;;addition
  11063.         DB    $31             ;;duplicate
  11064.         DB    $38             ;;end-calc
  11065.  
  11066.         LD      A,($5C7D)       ; COORDS-x
  11067.         CALL    L2D28           ; routine STACK-A
  11068.  
  11069.         RST     28H             ;; FP-CALC
  11070.         DB    $03             ;;subtract
  11071.         DB    $E0             ;;get-mem-0
  11072.         DB    $E2             ;;get-mem-2
  11073.         DB    $0F             ;;addition
  11074.         DB    $C0             ;;st-mem-0
  11075.         DB    $01             ;;exchange
  11076.         DB    $E0             ;;get-mem-0
  11077.         DB    $38             ;;end-calc
  11078.  
  11079.         LD      A,($5C7E)       ; COORDS-y
  11080.         CALL    L2D28           ; routine STACK-A
  11081.  
  11082.         RST     28H             ;; FP-CALC
  11083.         DB    $03             ;;subtract
  11084.         DB    $38             ;;end-calc
  11085.  
  11086.         CALL    L24B7           ; routine DRAW-LINE
  11087.         POP     BC              ;
  11088.         DJNZ    L2425           ; to ARC-LOOP
  11089.  
  11090.  
  11091. ;; ARC-END
  11092. L245F:  RST     28H             ;; FP-CALC
  11093.         DB    $02             ;;delete
  11094.         DB    $02             ;;delete
  11095.         DB    $01             ;;exchange
  11096.         DB    $38             ;;end-calc
  11097.  
  11098.         LD      A,($5C7D)       ; COORDS-x
  11099.         CALL    L2D28           ; routine STACK-A
  11100.  
  11101.         RST     28H             ;; FP-CALC
  11102.         DB    $03             ;;subtract
  11103.         DB    $01             ;;exchange
  11104.         DB    $38             ;;end-calc
  11105.  
  11106.         LD      A,($5C7E)       ; COORDS-y
  11107.         CALL    L2D28           ; routine STACK-A
  11108.  
  11109.         RST     28H             ;; FP-CALC
  11110.         DB    $03             ;;subtract
  11111.         DB    $38             ;;end-calc
  11112.  
  11113. ;; LINE-DRAW
  11114. L2477:  CALL    L24B7           ; routine DRAW-LINE
  11115.         JP      L0D4D           ; to TEMPS
  11116.  
  11117.  
  11118. ; ------------------
  11119. ; Initial parameters
  11120. ; ------------------
  11121. ;
  11122. ;
  11123.  
  11124. ;; CD-PRMS1
  11125. L247D:  RST     28H             ;; FP-CALC
  11126.         DB    $31             ;;duplicate
  11127.         DB    $28             ;;sqr
  11128.         DB    $34             ;;stk-data
  11129.         DB    $32             ;;Exponent: $82, Bytes: 1
  11130.         DB    $00             ;;(+00,+00,+00)
  11131.         DB    $01             ;;exchange
  11132.         DB    $05             ;;division
  11133.         DB    $E5             ;;get-mem-5
  11134.         DB    $01             ;;exchange
  11135.         DB    $05             ;;division
  11136.         DB    $2A             ;;abs
  11137.         DB    $38             ;;end-calc
  11138.  
  11139.         CALL    L2DD5           ; routine FP-TO-A
  11140.         JR      C,L2495         ; to USE-252
  11141.  
  11142.         AND     $FC             ;
  11143.         ADD     A,$04           ;
  11144.         JR      NC,L2497        ; to DRAW-SAVE
  11145.  
  11146. ;; USE-252
  11147. L2495:  LD      A,$FC           ;
  11148.  
  11149. ;; DRAW-SAVE
  11150. L2497:  PUSH    AF              ;
  11151.         CALL    L2D28           ; routine STACK-A
  11152.  
  11153.         RST     28H             ;; FP-CALC
  11154.         DB    $E5             ;;get-mem-5
  11155.         DB    $01             ;;exchange
  11156.         DB    $05             ;;division
  11157.         DB    $31             ;;duplicate
  11158.         DB    $1F             ;;sin
  11159.         DB    $C4             ;;st-mem-4
  11160.         DB    $02             ;;delete
  11161.         DB    $31             ;;duplicate
  11162.         DB    $A2             ;;stk-half
  11163.         DB    $04             ;;multiply
  11164.         DB    $1F             ;;sin
  11165.         DB    $C1             ;;st-mem-1
  11166.         DB    $01             ;;exchange
  11167.         DB    $C0             ;;st-mem-0
  11168.         DB    $02             ;;delete
  11169.         DB    $31             ;;duplicate
  11170.         DB    $04             ;;multiply
  11171.         DB    $31             ;;duplicate
  11172.         DB    $0F             ;;addition
  11173.         DB    $A1             ;;stk-one
  11174.         DB    $03             ;;subtract
  11175.         DB    $1B             ;;negate
  11176.         DB    $C3             ;;st-mem-3
  11177.         DB    $02             ;;delete
  11178.         DB    $38             ;;end-calc
  11179.  
  11180.         POP     BC              ;
  11181.         RET                     ;
  11182.  
  11183. ; ------------
  11184. ; Line drawing
  11185. ; ------------
  11186. ;
  11187. ;
  11188.  
  11189. ;; DRAW-LINE
  11190. L24B7:  CALL    L2307           ; routine STK-TO-BC
  11191.         LD      A,C             ;
  11192.         CP      B               ;
  11193.         JR      NC,L24C4        ; to DL-X-GE-Y
  11194.  
  11195.         LD      L,C             ;
  11196.         PUSH    DE              ;
  11197.         XOR     A               ;
  11198.         LD      E,A             ;
  11199.         JR      L24CB           ; to DL-LARGER
  11200.  
  11201. ; ---
  11202.  
  11203. ;; DL-X-GE-Y
  11204. L24C4:  OR      C               ;
  11205.         RET     Z               ;
  11206.  
  11207.         LD      L,B             ;
  11208.         LD      B,C             ;
  11209.         PUSH    DE              ;
  11210.         LD      D,$00           ;
  11211.  
  11212. ;; DL-LARGER
  11213. L24CB:  LD      H,B             ;
  11214.         LD      A,B             ;
  11215.         RRA                     ;
  11216.  
  11217. ;; D-L-LOOP
  11218. L24CE:  ADD     A,L             ;
  11219.         JR      C,L24D4         ; to D-L-DIAG
  11220.  
  11221.         CP      H               ;
  11222.         JR      C,L24DB         ; to D-L-HR-VT
  11223.  
  11224. ;; D-L-DIAG
  11225. L24D4:  SUB     H               ;
  11226.         LD      C,A             ;
  11227.         EXX                     ;
  11228.         POP     BC              ;
  11229.         PUSH    BC              ;
  11230.         JR      L24DF           ; to D-L-STEP
  11231.  
  11232. ; ---
  11233.  
  11234. ;; D-L-HR-VT
  11235. L24DB:  LD      C,A             ;
  11236.         PUSH    DE              ;
  11237.         EXX                     ;
  11238.         POP     BC              ;
  11239.  
  11240. ;; D-L-STEP
  11241. L24DF:  LD      HL,($5C7D)      ; COORDS
  11242.         LD      A,B             ;
  11243.         ADD     A,H             ;
  11244.         LD      B,A             ;
  11245.         LD      A,C             ;
  11246.         INC     A               ;
  11247.         ADD     A,L             ;
  11248.         JR      C,L24F7         ; to D-L-RANGE
  11249.  
  11250.         JR      Z,L24F9         ; to REPORT-Bc
  11251.  
  11252. ;; D-L-PLOT
  11253. L24EC:  DEC     A               ;
  11254.         LD      C,A             ;
  11255.         CALL    L22E5           ; routine PLOT-SUB
  11256.         EXX                     ;
  11257.         LD      A,C             ;
  11258.         DJNZ    L24CE           ; to D-L-LOOP
  11259.  
  11260.         POP     DE              ;
  11261.         RET                     ;
  11262.  
  11263. ; ---
  11264.  
  11265. ;; D-L-RANGE
  11266. L24F7:  JR      Z,L24EC         ; to D-L-PLOT
  11267.  
  11268.  
  11269. ;; REPORT-Bc
  11270. L24F9:  RST     08H             ; ERROR-1
  11271.         DB    $0A             ; Error Report: Integer out of range
  11272.  
  11273.  
  11274.  
  11275. ;***********************************
  11276. ;** Part 8. EXPRESSION EVALUATION **
  11277. ;***********************************
  11278. ;
  11279. ; It is a this stage of the ROM that the Spectrum ceases altogether to be
  11280. ; just a colourful novelty. One remarkable feature is that in all previous
  11281. ; commands when the Spectrum is expecting a number or a string then an
  11282. ; expression of the same type can be substituted ad infinitum.
  11283. ; This is the routine that evaluates that expression.
  11284. ; This is what causes 2 + 2 to give the answer 4.
  11285. ; That is quite easy to understand. However you don't have to make it much
  11286. ; more complex to start a remarkable juggling act.
  11287. ; e.g. PRINT 2 * (VAL "2+2" + TAN 3)
  11288. ; In fact, provided there is enough free RAM, the Spectrum can evaluate
  11289. ; an expression of unlimited complexity.
  11290. ; Apart from a couple of minor glitches, which you can now correct, the
  11291. ; system is remarkably robust.
  11292.  
  11293.  
  11294. ; ---------------------------------
  11295. ; Scan expression or sub-expression
  11296. ; ---------------------------------
  11297. ;
  11298. ;
  11299.  
  11300. ;; SCANNING
  11301. L24FB:  RST     18H             ; GET-CHAR
  11302.         LD      B,$00           ; priority marker zero is pushed on stack
  11303.                                 ; to signify end of expression when it is
  11304.                                 ; popped off again.
  11305.         PUSH    BC              ; put in on stack.
  11306.                                 ; and proceed to consider the first character
  11307.                                 ; of the expression.
  11308.  
  11309. ;; S-LOOP-1
  11310. L24FF:  LD      C,A             ; store the character while a look up is done.
  11311.         LD      HL,L2596        ; Address: scan-func
  11312.         CALL    L16DC           ; routine INDEXER is called to see if it is
  11313.                                 ; part of a limited range '+', '(', 'ATTR' etc.
  11314.  
  11315.         LD      A,C             ; fetch the character back
  11316.         JP      NC,L2684        ; jump forward to S-ALPHNUM if not in primary
  11317.                                 ; operators and functions to consider in the
  11318.                                 ; first instance a digit or a variable and
  11319.                                 ; then anything else.                >>>
  11320.  
  11321.         LD      B,$00           ; but here if it was found in table so
  11322.         LD      C,(HL)          ; fetch offset from table and make B zero.
  11323.         ADD     HL,BC           ; add the offset to position found
  11324.         JP      (HL)            ; and jump to the routine e.g. S-BIN
  11325.                                 ; making an indirect exit from there.
  11326.  
  11327. ; -------------------------------------------------------------------------
  11328. ; The four service subroutines for routines in the scannings function table
  11329. ; -------------------------------------------------------------------------
  11330.  
  11331. ; PRINT """Hooray!"" he cried."
  11332.  
  11333. ;; S-QUOTE-S
  11334. L250F:  CALL    L0074           ; routine CH-ADD+1 points to next character
  11335.                                 ; and fetches that character.
  11336.         INC     BC              ; increase length counter.
  11337.         CP      $0D             ; is it carriage return ?
  11338.                                 ; inside a quote.
  11339.         JP      Z,L1C8A         ; jump back to REPORT-C if so.
  11340.                                 ; 'Nonsense in BASIC'.
  11341.  
  11342.         CP      $22             ; is it a quote '"' ?
  11343.         JR      NZ,L250F        ; back to S-QUOTE-S if not for more.
  11344.  
  11345.         CALL    L0074           ; routine CH-ADD+1
  11346.         CP      $22             ; compare with possible adjacent quote
  11347.         RET                     ; return. with zero set if two together.
  11348.  
  11349. ; ---
  11350.  
  11351. ; This subroutine is used to get two coordinate expressions for the three
  11352. ; functions SCREEN$, ATTR and POINT that have two fixed parameters and
  11353. ; therefore require surrounding braces.
  11354.  
  11355. ;; S-2-COORD
  11356. L2522:  RST     20H             ; NEXT-CHAR
  11357.         CP      $28             ; is it the opening '(' ?
  11358.         JR      NZ,L252D        ; forward to S-RPORT-C if not
  11359.                                 ; 'Nonsense in BASIC'.
  11360.  
  11361.         CALL    L1C79           ; routine NEXT-2NUM gets two comma-separated
  11362.                                 ; numeric expressions. Note. this could cause
  11363.                                 ; many more recursive calls to SCANNING but
  11364.                                 ; the parent function will be evaluated fully
  11365.                                 ; before rejoining the main juggling act.
  11366.  
  11367.         RST     18H             ; GET-CHAR
  11368.         CP      $29             ; is it the closing ')' ?
  11369.  
  11370. ;; S-RPORT-C
  11371. L252D:  JP      NZ,L1C8A        ; jump back to REPORT-C if not.
  11372.                                 ; 'Nonsense in BASIC'.
  11373.  
  11374. ; ------------
  11375. ; Check syntax
  11376. ; ------------
  11377. ; This routine is called on a number of occasions to check if syntax is being
  11378. ; checked or if the program is being run. To test the flag inline would use
  11379. ; four bytes of code, but a call instruction only uses 3 bytes of code.
  11380.  
  11381. ;; SYNTAX-Z
  11382. L2530:  BIT     7,(IY+$01)      ; test FLAGS  - checking syntax only ?
  11383.         RET                     ; return.
  11384.  
  11385. ; ----------------
  11386. ; Scanning SCREEN$
  11387. ; ----------------
  11388. ; This function returns the code of a bit-mapped character at screen
  11389. ; position at line C, column B. It is unable to detect the mosaic characters
  11390. ; which are not bit-mapped but detects the ASCII 32 - 127 range.
  11391. ; The bit-mapped UDGs are ignored which is curious as it requires only a
  11392. ; few extra bytes of code. As usual, anything to do with CHARS is weird.
  11393. ; If no match is found a null string is returned.
  11394. ; No actual check on ranges is performed - that's up to the BASIC programmer.
  11395. ; No real harm can come from SCREEN$(255,255) although the BASIC manual
  11396. ; says that invalid values will be trapped.
  11397. ; Interestingly, in the Pitman pocket guide, 1984, Vickers says that the
  11398. ; range checking will be performed.
  11399.  
  11400. ;; S-SCRN$-S
  11401. L2535:  CALL    L2307           ; routine STK-TO-BC.
  11402.         LD      HL,($5C36)      ; fetch address of CHARS.
  11403.         LD      DE,$0100        ; fetch offset to chr$ 32
  11404.         ADD     HL,DE           ; and find start of bitmaps.
  11405.                                 ; Note. not inc h. ??
  11406.         LD      A,C             ; transfer line to A.
  11407.         RRCA                    ; multiply
  11408.         RRCA                    ; by
  11409.         RRCA                    ; thirty-two.
  11410.         AND     $E0             ; and with 11100000
  11411.         XOR     B               ; combine with column $00 - $1F
  11412.         LD      E,A             ; to give the low byte of top line
  11413.         LD      A,C             ; column to A range 00000000 to 00011111
  11414.         AND     $18             ; and with 00011000
  11415.         XOR     $40             ; xor with 01000000 (high byte screen start)
  11416.         LD      D,A             ; register DE now holds start address of cell.
  11417.         LD      B,$60           ; there are 96 characters in ASCII set.
  11418.  
  11419. ;; S-SCRN-LP
  11420. L254F:  PUSH    BC              ; save count
  11421.         PUSH    DE              ; save screen start address
  11422.         PUSH    HL              ; save bitmap start
  11423.         LD      A,(DE)          ; first byte of screen to A
  11424.         XOR     (HL)            ; xor with corresponding character byte
  11425.         JR      Z,L255A         ; forward to S-SC-MTCH if they match
  11426.                                 ; if inverse result would be $FF
  11427.                                 ; if any other then mismatch
  11428.  
  11429.         INC     A               ; set to $00 if inverse
  11430.         JR      NZ,L2573        ; forward to S-SCR-NXT if a mismatch
  11431.  
  11432.         DEC     A               ; restore $FF
  11433.  
  11434. ; a match has been found so seven more to test.
  11435.  
  11436. ;; S-SC-MTCH
  11437. L255A:  LD      C,A             ; load C with inverse mask $00 or $FF
  11438.         LD      B,$07           ; count seven more bytes
  11439.  
  11440. ;; S-SC-ROWS
  11441. L255D:  INC     D               ; increment screen address.
  11442.         INC     HL              ; increment bitmap address.
  11443.         LD      A,(DE)          ; byte to A
  11444.         XOR     (HL)            ; will give $00 or $FF (inverse)
  11445.         XOR     C               ; xor with inverse mask
  11446.         JR      NZ,L2573        ; forward to S-SCR-NXT if no match.
  11447.  
  11448.         DJNZ    L255D           ; back to S-SC-ROWS until all eight matched.
  11449.  
  11450. ; continue if a match of all eight bytes was found
  11451.  
  11452.         POP     BC              ; discard the
  11453.         POP     BC              ; saved
  11454.         POP     BC              ; pointers
  11455.         LD      A,$80           ; the endpoint of character set
  11456.         SUB     B               ; subtract the counter
  11457.                                 ; to give the code 32-127
  11458.         LD      BC,$0001        ; make one space in workspace.
  11459.  
  11460.         RST     30H             ; BC-SPACES creates the space sliding
  11461.                                 ; the calculator stack upwards.
  11462.         LD      (DE),A          ; start is addressed by DE, so insert code
  11463.         JR      L257D           ; forward to S-SCR-STO
  11464.  
  11465. ; ---
  11466.  
  11467. ; the jump was here if no match and more bitmaps to test.
  11468.  
  11469. ;; S-SCR-NXT
  11470. L2573:  POP     HL              ; restore the last bitmap start
  11471.         LD      DE,$0008        ; and prepare to add 8.
  11472.         ADD     HL,DE           ; now addresses next character bitmap.
  11473.         POP     DE              ; restore screen address
  11474.         POP     BC              ; and character counter in B
  11475.         DJNZ    L254F           ; back to S-SCRN-LP if more characters.
  11476.  
  11477.         LD      C,B             ; B is now zero, so BC now zero.
  11478.  
  11479. ;; S-SCR-STO
  11480. L257D:  JP      L2AB2           ; to STK-STO-$ to store the string in
  11481.                                 ; workspace or a string with zero length.
  11482.                                 ; (value of DE doesn't matter in last case)
  11483.  
  11484. ; Note. this exit seems correct but the general-purpose routine S-STRING
  11485. ; that calls this one will also stack any of its string results so this
  11486. ; leads to a double storing of the result in this case.
  11487. ; The instruction at L257D should just be a RET.
  11488. ; credit Stephen Kelly and others, 1982.
  11489.  
  11490. ; -------------
  11491. ; Scanning ATTR
  11492. ; -------------
  11493. ; This function subroutine returns the attributes of a screen location -
  11494. ; a numeric result.
  11495. ; Again it's up to the BASIC programmer to supply valid values of line/column.
  11496.  
  11497. ;; S-ATTR-S
  11498. L2580:  CALL    L2307           ; routine STK-TO-BC fetches line to C,
  11499.                                 ; and column to B.
  11500.         LD      A,C             ; line to A $00 - $17   (max 00010111)
  11501.         RRCA                    ; rotate
  11502.         RRCA                    ; bits
  11503.         RRCA                    ; left.
  11504.         LD      C,A             ; store in C as an intermediate value.
  11505.  
  11506.         AND     $E0             ; pick up bits 11100000 ( was 00011100 )
  11507.         XOR     B               ; combine with column $00 - $1F
  11508.         LD      L,A             ; low byte now correct.
  11509.  
  11510.         LD      A,C             ; bring back intermediate result from C
  11511.         AND     $03             ; mask to give correct third of
  11512.                                 ; screen $00 - $02
  11513.         XOR     $58             ; combine with base address.
  11514.         LD      H,A             ; high byte correct.
  11515.         LD      A,(HL)          ; pick up the colour attribute.
  11516.         JP      L2D28           ; forward to STACK-A to store result
  11517.                                 ; and make an indirect exit.
  11518.  
  11519. ; -----------------------
  11520. ; Scanning function table
  11521. ; -----------------------
  11522. ; This table is used by INDEXER routine to find the offsets to
  11523. ; four operators and eight functions. e.g. $A8 is the token 'FN'.
  11524. ; This table is used in the first instance for the first character of an
  11525. ; expression or by a recursive call to SCANNING for the first character of
  11526. ; any sub-expression. It eliminates functions that have no argument or
  11527. ; functions that can have more than one argument and therefore require
  11528. ; braces. By eliminating and dealing with these now it can later take a
  11529. ; simplistic approach to all other functions and assume that they have
  11530. ; one argument.
  11531. ; Similarly by eliminating BIN and '.' now it is later able to assume that
  11532. ; all numbers begin with a digit and that the presence of a number or
  11533. ; variable can be detected by a call to ALPHANUM.
  11534. ; By default all expressions are positive and the spurious '+' is eliminated
  11535. ; now as in print +2. This should not be confused with the operator '+'.
  11536. ; Note. this does allow a degree of nonsense to be accepted as in
  11537. ; PRINT +"3 is the greatest.".
  11538. ; An acquired programming skill is the ability to include brackets where
  11539. ; they are not necessary.
  11540. ; A bracket at the start of a sub-expression may be spurious or necessary
  11541. ; to denote that the contained expression is to be evaluated as an entity.
  11542. ; In either case this is dealt with by recursive calls to SCANNING.
  11543. ; An expression that begins with a quote requires special treatment.
  11544.  
  11545. ;; scan-func
  11546. L2596:  DB    $22, L25B3-$-1  ; $1C offset to S-QUOTE
  11547.         DB    '(', L25E8-$-1  ; $4F offset to S-BRACKET
  11548.         DB    '.', L268D-$-1  ; $F2 offset to S-DECIMAL
  11549.         DB    '+', L25AF-$-1  ; $12 offset to S-U-PLUS
  11550.  
  11551.         DB    $A8, L25F5-$-1  ; $56 offset to S-FN
  11552.         DB    $A5, L25F8-$-1  ; $57 offset to S-RND
  11553.         DB    $A7, L2627-$-1  ; $84 offset to S-PI
  11554.         DB    $A6, L2634-$-1  ; $8F offset to S-INKEY$
  11555.         DB    $C4, L268D-$-1  ; $E6 offset to S-BIN
  11556.         DB    $AA, L2668-$-1  ; $BF offset to S-SCREEN$
  11557.         DB    $AB, L2672-$-1  ; $C7 offset to S-ATTR
  11558.         DB    $A9, L267B-$-1  ; $CE offset to S-POINT
  11559.  
  11560.         DB    $00             ; zero end marker
  11561.  
  11562. ; --------------------------
  11563. ; Scanning function routines
  11564. ; --------------------------
  11565. ; These are the 11 subroutines accessed by the above table.
  11566. ; S-BIN and S-DECIMAL are the same
  11567. ; The 1-byte offset limits their location to within 255 bytes of their
  11568. ; entry in the table.
  11569.  
  11570. ; ->
  11571. ;; S-U-PLUS
  11572. L25AF:  RST     20H             ; NEXT-CHAR just ignore
  11573.         JP      L24FF           ; to S-LOOP-1
  11574.  
  11575. ; ---
  11576.  
  11577. ; ->
  11578. ;; S-QUOTE
  11579. L25B3:  RST     18H             ; GET-CHAR
  11580.         INC     HL              ; address next character (first in quotes)
  11581.         PUSH    HL              ; save start of quoted text.
  11582.         LD      BC,$0000        ; initialize length of string to zero.
  11583.         CALL    L250F           ; routine S-QUOTE-S
  11584.         JR      NZ,L25D9        ; forward to S-Q-PRMS if
  11585.  
  11586. ;; S-Q-AGAIN
  11587. L25BE:  CALL    L250F           ; routine S-QUOTE-S copies string until a
  11588.                                 ; quote is encountered
  11589.         JR      Z,L25BE         ; back to S-Q-AGAIN if two quotes WERE
  11590.                                 ; together.
  11591.  
  11592. ; but if just an isolated quote then that terminates the string.
  11593.  
  11594.         CALL    L2530           ; routine SYNTAX-Z
  11595.         JR      Z,L25D9         ; forward to S-Q-PRMS if checking syntax.
  11596.  
  11597.  
  11598.         RST     30H             ; BC-SPACES creates the space for true
  11599.                                 ; copy of string in workspace.
  11600.         POP     HL              ; re-fetch start of quoted text.
  11601.         PUSH    DE              ; save start in workspace.
  11602.  
  11603. ;; S-Q-COPY
  11604. L25CB:  LD      A,(HL)          ; fetch a character from source.
  11605.         INC     HL              ; advance source address.
  11606.         LD      (DE),A          ; place in destination.
  11607.         INC     DE              ; advance destination address.
  11608.         CP      $22             ; was it a '"' just copied ?
  11609.         JR      NZ,L25CB        ; back to S-Q-COPY to copy more if not
  11610.  
  11611.         LD      A,(HL)          ; fetch adjacent character from source.
  11612.         INC     HL              ; advance source address.
  11613.         CP      $22             ; is this '"' ? - i.e. two quotes together ?
  11614.         JR      Z,L25CB         ; to S-Q-COPY if so including just one of the
  11615.                                 ; pair of quotes.
  11616.  
  11617. ; proceed when terminating quote encountered.
  11618.  
  11619. ;; S-Q-PRMS
  11620. L25D9:  DEC     BC              ; decrease count by 1.
  11621.         POP     DE              ; restore start of string in workspace.
  11622.  
  11623. ;; S-STRING
  11624. L25DB:  LD      HL,$5C3B        ; Address FLAGS system variable.
  11625.         RES     6,(HL)          ; signal string result.
  11626.         BIT     7,(HL)          ; is syntax being checked.
  11627.         CALL    NZ,L2AB2        ; routine STK-STO-$ is called in runtime.
  11628.         JP      L2712           ; jump forward to S-CONT-2          ===>
  11629.  
  11630. ; ---
  11631.  
  11632. ; ->
  11633. ;; S-BRACKET
  11634. L25E8:  RST     20H             ; NEXT-CHAR
  11635.         CALL    L24FB           ; routine SCANNING is called recursively.
  11636.         CP      $29             ; is it the closing ')' ?
  11637.         JP      NZ,L1C8A        ; jump back to REPORT-C if not
  11638.                                 ; 'Nonsense in BASIC'
  11639.  
  11640.         RST     20H             ; NEXT-CHAR
  11641.         JP      L2712           ; jump forward to S-CONT-2          ===>
  11642.  
  11643. ; ---
  11644.  
  11645. ; ->
  11646. ;; S-FN
  11647. L25F5:  JP      L27BD           ; jump forward to S-FN-SBRN.
  11648.  
  11649. ; ---
  11650.  
  11651. ; ->
  11652. ;; S-RND
  11653. L25F8:  CALL    L2530           ; routine SYNTAX-Z
  11654.         JR      Z,L2625         ; forward to S-RND-END if checking syntax.
  11655.  
  11656.         LD      BC,($5C76)      ; fetch system variable SEED
  11657.         CALL    L2D2B           ; routine STACK-BC places on calculator stack
  11658.  
  11659.         RST     28H             ;; FP-CALC           ;s.
  11660.         DB    $A1             ;;stk-one            ;s,1.
  11661.         DB    $0F             ;;addition           ;s+1.
  11662.         DB    $34             ;;stk-data           ;
  11663.         DB    $37             ;;Exponent: $87,
  11664.                                 ;;Bytes: 1
  11665.         DB    $16             ;;(+00,+00,+00)      ;s+1,75.
  11666.         DB    $04             ;;multiply           ;(s+1)*75 = v
  11667.         DB    $34             ;;stk-data           ;v.
  11668.         DB    $80             ;;Bytes: 3
  11669.         DB    $41             ;;Exponent $91
  11670.         DB    $00,$00,$80     ;;(+00)              ;v,65537.
  11671.         DB    $32             ;;n-mod-m            ;remainder, result.
  11672.         DB    $02             ;;delete             ;remainder.
  11673.         DB    $A1             ;;stk-one            ;remainder, 1.
  11674.         DB    $03             ;;subtract           ;remainder - 1. = rnd
  11675.         DB    $31             ;;duplicate          ;rnd,rnd.
  11676.         DB    $38             ;;end-calc
  11677.  
  11678.         CALL    L2DA2           ; routine FP-TO-BC
  11679.         LD      ($5C76),BC      ; store in SEED for next starting point.
  11680.         LD      A,(HL)          ; fetch exponent
  11681.         AND     A               ; is it zero ?
  11682.         JR      Z,L2625         ; forward if so to S-RND-END
  11683.  
  11684.         SUB     $10             ; reduce exponent by 2^16
  11685.         LD      (HL),A          ; place back
  11686.  
  11687. ;; S-RND-END
  11688. L2625:  JR      L2630           ; forward to S-PI-END
  11689.  
  11690. ; ---
  11691.  
  11692. ; the number PI 3.14159...
  11693.  
  11694. ; ->
  11695. ;; S-PI
  11696. L2627:  CALL    L2530           ; routine SYNTAX-Z
  11697.         JR      Z,L2630         ; to S-PI-END if checking syntax.
  11698.  
  11699.         RST     28H             ;; FP-CALC
  11700.         DB    $A3             ;;stk-pi/2                          pi/2.
  11701.         DB    $38             ;;end-calc
  11702.  
  11703.         INC     (HL)            ; increment the exponent leaving pi
  11704.                                 ; on the calculator stack.
  11705.  
  11706. ;; S-PI-END
  11707. L2630:  RST     20H             ; NEXT-CHAR
  11708.         JP      L26C3           ; jump forward to S-NUMERIC
  11709.  
  11710. ; ---
  11711.  
  11712. ; ->
  11713. ;; S-INKEY$
  11714. L2634:  LD      BC,$105A        ; priority $10, operation code $1A ('read-in')
  11715.                                 ; +$40 for string result, numeric operand.
  11716.                                 ; set this up now in case we need to use the
  11717.                                 ; calculator.
  11718.         RST     20H             ; NEXT-CHAR
  11719.         CP      $23             ; '#' ?
  11720.         JP      Z,L270D         ; to S-PUSH-PO if so to use the calculator
  11721.                                 ; single operation
  11722.                                 ; to read from network/RS232 etc. .
  11723.  
  11724. ; else read a key from the keyboard.
  11725.  
  11726.         LD      HL,$5C3B        ; fetch FLAGS
  11727.         RES     6,(HL)          ; signal string result.
  11728.         BIT     7,(HL)          ; checking syntax ?
  11729.         JR      Z,L2665         ; forward to S-INK$-EN if so
  11730.  
  11731. ;===============================
  11732.                 IF BAS48_ONLY=1
  11733.                 CALL L028E
  11734.                 ELSE
  11735.                 JP L3B6C                ; Spectrum 128 patch
  11736.                 ENDIF
  11737. ;===============================
  11738.  
  11739. L2649:  LD      C,$00           ; the length of an empty string
  11740.         JR      NZ,L2660        ; to S-IK$-STK to store empty string if
  11741.                                 ; no key returned.
  11742.  
  11743.         CALL    L031E           ; routine K-TEST get main code in A
  11744.         JR      NC,L2660        ; to S-IK$-STK to stack null string if
  11745.                                 ; invalid
  11746.  
  11747.         DEC     D               ; D is expected to be FLAGS so set bit 3 $FF
  11748.                                 ; 'L' Mode so no keywords.
  11749.         LD      E,A             ; main key to A
  11750.                                 ; C is MODE 0 'KLC' from above still.
  11751.         CALL    L0333           ; routine K-DECODE
  11752. L2657:  PUSH    AF              ; save the code
  11753.         LD      BC,$0001        ; make room for one character
  11754.  
  11755.         RST     30H             ; BC-SPACES
  11756.         POP     AF              ; bring the code back
  11757.         LD      (DE),A          ; put the key in workspace
  11758.         LD      C,$01           ; set C length to one
  11759.  
  11760. ;; S-IK$-STK
  11761. L2660:  LD      B,$00           ; set high byte of length to zero
  11762.         CALL    L2AB2           ; routine STK-STO-$
  11763.  
  11764. ;; S-INK$-EN
  11765. L2665:  JP      L2712           ; to S-CONT-2            ===>
  11766.  
  11767. ; ---
  11768.  
  11769. ; ->
  11770. ;; S-SCREEN$
  11771. L2668:  CALL    L2522           ; routine S-2-COORD
  11772.         CALL    NZ,L2535        ; routine S-SCRN$-S
  11773.  
  11774.         RST     20H             ; NEXT-CHAR
  11775.         JP      L25DB           ; forward to S-STRING to stack result
  11776.  
  11777. ; ---
  11778.  
  11779. ; ->
  11780. ;; S-ATTR
  11781. L2672:  CALL    L2522           ; routine S-2-COORD
  11782.         CALL    NZ,L2580        ; routine S-ATTR-S
  11783.  
  11784.         RST     20H             ; NEXT-CHAR
  11785.         JR      L26C3           ; forward to S-NUMERIC
  11786.  
  11787. ; ---
  11788.  
  11789. ; ->
  11790. ;; S-POINT
  11791. L267B:  CALL    L2522           ; routine S-2-COORD
  11792.         CALL    NZ,L22CB        ; routine POINT-SUB
  11793.  
  11794.         RST     20H             ; NEXT-CHAR
  11795.         JR      L26C3           ; forward to S-NUMERIC
  11796.  
  11797. ; -----------------------------
  11798.  
  11799. ; ==> The branch was here if not in table.
  11800.  
  11801. ;; S-ALPHNUM
  11802. L2684:  CALL    L2C88           ; routine ALPHANUM checks if variable or
  11803.                                 ; a digit.
  11804.         JR      NC,L26DF        ; forward to S-NEGATE if not to consider
  11805.                                 ; a '-' character then functions.
  11806.  
  11807.         CP      $41             ; compare 'A'
  11808.         JR      NC,L26C9        ; forward to S-LETTER if alpha       ->
  11809.                                 ; else must have been numeric so continue
  11810.                                 ; into that routine.
  11811.  
  11812. ; This important routine is called during runtime and from LINE-SCAN
  11813. ; when a BASIC line is checked for syntax. It is this routine that
  11814. ; inserts, during syntax checking, the invisible floating point numbers
  11815. ; after the numeric expression. During runtime it just picks these
  11816. ; numbers up. It also handles BIN format numbers.
  11817.  
  11818. ; ->
  11819. ;; S-BIN
  11820. ;; S-DECIMAL
  11821. L268D:  CALL    L2530           ; routine SYNTAX-Z
  11822.         JR      NZ,L26B5        ; to S-STK-DEC in runtime
  11823.  
  11824. ; this route is taken when checking syntax.
  11825.  
  11826.         CALL    L2C9B           ; routine DEC-TO-FP to evaluate number
  11827.  
  11828.         RST     18H             ; GET-CHAR to fetch HL
  11829.         LD      BC,$0006        ; six locations required
  11830.         CALL    L1655           ; routine MAKE-ROOM
  11831.         INC     HL              ; to first new location
  11832.         LD      (HL),$0E        ; insert number marker
  11833.         INC     HL              ; address next
  11834.         EX      DE,HL           ; make DE destination.
  11835.         LD      HL,($5C65)      ; STKEND points to end of stack.
  11836.         LD      C,$05           ; result is five locations lower
  11837.         AND     A               ; prepare for true subtraction
  11838.         SBC     HL,BC           ; point to start of value.
  11839.         LD      ($5C65),HL      ; update STKEND as we are taking number.
  11840.         LDIR                    ; Copy five bytes to program location
  11841.         EX      DE,HL           ; transfer pointer to HL
  11842.         DEC     HL              ; adjust
  11843.         CALL    L0077           ; routine TEMP-PTR1 sets CH-ADD
  11844.         JR      L26C3           ; to S-NUMERIC to record nature of result
  11845.  
  11846. ; ---
  11847.  
  11848. ; branch here in runtime.
  11849.  
  11850. ;; S-STK-DEC
  11851. L26B5:  RST     18H             ; GET-CHAR positions HL at digit.
  11852.  
  11853. ;; S-SD-SKIP
  11854. L26B6:  INC     HL              ; advance pointer
  11855.         LD      A,(HL)          ; until we find
  11856.         CP      $0E             ; chr 14d - the number indicator
  11857.         JR      NZ,L26B6        ; to S-SD-SKIP until a match
  11858.                                 ; it has to be here.
  11859.  
  11860.         INC     HL              ; point to first byte of number
  11861.         CALL    L33B4           ; routine STACK-NUM stacks it
  11862.         LD      ($5C5D),HL      ; update system variable CH_ADD
  11863.  
  11864. ;; S-NUMERIC
  11865. L26C3:  SET     6,(IY+$01)      ; update FLAGS  - Signal numeric result
  11866.         JR      L26DD           ; forward to S-CONT-1               ===>
  11867.                                 ; actually S-CONT-2 is destination but why
  11868.                                 ; waste a byte on a jump when a JR will do.
  11869.                                 ; actually a JR L2712 can be used. Rats.
  11870.  
  11871. ; end of functions accessed from scanning functions table.
  11872.  
  11873. ; --------------------------
  11874. ; Scanning variable routines
  11875. ; --------------------------
  11876. ;
  11877. ;
  11878.  
  11879. ;; S-LETTER
  11880. L26C9:  CALL    L28B2           ; routine LOOK-VARS
  11881.         JP      C,L1C2E         ; jump back to REPORT-2 if not found
  11882.                                 ; 'Variable not found'
  11883.                                 ; but a variable is always 'found' if syntax
  11884.                                 ; is being checked.
  11885.  
  11886.         CALL    Z,L2996         ; routine STK-VAR considers a subscript/slice
  11887.         LD      A,($5C3B)       ; fetch FLAGS value
  11888.         CP      $C0             ; compare 11000000
  11889.         JR      C,L26DD         ; step forward to S-CONT-1 if string  ===>
  11890.  
  11891.         INC     HL              ; advance pointer
  11892.         CALL    L33B4           ; routine STACK-NUM
  11893.  
  11894. ;; S-CONT-1
  11895. L26DD:  JR      L2712           ; forward to S-CONT-2                 ===>
  11896.  
  11897. ; ----------------------------------------
  11898. ; -> the scanning branch was here if not alphanumeric.
  11899. ; All the remaining functions will be evaluated by a single call to the
  11900. ; calculator. The correct priority for the operation has to be placed in
  11901. ; the B register and the operation code, calculator literal in the C register.
  11902. ; the operation code has bit 7 set if result is numeric and bit 6 is
  11903. ; set if operand is numeric. so
  11904. ; $C0 = numeric result, numeric operand.            e.g. 'sin'
  11905. ; $80 = numeric result, string operand.             e.g. 'code'
  11906. ; $40 = string result, numeric operand.             e.g. 'str$'
  11907. ; $00 = string result, string operand.              e.g. 'val$'
  11908.  
  11909. ;; S-NEGATE
  11910. L26DF:  LD      BC,$09DB        ; prepare priority 09, operation code $C0 +
  11911.                                 ; 'negate' ($1B) - bits 6 and 7 set for numeric
  11912.                                 ; result and numeric operand.
  11913.  
  11914.         CP      $2D             ; is it '-' ?
  11915.         JR      Z,L270D         ; forward if so to S-PUSH-PO
  11916.  
  11917.         LD      BC,$1018        ; prepare priority $10, operation code 'val$' -
  11918.                                 ; bits 6 and 7 reset for string result and
  11919.                                 ; string operand.
  11920.        
  11921.         CP      $AE             ; is it 'VAL$' ?
  11922.         JR      Z,L270D         ; forward if so to S-PUSH-PO
  11923.  
  11924.         SUB     $AF             ; subtract token 'CODE' value to reduce
  11925.                                 ; functions 'CODE' to 'NOT' although the
  11926.                                 ; upper range is, as yet, unchecked.
  11927.                                 ; valid range would be $00 - $14.
  11928.  
  11929.         JP      C,L1C8A         ; jump back to REPORT-C with anything else
  11930.                                 ; 'Nonsense in BASIC'
  11931.  
  11932.         LD      BC,$04F0        ; prepare priority $04, operation $C0 +
  11933.                                 ; 'not' ($30)
  11934.  
  11935.         CP      $14             ; is it 'NOT'
  11936.         JR      Z,L270D         ; forward to S-PUSH-PO if so
  11937.  
  11938.         JP      NC,L1C8A        ; to REPORT-C if higher
  11939.                                 ; 'Nonsense in BASIC'
  11940.  
  11941.         LD      B,$10           ; priority $10 for all the rest
  11942.         ADD     A,$DC           ; make range $DC - $EF
  11943.                                 ; $C0 + 'code'($1C) thru 'chr$' ($2F)
  11944.  
  11945.         LD      C,A             ; transfer 'function' to C
  11946.         CP      $DF             ; is it 'sin' ?
  11947.         JR      NC,L2707        ; forward to S-NO-TO-$  with 'sin' through
  11948.                                 ; 'chr$' as operand is numeric.
  11949.  
  11950. ; all the rest 'cos' through 'chr$' give a numeric result except 'str$'
  11951. ; and 'chr$'.
  11952.  
  11953.         RES     6,C             ; signal string operand for 'code', 'val' and
  11954.                                 ; 'len'.
  11955.  
  11956. ;; S-NO-TO-$
  11957. L2707:  CP      $EE             ; compare 'str$'
  11958.         JR      C,L270D         ; forward to S-PUSH-PO if lower as result
  11959.                                 ; is numeric.
  11960.  
  11961.         RES     7,C             ; reset bit 7 of op code for 'str$', 'chr$'
  11962.                                 ; as result is string.
  11963.  
  11964. ; >> This is where they were all headed for.
  11965.  
  11966. ;; S-PUSH-PO
  11967. L270D:  PUSH    BC              ; push the priority and calculator operation
  11968.                                 ; code.
  11969.  
  11970.         RST     20H             ; NEXT-CHAR
  11971.         JP      L24FF           ; jump back to S-LOOP-1 to go round the loop
  11972.                                 ; again with the next character.
  11973.  
  11974. ; --------------------------------
  11975.  
  11976. ; ===>  there were many branches forward to here
  11977.  
  11978. ;; S-CONT-2
  11979. L2712:  RST     18H             ; GET-CHAR
  11980.  
  11981. ;; S-CONT-3
  11982. L2713:  CP      $28             ; is it '(' ?
  11983.         JR      NZ,L2723        ; forward to S-OPERTR if not    >
  11984.  
  11985.         BIT     6,(IY+$01)      ; test FLAGS - numeric or string result ?
  11986.         JR      NZ,L2734        ; forward to S-LOOP if numeric to evaluate  >
  11987.  
  11988. ; if a string preceded '(' then slice it.
  11989.  
  11990.         CALL    L2A52           ; routine SLICING
  11991.  
  11992.         RST     20H             ; NEXT-CHAR
  11993.         JR      L2713           ; back to S-CONT-3
  11994.  
  11995. ; ---------------------------
  11996.  
  11997. ; the branch was here when possibility of an operator '(' has been excluded.
  11998.  
  11999. ;; S-OPERTR
  12000. L2723:  LD      B,$00           ; prepare to add
  12001.         LD      C,A             ; possible operator to C
  12002.         LD      HL,L2795        ; Address: $2795 - tbl-of-ops
  12003.         CALL    L16DC           ; routine INDEXER
  12004.         JR      NC,L2734        ; forward to S-LOOP if not in table
  12005.  
  12006. ; but if found in table the priority has to be looked up.
  12007.  
  12008.         LD      C,(HL)          ; operation code to C ( B is still zero )
  12009.         LD      HL,L27B0 - $C3  ; $26ED is base of table
  12010.         ADD     HL,BC           ; index into table.
  12011.         LD      B,(HL)          ; priority to B.
  12012.  
  12013. ; ------------------
  12014. ; Scanning main loop
  12015. ; ------------------
  12016. ; the juggling act
  12017.  
  12018. ;; S-LOOP
  12019. L2734:  POP     DE              ; fetch last priority and operation
  12020.         LD      A,D             ; priority to A
  12021.         CP      B               ; compare with this one
  12022.         JR      C,L2773         ; forward to S-TIGHTER to execute the
  12023.                                 ; last operation before this one as it has
  12024.                                 ; higher priority.
  12025.  
  12026. ; the last priority was greater or equal this one.
  12027.  
  12028.         AND     A               ; if it is zero then so is this
  12029.         JP      Z,L0018         ; jump to exit via get-char pointing at
  12030.                                 ; next character.
  12031.                                 ; This may be the character after the
  12032.                                 ; expression or, if exiting a recursive call,
  12033.                                 ; the next part of the expression to be
  12034.                                 ; evaluated.
  12035.  
  12036.         PUSH    BC              ; save current priority/operation
  12037.                                 ; as it has lower precedence than the one
  12038.                                 ; now in DE.
  12039.  
  12040. ; the 'USR' function is special in that it is overloaded to give two types
  12041. ; of result.
  12042.  
  12043.         LD      HL,$5C3B        ; address FLAGS
  12044.         LD      A,E             ; new operation to A register
  12045.         CP      $ED             ; is it $C0 + 'usr-no' ($2D)  ?
  12046.         JR      NZ,L274C        ; forward to S-STK-LST if not
  12047.  
  12048.         BIT     6,(HL)          ; string result expected ?
  12049.                                 ; (from the lower priority operand we've
  12050.                                 ; just pushed on stack )
  12051.         JR      NZ,L274C        ; forward to S-STK-LST if numeric
  12052.                                 ; as operand bits match.
  12053.  
  12054.         LD      E,$99           ; reset bit 6 and substitute $19 'usr-$'
  12055.                                 ; for string operand.
  12056.  
  12057. ;; S-STK-LST
  12058. L274C:  PUSH    DE              ; now stack this priority/operation
  12059.         CALL    L2530           ; routine SYNTAX-Z
  12060.         JR      Z,L275B         ; forward to S-SYNTEST if checking syntax.
  12061.  
  12062.         LD      A,E             ; fetch the operation code
  12063.         AND     $3F             ; mask off the result/operand bits to leave
  12064.                                 ; a calculator literal.
  12065.         LD      B,A             ; transfer to B register
  12066.  
  12067. ; now use the calculator to perform the single operation - operand is on
  12068. ; the calculator stack.
  12069. ; Note. although the calculator is performing a single operation most
  12070. ; functions e.g. TAN are written using other functions and literals and
  12071. ; these in turn are written using further strings of calculator literals so
  12072. ; another level of magical recursion joins the juggling act for a while
  12073. ; as the calculator too is calling itself.
  12074.  
  12075.         RST     28H             ;; FP-CALC
  12076.         DB    $3B             ;;fp-calc-2
  12077. L2758:  DB    $38             ;;end-calc
  12078.  
  12079.         JR      L2764           ; forward to S-RUNTEST
  12080.  
  12081. ; ---
  12082.  
  12083. ; the branch was here if checking syntax only.
  12084.  
  12085. ;; S-SYNTEST
  12086. L275B:  LD      A,E             ; fetch the operation code to accumulator
  12087.         XOR     (IY+$01)        ; compare with bits of FLAGS
  12088.         AND     $40             ; bit 6 will be zero now if operand
  12089.                                 ; matched expected result.
  12090.  
  12091. ;; S-RPORT-C2
  12092. L2761:  JP      NZ,L1C8A        ; to REPORT-C if mismatch
  12093.                                 ; 'Nonsense in BASIC'
  12094.                                 ; else continue to set flags for next
  12095.  
  12096. ; the branch is to here in runtime after a successful operation.
  12097.  
  12098. ;; S-RUNTEST
  12099. L2764:  POP     DE              ; fetch the last operation from stack
  12100.         LD      HL,$5C3B        ; address FLAGS
  12101.         SET     6,(HL)          ; set default to numeric result in FLAGS
  12102.         BIT     7,E             ; test the operational result
  12103.         JR      NZ,L2770        ; forward to S-LOOPEND if numeric
  12104.  
  12105.         RES     6,(HL)          ; reset bit 6 of FLAGS to show string result.
  12106.  
  12107. ;; S-LOOPEND
  12108. L2770:  POP     BC              ; fetch the previous priority/operation
  12109.         JR      L2734           ; back to S-LOOP to perform these
  12110.  
  12111. ; ---
  12112.  
  12113. ; the branch was here when a stacked priority/operator had higher priority
  12114. ; than the current one.
  12115.  
  12116. ;; S-TIGHTER
  12117. L2773:  PUSH    DE              ; save high priority op on stack again
  12118.         LD      A,C             ; fetch lower priority operation code
  12119.         BIT     6,(IY+$01)      ; test FLAGS - Numeric or string result ?
  12120.         JR      NZ,L2790        ; forward to S-NEXT if numeric result
  12121.  
  12122. ; if this is lower priority yet has string then must be a comparison.
  12123. ; Since these can only be evaluated in context and were defaulted to
  12124. ; numeric in operator look up they must be changed to string equivalents.
  12125.  
  12126.         AND     $3F             ; mask to give true calculator literal
  12127.         ADD     A,$08           ; augment numeric literals to string
  12128.                                 ; equivalents.
  12129.                                 ; 'no-&-no'  => 'str-&-no'
  12130.                                 ; 'no-l-eql' => 'str-l-eql'
  12131.                                 ; 'no-gr-eq' => 'str-gr-eq'
  12132.                                 ; 'nos-neql' => 'strs-neql'
  12133.                                 ; 'no-grtr'  => 'str-grtr'
  12134.                                 ; 'no-less'  => 'str-less'
  12135.                                 ; 'nos-eql'  => 'strs-eql'
  12136.                                 ; 'addition' => 'strs-add'
  12137.         LD      C,A             ; put modified comparison operator back
  12138.         CP      $10             ; is it now 'str-&-no' ?
  12139.         JR      NZ,L2788        ; forward to S-NOT-AND  if not.
  12140.  
  12141.         SET     6,C             ; set numeric operand bit
  12142.         JR      L2790           ; forward to S-NEXT
  12143.  
  12144. ; ---
  12145.  
  12146. ;; S-NOT-AND
  12147. L2788:  JR      C,L2761         ; back to S-RPORT-C2 if less
  12148.                                 ; 'Nonsense in BASIC'.
  12149.                                 ; e.g. a$ * b$
  12150.  
  12151.         CP      $17             ; is it 'strs-add' ?
  12152.         JR      Z,L2790         ; forward to to S-NEXT if so
  12153.                                 ; (bit 6 and 7 are reset)
  12154.  
  12155.         SET     7,C             ; set numeric (Boolean) result for all others
  12156.  
  12157. ;; S-NEXT
  12158. L2790:  PUSH    BC              ; now save this priority/operation on stack
  12159.  
  12160.         RST     20H             ; NEXT-CHAR
  12161.         JP      L24FF           ; jump back to S-LOOP-1
  12162.  
  12163. ; ------------------
  12164. ; Table of operators
  12165. ; ------------------
  12166. ; This table is used to look up the calculator literals associated with
  12167. ; the operator character. The thirteen calculator operations $03 - $0F
  12168. ; have bits 6 and 7 set to signify a numeric result.
  12169. ; Some of these codes and bits may be altered later if the context suggests
  12170. ; a string comparison or operation.
  12171. ; that is '+', '=', '>', '<', '<=', '>=' or '<>'.
  12172.  
  12173. ;; tbl-of-ops
  12174. L2795:  DB    '+', $CF        ;        $C0 + 'addition'
  12175.         DB    '-', $C3        ;        $C0 + 'subtract'
  12176.         DB    '*', $C4        ;        $C0 + 'multiply'
  12177.         DB    '/', $C5        ;        $C0 + 'division'
  12178.         DB    '^', $C6        ;        $C0 + 'to-power'
  12179.         DB    '=', $CE        ;        $C0 + 'nos-eql'
  12180.         DB    '>', $CC        ;        $C0 + 'no-grtr'
  12181.         DB    '<', $CD        ;        $C0 + 'no-less'
  12182.  
  12183.         DB    $C7, $C9        ; '<='   $C0 + 'no-l-eql'
  12184.         DB    $C8, $CA        ; '>='   $C0 + 'no-gr-eql'
  12185.         DB    $C9, $CB        ; '<>'   $C0 + 'nos-neql'
  12186.         DB    $C5, $C7        ; 'OR'   $C0 + 'or'
  12187.         DB    $C6, $C8        ; 'AND'  $C0 + 'no-&-no'
  12188.  
  12189.         DB    $00             ; zero end-marker.
  12190.  
  12191.  
  12192. ; -------------------
  12193. ; Table of priorities
  12194. ; -------------------
  12195. ; This table is indexed with the operation code obtained from the above
  12196. ; table $C3 - $CF to obtain the priority for the respective operation.
  12197.  
  12198. ;; tbl-priors
  12199. L27B0:  DB    $06             ; '-'   opcode $C3
  12200.         DB    $08             ; '*'   opcode $C4
  12201.         DB    $08             ; '/'   opcode $C5
  12202.         DB    $0A             ; '^'   opcode $C6
  12203.         DB    $02             ; 'OR'  opcode $C7
  12204.         DB    $03             ; 'AND' opcode $C8
  12205.         DB    $05             ; '<='  opcode $C9
  12206.         DB    $05             ; '>='  opcode $CA
  12207.         DB    $05             ; '<>'  opcode $CB
  12208.         DB    $05             ; '>'   opcode $CC
  12209.         DB    $05             ; '<'   opcode $CD
  12210.         DB    $05             ; '='   opcode $CE
  12211.         DB    $06             ; '+'   opcode $CF
  12212.  
  12213. ; ----------------------
  12214. ; Scanning function (FN)
  12215. ; ----------------------
  12216. ; This routine deals with user-defined functions.
  12217. ; The definition can be anywhere in the program area but these are best
  12218. ; placed near the start of the program as we shall see.
  12219. ; The evaluation process is quite complex as the Spectrum has to parse two
  12220. ; statements at the same time. Syntax of both has been checked previously
  12221. ; and hidden locations have been created immediately after each argument
  12222. ; of the DEF FN statement. Each of the arguments of the FN function is
  12223. ; evaluated by SCANNING and placed in the hidden locations. Then the
  12224. ; expression to the right of the DEF FN '=' is evaluated by SCANNING and for
  12225. ; any variables encountered, a search is made in the DEF FN variable list
  12226. ; in the program area before searching in the normal variables area.
  12227. ;
  12228. ; Recursion is not allowed: i.e. the definition of a function should not use
  12229. ; the same function, either directly or indirectly ( through another function).
  12230. ; You'll normally get error 4, ('Out of memory'), although sometimes the sytem
  12231. ; will crash. - Vickers, Pitman 1984.
  12232. ;
  12233. ; As the definition is just an expression, there would seem to be no means
  12234. ; of breaking out of such recursion.
  12235. ; However, by the clever use of string expressions and VAL, such recursion is
  12236. ; possible.
  12237. ; e.g. DEF FN a(n) = VAL "n+FN a(n-1)+0" ((n<1) * 10 + 1 TO )
  12238. ; will evaluate the full 11-character expression for all values where n is
  12239. ; greater than zero but just the 11th character, "0", when n drops to zero
  12240. ; thereby ending the recursion producing the correct result.
  12241. ; Recursive string functions are possible using VAL$ instead of VAL and the
  12242. ; null string as the final addend.
  12243. ; - from a turn of the century newsgroup discussion initiated by Mike Wynne.
  12244.  
  12245. ;; S-FN-SBRN
  12246. L27BD:  CALL    L2530           ; routine SYNTAX-Z
  12247.         JR      NZ,L27F7        ; forward to SF-RUN in runtime
  12248.  
  12249.  
  12250.         RST     20H             ; NEXT-CHAR
  12251.         CALL    L2C8D           ; routine ALPHA check for letters A-Z a-z
  12252.         JP      NC,L1C8A        ; jump back to REPORT-C if not
  12253.                                 ; 'Nonsense in BASIC'
  12254.  
  12255.  
  12256.         RST     20H             ; NEXT-CHAR
  12257.         CP      $24             ; is it '$' ?
  12258.         PUSH    AF              ; save character and flags
  12259.         JR      NZ,L27D0        ; forward to SF-BRKT-1 with numeric function
  12260.  
  12261.  
  12262.         RST     20H             ; NEXT-CHAR
  12263.  
  12264. ;; SF-BRKT-1
  12265. L27D0:  CP      $28             ; is '(' ?
  12266.         JR      NZ,L27E6        ; forward to SF-RPRT-C if not
  12267.                                 ; 'Nonsense in BASIC'
  12268.  
  12269.  
  12270.         RST     20H             ; NEXT-CHAR
  12271.         CP      $29             ; is it ')' ?
  12272.         JR      Z,L27E9         ; forward to SF-FLAG-6 if no arguments.
  12273.  
  12274. ;; SF-ARGMTS
  12275. L27D9:  CALL    L24FB           ; routine SCANNING checks each argument
  12276.                                 ; which may be an expression.
  12277.  
  12278.         RST     18H             ; GET-CHAR
  12279.         CP      $2C             ; is it a ',' ?
  12280.         JR      NZ,L27E4        ; forward if not to SF-BRKT-2 to test bracket
  12281.  
  12282.  
  12283.         RST     20H             ; NEXT-CHAR if a comma was found
  12284.         JR      L27D9           ; back to SF-ARGMTS to parse all arguments.
  12285.  
  12286. ; ---
  12287.  
  12288. ;; SF-BRKT-2
  12289. L27E4:  CP      $29             ; is character the closing ')' ?
  12290.  
  12291. ;; SF-RPRT-C
  12292. L27E6:  JP      NZ,L1C8A        ; jump to REPORT-C
  12293.                                 ; 'Nonsense in BASIC'
  12294.  
  12295. ; at this point any optional arguments have had their syntax checked.
  12296.  
  12297. ;; SF-FLAG-6
  12298. L27E9:  RST     20H             ; NEXT-CHAR
  12299.         LD      HL,$5C3B        ; address system variable FLAGS
  12300.         RES     6,(HL)          ; signal string result
  12301.         POP     AF              ; restore test against '$'.
  12302.         JR      Z,L27F4         ; forward to SF-SYN-EN if string function.
  12303.  
  12304.         SET     6,(HL)          ; signal numeric result
  12305.  
  12306. ;; SF-SYN-EN
  12307. L27F4:  JP      L2712           ; jump back to S-CONT-2 to continue scanning.
  12308.  
  12309. ; ---
  12310.  
  12311. ; the branch was here in runtime.
  12312.  
  12313. ;; SF-RUN
  12314. L27F7:  RST     20H             ; NEXT-CHAR fetches name
  12315.         AND     $DF             ; AND 11101111 - reset bit 5 - upper-case.
  12316.         LD      B,A             ; save in B
  12317.  
  12318.         RST     20H             ; NEXT-CHAR
  12319.         SUB     $24             ; subtract '$'
  12320.         LD      C,A             ; save result in C
  12321.         JR      NZ,L2802        ; forward if not '$' to SF-ARGMT1
  12322.  
  12323.         RST     20H             ; NEXT-CHAR advances to bracket
  12324.  
  12325. ;; SF-ARGMT1
  12326. L2802:  RST     20H             ; NEXT-CHAR advances to start of argument
  12327.         PUSH    HL              ; save address
  12328.         LD      HL,($5C53)      ; fetch start of program area from PROG
  12329.         DEC     HL              ; the search starting point is the previous
  12330.                                 ; location.
  12331.  
  12332. ;; SF-FND-DF
  12333. L2808:  LD      DE,$00CE        ; search is for token 'DEF FN' in E,
  12334.                                 ; statement count in D.
  12335.         PUSH    BC              ; save C the string test, and B the letter.
  12336.         CALL    L1D86           ; routine LOOK-PROG will search for token.
  12337.         POP     BC              ; restore BC.
  12338.         JR      NC,L2814        ; forward to SF-CP-DEF if a match was found.
  12339.  
  12340.  
  12341. ;; REPORT-P
  12342. L2812:  RST     08H             ; ERROR-1
  12343.         DB    $18             ; Error Report: FN without DEF
  12344.  
  12345. ;; SF-CP-DEF
  12346. L2814:  PUSH    HL              ; save address of DEF FN
  12347.         CALL    L28AB           ; routine FN-SKPOVR skips over white-space etc.
  12348.                                 ; without disturbing CH-ADD.
  12349.         AND     $DF             ; make fetched character upper-case.
  12350.         CP      B               ; compare with FN name
  12351.         JR      NZ,L2825        ; forward to SF-NOT-FD if no match.
  12352.  
  12353. ; the letters match so test the type.
  12354.  
  12355.         CALL    L28AB           ; routine FN-SKPOVR skips white-space
  12356.         SUB     $24             ; subtract '$' from fetched character
  12357.         CP      C               ; compare with saved result of same operation
  12358.                                 ; on FN name.
  12359.         JR      Z,L2831         ; forward to SF-VALUES with a match.
  12360.  
  12361. ; the letters matched but one was string and the other numeric.
  12362.  
  12363. ;; SF-NOT-FD
  12364. L2825:  POP     HL              ; restore search point.
  12365.         DEC     HL              ; make location before
  12366.         LD      DE,$0200        ; the search is to be for the end of the
  12367.                                 ; current definition - 2 statements forward.
  12368.         PUSH    BC              ; save the letter/type
  12369.         CALL    L198B           ; routine EACH-STMT steps past rejected
  12370.                                 ; definition.
  12371.         POP     BC              ; restore letter/type
  12372.         JR      L2808           ; back to SF-FND-DF to continue search
  12373.  
  12374. ; ---
  12375.  
  12376. ; Success!
  12377. ; the branch was here with matching letter and numeric/string type.
  12378.  
  12379. ;; SF-VALUES
  12380. L2831:  AND     A               ; test A ( will be zero if string '$' - '$' )
  12381.  
  12382.         CALL    Z,L28AB         ; routine FN-SKPOVR advances HL past '$'.
  12383.  
  12384.         POP     DE              ; discard pointer to 'DEF FN'.
  12385.         POP     DE              ; restore pointer to first FN argument.
  12386.         LD      ($5C5D),DE      ; save in CH_ADD
  12387.  
  12388.         CALL    L28AB           ; routine FN-SKPOVR advances HL past '('
  12389.         PUSH    HL              ; save start address in DEF FN  ***
  12390.         CP      $29             ; is character a ')' ?
  12391.         JR      Z,L2885         ; forward to SF-R-BR-2 if no arguments.
  12392.  
  12393. ;; SF-ARG-LP
  12394. L2843:  INC     HL              ; point to next character.
  12395.         LD      A,(HL)          ; fetch it.
  12396.         CP      $0E             ; is it the number marker
  12397.         LD      D,$40           ; signal numeric in D.
  12398.         JR      Z,L2852         ; forward to SF-ARG-VL if numeric.
  12399.  
  12400.         DEC     HL              ; back to letter
  12401.         CALL    L28AB           ; routine FN-SKPOVR skips any white-space
  12402.         INC     HL              ; advance past the expected '$' to
  12403.                                 ; the 'hidden' marker.
  12404.         LD      D,$00           ; signal string.
  12405.  
  12406. ;; SF-ARG-VL
  12407. L2852:  INC     HL              ; now address first of 5-byte location.
  12408.         PUSH    HL              ; save address in DEF FN statement
  12409.         PUSH    DE              ; save D - result type
  12410.  
  12411.         CALL    L24FB           ; routine SCANNING evaluates expression in
  12412.                                 ; the FN statement setting FLAGS and leaving
  12413.                                 ; result as last value on calculator stack.
  12414.  
  12415.         POP     AF              ; restore saved result type to A
  12416.  
  12417.         XOR     (IY+$01)        ; xor with FLAGS
  12418.         AND     $40             ; and with 01000000 to test bit 6
  12419.         JR      NZ,L288B        ; forward to REPORT-Q if type mismatch.
  12420.                                 ; 'Parameter error'
  12421.  
  12422.         POP     HL              ; pop the start address in DEF FN statement
  12423.         EX      DE,HL           ; transfer to DE ?? pop straight into de ?
  12424.  
  12425.         LD      HL,($5C65)      ; set HL to STKEND location after value
  12426.         LD      BC,$0005        ; five bytes to move
  12427.         SBC     HL,BC           ; decrease HL by 5 to point to start.
  12428.         LD      ($5C65),HL      ; set STKEND 'removing' value from stack.
  12429.  
  12430.         LDIR                    ; copy value into DEF FN statement
  12431.         EX      DE,HL           ; set HL to location after value in DEF FN
  12432.         DEC     HL              ; step back one
  12433.         CALL    L28AB           ; routine FN-SKPOVR gets next valid character
  12434.         CP      $29             ; is it ')' end of arguments ?
  12435.         JR      Z,L2885         ; forward to SF-R-BR-2 if so.
  12436.  
  12437. ; a comma separator has been encountered in the DEF FN argument list.
  12438.  
  12439.         PUSH    HL              ; save position in DEF FN statement
  12440.  
  12441.         RST     18H             ; GET-CHAR from FN statement
  12442.         CP      $2C             ; is it ',' ?
  12443.         JR      NZ,L288B        ; forward to REPORT-Q if not
  12444.                                 ; 'Parameter error'
  12445.  
  12446.         RST     20H             ; NEXT-CHAR in FN statement advances to next
  12447.                                 ; argument.
  12448.  
  12449.         POP     HL              ; restore DEF FN pointer
  12450.         CALL    L28AB           ; routine FN-SKPOVR advances to corresponding
  12451.                                 ; argument.
  12452.  
  12453.         JR      L2843           ; back to SF-ARG-LP looping until all
  12454.                                 ; arguments are passed into the DEF FN
  12455.                                 ; hidden locations.
  12456.  
  12457. ; ---
  12458.  
  12459. ; the branch was here when all arguments passed.
  12460.  
  12461. ;; SF-R-BR-2
  12462. L2885:  PUSH    HL              ; save location of ')' in DEF FN
  12463.  
  12464.         RST     18H             ; GET-CHAR gets next character in FN
  12465.         CP      $29             ; is it a ')' also ?
  12466.         JR      Z,L288D         ; forward to SF-VALUE if so.
  12467.  
  12468.  
  12469. ;; REPORT-Q
  12470. L288B:  RST     08H             ; ERROR-1
  12471.         DB    $19             ; Error Report: Parameter error
  12472.  
  12473. ;; SF-VALUE
  12474. L288D:  POP     DE              ; location of ')' in DEF FN to DE.
  12475.         EX      DE,HL           ; now to HL, FN ')' pointer to DE.
  12476.         LD      ($5C5D),HL      ; initialize CH_ADD to this value.
  12477.  
  12478. ; At this point the start of the DEF FN argument list is on the machine stack.
  12479. ; We also have to consider that this defined function may form part of the
  12480. ; definition of another defined function (though not itself).
  12481. ; As this defined function may be part of a hierarchy of defined functions
  12482. ; currently being evaluated by recursive calls to SCANNING, then we have to
  12483. ; preserve the original value of DEFADD and not assume that it is zero.
  12484.  
  12485.         LD      HL,($5C0B)      ; get original DEFADD address
  12486.         EX      (SP),HL         ; swap with DEF FN address on stack ***
  12487.         LD      ($5C0B),HL      ; set DEFADD to point to this argument list
  12488.                                 ; during scanning.
  12489.  
  12490.         PUSH    DE              ; save FN ')' pointer.
  12491.  
  12492.         RST     20H             ; NEXT-CHAR advances past ')' in define
  12493.  
  12494.         RST     20H             ; NEXT-CHAR advances past '=' to expression
  12495.  
  12496.         CALL    L24FB           ; routine SCANNING evaluates but searches
  12497.                                 ; initially for variables at DEFADD
  12498.  
  12499.         POP     HL              ; pop the FN ')' pointer
  12500.         LD      ($5C5D),HL      ; set CH_ADD to this
  12501.         POP     HL              ; pop the original DEFADD value
  12502.         LD      ($5C0B),HL      ; and re-insert into DEFADD system variable.
  12503.  
  12504.         RST     20H             ; NEXT-CHAR advances to character after ')'
  12505.         JP      L2712           ; to S-CONT-2 - to continue current
  12506.                                 ; invocation of scanning
  12507.  
  12508. ; --------------------
  12509. ; Used to parse DEF FN
  12510. ; --------------------
  12511. ; e.g. DEF FN     s $ ( x )     =  b     $ (  TO  x  ) : REM exaggerated
  12512. ;
  12513. ; This routine is used 10 times to advance along a DEF FN statement
  12514. ; skipping spaces and colour control codes. It is similar to NEXT-CHAR
  12515. ; which is, at the same time, used to skip along the corresponding FN function
  12516. ; except the latter has to deal with AT and TAB characters in string
  12517. ; expressions. These cannot occur in a program area so this routine is
  12518. ; simpler as both colour controls and their parameters are less than space.
  12519.  
  12520. ;; FN-SKPOVR
  12521. L28AB:  INC     HL              ; increase pointer
  12522.         LD      A,(HL)          ; fetch addressed character
  12523.         CP      $21             ; compare with space + 1
  12524.         JR      C,L28AB         ; back to FN-SKPOVR if less
  12525.  
  12526.         RET                     ; return pointing to a valid character.
  12527.  
  12528. ; ---------
  12529. ; LOOK-VARS
  12530. ; ---------
  12531. ;
  12532. ;
  12533.  
  12534. ;; LOOK-VARS
  12535. L28B2:  SET     6,(IY+$01)      ; update FLAGS - presume numeric result
  12536.  
  12537.         RST     18H             ; GET-CHAR
  12538.         CALL    L2C8D           ; routine ALPHA tests for A-Za-z
  12539.         JP      NC,L1C8A        ; jump to REPORT-C if not.
  12540.                                 ; 'Nonsense in BASIC'
  12541.  
  12542.         PUSH    HL              ; save pointer to first letter       ^1
  12543.         AND     $1F             ; mask lower bits, 1 - 26 decimal     000xxxxx
  12544.         LD      C,A             ; store in C.
  12545.  
  12546.         RST     20H             ; NEXT-CHAR
  12547.         PUSH    HL              ; save pointer to second character   ^2
  12548.         CP      $28             ; is it '(' - an array ?
  12549.         JR      Z,L28EF         ; forward to V-RUN/SYN if so.
  12550.  
  12551.         SET     6,C             ; set 6 signaling string if solitary  010
  12552.         CP      $24             ; is character a '$' ?
  12553.         JR      Z,L28DE         ; forward to V-STR-VAR
  12554.  
  12555.         SET     5,C             ; signal numeric                       011
  12556.         CALL    L2C88           ; routine ALPHANUM sets carry if second
  12557.                                 ; character is alphanumeric.
  12558.         JR      NC,L28E3        ; forward to V-TEST-FN if just one character
  12559.  
  12560. ; it is more than one character but re-test current character so that 6 reset
  12561. ; Note. this is a rare lack of elegance. Bit 6 could be reset once before
  12562. ; entering the loop. Another puzzle is that this loop renders the similar
  12563. ; loop at V-PASS redundant.
  12564.  
  12565. ;; V-CHAR
  12566. L28D4:  CALL    L2C88           ; routine ALPHANUM
  12567.         JR      NC,L28EF        ; to V-RUN/SYN when no more
  12568.  
  12569.         RES     6,C             ; make long named type                 001
  12570.  
  12571.         RST     20H             ; NEXT-CHAR
  12572.         JR      L28D4           ; loop back to V-CHAR
  12573.  
  12574. ; ---
  12575.  
  12576.  
  12577. ;; V-STR-VAR
  12578. L28DE:  RST     20H             ; NEXT-CHAR advances past '$'
  12579.         RES     6,(IY+$01)      ; update FLAGS - signal string result.
  12580.  
  12581. ;; V-TEST-FN
  12582. L28E3:  LD      A,($5C0C)       ; load A with DEFADD_hi
  12583.         AND     A               ; and test for zero.
  12584.         JR      Z,L28EF         ; forward to V-RUN/SYN if a defined function
  12585.                                 ; is not being evaluated.
  12586.  
  12587. ; Note.
  12588.  
  12589.         CALL    L2530           ; routine SYNTAX-Z
  12590.         JP      NZ,L2951        ; JUMP to STK-F-ARG in runtime and then
  12591.                                 ; back to this point if no variable found.
  12592.  
  12593. ;; V-RUN/SYN
  12594. L28EF:  LD      B,C             ; save flags in B
  12595.         CALL    L2530           ; routine SYNTAX-Z
  12596.         JR      NZ,L28FD        ; to V-RUN to look for the variable in runtime
  12597.  
  12598. ; if checking syntax the letter is not returned
  12599.  
  12600.         LD      A,C             ; copy letter/flags to A
  12601.         AND     $E0             ; and with 11100000 to get rid of the letter
  12602.         SET     7,A             ; use spare bit to signal checking syntax.
  12603.         LD      C,A             ; and transfer to C.
  12604.         JR      L2934           ; forward to V-SYNTAX
  12605.  
  12606. ; ---
  12607.  
  12608. ; but in runtime search for the variable.
  12609.  
  12610. ;; V-RUN
  12611. L28FD:  LD      HL,($5C4B)      ; set HL to start of variables from VARS
  12612.  
  12613. ;; V-EACH
  12614. L2900:  LD      A,(HL)          ; get first character
  12615.         AND     $7F             ; and with 01111111
  12616.                                 ; ignoring bit 7 which distinguishes
  12617.                                 ; arrays or for/next variables.
  12618.  
  12619.         JR      Z,L2932         ; to V-80-BYTE if zero as must be 10000000
  12620.                                 ; the variables end-marker.
  12621.  
  12622.         CP      C               ; compare with supplied value.
  12623.         JR      NZ,L292A        ; forward to V-NEXT if no match.
  12624.  
  12625.         RLA                     ; destructively test
  12626.         ADD     A,A             ; bits 5 and 6 of A
  12627.                                 ; jumping if bit 5 reset or 6 set
  12628.  
  12629.         JP      P,L293F         ; to V-FOUND-2  strings and arrays
  12630.  
  12631.         JR      C,L293F         ; to V-FOUND-2  simple and for next
  12632.  
  12633. ; leaving long name variables.
  12634.  
  12635.         POP     DE              ; pop pointer to 2nd. char
  12636.         PUSH    DE              ; save it again
  12637.         PUSH    HL              ; save variable first character pointer
  12638.  
  12639. ;; V-MATCHES
  12640. L2912:  INC     HL              ; address next character in vars area
  12641.  
  12642. ;; V-SPACES
  12643. L2913:  LD      A,(DE)          ; pick up letter from prog area
  12644.         INC     DE              ; and advance address
  12645.         CP      $20             ; is it a space
  12646.         JR      Z,L2913         ; back to V-SPACES until non-space
  12647.  
  12648.         OR      $20             ; convert to range 1 - 26.
  12649.         CP      (HL)            ; compare with addressed variables character
  12650.         JR      Z,L2912         ; loop back to V-MATCHES if a match on an
  12651.                                 ; intermediate letter.
  12652.  
  12653.         OR      $80             ; now set bit 7 as last character of long
  12654.                                 ; names are inverted.
  12655.         CP      (HL)            ; compare again
  12656.         JR      NZ,L2929        ; forward to V-GET-PTR if no match
  12657.  
  12658. ; but if they match check that this is also last letter in prog area
  12659.  
  12660.         LD      A,(DE)          ; fetch next character
  12661.         CALL    L2C88           ; routine ALPHANUM sets carry if not alphanum
  12662.         JR      NC,L293E        ; forward to V-FOUND-1 with a full match.
  12663.  
  12664. ;; V-GET-PTR
  12665. L2929:  POP     HL              ; pop saved pointer to char 1
  12666.  
  12667. ;; V-NEXT
  12668. L292A:  PUSH    BC              ; save flags
  12669.         CALL    L19B8           ; routine NEXT-ONE gets next variable in DE
  12670.         EX      DE,HL           ; transfer to HL.
  12671.         POP     BC              ; restore the flags
  12672.         JR      L2900           ; loop back to V-EACH
  12673.                                 ; to compare each variable
  12674.  
  12675. ; ---
  12676.  
  12677. ;; V-80-BYTE
  12678. L2932:  SET     7,B             ; will signal not found
  12679.  
  12680. ; the branch was here when checking syntax
  12681.  
  12682. ;; V-SYNTAX
  12683. L2934:  POP     DE              ; discard the pointer to 2nd. character  v2
  12684.                                 ; in BASIC line/workspace.
  12685.  
  12686.         RST     18H             ; GET-CHAR gets character after variable name.
  12687.         CP      $28             ; is it '(' ?
  12688.         JR      Z,L2943         ; forward to V-PASS
  12689.                                 ; Note. could go straight to V-END ?
  12690.  
  12691.         SET     5,B             ; signal not an array
  12692.         JR      L294B           ; forward to V-END
  12693.  
  12694. ; ---------------------------
  12695.  
  12696. ; the jump was here when a long name matched and HL pointing to last character
  12697. ; in variables area.
  12698.  
  12699. ;; V-FOUND-1
  12700. L293E:  POP     DE              ; discard pointer to first var letter
  12701.  
  12702. ; the jump was here with all other matches HL points to first var char.
  12703.  
  12704. ;; V-FOUND-2
  12705. L293F:  POP     DE              ; discard pointer to 2nd prog char       v2
  12706.         POP     DE              ; drop pointer to 1st prog char          v1
  12707.         PUSH    HL              ; save pointer to last char in vars
  12708.  
  12709.         RST     18H             ; GET-CHAR
  12710.  
  12711. ;; V-PASS
  12712. L2943:  CALL    L2C88           ; routine ALPHANUM
  12713.         JR      NC,L294B        ; forward to V-END if not
  12714.  
  12715. ; but it never will be as we advanced past long-named variables earlier.
  12716.  
  12717.         RST     20H             ; NEXT-CHAR
  12718.         JR      L2943           ; back to V-PASS
  12719.  
  12720. ; ---
  12721.  
  12722. ;; V-END
  12723. L294B:  POP     HL              ; pop the pointer to first character in
  12724.                                 ; BASIC line/workspace.
  12725.         RL      B               ; rotate the B register left
  12726.                                 ; bit 7 to carry
  12727.         BIT     6,B             ; test the array indicator bit.
  12728.         RET                     ; return
  12729.  
  12730. ; -----------------------
  12731. ; Stack function argument
  12732. ; -----------------------
  12733. ; This branch is taken from LOOK-VARS when a defined function is currently
  12734. ; being evaluated.
  12735. ; Scanning is evaluating the expression after the '=' and the variable
  12736. ; found could be in the argument list to the left of the '=' or in the
  12737. ; normal place after the program. Preference will be given to the former.
  12738. ; The variable name to be matched is in C.
  12739.  
  12740. ;; STK-F-ARG
  12741. L2951:  LD      HL,($5C0B)      ; set HL to DEFADD
  12742.         LD      A,(HL)          ; load the first character
  12743.         CP      $29             ; is it ')' ?
  12744.         JP      Z,L28EF         ; JUMP back to V-RUN/SYN, if so, as there are
  12745.                                 ; no arguments.
  12746.  
  12747. ; but proceed to search argument list of defined function first if not empty.
  12748.  
  12749. ;; SFA-LOOP
  12750. L295A:  LD      A,(HL)          ; fetch character again.
  12751.         OR      $60             ; or with 01100000 presume a simple variable.
  12752.         LD      B,A             ; save result in B.
  12753.         INC     HL              ; address next location.
  12754.         LD      A,(HL)          ; pick up byte.
  12755.         CP      $0E             ; is it the number marker ?
  12756.         JR      Z,L296B         ; forward to SFA-CP-VR if so.
  12757.  
  12758. ; it was a string. White-space may be present but syntax has been checked.
  12759.  
  12760.         DEC     HL              ; point back to letter.
  12761.         CALL    L28AB           ; routine FN-SKPOVR skips to the '$'
  12762.         INC     HL              ; now address the hidden marker.
  12763.         RES     5,B             ; signal a string variable.
  12764.  
  12765. ;; SFA-CP-VR
  12766. L296B:  LD      A,B             ; transfer found variable letter to A.
  12767.         CP      C               ; compare with expected.
  12768.         JR      Z,L2981         ; forward to SFA-MATCH with a match.
  12769.  
  12770.         INC     HL              ; step
  12771.         INC     HL              ; past
  12772.         INC     HL              ; the
  12773.         INC     HL              ; five
  12774.         INC     HL              ; bytes.
  12775.  
  12776.         CALL    L28AB           ; routine FN-SKPOVR skips to next character
  12777.         CP      $29             ; is it ')' ?
  12778.         JP      Z,L28EF         ; jump back if so to V-RUN/SYN to look in
  12779.                                 ; normal variables area.
  12780.  
  12781.         CALL    L28AB           ; routine FN-SKPOVR skips past the ','
  12782.                                 ; all syntax has been checked and these
  12783.                                 ; things can be taken as read.
  12784.         JR      L295A           ; back to SFA-LOOP while there are more
  12785.                                 ; arguments.
  12786.  
  12787. ; ---
  12788.  
  12789. ;; SFA-MATCH
  12790. L2981:  BIT     5,C             ; test if numeric
  12791.         JR      NZ,L2991        ; to SFA-END if so as will be stacked
  12792.                                 ; by scanning
  12793.  
  12794.         INC     HL              ; point to start of string descriptor
  12795.         LD      DE,($5C65)      ; set DE to STKEND
  12796.         CALL    L33C0           ; routine MOVE-FP puts parameters on stack.
  12797.         EX      DE,HL           ; new free location to HL.
  12798.         LD      ($5C65),HL      ; use it to set STKEND system variable.
  12799.  
  12800. ;; SFA-END
  12801. L2991:  POP     DE              ; discard
  12802.         POP     DE              ; pointers.
  12803.         XOR     A               ; clear carry flag.
  12804.         INC     A               ; and zero flag.
  12805.         RET                     ; return.
  12806.  
  12807. ; ------------------------
  12808. ; Stack variable component
  12809. ; ------------------------
  12810. ; This is called to evaluate a complex structure that has been found, in
  12811. ; runtime, by LOOK-VARS in the variables area.
  12812. ; In this case HL points to the initial letter, bits 7-5
  12813. ; of which indicate the type of variable.
  12814. ; 010 - simple string, 110 - string array, 100 - array of numbers.
  12815. ;
  12816. ; It is called from CLASS-01 when assigning to a string or array including
  12817. ; a slice.
  12818. ; It is called from SCANNING to isolate the required part of the structure.
  12819. ;
  12820. ; An important part of the runtime process is to check that the number of
  12821. ; dimensions of the variable match the number of subscripts supplied in the
  12822. ; BASIC line.
  12823. ;
  12824. ; If checking syntax,
  12825. ; the B register, which counts dimensions is set to zero (256) to allow
  12826. ; the loop to continue till all subscripts are checked. While doing this it
  12827. ; is reading dimension sizes from some arbitrary area of memory. Although
  12828. ; these are meaningless it is of no concern as the limit is never checked by
  12829. ; int-exp during syntax checking.
  12830. ;
  12831. ; The routine is also called from the syntax path of DIM command to check the
  12832. ; syntax of both string and numeric arrays definitions except that bit 6 of C
  12833. ; is reset so both are checked as numeric arrays. This ruse avoids a terminal
  12834. ; slice being accepted as part of the DIM command.
  12835. ; All that is being checked is that there are a valid set of comma-separated
  12836. ; expressions before a terminal ')', although, as above, it will still go
  12837. ; through the motions of checking dummy dimension sizes.
  12838.  
  12839. ;; STK-VAR
  12840. L2996:  XOR     A               ; clear A
  12841.         LD      B,A             ; and B, the syntax dimension counter (256)
  12842.         BIT     7,C             ; checking syntax ?
  12843.         JR      NZ,L29E7        ; forward to SV-COUNT if so.
  12844.  
  12845. ; runtime evaluation.
  12846.  
  12847.         BIT     7,(HL)          ; will be reset if a simple string.
  12848.         JR      NZ,L29AE        ; forward to SV-ARRAYS otherwise
  12849.  
  12850.         INC     A               ; set A to 1, simple string.
  12851.  
  12852. ;; SV-SIMPLE$
  12853. L29A1:  INC     HL              ; address length low
  12854.         LD      C,(HL)          ; place in C
  12855.         INC     HL              ; address length high
  12856.         LD      B,(HL)          ; place in B
  12857.         INC     HL              ; address start of string
  12858.         EX      DE,HL           ; DE = start now.
  12859.         CALL    L2AB2           ; routine STK-STO-$ stacks string parameters
  12860.                                 ; DE start in variables area,
  12861.                                 ; BC length, A=1 simple string
  12862.  
  12863. ; the only thing now is to consider if a slice is required.
  12864.  
  12865.         RST     18H             ; GET-CHAR puts character at CH_ADD in A
  12866.         JP      L2A49           ; jump forward to SV-SLICE? to test for '('
  12867.  
  12868. ; --------------------------------------------------------
  12869.  
  12870. ; the branch was here with string and numeric arrays in runtime.
  12871.  
  12872. ;; SV-ARRAYS
  12873. L29AE:  INC     HL              ; step past
  12874.         INC     HL              ; the total length
  12875.         INC     HL              ; to address Number of dimensions.
  12876.         LD      B,(HL)          ; transfer to B overwriting zero.
  12877.         BIT     6,C             ; a numeric array ?
  12878.         JR      Z,L29C0         ; forward to SV-PTR with numeric arrays
  12879.  
  12880.         DEC     B               ; ignore the final element of a string array
  12881.                                 ; the fixed string size.
  12882.  
  12883.         JR      Z,L29A1         ; back to SV-SIMPLE$ if result is zero as has
  12884.                                 ; been created with DIM a$(10) for instance
  12885.                                 ; and can be treated as a simple string.
  12886.  
  12887. ; proceed with multi-dimensioned string arrays in runtime.
  12888.  
  12889.         EX      DE,HL           ; save pointer to dimensions in DE
  12890.  
  12891.         RST     18H             ; GET-CHAR looks at the BASIC line
  12892.         CP      $28             ; is character '(' ?
  12893.         JR      NZ,L2A20        ; to REPORT-3 if not
  12894.                                 ; 'Subscript wrong'
  12895.  
  12896.         EX      DE,HL           ; dimensions pointer to HL to synchronize
  12897.                                 ; with next instruction.
  12898.  
  12899. ; runtime numeric arrays path rejoins here.
  12900.  
  12901. ;; SV-PTR
  12902. L29C0:  EX      DE,HL           ; save dimension pointer in DE
  12903.         JR      L29E7           ; forward to SV-COUNT with true no of dims
  12904.                                 ; in B. As there is no initial comma the
  12905.                                 ; loop is entered at the midpoint.
  12906.  
  12907. ; ----------------------------------------------------------
  12908. ; the dimension counting loop which is entered at mid-point.
  12909.  
  12910. ;; SV-COMMA
  12911. L29C3:  PUSH    HL              ; save counter
  12912.  
  12913.         RST     18H             ; GET-CHAR
  12914.  
  12915.         POP     HL              ; pop counter
  12916.         CP      $2C             ; is character ',' ?
  12917.         JR      Z,L29EA         ; forward to SV-LOOP if so
  12918.  
  12919. ; in runtime the variable definition indicates a comma should appear here
  12920.  
  12921.         BIT     7,C             ; checking syntax ?
  12922.         JR      Z,L2A20         ; forward to REPORT-3 if not
  12923.                                 ; 'Subscript error'
  12924.  
  12925. ; proceed if checking syntax of an array?
  12926.  
  12927.         BIT     6,C             ; array of strings
  12928.         JR      NZ,L29D8        ; forward to SV-CLOSE if so
  12929.  
  12930. ; an array of numbers.
  12931.  
  12932.         CP      $29             ; is character ')' ?
  12933.         JR      NZ,L2A12        ; forward to SV-RPT-C if not
  12934.                                 ; 'Nonsense in BASIC'
  12935.  
  12936.         RST     20H             ; NEXT-CHAR moves CH-ADD past the statement
  12937.         RET                     ; return ->
  12938.  
  12939. ; ---
  12940.  
  12941. ; the branch was here with an array of strings.
  12942.  
  12943. ;; SV-CLOSE
  12944. L29D8:  CP      $29             ; as above ')' could follow the expression
  12945.         JR      Z,L2A48         ; forward to SV-DIM if so
  12946.  
  12947.         CP      $CC             ; is it 'TO' ?
  12948.         JR      NZ,L2A12        ; to SV-RPT-C with anything else
  12949.                                 ; 'Nonsense in BASIC'
  12950.  
  12951. ; now backtrack CH_ADD to set up for slicing routine.
  12952. ; Note. in a BASIC line we can safely backtrack to a colour parameter.
  12953.  
  12954. ;; SV-CH-ADD
  12955. L29E0:  RST     18H             ; GET-CHAR
  12956.         DEC     HL              ; backtrack HL
  12957.         LD      ($5C5D),HL      ; to set CH_ADD up for slicing routine
  12958.         JR      L2A45           ; forward to SV-SLICE and make a return
  12959.                                 ; when all slicing complete.
  12960.  
  12961. ; ----------------------------------------
  12962. ; -> the mid-point entry point of the loop
  12963.  
  12964. ;; SV-COUNT
  12965. L29E7:  LD      HL,$0000        ; initialize data pointer to zero.
  12966.  
  12967. ;; SV-LOOP
  12968. L29EA:  PUSH    HL              ; save the data pointer.
  12969.  
  12970.         RST     20H             ; NEXT-CHAR in BASIC area points to an
  12971.                                 ; expression.
  12972.  
  12973.         POP     HL              ; restore the data pointer.
  12974.         LD      A,C             ; transfer name/type to A.
  12975.         CP      $C0             ; is it 11000000 ?
  12976.                                 ; Note. the letter component is absent if
  12977.                                 ; syntax checking.
  12978.         JR      NZ,L29FB        ; forward to SV-MULT if not an array of
  12979.                                 ; strings.
  12980.  
  12981. ; proceed to check string arrays during syntax.
  12982.  
  12983.         RST     18H             ; GET-CHAR
  12984.         CP      $29             ; ')'  end of subscripts ?
  12985.         JR      Z,L2A48         ; forward to SV-DIM to consider further slice
  12986.  
  12987.         CP      $CC             ; is it 'TO' ?
  12988.         JR      Z,L29E0         ; back to SV-CH-ADD to consider a slice.
  12989.                                 ; (no need to repeat get-char at L29E0)
  12990.  
  12991. ; if neither, then an expression is required so rejoin runtime loop ??
  12992. ; registers HL and DE only point to somewhere meaningful in runtime so
  12993. ; comments apply to that situation.
  12994.  
  12995. ;; SV-MULT
  12996. L29FB:  PUSH    BC              ; save dimension number.
  12997.         PUSH    HL              ; push data pointer/rubbish.
  12998.                                 ; DE points to current dimension.
  12999.         CALL    L2AEE           ; routine DE,(DE+1) gets next dimension in DE
  13000.                                 ; and HL points to it.
  13001.         EX      (SP),HL         ; dim pointer to stack, data pointer to HL (*)
  13002.         EX      DE,HL           ; data pointer to DE, dim size to HL.
  13003.  
  13004.         CALL    L2ACC           ; routine INT-EXP1 checks integer expression
  13005.                                 ; and gets result in BC in runtime.
  13006.         JR      C,L2A20         ; to REPORT-3 if > HL
  13007.                                 ; 'Subscript out of range'
  13008.  
  13009.         DEC     BC              ; adjust returned result from 1-x to 0-x
  13010.         CALL    L2AF4           ; routine GET-HL*DE multiplies data pointer by
  13011.                                 ; dimension size.
  13012.         ADD     HL,BC           ; add the integer returned by expression.
  13013.         POP     DE              ; pop the dimension pointer.                              ***
  13014.         POP     BC              ; pop dimension counter.
  13015.         DJNZ    L29C3           ; back to SV-COMMA if more dimensions
  13016.                                 ; Note. during syntax checking, unless there
  13017.                                 ; are more than 256 subscripts, the branch
  13018.                                 ; back to SV-COMMA is always taken.
  13019.  
  13020.         BIT     7,C             ; are we checking syntax ?
  13021.                                 ; then we've got a joker here.
  13022.  
  13023. ;; SV-RPT-C
  13024. L2A12:  JR      NZ,L2A7A        ; forward to SL-RPT-C if so
  13025.                                 ; 'Nonsense in BASIC'
  13026.                                 ; more than 256 subscripts in BASIC line.
  13027.  
  13028. ; but in runtime the number of subscripts are at least the same as dims
  13029.  
  13030.         PUSH    HL              ; save data pointer.
  13031.         BIT     6,C             ; is it a string array ?
  13032.         JR      NZ,L2A2C        ; forward to SV-ELEM$ if so.
  13033.  
  13034. ; a runtime numeric array subscript.
  13035.  
  13036.         LD      B,D             ; register DE has advanced past all dimensions
  13037.         LD      C,E             ; and points to start of data in variable.
  13038.                                 ; transfer it to BC.
  13039.  
  13040.         RST     18H             ; GET-CHAR checks BASIC line
  13041.         CP      $29             ; must be a ')' ?
  13042.         JR      Z,L2A22         ; skip to SV-NUMBER if so
  13043.  
  13044. ; else more subscripts in BASIC line than the variable definition.
  13045.  
  13046. ;; REPORT-3
  13047. L2A20:  RST     08H             ; ERROR-1
  13048.         DB    $02             ; Error Report: Subscript wrong
  13049.  
  13050. ; continue if subscripts matched the numeric array.
  13051.  
  13052. ;; SV-NUMBER
  13053. L2A22:  RST     20H             ; NEXT-CHAR moves CH_ADD to next statement
  13054.                                 ; - finished parsing.
  13055.  
  13056.         POP     HL              ; pop the data pointer.
  13057.         LD      DE,$0005        ; each numeric element is 5 bytes.
  13058.         CALL    L2AF4           ; routine GET-HL*DE multiplies.
  13059.         ADD     HL,BC           ; now add to start of data in the variable.
  13060.  
  13061.         RET                     ; return with HL pointing at the numeric
  13062.                                 ; array subscript.                       ->
  13063.  
  13064. ; ---------------------------------------------------------------
  13065.  
  13066. ; the branch was here for string subscripts when the number of subscripts
  13067. ; in the BASIC line was one less than in variable definition.
  13068.  
  13069. ;; SV-ELEM$
  13070. L2A2C:  CALL    L2AEE           ; routine DE,(DE+1) gets final dimension
  13071.                                 ; the length of strings in this array.
  13072.         EX      (SP),HL         ; start pointer to stack, data pointer to HL.
  13073.         CALL    L2AF4           ; routine GET-HL*DE multiplies by element
  13074.                                 ; size.
  13075.         POP     BC              ; the start of data pointer is added
  13076.         ADD     HL,BC           ; in - now points to location before.
  13077.         INC     HL              ; point to start of required string.
  13078.         LD      B,D             ; transfer the length (final dimension size)
  13079.         LD      C,E             ; from DE to BC.
  13080.         EX      DE,HL           ; put start in DE.
  13081.         CALL    L2AB1           ; routine STK-ST-0 stores the string parameters
  13082.                                 ; with A=0 - a slice or subscript.
  13083.  
  13084. ; now check that there were no more subscripts in the BASIC line.
  13085.  
  13086.         RST     18H             ; GET-CHAR
  13087.         CP      $29             ; is it ')' ?
  13088.         JR      Z,L2A48         ; forward to SV-DIM to consider a separate
  13089.                                 ; subscript or/and a slice.
  13090.  
  13091.         CP      $2C             ; a comma is allowed if the final subscript
  13092.                                 ; is to be sliced e.g a$(2,3,4 TO 6).
  13093.         JR      NZ,L2A20        ; to REPORT-3 with anything else
  13094.                                 ; 'Subscript error'
  13095.  
  13096. ;; SV-SLICE
  13097. L2A45:  CALL    L2A52           ; routine SLICING slices the string.
  13098.  
  13099. ; but a slice of a simple string can itself be sliced.
  13100.  
  13101. ;; SV-DIM
  13102. L2A48:  RST     20H             ; NEXT-CHAR
  13103.  
  13104. ;; SV-SLICE?
  13105. L2A49:  CP      $28             ; is character '(' ?
  13106.         JR      Z,L2A45         ; loop back if so to SV-SLICE
  13107.  
  13108.         RES     6,(IY+$01)      ; update FLAGS  - Signal string result
  13109.         RET                     ; and return.
  13110.  
  13111. ; ---
  13112.  
  13113. ; The above section deals with the flexible syntax allowed.
  13114. ; DIM a$(3,3,10) can be considered as two dimensional array of ten-character
  13115. ; strings or a 3-dimensional array of characters.
  13116. ; a$(1,1) will return a 10-character string as will a$(1,1,1 TO 10)
  13117. ; a$(1,1,1) will return a single character.
  13118. ; a$(1,1) (1 TO 6) is the same as a$(1,1,1 TO 6)
  13119. ; A slice can itself be sliced ad infinitum
  13120. ; b$ () () () () () () (2 TO 10) (2 TO 9) (3) is the same as b$(5)
  13121.  
  13122.  
  13123.  
  13124. ; -------------------------
  13125. ; Handle slicing of strings
  13126. ; -------------------------
  13127. ; The syntax of string slicing is very natural and it is as well to reflect
  13128. ; on the permutations possible.
  13129. ; a$() and a$( TO ) indicate the entire string although just a$ would do
  13130. ; and would avoid coming here.
  13131. ; h$(16) indicates the single character at position 16.
  13132. ; a$( TO 32) indicates the first 32 characters.
  13133. ; a$(257 TO) indicates all except the first 256 characters.
  13134. ; a$(19000 TO 19999) indicates the thousand characters at position 19000.
  13135. ; Also a$(9 TO 5) returns a null string not an error.
  13136. ; This enables a$(2 TO) to return a null string if the passed string is
  13137. ; of length zero or 1.
  13138. ; A string expression in brackets can be sliced. e.g. (STR$ PI) (3 TO )
  13139. ; We arrived here from SCANNING with CH-ADD pointing to the initial '('
  13140. ; or from above.
  13141.  
  13142. ;; SLICING
  13143. L2A52:  CALL    L2530           ; routine SYNTAX-Z
  13144.         CALL    NZ,L2BF1        ; routine STK-FETCH fetches parameters of
  13145.                                 ; string at runtime, start in DE, length
  13146.                                 ; in BC. This could be an array subscript.
  13147.  
  13148.         RST     20H             ; NEXT-CHAR
  13149.         CP      $29             ; is it ')' ?     e.g. a$()
  13150.         JR      Z,L2AAD         ; forward to SL-STORE to store entire string.
  13151.  
  13152.         PUSH    DE              ; else save start address of string
  13153.  
  13154.         XOR     A               ; clear accumulator to use as a running flag.
  13155.         PUSH    AF              ; and save on stack before any branching.
  13156.  
  13157.         PUSH    BC              ; save length of string to be sliced.
  13158.         LD      DE,$0001        ; default the start point to position 1.
  13159.  
  13160.         RST     18H             ; GET-CHAR
  13161.  
  13162.         POP     HL              ; pop length to HL as default end point
  13163.                                 ; and limit.
  13164.  
  13165.         CP      $CC             ; is it 'TO' ?    e.g. a$( TO 10000)
  13166.         JR      Z,L2A81         ; to SL-SECOND to evaluate second parameter.
  13167.  
  13168.         POP     AF              ; pop the running flag.
  13169.  
  13170.         CALL    L2ACD           ; routine INT-EXP2 fetches first parameter.
  13171.  
  13172.         PUSH    AF              ; save flag (will be $FF if parameter>limit)
  13173.  
  13174.         LD      D,B             ; transfer the start
  13175.         LD      E,C             ; to DE overwriting 0001.
  13176.         PUSH    HL              ; save original length.
  13177.  
  13178.         RST     18H             ; GET-CHAR
  13179.         POP     HL              ; pop the limit length.
  13180.         CP      $CC             ; is it 'TO' after a start ?
  13181.         JR      Z,L2A81         ; to SL-SECOND to evaluate second parameter
  13182.  
  13183.         CP      $29             ; is it ')' ?       e.g. a$(365)
  13184.  
  13185. ;; SL-RPT-C
  13186. L2A7A:  JP      NZ,L1C8A        ; jump to REPORT-C with anything else
  13187.                                 ; 'Nonsense in BASIC'
  13188.  
  13189.         LD      H,D             ; copy start
  13190.         LD      L,E             ; to end - just a one character slice.
  13191.         JR      L2A94           ; forward to SL-DEFINE.
  13192.  
  13193. ; ---------------------
  13194.  
  13195. ;; SL-SECOND
  13196. L2A81:  PUSH    HL              ; save limit length.
  13197.  
  13198.         RST     20H             ; NEXT-CHAR
  13199.  
  13200.         POP     HL              ; pop the length.
  13201.  
  13202.         CP      $29             ; is character ')' ?        e.g a$(7 TO )
  13203.         JR      Z,L2A94         ; to SL-DEFINE using length as end point.
  13204.  
  13205.         POP     AF              ; else restore flag.
  13206.         CALL    L2ACD           ; routine INT-EXP2 gets second expression.
  13207.  
  13208.         PUSH    AF              ; save the running flag.
  13209.  
  13210.         RST     18H             ; GET-CHAR
  13211.  
  13212.         LD      H,B             ; transfer second parameter
  13213.         LD      L,C             ; to HL.              e.g. a$(42 to 99)
  13214.         CP      $29             ; is character a ')' ?
  13215.         JR      NZ,L2A7A        ; to SL-RPT-C if not
  13216.                                 ; 'Nonsense in BASIC'
  13217.  
  13218. ; we now have start in DE and an end in HL.
  13219.  
  13220. ;; SL-DEFINE
  13221. L2A94:  POP     AF              ; pop the running flag.
  13222.         EX      (SP),HL         ; put end point on stack, start address to HL
  13223.         ADD     HL,DE           ; add address of string to the start point.
  13224.         DEC     HL              ; point to first character of slice.
  13225.         EX      (SP),HL         ; start address to stack, end point to HL (*)
  13226.         AND     A               ; prepare to subtract.
  13227.         SBC     HL,DE           ; subtract start point from end point.
  13228.         LD      BC,$0000        ; default the length result to zero.
  13229.         JR      C,L2AA8         ; forward to SL-OVER if start > end.
  13230.  
  13231.         INC     HL              ; increment the length for inclusive byte.
  13232.  
  13233.         AND     A               ; now test the running flag.
  13234.         JP      M,L2A20         ; jump back to REPORT-3 if $FF.
  13235.                                 ; 'Subscript out of range'
  13236.  
  13237.         LD      B,H             ; transfer the length
  13238.         LD      C,L             ; to BC.
  13239.  
  13240. ;; SL-OVER
  13241. L2AA8:  POP     DE              ; restore start address from machine stack ***
  13242.         RES     6,(IY+$01)      ; update FLAGS - signal string result for
  13243.                                 ; syntax.
  13244.  
  13245. ;; SL-STORE
  13246. L2AAD:  CALL    L2530           ; routine SYNTAX-Z  (UNSTACK-Z?)
  13247.         RET     Z               ; return if checking syntax.
  13248.                                 ; but continue to store the string in runtime.
  13249.  
  13250. ; ------------------------------------
  13251. ; other than from above, this routine is called from STK-VAR to stack
  13252. ; a known string array element.
  13253. ; ------------------------------------
  13254.  
  13255. ;; STK-ST-0
  13256. L2AB1:  XOR     A               ; clear to signal a sliced string or element.
  13257.  
  13258. ; -------------------------
  13259. ; this routine is called from chr$, scrn$ etc. to store a simple string result.
  13260. ; --------------------------
  13261.  
  13262. ;; STK-STO-$
  13263. L2AB2:  RES     6,(IY+$01)      ; update FLAGS - signal string result.
  13264.                                 ; and continue to store parameters of string.
  13265.  
  13266. ; ---------------------------------------
  13267. ; Pass five registers to calculator stack
  13268. ; ---------------------------------------
  13269. ; This subroutine puts five registers on the calculator stack.
  13270.  
  13271. ;; STK-STORE
  13272. L2AB6:  PUSH    BC              ; save two registers
  13273.         CALL    L33A9           ; routine TEST-5-SP checks room and puts 5
  13274.                                 ; in BC.
  13275.         POP     BC              ; fetch the saved registers.
  13276.         LD      HL,($5C65)      ; make HL point to first empty location STKEND
  13277.         LD      (HL),A          ; place the 5 registers.
  13278.         INC     HL              ;
  13279.         LD      (HL),E          ;
  13280.         INC     HL              ;
  13281.         LD      (HL),D          ;
  13282.         INC     HL              ;
  13283.         LD      (HL),C          ;
  13284.         INC     HL              ;
  13285.         LD      (HL),B          ;
  13286.         INC     HL              ;
  13287.         LD      ($5C65),HL      ; update system variable STKEND.
  13288.         RET                     ; and return.
  13289.  
  13290. ; -------------------------------------------
  13291. ; Return result of evaluating next expression
  13292. ; -------------------------------------------
  13293. ; This clever routine is used to check and evaluate an integer expression
  13294. ; which is returned in BC, setting A to $FF, if greater than a limit supplied
  13295. ; in HL. It is used to check array subscripts, parameters of a string slice
  13296. ; and the arguments of the DIM command. In the latter case, the limit check
  13297. ; is not required and H is set to $FF. When checking optional string slice
  13298. ; parameters, it is entered at the second entry point so as not to disturb
  13299. ; the running flag A, which may be $00 or $FF from a previous invocation.
  13300.  
  13301. ;; INT-EXP1
  13302. L2ACC:  XOR     A               ; set result flag to zero.
  13303.  
  13304. ; -> The entry point is here if A is used as a running flag.
  13305.  
  13306. ;; INT-EXP2
  13307. L2ACD:  PUSH    DE              ; preserve DE register throughout.
  13308.         PUSH    HL              ; save the supplied limit.
  13309.         PUSH    AF              ; save the flag.
  13310.  
  13311.         CALL    L1C82           ; routine EXPT-1NUM evaluates expression
  13312.                                 ; at CH_ADD returning if numeric result,
  13313.                                 ; with value on calculator stack.
  13314.  
  13315.         POP     AF              ; pop the flag.
  13316.         CALL    L2530           ; routine SYNTAX-Z
  13317.         JR      Z,L2AEB         ; forward to I-RESTORE if checking syntax so
  13318.                                 ; avoiding a comparison with supplied limit.
  13319.  
  13320.         PUSH    AF              ; save the flag.
  13321.  
  13322.         CALL    L1E99           ; routine FIND-INT2 fetches value from
  13323.                                 ; calculator stack to BC producing an error
  13324.                                 ; if too high.
  13325.  
  13326.         POP     DE              ; pop the flag to D.
  13327.         LD      A,B             ; test value for zero and reject
  13328.         OR      C               ; as arrays and strings begin at 1.
  13329.         SCF                     ; set carry flag.
  13330.         JR      Z,L2AE8         ; forward to I-CARRY if zero.
  13331.  
  13332.         POP     HL              ; restore the limit.
  13333.         PUSH    HL              ; and save.
  13334.         AND     A               ; prepare to subtract.
  13335.         SBC     HL,BC           ; subtract value from limit.
  13336.  
  13337. ;; I-CARRY
  13338. L2AE8:  LD      A,D             ; move flag to accumulator $00 or $FF.
  13339.         SBC     A,$00           ; will set to $FF if carry set.
  13340.  
  13341. ;; I-RESTORE
  13342. L2AEB:  POP     HL              ; restore the limit.
  13343.         POP     DE              ; and DE register.
  13344.         RET                     ; return.
  13345.  
  13346.  
  13347. ; -----------------------
  13348. ; LD DE,(DE+1) Subroutine
  13349. ; -----------------------
  13350. ; This routine just loads the DE register with the contents of the two
  13351. ; locations following the location addressed by DE.
  13352. ; It is used to step along the 16-bit dimension sizes in array definitions.
  13353. ; Note. Such code is made into subroutines to make programs easier to
  13354. ; write and it would use less space to include the five instructions in-line.
  13355. ; However, there are so many exchanges going on at the places this is invoked
  13356. ; that to implement it in-line would make the code hard to follow.
  13357. ; It probably had a zippier label though as the intention is to simplify the
  13358. ; program.
  13359.  
  13360. ;; DE,(DE+1)
  13361. L2AEE:  EX      DE,HL           ;
  13362.         INC     HL              ;
  13363.         LD      E,(HL)          ;
  13364.         INC     HL              ;
  13365.         LD      D,(HL)          ;
  13366.         RET                     ;
  13367.  
  13368. ; -------------------
  13369. ; HL=HL*DE Subroutine
  13370. ; -------------------
  13371. ; This routine calls the mathematical routine to multiply HL by DE in runtime.
  13372. ; It is called from STK-VAR and from DIM. In the latter case syntax is not
  13373. ; being checked so the entry point could have been at the second CALL
  13374. ; instruction to save a few clock-cycles.
  13375.  
  13376. ;; GET-HL*DE
  13377. L2AF4:  CALL    L2530           ; routine SYNTAX-Z.
  13378.         RET     Z               ; return if checking syntax.
  13379.  
  13380.         CALL    L30A9           ; routine HL-HL*DE.
  13381.         JP      C,L1F15         ; jump back to REPORT-4 if over 65535.
  13382.  
  13383.         RET                     ; else return with 16-bit result in HL.
  13384.  
  13385. ; -----------------
  13386. ; THE 'LET' COMMAND
  13387. ; -----------------
  13388. ; Sinclair BASIC adheres to the ANSI-78 standard and a LET is required in
  13389. ; assignments e.g. LET a = 1  :   LET h$ = "hat".
  13390. ;
  13391. ; Long names may contain spaces but not colour controls (when assigned).
  13392. ; a substring can appear to the left of the equals sign.
  13393.  
  13394. ; An earlier mathematician Lewis Carroll may have been pleased that
  13395. ; 10 LET Babies cannot manage crocodiles = Babies are illogical AND
  13396. ;    Nobody is despised who can manage a crocodile AND Illogical persons
  13397. ;    are despised
  13398. ; does not give the 'Nonsense..' error if the three variables exist.
  13399. ; I digress.
  13400.  
  13401. ;; LET
  13402. L2AFF:  LD      HL,($5C4D)      ; fetch system variable DEST to HL.
  13403.         BIT     1,(IY+$37)      ; test FLAGX - handling a new variable ?
  13404.         JR      Z,L2B66         ; forward to L-EXISTS if not.
  13405.  
  13406. ; continue for a new variable. DEST points to start in BASIC line.
  13407. ; from the CLASS routines.
  13408.  
  13409.         LD      BC,$0005        ; assume numeric and assign an initial 5 bytes
  13410.  
  13411. ;; L-EACH-CH
  13412. L2B0B:  INC     BC              ; increase byte count for each relevant
  13413.                                 ; character
  13414.  
  13415. ;; L-NO-SP
  13416. L2B0C:  INC     HL              ; increase pointer.
  13417.         LD      A,(HL)          ; fetch character.
  13418.         CP      $20             ; is it a space ?
  13419.         JR      Z,L2B0C         ; back to L-NO-SP is so.
  13420.  
  13421.         JR      NC,L2B1F        ; forward to L-TEST-CH if higher.
  13422.  
  13423.         CP      $10             ; is it $00 - $0F ?
  13424.         JR      C,L2B29         ; forward to L-SPACES if so.
  13425.  
  13426.         CP      $16             ; is it $16 - $1F ?
  13427.         JR      NC,L2B29        ; forward to L-SPACES if so.
  13428.  
  13429. ; it was $10 - $15  so step over a colour code.
  13430.  
  13431.         INC     HL              ; increase pointer.
  13432.         JR      L2B0C           ; loop back to L-NO-SP.
  13433.  
  13434. ; ---
  13435.  
  13436. ; the branch was to here if higher than space.
  13437.  
  13438. ;; L-TEST-CH
  13439. L2B1F:  CALL    L2C88           ; routine ALPHANUM sets carry if alphanumeric
  13440.         JR      C,L2B0B         ; loop back to L-EACH-CH for more if so.
  13441.  
  13442.         CP      $24             ; is it '$' ?
  13443.         JP      Z,L2BC0         ; jump forward if so, to L-NEW$
  13444.                                 ; with a new string.
  13445.  
  13446. ;; L-SPACES
  13447. L2B29:  LD      A,C             ; save length lo in A.
  13448.         LD      HL,($5C59)      ; fetch E_LINE to HL.
  13449.         DEC     HL              ; point to location before, the variables
  13450.                                 ; end-marker.
  13451.         CALL    L1655           ; routine MAKE-ROOM creates BC spaces
  13452.                                 ; for name and numeric value.
  13453.         INC     HL              ; advance to first new location.
  13454.         INC     HL              ; then to second.
  13455.         EX      DE,HL           ; set DE to second location.
  13456.         PUSH    DE              ; save this pointer.
  13457.         LD      HL,($5C4D)      ; reload HL with DEST.
  13458.         DEC     DE              ; point to first.
  13459.         SUB     $06             ; subtract six from length_lo.
  13460.         LD      B,A             ; save count in B.
  13461.         JR      Z,L2B4F         ; forward to L-SINGLE if it was just
  13462.                                 ; one character.
  13463.  
  13464. ; HL points to start of variable name after 'LET' in BASIC line.
  13465.  
  13466. ;; L-CHAR
  13467. L2B3E:  INC     HL              ; increase pointer.
  13468.         LD      A,(HL)          ; pick up character.
  13469.         CP      $21             ; is it space or higher ?
  13470.         JR      C,L2B3E         ; back to L-CHAR with space and less.
  13471.  
  13472.         OR      $20             ; make variable lower-case.
  13473.         INC     DE              ; increase destination pointer.
  13474.         LD      (DE),A          ; and load to edit line.
  13475.         DJNZ    L2B3E           ; loop back to L-CHAR until B is zero.
  13476.  
  13477.         OR      $80             ; invert the last character.
  13478.         LD      (DE),A          ; and overwrite that in edit line.
  13479.  
  13480. ; now consider first character which has bit 6 set
  13481.  
  13482.         LD      A,$C0           ; set A 11000000 is xor mask for a long name.
  13483.                                 ; %101      is xor/or  result
  13484.  
  13485. ; single character numerics rejoin here with %00000000 in mask.
  13486. ;                                            %011      will be xor/or result
  13487.  
  13488. ;; L-SINGLE
  13489. L2B4F:  LD      HL,($5C4D)      ; fetch DEST - HL addresses first character.
  13490.         XOR     (HL)            ; apply variable type indicator mask (above).
  13491.         OR      $20             ; make lowercase - set bit 5.
  13492.         POP     HL              ; restore pointer to 2nd character.
  13493.         CALL    L2BEA           ; routine L-FIRST puts A in first character.
  13494.                                 ; and returns with HL holding
  13495.                                 ; new E_LINE-1  the $80 vars end-marker.
  13496.  
  13497. ;; L-NUMERIC
  13498. L2B59:  PUSH    HL              ; save the pointer.
  13499.  
  13500. ; the value of variable is deleted but remains after calculator stack.
  13501.  
  13502.         RST     28H             ;; FP-CALC
  13503.         DB    $02             ;;delete      ; delete variable value
  13504.         DB    $38             ;;end-calc
  13505.  
  13506. ; DE (STKEND) points to start of value.
  13507.  
  13508.         POP     HL              ; restore the pointer.
  13509.         LD      BC,$0005        ; start of number is five bytes before.
  13510.         AND     A               ; prepare for true subtraction.
  13511.         SBC     HL,BC           ; HL points to start of value.
  13512.         JR      L2BA6           ; forward to L-ENTER  ==>
  13513.  
  13514. ; ---
  13515.  
  13516.  
  13517. ; the jump was to here if the variable already existed.
  13518.  
  13519. ;; L-EXISTS
  13520. L2B66:  BIT     6,(IY+$01)      ; test FLAGS - numeric or string result ?
  13521.         JR      Z,L2B72         ; skip forward to L-DELETE$   -*->
  13522.                                 ; if string result.
  13523.  
  13524. ; A numeric variable could be simple or an array element.
  13525. ; They are treated the same and the old value is overwritten.
  13526.  
  13527.         LD      DE,$0006        ; six bytes forward points to loc past value.
  13528.         ADD     HL,DE           ; add to start of number.
  13529.         JR      L2B59           ; back to L-NUMERIC to overwrite value.
  13530.  
  13531. ; ---
  13532.  
  13533. ; -*-> the branch was here if a string existed.
  13534.  
  13535. ;; L-DELETE$
  13536. L2B72:  LD      HL,($5C4D)      ; fetch DEST to HL.
  13537.                                 ; (still set from first instruction)
  13538.         LD      BC,($5C72)      ; fetch STRLEN to BC.
  13539.         BIT     0,(IY+$37)      ; test FLAGX - handling a complete simple
  13540.                                 ; string ?
  13541.         JR      NZ,L2BAF        ; forward to L-ADD$ if so.
  13542.  
  13543. ; must be a string array or a slice in workspace.
  13544. ; Note. LET a$(3 TO 6) = h$   will assign "hat " if h$ = "hat"
  13545. ;                                  and    "hats" if h$ = "hatstand".
  13546. ;
  13547. ; This is known as Procrustian lengthening and shortening after a
  13548. ; character Procrustes in Greek legend who made travellers sleep in his bed,
  13549. ; cutting off their feet or stretching them so they fitted the bed perfectly.
  13550. ; The bloke was hatstand and slain by Theseus.
  13551.  
  13552.         LD      A,B             ; test if length
  13553.         OR      C               ; is zero and
  13554.         RET     Z               ; return if so.
  13555.  
  13556.         PUSH    HL              ; save pointer to start.
  13557.  
  13558.         RST     30H             ; BC-SPACES creates room.
  13559.         PUSH    DE              ; save pointer to first new location.
  13560.         PUSH    BC              ; and length            (*)
  13561.         LD      D,H             ; set DE to point to last location.
  13562.         LD      E,L             ;
  13563.         INC     HL              ; set HL to next location.
  13564.         LD      (HL),$20        ; place a space there.
  13565.         LDDR                    ; copy bytes filling with spaces.
  13566.  
  13567.         PUSH    HL              ; save pointer to start.
  13568.         CALL    L2BF1           ; routine STK-FETCH start to DE,
  13569.                                 ; length to BC.
  13570.         POP     HL              ; restore the pointer.
  13571.         EX      (SP),HL         ; (*) length to HL, pointer to stack.
  13572.         AND     A               ; prepare for true subtraction.
  13573.         SBC     HL,BC           ; subtract old length from new.
  13574.         ADD     HL,BC           ; and add back.
  13575.         JR      NC,L2B9B        ; forward if it fits to L-LENGTH.
  13576.  
  13577.         LD      B,H             ; otherwise set
  13578.         LD      C,L             ; length to old length.
  13579.                                 ; "hatstand" becomes "hats"
  13580.  
  13581. ;; L-LENGTH
  13582. L2B9B:  EX      (SP),HL         ; (*) length to stack, pointer to HL.
  13583.         EX      DE,HL           ; pointer to DE, start of string to HL.
  13584.         LD      A,B             ; is the length zero ?
  13585.         OR      C               ;
  13586.         JR      Z,L2BA3         ; forward to L-IN-W/S if so
  13587.                                 ; leaving prepared spaces.
  13588.  
  13589.         LDIR                    ; else copy bytes overwriting some spaces.
  13590.  
  13591. ;; L-IN-W/S
  13592. L2BA3:  POP     BC              ; pop the new length.  (*)
  13593.         POP     DE              ; pop pointer to new area.
  13594.         POP     HL              ; pop pointer to variable in assignment.
  13595.                                 ; and continue copying from workspace
  13596.                                 ; to variables area.
  13597.  
  13598. ; ==> branch here from  L-NUMERIC
  13599.  
  13600. ;; L-ENTER
  13601. L2BA6:  EX      DE,HL           ; exchange pointers HL=STKEND DE=end of vars.
  13602.         LD      A,B             ; test the length
  13603.         OR      C               ; and make a
  13604.         RET     Z               ; return if zero (strings only).
  13605.  
  13606.         PUSH    DE              ; save start of destination.
  13607.         LDIR                    ; copy bytes.
  13608.         POP     HL              ; address the start.
  13609.         RET                     ; and return.
  13610.  
  13611. ; ---
  13612.  
  13613. ; the branch was here from L-DELETE$ if an existing simple string.
  13614. ; register HL addresses start of string in variables area.
  13615.  
  13616. ;; L-ADD$
  13617. L2BAF:  DEC     HL              ; point to high byte of length.
  13618.         DEC     HL              ; to low byte.
  13619.         DEC     HL              ; to letter.
  13620.         LD      A,(HL)          ; fetch masked letter to A.
  13621.         PUSH    HL              ; save the pointer on stack.
  13622.         PUSH    BC              ; save new length.
  13623.         CALL    L2BC6           ; routine L-STRING adds new string at end
  13624.                                 ; of variables area.
  13625.                                 ; if no room we still have old one.
  13626.         POP     BC              ; restore length.
  13627.         POP     HL              ; restore start.
  13628.         INC     BC              ; increase
  13629.         INC     BC              ; length by three
  13630.         INC     BC              ; to include character and length bytes.
  13631.         JP      L19E8           ; jump to indirect exit via RECLAIM-2
  13632.                                 ; deleting old version and adjusting pointers.
  13633.  
  13634. ; ---
  13635.  
  13636. ; the jump was here with a new string variable.
  13637.  
  13638. ;; L-NEW$
  13639. L2BC0:  LD      A,$DF           ; indicator mask %11011111 for
  13640.                                 ;                %010xxxxx will be result
  13641.         LD      HL,($5C4D)      ; address DEST first character.
  13642.         AND     (HL)            ; combine mask with character.
  13643.  
  13644. ;; L-STRING
  13645. L2BC6:  PUSH    AF              ; save first character and mask.
  13646.         CALL    L2BF1           ; routine STK-FETCH fetches parameters of
  13647.                                 ; the string.
  13648.         EX      DE,HL           ; transfer start to HL.
  13649.         ADD     HL,BC           ; add to length.
  13650.         PUSH    BC              ; save the length.
  13651.         DEC     HL              ; point to end of string.
  13652.         LD      ($5C4D),HL      ; save pointer in DEST.
  13653.                                 ; (updated by POINTERS if in workspace)
  13654.         INC     BC              ; extra byte for letter.
  13655.         INC     BC              ; two bytes
  13656.         INC     BC              ; for the length of string.
  13657.         LD      HL,($5C59)      ; address E_LINE.
  13658.         DEC     HL              ; now end of VARS area.
  13659.         CALL    L1655           ; routine MAKE-ROOM makes room for string.
  13660.                                 ; updating pointers including DEST.
  13661.         LD      HL,($5C4D)      ; pick up pointer to end of string from DEST.
  13662.         POP     BC              ; restore length from stack.
  13663.         PUSH    BC              ; and save again on stack.
  13664.         INC     BC              ; add a byte.
  13665.         LDDR                    ; copy bytes from end to start.
  13666.         EX      DE,HL           ; HL addresses length low
  13667.         INC     HL              ; increase to address high byte
  13668.         POP     BC              ; restore length to BC
  13669.         LD      (HL),B          ; insert high byte
  13670.         DEC     HL              ; address low byte location
  13671.         LD      (HL),C          ; insert that byte
  13672.         POP     AF              ; restore character and mask
  13673.  
  13674. ;; L-FIRST
  13675. L2BEA:  DEC     HL              ; address variable name
  13676.         LD      (HL),A          ; and insert character.
  13677.         LD      HL,($5C59)      ; load HL with E_LINE.
  13678.         DEC     HL              ; now end of VARS area.
  13679.         RET                     ; return
  13680.  
  13681. ; ------------------------------------
  13682. ; Get last value from calculator stack
  13683. ; ------------------------------------
  13684. ;
  13685. ;
  13686.  
  13687. ;; STK-FETCH
  13688. L2BF1:  LD      HL,($5C65)      ; STKEND
  13689.         DEC     HL              ;
  13690.         LD      B,(HL)          ;
  13691.         DEC     HL              ;
  13692.         LD      C,(HL)          ;
  13693.         DEC     HL              ;
  13694.         LD      D,(HL)          ;
  13695.         DEC     HL              ;
  13696.         LD      E,(HL)          ;
  13697.         DEC     HL              ;
  13698.         LD      A,(HL)          ;
  13699.         LD      ($5C65),HL      ; STKEND
  13700.         RET                     ;
  13701.  
  13702. ; ------------------
  13703. ; Handle DIM command
  13704. ; ------------------
  13705. ; e.g. DIM a(2,3,4,7): DIM a$(32) : DIM b$(300,2,768) : DIM c$(20000)
  13706. ; the only limit to dimensions is memory so, for example,
  13707. ; DIM a(2,2,2,2,2,2,2,2,2,2,2,2,2) is possible and creates a multi-
  13708. ; dimensional array of zeros. String arrays are initialized to spaces.
  13709. ; It is not possible to erase an array, but it can be re-dimensioned to
  13710. ; a minimal size of 1, after use, to free up memory.
  13711.  
  13712. ;; DIM
  13713. L2C02:  CALL    L28B2           ; routine LOOK-VARS
  13714.  
  13715. ;; D-RPORT-C
  13716. L2C05:  JP      NZ,L1C8A        ; jump to REPORT-C if a long-name variable.
  13717.                                 ; DIM lottery numbers(49) doesn't work.
  13718.  
  13719.         CALL    L2530           ; routine SYNTAX-Z
  13720.         JR      NZ,L2C15        ; forward to D-RUN in runtime.
  13721.  
  13722.         RES     6,C             ; signal 'numeric' array even if string as
  13723.                                 ; this simplifies the syntax checking.
  13724.  
  13725.         CALL    L2996           ; routine STK-VAR checks syntax.
  13726.         CALL    L1BEE           ; routine CHECK-END performs early exit ->
  13727.  
  13728. ; the branch was here in runtime.
  13729.  
  13730. ;; D-RUN
  13731. L2C15:  JR      C,L2C1F         ; skip to D-LETTER if variable did not exist.
  13732.                                 ; else reclaim the old one.
  13733.  
  13734.         PUSH    BC              ; save type in C.
  13735.         CALL    L19B8           ; routine NEXT-ONE find following variable
  13736.                                 ; or position of $80 end-marker.
  13737.         CALL    L19E8           ; routine RECLAIM-2 reclaims the
  13738.                                 ; space between.
  13739.         POP     BC              ; pop the type.
  13740.  
  13741. ;; D-LETTER
  13742. L2C1F:  SET     7,C             ; signal array.
  13743.         LD      B,$00           ; initialize dimensions to zero and
  13744.         PUSH    BC              ; save with the type.
  13745.         LD      HL,$0001        ; make elements one character presuming string
  13746.         BIT     6,C             ; is it a string ?
  13747.         JR      NZ,L2C2D        ; forward to D-SIZE if so.
  13748.  
  13749.         LD      L,$05           ; make elements 5 bytes as is numeric.
  13750.  
  13751. ;; D-SIZE
  13752. L2C2D:  EX      DE,HL           ; save the element size in DE.
  13753.  
  13754. ; now enter a loop to parse each of the integers in the list.
  13755.  
  13756. ;; D-NO-LOOP
  13757. L2C2E:  RST     20H             ; NEXT-CHAR
  13758.         LD      H,$FF           ; disable limit check by setting HL high
  13759.         CALL    L2ACC           ; routine INT-EXP1
  13760.         JP      C,L2A20         ; to REPORT-3 if > 65280 and then some
  13761.                                 ; 'Subscript out of range'
  13762.  
  13763.         POP     HL              ; pop dimension counter, array type
  13764.         PUSH    BC              ; save dimension size                     ***
  13765.         INC     H               ; increment the dimension counter
  13766.         PUSH    HL              ; save the dimension counter
  13767.         LD      H,B             ; transfer size
  13768.         LD      L,C             ; to HL
  13769.         CALL    L2AF4           ; routine GET-HL*DE multiplies dimension by
  13770.                                 ; running total of size required initially
  13771.                                 ; 1 or 5.
  13772.         EX      DE,HL           ; save running total in DE
  13773.  
  13774.         RST     18H             ; GET-CHAR
  13775.         CP      $2C             ; is it ',' ?
  13776.         JR      Z,L2C2E         ; loop back to D-NO-LOOP until all dimensions
  13777.                                 ; have been considered
  13778.  
  13779. ; when loop complete continue.
  13780.  
  13781.         CP      $29             ; is it ')' ?
  13782.         JR      NZ,L2C05        ; to D-RPORT-C with anything else
  13783.                                 ; 'Nonsense in BASIC'
  13784.  
  13785.  
  13786.         RST     20H             ; NEXT-CHAR advances to next statement/CR
  13787.  
  13788.         POP     BC              ; pop dimension counter/type
  13789.         LD      A,C             ; type to A
  13790.  
  13791. ; now calculate space required for array variable
  13792.  
  13793.         LD      L,B             ; dimensions to L since these require 16 bits
  13794.                                 ; then this value will be doubled
  13795.         LD      H,$00           ; set high byte to zero
  13796.  
  13797. ; another four bytes are required for letter(1), total length(2), number of
  13798. ; dimensions(1) but since we have yet to double allow for two
  13799.  
  13800.         INC     HL              ; increment
  13801.         INC     HL              ; increment
  13802.  
  13803.         ADD     HL,HL           ; now double giving 4 + dimensions * 2
  13804.  
  13805.         ADD     HL,DE           ; add to space required for array contents
  13806.  
  13807.         JP      C,L1F15         ; to REPORT-4 if > 65535
  13808.                                 ; 'Out of memory'
  13809.  
  13810.         PUSH    DE              ; save data space
  13811.         PUSH    BC              ; save dimensions/type
  13812.         PUSH    HL              ; save total space
  13813.         LD      B,H             ; total space
  13814.         LD      C,L             ; to BC
  13815.         LD      HL,($5C59)      ; address E_LINE - first location after
  13816.                                 ; variables area
  13817.         DEC     HL              ; point to location before - the $80 end-marker
  13818.         CALL    L1655           ; routine MAKE-ROOM creates the space if
  13819.                                 ; memory is available.
  13820.  
  13821.         INC     HL              ; point to first new location and
  13822.         LD      (HL),A          ; store letter/type
  13823.  
  13824.         POP     BC              ; pop total space
  13825.         DEC     BC              ; exclude name
  13826.         DEC     BC              ; exclude the 16-bit
  13827.         DEC     BC              ; counter itself
  13828.         INC     HL              ; point to next location the 16-bit counter
  13829.         LD      (HL),C          ; insert low byte
  13830.         INC     HL              ; address next
  13831.         LD      (HL),B          ; insert high byte
  13832.  
  13833.         POP     BC              ; pop the number of dimensions.
  13834.         LD      A,B             ; dimensions to A
  13835.         INC     HL              ; address next
  13836.         LD      (HL),A          ; and insert "No. of dims"
  13837.  
  13838.         LD      H,D             ; transfer DE space + 1 from make-room
  13839.         LD      L,E             ; to HL
  13840.         DEC     DE              ; set DE to next location down.
  13841.         LD      (HL),$00        ; presume numeric and insert a zero
  13842.         BIT     6,C             ; test bit 6 of C. numeric or string ?
  13843.         JR      Z,L2C7C         ; skip to DIM-CLEAR if numeric
  13844.  
  13845.         LD      (HL),$20        ; place a space character in HL
  13846.  
  13847. ;; DIM-CLEAR
  13848. L2C7C:  POP     BC              ; pop the data length
  13849.  
  13850.         LDDR                    ; LDDR sets to zeros or spaces
  13851.  
  13852. ; The number of dimensions is still in A.
  13853. ; A loop is now entered to insert the size of each dimension that was pushed
  13854. ; during the D-NO-LOOP working downwards from position before start of data.
  13855.  
  13856. ;; DIM-SIZES
  13857. L2C7F:  POP     BC              ; pop a dimension size                    ***
  13858.         LD      (HL),B          ; insert high byte at position
  13859.         DEC     HL              ; next location down
  13860.         LD      (HL),C          ; insert low byte
  13861.         DEC     HL              ; next location down
  13862.         DEC     A               ; decrement dimension counter
  13863.         JR      NZ,L2C7F        ; back to DIM-SIZES until all done.
  13864.  
  13865.         RET                     ; return.
  13866.  
  13867. ; -----------------------------
  13868. ; Check whether digit or letter
  13869. ; -----------------------------
  13870. ; This routine checks that the character in A is alphanumeric
  13871. ; returning with carry set if so.
  13872.  
  13873. ;; ALPHANUM
  13874. L2C88:  CALL    L2D1B           ; routine NUMERIC will reset carry if so.
  13875.         CCF                     ; Complement Carry Flag
  13876.         RET     C               ; Return if numeric else continue into
  13877.                                 ; next routine.
  13878.  
  13879. ; This routine checks that the character in A is alphabetic
  13880.  
  13881. ;; ALPHA
  13882. L2C8D:  CP      $41             ; less than 'A' ?
  13883.         CCF                     ; Complement Carry Flag
  13884.         RET     NC              ; return if so
  13885.  
  13886.         CP      $5B             ; less than 'Z'+1 ?
  13887.         RET     C               ; is within first range
  13888.  
  13889.         CP      $61             ; less than 'a' ?
  13890.         CCF                     ; Complement Carry Flag
  13891.         RET     NC              ; return if so.
  13892.  
  13893.         CP      $7B             ; less than 'z'+1 ?
  13894.         RET                     ; carry set if within a-z.
  13895.  
  13896. ; -------------------------
  13897. ; Decimal to floating point
  13898. ; -------------------------
  13899. ; This routine finds the floating point number represented by an expression
  13900. ; beginning with BIN, '.' or a digit.
  13901. ; Note that BIN need not have any '0's or '1's after it.
  13902. ; BIN is really just a notational symbol and not a function.
  13903.  
  13904. ;; DEC-TO-FP
  13905. L2C9B:  CP      $C4             ; 'BIN' token ?
  13906.         JR      NZ,L2CB8        ; to NOT-BIN if not
  13907.  
  13908.         LD      DE,$0000        ; initialize 16 bit buffer register.
  13909.  
  13910. ;; BIN-DIGIT
  13911. L2CA2:  RST     20H             ; NEXT-CHAR
  13912.         SUB     $31             ; '1'
  13913.         ADC     A,$00           ; will be zero if '1' or '0'
  13914.                                 ; carry will be set if was '0'
  13915.         JR      NZ,L2CB3        ; forward to BIN-END if result not zero
  13916.  
  13917.         EX      DE,HL           ; buffer to HL
  13918.         CCF                     ; Carry now set if originally '1'
  13919.         ADC     HL,HL           ; shift the carry into HL
  13920.         JP      C,L31AD         ; to REPORT-6 if overflow - too many digits
  13921.                                 ; after first '1'. There can be an unlimited
  13922.                                 ; number of leading zeros.
  13923.                                 ; 'Number too big' - raise an error
  13924.  
  13925.         EX      DE,HL           ; save the buffer
  13926.         JR      L2CA2           ; back to BIN-DIGIT for more digits
  13927.  
  13928. ; ---
  13929.  
  13930. ;; BIN-END
  13931. L2CB3:  LD      B,D             ; transfer 16 bit buffer
  13932.         LD      C,E             ; to BC register pair.
  13933.         JP      L2D2B           ; JUMP to STACK-BC to put on calculator stack
  13934.  
  13935. ; ---
  13936.  
  13937. ; continue here with .1,  42, 3.14, 5., 2.3 E -4
  13938.  
  13939. ;; NOT-BIN
  13940. L2CB8:  CP      $2E             ; '.' - leading decimal point ?
  13941.         JR      Z,L2CCB         ; skip to DECIMAL if so.
  13942.  
  13943.         CALL    L2D3B           ; routine INT-TO-FP to evaluate all digits
  13944.                                 ; This number 'x' is placed on stack.
  13945.         CP      $2E             ; '.' - mid decimal point ?
  13946.  
  13947.         JR      NZ,L2CEB        ; to E-FORMAT if not to consider that format
  13948.  
  13949.         RST     20H             ; NEXT-CHAR
  13950.         CALL    L2D1B           ; routine NUMERIC returns carry reset if 0-9
  13951.  
  13952.         JR      C,L2CEB         ; to E-FORMAT if not a digit e.g. '1.'
  13953.  
  13954.         JR      L2CD5           ; to DEC-STO-1 to add the decimal part to 'x'
  13955.  
  13956. ; ---
  13957.  
  13958. ; a leading decimal point has been found in a number.
  13959.  
  13960. ;; DECIMAL
  13961. L2CCB:  RST     20H             ; NEXT-CHAR
  13962.         CALL    L2D1B           ; routine NUMERIC will reset carry if digit
  13963.  
  13964. ;; DEC-RPT-C
  13965. L2CCF:  JP      C,L1C8A         ; to REPORT-C if just a '.'
  13966.                                 ; raise 'Nonsense in BASIC'
  13967.  
  13968. ; since there is no leading zero put one on the calculator stack.
  13969.  
  13970.         RST     28H             ;; FP-CALC
  13971.         DB    $A0             ;;stk-zero  ; 0.
  13972.         DB    $38             ;;end-calc
  13973.  
  13974. ; If rejoining from earlier there will be a value 'x' on stack.
  13975. ; If continuing from above the value zero.
  13976. ; Now store 1 in mem-0.
  13977. ; Note. At each pass of the digit loop this will be divided by ten.
  13978.  
  13979. ;; DEC-STO-1
  13980. L2CD5:  RST     28H             ;; FP-CALC
  13981.         DB    $A1             ;;stk-one   ;x or 0,1.
  13982.         DB    $C0             ;;st-mem-0  ;x or 0,1.
  13983.         DB    $02             ;;delete    ;x or 0.
  13984.         DB    $38             ;;end-calc
  13985.  
  13986.  
  13987. ;; NXT-DGT-1
  13988. L2CDA:  RST     18H             ; GET-CHAR
  13989.         CALL    L2D22           ; routine STK-DIGIT stacks single digit 'd'
  13990.         JR      C,L2CEB         ; exit to E-FORMAT when digits exhausted  >
  13991.  
  13992.  
  13993.         RST     28H             ;; FP-CALC   ;x or 0,d.           first pass.
  13994.         DB    $E0             ;;get-mem-0  ;x or 0,d,1.
  13995.         DB    $A4             ;;stk-ten    ;x or 0,d,1,10.
  13996.         DB    $05             ;;division   ;x or 0,d,1/10.
  13997.         DB    $C0             ;;st-mem-0   ;x or 0,d,1/10.
  13998.         DB    $04             ;;multiply   ;x or 0,d/10.
  13999.         DB    $0F             ;;addition   ;x or 0 + d/10.
  14000.         DB    $38             ;;end-calc   last value.
  14001.  
  14002.         RST     20H             ; NEXT-CHAR  moves to next character
  14003.         JR      L2CDA           ; back to NXT-DGT-1
  14004.  
  14005. ; ---
  14006.  
  14007. ; although only the first pass is shown it can be seen that at each pass
  14008. ; the new less significant digit is multiplied by an increasingly smaller
  14009. ; factor (1/100, 1/1000, 1/10000 ... ) before being added to the previous
  14010. ; last value to form a new last value.
  14011.  
  14012. ; Finally see if an exponent has been input.
  14013.  
  14014. ;; E-FORMAT
  14015. L2CEB:  CP      $45             ; is character 'E' ?
  14016.         JR      Z,L2CF2         ; to SIGN-FLAG if so
  14017.  
  14018.         CP      $65             ; 'e' is acceptable as well.
  14019.         RET     NZ              ; return as no exponent.
  14020.  
  14021. ;; SIGN-FLAG
  14022. L2CF2:  LD      B,$FF           ; initialize temporary sign byte to $FF
  14023.  
  14024.         RST     20H             ; NEXT-CHAR
  14025.         CP      $2B             ; is character '+' ?
  14026.         JR      Z,L2CFE         ; to SIGN-DONE
  14027.  
  14028.         CP      $2D             ; is character '-' ?
  14029.         JR      NZ,L2CFF        ; to ST-E-PART as no sign
  14030.  
  14031.         INC     B               ; set sign to zero
  14032.  
  14033. ; now consider digits of exponent.
  14034. ; Note. incidentally this is the only occasion in Spectrum BASIC when an
  14035. ; expression may not be used when a number is expected.
  14036.  
  14037. ;; SIGN-DONE
  14038. L2CFE:  RST     20H             ; NEXT-CHAR
  14039.  
  14040. ;; ST-E-PART
  14041. L2CFF:  CALL    L2D1B           ; routine NUMERIC
  14042.         JR      C,L2CCF         ; to DEC-RPT-C if not
  14043.                                 ; raise 'Nonsense in BASIC'.
  14044.  
  14045.         PUSH    BC              ; save sign (in B)
  14046.         CALL    L2D3B           ; routine INT-TO-FP places exponent on stack
  14047.         CALL    L2DD5           ; routine FP-TO-A  transfers it to A
  14048.         POP     BC              ; restore sign
  14049.         JP      C,L31AD         ; to REPORT-6 if overflow (over 255)
  14050.                                 ; raise 'Number too big'.
  14051.  
  14052.         AND     A               ; set flags
  14053.         JP      M,L31AD         ; to REPORT-6 if over '127'.
  14054.                                 ; raise 'Number too big'.
  14055.                                 ; 127 is still way too high and it is
  14056.                                 ; impossible to enter an exponent greater
  14057.                                 ; than 39 from the keyboard. The error gets
  14058.                                 ; raised later in E-TO-FP so two different
  14059.                                 ; error messages depending how high A is.
  14060.  
  14061.         INC     B               ; $FF to $00 or $00 to $01 - expendable now.
  14062.         JR      Z,L2D18         ; forward to E-FP-JUMP if exponent positive
  14063.  
  14064.         NEG                     ; Negate the exponent.
  14065.  
  14066. ;; E-FP-JUMP
  14067. L2D18:  JP      L2D4F           ; JUMP forward to E-TO-FP to assign to
  14068.                                 ; last value x on stack x * 10 to power A
  14069.                                 ; a relative jump would have done.
  14070.  
  14071. ; ---------------------
  14072. ; Check for valid digit
  14073. ; ---------------------
  14074. ; This routine checks that the ASCII character in A is numeric
  14075. ; returning with carry reset if so.
  14076.  
  14077. ;; NUMERIC
  14078. L2D1B:  CP      $30             ; '0'
  14079.         RET     C               ; return if less than zero character.
  14080.  
  14081.         CP      $3A             ; The upper test is '9'
  14082.         CCF                     ; Complement Carry Flag
  14083.         RET                     ; Return - carry clear if character '0' - '9'
  14084.  
  14085. ; -----------
  14086. ; Stack Digit
  14087. ; -----------
  14088. ; This subroutine is called from INT-TO-FP and DEC-TO-FP to stack a digit
  14089. ; on the calculator stack.
  14090.  
  14091. ;; STK-DIGIT
  14092. L2D22:  CALL    L2D1B           ; routine NUMERIC
  14093.         RET     C               ; return if not numeric character
  14094.  
  14095.         SUB     $30             ; convert from ASCII to digit
  14096.  
  14097. ; -----------------
  14098. ; Stack accumulator
  14099. ; -----------------
  14100. ;
  14101. ;
  14102.  
  14103. ;; STACK-A
  14104. L2D28:  LD      C,A             ; transfer to C
  14105.         LD      B,$00           ; and make B zero
  14106.  
  14107. ; ----------------------
  14108. ; Stack BC register pair
  14109. ; ----------------------
  14110. ;
  14111.  
  14112. ;; STACK-BC
  14113. L2D2B:  LD      IY,$5C3A        ; re-initialize ERR_NR
  14114.  
  14115.         XOR     A               ; clear to signal small integer
  14116.         LD      E,A             ; place in E for sign
  14117.         LD      D,C             ; LSB to D
  14118.         LD      C,B             ; MSB to C
  14119.         LD      B,A             ; last byte not used
  14120.         CALL    L2AB6           ; routine STK-STORE
  14121.  
  14122.         RST     28H             ;; FP-CALC
  14123.         DB    $38             ;;end-calc  make HL = STKEND-5
  14124.  
  14125.         AND     A               ; clear carry
  14126.         RET                     ; before returning
  14127.  
  14128. ; -------------------------
  14129. ; Integer to floating point
  14130. ; -------------------------
  14131. ; This routine places one or more digits found in a BASIC line
  14132. ; on the calculator stack multiplying the previous value by ten each time
  14133. ; before adding in the new digit to form a last value on calculator stack.
  14134.  
  14135. ;; INT-TO-FP
  14136. L2D3B:  PUSH    AF              ; save first character
  14137.  
  14138.         RST     28H             ;; FP-CALC
  14139.         DB    $A0             ;;stk-zero    ; v=0. initial value
  14140.         DB    $38             ;;end-calc
  14141.  
  14142.         POP     AF              ; fetch first character back.
  14143.  
  14144. ;; NXT-DGT-2
  14145. L2D40:  CALL    L2D22           ; routine STK-DIGIT puts 0-9 on stack
  14146.         RET     C               ; will return when character is not numeric >
  14147.  
  14148.         RST     28H             ;; FP-CALC    ; v, d.
  14149.         DB    $01             ;;exchange    ; d, v.
  14150.         DB    $A4             ;;stk-ten     ; d, v, 10.
  14151.         DB    $04             ;;multiply    ; d, v*10.
  14152.         DB    $0F             ;;addition    ; d + v*10 = newvalue
  14153.         DB    $38             ;;end-calc    ; v.
  14154.  
  14155.         CALL    L0074           ; routine CH-ADD+1 get next character
  14156.         JR      L2D40           ; back to NXT-DGT-2 to process as a digit
  14157.  
  14158.  
  14159. ;*********************************
  14160. ;** Part 9. ARITHMETIC ROUTINES **
  14161. ;*********************************
  14162.  
  14163. ; --------------------------
  14164. ; E-format to floating point
  14165. ; --------------------------
  14166. ; This subroutine is used by the PRINT-FP routine and the decimal to FP
  14167. ; routines to stack a number expressed in exponent format.
  14168. ; Note. Though not used by the ROM as such, it has also been set up as
  14169. ; a unary calculator literal but this will not work as the accumulator
  14170. ; is not available from within the calculator.
  14171.  
  14172. ; on entry there is a value x on the calculator stack and an exponent of ten
  14173. ; in A.    The required value is x + 10 ^ A
  14174.  
  14175. ;; e-to-fp
  14176. ;; E-TO-FP
  14177. L2D4F:  RLCA                    ; this will set the          x.
  14178.         RRCA                    ; carry if bit 7 is set
  14179.  
  14180.         JR      NC,L2D55        ; to E-SAVE  if positive.
  14181.  
  14182.         CPL                     ; make negative positive
  14183.         INC     A               ; without altering carry.
  14184.  
  14185. ;; E-SAVE
  14186. L2D55:  PUSH    AF              ; save positive exp and sign in carry
  14187.  
  14188.         LD      HL,$5C92        ; address MEM-0
  14189.  
  14190.         CALL    L350B           ; routine FP-0/1
  14191.                                 ; places an integer zero, if no carry,
  14192.                                 ; else a one in mem-0 as a sign flag
  14193.  
  14194.         RST     28H             ;; FP-CALC
  14195.         DB    $A4             ;;stk-ten                    x, 10.
  14196.         DB    $38             ;;end-calc
  14197.  
  14198.         POP     AF              ; pop the exponent.
  14199.  
  14200. ; now enter a loop
  14201.  
  14202. ;; E-LOOP
  14203. L2D60:  SRL     A               ; 0>76543210>C
  14204.  
  14205.         JR      NC,L2D71        ; forward to E-TST-END if no bit
  14206.  
  14207.         PUSH    AF              ; save shifted exponent.
  14208.  
  14209.         RST     28H             ;; FP-CALC
  14210.         DB    $C1             ;;st-mem-1                   x, 10.
  14211.         DB    $E0             ;;get-mem-0                  x, 10, (0/1).
  14212.         DB    $00             ;;jump-true
  14213.  
  14214.         DB    $04             ;;to L2D6D, E-DIVSN
  14215.  
  14216.         DB    $04             ;;multiply                   x*10.
  14217.         DB    $33             ;;jump
  14218.  
  14219.         DB    $02             ;;to L2D6E, E-FETCH
  14220.  
  14221. ;; E-DIVSN
  14222. L2D6D:  DB    $05             ;;division                   x/10.
  14223.  
  14224. ;; E-FETCH
  14225. L2D6E:  DB    $E1             ;;get-mem-1                  x/10 or x*10, 10.
  14226.         DB    $38             ;;end-calc                   new x, 10.
  14227.  
  14228.         POP     AF              ; restore shifted exponent
  14229.  
  14230. ; the loop branched to here with no carry
  14231.  
  14232. ;; E-TST-END
  14233. L2D71:  JR      Z,L2D7B         ; forward to E-END  if A emptied of bits
  14234.  
  14235.         PUSH    AF              ; re-save shifted exponent
  14236.  
  14237.         RST     28H             ;; FP-CALC
  14238.         DB    $31             ;;duplicate                  new x, 10, 10.
  14239.         DB    $04             ;;multiply                   new x, 100.
  14240.         DB    $38             ;;end-calc
  14241.  
  14242.         POP     AF              ; restore shifted exponent
  14243.         JR      L2D60           ; back to E-LOOP  until all bits done.
  14244.  
  14245. ; ---
  14246.  
  14247. ; although only the first pass is shown it can be seen that for each set bit
  14248. ; representing a power of two, x is multiplied or divided by the
  14249. ; corresponding power of ten.
  14250.  
  14251. ;; E-END
  14252. L2D7B:  RST     28H             ;; FP-CALC                   final x, factor.
  14253.         DB    $02             ;;delete                     final x.
  14254.         DB    $38             ;;end-calc                   x.
  14255.  
  14256.         RET                     ; return
  14257.  
  14258.  
  14259.  
  14260.  
  14261. ; -------------
  14262. ; Fetch integer
  14263. ; -------------
  14264. ; This routine is called by the mathematical routines - FP-TO-BC, PRINT-FP,
  14265. ; mult, re-stack and negate to fetch an integer from address HL.
  14266. ; HL points to the stack or a location in MEM and no deletion occurs.
  14267. ; If the number is negative then a similar process to that used in INT-STORE
  14268. ; is used to restore the twos complement number to normal in DE and a sign
  14269. ; in C.
  14270.  
  14271. ;; INT-FETCH
  14272. L2D7F:  INC     HL              ; skip zero indicator.
  14273.         LD      C,(HL)          ; fetch sign to C
  14274.         INC     HL              ; address low byte
  14275.         LD      A,(HL)          ; fetch to A
  14276.         XOR     C               ; two's complement
  14277.         SUB     C               ;
  14278.         LD      E,A             ; place in E
  14279.         INC     HL              ; address high byte
  14280.         LD      A,(HL)          ; fetch to A
  14281.         ADC     A,C             ; two's complement
  14282.         XOR     C               ;
  14283.         LD      D,A             ; place in D
  14284.         RET                     ; return
  14285.  
  14286. ; ------------------------
  14287. ; Store a positive integer
  14288. ; ------------------------
  14289. ; This entry point is not used in this ROM but would
  14290. ; store any integer as positive.
  14291.  
  14292. ;; p-int-sto
  14293. L2D8C:  LD      C,$00           ; make sign byte positive and continue
  14294.  
  14295. ; -------------
  14296. ; Store integer
  14297. ; -------------
  14298. ; this routine stores an integer in DE at address HL.
  14299. ; It is called from mult, truncate, negate and sgn.
  14300. ; The sign byte $00 +ve or $FF -ve is in C.
  14301. ; If negative, the number is stored in 2's complement form so that it is
  14302. ; ready to be added.
  14303.  
  14304. ;; INT-STORE
  14305. L2D8E:  PUSH    HL              ; preserve HL
  14306.  
  14307.         LD      (HL),$00        ; first byte zero shows integer not exponent
  14308.         INC     HL              ;
  14309.         LD      (HL),C          ; then store the sign byte
  14310.         INC     HL              ;
  14311.                                 ; e.g.             +1             -1
  14312.         LD      A,E             ; fetch low byte   00000001       00000001
  14313.         XOR     C               ; xor sign         00000000   or  11111111
  14314.                                 ; gives            00000001   or  11111110
  14315.         SUB     C               ; sub sign         00000000   or  11111111
  14316.                                 ; gives            00000001>0 or  11111111>C
  14317.         LD      (HL),A          ; store 2's complement.
  14318.         INC     HL              ;
  14319.         LD      A,D             ; high byte        00000000       00000000
  14320.         ADC     A,C             ; sign             00000000<0     11111111<C
  14321.                                 ; gives            00000000   or  00000000
  14322.         XOR     C               ; xor sign         00000000       11111111
  14323.         LD      (HL),A          ; store 2's complement.
  14324.         INC     HL              ;
  14325.         LD      (HL),$00        ; last byte always zero for integers.
  14326.                                 ; is not used and need not be looked at when
  14327.                                 ; testing for zero but comes into play should
  14328.                                 ; an integer be converted to fp.
  14329.         POP     HL              ; restore HL
  14330.         RET                     ; return.
  14331.  
  14332.  
  14333. ; -----------------------------
  14334. ; Floating point to BC register
  14335. ; -----------------------------
  14336. ; This routine gets a floating point number e.g. 127.4 from the calculator
  14337. ; stack to the BC register.
  14338.  
  14339. ;; FP-TO-BC
  14340. L2DA2:  RST     28H             ;; FP-CALC            set HL to
  14341.         DB    $38             ;;end-calc            point to last value.
  14342.  
  14343.         LD      A,(HL)          ; get first of 5 bytes
  14344.         AND     A               ; and test
  14345.         JR      Z,L2DAD         ; forward to FP-DELETE if an integer
  14346.  
  14347. ; The value is first rounded up and then converted to integer.
  14348.  
  14349.         RST     28H             ;; FP-CALC           x.
  14350.         DB    $A2             ;;stk-half           x. 1/2.
  14351.         DB    $0F             ;;addition           x + 1/2.
  14352.         DB    $27             ;;int                int(x + .5)
  14353.         DB    $38             ;;end-calc
  14354.  
  14355. ; now delete but leave HL pointing at integer
  14356.  
  14357. ;; FP-DELETE
  14358. L2DAD:  RST     28H             ;; FP-CALC
  14359.         DB    $02             ;;delete
  14360.         DB    $38             ;;end-calc
  14361.  
  14362.         PUSH    HL              ; save pointer.
  14363.         PUSH    DE              ; and STKEND.
  14364.         EX      DE,HL           ; make HL point to exponent/zero indicator
  14365.         LD      B,(HL)          ; indicator to B
  14366.         CALL    L2D7F           ; routine INT-FETCH
  14367.                                 ; gets int in DE sign byte to C
  14368.                                 ; but meaningless values if a large integer
  14369.  
  14370.         XOR     A               ; clear A
  14371.         SUB     B               ; subtract indicator byte setting carry
  14372.                                 ; if not a small integer.
  14373.  
  14374.         BIT     7,C             ; test a bit of the sign byte setting zero
  14375.                                 ; if positive.
  14376.  
  14377.         LD      B,D             ; transfer int
  14378.         LD      C,E             ; to BC
  14379.         LD      A,E             ; low byte to A as a useful return value.
  14380.  
  14381.         POP     DE              ; pop STKEND
  14382.         POP     HL              ; and pointer to last value
  14383.         RET                     ; return
  14384.                                 ; if carry is set then the number was too big.
  14385.  
  14386. ; ------------
  14387. ; LOG(2^A)
  14388. ; ------------
  14389. ; This routine is used when printing floating point numbers to calculate
  14390. ; the number of digits before the decimal point.
  14391.  
  14392. ; first convert a one-byte signed integer to its five byte form.
  14393.  
  14394. ;; LOG(2^A)
  14395. L2DC1:  LD      D,A             ; store a copy of A in D.
  14396.         RLA                     ; test sign bit of A.
  14397.         SBC     A,A             ; now $FF if negative or $00
  14398.         LD      E,A             ; sign byte to E.
  14399.         LD      C,A             ; and to C
  14400.         XOR     A               ; clear A
  14401.         LD      B,A             ; and B.
  14402.         CALL    L2AB6           ; routine STK-STORE stacks number AEDCB
  14403.  
  14404. ;  so 00 00 XX 00 00 (positive) or 00 FF XX FF 00 (negative).
  14405. ;  i.e. integer indicator, sign byte, low, high, unused.
  14406.  
  14407. ; now multiply exponent by log to the base 10 of two.
  14408.  
  14409.         RST      28H            ;; FP-CALC
  14410.  
  14411.         DB    $34             ;;stk-data                      .30103 (log 2)
  14412.         DB    $EF             ;;Exponent: $7F, Bytes: 4
  14413.         DB    $1A,$20,$9A,$85 ;;
  14414.         DB    $04             ;;multiply
  14415.  
  14416.         DB    $27             ;;int
  14417.  
  14418.         DB    $38             ;;end-calc
  14419.  
  14420. ; -------------------
  14421. ; Floating point to A
  14422. ; -------------------
  14423. ; this routine collects a floating point number from the stack into the
  14424. ; accumulator returning carry set if not in range 0 - 255.
  14425. ; Not all the calling routines raise an error with overflow so no attempt
  14426. ; is made to produce an error report here.
  14427.  
  14428. ;; FP-TO-A
  14429. L2DD5:  CALL    L2DA2           ; routine FP-TO-BC returns with C in A also.
  14430.         RET     C               ; return with carry set if > 65535, overflow
  14431.  
  14432.         PUSH    AF              ; save the value and flags
  14433.         DEC     B               ; and test that
  14434.         INC     B               ; the high byte is zero.
  14435.         JR      Z,L2DE1         ; forward  FP-A-END if zero
  14436.  
  14437. ; else there has been 8-bit overflow
  14438.  
  14439.         POP     AF              ; retrieve the value
  14440.         SCF                     ; set carry flag to show overflow
  14441.         RET                     ; and return.
  14442.  
  14443. ; ---
  14444.  
  14445. ;; FP-A-END
  14446. L2DE1:  POP     AF              ; restore value and success flag and
  14447.         RET                     ; return.
  14448.  
  14449.  
  14450. ; -----------------------------
  14451. ; Print a floating point number
  14452. ; -----------------------------
  14453. ; Not a trivial task.
  14454. ; Begin by considering whether to print a leading sign for negative numbers.
  14455.  
  14456. ;; PRINT-FP
  14457. L2DE3:  RST     28H             ;; FP-CALC
  14458.         DB    $31             ;;duplicate
  14459.         DB    $36             ;;less-0
  14460.         DB    $00             ;;jump-true
  14461.  
  14462.         DB    $0B             ;;to L2DF2, PF-NEGTVE
  14463.  
  14464.         DB    $31             ;;duplicate
  14465.         DB    $37             ;;greater-0
  14466.         DB    $00             ;;jump-true
  14467.  
  14468.         DB    $0D             ;;to L2DF8, PF-POSTVE
  14469.  
  14470. ; must be zero itself
  14471.  
  14472.         DB    $02             ;;delete
  14473.         DB    $38             ;;end-calc
  14474.  
  14475.         LD      A,$30           ; prepare the character '0'
  14476.  
  14477.         RST     10H             ; PRINT-A
  14478.         RET                     ; return.                 ->
  14479. ; ---
  14480.  
  14481. ;; PF-NEGTVE
  14482. L2DF2:  DB    $2A             ;;abs
  14483.         DB    $38             ;;end-calc
  14484.  
  14485.         LD      A,$2D           ; the character '-'
  14486.  
  14487.         RST     10H             ; PRINT-A
  14488.  
  14489. ; and continue to print the now positive number.
  14490.  
  14491.         RST     28H             ;; FP-CALC
  14492.  
  14493. ;; PF-POSTVE
  14494. L2DF8:  DB    $A0             ;;stk-zero     x,0.     begin by
  14495.         DB    $C3             ;;st-mem-3     x,0.     clearing a temporary
  14496.         DB    $C4             ;;st-mem-4     x,0.     output buffer to
  14497.         DB    $C5             ;;st-mem-5     x,0.     fifteen zeros.
  14498.         DB    $02             ;;delete       x.
  14499.         DB    $38             ;;end-calc     x.
  14500.  
  14501.         EXX                     ; in case called from 'str$' then save the
  14502.         PUSH    HL              ; pointer to whatever comes after
  14503.         EXX                     ; str$ as H'L' will be used.
  14504.  
  14505. ; now enter a loop?
  14506.  
  14507. ;; PF-LOOP
  14508. L2E01:  RST     28H             ;; FP-CALC
  14509.         DB    $31             ;;duplicate    x,x.
  14510.         DB    $27             ;;int          x,int x.
  14511.         DB    $C2             ;;st-mem-2     x,int x.
  14512.         DB    $03             ;;subtract     x-int x.     fractional part.
  14513.         DB    $E2             ;;get-mem-2    x-int x, int x.
  14514.         DB    $01             ;;exchange     int x, x-int x.
  14515.         DB    $C2             ;;st-mem-2     int x, x-int x.
  14516.         DB    $02             ;;delete       int x.
  14517.         DB    $38             ;;end-calc     int x.
  14518.                                 ;
  14519.                                 ; mem-2 holds the fractional part.
  14520.  
  14521. ; HL points to last value int x
  14522.  
  14523.         LD      A,(HL)          ; fetch exponent of int x.
  14524.         AND     A               ; test
  14525.         JR      NZ,L2E56        ; forward to PF-LARGE if a large integer
  14526.                                 ; > 65535
  14527.  
  14528. ; continue with small positive integer components in range 0 - 65535
  14529. ; if original number was say .999 then this integer component is zero.
  14530.  
  14531.         CALL    L2D7F           ; routine INT-FETCH gets x in DE
  14532.                                 ; (but x is not deleted)
  14533.  
  14534.         LD      B,$10           ; set B, bit counter, to 16d
  14535.  
  14536.         LD      A,D             ; test if
  14537.         AND     A               ; high byte is zero
  14538.         JR      NZ,L2E1E        ; forward to PF-SAVE if 16-bit integer.
  14539.  
  14540. ; and continue with integer in range 0 - 255.
  14541.  
  14542.         OR      E               ; test the low byte for zero
  14543.                                 ; i.e. originally just point something or other.
  14544.         JR      Z,L2E24         ; forward if so to PF-SMALL
  14545.  
  14546. ;
  14547.  
  14548.         LD      D,E             ; transfer E to D
  14549.         LD      B,$08           ; and reduce the bit counter to 8.
  14550.  
  14551. ;; PF-SAVE
  14552. L2E1E:  PUSH    DE              ; save the part before decimal point.
  14553.         EXX                     ;
  14554.         POP     DE              ; and pop in into D'E'
  14555.         EXX                     ;
  14556.         JR      L2E7B           ; forward to PF-BITS
  14557.  
  14558. ; ---------------------
  14559.  
  14560. ; the branch was here when 'int x' was found to be zero as in say 0.5.
  14561. ; The zero has been fetched from the calculator stack but not deleted and
  14562. ; this should occur now. This omission leaves the stack unbalanced and while
  14563. ; that causes no problems with a simple PRINT statement, it will if str$ is
  14564. ; being used in an expression e.g. "2" + STR$ 0.5 gives the result "0.5"
  14565. ; instead of the expected result "20.5".
  14566. ; credit Tony Stratton, 1982.
  14567. ; A DB 02 delete is required immediately on using the calculator.
  14568.  
  14569. ;; PF-SMALL
  14570. L2E24:  RST     28H             ;; FP-CALC       int x = 0.
  14571. L2E25:  DB    $E2             ;;get-mem-2      int x = 0, x-int x.
  14572.         DB    $38             ;;end-calc
  14573.  
  14574.         LD      A,(HL)          ; fetch exponent of positive fractional number
  14575.         SUB     $7E             ; subtract
  14576.  
  14577.         CALL    L2DC1           ; routine LOG(2^A) calculates leading digits.
  14578.  
  14579.         LD      D,A             ; transfer count to D
  14580.         LD      A,($5CAC)       ; fetch total MEM-5-1
  14581.         SUB     D               ;
  14582.         LD      ($5CAC),A       ; MEM-5-1
  14583.         LD      A,D             ;
  14584.         CALL    L2D4F           ; routine E-TO-FP
  14585.  
  14586.         RST     28H             ;; FP-CALC
  14587.         DB    $31             ;;duplicate
  14588.         DB    $27             ;;int
  14589.         DB    $C1             ;;st-mem-1
  14590.         DB    $03             ;;subtract
  14591.         DB    $E1             ;;get-mem-1
  14592.         DB    $38             ;;end-calc
  14593.  
  14594.         CALL    L2DD5           ; routine FP-TO-A
  14595.  
  14596.         PUSH    HL              ; save HL
  14597.         LD      ($5CA1),A       ; MEM-3-1
  14598.         DEC     A               ;
  14599.         RLA                     ;
  14600.         SBC     A,A             ;
  14601.         INC     A               ;
  14602.  
  14603.         LD      HL,$5CAB        ; address MEM-5-1 leading digit counter
  14604.         LD      (HL),A          ; store counter
  14605.         INC     HL              ; address MEM-5-2 total digits
  14606.         ADD     A,(HL)          ; add counter to contents
  14607.         LD      (HL),A          ; and store updated value
  14608.         POP     HL              ; restore HL
  14609.  
  14610.         JP      L2ECF           ; JUMP forward to PF-FRACTN
  14611.  
  14612. ; ---
  14613.  
  14614. ; Note. while it would be pedantic to comment on every occasion a JP
  14615. ; instruction could be replaced with a JR instruction, this applies to the
  14616. ; above, which is useful if you wish to correct the unbalanced stack error
  14617. ; by inserting a 'DB 02 delete' at L2E25, and maintain main addresses.
  14618.  
  14619. ; the branch was here with a large positive integer > 65535 e.g. 123456789
  14620. ; the accumulator holds the exponent.
  14621.  
  14622. ;; PF-LARGE
  14623. L2E56:  SUB     $80             ; make exponent positive
  14624.         CP      $1C             ; compare to 28
  14625.         JR      C,L2E6F         ; to PF-MEDIUM if integer <= 2^27
  14626.  
  14627.         CALL    L2DC1           ; routine LOG(2^A)
  14628.         SUB     $07             ;
  14629.         LD      B,A             ;
  14630.         LD      HL,$5CAC        ; address MEM-5-1 the leading digits counter.
  14631.         ADD     A,(HL)          ; add A to contents
  14632.         LD      (HL),A          ; store updated value.
  14633.         LD      A,B             ;
  14634.         NEG                     ; negate
  14635.         CALL    L2D4F           ; routine E-TO-FP
  14636.         JR      L2E01           ; back to PF-LOOP
  14637.  
  14638. ; ----------------------------
  14639.  
  14640. ;; PF-MEDIUM
  14641. L2E6F:  EX      DE,HL           ;
  14642.         CALL    L2FBA           ; routine FETCH-TWO
  14643.         EXX                     ;
  14644.         SET     7,D             ;
  14645.         LD      A,L             ;
  14646.         EXX                     ;
  14647.         SUB     $80             ;
  14648.         LD      B,A             ;
  14649.  
  14650. ; the branch was here to handle bits in DE with 8 or 16 in B  if small int
  14651. ; and integer in D'E', 6 nibbles will accommodate 065535 but routine does
  14652. ; 32-bit numbers as well from above
  14653.  
  14654. ;; PF-BITS
  14655. L2E7B:  SLA     E               ;  C<xxxxxxxx<0
  14656.         RL      D               ;  C<xxxxxxxx<C
  14657.         EXX                     ;
  14658.         RL      E               ;  C<xxxxxxxx<C
  14659.         RL      D               ;  C<xxxxxxxx<C
  14660.         EXX                     ;
  14661.  
  14662.         LD      HL,$5CAA        ; set HL to mem-4-5th last byte of buffer
  14663.         LD      C,$05           ; set byte count to 5 -  10 nibbles
  14664.  
  14665. ;; PF-BYTES
  14666. L2E8A:  LD      A,(HL)          ; fetch 0 or prev value
  14667.         ADC     A,A             ; shift left add in carry    C<xxxxxxxx<C
  14668.  
  14669.         DAA                     ; Decimal Adjust Accumulator.
  14670.                                 ; if greater than 9 then the left hand
  14671.                                 ; nibble is incremented. If greater than
  14672.                                 ; 99 then adjusted and carry set.
  14673.                                 ; so if we'd built up 7 and a carry came in
  14674.                                 ;      0000 0111 < C
  14675.                                 ;      0000 1111
  14676.                                 ; daa     1 0101  which is 15 in BCD
  14677.  
  14678.         LD      (HL),A          ; put back
  14679.         DEC     HL              ; work down thru mem 4
  14680.         DEC     C               ; decrease the 5 counter.
  14681.         JR      NZ,L2E8A        ; back to PF-BYTES until the ten nibbles rolled
  14682.  
  14683.         DJNZ    L2E7B           ; back to PF-BITS until 8 or 16 (or 32) done
  14684.  
  14685. ; at most 9 digits for 32-bit number will have been loaded with digits
  14686. ; each of the 9 nibbles in mem 4 is placed into ten bytes in mem-3 and mem 4
  14687. ; unless the nibble is zero as the buffer is already zero.
  14688. ; ( or in the case of mem-5 will become zero as a result of RLD instruction )
  14689.  
  14690.         XOR     A               ; clear to accept
  14691.         LD      HL,$5CA6        ; address MEM-4-0 byte destination.
  14692.         LD      DE,$5CA1        ; address MEM-3-0 nibble source.
  14693.         LD      B,$09           ; the count is 9 (not ten) as the first
  14694.                                 ; nibble is known to be blank.
  14695.  
  14696.         RLD                     ; shift RH nibble to left in (HL)
  14697.                                 ;    A           (HL)
  14698.                                 ; 0000 0000 < 0000 3210
  14699.                                 ; 0000 0000   3210 0000
  14700.                                 ; A picks up the blank nibble
  14701.  
  14702.  
  14703.         LD      C,$FF           ; set a flag to indicate when a significant
  14704.                                 ; digit has been encountered.
  14705.  
  14706. ;; PF-DIGITS
  14707. L2EA1:  RLD                     ; pick up leftmost nibble from (HL)
  14708.                                 ;    A           (HL)
  14709.                                 ; 0000 0000 < 7654 3210
  14710.                                 ; 0000 7654   3210 0000
  14711.  
  14712.  
  14713.         JR      NZ,L2EA9        ; to PF-INSERT if non-zero value picked up.
  14714.  
  14715.         DEC     C               ; test
  14716.         INC     C               ; flag
  14717.         JR      NZ,L2EB3        ; skip forward to PF-TEST-2 if flag still $FF
  14718.                                 ; indicating this is a leading zero.
  14719.  
  14720. ; but if the zero is a significant digit e.g. 10 then include in digit totals.
  14721. ; the path for non-zero digits rejoins here.
  14722.  
  14723. ;; PF-INSERT
  14724. L2EA9:  LD      (DE),A          ; insert digit at destination
  14725.         INC     DE              ; increase the destination pointer
  14726.         INC     (IY+$71)        ; increment MEM-5-1st  digit counter
  14727.         INC     (IY+$72)        ; increment MEM-5-2nd  leading digit counter
  14728.         LD      C,$00           ; set flag to zero indicating that any
  14729.                                 ; subsequent zeros are significant and not
  14730.                                 ; leading.
  14731.  
  14732. ;; PF-TEST-2
  14733. L2EB3:  BIT     0,B             ; test if the nibble count is even
  14734.         JR      Z,L2EB8         ; skip to PF-ALL-9 if so to deal with the
  14735.                                 ; other nibble in the same byte
  14736.  
  14737.         INC     HL              ; point to next source byte if not
  14738.  
  14739. ;; PF-ALL-9
  14740. L2EB8:  DJNZ    L2EA1           ; decrement the nibble count, back to PF-DIGITS
  14741.                                 ; if all nine not done.
  14742.  
  14743. ; For 8-bit integers there will be at most 3 digits.
  14744. ; For 16-bit integers there will be at most 5 digits.
  14745. ; but for larger integers there could be nine leading digits.
  14746. ; if nine digits complete then the last one is rounded up as the number will
  14747. ; be printed using E-format notation
  14748.  
  14749.         LD      A,($5CAB)       ; fetch digit count from MEM-5-1st
  14750.         SUB     $09             ; subtract 9 - max possible
  14751.         JR      C,L2ECB         ; forward if less to PF-MORE
  14752.  
  14753.         DEC     (IY+$71)        ; decrement digit counter MEM-5-1st to 8
  14754.         LD      A,$04           ; load A with the value 4.
  14755.         CP      (IY+$6F)        ; compare with MEM-4-4th - the ninth digit
  14756.         JR      L2F0C           ; forward to PF-ROUND
  14757.                                 ; to consider rounding.
  14758.  
  14759. ; ---------------------------------------
  14760.  
  14761. ; now delete int x from calculator stack and fetch fractional part.
  14762.  
  14763. ;; PF-MORE
  14764. L2ECB:  RST     28H             ;; FP-CALC        int x.
  14765.         DB    $02             ;;delete          .
  14766.         DB    $E2             ;;get-mem-2       x - int x = f.
  14767.         DB    $38             ;;end-calca       f.
  14768.  
  14769. ;; PF-FRACTN
  14770. L2ECF:  EX      DE,HL           ;
  14771.         CALL    L2FBA           ; routine FETCH-TWO
  14772.         EXX                     ;
  14773.         LD      A,$80           ;
  14774.         SUB     L               ;
  14775.         LD      L,$00           ;
  14776.         SET     7,D             ;
  14777.         EXX                     ;
  14778.         CALL    L2FDD           ; routine SHIFT-FP
  14779.  
  14780. ;; PF-FRN-LP
  14781. L2EDF:  LD      A,(IY+$71)      ; MEM-5-1st
  14782.         CP      $08             ;
  14783.         JR      C,L2EEC         ; to PF-FR-DGT
  14784.  
  14785.         EXX                     ;
  14786.         RL      D               ;
  14787.         EXX                     ;
  14788.         JR      L2F0C           ; to PF-ROUND
  14789.  
  14790. ; ---
  14791.  
  14792. ;; PF-FR-DGT
  14793. L2EEC:  LD      BC,$0200        ;
  14794.  
  14795. ;; PF-FR-EXX
  14796. L2EEF:  LD      A,E             ;
  14797.         CALL    L2F8B           ; routine CA-10*A+C
  14798.         LD      E,A             ;
  14799.         LD      A,D             ;
  14800.         CALL    L2F8B           ; routine CA-10*A+C
  14801.         LD      D,A             ;
  14802.         PUSH    BC              ;
  14803.         EXX                     ;
  14804.         POP     BC              ;
  14805.         DJNZ    L2EEF           ; to PF-FR-EXX
  14806.  
  14807.         LD      HL,$5CA1        ; MEM-3
  14808.         LD      A,C             ;
  14809.         LD      C,(IY+$71)      ; MEM-5-1st
  14810.         ADD     HL,BC           ;
  14811.         LD      (HL),A          ;
  14812.         INC     (IY+$71)        ; MEM-5-1st
  14813.         JR      L2EDF           ; to PF-FRN-LP
  14814.  
  14815. ; ----------------
  14816.  
  14817. ; 1) with 9 digits but 8 in mem-5-1 and A holding 4, carry set if rounding up.
  14818. ; e.g.
  14819. ;      999999999 is printed as 1E+9
  14820. ;      100000001 is printed as 1E+8
  14821. ;      100000009 is printed as 1.0000001E+8
  14822.  
  14823. ;; PF-ROUND
  14824. L2F0C:  PUSH    AF              ; save A and flags
  14825.         LD      HL,$5CA1        ; address MEM-3 start of digits
  14826.         LD      C,(IY+$71)      ; MEM-5-1st No. of digits to C
  14827.         LD      B,$00           ; prepare to add
  14828.         ADD     HL,BC           ; address last digit + 1
  14829.         LD      B,C             ; No. of digits to B counter
  14830.         POP     AF              ; restore A and carry flag from comparison.
  14831.  
  14832. ;; PF-RND-LP
  14833. L2F18:  DEC     HL              ; address digit at rounding position.
  14834.         LD      A,(HL)          ; fetch it
  14835.         ADC     A,$00           ; add carry from the comparison
  14836.         LD      (HL),A          ; put back result even if $0A.
  14837.         AND     A               ; test A
  14838.         JR      Z,L2F25         ; skip to PF-R-BACK if ZERO?
  14839.  
  14840.         CP      $0A             ; compare to 'ten' - overflow
  14841.         CCF                     ; complement carry flag so that set if ten.
  14842.         JR      NC,L2F2D        ; forward to PF-COUNT with 1 - 9.
  14843.  
  14844. ;; PF-R-BACK
  14845. L2F25:  DJNZ    L2F18           ; loop back to PF-RND-LP
  14846.  
  14847. ; if B counts down to zero then we've rounded right back as in 999999995.
  14848. ; and the first 8 locations all hold $0A.
  14849.  
  14850.  
  14851.         LD      (HL),$01        ; load first location with digit 1.
  14852.         INC     B               ; make B hold 1 also.
  14853.                                 ; could save an instruction byte here.
  14854.         INC     (IY+$72)        ; make MEM-5-2nd hold 1.
  14855.                                 ; and proceed to initialize total digits to 1.
  14856.  
  14857. ;; PF-COUNT
  14858. L2F2D:  LD      (IY+$71),B      ; MEM-5-1st
  14859.  
  14860. ; now balance the calculator stack by deleting  it
  14861.  
  14862.         RST     28H             ;; FP-CALC
  14863.         DB    $02             ;;delete
  14864.         DB    $38             ;;end-calc
  14865.  
  14866. ; note if used from str$ then other values may be on the calculator stack.
  14867. ; we can also restore the next literal pointer from its position on the
  14868. ; machine stack.
  14869.  
  14870.         EXX                     ;
  14871.         POP     HL              ; restore next literal pointer.
  14872.         EXX                     ;
  14873.  
  14874.         LD      BC,($5CAB)      ; set C to MEM-5-1st digit counter.
  14875.                                 ; set B to MEM-5-2nd leading digit counter.
  14876.         LD      HL,$5CA1        ; set HL to start of digits at MEM-3-1
  14877.         LD      A,B             ;
  14878.         CP      $09             ;
  14879.         JR      C,L2F46         ; to PF-NOT-E
  14880.  
  14881.         CP      $FC             ;
  14882.         JR      C,L2F6C         ; to PF-E-FRMT
  14883.  
  14884. ;; PF-NOT-E
  14885. L2F46:  AND     A               ; test for zero leading digits as in .123
  14886.  
  14887.         CALL    Z,L15EF         ; routine OUT-CODE prints a zero e.g. 0.123
  14888.  
  14889. ;; PF-E-SBRN
  14890. L2F4A:  XOR     A               ;
  14891.         SUB     B               ;
  14892.         JP      M,L2F52         ; skip forward to PF-OUT-LP if originally +ve
  14893.  
  14894.         LD      B,A             ; else negative count now +ve
  14895.         JR      L2F5E           ; forward to PF-DC-OUT       ->
  14896.  
  14897. ; ---
  14898.  
  14899. ;; PF-OUT-LP
  14900. L2F52:  LD      A,C             ; fetch total digit count
  14901.         AND     A               ; test for zero
  14902.         JR      Z,L2F59         ; forward to PF-OUT-DT if so
  14903.  
  14904.         LD      A,(HL)          ; fetch digit
  14905.         INC     HL              ; address next digit
  14906.         DEC     C               ; decrease total digit counter
  14907.  
  14908. ;; PF-OUT-DT
  14909. L2F59:  CALL    L15EF           ; routine OUT-CODE outputs it.
  14910.         DJNZ    L2F52           ; loop back to PF-OUT-LP until B leading
  14911.                                 ; digits output.
  14912.  
  14913. ;; PF-DC-OUT
  14914. L2F5E:  LD      A,C             ; fetch total digits and
  14915.         AND     A               ; test if also zero
  14916.         RET     Z               ; return if so              -->
  14917.  
  14918. ;
  14919.  
  14920.         INC     B               ; increment B
  14921.         LD      A,$2E           ; prepare the character '.'
  14922.  
  14923. ;; PF-DEC-0$
  14924. L2F64:  RST     10H             ; PRINT-A outputs the character '.' or '0'
  14925.  
  14926.         LD      A,$30           ; prepare the character '0'
  14927.                                 ; (for cases like .000012345678)
  14928.         DJNZ    L2F64           ; loop back to PF-DEC-0$ for B times.
  14929.  
  14930.         LD      B,C             ; load B with now trailing digit counter.
  14931.         JR      L2F52           ; back to PF-OUT-LP
  14932.  
  14933. ; ---------------------------------
  14934.  
  14935. ; the branch was here for E-format printing e.g 123456789 => 1.2345679e+8
  14936.  
  14937. ;; PF-E-FRMT
  14938. L2F6C:  LD      D,B             ; counter to D
  14939.         DEC     D               ; decrement
  14940.         LD      B,$01           ; load B with 1.
  14941.  
  14942.         CALL    L2F4A           ; routine PF-E-SBRN above
  14943.  
  14944.         LD      A,$45           ; prepare character 'e'
  14945.         RST     10H             ; PRINT-A
  14946.  
  14947.         LD      C,D             ; exponent to C
  14948.         LD      A,C             ; and to A
  14949.         AND     A               ; test exponent
  14950.         JP      P,L2F83         ; to PF-E-POS if positive
  14951.  
  14952.         NEG                     ; negate
  14953.         LD      C,A             ; positive exponent to C
  14954.         LD      A,$2D           ; prepare character '-'
  14955.         JR      L2F85           ; skip to PF-E-SIGN
  14956.  
  14957. ; ---
  14958.  
  14959. ;; PF-E-POS
  14960. L2F83:  LD      A,$2B           ; prepare character '+'
  14961.  
  14962. ;; PF-E-SIGN
  14963. L2F85:  RST     10H             ; PRINT-A outputs the sign
  14964.  
  14965.         LD      B,$00           ; make the high byte zero.
  14966.         JP      L1A1B           ; exit via OUT-NUM-1 to print exponent in BC
  14967.  
  14968. ; ------------------------------
  14969. ; Handle printing floating point
  14970. ; ------------------------------
  14971. ; This subroutine is called twice from above when printing floating-point
  14972. ; numbers. It returns 10*A +C in registers C and A
  14973.  
  14974. ;; CA-10*A+C
  14975. L2F8B:  PUSH    DE              ; preserve DE.
  14976.         LD      L,A             ; transfer A to L
  14977.         LD      H,$00           ; zero high byte.
  14978.         LD      E,L             ; copy HL
  14979.         LD      D,H             ; to DE.
  14980.         ADD     HL,HL           ; double (*2)
  14981.         ADD     HL,HL           ; double (*4)
  14982.         ADD     HL,DE           ; add DE (*5)
  14983.         ADD     HL,HL           ; double (*10)
  14984.         LD      E,C             ; copy C to E    (D is 0)
  14985.         ADD     HL,DE           ; and add to give required result.
  14986.         LD      C,H             ; transfer to
  14987.         LD      A,L             ; destination registers.
  14988.         POP     DE              ; restore DE
  14989.         RET                     ; return with result.
  14990.  
  14991. ; --------------
  14992. ; Prepare to add
  14993. ; --------------
  14994. ; This routine is called twice by addition to prepare the two numbers. The
  14995. ; exponent is picked up in A and the location made zero. Then the sign bit
  14996. ; is tested before being set to the implied state. Negative numbers are twos
  14997. ; complemented.
  14998.  
  14999. ;; PREP-ADD
  15000. L2F9B:  LD      A,(HL)          ; pick up exponent
  15001.         LD      (HL),$00        ; make location zero
  15002.         AND     A               ; test if number is zero
  15003.         RET     Z               ; return if so
  15004.  
  15005.         INC     HL              ; address mantissa
  15006.         BIT     7,(HL)          ; test the sign bit
  15007.         SET     7,(HL)          ; set it to implied state
  15008.         DEC     HL              ; point to exponent
  15009.         RET     Z               ; return if positive number.
  15010.  
  15011.         PUSH    BC              ; preserve BC
  15012.         LD      BC,$0005        ; length of number
  15013.         ADD     HL,BC           ; point HL past end
  15014.         LD      B,C             ; set B to 5 counter
  15015.         LD      C,A             ; store exponent in C
  15016.         SCF                     ; set carry flag
  15017.  
  15018. ;; NEG-BYTE
  15019. L2FAF:  DEC     HL              ; work from LSB to MSB
  15020.         LD      A,(HL)          ; fetch byte
  15021.         CPL                     ; complement
  15022.         ADC     A,$00           ; add in initial carry or from prev operation
  15023.         LD      (HL),A          ; put back
  15024.         DJNZ    L2FAF           ; loop to NEG-BYTE till all 5 done
  15025.  
  15026.         LD      A,C             ; stored exponent to A
  15027.         POP     BC              ; restore original BC
  15028.         RET                     ; return
  15029.  
  15030. ; -----------------
  15031. ; Fetch two numbers
  15032. ; -----------------
  15033. ; This routine is called twice when printing floating point numbers and also
  15034. ; to fetch two numbers by the addition, multiply and division routines.
  15035. ; HL addresses the first number, DE addresses the second number.
  15036. ; For arithmetic only, A holds the sign of the result which is stored in
  15037. ; the second location.
  15038.  
  15039. ;; FETCH-TWO
  15040. L2FBA:  PUSH    HL              ; save pointer to first number, result if math.
  15041.         PUSH    AF              ; save result sign.
  15042.  
  15043.         LD      C,(HL)          ;
  15044.         INC     HL              ;
  15045.  
  15046.         LD      B,(HL)          ;
  15047.         LD      (HL),A          ; store the sign at correct location in
  15048.                                 ; destination 5 bytes for arithmetic only.
  15049.         INC     HL              ;
  15050.  
  15051.         LD      A,C             ;
  15052.         LD      C,(HL)          ;
  15053.         PUSH    BC              ;
  15054.         INC     HL              ;
  15055.         LD      C,(HL)          ;
  15056.         INC     HL              ;
  15057.         LD      B,(HL)          ;
  15058.         EX      DE,HL           ;
  15059.         LD      D,A             ;
  15060.         LD      E,(HL)          ;
  15061.         PUSH    DE              ;
  15062.         INC     HL              ;
  15063.         LD      D,(HL)          ;
  15064.         INC     HL              ;
  15065.         LD      E,(HL)          ;
  15066.         PUSH    DE              ;
  15067.         EXX                     ;
  15068.         POP     DE              ;
  15069.         POP     HL              ;
  15070.         POP     BC              ;
  15071.         EXX                     ;
  15072.         INC     HL              ;
  15073.         LD      D,(HL)          ;
  15074.         INC     HL              ;
  15075.         LD      E,(HL)          ;
  15076.  
  15077.         POP     AF              ; restore possible result sign.
  15078.         POP     HL              ; and pointer to possible result.
  15079.         RET                     ; return.
  15080.  
  15081. ; ---------------------------------
  15082. ; Shift floating point number right
  15083. ; ---------------------------------
  15084. ;
  15085. ;
  15086.  
  15087. ;; SHIFT-FP
  15088. L2FDD:  AND     A               ;
  15089.         RET     Z               ;
  15090.  
  15091.         CP      $21             ;
  15092.         JR      NC,L2FF9        ; to ADDEND-0
  15093.  
  15094.         PUSH    BC              ;
  15095.         LD      B,A             ;
  15096.  
  15097. ;; ONE-SHIFT
  15098. L2FE5:  EXX                     ;
  15099.         SRA     L               ;
  15100.         RR      D               ;
  15101.         RR      E               ;
  15102.         EXX                     ;
  15103.         RR      D               ;
  15104.         RR      E               ;
  15105.         DJNZ    L2FE5           ; to ONE-SHIFT
  15106.  
  15107.         POP     BC              ;
  15108.         RET     NC              ;
  15109.  
  15110.         CALL    L3004           ; routine ADD-BACK
  15111.         RET     NZ              ;
  15112.  
  15113. ;; ADDEND-0
  15114. L2FF9:  EXX                     ;
  15115.         XOR     A               ;
  15116.  
  15117. ;; ZEROS-4/5
  15118. L2FFB:  LD      L,$00           ;
  15119.         LD      D,A             ;
  15120.         LD      E,L             ;
  15121.         EXX                     ;
  15122.         LD      DE,$0000        ;
  15123.         RET                     ;
  15124.  
  15125. ; ------------------
  15126. ; Add back any carry
  15127. ; ------------------
  15128. ;
  15129. ;
  15130.  
  15131. ;; ADD-BACK
  15132. L3004:  INC     E               ;
  15133.         RET     NZ              ;
  15134.  
  15135.         INC      D              ;
  15136.         RET     NZ              ;
  15137.  
  15138.         EXX                     ;
  15139.         INC     E               ;
  15140.         JR      NZ,L300D        ; to ALL-ADDED
  15141.  
  15142.         INC     D               ;
  15143.  
  15144. ;; ALL-ADDED
  15145. L300D:  EXX                     ;
  15146.         RET                     ;
  15147.  
  15148. ; -----------------------
  15149. ; Handle subtraction (03)
  15150. ; -----------------------
  15151. ; Subtraction is done by switching the sign byte/bit of the second number
  15152. ; which may be integer of floating point and continuing into addition.
  15153.  
  15154. ;; subtract
  15155. L300F:  EX      DE,HL           ; address second number with HL
  15156.  
  15157.         CALL    L346E           ; routine NEGATE switches sign
  15158.  
  15159.         EX      DE,HL           ; address first number again
  15160.                                 ; and continue.
  15161.  
  15162. ; --------------------
  15163. ; Handle addition (0F)
  15164. ; --------------------
  15165. ; HL points to first number, DE to second.
  15166. ; If they are both integers, then go for the easy route.
  15167.  
  15168. ;; addition
  15169. L3014:  LD      A,(DE)          ; fetch first byte of second
  15170.         OR      (HL)            ; combine with first byte of first
  15171.         JR      NZ,L303E        ; forward to FULL-ADDN if at least one was
  15172.                                 ; in floating point form.
  15173.  
  15174. ; continue if both were small integers.
  15175.  
  15176.         PUSH    DE              ; save pointer to lowest number for result.
  15177.  
  15178.         INC     HL              ; address sign byte and
  15179.         PUSH    HL              ; push the pointer.
  15180.  
  15181.         INC     HL              ; address low byte
  15182.         LD      E,(HL)          ; to E
  15183.         INC     HL              ; address high byte
  15184.         LD      D,(HL)          ; to D
  15185.         INC     HL              ; address unused byte
  15186.  
  15187.         INC     HL              ; address known zero indicator of 1st number
  15188.         INC     HL              ; address sign byte
  15189.  
  15190.         LD      A,(HL)          ; sign to A, $00 or $FF
  15191.  
  15192.         INC     HL              ; address low byte
  15193.         LD      C,(HL)          ; to C
  15194.         INC     HL              ; address high byte
  15195.         LD      B,(HL)          ; to B
  15196.  
  15197.         POP     HL              ; pop result sign pointer
  15198.         EX      DE,HL           ; integer to HL
  15199.  
  15200.         ADD     HL,BC           ; add to the other one in BC
  15201.                                 ; setting carry if overflow.
  15202.  
  15203.         EX      DE,HL           ; save result in DE bringing back sign pointer
  15204.  
  15205.         ADC     A,(HL)          ; if pos/pos A=01 with overflow else 00
  15206.                                 ; if neg/neg A=FF with overflow else FE
  15207.                                 ; if mixture A=00 with overflow else FF
  15208.  
  15209.         RRCA                    ; bit 0 to (C)
  15210.  
  15211.         ADC     A,$00           ; both acceptable signs now zero
  15212.  
  15213.         JR      NZ,L303C        ; forward to ADDN-OFLW if not
  15214.  
  15215.         SBC     A,A             ; restore a negative result sign
  15216.  
  15217.         LD      (HL),A          ;
  15218.         INC     HL              ;
  15219.         LD      (HL),E          ;
  15220.         INC     HL              ;
  15221.         LD      (HL),D          ;
  15222.         DEC     HL              ;
  15223.         DEC     HL              ;
  15224.         DEC     HL              ;
  15225.  
  15226.         POP     DE              ; STKEND
  15227.         RET                     ;
  15228.  
  15229. ; ---
  15230.  
  15231. ;; ADDN-OFLW
  15232. L303C:  DEC     HL              ;
  15233.         POP     DE              ;
  15234.  
  15235. ;; FULL-ADDN
  15236. L303E:  CALL    L3293           ; routine RE-ST-TWO
  15237.         EXX                     ;
  15238.         PUSH    HL              ;
  15239.         EXX                     ;
  15240.         PUSH    DE              ;
  15241.         PUSH    HL              ;
  15242.         CALL    L2F9B           ; routine PREP-ADD
  15243.         LD      B,A             ;
  15244.         EX      DE,HL           ;
  15245.         CALL    L2F9B           ; routine PREP-ADD
  15246.         LD       C,A            ;
  15247.         CP      B               ;
  15248.         JR      NC,L3055        ; to SHIFT-LEN
  15249.  
  15250.         LD      A,B             ;
  15251.         LD      B,C             ;
  15252.         EX      DE,HL           ;
  15253.  
  15254. ;; SHIFT-LEN
  15255. L3055:  PUSH    AF              ;
  15256.         SUB     B               ;
  15257.         CALL    L2FBA           ; routine FETCH-TWO
  15258.         CALL    L2FDD           ; routine SHIFT-FP
  15259.         POP     AF              ;
  15260.         POP     HL              ;
  15261.         LD      (HL),A          ;
  15262.         PUSH    HL              ;
  15263.         LD      L,B             ;
  15264.         LD      H,C             ;
  15265.         ADD     HL,DE           ;
  15266.         EXX                     ;
  15267.         EX      DE,HL           ;
  15268.         ADC     HL,BC           ;
  15269.         EX      DE,HL           ;
  15270.         LD      A,H             ;
  15271.         ADC     A,L             ;
  15272.         LD      L,A             ;
  15273.         RRA                     ;
  15274.         XOR     L               ;
  15275.         EXX                     ;
  15276.         EX      DE,HL           ;
  15277.         POP     HL              ;
  15278.         RRA                     ;
  15279.         JR      NC,L307C        ; to TEST-NEG
  15280.  
  15281.         LD      A,$01           ;
  15282.         CALL    L2FDD           ; routine SHIFT-FP
  15283.         INC     (HL)            ;
  15284.         JR      Z,L309F         ; to ADD-REP-6
  15285.  
  15286. ;; TEST-NEG
  15287. L307C:  EXX                     ;
  15288.         LD      A,L             ;
  15289.         AND     $80             ;
  15290.         EXX                     ;
  15291.         INC     HL              ;
  15292.         LD      (HL),A          ;
  15293.         DEC     HL              ;
  15294.         JR      Z,L30A5         ; to GO-NC-MLT
  15295.  
  15296.         LD      A,E             ;
  15297.         NEG                     ; Negate
  15298.         CCF                     ; Complement Carry Flag
  15299.         LD      E,A             ;
  15300.         LD      A,D             ;
  15301.         CPL                     ;
  15302.         ADC     A,$00           ;
  15303.         LD      D,A             ;
  15304.         EXX                     ;
  15305.         LD      A,E             ;
  15306.         CPL                     ;
  15307.         ADC     A,$00           ;
  15308.         LD      E,A             ;
  15309.         LD      A,D             ;
  15310.         CPL                     ;
  15311.         ADC     A,$00           ;
  15312.         JR      NC,L30A3        ; to END-COMPL
  15313.  
  15314.         RRA                     ;
  15315.         EXX                     ;
  15316.         INC     (HL)            ;
  15317.  
  15318. ;; ADD-REP-6
  15319. L309F:  JP      Z,L31AD         ; to REPORT-6
  15320.  
  15321.         EXX                     ;
  15322.  
  15323. ;; END-COMPL
  15324. L30A3:  LD      D,A             ;
  15325.         EXX                     ;
  15326.  
  15327. ;; GO-NC-MLT
  15328. L30A5:  XOR     A               ;
  15329.         JP      L3155           ; to TEST-NORM
  15330.  
  15331. ; -----------------------------
  15332. ; Used in 16 bit multiplication
  15333. ; -----------------------------
  15334. ; This routine is used, in the first instance, by the multiply calculator
  15335. ; literal to perform an integer multiplication in preference to
  15336. ; 32-bit multiplication to which it will resort if this overflows.
  15337. ;
  15338. ; It is also used by STK-VAR to calculate array subscripts and by DIM to
  15339. ; calculate the space required for multi-dimensional arrays.
  15340.  
  15341. ;; HL-HL*DE
  15342. L30A9:  PUSH    BC              ; preserve BC throughout
  15343.         LD      B,$10           ; set B to 16
  15344.         LD      A,H             ; save H in A high byte
  15345.         LD      C,L             ; save L in C low byte
  15346.         LD      HL,$0000        ; initialize result to zero
  15347.  
  15348. ; now enter a loop.
  15349.  
  15350. ;; HL-LOOP
  15351. L30B1:  ADD     HL,HL           ; double result
  15352.         JR      C,L30BE         ; to HL-END if overflow
  15353.  
  15354.         RL      C               ; shift AC left into carry
  15355.         RLA                     ;
  15356.         JR      NC,L30BC        ; to HL-AGAIN to skip addition if no carry
  15357.  
  15358.         ADD     HL,DE           ; add in DE
  15359.         JR      C,L30BE         ; to HL-END if overflow
  15360.  
  15361. ;; HL-AGAIN
  15362. L30BC:  DJNZ    L30B1           ; back to HL-LOOP for all 16 bits
  15363.  
  15364. ;; HL-END
  15365. L30BE:  POP     BC              ; restore preserved BC
  15366.         RET                     ; return with carry reset if successful
  15367.                                 ; and result in HL.
  15368.  
  15369. ; -----------------------------
  15370. ; Prepare to multiply or divide
  15371. ; -----------------------------
  15372. ; This routine is called in succession from multiply and divide to prepare
  15373. ; two mantissas by setting the leftmost bit that is used for the sign.
  15374. ; On the first call A holds zero and picks up the sign bit. On the second
  15375. ; call the two bits are XORed to form the result sign - minus * minus giving
  15376. ; plus etc. If either number is zero then this is flagged.
  15377. ; HL addresses the exponent.
  15378.  
  15379. ;; PREP-M/D
  15380. L30C0:  CALL    L34E9           ; routine TEST-ZERO  preserves accumulator.
  15381.         RET     C               ; return carry set if zero
  15382.  
  15383.         INC     HL              ; address first byte of mantissa
  15384.         XOR     (HL)            ; pick up the first or xor with first.
  15385.         SET     7,(HL)          ; now set to give true 32-bit mantissa
  15386.         DEC     HL              ; point to exponent
  15387.         RET                     ; return with carry reset
  15388.  
  15389. ; --------------------------
  15390. ; Handle multiplication (04)
  15391. ; --------------------------
  15392. ;
  15393. ;
  15394.  
  15395. ;; multiply
  15396. L30CA:  LD      A,(DE)          ;
  15397.         OR      (HL)            ;
  15398.         JR      NZ,L30F0        ; to MULT-LONG
  15399.  
  15400.         PUSH    DE              ;
  15401.         PUSH    HL              ;
  15402.         PUSH    DE              ;
  15403.         CALL    L2D7F           ; routine INT-FETCH
  15404.         EX      DE,HL           ;
  15405.         EX      (SP),HL         ;
  15406.         LD      B,C             ;
  15407.         CALL    L2D7F           ; routine INT-FETCH
  15408.         LD      A,B             ;
  15409.         XOR     C               ;
  15410.         LD      C,A             ;
  15411.         POP     HL              ;
  15412.         CALL    L30A9           ; routine HL-HL*DE
  15413.         EX      DE,HL           ;
  15414.         POP     HL              ;
  15415.         JR      C,L30EF         ; to MULT-OFLW
  15416.  
  15417.         LD      A,D             ;
  15418.         OR      E               ;
  15419.         JR      NZ,L30EA        ; to MULT-RSLT
  15420.  
  15421.         LD      C,A             ;
  15422.  
  15423. ;; MULT-RSLT
  15424. L30EA:  CALL    L2D8E           ; routine INT-STORE
  15425.         POP      DE             ;
  15426.         RET                     ;
  15427.  
  15428. ; ---
  15429.  
  15430. ;; MULT-OFLW
  15431. L30EF:  POP     DE              ;
  15432.  
  15433. ;; MULT-LONG
  15434. L30F0:  CALL    L3293           ; routine RE-ST-TWO
  15435.         XOR     A               ;
  15436.         CALL    L30C0           ; routine PREP-M/D
  15437.         RET     C               ;
  15438.  
  15439.         EXX                     ;
  15440.         PUSH    HL              ;
  15441.         EXX                     ;
  15442.         PUSH    DE              ;
  15443.         EX      DE,HL           ;
  15444.         CALL    L30C0           ; routine PREP-M/D
  15445.         EX      DE,HL           ;
  15446.         JR      C,L315D         ; to ZERO-RSLT
  15447.  
  15448.         PUSH    HL              ;
  15449.         CALL    L2FBA           ; routine FETCH-TWO
  15450.         LD      A,B             ;
  15451.         AND     A               ;
  15452.         SBC     HL,HL           ;
  15453.         EXX                     ;
  15454.         PUSH    HL              ;
  15455.         SBC     HL,HL           ;
  15456.         EXX                     ;
  15457.         LD      B,$21           ;
  15458.         JR      L3125           ; to STRT-MLT
  15459.  
  15460. ; ---
  15461.  
  15462. ;; MLT-LOOP
  15463. L3114:  JR      NC,L311B        ; to NO-ADD
  15464.  
  15465.         ADD     HL,DE           ;
  15466.         EXX                     ;
  15467.         ADC     HL,DE           ;
  15468.         EXX                     ;
  15469.  
  15470. ;; NO-ADD
  15471. L311B:  EXX                     ;
  15472.         RR      H               ;
  15473.         RR      L               ;
  15474.         EXX                     ;
  15475.         RR      H               ;
  15476.         RR      L               ;
  15477.  
  15478. ;; STRT-MLT
  15479. L3125:  EXX                     ;
  15480.         RR      B               ;
  15481.         RR      C               ;
  15482.         EXX                     ;
  15483.         RR      C               ;
  15484.         RRA                     ;
  15485.         DJNZ    L3114           ; to MLT-LOOP
  15486.  
  15487.         EX      DE,HL           ;
  15488.         EXX                     ;
  15489.         EX      DE,HL           ;
  15490.         EXX                     ;
  15491.         POP     BC              ;
  15492.         POP     HL              ;
  15493.         LD      A,B             ;
  15494.         ADD     A,C             ;
  15495.         JR      NZ,L313B        ; to MAKE-EXPT
  15496.  
  15497.         AND     A               ;
  15498.  
  15499. ;; MAKE-EXPT
  15500. L313B:  DEC     A               ;
  15501.         CCF                     ; Complement Carry Flag
  15502.  
  15503. ;; DIVN-EXPT
  15504. L313D:  RLA                     ;
  15505.         CCF                     ; Complement Carry Flag
  15506.         RRA                     ;
  15507.         JP      P,L3146         ; to OFLW1-CLR
  15508.  
  15509.         JR      NC,L31AD        ; to REPORT-6
  15510.  
  15511.         AND     A               ;
  15512.  
  15513. ;; OFLW1-CLR
  15514. L3146:  INC     A               ;
  15515.         JR      NZ,L3151        ; to OFLW2-CLR
  15516.  
  15517.         JR      C,L3151         ; to OFLW2-CLR
  15518.  
  15519.         EXX                     ;
  15520.         BIT     7,D             ;
  15521.         EXX                     ;
  15522.         JR      NZ,L31AD        ; to REPORT-6
  15523.  
  15524. ;; OFLW2-CLR
  15525. L3151:  LD      (HL),A          ;
  15526.         EXX                     ;
  15527.         LD      A,B             ;
  15528.         EXX                     ;
  15529.  
  15530. ;; TEST-NORM
  15531. L3155:  JR      NC,L316C        ; to NORMALISE
  15532.  
  15533.         LD      A,(HL)          ;
  15534.         AND     A               ;
  15535.  
  15536. ;; NEAR-ZERO
  15537. L3159:  LD      A,$80           ;
  15538.         JR      Z,L315E         ; to SKIP-ZERO
  15539.  
  15540. ;; ZERO-RSLT
  15541. L315D:  XOR     A               ;
  15542.  
  15543. ;; SKIP-ZERO
  15544. L315E:  EXX                     ;
  15545.         AND     D               ;
  15546.         CALL    L2FFB           ; routine ZEROS-4/5
  15547.         RLCA                    ;
  15548.         LD      (HL),A          ;
  15549.         JR      C,L3195         ; to OFLOW-CLR
  15550.  
  15551.         INC     HL              ;
  15552.         LD      (HL),A          ;
  15553.         DEC     HL              ;
  15554.         JR      L3195           ; to OFLOW-CLR
  15555.  
  15556. ; ---
  15557.  
  15558. ;; NORMALISE
  15559. L316C:  LD      B,$20           ;
  15560.  
  15561. ;; SHIFT-ONE
  15562. L316E:  EXX                     ;
  15563.         BIT     7,D             ;
  15564.         EXX                     ;
  15565.         JR      NZ,L3186        ; to NORML-NOW
  15566.  
  15567.         RLCA                    ;
  15568.         RL      E               ;
  15569.         RL      D               ;
  15570.         EXX                     ;
  15571.         RL      E               ;
  15572.         RL      D               ;
  15573.         EXX                     ;
  15574.         DEC     (HL)            ;
  15575.         JR      Z,L3159         ; to NEAR-ZERO
  15576.  
  15577.         DJNZ    L316E           ; to SHIFT-ONE
  15578.  
  15579.         JR      L315D           ; to ZERO-RSLT
  15580.  
  15581. ; ---
  15582.  
  15583. ;; NORML-NOW
  15584. L3186:  RLA                     ;
  15585.         JR      NC,L3195        ; to OFLOW-CLR
  15586.  
  15587.         CALL    L3004           ; routine ADD-BACK
  15588.         JR      NZ,L3195        ; to OFLOW-CLR
  15589.  
  15590.         EXX                     ;
  15591.         LD       D,$80          ;
  15592.         EXX                     ;
  15593.         INC     (HL)            ;
  15594.         JR      Z,L31AD         ; to REPORT-6
  15595.  
  15596. ;; OFLOW-CLR
  15597. L3195:  PUSH    HL              ;
  15598.         INC     HL              ;
  15599.         EXX                     ;
  15600.         PUSH    DE              ;
  15601.         EXX                     ;
  15602.         POP     BC              ;
  15603.         LD      A,B             ;
  15604.         RLA                     ;
  15605.         RL      (HL)            ;
  15606.         RRA                     ;
  15607.         LD      (HL),A          ;
  15608.         INC     HL              ;
  15609.         LD      (HL),C          ;
  15610.         INC     HL              ;
  15611.         LD      (HL),D          ;
  15612.         INC     HL              ;
  15613.         LD      (HL),E          ;
  15614.         POP     HL              ;
  15615.         POP     DE              ;
  15616.         EXX                     ;
  15617.         POP     HL              ;
  15618.         EXX                     ;
  15619.         RET                     ;
  15620.  
  15621. ; ---
  15622.  
  15623. ;; REPORT-6
  15624. L31AD:  RST     08H             ; ERROR-1
  15625.         DB    $05             ; Error Report: Number too big
  15626.  
  15627. ; --------------------
  15628. ; Handle division (05)
  15629. ; --------------------
  15630. ;
  15631. ;
  15632.  
  15633. ;; division
  15634. L31AF:  CALL    L3293           ; routine RE-ST-TWO
  15635.         EX      DE,HL           ;
  15636.         XOR     A               ;
  15637.         CALL    L30C0           ; routine PREP-M/D
  15638.         JR      C,L31AD         ; to REPORT-6
  15639.  
  15640.         EX      DE,HL           ;
  15641.         CALL    L30C0           ; routine PREP-M/D
  15642.         RET     C               ;
  15643.  
  15644.         EXX                     ;
  15645.         PUSH    HL              ;
  15646.         EXX                     ;
  15647.         PUSH    DE              ;
  15648.         PUSH    HL              ;
  15649.         CALL    L2FBA           ; routine FETCH-TWO
  15650.         EXX                     ;
  15651.         PUSH    HL              ;
  15652.         LD      H,B             ;
  15653.         LD      L,C             ;
  15654.         EXX                     ;
  15655.         LD      H,C             ;
  15656.         LD      L,B             ;
  15657.         XOR     A               ;
  15658.         LD      B,$DF           ;
  15659.         JR      L31E2           ; to DIV-START
  15660.  
  15661. ; ---
  15662.  
  15663. ;; DIV-LOOP
  15664. L31D2:  RLA                     ;
  15665.         RL      C               ;
  15666.         EXX                     ;
  15667.         RL      C               ;
  15668.         RL      B               ;
  15669.         EXX                     ;
  15670.  
  15671. ;; div-34th
  15672. L31DB:  ADD     HL,HL           ;
  15673.         EXX                     ;
  15674.         ADC     HL,HL           ;
  15675.         EXX                     ;
  15676.         JR      C,L31F2         ; to SUBN-ONLY
  15677.  
  15678. ;; DIV-START
  15679. L31E2:  SBC     HL,DE           ;
  15680.         EXX                     ;
  15681.         SBC     HL,DE           ;
  15682.         EXX                     ;
  15683.         JR      NC,L31F9        ; to NO-RSTORE
  15684.  
  15685.         ADD     HL,DE           ;
  15686.         EXX                     ;
  15687.         ADC     HL,DE           ;
  15688.         EXX                     ;
  15689.         AND     A               ;
  15690.         JR      L31FA           ; to COUNT-ONE
  15691.  
  15692. ; ---
  15693.  
  15694. ;; SUBN-ONLY
  15695. L31F2:  AND     A               ;
  15696.         SBC     HL,DE           ;
  15697.         EXX                     ;
  15698.         SBC     HL,DE           ;
  15699.         EXX                     ;
  15700.  
  15701. ;; NO-RSTORE
  15702. L31F9:  SCF                     ; Set Carry Flag
  15703.  
  15704. ;; COUNT-ONE
  15705. L31FA:  INC     B               ;
  15706.         JP      M,L31D2         ; to DIV-LOOP
  15707.  
  15708.         PUSH    AF              ;
  15709.         JR      Z,L31E2         ; to DIV-START
  15710.  
  15711. ;
  15712. ;
  15713. ;
  15714. ;
  15715.  
  15716.         LD      E,A             ;
  15717.         LD      D,C             ;
  15718.         EXX                     ;
  15719.         LD      E,C             ;
  15720.         LD      D,B             ;
  15721.         POP     AF              ;
  15722.         RR      B               ;
  15723.         POP     AF              ;
  15724.         RR      B               ;
  15725.         EXX                     ;
  15726.         POP     BC              ;
  15727.         POP     HL              ;
  15728.         LD      A,B             ;
  15729.         SUB     C               ;
  15730.         JP      L313D           ; jump back to DIVN-EXPT
  15731.  
  15732. ; ------------------------------------
  15733. ; Integer truncation towards zero ($3A)
  15734. ; ------------------------------------
  15735. ;
  15736. ;
  15737.  
  15738. ;; truncate
  15739. L3214:  LD      A,(HL)          ;
  15740.         AND     A               ;
  15741.         RET     Z               ;
  15742.  
  15743.         CP      $81             ;
  15744.         JR      NC,L3221        ; to T-GR-ZERO
  15745.  
  15746.         LD      (HL),$00        ;
  15747.         LD      A,$20           ;
  15748.         JR      L3272           ; to NIL-BYTES
  15749.  
  15750. ; ---
  15751.  
  15752. ;; T-GR-ZERO
  15753. L3221:  CP      $91             ;
  15754.         JR      NZ,L323F        ; to T-SMALL
  15755.  
  15756.         INC     HL              ;
  15757.         INC     HL              ;
  15758.         INC     HL              ;
  15759.         LD      A,$80           ;
  15760.         AND     (HL)            ;
  15761.         DEC      HL             ;
  15762.         OR      (HL)            ;
  15763.         DEC     HL              ;
  15764.         JR      NZ,L3233        ; to T-FIRST
  15765.  
  15766.         LD      A,$80           ;
  15767.         XOR     (HL)            ;
  15768.  
  15769. ;; T-FIRST
  15770. L3233:  DEC     HL              ;
  15771.         JR      NZ,L326C        ; to T-EXPNENT
  15772.  
  15773.         LD      (HL),A          ;
  15774.         INC     HL              ;
  15775.         LD      (HL),$FF        ;
  15776.         DEC     HL              ;
  15777.         LD      A,$18           ;
  15778.         JR      L3272           ; to NIL-BYTES
  15779.  
  15780. ; ---
  15781.  
  15782. ;; T-SMALL
  15783. L323F:  JR      NC,L326D        ; to X-LARGE
  15784.  
  15785.         PUSH    DE              ;
  15786.         CPL                     ;
  15787.         ADD     A,$91           ;
  15788.         INC     HL              ;
  15789.         LD      D,(HL)          ;
  15790.         INC     HL              ;
  15791.         LD      E,(HL)          ;
  15792.         DEC     HL              ;
  15793.         DEC     HL              ;
  15794.         LD      C,$00           ;
  15795.         BIT     7,D             ;
  15796.         JR      Z,L3252         ; to T-NUMERIC
  15797.  
  15798.         DEC     C               ;
  15799.  
  15800. ;; T-NUMERIC
  15801. L3252:  SET     7,D             ;
  15802.         LD      B,$08           ;
  15803.         SUB     B               ;
  15804.         ADD     A,B             ;
  15805.         JR      C,L325E         ; to T-TEST
  15806.  
  15807.         LD      E,D             ;
  15808.         LD      D,$00           ;
  15809.         SUB     B               ;
  15810.  
  15811. ;; T-TEST
  15812. L325E:  JR      Z,L3267         ; to T-STORE
  15813.  
  15814.         LD      B,A             ;
  15815.  
  15816. ;; T-SHIFT
  15817. L3261:  SRL     D               ;
  15818.         RR      E               ;
  15819.         DJNZ    L3261           ; to T-SHIFT
  15820.  
  15821. ;; T-STORE
  15822. L3267:  CALL    L2D8E           ; routine INT-STORE
  15823.         POP     DE              ;
  15824.         RET                     ;
  15825.  
  15826. ; ---
  15827.  
  15828. ;; T-EXPNENT
  15829. L326C:  LD      A,(HL)          ;
  15830.  
  15831. ;; X-LARGE
  15832. L326D:  SUB     $A0             ;
  15833.         RET     P               ;
  15834.  
  15835.         NEG                     ; Negate
  15836.  
  15837. ;; NIL-BYTES
  15838. L3272:  PUSH    DE              ;
  15839.         EX      DE,HL           ;
  15840.         DEC     HL              ;
  15841.         LD      B,A             ;
  15842.         SRL     B               ;
  15843.         SRL     B               ;
  15844.         SRL     B               ;
  15845.         JR      Z,L3283         ; to BITS-ZERO
  15846.  
  15847. ;; BYTE-ZERO
  15848. L327E:  LD      (HL),$00        ;
  15849.         DEC     HL              ;
  15850.         DJNZ    L327E           ; to BYTE-ZERO
  15851.  
  15852. ;; BITS-ZERO
  15853. L3283:  AND     $07             ;
  15854.         JR      Z,L3290         ; to IX-END
  15855.  
  15856.         LD      B,A             ;
  15857.         LD      A,$FF           ;
  15858.  
  15859. ;; LESS-MASK
  15860. L328A:  SLA     A               ;
  15861.         DJNZ    L328A           ; to LESS-MASK
  15862.  
  15863.         AND     (HL)            ;
  15864.         LD      (HL),A          ;
  15865.  
  15866. ;; IX-END
  15867. L3290:  EX      DE,HL           ;
  15868.         POP     DE              ;
  15869.         RET                     ;
  15870.  
  15871. ; ----------------------------------
  15872. ; Storage of numbers in 5 byte form.
  15873. ; ==================================
  15874. ; Both integers and floating-point numbers can be stored in five bytes.
  15875. ; Zero is a special case stored as 5 zeros.
  15876. ; For integers the form is
  15877. ; Byte 1 - zero,
  15878. ; Byte 2 - sign byte, $00 +ve, $FF -ve.
  15879. ; Byte 3 - Low byte of integer.
  15880. ; Byte 4 - High byte
  15881. ; Byte 5 - unused but always zero.
  15882. ;
  15883. ; it seems unusual to store the low byte first but it is just as easy either
  15884. ; way. Statistically it just increases the chances of trailing zeros which
  15885. ; is an advantage elsewhere in saving ROM code.
  15886. ;
  15887. ;             zero     sign     low      high    unused
  15888. ; So +1 is  00000000 00000000 00000001 00000000 00000000
  15889. ;
  15890. ; and -1 is 00000000 11111111 11111111 11111111 00000000
  15891. ;
  15892. ; much of the arithmetic found in BASIC lines can be done using numbers
  15893. ; in this form using the Z80's 16 bit register operation ADD.
  15894. ; (multiplication is done by a sequence of additions).
  15895. ;
  15896. ; Storing -ve integers in two's complement form, means that they are ready for
  15897. ; addition and you might like to add the numbers above to prove that the
  15898. ; answer is zero. If, as in this case, the carry is set then that denotes that
  15899. ; the result is positive. This only applies when the signs don't match.
  15900. ; With positive numbers a carry denotes the result is out of integer range.
  15901. ; With negative numbers a carry denotes the result is within range.
  15902. ; The exception to the last rule is when the result is -65536
  15903. ;
  15904. ; Floating point form is an alternative method of storing numbers which can
  15905. ; be used for integers and larger (or fractional) numbers.
  15906. ;
  15907. ; In this form 1 is stored as
  15908. ;           10000001 00000000 00000000 00000000 00000000
  15909. ;
  15910. ; When a small integer is converted to a floating point number the last two
  15911. ; bytes are always blank so they are omitted in the following steps
  15912. ;
  15913. ; first make exponent +1 +16d  (bit 7 of the exponent is set if positive)
  15914.  
  15915. ; 10010001 00000000 00000001
  15916. ; 10010000 00000000 00000010 <-  now shift left and decrement exponent
  15917. ; ...
  15918. ; 10000010 01000000 00000000 <-  until a 1 abuts the imaginary point
  15919. ; 10000001 10000000 00000000     to the left of the mantissa.
  15920. ;
  15921. ; however since the leftmost bit of the mantissa is always set then it can
  15922. ; be used to denote the sign of the mantissa and put back when needed by the
  15923. ; PREP routines which gives
  15924. ;
  15925. ; 10000001 00000000 00000000
  15926.  
  15927. ; -----------------------------
  15928. ; Re-stack two `small' integers
  15929. ; -----------------------------
  15930. ; This routine is called to re-stack two numbers in full floating point form
  15931. ; e.g. from mult when integer multiplication has overflowed.
  15932.  
  15933. ;; RE-ST-TWO
  15934. L3293:  CALL    L3296           ; routine RESTK-SUB  below and continue
  15935.                                 ; into the routine to do the other one.
  15936.  
  15937. ;; RESTK-SUB
  15938. L3296:  EX      DE,HL           ; swap pointers
  15939.  
  15940. ; --------------------------------
  15941. ; Re-stack one number in full form
  15942. ; --------------------------------
  15943. ; This routine re-stacks an integer usually on the calculator stack
  15944. ; in full floating point form.
  15945. ; HL points to first byte.
  15946.  
  15947. ;; re-stack
  15948. L3297:  LD      A,(HL)          ; Fetch Exponent byte to A
  15949.         AND     A               ; test it
  15950.         RET     NZ              ; return if not zero as already in full
  15951.                                 ; floating-point form.
  15952.  
  15953.         PUSH    DE              ; preserve DE.
  15954.         CALL    L2D7F           ; routine INT-FETCH
  15955.                                 ; integer to DE, sign to C.
  15956.  
  15957. ; HL points to 4th byte.
  15958.  
  15959.         XOR     A               ; clear accumulator.
  15960.         INC     HL              ; point to 5th.
  15961.         LD      (HL),A          ; and blank.
  15962.         DEC     HL              ; point to 4th.
  15963.         LD      (HL),A          ; and blank.
  15964.  
  15965.         LD      B,$91           ; set exponent byte +ve $81
  15966.                                 ; and imaginary dec point 16 bits to right
  15967.                                 ; of first bit.
  15968.  
  15969. ; we could skip to normalize now but it's quicker to avoid
  15970. ; normalizing through an empty D.
  15971.  
  15972.         LD      A,D             ; fetch the high byte D
  15973.         AND     A               ; is it zero ?
  15974.         JR      NZ,L32B1        ; skip to RS-NRMLSE if not.
  15975.  
  15976.         OR      E               ; low byte E to A and test for zero
  15977.         LD      B,D             ; set B exponent to 0
  15978.         JR      Z,L32BD         ; forward to RS-STORE if value is zero.
  15979.  
  15980.         LD      D,E             ; transfer E to D
  15981.         LD      E,B             ; set E to 0
  15982.         LD      B,$89           ; reduce the initial exponent by eight.
  15983.  
  15984.  
  15985. ;; RS-NRMLSE
  15986. L32B1:  EX      DE,HL           ; integer to HL, addr of 4th byte to DE.
  15987.  
  15988. ;; RSTK-LOOP
  15989. L32B2:  DEC     B               ; decrease exponent
  15990.         ADD     HL,HL           ; shift DE left
  15991.         JR      NC,L32B2        ; loop back to RSTK-LOOP
  15992.                                 ; until a set bit pops into carry
  15993.  
  15994.         RRC     C               ; now rotate the sign byte $00 or $FF
  15995.                                 ; into carry to give a sign bit
  15996.  
  15997.         RR      H               ; rotate the sign bit to left of H
  15998.         RR      L               ; rotate any carry into L
  15999.  
  16000.         EX      DE,HL           ; address 4th byte, normalized int to DE
  16001.  
  16002. ;; RS-STORE
  16003. L32BD:  DEC     HL              ; address 3rd byte
  16004.         LD      (HL),E          ; place E
  16005.         DEC     HL              ; address 2nd byte
  16006.         LD      (HL),D          ; place D
  16007.         DEC     HL              ; address 1st byte
  16008.         LD      (HL),B          ; store the exponent
  16009.  
  16010.         POP     DE              ; restore initial DE.
  16011.         RET                     ; return.
  16012.  
  16013. ;****************************************
  16014. ;** Part 10. FLOATING-POINT CALCULATOR **
  16015. ;****************************************
  16016.  
  16017. ; As a general rule the calculator avoids using the IY register.
  16018. ; exceptions are val, val$ and str$.
  16019. ; So an assembly language programmer who has disabled interrupts to use
  16020. ; IY for other purposes can still use the calculator for mathematical
  16021. ; purposes.
  16022.  
  16023.  
  16024. ; ------------------
  16025. ; Table of constants
  16026. ; ------------------
  16027. ;
  16028. ;
  16029.  
  16030. ; used 11 times
  16031. ;; stk-zero                                                 00 00 00 00 00
  16032. L32C5:  DB    $00             ;;Bytes: 1
  16033.         DB    $B0             ;;Exponent $00
  16034.         DB    $00             ;;(+00,+00,+00)
  16035.  
  16036. ; used 19 times
  16037. ;; stk-one                                                  00 00 01 00 00
  16038. L32C8:  DB    $40             ;;Bytes: 2
  16039.         DB    $B0             ;;Exponent $00
  16040.         DB    $00,$01         ;;(+00,+00)
  16041.  
  16042. ; used 9 times
  16043. ;; stk-half                                                 80 00 00 00 00
  16044. L32CC:  DB    $30             ;;Exponent: $80, Bytes: 1
  16045.         DB    $00             ;;(+00,+00,+00)
  16046.  
  16047. ; used 4 times.
  16048. ;; stk-pi/2                                                 81 49 0F DA A2
  16049. L32CE:  DB    $F1             ;;Exponent: $81, Bytes: 4
  16050.         DB    $49,$0F,$DA,$A2 ;;
  16051.  
  16052. ; used 3 times.
  16053. ;; stk-ten                                                  00 00 0A 00 00
  16054. L32D3:  DB    $40             ;;Bytes: 2
  16055.         DB    $B0             ;;Exponent $00
  16056.         DB    $00,$0A         ;;(+00,+00)
  16057.  
  16058.  
  16059. ; ------------------
  16060. ; Table of addresses
  16061. ; ------------------
  16062. ;
  16063. ; starts with binary operations which have two operands and one result.
  16064. ; three pseudo binary operations first.
  16065.  
  16066. ;; tbl-addrs
  16067. L32D7:  DEFW    L368F           ; $00 Address: $368F - jump-true
  16068.         DEFW    L343C           ; $01 Address: $343C - exchange
  16069.         DEFW    L33A1           ; $02 Address: $33A1 - delete
  16070.  
  16071. ; true binary operations.
  16072.  
  16073.         DEFW    L300F           ; $03 Address: $300F - subtract
  16074.         DEFW    L30CA           ; $04 Address: $30CA - multiply
  16075.         DEFW    L31AF           ; $05 Address: $31AF - division
  16076.         DEFW    L3851           ; $06 Address: $3851 - to-power
  16077.         DEFW    L351B           ; $07 Address: $351B - or
  16078.  
  16079.         DEFW    L3524           ; $08 Address: $3524 - no-&-no
  16080.         DEFW    L353B           ; $09 Address: $353B - no-l-eql
  16081.         DEFW    L353B           ; $0A Address: $353B - no-gr-eql
  16082.         DEFW    L353B           ; $0B Address: $353B - nos-neql
  16083.         DEFW    L353B           ; $0C Address: $353B - no-grtr
  16084.         DEFW    L353B           ; $0D Address: $353B - no-less
  16085.         DEFW    L353B           ; $0E Address: $353B - nos-eql
  16086.         DEFW    L3014           ; $0F Address: $3014 - addition
  16087.  
  16088.         DEFW    L352D           ; $10 Address: $352D - str-&-no
  16089.         DEFW    L353B           ; $11 Address: $353B - str-l-eql
  16090.         DEFW    L353B           ; $12 Address: $353B - str-gr-eql
  16091.         DEFW    L353B           ; $13 Address: $353B - strs-neql
  16092.         DEFW    L353B           ; $14 Address: $353B - str-grtr
  16093.         DEFW    L353B           ; $15 Address: $353B - str-less
  16094.         DEFW    L353B           ; $16 Address: $353B - strs-eql
  16095.         DEFW    L359C           ; $17 Address: $359C - strs-add
  16096.  
  16097. ; unary follow
  16098.  
  16099.         DEFW    L35DE           ; $18 Address: $35DE - val$
  16100.         DEFW    L34BC           ; $19 Address: $34BC - usr-$
  16101.         DEFW    L3645           ; $1A Address: $3645 - read-in
  16102.         DEFW    L346E           ; $1B Address: $346E - negate
  16103.  
  16104.         DEFW    L3669           ; $1C Address: $3669 - code
  16105.         DEFW    L35DE           ; $1D Address: $35DE - val
  16106.         DEFW    L3674           ; $1E Address: $3674 - len
  16107.         DEFW    L37B5           ; $1F Address: $37B5 - sin
  16108.         DEFW    L37AA           ; $20 Address: $37AA - cos
  16109.         DEFW    L37DA           ; $21 Address: $37DA - tan
  16110.         DEFW    L3833           ; $22 Address: $3833 - asn
  16111.         DEFW    L3843           ; $23 Address: $3843 - acs
  16112.         DEFW    L37E2           ; $24 Address: $37E2 - atn
  16113.         DEFW    L3713           ; $25 Address: $3713 - ln
  16114.         DEFW    L36C4           ; $26 Address: $36C4 - exp
  16115.         DEFW    L36AF           ; $27 Address: $36AF - int
  16116.         DEFW    L384A           ; $28 Address: $384A - sqr
  16117.         DEFW    L3492           ; $29 Address: $3492 - sgn
  16118.         DEFW    L346A           ; $2A Address: $346A - abs
  16119.         DEFW    L34AC           ; $2B Address: $34AC - peek
  16120.         DEFW    L34A5           ; $2C Address: $34A5 - in
  16121.         DEFW    L34B3           ; $2D Address: $34B3 - usr-no
  16122.         DEFW    L361F           ; $2E Address: $361F - str$
  16123.         DEFW    L35C9           ; $2F Address: $35C9 - chrs
  16124.         DEFW    L3501           ; $30 Address: $3501 - not
  16125.  
  16126. ; end of true unary
  16127.  
  16128.         DEFW    L33C0           ; $31 Address: $33C0 - duplicate
  16129.         DEFW    L36A0           ; $32 Address: $36A0 - n-mod-m
  16130.         DEFW    L3686           ; $33 Address: $3686 - jump
  16131.         DEFW    L33C6           ; $34 Address: $33C6 - stk-data
  16132.         DEFW    L367A           ; $35 Address: $367A - dec-jr-nz
  16133.         DEFW    L3506           ; $36 Address: $3506 - less-0
  16134.         DEFW    L34F9           ; $37 Address: $34F9 - greater-0
  16135.         DEFW    L369B           ; $38 Address: $369B - end-calc
  16136.         DEFW    L3783           ; $39 Address: $3783 - get-argt
  16137.         DEFW    L3214           ; $3A Address: $3214 - truncate
  16138.         DEFW    L33A2           ; $3B Address: $33A2 - fp-calc-2
  16139.         DEFW    L2D4F           ; $3C Address: $2D4F - e-to-fp
  16140.         DEFW    L3297           ; $3D Address: $3297 - re-stack
  16141.  
  16142. ; the following are just the next available slots for the 128 compound literals
  16143. ; which are in range $80 - $FF.
  16144.  
  16145.         DEFW    L3449           ; $3E Address: $3449 - series-xx    $80 - $9F.
  16146.         DEFW    L341B           ; $3F Address: $341B - stk-const-xx $A0 - $BF.
  16147.         DEFW    L342D           ; $40 Address: $342D - st-mem-xx    $C0 - $DF.
  16148.         DEFW    L340F           ; $41 Address: $340F - get-mem-xx   $E0 - $FF.
  16149.  
  16150. ; Aside: 3E - 7F are therefore unused calculator literals.
  16151. ;        3E - 7B would be available for expansion.
  16152.  
  16153. ; --------------
  16154. ; The Calculator
  16155. ; --------------
  16156. ;
  16157. ;
  16158.  
  16159. ;; CALCULATE
  16160. L335B:  CALL    L35BF           ; routine STK-PNTRS is called to set up the
  16161.                                 ; calculator stack pointers for a default
  16162.                                 ; unary operation. HL = last value on stack.
  16163.                                 ; DE = STKEND first location after stack.
  16164.  
  16165. ; the calculate routine is called at this point by the series generator...
  16166.  
  16167. ;; GEN-ENT-1
  16168. L335E:  LD      A,B             ; fetch the Z80 B register to A
  16169.         LD      ($5C67),A       ; and store value in system variable BREG.
  16170.                                 ; this will be the counter for dec-jr-nz
  16171.                                 ; or if used from fp-calc2 the calculator
  16172.                                 ; instruction.
  16173.  
  16174. ; ... and again later at this point
  16175.  
  16176. ;; GEN-ENT-2
  16177. L3362:  EXX                     ; switch sets
  16178.         EX      (SP),HL         ; and store the address of next instruction,
  16179.                                 ; the return address, in H'L'.
  16180.                                 ; If this is a recursive call the the H'L'
  16181.                                 ; of the previous invocation goes on stack.
  16182.                                 ; c.f. end-calc.
  16183.         EXX                     ; switch back to main set
  16184.  
  16185. ; this is the re-entry looping point when handling a string of literals.
  16186.  
  16187. ;; RE-ENTRY
  16188. L3365:  LD      ($5C65),DE      ; save end of stack in system variable STKEND
  16189.         EXX                     ; switch to alt
  16190.         LD      A,(HL)          ; get next literal
  16191.         INC     HL              ; increase pointer'
  16192.  
  16193. ; single operation jumps back to here
  16194.  
  16195. ;; SCAN-ENT
  16196. L336C:  PUSH    HL              ; save pointer on stack
  16197.         AND     A               ; now test the literal
  16198.         JP      P,L3380         ; forward to FIRST-3D if in range $00 - $3D
  16199.                                 ; anything with bit 7 set will be one of
  16200.                                 ; 128 compound literals.
  16201.  
  16202. ; compound literals have the following format.
  16203. ; bit 7 set indicates compound.
  16204. ; bits 6-5 the subgroup 0-3.
  16205. ; bits 4-0 the embedded parameter $00 - $1F.
  16206. ; The subgroup 0-3 needs to be manipulated to form the next available four
  16207. ; address places after the simple literals in the address table.
  16208.  
  16209.         LD      D,A             ; save literal in D
  16210.         AND     $60             ; and with 01100000 to isolate subgroup
  16211.         RRCA                    ; rotate bits
  16212.         RRCA                    ; 4 places to right
  16213.         RRCA                    ; not five as we need offset * 2
  16214.         RRCA                    ; 00000xx0
  16215.         ADD     A,$7C           ; add ($3E * 2) to give correct offset.
  16216.                                 ; alter above if you add more literals.
  16217.         LD      L,A             ; store in L for later indexing.
  16218.         LD      A,D             ; bring back compound literal
  16219.         AND     $1F             ; use mask to isolate parameter bits
  16220.         JR      L338E           ; forward to ENT-TABLE
  16221.  
  16222. ; ---
  16223.  
  16224. ; the branch was here with simple literals.
  16225.  
  16226. ;; FIRST-3D
  16227. L3380:  CP      $18             ; compare with first unary operations.
  16228.         JR      NC,L338C        ; to DOUBLE-A with unary operations
  16229.  
  16230. ; it is binary so adjust pointers.
  16231.  
  16232.         EXX                     ;
  16233.         LD      BC,$FFFB        ; the value -5
  16234.         LD      D,H             ; transfer HL, the last value, to DE.
  16235.         LD      E,L             ;
  16236.         ADD     HL,BC           ; subtract 5 making HL point to second
  16237.                                 ; value.
  16238.         EXX                     ;
  16239.  
  16240. ;; DOUBLE-A
  16241. L338C:  RLCA                    ; double the literal
  16242.         LD      L,A             ; and store in L for indexing
  16243.  
  16244. ;; ENT-TABLE
  16245. L338E:  LD      DE,L32D7        ; Address: tbl-addrs
  16246.         LD      H,$00           ; prepare to index
  16247.         ADD     HL,DE           ; add to get address of routine
  16248.         LD      E,(HL)          ; low byte to E
  16249.         INC     HL              ;
  16250.         LD      D,(HL)          ; high byte to D
  16251.         LD      HL,L3365        ; Address: RE-ENTRY
  16252.         EX      (SP),HL         ; goes to stack
  16253.         PUSH    DE              ; now address of routine
  16254.         EXX                     ; main set
  16255.                                 ; avoid using IY register.
  16256.         LD      BC,($5C66)      ; STKEND_hi
  16257.                                 ; nothing much goes to C but BREG to B
  16258.                                 ; and continue into next ret instruction
  16259.                                 ; which has a dual identity
  16260.  
  16261.  
  16262. ; ------------------
  16263. ; Handle delete (02)
  16264. ; ------------------
  16265. ; A simple return but when used as a calculator literal this
  16266. ; deletes the last value from the calculator stack.
  16267. ; On entry, as always with binary operations,
  16268. ; HL=first number, DE=second number
  16269. ; On exit, HL=result, DE=stkend.
  16270. ; So nothing to do
  16271.  
  16272. ;; delete
  16273. L33A1:  RET                     ; return - indirect jump if from above.
  16274.  
  16275. ; ---------------------
  16276. ; Single operation (3B)
  16277. ; ---------------------
  16278. ; this single operation is used, in the first instance, to evaluate most
  16279. ; of the mathematical and string functions found in BASIC expressions.
  16280.  
  16281. ;; fp-calc-2
  16282. L33A2:  POP     AF              ; drop return address.
  16283.         LD      A,($5C67)       ; load accumulator from system variable BREG
  16284.                                 ; value will be literal eg. 'tan'
  16285.         EXX                     ; switch to alt
  16286.         JR      L336C           ; back to SCAN-ENT
  16287.                                 ; next literal will be end-calc at L2758
  16288.  
  16289. ; ----------------
  16290. ; Test five-spaces
  16291. ; ----------------
  16292. ; This routine is called from MOVE-FP, STK-CONST and STK-STORE to
  16293. ; test that there is enough space between the calculator stack and the
  16294. ; machine stack for another five-byte value. It returns with BC holding
  16295. ; the value 5 ready for any subsequent LDIR.
  16296.  
  16297. ;; TEST-5-SP
  16298. L33A9:  PUSH    DE              ; save
  16299.         PUSH    HL              ; registers
  16300.         LD      BC,$0005        ; an overhead of five bytes
  16301.         CALL    L1F05           ; routine TEST-ROOM tests free RAM raising
  16302.                                 ; an error if not.
  16303.         POP     HL              ; else restore
  16304.         POP     DE              ; registers.
  16305.         RET                     ; return with BC set at 5.
  16306.  
  16307. ; ------------
  16308. ; Stack number
  16309. ; ------------
  16310. ; This routine is called to stack a hidden floating point number found in
  16311. ; a BASIC line. It is also called to stack a numeric variable value, and
  16312. ; from BEEP, to stack an entry in the semi-tone table. It is not part of the
  16313. ; calculator suite of routines.
  16314. ; On entry HL points to the number to be stacked.
  16315.  
  16316. ;; STACK-NUM
  16317. L33B4:  LD      DE,($5C65)      ; load destination from STKEND system variable.
  16318.         CALL    L33C0           ; routine MOVE-FP puts on calculator stack
  16319.                                 ; with a memory check.
  16320.         LD      ($5C65),DE      ; set STKEND to next free location.
  16321.         RET                     ; return.
  16322.  
  16323. ; ---------------------------------
  16324. ; Move a floating point number (31)
  16325. ; ---------------------------------
  16326. ; This simple routine is a 5-byte LDIR instruction
  16327. ; that incorporates a memory check.
  16328. ; When used as a calculator literal it duplicates the last value on the
  16329. ; calculator stack.
  16330. ; Unary so on entry HL points to last value, DE to stkend
  16331.  
  16332. ;; duplicate
  16333. ;; MOVE-FP
  16334. L33C0:  CALL    L33A9           ; routine TEST-5-SP test free memory
  16335.                                 ; and sets BC to 5.
  16336.         LDIR                    ; copy the five bytes.
  16337.         RET                     ; return with DE addressing new STKEND
  16338.                                 ; and HL addressing new last value.
  16339.  
  16340. ; -------------------
  16341. ; Stack literals ($34)
  16342. ; -------------------
  16343. ; When a calculator subroutine needs to put a value on the calculator
  16344. ; stack that is not a regular constant this routine is called with a
  16345. ; variable number of following data bytes that convey to the routine
  16346. ; the integer or floating point form as succinctly as is possible.
  16347.  
  16348. ;; stk-data
  16349. L33C6:  LD      H,D             ; transfer STKEND
  16350.         LD      L,E             ; to HL for result.
  16351.  
  16352. ;; STK-CONST
  16353. L33C8:  CALL    L33A9           ; routine TEST-5-SP tests that room exists
  16354.                                 ; and sets BC to $05.
  16355.  
  16356.         EXX                     ; switch to alternate set
  16357.         PUSH    HL              ; save the pointer to next literal on stack
  16358.         EXX                     ; switch back to main set
  16359.  
  16360.         EX      (SP),HL         ; pointer to HL, destination to stack.
  16361.  
  16362.         PUSH    BC              ; save BC - value 5 from test room ??.
  16363.  
  16364.         LD      A,(HL)          ; fetch the byte following 'stk-data'
  16365.         AND     $C0             ; isolate bits 7 and 6
  16366.         RLCA                    ; rotate
  16367.         RLCA                    ; to bits 1 and 0  range $00 - $03.
  16368.         LD      C,A             ; transfer to C
  16369.         INC     C               ; and increment to give number of bytes
  16370.                                 ; to read. $01 - $04
  16371.         LD      A,(HL)          ; reload the first byte
  16372.         AND     $3F             ; mask off to give possible exponent.
  16373.         JR      NZ,L33DE        ; forward to FORM-EXP if it was possible to
  16374.                                 ; include the exponent.
  16375.  
  16376. ; else byte is just a byte count and exponent comes next.
  16377.  
  16378.         INC     HL              ; address next byte and
  16379.         LD      A,(HL)          ; pick up the exponent ( - $50).
  16380.  
  16381. ;; FORM-EXP
  16382. L33DE:  ADD     A,$50           ; now add $50 to form actual exponent
  16383.         LD      (DE),A          ; and load into first destination byte.
  16384.         LD      A,$05           ; load accumulator with $05 and
  16385.         SUB     C               ; subtract C to give count of trailing
  16386.                                 ; zeros plus one.
  16387.         INC     HL              ; increment source
  16388.         INC     DE              ; increment destination
  16389.         LD      B,$00           ; prepare to copy
  16390.         LDIR                    ; copy C bytes
  16391.  
  16392.         POP     BC              ; restore 5 counter to BC ??.
  16393.  
  16394.         EX      (SP),HL         ; put HL on stack as next literal pointer
  16395.                                 ; and the stack value - result pointer -
  16396.                                 ; to HL.
  16397.  
  16398.         EXX                     ; switch to alternate set.
  16399.         POP     HL              ; restore next literal pointer from stack
  16400.                                 ; to H'L'.
  16401.         EXX                     ; switch back to main set.
  16402.  
  16403.         LD      B,A             ; zero count to B
  16404.         XOR     A               ; clear accumulator
  16405.  
  16406. ;; STK-ZEROS
  16407. L33F1:  DEC     B               ; decrement B counter
  16408.         RET     Z               ; return if zero.          >>
  16409.                                 ; DE points to new STKEND
  16410.                                 ; HL to new number.
  16411.  
  16412.         LD      (DE),A          ; else load zero to destination
  16413.         INC     DE              ; increase destination
  16414.         JR      L33F1           ; loop back to STK-ZEROS until done.
  16415.  
  16416. ; -------------------------------
  16417. ; THE 'SKIP CONSTANTS' SUBROUTINE
  16418. ; -------------------------------
  16419. ; This routine traverses variable-length entries in the table of constants,
  16420. ; stacking intermediate, unwanted constants onto a dummy calculator stack,
  16421. ; in the first five bytes of ROM. The destination DE normally points to the
  16422. ; end of the calculator stack which might be in the normal place or in the
  16423. ; system variables area during E-LINE-NO; INT-TO-FP; stk-ten. In any case,
  16424. ; it would be simpler all round if the routine just shoved unwanted values
  16425. ; where it is going to stick the wanted value.
  16426. ; The instruction LD DE, $0000 can be removed.
  16427.  
  16428. ;; SKIP-CONS
  16429. L33F7:  AND     A               ; test if initially zero.
  16430.  
  16431. ;; SKIP-NEXT
  16432. L33F8:  RET     Z               ; return if zero.          >>
  16433.  
  16434.         PUSH    AF              ; save count.
  16435.         PUSH    DE              ; and normal STKEND
  16436.  
  16437.         LD      DE,$0000        ; dummy value for STKEND at start of ROM
  16438.                                 ; Note. not a fault but this has to be
  16439.                                 ; moved elsewhere when running in RAM.
  16440.                                 ; e.g. with Expandor Systems 'Soft ROM'.
  16441.                                 ; Better still, write to the normal place.
  16442.         CALL    L33C8           ; routine STK-CONST works through variable
  16443.                                 ; length records.
  16444.  
  16445.         POP     DE              ; restore real STKEND
  16446.         POP     AF              ; restore count
  16447.         DEC     A               ; decrease
  16448.         JR      L33F8           ; loop back to SKIP-NEXT
  16449.  
  16450. ; ---------------
  16451. ; Memory location
  16452. ; ---------------
  16453. ; This routine, when supplied with a base address in HL and an index in A
  16454. ; will calculate the address of the A'th entry, where each entry occupies
  16455. ; five bytes. It is used for reading the semi-tone table and addressing
  16456. ; floating-point numbers in the calculator's memory area.
  16457.  
  16458. ;; LOC-MEM
  16459. L3406:  LD      C,A             ; store the original number $00-$1F.
  16460.         RLCA                    ; double.
  16461.         RLCA                    ; quadruple.
  16462.         ADD     A,C             ; now add original to multiply by five.
  16463.  
  16464.         LD      C,A             ; place the result in C.
  16465.         LD      B,$00           ; set B to 0.
  16466.         ADD     HL,BC           ; add to form address of start of number in HL.
  16467.         RET                     ; return.
  16468.  
  16469. ; ------------------------------
  16470. ; Get from memory area ($E0 etc.)
  16471. ; ------------------------------
  16472. ; Literals $E0 to $FF
  16473. ; A holds $00-$1F offset.
  16474. ; The calculator stack increases by 5 bytes.
  16475.  
  16476. ;; get-mem-xx
  16477. L340F:  PUSH    DE              ; save STKEND
  16478.         LD      HL,($5C68)      ; MEM is base address of the memory cells.
  16479.         CALL    L3406           ; routine LOC-MEM so that HL = first byte
  16480.         CALL    L33C0           ; routine MOVE-FP moves 5 bytes with memory
  16481.                                 ; check.
  16482.                                 ; DE now points to new STKEND.
  16483.         POP     HL              ; original STKEND is now RESULT pointer.
  16484.         RET                     ; return.
  16485.  
  16486. ; --------------------------
  16487. ; Stack a constant (A0 etc.)
  16488. ; --------------------------
  16489. ; This routine allows a one-byte instruction to stack up to 32 constants
  16490. ; held in short form in a table of constants. In fact only 5 constants are
  16491. ; required. On entry the A register holds the literal ANDed with 1F.
  16492. ; It isn't very efficient and it would have been better to hold the
  16493. ; numbers in full, five byte form and stack them in a similar manner
  16494. ; to that used for semi-tone table values.
  16495.  
  16496. ;; stk-const-xx
  16497. L341B:  LD      H,D             ; save STKEND - required for result
  16498.         LD      L,E             ;
  16499.         EXX                     ; swap
  16500.         PUSH    HL              ; save pointer to next literal
  16501.         LD      HL,L32C5        ; Address: stk-zero - start of table of
  16502.                                 ; constants
  16503.         EXX                     ;
  16504.         CALL    L33F7           ; routine SKIP-CONS
  16505.         CALL    L33C8           ; routine STK-CONST
  16506.         EXX                     ;
  16507.         POP     HL              ; restore pointer to next literal.
  16508.         EXX                     ;
  16509.         RET                     ; return.
  16510.  
  16511. ; --------------------------------
  16512. ; Store in a memory area ($C0 etc.)
  16513. ; --------------------------------
  16514. ; Offsets $C0 to $DF
  16515. ; Although 32 memory storage locations can be addressed, only six
  16516. ; $C0 to $C5 are required by the ROM and only the thirty bytes (6*5)
  16517. ; required for these are allocated. Spectrum programmers who wish to
  16518. ; use the floating point routines from assembly language may wish to
  16519. ; alter the system variable MEM to point to 160 bytes of RAM to have
  16520. ; use the full range available.
  16521. ; A holds the derived offset $00-$1F.
  16522. ; This is a unary operation, so on entry HL points to the last value and DE
  16523. ; points to STKEND.
  16524.  
  16525. ;; st-mem-xx
  16526. L342D:  PUSH    HL              ; save the result pointer.
  16527.         EX      DE,HL           ; transfer to DE.
  16528.         LD      HL,($5C68)      ; fetch MEM the base of memory area.
  16529.         CALL    L3406           ; routine LOC-MEM sets HL to the destination.
  16530.         EX      DE,HL           ; swap - HL is start, DE is destination.
  16531.         CALL    L33C0           ; routine MOVE-FP.
  16532.                                 ; note. a short ld bc,5; ldir
  16533.                                 ; the embedded memory check is not required
  16534.                                 ; so these instructions would be faster.
  16535.         EX      DE,HL           ; DE = STKEND
  16536.         POP     HL              ; restore original result pointer
  16537.         RET                     ; return.
  16538.  
  16539. ; ------------------------------------
  16540. ; Swap first number with second number
  16541. ; ------------------------------------
  16542. ; This routine exchanges the last two values on the calculator stack
  16543. ; On entry, as always with binary operations,
  16544. ; HL=first number, DE=second number
  16545. ; On exit, HL=result, DE=stkend.
  16546.  
  16547. ;; exchange
  16548. L343C:  LD      B,$05           ; there are five bytes to be swapped
  16549.  
  16550. ; start of loop.
  16551.  
  16552. ;; SWAP-BYTE
  16553. L343E:  LD      A,(DE)          ; each byte of second
  16554.         LD      C,(HL)          ; each byte of first
  16555.         EX      DE,HL           ; swap pointers
  16556.         LD      (DE),A          ; store each byte of first
  16557.         LD      (HL),C          ; store each byte of second
  16558.         INC     HL              ; advance both
  16559.         INC     DE              ; pointers.
  16560.         DJNZ    L343E           ; loop back to SWAP-BYTE until all 5 done.
  16561.  
  16562.         EX      DE,HL           ; even up the exchanges
  16563.                                 ; so that DE addresses STKEND.
  16564.         RET                     ; return.
  16565.  
  16566. ; --------------------------
  16567. ; Series generator (86 etc.)
  16568. ; --------------------------
  16569. ; The Spectrum uses Chebyshev polynomials to generate approximations for
  16570. ; SIN, ATN, LN and EXP. These are named after the Russian mathematician
  16571. ; Pafnuty Chebyshev, born in 1821, who did much pioneering work on numerical
  16572. ; series. As far as calculators are concerned, Chebyshev polynomials have an
  16573. ; advantage over other series, for example the Taylor series, as they can
  16574. ; reach an approximation in just six iterations for SIN, eight for EXP and
  16575. ; twelve for LN and ATN. The mechanics of the routine are interesting but
  16576. ; for full treatment of how these are generated with demonstrations in
  16577. ; Sinclair BASIC see "The Complete Spectrum ROM Disassembly" by Dr Ian Logan
  16578. ; and Dr Frank O'Hara, published 1983 by Melbourne House.
  16579.  
  16580. ;; series-xx
  16581. L3449:  LD      B,A             ; parameter $00 - $1F to B counter
  16582.         CALL    L335E           ; routine GEN-ENT-1 is called.
  16583.                                 ; A recursive call to a special entry point
  16584.                                 ; in the calculator that puts the B register
  16585.                                 ; in the system variable BREG. The return
  16586.                                 ; address is the next location and where
  16587.                                 ; the calculator will expect its first
  16588.                                 ; instruction - now pointed to by HL'.
  16589.                                 ; The previous pointer to the series of
  16590.                                 ; five-byte numbers goes on the machine stack.
  16591.  
  16592. ; The initialization phase.
  16593.  
  16594.         DB    $31             ;;duplicate       x,x
  16595.         DB    $0F             ;;addition        x+x
  16596.         DB    $C0             ;;st-mem-0        x+x
  16597.         DB    $02             ;;delete          .
  16598.         DB    $A0             ;;stk-zero        0
  16599.         DB    $C2             ;;st-mem-2        0
  16600.  
  16601. ; a loop is now entered to perform the algebraic calculation for each of
  16602. ; the numbers in the series
  16603.  
  16604. ;; G-LOOP
  16605. L3453:  DB    $31             ;;duplicate       v,v.
  16606.         DB    $E0             ;;get-mem-0       v,v,x+2
  16607.         DB    $04             ;;multiply        v,v*x+2
  16608.         DB    $E2             ;;get-mem-2       v,v*x+2,v
  16609.         DB    $C1             ;;st-mem-1
  16610.         DB    $03             ;;subtract
  16611.         DB    $38             ;;end-calc
  16612.  
  16613. ; the previous pointer is fetched from the machine stack to H'L' where it
  16614. ; addresses one of the numbers of the series following the series literal.
  16615.  
  16616.         CALL    L33C6           ; routine STK-DATA is called directly to
  16617.                                 ; push a value and advance H'L'.
  16618.         CALL    L3362           ; routine GEN-ENT-2 recursively re-enters
  16619.                                 ; the calculator without disturbing
  16620.                                 ; system variable BREG
  16621.                                 ; H'L' value goes on the machine stack and is
  16622.                                 ; then loaded as usual with the next address.
  16623.  
  16624.         DB    $0F             ;;addition
  16625.         DB    $01             ;;exchange
  16626.         DB    $C2             ;;st-mem-2
  16627.         DB    $02             ;;delete
  16628.  
  16629.         DB    $35             ;;dec-jr-nz
  16630.         DB    $EE             ;;back to L3453, G-LOOP
  16631.  
  16632. ; when the counted loop is complete the final subtraction yields the result
  16633. ; for example SIN X.
  16634.  
  16635.         DB    $E1             ;;get-mem-1
  16636.         DB    $03             ;;subtract
  16637.         DB    $38             ;;end-calc
  16638.  
  16639.         RET                     ; return with H'L' pointing to location
  16640.                                 ; after last number in series.
  16641.  
  16642. ; -----------------------
  16643. ; Absolute magnitude (2A)
  16644. ; -----------------------
  16645. ; This calculator literal finds the absolute value of the last value,
  16646. ; integer or floating point, on calculator stack.
  16647.  
  16648. ;; abs
  16649. L346A:  LD      B,$FF           ; signal abs
  16650.         JR      L3474           ; forward to NEG-TEST
  16651.  
  16652. ; -----------------------
  16653. ; Handle unary minus (1B)
  16654. ; -----------------------
  16655. ; Unary so on entry HL points to last value, DE to STKEND.
  16656.  
  16657. ;; NEGATE
  16658. ;; negate
  16659. L346E:  CALL    L34E9           ; call routine TEST-ZERO and
  16660.         RET     C               ; return if so leaving zero unchanged.
  16661.  
  16662.         LD      B,$00           ; signal negate required before joining
  16663.                                 ; common code.
  16664.  
  16665. ;; NEG-TEST
  16666. L3474:  LD      A,(HL)          ; load first byte and
  16667.         AND     A               ; test for zero
  16668.         JR      Z,L3483         ; forward to INT-CASE if a small integer
  16669.  
  16670. ; for floating point numbers a single bit denotes the sign.
  16671.  
  16672.         INC     HL              ; address the first byte of mantissa.
  16673.         LD      A,B             ; action flag $FF=abs, $00=neg.
  16674.         AND     $80             ; now         $80      $00
  16675.         OR      (HL)            ; sets bit 7 for abs
  16676.         RLA                     ; sets carry for abs and if number negative
  16677.         CCF                     ; complement carry flag
  16678.         RRA                     ; and rotate back in altering sign
  16679.         LD      (HL),A          ; put the altered adjusted number back
  16680.         DEC     HL              ; HL points to result
  16681.         RET                     ; return with DE unchanged
  16682.  
  16683. ; ---
  16684.  
  16685. ; for integer numbers an entire byte denotes the sign.
  16686.  
  16687. ;; INT-CASE
  16688. L3483:  PUSH    DE              ; save STKEND.
  16689.  
  16690.         PUSH    HL              ; save pointer to the last value/result.
  16691.  
  16692.         CALL    L2D7F           ; routine INT-FETCH puts integer in DE
  16693.                                 ; and the sign in C.
  16694.  
  16695.         POP     HL              ; restore the result pointer.
  16696.  
  16697.         LD      A,B             ; $FF=abs, $00=neg
  16698.         OR      C               ; $FF for abs, no change neg
  16699.         CPL                     ; $00 for abs, switched for neg
  16700.         LD      C,A             ; transfer result to sign byte.
  16701.  
  16702.         CALL    L2D8E           ; routine INT-STORE to re-write the integer.
  16703.  
  16704.         POP     DE              ; restore STKEND.
  16705.         RET                     ; return.
  16706.  
  16707. ; -----------
  16708. ; Signum (29)
  16709. ; -----------
  16710. ; This routine replaces the last value on the calculator stack,
  16711. ; which may be in floating point or integer form, with the integer values
  16712. ; zero if zero, with one if positive and  with -minus one if negative.
  16713.  
  16714. ;; sgn
  16715. L3492:  CALL    L34E9           ; call routine TEST-ZERO and
  16716.         RET     C               ; exit if so as no change is required.
  16717.  
  16718.         PUSH    DE              ; save pointer to STKEND.
  16719.  
  16720.         LD      DE,$0001        ; the result will be 1.
  16721.         INC     HL              ; skip over the exponent.
  16722.         RL      (HL)            ; rotate the sign bit into the carry flag.
  16723.         DEC     HL              ; step back to point to the result.
  16724.         SBC     A,A             ; byte will be $FF if negative, $00 if positive.
  16725.         LD      C,A             ; store the sign byte in the C register.
  16726.         CALL    L2D8E           ; routine INT-STORE to overwrite the last
  16727.                                 ; value with 0001 and sign.
  16728.  
  16729.         POP     DE              ; restore STKEND.
  16730.         RET                     ; return.
  16731.  
  16732. ; -----------------------
  16733. ; Handle IN function (2C)
  16734. ; -----------------------
  16735. ; This function reads a byte from an input port.
  16736.  
  16737. ;; in
  16738. L34A5:  CALL    L1E99           ; routine FIND-INT2 puts port address in BC.
  16739.                                 ; all 16 bits are put on the address line.
  16740.         IN      A,(C)           ; read the port.
  16741.  
  16742.         JR      L34B0           ; exit to STACK-A (via IN-PK-STK to save a byte
  16743.                                 ; of instruction code).
  16744.  
  16745. ; -------------------------
  16746. ; Handle PEEK function (2B)
  16747. ; -------------------------
  16748. ; This function returns the contents of a memory address.
  16749. ; The entire address space can be peeked including the ROM.
  16750.  
  16751. ;; peek
  16752. L34AC:  CALL    L1E99           ; routine FIND-INT2 puts address in BC.
  16753.         LD      A,(BC)          ; load contents into A register.
  16754.  
  16755. ;; IN-PK-STK
  16756. L34B0:  JP      L2D28           ; exit via STACK-A to put value on the
  16757.                                 ; calculator stack.
  16758.  
  16759. ; ---------------
  16760. ; USR number (2D)
  16761. ; ---------------
  16762. ; The USR function followed by a number 0-65535 is the method by which
  16763. ; the Spectrum invokes machine code programs. This function returns the
  16764. ; contents of the BC register pair.
  16765. ; Note. that STACK-BC re-initializes the IY register if a user-written
  16766. ; program has altered it.
  16767.  
  16768. ;; usr-no
  16769. L34B3:  CALL    L1E99           ; routine FIND-INT2 to fetch the
  16770.                                 ; supplied address into BC.
  16771.  
  16772.         LD      HL,L2D2B        ; address: STACK-BC is
  16773.         PUSH    HL              ; pushed onto the machine stack.
  16774.         PUSH    BC              ; then the address of the machine code
  16775.                                 ; routine.
  16776.  
  16777.         RET                     ; make an indirect jump to the routine
  16778.                                 ; and, hopefully, to STACK-BC also.
  16779.  
  16780. ; ---------------
  16781. ; USR string (19)
  16782. ; ---------------
  16783. ; The user function with a one-character string argument, calculates the
  16784. ; address of the User Defined Graphic character that is in the string.
  16785. ; As an alternative, the ASCII equivalent, upper or lower case,
  16786. ; may be supplied. This provides a user-friendly method of redefining
  16787. ; the 21 User Definable Graphics e.g.
  16788. ; POKE USR "a", BIN 10000000 will put a dot in the top left corner of the
  16789. ; character 144.
  16790. ; Note. the curious double check on the range. With 26 UDGs the first check
  16791. ; only is necessary. With anything less the second check only is required.
  16792. ; It is highly likely that the first check was written by Steven Vickers.
  16793.  
  16794. ;; usr-$
  16795. L34BC:  CALL    L2BF1           ; routine STK-FETCH fetches the string
  16796.                                 ; parameters.
  16797.         DEC     BC              ; decrease BC by
  16798.         LD      A,B             ; one to test
  16799.         OR      C               ; the length.
  16800.         JR      NZ,L34E7        ; to REPORT-A if not a single character.
  16801.  
  16802.         LD      A,(DE)          ; fetch the character
  16803.         CALL    L2C8D           ; routine ALPHA sets carry if 'A-Z' or 'a-z'.
  16804.         JR      C,L34D3         ; forward to USR-RANGE if ASCII.
  16805.  
  16806.         SUB     $90             ; make udgs range 0-20d
  16807.         JR      C,L34E7         ; to REPORT-A if too low. e.g. usr " ".
  16808.  
  16809.         CP      $15             ; Note. this test is not necessary.
  16810.         JR      NC,L34E7        ; to REPORT-A if higher than 20.
  16811.  
  16812.         INC     A               ; make range 1-21d to match LSBs of ASCII
  16813.  
  16814. ;; USR-RANGE
  16815. L34D3:  DEC     A               ; make range of bits 0-4 start at zero
  16816.         ADD     A,A             ; multiply by eight
  16817.         ADD     A,A             ; and lose any set bits
  16818.         ADD     A,A             ; range now 0 - 25*8
  16819.         CP      $A8             ; compare to 21*8
  16820.         JR      NC,L34E7        ; to REPORT-A if originally higher
  16821.                                 ; than 'U','u' or graphics U.
  16822.  
  16823.         LD      BC,($5C7B)      ; fetch the UDG system variable value.
  16824.         ADD     A,C             ; add the offset to character
  16825.         LD      C,A             ; and store back in register C.
  16826.         JR      NC,L34E4        ; forward to USR-STACK if no overflow.
  16827.  
  16828.         INC     B               ; increment high byte.
  16829.  
  16830. ;; USR-STACK
  16831. L34E4:  JP      L2D2B           ; jump back and exit via STACK-BC to store
  16832.  
  16833. ; ---
  16834.  
  16835. ;; REPORT-A
  16836. L34E7:  RST     08H             ; ERROR-1
  16837.         DB    $09             ; Error Report: Invalid argument
  16838.  
  16839. ; -------------
  16840. ; Test for zero
  16841. ; -------------
  16842. ; Test if top value on calculator stack is zero.
  16843. ; The carry flag is set if the last value is zero but no registers are altered.
  16844. ; All five bytes will be zero but first four only need be tested.
  16845. ; On entry HL points to the exponent the first byte of the value.
  16846.  
  16847. ;; TEST-ZERO
  16848. L34E9:  PUSH    HL              ; preserve HL which is used to address.
  16849.         PUSH    BC              ; preserve BC which is used as a store.
  16850.         LD      B,A             ; preserve A in B.
  16851.  
  16852.         LD      A,(HL)          ; load first byte to accumulator
  16853.         INC     HL              ; advance.
  16854.         OR      (HL)            ; OR with second byte and clear carry.
  16855.         INC     HL              ; advance.
  16856.         OR      (HL)            ; OR with third byte.
  16857.         INC     HL              ; advance.
  16858.         OR      (HL)            ; OR with fourth byte.
  16859.  
  16860.         LD      A,B             ; restore A without affecting flags.
  16861.         POP     BC              ; restore the saved
  16862.         POP     HL              ; registers.
  16863.  
  16864.         RET     NZ              ; return if not zero and with carry reset.
  16865.  
  16866.         SCF                     ; set the carry flag.
  16867.         RET                     ; return with carry set if zero.
  16868.  
  16869. ; -----------------------
  16870. ; Greater than zero ($37)
  16871. ; -----------------------
  16872. ; Test if the last value on the calculator stack is greater than zero.
  16873. ; This routine is also called directly from the end-tests of the comparison
  16874. ; routine.
  16875.  
  16876. ;; GREATER-0
  16877. ;; greater-0
  16878. L34F9:  CALL    L34E9           ; routine TEST-ZERO
  16879.         RET     C               ; return if was zero as this
  16880.                                 ; is also the Boolean 'false' value.
  16881.  
  16882.         LD      A,$FF           ; prepare XOR mask for sign bit
  16883.         JR      L3507           ; forward to SIGN-TO-C
  16884.                                 ; to put sign in carry
  16885.                                 ; (carry will become set if sign is positive)
  16886.                                 ; and then overwrite location with 1 or 0
  16887.                                 ; as appropriate.
  16888.  
  16889. ; ------------------------
  16890. ; Handle NOT operator ($30)
  16891. ; ------------------------
  16892. ; This overwrites the last value with 1 if it was zero else with zero
  16893. ; if it was any other value.
  16894. ;
  16895. ; e.g NOT 0 returns 1, NOT 1 returns 0, NOT -3 returns 0.
  16896. ;
  16897. ; The subroutine is also called directly from the end-tests of the comparison
  16898. ; operator.
  16899.  
  16900. ;; NOT
  16901. ;; not
  16902. L3501:  CALL    L34E9           ; routine TEST-ZERO sets carry if zero
  16903.  
  16904.         JR      L350B           ; to FP-0/1 to overwrite operand with
  16905.                                 ; 1 if carry is set else to overwrite with zero.
  16906.  
  16907. ; -------------------
  16908. ; Less than zero (36)
  16909. ; -------------------
  16910. ; Destructively test if last value on calculator stack is less than zero.
  16911. ; Bit 7 of second byte will be set if so.
  16912.  
  16913. ;; less-0
  16914. L3506:  XOR     A               ; set xor mask to zero
  16915.                                 ; (carry will become set if sign is negative).
  16916.  
  16917. ; transfer sign of mantissa to Carry Flag.
  16918.  
  16919. ;; SIGN-TO-C
  16920. L3507:  INC     HL              ; address 2nd byte.
  16921.         XOR     (HL)            ; bit 7 of HL will be set if number is negative.
  16922.         DEC     HL              ; address 1st byte again.
  16923.         RLCA                    ; rotate bit 7 of A to carry.
  16924.  
  16925. ; -----------
  16926. ; Zero or one
  16927. ; -----------
  16928. ; This routine places an integer value of zero or one at the addressed location
  16929. ; of the calculator stack or MEM area.  The value one is written if carry is
  16930. ; set on entry else zero.
  16931.  
  16932. ;; FP-0/1
  16933. L350B:  PUSH    HL              ; save pointer to the first byte
  16934.         LD      A,$00           ; load accumulator with zero - without
  16935.                                 ; disturbing flags.
  16936.         LD      (HL),A          ; zero to first byte
  16937.         INC     HL              ; address next
  16938.         LD      (HL),A          ; zero to 2nd byte
  16939.         INC     HL              ; address low byte of integer
  16940.         RLA                     ; carry to bit 0 of A
  16941.         LD      (HL),A          ; load one or zero to low byte.
  16942.         RRA                     ; restore zero to accumulator.
  16943.         INC     HL              ; address high byte of integer.
  16944.         LD      (HL),A          ; put a zero there.
  16945.         INC     HL              ; address fifth byte.
  16946.         LD      (HL),A          ; put a zero there.
  16947.         POP     HL              ; restore pointer to the first byte.
  16948.         RET                     ; return.
  16949.  
  16950. ; -----------------------
  16951. ; Handle OR operator (07)
  16952. ; -----------------------
  16953. ; The Boolean OR operator. eg. X OR Y
  16954. ; The result is zero if both values are zero else a non-zero value.
  16955. ;
  16956. ; e.g.    0 OR 0  returns 0.
  16957. ;        -3 OR 0  returns -3.
  16958. ;         0 OR -3 returns 1.
  16959. ;        -3 OR 2  returns 1.
  16960. ;
  16961. ; A binary operation.
  16962. ; On entry HL points to first operand (X) and DE to second operand (Y).
  16963.  
  16964. ;; or
  16965. L351B:  EX      DE,HL           ; make HL point to second number
  16966.         CALL    L34E9           ; routine TEST-ZERO
  16967.         EX      DE,HL           ; restore pointers
  16968.         RET     C               ; return if result was zero - first operand,
  16969.                                 ; now the last value, is the result.
  16970.  
  16971.         SCF                     ; set carry flag
  16972.         JR      L350B           ; back to FP-0/1 to overwrite the first operand
  16973.                                 ; with the value 1.
  16974.  
  16975.  
  16976. ; -----------------------------
  16977. ; Handle number AND number (08)
  16978. ; -----------------------------
  16979. ; The Boolean AND operator.
  16980. ;
  16981. ; e.g.    -3 AND 2  returns -3.
  16982. ;         -3 AND 0  returns 0.
  16983. ;          0 and -2 returns 0.
  16984. ;          0 and 0  returns 0.
  16985. ;
  16986. ; Compare with OR routine above.
  16987.  
  16988. ;; no-&-no
  16989. L3524:  EX      DE,HL           ; make HL address second operand.
  16990.  
  16991.         CALL    L34E9           ; routine TEST-ZERO sets carry if zero.
  16992.  
  16993.         EX      DE,HL           ; restore pointers.
  16994.         RET     NC              ; return if second non-zero, first is result.
  16995.  
  16996. ;
  16997.  
  16998.         AND     A               ; else clear carry.
  16999.         JR      L350B           ; back to FP-0/1 to overwrite first operand
  17000.                                 ; with zero for return value.
  17001.  
  17002. ; -----------------------------
  17003. ; Handle string AND number (10)
  17004. ; -----------------------------
  17005. ; e.g. "You Win" AND score>99 will return the string if condition is true
  17006. ; or the null string if false.
  17007.  
  17008. ;; str-&-no
  17009. L352D:  EX      DE,HL           ; make HL point to the number.
  17010.         CALL    L34E9           ; routine TEST-ZERO.
  17011.         EX      DE,HL           ; restore pointers.
  17012.         RET     NC              ; return if number was not zero - the string
  17013.                                 ; is the result.
  17014.  
  17015. ; if the number was zero (false) then the null string must be returned by
  17016. ; altering the length of the string on the calculator stack to zero.
  17017.  
  17018.         PUSH    DE              ; save pointer to the now obsolete number
  17019.                                 ; (which will become the new STKEND)
  17020.  
  17021.         DEC     DE              ; point to the 5th byte of string descriptor.
  17022.         XOR     A               ; clear the accumulator.
  17023.         LD      (DE),A          ; place zero in high byte of length.
  17024.         DEC     DE              ; address low byte of length.
  17025.         LD      (DE),A          ; place zero there - now the null string.
  17026.  
  17027.         POP     DE              ; restore pointer - new STKEND.
  17028.         RET                     ; return.
  17029.  
  17030. ; -----------------------------------
  17031. ; Perform comparison ($09-$0E, $11-$16)
  17032. ; -----------------------------------
  17033. ; True binary operations.
  17034. ;
  17035. ; A single entry point is used to evaluate six numeric and six string
  17036. ; comparisons. On entry, the calculator literal is in the B register and
  17037. ; the two numeric values, or the two string parameters, are on the
  17038. ; calculator stack.
  17039. ; The individual bits of the literal are manipulated to group similar
  17040. ; operations although the SUB 8 instruction does nothing useful and merely
  17041. ; alters the string test bit.
  17042. ; Numbers are compared by subtracting one from the other, strings are
  17043. ; compared by comparing every character until a mismatch, or the end of one
  17044. ; or both, is reached.
  17045. ;
  17046. ; Numeric Comparisons.
  17047. ; --------------------
  17048. ; The 'x>y' example is the easiest as it employs straight-thru logic.
  17049. ; Number y is subtracted from x and the result tested for greater-0 yielding
  17050. ; a final value 1 (true) or 0 (false).
  17051. ; For 'x<y' the same logic is used but the two values are first swapped on the
  17052. ; calculator stack.
  17053. ; For 'x=y' NOT is applied to the subtraction result yielding true if the
  17054. ; difference was zero and false with anything else.
  17055. ; The first three numeric comparisons are just the opposite of the last three
  17056. ; so the same processing steps are used and then a final NOT is applied.
  17057. ;
  17058. ; literal    Test   No  sub 8       ExOrNot  1st RRCA  exch sub  ?   End-Tests
  17059. ; =========  ====   == ======== === ======== ========  ==== ===  =  === === ===
  17060. ; no-l-eql   x<=y   09 00000001 dec 00000000 00000000  ---- x-y  ?  --- >0? NOT
  17061. ; no-gr-eql  x>=y   0A 00000010 dec 00000001 10000000c swap y-x  ?  --- >0? NOT
  17062. ; nos-neql   x<>y   0B 00000011 dec 00000010 00000001  ---- x-y  ?  NOT --- NOT
  17063. ; no-grtr    x>y    0C 00000100  -  00000100 00000010  ---- x-y  ?  --- >0? ---
  17064. ; no-less    x<y    0D 00000101  -  00000101 10000010c swap y-x  ?  --- >0? ---
  17065. ; nos-eql    x=y    0E 00000110  -  00000110 00000011  ---- x-y  ?  NOT --- ---
  17066. ;
  17067. ;                                                           comp -> C/F
  17068. ;                                                           ====    ===
  17069. ; str-l-eql  x$<=y$ 11 00001001 dec 00001000 00000100  ---- x$y$ 0  !or >0? NOT
  17070. ; str-gr-eql x$>=y$ 12 00001010 dec 00001001 10000100c swap y$x$ 0  !or >0? NOT
  17071. ; strs-neql  x$<>y$ 13 00001011 dec 00001010 00000101  ---- x$y$ 0  !or >0? NOT
  17072. ; str-grtr   x$>y$  14 00001100  -  00001100 00000110  ---- x$y$ 0  !or >0? ---
  17073. ; str-less   x$<y$  15 00001101  -  00001101 10000110c swap y$x$ 0  !or >0? ---
  17074. ; strs-eql   x$=y$  16 00001110  -  00001110 00000111  ---- x$y$ 0  !or >0? ---
  17075. ;
  17076. ; String comparisons are a little different in that the eql/neql carry flag
  17077. ; from the 2nd RRCA is, as before, fed into the first of the end tests but
  17078. ; along the way it gets modified by the comparison process. The result on the
  17079. ; stack always starts off as zero and the carry fed in determines if NOT is
  17080. ; applied to it. So the only time the greater-0 test is applied is if the
  17081. ; stack holds zero which is not very efficient as the test will always yield
  17082. ; zero. The most likely explanation is that there were once separate end tests
  17083. ; for numbers and strings.
  17084.  
  17085. ;; no-l-eql, etc.
  17086. L353B:  LD      A,B             ; transfer literal to accumulator.
  17087.         SUB     $08             ; subtract eight - which is not useful.
  17088.  
  17089.         BIT     2,A             ; isolate '>', '<', '='.
  17090.  
  17091.         JR      NZ,L3543        ; skip to EX-OR-NOT with these.
  17092.  
  17093.         DEC     A               ; else make $00-$02, $08-$0A to match bits 0-2.
  17094.  
  17095. ;; EX-OR-NOT
  17096. L3543:  RRCA                    ; the first RRCA sets carry for a swap.
  17097.         JR      NC,L354E        ; forward to NU-OR-STR with other 8 cases
  17098.  
  17099. ; for the other 4 cases the two values on the calculator stack are exchanged.
  17100.  
  17101.         PUSH    AF              ; save A and carry.
  17102.         PUSH    HL              ; save HL - pointer to first operand.
  17103.                                 ; (DE points to second operand).
  17104.  
  17105.         CALL    L343C           ; routine exchange swaps the two values.
  17106.                                 ; (HL = second operand, DE = STKEND)
  17107.  
  17108.         POP     DE              ; DE = first operand
  17109.         EX      DE,HL           ; as we were.
  17110.         POP     AF              ; restore A and carry.
  17111.  
  17112. ; Note. it would be better if the 2nd RRCA preceded the string test.
  17113. ; It would save two duplicate bytes and if we also got rid of that sub 8
  17114. ; at the beginning we wouldn't have to alter which bit we test.
  17115.  
  17116. ;; NU-OR-STR
  17117. L354E:  BIT     2,A             ; test if a string comparison.
  17118.         JR      NZ,L3559        ; forward to STRINGS if so.
  17119.  
  17120. ; continue with numeric comparisons.
  17121.  
  17122.         RRCA                    ; 2nd RRCA causes eql/neql to set carry.
  17123.         PUSH    AF              ; save A and carry
  17124.  
  17125.         CALL    L300F           ; routine subtract leaves result on stack.
  17126.         JR      L358C           ; forward to END-TESTS
  17127.  
  17128. ; ---
  17129.  
  17130. ;; STRINGS
  17131. L3559:  RRCA                    ; 2nd RRCA causes eql/neql to set carry.
  17132.         PUSH    AF              ; save A and carry.
  17133.  
  17134.         CALL    L2BF1           ; routine STK-FETCH gets 2nd string params
  17135.         PUSH    DE              ; save start2 *.
  17136.         PUSH    BC              ; and the length.
  17137.  
  17138.         CALL    L2BF1           ; routine STK-FETCH gets 1st string
  17139.                                 ; parameters - start in DE, length in BC.
  17140.         POP     HL              ; restore length of second to HL.
  17141.  
  17142. ; A loop is now entered to compare, by subtraction, each corresponding character
  17143. ; of the strings. For each successful match, the pointers are incremented and
  17144. ; the lengths decreased and the branch taken back to here. If both string
  17145. ; remainders become null at the same time, then an exact match exists.
  17146.  
  17147. ;; BYTE-COMP
  17148. L3564:  LD      A,H             ; test if the second string
  17149.         OR      L               ; is the null string and hold flags.
  17150.  
  17151.         EX      (SP),HL         ; put length2 on stack, bring start2 to HL *.
  17152.         LD      A,B             ; hi byte of length1 to A
  17153.  
  17154.         JR      NZ,L3575        ; forward to SEC-PLUS if second not null.
  17155.  
  17156.         OR      C               ; test length of first string.
  17157.  
  17158. ;; SECND-LOW
  17159. L356B:  POP     BC              ; pop the second length off stack.
  17160.         JR      Z,L3572         ; forward to BOTH-NULL if first string is also
  17161.                                 ; of zero length.
  17162.  
  17163. ; the true condition - first is longer than second (SECND-LESS)
  17164.  
  17165.         POP     AF              ; restore carry (set if eql/neql)
  17166.         CCF                     ; complement carry flag.
  17167.                                 ; Note. equality becomes false.
  17168.                                 ; Inequality is true. By swapping or applying
  17169.                                 ; a terminal 'not', all comparisons have been
  17170.                                 ; manipulated so that this is success path.
  17171.         JR      L3588           ; forward to leave via STR-TEST
  17172.  
  17173. ; ---
  17174. ; the branch was here with a match
  17175.  
  17176. ;; BOTH-NULL
  17177. L3572:  POP     AF              ; restore carry - set for eql/neql
  17178.         JR      L3588           ; forward to STR-TEST
  17179.  
  17180. ; ---  
  17181. ; the branch was here when 2nd string not null and low byte of first is yet
  17182. ; to be tested.
  17183.  
  17184.  
  17185. ;; SEC-PLUS
  17186. L3575:  OR      C               ; test the length of first string.
  17187.         JR      Z,L3585         ; forward to FRST-LESS if length is zero.
  17188.  
  17189. ; both strings have at least one character left.
  17190.  
  17191.         LD      A,(DE)          ; fetch character of first string.
  17192.         SUB     (HL)            ; subtract with that of 2nd string.
  17193.         JR      C,L3585         ; forward to FRST-LESS if carry set
  17194.  
  17195.         JR      NZ,L356B        ; back to SECND-LOW and then STR-TEST
  17196.                                 ; if not exact match.
  17197.  
  17198.         DEC     BC              ; decrease length of 1st string.
  17199.         INC     DE              ; increment 1st string pointer.
  17200.  
  17201.         INC     HL              ; increment 2nd string pointer.
  17202.         EX      (SP),HL         ; swap with length on stack
  17203.         DEC     HL              ; decrement 2nd string length
  17204.         JR      L3564           ; back to BYTE-COMP
  17205.  
  17206. ; ---
  17207. ; the false condition.
  17208.  
  17209. ;; FRST-LESS
  17210. L3585:  POP     BC              ; discard length
  17211.         POP     AF              ; pop A
  17212.         AND     A               ; clear the carry for false result.
  17213.  
  17214. ; ---
  17215. ; exact match and x$>y$ rejoin here
  17216.  
  17217. ;; STR-TEST
  17218. L3588:  PUSH    AF              ; save A and carry
  17219.  
  17220.         RST     28H             ;; FP-CALC
  17221.         DB    $A0             ;;stk-zero      an initial false value.
  17222.         DB    $38             ;;end-calc
  17223.  
  17224. ; both numeric and string paths converge here.
  17225.  
  17226. ;; END-TESTS
  17227. L358C:  POP     AF              ; pop carry  - will be set if eql/neql
  17228.         PUSH    AF              ; save it again.
  17229.  
  17230.         CALL    C,L3501         ; routine NOT sets true(1) if equal(0)
  17231.                                 ; or, for strings, applies true result.
  17232.  
  17233.         POP     AF              ; pop carry and
  17234.         PUSH    AF              ; save A
  17235.  
  17236.         CALL    NC,L34F9        ; routine GREATER-0 tests numeric subtraction
  17237.                                 ; result but also needlessly tests the string
  17238.                                 ; value for zero - it must be.
  17239.  
  17240.         POP     AF              ; pop A
  17241.         RRCA                    ; the third RRCA - test for '<=', '>=' or '<>'.
  17242.         CALL    NC,L3501        ; apply a terminal NOT if so.
  17243.         RET                     ; return.
  17244.  
  17245. ; -------------------------
  17246. ; String concatenation ($17)
  17247. ; -------------------------
  17248. ; This literal combines two strings into one e.g. LET a$ = b$ + c$
  17249. ; The two parameters of the two strings to be combined are on the stack.
  17250.  
  17251. ;; strs-add
  17252. L359C:  CALL    L2BF1           ; routine STK-FETCH fetches string parameters
  17253.                                 ; and deletes calculator stack entry.
  17254.         PUSH    DE              ; save start address.
  17255.         PUSH    BC              ; and length.
  17256.  
  17257.         CALL    L2BF1           ; routine STK-FETCH for first string
  17258.         POP     HL              ; re-fetch first length
  17259.         PUSH    HL              ; and save again
  17260.         PUSH    DE              ; save start of second string
  17261.         PUSH    BC              ; and its length.
  17262.  
  17263.         ADD     HL,BC           ; add the two lengths.
  17264.         LD      B,H             ; transfer to BC
  17265.         LD      C,L             ; and create
  17266.         RST     30H             ; BC-SPACES in workspace.
  17267.                                 ; DE points to start of space.
  17268.  
  17269.         CALL    L2AB2           ; routine STK-STO-$ stores parameters
  17270.                                 ; of new string updating STKEND.
  17271.  
  17272.         POP     BC              ; length of first
  17273.         POP     HL              ; address of start
  17274.         LD      A,B             ; test for
  17275.         OR      C               ; zero length.
  17276.         JR      Z,L35B7         ; to OTHER-STR if null string
  17277.  
  17278.         LDIR                    ; copy string to workspace.
  17279.  
  17280. ;; OTHER-STR
  17281. L35B7:  POP     BC              ; now second length
  17282.         POP     HL              ; and start of string
  17283.         LD      A,B             ; test this one
  17284.         OR      C               ; for zero length
  17285.         JR      Z,L35BF         ; skip forward to STK-PNTRS if so as complete.
  17286.  
  17287.         LDIR                    ; else copy the bytes.
  17288.                                 ; and continue into next routine which
  17289.                                 ; sets the calculator stack pointers.
  17290.  
  17291. ; --------------------
  17292. ; Check stack pointers
  17293. ; --------------------
  17294. ; Register DE is set to STKEND and HL, the result pointer, is set to five
  17295. ; locations below this.
  17296. ; This routine is used when it is inconvenient to save these values at the
  17297. ; time the calculator stack is manipulated due to other activity on the
  17298. ; machine stack.
  17299. ; This routine is also used to terminate the VAL and READ-IN  routines for
  17300. ; the same reason and to initialize the calculator stack at the start of
  17301. ; the CALCULATE routine.
  17302.  
  17303. ;; STK-PNTRS
  17304. L35BF:  LD      HL,($5C65)      ; fetch STKEND value from system variable.
  17305.         LD      DE,$FFFB        ; the value -5
  17306.         PUSH    HL              ; push STKEND value.
  17307.  
  17308.         ADD     HL,DE           ; subtract 5 from HL.
  17309.  
  17310.         POP     DE              ; pop STKEND to DE.
  17311.         RET                     ; return.
  17312.  
  17313. ; ----------------
  17314. ; Handle CHR$ (2F)
  17315. ; ----------------
  17316. ; This function returns a single character string that is a result of
  17317. ; converting a number in the range 0-255 to a string e.g. CHR$ 65 = "A".
  17318.  
  17319. ;; chrs
  17320. L35C9:  CALL    L2DD5           ; routine FP-TO-A puts the number in A.
  17321.  
  17322.         JR      C,L35DC         ; forward to REPORT-Bd if overflow
  17323.         JR      NZ,L35DC        ; forward to REPORT-Bd if negative
  17324.  
  17325.         PUSH    AF              ; save the argument.
  17326.  
  17327.         LD      BC,$0001        ; one space required.
  17328.         RST     30H             ; BC-SPACES makes DE point to start
  17329.  
  17330.         POP     AF              ; restore the number.
  17331.  
  17332.         LD      (DE),A          ; and store in workspace
  17333.  
  17334.         CALL    L2AB2           ; routine STK-STO-$ stacks descriptor.
  17335.  
  17336.         EX      DE,HL           ; make HL point to result and DE to STKEND.
  17337.         RET                     ; return.
  17338.  
  17339. ; ---
  17340.  
  17341. ;; REPORT-Bd
  17342. L35DC:  RST     08H             ; ERROR-1
  17343.         DB    $0A             ; Error Report: Integer out of range
  17344.  
  17345. ; ----------------------------
  17346. ; Handle VAL and VAL$ ($1D, $18)
  17347. ; ----------------------------
  17348. ; VAL treats the characters in a string as a numeric expression.
  17349. ;     e.g. VAL "2.3" = 2.3, VAL "2+4" = 6, VAL ("2" + "4") = 24.
  17350. ; VAL$ treats the characters in a string as a string expression.
  17351. ;     e.g. VAL$ (z$+"(2)") = a$(2) if z$ happens to be "a$".
  17352.  
  17353. ;; val
  17354. ;; val$
  17355. L35DE:  LD      HL,($5C5D)      ; fetch value of system variable CH_ADD
  17356.         PUSH    HL              ; and save on the machine stack.
  17357.         LD      A,B             ; fetch the literal (either $1D or $18).
  17358.         ADD     A,$E3           ; add $E3 to form $00 (setting carry) or $FB.
  17359.         SBC     A,A             ; now form $FF bit 6 = numeric result
  17360.                                 ; or $00 bit 6 = string result.
  17361.         PUSH    AF              ; save this mask on the stack
  17362.  
  17363.         CALL    L2BF1           ; routine STK-FETCH fetches the string operand
  17364.                                 ; from calculator stack.
  17365.  
  17366.         PUSH    DE              ; save the address of the start of the string.
  17367.         INC     BC              ; increment the length for a carriage return.
  17368.  
  17369.         RST     30H             ; BC-SPACES creates the space in workspace.
  17370.         POP     HL              ; restore start of string to HL.
  17371.         LD      ($5C5D),DE      ; load CH_ADD with start DE in workspace.
  17372.  
  17373.         PUSH    DE              ; save the start in workspace
  17374.         LDIR                    ; copy string from program or variables or
  17375.                                 ; workspace to the workspace area.
  17376.         EX      DE,HL           ; end of string + 1 to HL
  17377.         DEC     HL              ; decrement HL to point to end of new area.
  17378.         LD      (HL),$0D        ; insert a carriage return at end.
  17379.         RES     7,(IY+$01)      ; update FLAGS  - signal checking syntax.
  17380.         CALL    L24FB           ; routine SCANNING evaluates string
  17381.                                 ; expression and result.
  17382.  
  17383.         RST     18H             ; GET-CHAR fetches next character.
  17384.         CP      $0D             ; is it the expected carriage return ?
  17385.         JR      NZ,L360C        ; forward to V-RPORT-C if not
  17386.                                 ; 'Nonsense in BASIC'.
  17387.  
  17388.         POP     HL              ; restore start of string in workspace.
  17389.         POP     AF              ; restore expected result flag (bit 6).
  17390.         XOR     (IY+$01)        ; xor with FLAGS now updated by SCANNING.
  17391.         AND     $40             ; test bit 6 - should be zero if result types
  17392.                                 ; match.
  17393.  
  17394. ;; V-RPORT-C
  17395. L360C:  JP      NZ,L1C8A        ; jump back to REPORT-C with a result mismatch.
  17396.  
  17397.         LD      ($5C5D),HL      ; set CH_ADD to the start of the string again.
  17398.         SET     7,(IY+$01)      ; update FLAGS  - signal running program.
  17399.         CALL    L24FB           ; routine SCANNING evaluates the string
  17400.                                 ; in full leaving result on calculator stack.
  17401.  
  17402.         POP     HL              ; restore saved character address in program.
  17403.         LD      ($5C5D),HL      ; and reset the system variable CH_ADD.
  17404.  
  17405.         JR      L35BF           ; back to exit via STK-PNTRS.
  17406.                                 ; resetting the calculator stack pointers
  17407.                                 ; HL and DE from STKEND as it wasn't possible
  17408.                                 ; to preserve them during this routine.
  17409.  
  17410. ; ----------------
  17411. ; Handle STR$ (2E)
  17412. ; ----------------
  17413. ;
  17414. ;
  17415.  
  17416. ;; str$
  17417. L361F:  LD      BC,$0001        ; create an initial byte in workspace
  17418.         RST     30H             ; using BC-SPACES restart.
  17419.  
  17420.         LD      ($5C5B),HL      ; set system variable K_CUR to new location.
  17421.         PUSH    HL              ; and save start on machine stack also.
  17422.  
  17423.         LD      HL,($5C51)      ; fetch value of system variable CURCHL
  17424.         PUSH    HL              ; and save that too.
  17425.  
  17426.         LD      A,$FF           ; select system channel 'R'.
  17427.         CALL    L1601           ; routine CHAN-OPEN opens it.
  17428.         CALL    L2DE3           ; routine PRINT-FP outputs the number to
  17429.                                 ; workspace updating K-CUR.
  17430.  
  17431.         POP     HL              ; restore current channel.
  17432.         CALL    L1615           ; routine CHAN-FLAG resets flags.
  17433.  
  17434.         POP     DE              ; fetch saved start of string to DE.
  17435.         LD      HL,($5C5B)      ; load HL with end of string from K_CUR.
  17436.  
  17437.         AND     A               ; prepare for true subtraction.
  17438.         SBC     HL,DE           ; subtract start from end to give length.
  17439.         LD      B,H             ; transfer the length to
  17440.         LD      C,L             ; the BC register pair.
  17441.  
  17442.         CALL    L2AB2           ; routine STK-STO-$ stores string parameters
  17443.                                 ; on the calculator stack.
  17444.  
  17445.         EX      DE,HL           ; HL = last value, DE = STKEND.
  17446.         RET                     ; return.
  17447.  
  17448. ; ------------
  17449. ; Read-in (1A)
  17450. ; ------------
  17451. ; This is the calculator literal used by the INKEY$ function when a '#'
  17452. ; is encountered after the keyword.
  17453. ; INKEY$ # does not interact correctly with the keyboard, #0 or #1, and
  17454. ; its uses are for other channels.
  17455.  
  17456. ;; read-in
  17457. L3645:  CALL    L1E94           ; routine FIND-INT1 fetches stream to A
  17458.         CP      $10             ; compare with 16 decimal.
  17459.         JP      NC,L1E9F        ; jump to REPORT-Bb if not in range 0 - 15.
  17460.                                 ; 'Integer out of range'
  17461.                                 ; (REPORT-Bd is within range)
  17462.  
  17463.         LD      HL,($5C51)      ; fetch current channel CURCHL
  17464.         PUSH    HL              ; save it
  17465.         CALL    L1601           ; routine CHAN-OPEN opens channel
  17466.  
  17467.         CALL    L15E6           ; routine INPUT-AD - the channel must have an
  17468.                                 ; input stream or else error here from stream
  17469.                                 ; stub.
  17470.         LD      BC,$0000        ; initialize length of string to zero
  17471.         JR      NC,L365F        ; forward to R-I-STORE if no key detected.
  17472.  
  17473.         INC     C               ; increase length to one.
  17474.  
  17475.         RST     30H             ; BC-SPACES creates space for one character
  17476.                                 ; in workspace.
  17477.         LD      (DE),A          ; the character is inserted.
  17478.  
  17479. ;; R-I-STORE
  17480. L365F:  CALL    L2AB2           ; routine STK-STO-$ stacks the string
  17481.                                 ; parameters.
  17482.         POP     HL              ; restore current channel address
  17483.         CALL    L1615           ; routine CHAN-FLAG resets current channel
  17484.                                 ; system variable and flags.
  17485.         JP      L35BF           ; jump back to STK-PNTRS
  17486.  
  17487. ; ----------------
  17488. ; Handle CODE (1C)
  17489. ; ----------------
  17490. ; Returns the ASCII code of a character or first character of a string
  17491. ; e.g. CODE "Aardvark" = 65, CODE "" = 0.
  17492.  
  17493. ;; code
  17494. L3669:  CALL    L2BF1           ; routine STK-FETCH to fetch and delete the
  17495.                                 ; string parameters.
  17496.                                 ; DE points to the start, BC holds the length.
  17497.         LD      A,B             ; test length
  17498.         OR      C               ; of the string.
  17499.         JR      Z,L3671         ; skip to STK-CODE with zero if the null string.
  17500.  
  17501.         LD      A,(DE)          ; else fetch the first character.
  17502.  
  17503. ;; STK-CODE
  17504. L3671:  JP      L2D28           ; jump back to STACK-A (with memory check)
  17505.  
  17506. ; ---------------
  17507. ; Handle LEN (1E)
  17508. ; ---------------
  17509. ; Returns the length of a string.
  17510. ; In Sinclair BASIC strings can be more than twenty thousand characters long
  17511. ; so a sixteen-bit register is required to store the length
  17512.  
  17513. ;; len
  17514. L3674:  CALL    L2BF1           ; routine STK-FETCH to fetch and delete the
  17515.                                 ; string parameters from the calculator stack.
  17516.                                 ; register BC now holds the length of string.
  17517.  
  17518.         JP      L2D2B           ; jump back to STACK-BC to save result on the
  17519.                                 ; calculator stack (with memory check).
  17520.  
  17521. ; -------------------------
  17522. ; Decrease the counter (35)
  17523. ; -------------------------
  17524. ; The calculator has an instruction that decrements a single-byte
  17525. ; pseudo-register and makes consequential relative jumps just like
  17526. ; the Z80's DJNZ instruction.
  17527.  
  17528. ;; dec-jr-nz
  17529. L367A:  EXX                     ; switch in set that addresses code
  17530.  
  17531.         PUSH    HL              ; save pointer to offset byte
  17532.         LD      HL,$5C67        ; address BREG in system variables
  17533.         DEC     (HL)            ; decrement it
  17534.         POP     HL              ; restore pointer
  17535.  
  17536.         JR      NZ,L3687        ; to JUMP-2 if not zero
  17537.  
  17538.         INC     HL              ; step past the jump length.
  17539.         EXX                     ; switch in the main set.
  17540.         RET                     ; return.
  17541.  
  17542. ; Note. as a general rule the calculator avoids using the IY register
  17543. ; otherwise the cumbersome 4 instructions in the middle could be replaced by
  17544. ; dec (iy+$2d) - three bytes instead of six.
  17545.  
  17546.  
  17547. ; ---------
  17548. ; Jump (33)
  17549. ; ---------
  17550. ; This enables the calculator to perform relative jumps just like
  17551. ; the Z80 chip's JR instruction
  17552.  
  17553. ;; jump
  17554. ;; JUMP
  17555. L3686:  EXX                     ;switch in pointer set
  17556.  
  17557. ;; JUMP-2
  17558. L3687:  LD      E,(HL)          ; the jump byte 0-127 forward, 128-255 back.
  17559.         LD      A,E             ; transfer to accumulator.
  17560.         RLA                     ; if backward jump, carry is set.
  17561.         SBC     A,A             ; will be $FF if backward or $00 if forward.
  17562.         LD      D,A             ; transfer to high byte.
  17563.         ADD     HL,DE           ; advance calculator pointer forward or back.
  17564.         EXX                     ; switch back.
  17565.         RET                     ; return.
  17566.  
  17567. ; -----------------
  17568. ; Jump on true (00)
  17569. ; -----------------
  17570. ; This enables the calculator to perform conditional relative jumps
  17571. ; dependent on whether the last test gave a true result
  17572.  
  17573. ;; jump-true
  17574. L368F:  INC     DE              ; collect the
  17575.         INC     DE              ; third byte
  17576.         LD      A,(DE)          ; of the test
  17577.         DEC     DE              ; result and
  17578.         DEC     DE              ; backtrack.
  17579.  
  17580.         AND     A               ; is result 0 or 1 ?
  17581.         JR      NZ,L3686        ; back to JUMP if true (1).
  17582.  
  17583.         EXX                     ; else switch in the pointer set.
  17584.         INC     HL              ; step past the jump length.
  17585.         EXX                     ; switch in the main set.
  17586.         RET                     ; return.
  17587.  
  17588. ; -----------------------
  17589. ; End of calculation (38)
  17590. ; -----------------------
  17591. ; The end-calc literal terminates a mini-program written in the Spectrum's
  17592. ; internal language.
  17593.  
  17594. ;; end-calc
  17595. L369B:  POP     AF              ; drop the calculator return address RE-ENTRY
  17596.         EXX                     ; switch to the other set.
  17597.  
  17598.         EX      (SP),HL         ; transfer H'L' to machine stack for the
  17599.                                 ; return address.
  17600.                                 ; when exiting recursion then the previous
  17601.                                 ; pointer is transferred to H'L'.
  17602.  
  17603.         EXX                     ; back to main set.
  17604.         RET                     ; return.
  17605.  
  17606.  
  17607. ; ------------------------
  17608. ; THE 'MODULUS' SUBROUTINE
  17609. ; ------------------------
  17610. ; (offset: $32 'n-mod-m')
  17611. ;
  17612. ;
  17613.  
  17614. ;; n-mod-m
  17615. L36A0:  RST     28H             ;; FP-CALC          17, 3.
  17616.         DB    $C0             ;;st-mem-0          17, 3.
  17617.         DB    $02             ;;delete            17.
  17618.         DB    $31             ;;duplicate         17, 17.
  17619.         DB    $E0             ;;get-mem-0         17, 17, 3.
  17620.         DB    $05             ;;division          17, 17/3.
  17621.         DB    $27             ;;int               17, 5.
  17622.         DB    $E0             ;;get-mem-0         17, 5, 3.
  17623.         DB    $01             ;;exchange          17, 3, 5.
  17624.         DB    $C0             ;;st-mem-0          17, 3, 5.
  17625.         DB    $04             ;;multiply          17, 15.
  17626.         DB    $03             ;;subtract          2.
  17627.         DB    $E0             ;;get-mem-0         2, 5.
  17628.         DB    $38             ;;end-calc          2, 5.
  17629.  
  17630.         RET                     ; return.
  17631.  
  17632.  
  17633. ; ------------------
  17634. ; THE 'INT' FUNCTION
  17635. ; ------------------
  17636. ; (offset $27: 'int' )
  17637. ;
  17638. ; This function returns the integer of x, which is just the same as truncate
  17639. ; for positive numbers. The truncate literal truncates negative numbers
  17640. ; upwards so that -3.4 gives -3 whereas the BASIC INT function has to
  17641. ; truncate negative numbers down so that INT -3.4 is -4.
  17642. ; It is best to work through using, say, +-3.4 as examples.
  17643.  
  17644. ;; int
  17645. L36AF:  RST     28H             ;; FP-CALC              x.    (= 3.4 or -3.4).
  17646.         DB    $31             ;;duplicate             x, x.
  17647.         DB    $36             ;;less-0                x, (1/0)
  17648.         DB    $00             ;;jump-true             x, (1/0)
  17649.         DB    $04             ;;to L36B7, X-NEG
  17650.  
  17651.         DB    $3A             ;;truncate              trunc 3.4 = 3.
  17652.         DB    $38             ;;end-calc              3.
  17653.  
  17654.         RET                     ; return with + int x on stack.
  17655.  
  17656. ; ---
  17657.  
  17658.  
  17659. ;; X-NEG
  17660. L36B7:  DB    $31             ;;duplicate             -3.4, -3.4.
  17661.         DB    $3A             ;;truncate              -3.4, -3.
  17662.         DB    $C0             ;;st-mem-0              -3.4, -3.
  17663.         DB    $03             ;;subtract              -.4
  17664.         DB    $E0             ;;get-mem-0             -.4, -3.
  17665.         DB    $01             ;;exchange              -3, -.4.
  17666.         DB    $30             ;;not                   -3, (0).
  17667.         DB    $00             ;;jump-true             -3.
  17668.         DB    $03             ;;to L36C2, EXIT        -3.
  17669.  
  17670.         DB    $A1             ;;stk-one               -3, 1.
  17671.         DB    $03             ;;subtract              -4.
  17672.  
  17673. ;; EXIT
  17674. L36C2:  DB    $38             ;;end-calc              -4.
  17675.  
  17676.         RET                     ; return.
  17677.  
  17678.  
  17679. ; ----------------
  17680. ; Exponential (26)
  17681. ; ----------------
  17682. ;
  17683. ;
  17684.  
  17685. ;; EXP
  17686. ;; exp
  17687. L36C4:  RST     28H             ;; FP-CALC
  17688.         DB    $3D             ;;re-stack
  17689.         DB    $34             ;;stk-data
  17690.         DB    $F1             ;;Exponent: $81, Bytes: 4
  17691.         DB    $38,$AA,$3B,$29 ;;
  17692.         DB    $04             ;;multiply
  17693.         DB    $31             ;;duplicate
  17694.         DB    $27             ;;int
  17695.         DB    $C3             ;;st-mem-3
  17696.         DB    $03             ;;subtract
  17697.         DB    $31             ;;duplicate
  17698.         DB    $0F             ;;addition
  17699.         DB    $A1             ;;stk-one
  17700.         DB    $03             ;;subtract
  17701.         DB    $88             ;;series-08
  17702.         DB    $13             ;;Exponent: $63, Bytes: 1
  17703.         DB    $36             ;;(+00,+00,+00)
  17704.         DB    $58             ;;Exponent: $68, Bytes: 2
  17705.         DB    $65,$66         ;;(+00,+00)
  17706.         DB    $9D             ;;Exponent: $6D, Bytes: 3
  17707.         DB    $78,$65,$40     ;;(+00)
  17708.         DB    $A2             ;;Exponent: $72, Bytes: 3
  17709.         DB    $60,$32,$C9     ;;(+00)
  17710.         DB    $E7             ;;Exponent: $77, Bytes: 4
  17711.         DB    $21,$F7,$AF,$24 ;;
  17712.         DB    $EB             ;;Exponent: $7B, Bytes: 4
  17713.         DB    $2F,$B0,$B0,$14 ;;
  17714.         DB    $EE             ;;Exponent: $7E, Bytes: 4
  17715.         DB    $7E,$BB,$94,$58 ;;
  17716.         DB    $F1             ;;Exponent: $81, Bytes: 4
  17717.         DB    $3A,$7E,$F8,$CF ;;
  17718.         DB    $E3             ;;get-mem-3
  17719.         DB    $38             ;;end-calc
  17720.  
  17721.         CALL    L2DD5           ; routine FP-TO-A
  17722.         JR      NZ,L3705        ; to N-NEGTV
  17723.  
  17724.         JR      C,L3703         ; to REPORT-6b
  17725.  
  17726.         ADD     A,(HL)          ;
  17727.         JR      NC,L370C        ; to RESULT-OK
  17728.  
  17729.  
  17730. ;; REPORT-6b
  17731. L3703:  RST     08H             ; ERROR-1
  17732.         DB    $05             ; Error Report: Number too big
  17733.  
  17734. ;; N-NEGTV
  17735. L3705:  JR      C,L370E         ; to RSLT-ZERO
  17736.  
  17737.         SUB     (HL)            ;
  17738.         JR      NC,L370E        ; to RSLT-ZERO
  17739.  
  17740.         NEG                     ; Negate
  17741.  
  17742. ;; RESULT-OK
  17743. L370C:  LD      (HL),A          ;
  17744.         RET                     ; return.
  17745.  
  17746. ; ---
  17747.  
  17748.  
  17749. ;; RSLT-ZERO
  17750. L370E:  RST     28H             ;; FP-CALC
  17751.         DB    $02             ;;delete
  17752.         DB    $A0             ;;stk-zero
  17753.         DB    $38             ;;end-calc
  17754.  
  17755.         RET                     ; return.
  17756.  
  17757.  
  17758. ; ----------------------
  17759. ; Natural logarithm (25)
  17760. ; ----------------------
  17761. ;
  17762. ;
  17763.  
  17764. ;; ln
  17765. L3713:  RST     28H             ;; FP-CALC
  17766.         DB    $3D             ;;re-stack
  17767.         DB    $31             ;;duplicate
  17768.         DB    $37             ;;greater-0
  17769.         DB    $00             ;;jump-true
  17770.         DB    $04             ;;to L371C, VALID
  17771.  
  17772.         DB    $38             ;;end-calc
  17773.  
  17774.  
  17775. ;; REPORT-Ab
  17776. L371A:  RST     08H             ; ERROR-1
  17777.         DB    $09             ; Error Report: Invalid argument
  17778.  
  17779. ;; VALID
  17780. L371C:  DB    $A0             ;;stk-zero
  17781.         DB    $02             ;;delete
  17782.         DB    $38             ;;end-calc
  17783.         LD      A,(HL)          ;
  17784.  
  17785.         LD      (HL),$80        ;
  17786.         CALL    L2D28           ; routine STACK-A
  17787.  
  17788.         RST     28H             ;; FP-CALC
  17789.         DB    $34             ;;stk-data
  17790.         DB    $38             ;;Exponent: $88, Bytes: 1
  17791.         DB    $00             ;;(+00,+00,+00)
  17792.         DB    $03             ;;subtract
  17793.         DB    $01             ;;exchange
  17794.         DB    $31             ;;duplicate
  17795.         DB    $34             ;;stk-data
  17796.         DB    $F0             ;;Exponent: $80, Bytes: 4
  17797.         DB    $4C,$CC,$CC,$CD ;;
  17798.         DB    $03             ;;subtract
  17799.         DB    $37             ;;greater-0
  17800.         DB    $00             ;;jump-true
  17801.         DB    $08             ;;to L373D, GRE.8
  17802.  
  17803.         DB    $01             ;;exchange
  17804.         DB    $A1             ;;stk-one
  17805.         DB    $03             ;;subtract
  17806.         DB    $01             ;;exchange
  17807.         DB    $38             ;;end-calc
  17808.  
  17809.         INC     (HL)            ;
  17810.  
  17811.         RST     28H             ;; FP-CALC
  17812.  
  17813. ;; GRE.8
  17814. L373D:  DB    $01             ;;exchange
  17815.         DB    $34             ;;stk-data
  17816.         DB    $F0             ;;Exponent: $80, Bytes: 4
  17817.         DB    $31,$72,$17,$F8 ;;
  17818.         DB    $04             ;;multiply
  17819.         DB    $01             ;;exchange
  17820.         DB    $A2             ;;stk-half
  17821.         DB    $03             ;;subtract
  17822.         DB    $A2             ;;stk-half
  17823.         DB    $03             ;;subtract
  17824.         DB    $31             ;;duplicate
  17825.         DB    $34             ;;stk-data
  17826.         DB    $32             ;;Exponent: $82, Bytes: 1
  17827.         DB    $20             ;;(+00,+00,+00)
  17828.         DB    $04             ;;multiply
  17829.         DB    $A2             ;;stk-half
  17830.         DB    $03             ;;subtract
  17831.         DB    $8C             ;;series-0C
  17832.         DB    $11             ;;Exponent: $61, Bytes: 1
  17833.         DB    $AC             ;;(+00,+00,+00)
  17834.         DB    $14             ;;Exponent: $64, Bytes: 1
  17835.         DB    $09             ;;(+00,+00,+00)
  17836.         DB    $56             ;;Exponent: $66, Bytes: 2
  17837.         DB    $DA,$A5         ;;(+00,+00)
  17838.         DB    $59             ;;Exponent: $69, Bytes: 2
  17839.         DB    $30,$C5         ;;(+00,+00)
  17840.         DB    $5C             ;;Exponent: $6C, Bytes: 2
  17841.         DB    $90,$AA         ;;(+00,+00)
  17842.         DB    $9E             ;;Exponent: $6E, Bytes: 3
  17843.         DB    $70,$6F,$61     ;;(+00)
  17844.         DB    $A1             ;;Exponent: $71, Bytes: 3
  17845.         DB    $CB,$DA,$96     ;;(+00)
  17846.         DB    $A4             ;;Exponent: $74, Bytes: 3
  17847.         DB    $31,$9F,$B4     ;;(+00)
  17848.         DB    $E7             ;;Exponent: $77, Bytes: 4
  17849.         DB    $A0,$FE,$5C,$FC ;;
  17850.         DB    $EA             ;;Exponent: $7A, Bytes: 4
  17851.         DB    $1B,$43,$CA,$36 ;;
  17852.         DB    $ED             ;;Exponent: $7D, Bytes: 4
  17853.         DB    $A7,$9C,$7E,$5E ;;
  17854.         DB    $F0             ;;Exponent: $80, Bytes: 4
  17855.         DB    $6E,$23,$80,$93 ;;
  17856.         DB    $04             ;;multiply
  17857.         DB    $0F             ;;addition
  17858.         DB    $38             ;;end-calc
  17859.  
  17860.         RET                     ; return.
  17861.  
  17862.  
  17863. ; -----------------------------
  17864. ; THE 'TRIGONOMETRIC' FUNCTIONS
  17865. ; -----------------------------
  17866. ; Trigonometry is rocket science. It is also used by carpenters and pyramid
  17867. ; builders.
  17868. ; Some uses can be quite abstract but the principles can be seen in simple
  17869. ; right-angled triangles. Triangles have some special properties -
  17870. ;
  17871. ; 1) The sum of the three angles is always PI radians (180 degrees).
  17872. ;    Very helpful if you know two angles and wish to find the third.
  17873. ; 2) In any right-angled triangle the sum of the squares of the two shorter
  17874. ;    sides is equal to the square of the longest side opposite the right-angle.
  17875. ;    Very useful if you know the length of two sides and wish to know the
  17876. ;    length of the third side.
  17877. ; 3) Functions sine, cosine and tangent enable one to calculate the length
  17878. ;    of an unknown side when the length of one other side and an angle is
  17879. ;    known.
  17880. ; 4) Functions arcsin, arccosine and arctan enable one to calculate an unknown
  17881. ;    angle when the length of two of the sides is known.
  17882.  
  17883. ;---------------------------------
  17884. ; THE 'REDUCE ARGUMENT' SUBROUTINE
  17885. ;---------------------------------
  17886. ; (offset $39: 'get-argt')
  17887. ;
  17888. ; This routine performs two functions on the angle, in radians, that forms
  17889. ; the argument to the sine and cosine functions.
  17890. ; First it ensures that the angle 'wraps round'. That if a ship turns through
  17891. ; an angle of, say, 3*PI radians (540 degrees) then the net effect is to turn
  17892. ; through an angle of PI radians (180 degrees).
  17893. ; Secondly it converts the angle in radians to a fraction of a right angle,
  17894. ; depending within which quadrant the angle lies, with the periodicity
  17895. ; resembling that of the desired sine value.
  17896. ; The result lies in the range -1 to +1.              
  17897. ;
  17898. ;                     90 deg.
  17899. ;
  17900. ;                     (pi/2)
  17901. ;              II       +1        I
  17902. ;                       |
  17903. ;        sin+      |\   |   /|    sin+
  17904. ;        cos-      | \  |  / |    cos+
  17905. ;        tan-      |  \ | /  |    tan+
  17906. ;                  |   \|/)  |          
  17907. ; 180 deg. (pi) 0 -|----+----|-- 0  (0)   0 degrees
  17908. ;                  |   /|\   |
  17909. ;        sin-      |  / | \  |    sin-
  17910. ;        cos-      | /  |  \ |    cos+
  17911. ;        tan+      |/   |   \|    tan-
  17912. ;                       |
  17913. ;              III      -1       IV
  17914. ;                     (3pi/2)
  17915. ;
  17916. ;                     270 deg.
  17917. ;
  17918.  
  17919. ;; get-argt
  17920. L3783:  RST     28H             ;; FP-CALC      X.
  17921.         DB    $3D             ;;re-stack
  17922.         DB    $34             ;;stk-data
  17923.         DB    $EE             ;;Exponent: $7E,
  17924.                                 ;;Bytes: 4
  17925.         DB    $22,$F9,$83,$6E ;;              X, 1/(2*PI)
  17926.         DB    $04             ;;multiply      X/(2*PI) = fraction
  17927.         DB    $31             ;;duplicate
  17928.         DB    $A2             ;;stk-half
  17929.         DB    $0F             ;;addition
  17930.         DB    $27             ;;int
  17931.  
  17932.         DB    $03             ;;subtract      now range -.5 to .5
  17933.  
  17934.         DB    $31             ;;duplicate
  17935.         DB    $0F             ;;addition      now range -1 to 1.
  17936.         DB    $31             ;;duplicate
  17937.         DB    $0F             ;;addition      now range -2 to +2.
  17938.  
  17939. ; quadrant I (0 to +1) and quadrant IV (-1 to 0) are now correct.
  17940. ; quadrant II ranges +1 to +2.
  17941. ; quadrant III ranges -2 to -1.
  17942.  
  17943.         DB    $31             ;;duplicate     Y, Y.
  17944.         DB    $2A             ;;abs           Y, abs(Y).    range 1 to 2
  17945.         DB    $A1             ;;stk-one       Y, abs(Y), 1.
  17946.         DB    $03             ;;subtract      Y, abs(Y)-1.  range 0 to 1
  17947.         DB    $31             ;;duplicate     Y, Z, Z.
  17948.         DB    $37             ;;greater-0     Y, Z, (1/0).
  17949.  
  17950.         DB    $C0             ;;st-mem-0         store as possible sign
  17951.                                 ;;                 for cosine function.
  17952.  
  17953.         DB    $00             ;;jump-true
  17954.         DB    $04             ;;to L37A1, ZPLUS  with quadrants II and III.
  17955.  
  17956. ; else the angle lies in quadrant I or IV and value Y is already correct.
  17957.  
  17958.         DB    $02             ;;delete        Y.   delete the test value.
  17959.         DB    $38             ;;end-calc      Y.
  17960.  
  17961.         RET                     ; return.       with Q1 and Q4           >>>
  17962.  
  17963. ; ---
  17964.  
  17965. ; the branch was here with quadrants II (0 to 1) and III (1 to 0).
  17966. ; Y will hold -2 to -1 if this is quadrant III.
  17967.  
  17968. ;; ZPLUS
  17969. L37A1:  DB    $A1             ;;stk-one         Y, Z, 1.
  17970.         DB    $03             ;;subtract        Y, Z-1.       Q3 = 0 to -1
  17971.         DB    $01             ;;exchange        Z-1, Y.
  17972.         DB    $36             ;;less-0          Z-1, (1/0).
  17973.         DB    $00             ;;jump-true       Z-1.
  17974.         DB    $02             ;;to L37A8, YNEG
  17975.                                 ;;if angle in quadrant III
  17976.  
  17977. ; else angle is within quadrant II (-1 to 0)
  17978.  
  17979.         DB    $1B             ;;negate          range +1 to 0.
  17980.  
  17981. ;; YNEG
  17982. L37A8:  DB    $38             ;;end-calc        quadrants II and III correct.
  17983.  
  17984.         RET                     ; return.
  17985.  
  17986.  
  17987. ;----------------------
  17988. ; THE 'COSINE' FUNCTION
  17989. ;----------------------
  17990. ; (offset $20: 'cos')
  17991. ; Cosines are calculated as the sine of the opposite angle rectifying the
  17992. ; sign depending on the quadrant rules.
  17993. ;
  17994. ;
  17995. ;           /|
  17996. ;        h /y|
  17997. ;         /  |o
  17998. ;        /x  |
  17999. ;       /----|    
  18000. ;         a
  18001. ;
  18002. ; The cosine of angle x is the adjacent side (a) divided by the hypotenuse 1.
  18003. ; However if we examine angle y then a/h is the sine of that angle.
  18004. ; Since angle x plus angle y equals a right-angle, we can find angle y by
  18005. ; subtracting angle x from pi/2.
  18006. ; However it's just as easy to reduce the argument first and subtract the
  18007. ; reduced argument from the value 1 (a reduced right-angle).
  18008. ; It's even easier to subtract 1 from the angle and rectify the sign.
  18009. ; In fact, after reducing the argument, the absolute value of the argument
  18010. ; is used and rectified using the test result stored in mem-0 by 'get-argt'
  18011. ; for that purpose.
  18012. ;
  18013.  
  18014. ;; cos
  18015. L37AA:  RST     28H             ;; FP-CALC              angle in radians.
  18016.         DB    $39             ;;get-argt              X     reduce -1 to +1
  18017.  
  18018.         DB    $2A             ;;abs                   ABS X.   0 to 1
  18019.         DB    $A1             ;;stk-one               ABS X, 1.
  18020.         DB    $03             ;;subtract              now opposite angle
  18021.                                 ;;                      although sign is -ve.
  18022.  
  18023.         DB    $E0             ;;get-mem-0             fetch the sign indicator
  18024.         DB    $00             ;;jump-true
  18025.         DB    $06             ;;fwd to L37B7, C-ENT
  18026.                                 ;;forward to common code if in QII or QIII.
  18027.  
  18028.         DB    $1B             ;;negate                else make sign +ve.
  18029.         DB    $33             ;;jump
  18030.         DB    $03             ;;fwd to L37B7, C-ENT
  18031.                                 ;; with quadrants I and IV.
  18032.  
  18033. ;--------------------
  18034. ; THE 'SINE' FUNCTION
  18035. ;--------------------
  18036. ; (offset $1F: 'sin')
  18037. ; This is a fundamental transcendental function from which others such as cos
  18038. ; and tan are directly, or indirectly, derived.
  18039. ; It uses the series generator to produce Chebyshev polynomials.
  18040. ;
  18041. ;
  18042. ;           /|
  18043. ;        1 / |
  18044. ;         /  |x
  18045. ;        /a  |
  18046. ;       /----|    
  18047. ;         y
  18048. ;
  18049. ; The 'get-argt' function is designed to modify the angle and its sign
  18050. ; in line with the desired sine value and afterwards it can launch straight
  18051. ; into common code.
  18052.  
  18053. ;; sin
  18054. L37B5:  RST     28H             ;; FP-CALC      angle in radians
  18055.         DB    $39             ;;get-argt      reduce - sign now correct.
  18056.  
  18057. ;; C-ENT
  18058. L37B7:  DB    $31             ;;duplicate
  18059.         DB    $31             ;;duplicate
  18060.         DB    $04             ;;multiply
  18061.         DB    $31             ;;duplicate
  18062.         DB    $0F             ;;addition
  18063.         DB    $A1             ;;stk-one
  18064.         DB    $03             ;;subtract
  18065.  
  18066.         DB    $86             ;;series-06
  18067.         DB    $14             ;;Exponent: $64, Bytes: 1
  18068.         DB    $E6             ;;(+00,+00,+00)
  18069.         DB    $5C             ;;Exponent: $6C, Bytes: 2
  18070.         DB    $1F,$0B         ;;(+00,+00)
  18071.         DB    $A3             ;;Exponent: $73, Bytes: 3
  18072.         DB    $8F,$38,$EE     ;;(+00)
  18073.         DB    $E9             ;;Exponent: $79, Bytes: 4
  18074.         DB    $15,$63,$BB,$23 ;;
  18075.         DB    $EE             ;;Exponent: $7E, Bytes: 4
  18076.         DB    $92,$0D,$CD,$ED ;;
  18077.         DB    $F1             ;;Exponent: $81, Bytes: 4
  18078.         DB    $23,$5D,$1B,$EA ;;
  18079.         DB    $04             ;;multiply
  18080.         DB    $38             ;;end-calc
  18081.  
  18082.         RET                     ; return.
  18083.  
  18084. ;-----------------------
  18085. ; THE 'TANGENT' FUNCTION
  18086. ;-----------------------
  18087. ; (offset $21: 'tan')
  18088. ;
  18089. ; Evaluates tangent x as    sin(x) / cos(x).
  18090. ;
  18091. ;
  18092. ;           /|
  18093. ;        h / |
  18094. ;         /  |o
  18095. ;        /x  |
  18096. ;       /----|    
  18097. ;         a
  18098. ;
  18099. ; the tangent of angle x is the ratio of the length of the opposite side
  18100. ; divided by the length of the adjacent side. As the opposite length can
  18101. ; be calculates using sin(x) and the adjacent length using cos(x) then
  18102. ; the tangent can be defined in terms of the previous two functions.
  18103.  
  18104. ; Error 6 if the argument, in radians, is too close to one like pi/2
  18105. ; which has an infinite tangent. e.g. PRINT TAN (PI/2)  evaluates as 1/0.
  18106. ; Similarly PRINT TAN (3*PI/2), TAN (5*PI/2) etc.
  18107.  
  18108. ;; tan
  18109. L37DA:  RST     28H             ;; FP-CALC          x.
  18110.         DB    $31             ;;duplicate         x, x.
  18111.         DB    $1F             ;;sin               x, sin x.
  18112.         DB    $01             ;;exchange          sin x, x.
  18113.         DB    $20             ;;cos               sin x, cos x.
  18114.         DB    $05             ;;division          sin x/cos x (= tan x).
  18115.         DB    $38             ;;end-calc          tan x.
  18116.  
  18117.         RET                     ; return.
  18118.  
  18119. ;----------------------
  18120. ; THE 'ARCTAN' FUNCTION
  18121. ;----------------------
  18122. ; (Offset $24: 'atn')
  18123. ; the inverse tangent function with the result in radians.
  18124. ; This is a fundamental transcendental function from which others such as asn
  18125. ; and acs are directly, or indirectly, derived.
  18126. ; It uses the series generator to produce Chebyshev polynomials.
  18127.  
  18128. ;; atn
  18129. L37E2:  CALL    L3297           ; routine re-stack
  18130.         LD      A,(HL)          ; fetch exponent byte.
  18131.         CP      $81             ; compare to that for 'one'
  18132.         JR      C,L37F8         ; forward, if less, to SMALL
  18133.  
  18134.         RST     28H             ;; FP-CALC
  18135.         DB    $A1             ;;stk-one
  18136.         DB    $1B             ;;negate
  18137.         DB    $01             ;;exchange
  18138.         DB    $05             ;;division
  18139.         DB    $31             ;;duplicate
  18140.         DB    $36             ;;less-0
  18141.         DB    $A3             ;;stk-pi/2
  18142.         DB    $01             ;;exchange
  18143.         DB    $00             ;;jump-true
  18144.         DB    $06             ;;to L37FA, CASES
  18145.  
  18146.         DB    $1B             ;;negate
  18147.         DB    $33             ;;jump
  18148.         DB    $03             ;;to L37FA, CASES
  18149.  
  18150. ;; SMALL
  18151. L37F8:  RST     28H             ;; FP-CALC
  18152.         DB    $A0             ;;stk-zero
  18153.  
  18154. ;; CASES
  18155. L37FA:  DB    $01             ;;exchange
  18156.         DB    $31             ;;duplicate
  18157.         DB    $31             ;;duplicate
  18158.         DB    $04             ;;multiply
  18159.         DB    $31             ;;duplicate
  18160.         DB    $0F             ;;addition
  18161.         DB    $A1             ;;stk-one
  18162.         DB    $03             ;;subtract
  18163.         DB    $8C             ;;series-0C
  18164.         DB    $10             ;;Exponent: $60, Bytes: 1
  18165.         DB    $B2             ;;(+00,+00,+00)
  18166.         DB    $13             ;;Exponent: $63, Bytes: 1
  18167.         DB    $0E             ;;(+00,+00,+00)
  18168.         DB    $55             ;;Exponent: $65, Bytes: 2
  18169.         DB    $E4,$8D         ;;(+00,+00)
  18170.         DB    $58             ;;Exponent: $68, Bytes: 2
  18171.         DB    $39,$BC         ;;(+00,+00)
  18172.         DB    $5B             ;;Exponent: $6B, Bytes: 2
  18173.         DB    $98,$FD         ;;(+00,+00)
  18174.         DB    $9E             ;;Exponent: $6E, Bytes: 3
  18175.         DB    $00,$36,$75     ;;(+00)
  18176.         DB    $A0             ;;Exponent: $70, Bytes: 3
  18177.         DB    $DB,$E8,$B4     ;;(+00)
  18178.         DB    $63             ;;Exponent: $73, Bytes: 2
  18179.         DB    $42,$C4         ;;(+00,+00)
  18180.         DB    $E6             ;;Exponent: $76, Bytes: 4
  18181.         DB    $B5,$09,$36,$BE ;;
  18182.         DB    $E9             ;;Exponent: $79, Bytes: 4
  18183.         DB    $36,$73,$1B,$5D ;;
  18184.         DB    $EC             ;;Exponent: $7C, Bytes: 4
  18185.         DB    $D8,$DE,$63,$BE ;;
  18186.         DB    $F0             ;;Exponent: $80, Bytes: 4
  18187.         DB    $61,$A1,$B3,$0C ;;
  18188.         DB    $04             ;;multiply
  18189.         DB    $0F             ;;addition
  18190.         DB    $38             ;;end-calc
  18191.  
  18192.         RET                     ; return.
  18193.  
  18194.  
  18195. ;----------------------
  18196. ; THE 'ARCSIN' FUNCTION
  18197. ;----------------------
  18198. ; (Offset $22: 'asn')
  18199. ; the inverse sine function with result in radians.
  18200. ; derived from arctan function above.
  18201. ; Error A unless the argument is between -1 and +1 inclusive.
  18202. ; uses an adaptation of the formula asn(x) = atn(x/sqr(1-x*x))
  18203. ;
  18204. ;
  18205. ;           /|
  18206. ;        1 / |
  18207. ;         /  |x
  18208. ;        /a  |
  18209. ;       /----|    
  18210. ;         y
  18211. ;
  18212. ; e.g. we know the opposite side (x) and hypotenuse (1)
  18213. ; and we wish to find angle a in radians.
  18214. ; we can derive length y by Pythagorus and then use ATN instead.
  18215. ; since y*y + x*x = 1*1 (Pythagorus Theorem) then
  18216. ; y=sqr(1-x*x)                         - no need to multiply 1 by itself.
  18217. ; so, asn(a) = atn(x/y)
  18218. ; or more fully,
  18219. ; asn(a) = atn(x/sqr(1-x*x))
  18220.  
  18221. ; Close but no cigar.
  18222.  
  18223. ; While PRINT ATN (x/SQR (1-x*x)) gives the same results as PRINT ASN x,
  18224. ; it leads to division by zero when x is 1 or -1.
  18225. ; To overcome this, 1 is added to y giving half the required angle and the
  18226. ; result is then doubled.
  18227. ; That is PRINT ATN (x/(SQR (1-x*x) +1)) *2
  18228. ; A value higher than 1 gives the required error as attempting to find  the
  18229. ; square root of a negative number generates an error in Sinclair BASIC.
  18230.  
  18231. ;; asn
  18232. L3833:  RST     28H             ;; FP-CALC      x.
  18233.         DB    $31             ;;duplicate     x, x.
  18234.         DB    $31             ;;duplicate     x, x, x.
  18235.         DB    $04             ;;multiply      x, x*x.
  18236.         DB    $A1             ;;stk-one       x, x*x, 1.
  18237.         DB    $03             ;;subtract      x, x*x-1.
  18238.         DB    $1B             ;;negate        x, 1-x*x.
  18239.         DB    $28             ;;sqr           x, sqr(1-x*x) = y
  18240.         DB    $A1             ;;stk-one       x, y, 1.
  18241.         DB    $0F             ;;addition      x, y+1.
  18242.         DB    $05             ;;division      x/y+1.
  18243.         DB    $24             ;;atn           a/2       (half the angle)
  18244.         DB    $31             ;;duplicate     a/2, a/2.
  18245.         DB    $0F             ;;addition      a.
  18246.         DB    $38             ;;end-calc      a.
  18247.  
  18248.         RET                     ; return.
  18249.  
  18250.  
  18251. ;-------------------------
  18252. ; THE 'ARCCOS' FUNCTION
  18253. ;-------------------------
  18254. ; (Offset $23: 'acs')
  18255. ; the inverse cosine function with the result in radians.
  18256. ; Error A unless the argument is between -1 and +1.
  18257. ; Result in range 0 to pi.
  18258. ; Derived from asn above which is in turn derived from the preceding atn.
  18259. ; It could have been derived directly from atn using acs(x) = atn(sqr(1-x*x)/x).
  18260. ; However, as sine and cosine are horizontal translations of each other,
  18261. ; uses acs(x) = pi/2 - asn(x)
  18262.  
  18263. ; e.g. the arccosine of a known x value will give the required angle b in
  18264. ; radians.
  18265. ; We know, from above, how to calculate the angle a using asn(x).
  18266. ; Since the three angles of any triangle add up to 180 degrees, or pi radians,
  18267. ; and the largest angle in this case is a right-angle (pi/2 radians), then
  18268. ; we can calculate angle b as pi/2 (both angles) minus asn(x) (angle a).
  18269. ;
  18270. ;
  18271. ;           /|
  18272. ;        1 /b|
  18273. ;         /  |x
  18274. ;        /a  |
  18275. ;       /----|    
  18276. ;         y
  18277. ;
  18278.  
  18279. ;; acs
  18280. L3843:  RST     28H             ;; FP-CALC      x.
  18281.         DB    $22             ;;asn           asn(x).
  18282.         DB    $A3             ;;stk-pi/2      asn(x), pi/2.
  18283.         DB    $03             ;;subtract      asn(x) - pi/2.
  18284.         DB    $1B             ;;negate        pi/2 -asn(x)  =  acs(x).
  18285.         DB    $38             ;;end-calc      acs(x).
  18286.  
  18287.         RET                     ; return.
  18288.  
  18289.  
  18290. ; --------------------------
  18291. ; THE 'SQUARE ROOT' FUNCTION
  18292. ; --------------------------
  18293. ; (Offset $28: 'sqr')
  18294. ; This routine is remarkable only in its brevity - 7 bytes.
  18295. ; It wasn't written here but in the ZX81 where the programmers had to squeeze
  18296. ; a bulky operating sytem into an 8K ROM. It simply calculates
  18297. ; the square root by stacking the value .5 and continuing into the 'to-power'
  18298. ; routine. With more space available the much faster Newton-Raphson method
  18299. ; should have been used as on the Jupiter Ace.
  18300.  
  18301. ;; sqr
  18302. L384A:  RST     28H             ;; FP-CALC
  18303.         DB    $31             ;;duplicate
  18304.         DB    $30             ;;not
  18305.         DB    $00             ;;jump-true
  18306.         DB    $1E             ;;to L386C, LAST
  18307.  
  18308.         DB    $A2             ;;stk-half
  18309.         DB    $38             ;;end-calc
  18310.  
  18311.  
  18312. ; ------------------------------
  18313. ; THE 'EXPONENTIATION' OPERATION
  18314. ; ------------------------------
  18315. ; (Offset $06: 'to-power')
  18316. ; This raises the first number X to the power of the second number Y.
  18317. ; As with the ZX80,
  18318. ; 0 ^ 0 = 1.
  18319. ; 0 ^ +n = 0.
  18320. ; 0 ^ -n = arithmetic overflow.
  18321. ;
  18322.  
  18323. ;; to-power
  18324. L3851:  RST     28H             ;; FP-CALC              X, Y.
  18325.         DB    $01             ;;exchange              Y, X.
  18326.         DB    $31             ;;duplicate             Y, X, X.
  18327.         DB    $30             ;;not                   Y, X, (1/0).
  18328.         DB    $00             ;;jump-true
  18329.         DB    $07             ;;to L385D, XISO   if X is zero.
  18330.  
  18331. ; else X is non-zero. Function 'ln' will catch a negative value of X.
  18332.  
  18333.         DB    $25             ;;ln                    Y, LN X.
  18334.         DB    $04             ;;multiply              Y * LN X.
  18335.         DB    $38             ;;end-calc
  18336.  
  18337.         JP      L36C4           ; jump back to EXP routine   ->
  18338.  
  18339. ; ---
  18340.  
  18341. ; these routines form the three simple results when the number is zero.
  18342. ; begin by deleting the known zero to leave Y the power factor.
  18343.  
  18344. ;; XISO
  18345. L385D:  DB    $02             ;;delete                Y.
  18346.         DB    $31             ;;duplicate             Y, Y.
  18347.         DB    $30             ;;not                   Y, (1/0).
  18348.         DB    $00             ;;jump-true
  18349.         DB    $09             ;;to L386A, ONE         if Y is zero.
  18350.  
  18351.         DB    $A0             ;;stk-zero              Y, 0.
  18352.         DB    $01             ;;exchange              0, Y.
  18353.         DB    $37             ;;greater-0             0, (1/0).
  18354.         DB    $00             ;;jump-true             0.
  18355.         DB    $06             ;;to L386C, LAST        if Y was any positive
  18356.                                 ;;                      number.
  18357.  
  18358. ; else force division by zero thereby raising an Arithmetic overflow error.
  18359. ; There are some one and two-byte alternatives but perhaps the most formal
  18360. ; might have been to use end-calc; rst 08; DB 05.
  18361.  
  18362.         DB    $A1             ;;stk-one               0, 1.
  18363.         DB    $01             ;;exchange              1, 0.
  18364.         DB    $05             ;;division              1/0        ouch!
  18365.  
  18366. ; ---
  18367.  
  18368. ;; ONE
  18369. L386A:  DB    $02             ;;delete                .
  18370.         DB    $A1             ;;stk-one               1.
  18371.  
  18372. ;; LAST
  18373. L386C:  DB    $38             ;;end-calc              last value is 1 or 0.
  18374.  
  18375.         RET                     ; return.               Whew!
  18376.  
  18377. ;*********************************
  18378. ;** Spectrum 128 Patch Routines **
  18379. ;*********************************
  18380.  
  18381. ; The new code added to the standard 48K Spectrum ROM is mainly devoted to the scanning and decoding of the keypad.
  18382. ; These routines occupy addresses 386E through to 3B3A. Addresses 3B3B through to 3C96 contain a variety of routines for the following purposes: displaying the new tokens 'PLAY' and 'SPECTRUM',
  18383. ; dealing with the keypad when using INKEY$, handling new 128 BASIC error messages, and producing the TV tuner display. Addresses 3BE1 to 3BFE and addresses 3C97 to 3CFF are unused and all contain 00.
  18384. ; Documented by Paul Farrow.
  18385.  
  18386. ; --------------------------------
  18387. ; SCAN THE KEYPAD AND THE KEYBOARD
  18388. ; --------------------------------
  18389. ; This patch will attempt to scan the keypad if in 128K mode and will then scan the keyboard.
  18390.  
  18391. ;; KEYS
  18392. L386E:  PUSH    IX
  18393.         BIT     4,(IY+$01)      ; [FLAGS] Test if in 128K mode
  18394.         JR      Z,L3879         ; Z=in 48K mode
  18395.  
  18396.         CALL    L3A42           ; Attempt to scan the keypad
  18397.  
  18398. ;; KEYS_CONT
  18399. L3879:  CALL    L02BF           ; Scan the keyboard
  18400.         POP     IX
  18401.         RET
  18402.  
  18403. ; ----------------------------------
  18404. ; READ THE STATE OF THE OUTPUT LINES
  18405. ; ----------------------------------
  18406. ; This routine returns the state of the four output lines (bits 0-3) in the lower four bits of L. The LSB of L corresponds to the output communication line to the keypad.
  18407. ; In this way the state of the other three outputs are maintained when the state of the LSB of L is changed and sent out to register 14 of the AY-3-8912.
  18408.  
  18409. ;; READ_OUTPUTS
  18410. L387F:  LD      C,$FD           ; FFFD = Address of the
  18411.         LD      D,$FF           ; command register (register 7)
  18412.         LD      E,$BF           ; BFFD = Address of the
  18413.         LD      B,D             ; data register (register 14)
  18414.         LD      A,$07
  18415.         OUT     (C),A           ; Select command register
  18416.         IN      H,(C)           ; Read its status
  18417.         LD      A,$0E
  18418.         OUT     (C),A           ; Select data register
  18419.         IN      A,(C)           ; Read its status
  18420.         OR      $F0             ; Mask off the input lines
  18421.         LD      L,A             ; L=state of output lines at the
  18422.         RET                     ; keypad socket
  18423.  
  18424. ; --------------------------
  18425. ; SET THE OUTPUT LINE, BIT 0
  18426. ; --------------------------
  18427. ; The output line to the keypad is set via the LSB of L.
  18428.  
  18429. ;; SET_REG14
  18430. L3896:  LD      B,D
  18431.         LD      A,$0E
  18432.         OUT     (C),A           ; Select the data register
  18433.         LD      B,E
  18434.         OUT     (C),L           ; Send L out to the data register
  18435.         RET                     ; Set the output line
  18436.  
  18437. ; ----------------------------------------
  18438. ; FETCH THE STATE OF THE INPUT LINE, BIT 5
  18439. ; ----------------------------------------
  18440. ; Return the state of the input line from the keypad in bit 5 of A.
  18441.  
  18442. ;; GET_REG14
  18443. L389F:  LD      B,D
  18444.         LD      A,$0E
  18445.         OUT     (C),A           ; Select the data register
  18446.         IN      A,(C)           ; Read the input line
  18447.         RET
  18448.  
  18449. ; ------------------------------
  18450. ; SET THE OUTPUT LINE LOW, BIT 0
  18451. ; ------------------------------
  18452.  
  18453. ;; RESET_LINE
  18454. L38A7:  LD      A,L
  18455.         AND     $FE             ; Reset bit 0 of L
  18456.         LD      L,A
  18457.         JR      L3896           ; Send out L to the data register
  18458.  
  18459. ; -------------------------------
  18460. ; SET THE OUTPUT LINE HIGH, BIT 0
  18461. ; -------------------------------
  18462.  
  18463. ;; SET_LINE
  18464. L38AD:  LD      A,L
  18465.         OR      $01             ; Set bit 0 of L
  18466.         LD      L,A
  18467.         JR      L3896           ; Send out L to the data register
  18468.  
  18469. ; -------------------
  18470. ; MINOR DELAY ROUTINE
  18471. ; -------------------
  18472. ; Delay for (B*13)+5 T-States.
  18473.  
  18474. ;; DELAY
  18475. L38B3:  DJNZ    L38B3
  18476.         RET
  18477.  
  18478. ; -------------------
  18479. ; MAJOR DELAY ROUTINE
  18480. ; -------------------
  18481. ; Delay for (B*271)+5 T-states.
  18482.  
  18483. ;; DELAY2
  18484. L38B6:  PUSH    BC
  18485.         LD      B,$10
  18486.         CALL    L38B3           ; Inner delay of 135 T-States
  18487.         POP     BC
  18488.         DJNZ    L38B6
  18489.         RET
  18490.  
  18491. ; ------------------------------------
  18492. ; MONITOR FOR THE INPUT LINE TO GO LOW
  18493. ; ------------------------------------
  18494. ; Monitor the input line, bit 5, for up to (B*108)+5 T-states.
  18495.  
  18496. ;; MON_B5_LO
  18497. L38C0:  PUSH    BC
  18498.         CALL    L389F           ; Read the state of the input line
  18499.         POP     BC
  18500.         AND     $20             ; Test bit 5, the input line
  18501.         JR      Z,L38CB         ; Exit if input line found low
  18502.         DJNZ    L38C0           ; Repeat until timeout expires
  18503.  
  18504. ;; EXT_MON_LO
  18505. L38CB:  RET
  18506.  
  18507. ; -------------------------------------
  18508. ; MONITOR FOR THE INPUT LINE TO GO HIGH
  18509. ; -------------------------------------
  18510. ; Monitor the input line, bit 5, for up to (B*108)+5 T-states.
  18511.  
  18512. ;; MON_B5_HI
  18513. L38CC:  PUSH    BC
  18514.         CALL    L389F           ; Read the state of the input line
  18515.         POP     BC
  18516.         AND     $20             ; Test bit 5, the input line
  18517.         JR      NZ,L38D7        ; Exit if input line found low
  18518.         DJNZ    L38CC           ; Repeat until timeout expires
  18519.  
  18520. ;; EXT_MON_HI
  18521. L38D7:  RET
  18522.  
  18523. ; -------------------------
  18524. ; READ KEY PRESS STATUS BIT
  18525. ; -------------------------
  18526. ; This entry point is used to read in the status bit for a keypad row. If a key is being pressed in the current row then the bit read in will be a 1.
  18527.  
  18528. ;; READ_STATUS
  18529. L38D8:  CALL    L387F           ; Read the output lines
  18530.         LD      B,$01           ; Read in one bit
  18531.         JR      L38E4
  18532.  
  18533. ; ----------------
  18534. ; READ IN A NIBBLE
  18535. ; ----------------
  18536. ; This entry point is used to read in a nibble of data from the keypad. It is used for two functions. The first is to read in the poll nibble and the second is to read in a row of key press data.
  18537. ; For a nibble of key press data, a bit read in as 1 indicates that the corresponding key was pressed.
  18538.  
  18539. ;; READ_NIBBLE
  18540. L38DF:  CALL    L387F           ; Read the state of the output lines
  18541.         LD      B,$04           ; Read in four bits
  18542.  
  18543. ;; READ_BIT
  18544. L38E4:  PUSH    BC
  18545.         CALL    L389F           ; Read the input line from the keypad
  18546.         POP     BC
  18547.         AND     $20             ; This line should initially be high
  18548.         JR      Z,L392D         ; Z=read in a 0, there must be an error
  18549.  
  18550.         XOR     A               ; The bits read in will be stored in register A
  18551.  
  18552. ;; BIT_LOOP
  18553. L38EE:  PUSH    BC              ; Preserve the loop count and any bits
  18554.         PUSH    AF              ; read in so far
  18555.         CALL    L38AD           ; Set the output line high
  18556.  
  18557.         LD      B,$A3           ; Monitor for 17609 T-states for the
  18558.         CALL    L38C0           ; input line to go low
  18559.         JR      NZ,L392B        ; NZ=the line did not go low
  18560.  
  18561.         CALL    L38A7           ; Set the output line low
  18562.         JR      L3901           ; Insert a delay of 12 T-states
  18563.  
  18564. L38FF:  DB    $FF, $FF
  18565.  
  18566. ;; BL_CONTINUE
  18567. L3901:  LD      B,$2B           ; Delay for 564 T-states
  18568.         CALL    L38B3
  18569.         CALL    L389F           ; Read in the bit value
  18570.         BIT     5,A
  18571.         JR      Z,L3911         ; Z=read in a 0
  18572.  
  18573.         POP     AF              ; Retrieve read in bits
  18574.         SCF                     ; Set carry bit
  18575.         JR      L3914
  18576.  
  18577. ;; BL_READ_0
  18578. L3911:  POP     AF              ; Retrieve read in bits
  18579.         SCF
  18580.         CCF                     ; Clear carry bit
  18581.  
  18582. ;; BL_STORE
  18583. L3914:  RRA                     ; Shift the carry bit into bit 0 of A
  18584.         PUSH    AF              ; Save bits read in
  18585.         CALL    L38AD           ; Set the output line high
  18586.  
  18587.         LD      B,$26           ; Delay for 499 T-states
  18588.         CALL    L38B3
  18589.  
  18590.         CALL    L38A7           ; Set the output line low
  18591.  
  18592.         LD      B,$23           ; Delay for 460 T-states
  18593.         CALL    L38B3
  18594.  
  18595.         POP     AF              ; Retrieve read in bits
  18596.         POP     BC              ; Retrieve loop counter and repeat
  18597.         DJNZ    L38EE           ; for all bits to read in
  18598.         RET
  18599.  
  18600. ; ----------
  18601. ; LINE ERROR
  18602. ; ----------
  18603. ; The input line was found at the wrong level. The output line is now set high which will eventually cause the keypad to abandon its transmissions.
  18604. ; The upper nibble of system variable FLAGS/ROW3 will be cleared to indicate that communications to the keypad is no longer in progress.
  18605.  
  18606. ;; LINE_ERROR
  18607. L392B:  POP     AF
  18608.         POP     BC              ; Clear the stack
  18609.  
  18610. ;; LINE_ERROR2
  18611. L392D:  CALL    L38AD           ; Set the output line high
  18612.  
  18613.         XOR     A               ; Clear FLAGS nibble
  18614.         LD      ($5B88),A       ; [FLAGS/ROW3]
  18615.  
  18616.         INC     A               ; Return zero flag reset
  18617.         SCF
  18618.         CCF                     ; Return carry flag reset
  18619.         RET
  18620.  
  18621. ; ---------------
  18622. ; POLL THE KEYPAD
  18623. ; ---------------
  18624. ; The Spectrum 128 polls the keypad by changing the state of the output line and monitoring for responses from the keypad on the input line.
  18625. ; Before a poll occurs, the poll counter must be decremented until it reaches zero. This counter causes a delay of three seconds before a communications attempt to the keypad is made.
  18626. ; The routine can exit at five different places and it is the state of the A register, the zero flag and the carry flag which indicates the cause of the exit. This is summarised below:
  18627. ;
  18628. ; A Register    Zero Flag       Carry Flag    Cause
  18629. ; 0             set             set           Communications already established
  18630. ; 0             set             reset         Nibble read in OK
  18631. ; 1             reset           reset         Nibble read in with an error or i/p line initially low
  18632. ; 1             reset           set           Poll counter has not yet reached zero
  18633. ;
  18634. ; The third bit of the nibble read in must be set for the poll to be subsequently accepted.
  18635.  
  18636. ;; ATTEMPT_POLL
  18637. L3938:  CALL    L387F           ; Read the output line states
  18638.  
  18639.         LD      A,($5B88)       ; [FLAGS/ROW3] Has communications already been
  18640.         AND     $80             ; established with the keypad?
  18641.         JR      NZ,L3999        ; NZ=yes, so skip the poll
  18642.  
  18643.         CALL    L389F           ; Read the input line
  18644.         AND     $20             ; It should be high initially
  18645.         JR      Z,L392D         ; Z=error, input line found low
  18646.  
  18647.         LD      A,($5B88)       ; [FLAGS/ROW3] Test if poll counter already zero thus
  18648.         AND     A               ; indicating a previous comms error
  18649.         JR      NZ,L395A        ; NZ=ready to poll the keypad
  18650.  
  18651.         INC     A               ; Indicate comms not established
  18652.         LD      ($5B88),A       ; [FLAGS/ROW3]
  18653.         LD      A,$4C           ; Reset the poll counter
  18654.         LD      ($5B89),A       ; [ROW2/ROW1]
  18655.         JR      L399C           ; Exit the routine
  18656.  
  18657. ;;POLL_KEYPAD
  18658. L395A:  LD      A,($5B89)       ; [ROW2/ROW1] Decrement the poll counter
  18659.         DEC     A
  18660.         LD      ($5B89),A       ; [ROW2/ROW1]
  18661.         JR      NZ,L399C        ; Exit the routine if it is not yet zero
  18662.  
  18663. ; The poll counter has reached zero so a poll of the keypad can now occur.
  18664.  
  18665.         XOR     A
  18666.         LD      ($5B88),A       ; [FLAGS/ROW3] Indicate that a poll can occur
  18667.         LD      ($5B89),A       ; [ROW2/ROW1]
  18668.         LD      ($5B8A),A       ; [ROW4/ROW5] Clear all the row nibble stores
  18669.  
  18670.         CALL    L38A7           ; Set the output line low
  18671.  
  18672.         LD      B,$21           ; Wait up to 3569 T-States for the
  18673.         CALL    L38C0           ; input line to go low
  18674.         JR      NZ,L392D        ; NZ=line did not go low
  18675.  
  18676.         CALL    L38AD           ; Set the output line high
  18677.  
  18678.         LD      B,$24           ; Wait up to 3893 T-States for the
  18679.         CALL    L38CC           ; input line to go high
  18680.         JR      Z,L392D         ; NZ=line did not go high
  18681.  
  18682.         CALL    L38A7           ; Set the output line low
  18683.  
  18684.         LD      B,$0F
  18685.         CALL    L38B6           ; Delay for 4070 T-States
  18686.         CALL    L38DF           ; Read in a nibble of data
  18687.         JR      NZ,L392D        ; NZ=error occurred when reading in nibble
  18688.  
  18689.         SET     7,A             ; Set bit 7
  18690.         AND     $F0             ; Keep only the upper four bits
  18691.                                 ; (Bit 6 will be set if poll successful)
  18692.         LD      ($5B88),A       ; [FLAGS/ROW3] Store the flags nibble
  18693.         XOR     A
  18694.         SRL     A               ; Exit: Zero flag set, Carry flag reset
  18695.         RET
  18696.  
  18697. ;; AP_SKIP_POLL
  18698. L3999:  XOR     A               ; Communications already established
  18699.         SCF                     ; Exit: Zero flag set, Carry flag set
  18700.         RET
  18701.  
  18702. ;; PK_EXIT
  18703. L399C:  XOR     A               ; Poll counter not zero
  18704.         INC     A
  18705.         SCF                     ; Exit: Zero flag reset, Carry flag set
  18706.         RET
  18707.  
  18708. ; -----------------------
  18709. ; SCAN THE KEYPAD ROUTINE
  18710. ; -----------------------
  18711. ; If a successful poll of the keypad occurs then the five rows of keys are read in and a unique key code generated.
  18712.  
  18713. ;; KEYPAD_SCAN
  18714. L39A0:  CALL    L3938           ; Try to poll the keypad
  18715.  
  18716.         LD      A,($5B88)       ; [FLAGS/ROW3] Test the flags nibble
  18717.         CPL
  18718.         AND     $C0             ; Bits 6 and 7 must be set in FLAGS
  18719.         RET     NZ              ; NZ=poll was not successful
  18720.  
  18721. ; The poll was successful so now read in data for the five keypad rows.
  18722.  
  18723.         LD      IX,$5B8A        ; [ROW4/ROW5]
  18724.         LD      B,$05           ; The five rows
  18725.  
  18726. ;; KS_LOOP
  18727. L39B0:  PUSH    BC              ; Save counter
  18728.  
  18729.         CALL    L38D8           ; Read the key press status bit
  18730.         JP      NZ,L3A3A        ; NZ=error occurred
  18731.  
  18732.         BIT     7,A             ; Test the bit read in
  18733.         JR      Z,L39DC         ; Z=no key pressed in this row
  18734.  
  18735.         CALL    L38DF           ; Read in the row's nibble of data
  18736.         JR      NZ,L3A3A        ; NZ=error occurred
  18737.  
  18738.         POP     BC              ; Fetch the nibble loop counter
  18739.         PUSH    BC
  18740.         LD      C,A             ; Move the nibble read in to C
  18741.         LD      A,(IX+$00)      ; Fetch the nibble store
  18742.         BIT     0,B             ; Test if an upper or lower nibble
  18743.         JR      Z,L39D6         ; Z=upper nibble
  18744.  
  18745.         SRL     C               ; Shift the nibble to the lower position
  18746.         SRL     C
  18747.         SRL     C
  18748.         SRL     C
  18749.         AND     $F0             ; Mask off the lower nibble of the
  18750.         JR      L39D8           ; nibble store
  18751.  
  18752. ;; KS_UPPER
  18753. L39D6:  AND     $0F             ; Mask off the upper nibble of the nibble store
  18754.  
  18755. ;; KS_STORE
  18756. L39D8:  OR      C               ; Combine the existing and new
  18757.         LD      (IX+$00),A      ; nibbles and store them
  18758.  
  18759. ;; KS_NEXT
  18760. L39DC:  POP     BC              ; Retrieve the row counter
  18761.         BIT     0,B             ; Test if next nibble store is required
  18762.         JR      NZ,L39E3        ; NZ=use same nibble store
  18763.  
  18764.         DEC     IX              ; Point to the next nibble store
  18765.  
  18766. ;; KS_NEW
  18767. L39E3:  DJNZ    L39B0           ; Repeat for the next keypad row
  18768.  
  18769. ; All five rows have now been read so compose a unique code for the key pressed.
  18770.  
  18771.         LD      E,$80           ; Signal no key press found yet
  18772.         LD      IX,$5B88        ; [FLAGS/ROW3]
  18773.         LD      HL,$3A3F        ; Point to the key mask data
  18774.         LD      B,$03           ; Scan three nibbles
  18775.  
  18776. ;; GEN_LOOP
  18777. L39F0:  LD      A,(IX+$00)      ; Fetch a pair of nibbles
  18778.         AND     (HL)            ; This will mask off the FLAGS nibble and the SHIFT/0 key
  18779.  
  18780.         JR      Z,L3A17         ; Z=no key pressed in these nibbles
  18781.  
  18782.         BIT     7,E             ; Test if a key has already been found
  18783.         JR      Z,L3A3C         ; Z=multiple keys pressed
  18784.  
  18785.         PUSH    BC              ; Save the loop counter
  18786.         PUSH    AF              ; Save the byte of key bit data
  18787.         LD      A,B             ; Move loop counter to A
  18788.         JR      L3A01           ; A delay of 12 T-States
  18789.  
  18790. L39FF:  DB    $FF, $FF        ; Unused locations
  18791.  
  18792. ;; GEN_CONT
  18793. L3A01:  DEC     A               ; These lines of code generate base
  18794.         SLA     A               ; values of 7, 15 and 23 for the three
  18795.         SLA     A               ; nibble stores 5B88, 5B89 & 5B8A.
  18796.         SLA     A
  18797.         OR      $07
  18798.         LD      B,A             ; B=(loop counter-1)*8+7
  18799.         POP     AF              ; Fetch the byte of key press data
  18800.  
  18801. ;; GEN_BIT
  18802. L3A0C:  SLA     A               ; Shift until a set key bit drops into the
  18803.         JP      C,L3A13         ; carry flag
  18804.  
  18805.         DJNZ    L3A0C           ; Decrement B for each 'unsuccessful' shift of the A register
  18806.  
  18807. ;; GEN_FOUND
  18808. L3A13:  LD      E,B             ; E=a unique number for the key pressed, between 1 - 19 except 2 & 3
  18809.  
  18810.         POP     BC              ; As a result shifting the set key bit
  18811.                                 ; into the carry flag, the A register will
  18812.                                 ; hold 00 if only one key was pressed
  18813.         JR      NZ,L3A3C        ; NZ=multiple keys pressed
  18814.  
  18815. ;; GEN_NEXT
  18816. L3A17:  INC     IX              ; Point to the next nibble store
  18817.         INC     HL              ; Point to the corresponding mask data
  18818.         DJNZ    L39F0           ; Repeat for all three 'nibble' bytes
  18819.  
  18820.         BIT     7,E             ; Test if any keys were pressed
  18821.         JR      NZ,L3A27        ; NZ=no keys were pressed
  18822.  
  18823.         LD      A,E             ; Copy the key code
  18824.         AND     $FC             ; Test for the '.' key (E=1)
  18825.         JR      Z,L3A27         ; Z='.' key pressed
  18826.  
  18827.         DEC     E
  18828.         DEC     E               ; Key code in range 2 - 17
  18829.  
  18830. ; The E register now holds a unique key code value between 1 and 17.
  18831.  
  18832. ;; GEN_POINT
  18833. L3A27:  LD      A,($5B8A)       ; [ROW4/ROW5] Test if the SHIFT key was pressed
  18834.         AND     $08
  18835.         JR      Z,L3A34         ; Z=the SHIFT key was not pressed
  18836.  
  18837. ; The SHIFT key was pressed or no key was pressed.
  18838.  
  18839.         LD      A,E             ; Fetch the key code
  18840.         AND     $7F             ; Mask off 'no key pressed' bit
  18841.         ADD     A,$12           ; Add on a shift offset of 12
  18842.         LD      E,A
  18843.  
  18844. ; Add a base offset of 5A to all key codes. Note that no key press will result in a key code of DA. This is the only code with bit 7 set and so will be detected later.
  18845.  
  18846. ;; GEN_NOSHIFT
  18847. L3A34:  LD      A,E
  18848.         ADD     A,$5A           ; Add a base offset of 5A
  18849.         LD      E,A             ; Return key codes in range 5B - 7D
  18850.         XOR     A
  18851.         RET                     ; Exit: Zero flag set, key found OK
  18852.  
  18853. ; These two lines belong with the loop above to read in the five keypad rows and are jumped to when an error occurs during reading in a nibble of data.
  18854.  
  18855. ;; KS_ERROR
  18856. L3A3A:  POP     BC              ; Clear the stack and exit
  18857.         RET                     ; Exit: Zero flag reset
  18858.  
  18859. ;; GEN_INVALID
  18860. L3A3C:  XOR     A               ; Exit: Zero flag reset indicating an
  18861.         INC     A               ; invalid key press
  18862.         RET
  18863.  
  18864. ; ----------------
  18865. ; KEYPAD MASK DATA
  18866. ; ----------------
  18867.  
  18868. ;; KEY_MASKS
  18869. L3A3F:  DB    $0F, $FF, $F2   ; Key mask data
  18870.  
  18871. ; ---------------
  18872. ; READ THE KEYPAD
  18873. ; ---------------
  18874. ; This routine reads the keypad and handles key repeat and decoding. The bulk of the key repeat code is very similar to that used in the equivalent keyboard routine and works are follows.
  18875. ; A double system of KSTATE system variables (KSTATE0 - KSTATE3 and KSTATE4 - KSTATE7) is used to allow the detection of one key while in the repeat period of the previous key.
  18876. ; In this way, a 'spike' from another key will not stop the previous key from repeating. For a new key to be acknowledged, it must be held down for at least 1/5th of a second, i.e. ten calls to KEYPAD.
  18877. ; The KSTATE system variables store the following data:
  18878. ;
  18879. ;       KSTATE0/4       Un-decoded Key Value (00-27 for keyboard, 5B-7D for keypad, FF for no key)
  18880. ;       KSTATE1/5       10 Call Counter
  18881. ;       KSTATE2/6       Repeat Delay
  18882. ;       KSTATE3/7       Decoded Key Value
  18883. ;
  18884. ; The code returned is then stored in system variable LAST_K (5C08) and a new key signalled by setting bit 5 of FLAGS (5C3B).
  18885. ;
  18886. ; If the Spectrum 128 were to operate identically to the standard 48K Spectrum when in 48K mode, it would have to spend zero time in reading the keypad.
  18887. ; As this is not possible, the loading on the CPU is reduced by scanning the keypad upon every other interrupt. A '10 Call Counter' is then used to ensure that a key is held down for at least 1/5th of a second
  18888. ; before it is registered. Note that this is twice as long as for keyboard key presses and so the keypad key repeat delay is halved.
  18889. ;
  18890. ; At every other interrupt the keypad scanning routine is skipped. The net result of the routine is simply to decrement both '10 Call Counters', if appropriate. By loading the E register with 80 ensures that
  18891. ; the call to KP_TEST will reject the key code and cause a return. A test for keyboard key codes prevents the Call Counter decrements affecting a keyboard key press. It would have been more efficient to execute
  18892. ; a return upon every other call to KEYPAD and then to have used a '5 Call Counter' just as the keyboard routine does.
  18893. ;
  18894. ; A side effect of both the keyboard and keypad using the same KSTATE system variables is that if a key is held down on the keypad and then a key is held down on the keyboard, both keys will be monitored and
  18895. ; repeated alternatively, but with a reduced repeat delay. This delay is between the keypad key repeat delay and the keyboard key repeat delay. This occurs because both the keypad and keyboard routines will
  18896. ; decrement the KSTATE system variable Call Counters. The keypad routine 'knows' of the existence of keyboard key codes but the reverse is not true.
  18897.  
  18898. ;; KEYPAD
  18899. L3A42:  LD      E,$80           ; Signal no key pressed
  18900.         LD      A,($5C78)       ; [FRAMES]
  18901.         AND     $01             ; Scan the keypad every other
  18902.         JR      NZ,L3A4F        ; interrupt
  18903.  
  18904.         CALL    L39A0
  18905.         RET     NZ              ; NZ=no valid key pressed
  18906.  
  18907. ;; KP_CHECK
  18908. L3A4F:  LD HL,$5C00             ; [KSTATE0] Test the first KSTATE variable
  18909.  
  18910. ;; KP_LOOP
  18911. L3A52:  BIT     7,(HL)          ; Is the set free?
  18912.         JR      NZ,L3A62        ; NZ=yes
  18913.  
  18914.         LD      A,(HL)          ; Fetch the un-decoded key value
  18915.         CP      $5B             ; Is it a keyboard code?
  18916.         JR      C,L3A62         ; C=yes, so do not decrement counter
  18917.  
  18918.         INC     HL
  18919.         DEC     (HL)            ; Decrement the 10 Call Counter
  18920.         DEC     HL
  18921.         JR      NZ,L3A62        ; If the counter reaches zero, then
  18922.                                 ; signal the set is free
  18923.         LD      (HL),$FF
  18924.  
  18925. ;; KP_CH_SET
  18926. L3A62:  LD      A,L             ; Jump back and test the second set if
  18927.         LD      HL,$5C04        ; [KSTATE4] not yet considered
  18928.         CP      L
  18929.         JR      NZ,L3A52
  18930.  
  18931.         CALL    L3AAE           ; Test for valid key combinations and
  18932.         RET     NZ              ; return if invalid
  18933.  
  18934.         LD      A,E             ; Test if the key in the first set is being
  18935.         LD      HL,$5C00        ; [KSTATE0] repeated
  18936.         CP      (HL)
  18937.         JR      Z,L3A9E         ; Jump if being repeated
  18938.  
  18939.         EX      DE,HL           ; Save the address of KSTATE0
  18940.         LD      HL,$5C04        ; [KSTATE4] Test if the key in the second set is
  18941.         CP      (HL)            ; being repeated
  18942.         JR      Z,L3A9E         ; Jump if being repeated
  18943.  
  18944. ; A new key will not be accepted unless one of the KSTATE sets is free.
  18945.  
  18946.         BIT     7,(HL)          ; Test if the second set is free
  18947.         JR      NZ,L3A83        ; Jump if set is free
  18948.  
  18949.         EX      DE,HL
  18950.         BIT     7,(HL)          ; Test if the first set is free
  18951.         RET     Z               ; Return if no set is free
  18952.  
  18953. ;; KP_NEW
  18954. L3A83:  LD      E,A             ; Pass the key code to the E register
  18955.         LD      (HL),A          ; and to KSTATE0/4
  18956.         INC     HL
  18957.         LD      (HL),$0A        ; Set the '10 Call Counter' to 10
  18958.         INC     HL
  18959.  
  18960.         LD      A,($5C09)       ; [REPDEL] Fetch the initial repeat delay
  18961.         SRL     A               ; Divide delay by two
  18962.         LD      (HL),A          ; Store the repeat delay
  18963.         INC     HL
  18964.  
  18965.         CALL    L3AD7           ; Decode the keypad key code
  18966.         LD      (HL),E          ; and store it in KSTATE3/7
  18967.  
  18968. ; This section is common for both new keys and repeated keys.
  18969.  
  18970. ;; KP_END
  18971. L3A94:  LD      A,E
  18972.         LD      ($5C08),A       ; [LAST_K] Store the key value in LAST_K
  18973.         LD      HL,$5C3B        ; FLAGS
  18974.         SET     5,(HL)          ; Signal a new key pressed
  18975.         RET
  18976.  
  18977. ; -------------------------
  18978. ; THE KEY REPEAT SUBROUTINE
  18979. ; -------------------------
  18980.  
  18981. ;; KP_REPEAT
  18982. L3A9E:  INC     HL
  18983.         LD      (HL),$0A        ; Reset the '10 Call Counter' to 10
  18984.         INC     HL
  18985.         DEC     (HL)            ; Decrement the repeat delay
  18986.         RET     NZ              ; Return if not zero
  18987.  
  18988.         LD      A,($5C0A)       ; [REPPER] The subsequent repeat delay is
  18989.         SRL     A               ; divided by two and stored
  18990.         LD      (HL),A
  18991.         INC     HL
  18992.         LD      E,(HL)          ; The key repeating is fetched
  18993.         JR      L3A94           ; and then returned in LAST_K
  18994.  
  18995. ; ----------------------------------------
  18996. ; THE TEST FOR A VALID KEY CODE SUBROUTINE
  18997. ; ----------------------------------------
  18998. ; The zero flag is returned set if the key code is valid. No key press, SHIFT only or invalid shifted key presses return the zero flag reset.
  18999.  
  19000. ;; KP_TEST
  19001. L3AAE:  LD      A,E
  19002.         LD      HL,$5B66        ; FLAGS3 Test if in BASIC or EDIT mode
  19003.         BIT     0,(HL)
  19004.         JR      Z,L3ABC         ; Z=EDIT mode
  19005.  
  19006. ; Test key codes when in BASIC/CALCULATOR mode
  19007.  
  19008.         CP      $6D             ; Test for shifted keys
  19009.         JR      NC,L3AD4        ; and signal an error if found
  19010.  
  19011. ;; KPT_OK
  19012. L3ABA:  XOR     A               ; Signal valid key code
  19013.         RET                     ; Exit: Zero flag set
  19014.  
  19015. ; Test key codes when in EDIT/MENU mode.
  19016.  
  19017. ;; KPT_EDIT
  19018. L3ABC:  CP      $80             ; Test for no key press
  19019.         JR      NC,L3AD4        ; NC=no key press
  19020.  
  19021.         CP      $6C             ; Test for SHIFT on its own
  19022.         JR      NZ,L3ABA        ; NZ=valid key code
  19023.  
  19024. L3AC4:  DB    $00, $00, $00   ; Delay for 64 T-States
  19025.         DB    $00, $00, $00
  19026.         DB    $00, $00, $00
  19027.         DB    $00, $00, $00
  19028.         DB    $00, $00, $00
  19029.         DB    $00
  19030.  
  19031. ;; KPT_INVALID
  19032. L3AD4:  XOR     A               ; Signal invalid key code
  19033.         INC     A
  19034.         RET                     ; Exit: Zero flag reset
  19035.  
  19036. ; ---------------------------
  19037. ; THE KEY DECODING SUBROUTINE
  19038. ; ---------------------------
  19039.  
  19040. ;; KP_DECODE
  19041. L3AD7:  PUSH    HL              ; Save the KSTATE pointer
  19042.         LD      A,E
  19043.         SUB     $5B             ; Reduce the key code range to
  19044.         LD      D,$00           ; 00 - 22 and transfer to DE
  19045.         LD      E,A
  19046.  
  19047.         LD      HL,$5B66        ; FLAGS3 Test if in EDIT or BASIC mode
  19048.         BIT     0,(HL)
  19049.         JR      Z,L3AEA         ; Z=EDIT/MENU mode
  19050.  
  19051. ; Use Table 1 when in CALCULATOR/BASIC mode.
  19052.  
  19053.         LD      HL,L3B13
  19054.         JR      L3B0F           ; Look up the key value
  19055.  
  19056. ; Deal with EDIT/MENU mode.
  19057.  
  19058. ;; KPD_EDIT
  19059. L3AEA:  LD      HL,L3B25        ; Use Table 4 for unshifted key
  19060.         CP      $11             ; presses
  19061.         JR      C,L3B0F
  19062.  
  19063. ; Deal with shifted keys in EDIT/MENU mode.
  19064.  
  19065. ; Use Table 3 with SHIFT 1 (delete to beginning of line), SHIFT 2 (delete to end of line), SHIFT 3 (SHIFT TOGGLE). Note that although SHIFT TOGGLE produces a unique valid code,
  19066. ; it actually performs no function when editing a BASIC program.
  19067.  
  19068.         LD      HL,L3B21
  19069.         CP      $15             ; Test for SHIFT 1
  19070.         JR      Z,L3B0F
  19071.  
  19072.         CP      $16             ; Test for SHIFT 2
  19073.         JR      Z,L3B0F
  19074.  
  19075.         JR      L3B01           ; Delay for 12 T-States
  19076.  
  19077. L3AFE:  DB    $00, $FF, $FF   ; Unused locations
  19078.  
  19079. ;; KPD_CONT
  19080. L3B01:  CP      $17             ; Test for SHIFT 3
  19081.         JR      Z,L3B0F
  19082.  
  19083. ; Use Table 2 with SHIFT 4 (delete to beginning of word) and SHIFT 5 (delete to end of word).
  19084.  
  19085.         LD      HL,L3B18
  19086.         CP      $21             ; Test for SHIFT 4 and above
  19087.         JR      NC,L3B0F
  19088.  
  19089. ;Use Table 1 for all other shifted key presses.
  19090.  
  19091.         LD      HL,L3B13
  19092.  
  19093. ;; KPD_EXIT
  19094. L3B0F:  ADD     HL,DE           ; Look up the key value
  19095.         LD      E,(HL)
  19096.         POP     HL              ; Retrieve the KSTATE address
  19097.         RET
  19098.  
  19099. ; --------------------------------
  19100. ; THE KEYPAD DECODE LOOK-UP TABLES
  19101. ; --------------------------------
  19102.  
  19103. ;; KPD_TABLE1
  19104. L3B13:  DB    $2E, $0D, $33   ; '.', ENTER, 3
  19105.         DB    $32, $31        ; 2, 1
  19106.  
  19107. ;; KPD_TABLE2
  19108. L3B18:  DB    $29, $28, $2A   ; ), (, *
  19109.         DB    $2F, $2D, $39   ; /, - , 9
  19110.         DB    $38, $37, $2B   ; 8, 7, +
  19111.  
  19112. ;; KPD_TABLE3
  19113. L3B21:  DB    $36, $35, $34   ; 6, 5, 4
  19114.         DB    $30             ; 0
  19115.  
  19116. ;; KPD_TABLE4
  19117. L3B25:  DB    $A5, $0D, $A6   ; Bottom, ENTER, Top
  19118.         DB    $A7, $A8, $A9   ; End of line, Start of line, TOGGLE
  19119.         DB    $AA, $0B, $0C   ; DEL right, Up, DEL
  19120.         DB    $07, $09, $0A   ; CMND, Right, Down
  19121.         DB    $08, $AC, $AD   ; Left, Down ten, Up ten
  19122.         DB    $AE, $AF        ; End word, Beginning of word
  19123.         DB    $B0, $B1, $B2   ; DEL to end of line, DEL to start of line, SHIFT TOGGLE
  19124.         DB    $B3, $B4        ; DEL to end of word, DEL to beginning of word
  19125.  
  19126. ; -----------------------------
  19127. ; PRINT NEW ERROR MESSAGE PATCH
  19128. ; -----------------------------
  19129.  
  19130. L3B3B:  BIT     4,(IY+$01)      ; FLAGS 3 - In 128K mode?
  19131.         JR      NZ,L3B46        ; NZ=128K mode
  19132.  
  19133. ; In 48K mode
  19134.  
  19135.         XOR     A               ; Replicate code from standard ROM that the patch over-wrote
  19136.         LD      DE,$1536
  19137.         RET    
  19138.  
  19139. ; In 128K mode
  19140.  
  19141. L3B46:  LD      HL,$010F        ; Vector table entry in Editor ROM -> JP $03A2
  19142.  
  19143. ; Return to Editor ROM at address in HL
  19144.  
  19145. L3B49:  EX      (SP),HL         ; Change the return address
  19146.         JP      $5B00           ; Page Editor ROM and return to the address on the stack
  19147.  
  19148. ; -------------------------------------
  19149. ; STATEMENT INTERPRETATION RETURN PATCH
  19150. ; -------------------------------------
  19151.  
  19152. L3B4D:  BIT     4,(IY+$01)      ; In 128K mode?
  19153.         JR      NZ,L3B58        ; NZ=128K mode
  19154.  
  19155. ; In 48K mode
  19156.  
  19157.         BIT     7,(IY+$0A)      ; replicate code from standard ROM that the patch over-wrote
  19158.         RET    
  19159.  
  19160. ; In 128K mode
  19161.  
  19162. L3B58:  LD      HL,$0112        ; Handle in Editor ROM by jumping to Vector table entry in Editor ROM -> JP #182A
  19163.         JR      L3B49
  19164.  
  19165. ; --------------------------
  19166. ; GO TO NEXT STATEMENT PATCH
  19167. ; --------------------------
  19168.  
  19169. L3B5D:  BIT     4,(IY+$01)      ; In 128K mode?
  19170.         JR      NZ,L3B67        ; NZ=128K mode
  19171.  
  19172. ; In 48K mode
  19173.  
  19174.         RST     18H             ; replicate code from standard ROM that the patch over-wrote
  19175.         CP      $0D
  19176.         RET    
  19177.  
  19178. ; In 128K mode
  19179.  
  19180. L3B67:  LD      HL,$0115        ; Handle in Editor ROM by jumping to Vector table entry in Editor ROM -> JP #18A8
  19181.         JR      L3B49
  19182.  
  19183. ; --------------------------------------
  19184. ; INKEY$ ROUTINE TO DEAL WITH THE KEYPAD
  19185. ; --------------------------------------
  19186.  
  19187. ;; KEYSCAN2
  19188. L3B6C:  CALL    L028E           ; KEYSCAN Scan the keyboard
  19189.         LD      C,$00
  19190.         JR      NZ,L3B80        ; NZ=multiple keys
  19191.  
  19192.         CALL    L031E           ; K_TEST
  19193.         JR      NC,L3B80        ; NC=shift only or no key
  19194.  
  19195.         DEC     D
  19196.         LD      E,A
  19197.         CALL    L0333           ; K_DECODE
  19198.         JP      L2657           ; S_CONT Get string and continue scanning
  19199.  
  19200. ;; KPI_SCAN
  19201. L3B80:  BIT     4,(IY+$01)      ; 128K mode?
  19202.         JP      Z,L2660         ; S_IK$_STK Z=no, stack keyboard code
  19203.  
  19204.         DI                      ; Disable interrupts whilst scanning
  19205.         CALL    L39A0           ; the keypad
  19206.         EI
  19207.         JR      NZ,L3B9A        ; NZ=multiple keys
  19208.  
  19209.         CALL    L3AAE           ; Test the keypad
  19210.         JR      NZ,L3B9A        ; NZ=no key, shift only or invalid combination
  19211.  
  19212.         CALL    L3AD7           ; Form the key code
  19213.         LD      A,E
  19214.         JP      L2657           ; S_CONT Get string and continue scanning
  19215.  
  19216. ;; KPI_INVALID
  19217. L3B9A:  LD      C,$00           ; Signal no key, i.e. length=0
  19218.         JP      L2660           ; S_IK$_STK
  19219.  
  19220. ; ---------------------
  19221. ; PRINT TOKEN/UDG PATCH
  19222. ; ---------------------
  19223.  
  19224. L3B9F:  CP      $A3             ; SPECTRUM (T)
  19225.         JR      Z,L3BAF
  19226.  
  19227.         CP      $A4             ; PLAY (U)
  19228.         JR      Z,L3BAF
  19229.  
  19230. ; In 48K mode here
  19231.  
  19232. L3BA7:  SUB     $A5             ; Check as per original ROM
  19233.         JP      NC,$0B5F
  19234.  
  19235.         JP      $0B56           ; Rejoin original ROM routine
  19236.  
  19237. L3BAF:  BIT     4,(IY+$01)      ; FLAGS3 - Bit 4=1 if in 128K mode
  19238.         JR      Z,L3BA7         ; Rejoin code for when in 48K mode
  19239.  
  19240. ; In 128K mode here
  19241.  
  19242.         LD      DE,L3BC9
  19243.         PUSH    DE              ; Stack return address
  19244.  
  19245.         SUB     $A3             ; Check whether the SPECTRUM token
  19246.  
  19247.         LD      DE,L3BD2        ; SPECTRUM token
  19248.         JR      Z,L3BC3
  19249.  
  19250.         LD      DE,L3BDA        ; PLAY token
  19251.  
  19252. L3BC3:  LD      A,$04           ; Signal not RND, INKEY$ or PI so that a trailing space is printed
  19253.         PUSH    AF
  19254.         JP      L0C17           ; Rejoin printing routine PO-TABLE+3
  19255.  
  19256. ; Return address from above
  19257.  
  19258. L3BC9:  SCF                     ; Return as if no trailing space
  19259.  
  19260.         BIT     1,(IY+$01)      ; Test if printer is in use
  19261.         RET     NZ              ; NZ=printer in use
  19262.  
  19263.         JP      $0B03           ; PO-FETCH - Return via Position Fetch routine
  19264.  
  19265. L3BD2           DC "SPECTRUM"   ;DEFM    "SPECTRU"       ; SPECTRUM token
  19266.                                 ;DB    'M'+$80
  19267.  
  19268. L3BDA           DC "PLAY"       ;DEFM    "PLA"           ; PLAY token
  19269.                                 ;DB    'Y'+$80
  19270.  
  19271. ;; KP_SCAN2
  19272. L3BDE:  JP      L3C01           ; This is not called from either ROM. It can be used to scan the keypad.
  19273.  
  19274. ;===============================
  19275. PRINTER_INITER  RST 8
  19276.                 DB _AY_PRN_INIT
  19277.                 RET
  19278.  
  19279. PRN_TOKEN       RST 8
  19280.                 DB _AY_PRN_TOKEN
  19281.                 RET
  19282.  
  19283.                 DUPL 0X3BFF-$,0
  19284.                 DW 0XFFFF
  19285. ;===============================
  19286.  
  19287. ;; KP_SCAN
  19288. L3C01:  JP      L39A0           ; This was to be called via the vector table in the EDITOR ROM but due to a programming error it never gets called.
  19289.  
  19290. ; -----------------------
  19291. ; TV TUNER VECTOR ENTRIES
  19292. ; -----------------------
  19293.  
  19294. L3C04:  JP      L3C10
  19295. L3C07:  JP      L3C10
  19296. L3C0A:  JP      L3C10
  19297. L3C0D:  JP      L3C10
  19298.  
  19299. ; ----------------
  19300. ; TV TUNER ROUTINE
  19301. ; ----------------
  19302. ; This routine generates a display showing all possible colours and emitting a continuous cycle of a 440Hz tone for 1 second followed by silence for 1 second.
  19303. ; Its purpose is to ease the tuning in of TV sets to the Spectrum 128's RF signal. The display consists of vertical stripes of width four character squares showing each of the eight colours
  19304. ; available at both their normal and bright intensities. The display begins with white on the left progressing up to black on the right. With in each colour stripe in the first eight rows is
  19305. ; shown the year '1986' in varying ink colours. This leads to a display that shows all possible ink colours on all possible paper colours.
  19306.  
  19307. ;; TV_TUNER
  19308. L3C10:  LD      A,$7F           ; Test for the BREAK key
  19309.         IN      A,($FE)
  19310.         RRA    
  19311.         RET     C               ; C=SPACE not pressed
  19312.  
  19313.         LD      A,$FE
  19314.         IN      A,($FE)
  19315.         RRA    
  19316.         RET     C               ; C=SPACE not pressed
  19317.  
  19318.         LD      A,$07
  19319.         OUT     ($FE),A         ; Set the border to white
  19320.  
  19321.         LD      A,$02           ; Open channel 2 (main screen)
  19322.         CALL    $1601
  19323.  
  19324.         XOR     A
  19325.         LD      ($5C3C),A       ; [TV_FLAG] Signal using main screen
  19326.  
  19327.         LD      A,$16           ; Print character 'AT'
  19328.         RST     10H
  19329.  
  19330.         XOR     A               ; Print character '0'
  19331.         RST     10H
  19332.  
  19333.         XOR     A               ; Print character '0'
  19334.         RST     10H
  19335.  
  19336.         LD      E,$08           ; Number of characters per colour
  19337.         LD      B,E             ; Paper counter + 1
  19338.         LD      D,B             ; Ink counter + 1
  19339.  
  19340. ;; TVT_ROW
  19341. L3C34:  LD      A,B             ; Calculate the paper colour
  19342.         DEC     A               ; Bits 3-5 of each screen attribute
  19343.                 DB 0XCB
  19344.                 RLA               ; holds the paper colour; bits 0-2
  19345.                 DB 0XCB
  19346.                 RLA               ; the ink colour
  19347.                 DB 0XCB
  19348.                 RLA
  19349.         ADD     A,D             ; Add the ink colour
  19350.         DEC     A
  19351.         LD      ($5C8F),A       ; [ATTR_T] Store as temporary attribute value
  19352.  
  19353.         LD      HL,L3C8F        ; TVT_DATA Point to the 'year' data
  19354.         LD      C,E             ; Get number of characters to print
  19355.  
  19356. ;; TVT_YEAR
  19357. L3C45:  LD      A,(HL)          ; Fetch a character from the data
  19358.         RST     10H             ; Print it
  19359.         INC     HL
  19360.         DEC     C
  19361.         JR      NZ,L3C45        ; Repeat for the 8 characters
  19362.  
  19363.         DJNZ    L3C34           ; Repeat for all colours in this row
  19364.  
  19365.         LD      B,E             ; Reset paper colour
  19366.         DEC     D               ; Next ink colour
  19367.         JR      NZ,L3C34        ; Produce next row with new ink colour
  19368.  
  19369.         LD      HL,$4800        ; Point to 2nd third of display file
  19370.         LD      D,H
  19371.         LD      E,L
  19372.         INC     DE              ; Point to the next display cell
  19373.         XOR     A
  19374.         LD      (HL),A          ; Clear first display cell
  19375.         LD      BC,$0FFF
  19376.         LDIR                    ; Clear lower 2 thirds of display file
  19377.  
  19378.         EX      DE,HL           ; HL points to start of attributes file
  19379.         LD      DE,$5900        ; Point to 2nd third of attributes file
  19380.         LD      BC,$0200
  19381.         LDIR                    ; Copy screen attributes
  19382.  
  19383. ; Now that the display has been constructed, produce a continuous cycle of a 440Hz tone for 1 second followed by a period of silence for 1 second (actually 962ms).
  19384.  
  19385.         DI                      ; Disable interrupts so that a pure tone can be generated
  19386.  
  19387. ;; TVT_TONE
  19388. L3C68:  LD      DE,$0370        ; DE=twice the tone frequency in Hz
  19389.         LD      L,$07           ; Border colour of white
  19390.  
  19391. ;; TVT_DURATION
  19392. L3C6D:  LD      BC,$0099        ; Delay for 950.4us
  19393.  
  19394. ;; TVT_PERIOD
  19395. L3C70:  DEC     BC
  19396.         LD      A,B
  19397.         OR      C
  19398.         JR      NZ,L3C70
  19399.  
  19400.         LD      A,L
  19401.         XOR     $10              ; Toggle the speaker output whilst
  19402.         LD      L,A              ; preserving the border colour
  19403.         OUT     ($FE),A
  19404.  
  19405.         DEC     DE               ; Generate the tone for 1 second
  19406.         LD      A,D
  19407.         OR      E
  19408.         JR      NZ,L3C6D
  19409.  
  19410. ; At this point the speaker is turned off, so delay for 1 second.
  19411.  
  19412.         LD      BC,$0000         ; Delay for 480.4us
  19413.  
  19414. ;; TVT_DELAY1
  19415. L3C83:  DEC     BC
  19416.         LD      A,B
  19417.         OR      C
  19418.         JR      NZ,L3C83
  19419.  
  19420. ;; TVT_DELAY2
  19421. L3C88:  DEC     BC               ; Delay for 480.4us
  19422.         LD      A,B
  19423.         OR      C
  19424.         JR      NZ,L3C88
  19425.  
  19426.         JR      L3C68            ; Repeat the tone cycle
  19427.  
  19428. ;; TVT_DATA
  19429. L3C8F:  DB    $13, $00         ; Bright, off
  19430.         DB    $31, $39         ; '1', '9'
  19431.         DB    $13, $01         ; Bright, on
  19432.         DB    $38, $36         ; '8', '6'
  19433.  
  19434. RST8_CMP        EX (SP),HL              ;HL
  19435.                 PUSH AF                 ;AF
  19436.                 LD A,(HL)
  19437.                 CP _AY_PRN_INIT
  19438.                 JR NC,RST8_YES
  19439. RST8_NO         POP AF
  19440.                 EX (SP),HL
  19441.                 LD HL,($5C5D)
  19442.                 LD ($5C5F),HL
  19443.                 JP L0053
  19444.  
  19445. RST8_YES        CP _AY_PRN_INIT+0X40
  19446.                 JR NC,RST8_NO
  19447.                 CP 0X73
  19448.                 JR NC,RST8_NO
  19449.                 PUSH BC                 ;BC
  19450.                 LD A,R
  19451.                 JP PE,RST8YES1
  19452.                 LD A,R
  19453. RST8YES1        DI
  19454.                 PUSH AF                 ;RF
  19455.                 PUSH HL                 ;ADR_RET
  19456.                 PUSH DE                 ;RAMNROM+DOS7FFD
  19457.                 LD BC,RD_1WINA0
  19458.                 IN H,(C)
  19459.                 IN A,(PEVO_CONF)
  19460.                 LD L,A
  19461.                 OR 1
  19462.                 OUT (PEVO_CONF),A
  19463.                 LD B,HIGH (RD_DOS7FFD)
  19464.                 IN E,(C)
  19465.                 DEC B
  19466.                 IN D,(C)
  19467.                 LD BC,WIN_A0
  19468.                 LD A,3
  19469.                 OUT (C),A
  19470.                 LD B,HIGH (WIN_P0)
  19471.                 XOR A
  19472.                 JP ADR_SEL_ROM
  19473.  
  19474.                 DUPL ADR_RST8END-$,0
  19475. RST8_END        LD A,L
  19476.                 OUT (PEVO_CONF),A
  19477.                 POP DE
  19478.                 POP HL
  19479.                 POP AF
  19480.                 JP PO,RST8END1
  19481.                 EI
  19482. RST8END1        POP BC
  19483.                 POP AF
  19484.                 EX (SP),HL
  19485.                 RET
  19486.  
  19487. ; ------
  19488. ; UNUSED
  19489. ; ------
  19490.  
  19491.                 DUPL 0X3D00-$,0
  19492.  
  19493. ; -------------------------------
  19494. ; THE 'ZX SPECTRUM CHARACTER SET'
  19495. ; -------------------------------
  19496.  
  19497. ;; char-set
  19498.  
  19499. ; $20 - Character: ' '          CHR$(32)
  19500.  
  19501. CHARS           binclude shr_3d00.bin
  19502.