title FIND 3.4 name ('FIND') ; ; Some basic settings ; FALSE equ 0 TRUE equ NOT FALSE ; vers equ 34 ; Version number ; RCPM equ FALSE ; True for RCPM use GERMAN equ FALSE ; True for German text ; ; FYNDE.ASM Copyright (C) 1982 ; Universidad Autonoma de Puebla ; ; The original of FIND wasn't copyright and neither is my work ; on it here. Bill Bolton ; ; ------------------------------------------------------------- ; ; Reassembly of FIND.COM, which was originally extracted from ; the CBBS(R) package available from Ward Christensen and Randy ; Suess. However, considerable rearrangement has taken place, ; most notably the following: ; ; * results in a screen of information ; * the search pattern may be a regular expression ; * label+line number as an alternative to line number ; * instance count reported, both per file and globally ; * files listed in a table in the data section at the end are ; automatically excluded ; * squeezed files do not deter the search ; ; To achieve compatibility with MicroShell the vertical bar may ; be replaced by exclamation point; all syntactic elements are ; defined by EQU's and may be redefined. LABEL|PATTERN is ; checked for balanced parentheses and non-null arguments to ; forestall the most common failure modes. Had MicroShell not ; been available, an option to direct the output to some disk ; file would probably have been included. ; ; VERSION LIST, in reverse order for easy on line scanning ; ;28/Sep/97 Added display current file ('?') in quiet mode ; Disable 'LINE' in option -N ; Werner Cirsovius, Hamburg, Germany ; ;04/Feb/95 Added quiet mode, print matching files only ; Werner Cirsovius, Hamburg, Germany ; ;16/Apr/94 Added sorted file list ; Werner Cirsovius, Hamburg, Germany ; ;20/Nov/89 Added Summary Statistic at the end of search ; Werner Cirsovius, Hamburg, Germany ; ;06/Jun/87 Added German help text ; Werner Cirsovius, Hamburg, Germany ; ;23/Oct/84 Added exclusion table code to check for file types ; not to search. Fixed bug when searching large files, ; often started on non-zero extent, which mightly ; confused the file unsqueezing mechanism. Now once a ; suitable file is found to search the extent is ; forced to zero to start. Added conditional code for ; RCPM use to test for SYS and F2 attributes along the ; lines of FIND+. Lifted usage message from FIND+, ; added version number to signon message. Version 2.0 ; Bill Bolton, Software Tools RCPM, Brisbane, ; Australia ; ;04/Jul/84 No false matches with nul lines. Harold V. Mcintosh ; ;01/Jul/84 Scan squeezed files. Harold V. McIntosh ; ;20/Dec/82 Originally written. Harold V. McIntosh ; ; ------------------------------------------------------------- $PRG macro db 'FIND' endm ; $VERS macro db vers/10 + '0','.',vers mod 10 + '0' endm ; null equ 00h CtrlC equ 03h ; Control C tab equ 09h ; Horizontal tab lf equ 0ah ; Line feed cr equ 0dh ; Carriage return EOF equ 1ah ; ^Z eot equ '$' NoMSB equ 01111111b ; ASCII mask HUFFMAN equ 076ffh ; Squeeze code SQ.BYTE equ 090h DECODE equ 0feh ; Delimiters for the command line lsq equ '[' ; Begin alternative list rsq equ ']' ; End alternative list lbr equ '{' ; Begin iterated expression rbr equ '}' ; End iterated expression orr equ '|' ; Separate alternatives ; Representatives of characters or classes. stab equ '_' ; Substitute for tab que equ '?' ; Represent any byte alf equ '@' ; Represent any alphanumeric ; CP/M and other locations and parameters OS equ 0000h ; CP/M's warm start BDOS equ 0005h ; CP/M's BDOS call FCB equ 005ch ; CP/M's file control block DMA equ 0080h ; CP/M's record buffer CCP equ 0080h ; CP/M's command line .drv equ 1 ; Length of drivr .nam equ 8 ; Length of file name .ext equ 3 ; Length of file extension _EX equ 12 ; Pointer to file extent _CR equ 32 ; Pointer to current record DLEN equ 32 ; Length of directory entry reclng equ 128 ; CP/M's record size ksiz equ 255 ; Sector capacity of IN buffer isiz equ ksiz*reclng ; Buffer 2 file extents in memory hsiz equ 256 ; Max characters in Huffman code ; .conout equ 2 ; BDOS Console out .condir equ 6 ; BDOS Direct console in .string equ 9 ; BDOS String out .open equ 15 ; BDOS Open file .srcfrs equ 17 ; BDOS Search for first file .srcnxt equ 18 ; BDOS Search for next file .dskrd equ 20 ; BDOS Sequential read .setdma equ 26 ; BDOS Set DMA buffer .parse equ 152 ; BDOS Parse file name ; _get equ -1 ; Get function ; ===== Start of program ===== aseg org 0100h sub a ; Test correct machine jp po,MachOK ld de,$ILL.MACH ld c,.string call BDOS ; Give message ret ; $ILL.MACH: db 'Z80 CPU required',eot ; MachOK: ld hl,$PRG.ID call mssg ; Message to console ld sp,(BDOS+1) ; Get top for stack ld a,(FCB+.drv) ; Test at least one input cp ' ' jr nz,name.ok ; .. yeap fuse: ld hl,$HELP ferm: call mssg ; Message to console jp OS bad.patt: ld hl,$BAD.PAT ; "bad pattern" jr ferm ; Final (error) message name.ok:: ld hl,CCP ; CP/M's command line ld e,(hl) ; Get length ld d,0 inc de add hl,de ; Point to end ld (hl),d ; Set end marker call proc.opt ; Process options ld bc,.drv+.nam+.ext ld de,$FCB ld hl,FCB ; CP/M's file control block ldir ; Block move ld hl,CCP ; CP/M's command line ld c,(hl) ; .. length inc hl ld a,(OPTSYN) ; Get command sync count ld b,a src.blnk: inc hl dec c ld a,(hl) or a jr z,bad.patt ; .. bad if nothing here cp ' ' jr nz,src.blnk djnz src.blnk ; .. skip possible option inc hl call bala ; Check balance of [], {}. call nula ; Check for null alternatives ld de,patt ; Command line pattern call muve ld de,$DTOT call set.ZERO ; Init ASCII 0 ld hl,0 ld (fcount),hl ; Clear a bit ld (lapo),hl ld hl,patt ; Command line pattern ld (papo),hl call next or a jr z,f.scan ld (papo),hl ld hl,patt ld (lapo),hl ; ; Scan the directory for file names in sorted order. ; f.scan: ld hl,($memry) ; Init dynamic memory pointer ld (filptr),hl ld (hl),0 ; .. clear entry ld hl,$GO.SORT call Qmssg ; Tell sorting ld de,DMA ; CP/M's record buffer call setdma ; Set buffer ld de,$FCB call srcfrs ; Search for 1st file jr ..fnth fnth: call srcnxt ; Search for next file ..fnth: inc a ; Test end jr z,..scan ; .. yeap rrca ; Directory code *32 rrca rrca add a,DMA+.drv-DLEN push af ld bc,1+DLEN/2 ld hl,(filptr) call _alloc ; Verify enough space pop af ld l,a ld h,0 ld bc,.nam+.ext ld de,(filptr) ldir ; Block move ex de,hl ld b,DLEN/2 -.nam-.ext+1 f0: ld (hl),c ; Clear next inc hl djnz f0 dec hl ld (filptr),hl ; Set new file pointer ld hl,(fcount) inc hl ; Bump file count ld (fcount),hl call Sort ; Sort files jr fnth ; ; We're all done. ; done: ld hl,$DTOT call Qmssg ; Final (error) message call tell.file ; Give summary jp OS ; ; Sample files from sorted list ; ..scan: ld hl,$SORT.END call Qmssg ; Tell sorting done ld hl,($memry) ; Reset file pointer ld (filptr),hl scan: ld hl,(filptr) ; Get file pointer ld a,(hl) or a jr z,done ; .. end ld (curptr),hl ; Save pointer ld bc,.nam+.ext ld de,FCB+.drv ; CP/M's file control block ldir ; Block move ld bc,DLEN/2 -.nam-.ext add hl,bc ; Skip info fields ld (filptr),hl xor a ld (FCB+_EX),a ; Make sure we start on extent 0 IF RCPM ; Your favourite catalogue ; File type ld a,(FCB+.drv+.nam) and NoMSB cp 'A' ; File type of ALL/AQL always OK jr nz,tagtest ; on Software Tools RCPM ld a,(FCB+.drv+.nam+1) and NoMSB cp 'L' call nz,qcheck ; Maybe squeezed jr nz,tagtest ; .. nope ld a,(FCB+.drv+.nam+2) and NoMSB cp 'L' jr z,ok tagtest: ld a,(FCB+.drv+1) add a,a ; TAG2 attribute set? jr c,scan ; Yes ld a,(FCB+.drv+.nam+1) add a,a ; SYS attribute set? jr c,scan ; Yes ENDIF ; Rcpm call ignore ; Disregard files in table jr nz,ok call passive ; .. set passive jr scan ; ; Open the file, check for squeezing. ; ok:: ld de,FCB ; CP/M's FCB call open ; Open file jp z,OS ; Quit [without message] xor a ld (FCB+_CR),a ; Block pointer ld (dens),a ; Z/nz=un/squeezed ld (mult),a ; Repeat factor ld hl,0 ld (ictr),hl ; Input counter ld hl,FCB+.drv+.nam+1 ld a,(hl) ; CP/M's file control block cp 'Q' jp nz,nsqz call gbyt ; Fetch one byte cp HIGH HUFFMAN jp nz,nsqz call gbyt ; Fetch one byte cp LOW HUFFMAN jp nz,nsqz ld hl,dens ; Z/nz=un/squeezed ld (hl),TRUE call rwor ; Fetch word ; ; Unsqueezed file name ; ld b,.nam+1+.ext ; Twelve spaces ld hl,$USQ.FN ; Unsqueezed file's name call fiuc ; Block fill ld b,.nam ld de,$USQ.FN ; Unsqueezed file's name luup: call gbyt ; Fetch one byte or a ; Test end of name jr z,ldic ; .. got it cp '.' ; Test delimiter jr z,luuw ; .. yeap ld (de),a ; .. save name inc de djnz luup luuz: call gbyt or a ; Test end of name jr z,ldic cp '.' ; .. wait for delimiter jr nz,luuz luuw: ld b,.ext ld de,$USQ.FN+.nam ld (de),a inc de luur: call gbyt or a ; Test end of extension jr z,ldic ; .. yeap ld (de),a ; .. save inc de djnz luur luus: call gbyt or a ; .. wait for end of name jr nz,luus ; ; Load code directory ; ldic: call rwor ; Fetch word (length) ld bc,hsiz ld a,c sub l ld a,b sbc a,h jr nc,ldii ld hl,$NO.ROOM ; 'code table won't fit' call mssg call passive ; .. mark passive jp scan ldii: add hl,hl ; .. length *4 add hl,hl ld c,l ld b,h ld de,code ; Code table ldij: call gbyt ; Fetch one byte ld (de),a ; Fill table inc de dec bc ld a,c or b jr nz,ldij ld hl,roco ; Rotation count ld (hl),1 ; ; Start data processing ; nsqz: ld de,$L.NUM ; 'line number' call set.ZERO ; Init ASCII 0 ld de,$FTOT ; 'file total' call set.ZERO ; Init ASCII 0 ld bc,.nam ld hl,FCB+.drv ; File name ld de,$F.NAM ; 'file name' ldir ; Block move ld bc,.ext ld hl,FCB+.drv+.nam ld de,$F.EXT ; 'file extension' ldir ; Block move ld hl,$F.HED call Qmssg ; Message to console ld a,(dens) or a jr z,sixs ld hl,$HE.SQ ; '[original]' call Qmssg sixs: ld a,(LINE) ; Test line number or a ld b,LLEN ; Six spaces ld hl,$L.LAB call nz,fiuc ; Block fill inc.line: ld hl,$L.NUM+ZLEN-1; Increment l.c. call inco ; Increment line counter ld hl,lbuf ; Line buffer ld b,-1 fill.line: inc b jp m,full.line push bc push hl call inch ; Char from big bffr to line bffr pop hl pop bc ld (hl),a inc hl bit 7,a ; Test ASCII file jr nz,no.text cp EOF jr nz,no.file.end call sav.file ; Save info for later ld hl,$FTOT fin.mes: call Qmssg ; Message to console jp scan no.text: call passive ; Mark passive ld hl,$NO.TEXT jr fin.mes ; Message to console no.file.end: cp lf jr nz,fill.line jr process full.line: ld (hl),cr inc hl ld (hl),lf inc hl ; ; Check console for termination request. If one ; is present, clear it out before leaving. ; process: ld (hl),0 ; Guarantee right hand fence call const ; Test key jr z,culi ; .. no cp CtrlC ; Test ^C jr nz,skpf? ld hl,$DONE ; "search terminated" jp ferm ; Final (error) message skpf?: cp '?' ; Test question about curent file jr nz,skpf ; .. nope call isQuiet ; Test quiet ld hl,$F.HED call nz,mssg ; .. print if 'Q'uiet jr culi skpf: ld hl,$SKP.REM ; "remainder of file skipped" call Qmssg ; Message to console call passive jp scan ; ; Scan the current line. ; First see if it is labelled. ; culi: ld hl,(lapo) ; Label pointer ld a,h or l jr z,no.label ; No label requested ex de,hl ld hl,lbuf call chek jr nz,no.label ; Label not found push hl ld b,LLEN ; Six spaces ld hl,$L.LAB call fiuc ; Block fill pop hl ld de,$L.LAB+LLEN-1 ld c,LLEN didl: dec hl ld a,(hl) cp tab ; Ignore tabs in text jr z,didl cp ' ' ; Quit at head of line jr c,dido ld (de),a ; .. unpack dec de dec c jr nz,didl dido: ld de,$L.NUM call set.ZERO ; Init ASCII 0 ; ; Now look for the pattern ; no.label: ld hl,lbuf ; Line buffer patt.loop: ld de,(papo) ; Pattern pointer push hl call chek pop hl jr z,patt.match ld a,(hl) cp cr jp z,inc.line ; Increment l.c. inc hl jr patt.loop ; ; Pattern matches, so type label & line containing it ; patt.match: ld a,(LINE) or a ld hl,$L.LAB ; Line label call nz,Qmssg ; Message to console ld hl,lbuf ; Line buffer call Qmssg ; Message to console ld hl,$FTOT+ZLEN-1 call inco ld hl,$DTOT+ZLEN-1 call inco jp inc.line ; Increment l.c. ; ; Increment ASCII counter at (HL-3). ; inco: ld a,(hl) ; Get current or '0' ; .. for ASCII inc a ; .. bump ld (hl),a cp '9'+1 ; Test overflow ret nz ; .. nope ld (hl),'0' ; Reset this one dec hl ; .. try previous jr inco ; ; Process option ; proc.opt:: ld de,($memry) ; Get top memory pointer push de ld hl,CCP+1 ld bc,reclng ldir ; .. move it up ex de,hl pop de push hl call cmdarg ; Cut command line pop ix ; Get back array pointer call ..proc.it ; .. run thru the code inc b dec b ; Verify remainder jp z,fuse ; .. nope ld l,(ix+0) ; Get next pointer ld h,(ix+1) ld (PB),hl ; .. save ld de,PB ld c,.parse call BDOS ; .. parse file ret ; ; Process options ^IX with max length in reg B ; ..proc.it: ld l,(ix+0) ; Get pointer ld h,(ix+1) ld a,(hl) cp '-' ; Test prefix ret nz ; .. nope, skip ld a,(OPTSYN) ; Get blank count for pattern inc a ; .. bump ld (OPTSYN),a inc hl ld a,(hl) ; Get key more.cmd: call find.cmd ; .. find command jr nz,illopt ; .. nope ld iy,opt.ret push iy ; Set return address push de ; .. execution address ret ; .. go illopt: ld hl,$ILL.OPT jp ferm ; Tell invalid option opt.ret: inc hl ld a,(hl) ; Test end or a jr nz,more.cmd ; .. nope, try more inc ix inc ix djnz ..proc.it jp fuse ; .. give a bit help ; ; Option '-Q' : Be quiet on output ; Q.opt: ld a,TRUE ld (QUIET),a ; Set quiet flag ret ; ; Option '-N' : No line numbers in output ; N.opt: ld a,FALSE ld (LINE),a ; Reset line flag ret ; ; Option '-L' : Treat files found as library files (.LBR) ; L.opt:: ret ; ; Test -Q option set - Z set indicates not set ; isQuiet: ld a,(QUIET) ; Test quiet or a ; Get flag ret ; ; Memory to console if not option -Q ; Qmssg: call isQuiet ; Test quiet ret nz ; .. yeap ; ; Memory to console ; mssg: ld a,(hl) and NoMSB ; No MSB ret z inc hl push hl call conout ; Type it pop hl jr mssg ; Message to console ; ; Decode next character - Carry set indicates end of file ; Zero set indicates zero value ; dnch: ld hl,code ; Init code table dncr: call rbit ; Read bit jr nc,dncs ; .. not set inc hl ; .. adjust table inc hl dncs: ld e,(hl) ; Fetch value inc hl ld d,(hl) ld a,d cp DECODE ; Test special code jr z,dnct ; .. yeap, end of file or a ; Test > 0 jp p,dncu ; .. yeap ld a,e ; Get byte cpl ; .. complement or a ; Get flags ret dnct: scf ; Set end of file ret ; ; Calculate +4*. ; dncu: ld hl,code ; Code table add hl,de ; Build index add hl,de add hl,de add hl,de jr dncr ; Try next ; ; Read one bit at a time - Carry reflects state ; rbit: push hl ld hl,roco ; Rotation count dec (hl) ; Count down jr nz,rbiu ; .. still any there ld (hl),8 ; Set byte count call gbyt ; Fetch one byte ld (roby),a ; Rotating byte rbiu: ld hl,roby ; Rotating byte rr (hl) ; .. rotate pop hl ret ; ; Read one word ; rwor: call gbyt ; Fetch lo byte ld l,a push hl call gbyt ; Fetch hi byte pop hl ld h,a ret ; ; Fetch the next byte. The input buffer will be refreshed ; if it is necessary. For normal files, one byte will be ; extracted from the input buffer; for squeezed files, ; one byte will be decoded from the incoming bit stream ; and subtracted from the checksum. ; inch: ld a,(dens) ; Z/nz = un/squeezed or a jr z,gbyt ; Fetch one byte ld a,(mult) ; Repeat factor or a jr z,gusq ; .. end of repetition dec a ld (mult),a ; Repeat factor ld a,(lach) ; Last character read ret gusq: call dnch ; Decode next character jr nc,guss ld a,EOF ; End of file detected ret guss: cp SQ.BYTE ; Test squeeze byte jr z,gusu ld (lach),a ; Last character read ret gusu: call dnch ; Get value jr nz,gusv ; .. got one ld a,SQ.BYTE ; Return byte if zero ret gusv: dec a dec a ld (mult),a ; Repeat factor ld a,(lach) ; Last character read ret ; ; Unsqueezed (normal) text ; gbyt: ld hl,(ictr) ; Input counter ld a,h or l call z,indi ; Disk to IN area ld hl,(ictr) ; Input counter dec hl ld (ictr),hl ; Input counter ld hl,(iptr) ; Input pointer ld a,(hl) ; Fetch byte inc hl ld (iptr),hl ; Input pointer ret ; ; Read buffer from file ; indi: ld b,ksiz ; Set record count ld hl,isiz ld (ictr),hl ; Input counter ld hl,ibuf ; Input buffer ld (iptr),hl ; Input pointer indd: ld (hl),EOF ; Set end of file push hl push bc ex de,hl call setdma ; Set disk buffer ld de,FCB ; CP/M's file control block call dskred ; Read a record pop bc pop hl ret nz ; End of file dec b ret z ld de,reclng ; CP/M's record size add hl,de ; Bump to next record jr indd ; ; Disregard certain files ; ignore:: ld c,$len ld iy,FCB+.drv+.nam ld ix,table$start ld de,.ext loop: call match ; Matched? ret z ; Yes add ix,de ; Bump to next entry dec c ; No, finished count? jr nz,loop ; No dec c ; Return non-zero ret ; ; Test extension match ^DE:^HL ; match: ld a,(iy+0) and NoMSB cp (ix+0) ; First character match? ret nz ; No ld a,(iy+1) and NoMSB cp (ix+1) ; Second character match? call nz,qcheck ; Squeezed version of file type? ret nz ; No ld a,(iy+2) and NoMSB cp (ix+2) ; Third character match? ret ; ; Test character in Accu 'Q' (Squeezed) - Z set says yes ; qcheck: cp 'Q' ; .. simple one ret ; ; Advance to next alternative ; nexx:: ld e,(hl) ; Fetch it inc hl ld d,(hl) ex de,hl next:: ld a,(hl) ; Get bayte or a ret z ; .. end inc hl call enda ret z call begb jr z,nexx jr next ; ; Block fill with B blank's starting at (HL). ; fiuc: ld (hl),' ' inc hl djnz fiuc ; Block fill ret ; ; Move and semi-compile the command line. ; muve: ld a,(hl) cp stab jr nz,munt ld a,tab munt: ld (de),a inc hl inc de cp rbr jr z,murb cp rsq jr z,murb cp lbr jr z,mulb cp lsq jr z,mulb must: dec c jr nz,muve ret murb: ex (sp),hl ld (hl),e inc hl ld (hl),d pop hl jr must mulb: push de inc de inc de jr must ; ; Check balance of []'s and {}'s. ; bala: push hl push bc ld b,1 ld c,1 balb: ld a,(hl) inc hl cp lsq jr nz,balc inc b jr balb balc: cp rsq jr nz,bald djnz balb jr balx bald: cp lbr jr nz,bale inc c jr balb bale: cp rbr jr nz,balf dec c jr z,balx jr balb balf: or a jr nz,balb ld a,c cp 1 jr nz,balx ld a,b cp 1 pop bc pop hl ret z balx: ld hl,$BAD.PAT ; "bad pattern" jp ferm ; Final (error) message ; ; Check for termination of alternative. ; enda: cp orr ret z endb: cp rsq ret z cp rbr ret z or a ret ; ; Check for beginning of alternative. ; bega: cp orr ret z begb: cp lsq ret z cp lbr ret ; ; Check for null alternative. ; nula: push hl call nulb pop hl ret nulb: ld a,(hl) inc hl or a ret z call bega jr nz,nulb ld a,(hl) call enda jr nz,nulb jr balx ; ; Check for given expression. ; chek: ld a,(de) inc de call enda ret z ld b,a ld a,(hl) cp cr jr z,chno ld a,b cp lbr jp z,chlb cp lsq jr z,chsq ld c,(hl) inc hl cp que jr z,chek cp alf jr z,chal cp c jr z,chek ld b,a ld a,c cp 'a' jr c,chno cp 'z'+1 jr nc,chno and 01011111b cp b jp z,chek chno: or 11111111b ret ; ; Check alphanumeric. ; chal: ld a,c cp '0' jr c,chno cp '9'+1 jr c,chek cp 'A' jr c,chno cp 'Z'+1 jr c,chek cp 'a' jr c,chno cp 'z'+1 jr c,chek jr chno ; ; Check list of alternatives. ; chsq: ld c,l ld b,h ld hl,(sqxx) push hl ld hl,(sqaa) push hl ld hl,(sqzz) push hl ld l,c ld h,b ld (sqxx),hl ex de,hl ld e,(hl) inc hl ld d,(hl) inc hl ld (sqaa),hl ex de,hl ld (sqzz),hl chaa: ld hl,(sqxx) call chek jr z,chff chbb: ld hl,(sqaa) ; Fail so find next alternative chcc: call next cp rsq jr z,chdd ; No more alternatives, so fail cp orr jr nz,chcc ld (sqaa),hl ex de,hl jr chaa ; Try next alternative chdd: ld hl,(sqxx) or 11111111b chee: ld c,l ld b,h pop hl ld (sqzz),hl pop hl ld (sqaa),hl pop hl ld (sqxx),hl ld l,c ld h,b ret chff: ld de,(sqzz) ; Good alternative, try rest call chek jr z,chee jr chbb ; ; Check iterative pattern. ; chlb: ld c,l ld b,h ld hl,(text) push hl ld hl,(texx) push hl ld hl,(rest) push hl ld hl,(repeat) push hl ld hl,(repp) push hl ld l,c ld h,b ld (text),hl ld (texx),hl ex de,hl ld e,(hl) inc hl ld d,(hl) inc hl ld (repeat),hl ld (repp),hl ld (rest),de chlc: ld de,(rest) ld hl,(text) call chek ; Check rest jr z,chzz chii: ld de,(repeat) ; Rest failed ld hl,(text) ; Keep same text call chek ; Try out the rer jr nz,choo ld (text),hl ; Repeater worked, record progress ld hl,(repp) ; Start alternatives over again ld (repeat),hl jr chlc choo: ld hl,(repeat) ; Rer failed, try next chxx: call next cp rbr jr z,chyy ; This was the last, quit cp orr jr nz,chxx ld (repeat),hl jr chii chyy: ld hl,(texx) or 0 ; Emphasize the RBR chzz: ld c,l ld b,h pop hl ld (repp),hl pop hl ld (repeat),hl pop hl ld (rest),hl pop hl ld (texx),hl pop hl ld (text),hl ld l,c ld h,b ret ; ; Save current file if any part found ; sav.file: ld de,$FTOT ld hl,$ZERO ld b,ZLEN src.zero: ld a,(de) cp (hl) ; Test zero in count jr nz,no.zero inc de inc hl djnz src.zero passive: ld hl,(curptr) set 7,(hl) ; Mark nothing to tell about ret ; .. none found no.zero: ld hl,(curptr) ; Get current pointer ld bc,.nam+.ext add hl,bc ; Point to line ex de,hl ld hl,$FTOT ld bc,ZLEN ldir ; .. and count ret ; ; Tell pattern if -Q selected ; tell.patt: call isQuiet ; Test quiet ret z ; .. nope ld hl,$SRC.PAT call mssg ; Give message ld hl,patt ; Get pattern call mssg ; .. print ret ; ; Give summary message ; tell.file: call ..tell.file ; Tell summary call isQuiet ; Test quiet ret z ; .. nope ld a,(NONE) ; Test any file or a ret nz ; .. yeap ld hl,$NONE call mssg ; Tell no file found ret ; ; Tell file data ; ..tell.file: call tell.patt ; Tell pattern if -Q selected ld hl,$CRLF call mssg ld hl,($memry) ; Init counter tell.in: ld a,(hl) or a ; Test done ret z ; .. exit bit 7,a ; Test any result jr nz,skp.tell push hl ld hl,NONE ld (hl),1 ; Indicate success ld hl,$FMS.1 call mssg ; Tell file pop hl ld bc,.nam ld de,$F.NAM ; 'file name' ldir ; Block move ld bc,.ext ld de,$F.EXT ; 'file extension' ldir ; Block move push hl ex de,hl ld (hl),c ; .. close end ld hl,$F.NAM call mssg ; Message to console ld hl,$FMS.2 call mssg ; Tell times pop hl call mssg inc hl push hl ld hl,$FMS.3 call mssg pop hl jr tell.in skp.tell: ld bc,DLEN/2 add hl,bc ; Skip entry jr tell.in ; ; Init ASCII zero to ^DE ; set.ZERO: ld bc,ZLEN ld hl,$ZERO ldir ; Block move ret ; ; Find command key in Accu ; find.cmd: push hl push bc ld hl,$CMTAB+$CL-1 ld bc,$CL cpdr ; Find command jr nz,not.val ld hl,$CMEXE add hl,bc ; Position pointer add hl,bc ld e,(hl) ; Fetch address inc hl ld d,(hl) not.val: pop bc pop hl ret ; ; Get arguments from command line ; ; ENTRY Reg HL points to string pointer array array ; Reg DE points to string line ; EXIT Reg B holds parameter count ; cmdarg:: ld b,0 ; Init count .cmdarg: call skpblk ; No blanks so far ld a,(de) or a ; Test end ret z ld (hl),e ; Save pointer inc hl ld (hl),d inc hl inc b ; .. bump count call skpitm ; Skip item ld a,(de) or a ; Test end here ret z xor a ld (de),a ; Clear line inc de jr .cmdarg ; .. try next ; ; Skip blanks in ASCII stream ; ; ENTRY Reg pair DE points to string buffer ; EXIT Reg pair DE points to first non blank character ; skp??b: inc de skpblk: ld a,(de) cp ' ' ; Test blank jr z,skp??b ; Skip it cp tab jr z,skp??b ; .. or tab ret ; ; Skip non-blanks in ASCII stream ; ; ENTRY Reg pair DE points to string buffer ; EXIT Reg pair DE points to first non blank character ; skp??i: inc de skpitm: ld a,(de) cp ' ' ; Test blank ret z cp tab ; .. tab ret z cp cr ; .. return ret z or a ; .. end of line jr nz,skp??i ret ; ; ==== The linear sort package ==== ; ; Compare ^IX : ^IY ; ; Z nC : ^IX = ^IY ; nZ nC : ^IX > ^IY ; nZ C : ^IX < ^IY ; CmpArr: push ix push iy pop hl pop de ld b,.nam+.ext ..cmp: ld a,(de) cp (hl) ; Compare ret nz ; .. not same inc hl inc de djnz ..cmp ret ; ; :=((HL-1)*16) + @ARR ; MulArr: dec hl .MulArr: add hl,hl ; * 2 add hl,hl ; * 4 add hl,hl ; * 8 add hl,hl ; *16 ld de,($memry) add hl,de ; .. get address ex de,hl pop hl ; Get caller push de jp (hl) ; .. return ; ; Linear sort ; ENTRY Reg HL contains number of files to be sorted ; Sort: dec hl ld a,l ; Exit if number = 1 or h ret z ld hl,2 ld (_i_),hl ; Init loop Sort.0: ld hl,(_i_) ; Get index dec hl ld (_j_),hl call .MulArr ; Get address pop hl ld de,$scr$ ld bc,DLEN/2 ldir ; .. save item ld ix,$scr$ ; .. load address Sort.1: ld hl,(_j_) call MulArr ; Get next address pop iy call CmpArr ; .. compare jr nc,Sort.2 ; .. nothing to change ld hl,(_j_) call .MulArr ; Get pointer to next pop de push iy pop hl ld bc,DLEN/2 ldir ; .. unpack ld hl,(_j_) dec hl ; .. bump down ld (_j_),hl ld a,l or h jr nz,Sort.1 Sort.2: ld hl,(_j_) call .MulArr ; Get address pop de push ix pop hl ld bc,DLEN/2 ldir ; .. unpack ld hl,(_i_) inc hl ; Bump to next ld (_i_),hl ex de,hl ld hl,(fcount) or a sbc hl,de ; Test done jr nc,Sort.0 ; .. nope ret ; ; Verify enough memory for sort ; ENTRY Reg HL holds current top ; Reg BC holds requested length ; _alloc: add hl,bc ; Get final address ld de,(BDOS+1) dec d ; .. one stack page or a sbc hl,de ; Test enough room ret c ; .. yeap ld hl,$NO.MEM call mssg ; Tell no memory jp OS ; ; ==== End of linear sort package ==== ; ; BDOS interface ; ; Set disk buffer ^DE ; setdma: ld c,.setdma ; Set buffer in call BDOS ret ; ; Search for 1st file ^DE ; srcfrs: ld c,.srcfrs ; Search 1st file call BDOS ret ; ; Search for next file ; srcnxt: ld c,.srcnxt ; Search next file call BDOS ret ; ; Open file ^DE ; open: ld c,.open ; Open file call BDOS inc a ; -1 is end ret ; ; Get character into Accu, Z flag set says none ; const: ld e,_get ld c,.condir ; Get console character call BDOS or a ; .. Zero is none ret ; ; Put character in Accu to console ; conout: ld e,a ld c,.conout ; Put character to console call BDOS ret ; ; Read record from file ^DE ; dskred: ld c,.dskrd ; Read record call BDOS or a ; Zero is O.K. ret ; ; Data area ; ; ========== Start of English text ========== IF NOT GERMAN $ILL.OPT: db cr,lf,'Invalid option, select -Q',cr,lf,null IF RCPM $HELP: db cr,lf,'Usage:',cr,lf,tab $PRG db ' [-opt] filename.typ string[|string]' db cr,lf,cr,lf db 'Where:',cr,lf db tab,'Selected option -Q prints summary of ' db 'matching files only' db cr,lf db tab,'Selected option -N prints matches without ' db 'line number' db cr,lf db tab,'filename.typ =',tab,'any CATALOG name, ' db '(* and ? allowed).' db cr,lf,lf db tab,tab,tab,'CATALOG names are...' db cr,lf db tab,tab,tab,'SIGM-1.AQL to SIGM-4.AQL, CPMCAT.AQL' db cr,lf db tab,tab,tab,'CUGCAT.AQL, MISC.AQL, PCBLUE.AQL' db cr,lf,lf db tab,'string',tab,' =',tab,'any string of ' db 'characters' db cr,lf db tab,tab,tab,'(* and ? not allowed).' db cr,lf,lf db tab,'|',tab,' =',tab,'optional OR connector ' db 'for multiple strings' db cr,lf db tab,tab,tab,'i.e. ' $PRG db ' MISC.AQL DOC|TXT' db cr,lf,cr,lf db 'Type HELP THIS-SYS for a full description of ' $PRG db cr,lf,null ENDIF ; Rcpm IF NOT RCPM $HELP: db cr,lf,'The command line',cr,lf,lf db ' ' $PRG db ' [-opt] D:FILE.EXT EXPRESSION',cr,lf,lf db 'will search through all instances of ' db 'FILE.EXT (which may be an ambiguous',cr,lf db 'reference) on disk D to find lines ' db 'containing EXPRESSION. Such lines will be' db cr,lf db 'presented on the console preceded by a ' db 'line number, and classified by file.',cr,lf db 'With option -Q selected only a summary of ' db 'matching files will be printed.',cr,lf db 'With option -N selected matches will be ' db 'printed without line numbers.',cr,lf db 'EXPRESSION may have the form LABEL|PATTERN or' db ' simply the form PATTERN.',cr,lf db 'Both may contain:',cr,lf db ' [p1|p2|...|pn] alternative strings' db cr,lf db ' {p1|p2|...|pn} repeated alternatives' db cr,lf db ' ? any single character',cr,lf db ' @ for any alphanumeric: a-z, A-Z, 0-9' db cr,lf db ' _ in place of horizontal tab',cr,lf db 'When a label is present, lines will be ' db 'numbered relative to the label.',cr,lf,lf db 'Example: X{?}:|[call|ret] will list calls ' db 'and returns relative to labels',cr,lf db 'like X0100: or X33:. LABEL begins in column ' db '1, PATTERN can begin in any column.',cr,lf db 'Squeezed files will be searched as well ' db 'as unsqueezed ones. Use ^C to quit.',cr,lf db 'Question mark in quiet mode displays current' db ' file, any other key skips rest of',cr,lf db 'file.',cr,lf,null ENDIF ; Not rcpm $PRG.ID: db cr,lf $PRG db ' Version ' $VERS $CRLF: db cr,lf,null $BAD.PAT: db '-- Bad Pattern --',null $DONE: db cr,lf,'-- Search Terminated --',null $NO.TEXT: db cr,lf,'Not a text file' $SKP.REM: db ' -- Remainder of File Skipped --',cr,lf,null $NO.ROOM: db ' -- Code Table Won''t Fit --',cr,lf,null $HE.SQ: db '[original] ' $USQ.FN: db 'original.xxx' ; Unsqueezed file's name db cr,lf,null $F.HED: db cr,lf db '----> File ' $F.NAM: db 'xxxxxxxx.' ; Filename $F.EXT: db 'xxx',cr,lf,null; File extension $L.LAB: db ' ' LLEN equ $-$L.LAB db '+' $L.NUM: db ' ',null $ZERO: db ' 0' ZLEN equ $-$ZERO $FTOT: db cr,lf db ' matching lines found in this file.' db cr,lf,null $DTOT: db ' matching lines in all the files ' db 'searched.',cr,lf,null $SRC.PAT: db cr,lf,'Pattern: ',null $NONE: db 'Pattern not found',cr,lf,null $FMS.1: db 'In file ',null $FMS.2: db ' found ',null $FMS.3: db ' times',cr,lf,null $GO.SORT: db '.. start sorting',cr,null $SORT.END: db ' ',cr,null $NO.MEM: db cr,lf,'% No memory for list of files',cr,lf,null ENDIF ; NOT german ; ========== End of English text, Start of German ========== IF GERMAN $ILL.OPT: db cr,lf,'Falsche Option, erlaubt ist -Q',cr,lf,null IF RCPM $HELP: db cr,lf,'Aufruf:',cr,lf,tab $PRG db ' [-Opt] filename.typ string[|string]',cr,lf,lf db 'Mit:',cr,lf db tab,'Die Option -Q listet nur die Summe der ' db 'gefundenen Dateien auf' db cr,lf db tab,'Die Option -N listet die Zeichenketten ' db 'ohne Zeilennummern auf' db cr,lf db tab,'filename.typ =',tab,'ein beliebiger CATALOG' db ' Name, (* und ? sind erlaubt).',cr,lf db tab,tab,tab,'CATALOG Namen sind...',cr,lf,lf db tab,tab,tab,'SIGM-1.AQL bis SIGM-4.AQL, ' db 'CPMCAT.AQL',cr,lf db tab,tab,tab,'CUGCAT.AQL, MISC.AQL, PCBLUE.AQL' db cr,lf,lf db tab,'string',tab,' =',tab,'eine beliebige ' db 'Zeichenkette',cr,lf db tab,tab,tab,'(* und ? sind nicht erlaubt).' db cr,lf,lf db tab,'|',tab,' =',tab,'optionale ODER ' db 'Verknuepfung fuer mehrere Zeichenketten',cr,lf db tab,tab,tab,'z.B. ' $PRG db ' MISC.AQL DOC|TXT',cr,lf,lf db 'Fuer eine komplette Beschreibung von ' $PRG db ' bitte HELP THIS-SYS eingeben',cr,lf,null ENDIF ; Rcpm IF NOT RCPM $HELP: db cr,lf,'Die Kommando-Zeile',cr,lf,lf db ' ' $PRG db ' [-Opt] D:FILE.EXT EXPRESSION',cr,lf,lf db 'durchsucht die Datei FILE.EXT auf Laufwerk D' db ' nach Zeilen, in denen der Ausdruck',cr,lf db 'EXPRESSION zu finden ist (Der Datei-Name' db ' darf * und ? enthalten, so dass',cr,lf db 'mehrere Dateien durchsucht werden koennen). ' db 'Die Zeilen werden auf dem' db cr,lf db 'Bildschirm ausgegeben mit vorangestellter ' db 'Zeilennummer sowie Angabe der gerade',cr,lf db 'durchsuchten Datei. Die Option -Q gibt nur ' db 'die Liste der Dateien aus, in denen',cr,lf db 'der gesuchte Ausdruck gefunden wurde.' db ' Die Option -N gibt nur den gefundenen',cr,lf db 'Ausdruck ohne die Zeilennummer aus.' db ' Der Ausdruck EXPRESSION kann bestehen',cr,lf db 'aus der Kombination LABEL|PATTERN oder ' db 'einfach nur aus PATTERN.' db cr,lf db 'Beide duerfen bestehen aus:',cr,lf db ' [p1|p2|...|pn] alternative ' db 'Zeichenketten',cr,lf db ' {p1|p2|...|pn} wiederholte ' db 'Zeichenketten',cr,lf db ' ? ein beliebiges Einzelzeichen',cr,lf db ' @ fuer ein beliebiges alphanumerisches ' db 'Zeichen: a-z, A-Z, 0-9',cr,lf db ' _ anstelle eines Tabulators',cr,lf db 'Wenn ein Label vorhanden ist, werden die ' db 'Zeilen relativ zum Label nummeriert.',cr,lf,lf db 'Beispiel: X{?}:|[call|ret] listet Calls und' db ' Returns relativ zu den Labels wie',cr,lf db 'z.B. X0100: oder X33:. Ein LABEL beginnt ' db 'immer in Spalte 1, PATTERN hingegen',cr,lf db 'kann in jeder beliebigen Spalte beginnen.' db ' Sogennante "Squeezed" Dateien werden',cr,lf db 'genauso durchsucht wie regulaere Dateien.' db ' Zum Abbrechen des Programmes kann',cr,lf db '^C benutzt werden, ein Fragezeichen bei der ' db 'Option -Q zeigt aktuelle Datei an,',cr,lf db 'jede andere Taste bricht die Suche innerhalb ' db 'der aktuellen Datei ab (Das ist',cr,lf db 'nur bei Mehrfach-Dateien wichtig).',cr,lf,null ENDIF ; Not rcpm $PRG.ID: db cr,lf $PRG db ' Version ' $VERS $CRLF: db cr,lf,null $BAD.PAT: db '-- Fehlerhaftes PATTERN --',null $DONE: db cr,lf,'-- Suche abgeschlossen --',null $NO.TEXT: db cr,lf,'Keine Textdatei' $SKP.REM: db ' -- Rest der Datei ignoriert --',cr,lf,null $NO.ROOM: db ' -- Kein Platz fuer Code Tabelle --',cr,lf,null $HE.SQ: db '[Original] ' $USQ.FN: db 'original.xxx' ; Unsqueezed file's name db cr,lf,null $F.HED: db cr,lf db '----> Datei ' $F.NAM: db 'xxxxxxxx.' ; Filename $F.EXT: db 'xxx',cr,lf,null; File extension $L.LAB: db ' ' LLEN equ $-$L.LAB db '+' $L.NUM: db ' ',null $ZERO: db ' 0' ZLEN equ $-$ZERO $FTOT: db cr,lf db ' passende Zeilen in dieser Datei ' db 'gefunden.',cr,lf,null $DTOT: db ' passende Zeilen in allen durchsuchten ' db 'Dateien gefunden.',cr,lf,null $SRC.PAT: db cr,lf,'Ausdruck: ',null $NONE: db 'Ausdruck nicht gefunden',cr,lf,null $FMS.1: db 'In Datei ',null $FMS.2: db ' gefunden ',null $FMS.3: db ' mal',cr,lf,null $GO.SORT: db '.. Dateien werden sortiert',cr,null $SORT.END: db ' ',cr,null $NO.MEM: db cr,lf,'% Kein Speicher fuer Datei Liste',cr,lf,null ENDIF ; German ; ========== End of German text ========== PB: dw 0,FCB $FCB: db 'DFilenameEXT',0 ds 19 sqxx: ds 2 sqaa: ds 2 sqzz: ds 2 text: ds 2 texx: ds 2 rest: ds 2 repeat: ds 2 repp: ds 2 lapo: ds 2 ; Label pointer papo: ds 2 ; Pattern pointer ; ; Table of file types to exclude for searchhing ; table$start: db 'COM' ; CP/M command file db 'OBJ' ; CP/M command file db 'LBR' ; LU/LAR library file db 'CMD' ; CP/M-86 command file db 'REL' ; Relocatable file db 'C0M' ; MSDOS command file db 'EXE' ; MSDOS command file db 'OVR' ; Overlay file db 'OVL' ; Overlay file db 'CRL' ; BDS C relocatable file db 'IRL' ; Libarary file $end equ $-table$start $len equ $end / 3 ; $CMTAB: db 'QNL' $CL equ $-$CMTAB $CMEXE: dw Q.opt dw N.opt dw L.opt QUIET: db FALSE ; Quiet flag OPTSYN: db 1 ; Blank count for pattern NONE: db 0 ; None flag for -Q option LINE: db TRUE ; True on numbered lines curptr: dw 0 filptr: dw 0 ; File buffer pointer $memry: dw fini+1 ; File buffer start fcount: dw 0 _i_: dw 0 _j_: dw 0 $scr$: ds 16 lbuf: ds 133 ; Line buffer dens: ds 1 ; Z/nz = un/squeezed roby: ds 1 ; Rotating byte roco: ds 1 ; Rotation count mult: ds 1 ; R factor lach: ds 1 ; Last character read ictr: ds 2 ; Input counter iptr: ds 2 ; Input pointer ; ibuf equ $ ; Input buffer patt equ ibuf+isiz ; Command line pattern code equ patt+256 ; Huffman code table fini equ code+4*hsiz end