;;; -*- TI-Asm -*-
;;;
;;; Mimas - Assembly language IDE for the TI-83 Plus
;;;
;;; Copyright (C) 2010 Benjamin Moody
;;;
;;; This program is free software: you can redistribute it and/or
;;; modify it under the terms of the GNU General Public License as
;;; published by the Free Software Foundation; either version 3 of the
;;; License, or (at your option) any later version.
;;;
;;; This program is distributed in the hope that it will be useful,
;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
;;; General Public License for more details.
;;;
;;; You should have received a copy of the GNU General Public License
;;; along with this program. If not, see .
;; ParseInstruction:
;;
;; Parse a string into an instruction. If successful, the output may
;; contain symbol references; the caller is responsible for either
;; storing the instruction in the program, or calling UnrefInstruction
;; to release those references.
;;
;; If an error occurs, any references that were created during parsing
;; will have been released; instrBuf will be set to a ref-neutral
;; value.
;;
;; Input:
;; - IX = address of ZT string to parse (must be in RAM)
;;
;; Output:
;; - Carry flag set if parsing fails
;; - IX = address of next character in string
;; - instrBuf contains parsed instruction
;;
;; Destroys:
;; - AF, BC, DE, HL
;; - OP1-OP6
;; - tempExprBuf
ParseInstruction:
;; Use tempExprBuf to store parsed (or partially-parsed)
;; expressions - if we are unable to parse the instruction
;; fully, any symbols referenced by tempExprBuf must be
;; unreffed
ld a,1
ld (tempExprLength),a
ld hl,ParseInstruction_CatchError
call APP_PUSH_ERRORH
call ParseInstructionMain
jr c,ParseInstruction_SyntaxError
call APP_POP_ERRORH
xor a
ret
ParseInstruction_CatchError:
call ParseInstruction_CleanUp
BCALL _JErrorNo
;; UNREACHABLE
ParseInstruction_SyntaxError:
call APP_POP_ERRORH
ParseInstruction_CleanUp:
ld hl,tempExprLength
ld c,(hl)
inc hl
call UnrefExprList
scf
;; fall through
;; ResetInstrBuf:
;;
;; Set instrBuf to a ref-neutral value (an empty comment).
;;
;; Destroys:
;; - A
ResetInstrBuf:
ld a,T_COMMENT
ld (instrBuf),a
ret
;;; main code ;;;
ParseInstruction_Comment:
push ix
pop de
inc de
;; omit an initial space if present (FormatInstruction always
;; puts a space after the semicolon in any case)
ld a,(de)
cp ' '
jr nz,ParseInstruction_Comment_NoSpace
inc de
ParseInstruction_Comment_NoSpace:
ld h,d
ld l,e
ld b,MAX_COMMENT_LENGTH
ParseInstruction_CommentLoop:
ld a,(hl)
or a
jr z,ParseInstruction_CommentDone
inc hl
djnz ParseInstruction_CommentLoop
ParseInstruction_CommentDone:
ld a,MAX_COMMENT_LENGTH
sub b
ld b,a
jr nz,ParseInstruction_CommentNonEmpty
ld hl,T_COMMENT
ld (instrBuf),hl
xor a
ret
ParseInstruction_CommentNonEmpty:
ld hl,instrBuf + 1
call PackCommentString
ld a,l
add a,T_COMMENT - low(instrBuf + 2)
ld (instrBuf),a
xor a
ret
ParseInstruction_Label:
push de
call NameToSymbolExpr
ParseInstruction_LabelError:
ld hl,emsg_ReservedName
call c,ThrowLineError
pop ix
call GetNextNonSpaceCharAfter
add a,-1
ret c
ld a,(tempExprLength)
add a,T_LABEL - 2
ld hl,instrBuf
ld (hl),a
ld hl,(tempExprBuf)
ld (instrBuf + 1),hl
ld a,l
sub X_PREV_ANON
cp 1
ret
ParseInstruction_EQU3:
inc de
inc de
ParseInstruction_EQU:
inc de
push de
call NameToSymbolExpr
jr c,ParseInstruction_LabelError
;; parse the equate value
pop ix
call ParseExprDefault
ret c
ld hl,S_EQU * 256 + T_SPECIAL
ld (instrBuf),hl
ld de,templ__n_n
jq_ ParseInstruction_CheckTemplateCopy
ParseInstructionMain:
;; find first non-space character on the line
call GetNextNonSpaceChar
cp Lsemicolon
jr z,ParseInstruction_Comment
push ix
call ParseSymbol
pop hl ; HL = start of first word on line
; IX = end of first word
ret c
;; check for label or EQU
push ix
call GetNextNonSpaceChar
ex (sp),ix
pop de ; DE = start of second word
cp ':'
jr z,ParseInstruction_Label
cp '='
jr z,ParseInstruction_EQU
push hl
ld hl,EQUStr
call CompareWords
pop hl
jr z,ParseInstruction_EQU3
;; normal instruction
ex de,hl
push ix
ld a,(ix)
push af
ld (ix),0
ld hl,normalMnemonics
ld bc,normalMnemonicsEnd
ld ix,SeekCompare_pMStr_pZStr
call BSearchS
jr nz,ParseInstruction_Special
pop af
pop ix
ld (ix),a
push hl
call ParseInstructionArgs
pop hl
ret c
ld a,l
sub low(normalMnemonics)
;; search for first instruction using this mnemonic
ld hl,normalInstructionMnemonicTable + 1
ld bc,I_last - 1
; ld e,a
; call BSearch1
cpir
dec hl
jr nz,ParseInstruction_InternalError
ParseInstruction_NormalLoop:
push hl
;; get corresponding template ptr
dec h ; -> normalInstructionTemplateHTable
ld d,(hl)
dec h ; -> normalInstructionTemplateLTable
ld e,(hl)
;; check if template matches the parsed arguments
call CheckExprTemplate
pop hl
jr z,ParseInstruction_NormalFound
;; any more instructions using same mnemonic?
ld a,(hl)
inc l
cp (hl)
jr z,ParseInstruction_NormalLoop
ParseInstruction_UnknownArguments:
ld hl,emsg_UnknownArguments
ParseInstruction_Error:
call ThrowLineError
;; UNREACHABLE
ParseInstruction_InternalError:
;; if we ever get here, it's a bug
BCALL _ErrSingularMat
;; UNREACHABLE
ParseInstruction_NormalFound:
ld a,l
ld (instrBuf + 1),a
xor a
ld (instrBuf),a
ParseInstruction_CopyNormalArgs:
ld de,instrBuf + 2
ld hl,(formatArgPtr0)
ld a,h
or l
jr z,ParseInstruction_NormalArgsDone
call CopyConstExpr
ld hl,(formatArgPtr1)
ld a,h
or l
jr z,ParseInstruction_NormalArgsDone
call CopyConstExpr
ld hl,(formatArgPtr2)
ld a,h
or l
call nz,CopyConstExpr
ParseInstruction_NormalArgsDone:
ld a,e
sub low(instrBuf + 2)
ld hl,instrBuf
xor (hl)
and 3Fh
xor (hl)
ld (hl),a
ret
ParseInstruction_Special:
ld hl,specialMnemonics
ld bc,specialMnemonicsEnd
call BSearchS
pop bc
pop ix
ld (ix),b
jr z,ParseInstruction_SpecialOK
ld hl,emsg_UnknownInstruction
jr ParseInstruction_Error
ParseInstruction_SpecialOK:
call GetNextNonSpaceChar
ld a,l
ld hl,S_BCALL * 256 + T_SPECIAL + 3
SWITCH_BEGIN
SWITCH_CASE low(specialMnemonics + smnem_BCALL), ParseInstruction_BCALL
SWITCH_CASE low(specialMnemonics + smnem_BJUMP), ParseInstruction_BJUMP
SWITCH_CASE low(specialMnemonics + smnem_DB), ParseInstruction_DB
SWITCH_CASE low(specialMnemonics + smnem_DW), ParseInstruction_DW
SWITCH_CASE low(specialMnemonics + smnem_BREAK), ParseInstruction_BREAK
SWITCH_CASE low(specialMnemonics + smnem_INCBIN), ParseInstruction_INCBIN_
SWITCH_CASE low(specialMnemonics + smnem_JQ), ParseInstruction_JQ
SWITCH_END
ld h,S_ALIGN
cp low(specialMnemonics + smnem_ALIGN)
jr z,ParseInstruction_SpecialOneArg
inc h ; S_ASSERT
cp low(specialMnemonics + smnem_ASSERT)
jr z,ParseInstruction_SpecialOneArg
inc h ; S_BLOCK
cp low(specialMnemonics + smnem_DS)
jr z,ParseInstruction_SpecialOneArg
ld h,S_ELSE
cp low(specialMnemonics + smnem_ELSE)
jr z,ParseInstruction_SpecialZeroArgs
inc h ; S_ENDIF
cp low(specialMnemonics + smnem_ENDIF)
jr z,ParseInstruction_SpecialZeroArgs
inc h ; S_IF
cp low(specialMnemonics + smnem_IF)
jr z,ParseInstruction_SpecialOneArg
inc h ; S_IFDEF
cp low(specialMnemonics + smnem_IFDEF)
jr z,ParseInstruction_SpecialSym
inc h ; S_IFNDEF
cp low(specialMnemonics + smnem_IFNDEF)
jr z,ParseInstruction_SpecialSym
inc h ; S_ORG
cp low(specialMnemonics + smnem_ORG)
jr z,ParseInstruction_SpecialOneArg
inc h ; S_RORG
cp low(specialMnemonics + smnem_RORG)
scf
ret nz
ParseInstruction_SpecialOneArg:
ld (instrBuf),hl
ParseInstruction_SpecialOneArg_OpSet:
ld de,templ__n
ParseInstruction_SpecialArgsSingle:
ld b,d
ld c,e
ParseInstruction_SpecialArgsDouble:
push bc
push de
call ParseInstructionArgs
pop de
pop bc
ret c
push bc
call CheckExprTemplate
pop de
jr z,ParseInstruction_CopyNormalArgs_
ld hl,instrBuf + 1
inc (hl)
ParseInstruction_CheckTemplateCopy:
call CheckExprTemplate
ParseInstruction_CopyNormalArgs_:
jq z,ParseInstruction_CopyNormalArgs
ParseInstruction_SpecialUnknownArguments:
jq_ ParseInstruction_UnknownArguments
ParseInstruction_SpecialZeroArgs:
ld (instrBuf),hl
ld de,templ_null
jr ParseInstruction_SpecialArgsSingle
ParseInstruction_SpecialSym:
call ParseInstruction_SpecialOneArg
ret c
ld a,(instrBuf+2)
and 0C0h
ret z
jr ParseInstruction_SpecialUnknownArguments
ParseInstruction_BJUMP:
inc h
ParseInstruction_BCALL:
ld (instrBuf),hl
push ix
pop hl
ld a,(hl)
call ParseSymbol
jr c,ParseInstruction_BCALL_BJUMP_Expr
ld a,(ix)
push af
ld (ix),0
call ROMCallNameToAddress
pop bc
ld (ix),b
jr nz,ParseInstruction_BCALL_BJUMP_Expr
ld (instrBuf + 3),hl
ld a,X_ROMCALL
ld (instrBuf + 2),a
or a
ret
ParseInstruction_BCALL_BJUMP_Expr:
push hl
pop ix
jr ParseInstruction_SpecialOneArg_OpSet
ParseInstruction_BREAK:
ld h,S_BREAK
ld de,templ_null
ld bc,templ__ccc
ParseInstruction_SpecialDouble:
ld (instrBuf),hl
jr ParseInstruction_SpecialArgsDouble
ParseInstruction_JQ:
ld h,S_JQ_n
ld de,templ__n
ld bc,templ__cc_n
jr ParseInstruction_SpecialDouble
ParseInstruction_DW:
ld h,S_WORD
ParseInstruction_DB_DW:
ld (instrBuf),hl
call ParseInstructionArgs
ret c
ParseInstruction_CopyAllArgs:
ld de,tempExprLength
ld a,(de)
ld l,a
ld h,0
add hl,de
ex de,hl ; DE = end of parsed exprs
inc hl ; HL = start of parsed exprs
push de
ld de,instrBuf + 2
ParseInstruction_CopyAllArgsLoop:
pop bc
or a
sbc hl,bc
add hl,bc
jq nc,ParseInstruction_NormalArgsDone
push bc
call CopyConstExpr
jr ParseInstruction_CopyAllArgsLoop
ParseInstruction_INCBIN_:
jr ParseInstruction_INCBIN
ParseInstruction_DB:
ld h,S_BYTE
ld a,(ix)
cp Lquote
jr nz,ParseInstruction_DB_DW
ld h,S_ASCII
ld (instrBuf),hl
inc ix
ld de,instrBuf + 2
ParseInstruction_ASCII_Loop:
ld a,(ix)
or a
scf
ret z
cp Lquote
jr z,ParseInstruction_ASCII_Done
call ParseQuotedChar
call CheckInstrBufOverflow
ld a,l
ld (de),a
inc de
jr ParseInstruction_ASCII_Loop
ParseInstruction_ASCII_Done:
call GetNextNonSpaceCharAfter
or a
jr z,ParseInstruction_ASCII_Finish
cp Lcomma
scf
ret nz
call GetNextNonSpaceCharAfter
cp '0'
scf
ret nz
call GetNextNonSpaceCharAfter
or a
scf
ret nz
ld a,S_ASCIZ
ld (instrBuf + 1),a
ParseInstruction_ASCII_Finish:
jq_ ParseInstruction_NormalArgsDone
ParseInstruction_INCBIN:
ld h,S_INCBIN
ld (instrBuf),hl
ld a,(ix)
cp Lquote
scf
ret nz
inc ix
push ix
pop de
push de
ld hl,prgmStr
ld b,4
call CompStrsN
jr z,ParseInstruction_INCBIN_Prgm
; ld hl,PicStr
; ld b,3
ld hl,tPic0 * 256 + tVarPict
ld (OP3),hl
ld hl,OP3
BCALL _Get_Tok_Strng
ld b,c
dec b
pop de
push de
call CompStrsN
jr nz,ParseInstruction_INCBIN_NotPic
ld a,(de)
cp '9'+1
jr nc,ParseInstruction_INCBIN_NotPic
cp '0'
jr c,ParseInstruction_INCBIN_NotPic
ld b,tPic0
jr z,ParseInstruction_INCBIN_Pic
add a,tPic1 - '1'
ld b,a
ParseInstruction_INCBIN_Pic:
inc de
ld a,(de)
cp Lquote
jr nz,ParseInstruction_INCBIN_NotPic
pop af
push de
pop ix
ld hl,tVarPict * 256 + PictObj
ld (instrBuf + 2),hl
ld de,instrBuf + 4
ld a,b
ld (de),a
inc de
ParseInstruction_INCBIN_Done:
call GetNextNonSpaceCharAfter
or a
scf
ret nz
jr ParseInstruction_ASCII_Finish
ParseInstruction_INCBIN_NotPic:
pop de
ld a,AppVarObj
ParseInstruction_INCBIN_Name:
ld de,instrBuf + 2
ld (de),a
inc de
ld b,9
ParseInstruction_INCBIN_NameLoop:
ld a,(ix)
or a
scf
ret z
cp Lquote
jr z,ParseInstruction_INCBIN_Done
call ParseQuotedChar
call CheckInstrBufOverflow
ld a,l
ld (de),a
inc de
djnz ParseInstruction_INCBIN_NameLoop
scf
ret
ParseInstruction_INCBIN_Prgm:
pop af
push de
pop ix
ld a,ProgObj
jr ParseInstruction_INCBIN_Name
;; CheckInstrBufOverflow:
;;
;; Throw an error if DE points to the end of instrBuf (i.e.,
;; instruction data is larger than 63 bytes.)
;;
;; Input:
;; - DE = output pointer
;;
;; Destroys:
;; - AF
CheckInstrBufOverflow:
ld a,e
cp low(instrBuf + 65)
ret nz
ld a,d
cp high(instrBuf + 65)
ret nz
ld hl,emsg_ExpressionTooComplex
call ThrowLineError
;; UNREACHABLE
;; ParseInstructionArgs:
;;
;; Parse a series of expressions separated by commas. The parsed
;; expressions are appended to the tempExprBuf.
;;
;; Input:
;; - IX = address of a zero-terminated string to parse
;;
;; Output:
;; - Carry flag set if parsing fails
;; - IX = address of next character in string
;; - tempExprBuf contains parsed expressions
;; - (tempExprLength) = length of parsed expressions + 1
;;
;; Destroys:
;; - AF, BC, DE, HL
;; - OP1-OP6
ParseInstructionArgs:
call GetNextNonSpaceChar
or a
ret z
push ix
pop hl
call ParseSymbol
jr c,ParseInstructionArgs_NotSysFlag
ld a,(ix)
or a
jr nz,ParseInstructionArgs_NotSysFlag
call SysFlagNameToCode
jr nz,ParseInstructionArgs_NotSysFlag
;; L = bit, H = offset
;; corresp. expression is , ( IY + )
ld de,tempExprLength
ld a,8
ld (de),a
inc de
ld a,l
ld (de),a
inc de
ld a,h
ld hl,templ__iIYpn + 1
ld bc,4 ; X_PAREN, X_ADD, X_REGVAL, X_REG_IY
ldir
ex de,hl
ld (hl),X_SYSFLAG
inc hl
ld (hl),a
or a
ret
ParseInstructionArgs_NotSysFlag:
push hl
pop ix
dec ix
ParseInstructionArgs_Loop:
inc ix
call ParseExprDefault
ret c
call GetNextNonSpaceChar
cp ','
jr z,ParseInstructionArgs_Loop
cp Lsemicolon
ret z
or a
ret z
scf
ret
;; CheckExprTemplate:
;;
;; Check if input expression list matches a given instruction
;; template.
;;
;; Input:
;; - DE = address of template (byte count followed by exprs)
;; - tempExprBuf = input expression list
;; - (tempExprLength) = input expression list byte count + 1
;;
;; Output:
;; - Zero flag set if expression matches template
;; - (formatArgPtr0) = address of first bytecode arg expression
;; - (formatArgPtr1) = address of second bytecode arg expression
;; - (formatArgPtr2) = address of third bytecode arg expression
;;
;; Destroys:
;; - AF, BC, DE, HL
CheckExprTemplate:
;; get template length
ld a,(de)
ld c,a
inc de
; ld hl,0
; ld (formatArgPtr0),hl
; ld (formatArgPtr1),hl
; ld (formatArgPtr2),hl
ld hl,formatArgPtr0
ld b,6
BCALL _ClrLp
ld hl,tempExprLength
ld b,(hl)
CheckExprTemplate_Next:
inc hl
CheckExprTemplate_Loop:
;; HL -> input expr
;; B = input expr byte count
;; DE -> template
;; C = template byte count
dec c
jr z,CheckExprTemplate_Finished
ld a,(de)
inc de
cp X_ARGVAL
jr z,CheckExprTemplate_GotArg
; cp X_ADD
; jr z,CheckExprTemplate_Sum
dec b
jr z,CheckExprTemplate_Failed
cp (hl)
jr z,CheckExprTemplate_Next
WARNING "FIXME: allow (IX), (IX-n), +c., for (IX+n)"
;; Allow AF in place of AF'
;; - template is X_REG_AF2
;; - actual data is X_REG_AF
cp X_REG_AF2
jr nz,CheckExprTemplate_NotAF2
ld a,(hl)
cp X_REG_AF
ret nz
jr CheckExprTemplate_Next
CheckExprTemplate_NotAF2:
;; Allow (HL) as a BCDEHLMA register argument
;; - template is X_REGVAL, X_ARGVAL, X_DEC6 + AC_BCDEHLMA + n
;; - actual data is X_PAREN, X_REGVAL, X_REG_HL
cp X_REGVAL
ret nz
ld a,b
cp 3
ret c
ld a,(hl)
cp X_PAREN
ret nz
inc hl
ld a,(hl)
cp X_REGVAL
ret nz
inc hl
ld a,(hl)
cp X_REG_HL
ret nz
dec hl
ld a,c
sub 3
ret c
inc a
ld c,a
ld a,(de)
inc de
cp X_ARGVAL
ret nz
ld a,(de)
inc de
push de
ld e,a
and AC_mask
cp AC_BCDEHLMA
jr nz,CheckExprTemplate_Failed1
push hl
ld hl,regihlbyte
jr CheckExprTemplate_ArgValueHL
CheckExprTemplate_Finished:
dec b
ret
; CheckExprTemplate_Sum:
; ;; Allow IX + a + b, etc. in place of IX + (a + b)
; ;; - template is X_ADD, X_REGVAL, X_REG_IX
; ;; - actual data is ( X_ADD | X_SUB ) * X_REGVAL, X_REG_IX
; push hl
; CheckExprTemplate_SumLoop:
; dec b
; jr z,CheckExprTemplate_Failed1
; ld a,(hl)
; inc hl
; sub X_ADD
; jr z,CheckExprTemplate_SumLoop
; dec a
; jr z,CheckExprTemplate_SumLoop
; cp X_REGVAL - X_SUB
; jr nz,CheckExprTemplate_Failed1
; dec c
; ld a,(de)
; inc de
; dec b
; jr z,CheckExprTemplate_Failed1
; cp (hl)
; inc hl
; jr nz,CheckExprTemplate_Failed1
CheckExprTemplate_Failed1:
pop de
CheckExprTemplate_Failed:
or 1
ret
CheckExprTemplate_GotArg:
dec c
jr z,CheckExprTemplate_Failed
ld a,(de)
inc de
push de
ld e,a ; E = argument type byte
; bits 0-1: argument #
; bits 2-5: argument category
and AC_mask
jr z,CheckExprTemplate_GotArgConstant
ld d,a ; D = argument category
;; register/condition argument
dec b
jr z,CheckExprTemplate_Failed1
inc b
ld a,(hl)
cp X_DEC6
jr c,CheckExprTemplate_Failed1
push hl
push bc
ld b,a ; B = input register #
ld a,d
rrca
ld d,a
rrca
add a,d ; A = argument category * 3/4
add a,low(argumentCategoryTable - 3)
ld l,a
ld h,high(argumentCategoryTable)
ld c,(hl) ; C = number of options in this category
inc hl
; call LdHLInd
ld a,(hl)
inc hl
ld h,(hl)
ld l,a ; HL -> list of options
ld a,b
ld b,0
cpir
pop bc
pop hl
jr z,CheckExprTemplate_ArgValueOK
cp X_REG_C
jr nz,CheckExprTemplate_Failed1
ld a,d
cp AC_ZCPS / 2
jr z,CheckExprTemplate_ArgValueCondC
cp AC_ZC / 2
jr nz,CheckExprTemplate_Failed1
CheckExprTemplate_ArgValueCondC:
push hl
ld hl,condcbyte
jr CheckExprTemplate_ArgValueHL
CheckExprTemplate_GotArgConstant:
;; constant argument
dec b
jr z,CheckExprTemplate_Failed1
inc b
ld a,(hl)
cp X_REGVAL
jr z,CheckExprTemplate_Failed1
; cp X_PAREN
; jr z,CheckExprTemplate_Failed1
CheckExprTemplate_ArgValueOK:
push hl
CheckExprTemplate_ArgValueHL:
ld a,e
and 3
jr z,CheckExprTemplate_ArgValue0
dec a
jr z,CheckExprTemplate_ArgValue1
ld (formatArgPtr2),hl
CheckExprTemplate_ArgValueDone:
pop hl
push bc
ld c,b
call SkipExprHL
ld b,c
pop de
ld c,e
pop de
jq_ CheckExprTemplate_Loop
CheckExprTemplate_ArgValue0:
ld (formatArgPtr0),hl
jr CheckExprTemplate_ArgValueDone
CheckExprTemplate_ArgValue1:
ld (formatArgPtr1),hl
jr CheckExprTemplate_ArgValueDone