;************************************************************************** ;* * ;* Non-banked/Banked BDOS for CP/M V3.1 * ;* * ;* Disassembly via the Masterful Disassembler on February 10, 1984. * ;* All labels not beginning with '?' or '@' are copyright (c) 1984 * ;* by Clark A. Calkins. Labels beginning with '?' or '@' may be * ;* copyright by Digital Research Inc., Pacific Grove, California. * ;* All comments are copyright (c) by Clark A. Calkins 1984. * ;* * ;* Note, at various places in the comments, reference is made to * ;* the CP/M System Guide or the Programmers Guide (ie "see sg #116" * ;* for page 116 of the System Guide). * ;* * ;* CP/M is a registered trademark of Digital Research, Pacific * ;* Grove, California. * ;* * ;************************************************************************** ; .SFCOND ;Do not list false conditionals ; ; Define configuation desired. ; FALSE EQU 0 TRUE EQU NOT FALSE BANKED EQU TRUE ;Set for a banked BDOS. ; ; Define initial address of this code. ; BNKBDOS: ; ; Now setup external address references compatible with GENCPM. ; ;************************************************************************** ;* * ;* Note that the address references below are interpreted by * ;* GENCPM and translated into the proper destination address for * ;* the module. These addresses must be flaged as relocatable in * ;* order for GENCPM to intercept them. Make no changes to these * ;* addresses unless the corresponding module has also been changed. * ;* GENCPM blindly follows the address references and does not care * ;* what realy is there. * ;* * ;************************************************************************** ; ; Setup System Control Block values. ; IF BANKED SCB$BASE EQU BNKBDOS-500H ;GENCPM requirement. ?WBOOT EQU SCB$BASE+68H ;Warm boot vector. ?CONST EQU SCB$BASE+6EH ;Console status vector. ?CONIN EQU SCB$BASE+74H ;Console input vector. ?CONOT EQU SCB$BASE+7AH ;Console output vector. ?LIST EQU SCB$BASE+80H ;List device vector. @STAMP EQU SCB$BASE+90H ;Vector for drives that have been stamped. @RELOG EQU SCB$BASE+92H ;Vector for drives stamped and re-loged. ; ; "Published" System Control Block starts here. ; @HSHCK EQU SCB$BASE+9CH ;Hash check byte. @HSHDRV EQU SCB$BASE+9DH ;Drive compare byte. @HSHNAME EQU SCB$BASE+9EH ;Filename code bytes. @HSHEXT EQU SCB$BASE+0A0H;Extent code byte. @VERSION EQU SCB$BASE+0A1H;CP/M version number storage. @RTNCODE EQU SCB$BASE+0ACH;Return code storage. @CHAIN EQU SCB$BASE+0B3H;Program chain flag byte. @SVBUF EQU SCB$BASE+0B4H;Flag saying to use previous line buffer. @WIDTH EQU SCB$BASE+0B6H;Colsole width byte. @COLUMN EQU SCB$BASE+0B7H;Console cursor column number. @BUFPTR EQU SCB$BASE+0BAH;Input line pointer. @POINTR EQU SCB$BASE+0BCH;Keyboard input pointer location. @CIVEC EQU SCB$BASE+0BEH;Console input redirection flag. @COVEC EQU SCB$BASE+0C0H;Console output redirection flag. @AIVEC EQU SCB$BASE+0C2H;Auxillary input redirection flag. @AOVEC EQU SCB$BASE+0C4H;Auxillary output redirection flag. @LOVEC EQU SCB$BASE+0C6H;List output redirection flag. @CTRLH EQU SCB$BASE+0CAH;Control-H active flag. @RUBOUT EQU SCB$BASE+0CBH;Rubout active flag. @KEYST EQU SCB$BASE+0CCH;Submit mode keyboard status byte. @MODE EQU SCB$BASE+0CFH;Console mode bytes. @BNKBF EQU SCB$BASE+0D1H; @DELIM EQU SCB$BASE+0D3H;Print string delimiter. @OUTFLG EQU SCB$BASE+0D4H;List output flag. @KEYLK EQU SCB$BASE+0D5H;Keyboard lock byte. @CRDMA EQU SCB$BASE+0D8H;Current DMA address. @CRDSK EQU SCB$BASE+0DAH;Current disk. @VINFO EQU SCB$BASE+0DBH;(de) registers on entry to this BDOS. @RESEL EQU SCB$BASE+0DDH;Flag byte indicating a file i/o function. @MEDCHG EQU SCB$BASE+0DEH;Media change flag byte. @FX EQU SCB$BASE+0DFH;BDOS function number. @USRCD EQU SCB$BASE+0E0H;Current user number. @ENTRY EQU SCB$BASE+0E1H;Main file position entry storage. @MATCH EQU SCB$BASE+0E5H; @MLTIO EQU SCB$BASE+0E6H;Multi-sector count byte. @ERMDE EQU SCB$BASE+0E7H;Error mode flag byte. @ERDSK EQU SCB$BASE+0EDH;Error disk. @MEDIA EQU SCB$BASE+0F0H;Possible media change flag (door open). @BFLGS EQU SCB$BASE+0F3H;BDOS flags. @DATE EQU SCB$BASE+0F4H;System date. @HOUR EQU SCB$BASE+0F6H;System hour. @MIN EQU SCB$BASE+0F7H;Minute. @SEC EQU SCB$BASE+0F8H;Second. @COMMON EQU SCB$BASE+0F9H;Base of common memory, ?ERJMP EQU SCB$BASE+0FBH;BDOS error handler. @MXTPA EQU SCB$BASE+0FEH;End of usable memory. ; ; Define Resident BDOS entry points and storage areas. ; RESBDOS EQU BNKBDOS-300H ;GENCPM address requirement. @@MOVE EQU RESBDOS+09H ;Data to/from memory bank (a). @@BANK1 EQU RESBDOS+0CH ;Data to/from memory bank (1). @@SEARCH EQU RESBDOS+0FH ;Search hash tables in memory bank (a). @@SRCH EQU RESBDOS+12H ;Record count byte. @@DIRFLG EQU RESBDOS+14H ;Hash search flag byte. @@XFCB EQU RESBDOS+15H ;Label or XFCB created flag byte. @@PSWRD EQU RESBDOS+16H ;Password entry enable flag byte. @@ALTER EQU RESBDOS+17H ;Storage location for alternate dir entry. @@USRDMA EQU RESBDOS+19H ;Users DMA address. @@BUFAD EQU RESBDOS+1BH ;Address of BCB buffer. @@FLAG EQU RESBDOS+1DH ;FCB has been updated flag. @@BUFFR EQU RESBDOS+1EH ;Location of users data buffer. @@KEYBFR EQU RESBDOS+20H ;Single character buffer in Resident BDOS. @@GETC EQU RESBDOS+21H ;Routine to get a byte from (hl) in bank (1). ENDIF ; ; Define BIOS entry points. ; BIOS EQU BNKBDOS-100H ;GENCPM requires relocatable addresses. ?BOOT EQU BIOS+00H ;Cold boot entry point. IF NOT BANKED ?WBOOT EQU BIOS+03H ;Warm boot. ?CONST EQU BIOS+06H ;Console status. ?CONIN EQU BIOS+09H ;...Input. ?CONOT EQU BIOS+0CH ;...Output. ?LIST EQU BIOS+0FH ;list device. ENDIF ?AUXO EQU BIOS+12H ;Auxillary output routine. ?AUXI EQU BIOS+15H ;Auxillary input routine. ?HOME EQU BIOS+18H ;Disk home routine. ?SLDSK EQU BIOS+1BH ;Select disk routine. ?STTRK EQU BIOS+1EH ;Set track routine. ?STSEC EQU BIOS+21H ;Set sector routine. ?STDMA EQU BIOS+24H ;Set DMA address routine. ?READ EQU BIOS+27H ;Disk read routine. ?WRITE EQU BIOS+2AH ;Disk write routine. ?SCTRN EQU BIOS+30H ;Sector translation routine. ?AUXIS EQU BIOS+36H ;Auxillary input status routine. ?AUXOS EQU BIOS+39H ;Auxillary output status routine. ?MLTIO EQU BIOS+45H ;Set multi-sector count. ?FLUSH EQU BIOS+48H ;Flush buffers routine. ?MOV EQU BIOS+4BH ;Block move routine. ?TIM EQU BIOS+4EH ;Time of day routine. ?STBNK EQU BIOS+54H ;Set memory bank routine. ?XMOV EQU BIOS+57H ;Bank to bank move routine. ; ; ASCII character code table. ; SOH EQU 1 ;Control-A. STX EQU 2 ;Control-B. ETX EQU 3 ;Control-C. ENQ EQU 5 ;Control-E. ACK EQU 6 ;Control-F. BEL EQU 7 ;Control-G (bell). BS EQU 8 ;Back space. TAB EQU 9 ;Tab char. LF EQU 10 ;Line feed. VT EQU 11 ;Control-K. CR EQU 13 ;Carriage return. DLE EQU 16 ;Control-P. DC1 EQU 17 ;Control-Q. DC2 EQU 18 ;Control-R. DC3 EQU 19 ;Control-S. DC4 EQU 20 ;Control-P. NAK EQU 21 ;Control-U. ETB EQU 23 ;Control-W. CAN EQU 24 ;Control-X. DEL EQU 127 ;Rubout. ; ; Define public entry points. ; ; public ??BDOS,??ERR ; ;************************************************************************** ; ; Start of code section. ; DEFB 0,0,0,0,0,0 ;Standard PRL file header (serial number). ; ; Main entry point to the Banked BDOS, CP/M v3.0. ; ??BDOS: EX DE,HL LD (@VINFO),HL ;Save entry parameters. EX DE,HL LD A,C LD (@FX),A ;Save function number. CP 14 ;Look for possible disk i/o functions. JP C,NORMAL LD HL,0 LD (BUFREC),HL ;Clear blocking buffer record number. LD A,(@CRDSK) LD (DRIVE),A IF BANKED DEC A LD (MOVFLAG),A ENDIF LD A,(@MLTIO) ;Check multi-sector count. DEC A ;1=Normal processing. JP Z,NORMAL LD HL,RWTBL FUNCHECK:LD A,(HL) ;End of table? OR A JP Z,NORMAL CP C ;No, found our function? JP Z,MULTI$IO ;Yes, process separately. INC HL ;...no, move on to next function. JP FUNCHECK ; ; Normal function processing. Setup our parameters ; and look through our function/address tables. ; NORMAL: LD A,E LD (SAVE$E),A LD HL,0 LD (RET$STAT),HL LD (@RESEL),HL ADD HL,SP ;Save users stack pointer. LD (USR$STK),HL IF NOT BANKED LD SP,STACK ;Set our own stack area. ENDIF LD HL,MAIN$RET ;Set main return address. PUSH HL LD A,C CP 51 ;Is function <51? JP NC,NORM01 LD C,E ;Yes, move function into (c) and LD HL,MAIN$FUN ;use main function address table. JP NORM02 NORM01: CP 128 ;Function >128? JP NC,PARSE ;Yes, process directly. SUB 98 ;Function <98 or >112? JP C,RETERROR ;...yes. CP 15 JP NC,RETERROR ;...yes too. LD HL,ALT$FUN ;Nope, use our table for 98-112. NORM02: LD E,A ;Get function (a) from table (hl). LD D,0 ADD HL,DE ADD HL,DE LD E,(HL) INC HL LD D,(HL) LD HL,(@VINFO) ;Reset parameters and EX DE,HL JP (HL) ;Jump to proper section. ; ;************************************************************************** ; ; BDOS error procesing routine. Enter with error ; number in (c) and determine if this is fatal or ; not (just return with error). Note that this is only called ; by the Resident BDOS. ; ??ERR: LD B,0 ;External error entry point. PUSH BC DEC C ;Make error code zero relative. LD HL,ERR$TBL ADD HL,BC ADD HL,BC LD E,(HL) ;Get address of error routine. INC HL LD D,(HL) EX DE,HL CALL PRT$ERR ;Call error processing routine. POP BC LD A,(@ERMDE) ;Check error mode byte. OR A ;Return with error? RET NZ ;...yes. JP BDOS$ERR ;Nope, warm start. ; ; File i/o functon table. ; RWTBL: DEFB 20,21,33,34,40,0;Read/write function numbers. ; IF BANKED DEFB 'COPYRIGHT (C) 1982, ' DEFB 'DIGITAL RESEARCH 151282' ELSE DEFB 'COPR. ',39,'82 DRI 151282' DEFB 199,199,199,199,199,199,199,199,199,199 DEFB 199,199,199,199,199,199,199,199,199,199 DEFB 199,199,199,199,199,199,199,199,199,199 DEFB 199,199,199,199,199,199,199,199,199,199 DEFB 199,199,199,199,199,199,199,199,199,199 DEFB 199,199,199,199,199,199,199,199,199,199 DEFB 199,199 STACK: ENDIF ; ; Main function table. ; MAIN$FUN:DEFW WARMBOOT,CON$IN;Functions 0-50. DEFW CONOUT,AUX$INP DEFW ?AUXO,?LIST DEFW DIRECT,AUX$INS DEFW AUX$OUS,PSTRING DEFW BUFF$INP,CONST DEFW VERSION,RESET DEFW DRIVESEL,OPEN DEFW CLOSE,SRCHFRST DEFW SRCHNEXT,DELETE DEFW READSEQ,WRITESEQ DEFW MAKEFILE,RENAME DEFW GETLGVEC,GETDISK DEFW SET$DMA,GETALVEC DEFW WRTPRTCT,GETROVEC DEFW SETFILE,GETPBVEC DEFW USERCODE,READRND DEFW WRITERND,FILESIZE DEFW SETRAN,RST$DRV DEFW IGNORE,IGNORE DEFW WRITERND,RETERROR DEFW IGNORE,IGNORE DEFW MULTISEC,SETMODE DEFW FRESPACE,CHAIN DEFW FLUSH,GT$STSCB DEFW DIR$BIOS ; ; Extra functons (CP/M 3.0). ; ALT$FUN:DEFW FREEBLKS,TRUNCATE;Functions 98-112. IF BANKED DEFW DIRLABEL,GETLABEL DEFW RD$DATE,WRT$XFCB DEFW DATETIME,TIMEDATE DEFW SETPSWD,GETSERL ELSE DEFW RETERROR,GETLABEL DEFW RD$DATE,RETERROR DEFW DATETIME,TIMEDATE DEFW IGNORE,GETSERL ENDIF DEFW GT$STRTN,CON$MODE DEFW CON$DLIM,BLOCK$IO DEFW BLOCK$IO ; ; Error message address table. ; ERR$TBL:DEFW IO$ERROR,DISK$RO;Error type table (1-9). DEFW FILE$RO,INVALID DEFW 0,0 DEFW PSWD$ERR,EXISTS DEFW FILENAME ; ; Handle function numbers greater than 128 here. The ; only one we can execute is #152 (parse filename). The ; others are MP/M functions which have no counter part ; in the system (so they are ignored). ; PARSE: CP 152 ;Is this function 152? RET NZ ;Ignore M/PM functions. LD HL,STORE$HL ;Set return address. PUSH HL LD HL,(@VINFO) ;Get address of file name. LD E,(HL) INC HL LD D,(HL) PUSH DE INC HL LD E,(HL) ;Get address of FCB. INC HL LD D,(HL) POP HL EX DE,HL PUSH HL ;Setup initial FCBcontents. XOR A ;Clear drive byte. LD (HL),A INC HL LD BC,200BH ;Move 11 spaces next. CALL STUFF$EM LD BC,4 ;Followed by 4 nulls. CALL STUFF$EM LD BC,2008H ;Then 8 spaces. CALL STUFF$EM LD BC,12 ;Then lastly 12 nulls. CALL STUFF$EM CALL NON$BLNK ;Get next non-blank char from input line. LD A,(DE) ;Get next byte (#2). CP ':' ;Is this a colon? DEC DE ;Reset (de) to first char. POP HL PUSH HL JP NZ,PARSE01 CALL DELIMITR ;Yes, check first char. JP Z,PARSE06 ;...delimiter, skip. SUB 'A' ;Is it a legal drive name (a-p)? JP C,PARSE08 ;Nope. CP DLE ;Maybe. JP NC,PARSE08 INC DE ;Yes, skip letter and colon. INC DE INC A ;Store drive name. LD (HL),A PARSE01:INC HL CALL DELIMITR ;Check next char for a delimiter. JP Z,PARSE06 ; ; Start of filename. Set (b) to length-1, and (c) to ; zero (allows asterix to mean fill field). ; LD BC,700H ;(b)=7 and (c)=0. PARSE02:LD A,(DE) ;End of name? CP '.' JP Z,PARSE03 CP ';' ;Start of password? JP Z,PARSE09 CALL STORECHR JP NZ,PARSE02 ;Continue for (b)+1 chars. JP PARSE06 PARSE03:INC DE ;Process extension. POP HL PUSH HL LD BC,9 ;Point ot it. ADD HL,BC LD BC,0200H ;(b)=length-1, (c)=0 (* ok). PARSE04:LD A,(DE) CP ';' ;Start of password? JP Z,PARSE09 CALL STORECHR ;Nope, just store. JP NZ,PARSE04 ;Continue til done. PARSE06:POP BC ;Done with extension. Check PUSH DE ;terminating char. CALL NON$BLNK DEC DE CALL DELIMITR ;Deliminator? POP HL RET NZ ;Nope, okay. LD HL,0 ;Yes, check it. OR A ;A null is okay here. RET Z CP CR ;So is a (cr). RET Z EX DE,HL ;Otherwise, error. RET ; ; Parsing error. Return ffff error code. ; PARSE07:POP BC PARSE08:POP BC LD HL,0FFFFH ;Set error code and return. RET PARSE09:INC DE ;Process password. POP HL PUSH HL LD BC,16 ;Point to it. ADD HL,BC LD BC,0701H ;Set length (b), no asterix processing (c<>0). PARSE10:CALL STORECHR JP NZ,PARSE10 LD A,7 ;Compute password length. SUB B POP HL PUSH HL LD BC,26 ;Store count in FCB+26. ADD HL,BC LD (HL),A LD A,(DE) ;What? Makes no sense. JP PARSE06 ; ; Store character from (de) into area at (hl). Set ; max length-1 in (b) and set (c) to zero if asterix ; is to be interpreted as a wild card fill request. ; STORECHR:CALL DELIMITR ;End of field? RET Z CP ' ' ;Legal char? INC DE JP C,PARSE07 ;Nope, error. INC B ;Field full? DEC B JP M,PARSE07 ;Yep, error. INC C ;Asterix is wild? DEC C JP NZ,STRCHR1 CP '*' ;Yes, is it one? JP Z,STRCHR2 ;Yes, fill field with "?". STRCHR1:LD (HL),A ;Store char. INC HL DEC B OR A ;Set zero flag at end of string. RET STRCHR2:LD (HL),'?' ;Fill remaining field with "?". INC HL DEC B JP P,STRCHR2 RET ; ; Table of legal delimiters. ; TBL$DEL:DEFB CR,TAB,' .,:',59,'[]=<>|',0;Ends with a null. ; ; Check character at (de) for a legal delimiter. Set ; the zero flag if yes. Otherwise return character in (a). ; Note lower case letters are converted into upper case. ; DELIMITR:LD A,(DE) ;Get char. PUSH HL LD HL,TBL$DEL ;Look thru our table. DELIM01:CP (HL) ;Found same? JP Z,DELIM02 INC (HL) ;Nope, end of table? DEC (HL) INC HL JP NZ,DELIM01 OR A ;Clear zero flag (not found). DELIM02:POP HL RET Z ;Return if a delimiter. CP 'a' ;Otherwise check for lower case. RET C CP '{' JP NC,DELIM03 AND 05FH ;Make upper case. DELIM03:AND 7FH ;Strip bit 7 always (why worry?). RET ; ; Stuff (c) characters of (b) into area at (hl). ; STUFF$EM:LD (HL),B ;Move (b) into next spot. INC HL DEC C ;Done? JP NZ,STUFF$EM RET ; ; Get the next character from (de) that is not a blank ; or a tab. Return with it in (a) and (de) pointing ; to next char. ; NON$BLNK:LD A,(DE) INC DE CP ' ' JP Z,NON$BLNK CP TAB JP Z,NON$BLNK RET ; ; Print error message in standard BDOS format. (hl) ; points to specific line and the remainder is filled ; in by the function number and filename (if appropriate). ; PRT$ERR:PUSH HL ;Save message pointer. CALL CRLF ;Add initial blank line (or end previous line). LD A,(CURDRIVE) ;Convert selected disk to ascii and place in message. ADD A,'A' LD (ERRDISK),A LD BC,CPMERROR ;Print initial message line. IF NOT BANKED CALL PRINT POP BC JP PRINT ELSE CALL PMESG POP BC ;Get addr of variable mesg into (bc). LD A,(@BFLGS) ;Do we display long messages? RLA JP NC,PMESG ;....no, print this line and return. CALL PMESG ;...yes, print this line followed by function #. LD A,(@FX) ;Get function # and convert to ascii. LD B,'0' LD HL,FUN$NUM ;Store it here. CP 100 ;Greater than 99? JP C,PERR01 LD (HL),'1' ;Yes, add leading "1" and adjust for it. INC HL SUB 100 PERR01: SUB LF ;Divide (a) by 10. Result in (b). JP C,PERR02 INC B JP PERR01 PERR02: LD (HL),B ;Stuff tens digit. INC HL ADD A,':' ;Convert reemainder into ones digit. LD (HL),A ;And stuff it followed by a space. INC HL LD (HL),' ' LD HL,MESG$END ;Add terminator now. LD (HL),0 LD A,(@RESEL) ;Do we need to add the filename? OR A JP Z,PERR03 ;...nope, we are ready to print. LD (HL),' ' ;...yes, clear terminator first. PUSH DE LD HL,(@VINFO) ;Point to filename. INC HL ;Skip drive byte. EX DE,HL LD HL,FNAME ;Store name here. LD C,8 ;Move the first 8 chars into place. CALL MOVE$C LD (HL),'.' ;Add separating period. INC HL LD C,ETX ;Now move extension into place. CALL MOVE$C POP DE PERR03: CALL CRLF ;End previous line. LD BC,BDOSMESG ;And print this last line (and return). JP PMESG ;...what??? (strange code). ; ; Print mesage pointed to by (bc). It must end ; with a null byte. ; PMESG: LD A,(BC) OR A RET Z PUSH BC LD C,A CALL CONOUT POP BC INC BC JP PMESG ; ; BDOS file function error message (standard format). ; BDOSMESG:DEFB 'BDOS Function = ' FUN$NUM:DEFB ' ' MESG$END:DEFB ' File = ' FNAME: DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0 ENDIF ; ; Set BDOS error codes here. ; BDOS$ERR:LD HL,0FFFDH ;Set BDOS error code. JP SET$RTRN BDOSABRT:LD HL,0FFFEH ;Set control-C abort code. SET$RTRN:LD (@RTNCODE),HL;Save program return code and warm boot. WARMBOOT:JP ?WBOOT USR$STK:DEFB 0,0 ;Safe store area for users stack ptr. ; ; Multi-sector i/o processing routine. This effectively ; executes the normal BDOS i/o function a given number ; of times. ; MULTI$IO:LD HL,0 ;Save initial stack ptr. ADD HL,SP LD (STK$SAVE),HL IF NOT BANKED LD SP,TMP$DMA ;Set our own stack. ENDIF LD HL,MULTIRET ;Set return address. PUSH HL CALL GET$REC ;Extract record bytes (rc,r0,r1,r2). CALL GET$DMA LD A,(@MLTIO) ;Set loop count. MULTI$01:PUSH AF LD (REMAINS),A ;Save Remaining count. CALL GO$NORM ;Process function normally. OR A ;Error? JP NZ,MULTIERR ;Yes... LD A,(@FX) ;Random i/o? CP 33 CALL NC,BUMP$REC ;Yes, bump record number. CALL BUMP$PTR ;Bump buffer ptr. POP AF ;More sectors to process? DEC A JP NZ,MULTI$01 LD H,A ;Nope, set good return code and exit. LD L,A RET STK$SAVE:DEFB 0,0 DEFB 199,199,199,199,199,199,199,199,199,199 TMP$DMA:DEFB 0,0 ; ; Process command normally. Reset original registers ; and execute. ; GO$NORM:LD A,(@FX) ;Get function back into (c). LD C,A LD HL,(@VINFO) ;Get FCB pointer into (de). EX DE,HL JP NORMAL ; ; Bump buffer address pointer by 128 bytes (one ; logical sector). ; BUMP$PTR:LD HL,(@CRDMA) ;Get current address. LD DE,128 ;Increment by 128. ADD HL,DE JP STDMA01 ; ; Save DMA address in temporary buffer. ; GET$DMA:LD HL,(@CRDMA) LD (TMP$DMA),HL RET ; ; Restore DMA address from our temporary buffer. ; PUT$DMA:LD HL,(TMP$DMA) ; ; Store (hl) as the DMA address. ; STDMA01:LD (@CRDMA),HL JP DO$IO4 ; ; Process i/o errors. If this is a physical disk error ; then return directly with error code. Otherwise ; return the number of completed sectors in (h). ; MULTIERR:POP BC ;Pop original sector count into (b). INC A ;Phisical disk error? RET Z ;Yes, just return. LD A,(@MLTIO) ;Okay, compute number of sectors SUB B ;completed without error. LD H,A RET ; ; Process returns from multi-sectored i/o here. ; MULTIRET:PUSH HL ;Save return code. LD A,(@FX) ;Random i/o? CP 33 CALL NC,SET$REC ;Yes, move record number into place. CALL PUT$DMA POP DE ;Set return code into regs. LD HL,(STK$SAVE);Reset stack pointer. LD SP,HL EX DE,HL LD A,L LD B,H RET ; ; Get a single character and return in (a). ; KEY$INP:LD HL,@@KEYBFR ;Check internal buffer first. LD A,(HL) LD (HL),0 ;Always clear it. OR A ;Empty? RET NZ JP ?CONIN ;Yes, access physical keyboard. ; ; Console input function (#1). ; CON$IN: LD HL,SAVESTAT ;Set return address. PUSH HL CONIN01:CALL KEY$INP ;Check keyboard. CALL CHKCNTRL ;Control character? JP C,CONIN02 PUSH AF ;Nope, save character and echo. LD C,A CALL CONOUT ;Echo w/ tab expansion. POP AF ;Get character and return. RET CONIN02:CALL CHKMODE1 ;Do we interpret control chars? RET NZ ;Nope, just return. CP DC3 ;Control-S? JP NZ,CONIN03 CALL WAITING ;Yes, wait for ^Q. JP CONIN01 CONIN03:CP DC1 ;Ignore ^Q and ^P here. JP Z,CONIN01 CP DLE JP Z,CONIN01 RET ;Just return control char. ; ; Check for a control character (excludes cr,lf,tab,bs). ; Set carry if this is one. ; CHKCNTRL:CP CR ;(cr)? RET Z CP LF ;(lf)? RET Z CP TAB ;(tab)? RET Z CP BS ;(bs)? RET Z CP ' ' ;None of the above, set carry on other RET ;control character. CONSTAT:LD A,(@@KEYBFR) ;Check internal buffer first. OR A ;Anything present? JP NZ,WAIT04 ;Yes, return a 1 in (a). CALL ?CONST ;Check physical keyboard. AND 1 ;Check bit 0 only. RET ; ; Set the bit in the SCB that indicates that the physical ; keyboard must be used for subsequent i/o. This ; is necessary to prevent SUBMIT input from aborting ; a running job. This status must be cleared to resume ; SUBMIT type operation. ; IF BANKED KEYLOCK:LD HL,@KEYLK ;Get address of keyboard lock byte. LD (HL),040H ;Set bit 6 on. EX (SP),HL ;Put this address on stack and return. JP (HL) ENDIF ; ; Check console mode bit #1 of first byte. Register (a) ; is preserved and reg (b) is used. ; CHKMODE1:LD B,A ;Save (a). LD A,(@MODE) ;Get first mode byte. AND 2 ;Check bit 1. LD A,B ;Restore (a) and reeturn. RET ; ; Check the keyboard. If ^S/^Q is enabled, this will be ; checked also. Otherwise, this returns the physical ; keyboard status. ; KBRDCHK:CALL CHKMODE1 ;Check console mode. ^S/^Q disabled? JP NZ,CONSTAT ;...yes, just check keyboard. LD A,(@@KEYBFR) ;Nope, check SCB buffer. OR A ;Anything already present? JP NZ,HALT ;...yes, check for control keys. IF BANKED LD A,(@KEYST) ;Under SUBMIT, use this as status if not INC A ;equal to 0ffh. JP Z,CONSTAT ;Go to console status only. ENDIF ; ; Check for a scroll halt function (^S). If one is ; found, then wait for ^Q to continue or ^C to abort. ; HLT$SCRL:CALL CHKMODE1 ;Scroll control disabLed? RET NZ LD A,(@@KEYBFR) ;Was ^S typed? CP DC3 JP Z,HALT IF BANKED CALL KEYLOCK ;Lock physical keyboard in. ENDIF CALL ?CONST ;Check keyboard now. IF BANKED POP HL LD (HL),0 ;Unlock keyboard. ENDIF AND 1 ;Anything ready? RET Z IF BANKED CALL KEYLOCK ;Lock again. ENDIF CALL ?CONIN ;Yes, get char. IF BANKED POP HL LD (HL),0 ;Unlock. ENDIF ; ; Check for control-S and wait or control-Q if found. We will ; also accept control-P as a priner on/off switch. Other chars ; between ^S and ^Q are ignored (they just beep). ; HALT: CP DC3 ;Was ^S typed? JP NZ,WAIT02 LD HL,@@KEYBFR ;Yes, did this come from the buffer? CP (HL) JP NZ,WAITING LD (HL),0 ;Yes, clear it then. WAITING: IF BANKED CALL KEYLOCK ;Wait for a ^Q or ^C (to abort). ENDIF CALL ?CONIN ;Get character. IF BANKED POP HL LD (HL),0 ;Unlock keyboard. ENDIF CP ETX ;Conrol-C? JP NZ,WAIT01 LD A,(@MODE) ;Yes, but do we abort on this? AND 8 JP Z,BDOSABRT ;Yes we do... XOR A WAIT01: SUB DC1 ;Control-Q? RET Z ;Yes, we are done waiting. INC A ;Control-P? CALL CHK$CHAR JP WAITING WAIT02: LD HL,@@KEYBFR LD B,A LD A,(@MODE) ;Abort on control-C? RRA JP NC,WAIT03 LD A,ETX ;Yes, is it one? CP (HL) RET Z ;Yes, return with zero set. WAIT03: LD A,B ;If char is not ^Q or ^P, then save it. CP DC1 JP Z,WAIT05 CP DLE JP Z,WAIT05 LD (HL),A ;Save (a) in internal buffer. WAIT04: LD A,1 ;Be sure (a) is non-zero. RET WAIT05: XOR A ;Waste character and return. LD (HL),A RET ; ; Check for a ^P to flip the printer echo flag. Other ; characters cause a beep only. ; CHK$CHAR:CALL Z,FLIP$FLG LD C,BEL ;Beep on unknown chrs. CALL NZ,?CONOT RET ; ; Flip the printer echo flag (if enabled). ; FLIP$FLG:LD A,(@MODE) ;Do we recognize ^P? AND DC4 JP NZ,FLIP01 ;...NOPE. LD HL,@OUTFLG LD A,1 ;...yes, flip bit 0 of output flag. XOR (HL) AND 1 ;Also clear other bits (why?). LD (HL),A RET FLIP01: XOR A ;Ignore ^P this time (no beep). RET ; ; Output (c) to the console. This routine is real ; strange. It looks like it used to do something ; else. But now it always goes to the console. ; OUT$C: LD A,(@FX) ;Check function code. DEC A ;Is it conin (echo)? JP Z,?CONOT LD A,B AND 8 JP NZ,?CONOT JP ?CONOT ; ; Output (c) to the console device with logical ; character processing (column adjustments). ; CONOT: LD A,(OUT$FLG) ;Check output flag (non-zero and we don't OR A ;output anything). JP NZ,CONOT01 LD A,(@MODE) ;Check console mode (why?). AND DC4 LD B,A PUSH BC LD A,(@FX) ;Are we eching an input char? DEC A CALL NZ,HLT$SCRL ;No, so check for scroll halt keys (^S). POP BC PUSH BC CALL OUT$C ;Output (c) now. POP BC LD A,B OR A JP NZ,CONOT01 PUSH BC LD A,(@OUTFLG) ;Echo to printer also? OR A CALL NZ,?LIST ;...yes. POP BC CONOT01:LD A,C ;Check character for carriage control. LD HL,@COLUMN CP DEL ;Ignore rubouts. RET Z INC (HL) ;Increment column number. CP ' ' ;Control character? RET NC ;Nope, we are done. DEC (HL) ;Yes, don't adjust column (yet). LD A,(HL) ;At the start of the line? OR A RET Z ;Yes, adjust no further. LD A,C ;Check for a backspace. CP BS JP NZ,CONOT02 DEC (HL) ;Yes, decrement counter and return. RET CONOT02:CP CR ;Is it a (cr)? RET NZ ;Nope, we are done. LD (HL),0 ;Yes, set column number to zero. RET ; ; Output (c) and expand control characters into ^X ; form. ; CONOT$C:LD A,C CALL CHKCNTRL ;Is this a control char? JP NC,CONOUT PUSH AF ;Yes, add leading "^". LD C,'^' CALL CONOT POP AF OR 040H ;Now make char upper case. LD C,A ;Are we at thr right edge? IF BANKED CALL CHKWIDTH RET Z ;Yes, just return without printing. ENDIF ; ; Main output routine. Character is in (c). Tabs will ; be exapnded if necessary (or allowed) and backspace ; (and rubout) will be handled as per user options. ; CONOUT: LD A,(@FX) ;Check function, are we echoing an DEC A ;input character? JP Z,CONOUT1 ;...yes, always print. LD A,(@MODE) ;Check console mode. AND 014H ;Don't expand tabs? JP NZ,CONOT ;...yes, just print (c) as is. CONOUT1:LD A,C ;Is this a tab? CP TAB JP NZ,CONOT ;...nope, just print. CONOUT2: IF BANKED LD A,(@FX) ;Check for input echo. CP SOH JP NZ,CONOUT3 ;...yes, don't care about screen width. CALL CHKWIDTH ;At right edge of screen? RET Z ;...yes, don't print any more. ENDIF CONOUT3:LD C,' ' ;Print one space. CALL CONOT LD A,(@COLUMN) ;Reached a tab stop? AND 7 JP NZ,CONOUT2 ;...no, continue. RET ;...yes, we are done. ; ; Process a backspace. This may or may not blank ; out the previous character. ^A only backs up one space. ; BCKSPACE:CALL BACKUP ;Backup one space. IF BANKED LD A,(SAVE$CH) ;Do we have to blank this out? CP 1 RET Z ENDIF LD C,' ' ;Yes, issue space followed by (bs). CALL ?CONOT ; ; Backup one column position. ; BACKUP: LD C,BS ;Send one backspace command. JP ?CONOT ; ; Print end of line marker ("#") and start new line on screen. ; END$LINE:LD C,'#' ;Print '#' then (cr/lf). CALL CONOT CALL CRLF ; ; Blank from left edge to the beginning cursor location. ; BLNK$LIN:LD A,(@COLUMN) ;Get current column number. LD HL,PHY$COL ;Reached physical end of screen? CP (HL) RET NC ;...yes, go no farther. LD C,' ' ;...nope, blank next column. CALL CONOT JP BLNK$LIN ; ; Output a carriage return, line feed combination. ; CRLF: LD C,CR CALL CONOT LD C,LF JP CONOT ; ; Output string at (bc) until delimiter reached. ; PRINT: LD HL,@DELIM ;Point to standard delimiter. LD A,(BC) ;Get next char. CP (HL) ;Same as delimiter? RET Z ;...yes, we are done. INC BC ;...nope, adjust pointer. PUSH BC LD C,A ;Print character. CALL CONOUT POP BC JP PRINT ; ; Get next input character from either the keyboard ; or the initialized buffer (supports the CCP multi- ; command line feature). ; GET$CHAR: IF BANKED LD HL,(LPTR) LD A,(HL) LD (TMP$BUF),A ENDIF LD HL,(@BUFPTR) ;Initialized buffer active? LD A,L OR H JP Z,KEY$INP ;Nope, use keyboard. IF BANKED CALL @@GETC ;Get char from buffer. ELSE LD A,(HL) ENDIF INC HL ;Bump pointer. OR A ;End of input? JP NZ,GETCHR1 LD HL,0 ;...yes, clear pointer. GETCHR1:LD (@BUFPTR),HL ;Save pointer. LD (@POINTR),HL ;Here too (why both?). RET NZ ;Return with char if present. JP KEY$INP ;Otherwise, check keyboard. ; ; Check to see if we are at the edge of the screen. ; Return with zero flag set if we are. ; IF BANKED CHKWIDTH:LD A,(@WIDTH) ;Set zero if at right edgee of screen. LD E,A LD A,(@COLUMN) CP E RET ; ; Move line from input buffer to area @(hl) up to ; ending null. (b) will be incremented by the number of ; characters moved. Note input pointer is not changed ; and ending null is not stored. ; MOVE$IT:EX DE,HL LD HL,(LPTR) EX DE,HL ; ; Move string from (de) to (hl) until a null byte ; is encountered (which is not moved). Count chars ; moved in (b). ; MOVE$STR:LD A,(DE) ;End of string? OR A RET Z ;...yes, we are done. INC DE ;No, bump pointers. INC HL LD (HL),A ;Store byte and continue. INC B JP MOVE$STR ; ; Fill the input line buffer from string at (hl) up ; to (b) characters. Add trailing null. ; LINEFILL:LD A,B ;Anything to move? OR A RET Z PUSH BC ;Yes, save count. LD C,B PUSH HL EX DE,HL INC DE LD HL,INP$BUF ;Move the data into here. CALL MOVE$C LD (HL),0 ;Add ending null byte. LD (LINE$BEG),HL;Save location of this point. POP HL POP BC RET ; ; Get or store current line in save buffer unless disabled. ; Enter with length of previous line in (b) and the access code ; in (c). (c)=0, get line, (c)<>0, put line. ; SET$LINE:LD A,(@SVBUF) ;Do we get line from save buffer? RLA ;Disabled? RET NC ;...yes, just return. LD HL,INP$BUF LD DE,SAV$BUF INC C ;Get or store? JP NZ,SETLEN01 EX DE,HL ;...store. Check count first. LD A,B OR A RET Z ;Ignore a zero char count. LD (SAV$LEN),A ;Save length of line. PUSH DE LD BC,SETLEN02 ;Setup return address. PUSH BC LD B,A SETLEN01:INC B ;Adjust count and move the line now. LD C,B JP MOVE$C ; ; Return here after a PUT function. ; SETLEN02:POP HL ;Clear buffers count byte. DEC HL LD (HL),0 RET ; ; Set cursor to current column position. ; SET$COL:LD A,(@COLUMN) LD (CUR$COL),A RET ; ; Blank out the left side until we reach the ; current column number. ; BLNKLEFT:LD A,(@COLUMN) ;Get current column. LD HL,PTRCOL CP (HL) ;Same? RET NC LD C,' ' ;...nope, continue sending spaces. CALL CONOT JP BLNKLEFT ; ; Move the cursor back until we reach the current ; column number. ; MOVELEFT:LD A,(CUR$COL) ;Reached current column yet? LD HL,@COLUMN CP (HL) RET NC LD C,BS ;...nope, one more backspace and continue. CALL CONOT JP MOVELEFT ; ; Check line length. The number of characters to the ; left of the cursor are in (b) already. We will ; count the spaces to the right. The max length ; allowed is in (c). We will BEEP if this is exceeded. ; And take alternate return path. ; LENGTH: PUSH BC PUSH HL LD HL,(LPTR) ;Get location of cursor in line. LD E,0 LEN01: LD A,(HL) ;Reached end of string? OR A JP Z,LEN02 INC E ;Nope, keep counting. INC HL JP LEN01 LEN02: LD A,B ;Compute total char count. ADD A,E CP C ;Exceed limit? PUSH AF LD C,BEL CALL NC,?CONOT ;Yes, beep. POP AF POP HL POP BC RET C ;Nope, return normally. POP DE POP DE JP BUFINP03 ; ; Check for a cursor move character. If not, undate line ; buffer. ; CURMOVE:LD A,(TMP$BUF) OR A RET Z LD A,(SAVE$CH) ;Check for cursor move commands only. CP SOH ;^A? RET Z CP ACK ;^F? RET Z CP ETB ;^W? RET Z ; ; Fix the currently displayed line for the key just pressed. ; FIXLINE:PUSH HL PUSH BC CALL SET$COL ;Set cursor to current column. LD HL,(LPTR) FIXLN01:LD A,(HL) ;Reached end of line null? OR A JP Z,FIXLN03 ;Yes, fix rest of screen and return. LD C,A ;Save character here. CALL CHKWIDTH ;Pased right edge of screen? JP C,FIXLN02 ;...nope. LD A,E ;Yes, set cursor at this edge. LD (@COLUMN),A JP FIXLN03 FIXLN02:PUSH HL CALL CONOT$C ;Output (c) now. POP HL INC HL JP FIXLN01 FIXLN03:LD A,(@COLUMN) LD (TMPSAVE),A CALL BLNKLEFT ;Blank to end of line. CALL MOVELEFT ;Move cursor back. LD A,(TMPSAVE) ;Reset its column too. LD (PTRCOL),A POP BC POP HL RET ; ; Set pointer to the end of the input line. ; SET$END:LD HL,LINE$END ;Set pointer to end of line. LD (LPTR),HL XOR A ;Set at end of line flag. LD (TMP$BUF),A RET ; ; Set pointer to beginning of input line. ; SET$BEG:LD HL,INP$BUF ;Set pointer to beginning of line. LD (LINE$BEG),HL RET ; ; If the cursor was already moved to the end of the ; line, then return it to its previous location. ; RESETCUR:LD HL,TMP$BUF ;Check end of line flag. LD A,(HL) OR A ;No at the end? RET NZ ;Nope, just return. INC (HL) ;Yes, clear the flag and reset the cursor. LD A,(@COLUMN) LD (PTRCOL),A RET ; ; Buffered input function #10. Read a line from ; the console with editing. ; BUFF$INP:CALL CHKWIDTH ;Passed end of screen? CALL NC,CRLF ;...yes, start new line. LD A,(SAV$LEN) ;Get length of any previous line. LD B,A LD C,0 ;Say this may be a GET request. CALL SET$LINE ;See if we are just editing a previous line. BUFINP01:CALL SET$BEG ;Set beginning of line pointer. CALL SET$END ;Set end of line also. BUFINP02:CALL CURMOVE ;Fix current line for previous key. XOR A ;Clear character storage buffer. LD (CH$BUFF),A ELSE BUFF$INP:LD A,D OR E JP NZ,BUFINP04 LD HL,(@CRDMA) LD (@VINFO),HL INC HL INC HL LD (@BUFPTR),HL BUFINP04: ENDIF LD A,1 ;Make output routines know they are LD (@FX),A ;echoing input chars. LD A,(@COLUMN) ;Establish cursor position. LD (PHY$COL),A LD HL,(@VINFO) ;Get address of users buffer. LD C,(HL) ;Get max char count. INC HL PUSH HL XOR A ;Clear input char count. LD B,A LD (LOG$COL),A ;Zero logical column counter. CP C ;Convert a zero length buffer into JP NZ,BUFINP03 INC C ;...a one char buffer. ; ; Get next input character. Current count is in (b) and max line length ; is in (c). Next storage location is in (hl). ; BUFINP03:PUSH BC PUSH HL BUFINP05: IF BANKED LD A,(CH$BUFF) ;Do we already have a char? OR A CALL Z,GET$CHAR ;...nope, get one. BUFINP06:LD (SAVE$CH),A ;Save char for now. ELSE CALL GET$CHAR ENDIF POP HL POP BC CP CR ;Was (cr) typed? JP Z,BUFINP53 CP LF ;How about a (lf)? JP Z,BUFINP53 IF BANKED CP ACK ;A (^F)? JP NZ,BUFINP08 CALL CHKWIDTH ;Yes, can we wove to the right though? DEC E CP E JP NC,BUFINP03 ;...nope, ignore. ; ; Move the cursor one space to the right (but not passed the end of ; the line). ; BUFINP07:EX DE,HL LD HL,(LPTR) ;Get pointer to cursor. LD A,(HL) ;At the end of the line? OR A JP Z,BUFINP13 ;Yes, ignore this key. INC HL ;Nope, bump the pointer. LD (LPTR),HL EX DE,HL JP BUFINP44 ;Be sure we don't go passed end of line buffer. ; BUFINP08:CP ETB ;Was (^W) typed? JP NZ,BUFINP17 BUFINP09:EX DE,HL ;Yes, is current line empty? LD HL,(LPTR) LD A,(HL) OR A JP Z,BUFINP11 EX DE,HL ;Nope, just move to the end of the line. CALL CHKWIDTH ;Are we passed the edge yet? DEC E CP E EX DE,HL JP C,BUFINP10 ;...nope. EX DE,HL ;Yes, fix the line from the current cursor. CALL FIXLINE EX DE,HL JP BUFINP12 ;Get another key. BUFINP10:LD HL,(LPTR) ;Get current cursor character. LD A,(HL) INC HL ;And bump it. LD (LPTR),HL JP BUFINP16 ; ; Recall previous line (how is this done?). ; BUFINP11:LD HL,TMP$BUF ;Is the cursor at the end of the line? LD A,(HL) LD (HL),0 ;Always becomes YES. OR A JP Z,BUFINP14 ;...yes. ; ; Key must be ignored. ; BUFINP12:LD HL,CH$BUFF ;Ignore the character just typed. LD (HL),0 BUFINP13:EX DE,HL JP BUFINP03 ; BUFINP14:LD A,(CH$BUFF) ;Was a character previously ready? OR A JP NZ,BUFINP15 ;...yep. LD A,B ;Check current character count. OR A ;Line empty? JP NZ,BUFINP13 ;Nope. CALL SET$BEG ;Yep, set beginning pointer. BUFINP15:LD HL,(LINE$BEG);Check beginning char. LD A,(HL) ;End-of-line null? OR A LD (CH$BUFF),A ;Save it just in case. JP Z,BUFINP13 ;Yes, process next key. INC HL ;Nope, bump pointer and continue. LD (LINE$BEG),HL BUFINP16:LD HL,CH$BUFF ;Now set ^W to automatically move to the LD (HL),ETB ;end of the previous line. EX DE,HL JP BUFINP44 ; ; Continue checking the input character in (a). ; BUFINP17:CP SOH ;Was (^A) typed? JP NZ,BUFINP18 LD A,(PHY$COL) ;Yes, backup one space if possible. LD D,A LD A,(@COLUMN) CP D ;Back to the start already? JP Z,BUFINP03 ;...yes, ignore this then. LD (OUT$FLG),A ;Prohibit output, LD A,B ;Any character been typed? OR A JP Z,BUFINP40 ;Nope. DEC B ;Yep, adjust count. PUSH HL CALL RESETCUR ;Reset cursor. POP DE LD HL,(LPTR) ;Adjust input line pointer. DEC HL LD (LPTR),HL LD A,(DE) ;Reset cursor character. LD (HL),A EX DE,HL JP BUFINP40 ; BUFINP18:CP STX ;(^B)? JP NZ,BUFINP23 LD A,(LOG$COL) ;At the beginning of the line? CP B JP NZ,BUFINP19 LD A,ETB ;Yes, move to the end then. LD (TMP$BUF),A LD (SAVE$CH),A JP BUFINP09 BUFINP19:EX DE,HL ;Move to the beginning of the line. LD HL,(LPTR) INC B BUFINP20:DEC B LD A,(LOG$COL) ;Reached start? CP B JP Z,BUFINP21 DEC HL ;Nope, move one more space. LD A,(DE) LD (HL),A DEC DE JP BUFINP20 BUFINP21:LD (LPTR),HL ;Reset pointer into input buffer. PUSH BC PUSH DE CALL RESETCUR ;Reset the cursor. BUFINP22:LD A,(@COLUMN) ;Now backup the cursor until we reach the LD B,A ;beginning of the line. LD A,(PHY$COL) CP B ;There yet? JP Z,BUFINP05 ;...yes, get next key. LD C,BS ;Nope, backup one more space. CALL CONOT JP BUFINP22 ;And continue. ; BUFINP23:CP VT ;Was (^K) typed? JP NZ,BUFINP24 ;Delete all characters from the cursor to EX DE,HL ;the right edge. LD HL,LINE$END ;Set end of line address. LD (LPTR),HL EX DE,HL CALL CURMOVE ;Fix the line now. JP BUFINP03 ; ; Continue checking (a). ; BUFINP24:CP BEL ;Was (^G) typed? JP NZ,BUFINP25 LD A,(TMP$BUF) ;Yes, delete cursor char. OR A ;Already at end of line? JP Z,BUFINP03 ;...yes, ignore then. JP BUFINP07 ENDIF ; ; Continue checking (a). ; BUFINP25:CP BS ;Backspace? JP NZ,BUFINP28 LD A,(@CTRLH) ;Is control-H active? INC A JP Z,BUFINP29 ;No, treat this as a rubout. BUFINP26:LD A,(PHY$COL) ;Anything to rubout? LD D,A LD A,(@COLUMN) CP D JP Z,BUFINP03 ;No, ignore this then. LD (OUT$FLG),A ;Disable output. LD A,B ;Decrement counter (but not passed zero). OR A JP Z,BUFINP27 DEC B BUFINP27:JP BUFINP40 ; ; Continue checking character in (a). ; BUFINP28:CP DEL ;Rubout typed? JP NZ,BUFINP30 LD A,(@RUBOUT) ;Is rubout active? INC A JP Z,BUFINP26 ;No, treat as control-H. BUFINP29: IF BANKED LD A,DEL LD (SAVE$CH),A LD A,(TMP$BUF) ;In the middle of the line? OR A JP NZ,BUFINP26 ;Yes, treat as a backspace. ENDIF LD A,B ;Anything to rubout? OR A JP Z,BUFINP03 ;Nope, ignore this then. LD A,(HL) ;Get character to echo. DEC B ;Update pointers. DEC HL JP BUFINP47 ;Then echo char. ; ; Check character in (a) some more. ; BUFINP30:CP ENQ ;(^E) typed? JP NZ,BUFINP31 PUSH BC ;Yes, insert physical end of line. LD A,B ;Save logical column number. LD (LOG$COL),A PUSH HL IF BANKED LD A,(TMP$BUF) OR A CALL NZ,BLNKLEFT ;Blank left side? ENDIF CALL CRLF ;Enter physical (cr/lf). IF BANKED CALL CURMOVE ENDIF XOR A ;Reset physical column number. LD (PHY$COL),A JP BUFINP05 ; ; Check (a) some more. ; BUFINP31:CP DLE ;Was (^P) typed? JP NZ,BUFINP32 PUSH HL ;Yes, flip the output flag. PUSH BC XOR A ;No beep on this. CALL CHK$CHAR POP BC POP HL JP BUFINP03 ; ; And more. ; BUFINP32:CP CAN ;Was (^X) typed? JP NZ,BUFINP35 POP HL BUFINP33:LD A,(PHY$COL) ;Physical start of user input line column. LD HL,@COLUMN CP (HL) ;Back to the start already? IF BANKED JP C,BUFINP34 ;...nope. LD HL,(LPTR) LD A,(HL) OR A JP NZ,BUFINP02 JP BUFINP01 ELSE JP NC,BUFINP04 ENDIF BUFINP34:DEC (HL) ;Decrement count. CALL BCKSPACE ;Erase one char at a time. JP BUFINP33 ; ; Still more checking. ; BUFINP35:CP NAK ;(^U) typed? JP NZ,BUFINP37 IF BANKED EX (SP),HL CALL LINEFILL ;Move current line into users line buffer. EX (SP),HL ENDIF BUFINP36:CALL END$LINE ;Print "#" and start over. POP HL IF BANKED JP BUFINP01 ELSE JP BUFINP04 ENDIF ; ; Check character typed (a). ; BUFINP37:CP DC2 ;Was (^R) typed? JP NZ,BUFINP44 XOR A ;Set so we see whole line again. LD (LOG$COL),A IF BANKED EX DE,HL CALL SET$END EX DE,HL LD A,B ;Anything to echo? OR A JP Z,BUFINP36 ;Nope, just start over. EX DE,HL ;Set previous line up the same as the LD HL,(LPTR) ;current line. Then we just "recall" INC B ;the previous line. BUFINP38:DEC B ;Done with whole line? JP Z,BUFINP39 DEC HL ;Nope, move next byte. LD A,(DE) LD (HL),A DEC DE JP BUFINP38 BUFINP39:LD (LPTR),HL ;Save pointer. PUSH BC PUSH DE CALL END$LINE ;Print "#" and start new line. LD A,ETB ;Pretend (^W) was typed now. LD (CH$BUFF),A LD (TMP$BUF),A JP BUFINP05 ENDIF ; ; Backed up or rubout to the start of the line. Start a new line. ; BUFINP40:PUSH BC CALL END$LINE ;End this line. POP BC POP HL PUSH HL PUSH BC BUFINP41:LD A,B ;Have we reduced (b) to zero? OR A JP Z,BUFINP42 INC HL ;Nope, output next char. LD C,(HL) DEC B POP DE ;Compute characters we have displayed. PUSH DE LD A,D SUB B LD D,A PUSH BC PUSH HL LD A,(LOG$COL) ;Passed the prompt? CP D CALL C,CONOT$C ;Yes, output one more. POP HL POP BC JP BUFINP41 BUFINP42:PUSH HL LD A,(OUT$FLG) ;Did we disable output? OR A JP Z,BUFINP05 ;No, get next input char. LD HL,@COLUMN ;Move back to this column. SUB (HL) LD (OUT$FLG),A ;Save backspace count. BUFINP43:CALL BCKSPACE ;Backup the cursor (OUT$FLG) places. LD HL,OUT$FLG DEC (HL) ;Done? JP NZ,BUFINP43 IF BANKED CALL CURMOVE ;Yes, set screen straight. ENDIF JP BUFINP05 ; ; The cursor is pointing to character (a). Check that this will ; fit on the line (beep if not and ignore). Otherwise it will ; be moved into the input buffer. ; BUFINP44:PUSH AF ;Save character. LD A,B ;Get current char count. CP C ;Room for one more? JP C,BUFINP45 ;...yes. POP AF ;Nope, ignore this and ring the bell. PUSH BC ;Save regs of course. PUSH HL LD C,BEL ;Just beep. CALL ?CONOT JP BUFINP05 ;Get next character. ; ; Okay, there is room for one more. ; BUFINP45: IF BANKED LD A,(SAVE$CH) ;Get input character. CP BEL ;Delete cursor character? JP Z,BUFINP46 ;...yes. LD A,(TMP$BUF) ;Are we at the end of the line? OR A CALL NZ,LENGTH ;Nope, check to see if the full line fits. ENDIF BUFINP46:POP AF ;Okay, store (a) into the buffer now. INC HL LD (HL),A INC B ;And count it. BUFINP47:PUSH BC ;Preserve. PUSH HL LD C,A ;Save character here. IF BANKED CALL SET$COL ;Set cursor to current column. ENDIF CALL CONOT$C ;Echo (c) now. POP HL ;Restore. POP BC IF BANKED LD A,(SAVE$CH) ;Check input charaacter. CP BEL ;Delete character? JP Z,BUFINP26 ;...yes. CP DEL ;Rubout? JP Z,BUFINP48 ;...yes. CALL CURMOVE ;Neither, so move the cursor. ENDIF BUFINP48:LD A,(@MODE) ;Check console mode byte. AND 8 ;Is ^C disabled? JP NZ,BUFINP49 ;...yes. LD A,(HL) ;Nope, was it one? CP ETX LD A,B JP NZ,BUFINP49 CP 1 ;Yes, but are we at the start of the line? JP Z,BDOSABRT ;Yes, abort then. BUFINP49: IF BANKED CP C ;Reached end of the users input buffer? JP NC,BUFINP52 ;...nope, get more. PUSH BC ;Yes, save regs. PUSH HL CALL CHKWIDTH ;Beyond the edge of the screen? JP C,BUFINP05 ;...nope, just get the next char. LD A,(TMP$BUF) ;Yes, are we at the end of the line? OR A JP Z,BUFINP50 ;...yes. LD A,(SAVE$CH) ;Check input char. CP ETB ;Was ^C typed? JP Z,BUFINP51 ;...yes. CP ACK ;No, was ^F typed? JP Z,BUFINP51 ;...yes. BUFINP50:LD A,ENQ ;No, neither. Force physical (cr/lf) and JP BUFINP06 ;continue. BUFINP51:POP HL ;Restore. POP BC DEC B ;Don't count this character after all. EX DE,HL LD HL,(LPTR) ;Backup the pointer. DEC HL LD (LPTR),HL LD A,(DE) ;Restore cursor character. LD (HL),A EX DE,HL ;Now move the cursor itself back. DEC HL PUSH BC PUSH HL CALL MOVELEFT XOR A ;Clear the buffer and get another key. LD (CH$BUFF),A JP BUFINP05 BUFINP52:XOR A ;Clear this buffer and get one more key. LD (CH$BUFF),A ENDIF JP BUFINP03 ; ; A carriage return was typed. Give the line to the use now. ; BUFINP53: IF BANKED CALL MOVE$IT ;Move trailing portion of line into place. ENDIF POP HL ;Store character count into buffer. LD (HL),B IF BANKED PUSH BC CALL LINEFILL ;Move beginning of line portion now. POP BC LD C,255 ;Set a PUT function code. CALL SET$LINE ;Now move the line into the users buffer. ENDIF LD HL,0 ;Clear the pointer.. LD (@BUFPTR),HL LD C,CR ;echo the carriage return and return. JP CONOT ; ; Auxiliary input (function #3). Read a character ; into register (a). ; AUX$INP:CALL ?AUXI JP SAVESTAT ; ; Direct console i/o. Register (e) indicates the exact ; function desired. (e)=ff : input/status, (e)=fe : status, ; (e)=fd : input, (e)=char : output. ; DIRECT: LD A,C ;Check option (note (c)=(e) here). INC A ;(c)=ff? JP Z,DIR$COMB INC A ;(c)=fe? JP Z,DIR$STAT INC A ;(c)=fd? JP Z,DIR$INP JP ?CONOT ;Must be an output request, do it. DIR$STAT:CALL CONSTAT ;Get status of console. JP NZ,RETERROR ;Save any char if ready. JP SAVESTAT ;Check console. DIR$COMB:CALL CONSTAT OR A ;Just return if nothing ready. RET Z ;Otherwise, get the ready char. DIR$INP:CALL KEY$INP ;Get a char from the console. JP SAVESTAT ; ; Auxiliary input status request. Return (0) if nothing ; is available now. ; AUX$INS:CALL ?AUXIS JP SAVESTAT ; ; Auxiliary output status request. If not ready for ; output, return (0). ; AUX$OUS:CALL ?AUXOS JP SAVESTAT ; ; Print delimited character string on the console device. ; Data may be echoed to the printer also. ; PSTRING:EX DE,HL ;Point (bc) to string and print it. LD C,L LD B,H JP PRINT ; ; Check the console status. Return (0) if nothing is ; ready. In CTRL-C only mode, (01) is reeturned only ; if ^C was typed. Otherwise (0) is returned. ; CONST: LD A,(@MODE) ;Check console mode. RRA ;CTRL-C mode only? JP NC,CHECKIT ;...nope. Just check it. IF BANKED LD HL,@KEYLK ;Set flag saying we entered this routine. LD (HL),080H PUSH HL ENDIF LD HL,CNST$RET ;Setup reeturn address. PUSH HL LD A,(@@KEYBFR) ;Check key buffer. CP ETX ;CTRL-C ready? JP Z,WAIT04 CALL ?CONST ;Nope, check console (even if something is ready). OR A ;Anything ready? RET Z ;...nope. CALL ?CONIN ;Yes, get the char. CP ETX ;Was if CTRL-C? JP Z,WAIT02 LD (@@KEYBFR),A ;Nope, save it, clear (a) and return. XOR A RET CNST$RET: IF BANKED CALL SAVESTAT ;Save status, then reeturn. POP HL ;Clear our flag. LD (HL),0 RET ELSE JP SAVESTAT ENDIF ; ; Just check the keyboard, save the status and return. ; CHECKIT:CALL KBRDCHK ; ; Save (a) as the return status byte (when a single byte is ; all that is expected). ; SAVESTAT:LD (RET$STAT),A ; ; Entry point when a "do nothing" routine is required. At times ; this address is placed on the stack as one of the available ; return locations. ; IGNORE: RET ; ; Set end-of-file error code (1). ; EOFERR: LD A,1 JP SAVESTAT ; ; Get or set the console mode bytes. If (de)=ffff then ; this is a GET function, else it is a SET function. ; See Programmers Guide, page 139 for specific details. ; CON$MODE:LD A,D ;Is this a get (de=ffff)? AND E INC A LD HL,(@MODE) JP Z,STORE$HL ;...yes. Go do it. EX DE,HL ;...no. This must be a SET. LD (@MODE),HL ;Just save parameters without any checking. RET ; ; Get or set the output delimiter character. If (de)=ffff ; then this is a GET, otherwise (e) will set as the ; delimining character. ; CON$DLIM:LD HL,@DELIM ;Get storage location. LD A,D ;Is this a GET (de=ffff)? AND E INC A LD A,(HL) ;Prepare for a get. JP Z,SAVESTAT LD (HL),E ;...no. Set delimiter and return. RET ; ; Block output request (either to the console or the ; list device). ; BLOCK$IO:EX DE,HL ;Get address of string block into (de). LD E,(HL) INC HL LD D,(HL) INC HL LD C,(HL) ;Now get leength of string into (bc). INC HL LD B,(HL) EX DE,HL BLKIO01:LD A,B ;Done yet? OR C RET Z PUSH BC ;Nope, send one more character. PUSH HL LD C,(HL) ;Get character into (c). LD A,(@FX) ;Check for console output. CP 111 JP Z,BLKIO02 CALL ?LIST ;Nope, use the list device. JP BLKIO03 BLKIO02:CALL CONOUT ;Output (c) to the console. BLKIO03:POP HL ;Bump pointer and decrement count. INC HL POP BC DEC BC JP BLKIO01 ;Continue with rest of block. ; ; Parameter storage area for the non-disk part of ; the BDOS. ; OUT$FLG:DEFB 0 ;Output enable/disable flag. PHY$COL:DEFB 0 ;Column # for start of user input (after prompt). IF BANKED LOG$COL:DEFB 0 ;Logical beginning column (for editing). SAVE$CH:DEFB 0 ;Last typed character. SAV$LEN:DEFB 0 ;Saved length of "prvious" line. ELSE @@KEYBFR:DEFB 0 ;Single key buffer. LOG$COL:DEFB 0 ;Logical beginning column (for editing). ENDIF ; ; Safe storage location for input line. Used to save previous line ; for editing. ; IF BANKED SAV$BUF:DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 ; ; Current input line buffer. ; INP$BUF:DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 LINE$END:DEFB 0 ;End of line buffer. LINE$BEG:DEFB 0,0 ;Pointer to beginning of typed input line. LPTR: DEFB 0,0 ;Pointer into line. TMP$BUF:DEFB 0 ;Temp buffer. CH$BUFF:DEFB 0 ;Single character buffer (last typed char). CUR$COL:DEFB 0 ;Current column of cursor. PTRCOL: DEFB 0 ;Some kind of cursor column number. TMPSAVE:DEFB 0 ;End of line flag. ENDIF IF BANKED TERM EQU 0 ELSE TERM EQU '$' ENDIF CPMERROR:DEFB 'CP/M Error On ' ERRDISK:DEFB ' : ',TERM IO$ERROR:DEFB 'Disk I/O',TERM INVALID:DEFB 'Invalid Drive',TERM FILE$RO:DEFB 'Read/Only File',TERM DISK$RO:DEFB 'Read/Only Disk',TERM PSWD$ERR: IF BANKED DEFB 'Password Error',TERM ENDIF EXISTS: DEFB 'File Exists',TERM FILENAME:DEFB '? in Filename',TERM RET$STAT:DEFB 0 ;Return status storage. ECODE: DEFB 0 ;Error code byte. ; ; Disk error handling routines. The BDOS error mode ; dictates what type of message is displayed (if any). ; RO$DISK:LD C,2 ;Set disk is read-only error. JP SET$STAT RO$FILE:LD C,3 ;File is read-only error code. JP SET$STAT INV$DISK:LD C,4 ;Invalid drive specified error code. LD A,0FFH LD (ACTIVE),A SET$STAT:LD H,C ;Save (c) as error code. LD L,0FFH ;Mark this as an error. LD (RET$STAT),HL;Save it now. ERR$JMP:LD A,(CURDRIVE) ;Get disk where error occured. LD (@ERDSK),A LD A,(@ERMDE) ;Display error message? INC A CALL NZ,?ERJMP ;Yes. Go do it. LD A,(@FX) ;Check original function. CP 27 ;Return allocation vector (#27)? JP Z,SET$SPCL ;Yes, set special return code. CP 31 ;Get device parameter block address (#31)? JP Z,SET$SPCL ;Ditto. JP MAIN$RET ; ; Clear or set a flag telling the Resident BDOS that ; the FCB was changed (@@FLAG=0) and must be moved ; back into the users space. ; IF BANKED SETMOV: LD A,(MOVFLAG) ;Set flag from storage. LD (@@FLAG),A RET ; ; Clear the move flags (means FCB has been changed and must be moved ; back into users space). ; CLRMOV: XOR A ;Clear the move flag (means FCB changed). LD (MOVFLAG),A LD (@@FLAG),A RET ENDIF ; ; The following two routines are used for 24 bit math ; for the random record number arithmatic. The accumulator ; is the three registers (B,D,E) with (b) the most ; significant byte. Note that no overflow errors are ; every detected. ; ; Subtract (bde)=(bde)-(hl). ; SUB24: LD A,E ;Subtract low byte. SUB L LD E,A LD A,D ;Then middle byte. SBC A,H LD D,A RET NC DEC B ;Decrement high byte if necessary. RET ; ; Addition, (bde)=(bde)+(hl). ; ADD24: LD A,E ;Add in first 16 bits. ADD A,L LD E,A LD A,D ADC A,H LD D,A RET NC INC B ;Adjust high byte if necessary. RET ; ; Shift left the register set (A,H,L). Note the (a) is ; most significant byte. The regiters are shifted (c) bits. ; SHIFTL24:INC C SHFTL01:DEC C ;Done all bits? RET Z ADD HL,HL ;Nope, shift low two bytes one more bit left. ADC A,A ;Shift high byte next. JP SHFTL01 ; ; Increment the random record number byte(s) for ; sequential access. ; BUMP$REC:CALL GET$R0 ;Point to record number byte (R0). INC (HL) ;Bump first byte. RET NZ INC HL ;Take care of any carry. INC (HL) RET NZ INC HL ;Adjust high byte if need be. INC (HL) RET ; ; Extract the record bytes. Use temporary storage ; location. ; GET$REC:CALL SET$REGS ;Setup registers (de points to FCB). EX DE,HL ;Change direction. ; ; Move three bytes from (de) to (hl). ; MOVE3: LD C,3 ;Move 3 bytes from (de) to (hl). JP MOVE$C ; ; Setup registers to access the record number bytes. ; SET$REGS:CALL GET$R0 ;Point to record number bytes in FCB. LD DE,RAN$REC ;Point to temp storage spot. RET ; ; Set the record number bytes from storage. (de) points ; to the file FCB. ; SET$REC:CALL SET$REGS JP MOVE3 ; ; Compare (c) bytes with strings at (de) and (hl). ; Return on zero if they are the same. ; COMP$C: LD A,(DE) ;Get next byte. CP (HL) ;Same as other string? RET NZ ;...no, return with zero flag cleared. INC HL ;So far, so good. Bump pointers. INC DE DEC C ;More characters to compare? RET Z ;...no, all done. Return with zero flag set. JP COMP$C ; ; Move the block of (c) characters from (de) to (hl). Note that zero ; will move no characters at all. ; MOVE$C: INC C MOVEC01:DEC C ;More to move? RET Z ;...nope, all done then. LD A,(DE) ;...yes, move next one. LD (HL),A INC DE ;Adjust pointers and continue. INC HL JP MOVEC01 ; ; Select disk from (d). Set carry flag if okay. ; SELECT$D:LD C,D ;Setect this disk (try at least). CALL ?SLDSK LD A,H ;Unsuccessful? OR L RET Z ;....Bad select. Return with carry cleared. LD E,(HL) ;Okay, get address of translate table. INC HL LD D,(HL) ;..into (de). INC HL ;Point to scratch area (9 bytes) and save pointers. LD (SCRATCH0),HL INC HL INC HL LD (SCRATCH2),HL INC HL INC HL LD (SCRATCH4),HL INC HL INC HL INC HL LD (SCRATCH7),HL INC HL LD (SCRATCH8),HL INC HL ;Get address of parameter block. INC HL EX DE,HL ;..into (de). LD (TRANSLAT),HL;Save address of translate table. LD HL,DPB ;Move remainder of parameter header (XDPH+12 - XDPH+24). LD C,13 CALL MOVE$C LD HL,(DPB) ;Move entire disk parameter block into our space. EX DE,HL LD HL,SPT LD C,17 CALL MOVE$C LD HL,(DSM) ;Get total blocks of space on ddisk. LD A,H ;Check high byte to sed if this is > 256. LD HL,BIG$DISK LD (HL),0FFH ;Assume a small disk. OR A ;Correct? JP Z,SLDSKD1 LD (HL),0 ;...nope, say it is a big disk. SLDSKD1:SCF ;Set the carry flag (good select). RET ; ; Initialize our parameters concerning the specified disk. ; DSK$INIT:CALL ?HOME ;Home the head. XOR A ;Clear the scratch areas. LD HL,(SCRATCH2) LD (HL),A INC HL LD (HL),A LD HL,(SCRATCH4) LD (HL),A INC HL LD (HL),A INC HL LD (HL),A RET ; ; Phisical disk read/write routines with error processing. ; ; Disk read routine. ; DSKREAD:LD A,1 ;Set i/o direction flag. LD (IODIRECT),A CALL ?READ JP DSKIOCHK ; DSKWRITE:XOR A ;Set i/o direction to write. LD (IODIRECT),A CALL ?WRITE ; ; General disk I/O error check routine. Enter with the BIOS ; return code in (a). ; DSKIOCHK:OR A ;Good i/o? RET Z ;Yes, just return (a=0). LD C,A CALL CHECKERR ;Check the error return code. LD A,C ;Error types > 2 are set to 1 here. CP 3 JP C,SET$STAT LD C,1 ;Set type to 1 and return. JP SET$STAT ; ; Check error code and process a "meadia changed" status. ; CHECKERR:INC A ;Was status media changed (ff)? RET NZ ;...nope. IF BANKED CALL DIRCHECK ;Check for read-only disk? RET Z ;...not needed (permanent). ENDIF LD HL,(LOGINVEC);Is device loged in? CALL DRV$TEST LD C,1 RET Z ;...no, say error type 1. CALL CHKDIR1 POP HL LD A,(@FX) ;Is this a "flush" request? CP 48 RET Z ;...yes, return code now. LD HL,CURDRIVE ;Check disks. LD A,(DRIVE) CP (HL) JP NZ,CHKERR1 CALL CHNG$OK ;Check for special file i/o error (only returns if not). LD A,(IODIRECT) ;Are we writing? OR A RET NZ LD C,2 ;...yes, say disk is read-only. JP SET$STAT ; ; Clear any changed flag. ; CHKERR1:XOR A LD (@MEDCHG),A RET ; ; Check disk to see if device is permanently mounted ; and to not check directory entries (see sg 41). ; Set zero flag if this is true. ; IF BANKED DIRCHECK:LD HL,(CKS) ;Set zero flag if this = 8000 hex. LD A,080H ;Check high byte for (80 hex). CP H RET NZ XOR A ;Check low byte for zero. CP L RET ENDIF ; ; Convert the directory entry number in @ENTRY into a block ; number for access. ; DIRBLOCK:LD HL,(@ENTRY) ;Get desired entry number. LD C,2 ;Convert into relative sector #. CALL SHIFTR LD (DIRSECT),HL ;Save this and convert to block #. LD B,0 EX DE,HL ; ; Store 24 bit block number from BDE regs. ; LOAD$BLK:LD HL,CURBLOCK ;Store block number (24 bit) from (BDE). LD (HL),E INC HL LD (HL),D INC HL LD (HL),B RET ; ; Set the track and sector to match the block number ; we want (stored in SCRATCH4). On exit, the track and ; sector will have been selected. ; TRK$SEC:LD HL,(SCRATCH2);Get current track number into (bc). LD C,(HL) INC HL LD B,(HL) PUSH BC LD HL,(SCRATCH4);Get destination block number. LD E,(HL) INC HL LD D,(HL) INC HL LD B,(HL) LD HL,(CURBLOCK);Get current block number into (chl). LD A,(CURBLOCK+2) LD C,A ; ; Move to a location before the desired block (lower track). ; TRKSEC01:LD A,L ;Is (bde) > (ahl) ? SUB E LD A,H SBC A,D LD A,C SBC A,B PUSH HL JP NC,TRKSEC02 ;...nope. LD HL,(SPT) ;...yes, decrement (bde) by sectors/track. CALL SUB24 POP HL EX (SP),HL ;Decrement track number (was in bc). DEC HL EX (SP),HL JP TRKSEC01 ; ; Now move to a location just beyond the desired block. ; TRKSEC02:LD HL,(SPT) ;Bump by one track. CALL ADD24 POP HL LD A,L ;Is (bde) < (chl) ? SUB E LD A,H SBC A,D LD A,C SBC A,B JP C,TRKSEC03 ;...yes. EX (SP),HL ;...nope, increment track number and move to next track. INC HL EX (SP),HL PUSH HL JP TRKSEC02 TRKSEC03:EX (SP),HL ;Move to start of previous track. PUSH HL LD HL,(SPT) CALL SUB24 POP HL PUSH DE PUSH BC PUSH HL EX DE,HL LD HL,(OFF) ;Add in system track offset value. ADD HL,DE LD B,H LD C,L LD (CURTRACK),HL;Save here and select this track (bc). CALL ?STTRK POP DE ;Save track number (less offset) in DPB. LD HL,(SCRATCH2) LD (HL),E INC HL LD (HL),D POP BC POP DE LD HL,(SCRATCH4);Now save corresponding block number. LD (HL),E INC HL LD (HL),D INC HL LD (HL),B POP BC LD A,C ;Compute relative block number (within track). SUB E LD L,A LD A,B SBC A,D LD H,A CALL PHY$SEC ;Convert to physical sectors. LD B,H LD C,L LD HL,(TRANSLAT);Do sector translation. EX DE,HL CALL ?SCTRN LD C,L ;Save sector and select it. LD B,H LD (CURSECTR),HL CALL ?STSEC LD HL,(@@BUFAD) ;Set dma address. LD C,L LD B,H JP ?STDMA PHY$SEC:LD A,(PSH) ;Get physical record shift factor. LD C,A JP SHIFTR ;Shift and return. ; ; Get block number from extent and record number. ; GETBLOCK:LD HL,BSH ;Get record shift. LD C,(HL) LD A,(SAVNREC) ;Get record number and shift it right (c) places. GETBLK1:OR A RRA DEC C JP NZ,GETBLK1 LD B,A ;Save result in (b). LD A,8 ;Convert extent into blocks too. SUB (HL) LD C,A ;(c)=8-BSH LD A,(SAVEXT) ;Get extent (masked) and shift left (c) places. GETBLK2:DEC C JP Z,GETBLK3 OR A RLA JP GETBLK2 GETBLK3:ADD A,B ;Now add in converted record number to yield the block #. RET GET$D0: LD HL,(@VINFO) LD DE,16 ADD HL,DE RET ; ; Extract block number (bc) from fcb. These may be eeither ; 8 or 16 bit block numbers (bc may range from 0-7 or 0-15). ; EXTBLOCK:CALL GET$D0 ;Point to start of block storage area in fcb. ADD HL,BC ;Add offset (assumes 8 bit numbers). LD A,(BIG$DISK) ;Are the block number 8 bits long? OR A JP Z,EXTBLK1 ;...nope. LD L,(HL) ;Yes, get block number into (hl). LD H,B ;Note that (b)=0. RET EXTBLK1:ADD HL,BC ;Add offset again (16 bit numbers). LD A,(HL) ;Extrack block number and return in (hl). INC HL LD H,(HL) LD L,A RET ; ; Compute block number from extent and record and ; extract it into (hl). Set the zero flag if unused. ; COMBLK: CALL GETBLOCK ;Get relative block number. LD (RELBLOCK),A ;And save for later. LD C,A ;Now extract the block number from the fcb. LD B,0 CALL EXTBLOCK LD (CURBLOCK),HL;And save it too. LD A,L ;Test for zero and return. OR H RET ; ; Adjust physical block number (CURBLOCK) and convert ; it to a logical sector (LOGSECT) that starts the ; referenced block. The desired relative sector is ; then added to yield the final sector. ; Note that sector translation still must be done. ; LOGICAL:LD A,(BSH) ;Get block shift factor to convert block to sector. LD C,A LD HL,(CURBLOCK);Get block and shift it left (c) places (overflow into (a)). XOR A CALL SHIFTL24 LD (CURBLOCK),HL;Save result (3 bytes). LD (CURBLOCK+2),A LD (LOGSECT),HL ;Also save logical sector. LD A,(BLM) ;Get block mask byte to get the relative LD C,A ;sector within the block. LD A,(SAVNREC) AND C LD B,A LD (RELSEC),A ;Save relative sector (within data block on disk). LD HL,CURBLOCK ;Now add this to the start of the block OR (HL) ;sector. LD (HL),A RET ; ; Clear the bits of the fcb coresponding to bit 7 ; of f8,t1,t2,t3. The present setting will be ; returned in (d). Bit 7 for t3, bit 4 for f8. ; CLR$BITS:LD HL,(@VINFO) ;Point to f8 byte in fcb. LD DE,8 ADD HL,DE LD C,4 ;Clear bit 7 of next 4 bytes and save in (a). CLRBT01:LD A,(HL) ;Get next byte. ADD A,A ;Shift bit 7 into carry flag. PUSH AF LD A,D ;Rotate carry flag into (d). RRA LD D,A POP AF RRCA ;Restore original byte less bit 7. LD (HL),A DEC HL ;Move to previous byte. DEC C JP NZ,CLRBT01 LD A,D ;Move result into (a) and return. RET ; ; Extract the s1 byte from the fcb and point (hl) there. ; GET$S1: CALL GET$EX ;Point to extent byte first. INC HL ;Bump to position of s1. LD A,(HL) ;Now get this byte. RET ; ; Point to start of random record number in fcb. ; GET$R0: LD HL,(@VINFO) LD DE,33 ADD HL,DE RET ; ; Point to extent byte in fcb. ; GET$EX: LD HL,(@VINFO) LD DE,12 ADD HL,DE RET ; ; Point to record count byte within fcb. ; GET$RCNT:LD HL,(@VINFO) LD DE,15 ADD HL,DE RET ; ; Point (hl) to current record number and (de) to ; record count byte, ; SETHLDE:CALL GET$RCNT EX DE,HL LD HL,17 ADD HL,DE RET ; ; Save current from FCB in our own space (makes for quicer ; access). ; STRDATA:CALL SETHLDE LD A,(HL) ;Get current record number and store. LD (SAVNREC),A EX DE,HL LD A,(HL) ;Get record count from fcb. OR A ;Zero? JP NZ,STRDT1 CALL COMPEXT LD C,A CALL OPNIT3 LD A,(HL) STRDT1: CP 129 ;Is record count > 127? JP C,STRDT2 LD A,128 ;Yes, stop it at 128. STRDT2: LD (SAVNXT),A ;Save record count. CALL GET$EX ;Point ot extent byte. LD A,(EXM) ;Get extent mask from DPB. AND (HL) ;Mask extent byte. LD (SAVEXT),A ;Save it now. RET ; ; Increment the current record number for sequential ; file access. The extent byte is restored to the ; saved value unless it is greater than 128 (in which ; case it is left as is). ; SETNREC:CALL SETHLDE LD A,(SAVNREC) ;Store record number into fcb. LD (HL),A LD A,(@FX) ;Are we doing sequential i/o? CP 22 JP NC,STNREC1 INC (HL) ;Yes, bump to next record. STNREC1:EX DE,HL ;Get current record count. LD A,(HL) CP 128 ;Greater than 128? RET NC LD A,(SAVNXT) ;Nope, set from our save area. LD (HL),A RET ; ; Clear the extent byte and the S2 byte. ; CLREXT: CALL GET$EX ;Save extent (0) in fcb. LD (HL),D INC HL ;Also stuff in s2 byte. INC HL LD (HL),D RET ; ; Fill memory at (hl) with bytes from (b). Move (c) ; characters (note 0=256). Point to next byte location. ; FILL$C: LD (HL),B INC HL DEC C RET Z JP FILL$C ; ; Shift (hl) right (c) bits. ; SHIFTR: INC C SHFTR: DEC C RET Z LD A,H OR A RRA LD H,A LD A,L RRA LD L,A JP SHFTR ; ; Compute an 8 bit checksum byte for the directory buffer. ; An 8 bit sum is computed for each extent and these ; are exclusive ored to form a unique check byte. ; CHECKSUM:LD HL,(DIRBUF) ;Point to the 128 byte directory buffer. LD BC,4 ;Set number of extents to process. CHKSUM1:LD D,32 XOR A ;Compute sum of bytes in this extent. CHKSUM2:ADD A,(HL) INC HL DEC D JP NZ,CHKSUM2 XOR B ;Exclusive or with previous sums and save. LD B,A DEC C ;If completed, return result in (a) and (b). JP NZ,CHKSUM1 RET ; ; Check for special disk accesses. Set media changed ; error if necessary (and don't return). ; CHKSPCL:CALL GET$S1 ;Check to see if the S1 byte is different. LD HL,(SCRATCH8) CP (HL) CALL NZ,CHKBUF ;...yes, is this allowed? ; ; Check for special user 0 access. ; SPLUSER:LD A,(HOLDF8) ;Is this a special user access? OR A RET Z LD HL,(@VINFO) ;Yes, set the FCB for this. XOR A LD (HL),A RET ; ; Check location of data buffer. Must be below BDOS (why?). ; CHKBUF: LD HL,(@@BUFFR) ;Get address of buffer. EX DE,HL LD HL,(@MXTPA) ;Is it below the BDOS? CALL SUB$HL JP NC,CHKBUF1 ;...nope, illegal. LD HL,(@RELOG) ;Okay, see if this drive has had time/date stamps CALL DRV$TEST ;written and then been re-loged in (illegal). RET Z ;..nope, okay (for now). CHKBUF1:POP HL ;Waste return addresses. POP HL ; ; Set error for an illegal media change. ; CHG$ERR:LD A,10 ;Media changed error. JP SAVESTAT ; ; Shift (hl) left (c) places. ; SHIFTL: INC C SHFTL1: DEC C ;Done yet? RET Z ADD HL,HL ;No, shift one more place. JP SHFTL1 ; ; Set bit in login vector for drive specified in ; address (ACTIVE). ; LOGINDRV:LD DE,LOGINVEC ;Get address of login vector. ; ; Set the bit in vector given by (de) corresponding ; to drive in (ACTIVE). ; SETDRIVE:LD A,(ACTIVE) ;Get drive to access. ; ; Set bit corresponding to (a) in vector at (de). ; BITSET: LD C,A ;Set shift count. LD HL,1 CALL SHIFTL ;Shift bit mask. LD A,(DE) ;Now and this with the present vector. OR L LD (DE),A INC DE LD A,(DE) OR H LD (DE),A RET ; ; Test drive at (ACTIVE) for read-only status. ; RO$TEST:LD HL,(RO$VECT) ; ; Drive test routine. Enter with (hl) pointing to a ; 16 bit vector and the drive specified in (28a9) will ; isolated. Return with the corresponding bit as bit #0 ; in (l) and flags set on this. ; DRV$TEST:LD A,(ACTIVE) ;Get drive to interogate into (c). LD C,A CALL SHIFTR ;Shift the vector. LD A,L ;Test bit #0 of (l). AND 1 RET ; ; Check status of disk drive. Return if okay to ; disk and file. Otherwise set disk (or file) as ; read only (write protected). ; CHKSTAT:CALL FCB2HL ;Point to fcb in directory. FILEWPRT:CALL CHKFILE ;Is file write protected? RET NC ;Nope, just return. JP RO$FILE ;Yes, set error status (bit 7 of byte t1) and return. ; ; Check file for a read only status (bit 7 of byte t1). ; CHKFILE:LD DE,9 ;Offset for t1. ADD HL,DE LD A,(HL) RLA RET CHKWPRT:CALL RO$TEST RET Z JP RO$DISK FCB2HL: LD HL,(DIRBUF) LD A,(REL$ADDR) ; ; Add (a) to (hl), result in (hl). ; ADDA2HL:ADD A,L LD L,A RET NC INC H RET ; ; Extract the S2 byte from the fcb. Return with it in (a) ; and (hl) pointing to it. ; GETS2: LD HL,(@VINFO) LD DE,14 ADD HL,DE LD A,(HL) RET ; ; Clear the S2 byte from the fcb. ; Bit 7 means FCB changed. ; Bit 6 means file changed. ; CLEARS2:CALL GETS2 ;Point to the byte LD (HL),0 ;and clear it. RET ; ; Clear theupper threen bits in the extent byte. ; CLEAR567:CALL GET$EX ;Get extent byte and strip bits 5,6,7. LD A,(HL) AND 01FH LD (HL),A RET ; ; Set bit 7 of the S2 byte in the FCB to indicate that it has been ; changed and needs to be written back to the disk when the file ; is closed. ; SETCHNG:CALL GETS2 ;Get the S2 byte. OR 080H ;Now set bit 7 and store. LD (HL),A RET ; ; Compare file position at (@ENTRY) with limit in ; (SCRATCH0). Set the carry flag if more files exist ; in the directory. ; MOREFLS:LD HL,(@ENTRY) ;We are up to this point. EX DE,HL LD HL,(SCRATCH0);And the limit is here. LD A,E ;Compare them, set carry if more remain. SUB (HL) INC HL LD A,D SBC A,(HL) RET ; ; Routine to keep the directory entry limit (SCRATCH0) ; up to date. If we are presently beyond this limit, ; we reset the limit. ; CHKNMBR:CALL MOREFLS ;Check if more remain. RET C INC DE ;Nope, stuff new limit value. LD (HL),D DEC HL LD (HL),E RET ; ; Subtrace (hl) from (de). Return result in (hl). Set carry. ; SUB$HL: LD A,E ;Subtract low byte. SUB L LD L,A LD A,D ;Now handle upper byte. SBC A,H LD H,A RET ; ; Set directory checksum byte value for the current ; sector in the buffer. ; DIRSET: LD C,0FEH ;Set flag for update. ; ; Routine to check or set the checksum byte for ; the current directory buffer. If (c)=ff, this is ; set and flag if changed operation, or (c)=fe this ; is just a set operation, (c)=anything else then this ; will check the present buffer and take appropriate ; action if a change is detected. ; CHKDIR: LD HL,(DIRSECT) ;Get relative directory sector. EX DE,HL LD HL,(CKS) ;Get size of directory to check. LD A,H AND 07FH ;Strip bit 7 (see SG 41). LD H,A CALL SUB$HL ;Do we have to check this sector? RET NC ;...nope, we are done. PUSH BC CALL CHECKSUM ;Okay, compute new checksum byte. LD HL,(CSV) ;Point to start of checksum table. EX DE,HL LD HL,(DIRSECT) ;Adjust for this directory sector. ADD HL,DE ;Point to present value. POP BC INC C ;Is this a test and flag operation? JP Z,CHKDIR2 ;...yes. INC C ;How about a set operation? JP Z,CHKDIR3 ;...yes. CP (HL) ;Just a test. Is the value the same? RET Z ;...yes, all done. CALL RO$TEST ;Nope, but is disk already read-only? RET NZ ;...yes, we can do no more. CHKDIR1:CALL PURGE$EM ;Nope, clear all associated BCB's. LD A,0FFH ;Clear drive flags too. LD (@MEDCHG),A LD (@HSHCK),A ;Clear hash access byte. CALL CKSTMP CALL LOGINDRV ;Be sure drive is loged-in. JP LOGOUT ;Now just log out and return. CHKDIR2:CP (HL) ;Same checksum value? LD (HL),A ;Always save newest value. RET Z ;..yes, okay. LD HL,(SCRATCH8);Nope, set bit 0 here to say a change was made. LD A,1 OR (HL) LD (HL),A RET CHKDIR3:LD (HL),A ;Just set the new value and return. RET ; ; Write protect the present drive. This will set ; the will set the bit for this drive in the read- ; only vector. ; WRTPRTCT:LD A,(DRIVE) ;Get the drive. LD DE,RO$VECT ;Point to vector table. CALL BITSET ;Okay, set this bit. LD HL,(DRM) ;Get total directory entries for this drive. INC HL ;Note that it was one less. EX DE,HL LD HL,(SCRATCH0);Now store it here. LD (HL),E INC HL LD (HL),D RET ; ; Check to see if the current drive has been time/date stamped. ; CKSTMP: LD HL,(@STAMP) ;Point to vector. CALL DRV$TEST ;Check for the current drive. RET Z ;...Not stamped. LD DE,@RELOG ;Yes, it was, set the re-log vector. JP SETDRIVE CHKTYPE:LD A,(CKS+1) ;Is drive permemantly mounted? AND 080H RET NZ ;...yes, check no further. LD HL,NXT$IO ;nope, so check for functions that invalidate ; ;a "search next" function. ; ; Check the function code against a table at (hl). ; Set the zero flag if is present in the table. ; CHKCODE:LD A,(@FX) ;Get function code. LD B,A CHKCD01:LD A,(HL) ;Get next byte from table. CP B ;Same as we are looking for? RET Z ;...yes, return with zero flag set. INC HL ;Move to next table entry. OR A ;End of table found? JP NZ,CHKCD01 INC A ;Yes, clear zero flag and return. RET ; ; Check media flag byte in DPH. Return with flags ; set on this. ; CHK$MF: LD HL,(SCRATCH8);Get address of media flag in DPH. INC HL LD A,(HL) ;Test for zero, non-zero. OR A RET ; ; A disk change was detected, is this okay? Return if yes. ; otherwise an error return will be executed. ; CHNG$OK:LD HL,MAIN$RET ;Set error return just in case. PUSH HL LD HL,RDWT$IO ;Check for a file i/o function. CALL CHKCODE JP Z,CHG$ERR ;Yes, can't change disks. LD HL,DIR$IO ;Directory close or search next? CALL CHKCODE JP Z,RETERROR ;Fatal error for this. POP HL ;All okay, use normal return address. RET RE$START:LD HL,@MEDCHG ;Media changed? LD A,(HL) OR A RET Z ;Nope, just return. LD (HL),0 ; ; Re-select drive and start directory search ; from the beginning. ; START: CALL SETDSK LD HL,0 ;Reset file position. LD (@ENTRY),HL XOR A LD (REL$ADDR),A ;And relative position. RET ; ; Set the S1 byte in the FCB from our copy. ; SETS1: LD HL,(SCRATCH8) LD C,(HL) ;Get our copy of this. CALL GET$S1 LD (HL),C ;Now store it in the FCB. RET ; ; Check current data BCB and clear ones with matching ; drive and record numbers (first 4 bytes). ; BCBCHK: LD HL,(DTABCB) LD C,4 JP CHK$BCB ; ; Clear all data BCB's associated with the current ; drive. ; PURGE$EM:LD HL,(DTABCB) JP CHK$BCB1 ; ; Check the directory BCB chain for selected drive. ; If found, clear the drive byte (frees this BCB). ; CHK$DBCB:LD HL,(DIRBCB) ;Search directory BCB's. ; ; Search the BCB's pointed to by (hl) and clear the ; ones associated with the selected drive. ; CHK$BCB1:LD C,1 ;Set compare limit to 1 byte. ; ; Search all BCB's pointed to by (hl) comparing ; with the one at (28aa). Compare the first (c) bytes. ; Free all that match (set drive code to ff). ; CHK$BCB:LD A,L ;Are any active? AND H ;(checking BCB header). INC A RET Z ;...nope, just return. IF BANKED LD E,(HL) ;Okay, get address of first one. INC HL LD D,(HL) EX DE,HL ENDIF CHKBCB01:PUSH HL IF BANKED PUSH BC ENDIF LD DE,CURDRIVE ;Is this the same one? CALL COMP$C IF BANKED POP BC ENDIF POP HL IF BANKED JP NZ,CHKBCB02 ELSE RET NZ ENDIF LD (HL),0FFH ;Yes, clear the drive byte. IF BANKED CHKBCB02:LD DE,13 ;Move on to the next one in chain. ADD HL,DE LD E,(HL) INC HL LD D,(HL) EX DE,HL LD A,L ;Is there more? OR H RET Z ;...no, we are done. JP CHKBCB01 ELSE RET ENDIF ; ; Extract the buffer address into (hl) and the bank ; into (L28FAH) from the BCB POINTED TO BY (HL). ; GETBUFF:PUSH DE LD DE,10 ;Point to buffer address. ADD HL,DE LD E,(HL) ;Get address into (de). INC HL LD D,(HL) IF BANKED INC HL LD A,(HL) ;Now get memory bank for it. LD (BCB$BNK),A ;And save. ENDIF EX DE,HL ;Move address into (hl) and return. POP DE RET ; ; Read the next directory sector into our buffer. ; DIRREAD:CALL DIRBLOCK ;Get block # for directory entry. LD A,3 JP DO$IO ; ; Write out the current directory buffer. ; DIRWRITE:CALL CHKWPRT ;Be sure we are not write protected. CALL DIRSET ;Set parameters. LD A,5 ; ; Directory I/O routine. Enter with function number in (a). ; Read = 3, write = 5. ; DO$IO: LD HL,0 LD (BUFBLK),HL LD HL,(DIRBCB) IF BANKED CP 5 JP NZ,DO$IO1 LD HL,(BCBADR) ;Get address of BCB. ENDIF DO$IO1: CALL BCBIO DO$IO2: LD HL,(@CRDMA) ;Reset users DMA address. JP DO$IO4 DO$IO3: CALL GETBUFF DO$IO4: LD (@@BUFAD),HL RET ; ; Move directory buffer into users DMA space. ; MOVEDIR:LD HL,(DIRBUF) ;Get address of our buffer. EX DE,HL LD HL,(@@USRDMA);Get users DMA address. LD BC,128 CALL ?MOV ;Move one full sector. LD HL,RET$STAT ;Check current error status. LD A,(HL) INC A ;Hardware error? RET Z ;Yes, return as is. LD A,(@ENTRY) ;Nope, then return the relative location AND 3 ;within this sector for the specified file LD (HL),A ;entry (0-3). RET ; ; Mark the current FCB as invalid. This will set bit 7 ; of the S2 byte and set the first block number to ffff. ; MARKFCB:CALL SETCHNG ;Set bit 7 of S2 in FCB. INC HL INC HL LD A,0FFH ;Now set the first block number to ffff. LD (HL),A INC HL LD (HL),A RET ; ; Check FCB fo being valid. Set zero flag if not. ; CHECKFCB:CALL GET$D0 ;Point to first data block. JP CKPOS ;Now check to see if it is valid. ; ; Check the current FCB and set an error status ; if is not still valid. ; CHKVALID:CALL CHECKFCB RET NZ ;Return, it is okay. POP HL ;Invalid, waste normal return and set error status. LD A,9 JP SAVESTAT ; ; Check the present file position. Set the zero flag ; if it equat to ffff. ; CKFILPOS:LD HL,@ENTRY ;Point to file position. ; ; Check the location pointed to by (hl). Set the ; zero flag if it points to ffff. ; CKPOS: LD A,(HL) ;First, are both bytes the same? INC HL CP (HL) RET NZ INC A ;Yes, set the zero flag if they are ff. RET ; ; Set file position to ffff. ; RSTFILPS:LD HL,0FFFFH LD (@ENTRY),HL RET ; ; Move on to the next file position and check for ; a directory change. Set error on media change and ; reset directory pointers. ; NXTNTRY:CALL NXTENTRY JP CHANGED? ; ; Move on to the next file position within the ; directory. If no more exist, set position flag ; to ffff. Enter with (c) containing the access ; code (see routine CHECKDIR for values). ; NXTENTRY:LD HL,(DRM) ;Get max directory entries -1. EX DE,HL LD HL,(@ENTRY) ;Bump to next entry. INC HL LD (@ENTRY),HL CALL SUB$HL ;Beyond directory limit? JP C,RSTFILPS ;...yes, reset and return. LD A,(@ENTRY) ;Get relative point within sector (32 bytes/entry). AND 3 ;Look within this sector only. LD B,5 ;Times 32 (5 ADDs would be better here). NXENT1: ADD A,A DEC B JP NZ,NXENT1 LD (REL$ADDR),A ;Save relative byte of entry (0-96). OR A ;Start of sector buffer? RET NZ ;...nope, just return. RDNXT: PUSH BC ;Save (c). CALL DIRREAD ;Read next directory sector. POP BC LD A,(@MEDCHG) ;Media changed? OR A RET NZ ;Yes, don't check any farther. JP CHKDIR ;Checksum next sector (note code is in (c)). ; ; Read next dirctory sector and check for change. ; Reset pointers if it has. ; DIRRDNXT:CALL RDNXT ;Read next sector. ; ; See if the directory has changed. If it has, then ; reset pointers and start from the beginning. ; Some functions do not allow a change however. ; CHANGED?:LD A,(@MEDCHG) ;Check changed flag. OR A RET Z ;Nope, just return. CALL CHNG$OK ;Yes, is this allowed? CALL RE$START ;Must be ok, reset pointers and JP DIRREAD ;read the first sector. ; ; Routine to get a bit from the storage allocation ; map for block number (bc). It is returned in (a), ; bit 0. Also (d) will be set to the original bit ; position and (hl) will point to the byte. ; CKBITMAP:LD A,C ;Determine bit of interest. AND 7 INC A LD E,A ;Place in (d) and (e). LD D,A LD H,B ;Convert block number to byte number LD L,C ;(8 bits per byte). LD C,3 CALL SHIFTR ;Compute (hl)=(hl)/8. LD B,H LD C,L ;Get offset into (bc). LD HL,(ALV) ;Allocation table starts here. ADD HL,BC ;Add offset and get bytefrom table. LD A,(HL) CKBMAP1:RLCA ;Now move the desired bit into bit 0. DEC E JP NZ,CKBMAP1 RET ; ; Set or clear a bit in the disk allocation storage ; map for block (bc). Enter with (e)=0 for a clear ; or (e)=1 for a set operation. ; STBITMAP:PUSH DE ;Save (e). CALL CKBITMAP ;Get byte of interest. AND 0FEH ;Clear the bit for this block. POP BC OR C ;Add in users bit. STBMAP1:RRCA ;Restore original position. DEC D JP NZ,STBMAP1 LD (HL),A ;Now stuff back into table. RET ; ; Allocation vector save/restore. This will move the ; allocation vector from the first half of the space to ; the second half or visa-versa. If the zero flag is ; set first half is moved to the second half. ; This is only used with double bit allocation vectors ; (see sg 38). ; MOVE$ALV: IF NOT BANKED LD A,(@BFLGS) ;Are double allocation vectors being used? RLCA RLCA RET C ;...nope. ENDIF PUSH AF CALL SETLNGTH ;Get max blocks/8+1. LD B,H LD C,L ;...into (bc). LD HL,(ALV) ;Point to first vector. LD D,H LD E,L ADD HL,BC ;Now point to sectod vector. POP AF ;Which way? JP Z,?MOV ;...from first to second. EX DE,HL ;...nope, from second to first. JP ?MOV ; ; Set or clear the file space in the disk allocation map. ; This assumes a double byte allocation vector. ; SETBOTH:PUSH BC ;Save set/clear code (c). CALL FILESET ;Set or clear space for this file. POP BC SETSCND: IF NOT BANKED LD A,(@BFLGS) ;Double allocation vectors? AND 40H RET NZ ;...nope. ENDIF PUSH BC CALL SETLNGTH ;Point to start of duplicate field. EX DE,HL LD HL,(ALV) POP BC PUSH HL ADD HL,DE LD (ALV),HL CALL FILESET ;Now set or clear this space. POP HL ;Restore allocation vector and return. LD (ALV),HL RET ; ; Routine to set or clear the allocated space for ; the specified file. Enter with (c)=0 to clear the ; space or (c)=1 to set it. ; FILESET:CALL FCB2HL ;Get address of file FCB. LD DE,16 ;Point to data storage. ADD HL,DE PUSH BC ;Save set/clear flag (c). LD C,17 ;Set max block count +1. FILSET1:POP DE DEC C ;All done? RET Z PUSH DE ;...yes. LD A,(BIG$DISK) ;Are block numbers 16 bit? OR A JP Z,FILSET2 ;...yes. PUSH BC PUSH HL LD C,(HL) ;Nope, get 8 bit block number into (bc). LD B,0 JP FILSET3 FILSET2:DEC C ;16 bit numbers, count extra byte. PUSH BC LD C,(HL) ;Extract block number into (bc). INC HL LD B,(HL) PUSH HL FILSET3:LD A,C ;Is this block used? OR B JP Z,FILSET4 ;...nope, skip this. LD HL,(DSM) ;Is this block within data space? LD A,L SUB C LD A,H SBC A,B CALL NC,STBITMAP ;Yes, set/clear this bit. FILSET4:POP HL ;Move on to next block. INC HL POP BC JP FILSET1 ; ; Set (hl) to the length of the disk allocation ; table for this drive. ; SETLNGTH:LD HL,(DSM) ;Get drive capacity (in blocks) -1. LD C,3 ;Divide by 8. CALL SHIFTR INC HL ;Plus one and return. RET ; ; Re-log the current drive (updates the bit map if necessary). ; RELOG: CALL CHK$MF ;Point to media flag byte in DPH. LD (HL),0 ;And set it to zero. CALL PURGE$EM ;Purge all data blocks. CALL CHK$DBCB ;Clear all directory blocks too. IF BANKED CALL DIRCHECK ;Is this a permenant disk. JP NZ,BITMAP ;No (removable), re-set the bit map. LD HL,(SCRATCH8);Has this ever been loged-in? CP (HL) LD (HL),2 ;Always becomes "yes". JP Z,BITMAP ;Nope, do it JP MOVE$ALV ENDIF ; ; Initialize the bit map for this drive. If hashing ; is enabled, then the tables are setup. ; BITMAP: CALL SETLNGTH ;Get length of table to (hl). LD B,H LD C,L LD HL,(ALV) ;Table starts here. BITMAP1:LD (HL),0 ;Clear table first. INC HL DEC BC LD A,B OR C JP NZ,BITMAP1 LD HL,(SCRATCH7);Clear this. LD (HL),A LD HL,(AL0) ;Get initial directory space. EX DE,HL LD HL,(ALV) ;Put this in table. LD (HL),E INC HL LD (HL),D CALL DSK$INIT ;Initialize the drive. LD HL,(SCRATCH0);Force next directory access to LD (HL),4 ;a sector in. INC HL LD (HL),0 CALL RSTFILPS ;Clear initial file position. LD HL,(HASH) ;Save hash table address. LD (LOGSECT),HL BITMAP2:LD C,0FFH ;Get to next file position and update map. CALL NXTNTRY CALL CKFILPOS ;More files present? JP Z,MOVE$ALV ;Nope, set allocation vector. CALL FCB2HL ;Okay, point to next directory entry. EX DE,HL LD HL,(LOGSECT) ;Is hashing enabled? LD A,H AND L INC A EX DE,HL CALL NZ,SETHASH ;Yes, set table for this entry. LD A,33 ;Is this a date/time stamp? CP (HL) JP Z,BITMAP2 ;Yes, there is no allocation then. LD A,0E5H ;Ditto for an empty sector. CP (HL) JP Z,BITMAP2 LD A,32 ;Is this a directory label? CP (HL) JP Z,BITMAP4 LD A,16 ;Is this a password entry? AND (HL) JP NZ,BITMAP3 ;Yes, no storage also. LD C,1 ;Entry is just a filename. Allocate CALL FILESET ;storage for it. BITMAP3:CALL CHKNMBR ;Update directory entry count. JP BITMAP2 ;Continue.... BITMAP4:LD DE,12 ;Directory label, get status byte. ADD HL,DE LD A,(HL) LD HL,(SCRATCH7);Save it here. LD (HL),A JP BITMAP3 ;Count entry, but takes up no space. ; ; Store the fill search status from last access. ; STSTATUS:LD A,(FNDSTAT) JP SAVESTAT ; ; Check the extents in (a) and (c). Set the zero flag ; if they refer to the same directory entry. ; SAME$EXT:PUSH BC PUSH AF LD A,(EXM) ;Set (b) as mask byte for extents. CPL LD B,A LD A,C ;Mask first extent (c). AND B LD C,A POP AF AND B ;Mask second. SUB C ;Any meaningful difference? AND 01FH ;Check bits 0-6. Set zero flag if the same. POP BC RET ; ; Look through allocation bytes in FCB and get the ; last used one. ; COMPEXT:CALL SETHLDE ;Point (hl) to end of FCB. LD C,16 ;Set search limit. LD B,C ;(b) is used as a position indicator. INC C PUSH BC CMPXT1: POP BC ;Check next block entry. DEC C XOR A CMPXT2: DEC HL ;Is next block empty? DEC B CP (HL) JP NZ,CMPXT3 ;...nope. DEC C ;More to check? JP NZ,CMPXT2 CMPXT3: LD A,C ;Here, block entry (c) may be empty. LD (RELBLOCK),A LD A,(BIG$DISK) ;Check for 16 bit block numbers. OR A LD A,B JP NZ,CMPXT4 RRA ;Adjust for 16 bit numbers. CMPXT4: PUSH BC ;Save where we are. PUSH HL LD L,A ;Now check to see if FCB is allowed LD H,0 ;to hold this many block numbers. LD A,(BSH) ;If not, we must skip this LD D,A ;entry (it is just junk). LD A,7 SUB D LD C,A CALL SHIFTR LD B,L LD A,(EXM) CP B POP HL JP C,CMPXT1 ;Skip this entry and get the next. CALL GET$EX ;Get extent byte. LD C,(HL) ;Get extent into (c). CPL ;Generate mask for it. AND 01FH AND C ;Mask out inter FCB extents. OR B ;Now add in relative extent. POP BC ;Restore block location. RET ; ; Set directory search parameters and prepare to ; lookup a file, password, time/date stamp, or label entry. ; Register (c) contains the directory checksum code ; byte (see CHECKDIR for values). ; SETSRCH:LD HL,(@VINFO) ;Save FCB to match. LD (SRCHFCB),HL SETLIMIT:LD A,C ;Save char count to match. LD (@MATCH),A CALL STHASH LD A,0FFH ;Clear status. LD (FNDSTAT),A RET ; ; Find first directory entry that matches the first ; fifteen bytes. ; FINDNAME:LD C,15 ;Set search byte limit. JP FINDFST ; ; Search for first entry with matching name only. ; SRCHFST:LD C,12 ;Check drive byte and name only. ; ; Fimnd the first directory entry that matches in the ; first (c) bytes. The users FCB area will used for ; comparisons. Set (@@PSWRD)to zero if password entries ; are not considered a match (unless the drive byte ; is set specifically for this). The flag at (PSWDFLG) ; will be set to non zero if a password entry was found. ; FINDFST:CALL SETSRCH ;Set search parameters. FINDIT: CALL RSTFILPS ;Reset file position pointer. CALL CHKTYPE ;Is FCB valid? CALL Z,DSK$INIT ;No, reset disk parameters. ; ; Find the next matching directory entry. Note that ; the search parameters must have already been set. ; FINDNXT:XOR A ;Clear "from user 0" flag byte. LD (USER0),A CALL HSHSRCH ;Set hash pointer (if enabled). JP NZ,FNDNXT8 ;...not found. LD C,0 ;Get next entry and check checksum byte. CALL NXTNTRY CALL CKFILPOS ;More entries? JP Z,FNDNXT8 ;...nope, not found. LD HL,(SRCHFCB) ;Check drive byte from FCB. EX DE,HL LD A,(DE) CP 0E5H ;Searching for an empty? JP Z,FNDNXT1 ;...yes, okay do it. PUSH DE CALL MOREFLS ;More entries exist? POP DE JP NC,FNDNXT8 ;...nope, not found. FNDNXT1:CALL FCB2HL ;Point (hl) to FCB in directory buffer. LD A,(@MATCH) ;Get match bye count into (c). LD C,A LD B,0 LD A,(HL) ;Is this entry empty? CP 0E5H CALL Z,FIRSTMT ;...yes, save location of first one. IF BANKED XOR A ;Say password not found (yet). LD (PSWDFLG),A LD A,(HL) ;Is this a password entry? AND 0EFH CP (HL) JP Z,FNDNXT2 ;...no. EX DE,HL ;Yes, are we looking for one? CP (HL) EX DE,HL JP NZ,FNDNXT2 ;...yes, then do it. LD A,(@@PSWRD) ;No, do we allow this to match anyway? OR A JP Z,FINDNXT ;...no, skip this entry. LD (PSWDFLG),A ;Yes, set flag for this. JP FNDNXT4 ;Say first byte matched. ENDIF FNDNXT2:LD A,C ;More bytes to compare? OR A JP Z,FNDNXT5 ;No, match found then. LD A,(DE) ;Check next byte. CP '?' ;A wild card? JP Z,FNDNXT4 ;Yes, automatic match. LD A,B ;Check location within FCB for special action. CP 13 ;S1 byte? JP Z,FNDNXT4 ;...yes, don't check. CP 12 ;Extent byte? JP Z,FNDNXT3 ;Yes, check all bits. CP 14 ;S2 byte? LD A,(DE) CALL Z,FNDNXT7 ;...yes, strip bits 6,7. SUB (HL) ;Does this byte match? AND 07FH ;We don't care about bit 7. JP NZ,FNDNXT9 ;No match, move to next entry. JP FNDNXT4 ;So far, so good. Continue search. FNDNXT3:LD A,(DE) ;Check the extent bytes. PUSH BC LD C,(HL) CALL SAME$EXT ;Are they the same? LD B,A ;Save result here. LD A,(USER0) INC A JP Z,FNDNXT10 XOR A ;Say user 0 has been checked. LD (FROMUSR0),A LD A,B ;Are the extents the same? POP BC OR A JP NZ,FINDNXT ;...nope, check next entry. FNDNXT4:INC DE ;So far the name matches, move on to the INC HL ;next byte. INC B ;Increment match byte count. DEC C JP FNDNXT2 FNDNXT5: IF BANKED LD A,(PSWDFLG) ;A matching entry was found. Was this a password? INC A JP NZ,FNDNXT6 ;...nope, just normal match. LD A,(@@ALTER+1);Yes, do we save where we found this? CP 0FEH CALL Z,SAVEMT ;...yes, save this position. JP FINDNXT ENDIF FNDNXT6:XOR A ;Okay, we found a match. Set status and return. LD (FNDSTAT),A LD (RET$STAT),A LD B,A INC B RET FNDNXT7:AND 03FH ;Mask out bits 6,7 of (a). RET FNDNXT8:CALL FIRSTMT ;Save this location as next available. CALL RSTFILPS ;Reset position pointer. RETERROR:LD A,0FFH ;Set not found error (zero flag). LD B,A INC B JP SAVESTAT FNDNXT9:LD A,B ;Names do not match. Is this first byte? OR A JP NZ,FINDNXT ;Nope, continue search. LD A,(HL) OR A JP NZ,FINDNXT LD A,(FROMUSR0) ;Can we ignore user numbers? OR A JP Z,FINDNXT LD (USER0),A ;Yes, say we did and see if name matches. JP FNDNXT4 FNDNXT10:OR B ;Matching with different user #. Are extents POP BC ;the same and is this user 0? LD BC,FINDNXT PUSH BC RET NZ ;...nope, not a match then. INC HL ;Is S2 byte zero? INC HL LD A,(HL) OR A RET NZ ;Nope, look at next entry. ; ; Save the present file position and continue searching. ; This is used to remember password entries, empty ; locations, or user 0 name matches. This way, we only ; scan the directory once for these multiple cases. ; SAVEMT: CALL STUFFMT ;Save present location (note we won't return). ; ; Save present entry number if FD17 unless it already ; is in use. If (FD18)=ff then it is available and we ; will move the present counter there (presumably our ; counter will not exceed feff). ; FIRSTMT:PUSH HL LD HL,(@@ALTER) ;Is storage available? INC H JP NZ,STFMT1 ;...nope, ignore this then. STUFFMT:LD HL,(@ENTRY) ;Move current entry into save area. LD (@@ALTER),HL STFMT1: POP HL RET ; ; Setup special search parameters. If (@@PSWRD)=ff then ; we will remember the location of a corresponding ; password entry. If (@@ALTER+1)=ff then we will remember ; the first empty entry encountered (may be pre-empted). ; IF BANKED XFCB$OK:LD A,0FFH ;Allow password entries to be remembered. STSPCL: LD (@@PSWRD),A LD A,0FEH ;Don't save empty slots. LD (@@ALTER+1),A RET ; ; Check to see if we have found a password entry for the indicated ; file (already searched for). ; GETPSWRD:LD A,(@@ALTER+1);Did we find a special entry last time? CP 0FEH RET Z ;...nope. CALL BEGSCTR ;Yes, set pointer to the start of the sector XOR A ;with this entry. Ignore casual password entries. CALL STSPCL LD HL,(SRCHFCB) LD A,(HL) ;Now search specifically for the corresponding OR 010H ;password XFCB entry. LD (HL),A LD C,12 ;Set search limit to name only. CALL SETLIMIT JP FINDNXT ;And go look for it. ; ; Setup to access one of the alternate files (either an empty or ; a password entry). ; SET$ALT:LD HL,(@ENTRY) ;Get this address and put into alternate LD (@@ALTER),HL ;spot. RET ; ; Search from the beginning of the current sector for the file. ; CONTSRCH:CALL BEGSCTR ;Get to the start of the current sector. LD C,15 ;Set search byte limit. CALL SETSRCH JP FINDNXT ;Look for next matching entry. ENDIF ; ; Erase files that match the current FCB. ; ERASE: CALL CLR$BITS ;Clear high bits in FCB and save them IF BANKED LD (FILEATR),A ;here. ERASE1: LD A,0FEH ;Set to match password entries also. CALL STSPCL ELSE RLA RET C ENDIF CALL SRCHFST ;Search for the first matching name. RET Z ;None? ERASE2: JP Z,ERASE5 ;Any more to search for? IF BANKED CALL FCB2HL ;Yes, get FCB address. LD A,(HL) ;Get drive byte. AND 010H ;Are we looking only for passwords? JP NZ,ERASE3 ;Yes, go try and delete. LD A,(FILEATR) ;Nope, check the archive bit (7). RLA ;Is it set? CALL NC,CHKSTAT ;Nope, is file write-protected (won't return CALL GETSCR7 ;if it is)? Are passwords required? RLA JP C,ERASE4 ;Yes, don't delete (???). ELSE CALL CHKSTAT ENDIF LD HL,(@VINFO) ;Get file to delete. CALL WILDS ;Any wild cards in name? JP Z,ERASE4 ;Yes, not allowed. JP DELNTY1 ;Okay, deleete this file. ; ; Delete (or try to delete) a password entry. ; ERASE3: IF BANKED CALL GETSCR7 ;Are passwords enabled? RLA JP NC,ERASE4 ;Nope, can't delete them then. CALL CKPSWRD ;Yes, correct one present? JP Z,ERASE4 ;Nope. CALL SETPSWRD ;Okay, take care of this entry and delete it. JP ERASE1 ENDIF ; ; Move on to the next matching name. ; ERASE4: CALL FINDNXT JP ERASE2 ; ; No more names. Look one more (why). ; ERASE5: CALL SRCHFST ; ; If the zero flag is not set, then assume that a file name entry ; is present and try to delete it. ; DELNTRY:JP Z,STSTATUS ;No more files? ; DELNTY1:CALL FCB2HL ;Point to users FCB. IF BANKED LD A,(HL) ;Is this a password query? AND 010H JP NZ,DELNTY2 LD A,(FILEATR) ;Nope, should we delete anyway? AND 080H JP NZ,DELNTY3 ;...nope. ENDIF DELNTY2:LD (HL),0E5H ;Mark this as empty. DELNTY3: IF BANKED PUSH AF CALL PSWDMODE ;Passwords enabled? OR A JP NZ,DELNTY4 LD (HL),A ;Yes, clear it for this file. ENDIF DELNTY4:CALL DIRWRITE ;Okay, write this back out. LD C,0 ;Set "clear space" flag. IF BANKED POP AF ;Did we delete a file? CALL Z,SETBOTH ;Yes, free the disk space. ELSE CALL SETBOTH ENDIF CALL SAVEHASH CALL FINDNXT ;Move on to the next entry. JP DELNTRY ; ; Get the next available empty disk block closest ; to block (bc). This will give priority to blocks ; in the forward direction but will still allocate ; storage in the reverse order under some conditions. ; They never learn. ; FNDSPACE:LD D,B ;Move starting block to (de). LD E,C ; ; Check the next block into the forward direction. (de) ; is used as the forward block pointer. ; FNDSPA1:LD HL,(DSM) ;Passed end of disk? LD A,E SUB L LD A,D SBC A,H JP NC,FNDSPA4 ;Yes, can't look then. INC DE ;Nope, bump pointer. PUSH BC PUSH DE LD B,D ;Is this block used? LD C,E CALL CKBITMAP RRA JP NC,FNDSPA3 ;Nope, use it then. POP DE POP BC ;...yes. ; ; Look at the preceeding block to see if it is used. We ; use (bc) as the backward block pointer. ; FNDSPA2:LD A,C ;Reached front of disk space? OR B JP Z,FNDSPA1 ;Yes, no space here. DEC BC ;Okay, bump pointer. PUSH DE PUSH BC CALL CKBITMAP ;Is this block available? RRA JP NC,FNDSPA3 ;Yes, use it then. POP BC ;Nope, continue looking. POP DE JP FNDSPA1 ; ; Empty block found at (bc). Mark it as used and return. ; FNDSPA3:RLA ;Restore byte and set bit 0. INC A CALL STBMAP1 ;Now set the map correct for this. POP HL POP DE RET FNDSPA4:LD A,C OR B JP NZ,FNDSPA2 LD HL,0 RET ; ; Update the directory FCB by moving (e) bytes ; from the users FCB. Set the CHAIN flag if relative ; byte (c) has bit 7 set. ; UPDATE: LD D,080H ;Set bit 7 mask "on". UPDATE1:CALL UPDATE3 ;Check for the presents of a special byte. INC C ;Bytes to move is now in (c). ; ; Move (c) bytes from users FCB into directory FCB. ; Bit 7 will be maintained. ; UPDATE2:DEC C ;Done? JP Z,DIRWRITE ;Yes, write it out. LD A,(HL) ;Get bit 7 from directory FCB byte. AND B PUSH BC LD B,A LD A,(DE) ;Get byte from users FCB. AND 07FH ;Strip bit 7. OR B ;Now add in previous bit 7 value. LD (HL),A ;Store it now. POP BC INC HL ;On to next byte. INC DE JP UPDATE2 ; ; Check relative byte (c) in users FCB for the ; special "$" flag. If found, set the chain byte, bit 7. ; Return with (bc) holding the original (de), (hl) ; pointing to the FCB in the directory buffer and ; (de) pointing to the byte infront of the "$". The ; zero flag is always cleared. ; UPDATE3:PUSH DE ;Save (de). LD B,0 ;Setup (bc) as relative offset. LD HL,(@VINFO) ;Point to users FCB. ADD HL,BC ;Add in offset INC HL ;plus 1. LD A,(HL) ;Is this byte a "$"? SUB '$' CALL Z,UPDATE4 ;Yes, set bit 7 of the chain byte. DEC HL EX DE,HL ;Point (de) to infront of "$". CALL FCB2HL ;Set (hl) pointing to FCB in directory buffer. POP BC ;Set (bc) as original (de). RET ; ; Set bit 0 of the chain flag byte. ; UPDATE4:LD DE,@CHAIN ;Point to chain flag byte. LD A,(DE) OR 1 ;Set bit 0 and store. LD (DE),A RET ; ; Check the users FCB for wild card characters. Set error ; flag if any found (error #9). ; ANYWILDS:LD HL,(@VINFO) ;Get address of users FCB. ; ; Check FCB pointed to by (hl) for wilds. These will ; not be allowed. ; ANYWLDS:CALL WILDS ;Any wilds found? RET NZ ;Nope, no problem. LD A,9 ;Yes, set error flag. JP STERROR ; ; Search the FCB at (hl) for wild card characters (?). ; Set the zero flag if any found. ; WILDS: LD C,11 ;Set search limit (name+ext). WILDS1: INC HL ;Move to next byte. LD A,'?' ;Is this a wild card? SUB (HL) AND 07FH RET Z ;Yes, return with zero set. DEC C ;Nope, more to check? JP NZ,WILDS1 OR A ;Nope, clear zero flag and return. RET ; ; Move drive specification from first name in FCB ; to second name position. ; MOVDRIVE:LD HL,(@VINFO) ;Get first drive name. LD A,(HL) LD BC,16 ;Move to second name. ADD HL,BC LD (HL),A ;Store it here and return. RET ; ; E N D O F P A R T # 1 ; ; ; ; S T A R T O F P A R T # 2 ; ; Rename a file in users FCB. The current name must ; already be in the first half and the new name in ; the second half. The drive of the first name ; will be used. ; CHGNAMES:CALL ANYWILDS ;No wild cards allowed. IF BANKED CALL VALIDPSW ;Check for passwords. CALL NZ,SETPSWRD ;Yes, check it. CALL XFCB$OK ;Set name search to find XFCBs also. ENDIF CALL MOVDRIVE ;Set drive byte in second name to same as first name. LD (SRCHFCB),HL ;Set second FCB as search target. CALL ANYWLDS ;No wild cards allowed in second name either. LD C,12 ;Check drive byte and name only. LD HL,(SRCHFCB) ;Save FCB to search for. CALL SETLIMIT ;Set search parameters. CALL FINDIT ;Search for second name. JP NZ,FILEXST ;File already exists, error. IF BANKED CALL GETPSWRD ;Any password attached? CALL NZ,DELNTY1 ;Yes, so what? ENDIF CALL MOVDRIVE ;Set drive in second FCB again. IF BANKED CALL XFCB$OK ;Allow XFCBs to match also. ENDIF CALL SRCHFST ;Find first matching filename. RET Z ;Does not exits? CALL CHKSTAT ;Be sure file or disk not write protected. CHGNMS1:LD C,16 ;Set to more than (e), no "$" action. LD E,12 ;Change the name (12 chars). CALL UPDATE CALL SAVEHASH CALL FINDNXT ;Find the next entry. JP NZ,CHGNMS1 ;Continue until no more. IF BANKED CALL GETPSWRD ;Now change password entries. JP Z,STSTATUS ;All done, save status and return. CALL MOVDRIVE ;Set drive with password bit set. JP CHGNMS1 ELSE JP STSTATUS ENDIF ; ; Save file attributes. ; SAVEATTR:CALL CLR$BITS ;Clear high bits in FCB. LD (FILEATR),A ;Preserve previous settings here. IF BANKED CALL VALIDPSW ;Check for passwords. CALL NZ,SETPSWRD ;Set password error (maybe). ENDIF CALL SRCHFST ;Search for first matching file name. RET Z ;None exist? SAVATR1:LD C,0 ;Now update this entry. LD E,12 CALL UPDATE3 CALL MOVE$C LD A,(FILEATR) ;Was this a system file? AND 040H JP Z,SAVATR2 ;...nope. PUSH HL CALL SETHLDE LD A,(HL) ;Yes, get current record and POP HL ;move it into the S1 byte. INC HL LD (HL),A SAVATR2:CALL DIRWRITE ;Write directory buffer now. CALL FINDNXT ;Look for next matching entry. JP Z,STSTATUS ;None, then we are done. JP SAVATR1 ; ; Open a file. ; OPENIT: CALL FINDNAME ;Search for name in directory. OPNIT1: RET Z ;Not there? OPNIT2: CALL SETCHNG ;Set open and not changed bit. LD E,A ;Save S2 here. PUSH HL DEC HL DEC HL LD D,(HL) ;Get extent byte and save. PUSH DE CALL FCB2HL ;Now move FCB into users space. EX DE,HL LD HL,(@VINFO) LD C,32 CALL MOVE$C CALL COMPEXT ;Get extent from allocated space. LD C,A ;And saveheere. POP DE POP HL LD (HL),E ;Restore S2 byte. DEC HL DEC HL LD (HL),D ;And extension. OPNIT3: LD B,0 EX DE,HL LD HL,3 ;Get to record count byte. ADD HL,DE LD A,(DE) ;Compare it with allocated space. SUB C JP Z,OPNIT5 ;Same? LD A,B ;More allocated? JP NC,OPNIT4 LD A,080H ;Yes, set bit 7 for this. OR (HL) OPNIT4: LD (HL),A ;Reset record count. RET OPNIT5: LD A,(HL) ;Any space allocated? OR A RET NZ ;Yes, okay then. OPNIT6: LD (HL),0 ;Clear the record count byte. LD A,(RELBLOCK) ;Block space empty? OR A RET Z LD (HL),080H ;Nope, set bit 7 then. RET ; ; Move 2 bytes from (de) to (hl) if (hl) points ; to a zero value. Return with zero flag set if ; the bytes were moved. Only (a) is altered. ; MOVEWORD:LD A,(HL) ;Does (hl) point to zero? INC HL OR (HL) DEC HL RET NZ ;...nope, just return. LD A,(DE) ;Yes, move 2 bytes then. LD (HL),A INC DE INC HL LD A,(DE) LD (HL),A DEC DE ;Restore regs. DEC HL RET ; ; Check the record count byte within the FCB. If this ; is greater than 128, then strip bit 7 from it. Enter ; with (hl) pointing to the extent byte already. (hl) ; will be preserved. ; CHKRCNT:PUSH HL ;Save this. LD DE,3 ;Offset from extent to record count byte. ADD HL,DE LD A,(HL) CP 129 ;>128? JP C,CHKRC1 AND 07FH ;Yes, strip bit 7 and save. LD (HL),A CHKRC1: POP HL ;Restore this and return. RET ; ; Routine to close a file specified by the users FCB. ; CLOSEIT:XOR A ;Clear status. LD (RET$STAT),A CALL RO$TEST ;Is disk or file read only? RET NZ ;Yes, can't close then. CALL GETS2 ;Check the S2 byte. AND 080H ;Was this extent changed? RET NZ ;Nope, no need to write then. CALL CHECKFCB ;Is the FCB still valid? JP Z,BADFCB ;Nope, set this error. ; ; Patch #001. Use to be "call compext" ; CALL PATCH1 ;Get proper extent byte. ; LD C,A LD B,(HL) ;Get extent from FCB. PUSH BC LD (HL),C ;Save new one. CALL CHKRCNT ;Correct record count? LD A,C CP B ;Different entent bytes? CALL C,OPNIT3 ;Yes, set proper record count. CALL CLSIT1 ;Close extent now. CALL GET$EX POP BC LD C,(HL) LD (HL),B JP OPNIT3 ; ; Update allocated space. This checks for a change ; in the FCB (close failed). ; CLSIT1: CALL FINDNAME ;Find file name. RET Z ;Not there? LD BC,16 CALL SETDEHL ;Point to allocated storage area. LD C,16 ;Set max block limit. CLSIT2: LD A,(BIG$DISK) ;Check for 16 bit block nmbrs. OR A JP Z,CLSIT5 LD A,(HL) ;Nope, get 8 bit block from users space. OR A ;Is it used? LD A,(DE) JP NZ,CLSIT3 LD (HL),A ;Nope, replace with block from directory FCB. CLSIT3: OR A ;Is directory block used? JP NZ,CLSIT4 LD A,(HL) ;Nope, replace with block from users FCB. LD (DE),A CLSIT4: CP (HL) ;Are both block numbers the same? JP NZ,BADFCB ;Nope, FCB has changed (illegal). JP CLSIT6 CLSIT5: CALL MOVEWORD ;16 bit block nmbrs. Fix users FCB. EX DE,HL CALL MOVEWORD ;Now the directory FCB. EX DE,HL LD A,(DE) ;Do they have the same block numbers? CP (HL) JP NZ,BADFCB ;Nope, illegal. INC DE ;Maybe, check second byte. INC HL LD A,(DE) CP (HL) JP NZ,BADFCB ;Nope, error. DEC C ;Count second byte of number. CLSIT6: INC DE ;Now move to next allocated block. INC HL DEC C ;More to check? JP NZ,CLSIT2 EX DE,HL ;Nope, check extent bytes next. LD BC,0FFECH ADD HL,BC PUSH HL CALL COMPEXT ;Compute extent. POP DE CALL CHKDEHL ;Compare them. LD (HL),A ;Update directory extent. LD (DE),A PUSH BC ;Save compare byte (b). LD BC,3 ;Move to record count byte. ADD HL,BC EX DE,HL ADD HL,BC POP BC DEC B ;Check match byte (1=no match). JP Z,CLSIT7 DEC B ;Matched (hl) but not (de)? JP Z,CLSIT8 ;...yep. LD A,(DE) ;Extents matched, check record count bytes. CP (HL) ;Updated space more than previous space? JP C,CLSIT7 ;Yer, okay. OR A ;Nope, is this zero? JP NZ,CLSIT8 CALL OPNIT6 ;Yes, clear record count byte. CLSIT7: EX DE,HL CLSIT8: LD A,(DE) ;Update directorys record count byte. LD (HL),A CALL FCB2HL ;Clear the archive bit (not archived yet). LD DE,11 ADD HL,DE LD A,(HL) AND 07FH LD (HL),A CALL SETCHNG ;Clear S2 bit 7 (file closed). LD C,1 ;Setup second allocation vector. CALL SETSCND ;Then write this directory buffer out. JP DIRWRITE ; ; Mark the FCB as invalid and set error code. ; BADFCB: CALL MARKFCB JP RETERROR ; ; Check (a) against the locations pointed to by (hl) ; and (de). Set (b)=1 if it does not match (hl), (b)=2 ; if it matches (hl) but not (de). And set (b)=3 if it ; matches both (zero flag also set in this case). No ; other registers altered. ; CHKDEHL:LD B,1 CP (HL) ;Does (a) match (hl)? RET NZ INC B EX DE,HL CP (HL) ;Yes, but does it match (de)? EX DE,HL RET NZ INC B ;Yes, it matches both. RET ; ; Clear the alternate file entry pointer. This is used ; as a secondary search result (password, empty, etc.). ; CLRALTER:LD HL,0FFFFH LD (@@ALTER),HL RET ; ; Change the directory extent number to point to the ; sector containing this entry. Each sector contains ; four entries. ; BEGSCTR:LD HL,(@@ALTER) ;Use alternate entry pointer. BEGSECTR:LD A,0FCH ;Mask off the lower 2 bits of (hl). AND L LD L,A DEC HL ;Decrement so that an increment gets LD (@ENTRY),HL ;us to the start of this sector. RET ; ; Routine to get the next empty directory entry. ; GETEMPTY:LD HL,@@ALTER ;Was an mt already found? CALL CKPOS CALL NZ,BEGSCTR ;Yes, move to start of this sector. LD HL,(@VINFO) ;Save users FCB address. PUSH HL LD HL,MT ;Look for this empty one. LD (@VINFO),HL LD C,1 ;Set to check drive byte only. CALL SETSRCH CALL FINDNXT ;Try and find it. POP HL ;Restore user FCB address. LD (@VINFO),HL RET Z ;Not found (no space)? IF BANKED LD A,(@@XFCB) ;Checking some flag in the resident BDOS. OR A RET NZ ENDIF LD DE,13 ;Clear S1. ADD HL,DE LD (HL),D INC HL LD A,(HL) ;Get S2. PUSH AF PUSH HL AND 03FH ;Clear bits 6,7. LD (HL),A INC HL LD A,1 ;Set flag (date/time stamps not cleared). LD C,17 ;Set to clear the allocated storage area. ; ; Clear area at (hl) for a total of (c) bytes. ; GTMT1: LD (HL),D ;Note (d) equals zero here. INC HL DEC C JP NZ,GTMT1 DEC A ;Have we already cleared the data/time area? LD C,D CALL Z,GETFIELD ;(set pointers to it). OR A LD C,10 ;(set field length). JP Z,GTMT1 ;...nope, so do it now. CALL CHKNMBR ;Update range of entry numbers. LD C,0 LD DE,32 ;Update directory FCB. CALL UPDATE1 POP HL POP AF LD (HL),A ;Reset S2. CALL SAVEHASH ;Setup hash data for this entry. JP SETCHNG ;Now mark as not written to and return. ; ; Routine to move on to the next logical extent. If the ; current entry has been filled, then it will be closed ; and the next one opened. ; GTNEXT: IF BANKED CALL CLRMOV ;Clear "move FCB" flag. ENDIF CALL GET$EX ;Get current extent from FCB. LD A,(HL) LD C,A INC C ;Bump by one. CALL SAME$EXT ;Same physical FCB? JP Z,GTNXT5 ;Yes, that was easy. PUSH HL ;Nope, close current extent. PUSH BC CALL CLOSEIT POP BC POP HL LD A,(RET$STAT) ;Okay? INC A RET Z ;Nope, return with error. LD A,01FH ;Mask new extent. AND C LD (HL),A ;And save in FCB. INC HL INC HL LD A,(HL) ;Get S2 and save temporarily. LD (TEMP001),A JP NZ,GTNXT1 ;Physical extent zero? INC (HL) ;Yes, bump S2. LD A,(HL) AND 63 ;Less than 64? JP Z,GTNXT4 ;...yes, special action. GTNXT1: CALL CLRALTER ;Open next extent. Clear alternate location CALL FINDNAME ;in case there is none and we want an empty. JP NZ,GTNXT2 ;...found. LD A,(RDWRTFLG) ;Not found, are we reading? INC A JP Z,GTNXT4 ;Yes, just end-of-file. CALL GETEMPTY ;Look for an empty spot. JP Z,GTNXT4 ;None? Then E-O-F also. JP GTNXT3 ;Okay, no need to open it though. GTNXT2: CALL OPNIT2 ;Open the next extent. GTNXT3: CALL SETS1 ;Mark it as open. CALL STRDATA ;Save record number from FCB. XOR A ;And clear next record number. LD (SAVNREC),A JP SAVESTAT ;All done, normal return. ; ; Process and end-of-file condition. ; GTNXT4: CALL GETS2 ;Restore original S2 contents. LD A,(TEMP001) LD (HL),A DEC HL ;Now restore the extent byte. DEC HL LD A,(HL) DEC A AND 01FH LD (HL),A JP EOFERR ;Set EOF error. ; ; Process those times when the current physical extent contains ; the desired logical extent. ; GTNXT5: INC (HL) ;Bump extent. CALL COMPEXT ;Get to last used area. LD C,A ;Anything been written here? CP (HL) JP NC,GTNXT6 DEC (HL) ;Nope, backup. LD A,(RDWRTFLG) ;Are we reading? INC A JP Z,EOFERR ;Yes, this is not allowed. INC (HL) ;Restore. GTNXT6: CALL CHKRCNT ;Correct record count byte (<129). CALL OPNIT3 ;Just go open this (an easy task). JP GTNXT3 ;And process normally. ; ; Read a file sequentially. ; RDSEQ: CALL CHKVALID LD A,0FFH ;Set flag to prevent reading unwritten data. LD (RDWRTFLG),A CALL STRDATA ;Put rec# and ext# into FCB. LD A,(SAVNREC) ;Get next record to read. LD HL,SAVNXT ;Get number of records in this extent. CP (HL) ;Within extent? JP C,RDSEQ1 CP 128 ;Nope, is this extent fully used? JP NZ,EOFERR ;Nope, end-of-file. CALL GTNEXT ;Okay, open next extent. LD A,(RET$STAT) ;Opened successfully? OR A JP NZ,EOFERR ;Nope, read error. RDSEQ1: IF BANKED CALL SETMOV ;Okay, set FCB move flag byte. ENDIF CALL COMBLK ;Compute block number to access. JP Z,EOFERR ;None? Then end-of-file. CALL LOGICAL ;Convert to logical sector. CALL FNDBLK ;Do we have to read from the disk? JP C,SETNREC ;...nope, we have it already. JP NZ,RDSEQ2 ;...nope also. CALL DO$IO2 ;Set DMA address. CALL TRK$SEC ;Determine track and sector and select them. IF BANKED LD A,1 ;Set bank (1). CALL ?STBNK ENDIF CALL DSKREAD ;Now read the disk and set next record. JP SETNREC RDSEQ2: LD HL,0 LD (BUFBLK),HL LD A,1 CALL DATBCBIO JP SETNREC ; ; Determine if desired block is in memory already. ; Set zero flag if no. ; FNDBLK: LD A,(RELSEC) ;Get logical sector. LD B,A LD A,(PHM) ;Get blocking mask. LD C,A AND B ;Get relative sector within block. PUSH AF ;Save (zero means start of data block). LD A,(BUFREC) CP 2 JP C,FNDBLK1 DEC A LD (BUFREC),A POP AF SCF RET NZ XOR A RET FNDBLK1:POP AF JP Z,FNDBLK4 FNDBLK2:LD A,C ;Get blocking PHM. OR A ;Any deblocking required? RET Z ;...nope, just return. FNDBLK3:OR 1 ;Yes, clear zero flag then return. RET FNDBLK4:LD A,C CPL LD D,A LD HL,SAVNREC ;Check remaining i/o requests. LD A,(REMAINS) CP 2 ;More than one? JP C,FNDBLK2 ADD A,(HL) ;Yes, add to starting number. CP 128 ;Don't go pased here. JP C,FNDBLK5 LD A,128 FNDBLK5:PUSH BC LD B,(HL) LD (HL),07FH PUSH BC PUSH HL PUSH AF LD A,(BLM) ;Get block mask byte. LD E,A INC E CPL AND B ;Mask off relative bits (point to start of LD B,A ;larger block). POP HL ;Save pointer. LD A,(RDWRTFLG) ;Reading? OR A JP Z,FNDBLK6 ;...yes. LD A,(SAVNXT) ;Nope, get max records this extent. AND D ;Mask off relative bits also. CP H ;Don't go pased here either. JP C,FNDBLK7 ;...okay. FNDBLK6:LD A,H ;Get max records. FNDBLK7:SUB B ;Subtract base record. LD C,A ;And save. CP E ;More than one block? JP C,FNDBLK13 ;Nope, okay. IF BANKED PUSH BC CALL GETBLOCK ;Get block number. LD B,A LD A,(RELBLOCK) CP B LD E,A JP Z,FNDBLK10 LD C,A PUSH BC LD B,0 CALL EXTBLOCK ;Extract block (bc) from FCB. ; ; Look through FCB for the largest contigeous area from (hl). ; FNDBLK8:PUSH HL INC BC ;Move to the next block. CALL EXTBLOCK ;Get it. POP DE ;Get previous block. INC DE ;Bump. LD A,D ;The same as in the FCB? SUB H LD D,A LD A,E SUB L OR D JP Z,FNDBLK8 ;Yes, keep looking. LD A,H ;Nope, did we just run out of space? OR L JP NZ,FNDBLK9 ;Nope. LD A,(RDWRTFLG) ;Yes, are we reading? OR A JP NZ,FNDBLK9 ;Yes. LD HL,(DSM) ;Nope, writing. Get max number of blocks LD A,L ;on the disk. Is (de) within limits? SUB E LD A,H SBC A,D JP C,FNDBLK9 ;Nope, skip bit map check. PUSH BC ;Okay, check the bit map to see if this PUSH DE ;has been allocated yet. LD B,D LD C,E CALL CKBITMAP POP HL POP BC RRA JP NC,FNDBLK8 ;Nope, keep looking. FNDBLK9:DEC C ;Check block order. POP DE LD A,D ;Need to reverse? CP C JP C,FNDBLK10 LD A,C ;Yep, get beginning block. FNDBLK10:SUB E ;Compute block size LD B,A ;and put in (b). INC B LD A,(BLM) ;Now adjust for block allocation size. INC A LD C,A FNDBLK11:DEC B ;Compute (a)=(b)*(c). JP Z,FNDBLK12 ADD A,C JP FNDBLK11 FNDBLK12:POP BC LD B,C ;Set (b) to physical block size. LD C,A ;Number of 128 byte sectors for i/o. LD A,(RDWRTFLG) ;Reading? OR A JP Z,FNDBLK13 LD A,B ;Yes, more than one physical block? CP C JP C,FNDBLK14 ;Yes, not allowed (truncate). ELSE LD C,E ENDIF FNDBLK13:LD A,C FNDBLK14:POP HL POP BC LD (HL),B POP BC LD HL,REMAINS ;Don't go beyond the multi-sector count LD D,(HL) ;remaining. SUB B CP D JP NC,FNDBLK15 LD D,A FNDBLK15:LD A,C CPL AND D LD (BUFREC),A JP Z,FNDBLK3 PUSH AF LD A,(RDWRTFLG) ;Reading? OR A JP Z,FNDBLK16 CALL FLUSHEM ;Yes, flush our buffers first. CALL DO$IO2 FNDBLK16:POP AF ;Save block count. LD H,A CALL PHY$SEC ;Convert to physical sector. LD A,H ;Set the multi i/o flag in the BIOS CP 1 ;if more than one sector is involved. LD C,A CALL NZ,?MLTIO XOR A ;Clear the zero flag before returning. RET ; ; Clear the FCB changed flag bit in the S2 byte. ; NOCHANGE:CALL GETS2 ;Get the S2 byte. AND 07FH ;Clear bit 7. LD (HL),A ;Stuff this back now. RET ; ; Set the file changed bit in the FCB S2 byte. Set the zero flag ; if it was no set before this call. ; FILECHNG:CALL GETS2 ;Get S2. AND 040H ;Set zero if bit 6 is not set. PUSH AF LD A,(HL) ;Now set bit 6 no matter what. OR 040H LD (HL),A POP AF ;Restore the zero fag and return. RET ; ; Write to a sequential file. ; WTSEQ: LD A,0 ;Allow writing to new extents. LD (RDWRTFLG),A CALL CHKWPRT ;Be sure we are not write protected. IF BANKED LD A,(HOLDF7) OR A LD A,3 JP NZ,STERROR ;File is read-only. ENDIF LD A,(HOLDF8) OR A LD A,3 JP NZ,STERROR ;File is read-only. LD HL,(@VINFO) ;Has file been set to read-only by the CALL FILEWPRT ;user? CALL CHKVALID ;Is the FCB still valid? CALL STMPUP ;Time/date stamp for file update. CALL STRDATA ;Update FCB record data. LD A,(SAVNREC) ;Get next record to write. CP 128 ;Within range? JP C,WTSEQ1 ;...yes. CALL GTNEXT ;No, get next extent. LD A,(RET$STAT) ;Okay? OR A RET NZ ;Nope, return with error. WTSEQ1: CALL COMBLK ;Okay, compute block number. JP Z,WTSEQ3 ;Unused? LD HL,CURDRIVE ;Check the currently active buffer. LD DE,BUFDRV LD C,3 CALL COMP$C ;Same as we want? JP Z,WTSEQ2 LD A,0FFH ;Nope, set flag saying we need a different one. LD (BUFFLG),A WTSEQ2: LD C,0 ;Say writing to used area. JP WTSEQ8 ; ; Get here when we need another block to write to. ; WTSEQ3: IF BANKED CALL CLRMOV ;Mark this FCB as changed. ENDIF CALL GETBLOCK ;Get block from extent and record numbers. LD (RELBLOCK),A ;Save. LD BC,0 ;Prepare to search from the beginning of the OR A ;disk. Is there a block number? JP Z,WTSEQ4 LD C,A ;Yes, extract previous one from the FCB DEC BC ;and use it as the search start point. CALL EXTBLOCK LD B,H LD C,L ; WTSEQ4: CALL FNDSPACE ;Find next available block around (bc). LD A,L ;Any? OR H JP NZ,WTSEQ5 LD A,2 ;Nope, disk is full. JP SAVESTAT WTSEQ5: LD (CURBLOCK),HL;Okay, save this as the current block. LD (BUFBLK),HL ;Save which block this buffer belongs to. XOR A ;Say buffer is used. LD (BUFFLG),A LD A,(CURDRIVE) ;And save the drive. LD (BUFDRV),A EX DE,HL ;Save block number in (de). LD HL,(@VINFO) ;Get address of FCB. LD BC,16 ;Get to data storage area. ADD HL,BC LD A,(BIG$DISK) ;8 or 16 bit block numbers? OR A LD A,(RELBLOCK) JP Z,WTSEQ6 CALL ADDA2HL ;8 bit, store it. LD (HL),E JP WTSEQ7 WTSEQ6: LD C,A ;16 bit numbers. LD B,0 ADD HL,BC ADD HL,BC LD (HL),E ;Store block number. INC HL LD (HL),D WTSEQ7: LD C,2 ;Say writing to new unallocated block. WTSEQ8: PUSH BC CALL LOGICAL ;Convert physical to logical sector. LD A,(@FX) ;Write random with zero fill? CP 40 JP NZ,WTSEQ12 ;Nope. LD A,C ;Yes, is this new territory? DEC A DEC A JP NZ,WTSEQ12 POP BC ;Yes, then we must zero the block first. PUSH AF LD HL,(CURBLOCK);Save current block number. PUSH HL LD HL,PHM ;Get block size in sectors. LD E,(HL) ;Get 128 sectors per block -1. INC E ;Adjust fot the -1. LD D,A ;Set (d)=0 and save on stack. PUSH DE LD HL,(DIRBCB) ;Get start of directory BCB chain. IF BANKED LD E,(HL) INC HL LD D,(HL) EX DE,HL ; ; Get to the last BCB in the chain. ; WTSEQ9: PUSH HL CALL NXTBCB ;Is there another one? POP DE JP NZ,WTSEQ9 ;Yes, continue the search. EX DE,HL ENDIF DEC A ;Set to 0ffh. LD (BUFFLG),A LD (HL),A ;Mark BCB as unused. CALL DO$IO3 ;Get buffer address into (hl). POP DE ;Get byte count (d)= 0. PUSH DE ;Reg (e) contains PHM+1. XOR A ;Blank out buffer (length is 128-d). ; ; Blank out the buffer area. The number of 128 byte sectors that ; fit in this buffer is in (e). ; WTSEQ10:LD (HL),A ;Zero out one sector at a time. INC HL INC D JP P,WTSEQ10 LD D,A ;Set to zero again. DEC E ;Fill next 128 byte sector. JP NZ,WTSEQ10 ;(if more remain). LD HL,(LOGSECT) ;Get logical sector and set access mode LD C,2 ;to "used area". WTSEQ11:LD (CURBLOCK),HL;Save current block. PUSH BC CALL BCBCHK ;Clear any previously used BCB for this block. CALL TRK$SEC ;Compute track and sector. IF BANKED XOR A ;Select bank 0. CALL ?STBNK ENDIF POP BC CALL DSKWRITE ;Write the sector now. LD HL,(CURBLOCK);Move on to the next sector. POP DE ;Get (de) as number of 128 byte sectors PUSH DE ;per block. ADD HL,DE ;Compute next sector. LD A,(BLM) ;Finished a physical block yet? AND L LD C,0 ;Set access mode to "continue unallocated". JP NZ,WTSEQ11 ;Nope, do more. POP HL POP HL ;Restore current block number. LD (CURBLOCK),HL CALL DO$IO2 ;Reset the users DMA address. WTSEQ12:POP DE ;Set stack right (previous (c) is now in (e)). LD A,(SAVNREC) ;Get next record. LD D,A ;And save. PUSH DE CALL FNDBLK ;Is this block already in one of our buffers? JP C,WTSEQ15 ;Yes, and we are in the middle of a buffer. JP Z,WTSEQ13 ;Nope. LD A,2 ;Set write mode. CALL DATBCBIO ;And write the to the BCB now. JP WTSEQ15 WTSEQ13:CALL DO$IO2 ;Writing to a new buffer block. CALL TRK$SEC ;Compute track and sector. IF BANKED LD A,1 ;Select proper bank. CALL ?STBNK ENDIF CALL BCBCHK ;Clear any matching BCB's. POP BC ;Reset access mode byte (c). PUSH BC LD A,(CURBLOCK) ;Is this the start of a physical block? LD HL,BLM AND (HL) JP Z,WTSEQ14 ;Yes. LD C,0 ;Nope, set flag (for pre-read?). WTSEQ14:CALL DSKWRITE ;Write the block now. WTSEQ15:POP BC ;Get record (b) and access flag (c). LD A,B LD HL,SAVNXT ;Within current record count? CP (HL) JP C,WTSEQ16 ;...yes. LD (HL),A ;Nope, update record count. INC (HL) LD C,2 ;And set flag for this. WTSEQ16:DEC C ;Writing to unallocated space? DEC C JP NZ,WTSEQ17 ;...nope. CALL NOCHANGE ;Yes, clear the FCB changed flag bit. WTSEQ17:CALL FILECHNG ;Say file is now changed. Was it previously? IF BANKED JP NZ,WTSEQ18 ;...yes. CALL NOCHANGE ;Nope, say FCB is not changed. CALL CLRMOV ;But move it back nto the users space. JP SETNREC ;Setup the next record to access. WTSEQ18:CALL SETMOV ;Set the FCB move flag ELSE CALL Z,NOCHANGE ENDIF JP SETNREC ;and set the next record. ; ; For random I/O, set the FCB for the desired record number ; based on the 'R0,R1,R2' bytes. ; On entry, register (c) contains 0ffh is this is a read ; and thus we can not access unwritten data. ; POSITION:PUSH BC LD HL,(@VINFO) ;Point to FCB. EX DE,HL LD HL,33 ;Get the 'R0' byte. ADD HL,DE LD A,(HL) AND 07FH ;Strip bit 7 for the record number. PUSH AF ;Save save for later. LD A,(HL) ;Now get bit 7 into carry. RLA INC HL LD A,(HL) ;Add it to the 'R1' byte. RLA AND 01FH ;Keep bits 0-4 as extent number. LD C,A LD A,(HL) ;Now get bits 6,7. AND 0F0H INC HL OR (HL) ;Add into 'R2' byte. RRCA ;Now shift right 4 places. RRCA RRCA RRCA LD B,A ;And save. LD A,(HL) ;Check for an overflow. AND 0FCH POP HL ;Pop record number into (h). LD L,6 ;Prepare in case of error. LD A,H JP NZ,POSITN8 ;...yes, report error. LD HL,32 ;Store record number in FCB. ADD HL,DE LD (HL),A LD A,(@FX) ;Check function number. CP 99 ;Is it truncate file? JP Z,POSITN3 ;...yes. PUSH DE ;Nope, check to see if FCB is still valid. CALL CHECKFCB POP DE JP Z,POSITN2 ;...nope. LD HL,14 ;Okay, compare the 'S2' byte with ADD HL,DE ;record, bits 12-17. LD A,B SUB (HL) AND 03FH JP NZ,POSITN2 ;Not the same, wrong extent. LD HL,12 ;Get extent byte. ADD HL,DE LD A,(HL) CP C ;Same extent? JP Z,POSITN6 ;...yes, okay. CALL SAME$EXT ;Maybe not, check physical extents. JP NZ,POSITN2 ;...nope, get next one. PUSH BC ;Has extent been written to? CALL COMPEXT POP BC CP C JP NC,POSITN1 ;...yes, okay. ; ; Un-written data. See if it is okay to use this space ; (not allowed for reads). ; POP DE ;Get access code into (e). 0ffh=reading. PUSH DE INC E ;Are we reading? JP NZ,POSITN1 ;...nope, okay. INC E ;Yes, error. POP DE JP EOFERR ;Set error code 1 and return. ; ; Okay, found correct position. ; POSITN1:LD (HL),C ;Save record count. LD C,A CALL CHKRCNT ;Make sure it is within range. CALL OPNIT3 ;Open this extent. JP POSITN5 ; ; Get here when another extent must be opened. We will ; close the current extent first. ; POSITN2:PUSH BC ;Save regs. PUSH DE CALL CLOSEIT ;Close current extent. POP DE POP BC LD L,3 ;Prepare for error. LD A,(RET$STAT) INC A JP Z,POSITN8 ;...yes. ; ; Open the next extent (if possible). ; POSITN3:CALL CLRALTER ;Clear alternate entry in case of empty. LD HL,12 ;Get to extent byte. ADD HL,DE PUSH HL LD D,(HL) ;Save current value. LD (HL),C ;Say which extent we require. INC HL INC HL LD A,(HL) ;Get 'S2' byte and save. LD E,A PUSH DE AND 040H ;Keep bit 6 (why?). OR B ;Add in desired byte. LD (HL),A CALL OPENIT ;Now try to open this extent. LD A,(RET$STAT) INC A ;Found? JP NZ,POSITN4 ;...yes. POP DE ;Nope, see if we can use an empty POP HL ;spot (not allowed for reading). POP BC PUSH BC PUSH HL PUSH DE LD L,4 ;Prepare for the worst. INC C ;Reading? JP Z,POSITN7 ;Yes, sorry. CALL GETEMPTY ;Okay, get next empty location. LD L,5 ;Prepare for the worst (again). JP Z,POSITN7 ;Sorry, none available. POSITN4:POP BC ;Okay, use this extent. POP BC CALL SETS1 ;Set the 'S1' byte from storage. POSITN5: IF BANKED CALL CLRMOV ;FCB changed, set flag. ENDIF POSITN6:POP BC ;Restore regs and return (successful). XOR A JP SAVESTAT ; ; Access errror (code is in (l)). Restore original FCB ; then return with error. ; POSITN7:POP DE EX (SP),HL LD (HL),D ;Restore extent and 'S2' bytes. INC HL INC HL LD (HL),E POP HL ;Get error code (l). POSITN8: IF BANKED CALL CLRMOV ;Save FCB changed. INC A ;Clear zero flag. ENDIF POP BC LD A,L ;Get error code and return. JP SAVESTAT ; ; Read a random record. ; READRAN:LD C,0FFH ;Set 'read' flag. CALL POSITION ;Find proper position. CALL Z,RDSEQ ;And read (if successful). RET ; ; Write a random record. ; WRITERAN:LD C,0 ;Set 'write' flag. CALL POSITION ;Find position. CALL Z,WTSEQ ;And write (if successful). RET ; ; Compute the random record number. Enter with (hl) pointing ; to an FCB and (de) containing the relative location of the ; record number bytes. On exit, reecord number is in (cba) ; and the zero flag is set if this is within bounds. ; COMPRAN:EX DE,HL ADD HL,DE ;Move to record number bytes. LD C,(HL) ;Get 'R0' byte. LD B,0 LD HL,12 ;Move to extent byte. ADD HL,DE LD A,(HL) ;Get extent. RRCA ;Move bit 0 into bit 7 position. AND 080H ;And keep it. ADD A,C ;Now add in record number. LD C,A LD A,0 ;Move any overflow into (b). ADC A,B LD B,A LD A,(HL) ;Now get other extent bits. RRCA AND 00FH ADD A,B ;Add this into (b) also. LD B,A LD HL,14 ;Get to 'S2' byte. ADD HL,DE LD A,(HL) ADD A,A ;Shift right 4 places. ADD A,A ADD A,A ADD A,A OR A ;(what, this makes no sense.) ADD A,B ;Add this in now. LD B,A PUSH AF ;Save carry (indicates overflow). LD A,(HL) ;Check bits 4,5. RRA RRA RRA RRA AND 3 ;Set to zero if none set. LD L,A POP AF ;Now retrieve carryflag. LD A,0 ADC A,L ;Either of these set (overflow error). RET ; ; Compare the 24 bit random record numbers at (cba) and ; where (hl) points. Set the carry flag if (cba) is the ; smaller of the two. ; COMPREC:LD E,A ;Preserve highest byte in (e). LD A,C ;Subtract lowest bytes. SUB (HL) LD D,A INC HL LD A,B ;Now middle bytes. SBC A,(HL) INC HL PUSH AF OR D LD D,A POP AF LD A,E ;Now the highest bytes. SBC A,(HL) RET ; ; Move the record number in (cbe) to area at (hl). ; MOVEREC:LD (HL),E ;Move highest byte. DEC HL LD (HL),B ;Now middle byte. DEC HL LD (HL),C ;Lastly the lowest byte. RET ; ; Compute maximum file space used. Setup the FCB to ; reflect the last record used for a random (or whatever) ; file. It reads the directory looking at all extents and ; searching for the largest record number. 'R0,R1,R2' will ; be set for this record. ; RANSIZE:CALL GET$R0 ;Get to the 'R0' byte. PUSH HL LD (HL),D ;Clear the current record number bytes (note (d)=0). INC HL LD (HL),D INC HL LD (HL),D CALL SRCHFST ;Look for first entry. RANSIZ1:JP Z,RANSIZ2 ;No more found? CALL FCB2HL ;Compute random record number for this. LD DE,15 CALL COMPRAN POP HL PUSH HL CALL COMPREC ;Compare, is this one larger? CALL NC,MOVEREC ;Yes, save it then. CALL FINDNXT ;Move on to the next extent. LD A,0 ;Always clear this (no errors possible). LD (RET$STAT),A JP RANSIZ1 RANSIZ2:POP HL RET ; ; Function to return the random record position of a ; file that has been read sequentially up to now. ; SETRAN: EX DE,HL LD DE,32 ;Compute record number. CALL COMPRAN LD HL,33 ;Now move it into FCB area. ADD HL,DE LD (HL),C INC HL LD (HL),B INC HL LD (HL),A RET ; ; Select the drive in (a), make it the current drive ; and also store it in buffer at (hl). ; SELDRIVE:LD (CURDRIVE),A SLCT$IT:LD (HL),A LD D,A LD HL,(LOGINVEC);Is this drive loged in? CALL DRV$TEST LD E,A ;Set (e)=0 for no, (e)=1 for yes. PUSH DE ;Save for later. CALL SELECT$D ;Select this drive anyway. POP HL ;...later. JP NC,INV$DISK ;Select error? DEC L ;Okay, set zero flag if this drive was loged in before. RET ; ; Select drive (e). ; SLCTSAV:LD HL,DRIVE LD (HL),E ;Store drive name. ; ; See if the selected drive is active. If now make it so. ; SETDSK: LD A,(DRIVE) ;Get newly selected drive. LD HL,ACTIVE ;Same as active drive? CP (HL) JP NZ,SLCT ;Nope, select it. CP 0FFH ;Maybe, was any drive active? RET NZ ;Yes, we are okay.Just return. ; ; Make the selected drive active. Log it in if necessary. ; SLCT: CALL SELDRIVE ;Select drive. Already loged-in? RET Z ;...yep. CALL RELOG ;RE-log the drive. LD HL,(SCRATCH8);Disk directory changed? LD A,(HL) AND 1 PUSH AF ;Zero means no. ADD A,(HL) ;Move bit 0 into bit 1 position. LD (HL),A POP AF CALL NZ,CKSTMP CALL LOGINDRV ;Log-in drive now. RET ; ; Routine to select the disk but clear the 'F8 and 'F7 flags ; such that the file is not write-protected. We really want to ; write to it. ; AUTOWRIT:XOR A ;Clear the various read-only flags. LD (HOLDF8),A IF BANKED LD (HOLDF7),A ENDIF JP AUTOSL1 ;Now select the disk. ; ; Auto drive select routine. This will select the specified ; drive or the current drive. ; AUTOSEL:LD BC,807FH ;(b)=128, (c)=127. LD HL,(@VINFO) ;Point to users FCB. LD DE,7 ;Check F7 bit 7. EX DE,HL ADD HL,DE IF BANKED LD A,(HL) AND B LD (HOLDF7),A ;Save it here. LD A,(HL) ;Now strip bit 7 and save back in FCB. AND C LD (HL),A ENDIF INC HL ;Now get F8 bit 7. LD A,(HL) AND B LD (HOLDF8),A ;An save it here. LD A,(HL) ;Now strip bit 7 and resave. AND C LD (HL),A CALL CLEAR567 ;Strip bits 5,6,7 of the extent byte. AUTOSL1:LD HL,0 ;Clear directory search buffers. IF BANKED LD (@@XFCB),HL ENDIF LD (@@ALTER),HL XOR A LD (FROMUSR0),A DEC A LD (@RESEL),A LD HL,(@VINFO) LD A,(HL) ;Get drive byte and save. LD (DRVBYTE),A AND 01FH DEC A ;Adjust to make zero relative. LD (SAVE$E),A ;Save for SELECT. CP 0FFH ;Use current drive? JP Z,AUTOSL2 LD (DRIVE),A ;Nope, save new one to access. AUTOSL2:CALL SETDSK ;Select drive. LD A,(@USRCD) ;Move user number into FCB. LD HL,(@VINFO) LD (HL),A AUTOSL3:CALL CHKTYPE ;Check function. CALL Z,CHK$DBCB ;Clear all DBCB's if function is in the table. CALL RSTMEDIA ;See if we need to re-login this drive. JP CHKMEDIA ; ; Reset the disk on a media change (if possible). ; RSTMEDIA:CALL CHK$MF ;Has media been changed in this drive? RET Z ;Nope, just return. LD (HL),0 CALL CHK$DBCB ;Clear associated directory BCB's. LD HL,(@ENTRY) PUSH HL CALL DSK$INIT ;Initialize disk parameters. CALL RSTFILPS ;Set FBE1 to ffff. RSTMED1:LD C,0 CALL NXTENTRY ;Get to next entry. LD HL,@MEDCHG ;Has media changed? LD A,(HL) OR A JP Z,RSTMED2 LD (HL),0 ;Yes, clear flag and see if we can restart. POP HL LD A,(@FX) ;Check function. CP 48 ;Flush buffers? RET Z ;...yes, just return (sorry). CALL START ;Start from the beginning. JP CHNG$OK ;And see if this is okay (where do we return?). RSTMED2:CALL MOREFLS ;Are there more entries in the directory? JP C,RSTMED1 ;Yes, check them. POP HL ;Nope, reset original entry pointer and return. LD (@ENTRY),HL RET ; ; Check for a change in the disk media. ; CHKMEDIA:LD HL,@MEDIA ;Do we need to check any drives? LD A,(HL) OR A RET Z LD (HL),0 ;...yes, clear this and check each drive. LD HL,(LOGINVEC);Search all 16 drives. LD A,16 CHKMED01:DEC A ;Next drive (P down to A). ADD HL,HL ;Loged-in? JP NC,CHKMED02 ;Nope, skip. PUSH AF PUSH HL LD HL,ACTIVE CALL SELDRIVE CALL WRITTEN ;Has drive been written to? CALL NZ,RSTMEDIA ;Yes, reset the disk. POP HL POP AF CHKMED02:OR A JP NZ,CHKMED01 JP SETDSK ; ; Check to see if the selected drive has been written to. ; This check the Buffer Control Block (see sg 44) and ; looks at the write flag (WFLG). In the banked system, ; it follows through the chain of BCB's. Return with ; the zero flag set if this drive has not been written ; to, and cleared if it has and needs to be flushed. ; WRITTEN:LD HL,(DTABCB) ;Get address of data BCB. LD A,L ;Any active? AND H INC A RET Z ;...no, say not written to. WRITN01: IF BANKED LD E,(HL) ;Extract address of BCB. INC HL LD D,(HL) LD A,E ;Is this one active? OR D RET Z ;...no, say not written to. LD HL,4 ;Point to WFLG byte in BCB. ELSE LD DE,4 ENDIF ADD HL,DE LD A,(HL) ;Check it, zero means buffer not "dirty". OR A IF BANKED RET NZ ;Return if written to. LD HL,13 ;Continue on to the next BCB in chain. ADD HL,DE JP WRITN01 ELSE RET ENDIF ; ; Get the password mode byte (bit 7). ; GETSCR7:LD HL,(SCRATCH7) LD A,(HL) IF NOT BANKED AND 7FH ENDIF RET ; ; Check for a valid password. Set the zero flag there ; is one (or one is not required). ; IF BANKED VALIDPSW:CALL GETSCR7 ;Get password flag byte. AND 080H ;Are they enabled for this drive? RET Z ;...nope. CALL PSWDSRCH ;Okay, is one attached to this file? RET Z ;...nope. JP CHKPSWD ;Yes, check to see if correct one was entered. ; ; Set password error (maybe). ; SETPSWRD:XOR A ;Don't look for other entries. LD (@@ALTER+1),A CALL FCB2HL ;Move this into safe place. EX DE,HL LD C,12 LD HL,TEMPFCB ;This is it. PUSH HL CALL MOVE$C ;Move it now (12 bytes only). LD A,(DE) ;Move extent byte too (why separate?). INC HL LD (HL),A POP DE LD HL,(@VINFO) ;Set drive byte from original. LD A,(HL) LD (DE),A PUSH HL EX DE,HL LD (@VINFO),HL ;Now search for this file name. CALL FINDNAME JP Z,SETPSW3 ;...not found. CALL PSWDMODE ;Get password mode. OR A JP NZ,SETPSW1 ;...none. EX DE,HL LD HL,PSWMODE LD B,(HL) ;Get previous mode. LD A,(DE) ;Get password mode byte. LD (HL),A ;Save it in our space. OR A ;Any passsword for this file? JP Z,SETPSW3 ;...nope. XOR B ;Any change in mode? AND 0E0H JP Z,SETPSW1 CALL PSWDSRCH ;Yes, search for password entry. JP Z,SETPSW1 ;...none found. LD A,(PSWMODE) LD (HL),A ;Now store new mode byte. CALL RO$TEST ;Is disk read-only? CALL Z,DIRWRITE ;Nope, write changed entry. SETPSW1:POP HL ;Reset users FCB address. LD (@VINFO),HL LD A,(@FX) ;Check original BDOS function. CP 15 ;Open? RET Z ;...yes, okay. CP 22 ;How about a make file entry? RET Z ;Yes, that is okay also. SETPSW2:LD A,7 ;Set password error flag. JP STERROR SETPSW3:XOR A ;No password for this file. LD (PSWMODE),A ;Clear our mode byte. CALL RO$TEST ;Is disk read-only? JP NZ,SETPSW4 CALL PSWDSRCH ;Nope, find password entry. PUSH AF LD HL,(@VINFO) ;Prepare to search for specific password entry. LD A,(HL) OR 010H ;Set password bit in drive byte. LD (HL),A POP AF ;Was a password entry found? CALL NZ,DELNTRY ;...yes, delete it. SETPSW4:POP HL ;Restore original FCB address and return. LD (@VINFO),HL RET ; ; Check password pointed to by (hl). Set zero flag if ; it matches. ; CHKPSWD:INC HL LD B,(HL) ;Get checksum byte. LD A,B OR A JP NZ,CKPSWD03 LD D,H ;Sum byte is zero, is there any pswd? LD E,L CKPSWD01:INC HL INC HL ;Look for a non null or space char. LD C,9 CKPSWD02:INC HL LD A,(HL) DEC C RET Z ;None, no password assigned. OR A JP Z,CKPSWD02 CP 32 JP Z,CKPSWD02 EX DE,HL ;Check passsword now. CKPSWD03:LD DE,10 ;Move to end (note reverse order). ADD HL,DE EX DE,HL LD HL,(@@USRDMA);Get un-encoded LD C,8 ;Set length. CKPSWD04:LD A,(DE) ;Get next byte and un-encode it. XOR B CP (HL) ;Same? JP NZ,CKPSWD05 ;...nope. DEC DE ;Okay so far, on to next char. INC HL DEC C JP NZ,CKPSWD04 ;More? RET ;Nope, all done. CKPSWD05:DEC DE ;Get to start of encoded pswd. DEC C JP NZ,CKPSWD05 INC DE ;Now check against default pswd. LD HL,PSWMODE+3 LD C,8 JP COMP$C ; ; Move password at (fd19) into ram at (hl). Format is ; checksum byte followed by encoded password. ; MOVEPSWD:PUSH HL LD BC,8 ;Set (b)=checksum, (c)=length. LD DE,11 ;Point to end of field. ADD HL,DE EX DE,HL LD HL,(@@USRDMA);Get address of password (DMA addr). ; ; Encode the password pointed to by (hl) and move into ; ram ending at (de). Its order will be reversed and each ; byte will be exlucssive or'd with the checksum byte. ; ENCODE: XOR A ;Enter with addr on stk for flag (0=null pswd). PUSH AF ;Save initial null byte. ENCODE01:LD A,(HL) ;Get and store next byte. LD (DE),A OR A ;Null? JP Z,ENCODE02 CP ' ' ;Or space? JP Z,ENCODE02 INC SP ;Neither, save this on stack. INC SP PUSH AF ENCODE02:ADD A,B ;Update checksum byte. LD B,A DEC DE ;Move on to next char. INC HL DEC C ;Done with (c) chars? JP NZ,ENCODE01 POP AF ;Any valid chars present? OR B POP HL ;Retrieve addr of flag byte. JP NZ,ENCODE03 ;...yes. LD A,(@FX) ;Nope, is this function #100 (set directory label)? CP 100 JP Z,ENCODE03 LD (HL),0 ;Nope, clear byte here (why?). ENCODE03:INC DE ;Now, exclusive or each byte with sum byte. LD C,8 ;Password is 8 bytes long. ENCODE04:LD A,(DE) ;Get next byte. XOR B ;Exclusive or with sum byte. LD (DE),A ;And store again. INC DE ;Do all (c) bytes. DEC C JP NZ,ENCODE04 INC HL RET ; ; Search for a password for the indicated file. Set ; the zero flag if one is not found. ; PSWDSRCH:LD HL,(@VINFO) ;Point to FCB. LD A,(HL) ;Save original drive byte. PUSH AF OR 010H ;Set the password bit for sure. LD (HL),A CALL SRCHFST ;Get first occurance. LD A,0 ;Clear status flag always. LD (RET$STAT),A LD HL,(@VINFO) ;Restore original contents. POP BC LD (HL),B RET Z ;None found? ; ; Set the password bit in the XFCB. This is bit 0 of ; the password mode bit. ; STPSWBIT:CALL FCB2HL ;Point to XFCB. EX DE,HL LD HL,12 ;Move to password mode byte. ADD HL,DE LD A,(HL) AND 0E0H ;Keep original bits (5,6,7). OR 1 ;Set bit 0, clear zero flag and return. RET ; ; Increment the users DMA address by (de) bytes. ; BUMPDMA:PUSH HL ;Save this. LD HL,(@@USRDMA);Get DMA address. ADD HL,DE ;Add offset and store. LD (@@USRDMA),HL POP HL RET ; ; Set up a password entry in the directory buffer. ; PSWUPD: CALL CHKNMBR ;Check entry number. LD BC,1014H ; ; Update directory entry for either a password, label, ; or date/time stamp. ; DIRUPD: PUSH BC CALL FCB2HL ;Get FCB address in directory. EX DE,HL LD HL,(@VINFO) ;Get users FCB address. EX DE,HL LD A,(DE) ;Get drive byte and set bit from (b). OR B LD (HL),A INC DE ;Move rest of name into our space. INC HL LD C,11 CALL MOVE$C POP BC INC C DIRUPD1:DEC C ;Zero out remainder of FCB. RET Z LD (HL),0 INC HL JP DIRUPD1 ; ; Set the password bit in the XFCB and check the password ; CKPSWRD:CALL STPSWBIT ;Set password bit. CKPSWRD1:PUSH HL CALL CHKPSWD ;Check the password at (hl) now. POP HL RET ENDIF ; ; Stamp a file for access or creation (time and date). ; CRSTAMP:LD C,0 JP SETSTAMP UPSTAMP:LD C,4 ;Set update time/date stamp. ; ; Set the time and date stamp at relative field (c) in ; SFCB. ; SETSTAMP:CALL GETFIELD ;Move to desired field in SFCB. OR A ;Successful? RET NZ ;...nope, just return. LD DE,DIRWRITE ;Okay, set up return location. PUSH DE NEWDATE:LD DE,@DATE ;Check to see if date is changed. PUSH HL PUSH DE LD C,0 CALL ?TIM ;Get current date/time from BIOS. LD C,4 CALL COMP$C ;Same? LD C,4 POP DE POP HL JP NZ,MOVE$C ;Nope, update field and write. POP HL ;Yes, don't write. Just return. RET ; ; Date and time stamp the present file. ; STAMPIT:CALL FCB2HL ;Point to FCB. ADD HL,BC LD DE,IGNORE ;Setup return address (just a RET instuction). PUSH DE JP NEWDATE ; ; Access a date/time stamp and extract a specific field. ; We must be pointing to the file of interest already. ; IF BANKED PSWDMODE:LD C,8 ;Offset for mode byte. ENDIF GETFIELD:LD A,(@ENTRY) ;Be sure we are pointing to a file. AND 3 CP 3 ;...pointing to a date/time stamp. Just return. RET Z LD B,A ;Save relative entry number (0-2). LD HL,(DIRBUF) ;Get start of directory sector. LD DE,96 ;Point to possible date/time stamp entry. ADD HL,DE LD A,(HL) SUB 33 ;Is it a date/time stamp? RET NZ LD A,B ;Yes, now point to data for the entry of interest. ADD A,A LD E,A ADD A,A ADD A,A ADD A,E INC A ;(a)=position*10+1. ADD A,C ;Now add in specific offset. LD E,A ADD HL,DE XOR A ;Set zero flag for successful access. RET ; ; Check for time and date stamps. Enter with bit mask ; in (c). Set zero flag if file should be stamped. ; STAMPOK:CALL BASEXT ;Is file elgible for stamping? RET NZ ;...nope. STAMPOK1:LD HL,(SCRATCH7);Okay, are stamps enabled? LD A,C AND (HL) JP NZ,RO$TEST ;Yes, see if drive is read-only. INC A RET ; ; See if the current FCB can be stamped. ; BASEXT: LD A,(EXM) ;Get extent mask. OR 0E0H ;Ignore bits 6,7. CPL LD B,A ;Save mask byte. CALL GET$EX ;Get extent byte. LD A,(HL) AND B ;Mask it, is this the base extent? RET NZ ;...nope, can't stamp. INC HL ;Okay, check the 'S2' byte next. INC HL LD A,(HL) ;If either bits 6 or 7 are set, no stamping. AND 03FH RET ; ; A file was updated, time and date stamp it as such if this was ; enabled. ; STMPUP: LD C,32 ;Point to update bit. CALL STAMPOK1 ;Do we stamp it for updates? RET NZ ;...nope. CALL GETS2 ;Okay, set flag saying it has already been AND 040H ;stamped (only do this once). RET NZ ;Already done. CALL GET$EX ;Save extent and the S2 byte. LD B,(HL) LD (HL),0 ;Clear extent. PUSH HL INC HL INC HL LD C,(HL) LD (HL),0 ;Clear S2. PUSH BC CALL FINDNAME ;Find the file and date/time stamp CALL NZ,UPSTAMP ;it for 'updated' (if found). XOR A ;Clear status always. LD (RET$STAT),A POP BC ;Restore extent byte and S2 byte. POP HL LD (HL),B INC HL INC HL LD (HL),C RET ;And we have finished. ; ; Return the version number (function #12). ; VERSION:LD A,(@VERSION) JP SAVESTAT ; ; Reset the disk system. Reselect drive and DMA address ; to 0080 hex (function #13). ; RESET: LD HL,0FFFFH ;Reset all drives. CALL LOGOUT XOR A ;Select drive A. LD (@CRDSK),A LD HL,128 ;Set DMA address to 80h. LD (@CRDMA),HL JP DO$IO2 ; ; Select drive specified by (e). Return with (a)=0 ; if okay, else (a)=1 on a disk i/o error or (a)=4 on ; an invalid drive. ; DRIVESEL:CALL SLCTSAV ;Select drive. LD A,(DRIVE) ;Only returns if okay, set drive in SCB table. LD (@CRDSK),A RET ; ; Open file pointed to by (de). Function #15. ; OPEN: CALL CLEARS2 ;Clear the S2 byte. CALL AUTOWRIT ;Select the disk and allow writes. CALL ANYWILDS ;Wild cards not allowed. LD A,(@USRCD) ;Get user code. OR A ;Is it zero? JP Z,OPEN1 LD A,0FEH ;Nope, allow search to find it user 0 LD (@@ALTER+1),A;as an alternate match. INC A LD (FROMUSR0),A ;Say this is not from user 0 (yet). OPEN1: CALL OPENIT ;Go open the file (if possible). CALL OPENOK ;Only return if file not found. LD HL,FROMUSR0 ;Are we in user 0? CP (HL) RET Z ;Yes, return non-existant. LD (HL),A ;Clear flag. LD A,(@@ALTER+1);Did we find a match under user 0? CP 0FEH RET Z ;Nope, rturn non-existant. CALL BEGSCTR ;Okay, get to start of this directory LD A,080H ;sector. Set flag saying that this came from LD (HOLDF8),A ;user 0 (file will be read-only). LD HL,(@VINFO) ;Set user number in FCB. LD (HL),0 LD C,15 ;Set search parameters. CALL SETSRCH CALL FINDNXT ;Find matching entry (actually a quick search). CALL OPNIT1 ;Now open it. CALL OPENOK ;Check that we can open it okay. RET ; ; Check that this is okay to open the file we just searched for. ; If the file was not found, set (a) to zero and return. Otherwise ; we will not return. ; OPENOK: CALL CKFILPOS ;Did we find a valid entry? RET Z ;...nope. CALL SETHLDE LD A,(HL) ;Get current record byte. INC A ;Equal to ffh? JP NZ,OPENOK1 DEC DE ;Yes, move S1 into CR field then. DEC DE LD A,(DE) LD (HL),A OPENOK1:POP HL ;Waste return address (we won't return now). LD A,(HOLDF8) ;Was file found in user 0 (read-only)? RLA JP NC,OPENOK2 ;...nope. LD HL,(@VINFO) ;Yes, is this a system file? LD DE,10 ;(look at bit 7 of T2 byte) ADD HL,DE LD A,(HL) AND 080H JP NZ,OPENOK2 ;...yes. LD (HOLDF8),A ;Nope, clear this and return an error (not JP RETERROR ;found). OPENOK2: IF BANKED CALL SETS1 ;Okay, set "file open" bit. CALL GETSCR7 ;Are we using passwords?. AND 080H JP Z,OPENOK6 ;...nope. CALL BASEXT ;Yes, is this the base extent? JP NZ,OPENOK3 ;Nope, forget it. CALL PSWDMODE ;Yes, check the password modes enabled. OR A ;Password found? JP NZ,OPENOK3 ;Nope, none for this file then. LD A,(HL) ;Okay, get password mode byte. AND 0C0H ;Required for read or write? JP Z,OPENOK6 ;Nope, skip check then. CALL SET$ALT ;Setup alternate entry name. CALL PSWDSRCH ;Look for a password. JP NZ,OPENOK4 ;...yes. CALL CONTSRCH ;Keep checking. RET Z ;...none found. CALL PSWDMODE ;Get password mode byte. OR A ;Is a password entry present? JP NZ,OPENOK6 ;Nope, not required then. LD (HL),A ;Clear mode (why?). CALL RO$TEST ;IS DRIVE read-only? CALL Z,DIRWRITE ;Nope, write this back out. JP OPENOK6 OPENOK3:CALL SET$ALT ;Setup alternate entry. CALL PSWDSRCH ;Search for a password. JP Z,OPENOK5 ;None. OPENOK4:CALL CHKPSWD ;Check passowrd. JP Z,OPENOK5 ;...okay. CALL SETPSWRD ;Set password error (maybe). LD A,(PSWMODE) ;Required for read orr write? AND 0C0H JP Z,OPENOK5 ;Nope, ignore. AND 080H ;Required for reading? JP NZ,SETPSW2 ;Yes, error. LD A,080H ;Nope, must be for writing. Make this file LD (HOLDF7),A ;read-only. OPENOK5:CALL CONTSRCH ;Okay, get to file name entry. RET Z ;Not there (how could that be???)? ENDIF OPENOK6:CALL SETS1 ;Say file has been opened. LD C,040H ;Time/date stamp for this access (if enabled). OPENOK7:CALL STAMPOK ;Can we date/time stamp this file? CALL Z,CRSTAMP ;Yes, set create/access stamp. LD DE,@STAMP ;Say drive has been stamped. JP SETDRIVE ; ; Close the specified file. ; CLOSE: CALL AUTOSEL ;Select the drive. CALL SETS1 ;Set the S1 byte from our own copy. CALL SPLUSER ;Setup for special user zero. CALL CLOSEIT ;Close the file. LD A,(RET$STAT) ;Okay? INC A RET Z ;Nope, go no further. JP FLSHBUF ;Yes, flush buffers. ; ; Search for the first occurence of a specified ; file name. ; SRCHFRST:EX DE,HL XOR A ;Set zero flag for "search first". ; ; File locator. ; FINDFILE:PUSH AF ;Save access flag. LD A,(HL) ;Special drive search? CP '?' ;Drive byte = "?" ? JP NZ,FNDFIL1 CALL SETDSK ;Select drive. CALL AUTOSL3 ;Check media. LD C,0 ;Zero is okay, set search length in (c). JP FNDFIL3 FNDFIL1:CALL GET$EX ;Check extent byte for an "?". LD A,(HL) CP '?' JP Z,FNDFIL2 CALL CLEAR567 ;Nope, clear bits 5,6,7 of extent byte. CALL CLEARS2 FNDFIL2:CALL AUTOWRIT LD C,15 ;Set search length to normal. FNDFIL3:POP AF PUSH AF ;Search for first entry? JP Z,FNDFIL4 ;...yes. LD HL,(@ENTRY) ;Nope, set pointer to start of sector PUSH HL ;and read it into our buffer. LD A,0FCH AND L LD L,A LD (@ENTRY),HL CALL DIRREAD POP HL ;Restore original pointer. LD (@ENTRY),HL FNDFIL4:POP AF LD HL,MOVEDIR ;Set return address. PUSH HL JP Z,FINDFST ;Find first entry? LD A,(@MATCH) ;Nope, set previous match byte length. LD C,A CALL SETSRCH JP FINDNXT ;Now find the next match. ; ; Search for the next occurence of a specifed file. ; SRCHNEXT: IF BANKED EX DE,HL LD (SRCHFCB),HL ;Save FCB to look for. ELSE LD HL,(SRCHFCB) LD (@VINFO),HL ENDIF OR 1 ;Set "search next" flag. JP FINDFILE ;Go do it. ; ; Delete a specified file from the directory. ; DELETE: CALL AUTOWRIT JP ERASE ; ; Read a file sequentially. ; READSEQ:CALL AUTOSEL ;Select the specified drive. CALL CHKSPCL ;Check for special user 0 access. JP RDSEQ ;Now read the file. ; ; Write to a file sequentially. ; WRITESEQ:CALL AUTOSEL ;Setect the drive. CALL CHKSPCL ;Check for special user 0 access. JP WTSEQ ;Now write. ; ; Create a new file with the given name. ; MAKEFILE: IF BANKED CALL CLR$BITS ;Clear the attribute bits and save LD (FILEATR),A ;here. ENDIF CALL CLEAR567 ;Clear upper bits of extent byte. CALL CLEARS2 ;And clear the S2 byte. CALL AUTOWRIT ;Select the disk allowing writes. CALL ANYWILDS ;No wil cards are allowed. CALL CLRALTER ;Clear "alternate" file name entry. CALL OPENIT ;Does the file already exist? CALL CKFILPOS ;Check resulting position. (ffff) means no. OR A JP Z,MAKEFL1 ;...nope. CALL COMPEXT ;Maybe, check extent bytes. CP (HL) JP NC,FILEXST ;Yes, this is not allowed. MAKEFL1:PUSH AF ;Save zero flag (no match found). IF BANKED CALL BASEXT ;Base extent? JP Z,MAKEFL2 ;...yes. CALL GETSCR7 ;Nope, are passwords enabled? AND 080H JP Z,MAKEFL2 ;Nope. CALL PSWDSRCH ;Yes, look for password. JP Z,MAKEFL2 ;None. CALL CKPSWRD1 ;Okay, check it. JP Z,MAKEFL2 ;Good password match. CALL SETPSWRD ;Nope, makbe a password error. LD A,(PSWMODE) ;Check mode byte. AND 0C0H ;Read or write password protected? JP NZ,SETPSW2 ;Yes, error. ENDIF MAKEFL2:POP AF ;Was any entry found? CALL NC,GETEMPTY ;Nope, look for an empty entry. CALL CKFILPOS ;Found? RET Z ;Nope, return (out of space). CALL SETS1 ;Okay, say this is open. IF BANKED CALL GETSCR7 ;Passwords enabled? AND 080H JP Z,MAKEFL5 ;Nope. LD A,(FILEATR) ;Yes, check file attributes. AND 040H ;Do we have to assing a password? JP Z,MAKEFL5 ;Nope. CALL BASEXT ;Yep, is this the base extent? JP NZ,MAKEFL5 ;Nope. CALL SET$ALT ;Search for password. CALL PSWDSRCH JP NZ,MAKEFL3 LD A,0FFH ;Not found, just look for an empty spot. LD (@@XFCB),A CALL GETEMPTY JP NZ,MAKEFL3 CALL FINDNAME ;None available, delete this file and return CALL DELNTRY ;an error (?). JP RETERROR MAKEFL3:CALL PSWUPD ;Update password. EX DE,HL LD HL,(@@USRDMA);Point to end of password. LD BC,8 ADD HL,BC EX DE,HL LD A,(DE) ;Get password mode byte. AND 0E0H ;Keep valid bits only. JP NZ,MAKEFL4 ;Nothing entered? LD A,080H ;Yep, assume read mode anyway. MAKEFL4:LD (PSWMODE),A ;Save mode byte. PUSH AF CALL STPSWBIT ;Point to password mode in XFCB. POP AF LD (HL),A ;Move new value in. CALL MOVEPSWD ;Move password into place (encoded). LD (HL),B CALL DIRLBL4 ;Save a new hash index for this entry. CALL CONTSRCH RET Z LD C,8 ;Get to password mode byte for this file. CALL GETFIELD OR A ;Is there one? JP NZ,MAKEFL5 ;Nope, can't change it then. LD A,(PSWMODE) ;Yes, update password mode and write this LD (HL),A ;back to the disk. CALL DIRWRITE CALL SETS1 ;Set file open bit. ENDIF MAKEFL5:LD C,050H ;Set date/time stamps for creation. CALL OPENOK7 LD C,020H ;Set update stamp. CALL STAMPOK RET NZ ;None supported? CALL UPSTAMP ;Okay, do it. JP FILECHNG ;Say file has changed. ; ; Set file accesing error from (a). ; FILEXST:LD A,8 ;File exists when it shouldn't. STERROR:LD C,A LD (ECODE),A CALL RETERROR JP ERR$JMP ; ; Rename a file. (de) points to a FCB with the current name ; in the first 16 bytes and the desired (new) name in the ; last 16 bytes. Normal disk errors are returned. ; RENAME: CALL AUTOWRIT JP CHGNAMES ; ; Get login vector and return in (hl). ; GETLGVEC:LD HL,(LOGINVEC) JP STORE$HL ; ; Get the currently selected disk and return it in (a). ; GETDISK:LD A,(DRIVE) JP SAVESTAT ; ; Set the DMA address to (de). ; SET$DMA:EX DE,HL LD (@CRDMA),HL ;Store revised address. JP DO$IO2 ; ; Get the allocation vector and return it to the user. ; GETALVEC:CALL SETDSK LD HL,(ALV) JP STORE$HL ; ; Get the read-only vector and return it. ; GETROVEC:LD HL,(RO$VECT) ;Get vector into (hl). JP STORE$HL ;Store and return. ; ; Set file attributes. (de) points to a FCB with the ; desired parameters set. See sg 98-99 for more details. ; SETFILE:CALL ANYWILDS CALL AUTOWRIT CALL SAVEATTR JP STSTATUS ; ; Get the address of the disk parameter block (DPB) for ; the currently selected drive. Return the value in (hl). ; GETPBVEC:CALL SETDSK LD HL,(DPB) ; ; Save (hl) as the return code word and we are done. ; STORE$HL:LD (RET$STAT),HL RET ; ; Get or set the user code. If (e)=ff, this is a GET ; request, otherwise it is a SET request. The user code ; widl be forced to the range 0-15. ; USERCODE:LD A,(SAVE$E) ;Check function code. CP 0FFH ;Is this a GET request? JP NZ,SET$USR ;...yes. LD A,(@USRCD) ;Just get the current value. JP SAVESTAT ; ; Set the user code to (a). ; SET$USR:AND 00FH ;Keep within range (0-15). LD (@USRCD),A ;Store and return. RET ; ; Read a specified random record from the file pointed ; to by (de). ; READRND:CALL AUTOSEL CALL CHKSPCL JP READRAN ; ; Write a specified random record to file at (de). ; WRITERND:CALL AUTOSEL CALL CHKSPCL JP WRITERAN ; ; Compute file size (virtual space used). Note that ; random files may have many "holes" which do not ; take up disk space. ; FILESIZE:CALL AUTOSEL JP RANSIZE ; ; Reset drives specified by (de). The drives are "loged out" ; RST$DRV:EX DE,HL ;Move drives to reset into (hl). ; ; Reset drives specified by (hl). This clears the login ; vector and the read-only vector. ; LOGOUT: LD A,L ;Compliment (hl). CPL LD E,A ;Save low byte in (e). LD A,H CPL LD HL,(LOGINVEC);Get current login vector. AND H ;Clear desired bits in high byte. LD D,A LD A,L ;And now the low byte. AND E LD E,A LD HL,(RO$VECT) ;Also clear the read-only vector. EX DE,HL LD (LOGINVEC),HL;Save new login vector. LD A,L AND E LD L,A LD A,H AND D LD H,A LD (RO$VECT),HL ;Save new read-only vector. LD A,0FFH LD (ACTIVE),A RET ; ; Set multi-sector count to (e). This must be in the ; range of 1 to 128 or an error is returned. ; MULTISEC:LD A,E ;Get count and check it. OR A ;Less than one? JP Z,RETERROR ;...yes, error. CP 129 ;Greater than 128? JP NC,RETERROR ;..yes, error also. LD (@MLTIO),A ;All okay, save value in SCB. RET ; ; Set BDOS error mode to (e). Note that only (ff) and (fe) ; mean anything. Other values just cause the default ; error mode to be used. Mode=(ff), Return Error Mode, ; =(fe), Display and Return Error Mode, otherwise Display ; Error and Abort Mode. ; SETMODE:LD A,E ;Get error mode byte. LD (@ERMDE),A ;Store in SCB. RET ; ; Get free space remaining on drive (e) (0-15). Value ; is returned in the first three bytes of the DMA buffer. ; If the drive has been marked as "read only", then ; this value may be incorrect. Standard disk error codes ; are returned. ; FRESPACE:CALL SLCTSAV ;Select the drive in (e) and make it active. LD HL,(ALV) ;Get the address of the allocation vector EX DE,HL ;into (de). CALL SETLNGTH ;Get its length into (hl). LD BC,0 ;Set (bc) as number of allocated blocks. FRSP1: LD A,(DE) ;Get next byte from vector. FRSP2: OR A ;Any more bits set? JP Z,FRSP4 ;Nope, move on to the next byte. FRSP3: RRA ;Yes, is left bit set? JP NC,FRSP3 ;Nope, shift until it is. INC BC ;Okay, count this block. JP FRSP2 ;And do the rest of the bits. FRSP4: INC DE ;Bumpt the pointers. DEC HL LD A,L ;More bytes remain? OR H JP NZ,FRSP1 ;Yes, check them too. LD HL,(DSM) ;All done, now get the max blocks per disk. INC HL ;(adjust for the -1) LD A,L ;Subtract the number of allocated blocks. SUB C LD L,A LD A,H SBC A,B LD H,A ;Result is now in (hl). LD A,(BSH) ;Now multiply by the block size (express as LD C,A ;a power of 2). XOR A CALL SHIFTL24 EX DE,HL ;Save the resulting number (which is the LD HL,(@@USRDMA);space remaining in sectors) in the first LD (HL),E ;three bytes of the DMA address. INC HL LD (HL),D INC HL LD (HL),A RET ;We are done. ; ; Chain to another program without operator intervention. ; The command line must have been placed in the DMA buffer ; prior to making this function call. The CCP will handle ; the actual command interpretation. ; CHAIN: LD HL,@CHAIN ;Set the chain bit (#7) here. LD A,(HL) OR 080H LD (HL),A INC E ;Do we initialize the default drive (see sg 119)? JP NZ,WARMBOOT LD A,(HL) ;Yes, set the initialize bit (#6) so that the OR 040H ;CCP knows this. LD (HL),A JP WARMBOOT FLUSH: CALL CHKMEDIA CALL ?FLUSH ;Flush any BIOS buffers. CALL DSKIOCHK ;Any errors? ; ; Free blocks allocated to any drive that have not been ; made permanent (by closing files). ; FREEBLKS:LD HL,(LOGINVEC);Look at all 16 drives. LD A,16 FRBLKS01:DEC A ;Check next drive (from P down to A). ADD HL,HL ;Loged-in? JP NC,FRBLKS05 ;...nope, skip this drive. PUSH AF PUSH HL LD E,A CALL SLCTSAV LD A,(@FX) ;Check for function #48 (flush buffers). CP 48 ;Is it? JP Z,FRBLKS02 CALL MOVE$ALV ;Move allocation vector from second to first half. JP FRBLKS03 FRBLKS02:CALL FLUSHEM LD A,(SAVE$E) ;Check initial parameter. INC A ;Did (e)=ff? JP NZ,FRBLKS04 ;...no, don't purge active data buffers. FRBLKS03:CALL PURGE$EM ;Purge all active buffers for this drive. FRBLKS04:POP HL ;Move on to next drive. POP AF FRBLKS05:OR A ;More drives to check? JP NZ,FRBLKS01 ;...yes. RET ; ; Flush data buffers. ; FLSHBUF:CALL ?FLUSH ;Flush the BIOS buffers (if it does blocking). CALL DSKIOCHK ;Check the return status. ; ; Flush our data buffers now. ; FLUSHEM:LD A,(PHM) ;Is any blocking requied? OR A RET Z ;Nope, we are done. LD A,4 ;Yes, set "flush" mode and write out our JP DATBCBIO ;buffers. ; ; Get or set a byte (or word) in the System Control Block (SCB). ; GT$STSCB:EX DE,HL LD A,(HL) ;Check relative address. CP 063H ;Within range? RET NC ;Nope, ignore this request. EX DE,HL LD HL,@HSHCK ;This is the base of the SCB (which is ADD A,L ;located in the Resident BDOS). LD L,A ;Add offset. EX DE,HL INC HL LD A,(HL) ;Check access function. CP 0FEH ;Get a word contents? JP NC,GTST01 EX DE,HL ;Yes, extract a word from the table and return. LD E,(HL) INC HL LD D,(HL) EX DE,HL JP STORE$HL ;Now return the value. GTST01: LD B,A ;Must be a store function, save code in (b). INC HL ;Store the first byte. LD A,(HL) LD (DE),A INC B ;Is it a word store function? RET Z ;Nope, we must be done already. INC HL ;Yes, store high byte then return. INC DE LD A,(HL) LD (DE),A RET ; ; Handle direct calls to the BIOS. ; DIR$BIOS:LD HL,DIRBIOS5 ;Set return address. PUSH HL EX DE,HL ;Check for function #27. IF BANKED LD A,(HL) CP 27 RET Z ;Yes, this is not performed. CP 00CH ;Set DMA address function? JP NZ,DIRBIOS1 LD DE,DIRBIOS3 ;Yes, return to here first. PUSH DE DIRBIOS1:CP 009H ;Select disk function? JP NZ,DIRBIOS2 LD DE,DIRBIOS4 ;Yes, then return here first. PUSH DE ENDIF DIRBIOS2:PUSH HL INC HL ;Extract the desired contents for the INC HL ;registers from the table. LD C,(HL) INC HL LD B,(HL) INC HL LD E,(HL) INC HL LD D,(HL) INC HL LD A,(HL) INC HL LD H,(HL) LD L,A EX (SP),HL LD A,(HL) ;Get funcction number. PUSH HL LD L,A ;Times three. ADD A,A ADD A,L LD HL,?BOOT ;Add to start of BIOS jump table. ADD A,L LD L,A EX (SP),HL ;Put address on stack and get value for INC HL ;register (a). LD A,(HL) POP HL ;Get address of routine. EX (SP),HL ;Put on stack and get contents for (hl). RET ;Go execute the desired function. ; ; Return here after setting the DMA address. We must be sure that memory ; bank (1) is selected. ; IF BANKED DIRBIOS3:LD A,1 ;Select bank (1) and execute normal return. JP ?STBNK ; ; We selected a different disk. Clear the SCRATCH8 byte (directory ; changed flag). ; DIRBIOS4:LD A,L ;Good select? OR H RET Z ;Nope, return with error. EX DE,HL ;Yes, clear the SCRATCH8 BYTE. LD HL,10 ADD HL,DE LD (HL),0 LD HL,(@COMMON) ;Is the DPH in common memory? CALL SUB$HL EX DE,HL RET NC ;Yes, then we are done. EX DE,HL LD HL,(@VINFO) ;Nope, return the DPH contents to the user. INC HL PUSH HL LD BC,25 CALL ?MOV POP HL ;Restore its address. RET ENDIF ; ; Return from a BIOS call. Save the appropriate status values and return. ; DIRBIOS5: IF BANKED LD (RET$STAT),HL;Assume that (hl) already contains the return LD B,A ;status. Save reg (a) incase it has status byte. LD HL,(@VINFO) ;Check function. LD A,(HL) CP 9 ;Select disk? RET Z ;Yes, this is okay. CP 16 ;Translate sector? RET Z ;Okay also. CP 20 ;Device table access? RET Z ;Yes, okay too. CP 22 ;Drive table? RET Z ;Yes, ditto. LD A,B ;Neither one of these, return status from (a) JP SAVESTAT ;instead. ELSE EX DE,HL LD HL,(USR$STK) LD SP,HL EX DE,HL RET ENDIF ; ; TRUNCATE:CALL AUTOWRIT ;Select the drive and make file writable. CALL ANYWILDS ;No wild cards are allowed. IF BANKED CALL VALIDPSW ;Be sure a valid password was entered. CALL NZ,SETPSWRD ;Maybe a password error? ENDIF LD C,0FFH ;Set "reading" flag. CALL POSITION ;Set the random record number bytes. JP NZ,RETERROR ;Error of some sort? CALL FCB2HL ;Get address of FCB. LD DE,15 ;Move to data storage area CALL COMPRAN ;And compute the random record number. CALL GET$R0 ;Point to start of record number bytes. CALL COMPREC ;Compare these values. JP C,RETERROR ;Not less than current file size? OR D ;Exactly equal is illegal too. JP Z,RETERROR CALL CHKSTAT ;Can disk and file be written to? CALL DIRWRITE ;Yes, re-write the directory FCB. CALL STMPUP ;Set time/date stamp for updates. CALL SRCHFST ;Search for first matching file. TRUNC1: JP Z,STSTATUS ;Done with search? CALL CHKEXT ;Nope, check these extents. Did we find a JP C,TRUNC3 ;larger one? PUSH AF ;Yes LD C,0 ;Clear the file space in the allocation map. CALL SETBOTH POP AF ;Were the extents the same? JP Z,TRUNC4 ;...yes. CALL FCB2HL ;Nope, erase this one. LD (HL),0E5H ;Mark as empty and update the hash tables. CALL SAVEHASH TRUNC2: CALL DIRWRITE ;Write the FCB back out. TRUNC3: CALL FINDNXT ;Find the next matching file entry. JP TRUNC1 TRUNC4: CALL STRDATA ;Store record data in FCB. CALL GETBLOCK ;Get block number (0-7 or 0-15). CALL FILLZ ;Fill remainder of FCB with zeros. CALL COMPEXT ;Check last block used. CP (HL) ;Set zero if none. LD (HL),A PUSH AF CALL SETHLDE LD A,(HL) ;Get current record number. INC A ;Bump and store as record count byte. LD (DE),A POP AF ;Any data in extent? EX DE,HL CALL NZ,OPNIT6 ;Yes, adjust record count byte. LD A,(RELBLOCK) ;At the start of a block? OR A CALL Z,OPNIT6 ;Yes, then clear the record count. LD BC,11 ;Point to the archive bytes. CALL SETDEHL EX DE,HL LD A,(HL) ;Strip it from here. AND 07FH LD (HL),A INC HL ;Move to the extent bytes. INC DE LD A,(DE) ;And move this over too. LD (HL),A INC HL ;Clear the S1 byte. LD (HL),0 INC HL ;Move to the record count bytes. INC HL INC DE INC DE INC DE LD C,17 ;Now move all of the allocation space into CALL MOVE$C ;this space. LD C,1 ;Set the space as used in the allocation map. CALL SETBOTH JP TRUNC2 ; ; Set (hl) pointing to users FCB+(bc) and (de) to ; directory FCB+(bc). ; SETDEHL:CALL FCB2HL ;Get directory FCB. ADD HL,BC ;Add desired offset. EX DE,HL LD HL,(@VINFO) ;Ditto for the users FCB. ADD HL,BC RET ; ; Compare file extents at (hl) and (de). Set the carry flag if the one ; at (hl) references larger record numbers than the one at (de). ; CHKEXT: LD BC,14 ;Get the S2 bytes. CALL SETDEHL LD A,(HL) AND 03FH ;Strip file changed status bits. LD B,A ;We are left with the random rec overflow. LD A,(DE) ;Same highest 6 bits? CP B RET NZ ;...nope, return with carry set (hl>de). DEC HL ;Okay, check the extents. DEC HL DEC DE DEC DE LD A,(DE) LD C,(HL) CALL SAME$EXT RET Z ;Same? LD A,(DE) ;Not the same, set carry if the one at (hl) CP (HL) ;is grreater than the one at (de). RET ; ; Fill FCB with zeros after the (a)th block number. ; FILLZ: INC A ;Bump. LD HL,BIG$DISK ;16 bit numbers? INC (HL) JP Z,FILLZ1 ADD A,A ;Yes, adjust for this. FILLZ1: DEC (HL) ;Restore this of course. CALL GET$D0 ;Point to start of block storage. LD C,A LD B,0 ADD HL,BC ;Move to start of field to be zeroed. LD A,16 ;Max field length. FILLZ2: CP C ;Reached end? RET Z ;...yex. LD (HL),B ;Nope, stuff one more zero. INC HL ;Bump pointer. INC C ;Decrement counter. JP FILLZ2 ; ; Create or update a directory label for the specified drive. ; IF BANKED DIRLABEL:CALL AUTOWRIT ;Select this drive for writing. LD HL,(@VINFO) ;Set first byte to a time/date stamp. LD (HL),21H ;See if any are present on this drive. LD C,1 ;Set search limit. CALL FINDFST ;Try to find this. JP NZ,DIRLBL1 ;...yes. If not, then it is not legal to enable tem. CALL GET$EX ;Move to the Label data type byte. LD A,(HL) ;Check for date/time stamping. AND 070H ;Yes? JP NZ,RETERROR ;This is not allowed. DIRLBL1:LD HL,(@VINFO) ;Okay, search for the disk label. LD (HL),20H LD C,1 CALL CLRALTER ;Also accept an empty in case there is none. CALL FINDFST ;Look for it. JP NZ,DIRLBL2 ;OKAY. LD A,0FFH ;Nope, disable alternate name matches and LD (@@XFCB),A ;look for an empty entry for this. CALL GETEMPTY RET Z ;Not found, return with error already set. CALL PSWUPD ;Setup a password entry. LD BC,24 ;Set label creation date/time. CALL STAMPIT CALL CRSTAMP DIRLBL2:LD BC,28 ;Set label update date/time stamp. CALL STAMPIT CALL UPSTAMP CALL CKPSWRD ;Check that supplied password is okay. JP NZ,SETPSW2 ;Password error. LD BC,0 ;Update the label now. CALL DIRUPD LD A,(DE) ;Get label data byte. OR 1 ;Set "label exists" bit. LD (HL),A ;And store. PUSH HL LD HL,(SCRATCH7);Also move this into drive password mode LD (HL),A ;flag byte. POP HL DIRLBL3:LD A,(DE) ;Is there a new password to be used? AND 1 JP Z,DIRLBL4 ;Nope. LD DE,8 ;Yes, it follows the old one. CALL BUMPDMA CALL MOVEPSWD ;Move it into place. LD (HL),B ;Save check-sum. LD DE,-8 ;Reset the DMA address. CALL BUMPDMA DIRLBL4:CALL SAVEHASH ;Update the hash tables for this entry JP DIRWRITE ;and write this put to the disk. ENDIF ; ; Return the directory label data (function #101). ; GETLABEL:CALL SLCTSAV ;Select disk (e) and make it active. CALL GETSCR7 ;Get the label data byte. JP SAVESTAT ;All done. ; ; Read file date stamps and password mode (function #102). ; RD$DATE:CALL AUTOWRIT ;Select drive. CALL ANYWILDS ;No wild cards allowed. CALL CLREXT ;Zero the extent and S2 bytes. CALL FINDNAME ;Find this file. RET Z ;None? CALL GET$D0 ;Zero the password field in users area. LD BC,8 CALL FILL$C PUSH HL LD C,0 ;Get to start of SFCB for this file. CALL GETFIELD OR A ;Exists? JP NZ,RDATE1 ;Nope. POP DE EX DE,HL ;Okay, move the first eight bytes into the LD C,8 ;users space as is. IF BANKED CALL MOVE$C LD A,(DE) ;Get password mode byte. JP RDATE2 ELSE JP MOVE$C ENDIF RDATE1: POP HL ;No stamp exists, zero the users area. LD BC,8 IF BANKED CALL FILL$C CALL PSWDSRCH ;Search for a password somewhere else. RET Z ;Nothing, just return zeros. LD A,(HL) ;Okay, get password mode byte. RDATE2: CALL GET$EX ;Move (a) into the password mode field LD (HL),A ;and return. RET ELSE JP FILL$C ENDIF ; ; Write a file XFCB (time/date stamp and password). ; IF BANKED WRT$XFCB:CALL AUTOWRIT ;Select the drive. CALL GETSCR7 ;Get mode byte for this disk. RLA ;Passwords requiredd? JP NC,RETERROR ;Nope, what are we doing then? CALL ANYWILDS ;Okay, be sure no wild cards have been used. CALL GET$EX ;Get the password mode from the users XFCB. LD B,(HL) PUSH HL PUSH BC CALL CLREXT ;Zero the mode out. CALL FINDNAME ;Look for the file name. POP BC POP HL LD (HL),B ;Restore the password mode. RET Z ;No matching name found??? CALL CLRALTER ;Okay, search for a password (and accept an CALL PSWDMODE ;empty if need be). OR A ;Did we already find the password stamp? JP Z,WXFCB6 ;...yes. CALL PSWDSRCH ;Nope, go look for it. JP NZ,WXFCB2 ;Okay, we found it. WXFCB1: LD A,0FFH ;None found. Look again. LD (@@XFCB),A ;(do not accept any substitutes) CALL SRCHFST RET Z ;Nothing? CALL GETEMPTY ;Okay, find an empty slot. RET Z ;None? CALL PSWUPD ;Update directory for the password. WXFCB2: CALL CKPSWRD ;Was a valid password given? JP NZ,SETPSW2 ;Nope, error. PUSH HL CALL GET$EX ;Point to new password mode byte. POP DE EX DE,HL LD A,(HL) OR A JP NZ,WXFCB3 LD A,(DE) ;Is a new password desired? AND 1 JP NZ,WXFCB3 ;...yes. CALL DIRLBL4 ;Nope, update our hash tables now. JP WXFCB5 WXFCB3: LD A,(DE) ;Check to see if any password modes have AND 0E0H ;been enabled? JP NZ,WXFCB4 LD A,080H ;Assume read mode if nothing given. WXFCB4: LD (HL),A ;Update the mode byte and move the new CALL DIRLBL3 ;password into place. WXFCB5: CALL STPSWBIT ;Set the password exists bit. DEC A ;Remove bit 0 and save in our space. LD (PSWMODE),A CALL CLREXT ;Clear the mode byte in the FCB. CALL FINDNAME ;Look for a file. RET Z ;None found? CALL PSWDMODE ;Get current password mode. OR A ;None? RET NZ ;Correct, do no mor. LD A,(PSWMODE) ;Okay, move the new mode word into place LD (HL),A ;and write this back out. JP DIRWRITE ; ; Found a valid password XFCB (maybe). ; WXFCB6: LD A,(HL) PUSH AF ;Save mode byte. CALL PSWDSRCH ;Search for he password. POP BC JP Z,WXFCB1 ;None, just use an empty. LD (HL),B ;Okay, restore this mode byte. JP WXFCB2 ENDIF ; ; Set date and time (function #104). ; DATETIME:LD HL,@DATE ;Move the date and time data into here. CALL MOVE4 ;Move all 4 bytes. LD (HL),0 ;Set the seconds field to zero (see pg 134). LD C,0FFH ;Also tell the BIOS. JP ?TIM ; ; Get the date and time (function #105). ; TIMEDATE:LD C,0 ;Set "get" function. CALL ?TIM ;Ask the BIOS. LD HL,@DATE ;Now move it from here into the users EX DE,HL ;space. CALL MOVE4 ;Move all 4 bytes. LD A,(DE) ;Get the seconds field and return it in (a). JP SAVESTAT ; ; Move four bytes from (de) to (hl). Registers are left at the end of ; the fields. ; MOVE4: LD C,4 JP MOVE$C ; ; Set the default password to the 8 character string at ; (de). This will be used when passwords are not supplied ; with the other commands. ; IF BANKED SETPSWD:LD HL,PSWMODE+10 EX DE,HL LD BC,8 PUSH HL JP ENCODE ENDIF ; ; Get serial number (at base of BDOS) and move it into ; ram at (de). It is 6 bytes long. ; GETSERL:LD HL,BNKBDOS ;Serial number is here (base of BDOS). EX DE,HL LD C,6 ;Now move it into place. JP MOVE$C ; ; Get or set program return code. If (de)=ffff, then this ; is a GET request. Otherwise (de) will be set as the ; return code. ; GT$STRTN:LD A,D ;Check for a GET request. AND E INC A LD HL,(@RTNCODE) JP Z,STORE$HL ;...yes, return current value. EX DE,HL ;Nope, set value to (de) and reeturn. LD (@RTNCODE),HL RET SET$SPCL:LD HL,0FFFFH ;Set the special error return code. LD (RET$STAT),HL ; ; Main command return location. The return status must ; already be set in (RET$STAT). ; MAIN$RET:LD A,(@RESEL) ;Do we have to update the users FCB? OR A JP Z,MRET01 ;Nope. LD HL,(@VINFO) ;Yes, move the drive byte into it. LD A,(DRVBYTE) LD (HL),A IF BANKED LD DE,7 ;Now move 'F7 bit into it. ADD HL,DE LD A,(HOLDF7) OR (HL) LD (HL),A INC HL ;And ditto the 'F8 bit. ELSE LD DE,8 ADD HL,DE ENDIF LD A,(HOLDF8) OR (HL) LD (HL),A ; ; Restore the users stack. Get the return status and go back home. ; MRET01: LD HL,(USR$STK) ;Restore users stack pointer. LD SP,HL LD HL,(RET$STAT);Get return status code and return. LD A,L LD B,H RET ; ; Main data storage area for the disk fil system. ; MT: DEFB 0E5H ;Empty entry flag byte. RO$VECT:DEFB 0,0 ;Drive read-only vector storage. LOGINVEC:DEFB 0,0 ;Drive login vector storage. IF NOT BANKED @@USRDMA: @@BUFAD:DEFB 0,0 ENDIF DIRBUF: DEFB 0,0 SCRATCH0:DEFB 0,0 ;Addresses of various scratch areas used SCRATCH2:DEFB 0,0 ;by the BDOS. SCRATCH4:DEFB 0,0 SCRATCH7:DEFB 0,0 ;Bit 1 means passwords enabled for this drive. SCRATCH8:DEFB 0,0 ;Bit 0 means directory changed. DPB: DEFB 0,0 ;Address of parameter block. CSV: DEFB 0,0 ;Addr of checksum vector. ALV: DEFB 0,0 ;Addr of allocation vector. DIRBCB: DEFB 0,0 ;Addr of directory buffer control block (head). DTABCB: DEFB 0,0 ;Addr of data BCB list head. HASH: DEFB 0,0 ;Addr of hash table. HASHBANK:DEFB 0 ;Memory bank containing hash table (bnk 1 not allowed). ; SPT: DEFB 0,0 ;Users disk parameter block. BSH: DEFB 0 BLM: DEFB 0 EXM: DEFB 0 DSM: DEFB 0,0 DRM: DEFB 0,0 AL0: DEFB 0,0 CKS: DEFB 0,0 OFF: DEFB 0,0 PSH: DEFB 0 PHM: DEFB 0 ; DIRSECT:DEFB 0,0 ;Relative sector for directory entry. RELSEC: DEFB 0 BUFFLG: DEFB 0 ; ; Note order of next three bytes cannot be changed. ; BUFDRV: DEFB 0 ;Drive which owns the buffer. BUFBLK: DEFB 0,0 ;Current block number. ; BUFREC: DEFB 0 ;Record number. REMAINS:DEFB 0 TRANSLAT:DEFB 0,0 RDWRTFLG:DEFB 0 FNDSTAT:DEFB 0 SAVE$E: DEFB 0 RELBLOCK:DEFB 0 ;Relative block # in FCB (0-15 or 0-7). IF BANKED SRCHFCB:DEFB 0,0 PSWDFLG:DEFB 0 ENDIF BIG$DISK:DEFB 0 ;Set to ff for 8 bit block numbers. DRIVE: DEFB 0 SAVNXT: DEFB 0 ;Extent byte (original). SAVEXT: DEFB 0 ;Extent number (masked). TEMP001:DEFB 0 SAVNREC:DEFB 0 ;Current record number. ACTIVE: DEFB 255 ; ; Note, the next four bytes are in a special order. They cannot be ; changed. ; CURDRIVE:DEFB 255 ;Current drive selected. CURBLOCK:DEFB 0,0,0 ; RAN$REC:DEFB 0,0,0 LOGSECT:DEFB 0,0 ;Logical sector number. FILEATR:DEFB 0 ;File attribute bits (f8-t3). IODIRECT:DEFB 0 HOLDF8: DEFB 0 IF BANKED HOLDF7: DEFB 0 ENDIF REL$ADDR:DEFB 0 TEMP01: DEFB 0,0,0,0 IF BANKED MOVFLAG:DEFB 0 ;FCB changed flag and must be moved into users area (=0). ELSE @@SRCH: DEFB 0,0 @@ALTER:DEFB 0 LFD18H: DEFB 0 ENDIF FROMUSR0:DEFB 0 USER0: DEFB 0 DRVBYTE:DEFB 0 ;Drive byte of selected drive. NXT$IO: DEFB 15,16,17,19 ;Functions that invalidate a "search next" function. DEFB 22,23,30,35,99,100,102,103,0 RDWT$IO:DEFB 20,21,33,34 ;Disk read/write functions. DEFB 40,41,0 DIR$IO: DEFB 16,18,0 ;Close and search next functions. IF BANKED TEMPFCB:DEFB 0,0,0,0 ;Temp storage for an FCB (used for password searches). DEFB 0,0,0,0,0,0,0,0,0 ; ; Passowrd storage. ; PSWMODE:DEFB 0,0,0 DEFB 0,0,0,0,0,0,0,0 ENDIF RBLOCK: DEFB 0 BCBADR: DEFB 0,0 IF BANKED BCBSAV: DEFB 0,0 ;Address of Buffer Control Block. BCBLNK: DEFB 0,0 FRSTMT: DEFB 0,0 ;First empty disk buffer. FRSTAVIL:DEFB 0,0 ;First available disk buffer (not empty). BCB$BNK:DEFB 0 ENDIF CURTRACK:DEFB 0,0 CURSECTR:DEFB 0,0 ; ; Data buffer access routine. Enter with access code in (a). ; =1, Read data BCB. ; =2, Write data BCB. ; =4, Flush all data BCB's for current drive. ; DATBCBIO:LD HL,(DTABCB) ;Get address of BCB chain. IF BANKED CP 4 ;Flush request? JP NZ,BCBIO ;Nope, use main routine. ; ; Flush all BCB for the current drive that have been written to. ; FLSHBF1:LD E,(HL) ;Get address of start of chain. INC HL LD D,(HL) LD HL,0FFFFH ;Set flag for nothing written as yet. LD (CURTRACK),HL EX DE,HL FLSHBF2:LD A,(CURDRIVE) ;Does this BCB reference the same drive? CP (HL) JP NZ,FLSHBF3 ;Nope, go to next. EX DE,HL ;Yes, check the "written to" flag. LD HL,4 ADD HL,DE LD A,(HL) EX DE,HL INC A ;Was it written to? JP NZ,FLSHBF3 ;Nope, skip then. PUSH HL ;Yes, get track number for this block. INC DE INC DE EX DE,HL LD E,(HL) INC HL LD D,(HL) LD HL,(CURTRACK);Compare track with previously found track. CALL SUB$HL ;Is this a closer track? POP HL JP NC,FLSHBF3 ;Nope, skip. EX DE,HL ;Yes, save this track and BCB address. LD (CURTRACK),HL EX DE,HL LD (CURSECTR),HL FLSHBF3:CALL NXTBCB ;Look for the next BCB. JP NZ,FLSHBF2 ;Continue if more available. LD HL,CURTRACK ;Okay, get the track number to see if CALL CKPOS ;anything was found. RET Z ;Nope, we must be done. LD HL,(CURSECTR);Okay, get the address of the BCB with the XOR A ;nearest track and write it out. LD A,4 CALL BCBIO LD HL,(DTABCB) JP FLSHBF1 ;Continue until all have been written. ENDIF ; ; Buffer Control Block (BCB) access routine. The address must ; be in (hl) and the function in (a). ; =1, read sequential. ; =2, write sequential. ; =3, read ; =4, flush buffer. ; =5, write (special). ; BCBIO: PUSH AF ;Save function number. CALL GET$PHM ;Get physical record mask (b), (c)=compliment. LD A,(CURBLOCK) ;Compute relative block within buffer. LD E,A AND B LD (RBLOCK),A ;Save relative block number. LD A,E AND C ;Save base block number (start of buffer). LD (CURBLOCK),A IF BANKED POP AF PUSH AF CALL NZ,FINDBCB ;Find buffer address. ENDIF LD (BCBADR),HL ;Save it. CALL GETBUFF ;Get buffer address. LD (@@BUFAD),HL ;Save it in common. CALL ACCBCB ;Access BCB now. LD A,(HL) ;Get drive byte. INC A ;Used? JP Z,BCBIO3 ;Nope. POP AF ;Yes, check original function. PUSH AF CP 4 ;Greater than 3? JP NC,BCBIO1 ;...yes, don't compare specifics. ; ; Patch #001. Use to be "call comp$c". ; CALL PATCH2 ;Nope, is this block for the current drive? ; JP Z,BCBIO7 ;...yes. XOR A ;Clear this for sure. BCBIO1: CALL BCBWFLG ;Point to the "written to" flag. CP 5 ;Function #5? JP Z,BCBIO2 ;Yes, write the buffer even if not written to. LD A,(HL) ;Buffer written to? OR A JP Z,BCBIO3 ;...nope. ; ; Write out the buffer. ; BCBIO2: LD (HL),0 ;Clear the written to flag byte. LD HL,(CURBLOCK);Save current data. PUSH HL LD A,(CURBLOCK+2) PUSH AF CALL ACCBCB ;Set disk parameters to that of the buffer. EX DE,HL CALL MOVE$C LD HL,ACTIVE ;Select the drive if it is not active. LD A,(CURDRIVE) CP (HL) CALL NZ,SLCT$IT LD A,1 ;Set write mode. CALL Z,BUFIO ;Write if the select was successful. POP BC ;Reset the disk parameters POP DE CALL LOAD$BLK CALL SETDSK ;Re-select the active disk also. BCBIO3: POP AF CP 4 RET NC PUSH AF CP 2 JP NZ,BCBIO4 LD HL,BUFFLG LD A,(RELSEC) CP (HL) JP NC,BCBIO5 ; ; Patch #001. Used to be "ld hl,(bcbadr)". ; BCBIO4: CALL PATCH3 ;Set buffer unallocated ; LD (HL),0FFH LD A,2 ;Set read mode. JP BCBIO6 BCBIO5: INC A LD (HL),A XOR A ;Clear (no actual i/o). BCBIO6: CALL BUFIO ;Read or write buffer. CALL ACCBCB ;Setup initial 4 bytes of BCB. CALL MOVE$C LD (HL),0 ;Clear the "written-to" flag. IF BANKED INC HL ;Set the (oo) byte to zero if we are at the CALL EXTPHM ;beginning of a block, or to (sector$size/128). ENDIF BCBIO7: LD A,(RBLOCK) ;Get relative block number. INC A ;Now compute relative address (128 bytes per LD DE,128 ;these blocks). LD HL,-128 BCBIO8: ADD HL,DE DEC A JP NZ,BCBIO8 EX DE,HL ;Now add this the start of the buffer. LD HL,(@@BUFAD) ADD HL,DE POP AF ;Check original function. CP 3 ;Function #3? JP NZ,BCBIO9 ;Nope. LD (DIRBUF),HL ;Just save address of data and return. RET BCBIO9: EX DE,HL LD HL,(@CRDMA) ;Get DMA address. LD BC,128 CP 1 ;Check function. Read sequential? IF BANKED JP NZ,BCBIO10 ;Nope. LD A,(@COMMON+1);Yes, need to switch memory banks? DEC A ;(is buffer in common memory?) CP D JP C,@@BANK1 ;(yes), don't have to switch. LD A,(BCB$BNK) ;Get buffer bank. LD C,A LD B,1 ;Move data into this bank. CALL XMOVE ;Prepare for the bank-to-bank move. LD BC,128 ;Set byte count. JP @@BANK1 ;Now go move it. BCBIO10:EX DE,HL ;Process a sequential write here. LD A,(@COMMON+1);Need to switch banks? DEC A CP H JP C,BCBIO11 ;...nope. LD A,(BCB$BNK) ;Yes, get buffer bank. LD B,A LD C,1 ;Move into this bank. CALL XMOVE ;Prepare for bank-to-bank move. LD BC,128 ;Set byte count. BCBIO11:CALL @@BANK1 ;Move the data into our buffer. ELSE JP Z,?MOV EX DE,HL CALL ?MOV ENDIF CALL BCBWFLG ;Say buffer has been written to. LD (HL),0FFH RET ; ; Get physical record mask into (b), compliment into (c). ; GET$PHM:LD A,(PHM) LD B,A CPL LD C,A RET ; ; Access the BCB. Set (hl) to its basse address, (de) to the spects ; for the current drive, and (c) to 4 and return. This is a general ; register setup routine. ; ACCBCB: LD HL,(BCBADR) ;Get address of the BCB. LD DE,CURDRIVE ;Now the current drive stuff. LD C,4 ;Set compare count. RET ; ; Point to the BCB written flag byte (0=not written to). ; BCBWFLG:LD DE,4 ;Set offset. LD HL,(BCBADR) ;Get base address. ADD HL,DE ;Adjust. RET ; ; Move block from (de) to (hl). Registers (de) and (hl) are ; preserved. ; IF BANKED XMOVE: PUSH HL ;Save regs. PUSH DE CALL ?XMOV ;Use the BIOS move routine. POP DE ;Restore regs. POP HL RET ENDIF ; ; Read or write to a Buffer Control Block. If (a)=1, then we will ; write. If (a) > 1 then we will read. Otherwise, no I/O takes ; place. ; BUFIO: PUSH AF ;Save access code. CALL TRK$SEC ;Set track and sector. IF BANKED LD A,(BCB$BNK) ;Select the proper bank. CALL ?STBNK ENDIF LD C,1 ;Set access mode. POP AF ;Read or write? DEC A JP Z,DSKWRITE CALL P,DSKREAD ;Read unless (a) was zero. CALL BCBWFLG ;Move track and sector info into block. INC HL INC HL LD DE,CURTRACK LD C,4 JP MOVE$C ; ; System Control Block for Non-Banked systems. ; IF NOT BANKED ; ; Patch area #001. ; ; Extension of the file close routine. Set a flag saying that ; this is or is not a permanently mounted drive. ; PATCH1: LD A,(CKS+1) ;Check bit 15 of CKS vector. SCB$BASE: RLA ;Is this drive permanently mounted? JP C,COMPEXT ;Yes, just go compute extent. LD A,0FFH ;No it's not, set flag then go LD (PERMFLG),A ;compute extent. JP COMPEXT ; ; Patch to see if the drive is permanently mounted before checking ; specific parameters. ; PATCH2: CP 3 ;Reading? JP NZ,COMP$C ;Nope, don't care. Just check parms. LD A,(PERMFLG) ;Yes, is device permanent? OR A JP Z,COMP$C ;Yep, just check specifics. POP HL ;Nope, waste original PSW and just JP BCBIO4 ;read the buffer. ; ; Clear the permanent flag byte and then return the BCB ; address in (hl). ; PATCH3: XOR A ;Clear the flag. LD (PERMFLG),A LD HL,(BCBADR) ;Get BCB address. RET ;And we are done. ; PERMFLG:DEFB 0 ;Flag byte (0=permanently mounted drive). ; DEFB 0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 @STAMP: DEFB 0,0 ;Vector for drives that have been stamped. @RELOG: DEFB 0,0 ;Vector for drives stamped and re-loged. DEFB 0,0,0,2 DEFW ??BDOS DEFB 0AFH,0C9H ; ; "Published" System Control Block starts here. ; @HSHCK: DEFB 0 ;Hash check byte. @HSHDRV:DEFB 0 ;Drive compare byte. @HSHNAME:DEFB 0,0 ;Filename code bytes. @HSHEXT:DEFB 0 ;Extent code byte. @VERSION:DEFB 31H,0,0,0,0,0,0;CP/M version number storage. DEFB 0,0,0,0 @RTNCODE:DEFB 0,0 ;Return code storage. DEFB 0,0,0,0,0 @CHAIN: DEFB 0 ;Program chain flag byte. @SVBUF: DEFB 0,0 ;Flag saying to use previous line buffer. @WIDTH: DEFB 0 ;Console width byte. @COLUMN:DEFB 0 ;Console cursor column number. DEFB 0,0 @BUFPTR:DEFB 0,0 ;Input line pointer. @POINTR:DEFB 0,0 ;Keyboard input pointer location. @CIVEC: DEFB 0,0 ;Console input redirection flag. @COVEC: DEFB 0,0 ;Console output redirection flag. @AIVEC: DEFB 0,0 ;Auxillary input redirection flag. @AOVEC: DEFB 0,0 ;Auxillary output redirection flag. @LOVEC: DEFB 0,0 ;List output redirection flag. DEFB 0,0 @CTRLH: DEFB 0 ;Control-H active flag. @RUBOUT:DEFB 0 ;Rubout active flag. @KEYST: DEFB 0 ;Submit mode keyboard status byte. DEFB 0,0 ; @MODE: DEFB 0,0 ;Console mode bytes. @BNKBF: DEFB 0,0 ; @DELIM: DEFB '$' ;Print string delimiter. @OUTFLG:DEFB 0 ;List output flag. @KEYLK: DEFB 0 ;Keyboard lock byte. DEFW @HSHCK ;Base address of SCB table. @CRDMA: DEFW 80H ;Current DMA address. @CRDSK: DEFB 0 ;Current disk. @@BUFFR: @VINFO: DEFB 0,0 ;(de) registers on entry to this BDOS. @RESEL: DEFB 0 ;Flag byte indicating a file i/o function. @MEDCHG:DEFB 0 ;Media change flag byte. @FX: DEFB 0 ;BDOS function number. @USRCD: DEFB 0 ;Current user number. @ENTRY: DEFB 0,0 ;Main file position entry storage. SRCHFCB:DEFB 0,0 @MATCH: DEFB 0 ; @MLTIO: DEFB 1 ;Multi-sector count byte. @ERMDE: DEFB 0 ;Error mode flag byte. DEFB 0,0FFH,0FFH,0FFH,0 @ERDSK: DEFB 0 ;Error disk. DEFB 0,0 @MEDIA: DEFB 0 ;Possible media change flag (door open). DEFB 0,0 @BFLGS: DEFB 0 ;BDOS flags. @DATE: DEFB 0FFH,0FFH ;System date. @HOUR: DEFB 0FFH ;System hour. @MIN: DEFB 0FFH ;Minute. @SEC: DEFB 0FFH ;Second. @COMMON:DEFB 0,0 ;Base of common memory, ?ERJMP: JP ??ERR ;BDOS error handler. @MXTPA: DEFW ??BDOS ;End of usable memory. ENDIF ; ; Find a Buffer Control Block (BCB). ; IF BANKED FINDBCB:LD (BCBLNK),HL LD DE,-13 ;Point to start of BCB and save. ADD HL,DE LD (BCBSAV),HL CALL NXTBCB ;Point to first block in chain. PUSH HL CALL NXTBCB ;Get address of next one. POP HL RET Z ;None found? EX DE,HL LD HL,0 ;Clear empty and available pointers. LD (FRSTMT),HL LD (FRSTAVIL),HL EX DE,HL ; ; Search link list for a matching entry. Save location of last empty ; or first available buffer of the same size. ; SRCHLST:LD (BCBADR),HL ;Save address. CALL ACCBCB ;Same as what we are looking for? CALL COMP$C JP Z,SRCHL7 ;...yes. LD HL,(BCBADR) ;Is this one empty? LD A,(HL) INC A JP NZ,SRCHL1 EX DE,HL ;Yes, save its location. LD HL,(BCBSAV) LD (FRSTMT),HL JP SRCHL2 SRCHL1: LD A,(CURDRIVE) ;Does this buffer belong to the current drive? CP (HL) JP NZ,SRCHL3 EX DE,HL ;...yes. Is blocking required? LD HL,5 ADD HL,DE LD A,(PHM) OR A JP Z,SRCHL2 CP (HL) ;Yes, is this buffer the same size? JP NZ,SRCHL2 LD HL,(FRSTAVIL);Yes, have we already seen an available one? LD A,L OR H JP NZ,SRCHL2 LD HL,(BCBSAV) ;Nope, save this location. LD (FRSTAVIL),HL SRCHL2: EX DE,HL SRCHL3: PUSH HL CALL NXTBCB ;Get address of next BCB. POP DE JP Z,SRCHL4 ;...none remaining. EX DE,HL ;Okay, continue the search. LD (BCBSAV),HL EX DE,HL JP SRCHLST ; ; A matching entry was not found. Save the first available or the ; last empty if possible. ; SRCHL4: LD HL,(FRSTAVIL);Did we find an available one? LD A,L OR H JP NZ,SRCHL5 ;..yes, save it then. LD HL,(FRSTMT) ;Nope, how about an empty? LD A,L OR H JP Z,SRCHL6 ;...nope, can't save anything. SRCHL5: LD (BCBSAV),HL ;Okay, save this buffer. SRCHL6: LD HL,(BCBSAV) CALL NXTBCB LD (BCBADR),HL CALL NXTBCB ;Get address of check-sum vector. EX DE,HL CALL STCKSM ;Store the check-sum vector address. LD HL,(BCBLNK) ;Stuff the link address next. LD E,(HL) ;Extract address of next BCB. INC HL LD D,(HL) LD HL,(BCBADR) ;Now stuff it into this other BCB. LD BC,13 ADD HL,BC LD (HL),E INC HL LD (HL),D LD HL,(BCBADR) ;Now re-assign this link address. EX DE,HL LD HL,(BCBLNK) LD (HL),E INC HL LD (HL),D EX DE,HL RET SRCHL7: LD HL,(BCBADR) ;Check relative block for this buffer. LD DE,5 ADD HL,DE LD A,(RBLOCK) CP (HL) ;The same? JP Z,SRCHL8 ;...yes. INC (HL) ;Nope, but is it the same as the next one? CP (HL) JP Z,SRCHL8 ;...yes. CALL EXTPHM ;Nope, set block number. SRCHL8: LD HL,(BCBADR) ;Does this BCB link the the one at BCBLNK? EX DE,HL LD HL,(BCBLNK) LD A,(HL) INC HL LD L,(HL) LD H,A CALL SUB$HL OR L EX DE,HL RET Z ;Yes, then we are done. JP SRCHL6 ; ; Store check-sum vector (de) in DPH. ; STCKSM: LD HL,(BCBSAV) ;Get address of DPH. LD BC,13 ;Move to check-sum vector area. ADD HL,BC LD (HL),E ;And store it. INC HL LD (HL),D RET ; ; Move to the next BCB in the chain. Set the zero flag if this ; is the last one (hl=0). Return the address of the next one in (hl). ; NXTBCB: LD BC,13 ;Offset to chain address. ADD HL,BC LD E,(HL) ;Extract addrss of next BCB. INC HL LD D,(HL) EX DE,HL ;Return address in (hl). LD A,H ;Set zero flag if there is no more. OR L RET ; ; Move relative block into (hl) unless it is non zero. Then move ; the number of 128 byte sectors per physical block (PHM). ; EXTPHM: LD A,(RBLOCK) ;Get relative block. LD (HL),A ;Move it. OR A ;Zero? RET Z LD A,(PHM) ;Nope, get this instead. INC A ;Adjust for the -1 initially. LD (HL),A ;And save it. RET ENDIF ; ; Setup the hash data for the fcb at (hl) and store ; the data at address at (de) in bank (HASHBANK). ; SETHASH:PUSH HL ;Save fcb address. PUSH DE CALL GENHASH ;Generate hash data for fcb at (hl). POP HL LD DE,@HSHDRV ;Now move this data into the hash table. LD BC,4 ;### Move 4 bytes. IF BANKED LD A,(HASHBANK) ;Get memory bank for has tables. CALL @@MOVE ELSE CALL ?MOV ENDIF LD (LOGSECT),HL ;Save next address. POP HL ;Restore fcb address. RET ; ; Set hashing for an (a) character search limit. ; STHASH: OR A ;Determine extent of hash match reqd. RET Z ;None? CP 12 ;Less than full name? JP C,STHSH3 ;Yes, check drive only. LD A,2 ;Check drive and name only? JP Z,STHSH1 ;...yes. LD A,3 ;Nope, check extent also. STHSH1: LD (@HSHCK),A ;Save search type byte. EX DE,HL CALL HASHING ;Is hashing enabled? RET Z EX DE,HL LD A,(@FX) ;Check BDOS function being processed. CP 16 ;Close file? JP Z,GENHASH ;...yes. CP 35 ;Compute file size? JP Z,STHSH2 ;...yes. CP 20 ;Open, search, delete? JP NC,GENHASH ;...nope, use ode as is. ; ; For file searches, opens, deletes, always match the ; file name and drive bytes unless there are wild cards ; present. In this case, only check the drive byte. ; STHSH2: LD A,2 ;Set the check drive and name. LD (@HSHCK),A PUSH HL CALL WILDS ;Any wild cards present? POP HL JP NZ,GENHASH ;Nope, generate hash data now. STHSH3: XOR A ;Set to match the drive byte only. LD (@HSHCK),A ; ; Generate the hash data to search for a specified file. ; The file is divided into three sections. The drive ; code (including passwords), the file name, and the ; extent byte. Each section is encoded into separate ; entries into the hash tables. A search byte tells the ; resident BDOS which parts need to match. ; GENHASH:LD A,(HL) ;Stuff drive code into hash block. LD (@HSHDRV),A INC HL EX DE,HL LD HL,0 ;Is this entry a label or time/date stamp? AND 020H JP NZ,GENHSH5 ;Yes, no name to encode. ; ; Generate a hash word based on the filename and ; extension bytes. This is similar to the CRC code ; that disk controllers use. This results in a 16 bit ; word that represents this file entry (this is not ; always a unique word). ; LD BC,0B08H ;(b)=11, (c)=8. GENHSH1:DEC C ;End of file name part? PUSH BC JP Z,GENHSH2 ;...yes. DEC C ;End of extension part? DEC C JP Z,GENHSH2 ;...yes. ADD HL,HL ;Nope, shift (hl) left. ADC A,A ;Save overflow in (a). PUSH AF LD A,B ;Is this an odd or even byte. RRA JP C,GENHSH3 ;...odd. POP AF ;Shift even bytes one more bit. ADD HL,HL ADC A,A GENHSH2:PUSH AF GENHSH3:LD A,(DE) ;Get next byte from file name. AND 07FH SUB 020H ;Make zero relative. RRA ;Even or odd? JP NC,GENHSH4 ;...even. RLA ;Odd, restore original byte. GENHSH4:LD C,A ;Now add (a) into sum word (hl). LD B,0 POP AF ADD HL,BC ADC A,0 ;Keep overflow here too. POP BC INC DE DEC B ;More characcters to check? JP NZ,GENHSH1 GENHSH5:LD (@HSHNAME),HL;Nope, save (hl) as hash data for filename. LD HL,@HSHDRV ;Move right 2 bits from overflow into drive byte. AND 3 RRCA RRCA OR (HL) ;Add to current drive code. LD (HL),A AND 020H ;Is a filename present? JP NZ,GENHSH8 ;...nope. LD A,(DE) ;Yes, get extent byte. AND 01FH LD C,A INC DE INC DE LD A,(DE) ;Now get the S2 byte. AND 03FH RRCA ;Move bits 0,1,2 into bits 5,6,7. RRCA RRCA LD D,A AND 7 LD B,A LD A,D AND 0E0H OR C LD C,A LD A,(EXM) ;Encode the extent and S2 bytes. GENHSH6:RRA JP NC,GETHSH7 PUSH AF LD A,B RRA LD B,A LD A,C RRA LD C,A POP AF JP GENHSH6 GETHSH7:LD A,B ;Move low overflow bit into hash drive code byte. AND 1 RRCA RRCA GENHSH8:RRCA OR (HL) LD (HL),A ;Save drive code byte with this bit. LD DE,3 ;Now save the extent encoded byte. ADD HL,DE LD (HL),C RET ; ; Is hashing enabled for this drive? Set zero flag ; if not enabled. ; HASHING:LD HL,(HASH) ;Get address of hash table. LD A,L ;Either byte = ff means not enabled. OR H INC A RET ; ; Set search limit for the BDOS hash routines. If @MATCH ; is set to one, then search the entire directory space. ; Else, search allocated space only. ; HSHSRCH:CALL HASHING ;Is hashing enabled? RET Z LD A,(@HSHCK) ;Maybe. INC A RET Z LD A,(@MATCH) ;Yes, any thing to search for? OR A RET Z LD HL,(SCRATCH0);Okay, get num of allocated dir entries. LD E,(HL) INC HL LD D,(HL) EX DE,HL DEC A ;Search entire directory? JP NZ,HSHSRH1 LD HL,(DRM) ;Yes, get limit. HSHSRH1:LD (@@SRCH),HL ;Save search limit. IF BANKED LD A,(HASHBANK) ;Get memory bank with hash tables. ENDIF LD HL,(HASH) ;Get address of table. IF BANKED CALL @@SEARCH ;Now search for the file. JP NZ,HSHSRH2 ;...not found. LD A,(@@DIRFLG) ;Do we need to read in the directory buffer for this? OR A LD C,0 CALL NZ,DIRRDNXT ;...yes, do it then. LD A,(@FX) ;Check BDOS function being processed. SUB 18 ;Search for next entry? RET Z ;...yes. LD A,(@HSHCK) ;Hashing enabled? INC A CALL Z,RSTFILPS ;Nope, reset file position. XOR A ;Clear zero flag (name found) and return. RET ELSE LD B,H LD C,L LD HL,(@@SRCH) ;Get number of directory entries available. EX DE,HL LD HL,(@ENTRY) ;Get starting record number. PUSH HL CALL SUB$HL ;Compute number remaining to search. POP DE OR L ;(hl)=0? RET Z ;...yes, done. PUSH HL ;Save search limit. INC DE ;Bump address. EX DE,HL PUSH HL ;And save on stack. DEC HL ;Point to initial entry (4 bytes each). ADD HL,HL ;*2 ADD HL,HL ;*4 ADD HL,BC ;Add to start of hash table. ; ; Search next entry from (hl). ; HASHSRCH:LD DE,4 ;Point to next one. ADD HL,DE LD DE,@HSHDRV ;Compare first byte (drive code). LD A,(DE) XOR (HL) ;Isolate different bits. AND 01FH ;Only look at drive and password bits now. JP NZ,HSHNXT2 ;...not the same. CALL SAME ;Same drive, now check name and extent bytes. JP Z,HSHNXT4 ;Okay, we found it. ; ; Move on to the next entry. ; HASHNXT:EX DE,HL ;Save pointer to next entry in (de). POP HL HSHNXT1:INC HL ;Increment entry counter. EX (SP),HL ;Now decrement count of entries to search. DEC HL LD A,L OR H EX (SP),HL ;Replace on stack. PUSH HL ;Save entry number. EX DE,HL ;Restore its address and continue until JP NZ,HASHSRCH ;there are no more entries to look at. POP HL ;return. POP HL ENDIF HSHSRH2:CALL CKFILPOS ;Does file position equal ffff? RET NZ CALL CHKTYPE ;Does file have to be present? RET NZ ;...yes, it wasn't. LD A,0FFH ;Say not found and return last allocated space. LD (@HSHCK),A LD HL,(SCRATCH0) LD E,(HL) INC HL LD D,(HL) EX DE,HL DEC HL CALL BEGSECTR ;Set to start of last dir sector. XOR A ;And pretend name was found. RET IF NOT BANKED ; ; Drive bytes did not compare. Check our flags to see if can use ; ignore this drive difference. ; HSHNXT2:LD A,(@@ALTER+1);Get first flag. If this equals ff then INC A ;we will check for an empty entry and JP Z,HSHNXT6 ;save its location. INC A ;If this equaled fe then we will save JP NZ,HASHNXT ;a password entry (if we found one). CALL SAME JP NZ,HASHNXT ;Not the same, just continue searching. LD A,(HL) ;Check user number. AND 01FH JP NZ,HASHNXT ;Not user 0 (or with password), ignore. ; ; A matching entry was found in the table. Save its location so ; Banked BDOS can use this. ; HSHNXT4:LD HL,(@ENTRY) ;Get starting entry into (de). EX DE,HL POP HL ;Get location where we matched+1. DEC HL ;Adjust. LD (@ENTRY),HL ;And save it back in here. POP BC ;Set stack straight. LD A,L ;See if this entry is at the end of a sector. AND 3 CP 3 RET Z ;Yes, just return now. LD A,E ;Back original pointer to the start of a AND 0FCH ;sector. LD E,A LD A,L ;Now do the same for the matching entry. AND 0FCH LD L,A CALL SUB$HL ;Do they start in the same sector? OR L RET Z ;Yes, good. Just return. CALL RDNXT LD A,(@HSHCK) INC A CALL Z,RSTFILPS XOR A RET ; ; Search for an empty entry (?). ; HSHNXT6:LD A,(HL) ;Get drive byte. CP 0F5H ;This would be correct for an empty? JP NZ,HASHNXT ;Not one, just continue. ; ; Save the current entry in an alternate location and then continue ; searching for the real name. This is used to speed accesses to ; passwords and empty locations. ; HSHNXT7:EX DE,HL POP HL LD (@@ALTER),HL ;Store this entry here and continue. JP HSHNXT1 ; ; Check to see if (hl) and (de) point to the same hash entry. ; Note that (SCB) contains either 0,2, or 3. If 0, then only check ; the drive byte. If 2, then drive and name bytes only. If 3 then ; check drive, name, and extent bytes. ; SAME: LD A,(@HSHCK) ;Get check specification byte. OR A ;Zero? RET Z ;Then we are done (a match). LD C,A ;Save for now. RRCA ;Construct mask byte to check bits 5,6,7. RRCA RRCA OR 90H LD B,A ;Save mask. LD A,(DE) ;Get drive byte. XOR (HL) ;Isolate different bits. AND B ;Mask off unused bits. RET NZ ;Not zero? No match then. PUSH HL ;Here we must check either 2 or 3 bytes INC HL ;to see if we have the correct entry. INC DE CALL COMP$C ;Set the zero flg if they are the same. POP HL RET ENDIF ; ; The file at (fcb) was generated at directory position ; (@ENTRY). Save the related hash data into the appropriate ; table so we can look this file up rapidly next time. ; SAVEHASH:CALL HASHING ;Is hashing enabled? RET Z LD HL,TEMP01 ;Yes, save current hash data in safe area. LD DE,@HSHDRV LD BC,4 PUSH HL PUSH DE PUSH BC CALL ?MOV LD HL,(HASH) ;Get address of hash table. PUSH HL CALL FCB2HL ;Get fcb for hashing. CALL GENHASH ;Generate hash data for this fcb. LD HL,(@ENTRY) ;Get its current position in directory. ADD HL,HL ;Point to this area within hash table. ADD HL,HL POP DE ADD HL,DE POP BC POP DE PUSH DE ;Now setup to move new data into hash table. PUSH BC IF BANKED LD A,(HASHBANK) CALL @@MOVE ;Now move the new data in. ELSE CALL ?MOV ENDIF POP BC ;And restore previous hash data. POP HL POP DE JP ?MOV ; ; Patch area #001. ; ; Extension of the file close routine. Set a flag saying that ; this is or is not a permanently mounted drive. ; IF BANKED PATCH1: LD A,(CKS+1) ;Check bit 15 of CKS vector. RLA ;Is this drive permanently mounted? JP C,COMPEXT ;Yes, just go compute extent. LD A,0FFH ;No it's not, set flag then go LD (PERMFLG),A ;compute extent. JP COMPEXT ; ; Patch to see if the drive is permanently mounted before checking ; specific parameters. ; PATCH2: CP 3 ;Reading? JP NZ,COMP$C ;Nope, don't care. Just check parms. LD A,(PERMFLG) ;Yes, is device permanent? OR A JP Z,COMP$C ;Yep, just check specifics. POP HL ;Nope, waste original PSW and just JP BCBIO4 ;read the buffer. ; ; Clear the permanent flag byte and then return the BCB ; address in (hl). ; PATCH3: XOR A ;Clear the flag. LD (PERMFLG),A LD HL,(BCBADR) ;Get BCB address. RET ;And we are done. ; PERMFLG:DEFB 0 ;Flag byte (0=permanently mounted drive). ; ; Fill remainder of page with zeros. ; DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 DEFB 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 ; ; End of patch #001. ; ENDIF ; ;*************************************************************************** ;* * ;* E N D O F C P / M B D O S * ;* * ;*************************************************************************** ; END