TITLE "LINKPRL Map-generating linker" ;================================================================ VER EQU 33 ; Copyright (C) 1989 by Harold F. Bower ;---------------------------------------------------------------- ; Link MicroSoft .REL files to .PRL-type with Relocation bit map. ; Originally developed in 1983 in a crude form to produce bit ; maps for small relocatable utilities. This version implements ; the standard RSX format with header record, object with ORG of ; 100H, followed by bit map. ; ; Harold F. Bower ; P.O. Box 313 ; Ft. Meade, MD 20755 ;---------------------------------------------------------------- ; Standard equates BELL EQU 07H ; Bell character HT EQU 09H ; Tab character LF EQU 0AH ; Line Feed CR EQU 0DH ; Carriage Return ; BDOS function calls CONOUT EQU 2 ; Console output PTSTR EQU 9 ; Print string RDSTR EQU 10 ; Read console string OPENF EQU 15 ; Open file CLOSEF EQU 16 ; Close file DELF EQU 19 ; Delete file READSQ EQU 20 ; Read sequential WRITSQ EQU 21 ; Write sequential MAKEF EQU 22 ; Make file SETDMA EQU 26 ; Set dma address ; Default memory locations WBOOT EQU 0000H ; CP/M Warm Boot entry BDOS EQU 0005H ; CP/M Bdos entry point FCB EQU 005CH ; Default file control block BUFF EQU 0080H ; Default CP/M sector buffer ; Miscellaneous Values KYBLEN EQU 32 ; Length of keyboard buffer ; Begin program by checking for valid file name from command line BEGIN: LD (STACK),SP ; Save entry stack for Help return LD SP,STACK ; Set local stack CALL PRT001 ; Print opening banner DEFB CR,LF,'Bit-map Linker V',VER/10+'0','.' DEFB VER MOD 10+'0',HT,'19 Aug 89' DEFB ' (C) H.F.Bower',CR,LF,LF,'$' PRT001: POP DE CALL PRTMSG LD A,(FCB+1) ; Check for filename CP ' ' JP Z,NONAME ; ..jump Error and abort if none CP '/' ; Is it a Help request? JP NZ,BEGIN0 ; ..jump if not and continue CALL PRT002 DEFB CR,LF,'LINKPRL',CR,LF,LF DEFB ' Purpose:',CR,LF DEFB HT,'Produce COM or PRL file from MicroSoft REL' DEFB CR,LF,LF,' Usage:',CR,LF DEFB HT,'LINKPRL // - Print this message',CR,LF DEFB HT,'LINKPRL FOO - Link FOO.REL',CR,LF,LF,'$' PRT002: POP DE ; Else print help CALL PRTMSG LD SP,(STACK) ; Restore entry stack RET ; ..and quit here BEGIN0: LD HL,FCB+9 ; Check for filetype LD A,(HL) CP ' ' ; If none JR NZ,START1 ; .assume .REL LD HL,RELTYP ; ..and load FCB CALL MOVTYP START1: CALL OPENFILE ; Open source .REL file ; Now the program starts... ; Internal Register Useage: ; B = bit count for source byte ; C = source byte shifted, b7=current ; D = General Purpose counter ; E = output byte for map ; HL = pointer to input file ; BC' = Program 'ORG' location ; DE' = Data 'ORG' location ; HL' = 16-bit accumulator for ; displacement calculations ; IX = physical load location ; IY = points to flags ; Calculate available memory and zero storage ; locations up to the BDOS base page LD HL,(BDOS+1) ; Get BDOS starting address LD L,0 ; ..and set page boundary DEC HL ; ...down one for safety LD DE,TEMP ; Get first address PUSH DE ; ..and save OR A SBC HL,DE ; ..and calculate difference LD C,L LD B,H POP HL ; Restore starting addr LD (HL),0 ; ..zero first spot LD E,L LD D,H ; Copy addr INC DE ; ..plus one LDIR ; ..move the 0 along ; Set initial values in storage since memory was set to ; zero by action above LD A,128 ; Set pointer to trigger LD (INPTR),A ; initial read LD IX,OUTFIL ; Set IX for load LD IY,FLAGS ; Set IY to flags byte MODE: CALL PRT003 ; Prompt for operation mode DEFB CR,LF,'Link to .COM or .PRL (C/P) :$' PRT003: POP DE CALL PRTMSG LD A,KYBLEN ; Set buffer length CALL GETINP LD A,(HL) ; Just look at the first CALL UPPER CP 03H ; Crtl-C? JP Z,WBOOT CP 'C' ; Check operating mode RES 3,(IY+0) ; ..clear Map generation flag for COM LD DE,0100H ; Set default load addr for files JR Z,ADRLOP ; ..jump if .COM CP 'P' ; Is it a PRL request? JR NZ,MODE ; ..jump If not 'C' or 'P', error SET 3,(IY+0) ; Else set PRL Map generation flag ADRLOP: PUSH DE ; Save address CALL PRT004 DEFB CR,LF,'Enter Hex load addr (Default = $' PRT004: POP DE CALL PRTMSG POP HL ; Bring address back.. CALL PRTHEX ; ..and print it PUSH HL ; Now save address again CALL PRT005 ; ..and print end of prompt line DEFB 'H) :$' PRT005: POP DE CALL PRTMSG LD A,KYBLEN ; Set line length CALL GETINP ; ..and get a line DEC HL ; Get count LD B,(HL) ; ..to B INC HL EX DE,HL LD A,B OR A ; Cnt = 0 for default JR Z,DEFAULT LD HL,0000 ; Start with clear register CALL GETNUM EX (SP),HL ; Swap new number for stack LD A,B ; Check for valid Hex address OR A JR Z,DEFAULT ; Jump if Ok EX (SP),HL ; If bad, swap back again CALL PRT006 DEFB CR,LF,BELL,'++ Hex Digit Error ++',CR,LF,'$' PRT006: POP DE CALL PRTMSG ; ..print error msg POP DE ; Restore default address JR ADRLOP ; ..and try again DEFAULT: POP HL ; Get address from stack LD (ORGADR),HL LD HL,BUFF CALL READ ; Set bit position JR LOOP0 ; ..and jump to test bit ;===============================================; ; M a i n P r o g r a m L o o p ; ;===============================================; LOOP: CALL GETBIT ; Get a source bit into position LOOP0: JR NZ,LOOP1 ; ..jump if 1x form and test next CALL BYTE0 ; 0 = load 8 bits absolute JR LOOP ; ..and back for more ; We have 1x form. Check the second bit LOOP1: CALL GETBIT ; Get a source bit into position JR Z,LOOP2 ; ..jump if it is 10x form CALL GETBIT ; We have 11x, Check 3rd bit JR NZ,COMREL ; 1 = Common, 0 = Data ; We have 110 = Data Relative. CALL ADDR16 ; Get 16 bits, data relative EXX ; Do the math in alternate regs LD HL,(TEMP) ; Load the offset ADD HL,DE ; ..and add DSEG base from DE' JR OUTV ; Write a 01 to Bit Map ; We have 111 = Common Relative. COMREL: CALL ADDR16 ; Get 16 bits, common rel PUSH HL ; Write 01 to map PUSH DE LD DE,(COMMAD) ; Add Common Base address LD HL,(TEMP) ; ..to accumulated offset ADD HL,DE POP DE EX (SP),HL EXX POP HL JR OUTV ; Save value & write 01 to Bit Map ; We have 10x form. Check the third bit LOOP2: CALL GETBIT ; Get a bit in position JR Z,SPECL ; ..jump if 100 (Special Link Item) ; We have 101 = Program Relative. CALL ADDR16 ; Get 16 bits, prog relative EXX ; ..writing 01 in bit map LD HL,(TEMP) ADD HL,BC OUTV: LD A,L ; Vector here to output EXX ; ..relative addresses CALL BYTE0V ; Low byte has 0 Map Bit EXX LD A,H ; Get Hi byte EXX CALL BYTE1V ; ..write with 1 Map Bit JR LOOP ; Arrive here if special link (100xxxxxxxx) ; We don't do much with these, most just print information SPECL: CALL GETTYP ; Get 4 bit type EXX ; Swap to alternates to get free HL' LD HL,SPLTBL ; Offset from table start ADD A,A ; Double value for 2-byte entries ADD A,L LD L,A JR NC,SPECL0 ; Bypass next if no Overflow INC H SPECL0: LD A,(HL) ; Addr.low to A.. INC HL LD H,(HL) ; Addr.high to H LD L,A ; Complete address to HL PUSH HL ; Address to stack to simulate CALL EXX ; ..back to primary registers RET ; Jump to Address on stack SPLTBL: DEFW ENTRY ; 0 = Entry Symbol DEFW COMNAM ; 1 = Common Block Name DEFW PGNAME ; 2 = Program Name DEFW SEARCH ; 3 = Library Search DEFW UNDEF0 ; 4 = (undefined) DEFW COMMON ; 5 = Common Size DEFW CHNEXT ; 6 = Chain External DEFW ENTRPOINT ; 7 = Entry Point DEFW UNDEF1 ; 8 = (undefined) DEFW EXTOFF ; 9 = External + offset DEFW DATSIZ ; 10 = Data Size DEFW LODLOC ; 11 = Load Location DEFW CHNADDR ; 12 = Chain Address DEFW PRGSIZ ; 13 = Program Size DEFW FINI ; 14 = End of Program DEFW FINI ; 15 = Module End ; End of activity, so wind it up and exit. FINI: BIT 3,(IY+0) ; Are we generating a Bit Map? JR Z,FINI0A ; ..jump if not LD A,(COUNT) ; Else do we have any Map Bits left? OR A JR Z,FINI0 ; ..jump if not FINLOP: OR A ; Insure Zero bit shifted RL E ; ..to fill last byte INC A ; Bump map bit count CP 8 ; End of a byte yet? JR C,FINLOP ; ..loop if not LD HL,(BITMAP) ; Save the final Map Byte LD (HL),E INC HL ; ..and bump last byte pointer LD (BITMAP),HL ; Save highest byte address FINI0: CALL PRT007 DEFB CR,LF,'Bit Map begins @ ORG + $' PRT007: POP DE CALL PRTMSG ; Print Start of Map message FINI0A: LD DE,(PROGSZ) ; Calculate CSEG+DSEG size LD HL,(DATASZ) ADD HL,DE BIT 3,(IY+0) ; Are we generating a map? JR Z,SMALL ; ..jump if not to save just CSEG+DSEG CALL PRTHEX ; Else Print 16-bit Hex value LD HL,(BITMAP) ; Get ending address DEC H ; ..compensating for Size Page LD DE,OUTFIL ; Now get starting addr OR A SBC HL,DE ; Calculate size CALL PRT008 DEFB CR,LF,'Bit Map ends @ ORG + $' PRT008: POP DE CALL PRTMSG ; Print Map Ending message.. CALL PRTHEX ; ..and HEX address INC H ; ..(correcting size for save) SMALL: LD A,L ; Check for partial page AND 7FH PUSH AF ; ..save result in Z flag ; Divide HL by 128. This code is shorter than 7 shifts right ; with Zero fill. RL L ; MSB of L to carry flag LD L,H ; Move high byte to low LD H,0 ; ..and null high byte ADC HL,HL ; Shift all left, carry to LSB of L POP AF ; Return partial page flag (Z) JR Z,SMALL0 ; ..jump if no partial page INC HL ; Else compensate by bumping count SMALL0: LD C,L ; Move sector count to BC LD B,H CALL WRITEIT ; Write the file to disk LD DE,FCB LD C,CLOSEF ; ..and close it CALL BDOS INC A JR NZ,FINI2 ; Jump if Close OK CALL PRT009 ; ..else print error message DEFB CR,LF,'Cannot Close .PRL file !',BELL,CR,LF,'$' PRT009: POP DE CALL PRTMSG FINI2: JP 0000H ; Quit with warm boot ENTRY: PUSH DE ; Print entry name(s) when found CALL PTEXIT DEFB 'Entry point : $' COMNAM: PUSH DE ; Print common block when found CALL PTEXIT DEFB 'Common name : $' PGNAME: PUSH DE ; Print program name when found CALL PTEXIT DEFB CR,LF,'Program Name : $' SEARCH: PUSH DE ; Print library to search CALL PTEXIT DEFB 'Search Library : $' UNDEF0: PUSH DE ; Print reserved error if found CALL PTEXIT DEFB CR,LF,'UNDEFINED : $' PTEXIT: POP DE ; Restore string start addr CALL PRTMSG ; .and print the string POP DE CALL PNAME ; ..followed by item name JP SZEXIT ; ...and size/address ; Define COMMON if found COMMON: CALL GET16 ; Get the value PUSH DE ; While temp has value CALL ABVCTR ; ..print label & name DEFB 'COMMON : $' ABVCTR: POP DE ; Restore string start addr CALL PRTMSG CALL PNAME ; Print item name CALL PRT010 DEFB ' = $' PRT010: POP DE CALL PRTMSG ; ..and equate string POP DE CALL PRT16 ; Now print value LD HL,(TEMP) ; Get common address LD (COMMAD),HL ; ..and save it JP VECTOR ; List external chain references when found CHNEXT: CALL GET16 ; Get the address PUSH DE ; While temp has value CALL ABVCTR ; Go print label name & value DEFB 'Chain EXTERNAL : $' ; List entry points when found ENTRPOINT: CALL GET16 ; Get the address PUSH DE ; While temp has value CALL ABVCTR ; Go print label name & value DEFB 'Entry Point : $' ; Print A & B error if found UNDEF1: CALL GET16 ; Get address PUSH DE ; Print label & name CALL ABVCTR ; Go print label name & value DEFB 'Undefined !!! : $' ; Print External + Offset if found EXTOFF: PUSH DE CALL CHNAD0 ; Print message DEFB 'External + Offset = $' ; Print Chain Address if found CHNADDR: PUSH DE CALL CHNAD0 DEFB 'Chain Address = $' CHNAD0: POP DE CALL PRTMSG ; Print the addressed message POP DE CALL PVAL ; ..and its value JR SZEXIT ; Print data area size when found DATSIZ: PUSH DE CALL PRT011 DEFB 'Data Area Size : $' PRT011: POP DE CALL PRTMSG ; Print the text message POP DE CALL PVAL ; ..and the value/address LD (DATASZ),HL SET 0,(IY+0) ; Show data area OK JR SZEXIT ; Print program size when found PRGSIZ: PUSH DE CALL PRT012 DEFB 'Program Size : $' PRT012: POP DE CALL PRTMSG ; Print the text message POP DE CALL PVAL ; ..and its value LD (PROGSZ),HL SET 1,(IY+0) ; Show data area OK SZEXIT: CALL SETSTAT VECTOR: CALL CRLF ; Wind up on a new line JP LOOP ; Print load location when found LODLOC: CALL GET16 ; Get a 16-bit address LD (LODPTR),HL ; ..store BIT 7,(IY+0) ; Is this first reference? JR NZ,LOD1 ; ..jump if not, only print 1st Load BIT 3,(IY+0) ; Is this a PRL operation? JR Z,LOD1 ; ..jump and don't print if .COM PUSH DE CALL PRT013 DEFB 'Load Location : $' PRT013: POP DE CALL PRTMSG ; Else Print Load Location msg CALL PRT16 ; ..and 16-bit value POP DE CALL CRLF ; Move to a new line LOD1: JP CHECKLOAD ; Pad to location with Nulls ;..... ; Subroutine for name/value retrieval PNAME: LD D,3 ; Get char count XOR A CALL GBITS ; Assemble 3-bits for count OR A ; Is it 0 for 8 chars? JR NZ,PNAME0 ; ..jump if not LD A,8 ; Else set to desired eight PNAME0: LD D,A ; Move cc to counter PNAME1: PUSH DE ; Get & print 1 char LD D,8 ; ..8 bits/char CALL GBITS CALL PRINTC ; Print it POP DE DEC D JR NZ,PNAME1 ; Go back for more RET PVAL: CALL GET16 ; Get 16 bit value PRT16: LD HL,(TEMP) ; Retrieve 16-bit value PRTHEX: LD A,H CALL HEXOUT ; Print hi-byte in HEX.. LD A,L JP HEXOUT ; ..then lo-byte and quit ;------------------------------------------------------------- ; L o w e r - l e v e l B i t M a n i p u l a t i o n ;------------------------------------------------------------- ; Get a bit from the input file, reading disk file as necessary GETBIT: RL C ; Rotate byte for test DJNZ READX ; ..jump if new byte not necessary ; Need another byte from the file, so fall thru.. READ: PUSH AF ; Set up addresses and PUSH DE ; ..read a byte LD A,(INPTR) ; Check pointer for disk read CP 128 CALL NC,DISKRD ; Read disk if pointer > 127 LD E,A ; Set pointer for offset LD D,0 LD HL,BUFF ; Start from base ADD HL,DE INC A ; Bump pointer LD (INPTR),A ; ..and save LD C,(HL) ; Get a byte LD B,8 ; ..and set counter POP DE POP AF READX: BIT 7,C ; Set Zero flag to MSB of subject byte RET ; Accumulate 16-bits from input file as pointer. ; EXIT: Variable TEMP contains 16-bit value GET16: XOR A LD D,2 ; Get number type CALL GBITS ; ..but don't do anything with it LD (TYPLOD),A ; Save load type ADDR16: CALL GETBYT ; Get low byte EX AF,AF' ; ..and temporarily save CALL GETBYT ; Now get hi byte LD H,A ; Prepare to save 16-bit value & return EX AF,AF' ; Get Low byte back LD L,A LD (TEMP),HL ; Save the Word if needed RET ;..... ; Output a byte with a 1 Map Bit BYTE1V: SCF ; Set Carry flag for 1 in Bit Map JR CHKWRT ; ..and do it ;..... ; Accumulate 8 bits into a byte and output with a 0 Map Bit BYTE0: CALL GETBYT ; Gather 8 bits into a byte BYTE0V: OR A ; Reset varry for 0 in Bit Map ;..fall thru to.. ;..... ; Check for output write status on Map Bit ; Carry Flag unaffected until shifted into E Register CHKWRT: BIT 2,(IY+0) ; Check ok-to-load JR Z,CHKWR2 ; ..Error if flag = 0 LD (IX+0),A ; Save Code byte INC IX ; ..and bump code pointer PUSH HL ; Preserve regs LD HL,(PCNTR) INC HL ; Increment Pseudo-Program Counter LD (PCNTR),HL RL E ; Rotate Map from Carry into E LD HL,COUNT INC (HL) ; Bump count.. BIT 3,(HL) ; ..check = 8? JR Z,CHKWR1 ; Exit if < 8 LD (HL),0 ; ..else reset counter to 0 LD HL,(BITMAP) ; Write 8 Map bits out LD (HL),E INC HL ; ..bumping address LD (BITMAP),HL LD E,0 ; Preset next map byte to 0 CHKWR1: POP HL ; Restore regs RET CHKWR2: CALL ERRV ; Print message & Abort DEFB CR,LF,BELL,'Write attempt before areas sized !$' ;..... ; Get 4-bit designator for Special Link Type GETTYP: LD D,4 ; Get type of spec link XOR A ; ..into A register JR GBITS ; Jump to do the work ;..... ; Get 8-bit byte into the accumulator GETBYT: LD D,8 ; 8 bits to a byte GBITS: CALL GETBIT ; Get one of the little buggers SCF ; Prepare to shift in "1" bit JR NZ,GBITS0 ; ..jump if MSB is a "1" CCF ; Else complement carry for "0" bit GBITS0: RLA ; Rotate bit into accumulator DEC D ; Count down number of loops JR NZ,GBITS ; ..and continue til no more bits RET ;..... ; Compare new load location with internal counter and ; fill bit map with 0 to new location CHECKLOAD: PUSH HL PUSH BC ; Save registers PUSH DE LD HL,(LODPTR) ; Get new load address LD A,(TYPLOD) ; Check type of load CP 2 ; Type 1 = prog seg. JR C,CHECK2 JR Z,CHECK1 ; Type 2 = data seg. LD DE,(DATASZ) ; Must be common ADD HL,DE CHECK1: LD DE,(PROGSZ) ; Data area starts at end of prog. ADD HL,DE CHECK2: SET 7,(IY+0) ; Set to show not init load LD DE,(PCNTR) ; Get internal location OR A SBC HL,DE ; Now we have the difference POP DE ; Restore output byte CHECK0: LD A,H ; Ready for exit? OR L JR Z,CHECKEND CALL BYTE0V ; Write a zero & increment IX DEC HL JR CHECK0 ; ..back for more CHECKEND: POP BC ; Restore registers POP HL JP LOOP ; ..and start again ; Check status of area set flags. If Program and Data areas are sized, ; Set OK-to-Load flag, and load registers and pointers SETSTAT: BIT 0,(IY+0) ; Data size set? RET Z ; ..Ret if not BIT 1,(IY+0) ; Program size set? RET Z ; ..Ret if not SET 2,(IY+0) ; Ready, so set ok-to-load PUSH HL ; Save registers PUSH DE EXX ; Store in alternage regs LD BC,(ORGADR) ; Set program 'ORG' LD HL,(PROGSZ) ADD HL,BC EX DE,HL ; Data 'ORG' in de EXX ; Now back again LD DE,(PROGSZ) ; Calculate combined CSEG/DSEG size LD HL,(DATASZ) ADD HL,DE BIT 3,(IY+0) ; Are we doing a PRL link? JR Z,SETST0 ; ..jump if not LD (IX+1),L ; Else save size in output file Page 0 LD (IX+2),H LD IX,OUTFIL+100H ; ..and Reset output to Page 1 for code LD DE,100H ; Increase size for PRL header page ADD HL,DE SETST0: LD DE,OUTFIL ; Calculate start of bit map ADD HL,DE LD (BITMAP),HL POP DE ; Restore registers POP HL RET ;---------------------------------------------------------------; ; C P / M I n t e r f a c e R o u t i n e s ; ;---------------------------------------------------------------; ; Open a disk file specified in the File Control Block ; Print error and abort to CP/M if unable to open. OPENFILE: LD DE,FCB ; Open file whose name is LD C,OPENF ; ..in FCB CALL BDOS CP 0FFH ; Good open? RET NZ ; ..return if so CALL ERRV ; Print message and finish DEFB '++ Cannot Open File ++',CR,LF,BELL,'$' ; Read a 128-byte sector into the program buffer from the file ; specified in the FCB. ; Print error message and abort to CP/M if error in reading. DISKRD: LD DE,BUFF ; Read a sector into input buffer LD C,SETDMA CALL BDOS ; Set DMA address to buffer area LD C,READSQ LD DE,FCB ; ..and read a sector CALL BDOS OR A ; Good read? RET Z ; ..return to caller if good JR WRTERR ; Else print msg and abort WRITEIT: PUSH BC ; Save count BIT 3,(IY+0) ; Is this a .COM file? LD HL,COMTYP ; .get set JR Z,WRTGO ; ..jump if .COM LD HL,PRLTYP ; No, must be .PRL WRTGO: CALL MOVTYP EX DE,HL LD B,24 ; Clear 24 places in FCB WR0: LD (HL),0 ; ..to Zero INC HL DJNZ WR0 LD DE,FCB ; Point to the File Control Block PUSH DE LD C,DELF ; ..and kill any old copies CALL BDOS POP DE LD C,MAKEF ; Make new file CALL BDOS POP BC ; Restore count INC A ; Was Make ok? JR Z,MAKERR LD DE,128 ; Set block size LD HL,OUTFIL ; Get start address WRTLOP: LD A,B ; Check count for end OR C RET Z PUSH HL ; Save registers PUSH DE PUSH BC EX DE,HL LD C,SETDMA ; Set transfer addr CALL BDOS LD DE,FCB LD C,WRITSQ ; Write a sector CALL BDOS OR A ; Were there any errors? JR NZ,WRTERR ; ..jump if so POP BC ; Restore registers POP DE POP HL DEC BC ; Decrease block counter ADD HL,DE ; Set next block address JR WRTLOP WRTERR: CALL ERRV DEFB CR,LF,'++ ERROR writing file ++',BELL DEFB CR,LF,'...Aborting !$' ERRV: POP DE ; Restore message address CALL PRTMSG ; Print error message JP FINI2 MAKERR: CALL ERRV ; Say that we have Creation Problems DEFB CR,LF,BELL,'Directory Full - Abort !$' NONAME: CALL ERRV ; No name in FCB DEFB CR,LF,'No File Name !',CR,LF,BELL,'$' ;..... ; Set character count in 'A' to keyboard buffer ; max length and get up to that many characters ; ENTER: A has maximum buffer length ; EXIT: HL points to 1st char in buffer GETINP: LD DE,BUFF PUSH DE ; Save address LD (DE),A LD C,RDSTR CALL BDOS ; Get the string POP HL ; ..restore the pointer INC HL INC HL ; ...to the 1st char RET ; Print message addressed by DE to console ; Preserve BC and HL registers PRTMSG: PUSH HL ; Preserve registers PUSH BC LD C,PTSTR ; Write string w/BDOS function CALL BDOS POP BC ; ..restore regs POP HL RET ; Print character in A-register to Console ; Preserve BC and HL register pairs PRINTC: PUSH HL ; Preserve registers PUSH BC LD E,A LD C,CONOUT ; Print with BDOS function CALL BDOS POP BC ; ..restore regs POP HL RET ;-------------------------------------------------------; ; U T I L I T Y S u b r o u t i n e s ; ;-------------------------------------------------------; MOVTYP: LD DE,FCB+9 ; Load 3 byte filetype LD BC,3 ; ..to FCB LDIR RET ;..... ; Convert 'B' bytes in string addressed by DE to binary in HL. ; RETURN: Zero flag set = Ok. GETNUM: LD A,(DE) ; Get a character CALL UPPER ; ..in uppercase CALL CV2BIN ; Convert to Binary JR C,GETERR ; ..going error if not digit PUSH DE LD E,A LD D,0 ADD HL,HL ; Multiply by 16 ADD HL,HL ADD HL,HL ADD HL,HL ADD HL,DE ; ..add in new digit POP DE INC DE DJNZ GETNUM RET ; Zero set if ok GETERR: OR 0FFH ; Set error return status RET ;..... ; Convert character in 'A' to uppercase UPPER: CP 'a' ; Is it Less than "a"? RET C ; ..quit if so CP 'z'+1 ; Less than "z"+1? RET NC ; ..Return if not AND 5FH ; Else convert lower to uppercase RET ;..... ; Convert ascii char in 'A' to Hex. Return carry ; RETURN: Carry set = invalid hex digit. ; Carry clear = legal Hex digit CV2BIN: SUB '0' ; Subtract number bias RET C ; ..return if bad CP 10 ; Is it in 0..9? CCF RET NC ; ..return if so w/Carry Clear SUB 7 ; A-F? CP 10 RET C ; ..return Carry set if not CP 16 ; Less than "G"? CCF ; ..return w/Carry Clear if so RET ;..... ; Write CRLF sequence to Console ; Preserve BC, DE, and HL register pairs CRLF: PUSH HL ; Save registers PUSH DE PUSH BC LD A,CR CALL PRINTC ; Send a Carriage Return LD A,LF CALL PRINTC ; ..and Line Feed POP BC ; Restore regs POP DE POP HL RET ;..... ; Print character in A-register to Console as two Hex digits ; Preserve all registers HEXOUT: PUSH HL ; Preserve registers PUSH DE PUSH BC PUSH AF RRCA ; Move Hi Nybble to Low RRCA RRCA RRCA CALL HEXDIG ; ..Print Nybble as Hex digit POP AF ; Restore Low Nybble CALL HEXDIG ; ..and print as Hex digit POP BC POP DE POP HL RET HEXDIG: AND 0FH ; Print '0'-'9', 'A'-'F' ADD A,90H DAA ADC A,40H DAA JR PRINTC ;..... ; File Type fields for Input/Output Names RELTYP: DEFB 'REL' COMTYP: DEFB 'COM' PRLTYP: DEFB 'PRL' ;-------------------------------------------------------; ; V A R I A B L E S T O R A G E ; ;-------------------------------------------------------; DSEG ; Put data in the right segment DEFS 64 ; Room for stack STACK: DEFS 2 ; Storage for entry stack TEMP: DEFS 2 ; Temporary working storage COMMAD: DEFS 2 ; Start address of COMMON area COMMSZ: DEFS 2 ; COMMON size PROGSZ: DEFS 2 ; PROGRAM size DATASZ: DEFS 2 ; DATA size COUNT: DEFS 1 ; Output bit count BITMAP: DEFS 2 ; Bit map address PCNTR: DEFS 2 ; Program relative counter LODPTR: DEFS 2 ; Load location storage TYPLOD: DEFS 1 ; Type of load operation FLAGS: DEFS 1 ; Flags for operations: ; B7 - 0 = no load loc set ; 3 - 0 = COM (No Map), 1 = PRL (Map) ; 2 - 1 = OK to load ; 1 - 0 = No pgm size set ; 0 - 0 = No data size set ORGADR: DEFS 2 ; Address to 'ORG' INPTR: DEFS 1 ; Input pointer to next byte OUTFIL: ; ++ Assembled code starts here ++ END