;;; -*- 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 . ;; BuildProgram: ;; ;; Assemble and link the output program. ;; ;; Input: ;; - curProgFileName = program file name ;; - asmOutputFileName = destination file name ;; - (asmSkipAddressCheck) = 1 to skip the code segment address check ;; - noOutput,(iy+asm_Flag2) = 1 to check for errors only (don't write ;; any output) ;; ;; Destroys: ;; - AF, BC, DE, HL, IX ;; - Current program and section information ;; - all temporary buffers ;; - lots of other stuff BuildProgram: BCALL _RunIndicOn ; ld hl,BuildProgram_CatchError ; call APP_PUSH_ERRORH ;; Create the debug file. BuildProgram_CheckDebugFile: ld hl,DEBUGHEADER_LENGTH ld (debugFileSize),hl ld de,debugFileName call CreateVarCheckDup ld (debugFileStartPtr),de xor a ld (debugFileStartPage),a ld hl,debugHeaderInitData ldir ;; STEP 0: Resolve program dependencies. ;; Import main program ld hl,curProgFileName call AddBuildProgram ;; For each program... call LoadFirstBuildProgram BuildProgram_ImportLoop: ;; for each file marked to be imported by that program... ld hl,(curProgHeader + PROGHEADER_IMPORT_START) ld bc,9 BuildProgram_GetProgramImportsLoop: BCALL _ChkErrBreak or a ld de,(curProgHeader + PROGHEADER_IMPORT_END) sbc hl,de jr nc,BuildProgram_GetProgramImportsDone add hl,de push bc push hl call GetProgramData ;; add the imported file (note: if it's added, it's added ;; to the end of the list) call AddBuildProgram pop hl pop bc add hl,bc jr BuildProgram_GetProgramImportsLoop BuildProgram_GetProgramImportsDone: call LoadNextBuildProgram jr nc,BuildProgram_ImportLoop ;; Done resolving dependencies ld hl,(debugFileStartPtr) ld de,DEBUGHEADER_SYMBOL_START add hl,de ld de,(debugFileSize) ld (hl),e inc hl ld (hl),d ;; STEP 1: Allocate space for program symbols, and link ;; global symbols together. ;; We allocate 3 bytes for each symbol in each program. ;; During the symbol linking phase, these bytes will be filled ;; with either: ;; (a) 00 ?? ?? -> local or unused symbol ;; (b) FF NL NH -> link to symbol at debug offset NH.NL ;; (c) SP SL SH -> global symbol, with string located at SP:SH.SL ;; Clear hash table ld hl,asmHashBins ld bc,512 BCALL _MemClear ;; Save current OPS level ld hl,(OPS) ld de,(OPBase) or a sbc hl,de push hl ;; For each program... call LoadFirstBuildProgram BuildProgram_GenSymbolsLoop: ;; Set the program's symbol offset to the current length of ;; the debug file. ld hl,(debugFileStartPtr) ld de,(curProgInfoOffset) add hl,de ld de,9 add hl,de ld de,(debugFileSize) ld (hl),e inc hl ld (hl),d ;; Allocate 3 bytes in the debug file for each of the ;; program's symbols. ;; Note: I *think* it's safe for us to allocate memory here. ;; (If not, easy fix would be to do all the allocation in ;; one pass, then go back and do the linking in a second ;; pass.) ;; Hash table internal links are simple RAM pointers. These ;; pointers are to the OPS, so they're safe as long as we ;; don't create or delete variables. We won't do any of ;; that unless we run out of memory and there are dirty ;; temporary variables (which there shouldn't be, but maybe ;; we should run a CleanAll to be absolutely sure.) ;; The actual string pointers are absolute pointers to the ;; original source files, and if for some strange reason the ;; debug file were stored *before* a source file in RAM, bad ;; stuff would happen. (Since we just created the debug ;; file a minute ago, the only reason for this would be if a ;; source file were itself stored in temp memory.) ld hl,(curProgSymbolCount) push hl ld d,h ld e,l add hl,de add hl,de ld b,h ld c,l call GrowDebugFile pop hl ld bc,(debugFileSize) jr BuildProgram_AddProgSymbolsBegin BuildProgram_AddProgSymbolsLoop: BCALL _ChkErrBreak ;; HL = number of symbols left to check ;; BC = corresponding debug file offset dec hl dec bc dec bc dec bc push hl call GetProgramSymbolInfo ld a,0 jr c,BuildProgram_AddProgSymbols_IsUnused ;; HL = offset to symbol string call GetProgramDataByte and 0F0h ; high 4 bits of first byte are zero ; for a local label jr z,BuildProgram_AddProgSymbols_IsLocal call ProgramOffsetToAddress push af push hl push bc call FindAsmGlobalSymbol pop bc ;; C -> symbol already exists; DE = debug file offset jr c,BuildProgram_AddProgSymbols_Link ;; NC -> symbol doesn't exist; HL = place to add link to hash table call AddAsmGlobalSymbol pop de pop af jr BuildProgram_AddProgSymbols_NoLink BuildProgram_AddProgSymbols_Link: ;; DE = symbol to link to pop af pop af ld a,0FFh BuildProgram_AddProgSymbols_NoLink: BuildProgram_AddProgSymbols_IsUnused: BuildProgram_AddProgSymbols_IsLocal: ;; A = symbol status / page number ;; DE = symbol pointer / link ld hl,(debugFileStartPtr) add hl,bc ld (hl),a inc hl ld (hl),e inc hl ld (hl),d pop hl BuildProgram_AddProgSymbolsBegin: ;; HL = number of symbols left to check ld a,h or l jr nz,BuildProgram_AddProgSymbolsLoop call LoadNextBuildProgram jr nc,BuildProgram_GenSymbolsLoop ;; Done linking global symbols ;; STEP 2: Pre-define symbols that correspond to constants ;; provided by "pre-compiled header" files. ;; At this point, any symbol that matches a constant will ;; have its value set to the appropriate constant value, and ;; its status set to FE. (Note that this means if multiple ;; files define the same constant, only the first definition ;; will be used - we won't even notice that there's a ;; conflict!) call LoadFirstBuildProgram BuildProgram_SetConstantsLoop: ld hl,(curProgHeader + PROGHEADER_CONSTANT_START) ;; initial sentinel = 3 bytes at start of constant table inc hl jr BuildProgram_SetProgConstantsBegin BuildProgram_SetProgConstantsLoop: add hl,de BCALL _ChkErrBreak ;; HL = offset to position in constant table ;; (prog+HL) = LSB of constant value ;; (prog+HL+1) = MSB of constant value ;; (prog+HL+2 ... prog+HL+n) = compressed string push hl ; save current program offset call ProgramOffsetToAddress call Load_DE_AHL push de ; save constant value call Inc_AHL ld de,OP1 call SymbolStringToRAM push bc call FindAsmGlobalSymbolOP1 pop bc jr nc,BuildProgram_SetProgConstants_NotUsed ld hl,(debugFileStartPtr) add hl,de pop de ;; HL = address of symbol in debug file ;; DE = constant value ld (hl),0FEh inc hl ld (hl),e inc hl ld (hl),d push af BuildProgram_SetProgConstants_NotUsed: pop af pop hl ;; skip forward B+2 bytes ld c,b ld b,0 add hl,bc BuildProgram_SetProgConstantsBegin: inc hl inc hl ld de,(curProgHeader + PROGHEADER_CONSTANT_END) or a sbc hl,de jr c,BuildProgram_SetProgConstantsLoop call LoadNextBuildProgram jr nc,BuildProgram_SetConstantsLoop ;; Free hash table pop de ld hl,(OPBase) add hl,de ld (OPS),hl ;; Anonymous symbol table begins after all normal symbols ld hl,(debugFileSize) ld (anonSymbolStartOffset),hl ;; STEP 3: Clear all remaining symbols. ;; All symbols whose status is not FF (link) or FE (predefined ;; constant) will now have their status set to 0. ld bc,(debugFileStartPtr) add hl,bc ex de,hl ld hl,(programInfoEndOffset) add hl,bc jr BuildProgram_ClearSymbolsBegin BuildProgram_ClearSymbolsLoop: add hl,de ld a,(hl) cp 0FEh jr nc,BuildProgram_ClearSymbolsSkip ld (hl),0 BuildProgram_ClearSymbolsSkip: inc hl inc hl inc hl BuildProgram_ClearSymbolsBegin: or a sbc hl,de jr c,BuildProgram_ClearSymbolsLoop ;; STEP 4: Run initial assembly passes until symbols stop ;; changing. ld a,1 BuildProgram_InitialAssemblyLoop: ld (asmPassNumber),a xor a ld (flags + asm_Flag1),a ;; initialize min/max load PC ld hl,0 ld (asmMaxLoadPC),hl dec hl ld (asmMinLoadPC),hl call AssembleAllSections ld hl,asmPassNumber inc (hl) bit symbolsChanged,(iy+asm_Flag1) jr z,BuildProgram_InitialAssemblyDone ld a,(hl) cp MAX_PASSES jr c,BuildProgram_InitialAssemblyLoop ld hl,emsg_TooManyPasses call ThrowGeneralError ;; UNREACHABLE ; BuildProgram_OpenOutputFile_Error: ; ;; An error occurred while trying to create the output file. ; ;; Try archiving the debug file to free up more RAM. ; cp E_Memory ; jr nz,BuildProgram_OpenOutputFile_Failed1 ; ld a,(debugFileStartPage) ; or a ; BuildProgram_OpenOutputFile_Failed1: ; jq nz,JErrorNo ; ld hl,debugFileName ; push hl ; call ArcUnarcVar ; pop hl ; rst rMOV9TOOP1 ; call ChkFindSymVarDataStart ; jq c,JErrorNo ; call Add_AHL_2 ; ld (debugFileStartPage),a ; ld (debugFileStartPtr),hl BuildProgram_InitialAssemblyDone: ;; STEP 5: Run final assembly pass; write output file. ;; NOTE: We should not throw any assembly-related errors ;; after this point. The early assembly passes should have ;; verified that the program is written correctly, and all we ;; have to do is write it to the output file. This will be ;; important when and if we allow writing output to the ;; archive -- we don't want to have a garbage file written to ;; the archive every time we try, and fail, to assemble the ;; program. ; ld hl,BuildProgram_OpenOutputFile_Error ; call APP_PUSH_ERRORH ld hl,(asmMaxLoadPC) inc hl ld de,(asmMinLoadPC) or a sbc hl,de jr c,BuildProgram_OpenOutputFile_Empty ld de,asmOutputFileName call CreateVarCheckDup ex de,hl ld (asmOutputFilePtr),hl ;; If output file size > 1, clear it ld a,c dec a or b jr z,BuildProgram_OpenOutputFile_Length1 ld a,0FFh BCALL _MemSet BuildProgram_OpenOutputFile_Length1: ; call APP_POP_ERRORH ld a,1 << inFinalPass ld (flags + asm_Flag1),a call AssembleAllSections BCALL _RunIndicOff ret BuildProgram_OpenOutputFile_Empty: ld hl,emsg_ProgramEmpty call ThrowGeneralError ;; UNREACHABLE ; BuildProgram_CatchError: ; call FreeTempBuffers ; BCALL _JErrorNo ; ;; UNREACHABLE ;; AssembleAllSections: ;; ;; Assemble the currently-selected programs. ;; ;; Destroys: ;; - AF, BC, DE, HL, IX AssembleAllSections: ld hl,0 ld (asmAnonSymbolNumber),hl ld (asmLoadPC),hl ld (asmExecPC),hl xor a AssembleAllSections_SegmentLoop: ;; A = current segment (header/code/data/footer) push af call LoadFirstBuildProgram AssembleAllSections_ProgramLoop: call LoadFirstSection jr c,AssembleAllSections_NextProgram AssembleAllSections_SectionLoop: ld a,(curSectionHeader + SECTHEADER_SECTION_TYPE) pop bc push bc ;; skip section if not in the correct segment, or if section ;; is marked as disabled and SECTION_DISABLED | SEGMENT_MASK cp b call z,AssembleSection call LoadNextSection jr nc,AssembleAllSections_SectionLoop AssembleAllSections_NextProgram: call LoadNextBuildProgram jr nc,AssembleAllSections_ProgramLoop pop af inc a cp NUM_SEGMENTS jr c,AssembleAllSections_SegmentLoop ret ;; AssembleSection: ;; ;; Assemble the current section. ;; ;; Destroys: ;; - AF, BC, DE, HL, IX ;; - instrBuf ;; - Assembler state AssembleSection: ld hl,0 ld (asmConditionalCount),hl ld hl,(curSectionHeader + SECTHEADER_DATA_START) jr AssembleSection_Begin AssembleSection_Loop: BCALL _ChkErrBreak push hl ld (asmLineOffset),hl call AssembleProgramInstr pop hl call NextProgramInstr AssembleSection_Begin: ld de,(curSectionHeader + SECTHEADER_DATA_END) or a sbc hl,de add hl,de jr c,AssembleSection_Loop ld hl,(asmConditionalCount) ld a,h or l ret z ld hl,emsg_MissingENDIF call ThrowLineError ;; UNREACHABLE ;; AssembleProgramInstr: ;; ;; Assemble a single instruction from the current program. ;; ;; Input: ;; - HL = program offset to start of instruction ;; ;; Destroys: ;; - AF, BC, DE, HL, IX ;; - instrBuf ;; - Assembler state AssembleProgramInstr: call GetProgramInstr ld a,(hl) ; instruction type / length ld b,a and 3Fh ld c,a inc c ; C = number of arg bytes + 1 inc hl inc hl push hl pop ix ld hl,(asmLoadPC) ld (asmLineLoadPC),hl ld hl,(asmExecPC) ld (asmLineExecPC),hl xor b ; get instruction type jr z,AssembleInstr_Normal cp T_LABEL jq z,AssembleInstr_Label cp T_COMMENT ; comment ret z ;; otherwise it's a special instruction ld a,(ix + -1) dec a add a,a cp S_last * 2 - 1 call nc,Error_Bytecode add a,low(specialInstructionTable) ld l,a ld h,high(specialInstructionTable) ld e,(hl) inc hl ld d,(hl) jq_ Call_DE AssembleInstr_Normal: call ReturnIfConditionalUnsuccessful ;; look up instruction rule ld a,(ix + -1) cp I_last + 1 call nc,Error_Bytecode ld l,a ld h,high(normalInstructionRuleLTable) ld e,(hl) inc h ; -> normalInstructionRuleHTable ld d,(hl) AssembleInstr_NormalLoop: ld a,(de) inc de SWITCH_BEGIN SWITCH_CASE R_BYTE, AssembleInstr_ArgByte SWITCH_CASE R_WORD, AssembleInstr_ArgWord SWITCH_CASE R_REL, AssembleInstr_ArgRel SWITCH_CASE R_SBYTE, AssembleInstr_ArgSByte SWITCH_CASE R_SREG, AssembleInstr_ArgSReg SWITCH_CASE R_DREG, AssembleInstr_ArgDReg SWITCH_CASE R_BITREG, AssembleInstr_ArgBitReg SWITCH_CASE R_RST, AssembleInstr_ArgRst SWITCH_CASE R_IX, AssembleInstr_IXPrefix SWITCH_CASE R_END, AssembleInstr_Done SWITCH_END dec de AssembleInstr_IXPrefix: inc de AssembleInstr_Byte: call EmitByteExec jr AssembleInstr_NormalLoop AssembleInstr_ArgByte: ;; normal byte value (either signed or unsigned) call EvalExprByte AssembleInstr_ByteL: ld a,l jr AssembleInstr_Byte AssembleInstr_ArgWord: ;; word value call EvalExpr call EmitWord jr AssembleInstr_NormalLoop AssembleInstr_ArgRel: ;; relative jump: subtract (PC + 1) (since PC currently ;; equals the address of the arg byte) call EvalExpr push bc ld bc,(asmExecPC) scf sbc hl,bc pop bc AssembleInstr_ArgSByteValue: call RangeCheckSByte jr AssembleInstr_ByteL AssembleInstr_ArgSByte: ;; signed byte value call EvalExpr jr AssembleInstr_ArgSByteValue AssembleInstr_ArgSReg: ;; source register call EvalExprByte ld a,(de) inc de xor l and 0F8h xor l jr AssembleInstr_Byte AssembleInstr_ArgDReg: ;; destination register call EvalExprByte ld a,l and 7 rlca rlca rlca ld l,a ld a,(de) inc de or l jr AssembleInstr_Byte AssembleInstr_ArgBitReg: ;; bit plus register (two expressions) call EvalExprBit ld a,l rlca rlca rlca push af call EvalExprByte ld a,l and 7 pop hl or h ld l,a ld a,(de) inc de or l jr AssembleInstr_Byte AssembleInstr_ArgRst: ;; rst address call EvalExprByte ld a,l and 0C7h jr nz,RangeCheckByte_Error ld a,l or 0C7h jr AssembleInstr_Byte ; Error_InvalidArg: ; ex de,hl ; ld hl,emsg_InvalidArgument ; call ThrowLineError ; ;; UNREACHABLE AssembleInstr_Label: call ReturnIfConditionalUnsuccessful ld d,(ix + -1) ld e,(ix) ld hl,(asmExecPC) ;; fall through ;; SetAsmSymbolValue: ;; ;; Set the value of a symbol. ;; ;; Throw an error if a symbol is defined multiple times during the ;; same assembly pass. ;; ;; Input: ;; - DE = symbol number, or D = X_NEXT_ANON for an anonymous label ;; - HL = value to set symbol to ;; ;; Destroys: ;; - AF, DE, HL SetAsmSymbolValue: ld a,d cp X_NEXT_ANON jr nz,SetAsmSymbolValue_NotAnon push hl ld hl,(asmAnonSymbolNumber) inc hl ld (asmAnonSymbolNumber),hl dec hl call GetAsmAnonSymbolPtr jr c,SetAsmSymbolValue_NewAnon push af or a jr nz,SetAsmSymbolValue_ArchivedAnon jr SetAsmSymbolValue_SetAnon SetAsmSymbolValue_NewAnon: set symbolsChanged,(iy + asm_Flag1) push bc ld bc,2 call GrowDebugFile ex de,hl pop bc pop de ld (hl),e inc hl ld (hl),d AssembleInstr_Done: ret SetAsmSymbolValue_NotAnon: push hl push de call GetAsmSymbolPtr or a jr nz,SetAsmSymbolValue_Archived ld a,(asmPassNumber) inc (hl) cp (hl) ld (hl),a jr c,SetAsmSymbolValue_AlreadyDefined inc hl SetAsmSymbolValue_SetAnon: pop de pop de ld a,(hl) ld (hl),e inc hl cp e ld a,(hl) ld (hl),d jr nz,SetAsmSymbolValue_Changed cp d ret z SetAsmSymbolValue_Changed: set symbolsChanged,(iy + asm_Flag1) ret SetAsmSymbolValue_Archived: call Inc_AHL SetAsmSymbolValue_ArchivedAnon: call Load_DE_AHL pop af pop hl or a sbc hl,de ret z ;; if we ever get here, it's a bug BCALL _ErrIterations ;; UNREACHABLE SetAsmSymbolValue_AlreadyDefined: pop de ld hl,emsg_SymbolRedefined call ThrowLineError ;; UNREACHABLE ;; EvalExprByte: ;; ;; Retrieve the value of an argument expression, and check that the ;; value is suitable to be written as a byte. (Since there is no way ;; in general of knowing whether the user intends for a value to be ;; signed or unsigned, all values between -128 and 255 are considered ;; legal byte values.) ;; ;; If the input is not valid, throw an error. Don't throw an error if ;; we are in pass 1, however, since the value may be out of range due ;; to undefined symbols. ;; ;; Input: ;; - IX = expression pointer ;; - C = expression byte count + 1 ;; ;; Output: ;; - IX, C updated ;; - HL = value ;; ;; Destroys: ;; - AF EvalExprByte: call EvalExpr RangeCheckByte: ld a,h or a ret z ;; fall through ;; RangeCheckSByte: ;; ;; Check that the input value is suitable to be written as a signed ;; byte (between -128 and 127.) If the input is not valid, throw an ;; error. ;; ;; Input: ;; - HL = value ;; ;; Destroys: ;; - AF RangeCheckSByte: ld a,l add a,a sbc a,a RangeCheckSByte_Test: xor h ret z RangeCheckByte_Error: ld a,(asmPassNumber) dec a ret z ex de,hl ld hl,emsg_ArgOutOfRange call ThrowLineError ;; UNREACHABLE ;; EvalExprBit: ;; ;; Retrieve the value of an argument expression, and check that the ;; input value is between 0 and 7. If the input is not valid, throw ;; an error. ;; ;; Input: ;; - IX = expression pointer ;; - C = expression byte count + 1 ;; - HL = value ;; ;; Destroys: ;; - AF EvalExprBit: call EvalExpr ld a,l cp 8 jr nc,RangeCheckByte_Error xor a jr RangeCheckSByte_Test ;; GetAsmSymbolValue: ;; ;; Get the value of a symbol. (Symbols are referred to by their ;; indices as defined by the current program file; note that if we're ;; assembling more than one program file, the same symbol number will ;; refer to different symbols at different times during the build ;; process.) ;; ;; Input: ;; - HL = symbol number, or H = X_NEXT_ANON or X_PREV_ANON for an ;; anonymous label ;; ;; Output: ;; - HL = value ;; - Carry flag set if symbol has not been defined in this pass ;; - A = 0 if symbol has never been defined (in which case HL contains ;; garbage) ;; ;; Destroys: ;; - AF GetAsmSymbolValue: push de ex de,hl ld hl,(asmAnonSymbolNumber) ld a,d cp X_NEXT_ANON jr z,GetAsmSymbolValue_NextAnon cp X_PREV_ANON jr z,GetAsmSymbolValue_PrevAnon push bc call GetAsmSymbolPtr call Load_B_DE_AHL ld hl,asmPassNumber ld a,b cp (hl) ex de,hl pop bc pop de ret GetAsmSymbolValue_PrevAnon: dec hl GetAsmSymbolValue_NextAnon: call GetAsmAnonSymbolPtr sbc a,a inc a jr c,GetAsmAnonSymbolPtr_NeverDefined ld e,(hl) inc hl ld d,(hl) ex de,hl GetAsmAnonSymbolPtr_NeverDefined: pop de ret ;; GetAsmSymbolPtr: ;; ;; Get the address of a symbol entry in the debug file. (Each symbol ;; entry is 3 bytes: flags, then value.) ;; ;; Input: ;; - DE = symbol number ;; ;; Output: ;; - AHL = address of symbol in debug file ;; ;; Destroys: ;; - AF, DE GetAsmSymbolPtr: call GetProgramSymbolOffsetDE jr c,Error_Bytecode ld hl,(curProgSymbolOffset) add hl,de add hl,de add hl,de ex de,hl push bc GetAsmSymbolPtr_Loop: ld hl,(debugFileStartPtr) ld a,(debugFileStartPage) call Add_AHL_DE ;; check if symbol is an alias push af push hl call Load_B_DE_AHL pop hl pop af inc b jr z,GetAsmSymbolPtr_Loop pop bc ret Error_Bytecode: ld hl,emsg_BytecodeError jq_ ThrowLineError ;; UNREACHABLE ;; GetAsmAnonSymbolPtr: ;; ;; Get the address of an anonymous symbol entry in the debug file. ;; (Each anonymous symbol entry is 2 bytes only.) ;; ;; Input: ;; - HL = anonymous symbol index ;; ;; Output: ;; - Carry flag set if symbol has not yet been created ;; - AHL = address of symbol in debug file ;; ;; Destroys: ;; - F, DE GetAsmAnonSymbolPtr: add hl,hl ld de,(anonSymbolStartOffset) add hl,de ex de,hl ld hl,(debugFileSize) dec hl sbc hl,de ret c ld hl,(debugFileStartPtr) ld a,(debugFileStartPage) call Add_AHL_DE or a ret ;; AddBuildProgram: ;; ;; Add a program to the list of files to be assembled. (The debug ;; file is assumed to be stored in main RAM.) ;; ;; Input: ;; - HL = address of program name (in TI 9-byte format) ;; ;; Destroys: ;; - AF, BC, DE, HL AddBuildProgram: ;; check if name matches an already-imported program push hl ld hl,(debugFileSize) push hl AddBuildProgram_Loop: pop hl ld bc,-11 ; NOTE: assuming debug header < 11 bytes add hl,bc jr nc,AddBuildProgram_AddNew pop de push de push hl ld b,9 call CompStrsN jr nz,AddBuildProgram_Loop ;; name matches -> nothing more to do pop af pop af ret AddBuildProgram_AddNew: ld bc,11 call GrowDebugFile ld hl,(debugFileSize) ld (programInfoEndOffset),hl pop hl BCALL _Mov9B ret ;; LoadFirstBuildProgram: ;; ;; Set up pointers and buffers for reading the first input file. ;; ;; Destroys: ;; - AF, BC, DE, HL ;; - OP1 LoadFirstBuildProgram: ld hl,DEBUGHEADER_LENGTH jr LoadBuildProgram ;; LoadNextBuildProgram: ;; ;; Set up pointers and buffers for reading the next input file. ;; ;; Output: ;; - Carry flag set if no more programs to read ;; ;; Destroys: ;; - AF, BC, DE, HL ;; - OP1 LoadNextBuildProgram: ld hl,(curProgInfoOffset) ld bc,11 add hl,bc LoadBuildProgram: ld (curProgInfoOffset),hl ld de,(programInfoEndOffset) or a sbc hl,de ccf ret c add hl,de ex de,hl ld hl,(debugFileStartPtr) ld a,(debugFileStartPage) call Add_AHL_DE ld de,OP1 ld bc,9 call FlashToRAM call Load_DE_AHL ld (curProgSymbolOffset),de jq_ LoadProgram ;; GrowDebugFile: ;; ;; Insert memory at the end of the debug file (which must be in main ;; RAM.) ;; ;; Input: ;; - BC = number of bytes to insert ;; ;; Output: ;; - DE = address of newly-inserted memory ;; ;; Destroys: ;; - AF, HL GrowDebugFile: ld a,(debugFileStartPage) or a jr nz,GrowDebugFile_Archived ld hl,(debugFileSize) add hl,bc ld (debugFileSize),hl ld de,(debugFileStartPtr) sbc hl,bc add hl,de call DoInsertMem ld hl,(debugFileStartPtr) dec hl dec hl ld a,(hl) add a,c ld (hl),a inc hl ld a,(hl) adc a,b ld (hl),a ret GrowDebugFile_Archived: ld a,E_Archived BCALL _JError ;; UNREACHABLE