;Utility routines ;TODO: this file really needs some serious cleanup (to remove unused code, if nothing else...we need all the space we can get) include "settings.inc" include "ti83plus.inc" include "equates.inc" SEGMENT Main GLOBALS ON Var progress,1 PutSAppCenter: push hl ld b,0 $$: ld a,(hl) inc hl inc b cp ' ' jr z,$F or a jr nz,$B $$: ld a,16 sub b srl a pop hl ld (curCol),a jr PutSApp VPutSAppCol: ld e,(hl) inc hl ld d,(hl) inc hl ld (penCol),de jr VPutSApp VPutSAppRow: ld a,(hl) inc hl ld (penRow),a jr VPutSAppCenter Mult16By8: ;A = operand 1 ;DE = operand 2 ;Output: HL = A * DE ld hl,0 Mult16By8_Loop: and 0FFh ret z bit 0,a jr z,$F add hl,de $$: sla e rl d srl a jr Mult16By8_Loop Div16By16: ;HL = numerator ;DE = denominator ;Outputs: DE = HL / DE ; HL = HL % DE ld a,d or e jr nz,$F ret $$: xor a ld ix,8251h ld (ix+0),l ld (ix+1),h ld h,a ld l,a ld (ix+2),a ld b,16 Div16By16_Loop2: sla (ix+0) rl (ix+1) rl l rl h rl (ix+2) or a sbc hl,de ld a,(ix+2) sbc a,0 ld (ix+2),a jp p,$F add hl,de ld a,(ix+2) adc a,0 ld (ix+2),a jr Div16By16_Loop $$: set 0,(ix+0) Div16By16_Loop: djnz Div16By16_Loop2 ld e,(ix+0) ld d,(ix+1) ret DisplayProgress: bit silentInstall,(iy+hookManFlags) ret nz ;A is percentage ;So 95*(A/100) push ix push de push hl push bc ld d,0 ld e,a ld a,95 call Mult16By8 ;HL = 95 * A ld de,100 call Div16By16 ld a,e pop bc pop hl pop de pop ix DisplayProgressRaw: ;A is column (0-95) ld (progress),a cp 95 jr c,$F ld a,95 $$: push bc push de push hl ld d,0 ld c,a and 0F8h srl a srl a srl a ;Fill in A bytes ld b,a ld hl,plotSScreen+(12*57) or a jr z,noFullBytes $$: ld (hl),0FFh inc hl inc d djnz $B noFullBytes: ld a,c and 7 jr z,calcDone ld b,a xor a $$: scf rra djnz $B ld (hl),a inc hl inc d calcDone: ld a,12 sub d jr z,calcDone2 $$: dec d jr z,$F ld (hl),0 inc hl jr $B calcDone2: $$: ld hl,plotSScreen+(12*57) ld de,plotSScreen+(12*58) ld b,12*7 $$: ld a,(hl) ld (de),a inc hl inc de djnz $B call fastCopy pop hl pop de pop bc ret MemClear: ld d,h ld e,l ld (hl),0 inc de dec bc ldir ret cphlde: push hl or a sbc hl,de pop hl ret DisplayPressAnyKey: ld hl,0007h ld (curRow),hl ld hl,sPressAnyKey jr PutSApp sPressAnyKey: DB "Press any key",0CEh,0 AnimateRunIndicator: push af push bc push de push hl push ix call animateRunIndic pop ix pop hl pop de pop bc pop af ret animateRunIndic: di ld a,2Bh B_CALL lcd_busy out (10h),a ld hl,indicBusy rrc (hl) ld c,(hl) ld b,8 ld d,80h animateLoop: ld a,d call outPort10h call LCDCommand7 B_CALL lcd_busy in a,(11h) B_CALL lcd_busy in a,(11h) ld e,a ld a,d call outPort10h call LCDCommand7 ld a,e rr c jr c,$F res 0,a jr animateDone $$: set 0,a animateDone: B_CALL lcd_busy out (11h),a inc d djnz animateLoop ret LCDCommand7: push af ld a,5 B_CALL lcd_busy out (10h),a pop af ret outPort10h: push af ld a,7 B_CALL lcd_busy out (10h),a pop af cp 80h ret c cp 0C0h ret nc B_CALL lcd_busy out (10h),a ret UnlockFlash: ;Unlocks Flash protection. ;Destroys: ; appBackUpScreen ; pagedCount ; pagedGetPtr ; arcInfo ; iMathPtr5 ; pagedBuf ; ramCode ld hl,UnlockFlashStart ld de,appBackUpScreen ld bc,UnlockFlashEnd-UnlockFlashStart ldir jp appBackUpScreen UnlockFlashStart: in a,(6) push af ld a,7Bh call translatePage-UnlockFlashStart+appBackUpScreen out (6),a ld hl,5092h ld e,(hl) inc hl ld d,(hl) inc hl ld a,(hl) call translatePage-UnlockFlashStart+appBackUpScreen out (6),a ex de,hl ld a,0CCh ld bc,0FFFFh cpir ld e,(hl) inc hl ld d,(hl) push de pop ix ld hl,9898h ld (hl),0C3h inc hl ld (hl),(returnPoint-UnlockFlashStart+appBackUpScreen) & 11111111b inc hl ld (hl),(returnPoint-UnlockFlashStart+appBackUpScreen) >> 8 ld hl,pagedBuf ld (hl),98h ld de,pagedBuf+1 ld bc,49 ldir ld (iMathPtr5),sp ld hl,(iMathPtr5) ld de,9A00h ld bc,50 ldir ld de,(iMathPtr5) ld hl,-16 add hl,de ld (iMathPtr5),hl di ld iy,0056h-25h ld a,50 ld (pagedCount),a ld a,8 ld (arcInfo),a jp (ix) translatePage: ld b,a in a,(2) and 80h jr z,$F in a,(21h) and 3 ld a,b ret nz and 3Fh ret $$: ld a,b and 1Fh ret returnPoint: ld iy,flags ld hl,(iMathPtr5) ld de,16 add hl,de ld sp,hl ex de,hl ld hl,9A00h ld bc,50 ldir pop af out (6),a ret UnlockFlashEnd: invert_lines: ld c,12 $$: ld a,(hl) cpl ld (hl),a inc hl dec c jr nz,$B djnz invert_lines ret SoftKey: ld a,(hl) inc hl push hl push af ld bc,7 ld de,95*256+7 B_CALL DarkLine ;top line ld b,17 ld d,b ld e,0 pop af rr a push af jr nc,$F B_CALL DarkLine $$: ld b,38 ld d,b pop af rr a push af jr nc,$F B_CALL DarkLine $$: ld b,57 ld d,b pop af rr a push af jr nc,$F B_CALL DarkLine $$: ld b,76 ld d,b pop af rr a jr nc,$F B_CALL DarkLine ; ld b,0 ; ld d,b ; B_CALL DarkLine ; ld b,95 ; ld d,b ; B_CALL DarkLine COMMENT ~ SoftKey: push hl ld bc,51*256+7 ld de,51*256+57 B_CALL DarkLine ld bc,7 ld de,95*256+7 B_CALL DarkLine ld bc,19*256+7 ld de,19*256 B_CALL DarkLine ld bc,38*256+7 ld de,38*256 B_CALL DarkLine ld bc,57*256+7 ld de,57*256 B_CALL DarkLine ld bc,76*256+7 ld de,76*256 B_CALL DarkLine ~ $$: pop hl ld b,(hl) inc hl $$: ld e,(hl) inc hl ld d,(hl) inc hl ld (penCol),de call vputstring djnz $B ret VPutSAppCenter: push hl call SStringLen pop hl ld a,95 sub c srl a ld (penCol),a VPutSApp: ld a,(hl) inc hl or a ret z B_CALL VPutMap jr VPutSApp PutSApp: ld a,(hl) inc hl or a ret z B_CALL PutMap ld a,(curCol) inc a ld (curCol),a cp 16 jr nz,PutSApp xor a ld (curCol),a ld a,(curRow) cp 7 jr z,PutSApp inc a ld (curRow),a jr PutSApp SStringLen: ld c,0 $$: ld a,(hl) inc hl or a ret z push hl ld h,0 ld l,a add hl,hl add hl,hl add hl,hl B_CALL SFont_Len ld a,b pop hl add a,c ld c,a jr $B IPutS11: push hl push bc ld bc,0 ld (curRow),bc ld b,8 $$: ld a,(hl) or a jr z,$F inc hl B_CALL PutC djnz $B $$: pop bc pop hl ret myLoadCIndPaged: B_CALL LoadCIndPaged inc_BHL: inc hl inc_BHL_1: bit 7,h ret z inc b res 7,h set 6,h ret myLoadDEIndPaged: B_CALL LoadDEIndPaged jr inc_BHL myBHL_plus_DE: add hl,de jr inc_BHL_1 ;Draws horizontal dotted line ;Input: bc = (x,y) coordinate of first point (lower left corner is (0,0)) ; e = column to stop at ;Output: line drawn FunkyLine: ld d,1 FunkyLine_Loop: B_CALL IPoint inc b inc b ld a,b cp e jp m,FunkyLine_Loop ret vputstring: ld a,(hl) inc hl or a ret z B_CALL VPutMap jr vputstring DispA: push hl ld c,-1 DispA_loop: inc c sub 10 jr nc,DispA_loop add a,10 push af ld a,c add a,'0' B_CALL PutC pop af add a,'0' B_CALL PutC pop hl ret IGetKey: push ix push bc push de push hl res onInterrupt,(iy+onFlags) B_CALL GetKey pop hl pop de pop bc pop ix ret IPutS: ld a,(hl) inc hl or a ret z call IPutC jr IPutS IPutC: push hl ;don't think these are necessary push bc B_CALL PutC pop bc pop hl ret Var TempNum,2 GetHexA: ;lets user input an 8 bit number in hexadecimal ;prompt is at currow,curcol ;number is returned in a set curAble,(iy+curFlags) ld b,2 ld hl,TempNum getnumhloop: call IGetKey cp 2 jp nz,gnhnotback ld a,b cp 2 jp z,gnhnotback ld a,' ' B_CALL PutMap ld hl,curCol dec (hl) jp GetHexA gnhnotback: sub 142 cp 10 jp c,gnhnumpressed sub 12 cp 6 jp c,gnhletpressed jp getnumhloop gnhnumpressed: ld (hl),a inc hl add a,48 call IPutC djnz getnumhloop jp gnhdone gnhletpressed: add a,10 ld (hl),a inc hl add a,55 call IPutC djnz getnumhloop gnhdone: dec hl ld b,(hl) dec hl ld a,(hl) rlca rlca rlca rlca or b res curAble,(iy+curFlags) ret DispHexHL: push af push bc push de push hl push ix ld a,h call DispHexA ld a,l call DispHexA pop ix pop hl pop de pop bc pop af ret DispHexA: push ix push af push hl push bc push af rrca rrca rrca rrca call dispha pop af call dispha pop bc pop hl pop af pop ix ret dispha: and 15 cp 10 jp nc,dhlet add a,48 jp dispdh dhlet: add a,55 dispdh: call IPutC ret PutHexDE: ld a,d call PutHexA ld a,e PutHexA: push ix push af push bc push af rrca rrca rrca rrca call putha pop af call putha pop bc pop af pop ix ret putha: and 15 cp 10 jr nc,puthlet add a,48 jr putdh puthlet: add a,55 putdh: ld (hl),a inc hl ret ;DialogBox ; Input ; (H,L) = (y,x) upper left ; (D,E) = (y,x) lower right ;H and l must be >= 1 ;D must be <= 62 ;E must be <= 93 ;Text inside the box must be displayed manually DialogBox: push hl push de dec h dec l inc d inc d inc e inc e B_CALL EraseRectBorder pop de pop hl push hl push de B_CALL DrawRectBorderClear pop de pop hl push hl push de inc d inc e B_CALL DrawRectBorder pop de pop hl ld a,h xor 63 ;Adjust for funny IPoint coordinates ld h,a ld a,d xor 63 ld b,l ld c,h ld d,0 B_CALL IPoint ;(b,c) = (x,y xor 63) - upper left ld b,e B_CALL IPoint inc b B_CALL IPoint dec c B_CALL IPoint ld c,a dec c B_CALL IPoint ld b,l B_CALL IPoint inc b B_CALL IPoint dec b inc c B_CALL IPoint ret VStrLen: ld b,0 VStrLen_Loop: ld a,(hl) or a ret z push hl ld h,0 ld l,a add hl,hl add hl,hl add hl,hl push bc B_CALL SFont_Len ld a,b pop bc pop hl inc hl add a,b ld b,a jr VStrLen_Loop fastCopy: ;This only updates the last 7 lines of the LCD ld a,(OP1) push af di ld hl,plotSScreen+(12*57) ld b,7 ;64 ld a,07h out (10h),a ld a,80h-1+57 layerloop1: push bc ld b,0Ch inc a ld (OP1),a call lcddelay out (10h),a call lcddelay ld a,20h out (10h),a layerloop2: ld a,(hl) call lcddelay out (11h),a inc hl djnz layerloop2 pop bc ld a,(OP1) djnz layerloop1 ld a,5 call lcddelay out (10h),a ; ei pop af ld (OP1),a ret lcddelay: push af in a,(2) and 80h jr nz,$F pop af push af push hl pop hl pop af ret $$: pop af push af lcddelayloop: in a,(2) and 2 jr z,lcddelayloop pop af ret VEraseEOL: ld a,' ' B_CALL VPutMap ld a,(penCol) cp c jp m,VEraseEOL ret cmpstr: ld a,(de) cp (hl) ret nz or a ret z inc de inc hl jr cmpstr cmpstrb: ld a,(de) cp (hl) ret nz inc de inc hl djnz cmpstrb xor a ret putsb: push bc push hl $$: ld a,(hl) B_CALL PutC inc hl djnz $B pop hl pop bc ret