; LDIR-H1 ; 05 May 1988 ; ; based on Steve Greenberg's LDIR-B ; ; ; This program shows the member files in a .LBR. May be used by itself ; or can be called by LUX77B. Can be used on an RCPM or individual CP/M ; system. Place on A0: Shows the names of the library files, how long ; they are in both records and 'k' and their normal 'uncrunched' name. ; ;----------------------------------------------------------------------- ; ; LDIR-H1 - 05/05/88 Checks for BYE5 in use - Irv Hoff ; LDIR-H - 02/17/88 - Irv Hoff ; LDIR-B12 - 11/05/87 Added ZCPR3 capability - Bruce Morgen ; LDIR-B - 10/17/87 - Steven Greenberg ; ;----------------------------------------------------------------------- ; .Z80 ; Only needed if using M80/L80 ASEG ; Only needed if using M80/L80 ORG 100H ; ; ; ASCII equates ; BS EQU 08H ; Backspace CR EQU 0DH ; Carriage return LF EQU 0AH ; Linefeed ; ; CP/M address equates ; DFCB EQU 005CH ; Default file control block #1 FCB2 EQU 006CH ; Default file control block #2 DDMA EQU 0080H ; Default DMA address BDOS EQU 0005H ; BDOS entry point ; ; BDOS function equates ; CONIN EQU 1 ; Console input (single character) CONOUT EQU 2 ; Output single char to console PRTSTR EQU 9 ; Print string to console CONST EQU 11 ; Get console status OPEN EQU 15 ; Open file READ EQU 20 ; Read file (sequential) SETDMA EQU 26 ; Set dma address GSUSER EQU 32 ; Get/set user code RDRND EQU 33 ; Read random ; ;----------------------------------------------------------------------- ; ENTRY: JP START ; ; ; Following two lines for the ZCPR3 Enviornment descriptor, ignore if ; not using ZCPR3. DEFB 'Z3ENV',1 ; Z3EADR: DEFW 00 ; Set by CPR or the Z3INS utility if Z3 ; ;----------------------------------------------------------------------- ; NLN: DEFB 22 ; #of lines before [more] prompt WHLLOC: DEFW 003EH ; Wheel byte location ; ;----------------------------------------------------------------------- ; ; Start of program ; ;----------------------------------------------------------------------- ; START: LD (STACK),SP ; Save system stack pointer LD SP,STACK ; Set to local area ; ; Check for BYE5 ; LD C,32 ; Get current user area LD E,0FFH CALL BDOSAV PUSH AF ; Save current usea area temporarily LD C,32 ; Check for BYE5 LD E,241 CALL BDOSAV LD (BYE5),A ; Store answer (4Dh if BYE5 is in use) POP AF ; Get current user area back LD C,32 ; Restore current user area LD E,A CALL BDOSAV ; ; See if using ZCPR3, if not, exit ; LD HL,(Z3EADR) ; Get possible Z3 environment pointer LD A,L OR H JR Z,NOTZ3 ; If (Z3EADR) = 0000H, assume non-Z3 ; LD A,(DFCB+2) CP '/' JP Z,GIVUSG ; Exit if looking for use of program ; LD A,(DFCB+13) ; Otherwise get CCP-parsed user # LD E,A ; Log in via BDOS function #32 LD C,GSUSER CALL BDOSAV ; HL is preserved at BDOSAV LD DE,29H ; Offset to wheel address in DE ADD HL,DE ; Add it to environment address LD E,(HL) ; LSB in E INC HL ; Bump pointer LD D,(HL) ; MSB in D LD (WHLLOC),DE ; Poke into LDIR-B LD DE,6 ; Offset to CRT selection ADD HL,DE ; Add it in LD E,3 ; D=0, so DE=0003h LD A,(HL) ; Get selected CRT # in A OR A ; Test for zero JR Z,CRT0 ; If CRT #0, just 3 bumps ADD HL,DE ; Otherwise 6 bumps ; CRT0: ADD HL,DE LD A,(HL) ; Get "usable" CRT lines LD (NLN),A ; Poke into LDIR-B ; ; Skips above section if not ZCPR3 ; NOTZ3: LD A,(DFCB+1) ; Any commands requested? CP ' ' JP Z,GIVUSG ; If not, give usage ; LD A,(BDOS+2) ; Subtract 2k+ (for CCP) from TPA SUB 11 ; - and save for later check LD (OVFTPA),A LD A,(NLN) ; Set line count LD (LINCTR),A LD HL,'RB' ; Last 2 letters of "LBR" (backwords) LD (DFCB+10),HL ; Put at FCB+10 and +11 LD A,'L' ; Similarly LD (DFCB+9),A ; Now we have a forced "LBR" extension LD HL,FCB2+1 ; Put possible user wildcard LD DE,WLDFCB ; filespec into a safe buffer LD BC,11 LDIR LD DE,DFCB+12 ; Clear rest of FCB LD B,24 ; # of zeroes for the rest XOR A ; A zero, obviously ; ZLP2: LD (DE),A ; Put those in INC DE DJNZ ZLP2 ; LD HL,0 ; Set "number of files" counter to zero LD (NFILES),HL LD DE,DFCB ; Open the library file LD C,OPEN CALL BDOSAV INC A JP Z,NOSUCH ; Can't find that file, display error ; LD A,(DFCB+10) ; Check if file has .SYS attribute AND 80H JR Z,NONSYS ; If not, it's OK ; LD HL,(WHLLOC) ; If .SYS extent, check if wheel is on LD A,(HL) ; Get the wheel byte itself OR A JP Z,NOSUCH ; If zero, pretend there is no such file ; NONSYS: LD C,SETDMA ; Make sure the default DMA is 80H LD DE,DDMA CALL BDOSAV CALL CRLF ; Type a CR/LF sequence to the screen LD DE,LBRNAM ; Followed by "Library File =" CALL MESAGE LD HL,DFCB+1 ; Point to the LBR's filename CALL PFNAME ; Routine types the specified filename LD A,(WLDFCB) ; Has user specified a wildcard? SUB ' ' JR Z,NOWILD ; If not, finished with display ; CALL BLANK3 ; Otherwise print three blanks LD DE,FNMSG ; Point at "( --> " CALL MESAGE ; Print it LD HL,WLDFCB ; Point at wildcard CALL PFNAME ; Type it out as filename.typ LD A,')' ; Close parenthesis CALL TYPE ; NOWILD: CALL CRLF ; Another CR/LF, obviously CALL READ1 ; Read the library's 1st record LD HL,DDMA ; Point to first byte LD A,(HL) ; Validity check, the dirctory entry OR A ; for the directory itself must be ; "active" (zero) JP NZ,CORUPT ; Else the library is corrupt ; ; We would normally check for eleven blank characters next (the filename ; area of the directory entry for the directory itself. We will skip ; this validity check, however, because some MS-DOS library programs ; actually insert the library's name here. Skipping the check insures ; compatibility. ; LD HL,DDMA+12 ; More validity checking: XOR A ; The library's "index" must be zero CP (HL) JP NZ,CORUPT ; If INDEX(low) >0, .LBR is corrupt ; INC HL CP (HL) JP NZ,CORUPT ; Likewise for INDEX(high) ; INC HL LD A,(HL) ; Get length of directory(low) INC HL LD H,(HL) ; Get length of directory(high) LD L,A ; Full directory length in HL OR H JP Z,CORUPT ; 0-length LBR directory is corrupt ; LD (DIRLEN),HL ; It's big enough, store it ; ; Program operation: We will read the entire .LBR directory into memory ; in one shot, avoiding having to go back to it later as we are reading ; the first record of various member files (should minimize head move- ; ment and maximize speed). Only the 19 bytes of interest out of the ; 32 will be saved for each entry, however, and entries flagged as de- ; leted or non-existant will be skipped. ; LD DE,DIRBUF ; Directory data starting here JR SKIP1 ; Jump into loop (only 3 entries ; ; first record) ; ;----------------------------------------------------------------------- ; MAINLP: LD HL,DDMA+00 ; 1st entry per record CALL ACTIVQ ; Active? CALL Z,PRCENT ; Routine copies 19 of this entry ; ; into "DIRBUF" SKIP1: LD HL,DDMA+20H ; As above, 3 more times / recird CALL ACTIVQ ; Active? CALL Z,PRCENT LD HL,DDMA+40H CALL ACTIVQ ; Active? CALL Z,PRCENT LD HL,DDMA+60H CALL ACTIVQ ; Active? CALL Z,PRCENT LD HL,(DIRLEN) DEC HL LD A,L OR H JR Z,DUNDIR ; Done reading in directory, go process ; LD (DIRLEN),HL ; Else store length remaining CALL READ1 ; and read another record into DDMA JR MAINLP ; Loop, without resetting DE ; ;----------------------------------------------------------------------- ; ; Routine to move 19 key bytes from one entry into sequential memory in ; "DIRBUF". HL points to the .LBR directory entry in queston, DE con- ; tinues to increment through "dirbuf" for all entries. ; PRCENT: INC HL ; Skip flag byte, we already know its ; "active" LD BC,19 ; number of bytes to be moved LDIR ; (DE is incrementing through DIRBUF) LD HL,(NFILES) ; Ok to clobber HL now (not DE!) INC HL ; Increment the "# of files" counter LD (NFILES),HL LD A,(OVFTPA) ; Be extra cautious and make sure SUB D ; "DE" never approaches end of TPA JP C,CORUPT ; If it does, the .LBR is corrupt ; RET ; (A TPA that small, is "corrupt") ; ;----------------------------------------------------------------------- ; ; Now we are done reading the directory information, and it is time to ; start processing, starting from the beginning of "DIRBUF" ; DUNDIR: LD HL,(NFILES) ; Test for no matching members LD A,L OR H JR NZ,DODIR LD DE,EMPMSG ; Show the message CALL MESAGE JP EXIT ; Return to CCP, all done ;..... ; DODIR: LD DE,HEDING ; Type main heading CALL MESAGE LD HL,DIRBUF ; Back to beginning of packed data ; to be processed ; ;----------------------------------------------------------------------- ; NAMLP: LD A,(LINCTR) ; Top of main loop, one loop per entry DEC A LD (LINCTR),A ; Keep track of lines per console screen CALL CKABRT ; Check for ^C, etc, also [more] pause LD A,CR ; In case "DKABRT" echoed extraneous chars, CALL TYPE ; - an extra CR so we'll write over them CALL PFNAME ; Type a filename (increase HL by 11) CALL BLANK2 ; Type 2 blanks LD E,(HL) ; Get the entry's "INDEX" for later reference INC HL LD D,(HL) INC HL LD (INDEX),DE ; Put 2 byte index value there for now LD E,(HL) ; Get the member's file size in records INC HL LD D,(HL) INC HL ; ; The member's file size can be processed immediately, since according ; to the format, it's the next thing we want to type to the screen ; anyway. The code below will take the length in records (now in DE), ; divide it by eight, convert that to BCD, and then print the remainder ; as the fractional part of the size in "k". ; ; ; Get number of records into DE, then go print that first ; PUSH HL ; Save pointer and size in records PUSH DE EX DE,HL ; Recs to HL CALL DECOUT ; Print with leading blanks POP DE ; Get number of records back LD HL,7 ADD HL,DE EX DE,HL ; new number of records into DE POP HL XOR A ; We'll accumulate the fractional part in here SRL D ; } RR E ; } RRA ; } SRL D ; } Divide by 8, shifting remainder into A RR E ; } RRA ; } SRL D ; } RR E ; } RRA ; } RRA RRA ; A now has the remainder times 8. PUSH HL ; Save our pointer too. EX DE,HL CALL DECOUT ; Converts the # in HL to BCD and types it. POP HL INC HL INC HL INC HL INC HL LD (HLSAVE),HL ; Save our pointer again LD DE,ENDSIZ CALL MESAGE ; And output that to the console ; ; Now we examine the middle letter of the extension to determine the ; file's storage "method" (ie "Crunched", "Squeezed", or nothing). This ; version of the program is lazy and doesn't bother to read the file for ; verification. The "PFNAME" routine which previously typed the file- ; name conveniently saved the middle letter of the extension in "EXTCHR" ; LD A,(EXTCHR) ; Get filetype by mid ext letter CP 'Z' ; Crunched? JR Z,NAMLP1 CP 'Q' JR NZ,NZRO ; NAMLP1: CALL RDHDR ; Read the member's 1st record into DDMA LD A,(EXTCHR) ; Get filetype by mid ext letter CP 'Z' ; Crunched? LD DE,TYPE1 JR Z,CORECT CP 'Q' ; Squeezed? LD DE,TYPE2 JR Z,CORECT ; NZRO: LD DE,TYPE3 ; For non-compressed ; CORECT: CALL MESAGE ; Whatever it is, type it CALL BLANK3 ; Type 3 blanks LD A,(EXTCHR) ; Re-analyze extension CP 'Z' ; Crunched? LD HL,DDMA+2 JR Z,MAKEUP ; Go to next LBR member ; CP 'Q' LD HL,DDMA+4 JR Z,MAKEUP ; DUNLIN: CALL CRLF ; Done with whole line; move to next ; .LBR member LD HL,(NFILES) ; Decrement the number of files count ; to see if we're done DEC HL LD (NFILES),HL LD A,H OR L LD HL,(HLSAVE) ; Before looping, restore HL (now ; pointing to next packed directory ; in "DIRBUF". JP NZ,NAMLP ; Get the next file ; ;----------------------------------------------------------------------- ; ; Subroutines ; ;----------------------------------------------------------------------- ; ; Terminate. Return to CCP. ; EXIT: LD SP,(STACK) ; Reset the original stack, go to CCP RET ; ;----------------------------------------------------------------------- ; GIVUSG: LD DE,USAGE ; Give usage instructions and exit CALL MESAGE JR EXIT ; Return to CCP ; ;_______________________________________________________________________ ; ; Read in the 1st 128 bytes of a member file. The file's index is in ; "INDEX". ; RDHDR: LD HL,(INDEX) ; Get index of file LD (DFCB+33),HL ; Put it in the rr field at fcb+33,34 XOR A LD (DFCB+35),A ; Make sure this is zero LD C,RDRND ; Prepare for random read LD DE,DFCB CALL BDOSAV ; Read first record of the file to the ddma OR A JP NZ,CORUPT ; (if read operation failed) RET ; ;----------------------------------------------------------------------- ; ; Print a file's real name ; MAKEUP: LD DE,FNMSG ; "--> " CALL MESAGE LD B,12 ; Necessary? ; MAKELP: LD A,(HL) INC HL CP 10H ; Usually 00 terminates; stop at any of JR C,DUNAME ; 16 obviously non-ASCII bytes for ; future expansion of system dependent ; information area. CP '[' ; Start of a comment? JR Z,DUNAME ; If yes, ignore CALL TYPE DJNZ MAKELP ; (also could stop 3 bytes past ".") ; DUNAME: CALL BLANK1 ; Follow with 1 blank and a ")" JP DUNLIN ; ;----------------------------------------------------------------------- ; TYPE: PUSH AF ; Type the char in A; save all registers PUSH BC PUSH DE LD E,A LD C,CONOUT CALL BDOSAV POP DE POP BC POP AF RET ; ;----------------------------------------------------------------------- ; CRLF: LD A,CR ; Type a CR/LF sequence to the console CALL TYPE LD A,LF CALL TYPE RET ; ;----------------------------------------------------------------------- ; NOSUCH: LD DE,NSMSG ; Type "File not found" and exit CALL MESAGE JP EXIT ; Return to CCP ; ;----------------------------------------------------------------------- ; READ1: PUSH DE ; Sequential read next record to DDMA. ; Kills BC. LD DE,DFCB LD C,READ CALL BDOSAV OR A JP NZ,CORUPT ; If unexpected EOF error POP DE RET ; ;----------------------------------------------------------------------- ; MESAGE: PUSH BC ; Type string pointed to by DE (ends LD C,PRTSTR ; with '$') CALL BDOSAV POP BC RET ; ;----------------------------------------------------------------------- ; BDOSAV: PUSH IY ; CALL BDOS, save all regs (except A) PUSH IX PUSH HL PUSH DE PUSH BC CALL BDOS POP BC POP DE POP HL POP IX POP IY RET ; ;----------------------------------------------------------------------- ; ; Monitor "LINCTR" - if zero, pause and wait for another character to ; continue, then then reset "LINCRT" to the "NLN" value (unless the ; "continue character was a space, in which case reset "LINCTR" to "1" ; to display only one additional line). Check console input status, ; get a character if necessary. Abort if it is one of the 6 abort char- ; acters. Space sets "LINCTR" to "1" at any time. Pause on ^S, waiting ; for another character (and process it as above [except another ^S]). ; That should about cover it. ; CKABRT: PUSH IX ; Save original values PUSH IY PUSH AF PUSH BC PUSH DE LD A,(LINCTR) ; # of lines on current screen so far OR A JR NZ,NLNZ ; Br if not zero yet ; LD A,(NLN) ; Reset the line counter in advance LD (LINCTR),A LD DE,MORPRM ; "[more]" prompt CALL MESAGE ; ; Check both remote input and local keyboard for a character, but first ; see if BYE5 is present. ; WA4CH: LD A,(BYE5) ; Using BYE5? CP 77 JR NZ,WA5CH ; If not, exit ; LD C,61 ; Special BDOS call for remote status CALL BDOSAV OR A JR Z,WA5CH ; No remote character, check local ; LD C,64 CALL BDOSAV JR GOT1A ; WA5CH: LD C,CONST ; Loop till we get any character CALL BDOSAV OR A JR Z,WA4CH ; Allows checking for remote input also ; LD C,CONIN CALL BDOSAV JR GOT1A ; Got a character, see what it is ; ;----------------------------------------------------------------------- ; NLNZ: LD A,(BYE5) ; BYE5 in use? CP 77 JR NZ,NLNZN ; If not, exit ; LD C,61 ; Got a remote character to pause? CALL BDOSAV OR A JR Z,NLNZN ; No, check for local character ; LD C,64 ; Have charcter, get it CALL BDOSAV OR A JR GOT1 ; See what it is ; NLNZN: LD C,CONST ; Normally, just check console status. CALL BDOSAV OR A JR Z,RETABT ; No character, back to work ; LD C,CONIN ; Get the pending console character CALL BDOSAV JR GOT1 ; RETABT: POP DE ; Always return from this subr from here POP BC POP AF POP IY POP IX RET ; ;----------------------------------------------------------------------- ; ; Got a character, see what it is, if a space, turn up a single line. ; GOT1: CP 'S'-40H ; CTL-S pauses JR Z,WA4CH ; GOT1A: PUSH AF CP ' ' JR C,GOT1B LD DE,ERASE CALL MESAGE ; GOT1B: POP AF CP ' ' ; Space sets the line counter to one JR Z,SET1 AND 1FH ; ^C, ^K, ^X, C, K, X, etc all abort CP 'C'-40H JR Z,ABRT CP 'K'-40H JR Z,ABRT CP 'X'-40H JR NZ,RETABT ; Ignore other keys ; ABRT: JP EXIT ; Return to CCP ; SET1: LD A,1 ; Set line counter to '1' LD (LINCTR),A JR RETABT ; ;----------------------------------------------------------------------- ; PFNAME: LD B,8 ; Print filename spec'd by HL. Inject ; the "." ; FNLP: LD A,(HL) ; } INC HL ; } type 8 filename chars CALL TYPE ; } DJNZ FNLP ; } ; LD A,'.' ; Inject a "." CALL TYPE LD A,(HL) ; Type first ext char INC HL CALL TYPE LD A,(HL) ; Side effect of this routine, save INC HL ; middle extent character for possible CALL TYPE ; later analysis AND 05FH ; Upper-case to be sure LD (EXTCHR),A ; Save for later analysis LD A,(HL) ; Type the 3rd and final extent char. INC HL CALL TYPE RET ; ;----------------------------------------------------------------------- ; CORUPT: LD DE,CORMSG ; Type "library file corrupt", and exit CALL MESAGE JP EXIT ; Return to CCP ; ;----------------------------------------------------------------------- ; BLANK3: LD A,' ' ; Type 3 blanks to the console CALL TYPE ; BLANK2: LD A,' ' ; Likewise 2 bytes CALL TYPE ; BLANK1: LD A,' ' ; A single oarty CALL TYPE RET ; ;----------------------------------------------------------------------- ; ; Convert a binary number to four ASCII characters and type them, right ; justified. ; DECOUT: CALL DIV10 ; Divide original # (in HL), by 10 LD A,L ; Get remainder from L, (0-9) PUSH AF ; Save in reverse order retrieval later EX DE,HL ; Old dividend becomes new divisor CALL DIV10 ; Repeat 3 more times LD A,L PUSH AF EX DE,HL CALL DIV10 LD A,L PUSH AF EX DE,HL CALL DIV10 LD A,L PUSH AF EX DE,HL LD B,3 ; Becomes loop counter LD C,0EFH ; Mask to convert zeroes to blanks ; DECLP: POP AF ; Type the 4 digits, with leading 0 ; suppression OR A ; Is it zero? JR Z,LVMASK ; Leave mask set if so LD C,0FFH ; Else cancel masking (0FF zeroes to ; blanks) ; LVMASK: ADD A,'0' ; Convert to ASCII AND C ; Possibly blank a zero CALL TYPE ; Output the character DJNZ DECLP ; Do the first 3 digits ; POP AF ; Last digit is easy, never blank it ADD A,'0' ; Convert to ACSII CALL TYPE ; Type it and return RET ; ;----------------------------------------------------------------------- ; DIV10: EX DE,HL ; Divide 16 bit value in HL by 10 LD HL,0 ; Zero the low byte LD BC,-10 ; We can skip the negation code LD A,11H ; Iterations, 17 require to get all JR UM1 ; the DE bits ; UM0: ADC HL,HL ; UM1: ADD HL,BC ; Divide HLDE by -BC JR C,UM2 ; If it fits SBC HL,BC ; Else restore it OR A ; Make sure carry is 0 ; UM2: RL E ; Result bit to DE RL D DEC A JR NZ,UM0 ; Continue RET ; ;----------------------------------------------------------------------- ; ; Check a library directory entry before reading it into DIRBUF. ; Returns Z if the entry is OK, NZ if it is to be skipped. ; ACTIVQ: LD A,(HL) ; Must be an active member OR A RET NZ ; Otherwise return NZ PUSH DE ; Save incoming DE LD DE,WLDFCB ; Point to user's wildcard LD A,(DE) SUB ' ' ; Is it blank? JR NZ,CHKWLD ; If not, use it POP DE ; Otherwise return Z RET ; CHKWLD: PUSH HL ; Now save incoming HL INC HL ; Bump to member filename LD B,11 ; Check 11 bytes ; GETENT1:LD A,(DE) ; Check for match with wildcards LD C,(HL) ; Get target char INC HL ; Pt to next INC DE CP '?' ; Wild match? JR Z,GETENT2 CP C ; Match? JR NZ,GETE0 ; Skip if not, return NZ ; GETENT2:DJNZ GETENT1 ; Count down until zero ; GETE0: POP HL POP DE RET ; ;----------------------------------------------------------------------- ; CORMSG: DEFB CR,LF,'+++ Library file is corrupt +++',CR,LF,'$' EMPMSG: DEFB CR,LF,'+++ No (matching) members found +++',CR,LF,'$' ERASE: DEFB BS,' ',BS,'$' ENDSIZ: DEFB 'k ','$' FNMSG: DEFB '--> ','$' ; Precedes uncompressed filename display LBRNAM: DEFB 'Library File = ','$' MORPRM: DEFB '[more] ','$' NSMSG: DEFB CR,LF,'+++ Library file not found +++',CR,LF,'$' ; TYPE1: DEFB ' Crunched','$' TYPE2: DEFB ' Squeezed','$' TYPE3: DEFB ' -- ','$' ; [Method = "none"] ; ;----------------------------------------------------------------------- ; USAGE: DEFB CR,LF,'vH1',CR,LF,LF DEFB 'To Use: B>LDIR lbrname ' DEFB '<<-- no .LBR extent needed',CR,LF,LF,'$' ; HEDING: DEFB CR,LF DEFB ' Name Length Method Original name' DEFB CR,LF DEFB '============ === ==== ======== =================' DEFB CR,LF,'$' ; ;----------------------------------------------------------------------- ; BYE5: DEFS 1 ; Checks for presence of BYE5 DIRLEN: DEFS 2 ; Directory length, number of records INDEX: DEFS 2 ; An RA index value to a beg of a menber file EXTCHR: DEFS 1 ; Middle letter of filename extension saved here NFILES: DEFS 2 ; Overall loop counter for program operation HLSAVE: DEFS 2 ; Temp storage for HL OVFTPA: DEFS 1 ; To monitor program case it tries to go nuts LINCTR: DEFS 1 ; Line counter for "[more]" prompt WLDFCB: DEFS 11 ; Safe storage for FCB2 filenametyp ; DEFS 80H ; Stack area for program's use ; STACK: DEFS 2 ; CCP stack address ; DIRBUF: DEFS 1024*19 ; (Not really part of program) - maximum memory ; needed for a 1024 member library END