;;; -*- 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 . ;; StackCheck: ;; ;; Throw an error if the stack pointer is dangerously low. Note that ;; we are assuming it is valid to treat all such errors as line errors ;; (currently, the only case when a stack overflow is even conceivable ;; is in argument expressions.) ;; ;; Destroys: ;; - F StackCheck: push hl ld hl,10000h - 0FEA6h ; leave at least 64 bytes of stack ; free add hl,sp pop hl ret c Error_ExpressionOverflow: ld hl,emsg_StackOverflow ;; fall through ;; ThrowLineError: ;; ;; Throw an error which is associated with part of the program code. ;; If the error occurs while we are assembling, we automatically ;; "Goto" the relevant part of the code. ;; ;; Input: ;; - HL = message format string ;; - DE = format parameter ThrowLineError: ld a,E_AppErr1 | 80h jr ThrowError ;; ThrowGeneralError: ;; ;; Throw a general error (one which is not associated with a ;; particular part of the program code.) ;; ;; Input: ;; - HL = message format string ;; - DE = format parameter ThrowGeneralError: ld a,E_AppErr1 & 7Fh ThrowError: ld (customErrorStr),hl ld (customErrorParam),de BCALL _JError ;; UNREACHABLE ;; CompStrsN: ;; ;; Compare two strings. ;; ;; Input: ;; - HL = address of first string ;; - DE = address of second string ;; - B = number of bytes to compare ;; ;; Output: ;; - Z if strings are identical in the first B bytes ;; - If strings match, B = 0, and HL and DE advanced by B bytes ;; ;; Destroys: ;; - AF, B, DE, HL CompStrsN: ld a,(de) cp (hl) inc de inc hl ret nz djnz CompStrsN ret ;; CompareWords: ;; ;; Compare two strings, ignoring case. (abc is considered equal to ;; ABC.) The first string must be 0-terminated; the second may be ;; terminated by a whitespace or other non-word-constituent character. ;; ;; Non-letters come before letters; underscore comes before ;; everything. ;; ;; Input: ;; - HL = address of first string (zero-terminated) ;; - DE = address of second string (terminated by 0 or any non-word character) ;; ;; Output: ;; - Zero flag set (and carry flag reset) if two strings are equal ;; - Carry flag set if string at HL is alphabetically earlier than the ;; string at DE ;; - If strings are not equal, HL and DE are set to the respective ;; addresses of the first byte that differs. ;; ;; Destroys: ;; - AF, B CompareWords: push de push hl jr CompareWords_Begin CompareWords_CharsEqual: or a jr z,CompareWords_Done CompareWords_NextChar: inc de inc hl CompareWords_Begin: ld a,(de) call IsWordChar jr nc,CompareWords_NotEndOfWord xor a CompareWords_NotEndOfWord: cp (hl) jr z,CompareWords_CharsEqual call CompareStrings_Norm ld b,a ld a,(hl) call CompareStrings_Norm cp b jr z,CompareWords_NextChar CompareWords_Done: pop hl pop de ret CompareStrings_Norm: or a ret z sub '_' - 1 ret c cp 1 ret z sub 20h ret ;; SignedDiv_HL_DE: ;; ;; Divide (signed) HL by DE. Throw an error if DE = 0. ;; ;; Input: ;; - HL = numerator ;; - DE = denominator ;; ;; Output: ;; - DE = quotient (rounded towards -infinity) ;; - HL = remainder (same sign as denominator) ;; ;; Destroys: ;; - AF SignedDiv_HL_DE: ld a,d or e jr z,Error_DivideBy0_IfNotFirstPass push bc ;; check if DE < 0 ld a,d add a,a sbc a,a and 41h ld c,a jr z,SignedDiv_HL_DE_DenPos ;; negate DE ex de,hl call NegHL ex de,hl SignedDiv_HL_DE_DenPos: ;; C = 00 if d >= 0, 41 if d < 0 ;; check if HL < 0 ld a,h add a,a jr nc,SignedDiv_HL_DE_NumPos ;; negate HL call NegHL inc c SignedDiv_HL_DE_NumPos: ;; C = 00 if n >= 0 and d >= 0, 01 if n < 0 and d >= 0, ;; 41 if n >= 0 and d < 0, 42 if n < 0 and d < 0 push bc call Div_HL_DE ld b,a ; BC = quotient ; HL = remainder pop af ; CF set if n * d < 0, ZF set if d < 0 ;; n > 0, d > 0 -> q = (n/d), r = (n%d) ;; n < 0, d > 0 -> q = -(-n/d), r = 0 ;; or q = -(-n/d) - 1, r = -(-n%d) + d ;; n > 0, d < 0 -> q = -(n/-d), r = 0 ;; or q = -(n/-d) - 1, r = (n%-d) + d ;; n < 0, d < 0 -> q = (-n/-d), r = -(-n%-d) jr nc,SignedDiv_HL_DE_QuotientPos push af ;; negate BC xor a sub c ld c,a sbc a,a sub b ld b,a ;; if remainder nonzero, negate mod DE (and decrement quotient) ld a,h or l jr z,SignedDiv_HL_DE_QuotientNeg_Exact ex de,hl sbc hl,de dec bc SignedDiv_HL_DE_QuotientNeg_Exact: pop af SignedDiv_HL_DE_QuotientPos: jr nz,SignedDiv_HL_DE_RemainderPos ;; negate HL call NegHL SignedDiv_HL_DE_RemainderPos: ld d,b ld e,c pop bc ret Error_DivideBy0_IfNotFirstPass: ld a,(asmPassNumber) dec a ret z ld hl,emsg_DivideBy0 call ThrowLineError ;; UNREACHABLE ;; Div_HL_DE: ;; ;; Divide (unsigned) HL by DE. ;; ;; Input: ;; - HL = numerator ;; - DE = denominator ;; ;; Output: ;; - AC = quotient ;; - HL = remainder ;; ;; Destroys: ;; - F, B Div_HL_DE: ld a,h ld c,l Div_AC_DE: ld b,17 ld hl,0 dec c Div_AC_DE_Loop1: inc c dec b ret z Div_AC_DE_Loop2: sla c rla adc hl,hl sbc hl,de jr nc,Div_AC_DE_Loop1 add hl,de djnz Div_AC_DE_Loop2 ret ;; Mul_HL_DE: ;; ;; Multiply HL by DE. ;; ;; Input: ;; - HL = first number ;; - DE = second number ;; ;; Output: ;; - HL = product ;; ;; Destroys: ;; - AF, BC Mul_HL_DE: ld a,h ld c,l Mul_AC_DE: ld b,17 ld hl,0 Mul_AC_DE_Loop1: dec b ret z Mul_AC_DE_Loop2: add hl,hl sla c rla jr nc,Mul_AC_DE_Loop1 add hl,de djnz Mul_AC_DE_Loop2 ret ;; Call_DE: ;; ;; Call DE. ;; ;; Input: ;; - DE = address to be called Call_DE: push de ; SETRETURN ret ;; Call_IX: ;; ;; Call IX. ;; ;; Input: ;; - IX = address to be called Call_IX: jp (ix) ;; CreateVarCheckDup: ;; ;; Create a program or appvar; if a variable already exists with the ;; same name, delete it first. ;; ;; Input: ;; - DE = address of variable name ;; - HL = size of variable ;; ;; Output: ;; - OP4 = variable name ;; - HL = address of variable's VAT entry ;; - DE = address of start of variable data (following length word) ;; - BC = size of variable ;; ;; Destroys: ;; - AF, IX ;; - OP1, OP2 CreateVarCheckDup: ex de,hl push de call DelVarIfExists pop hl CreateVarNoCheckDup: push hl ld a,(OP1) BCALL _CreateVar pop bc inc de inc de ret ;; DoInsertMem: ;; ;; Insert memory, if there's enough. If there isn't enough, throw an ;; error. ;; ;; Input: ;; - BC = number of bytes to allocate ;; - HL = address to insert memory (all pointers >= this address will ;; be moved forwards) ;; ;; Output: ;; - DE = address of newly-inserted memory ;; ;; Destroys: ;; - AF, HL ;; - (insDelPtr) DoInsertMem: ld (insDelPtr),hl push bc ld h,b ld l,c BCALL _ErrNotEnoughMem ld hl,(insDelPtr) ex de,hl BCALL _InsertMem pop bc ret ;; DelVarIfExists: ;; ;; Delete a variable if it exists. ;; ;; Input: ;; - HL = address of variable name ;; ;; Output: ;; - OP1 = variable name ;; ;; Destroys: ;; - AF, BC, DE, HL, IX DelVarIfExists: rst rMOV9TOOP1 DelVarIfExists_Loop: BCALL _ChkFindSym ret c BCALL _DelVarArc jr DelVarIfExists_Loop ;; ArcUnarcVar: ;; ;; Archive or unarchive a variable. (If garbage collection is needed, ;; textShadow will be redisplayed afterwards, so we clear it here, and ;; also redisplay the current screen buffer after archiving if we are ;; successful.) ;; ;; Input: ;; - HL = address of variable name ;; ;; Destroys: ;; - AF, BC, DE, HL, IX (?) ;; - OP1, OP3 ;; - textShadow ;; - other RAM areas? ArcUnarcVar: rst rMOV9TOOP1 BCALL _ClrTxtShd BCALL _Arc_Unarc jq_ XBufCpy ;; ChkFindSymVarDataStart: ;; ;; Search for a variable on the calculator; return the actual start of ;; the file's data, if it exists. ;; ;; Input: ;; - OP1 = variable name ;; ;; Output: ;; - Carry flag set if variable doesn't exist ;; - AHL = address of file's data (address of the length word, if a ;; program/appvar) ;; ;; Destroys: ;; - F, B, DE ChkFindSymVarDataStart: BCALL _ChkFindSym ret c ;; fall through ;; GetVarDataStart: ;; ;; Find the actual start of a file's data (skipping over the archive ;; header if any.) ;; ;; Input: ;; - HL = address of type byte of VAT entry ;; ;; Output: ;; - AHL = address of file's data (address of the length word, if a ;; program/appvar) ;; ;; Destroys: ;; - F, B, DE GetVarDataStart: dec hl dec hl dec hl ld e,(hl) dec hl ld d,(hl) dec hl ld a,(hl) ex de,hl or a ret z ld de,9 call Add_AHL_DE ; skip to name length call Load_DE_AHL ; E = name length, AHL -> start of name ld d,0 ;; fall through ;; Add_AHL_DE: ;; ;; Add an unsigned 16-bit offset to absolute address AHL. ;; ;; Input: ;; - AHL = absolute address ;; - DE = offset ;; ;; Output: ;; - AHL = adjusted address ;; ;; Destroys: ;; - F Add_AHL_DE: bit 7,h add hl,de ret nz jr c,Add_AHL_DE_Adjust bit 7,h ret z Add_AHL_DE_Adjust: push bc ld b,a ld c,40h ld a,h sub c Add_AHL_DE_Loop: inc b ld h,a sub c cp c jr nc,Add_AHL_DE_Loop ld a,b pop bc or a ret ;; Add_AHL_2: ;; ;; Add 2 to absolute address AHL. ;; ;; Input: ;; - AHL = absolute address ;; ;; Output: ;; - AHL = increased by 2 ;; ;; Destroys: ;; - F Add_AHL_2: call Inc_AHL ;; fall through ;; Inc_AHL: ;; ;; Increment absolute address AHL. ;; ;; Input: ;; - AHL = absolute address ;; ;; Output: ;; - AHL = incremented ;; ;; Destroys: ;; - F Inc_AHL: bit 7,h inc hl ret nz bit 7,h ret z inc a ld h,40h ret ;; Dec_AHL: ;; ;; Decrement absolute address AHL. ;; ;; Input: ;; - AHL = absolute address ;; ;; Output: ;; - AHL = decremented ;; ;; Destroys: ;; - F ; Dec_AHL: ; bit 7,h ; dec hl ; ret nz ; bit 6,h ; ret nz ; dec a ; ld h,7Fh ; ret ;; Load_A_AHL: ;; ;; Read a byte from memory. ;; ;; Input: ;; - AHL = absolute address ;; ;; Output: ;; - A = value read ;; ;; Destroys: ;; - F ;; - ramCode Load_A_AHL: push bc call Load_B_AHL ld a,b pop bc ret ;; Load_B_AHL: ;; ;; Read a byte from memory. ;; ;; Input: ;; - AHL = absolute address ;; ;; Output: ;; - B = value read ;; ;; Destroys: ;; - F ;; - ramCode Load_B_AHL: ld b,(hl) bit 7,h ret nz Load_B_AHL_Flash: RAM_CODE_BEGIN Load_B_AHL_end out (6),a ld b,(hl) ret Load_B_AHL_end: ;; Load_B_DE_AHL: ;; ;; Read three bytes from memory. ;; ;; Input: ;; - AHL = absolute address of first byte ;; ;; Output: ;; - AHL = address of third byte ;; - B = first byte ;; - E = second byte ;; - D = third byte ;; ;; Destroys: ;; - F ;; - ramCode Load_B_DE_AHL: call Load_B_AHL call Inc_AHL ;; fall through ;; Load_DE_AHL: ;; ;; Read a little-endian word from memory. ;; ;; Input: ;; - AHL = absolute address of least significant byte ;; ;; Output: ;; - AHL = address of most significant byte ;; - DE = value read ;; ;; Destroys: ;; - F ;; - ramCode Load_DE_AHL: bit 7,h jr z,Load_DE_AHL_FromFlash ld e,(hl) inc hl ld d,(hl) ret Load_DE_AHL_FromFlash: RAM_CODE_BEGIN Load_DE_AHL_end out (6),a ld e,(hl) inc hl bit 7,h jr z,Load_DE_AHL_NoPageFlip inc a out (6),a ld h,40h Load_DE_AHL_NoPageFlip: ld d,(hl) ret Load_DE_AHL_end: ;; FlashToRAM: ;; ;; Copy data from Flash (or RAM) to RAM. ;; ;; Input: ;; - AHL = address of data to be copied ;; - DE = buffer to place received data ;; - BC = number of bytes to copy (must be nonzero) ;; ;; Output: ;; - AHL = address of data following the input ;; - DE = end of output buffer ;; - BC = 0 ;; ;; Destroys: ;; - F (carry flag preserved) ;; - ramCode FlashToRAM: bit 7,h jr z,FlashToRAM_FromFlash ldir ret FlashToRAM_FromFlash: RAM_CODE_BEGIN FlashToRAM_end FlashToRAM_SetPage: out (6),a FlashToRAM_Loop: ldi jp po,FlashToRAM_Done + ramCode - FlashToRAM_SetPage bit 7,h jr z,FlashToRAM_Loop ld h,40h inc a jr FlashToRAM_SetPage FlashToRAM_Done: bit 7,h ret z ld h,40h inc a ret FlashToRAM_end: ;; RAMCodeBegin: ;; ;; Copy code into the ramCode area and execute it. Do not call this ;; routine directly; use the RAM_CODE_BEGIN and RAM_CODE_END macros. ;; ;; Input: ;; - ((SP)) = length of code ;; - (SP) + 1 = code ;; - (SP + 2) = place to return when we're done RAMCodeBegin: ex (sp),hl push af push bc push de ld c,(hl) inc hl ld de,ramCode ; = 8100h ld b,e ld (RAMCodeStubTarget),de ldir pop de pop bc pop af pop hl jp RAMCodeCallNoSwitch ;; Page1Call: ;; ;; Call a routine on app page 1. ;; ;; Input: ;; - ((SP)) = address to call ;; - (SP + 2) = place to return when we're done Page1Call: ex (sp),hl push af push de ld de,RAMCodeStubTarget ldi ldi inc bc inc bc pop de pop af pop hl jp RAMCodeCall RAMCodeStub: push af RAMCodeP1Patch equ $ + RAMCodeCall - RAMCodeStub + 1 ld a,0 out (6),a pop af RAMCodeCallNoSwitch equ $ + RAMCodeCall - RAMCodeStub RAMCodeStubTarget equ $ + RAMCodeCall - RAMCodeStub + 1 call ramCode push af RAMCodeP0Patch equ $ + RAMCodeCall - RAMCodeStub + 1 ld a,0 out (6),a pop af ret ;; ShowNumberedMenuSwitch: ;; ;; Display a numbered menu (see ShowNumberedMenu), and then perform a ;; switch to jump to one of several cases based on which option was ;; chosen. ;; ;; Input: ;; - HL = address of menu structure ;; - (SP) = sequence of cases ;; ;; Destroys: ;; - AF, BC, DE, HL ;; - OP1-OP6 ;; - minPenCol ;; - Contents of LCD and saveSScreen ShowNumberedMenuSwitch: call ShowNumberedMenu ;; fall through ;; SwitchBegin: ;; ;; Check if A equals any of a series of values, and perform a ;; corresponding relative jump if so. ;; ;; Input: ;; - A = value to check ;; - (SP) = sequence of 'cases', each consisting of a byte value ;; followed by an unsigned PC displacement to jump to if that value ;; matches A; sequence is terminated by FF ;; ;; Output: ;; - If a case matches, zero flag is set and carry flag reset ;; ;; Destroys: ;; - F SwitchBegin: ex (sp),hl push bc ld c,a ld b,0FFh jr SwitchBegin_Start SwitchBegin_Loop: cp c jr z,SwitchBegin_Found inc hl SwitchBegin_Start: ld a,(hl) inc hl cp b jr nz,SwitchBegin_Loop ld a,c SwitchBegin_Done: pop bc ex (sp),hl ret SwitchBegin_Found: ld c,(hl) inc b add hl,bc jr SwitchBegin_Done ;; BufVPutHex16: ;; ;; Display a 16-bit number in hexadecimal. ;; ;; Input: ;; - BC = number to display ;; - (curScreenBuffer) = address of screen buffer ;; ;; Destroys: ;; - AF, B, DE, IX BufVPutHex16: call BufVPutHex8 ld b,c BufVPutHex8: ld a,b call HexHToASCII call BufVPutMap ld a,b call HexLToASCII call BufVPutMap ret ;; HexLToASCII: ;; HexHToASCII: ;; ;; Convert a nibble of A into an ASCII hex digit. ;; ;; Input: ;; - A = value ;; ;; Output: ;; - A = ASCII character ;; ;; Destroys: ;; - F HexHToASCII: rrca rrca rrca rrca HexLToASCII: or 0F0h ; F0 ... F9 / FA ... FF daa ; +50 ... +59 / +60 ... +65 add a,0A0h ; F0 ... F9 / +00 ... +05 adc a,40h ; +30 ... +39 / +41 ... +46 DummyRet: ret