; *** Code ***
; Checks whether A is 'N' or 'M'
checkNOrM:
cp 'N'
ret z
cp 'M'
ret
; Checks whether A is 'n', 'm'
checknm:
cp 'n'
ret z
cp 'm'
ret
checklxy:
cp 'l'
ret z
; Checks whether A is 'x', 'y'
checkxy:
cp 'x'
ret z
cp 'y'
ret
; Reads string in (HL) and returns the corresponding ID (I_*) in A. Sets Z if
; there's a match.
getInstID:
push bc
push de
ld b, I_XOR+1 ; I_XOR is the last
ld c, 4
ld de, instrNames
call findStringInList
pop de
pop bc
ret
; Parse the string at (HL) and check if it starts with IX+, IY+, IX- or IY-.
; Sets Z if yes, unset if no. On success, A contains either '+' or '-'.
parseIXY:
push hl
ld a, (hl)
call upcase
cp 'I'
jr nz, .end ; Z already unset
inc hl
ld a, (hl)
call upcase
cp 'X'
jr z, .match1
cp 'Y'
jr z, .match1
jr .end ; Z already unset
match1:
; Alright, we have IX or IY. Let's see if we have + or - next.
inc hl
ld a, (hl)
cp '+'
jr z, .end ; Z is already set
cp '-'
; The value of Z at this point is our final result
end:
pop hl
ret
; find argspec for string at (HL). Returns matching argspec in A.
; Return value 0xff holds a special meaning: arg is not empty, but doesn't match
; any argspec (A == 0 means arg is empty). A return value of 0xff means an
; error.
;
; If the parsed argument is a number constant, 'N' is returned and DE contains
; the value of that constant.
parseArg:
call strlen
or a
ret z ; empty string? A already has our result: 0
push bc
push hl
ld de, argspecTbl
; DE now points the the "argspec char" part of the entry, but what
; we're comparing in the loop is the string next to it. Let's offset
; DE by one so that the loop goes through strings.
inc de
ld b, ARGSPEC_TBL_CNT
loop1:
ld a, 4
call strncmpI
jr z, .found ; got it!
ld a, 5
call addDE
djnz .loop1
; We exhausted the argspecs. Let's see if we're inside parens.
call enterParens
jr z, .withParens
; (HL) has no parens
call .maybeParseExpr
jr nz, .nomatch
; We have a proper number in no parens. Number in DE.
ld a, 'N'
jr .end
withParens:
ld b, 0 ; make sure it doesn't hold '-'
ld c, 'M' ; C holds the argspec type until we reach
; .numberInParens
; We have parens. First, let's see if we have a (IX+d) type of arg.
call parseIXY
jr nz, .parseNumberInParens ; not I{X,Y}. just parse number.
; We have IX+/IY+/IX-/IY-.
; A contains either '+' or '-'. Save it for later, in B.
ld b, a
inc hl ; (HL) now points to X or Y
ld a, (hl)
call upcase
inc hl ; advance HL to the number part
inc hl ; this is the number
cp 'Y'
jr nz, .notY
ld c, 'y'
jr .parseNumberInParens
notY:
ld c, 'x'
parseNumberInParens:
call .maybeParseExpr
jr nz, .nomatch
; We have a proper number in parens. Number in DE
; is '-' in B? if yes, we need to negate the low part of DE
ld a, b
cp '-'
jr nz, .dontNegateDE
; we need to negate the low part of DE
; TODO: when parsing routines properly support unary negative numbers,
; We could replace this complicated scheme below with a nice hack where
; we start parsing our displacement number at the '+' and '-' char.
ld a, e
neg
ld e, a
dontNegateDE:
ld a, c ; M, x, or y
jr .end
nomatch:
; We get no match
ld a, 0xff
jr .end
found:
; found the matching argspec row. Our result is one byte left of DE.
dec de
ld a, (de)
; When we have non-numerical args, we set DE to zero to have a clean
; result.
ld de, 0
end:
pop hl
pop bc
ret
maybeParseExpr:
; Before we try to parse expr in (HL), first check if we're in first
; pass if we are, skip parseExpr. Most of the time, that parse is
; harmless, but in some cases it causes false failures. For example,
; a "-" operator can cause is to falsely overflow and generate
; truncation error.
ld de, 0 ; in first pass, return a clean zero
call zasmIsFirstPass
ret z
jp parseExpr
; Returns, with Z, whether A is a groupId
isGroupId:
or a
jp z, unsetZ ; not a group
cp 0xd ; max group id + 1
jp nc, unsetZ ; >= 0xd? not a group
; A is a group. ensure Z is set
cp a
ret
; Find argspec A in group id H.
; Set Z according to whether we found the argspec
; If found, the value in A is the argspec value in the group (its index).
findInGroup:
push bc
push hl
or a ; is our arg empty? If yes, we have nothing to do
jr z, .notfound
push af
ld a, h
cp 0xa
jr z, .specialGroupCC
cp 0xb
jr z, .specialGroupABCDEHL
jr nc, .notfound ; > 0xb? not a group
pop af
; regular group
push de
ld de, argGrpTbl
; group ids start at 1. decrease it, then multiply by 4 to have a
; proper offset in argGrpTbl
dec h
push af
ld a, h
rla
rla
call addDE ; At this point, DE points to our group
pop af
ex de, hl ; And now, HL points to the group
pop de
ld bc, 4
jr .find
specialGroupCC:
ld hl, argGrpCC
jr .specialGroupEnd
specialGroupABCDEHL:
ld hl, argGrpABCDEHL
specialGroupEnd:
pop af ; from the push af just before the special group check
ld bc, 8
find:
; This part is common to regular and special group. We expect HL to
; point to the group and BC to contain its length.
push bc ; save the start value loop index so we can sub
loop:
cpi
jr z, .found
jp po, .notfound
jr .loop
found:
; we found our result! Now, what we want to put in A is the index of
; the found argspec.
pop hl ; we pop from the "push bc" above. L is now 4 or 8
ld a, l
sub c
dec a ; cpi DECs BC even when there's a match, so C == the
; number of iterations we've made. But our index is
; zero-based (1 iteration == 0 index).
cp a ; ensure Z is set
jr .end
notfound:
pop bc ; from the push bc in .find
call unsetZ
end:
pop hl
pop bc
ret
; Compare argspec from instruction table in A with argument in (HL).
; IX must point to argspec row.
; For constant args, it's easy: if A == (HL), it's a success.
; If it's not this, then we check if it's a numerical arg.
; If A is a group ID, we do something else: we check that (HL) exists in the
; groupspec (argGrpTbl). Moreover, we go and write the group's "value" (index)
; in (HL+1). This will save us significant processing later in spitUpcode.
; Set Z according to whether we match or not.
matchArg:
cp (hl)
ret z
; not an exact match. Before we continue: is A zero? Because if it is,
; we have to stop right here: no match possible.
or a
jr nz, .skip1 ; not a zero, we can continue
; zero, stop here
cp 1 ; unset Z
ret
skip1:
; If our argspec is 'l', then we also match 'x' and 'y'
cp 'l'
jr nz, .skip2
; Does it accept IX and IY?
bit 4, (ix+3)
ld a, (hl)
jp nz, checkxy ; bit set: our result is checkxy
; doesn't accept? then we don't match
jp unsetZ
skip2:
; Alright, let's start with a special case. Is it part of the special
; "BIT" group, 0xc? If yes, we actually expect a number, which will
; then be ORed like a regular group index.
cp 0xc
jr z, .expectsBIT
; not an exact match, let's check for numerical constants.
call upcase
call checkNOrM
jr z, .expectsNumber
jr .notNumber
expectsNumber:
; Our argument is a number N or M. Never a lower-case version. At this
; point in the processing, we don't care about whether N or M is upper,
; we do truncation tests later. So, let's just perform the same == test
; but in a case-insensitive way instead
cp (hl)
ret ; whether we match or not, the result of Z is
; the good one.
expectsBIT:
ld a, (hl)
cp 'N'
inc hl
ld a, (hl)
dec hl
cp 8
jr c, .isBit ; A < 8
; not a bit
or a ; unset Z
ret
isBit:
cp a ; set Z
ret
notNumber:
; A bit of a delicate situation here: we want A to go in H but also
; (HL) to go in A. If not careful, we overwrite each other. EXX is
; necessary to avoid invoving other registers.
push hl
exx
ld h, a
push hl
exx
ld a, (hl)
pop hl
call findInGroup
pop hl
ret nz
; we found our group? let's write down its "value" in (HL+1). We hold
; this value in A at the moment.
inc hl
ld (hl), a
dec hl
ret
; *** Special opcodes ***
; The special upcode handling routines below all have the same signature.
; Instruction row is at IX and we're expected to perform the same task as
; spitUpcode. The number of bytes, however, must go in C instead of A
; No need to preserve HL, DE, BC and IX: it's handled by spitUpcode already.
; Handle like a regular "JP (IX+d)" except that we refuse any displacement: if
; a displacement is specified, we error out.
handleJPIXY:
ld a, (INS_CURARG1+1)
or a ; numerical argument *must* be zero
jr nz, .error
; ok, we're good
ld a, 0xe9 ; second upcode
ld (INS_UPCODE), a
ld c, 1
ret
error:
ld c, 0
ret
handleBITR:
ld b, 0b01000000
jr _handleBITR
handleSETR:
ld b, 0b11000000
jr _handleBITR
handleRESR:
ld b, 0b10000000
_handleBITR:
; get group value
ld a, (INS_CURARG2+1) ; group value
ld c, a
; write first upcode
ld a, 0xcb ; first upcode
ld (INS_UPCODE), a
; get bit value
ld a, (INS_CURARG1+1) ; 0-7
rlca ; clears cary if any
rla
rla
; Now we have group value in stack, bit value in A (properly shifted)
; and we want to OR them together
or c ; Now we have our ORed value
or b ; and with our "base" value and we're good!
ld (INS_UPCODE+1), a
ld c, 2
ret
handleIM:
ld a, (INS_CURARG1+1)
cp 0
jr z, .im0
cp 1
jr z, .im1
cp 2
jr z, .im2
; error
ld c, 0
ret
im0:
ld a, 0x46
jr .proceed
im1:
ld a, 0x56
jr .proceed
im2:
ld a, 0x5e
proceed:
ld (INS_UPCODE+1), a
ld a, 0xed
ld (INS_UPCODE), a
ld c, 2
ret
handleLDIXYn:
ld a, 0x36 ; second upcode
ld (INS_UPCODE), a
ld a, (INS_CURARG1+1) ; IXY displacement
ld (INS_UPCODE+1), a
ld a, (INS_CURARG2+1) ; N
ld (INS_UPCODE+2), a
ld c, 3
ret
handleLDIXYr:
ld a, (INS_CURARG2+1) ; group value
or 0b01110000 ; second upcode
ld (INS_UPCODE), a
ld a, (INS_CURARG1+1) ; IXY displacement
ld (INS_UPCODE+1), a
ld c, 2
ret
handleLDrIXY:
ld a, (INS_CURARG1+1) ; group value
rlca \ rla \ rla
or 0b01000110 ; second upcode
ld (INS_UPCODE), a
ld a, (INS_CURARG2+1) ; IXY displacement
ld (INS_UPCODE+1), a
ld c, 2
ret
handleLDrr:
; first argument is displaced by 3 bits, second argument is not
; displaced and we or that with a leading 0b01000000
ld a, (INS_CURARG1+1) ; group value
rlca
rla
rla
ld c, a ; store it
ld a, (INS_CURARG2+1) ; other group value
or c
or 0b01000000
ld (INS_UPCODE), a
ld c, 1
ret
handleRST:
ld a, (INS_CURARG1+1)
; verify that A is either 0x08, 0x10, 0x18, 0x20, 0x28, 0x30 or 0x38.
; Good news: the relevant bits (bits 5:3) are already in place. We only
; have to verify that they're surrounded by zeroes.
ld c, 0b11000111
and c
jr nz, .error
; We're in range. good.
ld a, (INS_CURARG1+1)
or c
ld (INS_UPCODE), a
ld c, 1
ret
error:
ld c, 0
ret
; Compute the upcode for argspec row at (IX) and arguments in curArg{1,2} and
; writes the resulting upcode to IO.
; A is zero, with Z set, on success. A is non-zero, with Z unset, on error.
spitUpcode:
push de
push hl
push bc
; before we begin, are we in a 'l' argspec? Is it flagged for IX/IY
; acceptance? If yes, a 'x' or 'y' instruction? Check this on both
; args and if we detect a 'x' or 'y', things are *always* the same:
; the upcode is exactly the same as its (HL) counterpart except that
; it is preceeded by 0xdd or 0xfd. If we're 'x' or 'y', then it means
; that we've already been matched to a 'l' argspec, so after spitting
; 0xdd or 0xfd, we can continue as normal.
ld a, (ix+1)
call checklxy
jr z, .isl
ld a, (ix+2)
call checklxy
jr nz, .begin ; no point in checking further.
isl:
ld a, (INS_CURARG1)
cp 'x'
jr z, .isx
cp 'y'
jr z, .isy
ld a, (INS_CURARG2)
cp 'x'
jr z, .isx
cp 'y'
jr z, .isy
jr .begin
isx:
ld a, 0xdd
call ioPutB
jr .begin
isy:
ld a, 0xfd
call ioPutB
begin:
; Are we a "special instruction"?
bit 5, (ix+3)
jr z, .normalInstr ; not set: normal instruction
; We are a special instruction. Fetch handler (little endian, remember).
ld l, (ix+4)
ld h, (ix+5)
call callHL
; We have our result written in INS_UPCODE and C is set.
jp .writeIO
normalInstr:
; we begin by writing our "base upcode", which can be one or two bytes
ld a, (ix+4) ; first upcode
ld (INS_UPCODE), a
; from this point, DE points to "where we are" in terms of upcode
; writing.
ld de, INS_UPCODE+1
ld c, 1 ; C holds our upcode count
; Now, let's determine if we have one or two upcode. As a general rule,
; we simply have to check if (ix+5) == 0, which means one upcode.
; However, some two-upcodes instructions have a 0 (ix+5) because they
; expect group OR-ing into it and all other bits are zero. See "RLC r".
; To handle those cases, we *also* check for Bit 6 in (ix+3).
ld a, (ix+5) ; second upcode
or a ; do we have a second upcode?
jr nz, .twoUpcodes
bit 6, (ix+3)
jr z, .onlyOneUpcode ; not set: single upcode
twoUpcodes:
; we have two upcodes
ld (de), a
inc de
inc c
onlyOneUpcode:
; now, let's see if we're dealing with a group here
ld a, (ix+1) ; first argspec
call isGroupId
jr z, .firstArgIsGroup
; First arg not a group. Maybe second is?
ld a, (ix+2) ; 2nd argspec
call isGroupId
jr nz, .writeExtraBytes ; not a group? nothing to do. go to
; next step: write extra bytes
; Second arg is group
ld hl, INS_CURARG2
jr .isGroup
firstArgIsGroup:
ld hl, INS_CURARG1
isGroup:
; A is a group, good, now let's get its value. HL is pointing to
; the argument. Our group value is at (HL+1).
inc hl
ld a, (hl)
; Now, we have our arg "group value" in A. Were going to need to
; displace it left by the number of steps specified in the table.
push af
ld a, (ix+3) ; displacement bit
and 0xf ; we only use the lower nibble.
ld b, a
pop af
call rlaX
; At this point, we have a properly displaced value in A. We'll want
; to OR it with the opcode.
; However, we first have to verify whether this ORing takes place on
; the second upcode or the first.
bit 6, (ix+3)
jr z, .firstUpcode ; not set: first upcode
or (ix+5) ; second upcode
ld (INS_UPCODE+1), a
jr .writeExtraBytes
firstUpcode:
or (ix+4) ; first upcode
ld (INS_UPCODE), a
jr .writeExtraBytes
writeExtraBytes:
; Good, we are probably finished here for many primary opcodes. However,
; some primary opcodes take 8 or 16 bit constants as an argument and
; if that's the case here, we need to write it too.
; We still have our instruction row in IX and we have DE pointing to
; where we should write next (which could be the second or the third
; byte of INS_UPCODE).
ld a, (ix+1) ; first argspec
ld hl, INS_CURARG1
call checkNOrM
jr z, .withWord
call checknm
jr z, .withByte
ld a, (INS_CURARG1)
call checkxy
jr z, .withByte
ld a, (ix+2) ; second argspec
ld hl, INS_CURARG2
call checkNOrM
jr z, .withWord
call checknm
jr z, .withByte
ld a, (INS_CURARG2)
call checkxy
jr z, .withByte
; nope, no number, alright, we're finished here
jr .writeIO
withByte:
inc hl
; HL points to our number (LSB), with (HL+1) being our MSB which should
; normally by zero. However, if our instruction is jr or djnz, that
; number is actually a 2-bytes address that has to be relative to PC,
; so it's a special case. Let's check for this special case.
bit 7, (ix+3)
jr z, .absoluteValue ; bit not set? regular byte value,
; Our argument is a relative address ("e" type in djnz and jr). We have
; to subtract PC from it.
; First, check whether we're on first pass. If we are, skip processing
; below because not having real symbol value makes relative address
; verification falsely fail.
inc c ; one extra byte is written
call zasmIsFirstPass
jr z, .writeIO
; We're on second pass
push de ; Don't let go of this, that's our dest
push hl
call zasmGetPC ; --> HL
ex de, hl
pop hl
call intoHL
dec hl ; what we write is "e-2"
dec hl
call subDEFromHL
pop de ; Still have it? good
; HL contains our number and we'll check its bounds. If It's negative,
; H is going to be 0xff and L has to be >= 0x80. If it's positive,
; H is going to be 0 and L has to be < 0x80.
ld a, l
cp 0x80
jr c, .skipHInc ; a < 0x80, H is expected to be 0
; A being >= 0x80 is only valid in cases where HL is negative and
; within bounds. This only happens is H == 0xff. Let's increase it to 0.
inc h
skipHInc:
; Let's write our value now even though we haven't checked our bounds
; yet. This way, we don't have to store A somewhere else.
ld (de), a
ld a, h
or a ; cp 0
jr nz, .numberTruncated ; if A is anything but zero, we're out
; of bounds.
jr .writeIO
absoluteValue:
; verify that the MSB in argument is zero
inc hl ; MSB is 2nd byte
ld a, (hl)
dec hl ; HL now points to LSB
or a ; cp 0
jr nz, .numberTruncated
push bc
ldi
pop bc
inc c
jr .writeIO
withWord:
inc hl ; HL now points to LSB
; Clear to proceed. HL already points to our number
push bc
ldi ; LSB written, we point to MSB now
ldi ; MSB written
pop bc
inc c ; two extra bytes are written
inc c
; to writeIO
writeIO:
; Before we write IO, let's check a very specific case: is our first
; upcode 0xcb and our byte count == 3? If yes, then swap the two last
; bytes. In all instructions except 0xcb ones, IX/IY displacement comes
; last, but in all 0xcb instructions, they come 2nd last.
call .checkCB
; Let's write INS_UPCODE to IO
dec c \ inc c ; is C zero?
jr z, .numberTruncated
ld b, c ; save output byte count
ld hl, INS_UPCODE
loopWrite:
ld a, (hl)
call ioPutB
jr nz, .ioError
inc hl
djnz .loopWrite
cp a ; ensure Z
jr .end
numberTruncated:
; Z already unset
ld a, ERR_OVFL
jr .end
ioError:
; Z already unset
ld a, SHELL_ERR_IO_ERROR
; continue to .end
end:
pop bc
pop hl
pop de
ret
checkCB:
ld a, (INS_UPCODE)
cp 0xcb
ret nz
ld a, c
cp 3
ret nz
; We are in 0xcb + displacement situation. Swap bytes 2 and 3.
ld a, (INS_UPCODE+1)
ex af, af'
ld a, (INS_UPCODE+2)
ld (INS_UPCODE+1), a
ex af, af'
ld (INS_UPCODE+2), a
ret
; Parse argument in (HL) and place it in (IX)
; Sets Z on success, reset on error.
processArg:
call parseArg
cp 0xff
jr z, .error
ld (ix), a
; When A is a number, DE is set with the value of that number. Because
; We don't use the space allocated to store those numbers in any other
; occasion, we store DE there unconditonally, LSB first.
ld (ix+1), e
ld (ix+2), d
cp a ; ensure Z
ret
error:
ld a, ERR_BAD_ARG
or a ; unset Z
ret
; Parse instruction specified in A (I_* const) with args in I/O and write
; resulting opcode(s) in I/O.
; Sets Z on success. On error, A contains an error code (ERR_*)
parseInstruction:
push bc
push hl
push de
; A is reused in .matchPrimaryRow but that register is way too changing.
; Let's keep a copy in a more cosy register.
ld c, a
xor a
ld (INS_CURARG1), a
ld (INS_CURARG2), a
call readWord
jr nz, .nomorearg
ld ix, INS_CURARG1
call processArg
jr nz, .end ; A is set to error, Z is unset
call readComma
jr nz, .nomorearg
call readWord
jr nz, .badfmt
ld ix, INS_CURARG2
call processArg
jr nz, .end ; A is set to error, Z is unset
nomorearg:
; Parsing done, no error, let's move forward to instr row matching!
; To speed up things a little, we use a poor man's indexing. Full
; bisecting would involve too much complexity.
ld a, c ; recall A param
ld ix, instrTBl
cp I_EX
jr c, .loop
ld ix, instrTBlEX
cp I_LD
jr c, .loop
ld ix, instrTBlLD
cp I_RET
jr c, .loop
ld ix, instrTBlRET
loop:
ld a, c ; recall A param
call .matchPrimaryRow
jr z, .match
ld de, INSTR_TBL_ROWSIZE
add ix, de
ld a, 0xff
cp (ix)
jr nz, .loop
; No signature match
ld a, ERR_BAD_ARG
or a ; unset Z
jr .end
match:
; We have our matching instruction row. We're getting pretty near our
; goal here!
call spitUpcode
jr .end ; Z and A set properly, even on error
badfmt:
; Z already unset
ld a, ERR_BAD_FMT
end:
pop de
pop hl
pop bc
ret
; Compare primary row at (IX) with ID in A. Sets Z flag if there's a match.
matchPrimaryRow:
cp (ix)
ret nz
; name matches, let's see the rest
ld hl, INS_CURARG1
ld a, (ix+1)
call matchArg
ret nz
ld hl, INS_CURARG2
ld a, (ix+2)
jp matchArg
; In instruction metadata below, argument types arge indicated with a single
; char mnemonic that is called "argspec". This is the table of correspondence.
; Single letters are represented by themselves, so we don't need as much
; metadata.
; Special meaning:
; 0 : no arg
; 1-10 : group id (see Groups section)
; 0xff: error
; argspecs not in the list:
; n -> N
; N -> NN
; m -> (N) (running out of mnemonics. 'm' for 'memory pointer')
; M -> (NN)
; Groups
; Groups are specified by strings of argspecs. To facilitate jumping to them,
; we have a fixed-sized table. Because most of them are 2 or 4 bytes long, we
; have a table that is 4 in size to minimize consumed space. We treat the two
; groups that take 8 bytes in a special way.
;
; The table below is in order, starting with group 0x01
argGrpTbl:
.db "bdha" ; 0x01
.db "ZzC=" ; 0x02
.db "bdhs" ; 0x03
.db "bdXs" ; 0x04
.db "bdYs" ; 0x05
; SPECIAL GROUP "BIT": 0xc
; When special group "0xc" shows up in argspec, it means: accept a number
; between 0 and 7. The value is then treated like a regular group value.
; This is a list of all supported instructions. Each row represent a combination
; of instr/argspecs (which means more than one row per instr). Format:
;
; 1 byte for the instruction ID
; 1 byte for arg constant
; 1 byte for 2nd arg constant
; 1 byte displacement for group arguments + flags
; 2 bytes for upcode (2nd byte is zero if instr is one byte)
;
; An "arg constant" is a char corresponding to either a row in argspecTbl or
; a group index in argGrpTbl (values < 0x10 are considered group indexes).
;
; The displacement bit is split in 2 nibbles: lower nibble is the displacement
; value, upper nibble is for flags:
;
; Bit 7: indicates that the numerical argument is of the 'e' type and has to be
; decreased by 2 (djnz, jr).
; Bit 6: it indicates that the group argument's value is to be placed on the
; second upcode rather than the first.
; Bit 5: Indicates that this row is handled very specially: the next two bytes
; aren't upcode bytes, but a routine address to call to handle this case with
; custom code.
; Bit 4: When in an 'l' argspec, this means "I accept IX and IY variants".