[net.micro.pc] dynamic ramdisk, program interupter, fast find for MS-DOS 2.x

jnw@mcnc.UUCP (John White) (01/30/85)

# use sh to extract
echo extracting README
cat >README <<xyzzy
The following utilities should be made with the DeSmet C package.
All are for MS-DOS 2.x and were written on a Tandy 2000 by me and
will work on the IBM-PC. Int.a is set up for the IBM-PC as sent.

ram.sys, setram.exe -- a ramdisk whose memory can be allocated and freed
        without rebooting. Make with makeram.bat

int.com -- a terminate-and-stay-resident program that allows a program
        to be interupted when in a CPU loop.
        This program will not port to other MS-DOS machines without
        modification (see int_port.doc). Make with makeint.bat

ffind.exe -- a find program that is fast and can search a large number
        of files easily. Compile and link normally.

Bennet Todd has agreed to supply binaries to anyone who doesn't have
the DeSmet package and who can't find anyone who does. He can be reached at

Bennett Todd -- The Happy Hacker
...{decvax,ihnp4,akgua}!mcnc!ecsvax!bet

I hope you find these programs useful. If you find any undocumented
"features" you can mail them to me at    mcnc!jnw
                                           John N. White
xyzzy

echo extracting ram.a
cat >ram.a <<xyzzy
;	RAM.A	MS-DOS V2.0 RAM DISK PROGRAM
;	assemble with the DeSmet assembler
;	Like the IBM ramdisk but with a setram feature. - John N. White

SRH_LEN		EQU	13		;LENGTH
SRH_STA_FLD	EQU	3		;STATUS FIELD

DTA		EQU	SRH_LEN+1	;DATA TRANSFER ADDRESS
COUNT		EQU	DTA+4
SSN		EQU	COUNT+2		;START SECTOR NUMBER

RET_BYTE	EQU	DTA		;RETURN BYTE

BPBA_PTR	EQU	COUNT		;POINTER TO BPB
;	INITIALIZE
UNITS		EQU	SRH_LEN
BR_ADDR_0	EQU	SRH_LEN+1
BR_ADDR_1	EQU	BR_ADDR_0+2
BPB_PTR_OFF	EQU	BR_ADDR_0+4
BPB_PTR_SEG	EQU	BPB_PTR_OFF+2

	CSEG
;	DEVICE HEADER
NEXT_DEV	DW	-1,-1
ATTRIBUTE	DW	6000H		;IOCTL supported
STRATEGY	DW	DEV_STRATEGY
INTERRUPT	DW	DEV_INT
DEV_NAME	DB	1		;NUMBER OF DEVICES
		DB	0,0,0,0,0,0,0

RH_OFF		DW	0		;REQUEST HEADER OFFSET
RH_SEG		DW	0		;SEGMENT

;	CURRENT INFORMATION
TOTAL		DW	0		;NUMBER OF SECTORS TO TRANSFER
START_SEC	DW	0		;FIRST SECTOR
VDISK_PTR	DW	0
USER_DTA	DW	0,0		;USERS DATA TRANSFER ADDRESS
BPB		DW	512		;PER SECTOR
		DB	1		;ALLOCATION UNIT
		DW	0		;0 RESERVED
		DB	1		;1 FAT
		DW	32		;DIRECTORY ENTRIES
SECTORS		DW	10H		;SECTORS TOTAL
MEDIA_TYPE	DB	0FCH		;MEDIA BYTE
FAT_SIZE	DW	3		;SECTORS IN FATS
BPB_PTR		DW	BPB
MEDIA_IN	DB	-1		;MEDIA IN DRIVE IF 1

FUNTAB:
	DW	INIT
	DW	MEDIA_CHECK
	DW	BUILD_BPB
	DW	IOCTLI
	DW	INPUT
	DW	EXIT
	DW	EXIT
	DW	EXIT
	DW	OUTPUT
	DW	OUTPUT			;DONT BOTHER VERIFYING
	DW	EXIT
	DW	EXIT
	DW	IOCTLO

IN_SAVE:MOV	AX,ES:WORD [BX+DTA]	;SAVE CALLERS DTA
	MOV	DS:WORD USER_DTA,AX
	MOV	AX,ES:WORD [BX+DTA+2]
	MOV	DS:WORD USER_DTA+2,AX
	MOV	AX,ES:WORD [BX+SSN]	;START SECTOR
	MOV	DS:START_SEC,AX
	MOV	AX,ES:WORD [BX+COUNT]	;COUNT OF SECTORS
	MOV	AH,0
	MOV	DS:WORD TOTAL,AX
	RET

CALC_ADDR:
	MOV	AX,DS:START_SEC
	MOV	CL,5			;TURN SECTORS INTO PARAGRAPHS
	SHL	AX,CL
	ADD	AX,DS:VDISK_PTR
	MOV	CH,DS:BYTE TOTAL	;CX=LENGTH IN WORDS
	MOV	CL,0
	MOV	DS,AX			;MOVE ADDRESS TO DS:SI
	XOR	SI,SI
	RET

;	STRATEGY ENTRY
DEV_STRATEGY:
	MOV	CS:RH_SEG,ES		;SAVE ES:BX
	MOV	CS:RH_OFF,BX
	LRET

;	DEVICE INTERRUPT HANDLER
DEV_INT:
	PUSH	DS			;SAVE STATE
	PUSH	ES
	PUSH	AX
	PUSH	BX
	PUSH	CX
	PUSH	DX
	PUSH	SI
	PUSH	DI
;		SET STATUS TO ALL OK
	MOV	ES:WORD [BX+SRH_STA_FLD],100H
	MOV	AL,ES:[BX+2]		;GET FUNCTION BYTE
	SHL	AL,1			;TIMES 2
	MOV	AH,0
	MOV	DI,AX			;FUNCTION OFFSET
	PUSH	CS
	POP	DS
	JMP	WORD FUNTAB[DI]

;	MEDIA CHECK
;media status is -1 after release of memory
MEDIA_CHECK:
	MOV	AL,DS:MEDIA_IN
	MOV	ES:BYTE [BX+RET_BYTE],AL
	JMP	EXIT

;	BUILD BIOS PARAMETER BLOCK
BUILD_BPB:
	MOV	ES:WORD [BX+BPBA_PTR],OFFSET BPB
	MOV	ES:WORD [BX+BPBA_PTR+2],CS
	CMP	DS:MEDIA_IN,1
	JE	EXIT
	CMP	DS:VDISK_PTR,0
	JZ	EXIT
	MOV	DS:MEDIA_IN,1
	CLD
	MOV	ES,DS:VDISK_PTR
	MOV	DI,0			;ZERO OUT FAT
	MOV	AL,DS:MEDIA_TYPE
	XOR	AL,1			;FORCE MS-DOS TO LOOK AT SECTOR COUNT
	MOV	DS:MEDIA_TYPE,AL
	STOSB				;SET FIRST 3 BYTES OF FAT
	MOV	AX,0FFFFH
	STOSW
	MOV	CX,16*512-3		;SIZE OF REST OF FAT + DIRECTORY
	XOR	AL,AL
REP	STOSB				;FAT IS ZERO
	JMP	EXIT

;	READ A SECTOR
INPUT:
	CMP	DS:MEDIA_IN,1		;MAKE SURE MEDIA IN DRIVE
	JNE	BAD_EXIT
	CALL	IN_SAVE
	CALL	CALC_ADDR		;GET SECTOR ADDRESS
	LES	DI,CS:USER_DTA		;LOAD DESTINATION ADDRESS
	CLD
REP	MOVSW				;MOVE READ DATA
	JMP	EXIT

;	WRITE A SECTOR
OUTPUT:
	CMP	DS:MEDIA_IN,1		;MAKE SURE MEDIA IN DRIVE
	JNE	BAD_EXIT
	CALL	IN_SAVE
	CALL	CALC_ADDR		;GET DESTINATION ADDRESS
	PUSH	DS
	POP	ES			;PUT DESTINATION INTO ES:DI
	MOV	DI,SI
	LDS	SI,CS:USER_DTA		;LOAD SOURCE ADDRESS
	CLD
REP	MOVSW
	JMP	EXIT

BAD_EXIT:
	MOV	ES:WORD [BX+SRH_STA_FLD],8002H
	JMP	EXIT

;	IOCTLI
IOCTLI:
	CALL	IN_SAVE
	MOV	AX,DS:VDISK_PTR
	LDS	DI,DS:USER_DTA
	MOV	DS:[DI],AX
	JMP	EXIT

;	IOCTLO
IOCTLO:
	CALL	IN_SAVE
	PUSH	DS
	LDS	DI,CS:USER_DTA
	MOV	AX,DS:[DI]
	MOV	CX,DS:[DI+2]
	POP	DS
	MOV	DS:VDISK_PTR,AX
	MOV	AX,CX
	MOV	DS:SECTORS,AX
	SHR	AX,1			;FIND FAT SIZE
	ADD	AX,CX
	MOV	CL,9
	SHR	AX,CL
	INC	AX
	MOV	DS:WORD FAT_SIZE,AX
	MOV	DS:BYTE MEDIA_IN,-1


;	COMMON EXIT
EXIT:	POP	DI
	POP	SI
	POP	DX
	POP	CX
	POP	BX
	POP	AX
	POP	ES
	POP	DS
	LRET

;	INTILLIZATION
INIT:
	MOV	AX,OFFSET INIT		;RAM IS AT END OF THIS CODE
	MOV	CL,4			;MAKE PARAS
	SHR	AX,CL
	INC	AX			;1 FOR ROUND UP
	PUSH	CS
	POP	DI
	ADD	AX,DI			;ADD CURRENT CS
	PUSH	ES
	POP	DS
	MOV	DS:WORD [BX+BR_ADDR_0],0 ;SET FREE ADDRESS
	MOV	DS:WORD [BX+BR_ADDR_1],AX
	MOV	DS:BYTE [BX+UNITS],1	;ONE UNIT
	MOV	DS:WORD [BX+BPB_PTR_OFF],OFFSET BPB_PTR
	MOV	DS:WORD [BX+BPB_PTR_SEG],CS
	JMP	EXIT

	END
xyzzy

echo extracting ram.doc
cat >ram.doc <<xyzzy
This ramdisk starts out with no memory. To allocate memory for it use:
	setram drive kbytes
where drive is the drive letter and kbytes is the number of kbytes to alloc.
Memory can only be allocated when there is currently no memory allocated
to the ramdisk.
example, if the ramdisk is drive e and a 68k ramdisk is desired
	setram e 68

To deallocate the memory that was allocated for the ramdisk, use:
	setram drive
where drive is the drive letter.
example, if the ramdisk is drive e
	setram e

This ramdisk allows up to 32 directory entries in the root directory.
To use it, there must be a line in the config.sys file
	device=ram.sys
and if an initial ramdisk is desired, the line
	setram drive kbytes
can be put in the autoexec.bat file.

Don't allocate memory if there is currently in memory a program that will
terminate and free up its memory, as the setram memory will be allocated after
this program and memory will become segmented. Also, don't run a
terminate-and-stay-resident program when memory is allocated for the ramdisk
because when the ramdisk memory is deallocated memory will be segmented.
If memory is deallocated in a .bat file, then memory will be segmented until
the .bat file terminates, so don't do anything in that bat file after
a deallocation if this segmentation could cause a problem (such as
reallocating memory with setram or running a terminate and stay resident
program).
xyzzy

echo extracting setram.c
cat >setram.c <<xyzzy
/* Set the ramdisk to the specified number of kbytes */
/* must be linked with -s1000 */
/* written by John N. White */

unsigned size;
unsigned zero[2],loci[256];
int err,drive,loc,old;

main(argc,argv)
char **argv;{
	int i;
	if(argc<2){
usage:	puts("setram - program to set size of ramdisk in kbytes\n");
		puts("usage:\n");
		puts("setram drive kbytes    to allocate memory for ramdisk\n");
		puts("setram drive           to free memory from ramdisk");
		exit(1);
	}
	i=argv[1][0];
	if(i>='a') i-=32;		/* set to upper case */
	drive=i-'A'+1;
	if(drive<0 || drive>31) goto usage;
	getold();
	if(old){
		if(argc>2){
			puts("ramdisk already has memory");
			exit(1);
		}
		clear();
		exit(0);
	}
	if(argc<3){
		puts("no memory allocated to ramdisk");
		exit(1);
	}
	size=atoi(argv[2]);
	if(size<8 || size>800) goto usage;
	loci[1]=size<<1;
	size<<=6;
#asm
	mov		ah,4ah			;modify programs allocated block
	mov		cx,cs
	sub		cx,10h
	mov		word loc_,cx
	mov		word loci_,cx
	mov		es,cx			;start of partition
	mov		bx,word size_	;new size
	int		21h
	jc		err

	mov		ax,cs			;get pointer to environment block
	sub		ax,10h
	mov		es,ax
	mov		es,es:[2Ch]
	mov		ah,49h			;dealloc environment block
	int		21h
	jc		err

	mov		ax,4405h		;IOCTL call to ramdisk
	mov		bx,word drive_
	mov		dx,offset loci_
	mov		cx,4
	int		21h
	jnc		ok
err:
	mov		word err_,ax
	jmp		main_error_
ok:
	mov		ax,3100h
	mov		dx,word size_
	int		21h
	jmp		err
#
error:
	puts("error number ");
	err&=63;
	if(err>9) putchar(err/10+'0');
	putchar(err%10+'0');
	puts(" (decimal)");
	exit(1);
}

getold(){
#asm
	mov		ax,4404h		;IOCTL call to ramdisk
	mov		bx,word drive_
	mov		dx,offset loci_
	mov		cx,2
	int		21h
	jc		err
#
	old=loci[0];
}

/* Clear the ramdisk */
clear(){
#asm
	mov		ah,49h			;free mem
	mov		es,word old_
	int		21h
	jc		err

	mov		ax,4405h		;IOCTL call to ramdisk
	mov		bx,word drive_
	mov		dx,offset zero_
	mov		cx,4
	int		21h
	jc		err
#
	return;
}
xyzzy

echo extracting makeram.bat
cat >makeram.bat <<xyzzy
echo off
rem make ram.sys and setram.exe using the DeSmet assembler

later setram.c setram.exe
if not errorlevel 1 goto nosetram
c88 setram
if errorlevel 1 goto stop
echo  
bind setram -s1000
if errorlevel 1 goto stop
echo  
del setram.o
:nosetram

later ram.a ram.sys
if not errorlevel 1 goto stop
asm88 ram
if errorlevel 1 goto stop
echo  
bind ram -a -sFFFF
echo  
del ram.o
exe2bin ram.exe ram.sys
del ram.exe
:stop
xyzzy

echo extracting int.a
cat >int.a <<xyzzy
;Program to allow a program to be interupted at any time.
;assemble with bat file makeint, for tandy 2000
;Assemble with the DeSmet assembler using the make file makeint.bat
;Written by John N. White		last mod 1/25/85
;Note that some tricks were used to get a .com file with an interupt handler
;with the DeSmet package which normally produces .exe files.
;The timer interupt is intercepted and every 20 ticks this code is entered.
;If the cs:ip that was being executed is greater than the end of this
;program (which is terminate and stay resident) then a check is made on
;the keyboard status. If both shifts and the alt key are depresed then
;the program is terminated by putting an int 21h into its code and jumping to
;it. The address that was interupted will be displayed. If cs:ip is less
;than the end of this program then every tick will be checked instead of every
;20. The normal clock tick point is entered after this program finishes.
DAT	equ	+100h			;The DeSmet stuff assumes CS:0 is the
					;start while in a .com file CS:100 is.

EXTRA	equ	0Ch			;This is the extra bytes on the stack
					;over what a simple interupt should
					;have. Tandy 2000 = 1Ah, IBM = 0Ch
					;(for dos 2.x)
	cseg
	jmp	init

check:
	sti
	push	bp
	push	ax
	push	cx
	mov	bp,sp
	mov	ax,[bp+6+EXTRA]		;1A extera stuff on stack over raw int
	mov	cl,4
	shr	ax,cl
	add	ax,[bp+8+EXTRA]
	cmp	ax,cs:addr DAT
	jbe	next_tick
	cmp	ax,0C000h
	jae	next_tick
	mov	ah,2
	int	16h
	not	al
	and	al,0Bh			;see if both shifts and alt key pressed
	jz	interupt_process
next_tick:
	pop	cx
	pop	ax
	pop	bp
tick:	db	0EAh,0,0,0,0		;will be set by init

interupt_process:
	push	bx
	push	si
;grab old cs:ip of doomed program
	mov	bx,[bp+6+EXTRA]
	push	bx
	mov	bx,[bp+8+EXTRA]
;cause return to die instead of return to doomed program
	mov	word [bp+6+EXTRA],offset die DAT
	mov	word [bp+8+EXTRA],cs
	mov	si,offset csnum DAT
	mov	cx,4
csloop:
	call	cdigit
	loop	csloop
	mov	si,offset ipnum DAT
	pop	bx
	mov	cx,4
iploop:
	call	cdigit
	loop	iploop
	mov	si,offset dstring DAT	;display dstring
dloop:
	mov	bl,0
	mov	al,cs:[si]
	inc	si
	and	al,al
	jz	done
	mov	ah,14
	int	10h			;display char
	jmp	dloop

done:
	pop	si
	pop	bx
	jmp	next_tick

die:
	mov	ax,4c01h		;terminate current process
	int	21h

;convert lowest 4 bits in bx (>>=4) to hex digit at [si--]
cdigit:
	mov	al,bl
	and	al,0Fh
	shr	bx,1
	shr	bx,1
	shr	bx,1
	shr	bx,1
	cmp	al,9
	jle	noadd
	add	al,7
noadd:	add	al,30h
	mov	cs:byte [si],al
	dec	si
	ret

addr:	dw	0FFFFh			;segment addr at end of this code
dstring:db	0Dh,0Ah,'c','s','=',0,0,0
csnum:	db	0,',',' ','i','p','=',0,0,0
ipnum:	db	0,0Dh,0Ah,0

init:
	mov	ax,351Ch		;get tick interupt vector
	int	21h
	mov	ds:word tick+1 DAT,bx
	mov	ds:word tick+3 DAT,es

	mov	ax,251Ch		;set new tick vector
	mov	dx,offset check DAT
	int	21h

	mov	ax,cs
	mov	dx,offset init+0Fh DAT
	mov	cl,4
	shr	dx,cl
	add	ax,dx
	mov	ds:addr DAT,ax
	mov	ax,3100h		;terminate and stay resident
	int	21h
	end
xyzzy

echo extracting int.doc
cat >int.doc <<xyzzy
int.com  ---  written by John N. White for the Tandy 2000 with ms-dos 2.x
int.com allows a program to be interupted at any time (not just when a
function call is being processed).

To use, just run int.com (note: only run it one time after a bootup).
Then, to interupt a program, hold down both shift keys and the alt key all
at the same time untill the program terminates. The cs and ip registers
will be displayed.

This is a terminate and stay resident program. Every time an int 1C (hex)
occures, (from the timer, about 20 times a second) the location of the
routine that was being executed is examined. If the code follows the
end of the int.com code then a bios call (16h with ah=2) is done to check
the shift status of the keyboard. If the appropriate keys are being held
down, then the return address to the program is modified to point to
a program terminate function call in int.com .
If more than one terminate-and-stay-resident programs will be run, this
should be the last one because it may interupt any program that follows it.
int.com will not interupt code preceeding it so dos function calls and
system interupt handlers will not be interupted. This means that no interupt
will occur if a program is waiting for keyboard input as a bios call handles
that. Also, no interupt will occur if the keyboard hold is on.
Interupts must be enabled or the timer tick won't be seen. Normally programs
start with interupts enabled but in debug they start disabled. Interupts
can be enabled in debug by typeing rf followed by ei .
xyzzy

echo extracting int_port.doc
cat >int_port.doc <<xyzzy
	The program int.com is not necessarily portable between different
ms-dos machines. The unportability is due to the value of EXTRA in the source.
If int 1Ch was a hardware interupt, the value of EXTRA is 0. But int 1Ch is
usually a software interupt invoked from the timer tick interupt handler
(int 8) and thus int.com must reach deeper into the stack to find the programs
cs:ip values. The value of extra can be found in two ways.
	The debugger can be used to look through the interupt code that calls
int 1Ch and the value of EXTRA can be guessed. There are 6 bytes for an
extra interupt, 2 bytes for each push, 16 bytes for a pushall on the 186.
The Tandy 2000 has int 8, a pushall, and 2 pushes in effect so
6+16+(2*2)=26 (=1Ah)    is the value of EXTRA.
The IBM has int 8, and 3 pushes in effect so
6+(2*3)=12 (=0Ch)       is the value of EXTRA.

Another way is to enter the debugger and type: (The int3 should end up at 113)
a100
cli
mov ax,0
mov ds,ax
mov word [70],113
mov [72],cs
sti
jmp 111
int3

r
g

Now, if everything is working properly, you will have two register dumps
to compare. Subtracting the SP value of the second from the first gives the
number of bytes added to the stack by the interupts. Subtract 6 from this
value to get the value EXTRA should have. (Be sure to do the arithmetic
carefully, The SP values are in hex). By the way, your machine will need
to be rebooted now.
Example:
For the Tandy 2000 the SP=FFEE and FFCE. (hex)
EEh-CEh=20h, 20h-6=1Ah and the value for EXTRA is 1Ah
For the IBM the SP=FFEE and FFDC. (hex)
EEh-DCh=12h, 12h-6=0Ch and the value for EXTRA is 0Ch

Note that int.com only interupts a program when the cs:ip values are
larger than the end of the int.com code and smaller than C0000 (hex).
I don't know whether this is appropriate for all ms-dos machines.
xyzzy

echo extracting makeint.bat
cat >makeint.bat <<xyzzy
echo off
rem make int.com

asm88 int
echo  
bind int -a -sFFFF
echo  
del int.o
exe2bin int.exe int.com
del int.exe
xyzzy

echo extracting ffind.c
cat >ffind.c <<xyzzy
/* Fast find for searching large source for a string - John N. White */
/* The first arg is the string, any additional args must be on the same line
 * (of the source file) in the correct order for the line to be printed.
 * The names of files to be searched are read from stdin untill EOF */
#define stdin 0		/* DeSmet value for stdin */
int f,curflag,fs,fe;
char *fname,fbuf[2048],line[258],curfile[128];
char *le,*lend= &line[256];

main(argc,argv)
char **argv;{
	int i,j;
	if(argc<2){
		puts("need string to search for");
		exit(1);
	}
	findall(argc,argv);
}

/* find next file and set f to it */
nextfile(){
	int c,i;
	if(f>0) close(f);
	curflag=1;
	fe=fs=2048;
loop:
	while((c=getc(stdin))<=' ' || c==',') if(c<0) exit(0);
	i=0;
	do{ if(i<127) curfile[i++]=c; }
		while((c=getc(stdin))>' ' && c!=',');
	curfile[i]=0;
	f=open(curfile,0);
	if(f<=0){
		puts("******** can't open file ");
		puts(curfile);
		puts("\n");
		goto loop;
	}
}

/* find all lines in the current file containing string */
findall(argc,argv)
char **argv;{
	char *p,*q,*r,*string;
	int c;
	string=argv[1];
	c= *string;
loop:
	getline();
	for(p=line;p<le;p++) if(*p==c){
		for(q=p,r=string;*r && *r== *q;q++,r++);
		if(!*r && cmpnext(argc,argv,q)){
			if(curflag){
				puts("---- file: ");
				puts(curfile);
				puts(" ----\n");
				curflag=0;
			}
			puts(line);
			puts("\n");
			goto loop;
		}
	}
	goto loop;
}

/* compare next arg with remainder of string, ret true if ok */
cmpnext(argc,argv,cline)
char **argv, *cline;{
	char *p,*q,*r,*string;
	int c;
	if(argc<3) return(1);	/* if no more args */
	string=argv[2];
	c= *string;
	for(p=cline;p<le;p++) if(*p==c){
		for(q=p,r=string;*r && *r== *q;q++,r++);
		if(!*r && cmpnext(argc-1,argv+1,q)) return(1);
	}
	return(0);
}

/* get the next line of the current file into line */
getline(){
	int j;
loop:
	if(fe<1) nextfile();
	for(le=line;
		(j=fs<fe?fbuf[fs++]:((fs=1,(fe=read(f,fbuf,2048))<1)?'\n':*fbuf))!='\n'
		&& le<lend;
		le++) *le=j;
	*le=0;
	if(! *line) goto loop;
}
xyzzy

echo extracting ffind.doc
cat >ffind.doc <<xyzzy
ffind - written by John N. White
ffind scans files whose names are entered through stdin (until end-of-file).
If the args match a line in a file, then the name of the file and all lines
with matches are printed.
The args are considered to match a line if all the args are contained in the
line and in the correct order.
The filenames fed in may be separated by spaces, tabs, commas, or new-lines.
Example:
	ffind if ( ){
matches:
	if(i==0){
	if  ( i == 0 ){
but not
	if(i==0) {
	(i==0){ if

Note that if a set of files are to be searched many times, The names of those
files can be put in a file (say, "list") and a macro can be
defined (say, "f.bat") that scans those files. f.bat whould contain:
	ffind %1 %2 %3 %4 %5 %6 %7 %8 %9 < list

When entering filenames by hand remember end-of-file is CTRL Z.
xyzzy