stripped 7 bytes by reordering some code, and replacing several JPs with JRs
[bz80asm.git] / bzasm80.zas
blob7ec96e156b0da8748986077a5eabfaf6e723de9a
1 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2 ;; Z80 assembler, based on the code from BBC Basic for Z80
3 ;; original code was written by R.T.Russell
4 ;; the original license:
5 ;;
6 ;; Copyright (c) 1984-2000 R.T. Russell
7 ;;
8 ;; This software is provided 'as-is', without any express or implied
9 ;; warranty. In no event will the authors be held liable for any damages
10 ;; arising from the use of this software.
12 ;; Permission is granted to anyone to use this software for any purpose,
13 ;; including commercial applications, and to alter it and redistribute it
14 ;; freely, subject to the following restrictions:
16 ;; 1. The origin of this software must not be misrepresented; you must not
17 ;;    claim that you wrote the original software. If you use this software
18 ;;    in a product, an acknowledgment in the product documentation would be
19 ;;    appreciated but is not required.
20 ;; 2. Altered source versions must be plainly marked as such, and must not be
21 ;;    misrepresented as being the original software.
22 ;; 3. This notice may not be removed or altered from any source distribution.
24 ;; modifications, cleanups, etc. by Ketmar Dark // Invisible Vector
26 ; define this if you want ORG/ENT/DISP
27 IF !defined(BZ80ASM_ORGENTDISP)
28 BZ80ASM_ORGENTDISP equ 0
29 ENDIF
31   MODULE BZ80ASM
33 PC: defw #C000  ; logical program counter for the code
35 IF @BZ80ASM_ORGENTDISP
36 ; ORG/DISP sets this to its value
37 NEW_ORGENT: defw 0
38 ; ORG/ENT sets this to the corresponding type
39 ; it is reset at each call to ASSEM
40 ORGENT_NONE equ 0
41 ORGENT_ORG equ 1
42 ORGENT_DISP equ 2
43 ORGENT_ENT equ 3
44 ORGENT_TYPE: defw ORGENT_NONE
45 ENDIF
47 ; address of the routine that will be called if JR/DJNZ destination is too far away
48 ; you can simply RET from it if you want to ignore this error
49 ; note that stack is filled with garbage, so use `ASM_ERROR_EXIT` to bail out
50 ; this is not checked for zero, so if you will not init this, "CALL 0" will be executed
51 ; ret L to the byte that will be put on normal return
52 ASM_JR_TOO_FAR_CB: defw 0
54 ; on entry, ASSEM will store SP here
55 ; you can use this to reset the stack, and use RET to return to the caller
56 ; or simply use ASM_ERROR_EXIT (which will set carry too)
57 ASM_SP0: defw 0
59 ; ASSEM sets this if it hits mnemonics without a handler
60 ; you can add your own mnemonics to the assembler, and it
61 ; will set this to non-zero if it hits them
62 ; use this byte as decrementing counter, like this:
63 ;  jr    nc,no_error
64 ;  ld    a,(ASM_BAD_B)
65 ;  or    a
66 ;  jr    z,syntax_error
67 ;  ld    b,a
68 ;  djnz  not_first_one
69 ;    handle first instruction
70 ;  not_first_one:
71 ;  djnz  not_second_one
72 ;    handle second instruction
73 ;  ...and so on
74 ; ADDITIONALLY, this will be set to #FF on invalid token
75 ; this can be used to process labels (because otherwise
76 ; there is no way to tell if we got some bad operands, or
77 ; an unknown mnemonics)
78 ASM_BAD_B: defw 0
81 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
82 ;; expression parser variables
84 ;; set this to the address of error routine
85 ;; note that you cannot return from it, you HAVE to abort everything
86 ;; also note that machine stack is undefined, and SP should be set
87 ;; to some initial value
88 ;; "undefined" means that machine stack can contain alot of garbage,
89 ;; but will never be underflowed
91 ;; this function is called with error code in A
93 ;; you can load your own error code in A, and do:
94 ;;  jp  BZ80ASM.PARSE_EXPR_ERROR_A
95 EXPR_ERROR_CB: defw 0
97 ;; error codes
98 ;; expected number, but got something incomprehensible
99 EXPR_ERR_NUMBER_EXPECTED equ 1
100 ;; expected string, but got something incomprehensible
101 EXPR_ERR_STRING_EXPECTED equ 2
102 ;; expected ")", but got something strange
103 EXPR_ERR_RPAREN_EXPECTED equ 3
104 ;; expected ")", but got something strange
105 EXPR_ERR_DIVISION_BY_ZERO equ 4
107 ;; the asm never generates the following errors, but
108 ;; they may be useful for a main driver
110 ;; you can use this to dispatch "short jump destination is too far" error
111 ;; just do this in `ASM_JR_TOO_FAR_CB`:
112 ;;   ld  a,EXPR_ERR_JR_TOO_FAR
113 ;;   jp  BZ80ASM.PARSE_EXPR_ERROR_A
114 EXPR_ERR_JR_TOO_FAR equ 5
116 ;; this "unknown label" error can be used by label manager
117 EXPR_ERR_UNKNOWN_LABEL equ 6
118 ;; this error can be used by label manager if it cannot parse a label
119 EXPR_ERR_INVALID_LABEL_NAME equ 7
120 ;; this error can be used by label manager
121 EXPR_ERR_DUPLICATE_LABEL equ 8
123 ;; general "bad syntax" error, when you don't have anything better
124 EXPR_ERR_BAD_SYNTAX equ 9
126 ;; offset your own error codes with this
127 EXPR_ERR_USERDEF equ 10
130 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
131 ;; label manager callback
133 ;; find a label
134 ;; this is called from assembler to find an existing label.
135 ;; IY points to the first char of a label name.
136 ;; after parsing, IY should point right after the parsed name.
137 ;; all registers expect IY can be trashed (including IX).
139 ;; for forward referencing, label manager can create unknown
140 ;; labels, and set their value to (BZ80ASM.PC).
141 ;; it is important to set new labels to PC to avoid errors
142 ;; with short jumps if your "jr too far" error handler always
143 ;; bombs out. otherwise, you can set the label to anything
144 ;; you like.
146 ;; IN:
147 ;;   IY: text input buffer
148 ;; OUT:
149 ;;   IY: text input buffer after the label
150 ;;   HL: label value
151 ;;   CARRY FLAG: set if label wasn't found
152 ;;               expression parser will bomb out in this case
153 ;; on error, IY doesn't matter, because it will be restored
154 ;; by the calling code
155 GETLABEL_CB: defw 0
158 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
159 ; string terminator
160 CR equ 13
163 asmsizest = $
164 csizest = $
166 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
167 ;; ASSEMBLER:
168 ;; LANGUAGE-INDEPENDENT CONTROL SECTION:
169 ;;  Inputs:
170 ;;    IY: text buffer
171 ;;    IX: destination to put generated code at
172 ;;  Outputs:
173 ;;    A: delimiter
174 ;;    IY: delimiter position in text buffer
175 ;;    IX: points right after the generated code
176 ;;    carry set if syntax error (and A is undefined in this case)
177 ;;    others are dead (including extra register set and extra accum/flags)
179 ASSEM:
180   ; reset org/ent type
181   xor   a
182   IF @BZ80ASM_ORGENTDISP
183   ld    (ORGENT_TYPE),a
184   ENDIF
185   ld    (ASM_BAD_B),a
186   ld    (ASM_SP0),sp
187 ASSEM1:
188   call  SKIP
189   inc   iy
190   cp    ':'
191   jr    z,ASSEM1
192   ; this was used to terminate assembler section in BBC Basic
193   ;cp    ']'
194   ;ret   z
195   cp    CR
196   ret   z
197   dec   iy
198   push  ix
199   ;push  iy
200   call  ASMB
201   ;pop   bc
202   pop   de
203   ; exit if syntax error
204   ret   c
205   ; skip delimiters (but not terminators)
206   call  SKIP
207   ; exit with error flag if we're not at a terminator
208   scf
209   ret   nz
210   ; advance PC
211   push  ix
212   pop   hl
213   or    a
214   sbc   hl,de
215   ex    de,hl           ;DE= NO. OF BYTES
216   ld    hl,(PC)
217   add   hl,de
218   ld    (PC),hl         ;UPDATE PC
219   ; reset carry and Z
220   xor   a
221   ret
223 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
225 ;; jump here to restore stack, and exit with error (carry set)
227 ASM_ERROR_EXIT:
228   ld    sp,(ASM_SP0)
229   scf
230   ret
232 ASMB_BAD_MNEMO:
233   ld    a,255
234   ld    (ASM_BAD_B),a
235   ; carry is still set
236   ret
238 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
240 ;; PROCESSOR-SPECIFIC TRANSLATION SECTION:
242 ;; REGISTER USAGE: B - TYPE OF MOST RECENT OPERAND
243 ;;                 C - OPCODE BEING BUILT
244 ;;                 D - (IX) OR (IY) FLAG
245 ;;                 E - OFFSET FROM IX OR IY
246 ;;                HL - NUMERIC OPERAND VALUE
247 ;;                IX - CODE DESTINATION
248 ;;                IY - SOURCE TEXT POINTER
249 ;;    Inputs: A = initial character
250 ;;   Outputs: Carry set if syntax error.
252 ASMB:
253   call  SKIP
254   ret   z
255   ld    hl,OPCODS
256   call  FIND
257   ; carry flag set on error
258   jr    c,ASMB_BAD_MNEMO
259   ; A contains token index
260   ; B contains token data byte
261   ld    c,b     ;ROOT OPCODE
262   ld    d,0     ;CLEAR IX/IY FLAG
264   ; now:
265   ; A contains token index
266   ; C contains token data byte
267   ; D contains IX/IY flag
269 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
271 ;; GROUP 0 - TRIVIAL CASES REQUIRING NO COMPUTATION
272 ;; GROUP 1 - AS GROUP 0 BUT WITH "ED" PREFIX
274   sub   OPC_COUNT_GROUPS_0_AND_1
275   jr    nc,GROUP2
276   cp    OPC_COUNT_GROUP_0-OPC_COUNT_GROUPS_0_AND_1
277   call  nc,EDX
278   jr    BYTE0
280 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
282 ;; GROUP 2 - BIT, RES, SET
283 ;; GROUP 3 - RLC, RRC, RL, RR, SLA, SRA, SRL
285 GROUP2:
286   sub   OPC_COUNT_GROUPS_2_AND_3
287   jr    nc,GROUP4
288   cp    OPC_COUNT_GROUP_2-OPC_COUNT_GROUPS_2_AND_3
289   call  c,CBIT
290   ret   c
291   call  REGLO
292   ret   c
293   call  CBX
294   jr    BYTE0
296 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
298 ;; GROUP 4 - PUSH, POP, EX (SP)
300 GROUP4:
301   sub   OPC_COUNT_GROUP_4
302   jr    nc,GROUP5
304   call  PAIR
305   ret   c
306   jr    BYTE0
308 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
310 ;; GROUP 5 - SUB, AND, XOR, OR, CP
311 ;; GROUP 6 - ADD, ADC, SBC
313 GROUP5:
314   sub   OPC_COUNT_GROUPS_5_AND_6
315   jr    nc,GROUP7
316   cp    OPC_COUNT_GROUP_5-OPC_COUNT_GROUPS_5_AND_6
317   ld    b,7
318   call  nc,OPND
319   ld    a,b
320   cp    7
321   jr    nz,G6HL
323   call  REGLO
324   ld    a,c
325   jr    nc,BIND1
326   xor   46H
327   call  BIND
328 DBX:
329   call  NUMBER
330   jr    VAL8
332 G6HL:
333   and   3FH
334   cp    12
335   scf
336   ret   nz
337   ld    a,c
338   cp    80H
339   ld    c,9
340   jr    z,G4
341   xor   1CH
342   rrca
343   ld    c,a
344   call  EDX
345   jr    G4
347 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
349 ;; GROUP 7 - INC, DEC
351 GROUP7:
352   sub   OPC_COUNT_GROUP_7
353   jr    nc,GROUP8
354   call  REGHI
355   ld    a,c
356 BIND1:
357   jp    nc,BIND
358   xor   64H
359   rlca
360   rlca
361   rlca
362   ld    c,a
363   call  PAIR1
364   ret   c
365 BYTE0:
366   ld    a,c
367   jr    BYTE2
369 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
371 ;; GROUP 8 - IN
372 ;; GROUP 9 - OUT
374 GROUP8:
375   sub   OPC_COUNT_GROUPS_8_AND_9
376   jr    nc,GROUPA
377   cp    OPC_COUNT_GROUP_8-OPC_COUNT_GROUPS_8_AND_9
378   call  z,CORN
379   ex    af,af'
380   call  REGHI
381   ret   c
382   ex    af,af'
383   call  c,CORN
384   inc   h
385   jr    z,BYTE0
386   ld    a,b
387   cp    7
388   scf
389   ret   nz
390   ld    a,c
391   xor   3
392   rlca
393   rlca
394   rlca
395   call  BYTE
396   jr    VAL8
398 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
400 ;; GROUP 10 - JR, DJNZ
402 GROUPA:
403   sub   OPC_COUNT_GROUP_10
404   jr    nc,GROUPB
405   cp    OPC_COUNT_GROUP_10_JRS-OPC_COUNT_GROUP_10
406   call  nz,COND
407   ld    a,c
408   jr    nc,GRPA
409   ld    a,18H
410 GRPA:
411   call  BYTE
412   call  NUMBER
413   ld    de,(PC)
414   inc   de
415   scf
416   sbc   hl,de
417   ld    a,l
418   rla
419   sbc   a,a
420   cp    h
421 TOOFAR:
422   call  nz,JR_TOO_FAR
423 VAL8:
424   ld    a,l
425   jr    BYTE2
427 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
429 ;; GROUP 11 - JP
431 GROUPB:
432   ld    b,a
433   jr    nz,GROUPC
434   call  COND
435   ld    a,c
436   jr    nc,GRPB
437   ld    a,b
438   and   3FH
439   cp    6
440   ld    a,0E9H
441   jr    z,BYTE2
442   ld    a,0C3H
443 GRPB:
444   call  BYTE
445   jr    ADDR
447 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
449 ;; GROUP 12 - CALL
451 GROUPC:
452   djnz  GROUPD
453 GRPC:
454   call  GRPE
455 ADDR:
456   call  NUMBER
457 VAL16:
458   call  VAL8
459   ld    a,h
460   jr    BYTE2
462 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
464 ;; GROUP 13 - RST
466 GROUPD:
467   djnz  GROUPE
468   call  NUMBER
469   and   c
470   or    h
471   jr    nz,TOOFAR
472   ld    a,l
473   or    c
474 BYTE2:
475   jr    BYTE1
477 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
479 ;; GROUP 14 - RET
481 GROUPE:
482   djnz  GROUPF
483 GRPE:
484   call  COND
485   ld    a,c
486   jr    nc,BYTE1
487   or    9
488   jr    BYTE1
490 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
492 ;; GROUP 15 - LD
494 GROUPF:
495   djnz  MISC
496   call  LDOP
497   jr    nc,LDA
498   call  REGHI
499   ex    af,af'
500   call  SKIP
501   cp    '('
502   jr    z,LDIN
503   ex    af,af'
504   jp    nc,G6
505   ld    c,1
506   call  PAIR1
507   ret   c
508   ld    a,14
509   cp    b
510   ld    b,a
511   call  z,PAIR
512   ld    a,b
513   and   3FH
514   cp    12
515   ld    a,c
516   jr    nz,GRPB
517   ld    a,0F9H
518   jr    BYTE1
519   ;
520 LDIN:
521   ex    af,af'
522   push  bc
523   call  nc,REGLO
524   ld    a,c
525   pop   bc
526   jr    nc,BIND
527   ld    c,0AH
528   call  PAIR1
529   call  LD16
530   jr    nc,GRPB
531   call  NUMBER
532   ld    c,2
533   call  PAIR
534   call  LD16
535   ret   c
536   call  BYTE
537   jr    VAL16
539 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
540 ;; misc. instructions
541 MISC:
542   jp    MISC_DEFB
545 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
547 ;; SUBROUTINES
550 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
552 JR_TOO_FAR:
553   ld    hl,(ASM_JR_TOO_FAR_CB)
554   jp    (hl)
556 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
558 LDA:
559   cp    4
560   call  c,EDX
561   ld    a,b
562 BYTE1:
563   jr    BYTE
565 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
567 LD16:
568   ld    a,b
569   jr    c,LD8
570   ld    a,b
571   and   3FH
572   cp    12
573   ld    a,c
574   ret   z
575   call  EDX
576   ld    a,c
577   or    43H
578   ret
580 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
582 LD8:
583   cp    7
584   scf
585   ret   nz
586   ld    a,c
587   or    30H
588   ret
590 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
592 CORN:
593   push  bc
594   call  OPND
595   bit   5,b
596   pop   bc
597   jr    z,NUMBER
598   ld    h,-1
599 EDX:
600   ld    a,0EDH
601   jr    BYTE
603 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
605 CBX:
606   ld    a,0CBH
607 BIND:
608   cp    76H
609   scf
610   ret   z               ;REJECT LD (HL),(HL)
611   call  BYTE
612   inc   d
613   ret   p
614   ld    a,e
615   jr    BYTE
617 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
619 OPND:
620   push  hl
621   ld    hl,OPRNDS
622   call  FIND
623   pop   hl
624   ret   c
625   bit   7,b
626   ret   z
627   bit   3,b
628   push  hl
629   call  z,OFFSET
630   ld    e,l
631   pop   hl
632   ld    a,0DDH
633   bit   6,b
634   jr    z,OP1
635   ld    a,0FDH
636 OP1:
637   or    a
638   inc   d
639   ld    d,a
640   ret   m
641 BYTE:
642   ld    (ix),a
643   inc   ix
644   or    a
645   ret
647 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
649 OFFSET:
650   ld    a,(iy)
651   cp    ')'
652   ld    hl,0
653   ret   z
655 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
656 ;; parse numeric expression
657 NUMBER:
658   call  SKIP
659   push  bc
660   push  de
661   push  ix
662   call  PARSE_INT_EXPR
663   ; HL: expression value
664   pop   ix
665   pop   de
666   pop   bc
667   ld    a,l
668   or    a
669   ret
671 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
673 REG:
674   call  OPND
675   ret   c
676   ld    a,b
677   and   3FH
678   cp    8
679   ccf
680   ret
682 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
684 REGLO:
685   call  REG
686   ret   c
687   jr    ORC
689 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
691 REGHI:
692   call  REG
693   ret   c
694   jr    SHL3
696 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
698 COND:
699   call  OPND
700   ret   c
701   ld    a,b
702   and   1FH
703   sub   16
704   jr    nc,SHL3
705   cp    -15
706   scf
707   ret   nz
708   ld    a,3
709   jr    SHL3
711 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
713 PAIR:
714   call  OPND
715   ret   c
716 PAIR1:
717   ld    a,b
718   and   0FH
719   sub   8
720   ret   c
721   jr    SHL3
723 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
725 CBIT:
726   call  NUMBER
727   cp    8
728   ccf
729   ret   c
730 SHL3:
731   rlca
732   rlca
733   rlca
734 ORC:
735   or    c
736   ld    c,a
737   ret
740 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
742 ;; common defb/defw code
743 ;;   carry set if we want words
745 COM_DEFBW:
746   push  af
747   push  ix
748   call  PARSE_INT_EXPR
749   pop   ix
750   ; HL: value
751   ld    (ix),l
752   inc   ix
753   pop   af
754   jr    nc,COM_DEFBW_BYTE
755   ld    (ix),h
756   inc   ix
757 COM_DEFBW_BYTE:
758   ex    af,af'
759   ; check for comma
760   call  SKIP
761   ret   z
762   ex    af,af'
763   jr    COM_DEFBW
765 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
767 ;; DEFB
769 MISC_DEFB:
770   djnz  MISC_DEFW
771 DEFB_LOOP:
772   or    a
773   jr    COM_DEFBW
775 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
777 ;; DEFW
779 MISC_DEFW:
780   djnz  MISC_DEFM
781 DEFW_LOOP:
782   scf
783   jr    COM_DEFBW
785 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
787 ;; DEFM
789 MISC_DEFM:
790   djnz  MISC_ORG
791 DEFM_LOOP:
792   push  ix
793   call  PARSE_STR_EXPR
794   pop   ix
795   ; HL: buffer address
796   ;  E: buffer length
797   xor   a
798   cp    e
799   jr    z,DEFM1_DONE_ONE
800 DEFM1:
801   ld    a,(hl)
802   inc   hl
803   call  BYTE
804   dec   e
805   jr    nz,DEFM1
806 DEFM1_DONE_ONE:
807   ; check for comma
808   call  SKIP
809   ret   z
810   jr    DEFM_LOOP
812 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
814 ;; ORG
816 MISC_ORG:
817   IF @BZ80ASM_ORGENTDISP
818   djnz  MISC_DISP
819   ld    a,ORGENT_ORG
820 COM_ORGENT:
821   ld    (ORGENT_TYPE),a
822   call  NUMBER
823   ld    (NEW_ORGENT),hl
824   or    a
825   ret
827 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
829 ;; DISP
831 MISC_DISP:
832   djnz  MISC_ENT
833   ld    a,ORGENT_DISP
834   jr    COM_ORGENT
836 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
838 ;; ENT
840 MISC_ENT:
841   djnz  MISC_WTF
842   ld    a,ORGENT_ENT
843   jr    COM_ORGENT
845 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
847 ;; error (the thing that should not be)
849 MISC_WTF:
850   ENDIF
851   ; set "unknown instruction index"
852   ; b may be zero here
853   ld    a,b
854   inc   a
855   ld    (ASM_BAD_B),a
856   scf
857   ret
860 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
861 ;; search the table for a token from the input buffer
862 ;; skips leading delimiters, and the token itself (if found)
863 ;; tokens in the table must have bit 7 set on the last char
864 ;; table ends with zero byte instead of first token char
865 ;; each token is followed by a data byte
866 ;; IN:
867 ;;   IY: text buffer
868 ;; OUT:
869 ;;   IY: new position in the text buffer
870 ;;    A: token number
871 ;;    B: token data byte
872 ;;   carry flag set on error (invalid char, or token not found)
873 ;;   on error, delimiters are still skipped
875 LDOP:
876   ld    hl,LDOPS
877 ; main table search entry point
878 FIND:
879   call  SKIP
880 EXIT:
881   ld    b,0
882   scf
883   ret   z
884   ; reject chars with high bit set
885   cp    128
886   ccf
887   ret   c
889 FIND0:
890   ; check the first char
891   ld    a,(hl)
892   or    a
893   jr    z,EXIT
894   xor   (iy)
895   and   %01011111   ; for case-insensitivity
896   jr    z,FIND2
897   ; first char is not matched, skip this token
898 FIND1:
899   bit   7,(hl)
900   inc   hl
901   jr    z,FIND1
902   ; skip token data byte
903   inc   hl
904   ; increment token counter
905   inc   b
906   jr    FIND0
908   ; first char matched, check the rest
909   ; A holds zero (due to xor/and)
910 FIND2:
911   push  iy
912 FIND3:
913   ; last token char?
914   bit   7,(hl)
915   inc   iy
916   inc   hl
917   jr    nz,FIND5
918   ; not the last token char
919   ; this compares (HL) with 0, because
920   ; A is guaranteed to hold zero here
921   cp    (hl)
922   ; zero byte in token means "skip delimiters"
923   ; it is used in some opcodes with fixed operands
924   call  z,SKIP0
925   ; load token char
926   ld    a,(hl)
927   ; compare with input char
928   xor   (iy)
929   and   %01011111   ; for case-insensitivity
930   jr    z,FIND3
932   ; alas, doesn't match
933 FIND4:
934   ; restore input stream pointer
935   pop   iy
936   ; and skip this token
937   jr    FIND1
939   ; we'll come here if we succesfully matched a token
940 FIND5:
941   ; if it isn't followed by a delimiter, '+' or '-', this is not a valid token
942   call  DELIM
943   call  nz,SIGN
944   jr    nz,FIND4
946   ; this token is valid
947 FIND6:
948   ; move token index to A
949   ld    a,b
950   ; load B with token data byte
951   ld    b,(hl)
952   ; drop original input stream position
953   pop   hl
954   ; we're done here
955   ; note that carry flag is guaranteed to be reset
956   ret
959 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
960 ;; used by FIND
961 SIGN:
962   cp    '+'
963   ret   z
964   cp    '-'
965   ret
967 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
968 ;; this entry point is used by FIND
969 SKIP0:
970   inc   hl
971 ;; this entry point is used to skip blanks and delimiters
972 ;; note that comma and right paren are considered blanks too
973 ;; as a consequence, operands may be delimited by spaces, or
974 ;; right parens, lol
975 ;; returns current char in A (and IY pointing to it)
976 ;; zero flag set if we hit a terminator
977 ;; zero flag reset if we hit a non-delimiter
978 SKIP:
979   ; delimiter or terminator?
980   call  DELIM
981   ret   nz
982   ; if this is terminator, still stop
983   call  TERM
984   ret   z
985   ; this is delimiter, skip it
986   inc   iy
987   jr    SKIP
989 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
990 ;; used by FIND and SKIP
991 ;; check if the current char is a delimiter or a terminator
992 ;; zero flag set on delimiter/terminator
993 DELIM:
994   ld    a,(iy)          ;ASSEMBLER DELIMITER
995   cp    ' '
996   ret   z
997   cp    ','
998   ret   z
999   cp    ')'
1000   ret   z
1002 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1003 ;; entry point for SKIP
1004 TERM:
1005   cp    ';'             ;ASSEMBLER TERMINATOR
1006   ret   z
1007   ;cp    '\'
1008   ;ret   z
1010 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1011 ;; also used by assembler to check for command separator
1012 ;; the assembler itself does nothing with separators
1013 ASM_IS_SEP:
1014   cp    ':'             ;ASSEMBLER SEPARATOR
1015   ret   nc
1016   cp    CR
1017   ret
1019 csizest = $-csizest
1020 $printf "assembler size: %d", csizest
1023 csizest = $
1025 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1026 ;; parse integer number (without sign)
1027 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1029 ;; this is advanced number parser
1030 ;; it understands alot of suffixes and prefixes:
1031 ;;   $     -- lone "$" means "current PC"
1032 ;;   #nnnn -- hex
1033 ;;   $nnnn -- hex
1034 ;;   &nnnn -- hex
1035 ;;   %nnnn -- binary
1036 ;;   0Xnnn -- hex
1037 ;;   0Onnn -- octal
1038 ;;   0Bnnn -- binary
1039 ;;   nnnnH -- hex
1040 ;;   nnnnB -- binary
1041 ;;   nnnnO -- octal
1042 ;; everything is case-insensitive
1043 ;; you can separate digits with underscores
1044 ;; (i.e. "12_34_5" will work, underscores are simply ignored)
1047 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1049 ;; parse a number, push it onto the stack
1050 ;; understands prefixes and suffixes
1052 ;; IN:
1053 ;;   IY: text buffer
1054 ;; OUT:
1055 ;;   IY: text buffer after the expression
1056 ;;   HL: number
1057 ;;   carry flag reset
1058 ;;  OR: (cannot parse as a number)
1059 ;;   IY: unchanged
1060 ;;   carry flag set
1061 ;;  DE,AF,flags: dead
1063 PARSE_NUMBER:
1064   call  PARSER_SKIP_BLANKS
1065   scf
1066   ret   z
1067   push  iy          ; we will need to rollback on error
1068   ; A already contains a char, loaded by `PARSER_SKIP_BLANKS`
1069   cp    '#'
1070   jr    z,.hexprefix
1071   cp    '$'
1072   jr    z,.maybe_lone_dollar
1073   cp    '&'
1074   jr    z,.hexprefix
1075   cp    '%'
1076   jr    z,.binprefix
1077   ; no, leading zero doesn't mean "octal", this is stupid
1078   ; but we may have prefixes like "0x" and such
1079   cp    '0'
1080   jr    z,.maybe_zero_prefix
1081   ; check if we have a digit here
1082   call  PARSER_CONV_DIGIT
1083   jr    c,.not_a_number_carry_set
1084   cp    10
1085   ; nope, do not allow it, all numbers must start with a digit
1086   ;jr    nc,.must_be_hex_with_sfx
1087   ccf
1088   jr    c,.not_a_number_carry_set
1089 .do_normal_decimal:
1090   ; done with prefixes, try decimal number
1091   ; we'll switch to suffix checking on hex digit
1092   ld    hl,0        ; accumulator
1093 .decimal_loop:
1094   call  .getDigit
1095   jr    c,.decimal_done
1096   cp    10
1097   jr    nc,.must_be_hex_with_sfx
1098   ; HL=HL*10
1099   add   hl,hl
1100   ld    de,hl
1101   add   hl,hl
1102   add   hl,hl
1103   add   hl,de
1104   ; HL=HL+A
1105   ld    e,a
1106   ld    d,0
1107   add   hl,de
1108   ; next char
1109   inc   iy
1110   jr    .decimal_loop
1111 .decimal_done:
1112   ; check for suffix
1113   ld    a,(iy)
1114   and   %11011111   ; cheap uppercase
1115   cp    'H'
1116   jr    z,.must_be_hex_with_sfx
1117   cp    'B'
1118   jr    z,.bin_with_sfx
1119   cp    'O'
1120   jr    z,.oct_with_sfx
1121   ; no suffix, we're done
1123 .success:
1124   pop   de          ; drop iy
1125   ; reset carry flag
1126   or    a
1127   ret
1129 .not_a_number_carry_set:
1130   pop   iy
1131   ret
1133 .hexprefix:
1134   ; skip prefix
1135   inc   iy
1136   call  .parse_as_hex
1137 .after_prefix:
1138   jr    c,.not_a_number_carry_set
1139   jr    .success
1141 .maybe_lone_dollar:
1142   ; lone dollar means "PC"
1143   inc   iy
1144   call  .parse_as_hex
1145   ; the only case we may gen an error here is
1146   ; when our dollar isn't followed by a digit
1147   jr    nc,.success
1148   ; lone dollar is good too
1149   ; IY points right after the dollar here
1150   ld    hl,(BZ80ASM.PC)
1151   jr    .success
1153 .binprefix:
1154   ; skip prefix
1155   inc   iy
1156   call  .parse_as_bin
1157   jr    .after_prefix
1159 .maybe_binprefix:
1160   ; things like "0BEEFh" should be parsed as hex
1161   ; skip prefix
1162   inc   iy
1163   call  .parse_as_bin
1164   jr    c,.must_be_hex_with_sfx
1165   ; check for 'H'
1166   ld    a,(iy)
1167   and   %11011111   ; cheap uppercase
1168   cp    'H'
1169   jr    z,.must_be_hex_with_sfx
1170   jr    .success
1172 .octprefix:
1173   ; skip prefix
1174   inc   iy
1175   call  .parse_as_oct
1176   jr    .after_prefix
1178 .maybe_zero_prefix:
1179   ; check for '0x' and such
1180   ; skip '0'
1181   inc   iy
1182   ; load and prefix
1183   ; there's no need to skip it, as it will be
1184   ; skipped by the corresponding subroutine
1185   ld    a,(iy)
1186   ; so IY will point to the actual number
1187   and   %11011111   ; cheap uppercase
1188   cp    'X'
1189   jr    z,.hexprefix
1190   cp    'B'
1191   jr    z,.maybe_binprefix
1192   cp    'O'
1193   jr    z,.octprefix
1194   ; do not reparse '0', no need to backup
1195   jr    .do_normal_decimal
1197 .must_be_hex_with_sfx:
1198   ; reparse as hex, and check for suffix
1199   pop   iy
1200   push  iy
1201   call  .parse_as_hex
1202   jr    c,.not_a_number_carry_set
1203   ld    a,(iy)
1204   inc   iy
1205   and   %11011111   ; cheap uppercase
1206   cp    'H'
1207   jr    z,.success
1209 .bin_with_sfx:
1210   ; reparse as bin, skip suffix (it is guaranteed to be there)
1211   pop   iy
1212   push  iy
1213   call  .parse_as_bin
1214 .done_guaranteed_suffix:
1215   jr    c,.not_a_number_carry_set
1216   ; skip suffix
1217   inc   iy
1218   jr    .success
1220 .oct_with_sfx:
1221   ; reparse as bin, skip suffix (it is guaranteed to be there)
1222   pop   iy
1223   push  iy
1224   call  .parse_as_bin
1225   jr    .done_guaranteed_suffix
1227 .parse_as_hex:
1228   ld    hl,0        ; accumulator
1229   ; check first digit (as this is general parser)
1230   call  .getDigitNoUnder
1231   ret   c
1232 .parse_as_hex_loop:
1233   inc   iy
1234   add   hl,hl
1235   add   hl,hl
1236   add   hl,hl
1237   add   hl,hl
1238   ld    e,a
1239   ld    d,0
1240   add   hl,de
1241   call  .getDigit
1242   jr    nc,.parse_as_hex_loop
1243   ; clear carry flag (it is always set here)
1244   ccf
1245   ret
1247 .parse_as_bin:
1248   ld    hl,0        ; accumulator
1249   ; check first digit (as this is general parser)
1250   ld    a,(iy)
1251   call  .getDigitNoUnderBin
1252   ret   c
1253 .parse_as_bin_loop:
1254   inc   iy
1255   add   hl,hl
1256   ld    e,a
1257   ld    d,0
1258   add   hl,de
1259   call  .getBinDigit
1260   jr    nc,.parse_as_bin_loop
1261   ; clear carry flag (it is always set here)
1262   ccf
1263   ret
1265 .parse_as_oct:
1266   ld    hl,0        ; accumulator
1267   ; check first digit (as this is general parser)
1268   ld    a,(iy)
1269   call  .getDigitNoUnderOct
1270 .parse_as_oct_loop:
1271   inc   iy
1272   add   hl,hl
1273   add   hl,hl
1274   add   hl,hl
1275   ld    e,a
1276   ld    d,0
1277   add   hl,de
1278   call  .getOctDigit
1279   jr    nc,.parse_as_oct_loop
1280   ; clear carry flag (it is always set here)
1281   ccf
1282   ret
1285 .getDigit_inc:
1286   inc   iy
1287 .getDigit:
1288   ld    a,(iy)
1289   cp    '_'
1290   jr    z,.getDigit_inc
1291   jr    PARSER_CONV_DIGIT
1293   ; d: base
1294 .getDigitInBase:
1295   call  .getDigit
1296   ret   c
1297   cp    d
1298   ccf
1299   ret
1301 .getDigitNoUnder:
1302   ld    a,(iy)
1303   jr    PARSER_CONV_DIGIT
1305 .getDecDigit:
1306   ld    d,10
1307   jr    .getDigitInBase
1309 .getDigitNoUnderOct:
1310   ld    a,(iy)
1311 .getOctDigit:
1312   ld    d,8
1313   jr    .getDigitInBase
1315 .getDigitNoUnderBin:
1316   ld    a,(iy)
1317 .getBinDigit:
1318   ld    d,2
1319   jr    .getDigitInBase
1322 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1323 ;; converts 'A' to digit (assume hex)
1324 ;; carry set: not a digit char (and A is destroyed)
1326 PARSER_CONV_DIGIT:
1327   sub   '0'
1328   ret   c
1329   cp    10
1330   ccf
1331   ret   nc
1332   add   a,'0'
1333   and   %11011111   ; cheap uppercase
1334   sub   'A'-10
1335   ret   c
1336   cp    16
1337   ccf
1338   ret
1340 csizest = $-csizest
1341 $printf "assembler numparse size: %d", csizest
1344 csizest = $
1346 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1347 ;; math expression parser
1348 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1350 PARSE_EXPR_ERROR_A:
1351   ld    hl,(EXPR_ERROR_CB)
1352   jp    (hl)
1354 PARSE_EXPR_ERROR_0DIV:
1355   ld    a,EXPR_ERR_DIVISION_BY_ZERO
1356   jr    PARSE_EXPR_ERROR_A
1358 PARSE_EXPR_ERROR_INT:
1359   ld    a,EXPR_ERR_NUMBER_EXPECTED
1360   jr    PARSE_EXPR_ERROR_A
1363 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1365 ;; parse an integer expression
1366 ;; IN:
1367 ;;   IY: text buffer
1368 ;; OUT:
1369 ;;   IY: text buffer after the expression
1370 ;;   HL: expression value
1371 ;;   everything other (including all alternate registers) is dead
1373 ;; priorities:
1374 ;;   unaries
1375 ;;   * / %
1376 ;;   + -
1377 ;;   << >>
1379 PARSE_INT_EXPR:
1380   call  PARSER_SKIP_BLANKS
1381   jr    z,PARSE_EXPR_ERROR_INT
1382   ; unary "+" or "-"?
1383   call  BZ80ASM.SIGN
1384   jr    nz,.doexpr
1385   push  af
1386   inc   iy
1387   call  .doexpr
1388   pop   af
1389   ; check for negate
1390   cp    '-'
1391   ret   nz
1392   ; negate HL
1393   or    a
1394   ld    de,0
1395   ex    de,hl
1396   sbc   hl,de
1397   ret
1399 .doexpr:
1400 ;; |
1401 .bitor:
1402   ; get first operand
1403   ; already done above
1404   call  .bitxor
1405 .bitor_next:
1406   ; check for operation
1407   call  PARSER_SKIP_BLANKS
1408   ret   z       ; exit on EOL
1409   cp    '|'
1410   ret   nz
1411   ; get second operand
1412   ld    bc,.bitxor
1413   call  .go_down_bc
1414   ld    a,l
1415   or    e
1416   ld    l,a
1417   ld    a,h
1418   or    d
1419   ld    h,a
1420   jr    .bitor_next
1422 ;; ^
1423 .bitxor:
1424   ; get first operand
1425   call  .bitand
1426 .bitxor_next:
1427   ; check for operation
1428   call  PARSER_SKIP_BLANKS
1429   ret   z       ; exit on EOL
1430   cp    '^'
1431   ret   nz
1432   ; get second operand
1433   ld    bc,.bitand
1434   call  .go_down_bc
1435   ld    a,l
1436   xor   e
1437   ld    l,a
1438   ld    a,h
1439   xor   d
1440   ld    h,a
1441   jr    .bitxor_next
1443 ;; &
1444 .bitand:
1445   ; get first operand
1446   call  .shlshr
1447 .bitand_next:
1448   ; check for operation
1449   call  PARSER_SKIP_BLANKS
1450   ret   z       ; exit on EOL
1451   cp    '&'
1452   ret   nz
1453   ; get second operand
1454   ld    bc,.shlshr
1455   call  .go_down_bc
1456   ld    a,l
1457   and   e
1458   ld    l,a
1459   ld    a,h
1460   and   d
1461   ld    h,a
1462   jr    .bitand_next
1464 ;; << >>
1465 .shlshr:
1466   call  .addsub
1467 .shlshr_next:
1468   ; check for operation
1469   call  PARSER_SKIP_BLANKS
1470   ret   z       ; exit on EOL
1471   ; (iy+0) and (iy+1) should be equal
1472   cp    (iy+1)
1473   ret   nz
1474   cp    '<'     ; %0011_1100
1475   jr    z,.doshift
1476   cp    '>'     ; %0011_1110
1477   ret   nz
1478 .doshift:
1479   ; get second operand
1480   inc   iy      ; skip operation part
1481   ld    bc,.addsub
1482   call  .go_down_bc
1483   ex    af,af'
1484   ; HL: number to shift
1485   ; DE: amount
1486   ld    a,d
1487   or    a
1488   jr    nz,.shift_too_far
1489   ld    a,e
1490   cp    16
1491   jr    nc,.shift_too_far
1492   ld    b,a
1493   ex    af,af'
1494   cp    '<'
1495   jr    z,.do_shl
1496   ; shr
1497 .do_shr_loop:
1498   srl   h
1499   rr    l
1500   djnz  .do_shr_loop
1501   jr    .shlshr_next
1502   ; shl
1503 .do_shl:
1504   ; shl
1505   sla   l
1506   rl    h
1507   djnz  .do_shl
1508   jr    .shlshr_next
1509 .shift_too_far:
1510   ld    hl,0
1511   jr    .shlshr_next
1513 ;; + -
1514 .addsub:
1515   ; get first operand
1516   call  .muldiv
1517 .addsub_next:
1518   ; check for operation
1519   call  PARSER_SKIP_BLANKS
1520   ret   z       ; exit on EOL
1521   cp    '+'     ; %0010_1011
1522   jr    z,.doaddsub
1523   cp    '-'     ; %0010_1101
1524   ret   nz
1525 .doaddsub:
1526   ; get second operand
1527   ld    bc,.muldiv
1528   call  .go_down_bc
1529   cp    '-'
1530   jr    z,.dosub
1531   add   hl,de
1532   jr    .addsub_next
1533 .dosub:
1534   sbc   hl,de
1535   jr    .addsub_next
1537 ;; * / %
1538 .muldiv:
1539   ; get first operand
1540   call  .term
1541 .muldiv_next:
1542   ; check for operation
1543   call  PARSER_SKIP_BLANKS
1544   ret   z       ; exit on EOL
1545   cp    '*'     ; %0010_1010
1546   jr    z,.domuldiv
1547   cp    '/'     ; %0010_1111
1548   jr    z,.domuldiv
1549   cp    '%'     ; %0010_0101
1550   ret   nz
1551 .domuldiv:
1552   ; get second operand
1553   ld    bc,.term
1554   call  .go_down_bc
1555   ld    bc,hl
1556   cp    '*'
1557   jr    z,.domul
1558   ex    af,af'  ; save operation
1559   ; div or mod
1560   ld    a,e
1561   or    d
1562   jp    z,PARSE_EXPR_ERROR_0DIV
1563   call  PARSER_UDIV_BC_DE
1564   ; was it div or mod?
1565   ex    af,af'
1566   cp    '%'
1567   jr    z,.muldiv_next  ; remainder already in hl
1568   ; division
1569   ld    hl,bc
1570   jr    .muldiv_next
1571 .domul:
1572   call  PARSER_UMUL_BC_DE
1573   jr    .muldiv_next
1575 ;; parse term, also process unaries and parens
1576 .term:
1577   call  PARSER_SKIP_BLANKS
1578   jp    z,PARSE_EXPR_ERROR_INT
1579   inc   iy      ; skip operation
1580   ld    c,')'
1581   cp    '('
1582   jr    z,.term_lparen
1583   cp    '['
1584   ld    c,']'
1585   jr    z,.term_lparen
1586   cp    '~'
1587   jr    z,.term_ubitnot
1588   ; this must be number
1589   dec   iy      ; undo skip
1590   call  PARSE_NUMBER
1591   ret   nc
1592   ; check for labels
1593   push  iy      ; for correct error position
1594   push  ix      ; the only register we care about
1595   ld    hl,.term_checklabel_ret
1596   push  hl
1597   ld    hl,(GETLABEL_CB)
1598   jp    (hl)
1599 .term_checklabel_ret:
1600   pop   ix
1601   pop   de
1602   ret   nc
1603   ; oops, error
1604   ; restore position for correct error reporting
1605   push  de
1606   pop   iy
1607   jp    PARSE_EXPR_ERROR_INT
1609   ;; "("
1610 .term_lparen:
1611   ;; C contains matching rparen
1612   push  bc
1613   call  PARSE_INT_EXPR
1614   call  PARSER_SKIP_BLANKS
1615   jr    z,PARSE_EXPR_ERROR_RPAREN
1616   pop   bc
1617   cp    c
1618   jr    nz,PARSE_EXPR_ERROR_RPAREN
1619   inc   iy
1620   ret
1622   ;; "~"
1623 .term_ubitnot:
1624   call  .term
1625   ld    a,h
1626   cpl
1627   ld    h,a
1628   ld    a,l
1629   cpl
1630   ld    l,a
1631   ret
1633   ;; call subroutine at BC
1634   ;; AF: preserved
1635   ;; HL: preserved
1636   ;; DE: subroutine result
1637   ;; i.e. HL is op0, DE is op1
1638 .go_down_bc:
1639   push  hl
1640   push  af      ; A holds operation
1641   inc   iy      ; skip operation
1642   ld    hl,.go_down_bc_ret
1643   push  hl
1644   push  bc
1645   ret
1646 .go_down_bc_ret:
1647   pop   af
1648   pop   de
1649   ex    de,hl
1650   ret
1652 PARSE_EXPR_ERROR_RPAREN:
1653   ld    a,EXPR_ERR_RPAREN_EXPECTED
1654   jp    PARSE_EXPR_ERROR_A
1657 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1659 ;; HL=BC*DE
1661 ;; BC,DE,A,flags: dead
1663 PARSER_UMUL_BC_DE:
1664   ; DEHL=BC*DE
1665   ld    hl,0
1666   ld    a,16
1667 .loop:
1668   add   hl,hl
1669   rl    e
1670   rl    d
1671   jr    nc,.skip
1672   add   hl,bc
1673   jr    nc,.skip
1674   inc   de
1675 .skip:
1676   dec   a
1677   jr    nz,.loop
1678   ret
1681 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1683 ;; performs BC/DE
1684 ;; OUT:
1685 ;;   BC: quotient
1686 ;;   HL: remainder
1688 ;; DE,A,flags: dead
1690 PARSER_UDIV_BC_DE:
1691   ld    hl,0
1692   ld    a,16
1693 .loop:
1694   sll   c
1695   rl    b
1696   adc   hl,hl
1697   sbc   hl,de
1698   jr    nc,.skip
1699   add   hl,de
1700   dec   c
1701 .skip:
1702   dec   a
1703   jr    nz,.loop
1704   ret
1707 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1709 ;; parse a string expression
1711 ;; IN:
1712 ;;   IY: text buffer
1713 ;; OUT:
1714 ;;   HL: string buffer start
1715 ;;    E: parsed string length
1716 ;;   everything other (including all alternate registers) is dead
1718 PARSE_STR_EXPR:
1719   call  PARSER_SKIP_BLANKS
1720   jr    z,PARSE_EXPR_ERROR_STR
1721   cp    34
1722   jr    z,.strok
1723   cp    39
1724   jr    nz,PARSE_EXPR_ERROR_STR
1725 .strok:
1726   ld    c,a  ; terminator
1727   inc   iy
1728   ; remember buffer start
1729   push  iy
1730 .strloop:
1731   ld    a,(iy)
1732   or    a
1733   jr    z,PARSE_EXPR_ERROR_STR
1734   cp    CR
1735   jr    z,PARSE_EXPR_ERROR_STR
1736   inc   iy
1737   cp    c
1738   jr    nz,.strloop
1739   ; done string parsing, calc length
1740   pop   hl  ; buffer start
1741   ex    de,hl
1742   push  iy
1743   pop   hl
1744   ; DE: buffer start
1745   ; HL: buffer end
1746   or    a
1747   sbc   hl,de
1748   ex    de,hl
1749   ret
1751 PARSE_EXPR_ERROR_STR:
1752   ld    a,EXPR_ERR_STRING_EXPECTED
1753   jp    PARSE_EXPR_ERROR_A
1756 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1757 ;; skip blanks
1758 ;; returns current char in A
1759 ;; sets zero flag on EOL
1760 ;; IN:
1761 ;;   IY: text buffer
1762 ;; OUT:
1763 ;;   IY: text buffer at non-blank or EOL
1764 ;;    A: non-blank or EOL char
1765 ;;   zero flag is set on EOL
1767 PARSER_SKIP_BLANKS:
1768   ld    a,(iy)
1769   or    a
1770   ret   z
1771   cp    13
1772   ret   z
1773   inc   iy
1774   cp    33
1775   jr    c,PARSER_SKIP_BLANKS
1776   dec   iy
1777   ; reset zero flag
1778   or    a
1779   ret
1781 csizest = $-csizest
1782 $printf "assembler exprparse size: %d", csizest
1785 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
1786 ;; various tables -- mnemonics, operands...
1788 csizest = $
1790 ;; number of "trivial" opcodes without any special processing
1791 OPC_COUNT_GROUPS_0_AND_1 equ 39
1792 ;; number of non-ED-prefixed instructions in "trivial"
1793 OPC_COUNT_GROUP_0 equ 15
1795 ;; total number of CB-prefixed instructions (GROUPS 2 and 3)
1796 OPC_COUNT_GROUPS_2_AND_3 equ 10
1797 ;; number of direct bit manipulation instructions in CB list (GROUP 2)
1798 OPC_COUNT_GROUP_2 equ 3
1800 ;; push, pop, ex (sp),rr
1801 OPC_COUNT_GROUP_4 equ 3
1803 ;; ALU with accum
1804 OPC_COUNT_GROUP_5 equ 5
1805 ;; ALU with accum
1806 OPC_COUNT_GROUP_6 equ 3
1807 ;; GROUPS 5 and 6
1808 OPC_COUNT_GROUPS_5_AND_6 equ OPC_COUNT_GROUP_5+OPC_COUNT_GROUP_6
1810 ;; INC/DEC
1811 OPC_COUNT_GROUP_7 equ 2
1813 ;; IN
1814 OPC_COUNT_GROUP_8 equ 1
1815 ;; OUT
1816 OPC_COUNT_GROUP_9 equ 1
1817 ;; GROUPS 8 and 9
1818 OPC_COUNT_GROUPS_8_AND_9 equ OPC_COUNT_GROUP_8+OPC_COUNT_GROUP_9
1820 ; JR,DJNZ
1821 OPC_COUNT_GROUP_10 equ 2
1822 OPC_COUNT_GROUP_10_JRS equ 1
1825 ;; WARNING! the assembler has some hard-coded mnemonics counts
1826 ;;          scattered across the code, so don't mess with the tables!
1827 ;;          i may document this in the future, but for now, leave it as it is.
1828 ;; mnemonics
1829 OPCODS:
1830   ; GROUPS 0 AND 1: "trivial" (39, OPC_COUNT_GROUPS_0_AND_1)
1831   ; GROUP 0: "trivial" one-byte (15, OPC_COUNT_GROUP_0)
1832   defx  "NOP"
1833   defb  0
1834   defx  "RLCA"
1835   defb  7
1836   defm  "EX",0,"AF",0
1837     defx "AF'"
1838   defb  8
1839   defx  "RRCA"
1840   defb  #0F
1841   defx  "RLA"
1842   defb  #17
1843   defx  "RRA"
1844   defb  #1F
1845   defx  "DAA"
1846   defb  #27
1847   defx  "CPL"
1848   defb  #2F
1849   defx  "SCF"
1850   defb  #37
1851   defx  "CCF"
1852   defb  #3F
1853   defx  "HALT"
1854   defb  #76
1855   defx  "EXX"
1856   defb  #D9
1857   defm  "EX",0,"DE",0
1858     defx "HL"
1859   defb  #EB
1860   defx  "DI"
1861   defb  #F3
1862   defx  "EI"
1863   defb  #FB
1864   ; GROUP 1: "trivial" ED-prefixed (24, OPC_COUNT_GROUPS_0_AND_1-OPC_COUNT_GROUP_0)
1865   defx  "NEG"
1866   defb  #44
1867   defm  "IM",0
1868     defx  "0"
1869   defb  #46
1870   defx  "RETN"
1871   defb  #45
1872   defx  "RETI"
1873   defb  #4D
1874   defm  "IM",0
1875     defx  "1"
1876   defb  #56
1877   defm  "IM",0
1878     defx  "2"
1879   defb  #5E
1880   defx  "RRD"
1881   defb  #67
1882   defx  "RLD"
1883   defb  #6F
1884   defx  "LDI"
1885   defb  #A0
1886   defx  "CPI"
1887   defb  #A1
1888   defx  "INI"
1889   defb  #A2
1890   defx  "OUTI"
1891   defb  #A3
1892   defx  "LDD"
1893   defb  #A8
1894   defx  "CPD"
1895   defb  #A9
1896   defx  "IND"
1897   defb  #AA
1898   defx  "OUTD"
1899   defb  #AB
1900   defx  "LDIR"
1901   defb  #B0
1902   defx  "CPIR"
1903   defb  #B1
1904   defx  "INIR"
1905   defb  #B2
1906   defx  "OTIR"
1907   defb  #B3
1908   defx  "LDDR"
1909   defb  #B8
1910   defx  "CPDR"
1911   defb  #B9
1912   defx  "INDR"
1913   defb  #BA
1914   defx  "OTDR"
1915   defb  #BB
1917   ; GROUPS 2 AND 3: CB-prefixed (10, OPC_COUNT_GROUPS_2_AND_3)
1918   ; GROUP 2: direct bit manipulation (3, OPC_COUNT_GROUP_2)
1919   defx  "BIT"
1920   defb  #40
1921   defx  "RES"
1922   defb  #80
1923   defx  "SET"
1924   defb  #C0
1925   ; GROUP 3: shifts (7, OPC_COUNT_GROUPS_2_AND_3-OPC_COUNT_GROUP_2)
1926   defx  "RLC"
1927   defb  0
1928   defx  "RRC"
1929   defb  8
1930   defx  "RL"
1931   defb  #10
1932   defx  "RR"
1933   defb  #18
1934   defx  "SLA"
1935   defb  #20
1936   defx  "SRA"
1937   defb  #28
1938   defx  "SRL"
1939   defb  #38
1941   ; GROUP 4: push,pop,ex (sp),rr (OPC_COUNT_GROUP_4)
1942   defx  "POP"
1943   defb  #C1
1944   defx  "PUSH"
1945   defb  #C5
1946   defm  "EX",0
1947     defx  "(SP"
1948   defb  #E3
1950   ; GROUP 5: ALU with accumulator (OPC_COUNT_GROUP_5)
1951   defx  "SUB"
1952   defb  #90
1953   defx  "AND"
1954   defb  #A0
1955   defx  "XOR"
1956   defb  #A8
1957   defx  "OR"
1958   defb  #B0
1959   defx  "CP"
1960   defb  #B8
1961   ;k8: for some reason i cannot remove those two
1962   ;defb  TAND
1963   ;defb  #A0
1964   ;defb  TOR
1965   ;defb  #B0
1967   ; GROUP 6: ALU with accumulator or HL (OPC_COUNT_GROUP_6)
1968   defx  "ADD"
1969   defb  #80
1970   defx  "ADC"
1971   defb  #88
1972   defx  "SBC"
1973   defb  #98
1975   ; GROUP 7: inc,dec (2, OPC_COUNT_GROUP_7)
1976   defx  "INC"
1977   defb  4
1978   defx  "DEC"
1979   defb  5
1981   ; GROUP 8: in (1, OPC_COUNT_GROUP_8)
1982   defx  "IN"
1983   defb  #40
1984   ; GROUP 9: out (1, OPC_COUNT_GROUP_9)
1985   defx  "OUT"
1986   defb  #41
1988   ; GROUP 10: jr,djnz (2, OPC_COUNT_GROUP_10)
1989   defx  "JR"
1990   defb  #20
1991   defx  "DJNZ"
1992   defb  #10
1994   ; GROUP 11: jp (strictly one)
1995   defx  "JP"
1996   defb  #C2
1998   ; GROUP 12: call (strictly one)
1999   defx  "CALL"
2000   defb  #C4
2002   ; GROUP 13: rst (strictly one)
2003   defx  "RST"
2004   defb  #C7
2006   ; GROUP 14: ret (strictly one)
2007   defx  "RET"
2008   defb  #C0
2010   ; GROUP 15: ld (strictly one)
2011   defx  "LD"
2012   defb  #40
2014   ; miscellaneous assembler instructions
2015   ; WARNING! the order matters!
2016   defx  "DEFB"
2017   defb  0
2018   ;
2019   defx  "DEFW"
2020   defb  0
2021   ;
2022   defx  "DEFM"
2023   defb  0
2025   IF @BZ80ASM_ORGENTDISP
2026   defx  "ORG"
2027   defb  0
2028   ;
2029   defx  "DISP"
2030   defb  0
2031   ;
2032   defx  "ENT"
2033   defb  0
2034   ENDIF
2035   ; softinclude user instructions
2036   include "?bzasm80_user_mnemonics.zas"
2038   ; no more
2039   defb  0
2041 ;; operands
2042 OPRNDS:
2043   defx  "B"
2044   defb  0
2045   defx  "C"
2046   defb  1
2047   defx  "D"
2048   defb  2
2049   defx  "E"
2050   defb  3
2051   defx  "H"
2052   defb  4
2053   defx  "L"
2054   defb  5
2055   defx  "(HL"
2056   defb  6
2057   defx  "A"
2058   defb  7
2059   defx  "(IX"
2060   defb  #86
2061   defx  "(IY"
2062   defb  #C6
2063   ;
2064   defx  "BC"
2065   defb  8
2066   defx  "DE"
2067   defb  10
2068   defx  "HL"
2069   defb  12
2070   defx  "IX"
2071   defb  #8C
2072   defx  "IY"
2073   defb  #CC
2074   defx  "AF"
2075   defb  14
2076   defx  "SP"
2077   defb  14
2078   ;
2079   defx  "NZ"
2080   defb  16
2081   defx  "Z"
2082   defb  17
2083   defx  "NC"
2084   defb  18
2085   defx  "PO"
2086   defb  20
2087   defx  "PE"
2088   defb  21
2089   defx  "P"
2090   defb  22
2091   defx  "M"
2092   defb  23
2093   ;
2094   defx  "(C"
2095   defb  #20
2096   ;
2097   defb  0
2100 LDOPS:
2101   defm  "I"
2102   defb  0
2103   defx  "A"
2104   defb  #47
2105   defm  "R"
2106   defb  0
2107   defx  "A"
2108   defb  #4F
2109   defm  "A"
2110   defb  0
2111   defx  "I"
2112   defb  #57
2113   defm  "A"
2114   defb  0
2115   defx  "R"
2116   defb  #5F
2117   defm  "(BC"
2118   defb  0
2119   defx  "A"
2120   defb  2
2121   defm  "(DE"
2122   defb  0
2123   defx  "A"
2124   defb  #12
2125   defm  "A"
2126   defb  0
2127   defx  "(BC"
2128   defb  #0A
2129   defm  "A"
2130   defb  0
2131   defx  "(DE"
2132   defb  #1A
2133   ;
2134   defb  0
2136 csizest = $-csizest
2137 $printf "assembler tables size: %d", csizest
2139 asmsizest = $-asmsizest
2140 $printf "full assembler size: %d", asmsizest
2142 ; so they won't clutter symbol table
2143 csizest = -1
2144 asmsizest = -1
2146   ENDMODULE BZ80ASM