;Grammer ;================: ;\\ /\ : ; \\ //\\ : ; \\ // \\ : ; \\/----\\ : ; //\----//\ : ; // \\ // \\ : ; // \\// \\ : ;// \/ \\: ;================: ;Project.........Grammer ;Program.........Grammer ;Author..........Zeda Thomas (Xeda112358 / ThunderBolt) ;E-mail..........xedaelnara@gmail.com ;Size............ ;Language........English ;Programming.....Assembly ;Version.........v2.50 ;I rarely update this stuff ;Last Update.....27 Nov 2019 ;This is not accurate, probably #define NO_JUMP_TABLE #include "grammer2.5.inc" #include "grammer.inc" #define Coord(y,x) .db 01,y,x #define SHELL_BROKEN #define speed #define K_DELAY_DEFAULT 13 #define K_DELAY_ACCEL 3 #define ALIGN_COMMAND_TABLE ;Comment this to potentially save some bytes, uncomment to save some clock cycles #define include_fire #define include_ncr ;#define include_LoadTSA ;#define include_interrupt #define INCLUDE_GRAMPKG #define INDEX_VFONT ;Allows faster font access for key portions of the font #define char_TI_TOK .org $4000 .db $80,$0F, 0,0,0,0 .db $80,$12, $01,$04 ;signing key ID .db $80,$47, "Grammer" ;change the $47 according to name len. .db $80,$81, 2 ;num pages .db $80,$90 ;no splash .db $03,$22,$09,$00 ;date stamp .db $02,$00 ;date stamp signature .db $80,$70 ;final field jp main jumptable: #include "jmptable.z80" SelectedProg: bcall(_OP5ToOP1) ; ld de,OP1 ; ld hl,OP5 ; call mov9 SelectedProgOP1: ld hl,gbuf ld (BufPtr),hl bcall(_ChkFindSym) ret c ld hl,cmdShadow+2 ld a,$BB cp (hl) jr nz,+_ inc l ld a,$6D cp (hl) jp z,EndHook_prepush _: ld a,(TempWord3) or a jr z,ExecOP1 ;Here we need to move the code to RAM. ; We will perform some minor pre-compiling ; Currently it is just: ; Convert numbers to raw binary #include "precompile.z80" jr ExecOP1 ProgramAccessStart: bcall(_RclAns) sub 4 jr nz,begin_parse ex de,hl ld c,(hl) inc hl ld b,(hl) inc hl ld de,OP1 ldir ld (de),a ExecOP1: ld hl,OP1 ld de,basic_prog call mov9 bcall(_ChkFindSym) ld a,b ret c or a \ ret nz ex de,hl ld c,(hl) inc hl ld b,(hl) inc hl parse_via_ptr: ;HL points to code ;BC is the size ld (parsePtr),hl ld (progStart),hl add hl,bc ld (progEnd),hl ld h,a \ ld l,a ld (parseError),hl begin_parse: #ifdef include_interrupt di ld a,11 out (3),a ld a,6 out (4),a ;set slowest hardware timer mode ld a,41h ld i,a im 2 ei #endif call SetUpData ; call progmeta ld hl,BreakProgram push hl ParserNext: ld de,ParserNext push de ParseArg: bit IntActiveFlag,(iy+InternalFlag) call z,parser_interrupt bit OnBlockFlag,(iy+UserFlags) call z,onbreak ld hl,(parsePtr) ParseArg2: ld a,(hl) inc hl ld (parsePtr),hl #ifdef ALIGN_COMMAND_TABLE ld h,CommandJumpTable>>8 add a,a ld l,a jr nc,+_ inc h _: rra ld e,(hl) inc l #else ld e,a ld hl,CommandJumpTable ld d,0 add hl,de add hl,de ld e,(hl) inc hl #endif ld d,(hl) push de ld hl,(parsePtr) ret OutputToken: ld a,(hl) cp 11 jr nz,+_ call ParseNextFullArg ld a,c ld (OutputLogic),a ret _: call ParseFullArg ld hl,textmode ld (hl),c ld e,a ld a,c #ifdef INDEX_VFONT push af #endif ld bc,FontSet or a jr z,+_ ld bc,vFont dec a jr z,+_ ld bc,FontSet dec a jr z,+_ dec a ld c,a ;this part is based on E37's fasttext routine push de ld a,(iy+hookflags3) ;Need to disable font hooks flag while we push af ;try to locate the font data, or we might res fontHookActive,(iy+hookflags3) ;get a pointer to the custom font table. dec c call z,sfont_ptr call nz,lfont_ptr pop af ld (iy+hookflags3),a ld b,d ld c,e pop de _: ld a,e cp 2Bh call z,ParseNextFullArg ld (FontPointer),bc ld b,a ld c,0 ld a,(textmode) cp 4 jr c,+_ ld c,3 ;OS small font jr z,+_ ld c,$7F ;OS large font _: ld a,b cp $2B call z,ParseNextFullArg ld a,c ld (font_ptr_page),a #ifdef INDEX_VFONT pop af dec a ret nz ;need to find chars 32, 48, 64, and 96 ld hl,(FontPointer) ;HL points to the font ;The first byte is the height of the font ld e,(hl) ld d,0 inc hl ld b,33 call lookupchar_vfont ld (vfont_index),hl ld b,17 call lookupchar_vfont ld (vfont_index+2),hl ld b,17 call lookupchar_vfont ld (vfont_index+4),hl ld b,33 call lookupchar_vfont ld (vfont_index+6),hl ld bc,(FontPointer) ret vputc_loc_loop: ld a,(hl) inc hl dec a jp m,vputc_loc_loop_end _: add hl,de sub 8 jr nc,-_ vputc_loc_loop_end: lookupchar_vfont: ;DE is the height ;HL points to the font data ;B is the char+1 djnz vputc_loc_loop #endif ret sfont_ptr: bcall(_SFont_Len) xor a ret lfont_ptr: ld hl,$6D81 call is_start_lfont ret z ld hl,$7184 call is_start_lfont ret z jp err_fatal is_start_lfont: push hl ld de,lFont_record ld a,$7F ;bootcode ld bc,3 call readarc pop de ld hl,lFont_record ld a,(hl) sub 5 ret nz inc hl or (hl) ret nz inc hl or (hl) ret NewLine: ld hl,(BufPtr) ld (gbuf_temp),hl ld (Ans),bc IncPtr: _Ret: ret augment: call ParseFullArg ld h,b \ ld l,c bcall(_EnoughMem) jp c,ErrMem push de call ParseNextFullArg push bc ld hl,(parsePtr) inc hl ld (parsePtr),hl call GetVarInfo jp c,Pop2Exit or a \ jp nz,Pop2Exit ld hl,(parsePtr) ld (parsePtr),hl ex de,hl ld c,(hl) \ inc hl ld b,(hl) ld (TempWord1),hl pop de \ pop hl InsertData: push hl add hl,bc ld b,h \ ld c,l ld hl,(TempWord1) ld (hl),b \ dec hl ld (hl),c \ inc hl \ inc hl add hl,de pop de ;hl points to where to insert data ;de is the number of bytes to insert push de \ push hl ld a,h \ or l jr z,+_ ex de,hl bcall(_InsertMem) _: ld hl,(parsePtr) ld (parsePtr),hl pop hl \ pop bc ld d,h \ ld e,l ZeroMem: ld a,b \ or c \ ld a,0 push de call nz,SetMem pop bc ret _: ld hl,tilemap_new ld (next_page_call_address),hl jp next_page_call PtChange: call ParseFullArg ;To get the tilemap routine correct ld a,c or a jr nz,-_ call ParseNextFullArg ;Map Data push bc call ParseNextFullArg ;Tile Data push bc call ParseNextFullArg ;MapWidth push bc call ParseNextFullArg ;MapX offset ld (TempWord2),bc call ParseNextFullArg ;MapY offset ld (TempWord3),bc call ParseNextFullArg ;Sprite Method push bc cp 2Bh call z,ParseNextFullArg_Buffer pop bc ld a,c pop hl pop bc pop de jp TileMap1 solveSet: call ParseFullArg ld a,c sub 3 jr z,ErrorHandle dec a jr z,CallError ld hl,solveSet_p1 ld (next_page_call_address),hl jp next_page_call _: ErrorHandle: call ParseNextFullArg ld (ParseError),bc ret CallError: call ParseNextFullArg ld a,c cp 2 jr nz,HandleError call ParseNextFullArg ld h,b \ ld l,c call GetGrammerText ld hl,13 or a sbc hl,bc jr nc,+_ CustomError: ld bc,12 _: ex de,hl ld de,appErr1 ldir xor a ld (de),a ld a,2 HandleError: jp GramHandl DSToken: ld a,(hl) \ inc hl call VarP ret nc ld (parsePtr),de ld e,(hl) \ inc hl \ ld d,(hl) ld a,(de) \ ld c,a dec de \ ld (hl),d \ dec hl \ ld (hl),e ld b,0 \ ret ISToken: ld a,(hl) \ inc hl call VarP ret nc ld (parsePtr),de g_ReadByte: ld e,(hl) \ inc (hl) \ inc hl \ ld d,(hl) jr nz,+_ inc (hl) _: ex de,hl ld c,(hl) ld b,0 dec de ex de,hl ret AnsToken: ld bc,(Ans) \ ret seqToken: CopyHex: ex de,hl ld h,b \ ld l,c _: call PutHexFromDE jr z,+_ call PutHexFromDE inc hl jr nz,-_ dec hl xor a rld _: ld (parsePtr),de ld b,h \ ld c,l ret PutHexFromDE: inc de ld a,(de) cp 3Fh ret z cp 3Ah jr c,+_ sub 7 _: rld ret SetData: ;[ ld a,(hl) cp 16 jr z,CopyHex ;[( cp 6 jr z,+_ ;[[ dec hl ld (parsePtr),hl scf _: sbc a,a ld e,a ld h,b \ ld l,c SetData_loop: push hl push de call ParseNextFullArg pop de rlc e jr nc,+_ dec hl ld a,(hl) cp 11 inc hl _: ld a,(hl) pop hl ld (hl),c \ inc hl jr nz,+_ ld (hl),b \ inc hl _: cp 2Bh jr z,SetData_loop ld b,h ld c,l ret VarName: ld e,a ld d,(hl) inc d call GetNextVarNum dec d ld (parsePtr),hl ld (OP1+1),de xor a ld (OP1+3),a rst rFindSym jp VarTokenStepIn FuncToken: call ParseFullArg ld (IntLoc),bc ld bc,80h cp 2Bh call z,ParseNextFullArg dec bc \ inc b \ inc c ld (IntMax),bc ld (IntCount),bc ret SendToken: ld a,(hl) cp $AE jr nz,NotSendByte ;timer,byte ;success or fail call ParseNextFullArg push bc call ParseNextFullArg pop de #include "subroutines/sendbyte.z80" NotSendByte: call ParseFullArg push bc ;Size of the var inc hl \ ld (parsePtr),hl call GetVarName ex de,hl ld de,OP1 ldir xor a ld (de),a bcall(_ChkFindSym) pop hl jr nc,+_ ld a,(OP1) and 1fh bcall(_EnoughMem) jp c,ErrMEM ex de,hl bcall(_CreateVar) ex de,hl ld a,b or c inc hl inc hl push hl call nz,ZeroMem pop bc ret _: inc de \ inc de ld c,e \ ld b,d ret FixToken: ld a,(hl) cp 93h jr nz,SetMode call ParseNextFullArg ld a,c ld (TextPauseTime),a ret SetMode: ld a,(flags+UserFlags) ld b,0 ; not needed, per se, but nice for output ld c,a call ParseFullArg ld a,c ld (flags+UserFlags),a ret FloatModeToggle: ;Toggles float mode. ;In float mode, operations default to float operations. ld a,(flags+ModeFlags2) xor 1<>8 adc a,0 ld h,a ld c,(hl) inc hl ld a,b ;restore A ld b,(hl) push bc cp $2B call z,ParseNextFullArg_Buffer pop ix pop de pop hl #include "gfx/line.z80" plotLUT: .dw pxloff .dw pxlon .dw pxlchange LeftParantheses: ;Read a byte call ParseFullArg ld h,b ld l,c ld c,(hl) ld b,0 ret LeftBracket: ;Read a word (little endian) call ParseFullArg ld h,b ld l,c ld c,(hl) inc hl ld b,(hl) ret iPart: ;Write a word (little endian) call ParseFullArg push bc call ParseNextFullArg pop hl ld e,(hl) ld (hl),c inc hl ld d,(hl) ld (hl),b ld b,d ld c,e ret int: ;Write byte ld a,(hl) cp $3A jr z,intf cp $AE ;checks for ' push af call ParseFullArg push bc call ParseNextFullArg pop hl pop af jr nz,+_ ;Write a byte ld a,(bc) ld e,(hl) ld (hl),a ld a,e ld (bc),a ret _: ld e,(hl) ld (hl),c ld c,e ld b,$00 ret intf: call ParseNextFullArg ld hl,singleTo_int16 ld (next_page_call_address),hl ld h,b ld l,c call next_page_call ld b,h ld c,l ret GetToken: ld a,(hl) cp $AE jp z,GetByte call GetVarName ex de,hl ld de,OP1 ldir xor a ld (de),a bcall(_ChkFindSym) VarTokenStepIn: jp c,return_BC_0 ex de,hl ld a,b or a jr z,+_ ld b,0 add hl,bc ld c,10 adc hl,bc jp p,+_ ld h,$40 inc a _: ld (ThetaPrimeVar),a inc hl inc hl ld b,h ld c,l ret RepeatToken: push hl ex de,hl pop hl call EndOfLine ld (parsePtr),hl bit invlogic,(iy+gflags) res invlogic,(iy+gflags) jr nz,NotRepeatLoop RepeatLoop: call RepeatLooper jr z,RepeatLoop ExitRepeat: ld (parsePtr),hl ret NotRepeatLoop: call RepeatLooper jr nz,NotRepeatLoop jr ExitRepeat RepeatLooper: push de call ParserNext ld hl,(parsePtr) pop de push de push hl ld (parsePtr),de push bc call ParseCondition ld a,b \ or c Pop3Exit: pop bc Pop2Exit: pop hl Pop1Exit: pop de ret WhileToken: bit invlogic,(iy+gflags) res invlogic,(iy+gflags) jr nz,NotWhileLoop WhileLoop: push hl ld (parsePtr),hl call ParseCondition ld a,b or c jr z,EndWhileLoop call ParserNext pop hl jr WhileLoop NotWhileLoop: push hl ld (parsePtr),hl call ParseCondition ld a,b or c jr nz,EndWhileLoop call ParserNext pop hl jr NotWhileLoop EndWhileLoop: pop de call FindEndToken ld (parsePtr),hl ret EndToken: pop de ret ErrorJump: ; If we are currently parsing an errorthen we don't want to be stuck in an infinite loop ! bit errorChecking,(iy+InternalFlag) ret nz set errorChecking,(iy+InternalFlag) push de push hl push bc ld hl,(parsePtr) ld (ErrorLoc),hl ld hl,(parseError) ld a,h or l ld a,(cxErrorEP) call z,GramHandl jr z,L5c05 ld c,a ld b,0 ld de,(parsePtr) ld (qmarkVar),de ld (parsePtr),hl ld hl,(ThetaPrimeVar) push hl ld hl,(Ans) ld (Ans),bc push hl call ParserNext ld a,(hl) ld hl,(qmarkVar) ld (parsePtr),hl cp $11 jr nz,+_ pop hl pop hl pop hl jr L5c06 _: pop hl ld (Ans),hl pop hl ld (ThetaPrimeVar),hl L5c05: pop bc L5c06: pop hl pop de res errorChecking,(iy+InternalFlag) ret PtOn: call ParseFullArg ld a,c \ and 7 res SlowTextFlag,(iy+InternalFlag) bit 3,c jr z,+_ set SlowTextFlag,(iy+InternalFlag) _: push af cp 7 \ jr nz,+_ ld hl,flags+33 ld a,16 xor (hl) ld (hl),a _: call ParseNextFullArg bit SlowTextFlag,(iy+InternalFlag) jr z,+_ call ConvHexTo86ECh ld bc,saveSScreen _: push bc call ParseNextFullArg ld (TempWord2),bc ld b,0 ld h,b ld l,c add hl,hl add hl,bc add hl,hl add hl,hl push hl call ParseNextFullArg pop hl add hl,bc push hl cp 2Bh ld c,1 call z,ParseNextFullArg ld b,c push bc cp 2Bh ld c,$08 call z,ParseNextFullArg pop af ld b,a ld a,(TempWord2) add a,c \ dec a \ sub 64 jr c,HeightIsFinePtOn ld d,a \ ld a,c \ sub d \ ld c,a \ dec c HeightIsFinePtOn: push bc ld bc,(BufPtr) ld hl,(parsePtr) ld a,(hl) cp 2Bh call z,ParseNextFullArg ld d,b \ ld e,c pop bc pop hl add hl,de pop de ld a,(TempWord2) \ inc a \ sub 64 \ jp nc,pop1exit pop af DrawSpriteXxY: push hl ld hl,bigtile ld (next_page_call_address),hl pop hl jp next_page_call QuoteToken: push hl call GetGrammerStr ld (parsePtr),hl ld (ThetaPrimeVar),bc pop bc ret GetKeyToken: ld a,(hl) cp 16 jr nz,GetKey call ParseNextFullArg+3 ld a,c CheckKey: ;46 bytes: ;Input: ; A is the key to test for ;Output: ; BC is 1 if the key is pressed, 0 if it is not ; z if the key is pressed, nz if not cp 41 ;on-key jr z,check_for_ON_key di _: dec a \ and 63 ld b,a and 7 srl b \ srl b \ srl b inc b \ inc a ;b = 2; a = 1 ld c,a ld a,7Fh _: rlca djnz -_ out (1),a ld b,c ld a,80h _: rlca djnz -_ ld c,a in a,(1) and c CheckKey_End: ld c,b ret nz inc c ret check_for_ON_key: in a,(4) and 8 ld bc,0 ret nz inc c ret GetKeyDebounce: ei halt call GetKey ld hl,k_save cp (hl) jr nz,newkeypress ;if the keys match, decrement k_count inc hl dec (hl) jr z,+_ xor a ret _: inc hl ld a,(hl) sub K_DELAY_ACCEL+1 jr nc,+_ xor a _: inc a ld (hl),a dec hl ld (hl),a dec hl ld a,(hl) ret newkeypress: ld (hl),a inc hl ld (hl),K_DELAY_DEFAULT inc hl ld (hl),K_DELAY_DEFAULT ret ;=============================================================== GetKey: ;=============================================================== ;Outputs: ; a is a value from 0 to 56 that is the keypress ; bc is also the key press ; d has a bit reset, the rest are set (this is the last key group tested) ; e is a with a mask of %11111000 ; hl is not modified ;=============================================================== di ld de,$FE00 ld a,d out (1),a push af \ pop af in a,(1) ld b,e xor $FF \ jr z,+_ ld d,a ld c,16 \ cp 15 \ ret z ld c,5 ld a,3 \ and d \ cp 3 \ ret z \ inc c ld a,5 \ and d \ cp 5 \ ret z \ inc c ld a,10 \ and d \ cp 10 \ ret z \ inc c ld a,12 \ and d \ cp 12 \ ret z ld a,d cpl ld c,e jp key_add _: ld c,a _: rlc d ld a,d out (1),a inc e sub 7Fh jp z,CheckOnPress in a,(1) inc a jr z,-_ dec a key_add: inc c rra jr c,key_add ld a,e rlca \ rlca \ rlca add a,c ld c,a ret CheckOnPress: in a,(4) and 8 sub 1 sbc a,a and 41 ld c,a ret ElseToken: ;Check for an If token, maybe? push bc call FindEndToken ld (parsePtr),hl pop bc pop af ret IfToken: push bc call ParseCondition ld a,b or c jr z,+_ scf _: pop bc ld hl,flags+gflags bit invlogic,(hl) jr z,+_ res invlogic,(hl) ccf _: ret c ld hl,(parsePtr) inc hl ld a,(hl) push bc cp $CF ;Then token jr z,nothen call EndOfLine _: ld (parsePtr),hl pop bc ret nothen: call z,FindElseEnd cp $D0 ;Check if it was an Else token jr nz,-_ ld (parsePtr),hl pop bc jp ParserNext VarToken: call VarP ld (parsePtr),de ld c,(hl) inc hl ld b,(hl) ex de,hl ld a,(hl) inc hl call VarP ret nc ld (parsePtr),de ld e,c ld d,b ld c,(hl) inc hl ld b,(hl) set FactorialFlag,(iy+InternalFlag) ret ParseNextFullArg_Buffer: ;Input: z flag ;Result: ; z : Parse the next argument, result in BC ; nz : Returns BC as the pointer to the main buffer ld bc,(BufPtr) call z,ParseNextFullArg ld (gbuf_temp),bc ret ParseNextFullArg: ld hl,(parsePtr) ParseNextFullArg_Inc: inc hl ParseNextFullArg_HL: ld (parsePtr),hl ParseFullArg: bit FactorialFlag,(iy+InternalFlag) jr nz,+_ ld de,0 _: res FactorialFlag,(iy+InternalFlag) ld hl,(parsePtr) ld a,(hl) call EndOArg ret z cp 29h ret z call ParseArg jr ParseFullArg ParseCondition: call ParseArg ld hl,(parsePtr) ld a,3Fh cp (hl) jr nz,ParseCondition ret GetNextVarNum: inc hl ld a,(hl) cp $AE jr nz,+_ set Mod2nd,(iy+InternalFlag) ret _: sub 3Ah add a,10 ret nc ld a,d add a,a add a,a add a,d add a,a ld d,a ld a,(hl) and 15 add a,d ld d,a jr GetNextVarNum StoString: ld e,a ld d,(hl) inc d call GetNextVarNum dec d ld (parsePtr),hl ld h,b ld l,c push bc ;Data in Grammer prg push de ;D= Str Nr; E=AA call GetGrammerStr pop hl bit Mod2nd,(iy+InternalFlag) jr z,+_ inc bc _: push bc ld b,h ld c,l ld (OP1+1),hl xor a ld (OP1+3),a ld (OP1+1),bc rst rFindSym jr c,+_ ;HL = pointer to the variable's Symbol Table entry ;DE = pointer to the variable's data structure ;B = 0 for Ram, or Flashpage ;OP1=.db StrngObj,tVarStrng,tStr1,0,0; not all n�tig bcall(_DelVarArc) _: pop hl ;length push hl bcall(_CreateStrng) inc de inc de pop bc pop hl ldir bit Mod2nd,(iy+InternalFlag) ret z res Mod2nd,(iy+InternalFlag) dec de ld a,3Fh ld (de),a ret StoDisp: ld (parsePtr),hl ld h,c ld l,c ld a,c cp 16 jr nc,+_ inc c dec c jr z,+_ ld l,%10101010 dec c jr z,+_ setgray4: ld hl,%0000001011011011 ;H is 2 _: ld (graymask),hl ret StoToken: ld a,(hl) inc hl cp $AA \ jp z,StoString cp $DC \ jp z,StoInput cp $DE \ jr z,StoDisp cp $01 \ jp z,StoModule cp $3A \ jr z,StoFloat cp $2C \ jr nz,NotOSVar ;Save Grammer's Ans push bc ;Make sure it is a valid name ld a,(hl) cp 72h ;Ans jr z,+_ cp 'A' jp c,ErrBadTOken cp 'Z'+2 jp nc,ErrBadTOken _: ;It is valid, so update parsePtr inc hl ld (parsePtr),hl ;Now write the name to OP1 ld (OP1+1),a ld hl,0 ld (OP1+2),hl ;Convert BC to a float in OP2 ld h,b ld l,c bcall(_SetXXXXOP2) ;Find the var rst rFindSym jr c,create_OS_real ;If it is a non-real, delete it and create it as a real var and $1F jr nz,delete_create_OS_real ;If it is archived, just delete it and start anew or b jr z,sto_real delete_create_OS_real: bcall(_DelVarArc) create_OS_real: bcall(_CreateReal) sto_real: ;Copy OP2 to the number ld hl,OP2 call mov9 ;restore Grammer's Ans pop bc ret NotAVar: ld (parsePtr),hl ret StoFloat: ld a,(hl) call VarP jr nc,NotAVar ld (parsePtr),de ld e,(hl) inc hl ld d,(hl) ld h,b ld l,c jp mov4_page0 NotOSVar: call VarP jr nc,NotAVar push hl push bc ld bc,stack_base or a sbc hl,bc add hl,bc pop bc jr nz,+_ ld (stack_ptr),bc _: ld a,(de) ex de,hl inc hl call VarP jr c,+_ dec hl ex de,hl \ pop hl _: ld (hl),c inc hl ld (hl),b ld (parsePtr),de ret nc pop hl ld de,(ThetaPrimeVar) ld (hl),e inc hl ld (hl),d ret StoModule: inc hl ld (parsePtr),hl ld hl,module_count ld a,(hl) cp 5 jp nc,ErrPkgNotFound ;now should verify the module inc (hl) adc a,a add a,l ld l,a ld (hl),c inc hl ld (hl),b ;Check if BC points to the name of a valid module. call GetVarName_BC call GetVarInfo_ jp c,module_not_found call GetVarInfoVarFound push hl ld hl,verify_package ld (next_page_call_address),hl pop hl call next_page_call ret nc jp module_not_found StoInput: ld a,(hl) cp $AE jr z,sto_input_size ld (parsePtr),hl ld (input_base),bc ret sto_input_size: inc hl ld (parsePtr),hl ld (input_size),bc ret Return: call EndOfLine ld c,l ld b,h ret GotoToken: push bc call ParseFullArg ld (parsePtr),bc pop bc ret DispGraph: ld a,(hl) call EndOArg call nz,isop jp z,GraphToLCD call ParseFullArg ld h,b ld l,c ld ixh,b ld ixl,c jp BufferToLCD EndOArg: cp 4 \ ret z ;-> EndOArgNotSto: cp 2Bh \ ret z ;, EndOfLine_newcol: cp 3Fh \ ret z ;NL ; cp 3Ah \ ret z cp 3Eh \ ret z ;: or a ret isop: cp $82 ;* ret z cp $83 ;/ ret z cp $95 ; nCr cp 1 ;>Frac ret z cp 2 ;>Dec ret z cp $6A ret c cp $72 jr nc,+_ cp a ret _: or a ret ;=============================================================== FindEndToken: ;=============================================================== ;Input: ; HL is an address ;Outputs: ; HL points to the byte after the proper End token ;=============================================================== ld b,0 SearchEnd_inc: inc b SearchEndLoop: inc hl ld a,(hl) ; Make sure it isn't >Nom( cp $BB jr nz,+_ inc hl ld a,(hl) cp 5 jr z,SearchEnd_inc jr SearchEndLoop _: call Is_2_Byte jr nz,+_ inc hl jr SearchEndLoop _: ld a,(hl) sub $CF ;Then jr c,SearchEndLoop ;**Just to save time jr z,SearchEnd_inc dec a dec a \ jr z,SearchEnd_inc ;While dec a \ jr z,SearchEnd_inc ;Repeat dec a \ jr z,SearchEnd_inc ;For dec a \ jr nz,SearchEndLoop ;End djnz SearchEndLoop inc hl ret FindElseEnd: ;Input: ; HL is an address ;Outputs: ; HL points to the byte after the proper Else or End token ; A is the last token checked ld b,0 FindElseEnd_: inc b FindElseEndLoop: inc hl ld a,(hl) ; Make sure it isn't >Nom( cp $BB jr nz,+_ inc hl ld a,(hl) cp 5 jr z,FindElseEnd_ jr FindElseEndLoop _: call Is_2_Byte jr nz,+_ inc hl jr FindElseEndLoop _: ld a,(hl) sub $CF ;Then jr c,FindElseEndLoop jr z,FindElseEnd_ ;Then dec a \ jr z,check_else dec a \ jr z,FindElseEnd_ ;While dec a \ jr z,FindElseEnd_ ;Repeat dec a \ jr z,FindElseEnd_ ;For dec a \ jr nz,FindElseEndLoop _: djnz FindElseEndLoop ld a,(hl) inc hl ret check_else: ;If this isn't THE `Else`, then we don't want to decrement the counter djnz FindElseEnd_ ld a,(hl) inc hl ret ;=============================================================== GetGrammerText: ;=============================================================== ;Input: ; HL points to the start of the string ;Outputs: ; A is the value of the ending byte of the string ; BC is the size of the string ; DE points to the start of the converted string ; HL points to the ending byte of the string ; z flag is set ;=============================================================== ld de,saveSScreen GetGrammerText_DE: ld bc,0 push de TextConvert: ld a,(hl) cp 4 ;-> jr z,TextConvertEnd cp 3Fh ;newline jr z,TextConvertEnd cp 2Ah ;" jr z,TextConvertEnd call TokToASCII+3 jp TextConvert ld de,OP3 TokToASCII: ;Inputs: ; HL points to the token ; DE points to where the token should get converted to ;Outputs: ; HL is incremented ; DE points to the byte after the string ; BC is the size of the string ld bc,0 push hl push bc push de bcall(_Get_Tok_Strng) pop de pop hl add hl,bc push hl ld hl,OP3 ldir pop bc pop hl ld a,(hl) call Is_2_Byte inc hl ret nz inc hl ret TextConvertEnd: inc hl pop de ret ;=============================================================== GetGrammerStr: ;=============================================================== ;Input: ; HL points to the start of the string ;Outputs: ; A is the value of the ending byte of the string ; BC is the size of the string ; HL points to the ending byte of the string ; z flag is set ;=============================================================== ld bc,-1 ; inc hl _: ld a,(hl) inc bc or a \ ret z cp 4 \ ret z cp 3Fh \ ret z inc hl cp 2Ah \ jr nz,-_ ret VarP: cp $AF ;? token jr nz,VarPointer ex de,hl scf ld hl,qmarkVar ret ;=============================================================== VarPointer: ;=============================================================== ;Inputs: ; A is the var to return the pointer of ; hl points to the next byte ;Outputs: ; A is the lower 8-bits of the pointer ; BC is not affected ; DE should be used to update (parsePtr) ; HL points to the var data ; c flag is reset if A was not a var token cp $BB jr nz,NotBBvar ld d,h ld e,l ld a,(hl) cp $4B ;Pmt_End jr z,Pmt_End_ptr cp $4C ;Pmt_Bgn jr z,Pmt_Bgn_ptr sub 203 ret nc sub -16 adc a,10 cp 26 ret nc add a,a ld hl,pvars+54 add a,l ld l,a #if (pvars+54)&255>=204 jr nc,+_ inc h _: #endif inc de scf ret Pmt_End_ptr: ld hl,stack_top inc de scf ret Pmt_Bgn_ptr: ld hl,stack_base inc de scf ret NotBBVar: cp 'A' ccf ret nc cp 'Z'+2 ret nc sub 'A' rlca ld d,pvars>>8 ld e,a ld a,(hl) cp $AE jr nz,+_ ld a,54 add a,e ld e,a inc hl _: ld a,e add a,pvars&255 ld e,a #if pvars&255>=202 jr nc,+_ inc d _: #endif ex de,hl scf ret ;=============================================================== EndOfLine: ;=============================================================== ;Input: ; HL is a pointer ;Output: ; HL points to the next line ;=============================================================== ld a,3Fh push bc ld bc,0 cpir pop bc ret ;=============================================================== IsHexTok: ;=============================================================== ;Input: ; DE points to the byte ;Output: ; DE is incremented by 1 ; A is the hex value if A is a hex token ; nc if A is a hex token ; c if A is not a hex token ;=============================================================== ld a,(de) inc de cp 47h ccf ret c cp 'A' jr nc,+_ cp 3Ah ccf ret c .db $DA ;start of jp c,** _: sub 7 sub 30h ret ;=============================================================== ConvRStr: ;=============================================================== ;Input: ; DE points to the base 10 number string in RAM. ;Outputs: ; HL is the 16-bit value of the number ; DE points to the byte after the number ; BC is HL/10 ; z flag reset (nz) ; c flag reset (nc) ;Destroys: ; A (actually, add 30h and you get the ending token) ;Size: 41 bytes ;Speed: 134+(106+{0,9})n ; n is the number of digits ; c is at most n-2 ; at most 691 cycles for any 16-bit decimal value ;=============================================================== dec hl bit baseInput,(iy+UserFlags) jp nz,ConvHexStr bit floatmode,(iy+ModeFlags2) jr nz,ConvRStr_Float ex de,hl ld hl,0 push de ;save in case we encounter a float _: ld a,(de) sub 30h cp 10 jr nc,+_ inc de ld b,h ld c,l add hl,hl add hl,hl add hl,bc add hl,hl add a,l ld l,a jr nc,-_ inc h jp -_ _: jr z,+_ ;means it was a decimal point pop bc ld (parsePtr),de ld b,h ld c,l ret _: pop hl ConvRStr_Float: ;HL points to the string dec hl ld a,(hl) cp $B0 ;neg sign token jr nz,+_ ;Need to pop off the return address; not returning to the neg routine pop de pop de .db $FE ;start of cp *, causes the inc hl to be ignored _: inc hl ;HL points to the float push hl call floatstackpush ld b,h ld c,l ld hl,str2single ld (next_page_call_address),hl pop hl call next_page_call ld hl,(ptr_sto) ld (parsePtr),hl ret SetMem: ld (hl),a ld d,h ld e,l cpi ret po ex de,hl ldir ret ;=============================================================== Is_2_Byte: ;=============================================================== cp $EF \ ret z cp $BB \ ret z cp $7E \ ret z Is_Var_Name: sub $AA \ ret z ;AA add a,$47 \ ret z ;63 inc a \ ret z inc a \ ret z inc a \ ret z add a,2 \ ret z inc a \ ret z inc a \ ret ConvHexTo86ECh: ;max: 174n+91 ;min: 128n+56 ;avg: 145.25x+79 (typical avg, assuming most end in newline) ;An 8x8 sprite is now 6% faster on avg. than versions <2.50 ld d,b ld e,c ld hl,86ECh ld bc,$0A30 ConvHexLoop7: ; HL points to where to convert ; DE is where to convert from ld a,(de) inc de sub c ret c cp b jr c,+_ sub 17 ret c cp 6 ret nc add a,b _: rld ld a,(de) inc de sub c ret c cp b jr c,+_ sub 17 ret c cp 6 ret nc add a,b _: rld inc hl jp ConvHexLoop7 IsConditional: cp $D8 \ ret z ;pause cp $CE \ ret z ;if cp $D1 \ ret z ;while cp $D2 \ ret ;repeat EraseParticle: ld c,(hl) inc hl ld b,(hl) ;pixel off push bc call GetPixelLoc pop bc ret isStartMenu_valid: ld a,(OP1+1) cp $23 jr z,StartMenu_invalid cp $21 jr z,StartMenu_invalid ld hl,(VATPtr) ld a,(hl) cp 1 ;don't want lists jr nz,+_ StartMenu_invalid: or a ret _: cp 13 ;don't want complex lists jr z,StartMenu_invalid cp 17h ;don't want GroupVars jr z,StartMenu_invalid bit 6,(iy+UserFlags) ;must be AppV jr z,+_ cp 15h ret nz _: ;need to pull in six bytes #ifdef include_LoadTSA call LoadReadArc #endif ld bc,-3 add hl,bc ld e,(hl) dec hl ld d,(hl) dec hl ld a,(hl) or a jr z,+_ ld b,a dec hl ld a,(hl) add a,10 add a,e ld e,a ld a,b jr nc,+_ inc d jp po,+_ inc a ld d,$40 _: ex de,hl ld de,cmdShadow ld bc,2 call ReadArc ld bc,(cmdShadow) ;need to save A:HL, BC ld (TempWord3),a ld (TempWord4),bc ld (TempWord5),hl _: ld bc,4 call ReadArc ld hl,cmdShadow+2 bit OnBlockFlag,(iy+UserFlags) ;ASM only jp nz,asm_header_only ;non-ASM and ASM alike bit baseInput,(iy+UserFlags) ret z ;doesn't have any special filters ;must be a Grammer Var ;header is either $BB,$6D,$55,$C9 or $3A,$30,$3E ld a,(hl) \ cp $BB \ jr z,+_ cp $3A \ ret nz inc hl \ ld a,(hl) \ cp $30 \ ret nz inc hl \ ld a,(hl) \ cp $3E \ ret _: inc hl \ ld a,(hl) \ cp $6D \ ret nz inc hl \ ld a,(hl) \ cp $55 \ ret nz inc hl \ ld a,(hl) \ cp $C9 ret asm_header_only: ;first two bytes must be $BB,$6D ; ld a,(hl) \ cp $BB \ ret nz inc hl \ ld a,(hl) \ cp $6D \ ret nz bit baseInput,(iy+UserFlags) ret z ;next two bytes must be $55,$C9 ; inc hl \ ld a,(hl) \ cp $55 \ ret nz inc hl \ ld a,(hl) \ cp $C9 ret #ifdef include_LoadTSA ReadArc: call LoadReadArc jp TSA #else ReadArc = TSA #endif ReadArcData: #ifdef include_loadTSA .dw ReadArcEnd-ReadArc-2 #endif #include "readarc.z80" ReadArcEnd: FindGVarData: ld hl,GVarData rst rMov9ToOP1 bcall(_ChkFindSym) ld a,b jr nc,GetVarInfoVarFound ld hl,3 bcall(_CreateAppVar) ld hl,4 add hl,de xor a ld (hl),a dec hl ld (hl),a dec hl ld (hl),a ret GetVarName: call ParseFullArg GetVarName_BC: ld h,b ld l,c GetVarName_: ld a,(hl) and 1Fh ld de,OP1 sub 5 \ jp z,GetGrammerText_DE dec a \ jp z,GetGrammerText_DE sub 15 \ jp z,GetGrammerText_DE dec a \ jp z,GetGrammerText_DE ld bc,3 ld d,h \ ld e,l add hl,bc cp a ret GetVarInfo: ;Returns name in OP1 ;A is the flashpage ;HL points to SymEntry ;DE points to size bytes ;BC is the length of the name (for use when finding archived data) ;nc if it exists ;z if it is in RAM call GetVarName GetVarInfo_: ex de,hl ld de,OP1 push bc ldir xor a ld (de),a bcall(_ChkFindSym) ld a,b pop bc ret c or a ret GetvarInfo2: ;Inputs: ; The next argument to parse points to the name of the var to get info about ;Outputs: ; A is the ending page (start of data) ; BC is the size of the var ; DE points to the SymEntry ; HL points to the data ; c is set if the var does not exist #ifdef include_LoadTSA call LoadReadArc #endif call GetVarInfo ret c GetVarInfoVarFound: ex de,hl or a jr nz,+_ ld c,(hl) \ inc hl ld b,(hl) \ inc hl ret _: add hl,bc ld c,9 add hl,bc bit 7,h jr z,+_ ld h,40h inc a _: push de ld de,OP2 ld bc,2 call ReadArc ld bc,(OP2) pop de or a ret GPutSI: ; The string to display immediately follows the call ; The string is zero terminated ;Outputs: ; All registers are preserved ex (sp),hl push de push bc push af call GPutS pop af pop bc pop de ex (sp),hl ret DrawRectToGraphI: ex (sp),hl ; push de \ push bc \ push af ld e,(hl) \ inc hl ld c,(hl) \ inc hl ld b,(hl) \ inc hl ld d,(hl) \ inc hl ld a,(hl) \ inc hl ex (sp),hl jp DrawRectToGraph ExecLine_: ld a,(hl) inc hl call VarP ret nc parse_by_ptr_to_ptr: push de push hl ld a,(hl) inc hl ld h,(hl) ld l,a call ParseNextFullArg_HL ld de,(parsePtr) pop hl inc de ld (hl),e inc hl ld (hl),d pop hl ld (parsePtr),hl ret ExecLine: call ParseFullArg push bc cp 2Bh ld bc,(ProgStart) call z,ParseNextFullArg push bc ld bc,32768 cp 2Bh call z,ParseNextFullArg push bc cp 2Bh ld bc,63 call z,ParseNextFullArg ld a,c pop bc pop hl pop de call SearchLine_00 ld b,d ld c,e jp g_expr Byte: ld b,0 ld c,(hl) inc hl ld (parsePtr),hl ret Word: ld c,(hl) inc hl ld b,(hl) inc hl ld (parsePtr),hl ret NegRelPtr: ld c,(hl) inc hl ld b,(hl) inc hl ld (parsePtr),hl ld hl,(progEnd) or a sbc hl,bc ld b,h ld c,l ret Base2Num: ld bc,0 ld d,b ld e,c _: ld a,(hl) sub '2' add a,2 jr nc,+_ rrca rl c rl b rl e rl d inc hl jp -_ ;It saves 2 cycles using JP D: _: set FactorialFlag,(iy+InternalFlag) ld (parsePtr),hl ret _: ld hl,lnSingle jp float_stepin_1 LnToken: ld a,(hl) cp 3Ah jr z,-_ cp $B0 push bc jr z,JumpBack call ParseFullArg dec bc inc b inc c ld d,b \ ld e,c ld bc,0 _: ld a,3Fh cpir dec e jr nz,-_ dec d jr nz,-_ ld (parsePtr),hl pop bc ret JumpBack: call ParseNextFullArg inc b inc c ld d,b \ ld e,c dec hl ld bc,0 _: ld a,3Fh cpdr dec e jr nz,-_ dec d jr nz,-_ ld (parsePtr),hl pop bc ret cmdJmp: #ifdef ALIGN_COMMAND_TABLE ld h,CommandJumpTable>>8 add a,a jr nc,+_ inc h _: ld l,a #else ld hl,CommandJumpTable add a,a jr nc,+_ inc h _: add a,l ld l,a jr nc,+_ inc h _: #endif ld a,(hl) inc hl ld h,(hl) ld l,a push hl ld hl,(parsePtr) ret menu: ld hl,menu_code_start ld (next_page_call_address),hl jp next_page_call pushvars_00: ld de,pushvars ld (next_page_call_address),de jp next_page_call FracToken_00: ld de,FracToken ld (next_page_call_address),de jp next_page_call ParamToken_00: ld de,ParamToken ld (next_page_call_address),de jp next_page_call LblToken: ld hl,LblToken_01 ld (next_page_call_address),hl jp next_page_call FS_createvar_max: push hl ld hl,FS_createvar_max_01 jr jp_next_page_call FS_delvar: push hl ld hl,FS_delvar_01 jr jp_next_page_call FS_resize: push hl ld hl,FS_resize_01 jr jp_next_page_call FS_findvar: push hl ld hl,FS_findvar_01 jr jp_next_page_call SearchString: push hl ld hl,searchstring_routine jr jp_next_page_call SearchLine_00: push hl ld hl,SearchLine jr jp_next_page_call DrawRectToGraph: push hl ld hl,drawrect jp_next_page_call: ld (next_page_call_address),hl pop hl jp next_page_call DegreeToken: call ParseFullArg ld (gbuf_temp),bc inc hl jp ParseArg2 todectoken: ;Takes a pointer to a string and converts it to a float ld hl,str2single ld (next_page_call_address),hl push bc call floatstackpush ld b,h ld c,l pop hl jp next_page_call InputToken: ld de,s_null ld a,(hl) call EndOArg call nz,isop jr z,+_ call ParseFullArg ld h,b ld l,c ld de,OP1 call GetGrammerText_DE ld h,b ld l,c add hl,de ld (hl),0 _: ld hl,input ld (next_page_call_address),hl call next_page_call ld b,h ld c,l ret GraphToLCD: ld hl,GraphToLCD_ ld (next_page_call_address),hl jp next_page_call BufferToLCD: ld ix,BufferToLCD_ ld (next_page_call_address),ix jp next_page_call #include "main.z80" #include "module.z80" #include "ramcode.z80" #include "routines.z80" #include "SetUpData.z80" #include "parserhook.z80" #include "cmd/particle.z80" #ifdef include_LoadTSA #include "cmd/loadtsa.z80" #endif #include "gfx/text.z80" #include "gfx/getpixelloc_nobound.z80" #include "gfx/GetPixelLoc.z80" #include "gfx/TileMap1.z80" #include "math/mul16.z80" #include "math/HL_Div_C.z80" #include "math/DEHL_Div_C.z80" #include "math/HL_Div_BC.z80" #include "subroutines/getbyte.z80" #include "grammerdata.z80" #include "math.z80" #include "subroutines/chardim.z80" #include "subroutines/ConvOP1.z80" #include "parserinterrupt.z80" #include "startmenu.z80" #include "err.z80" #include "commandtable.z80" .echo "Page 0: ",$8000-$," bytes remaining" #if $>$8000 .error "ERR!! Page 1 is over by ",$-$8000," bytes!" #else .fill $8000-$,255 #endif #include "01.z80" .echo "RamCode : ",RamCodeEnd-RamCodeStart