;Program name: CFGSUBS.Z80 ;Author: Al Hawley ;Date 10/26/91 ;Previous Date 09/17/91 ;Program function: Subroutines used with ZCNFG ;standard definitions .XLIST ;don't bother listing in PRN INCLUDE SYSDEF .LIST ;symbols from other modules ;from ZCNFG EXT Z3ENV,DEFDU,QUIT EXT COLCNT,ROWCNT,UCFLAG ;from CFGLIB EXT SDELM ;from SYSLIB EXT SETDMA,MA2HC,GUA,SUA,@BDOSA,ISPRINT ;from VLIB EXT VPSTR,STNDOUT,STNDEND ;symbols availale to other modules PUBLIC B2BCD,CLSFIL,CIN,COUT,CST,DEF_FT PUBLIC DEF_DU,DEF_FN,GUA,OPNFIL,RANGE,ISTXTF PUBLIC RDFILE,RDREC,STORDT,STRCPY,ISFNC PUBLIC TYPLIN,VCOUT,WRREC,MOVE2Z,SKIP2Z ;======================================================= DEF_DU: ;provides defaults for undefined D and/or U ;entry- HL = DU with possible undefined values ; BC = default DU ;exit- HL = DU with no ambiguity ; BC preserved LD A,31 ;max user CP L ;usr > max? JR NC,FIXA1 ;no if NC, don't adjust LD L,C ;install default user FIXA1:: LD A,16 ;max drive (1...16) CP H ;drive > max? RET NC ;done if not, else CCF ;reset carry, and LD H,B ;install default drive RET ;======================================================= DEF_FN: ;install the default FileName in the ;target FN field if it is empty. ;entry- DE -> target FCB ; HL -> default FN ;exit- flags NZ = no replacement ; Z = FN field filled ; DE preserved ; B = 0 PUSH DE INC DE ;->FN LD BC,8 ;(length of fn field) LD A,(DE) CP SPC ;if the fn field is still empty, JR NZ,DEFFNX ;(it isn't if nz) LDIR ;use target fn for overlay name DEFFNX: POP DE RET ;========================================================= DEF_FT: ;install the default filetype in the fcb filetype ; field if it is currently filled with spaces. ;on entry, DE -> initialized FCB ; HL -> default file type ;exit- flags NZ = no replacement ; Z = FN field filled ; DE is preserved. ; B = O PUSH DE EX DE,HL LD BC,9 ADD HL,BC LD A,' ' CP A,(HL) ;first char of type blank? JR NZ,FCBTYX ;return if not. User has supplied type EX DE,HL ;de -> fcb+9, hl -> def type LD BC,3 ;3 char to move LDIR ;move 'em FCBTYX: POP DE ;fcb address RET ;======================================================= ; TEST FOR DE WITHIN RANGE RANGE: ;Returns NC if DE is within the range. The range ;of values includes the endpoints. Returns CY set ;if DE > Max or DE < Min ;entry- DE = value to test ; HL = high end of range ; BC = low end of range ;exit- DE and BC preserved ; HL destroyed ; Cy set = out of range, NC within OR A SBC HL,DE ;test high limit RET C ;de higher than max PUSH DE ;save test value EX DE,HL SBC HL,BC ;test lower limit POP DE RET ;cy set = lower than min ;======================================================= ; B2BCD - Convert Binary Byte to BCD B2BCD: ;entry- A = binary value to convert ;exit- A = bcd tens,ones ; B = tens in high nibl ; C = hundreds ; flags, Z = number <100, NZ = number >99 LD BC,0FFFFH ;b,c =-1, rdy for first increment B2BCD1: INC C ;accumulate hundreds SUB 100 JR NC,B2BCD1 ADD 100 ;too much - back up! B2BCD0: INC B ;accumulate 10s SUB 10 JR NC,B2BCD0 ADD 10 ;too much - back up! RLC B ;shift into high nibl RLC B RLC B RLC B OR B ;..and put into high nibl of A INC C DEC C ;return nz if 100s present RET ;..and Z if not ;======================================================= ; CONVERT BINARY TO DATE STRING STORDT: ; BYTE -> 2 ASCII CHAR, 1 POSITION SKIPPED. ; Typically used to fill in '__/__/__' ;entry- HL -> Source (bytes) ; DE -> Destination for ASCII ; B = number of bytes to convert ;exit- HL -> next dest. & source ; DE is preserved PUSH DE STRDT0: PUSH BC ;counter LD A,(HL) CALL MA2HC ;send Hex ASCII to dest. INC DE ;skip a dest. position INC HL ;-> next source byte POP BC ;recover counter DJNZ STRDT0 POP DE RET ;=========================================================== ;CST, CIN, and COUT are replacements for the ;SYSLIB routines of the same name. Whereas SYSLIB ;uses BIOS calls for these functions, the replacements ;here use DOS function 6 calls for console status, ;input, and output. These routines take the place of ;SYSLIB routines with the same name if this module is ;linked ahead of SYSLIB. ;-------------------------- CST: ;console status using DOS function6 with ;Z flag inverted to agree with SYSLIB CST. CALL CST6 ; get FN 6 console stat JR Z,CSTX ; invert the Z flag LD A,1 CSTX: DEC A ; a->0ff if z, a->0 if nz RET ; and flags are readjusted to match ;console status using DOS function 6 ;exit- Z = no character waiting ; NZ = Character waiting CST6: PUSH DE PUSH BC PUSH HL LD E,0FEH ; console status call LD C,6 ; bdos function number CALL BDOS AND A ; anything there? POP HL POP BC POP DE RET ;-------------------------- CIN: ;console input using DOS function 6 ;exit- A contains the character, and NZ ; if A=0 then there was no character ; and Z PUSH DE PUSH BC PUSH HL LD E,0FFH ; get console input LD C,6 CALL BDOS AND A ; will be nz if present POP HL POP BC POP DE RET ;-------------------------- VCOUT: ;console output with highlighting CP 3 ;0,1, or 2? JR NC,COUT ;use cout if not OR A ;00? RET Z ;don't even bother sending! DEC A ;1? (^A) ? JP Z,STNDOUT ;yep, start standout mode & ret JP STNDEND ;else must be end of standout ;-------------------------- COUT: ; COUT - console output using DOS function 6 ;entry- A = char to be output, 0-FCH ;exit- char sent to console ; AF and 8080 registers preserved OR A RET Z ;don't send nulls to console PUSH DE PUSH BC PUSH HL PUSH AF res 7,a ;don't send graphics! CALL TABS LD E,A LD C,6 CALL NC,BDOS POP AF POP HL POP BC POP DE RET ;=========================================================== TABS: ;tabs routine to be called from cout ; NOTE: this routine does not account for ; BS and 7fh characters LD HL,COLCNT ;column counter (in ZCNFG) LD C,(HL) CP TAB JR Z,TABIFY CP CR JR NZ,TABS01 LD C,0 ;CR resets column counter JR TABSX TABS01: CP LF JR NZ,TABS02 INC HL INC (HL) ;increment line counter DEC HL TABS02: CP SPC ;ret cy set for cntl chars CCF ;NC = current char is string to copy ; DE->destination ; B = Max length of string ; C = 0 or special terminator ;exit- A = delimiter ; B = unused locations in dest. ; HL->delimiter ; DE->next unwritten loc in dest. ; the delimiter is not copied. LD A,(HL) CP '$' ;delimiter? RET Z OR A,A ;delimiter? RET Z CP C ;named terminator? RET Z BIT 7,A JR NZ,STRHBS LD (DE),A ;transfer a byte INC HL INC DE DJNZ STRCPY RET STRHBS: RES 7,A ;reset high bit LD (DE),A ;transfer last char INC DE ;next dest DEC B ;count the char RET ;ret hl->delimiting char ;================================================= ; PRINT NULL TERMINATED STRING TYPLIN: EX DE,HL CALL VPSTR EX DE,HL RET ;========================================================= MOVE2Z: ;copy a null terminated string from (HL) ;to (DE). Don't copy the null. Ret HL->null ;entry- HL -> source ; DE -> destination ;exit- AF = 0,Z,NC ; BC,DE,HL used LD A,(HL) OR A RET Z LDI JR MOVE2Z ;========================================================= SKIP2Z: ;scan until binary zero. ;entry- HL-> null or null terminated string ;exit- AF = 0,Z,NC ; HL-> byte following the 0. LD A,(HL) INC HL OR A JR NZ,SKIP2Z RET ;================================================= ISTXTF: ;scan a block of bytes for non-printable ;characters. The block is terminated by ;the byte in A or by the end-of-field. ;If A=-1, then only field length is used. ;entry- HL->start of block ; B = string field length ; A = String terminator byte ;UCFLAG is bitmapped, ; B0 set = UC only ; B7 set = ignore high bit ;exit- ; HL preserved ; flags- Z,NC = all are printable ; B = trailing unused bytes in field ; C = bytes used by string, incl leading sp ; D = leading spaces ; E = String terminator byte ; flags- NZ,C = non printing char found ; BC,DE undefined PUSH HL LD E,A ;save terminator LD C,0 ;string length counter LD D,C ISTXT1: LD A,(HL) CP SPC JR NZ,ISTXT2 INC D ;count leading spaces INC C ; and total spc + str INC HL DJNZ ISTXT1 POP HL RET ;string is all spaces ISTXT2: PUSH DE ;save leading space count LD A,(UCFLAG) LD D,A ;UC only if -1 ISTXT3: ; LD A,(HL) LD A,D AND 80H ;isolate bit 7 CPL ;make high bit mask AND (HL) ;ignore high bit if D7 was 1, ;allowing HBS chars in string. CP E ;end of string? JR Z,ISTXTX INC HL CALL ISPRINT ;printable? SCF ;..in case not JR NZ,ISTXTX ;test for LC if bit 0 of UCFLAG = 1 BIT 0,D ;NZ = CAPS ONLY JR Z,ISTXT4 ;Z = LC is OK CP 61H ;CAP? JR C,ISTXT4 ;Cy=yes, pass it CP '{' ;also pass specials JR C,ISTXTX ;LC is an error ISTXT4: INC C ;count string bytes DJNZ ISTXT3 XOR A ;all printable ISTXTX: POP DE ;leading spaces in D POP HL RET ;================================================= ISFNC: ;determines if a character is part of ;the set which defines a filename. ;This is all characters from "!" to "Z" ;except those listed in the table below. ;entry- A = byte to test ;exit- all regs preserved except F ; NC = character may be part of FN ; C = char is outside the set. cp 5bh ccf ret c ;C = >'Z' cp '!' ret c ;C = < '!' push hl push bc ld hl,nfndat ld bc,nfndend-nfndat cpir ;CY unaffected, still reset pop bc pop hl ret nz ;NZ = not in list scf ;show reject if found ret nfndat: db '%()*,./;:<>=?' nfndend: ;================================================= ; OPEN FILE OPNFIL: ;entry- DE -> file FCB ; user number at (DE-1) ;exit- Z = file not found DEC DE LD A,(DE) INC DE call setusr LD A,15 CALL @BDOSA CP 255 JR RESUSR ;================================================= ; CLOSE FILE ;entry- DE -> file FCB ; user number at (DE-1) CLSFIL: LD A,16 CALL @BDOSA INC A RET NZ LD DE,CLOSER JR ERRORX ;================================================= SETUSR: ;set the user number to that passed in A ;if it is a number <255 CP 0FFH ;is default requested? JP NZ,SUA ;jmp if user specified ;else fall through and set default user ;================================================= ;RESTORE THE DEFAULT USER NUMBER RESUSR: PUSH AF LD A,(DEFDU) CALL SUA POP AF RET ;================================================= ; READ ENTIRE FILE INTO DMA ADDRESS ;entry- DE -> FCB ; HL = DMA address RDFILE: LD BC,128 ;sector size RDF_LP: CALL SETDMA CALL RDREC RET C ;end of file ADD HL,BC JR RDF_LP ;================================================= ; READ NEXT RECORD RDREC: LD A,20 CALL @BDOSA RET Z CP 2 ;check for eof RET C OR 30H ;make ascii LD (RDERRN),A LD DE,READER JR ERRORX ;================================================= ; WRITE NEXT RECORD WRREC: LD A,21 CALL @BDOSA RET Z CP 1 JP Z,DIRFUL OR 30H ;make ascii LD (WRERRN),A LD DE,WRITER JR ERRORX ;================================================= ; DIRECTORY FULL ERROR ENTRY POINT DIRFUL: LD DE,DIRER ERRORX: CALL TYPLIN JP QUIT DIRER: DB 'DIRECTORY FULL',0 CLOSER: DB 'CLOSE ERROR',0 READER: DB CR,LF,'READ ERROR =' RDERRN: DB ' ',0 WRITER: DB CR,LF,'WRITE ERROR =' WRERRN: DB ' ',0 ;================================================= END