title String detection name ('STRINGS') maclib base80 ; Program STRINGS ; Copyright (C) Werner Cirsovius ; Hohe Weide 44 ; D-2000 Hamburg 20 ; Tel.:+49/040 4223247 ; Version 1.0, January 1989 ; Find printable strings in an binary file ; Call it: ; STRINGS [-T FORMAT1 [ FORMAT2 ] | -O] [-N NUMBER | -NUMBER] FILE ; -t format1 ; Write each string preceded by its byte offset from the ; start of the file. The format is dependent on the single ; character used as the format option-argument: ; d The offset will be written in decimal. ; o The offset will be written in octal. ; x The offset will be written in hexadecimal. ; A second extension character selects output format: ; a Display with offset 0100 which is the CP/M start address. ; r Displays in format "Record_Number/Record_Offset". ; -o Equivalent to -t d option which may follow the second format character. ; -n number | -number ; Use a number as the minimum string length rather than ; the default, which is 4. ARGMAX equ 3 ; ; Digit places for signed 32 bit number - uses 31 bit only ; ; Normal and address mode (max value) ; ; Hexadecimal 7FFFFFFF 8 digits ; Decimal 2147483647 10 digits ; Octal 17777777777 11 digits ; ; Record mode (max value) [RECORD/POINTER] ; ; Hexadecimal FFFFFF/7F 9 digits ; Decimal 16777215/127 12 digits ; Octal 77777777/177 12 digits ; MAXNUM equ 12 ; Digit places FIL.bit equ 7 T.pat equ 00000001b N.pat equ 00000010b FIL.pat equ 1 SHL FIL.bit entry $memry ext cmdarg,fparse,wcard,fildrv ext ascbyt,hexout,dout32,decin ext conout,conchd,string,strcn0,crlf,@crlf ext open,rdfcb,rdbuf,dskget dseg $HELP: db 'Find printable strings in an binary file' db cr,lf,lf db 'Call it:' db cr,lf,lf db tab,'STRINGS [-T FORMAT1 [ FORMAT2 ] | -O] [-N NUMBER | -NUMBER] FILE' db cr,lf,lf db '-t format1' db cr,lf db ' Write each string preceded by its byte offset from the' db cr,lf db ' start of the file. The format is dependent on the single' db cr,lf db ' character used as the format option-argument:' db cr,lf,lf db ' d The offset will be written in decimal.' db cr,lf,lf db ' o The offset will be written in octal.' db cr,lf,lf db ' x The offset will be written in hexadecimal.' db cr,lf,lf db ' A second extension character selects output format:' db cr,lf,lf db ' a Display with offset 0100 which is the CP/M start address.' db cr,lf,lf db ' r Displays in format "Record_Number/Record_Offset".' db cr,lf,lf db '-o Equivalent to -t d option which may follow the second format character.' db cr,lf,lf db '-n number | -number' db cr,lf db ' Use a number as the minimum string length rather than' db cr,lf db ' the default, which is 4.' db cr,lf,eot $ILLOPT: db 'Invalid option "-' $OPTCHR: db 'x"',eot $ILLSEL: db 'Invalid option selection >' $OPTILL: db 'x<',eot $ILLPARSE: db ' is an invalid file specification',eot $ILLWILD: db 'Wildcard not allowed in filename',eot $NOFIN: db 'Missing file',eot $TOOMANY: db 'Too many files selected',eot $FILE: db 'File ',eot $NOFILE: db ' not found',eot $OPT: db 'TO' N$OPT equ $-$OPT db 'N' OptLen equ $-$OPT OptTab: dw T.sel,O.sel,N.sel $MODE: db 'NXDO' ModLen equ $-$MODE ModTab: dw N.mod dw X.mod,D.mod,O.mod dw XR.mod,DR.mod,OR.mod modoffs: dw 0 ; 2*OptLen if record mode dispmod: db null modexe: dw OS $NULL: db null FORMAT: db 'N' ; Default is no format NUMBER: ds 2 STRLEN: dw 4 ; Default are 4 characters ARGC: ds 1 ARGV: ds 2*ARGMAX OUTLINE: ds 2 CURLINE: ds 2 $memry: ds 2 PARSPB: dw $-$,FCB cmdstat: db 00000000b Rec32: db 0,0,0 RECoffs: db 0 RECptr: db 0 ASCIIpos: db 0,0,0,0 NumLen equ $-ASCIIpos ASCIIoffs: ds NumLen Tmpoffs: ds NumLen+1 cseg ; ; Copy current ASCII position ; cpyOffs: ld hl,(ASCIIpos) ; Real simple ld (ASCIIoffs),hl ld hl,(ASCIIpos+2) ld (ASCIIoffs+2),hl ld a,(RECptr) ld (RECoffs),a ret ; ; Add a 1 to current ASCII position ; bmpPos: ld a,(dispmod) ; Get display mode cp 'R' ; Test record jr nz,bmpNorm ; Nope ld hl,RECptr ; Point to record position inc (hl) ; Bump it ld a,(hl) sub reclng ; Test record dine ret nz ; Nope ld (hl),a ; Clear pointer then add 1 bmpNorm: push bc ld hl,ASCIIpos+NumLen-1 ld b,NumLen call _bmp pop bc ret _bmp: inc (hl) ; Advance ret nz ; Exit if not 0xFF dec hl djnz _bmp ret ; ; Print current offset ; prOffs: push bc ld de,(NUMBER) ; Point to number ld hl,(modexe) ; Get execution address jp (hl) ; Execute selection ; ; Hex output of 24+7 bit number - Format FFFFFF/7F (9 places) ; XR.mod:: ld hl,ASCIIoffs+1 ; Point to hi part call ascbyt ; Convert it ld hl,(ASCIIoffs+2) call hexout ; Convert lo part then call stdel ; Store delimiter ld hl,RECoffs call ascbyt ; Convert pointer ld b,9 ; Set length jr Proc32 ; Then print it ; ; Process reverse hex output ; rhexout: ld a,l ; Swap hi and lo ld l,h ld h,a call hexout ret ; ; Hex output of 31 bit number - Format 7FFFFFFF (8 places) ; X.mod: ld hl,(ASCIIoffs) ; Get hi part call rhexout ; Convert it ld hl,(ASCIIoffs+2) call rhexout ; Convert lo part then ld b,8 ; Set length Proc32: ld a,eot ld (de),a ; Close line Prxx32: ld a,MAXNUM sub b ; Calculate filler ld b,a ld e,' ' call nz,conchd ; Give leading blanks ld de,(NUMBER) call string ; Print number ld a,':' call conout ; Print delimiter N.mod: pop bc ; Get back reg ret ; ; Decimal output of 24+7 bit number - Format 16777215/127 (12 places) ; DR.mod:: call D32out ; Process conversion ex de,hl push bc ; save length call stdel ; Set delimiter call RECout ; Convert record number ld a,b ; Get length pop bc ; Get back old length add a,b inc a ; Remember delimiter jr Prxx32 ; Print it ; ; Decimal output of 31 bit number - Format 2147483647 (10 places) ; D.mod: call D32out ; Process conversion jr Prxx32 ; Print it ; ; Octal output of 24+7 bit number - Format 77777777/177 (12 places) ; OR.mod:: call copy32 ; Copy number ld c,8 ; Set max digits ld b,3 call oout32 ; Convert number call stdel ; Set delimiter ld c,3 ; Set max digits ld b,2 ; Start with two bits call oout32 ; Convert number ld b,12 ; Set length jr Proc32 ; Print it ; ; Octal output of 31 bit number - Format 17777777777 (11 places) ; O.mod: call copy32 ; Copy number ld c,11 ; Set max digits ld b,2 ; Start with two bits call oout32 ; Convert number ld b,11 ; Set length jr Proc32 ; Print it ; ; Convert a 31 bit number to octal ; oout32: ld ix,ASCIIoffs ; Init number pointer oct1: sla (ix+4) ; Shift hi bit rl (ix+3) rl (ix+2) rl (ix+1) rl (ix+0) rla djnz oct1 and 00000111b add a,'0' ; Make ASCII ld (de),a inc de ld b,3 ; Change bit count dec c jr nz,oct1 ret ; ; Copy 32 bit number ; copy32: ld hl,(ASCIIoffs) ; Copy number ld (Tmpoffs),hl ld hl,(ASCIIoffs+2) ld (Tmpoffs+2),hl ld a,(RECoffs) ld (Tmpoffs+NumLen),a ret ; ; Process 32 bit decimal conversion ; ; -> Record number ; RECout: push de ld hl,Rec32 ; Point to value jr do32 ; ; -> Offset number ; D32out: push de ld hl,ASCIIoffs ; Point to value do32: ld b,eot call dout32 ; Convert number pop de ; Get back number pointer push hl or a sbc hl,de ld b,l ; Get length pop hl ret ; ; Store delimiter ; stdel: ld a,'/' ld (de),a ; Store delimiter inc de ret ; ; Reset ASCII settings ; resASCII: ld hl,(OUTLINE) ; Get line pointer ld (CURLINE),hl ; Set it xor a ld (hl),a ; Clear string ld c,a ; And length ld b,a ret ; ; Print ASCII string ; prASCII: ld hl,(STRLEN) ; Get length of string dec hl or a sbc hl,bc ; Test enough characters ret nc ; Nope call prOffs ; Print offset ld de,(OUTLINE) ; Get line pointer call strcn0 ; Print line call crlf ret ; ; Test byte a character ; Carry set if not ASCII ; isASCII: cp ' ' ; Test range ret c ; Binary cp '~'+1 ccf ret ; ; *********************** THE REAL JOB *********************** ; ; Find ASCII string ; findASCII:: call resASCII ; Reset settings nxtASCII: call dskget ; Read byte from file jr c,endASCII call isASCII ; Test character in range jr c,isBinary ; Nope ld hl,(CURLINE) ld (hl),a ; Save ASCII inc hl ld (hl),null ld (CURLINE),hl ; Advance pointer ld a,c ; Test first ASCII or b call z,cpyOffs ; Copy offset if so inc bc call bmpPos ; Advance position jr nxtASCII ; Try next isBinary: call prASCII call bmpPos ; Advance position jr findASCII ; Try next endASCII: call prASCII ; Print ASCII if any there ld de,@crlf ; Return empty line ret ; ; ************************************************************ ; ; Init program environment ; initprg: call new ; Build dynamic space for files ld de,CCPlen ld hl,ARGV ld b,ARGMAX call cmdarg ; Get arguments ld (ARGC),a ; Save ld de,$HELP ret ; ; Build dynamic space for destination file ; new: call dummyfcb ; Build blank FCB ld hl,($memry) ; Get top address ld (rdfcb),hl ; Set source FCB ld bc,fcblen call Fblank ; Blank file add hl,bc ld (rdbuf),hl ; Set buffer ld bc,reclng add hl,bc ld (NUMBER),hl ; Set digit pointer ld bc,MAXNUM+1 add hl,bc ld (OUTLINE),hl ; Set line pointer ret ; ; Build empty standard FCB ; dummyfcb: ld de,$NULL call doparse ; Dummy parse ret ; ; Execute file parsing ; doparse: ld (PARSPB),de ; Save string pointer ld de,PARSPB call fparse ; Parse file ret ; ; Blank file ^HL - length in reg BC ; Fblank: push hl push bc ex de,hl ld hl,FCB ldir ; Unpack file pop bc pop hl ret ; ; Scan command line ; scancmd: ld ix,cmdstat ; Init status pointer ld hl,ARGV ; Init command pointer ld a,(ARGC) ; Get count ld b,a scanLoop: ld e,(hl) ; Fetch pointer inc hl ld d,(hl) inc hl push bc push hl ld a,(de) ; Get beginning character cp '-' jr z,scanopt call getfile ; Try file jr scannxt scanopt: call getopt ; Process option scannxt: pop hl pop bc ret c ; Error djnz scanLoop or a ret ; ; Test if Accu a digit 0..9 ; Carry set says not ; isdigit: dec de ; Fix pointer ld bc,N$OPT ; Init -N option cp '0' ; Test range ret c cp '9'+1 ccf ret ; ; Find option ; getopt: inc de ; Skip '-' ld a,(de) ; Get option character moreopt: ld hl,$OPT+OptLen-1 ld bc,OptLen cpdr ; Find option jr z,fndopt call isdigit ; Test digit jr nc,fndopt ; Yeap ld ($OPTCHR),a ; Save selected option ld de,$ILLOPT ; Return error message scf ret fndopt: inc de ; Skip character ld hl,OptTab add hl,bc add hl,bc ld c,(hl) ; Get address inc hl ld b,(hl) ld hl,optret push hl push bc ret ; Execute optret: jr nc,optnxt dec de ld a,(de) ld ($OPTILL),a ; Set error character ld de,$ILLSEL ; Return error ret optnxt: ld a,(de) ; Test end of option or a jr nz,moreopt ret ; ; Select -O option ; It implies default decimal selection ; O.sel: ld a,'D' ; Set decimal ld (FORMAT),a ld c,T.pat setOpt: ld a,(ix) and c ; Test option already set scf ret nz ; Yeap, error setbit: ld a,c or (ix) ; Build pattern ld (ix),a ret ; ; Select -T option ; May be -Ta or -Tab ; T.sel: ld c,T.pat call setOpt ; Set option ret c ; Error ld a,(de) ; Get offset ld (FORMAT),a ; Set it call getmode ; Find mode scf ret nz ; Error inc de ; Skip character ld a,(de) ; Get second one or a ret z ; End of option ld (dispmod),a ; Save option inc de cp 'A' ; Test address ret z cp 'R' ; Test record ret z scf ret ; Error ; ; Select -N option ; N.sel: ld c,N.pat call setOpt ; Set option ret c ; Error inc de ; Point to number ld b,null ; Set delimiter call decin ; Get number ld (STRLEN),hl ; Set number ret ; ; Parse file ; getfile: push de call doparse ; Parse file pop de jr nc,fileok illparse: ld de,(PARSPB) ; Get file pointer call strcn0 ; Tell error ld de,$ILLPARSE scf ret fileok: ld a,l or h ; Verify correct end jr nz,illparse ld c,FIL.pat ; Set file bit call setOpt ex de,hl ld de,$TOOMANY ; Too many files selected ret c push hl ld de,(rdfcb) ; Init file ld hl,FCB ld bc,.fdrv+.fname+.fext ldir ; Unpack file pop de or a ret ; ; Find mode ; getmode: ld hl,$MODE+ModLen-1 ld bc,ModLen cpdr ; Find mode ret ; ; Activate format options ; enableform: ld a,(dispmod) ; Get option cp 'R' ; Test record display jr nz,isADDR ld hl,2*OptLen ld (modoffs),hl ; Set offset jr setTable isADDR: cp 'A' ; Test address jr nz,setTable ld a,high TPA ld (ASCIIpos+NumLen-2),a setTable: ld a,(FORMAT) ; Get format call getmode ; Find it jr z,fndmod ; Got it ld bc,0 ; Set default NONE ld (modoffs),bc fndmod: ld hl,(modoffs) ; Fetch mode offset add hl,bc add hl,bc ld bc,ModTab add hl,bc ld c,(hl) ; Get address inc hl ld b,(hl) ld (modexe),bc ; Save address ret ; ; Give start message and filename ^DE ; Return message in ^HL in ^DE ; tellfile: push de ld de,$FILE call string ; Give message pop de call fildrv ; Tell file ex de,hl ; Get message ret ; ; %%%%%%%%%%%%%%%%%%%%% ; %%% START STRINGS %%% ; %%%%%%%%%%%%%%%%%%%%% ; _MAIN: ld sp,(TPAtop) ; Get local stack call initprg ; Init program environment call nc,scancmd ; Scan command line jr c,_exit ; Give help if invalid input ld a,FIL.pat and (ix) ; Test file ld de,$NOFIN jr z,_exit ; Nope, error call enableform ; Activate format ld de,(rdfcb) call wcard ; Verify no wildcard ld de,$ILLWILD jr z,_exit ld de,(rdfcb) call open ; Open source file ld hl,$NOFILE jr c,_abort call findASCII ; Find ASCII strings jr _exit _abort: call tellfile _exit: call string ; Give final message jp OS end _MAIN