;LNUMBEREDMENU NumberedMenu ;LSOFTKEY SoftKey ;LPUTSAPP PutSApp ;LVPUTSAPP VPutSApp ;LSELECTIONLIST SelectionList ;LSOFTKEYG SoftKeyG ;LSTRINGINPUT StringInput ;LDIALOGBOX DialogBox ;LLISTVIEW ListView ;LNUMBEREDMENUQUIT NumberedMenuQuit ;LDISPHEXA DispHexA ;LRUNBASICPROG RunBasicProg ;LGETBYTETIOSW GetByteTIOSW ;LRETNZ RetNZ ;LGETBYTETIOS GetByteTIOS ;LSENDBYTETIOS SendByteTIOS ;LSETCONTRAST SetContrast ;LCONTRASTUP ContrastUp ;LCONTRASTDOWN ContrastDown ;LDISPBIN DispBin ;LDELAYB DelayB ;LCPHLBC CpHLBC ;LMULTHLDE MultHLDE ;LMULTHE MultHE ;LMULTHEFAST MultHE ;LMULTDEBC MultDEBC ;LHOMETEXTMENU HomeTextMenu ;LDISPHOMETEXT DispHomeText ;LDISPHOMETEXTC DispHomeTextC ;LSCROLLINGCREDITS ScrollingCredits ;LDELAYS DelayS ;LGETPIXEL GetPixel ;LCENTERTEXT CenterText ;LNEXTSTRING NextString ;LGETHEXA GetHexA ;LDISPHEXHL DispHexHL ;LGETHEXHL GetHexHL ;LFINDINDEXTEXT FindIndexText ;LDISPBINA DispBinA ;LRANDNUM RandNum ;LASCIITOHEX ASCIIToHex ;LISHEXDIGIT IsHexDigit ;LDISPBLANK DispBlank ;LSTRINGINPUTTIOS StringInputTIOS ;LEXPRINPUTTIOS ExprInputTIOS ;LHEXTOASCII HexToASCII ;LSECRETKEYS EnableSecretKeys, DisableSecretKeys ;LTIOSMODLINK TIOSModLinkSend,TIOSModLinkGet ;LFASTLINEBLACK FastLineBlack ;LCOPYBSTRINGS CopyBStrings ;LVDISPHEXA VDispHexA ;LVDISPHEXHL VDispHexHL ;LVNEWLINE VNewLine ;LRETZ RetZ NOLIST IFDEF LVDISPHEXHL IFNDEF LVDISPHEXA DEFINE LVDISPHEXA ENDIF VDispHexHL: ld a,h call VDispHexA ld a,l ENDIF IFDEF LVDISPHEXA IFNDEF LHEXTOASCII DEFINE LHEXTOASCII ENDIF VDispHexA: push hl push bc call HexToASCII ld a,h push hl B_CALL VPutMap pop hl ld a,l B_CALL VPutMap pop bc pop hl ret ENDIF IFDEF LCOPYBSTRINGS CopyBStrings: B_CALL StrCopy inc hl inc de djnz CopyBStrings ret ENDIF IFDEF LFASTLINEBLACK IFNDEF LGETPIXEL DEFINE LGETPIXEL ENDIF FastLineBlack: ;displays a line to the graphbuffer ;input ;hl=x1, y1 ;de=x2, y2 ;output ;line is drawn to the graphbuffer ;Requires on byte xdir and ydir mem addresses di ld a,1 ld (xdir),a ld (ydir),a ld a,d sub h ld b,a jp nc,flokx neg ld b,a ld a,255 ld (xdir),a flokx: ld a,e sub l ld c,a jp nc,floky neg ld c,a ld a,255 ld (ydir),a floky: ld e,0 ;error ld a,b cp c jp c,fly ld d,b ;resx inc b fllx: call PixelOnFL ld a,(xdir) add a,h ld h,a ld a,e add a,c ld e,a cp d jp c,flxok sub d ld e,a ld a,(ydir) add a,l ld l,a flxok: djnz fllx ei ret fly: ld a,b ld b,c ld c,a ld d,b inc b flly: call PixelOnFL ld a,(ydir) add a,l ld l,a ld a,e add a,c ld e,a cp d jp c,flyok sub d ld e,a ld a,(xdir) add a,h ld h,a flyok: djnz flly ret PixelOnFL: push hl exx pop de ld a,e bit 6,a jp nz,PixelOnFLClip ld a,d cp 96 jp nc,PixelOnFLClip call GetPixel or (hl) ld (hl),a PixelOnFLClip: exx ret ENDIF IFDEF LTIOSMODLINK IFNDEF LGETBYTETIOS DEFINE LGETBYTETIOS ENDIF IFNDEF LSENDBYTETIOS DEFINE LSENDBYTETIOS ENDIF linkwait EQU 6000h TIOSModLinkGet: in a,(2) and 80h jr nz,TIOSModLinkGetSE in a,(0) and d0d1_bits cp d0d1_bits jp z,noio TIOSModLinkGetSE: jp GetByteTIOS COMMENT ~ di ld hl,iodata ld (hl),a ld bc,15 dblp1: in a,(0) and d0d1_bits cp (hl) jp nz,noio dec bc ld a,b or c jr nz,dblp1 AppOnErr linkfail set indicOnly,(iy+indicFlags) call recbyte res indicOnly,(iy+indicFlags) ld (iodata),a AppOffErr ld a,d0hd1h out (0),a ld a,(iodata) cp a ei ret recbyte: ld b,8 l43b2: ld de,linkwait jr l43cd l43b7: in a,(0) and 3 jr z,l4421 cp 3 jp nz,l43d6 in a,(0) and 3 jr z,l4421 cp 3 jp nz,l43d6 l43cd: dec de ld a,d or e jp nz,l43b7 B_CALL ErrLinkXmit l43d6: cp 2 jr z,l4409 ld a,1 out (0),a rr c ld de,linkwait l43e3: in a,(0) and 3 cp 2 jp z,l43f4 dec de ld a,d or e jp nz,l43e3 jr l4421 l43f4: ld a,0 out (0),a ld d,4 l43fa: dec d jr z,l4405 in a,(0) and 3 cp 3 jr nz,l43fa l4405: djnz l43b2 ld a,c ret l4409: ld a,2 out (0),a rr c ld de,linkwait l4412: in a,(0) and 3 cp 1 jp z,l43f4 dec de ld a,d or e jp nz,l4412 l4421: B_CALL ErrLinkXmit ~ TIOSModLinkSend: ld b,a in a,(2) and 80h ld a,b jp nz,SendByteTIOS di push af ld a,d0hd1h out (0),a pop af set indicOnly,(iy+indicFlags) ld hl,linkfail call APP_PUSH_ERRORH call sendit endexio: res indicOnly,(iy+indicFlags) ld (iodata),a call APP_POP_ERRORH ld a,d0hd1h out (0),a ld a,(iodata) cp a ei ret linkfail: ld a,d0hd1h out (0),a noio: ei or 1 ret sendit: ld c,a ld b,8 l41e4: ld de,linkwait rr c jr nc,l41f0 ld a,2 jp l41f2 l41f0: ld a,1 l41f2: out (0),a l41f4: in a,(0) and 3 jp z,l420b in a,(0) and 3 jp z,l420b dec de ld a,d or e jp nz,l41f4 l4208 B_CALL ErrLinkXmit l420b: ld a,0 out (0),a ld de,linkwait l4212: dec de ld a,d or e jr z,l4208 in a,(0) and 3 cp 3 jp nz,l4212 djnz l41e4 ret ENDIF IFDEF LSECRETKEYS IFNDEF LRETNZ DEFINE LRETNZ ENDIF ;Secret Keys is a background key hook that monitors ; keypresses for a certain sequence of keys. Used ; for secret codes and the like. It is meant for ; short term use only (not while TIOS is running) and ; backs up the key hook information is uses. It needs ; four bytes at SecretKeyBackup, a two byte pointer at ; SecretKeySeq, one byte at SecretKeyNum, one byte at ; SecretKeyFlag, and the number of bytes in the key ; sequence at SecretKeyBuffer. ;EnableSecretKeys will enable the routine and look for ; the key sequence located at HL, with length of A. ;DisableSecretKeys will disable the routine and return ; NZ if the key sequence was pressed. ;You can check at any time if the key sequence was ; pressed by checking the value in SecretKeyFlag. A ; non-zero value means that the sequence was pressed. ;This version is for use during scrolling credits or ; other small font intensive applications. EnableSecretKeys: ld (SecretKeySeq),hl ld (SecretKeyNum),a ld c,a ld b,0 ld hl,SecretKeyBuffer B_CALL MemClear ld (SecretKeyFlag),a ld hl,(fontHookPtr) ld (SecretKeyBackup),hl ld a,(fontHookPage) ld (SecretKeyBackup+2),a ld a,(flags+SysHookFlg2) ld (SecretKeyBackup+3),a in a,(6) ld (fontHookPage),a ld hl,SecretKeyHook ld (fontHookPtr),hl set appWantFont,(iy+SysHookFlg2) ret DisableSecretKeys: ld hl,(SecretKeyBackup) ld (fontHookPtr),hl ld a,(SecretKeyBackup+2) ld (fontHookPtr),a ld a,(SecretKeyBackup+3) ld (flags+SysHookFlg2),a ld a,(SecretKeyFlag) or a ret SecretKeyHook: add a,e push bc ld a,(kbdScanCode) or a jr z,SecretKeyHookNZ ld b,a ld a,(SecretKeyBuffer) cp b jr z,SecretKeyHookNZ ld a,b push af ld hl,SecretKeyBuffer ld a,(SecretKeyNum) ld c,a pop af ld b,0 push bc dec bc add hl,bc ld d,h ld e,l dec hl lddr inc hl pop bc ld b,c ld (hl),a ld de,(SecretKeySeq) SecretKeyHookLoop: ld a,(de) cp (hl) jr nz,SecretKeyHookNZ inc hl inc de djnz SecretKeyHookLoop ld (SecretKeyFlag),a SecretKeyHookNZ: pop bc jp RetNZ ENDIF IFDEF LEXPRINTPUTIOS IFNDEF LSTRINGINPUTTIOS DEFINE LSTRINGINPUTTIOS ENDIF ExprInputTIOS: ;Inputs a string via TIOS input routine, then ;tries to parse it. Returns carry set if ;there was an error in parsing. Same inputs ;as InputStringTIOS. call StringInputTIOS AppOnErr ExprITIOSErr B_CALL ParseInp AppOffErr xor a ret ExprTIOSErr: scf ret ENDIF IFDEF LSTRINGINPUTTIOS StringInputTIOS: ;Inputs a string from the TIOS. ;HL = where to put prompt ;textShadow = background for prompt ld (textShadCur),hl set cmdExec,(iy+cmdFlags) set appTextSave,(iy+appFlags) ld hl,cmdShadow ld de,cmdShadowBackup ld bc,134 ldir AppOnErr StringITIOSErr B_CALL InputString AppOffErr StringITIOSErr: B_CALL ReloadAppEntryVecs ld hl,cmdShadowBackup ld de,cmdShadow ld bc,134 ldir res cmdExec,(iy+cmdFlags) res appTextSave,(iy+appFlags) res indicRun,(iy+indicFlags) ret ENDIF IFDEF LDISPBLANK DispBlank: push af ld a,' ' B_CALL PutC pop af ret ENDIF IFDEF LASCIITOHEX IFNDEF LISHEXDIGIT DEFINE LISHEXDIGIT ENDIF ASCIIToHex: ;Converts two ASCII bytes @ HL to a number in A ;CA = 0 = invalid digit ;If valid digit, HL=HL+2 ld a,(hl) call IsHexDigit ret nc rrca rrca rrca rrca ld b,a inc hl ld a,(hl) inc hl call IsHexDigit ret nc or b scf ret ENDIF IFDEF LISHEXDIGIT IsHexDigit: ;Checks if A is a ASCII nibble ;CA = 1 = Yes, value in lower 4 bits of A ;CA = 0 = NO sub '0' cp 10 jr c,IsHexDigitNum sub 'A'-'0' cp 6 ret nc add a,10 IsHexDigitNum scf ret ENDIF IFDEF LRANDNUM RandNum: push hl push de ld hl,(0FFFFh-370) ld a,r ld d,a ld e,(hl) add hl,de add a,l xor h ld (0FFFFh-370),hl ld hl,0 ld e,a ld d,h RandNumLoop: add hl,de djnz RandNumLoop ld a,h pop de pop hl ret ENDIF IFDEF LDISPBINA DispBinA: ld b,8 ld c,a DispBinALoop: rl c ld a,'0' adc a,0 B_CALL PutC djnz DispBinALoop ret ENDIF IFDEF LFINDINDEXTEXT FindIndexText: ;Finds string A in list HL or a ret z push bc push de ld d,a xor a FindIndexTextLoop: ld b,h cpir dec d jr nz,FindIndexTextLoop pop de pop bc ret ENDIF IFDEF LGETHEXHL IFNDEF LGETHEXA DEFINE LGETHEXA ENDIF GetHexHL: call GetHexA push af call GetHexA ld l,a pop af ld h,a ret ENDIF IFDEF LGETHEXA GetHexA: ; lets user input an 8 bit number in hexadecimal ; prompt is at currow,curcol ; number is returned in a ; requires two bytes at GetHexATemp set curAble,(iy+curFlags) ld a,' ' ld (curUnder),a ld b,2 ld hl,GetHexATemp GetHexALoop: push bc push hl call IGetKey pop hl pop bc cp 2 jr nz,GetHexANotBack ld a,b cp 2 jr z,GetHexANotBack ld a,' ' B_CALL PutMap ld hl,curCol dec (hl) jr GetHexA GetHexANotBack: sub 142 cp 10 jr c,GetHexANum sub 12 cp 6 jr c,GetHexALet jr GetHexALoop GetHexANum: ld (hl),a inc hl add a,48 B_CALL PutC djnz GetHexALoop jr GetHexADone GetHexALet: add a,10 ld (hl),a inc hl add a,55 B_CALL PutC djnz GetHexALoop GetHexADone: dec hl ld b,(hl) dec hl ld a,(hl) rlca rlca rlca rlca or b res curAble,(iy+curFlags) ret ENDIF IFDEF LSCROLLINGCREDITS IFNDEF LGETPIXEL DEFINE LGETPIXEL ENDIF IFNDEF LDELAYS DEFINE LDELAYS ENDIF IFNDEF LCENTERTEXT DEFINE LCENTERTEXT ENDIF IFNDEF LNEXTSTRING DEFINE LNEXTSTRING ENDIF ScrollingCredits: ;hl -> list of credits, 0hFF terminated ;requires 121 byte ScrollingCBuf push hl B_CALL ClrLCDFull B_CALL GrBufClr pop hl ei set textWrite,(iy+sGrFlags) ScrollingCLoop: ld a,8 ld (ScrollingCBuf),a push hl ld a,56 call CenterText ScrollingCLoop2: call ScrollingCDispS ld b,15 call DelayS ld a,(ScrollingCBuf) dec a ld (ScrollingCBuf),a jr nz,ScrollingCLoop2 pop hl call NextString ld a,(hl) inc a jr nz,ScrollingCLoop ld b,200 res textWrite,(iy+sGrFlags) jp DelayS ScrollingCDispS: ld b,54 ld hl,plotSScreen B_CALL RestoreDisp ei ld hl,plotSScreen+648 ld bc,120 ld de,ScrollingCBuf+1 push bc push hl push de ldir ld bc,108 ld hl,plotSScreen+660 B_CALL MemClear ; ld b,0 BC = 0 after MemClear ScrollingCDispSL: push bc ld a,b ld e,54 call GetPixel ld d,a and (hl) pop bc jr z,ScrollingCDispSS push bc ld c,d ld b,9 ld de, 12 ScrollingCDispSBL: ld a, (hl) or c ld (hl), a add hl, de DJNZ ScrollingCDispSBL pop bc ScrollingCDispSS: inc b ld a,b cp 96 jr nz,ScrollingCDispSL B_CALL GrBufCpy ld b,10 call DelayS pop hl pop de pop bc ldir ld hl,plotSScreen+12 ld de,plotSScreen ld bc,756 ldir ret ENDIF IFDEF LCENTERTEXT IFNDEF LVPUTSAPP DEFINE LVPUTSAPP ENDIF CenterText: ;hl=string ;a=penrow to disp at ;Needs buffer, CenterTextBuf ld (penRow),a ld de,CenterTextBuf+1 push de B_CALL StrCopy pop hl B_CALL StrLength dec hl ld (hl),c B_CALL SStringLength sra b ld a,48 sub b ld (penCol),a inc hl jp VPutSApp ENDIF IFDEF LNEXTSTRING NextString: push af push bc xor a ld b,h cpir pop bc pop af ret ENDIF IFDEF LGETPIXEL ; input: e=y coordinate ; a=x coordinate ; output: a holds data for pixel (e.g. %00100000) ; hl->byte where pixel is on the gbuf GetPixel: ld d,00 ld h,d ld l,e add hl,de add hl,de add hl,hl add hl,hl ld de,plotSScreen add hl,de ld b,00 ld c,a and 00000111b srl c srl c srl c add hl,bc ld b,a inc b ld a,00000001b getPixelLoop: rrca djnz getPixelLoop ret ENDIF IFDEF LHOMETEXTMENU IFNDEF LDISPHOMETEXT DEFINE LDISPHOMETEXT ENDIF HomeTextMenu: ;HL -> Menu Structure ;Displays menu and waits for option to be chosen ;Jumps to appropriate address push hl B_CALL ClrLCDFull B_CALL HomeUp pop hl ld b,(hl) inc hl push hl ld e,b sla e ld d,0 add hl,de ;HL -> to text strings inc b ;Number of Text Strings to display push bc call DispHomeText pop bc dec b pop hl HomeTextMenuLoop: push hl push bc call IGetKey pop bc pop hl IFDEF CALCSYS cp kClear jr nz,HomeTextNotClear ld a,b add a,k0 HomeTextNotClear: ENDIF sub k1 cp b jr nc,HomeTextMenuLoop add a,a ld e,a ld d,0 add hl,de B_CALL LdHLInd jp (hl) ENDIF IFDEF LDISPHOMETEXTC IFNDEF LDISPHOMETEXT DEFINE LDISPHOMETEXT ENDIF DispHomeTextC: ;Clears screen, and loads B from structure push hl B_CALL ClrLCDFull B_CALL HomeUp pop hl ld b,(hl) inc hl ENDIF IFDEF LDISPHOMETEXT IFNDEF LPUTSAPP DEFINE LPUTSAPP ENDIF DispHomeText: ;displays B number of texts on homescreen ld c,b DispHomeTextLoop: ld a,c sub b ld d,0 ld e,a ld (curRow),de call PutSApp djnz DispHomeTextLoop ret ENDIF IFDEF LMULTHE MultHE: ld l,0 ld d,l ld b,8 MultHELoop: add hl,hl jr nc,MultHENoAdd add hl,de MultHENoAdd: djnz MultHELoop ret ENDIF IFDEF LMULTHEFAST IFDEF LMULTHE ERROR "Can't use LMULTHE and LMULTHEFAST" ELSE MultHE: ld l,0 ld d,l ld b,8 add hl,hl jp nc,MultHESkip1 add hl,de MultHESkip1: add hl,hl jp nc,MultHESkip2 add hl,de MultHESkip2: add hl,hl jp nc,MultHESkip3 add hl,de MultHESkip3: add hl,hl jp nc,MultHESkip4 add hl,de MultHESkip4: add hl,hl jp nc,MultHESkip5 add hl,de MultHESkip5: add hl,hl jp nc,MultHESkip6 add hl,de MultHESkip6: add hl,hl jp nc,MultHESkip7 add hl,de MultHESkip7: add hl,hl ret nc add hl,de ret ENDIF ENDIF IFDEF LMULTHLDE IFNDEF LMULTDEBC DEFINE LMULTDEBC ENDIF MultHLDE: ld b,h ld c,l ENDIF IFDEF LMULTDEBC MultDEBC: ld a,16 ld hl,0 MultDEBCLoop: add hl,hl ex de,hl adc hl,hl jr nc,MultDEBCNoAdd ex de,hl add hl,bc jr nc,MultDEBCNoAdd inc de MultDEBCNoAdd: dec a jr nz,MultDEBCLoop ret ENDIF IFDEF LCPHLBC CpHLBC: ;input ;hl/bc=nums ;output ;nondescructive compare push hl or a sbc hl,bc pop hl ret ENDIF IFDEF LDELAYS IFNDEF LDELAYB DEFINE LDELAYB ENDIF DelayS: xor a out (1),a in a,(1) inc a ret nz ENDIF IFDEF LDELAYB DelayB: ;delay routine ;input ;b=delay amount ;output ;delays for a bit ei DelayL: halt djnz DelayL ret ENDIF IFDEF LDISPBIN DispBin: ;displays a number in binary in homescreen font ;input ;a=number ;output ;number displayed on homescreen ld b,8 ld c,a DBloop: rl c ld a,'0' adc a,0 B_CALL PutC djnz DBloop ret ENDIF IFDEF LCONTRASTUP IFNDEF LSETCONTRAST DEFINE LSETCONTRAST ENDIF ContrastUp: ;increments the contrast ;input ;(none) ;output ;nz=out of range ;lcd and system updated ld a,(contrast) inc a jr SetContrast ENDIF IFDEF LCONTRASTDOWN IFNDEF LSETCONTRAST DEFINE LSETCONTRAST ENDIF ContrastDown: ;decrements the contrast ;input ;(none) ;output ;nz=out of range ;lcd and system updated ld a,(contrast) dec a ENDIF IFDEF LSETCONTRAST IFNDEF LRETNZ DEFINE LRETNZ ENDIF SetContrast: ;sets the contrast in system and lcd ;input ;a=contrast (0-27) ;output ;nz=out of range ;lcd and system updated cp 28 jr nc,RetNZ ld (contrast),a add a,18h or 0c0h out (10h),a cp a ret ENDIF IFDEF LSENDBYTETIOS IFNDEF LRETNZ DEFINE LRETNZ ENDIF SendByteTIOS: ;sends a byte in tios protocol through link port ;input ;a=byte ;output ;nz=error, can't send ld hl,RetNZ call APP_PUSH_ERRORH IFDEF TI83P B_CALL SendAByte ELSE IFDEF TI73 ld a,11 ld (asm_Ind_Call),a B_CALL Exec_IO ENDIF IFNDEF TI73 ERROR "SendByteBlahBlah" call TIOSModLinkSend ENDIF ENDIF call APP_POP_ERRORH cp a ret ENDIF IFDEF LGETBYTETIOS IFNDEF LRETNZ DEFINE LRETNZ ENDIF GetByteTIOS: ;receives a byte in tios protocol through the link port ;input ;(none) ;output ;nz=error, can't recieve ;a=byte ld hl,RetNZ call APP_PUSH_ERRORH IFDEF TI83P B_CALL RecAByteIO ELSE IFDEF TI73 ld a,22 ld (asm_Ind_Call),a B_CALL Exec_IO ENDIF IFNDEF TI73 call TIOSModLinkGet ERROR "Other Link Routines" ENDIF ENDIF ld (RecByteBuffer),a call APP_POP_ERRORH ld a,(RecByteBuffer) cp a ret ENDIF IFDEF LGETBYTETIOSW IFNDEF LRETNZ DEFINE LRETNZ ENDIF GetByteTIOSW: ;gets a byte in tios protocol through the link port ;doesn't timeout, cancel with [on] key. ;input ;a=byte ;output ;nz=error, can't send ld hl,RetNZ call $59 B_CALL Rec1stByteNC ld (RecByteBuffer),a call $5c ld a,(RecByteBuffer) cp a ret ENDIF IFDEF LRUNBASICPROG Runprog: ; The name of the program ; should be in OP1 B_CALL ChkFindSym ; Check if program exists ret c ; C flag set shows failure set cmdExec,(iy+cmdFlags) ; Step 1 set progExecuting,(iy+newDispF) ; Step 2 set indicRun,(iy+indicFlags) ; Step 3 ld hl,cmdShadow ld de,appBackUpScreen ld bc,134 ldir ; Step 4 ld hl,textShadow ld bc,128 ld a,Lspace B_CALL MemSet ; Step 5 ld hl,0000h ld (textShadCur),hl ; Step 6 B_CALL ClrLCDFull ; Step 7 ; Step 8 - If any RAM was ; allocated, it would be ; deallocated here AppOnErr basicerror ; Step 9 B_CALL ParseInp ; Execute the program AppOffErr ; Step 10 basicerror: B_CALL ReloadAppEntryVecs ; Step 11 ld hl,appBackUpScreen ld de,cmdShadow ld bc,134 ldir ; Step 12 ; Step 13 - RAM can be ; reallocated now if ; necessary res indicRun,(iy+indicFlags) ; Step 14 xor a ; Reset C flag to show ; success ret ENDIF IFDEF LDISPHEXHL IFNDEF LDISPHEXA DEFINE LDISPHEXA ENDIF DispHexHL: ld a,h call DispHexA ld a,l ENDIF IFDEF LDISPHEXA IFNDEF LHEXTOASCII DEFINE LHEXTOASCII ENDIF DispHexA: push hl push bc call HexToASCII ld a,h B_CALL PutC ld a,l B_CALL PutC pop bc pop hl ret ENDIF IFDEF LHEXTOASCII HexToASCII: push af rrca rrca rrca rrca call HTAConv ld h,a pop af call HTAConv ld l,a ret HTAConv: and 15 cp 10 jr nc,HTAConvLet add a,48 ret HTAConvLet: add a,55 ret ENDIF IFDEF LLISTVIEW IFNDEF LVPUTSAPP DEFINE LVPUTSAPP ENDIF ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; List View ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;This routine needs a buffer in ram equal to or greater than the size ;of the largest item in the list. It uses the equate ListViewMem ListView: ;Input ;hl points to list data ;Output ;b is the list item choosen set textWrite,(IY+sGrFlags) ld b,1 ;b=selected item ld c,b ;c=top item on screen ld d,0 ;d=letters to skip lvReDisp: ;Display text and cursor push hl push bc push de B_CALL GrBufClr pop de pop bc pop hl call lvDispText ;Displays the Text call lvDispCursor ;Displays the inverted cursor lvLoop: push hl push bc push de B_CALL GrBufCpy ;Text and cursor are in graph ;buffer, so a buffer copy is ;necessary B_CALL GetKey pop de pop bc pop hl cp kDown jr z,lvDown cp kUp jr z,lvUp cp kRight jr z,lvRight cp kLeft jr z,lvLeft cp kEnter ret z jr lvLoop lvLeft: ;scroll left ld a,d or a ;is d=0? are we all the ;way to the left? jr z,lvLoop dec d jr lvReDisp lvRight: ;scroll right push bc push de push hl ld c,b call lvGetStrPtr ;hl now points to selected ;string ld e,d ld d,0 add hl,de ld de,ListViewMem+1 B_CALL StrCopy ;string needs to be in ram ;so sstringlength be used ld hl,ListViewMem+1 B_CALL StrLength dec hl ld (hl),c B_CALL SStringLength cp 95 pop hl pop de pop bc jr c,lvLoop inc d jr lvReDisp lvDown: ;move cursor down ld a,(hl) cp b ;already at bottom? jr z,lvLoop ld d,0 inc b ld a,c add a,8 cp b ;need to scroll down? jr nz,lvReDisp inc c jr lvReDisp lvUp: ;move cursor up ld a,b dec a ;already at top? jr z,lvLoop ld d,0 ld b,a cp c ;need to scroll up? jr nc,lvReDisp dec c jr lvReDisp lvDispCursor: ;Display Cursor push de push hl push bc ld a,b sub c ld l,a ld h,12*8 ;The cursor is 8 rows of ;12 bytes in plotsscreen B_CALL HTimesL ;We multiply the cursor ;size (8*12=96) by the ;current position of the ;cursor to get the offset ;from plotsscreen ld de,plotSScreen add hl,de ld bc,12*8 ;Cursor size is 96 bytes lvDCLoop: ld a,(hl) cpl ;Invert graph buffer byte ld (hl),a inc hl dec bc ld a,b or c jr nz,lvDCLoop pop bc pop hl pop de ret lvDispText: ;Display text push hl push bc push de ld a,c add a,8 ld e,a ;where to stop call lvGetStrPtr push hl ld hl,0101h ld (penCol),hl pop hl lvDTLoop: ld a,b cp c jr nz,lvDTNotSel ;current selected text? push de ld e,d ld d,0 add hl,de pop de lvDTNotSel: call VPutSApp ;display text jr nc,lvDTNoArrow ;carry set if off screen ld a,91 ld (penCol),a ld a,5 push hl push de B_CALL VPutMap pop de pop hl lvDTNoArrow: ld a,1 ld (penCol),a ld a,(penRow) add a,8 ;goto next text/cursor ;position ld (penRow),a inc c ld a,c cp e jr nz,lvDTLoop pop de pop bc pop hl ret lvGetStrPtr: ;returns hl=pointer to ;string c inc hl ld a,c dec a ret z ;already pointing to first ;string push bc ld b,h lvDTCpirLoop: push af xor a cpir pop af dec a jr nz,lvDTCpirLoop pop bc ret ENDIF IFDEF SAVE_THE_WHALES WARNING "You better!!!" ENDIF IFDEF LDIALOGBOX ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; Dialog Box ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ 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 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 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 ENDIF IFDEF LSTRINGINPUT ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; String Input ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ StringInput: ;Input ;hl -> where to save input ;b = max characters ;currow,curcol = cursor location ;Output ;hl is preserved ;bc = number of characters inputted push hl ld de,(curRow) push de set curAble,(IY+curFlags) ld c,b ;c = backup of max chars ld d,0 ;d = how many chars after current cursor location ; last inpuuted char is ld (hl),d ld a,Lspace ld (curUnder),a ;curUnder is the character that is shown during ;cursor blink B_CALL PutMap siLoop: push hl push de push bc call IGetKey pop bc pop de pop hl cp kDel jr z,siDel cp kClear jr z,siClear cp kEnter jp z,siEnter cp kLeft jp z,siLeft cp kRight jp z,siRight cp kDown jp z,siDown cp kUp jp z,siUp cp kSpace jp z,siSpace cp kComma jp z,siComma sub k0 cp 10 jp c,siNumber sub kCapA-k0 cp 26 jp c,siLetter jr nz,siLoop ld a,'X'-'A' jp siLetter siDel: ;delete a character inc d dec d ;are we at the end of the string? jr z,siLoop push de push bc push hl ld b,d ld de,(curRow) push de ld d,h ld e,l inc de dec b ;are we deleting the last character? ld c,Lspace jr z,siDelLoopSkip ;if so, we want to have curUnder=Lspace ;and we don't need to display shifted ;characters ; ld c,(hl) ;else, we want curUnder=next character ld a,(de) ld c,a ;err, actually, don't we want this? siDelLoop: ;This loop displays all the remaining ;characters after the one we're deleting, ;but shifted back one position ld a,(de) B_CALL PutC ld (hl),a inc hl inc de djnz siDelLoop siDelLoopSkip: ld (hl),0 ;needs to be zero terminated, right? ld a,Lspace B_CALL PutC ld a,c ld (curUnder),a pop de ld (curRow),de pop hl pop bc pop de dec d jp siLoop siClear: ;clear all characters ld a,c sub b add a,d or a ;nothing to clear? jp z,siLoop ld e,d ld d,0 add hl,de ld (hl),0 ;zero terminate current text pop de ld (curRow),de ;restore original cursor location pop hl push bc B_CALL StrLength ;get length of string inc c ;need to erase cursor too push hl push de siClearLoop: ;clear all previously entered text ld a,Lspace B_CALL PutC dec c jr nz,siClearLoop pop de ld (curRow),de pop hl pop bc ld b,c ;restore backup of max # of chars jp StringInput siEnter: ld a,(curUnder) B_CALL PutMap ;Display character under cursor, so we ;don't get a black box ; ld e,d ; ld d,0 ; add hl,de ;wait...what was this for? ld hl,curRow dec d inc d jr z,siEnterLoopSkip siEnterLoop: ;Updates cursor position to end ld a,(curCol) inc a and 15 ld (curCol),a or a jr nz,siEnterLoopCont inc (hl) siEnterLoopCont: dec d jr nz,siEnterLoop siEnterLoopSkip: pop de ; ld (curRow),de ;restore original cursor location pop hl B_CALL StrLength ;find string length inc bc ;add one for zero terminator res curAble,(IY+curFlags) ;turn of cursor ret siNumber: add a,L0 jr siLetCont siLetter: add a,LcapA siLetCont: dec b inc b ;Have we displayed the maximum # of ;characters? jp z,siLoop ld (hl),a B_CALL PutC inc hl ld a,d dec d dec b or a ld a,(hl) ld (curUnder),a ;reset curUnder to next character jp nz,siLoop inc d ld a,Lspace ld (curUnder),a ld (hl),0 jp siLoop siSpace: ld a,' ' jr siLetCont siComma: ld a,',' jr siLetCont siLeft: ;move left ld a,b cp c ;are we all the way to the left? jp z,siLoop inc b ld a,d inc d ;we've moved farther away from the end call siLDAHL B_CALL PutMap dec hl ld a,(hl) ld (curUnder),a ld a,(curCol) dec a ;cursor location one to the left ld (curCol),a jp p,siLoop ;jumps if there was no overflow ld a,15 ld (curCol),a ld a,(curRow) dec a ld (curRow),a jp siLoop siUp: ;move up ld a,b add a,15 cp c ;have we typed more than 15 characters? jp nc,siLoop ;if not, we can't move up ld b,a inc b ld a,d add a,16 ld d,a call siLDAHL B_CALL PutMap push de ld de,16 sbc hl,de ;text pointer up a row (row=16 bytes) pop de ld a,(curRow) dec a ;move cursor up a row ld (curRow),a ld a,(hl) ld (curUnder),a jp siLoop siLDAHL: ;loads a character from (hl) and ;converts it to Lspace if it is 0 ld a,(hl) or a ret nz ld a,Lspace ret siDown: ;move down ld e,16 ld a,d sub e ;are there are least 16 after cursor? jp c,siLoop ;if not, we can't move down ld d,a ld a,b sub e ld b,a ld a,(hl) B_CALL PutMap push de ld d,0 add hl,de pop de call siLDAHL ld (curUnder),a ld a,(curRow) inc a ld (curRow),a jp siLoop siRight: ;move right ld a,d or a ;are there any more chars after cursor? jp z,siLoop dec b ld a,(hl) B_CALL PutMap inc hl dec d call siLDAHL ld (curUnder),a ld a,(curCol) inc a ;move cursor over ld (curCol),a cp 16 ;did we scroll jp nz,siLoop xor a ld (curCol),a ld a,(curRow) inc a ld (curRow),a jp siLoop ENDIF IFDEF LSOFTKEYG IFNDEF LVPUTSAPP DEFINE LVPUTSAPP ENDIF ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; Graphic Soft Key ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ SoftKeyG: push hl ld de,appBackUpScreen ld hl,skgPic ;graphic button ld bc,26 ldir ;need to copy graphic to ram for use ;with displayimage ld de,56*256+3 skgLoop: push de ld hl,appBackUpScreen B_CALL DisplayImage pop de ld a,e add a,18 ;move right 18 pixels-next image location ld e,a cp 93 ;done displaying? jr nz,skgLoop pop hl ld a,57 ld (penRow),a ld a,5 skgLoop2: ;loop to display text inside graphics ld (penCol),a push af call VPutSApp pop af add a,18 cp 95 jr nz,skgLoop2 ret skgPic: db 8,17 db 00111111b,11111110b,00000000b db 01000000b,00000001b,00000000b db 10000000b,00000000b,10000000b db 10000000b,00000000b,10000000b db 10000000b,00000000b,10000000b db 10000000b,00000000b,10000000b db 01000000b,00000001b,00000000b db 00111111b,11111110b,00000000b ENDIF IFDEF LSELECTIONLIST IFNDEF LPUTSAPP DEFINE LPUTSAPP ENDIF ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; Selection List ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ SelectionList: ;Input ;hl points to list data ;Output ;b is the list item choosen push hl B_CALL ClrLCDFull pop hl ld b,1 ;b=current item ld c,1 ;c=top display item ld e,0 ;e = 0 = need to redisp text slReDisp: inc e dec e ;is e=0? (do we need to redisplay text?) jr nz,slReDispCont push bc push hl push de B_CALL ClrLCDFull pop de pop hl pop bc call slDispText ;display text slReDispCont: call slDispCur ;display cursor slLoop: push bc push hl push de B_CALL GetKey pop de pop hl pop bc IFDEF DEVBASE cp kClear jr nz,slNotClear ld b,0 ret slNotClear: ENDIF cp kDown jr z,slDown cp kUp jr z,slUp cp kEnter ret z jr slLoop slUp: ld a,b dec a ;already at first item? jr z,slLoop ld b,a cp c ;need to adjust top of screen (scroll up)? jr nc,slReDisp ld e,0 ;if we adjust top of screen, we need to ;redisplay text dec c jr slReDisp slDown: ld a,(hl) cp b ;already at last item? jr z,slLoop inc b ld a,c add a,8 cp b ;need to adjust top of screen (scroll down)? jr nz,slReDisp ld e,0 inc c jr slReDisp slDispCur: ;display cursor ld a,b sub c ;selected item-top of screen=where to display ld (curRow),a ld d,a xor a ld (curCol),a ld a,Lconvert B_CALL PutMap ld a,d or a jr z,slDCZero dec a ld (curRow),a ld a,Lspace B_CALL PutMap slDCZero: ld a,d cp 7 ret z inc a ld (curRow),a ld a,Lspace B_CALL PutMap ret slDispText: ;display text push de push hl push bc push bc ld e,(hl) inc hl ld d,c dec d jr z,slDispTextCont ;already in place for first text item xor a ld b,h ;enough for our cpir slDTCpirLoop: cpir dec d jr nz,slDTCpirLoop slDispTextCont: ;hl points to first string pop bc ld a,e inc a sub c cp 9 ;are there more than 8 strings left? jr c,slDTOverflow ld a,8 ;if so, set # of strings to display at 8 slDTOverflow: ld b,a xor a ;curRow slDTLoop: ld (curRow),a inc a push af ld a,1 ld (curCol),a call PutSApp ;display text pop af djnz slDTLoop pop bc pop hl pop de ld e,1 ;text updated, don't need to update next time ret ENDIF IFDEF LSOFTKEY IFNDEF LVPUTSAPP DEFINE LVPUTSAPP ENDIF ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; Soft Key ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ SoftKey: ;Input ; hl -> key text ;Ouput ; soft keys are displayed to screen push hl ld bc,0007h ld de,95*256+7 ld h,1 B_CALL ILine ld b,19 ld d,b ld e,0 B_CALL ILine ld b,38 ld d,b B_CALL ILine ld b,57 ld d,b B_CALL ILine ld b,76 ld d,b B_CALL ILine ld b,0 ld d,b B_CALL ILine ld b,95 ld d,b B_CALL ILine pop hl ld a,57 ld (penRow),a ld a,3 SoftKeyLoop: ;loop to display text inside boxes ld (penCol),a push af call VPutSApp pop af add a,19 cp 98 jr nz,SoftKeyLoop ret ENDIF IFDEF LNUMBEREDMENU IFNDEF LPUTSAPP DEFINE LPUTSAPP ENDIF ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; Numbered Menu ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ NumberedMenu: ;Input ; hl -> menu data ;Output ; a = column ; d = currently selected item ld b,(hl) nmRestart: ld c,1 ;c = top display item in column ld d,c ;d = currently selected item ld e,0 ;e = 0 = need to refresh text nmLoop: dec e inc e ;do we need to refresh text? jr nz,nmLoopCont ;if not, we don't need to clear screen push hl push bc push de B_CALL ClrLCDFull pop de pop bc pop hl nmLoopCont: call nmDispHeaders ;Display column headers call nmDispNumbers ;Display row number/letters nmLoop2: push hl push bc push de B_CALL GetKey pop de pop bc pop hl cp kRight jr z,nmMoveRight cp kLeft jr z,nmMoveLeft cp kUp jr z,nmMoveUp cp kDown jr z,nmMoveDown cp kEnter jr z,nmQuit cp k0 jr z,nmPress0 sub k1 cp 10 jr c,nmPressNum sub kCapA-k1 cp 27 jr c,nmPressLet jr nmLoop2 nmPressLet: add a,10 jr nmPressNum nmPress0: ld a,9 nmPressNum: inc a ld e,a call nmGetColSize cp e ;does the number/letter pressed exist? jr c,nmLoop2 ;if not, return to getkey loop ld d,e nmQuit: ld a,(hl) inc a sub b ;columns are used backwards in routine ;so column needs to be reversed for ;output ret nmMoveLeft: ;move left ld c,1 ld d,c ld e,0 ;need to refresh text ld a,b inc b ;goto previous column cp (hl) ;were we at first column? jr nz,nmLoop ld b,1 ;if it was the first column, we need to ;reset the column to last jr nmLoop nmMoveRight: ;move right ld c,1 ld d,c ld e,0 ;need to refresh text dec b ;goto next column ld a,b or a ;were we at the last column? jr nz,nmLoop ld b,(hl) ;if it was the last column, we need to ;reset the column to first jr nmLoop nmMoveUp: ;move up ld a,d dec d jr z,nmMUCarry ;scrolling from top back to bottom cp c ;is current = top? jr nz,nmLoop ;if not, don't worry about top ld e,0 ;refresh text if we changed top dec c jr nmLoop nmMUCarry: ld e,0 ;refresh text if going top to bottom inc d ld a,(8442h) ;key repeat location cp 31h ;was the key repeating? jr c,nmLoop2 ;if so, we don't want to jump to bottom call nmGetColSize ld d,a sub 6 ld c,a jp nc,nmLoop ld c,1 jp nmLoop nmMoveDown: ;move down call nmGetColSize cp d jr z,nmMDCarry ;scrolling from bottom back to top ld a,d inc d sub c cp 6 ;do we need to adjust top too? jp nz,nmLoop ld e,0 ;refresh text if adjusting top inc c jp nmLoop nmMDCarry: ld e,0 ;refresh text for bottom to top ld a,(8442h) ;key repeat location cp 31h jp c,nmLoop2 jp nmRestart nmGetColPointer: ;returns hl=pointer to column b push de ld a,(hl) sub b ld e,a sla e ld d,0 inc hl add hl,de B_CALL LdHLInd pop de ret nmGetColSize: ;returns a=# items in current column push hl call nmGetColPointer ld a,(hl) pop hl ret nmDispNumbers: ;display numbers and text push hl push bc push de push de call nmGetColPointer ld e,(hl) ;e=# of entries in column inc hl call nmCpirOffset ;hl->first text string to display ld b,1 nmDNLoop: ld a,b ld (curRow),a xor a ld (curCol),a ld a,c cp d ;is it the current selected item? jr nz,nmDNNoInv set textInverse,(IY+textFlags) ;if so, we need to inver the number nmDNNoInv: call nmGetChar ;a=char representation of c B_CALL PutC ld a,b cp 1 ;if it's not the first, no up arrow jr nz,nmDNNoArrowUp cp c ;if there are non above, no up arrow jr z,nmDNNoArrowUp ld a,LupArrow B_CALL PutC jr nmDNCont nmDNNoArrowUp: cp 7 ;if it's not the last, no down arrow jr nz,nmDNNoArrowDown ld a,c cp e ;if there's none below, no down arrow jr z,nmDNNoArrowDown ld a,LdownArrow B_CALL PutC jr nmDNCont nmDNNoArrowDown: ;if we don't need an up or down arrow ld a,Lcolon ;we want a colon B_CALL PutC nmDNCont: pop af push af res textInverse,(IY+textFlags) ;text shouldn't be inverted call nc,PutSApp ;if e=0 then we need to display text ld a,c cp e jr z,nmDNEnd inc b inc c ld a,b cp 8 jr nz,nmDNLoop nmDNEnd: pop de pop de ld e,1 pop bc pop hl ret nmCpirOffset: ;returns c strings into list hl ld b,c dec b ret z xor a nmCOLoop: push bc ld b,h cpir pop bc djnz nmCOLoop ret nmGetChar: ;retuns a = char equate for char c ld a,c cp 10 jr z,nmGCZero jr nc,nmGCLetter add a,L0 ret nmGCZero: ld a,L0 ret nmGCLetter: add a,LcapA-11 ret nmDispHeaders: ;Display the headers push hl push bc push de ld a,b ;a = highlighted column = current column ld b,(hl) ld e,b sla e ld d,0 add hl,de inc hl ld de,0 ld (currow),de nmDHLoop: cp b ;is this the inverted text header? jr nz,cmDHNoInv set textInverse,(IY+textFlags) cmDHNoInv: call nmPutS ;display header djnz nmDHLoop pop de pop bc pop hl ret nmPutS: ;display string with a space after it push af call PutSApp res textInverse,(IY+textFlags) ld a,Lspace B_CALL PutC pop af ret ENDIF IFDEF LNUMBEREDMENUQUIT IFNDEF LPUTSAPP DEFINE LPUTSAPP ENDIF IFDEF LNUMBEREDMENU WARNING "Both NumberedMenu and NumberedMenuQuit are enabled" ENDIF ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ ; Numbered Menu w/Quit ;------------------------------------------------------------------ ;------------------------------------------------------------------ ;------------------------------------------------------------------ NumberedMenuQuit: ;Input ; hl -> menu data ;Output ; a = column ; d = currently selected item ld b,(hl) nmRestart: ld c,1 ;c = top display item in column ld d,c ;d = currently selected item ld e,0 ;e = 0 = need to refresh text nmLoop: dec e inc e ;do we need to refresh text? jr nz,nmLoopCont ;if not, we don't need to clear screen push hl push bc push de B_CALL ClrLCDFull pop de pop bc pop hl nmLoopCont: call nmDispHeaders ;Display column headers call nmDispNumbers ;Display row number/letters nmLoop2: push hl push bc push de B_CALL GetKey pop de pop bc pop hl cp kRight jr z,nmMoveRight cp kLeft jr z,nmMoveLeft cp kUp jr z,nmMoveUp cp kDown jr z,nmMoveDown cp kEnter jr z,nmQuit cp kQuit jr z,nmQuitQuit cp k0 jr z,nmPress0 sub k1 cp 10 jr c,nmPressNum sub kCapA-k1 cp 27 jr c,nmPressLet jr nmLoop2 nmPressLet: add a,10 jr nmPressNum nmPress0: ld a,9 nmPressNum: inc a ld e,a call nmGetColSize cp e ;does the number/letter pressed exist? jr c,nmLoop2 ;if not, return to getkey loop ld d,e nmQuitQuit: ld d,0 nmQuit: ld a,(hl) inc a sub b ;columns are used backwards in routine ;so column needs to be reversed for ;output ret nmMoveLeft: ;move left ld c,1 ld d,c ld e,0 ;need to refresh text ld a,b inc b ;goto previous column cp (hl) ;were we at first column? jr nz,nmLoop ld b,1 ;if it was the first column, we need to ;reset the column to last jr nmLoop nmMoveRight: ;move right ld c,1 ld d,c ld e,0 ;need to refresh text dec b ;goto next column ld a,b or a ;were we at the last column? jr nz,nmLoop ld b,(hl) ;if it was the last column, we need to ;reset the column to first jr nmLoop nmMoveUp: ;move up ld a,d dec d jr z,nmMUCarry ;scrolling from top back to bottom cp c ;is current = top? jr nz,nmLoop ;if not, don't worry about top ld e,0 ;refresh text if we changed top dec c jp nmLoop nmMUCarry: ld e,0 ;refresh text if going top to bottom inc d ld a,(8442h) ;key repeat location cp 31h ;was the key repeating? jr c,nmLoop2 ;if so, we don't want to jump to bottom call nmGetColSize ld d,a sub 6 ld c,a jp nc,nmLoop ld c,1 jp nmLoop nmMoveDown: ;move down call nmGetColSize cp d jr z,nmMDCarry ;scrolling from bottom back to top ld a,d inc d sub c cp 6 ;do we need to adjust top too? jp nz,nmLoop ld e,0 ;refresh text if adjusting top inc c jp nmLoop nmMDCarry: ld e,0 ;refresh text for bottom to top ld a,(8442h) ;key repeat location cp 31h jp c,nmLoop2 jp nmRestart nmGetColPointer: ;returns hl=pointer to column b push de ld a,(hl) sub b ld e,a sla e ld d,0 inc hl add hl,de B_CALL LdHLInd pop de ret nmGetColSize: ;returns a=# items in current column push hl call nmGetColPointer ld a,(hl) pop hl ret nmDispNumbers: ;display numbers and text push hl push bc push de push de call nmGetColPointer ld e,(hl) ;e=# of entries in column inc hl call nmCpirOffset ;hl->first text string to display ld b,1 nmDNLoop: ld a,b ld (curRow),a xor a ld (curCol),a ld a,c cp d ;is it the current selected item? jr nz,nmDNNoInv set textInverse,(IY+textFlags) ;if so, we need to inver the number nmDNNoInv: call nmGetChar ;a=char representation of c B_CALL PutC ld a,b cp 1 ;if it's not the first, no up arrow jr nz,nmDNNoArrowUp cp c ;if there are non above, no up arrow jr z,nmDNNoArrowUp ld a,LupArrow B_CALL PutC jr nmDNCont nmDNNoArrowUp: cp 7 ;if it's not the last, no down arrow jr nz,nmDNNoArrowDown ld a,c cp e ;if there's none below, no down arrow jr z,nmDNNoArrowDown ld a,LdownArrow B_CALL PutC jr nmDNCont nmDNNoArrowDown: ;if we don't need an up or down arrow ld a,Lcolon ;we want a colon B_CALL PutC nmDNCont: pop af push af res textInverse,(IY+textFlags) ;text shouldn't be inverted call nc,PutSApp ;if e=0 then we need to display text ld a,c cp e jr z,nmDNEnd inc b inc c ld a,b cp 8 jr nz,nmDNLoop nmDNEnd: pop de pop de ld e,1 pop bc pop hl ret nmCpirOffset: ;returns c strings into list hl ld b,c dec b ret z xor a nmCOLoop: push bc ld b,h cpir pop bc djnz nmCOLoop ret nmGetChar: ;retuns a = char equate for char c ld a,c cp 10 jr z,nmGCZero jr nc,nmGCLetter add a,L0 ret nmGCZero: ld a,L0 ret nmGCLetter: add a,LcapA-11 ret nmDispHeaders: ;Display the headers push hl push bc push de ld a,b ;a = highlighted column = current column ld b,(hl) ld e,b sla e ld d,0 add hl,de inc hl ld de,0 ld (currow),de nmDHLoop: cp b ;is this the inverted text header? jr nz,cmDHNoInv set textInverse,(IY+textFlags) cmDHNoInv: call nmPutS ;display header djnz nmDHLoop pop de pop bc pop hl ret nmPutS: ;display string with a space after it push af call PutSApp res textInverse,(IY+textFlags) ld a,Lspace B_CALL PutC pop af ret ENDIF IFDEF LVPUTSAPP VPutSApp: ;display text in small font ld a,(hl) inc hl inc a dec a ;use inc and dec to preserve carry ret z push hl push de B_CALL VPutMap pop de pop hl jr VPutSApp ENDIF IFDEF LPUTSAPP PutSApp: ;display a string of large text ld a,(hl) inc hl or a ret z B_CALL PutC jr PutSApp ENDIF IFDEF LVNEWLINE VNewLine: ld a,(penRow) add a,7 ld (penRow),a ret ENDIF IFDEF LRETNZ RetNZ: xor a inc a ret ENDIF IFDEF LRETZ RetZ: cp a ret ENDIF LIST