title MLOAD Multi-File Hex Load Utility name ('MLOAD') $$VER macro db '2.7' endm $$PRG macro db 'MLOAD' endm ; ; ********************************* ; * MLOAD.MAC * ; * Multi-file Hex Load Utility * ; * for CP/M * ; ********************************* ; ; ; Replacement for the CP/M 2.x "LOAD" program: ; This program fixes many of the problems associated ; with the "CP/M 2.x", load program, ; and adds many new features. ; ; ---------------- ; ; Rev 2.7 ; 07/06/96 ; Property of NightOwl Software, Inc. Fort Atkinson, WI 53538 ; Allow .REL file loading ; ; ---------------- ; ; Rev 2.6 ; 06/07/92 ; Property of NightOwl Software, Inc. Fort Atkinson, WI 53538 ; Slightly changed by W.Cirsovius ; ; ---------------- ; ; Rev 2.5 ; 03/10/88 ; Property of NightOwl Software, Inc. Fort Atkinson, WI 53538 ; Written by Ron Fowler, Nightowl Software, Inc. ; ; ---------------- ; Notice: this program is NOT public domain; copyright is retained by ; NightOwl Software, Inc. of Fort Atkinson, WI ... All Rights Reserved. ; ; License is granted for free use and re-distribution this program, as ; long as such use and re-distribution is done without profit. ; ; ---------------- ; ; modification history: ; ; 2.5 (WOD) This version corrects a bug that overlayed the first six ; bytes of the CCP. The error did not show up unless a ; jump to the CCP was done without a warm boot since MLOAD ; used. This source file has been modified here with ; concurrence of the author of MLOAD, Ron Fowler. ; ; 2.4 (RGF) We apologize for this relatively insubstantial update, ; but someone has caused what we consider to be a problem, ; by making changes to the program, and re-releasing under ; the same version number. The changes in this case were ; conversion of the opcode fields (but not the comments, ; can you believe that??) of every line to upper case! That ; totally invalidated the CRC of the source file, since there ; are now two different MLOAD 2.3's running around. ; ; We DO NOT want these stupid mixed upper/lower case changes. ; Someone somewhere has decided that this is the way assembly ; language source should be, and we most VEHEMENTLY disagree. ; It's a pain in the neck to make changes to and we don't ; care to run our programs through conversion programs every ; time we make changes. ; ; So ... leave the case of this file AS IS. Any changes made ; to this program and not co-ordinated through us may very ; well endanger availability of source code when we make ; future updates. 'nuff said --NightOwl Software ; ; 2.3 (RGF) Trivial cosmetic changes ; 2.2 (RGF) Modified copyright notice to show new owner of the ; program. ; 2.1 (RGF) Fixed problem on disk-full when writing output file ; (mload previously didn't error out on a full disk) ; 2.0 (RGF) Added the ability to pre-load a non-hex file, allowing ; mload to be used to load hex file patches (obviating any ; need to use DDT). The normal mload syntax is preserved. ; the first (and only the first) filespec (after the "=", ; if used) may be non-hex; the filetype must be specified. ; Examples: ; ; 1) mload ws.com,wspatch ; 2) mload MEXTEST=MEX112.COM,MXO-US13 ; 3) mload ws.ovr,ovrpatch ; ; The first example loads WS.COM, overlays it with ; wspatch.hex, and writes the output to WS.COM. The ; second example loads MEX112.COM, overlays it with ; MXO-US13.HEX, and writes the output file to MEXTEST.COM. ; (note that the second example is the recommended technique, ; since it preserves the original file). The third example ; loads WS.OVR and patches it with the file "OVRPATCH.HEX". ; ; Also added this rev: ZCPR2-style du specs are now fully ; supported, for both input and output files. Thus, the ; following command lines are permissable: ; ; b3>mload a4:myfile.com=0:bigfil,b6:patch1,c9:patch2 ; a6>mload b5:=c3:mdm717.com,mdmpatch ; ; After loading, an additional information line is now printed ; in the statistics report, which displays the true size of the ; saved image (the previous report was technically correct, but ; could result in confusion for certain kinds of files with ; imbedded "DS" and "ORG" statements in the original source code). ; ; 1.0 - 1.4 (RGF) change log removed to conserve space ; ; originally written by ron fowler, fort atkinson, wisconsin ; ; ; ; For assembly with asm.com or mac (delete above title line if ; assembling with asm.com). ; ; This program is a replacement for the cp/m "LOAD" program. ; Why replace "LOAD"? well... LOAD.COM has a few deficiencies. ; For example, if your hex file's origin is above 100h, LOAD.COM ; prepends blank space to the output file to insure it will work ; as a CP/M transient. It cares not if the file is not intended ; as a CP/M transient. it also doesn't like hex records with mixed ; load addresses (for example, one that loads below a previous record -- ; which is a perfectly legitimate happenstance). Also, LOAD.COM ; can load only one program at a time, and has no provision for ; a load bias in the command specification. Finally, there is no ; provision for user specification of the output file name. ; ; ; Hence, this program.... ; ;------------------------------------------------------------ ; ; Syntax is as follows: ; ; mload {{,...} {bias} ; ; where is the (optional!;) output file name (only the drive ; spec and primary filename may be specified; the output filetype is ; derived exclusively from the 3-byte string at 103h within MLOAD), ; specifies files to load and is the offset within ; the saved image to apply when loading the file. ; ; MLOAD with no arguments prints a small help message -- this message ; is also printed whenever a command line syntax error occurs. ; ; Filenames may contain drive/user specs, and must not contain wildcards. ; Input filenames must be separated by commas, and a space is required ; between the last filename and the optional bias. ; ; A load information summary is printed at the successful conclusion ; of the load. Any errors in loading will generally include the name ; of the file in question. ; ; If no output filename is specified, it will be derived from the first ; input filename, with filetype of 'COM', if not otherwise specified ; (this default filetype may be patched directly into mload via DDT ; (or with MLOAD itself, using a patch file) -- its location is at 103H ; in MLOAD.COM). Note that a command line of the form "C:=" ; will place the output file on the "C" drive with the same primary ; filename as the input file. ; ; In its simplest form, MLOAD's syntax is identical to LOAD.COM; thus ; there should be no problem in learning to use the new program. The ; only significant difference here is that, under LOAD.COM, all files ; are output starting at 100h, even if they originate elsewhere. MLOAD ; outputs starting at the hex file origin (actually, the first hex rec- ; ord specifies the output load address). The bias option may be used ; to override this. ; ; An example should clarify this. Suppose you have a file that loads ; at 1000h. LOAD.COM would save an output file that begins at 100h and ; loads past 1000h (to wherever the program ends). MLOAD will save an ; output file starting from 1000h only. If, for some reason you need the ; file to start at 100h in spite of its 1000h origin (i can think of sev- ; eral circumstances where this would be necessary), you'd have to specify ; a bias to mload. thus, using this example, "MLOAD MYFILE 0F00" would do. ; ; Note that this program re-initializes itself each time it is run. ; Thus, if your system supports a direct branch to the tpa (via a zero-length ; .COM file, or the ZCPR "GO" command), you may safely re-execute MLOAD. ; ; Please report any bugs, bug fixes, or enhancements to ; ; "FORT FONE FILE FOLDER" rcpm/cbbs ; Fort Atkinson, Wisconsin ; (414) 563-9932 (no ring back) ; ; --Ron Fowler ; 03/08/84 updated 1/31/85 ; ;------------------------------------------------------------ ; ; CP/M equates ; OS equ 0000h ; Warm boot BDOS equ 0005h ; System entry (also top of mem pntr) FCB equ 005ch ; Default file control block DMA equ 0080h ; Default buffer ; TPA equ 0100h ; Transient program area ; _drv equ 1 _nam equ 8 _ext equ 3 FCBlen equ 33 ; ; CP/M system calls ; .conout equ 2 ; Print char .string equ 9 ; Print string .vers equ 12 ; Get OS version .seldsk equ 14 ; Select disk drive .open equ 15 ; Open file .close equ 16 ; Close file .srcfrs equ 17 ; Search for first .fsrnxt equ 18 ; Search for next .delete equ 19 ; Delete file .rdseq equ 20 ; Read record .wrseq equ 21 ; Write record .make equ 22 ; Create file .getdsk equ 25 ; Return dflt drive # .setdma equ 26 ; Set dma address .usrcod equ 32 ; Get/set user # .rdrnd equ 33 ; Read random .wrrnd equ 34 ; Write random .filsiz equ 35 ; Compute file size .setrnd equ 36 ; Set random ; _get equ -1 ; CPM.3 equ 30h ; ; ASCII character constants ; null equ 00h bel equ 07h tab equ 09h lf equ 0ah cr equ 0dh eof equ 1ah ; CP/M end-of-file mark eot equ '$' ; RecLng equ 128 HiMask equ 11110000b LoMask equ 00001111b NoMSB equ 01111111b ; ; The default output filetype is located at 103h for easy patching ; OutTyp: db 'COM' $ILL.CPU: $$PRG db ' requires Z80 CPU',eot $ILL.OS: $$PRG db ' requires CP/M 3.x',eot MLOAD: sub a ; Test right machine ld de,$ILL.CPU jp po,CPU.Ok ErrStr: ld c,.string call BDOS ; Tell error jp OS ; .. break CPU.Ok: ld c,.vers call BDOS ; Get system version cp CPM.3 ld de,$ILL.OS jr c,ErrStr ld sp,LocStk ; Load local stack call ImStr ; Sign on $$PRG db '-Z80 ver. ' $$VER db cr,lf,lf db '[From: Copyright (C) 1983, 1984, 1985' db ' by NightOwl Software, Inc.]' db cr,lf db 'Mods 1992, 1996 - Werner Cirsovius' db cr,lf,null call SetUp ; Initialize Main: call NxtFile ; Parse and read next input file jr c,Done ; No more... call LoadFile ; Yep, load it call CloseFile ; Close it (in case MP/M or TurboDOS) jr Main ; Maybe more Done: call WrtFile ; Write the output file jp OS ; Warm-boot ; ; Load program initialization ; SetUp: ld hl,VarSet ; Initialize variables ld de,Vars ld bc,VarLen ; By moving in default values ldir ld de,(CmdPtr) ; Get first free mem pointer ld hl,DMA ; Point to command tail bufr ld a,(hl) ; Get its length inc hl or a ; Does it have any length? jp z,Help ; Nope, go give usage help ld c,a ; Yep, get length to b ld b,0 ldir ; Move cmd tail to buffer xor a ld (de),a ; Stuff a terminator inc de ; Point to first free memory ld (FileBuf),de ; Set up file buffer ld hl,(BDOS+1) ; Get top of memory pointer sub e ; Round system to page boundary ld c,a ; With result in bc ld a,h sbc a,d ld b,a ld h,d ; Buffer pointer to hl ld l,e inc de dec bc ld (hl),null ; Clear buffer ldir ; ; Look for a bias specification in command line ; ld hl,(CmdPtr) ; Point to command buffer-1 dec hl call ScanBlnk ; Scan past blanks or a ; No non-blank chars? jp z,Help ; Then go print help text FndSpc: inc hl ; Point to next ld a,(hl) ; Fetch it or a ; Test it ret z ; Line ended, return cp ' ' ; Nope, test for blank jr nz,FndSpc ; Not blank, continue call ScanBlnk ; Skip blanks or a ; End-of-line? ret z ; Return if so ; ; HL points to bias in command line ; ld de,0 ; Init bias call HexDig ; Insure a hex digit jp c,SynErr ; Bad... HexLoop: ld a,(hl) ; No. get next char inc hl ; Skip over it call HexDig ; Test for hex digit jr c,HexEnd ex de,hl ; Bias to hl add hl,hl ; Skift left 4 to make room add hl,hl ; .. for new hex digit add hl,hl add hl,hl ex de,hl ; Back to de add a,e ; Add in new digit ld e,a jr nc,HexLoop ; Jump if no 8-bit ovfl inc d ; Carry jr HexLoop HexEnd: or a ; Must end on null terminator jp nz,SynErr ld (Bias),de ; Stuff bias ret ; Done ; ; Parse next input name, and open resultant file ; NxtFile: xor a ld (REL.Flg),a ; Clear rel file access ld hl,(CmdPtr) ; Get command line pointer Next2: ld de,FCB ; Destination fcb call FParse ; Parse a filename cp '=' ; Stopped on output specifier? jr nz,NotEQ ld a,(FO+1+_drv) ; Insure no name yet specified cp ' ' jp nz,SynErr ; Syntax error if already named ld a,(OutFlag) ; Already been here? or a jp nz,SynErr ; Can't be here twice inc a ; Flag that we've been here ld (OutFlag),a inc b ; Insure no ambiguous output name dec b jp nz,FN.Err inc hl ; Skip over '=' push hl ; Save cmd line pointer ld hl,FCB-1 ; Move the name to output name hold ld de,FO ld bc,1+_drv+_nam+_ext ldir ; Drive spec too pop hl ; Restore command line pointer jr Next2 ; Go parse another NotEQ: cp ',' ; Stopped on comma? jr z,GotComma ; Jump if so ld (hl),null ; Nope, insure end of input dec hl ; Don't advance over fake end GotComma: inc hl ; Skip over comma ld (CmdPtr),hl ; Save new command line pntr ld a,b ; Get ambig char count or a ; Test it jp nz,FN.Err ; Allow no ambig characters ld (BufPtr),a ; Force a disk read ld de,FCB+_drv ; Look at parsed filename ld a,(de) cp ' ' ; Blank? (input ended?) scf ; Get carry ready in case so ret z ; Return cy if input gone dec de ; Nope, point de to start of fcb Open2: push de ; Try to open the file ld c,.open call .BDOS pop de inc a ; Return=0ffh? jr nz,OpenOk ; Jump if not ; ; File not found: if filetype blank, set to 'hex' and try again ; ld hl,FCB+_drv+_nam; Point to file type ld a,(hl) ; Anything there? cp ' ' jp nz,NoFilErr ; Yes, so file not found ld (hl),'H' ; Nope, fill in 'hex' inc hl ld (hl),'E' inc hl ld (hl),'X' jr Open2 ; Go try again ; ; Here after a good file open ; OpenOk: call $$HEXchk ; Is this a hex file? ret z ; If so, all done call $$RELchk ; Is this a rel file? ld hl,REL.Flg jr z,OpenREL ; Set flag if so ld hl,COM.Flg ; No, get pointer to flag ld a,(hl) ; Loading first file? or a ret nz ; If not, ignore type, consider hex OpenREL: inc (hl) ; Else, set the flag ret ; ; Load current file ; LoadFile: ld a,(COM.Flg) ; Loading a com file? rra jp c,LoadCOM ; Jump if so ld a,(REL.Flg) ; Loading a rel file? rra jp c,LoadREL ; Jump if so ld hl,(Bias) ; Else get bias on top of stack push hl ; ; Load a .HEX record ; LoadLoop: call Get ; Get next file byte sbc a,':' ; Look for start-record mark jr nz,LoadLoop ; Scan until found ld (CkSum),a ; Got it, init checksum to zero ld d,a ; Upper byte of rec cnt=0 pop bc ; Retrieve bias adrs push bc ; Save it again call GetBytCS ; Get hex byte w/checksum ld e,a ; De now has record length or a ; Test it jr z,.pop.HL ; All done if=0 call GetBytCS ; Hi byte of rec ld adrs ld h,a ; Accumulate in hl call GetBytCS ; Get lo byte ld l,a ; Put lo in l ld a,(LoadFlg) ; Test load flag or a call z,LoadInit ; Not first record, initialize push hl ; Save load address add hl,de ; Add in record length dec hl ; Make highest, not next call CheckMem ; Check enough memory pop hl ; Restore load address add hl,bc ; Add bias to load adrs push de ; Save record length push hl ld hl,(ByteCnt) ; Add record length to byte count add hl,de ld (ByteCnt),hl pop de ld hl,(Offset) ; Calculate true memory adrs add hl,de ; Hl=true loading adrs pop de ; Restore record length call GetBytCS ; Skip unused byte of INTEL format ; ; Move the record into memory ; RecLoop: call GetBytCS ; Get hex byte ld (hl),a ; Store it in buffer inc hl ; Point to next dec e ; Count down jr nz,RecLoop ; Until record all read call GetBytCS ; Get checksum byte jr z,LoadLoop ; Good load, go do nxt record jp CS.Err ; Final add cksum should sum 0 ; ; Get next hex byte from input, and ; accumulate a checksum ; GetBytCS: push hl push de push bc ; Save em all call HexIn ; Get hex byte ld b,a ; Save in b ld hl,CkSum ; Add to checksum ld a,(hl) add a,b ld (hl),a ld a,b ; Get byte back pop bc pop de ; Restore checksum .pop.HL: pop hl ; Restore other regs ret ; ; Routine to get next byte from input...forms ; byte from two ascii hex characters ; HexIn: call Get ; Get next input file byte call HexValidate ; Convert to binary w/validation rlca ; Move into ms nybble rlca rlca rlca and HiMask ; Kill possible garbage push af ; Save it call Get ; Get next byte call HexValidate ; Convert it, w/validation pop bc ; Get back first or b ; Or in second ret ; Good byte in a ; ; Check enough memory ; CheckMem: ld a,(HiPC) ; A new high? sub l ld a,(HiPC+1) sbc a,h ret nc ; Return if not ld (HiPC),hl ; Yep, update hipc push de ; Save reclen ld de,(Offset) ; Get offset to form true memory adrs add hl,de ; Add in offset add hl,bc ; And bias ld (HiLoad),hl ; Mark highest true memory load adrs ld a,(BDOS+2) ; Validate against top-mem pointer cp h jp c,MemFull ; Jump if out of memory pop de ; Restore reclen ret ; ; Get - utility subroutine to get next ; byte from disk file Get: push hl ; Save all regs push de push bc ld a,(BufPtr) ; Get input bufr pointer and RecLng-1 ; Wound back to 0? call z,.DiskRd ; Go read sector if so inc a ld (BufPtr),a ; Store 0 as new buf ptr ld d,0 ; Else form 16 bit offset ld e,a ld hl,DMA-1 ; From tbuf add hl,de ; Add in offset ld a,(hl) ; Get next byte cp eof ; End of file? call z,TstREL ; Test for rel file if so or a ; Return carry clear pop bc ; Restore and return pop de pop hl ret ; ; Found EOF (1ah) pattern - valid on rel file only ; TstREL: ld a,(REL.Flg) ; Test rel file rra ld a,(hl) ; Get byte ret c ; Ok if REL file jp EOF.Err ; Error if not ; ; Read next sector from disk ; .DiskRd: call DiskRd jp nz,EOF.Err ; Error if phys end of file ret DiskRd: ld c,.rdseq ; Bdos "READ SEC" function ld de,FCB call .BDOS ; Read sector or a ret ; ; Load a .REL file ; LoadREL: ld a,-1 ld (RELbits),a ; Init .REL bit count RELloop: call GetBit ; Get bit from rel file jr c,SpcBit call GetByte ; Get a constant byte call StByte jr RELloop SpcBit: call Get2Bits ; Read two address bits or a ; Test address jp nz,RELerr ; Invalid here ld de,RELloop push de ; Set return address call Get4Bits ; Read four bits add a,a ; For index ld e,a ld d,0 ld ix,RELexec ; Point to execution table add ix,de ; Build index ld e,(ix+0) ; Fetch address ld d,(ix+1) push de ; Execute item ret ; ; Found items - ; 0 - Entry symbol ; 2 - Program name ; SymbItem: call BField ; Load name of symbol ret ; ; Found item 7 - Define entry point ; DefENT: exx call ValAField ; Load valid AField call BField ; Get BField exx ret ; ; Found item A - Define data size ; LdDSize: exx ld de,0 ; Init valid size call ValAField ; Get valid AField TstSize: or a sbc hl,de ; Verify correct size exx ret z ; Ok jr RELerr ; ; Found item D - Define program size ; LdCSize: exx ld de,0 ; Init valid size ld c,01b ; Set program relative call ValCSeg jr TstSize ; Test valid size ; ; Found item B - Set location counter ; SetLoc: call ValAField ; Get location counter ld a,(LoadFlg) ; Test load in progress or a call z,LoadInit ; Init load if not ret ; ; Found item E - End module ; EndOfModule: exx call ValAField ; Get transfer value ld a,l or h ; Verify 0000 exx pop bc jp z,LoadREL ; Try next module jr RELerr ; ; Found item F - End file ; EndOfFile: pop bc ; Clean stack ret ; And exit ; ; Detected not supported REL-item - exit ; RELerr: call ErrExit ; Exit with message db 'Not supported REL80 code detected' db cr,lf db 'Use a full function linker instead' db cr,lf,null ; ; Load valid AField ; ValAField: ld c,00b ; Set absolute ValCSeg: call LdRELadr ; Load address cp c ; Verify correct address mode ret z jr RELerr ; ; Store byte into memory ; StByte: push hl push af push hl ld bc,(Bias) call CheckMem ; Check enough memory ld hl,(Bytecnt) inc hl ; Advance byte count ld (Bytecnt),hl pop hl add hl,bc ld de,(Offset) add hl,de ; Build real address pop af ld (hl),a ; Save byte pop hl inc hl ret ; ; Load 16 bir word into reg HL ; LdREL16: call GetByte ; Load lo byte ld l,a call GetByte ; Then hi byte ld h,a ret ; ; Read two control bits ; Get2Bits: ld a,2 ; Get counter jr GetxBits ; ; Read three control bits ; Get3Bits: ld a,3 ; Get counter jr GetxBits ; ; Read four special link bits ; Get4Bits: ld a,4 ; Get counter jr GetxBits ; ; Load a byte from rel file ; GetByte: ld a,8 ; Get counter GetxBits: push bc ld b,a ; Unpack count ld c,0 ; Init result GetBitLoop: call GetBit ; Load bit rl c ; Shift it in djnz GetBitLoop ld a,c pop bc ret ; ; Load a bit from rel file - Carry reflects that bit ; GetBit: push hl ld hl,RELbyte ; Point to byte ld a,(hl) inc hl inc (hl) ; Advance bit count jr nz,MoreBits call Get ; Get new byte ld (hl),-8 ; Init remaining count MoreBits: add a,a ; Get carry dec hl ld (hl),a ; Bring back new byte pop hl ret ; ; Load address into Accu mode and address into reg HL ; LdRELadr: call Get2Bits ; Get address bits push af call LdREL16 ; Load word pop af ret ; ; Load a BField - lll.ch1.-chn ; BField: call Get3Bits ; Get length of symbol or a ; Test any jr nz,BF.not0 inc a ; Map 0 -> 1 BF.not0: ld b,a BFloop: call GetByte ; Get characters djnz BFloop ret ; ; Load a .COM file ; LoadCOM: inc (hl) ; Bump the comfile flag ld hl,TPA ; Set origin call LoadInit ; And initialize ld de,(Bias) ; Add in bias add hl,de ld de,(Offset) ; And offset add hl,de ex de,hl ; De has absolute mem adrs of load COMloop: ld hl,RecLng ; Calculate next dma add hl,de ld a,(BDOS+2) ; Check for space cp h jp c,MemFull ; Jump if none push hl ; Else save next dma push de ; And this dma call SetDMA ; Set this dma call DiskRd ; Read next record pop hl ; Recall this dma pop de ; De=next dma jr nz,LoadEnd ; Jump if end of read ld hl,(COM.size) ; No, advance com byte count ld bc,RecLng add hl,bc ld (COM.size),hl jr COMloop ; Continue LoadEnd: dec hl ; One less byte is highest ld (HiLoad),hl ; Set a new high ld hl,(COM.size) ; Hi pc=bytecount+100h ld de,TPA add hl,de ld de,(Bias) ; Add in bias add hl,de ld (HiPC),hl ld de,DMA ; Reset dma for hex files ; ; Set disk buffer ; SetDMA: ld c,.setdma call .BDOS ret ; ; Write output file ; WrtFile: ld de,FCB ; Point to fcb push de ; Save 2 copies of pointer push de call InitFCB ; Initialize output fcb ld hl,FO ; Move output name in dec de ; Point to user # (prior to fcb) ld bc,1+_drv+_nam ; Move user, drive, primary name ldir ld a,(hl) ; Output type blank? cp ' ' jr nz,WrtExtCp ; Jump if not ld hl,OutTyp ; Yes, move dflt output filetype in WrtExtCp: ld bc,_ext ldir pop de ; Restore fcb pointer ld c,.delete ; Erase any existing file call .BDOS pop de ; Restore fcb pointer ld c,.make ; Create a new file call .BDOS inc a ; Good create? jp z,DirFull ; Goto directory full error if not ld de,(HiLoad) ; Yep, get top of bufr pntr ld hl,(FileBuf) ; Get start of bufr adrs ld a,e ; Calculate output file size sub l ld c,a ; With result in bc ld a,d sbc a,h ld b,a ld a,b ; Test length or c jp z,LoadErr ; Nothing to write??? ld de,FCB ; Get fcb pointer WrtLoop: push bc ; Save count push de ; And fcb pointer ex de,hl ; Get memory pointer to de ld hl,RecLng ; Add in sector length for next pass add hl,de ex (sp),hl ; Save next dma push hl ; Above fcb call SetDMA ; Set transfer address pop de ; Fetch fcb pointer push de ; Save it again ld c,.wrseq ; Write a sector call .BDOS or a ; Test result jp nz,DskFull ; Disk full error... ld hl,(RecCnt) ; No,increment count of records inc hl ld (RecCnt),hl pop de ; Restore fcb pointer pop hl ; And memory write pointer pop bc ; And count ld a,c ; Subtract 128 (sec size) from count sub RecLng ld c,a jr nc,WrtLoop ; Jump if some left ld a,b ; Hi-order borrow sub 1 ; Do it (can't "DCR B", doesn't affect cy) ld b,a ; Restore jr nc,WrtLoop ; Jump if more left call CloseFile ; Close output file ; ; Report statistics to console ; call ImStr db cr,lf,'Loaded ',null ld hl,(ByteCnt) ; Print # bytes call DecOut call ImStr db ' bytes (',null call HexOut call ImStr db 'h)',null call ImStr db ' to file %',null ld a,(COM.Flg) ; Did we load a comfile too? or a jr z,NotCOM ; Jump if not call ImStr db cr,lf,'Over a ',null ld hl,(COM.size) call DecOut call ImStr db ' byte binary file',null NotCOM: call ImStr db cr,lf,'Start address: ',null ld hl,(LoadAdr) ; Print loading address call HexOut call ImStr db 'h Ending address: ',null ld hl,(HiPC) ; Print ending load address call HexOut call ImStr db 'h, ',null ld hl,(Bias) ; Get bias ld a,l or h ; .. test any jr nz,TellBias ; .. yeap call ImStr db 'No bias',null jr SkpBias TellBias: call ImStr db 'Bias: ',null call HexOut call ImStr db 'h',null SkpBias: call ImStr db cr,lf db 'Saved image size: ',null ld hl,(RecCnt) ; Get count of image records push hl ; Save it ld h,l ld l,0 srl h rr l call DecOut ; Print it call ImStr db ' bytes (',null call HexOut ; Now in hex call ImStr db 'h, - ',null pop hl ; Recall record count call DecOut ; Print it call ImStr db ' record(s))',cr,lf,null ld hl,(LoadAdr) ; Fetch loading address ld de,TPA or a sbc hl,de ; Test if =tpa ret z ; Return if tpa call ImStr ; Not, so print warning msg db cr,lf,bel db '++ Warning: program origin NOT at 100H ++' db cr,lf,null ret ; Done ; ; *********************** ; * utility subroutines * ; *********************** ; ; Routine to close any open file ; CloseFile: ld de,FCB ld c,.close call .BDOS inc a ; Test close result ret nz jp ClosErr ; Jump if error ; ; Print message in-line with code ; ImStr: ex (sp),hl ; Message pntr to hl call PrAtHL ; Print it ex (sp),hl ; Restore and return ret ; ; Print msg pointed to by hl until null. expand ; '%' char to current filename. ; PrAtHL: ld a,(hl) ; Fetch char inc hl ; Point to next or a ; Terminator? ret z ; Then done cp '%' ; Want filename? jr z,PrtFN ; Go do it if so call Type ; Nope, just print char jp PrAtHL ; Continue PrtFN: push hl ; Save pointer push bc ld a,(FCB) ; Fetch dr field of FCB dec a ; Default drive? call m,GetDsk ; Get logged-in drive # add a,'A' ; Make drive name printable call Type ; Print it ld a,(FCB-1) ; Get user # cp -1 ; Null? call z,GetUsr ; Iff so, get current user ld l,a ; To hl ld h,0 call DecOut ; Print it ld a,':' ; Drive names followed by colon call Type ld hl,FCB+_drv ; Setup for name ld b,_nam ; Print up to 8 call PrtNam ld a,'.' ; Print dot call Type ld b,_ext ; Print filetype field call PrtNam pop bc pop hl ; Restore and continue jr PrAtHL ; ; print file name .HL max length in b. don't print spaces ; PrtNam: ld a,(hl) ; Fetch a char cp ' ' ; Blank? call nz,Type ; Print if not inc hl ; Move to next djnz PrtNam ; Continue ret ; ; Print HL in decimal on console ; DecOut: push hl ; Save everybody push de push bc ld bc,-10 ; Conversion radix ld de,-1 DecLoop: add hl,bc inc de jr c,DecLoop ld bc,10 add hl,bc ex de,hl ld a,h or l call nz,DecOut ; This is recursive ld a,e add a,'0' call Type pop bc pop de pop hl ret ; ; Newline on console ; NL: ld a,cr call Type ld a,lf jr Type ; ; Print hl on console in hex ; HexOut: ld a,h ; Get hi call HexByte ; Print it ld a,l ; Get lo, fall into HexByte ; ; Type accumulator on console in hex ; HexByte: push af ; Save byte rra ; Get ms nybble.. rra ; ..into lo 4 bits rra rra call Nybble pop af ; Get back byte Nybble: and LoMask ; Mask ms nybble add a,90h ; Add offset daa ; Decimal adjust a-reg adc a,40h ; Add offset daa ; Fall into type ; ; Type char in a on console ; Type: push hl ; Save all push de push bc ld e,a ; CP/M outputs from e ld c,.conout call .BDOS pop bc pop de pop hl ret ; ; Scan to first non-blank char in string @hl ; ScanBlnk: inc hl ; Next ld a,(hl) ; Fetch it cp ' ' jr z,ScanBlnk ret ; ; Get hex digit and validate ; HexValidate: call HexDig ; Get hex digit ret nc jp FormErr ; Jump if bad ; ; Get hex digit, return cy=1 if bad digit ; HexDig: cp '0' ; Lo boundary test ret c ; Bad already? cp '9'+1 ; No, test hi jr c,HexCnvt ; Jump if numeric cp 'A' ; Test alpha ret c ; Bad? cp 'F'+1 ; No, upper alpha bound ccf ; Pervert carry ret c ; Bad? sub 'A'-'9'-1 ; No, adjust to 0-f HexCnvt: and LoMask ; Make it binary ret ; ; ****************** ; * error handlers * ; ****************** ; FN.Err: call ErrExit ; Exit with message db 'Ambiguous file name: % not allowed.',null NoFilErr: call ErrExit db 'File % not found.',null DskFull: call ErrExit db 'Disk full.',null DirFull: call ErrExit db 'Directory full.',null EOF.Err: call ErrExit db 'Premature end-of-file in %',null CS.Err: call ErrExit db 'Checksum error in %',null ClosErr: call ErrExit db 'Can''t close %',null MemFull: call ErrExit db 'Memory full while loading %',null FormErr: call ErrExit db 'Format error in file %',null LoadErr: call ErrExit db 'Writing %, nothing loaded',null SynErr: call NL call ImStr db ' Command line syntax error' db cr,lf,lf,null Help: call ErrExit ; Print help text $$PRG db ' syntax:',cr,lf,cr,lf $$PRG db ' {=}{,...} {}',cr,lf db tab,'(brackets denote optional items)',cr,lf,cr,lf db tab,' is the optional output filename',cr,lf db tab,' are input file(s)',cr,lf db tab,' is a hex load offset within the output file' db cr,lf,cr,lf db tab,' may be an optional non-HEX or -REL file to be patched',cr,lf db tab,'by subsequently named HEX or REL files (specifying',cr,lf db tab,'The filetype enables this function).' db cr,lf,cr,lf db 'Drive/user notation may be used in all file specifications' db cr,lf db '(e.g., "B3:MYFILE.COM, "A14:MDM7.HEX").' db cr,lf,null ; ; General error handler ; ErrExit: call NL ; New line pop hl ; Fetch error msg pointer call PrAtHL ; Print it call NL jp OS ; Done ; ; Initialize load parameters ; LoadInit: ld a,1 ; First record, set load flag ld (LoadFlg),a ld (LoadAdr),hl ; Save load address ld (HiPC),hl ; And hi load push de ; Save record length ex de,hl ; De=load address ld hl,(FileBuf) ; Get address of file buffer or a sbc hl,de ; Subtract load adrs from file buffer ld (Offset),hl ; Save as load offset push de ; Save load address on stack push bc ; Save bias ld de,FO+1+_drv ; Check output filename ld a,(de) ; (first char) cp ' ' jr nz,NameSkp ; Jump if so ld hl,FCB+_drv ; Get first name pointer ld bc,_nam ; (don't include drive spec) ldir ; ; Check for outflg=1 (presence of an "="). note that the ; filename may well be blank, and yet outflg <>0, for example ; in the case of "A:=" or "C4:=". in ; this case, we want to remember the drive/user specified, but ; use the first input file to form the output name. otherwise, ; we use the current drive/user. ; ld a,(OutFlag) ; Was there an "="? or a jr nz,NameSkp ; Jump if so ld hl,FO ; Get destination pointer call GetUsr ; Get current user # ld (hl),a inc hl ; Point to drive call GetDsk ; Get it inc a ; Fcb's drive is 1-relative ld (hl),a NameSkp: ld a,1 ; Insure "=" cannot occur anymore ld (OutFlag),a pop bc ; Restore bias pop hl ; Load address to hl pop de ; Restore record length ret ; ; ********************************* ; * file name parsing subroutines * ; ********************************* ; ; Credit where credit's due: ; -------------------------- ; these routines were lifted from bob van valzah's ; "FAST" program. ; ; ********************************* ; * file name parsing subroutines * ; ********************************* ; ; Getfn gets a file name from text pointed to by reg hl into ; an fcb pointed to by reg de. leading delimeters are ; ignored. allows drive spec of the form (drive/user). ; this routine formats all 33 bytes of the fcb (but not ran rec). ; ; Entry de first byte of fcb ; Exit b=# of '?' in name ; fcb-1= user # parsed (if specified) or 255 ; FParse: call InitFCB ; Init 1st half of fcb call GetStart ; Scan to first character of name call GetDrv ; Get drive/user spec. if present ld a,b ; Get user # or 255 cp -1 ; 255? jr z,.FParse ; Jump if so dec de ; Back up to byte preceeding fcb dec de ld (de),a ; Stuff user # inc de ; Onward inc de .FParse: call Get.P.S ; Get primary and secondary name ret ; ; Initfcb fills the fcb with dflt info - 0 in drive field ; all-blank in name field, and 0 in ex,s1,s2,rc, disk ; allocation map, and random record # fields ; InitFCB: push hl push de call GetUsr ; Init user field pop de pop hl push de ; Save fcb loc dec de ld (de),a ; Init user # to currnt user # inc de ex de,hl ; Move it to hl ld (hl),0 ; Drive=default inc hl ; Bump to name field ld b,_nam+_ext ; Zap all of name fld InitLoop: ld (hl),' ' inc hl djnz InitLoop ld b,FCBlen-_nam-_ext ZeroLoop: ld (hl),0 ; Zero others, up to nr field inc hl djnz ZeroLoop ex de,hl ; Restore hl pop de ; Restore fcb pointer ret ; ; Getstart advances the text pointer (reg hl) to the first ; non delimiter character (i.e. ignores blanks). returns a ; flag if end of line (00h or ';') is found while scaning. ; Exit hl pointing to first non delimiter ; a clobbered ; zero set if end of line was found ; GetStart: call GetChar ; See if pointing to delim? ret nz ; Nope - return or a ; Physical end? ret z ; Yes - return w/flag inc hl ; Nope - move over it jr GetStart ; And try next char ; ; Getdrv checks for the presence of a du: spec at the text ; pointer, and if present formats drive into fcb and returns ; user # in b. ; ; Entry hl text pointer ; de pointer to first byte of fcb ; Exit hl possibly updated text pointer ; de pointer to second (primary name) byte of fcb ; b user # if specified or 0ffh ; GetDrv: ld b,-1 ; Default no user # push hl ; Save text pointer DrvScan: call GetChar ; Get next char inc hl ; Skip pointer over it jr nz,DrvScan ; Scan until delimiter cp ':' ; Delimiter a colon? inc de ; Skip dr field in fcb in case not pop hl ; And restore text pointer ret nz ; Return if no du: spec ld a,(hl) ; Got one, get first char call UpCase ; May be drive name, cvt to upper case cp 'A' ; Alpha? jr c,IsNum ; Jump to get user # if not sub 'A'-1 ; Yes, convert from ascii to # dec de ; Back up fcb pointer to dr field ld (de),a ; Store drive # into fcb inc de ; Pass pointer over drv inc hl ; Skip drive spec in text IsNum: ld a,(hl) ; Fetch next inc hl cp ':' ; Du delimiter? ret z ; Done then dec hl ; Nope, back up text pointer ld b,0 ; Got a digit, init user value U.Loop: ld a,b ; Get accumulated user # add a,a ; * 10 for new digit add a,a add a,b add a,a ld b,a ; Back to b ld a,(hl) ; Get text char sub '0' ; Make binary add a,b ; Add to user # ld b,a ; Updated user # inc hl ; Skip over it ld a,(hl) ; Get next cp ':' ; End of spec? jr nz,U.Loop ; Jump if not inc hl ; Yep, return txt pointer past du: ret ; ; Get.p.s gets the primary and secondary names into the fcb. ; Entry hl text pointer ; Exit hl character following secondary name (if present) ; Get.P.S: ld c,_nam ; Max length of primary name ld b,0 ; Init count of '?' call GetName ; Pack primary name into fcb ld a,(hl) ; See if terminated by a period cp '.' ret nz ; Nope - secondary name not given ; Return default (blanks) inc hl ; Yup - move text pointer over period GotDot: ld a,c ; Yup - update fcb pointer to secondary or a jr z,Get.FExt inc de dec c jr GotDot Get.FExt: ld c,_ext ; Max length of secondary name call GetName ; Pack secondary name into fcb ret ; ; Getname copies a name from the text pointer into the fcb for ; a given maximum length or until a delimiter is found, which ; ever occurs first. if more than the maximum number of ; characters is present, character are ignored until a ; a delimiter is found. ; Entry hl first character of name to be scanned ; de pointer into fcb name field ; c maximum length ; Exit hl pointing to terminating delimiter ; de next empty byte in fcb name field ; c max length - number of characters transfered ; GetName: call GetChar ; Are we pointing to a delimiter yet? ret z ; If so, name is transfered inc hl ; If not, move over character cp '*' ; Ambigious file reference? jr z,Ambiguous ; If so, fill the rest of field with '?' cp '?' ; Afn reference? jr nz,NotWild ; Skip if not inc b ; Else bump afn count NotWild: call UpCase ; If not, convert to upper case ld (de),a ; And copy into name field inc de ; Increment name field pointer dec c ; If name field full? jr nz,GetName ; Nope - keep filling jr GetDelim ; Yup - ignore until delimiter Ambiguous: ld a,'?' ; Fill character for wild card match FillWild: ld (de),a ; Fill until field is full inc de inc b ; Increment count of '?' dec c jr nz,FillWild ; Fall thru to ingore rest of name GetDelim: call GetChar ; Pointing to a delimiter? ret z ; Yup - all done inc hl ; Nope - ignore antoher one jr GetDelim ; ; Getchar gets the character pointed to by the text pointer ; and sets the zero flag if it is a delimiter. ; Entry hl text pointer ; Exit hl preserved ; a character at text pointer ; z set if a delimiter ; GetChar: ld a,(hl) ; Get the character, test for delim ; ; Test char in a for filename delimiter ; cp '/' ret z cp '.' ret z cp ',' ret z cp ' ' ret z cp ':' ret z cp '=' ret z or a ; Set zero flag on end of text ret ; ; BDOS entry: preserves bc, de. if system call is a file ; function, this routine logs into the drive/ ; user area specified, then logs back after ; the call. ; .BDOS: call FilfChk ; Check for a file function jr nz,F.BDOS ; Jump if not a file function call GetDU ; Get drive/user ld (SaveDU),hl ld a,(de) ; Get fcb's drive ld (FCBdrv),a ; Save it dec a ; Make 0-relative jp m,BDOS.. ; If not default drive, jump ld h,a ; Copy to h BDOS..: xor a ; Set fcb to default ld (de),a dec de ; Get fcb's user # ld a,(de) ld l,a inc de ; Restore de call SetDU ; Set fcb's user ; ; Note that unspecified user # (value=0ffh) becomes ; a GetUsr call, preventing ambiguity. ; call F.BDOS ; Do user's system call push af ; Save result push hl ld a,(FCBdrv) ; Restore fcb's drive ld (de),a ld hl,(SaveDU) ; Restore prior drive/user call SetDU pop hl ; Restore bdos result registers pop af ret ; ; Local variables for bdos replacement routine ; SaveDU: dw 0 ; Saved drive,user FCBdrv: db 0 ; Fcb's drive DMAadr: dw DMA ; Current dma adrs ; F.BDOS: push de push bc ld a,c ; Doing setdma? cp .setdma jr nz,F.BDOS.. ; Jump if not ld (DMAadr),de ; Yep, keep a record of dma addresses F.BDOS..: call BDOS pop bc pop de ret ; ; Get drive, user: H=drv, L=user ; GetDU: call GetUsr ; Get user # push af ; Save it call GetDsk ; Get drive ld h,a ; Drive returned in h pop af ld l,a ; User in l ret ; ; Set drive, user: H=drv, L=user ; SetDU: push bc ; Don't modify bc push de push hl ; Save info ld e,h ; Drive to e ld c,.seldsk ; Set it call F.BDOS pop hl ; Recall info push hl ld e,l ; User # to e ld c,.usrcod call F.BDOS ; Set it pop hl pop de pop bc ret ; ; Check for file-function: open, close, read random, write ; random, read sequential, write sequential. ; FilfChk: ld a,c ; Get function # cp .open ret z ret c ; Ignore lower function #'s cp .close ; (they're not file-related) ret z cp .rdseq ret z cp .wrseq ret z cp .rdrnd ret z cp .wrrnd ret z cp .srcfrs ret z cp .fsrnxt ret z cp .delete ret z cp .make ret z cp .filsiz ret z cp .setrnd ret ; ; Convert char to upper case ; UpCase: cp 'a' ; Check lo bound ret c cp 'z'+1 ; Check hi ret nc sub 'a'-'A' ; Convert ret ; ; Check for rel filetype in fcb name ; $$RELchk: push hl ld hl,$$REL ; Point hl to "REL" jr XXchk ; ; Check for hex filetype in fcb name ; $$HEXchk: push hl ld hl,$$HEX ; Point hl to "HEX" XXchk: push de push bc ld b,_ext ; Type is 3 chars ld de,FCB+_drv+_nam; Point de to type field $HEXloop: ld a,(de) and NoMSB ; Ignore attributes cp (hl) inc hl inc de jr nz,HEXexit ; Jump if not com djnz $HEXloop HEXexit: pop bc ; Z reg has result pop de pop hl ret ; $$HEX: db 'HEX' $$REL: db 'REL' ; ; Routine to return user # without disturbing registers ; GetUsr: push hl push de push bc ld c,.usrcod ld e,_get call .BDOS pop bc pop de pop hl ret ; ; Routine to return drive # without disturbing registers ; GetDsk: push hl push de push bc ld c,.getdsk call .BDOS pop bc pop de pop hl ret ; ; Table for REL file items ; RELexec: dw SymbItem ; 0 - Entry symbol dw RELerr ; 1 - Not supported dw SymbItem ; 2 - Program name dw RELerr ; 3 - Not supported dw RELerr ; 4 - Not supported dw RELerr ; 5 - Not supported dw RELerr ; 6 - Not supported dw DefENT ; 7 - Define entry point dw RELerr ; 8 - Not supported dw RELerr ; 9 - Not supported dw LdDSize ; A - Define data size dw SetLoc ; B - Set location counter dw RELerr ; C - Not supported dw LdCSize ; D - Define program size dw EndOfModule ; E - End module dw EndOfFile ; F - End file ; ; These are the initial values of the variables, and ; are moved into the variables area by the setup routine. ; if you add variables, be sure to add their intial value ; into this table in the order corresponding to their ; occurance in the variables section. ; VarSet: dw 0 ; Bias dw 0 ; Hiload dw 0 ; Hipc db 0 ; Cksum dw CmdBuf ; Cmdptr db 0 ; Bufptr db 0 ; Laodflg dw CmdBuf ; Filebuf dw 0 ; Offset dw 0 ; Loadadr db 0,0 db ' ' ; FO dw 0 ; Reccnt dw 0 ; Bytecnt db 0 ; Com.flg dw 0 ; Com.size db 0 ; Outflag ; VarLen equ $-VarSet ; Define length of init table ; ; working variables ; Vars equ $ ; Define variables area start ; Bias: ds 2 ; Load offset HiLoad: ds 2 ; Highest true load address HiPC: ds 2 ; Highest pc CkSum: ds 1 ; Record checksum CmdPtr: ds 2 ; Command line pointer BufPtr: ds 1 ; Input buffer pointer LoadFlg: ds 1 ; Something-loaded flag FileBuf: ds 2 ; File buffer location Offset: ds 2 ; Load offset into buffer LoadAdr: ds 2 ; Load address FO: ds 1+_drv+_nam+_ext; Output drive+name RecCnt: ds 2 ; Output file record count ByteCnt: ds 2 ; Output file bytes loaded count COM.Flg: ds 1 ; Flags com file encountered COM.size: ds 2 ; Size of a loaded com file OutFlag: ds 1 ; Flags an "=" present in cmd line RELbyte: db 0 RELbits: db -1 REL.Flg: db 0 ; ; end of working variables ; ; stack stuff ; ; ds 2*50 ; 50-level stack LocStk equ $ ; CmdBuf equ $ ; Command buffer location ; end MLOAD