; CP/M Z80 library manager - (C) 1988 A.E. Hawley .title Z-SYSTEM & CP/M LIBRARY MANAGER .SBTTL VERSION, DEFINITIONS ;THIS FILE ASSEMBLES WITH THE ZMAC ASSEMBLER. ;Use of other assemblers may require translation ;of some pseudo-op instructions. vers equ '1' ;version number rev equ '2' day equ '1' ;version date day1 equ '8' ;second digit month equ '1' month1 equ '2' ;second digit year equ '8' ;last digit only ;===================================================== ;references to and from other module(s) ;in libsubs ext BLANK,CLSFIL,CONIN,CONOUT,CRLF ext DEFDU,DELFIL,DOFTYP,ERROR ext MAKFIL,OPNFIL ext REC2WR,RDREC,RENFIL,RETUD,SETDMA ext TYPLIN,WRREC,X128 ;in liblib ext fill,fname,getbit,inibit,pkgoff ;bitcnt and getrel are required by getbit public $memry,z3env .request LIBLIB ;mREL library made with RLIB .xlist .in LIBDEF ;Definitions & Macros source file .list ;===================================================== .SBTTL 'PROGRAM ENTRY & INITIALIZATION' PAGE start: jp begin ;===================================================== db 'Z3ENV' ;identifies program as ZCPR3 utility db 1 ;external environment Z3ENV: dw 0 ;this address set by Z3INS or ZCPR33 dw start ;for type 3,4 Env ;===================================================== ;place for default options here. Same structure as in ZAS pgmid: dc 'RLIB ' ;program ID for use by configuration pgm lbopt1: db 1 shl pubflg ;first bitmapped config option byte lbopt2: db 0,0 ;two more, for spares libext: db 'REL' ;default extension for mrel library files srcext: db 'REL' ;default extension for source files tmpext: db '$$$' ;default ext. for temp. file ;configurable buffer sizes, in number of 128 byte records libopl: db oblen ;buffer for main rel library file srcopl: db sblen ;buffer for source (REL) files cmdopl: db cblen ;buffer for CMD line or CMD file ds 3,0 ;for other defaults ;standard initial data for indexed DATA area inidat: ds 7,0 db 5 ;initial names/line in display db 20 ;lines/screen for paging endata: ;used for length calc ;===================================================== .sbttl MAIN PROGRAM ROUTINE PAGE begin: ld (stack),sp ;save caller stack ld sp,stack ;and use local stack ld ix,data ld de,signon ;advertise call typlin call zinit ;if Z3, install pgm name etc. call help call init ;setup buffer locations ;and init data area call docmd ;process command tail call dofile ;Create/open LIB and ;temp output files ld iy,(libbeg) ;->destination buffer bit pubflg,(ix+outopt) call nz,ptitl1 ;send title line if P option ;===================================================== ;This is the head of the main processing loop, each ;iteration of which processes one input file, starting ;with the main LIB input file. psfile: xor a ld (fcb+12),A ;reset the fcb ld (fcb+15),A ld (fcb+32),A ld DE,fcb call opnfil ;open the file jp z,badfil ;do the first buffer load call bufld ;return hl->srcbuf ;make sure the current file is a proper mREL file. ld a,(hl) ;get the first byte and 0feh ;select 7 high bits cp mrlnam ;must be 84h to be jp nz,badrel ;a mrel file res eos,(ix+status) ;erase end-of-source flag ;initialize the getbit routine with the first byte of the ;file and the address of the 'get-next-byte' (getrel) routine ld a,(hl) ;recover first byte ld hl,getrel call inibit ;initialize getbit routine ; jp psrmod ;the next execution addr. ;===================================================== .sbttl REL MODULE PROCESSING PAGE ;beginning of loop, each iteration of which processes ;a REL module until the end of file is reached. ;Exit is via mREL eof directing execution ;to ENDFIL. psrmod: call psritm ;do a REL item bit eos,(ix+status) jr nz,srcdon ;the exit bit eom,(ix+status) call nz,endmod ;module done jr psrmod ;do the next item. ;===================================================== ;Process End-of-Module returned by psritm endmod: bit pubflg,(ix+outopt) call nz,ccrlfr ;terminate pubic symbol display ld A,(outopt+data) and 1 shl delflg ! 1 shl repflg ret z ;do the following for Delete/Replace options set namflg,(ix+outopt) res skpflg,(ix+outopt) ret ;===================================================== ;Process End-of-File returned from the ;REL bit stream and return to the main ;processing loop to do the next file (if any) srcdon: bit modflg,(ix+outopt) call nz,ccrlfr ;terminate module name display ld A,(outopt+data) and 1 shl appflg ! 1 shl repflg JR Z,libdon ;skip if Display or Delete ld (ix+outopt),16 ;make Append call appin ;set up file to append jr nc,psfile ;go load the file buffer ;..unless this is the last file, in which case.. ; jp libdon ;finish the library ;===================================================== .SBTTL END OF LIBRARY PROCESSING PAGE ;All input files have been processed. Clean ;up output buffers and close files, deleting ;those that are empty. Rename the temporary ;file and erase the original REL library. libdon: ld A,(outopt+data) and 1 shl pubflg ! 1 shl modflg jp nz,mainx ;quit if display only bit 0,(ix+wrflg) ;check for jr nz,ld0 ;an empty ld hl,(libbeg) ld a,(hl) ;library cp mrleof ;mREL end-of-file? jr z,ld2 ;delete the temporary file & quit ld0: res namflg,(ix+outopt) ld hl,eofbyt call strbyt ;deposit the mrel eof byte ld de,(libcnt) ;remaining space in buffer ld hl,(libsiz) ;buffer size or a sbc hl,de jp z,mainx ;abort if empty buffer call rec2wr ;convert to number of 128 byte records ld1: ld B,L call libwr ;write out the library ld de,libfcb call clsfil ;this is still .$$$ ;Prepare to rename the .$$$ to .REL ld hl,srcfcb ;copy lib fn.ft to the.. ld de,libcb2 ;rename field ld bc,16 ldir ;delete the .REL (original library file) ld de,srcfcb ;delete the RENAME target call delfil ;rename the .$$$ file to .REL xor a ld (libcb2),a ;must be 0 for RENAME function ld de,libfcb call renfil ;rename from (fcb) to (fcb+16) jp mainx ;done. exit ;here when .$$$ is empty ld2: ld de,libfcb call delfil ;delete it mainx: rst 0 ;main exit ;===================================================== .SBTTL FILE & COMMAND ROUTINES PAGE ; LOAD SOURCE BUFFER FROM FILE bufld: push bc push de bit 0,(ix+eofflg) jp nz,badrel ld a,(srclen) ;source buffer length ld b,a ld de,(srcbeg) jr bufld1 bufld0: ld hl,sector ;cpm record size add hl,de ex de,hl bufld1: push de call setdma ld de,fcb call rdrec ;read record from file or a ;check for read errors pop de jr nz,buflde ;jump on eof or bad read djnz bufld0 bufldx: ld hl,(srcsiz) ;buffer size ld (srccnt),hl ;init bytes remaining ld hl,(srcbeg) ld (srcptr),hl ;init srcptr pop de pop bc ret ;exception processing during buffer load buflde: cp 2 ;end of file? jp nc,rderr ;1=physical end of file set 0,(ix+eofflg) ;here on eof JR bufldx ;===================================================== ; PROCESS COMMAND LINE ;copy the command tail to cmdbuf until Option ;separator or end-of-command. ;Set the option if it is present ;Identify the REL Library name, and put it into ;the destination FCB and the source FCB, with an ;extension of $$$ in the first and REL in the second. docmd: ld hl,tbuf ;->cmd tail in tbuf ld B,(HL) ;GET LENGTH inc hl ld a,spc dcspc: cp (hl) ;skip leading spaces jr nz,dcspcx ;..in the command line inc hl djnz dcspc dcspcx: ld de,(cmdbeg) ;->local cmd buffer dc0: ld a,(hl) cp '=' jr nz,dc1 ld (ix+outopt),1 shl appflg dc1: cp spc ;end of list? jr z,dcopt ;yes, if space cp '/' jr z,dcopt ;..or the option indicator ld (DE),A ;transfer char to cmd buff inc de dc2: inc hl ;entry to skip cmd buff transfer djnz dc0 ;get another char. ex de,hl ld (hl),cr ;terminate command line dc3: ld hl,(cmdbeg) ;init fcb, fill with ld de,srcfcb ;filespec at cmdbeg. ld bc,(defdu) ;put explicit/default call fname ;DU at FCB-1 & FCB jp nz,synerr ld a,(hl) cp cr jr z,dc31 inc hl ;->char AFTER the delimiter dc31: ld (cmdptr),hl push af ;save the terminator ld de,srcfcb ld hl,libext call doftyp ;default or explicit name ;the fcb for the SOURCE library has been set up. ;Now set up the Destination FCB with the same name ;and DU, but with a temporary filetype extension. ld hl,srcfcb-1 ld de,libfcb-1 ld bc,10 ldir ld de,libfty ld hl,tmpext ;temporary file extension ld bc,3 ldir pop af ;recover terminator cp '=' ;was it a library spec? jr z,dc4 ld a,(outopt+data) and 1 shl pubflg ! 1 shl modflg jp z,synerr ;illegal. abort with message ;Set up the System fcb to access the requested ;library file with the implied or explicit filespec. dc4: ld hl,srcfcb-1 ;include the user# ld de,fcb-1 ;system FCB at 5ch ld bc,13 ;user+dr+fn+ft ldir ;DE -> .typ field ret dcopt: dec b ;end of line? ld a,cr ld (de),a ;terminate cmd line jp z,dc3 ;no options, so continue inc hl ld a,(hl) ;get next char cp '/' jr z,dcopt ;ignore '/' cp spc jr z,dcopt ;..and spaces call doopts ;found possible option char jr dc3 ;we did, if here ;===================================================== ; SET COMMAND LINE OPTION ;Identify the first character after the option ;delimiter as the (only) option. Set flags ;according to the option selected. Use the default ;option flags if A option or NO option. doopts: ld a,(hl) exx ld (char),a ld hl,clopts ld bc,cloptv-clopts cpir add hl,bc add hl,bc add hl,bc ldhlhl push hl exx ret ;jump to the routine clopts: db 'DPMRA' char: ds 1 ;the test character is always found. cloptv: dw badopt ;if none of clopts list dw aopt,ropt,mopt,popt,dopt ;===================================================== dopt: ld (ix+outopt),1 ;delete set namflg,(ix+outopt) ret popt: ld (ix+outopt),1 shl 1 ;publics ret mopt: ld (ix+outopt),1 shl 2 ;modules ret ropt: ld (ix+outopt),1 shl 3 ;replace set namflg,(ix+outopt) ret aopt: ld (ix+outopt),1 shl 4 ;append ret ;..and if none of the above, then.. badopt: ld de,optmsg ;tell about bad option char. call typlin ld de,usemsg ;show what's right jp error ;===================================================== ; set UP LIB & TEMP FILES ;If an option has been set, then ONLY that bit in ;the data+outopt byte is set. Otherwise (default) ; the byte contains 00010000b. (Append) dofile: ld a,(outopt+data) and 1 shl modflg ! 1 shl pubflg jr nz,dofil1 ;jmp if display only ;erase and remake a temp .$$$ file ld de,libfcb ;for a|d|r option call delfil call makfil ;gets renamed later! ;meantime, it's opened for read/write dofil1: ;fcb contains the .REL spec ld de,fcb ;open source fcb for .rel call opnfil ret nz ;ok, start reading it ;here when the .REL file is not found. If the append flag is ;set, then go ahead and read source modules into the temporary ;output file. bit appflg,(ix+outopt) ;file not found so must be append jp z,badfil ;if append is not the option, ;then there's something wrong! ;LIB file not found, so create an output file, then ;open the first REL module file for appending. ld hl,(cmdptr) ;first, make sure there is ld a,(hl) ;something to append! CP cr jp z,badfil ;z = no module list call appin ;gets next file, iy->LIBBUF ;..if cy set, there is no file to append. ret ;===================================================== .SBTTL MREL BIT STREAM PROCESSING PAGE ;===================================================== ;read and process a single item from the mREL bit ;stream in the input buffer. The module name is the ;first item in the stream. The End-of-module or ;End-of-file is the last item. psritm: gbits 1 dec a jp m,absbyt jr relitm ;===================================================== ; PROCESS ABSOLUTE BYTE ABSBYT: gbits 8 ret ;===================================================== ; PROCESS RELOCATABLE ITEM RELITM: gbits 2 dec a jp m,splink gbits 16 ret ;===================================================== ; GET SPECIAL LINK ITEM SPLINK: gbits 4 ld e,a ld D,0 ld hl,sltbl add hl,de add hl,de ld e,(hl) inc hl ld d,(hl) ex de,hl jp (hl) ;===================================================== ;Table of entry points for processing the 16 ;possible special link items of the MREL format. sltbl: dw entsym,selcom,prgnam,lisrch dw extlnk,sizcom,chnext,entpnt dw extmo,extpo,sizdat,setloc dw chnadr,sizprg,endprg,endfil ;===================================================== ; ENTRY SYMBOL entsym: call bfield bit pubflg,(ix+outopt) ret z call prtsym ;display string in symbuf ret ;===================================================== ; SELECT COMMON BLOCK SELCOM: jp bfield ;===================================================== ; PROGRAM NAME prgnam: call bfield ;returns pgmname in symbuf res namflg,(ix+outopt) ;turn off module name storage res eom,(ix+status) ;..and end-of-module flag ld hl,nambuf ;initialize nambuf pointer ld (namptr),hl bit modflg,(ix+outopt) ;display the symbol if one jr nz,pn1 ;of the display options is on. inc (ix+fwid) ;make this line 1 field wider bit pubflg,(ix+outopt) jr nz,pn1 bit delflg,(ix+outopt) ;display symbol with a message jr nz,pn2 ;if this one is to be deleted bit repflg,(ix+outopt) ;or 'replaced' jr nz,pn2 ret ;its an append ;here for one of the display options PN1: res pdone,(ix+status) ;inhibit leading blanks jp prtsym ;display string in SYMBUF ;here when deletion or delete/append is the option pn2: call namchk ;is it named on the cmd line? jr nc,pn3 ;jump if not ;this is one of the modules named on the cmd line.. ld de,delmsg ;'deleting..' call typlin call prtsym ;display string in SYMBUF set skpflg,(ix+outopt) ;delete module by skipping it. ret ;here for modules that are to be retained and ;copied to the new library file (not deleted). pn3: ld b,(ix+symlen) ;this module wont be skiped inc b ld hl,nambuf ;so output the name pn4: call strbyt ;send (nambuf) to dest buffer inc hl djnz pn4 ret ;===================================================== ; REQUEST LIBRARY SEARCH lisrch: call bfield ;library search ret ; EXTERNAL LINK ITEM extlnk: ld de,elierr ;external link item jp superr ;===================================================== sizcom: ;common size chnext: ;chain external entpnt: ;entry point call afield call bfield ret ;===================================================== extmo: ;external - offset extpo: ;external + offset sizdat: ;data size setloc: ;set location counter chnadr: ;chain address sizprg: ;program size call afield ret ;===================================================== ; END OF PROGRAM endprg: call afield ;scan through module start addr ld a,l ;hl=(bitcnt), count in L cp 8 set eom,(ix+status) ;indicate end of module ret z ;done if so. ld b,a jp getbit ;finish out a byte ;and return ;===================================================== ; END OF FILE endfil: set eos,(ix+status) ;mark mrel end of file ret ;===================================================== ; GET A FIELD ;reads the 'A' field, ignores the contents afield: gbits 18 ret ;===================================================== ; GET B FIELD HL=NAME ;Store symbol length in symlen, ;store symbol name in symbuf ;Preserve HL bfield: push hl gbits 3 dec a ;convert 0 length and 111b ;.to 8, allowing up to inc a ;8 byte names & symbols ld (ix+symlen),a ld (ix+lopcnt),a ld hl,symbuf bfloop: push hl gbits 8 pop hl ld (hl),a inc hl dec (ix+lopcnt) jr nz,bfloop bf2: pop hl ret ;===================================================== .SBTTL MREL SERVICING ROUTINES ;===================================================== ;the input byte has been exhausted. Move it ;to the destination buffer, then get another ;This Routine is called from GETBIT after it ;has been initialized with the address of GETREL. ;call WITH ; Source & Destination FCBs and buffers valid ;RETURN WITH ; HL -> New input byte ; A = (hl) ; BC,DE preserved getrel: ld hl,(srcptr) call strbyt ;send to dest or nambuf ;preserves BC,DE,HL getbyt: push bc ;get next byte from SRC buffer ld hl,(srcptr) ld bc,(srccnt) cpi ;inc pointer & test buffer exhausted ld (srccnt),bc ld (srcptr),hl call po,bufld ;if so, refill from source ld a,(hl) ;the new input byte pop bc ret ;===================================================== .sbttl SUBROUTINES PAGE ;sets up the FCB for the next file to be ;processed. The filename is obtained from the ;list on the command line, now in the local ;command line buffer. appin: ld hl,(cmdptr) ld a,(hl) CP cr scf ;in case end of list ret z ;z = end of list res 0,(ix+eofflg) ld de,fcb ;get filespec for module ld bc,(defdu) ;put explicit/default call fname ;DU at FCB-1 & FCB jp nz,synerr ld a,cr cp (hl) jr z,appin1 inc hl ;->char AFTER the delimiter appin1: ld (cmdptr),hl ;unless it's a cr (eoc) ld de,fcb ;fill in the filetype ld hl,srcext call doftyp ;default type if required ld de,appmsg ;'Appending ' call typlin ld hl,fcb+1 call prtfil ;send module name (=fn) call crlf or a ;reset cy ret ;===================================================== ; WRITE OUT LIB BUFFER ;Write B records from the LIB buffer libwr: ld de,(libbeg) set 0,(ix+wrflg) ;indicate write done. cw1: call setdma ex de,hl ld de,libfcb call wrrec ld de,128 add hl,de ex de,hl djnz cw1 ret ;===================================================== ; PRINT SYMBOL ;print the string at SYMBUF, length (ix+symlen) prtsym:: bit pubflg,(ix+outopt) jr z,ps0 ;jmp if not displaying public symbols bit pdone,(ix+status) jr z,ps0 ;jmp if not at start of a new line ld b,10 call blank ;send a blank field at start of new line ps0: res pdone,(ix+status) ld hl,symbuf ld b,(ix+symlen) ld c,10 ;field width for names ps1: ld a,(hl) inc hl dec c call conout djnz ps1 ps2: ld b,c call blank ;left justified in field of 10 bit delflg,(ix+outopt) jp nz,crlf ;conditional crlf. include screen pause ccrlf: dec (ix+fwid) ret nz ccrlfr: ld (ix+fwid),5 ;print 'em 5 across call crlf ;start a new line bit pubflg,(ix+outopt) jr z,pause ;displaying names & entry points? set pdone,(ix+status) ;yes, set up for leading spaces pause: dec (ix+scrlin) ;count lines sent to screen ret nz ld a,(inidat+scrlin) ld (ix+scrlin),a ;reinitialize the screen line counter ld de,pawsm ;'strike any key..' ;turn printer off here, if it's active call typlin call conin ld de,epaws ;erase pause msg - hard on a printer! call typlin ;turn the printer back on if required bit pubflg,(ix+outopt) ;module names plus publics? ret z ;done if not ptitl1: ;..else send a new header line ; res pdone,(ix+status) ld de,titl01 ;send title line call typlin ret ;===================================================== ; STORE REL STREAM BYTE IN LIBBUF OR NAMBUF ;stores a bit stream byte in the LIB buffer, ;writing the buffer to disk when it becomes full ;OR stores the bit stream byte in NAMBUF for later ;possible transfer to the LIB buffer if this module ;is not being skipped. That decision is made after ;the name has been read and analysed. ;call WITH: ; iy -> next LIB buffer loc ; HL -> byte to store ;RETURN WITH: ; BC,DE,HL preserved ; iy -> next LIB buffer loc (may be unchanged) strbyt: ld a,(outopt+data) and 1 shl pubflg ! 1 shl modflg ! 1 shl namflg ! 1 shl skpflg jr z,ssstor ;here if Public, or Module names, or skipping, or namflg set bit namflg,a ;doing a module name? ret z ;return if not ;redirect bit stream byte to the name buffer. ;It will be transferred later to the LIB buffer if ;this module is to be included in the new LIB push bc ld bc,(namptr) ld a,(hl) ;SAVE IN ld (bc),a ;NAME BUFFER inc bc ld (namptr),bc pgndon: pop bc ret ;here if append, delete, or replace ssstor: push bc ld a,(hl) ;transfer a byte ld (iy+0),a INC iy ld bc,(libcnt) ;maintain 'bytes left' dec bc ;counter ld (libcnt),bc ld a,b ;test for no space left or c jp nz,ssdone push hl ;write out buffer if push de ;no space left ld a,(liblen) ;b = number of records to write ld b,a call libwr ld hl,(libsiz) ;initialize counter ld (libcnt),hl ld iy,(libbeg) ;initialize buffer pointer pop de pop hl ssdone: pop bc ret ;===================================================== ; CHECK COMMAND LINE FOR NAME IN SYMBUF namchk: ld de,(cmdptr) nc1: ld hl,symbuf ld b,(ix+symlen) nc2: ld a,(de) inc de cp (hl) inc hl jr nz,ncskip djnz nc2 ld a,(de) ;must have terminator cp ',' ;to be a real match jr z,ncfnd cp cr jr z,ncfnd or a ret ncfnd: scf ret ncskip: ld a,(de) ;skip current entry inc de cp ',' jr z,nc1 cp cr ret z jr ncskip ;========================================================= .SBTTL HELP & INITIALIZATION PAGE help: ;help is invoked with an empty command tail, or one or two ;'/' or '?' characters. The '/' and '?' are interchangeable. ld A,(fcb+1) cp ' ' ;if nothing there, show help jr z,prhelp and a,2fh ;make '/' and '?' equivalent cp '/' ;possible help request? ret nz ld a,(fcb+2) cp ' ' ;just one slash means help jr z,prhelp and a,2fh ;make '/' and '?' equivalent cp '/' ;also respond to 2 slashes ret nz prhelp: ld de,hlpmsg ;print help message call typlin ; jp mainx ;done. ld sp,(stack) ;recover caller stack ret ;return without warm boot ;===================================================== init: call retud ld de,($memry) ;allocate buffers and fill in buffer control blocks allocb cmd allocb lib allocb src ;initialize indexed data area ld bc,endata-inidat ld hl,inidat ld de,data ldir ld a,(lbopt1) ld (ix+outopt),a ;initialize other data ld hl,nambuf ld (namptr),hl ret zinit: ld hl,(z3env) ld a,h or l ret z ;not Z3 ;install the name of this program in the help screen ld e,exfcbo ;Z3 external FCB offset call pkgoff ;DE -> ext fcb ex de,hl inc hl ;->filename ld de,myname+7 ;pgm name in help screen ld a,(de) cp spc ;is the last char blank ? ret nz ;if not, name is already installed. cpynam: ld bc,7 add hl,bc ;hl->last char in fcb name ex de,hl sbc hl,bc ;->invok1 ex de,hl ld b,8 ld a,spc call fill ;increments de to myname+8 ld b,8 ;copy up to 8 char. cpnm1: ld a,(hl) dec hl cp spc jr z,cpnm2 ;don't copy spaces dec de ;dec first to get back into range ld (de),a cpnm2: djnz cpnm1 ret ;===================================================== .SBTTL ERROR HANDLING PAGE badfil: ld hl,fcb+1 ;entry for other fcb's badf2: ld de,ermsg1 ;report not found call typlin call prtfil ld a,"'" call conout jp mainx ;===================================================== ;Print a filename.typ on the console ;call WITH ; HL -> FN.FT (format xxxxxxxx.xxx, space filled) prtfil: ld b,8 ;xxxxxxxx call zl1 ld a,'.' call conout ld b,3 ;xxx call zl1 ret ;Print up to (b) characters or until spc zl1: ld a,(hl) inc hl cp ' ' jr z,zl2 call conout djnz zl1 ret ;(b) char sent, hl->next field zl2: dec hl ;back up to last char zl3: inc hl ;->delimiter djnz zl3 ;repeat until end of field ret ;===================================================== ;called from 'load source buffer' if EOFflag ;..also used for exit for non-rel file. badrel: ld hl,fcb+1 call prtfil ld de,ermsg4 jr error rderr: ld de,ermsg2 jr error superr: call typlin ld de,supmsg ;not supported! jr error synerr: ld de,synmsg ;syntax error jr error error: call typlin jp mainx ;===================================================== .SBTTL MESSAGE POOL OPTMSG: db 'Invalid option specification!',cr,lf,cr,lf,0 signon: db cr,lf,lf db 'Z/CPM Library Manager, Version ',vers,'.',rev,' Copyright 1988 ' db 'A.E. Hawley',cr,lf,lf,0 hlpmsg: db 'Function: Create, Modify, or display contents of',cr,lf db ht,' a REL format Library file (LIB).',cr,lf,lf usemsg: db 'Syntax:',cr,lf,' ' myname: db ' RLIB LIB[=MOD[,MOD...]] [[/]