home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 September
/
Simtel20_Sept92.cdr
/
msdos
/
pcmag
/
vol9n03.arc
/
CHKFILEC.ASM
< prev
next >
Wrap
Assembly Source File
|
1990-01-05
|
60KB
|
980 lines
PAGE 60,132
TITLE CHKFILEC - High performance file checker - compressed.
; SUBTTL General program description and use of common storage
; ----------------------------------------------------------------------------;
; CHKFILEC - characterize files by check values, time, date and size. ;
; ----------------------------------------------------------------------------;
; CHKFILE 1.0 ■ PCDATA TOOLKIT Copyright (c) 1990 Ziff Communications Co. ;
; PC Magazine ■ Wolfgang Stiller ;
; ;
; Purpose: ;
; CHKFILEC will read files and then characterize them with unique ;
; check values, update date, update time and file size. This data ;
; will be written in compressed form to the report file. This ;
; data can be used to validate file integrity by using program ;
; CFcompC to compare the report files and report any changes. ;
; ----------------------------------------------------------------------------;
;Format: ;
; ;
;CHKFILEC filespec1 filespec2 [/D] [/I:aa] [/T] [/1] [/2] ;
; ;
; filespec1 is the file specification for the file(s) to read. Wild cards ;
; such as * or ? can be used as well as a drive or directory. ;
; filespec2 will contain compressed report of file check data for CFcompC. ;
; "/D" Display directory entries as well as regular files ;
; "/I:aa" Ignore files beginning with characters aa (must be 2 chars). ;
; "/T" Ignored if coded. Totals are always generated. ;
; "/1" Utilizes an alternate algorithm for check value 1. ;
; "/2" Utilizes an alternate algorithm for check value 2. ;
; ;
; ----------------------------------------------------------------------------;
;Remarks: ;
; CHKFILEC has been specifically designed for high speed operation using ;
; a minimal of resources. It will run on any DOS PC with at least 64K ;
; free memory. CHKFILEC will read all files independent of whether they ;
; have the hidden or the system attribute set. CHKFILEC produces a ;
; report line for each file (and optionally directory) matching the ;
; primary file specification. CHKFILEC will report for each file in the ;
; current or specified directory the following information: File status ;
; byte, file or directory name, check value 1, check value 2, file size, ;
; and the DOS date and time of last update. This information is written ;
; to the report file specified in filespec2. All values are written in ;
; compressed (binary) form to this file. The file status byte identifies ;
; the file type and whether a read or open error occurred while ;
; processing the file. The filename is encrypted to make it more ;
; difficult to locate and modify this file. The report file in addition ;
; to always containing totals of the check values, contains 32 bits of ;
; internal check information which makes makes the file self-checking. ;
; CFcompC verifies this check data and will refuse to process any report ;
; file which has been damaged. ;
; ;
; If CHKFILEC encounters an error related to misuse of its parameters, it ;
; will produce an error message followed by a beep and a request for a ;
; key press. After a key press, it will display a description of the ;
; correct syntax. ;
; ;
; Both check values utilize a very high speed algorithm for computation. ;
; Check value 1 is an arithmetic sum (or difference for /1) of all bytes ;
; in each file being checked. Check value 2 utilizes a high speed hash ;
; type algorithm which utilizes circular shifts and the exclusive or ;
; function to generate a unique 16 value which is dependent not only on ;
; the value of each byte in the file, but the order of those values. If ;
; /1 or /2 are specified, either or both of these algorithms can be ;
; changed. This change is done at initialization time, so that the speed ;
; of the check value computation is not affected by these options. The ;
; /1, /2 and /T options are provided mainly to make CHKFILEC compatible ;
; with CHKfile. ;
; ;
; ----------------------------------------------------------------------------;
; CHKFILEC will report for each file in the current or specified directory ;
; the following information: ;
; Name of file, check values, (two 16 bit values ), the DOS time ;
; and date stamps of the file, and file size in hex bytes ;
; ;
; Format for report (filespec2) lines: Field size in bytes: ;
;File File Name + Chk Chk File Update Update 1 ;
;Type Extension: Val1 Val2 Size: Date: Time: 1 ;
;---- ------------ ---- ---- -------- -------- -------- 1__________ ;
; T filename.ext xxxx yyyy FileSize mm/dd/yy hh:mm:ss 1 ;
; 1 1 1 1 1 1 1 1 ;
; 1 1 1 1 1 1 1__Time of last update 2 ;
; 1 1 1 1 1 1__________ Date of last update 2 ;
; 1 1 1 1 1____________________ Size of file in bytes 4 ;
; 1 1 1 1___________________________ Check value2 for file 2 ;
; 1 1 1________________________________ Check value1 for file 2 ;
; 1 1_________________________________________ File name(encrypted) 12 ;
; 1___________________________________________________1=file 2=directory 1 ;
; Total record length for report file (REP_REC) is 25 bytes. ;
; ;
; ** See REP_REC definition for detail on field sizes ** ;
; ;
; Check value 1 - Is a modified check sum or difference - 16 bits. ;
; Check value 2 - Is a modified cumulative XOR of each character in ;
; file - 16 bits. ;
; ;
; The entire report file once written is self-checking because of the ;
; Totals record which is written out after all file check records. ;
; The totals record contains a final 32 bits of check data which is ;
; calculated by a different algorithm than that used by the files. This ;
; Check data will be validated each time the report file is read. ;
; ;
; ----------------------------------------------------------------------------;
; CHKFILEC will return the following DOS ERRORLEVELs: ;
; ;
; 00 - Normal completion - at least one file was reported. ;
; 04 - No files were checked. Either none match the filespec or all ;
; matched files were ignored by the /I parameter. ;
; 08 - Normal processing except open or I/O error detected on a file being ;
; checked. ;
; 32 - Open or write failed to the report output file ;
; 64 - (40h) Program failure due to invalid path or drive specified. ;
; 128 - (80h) Syntax error or missing parameters on program initiation. ;
; ;
; ----------------------------------------------------------------------------;
;---------------------------------------------------------------;
; Constants: ;
;---------------------------------------------------------------;
BOX EQU 254 ;Small box character code
CR EQU 0Dh
LF EQU 0Ah
CRLF EQU 0A0Dh ;Carriage return line feed.
CSEG SEGMENT
ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:CSEG
;---------------------------------------------------------------;
; D T A description (data transfer area): ;
;---------------------------------------------------------------;
ORG 80h ;DTA and parameter line in PSP
DTA_start DB 21 DUP (?) ; Reserved part of DTA + parm start
DTA_F_attr DB ? ; File attribtute
DTA_F_time DW ? ; File time
DTA_F_date DW ? ;File date
DTA_FS_lowr DW ? ;File size lower part
DTA_FS_HIr DW ? ;File size upper part
DTA_F_name DB 13 DUP(?) ;File name and extension
SUBTTL Main program
;******************************************************************************;
;** Main program begins here -CHKFILEC- **;
;******************************************************************************;
ORG 100h ; THIS IS A COM TYPE PROGRAM
CHKFILEC:
CALL Parse_parms_Print_Header ;Parse cmdline paramters + prnt header
; + find first match on file name
; ----------------------------------------------------------------------------;
; F O R M A T F I L E I N F O ;
; Process information extracted from the directory entries (the DTA) ;
; ----------------------------------------------------------------------------;
; GENERAL ALGORITHM: ;
; 1) Check if this is a .. or . directory or a file to ignore (/I:xx) ;
; If its to be ignored, go try to do another FIND NEXT generic match. ;
; 2) Extract file name, size, date and time from the DTA. ;
; 3) IF its a directory, indicate by placing DIR. in the checksum field, ;
; otherwise the file will be opened and processed. ;
; ----------------------------------------------------------------------------;
Format_File_Info:
;----------------------------------------------------------------------------;
; Check if this is a file name to ignore (the .. and . directories or a file ;
; begining with xx from the "/I:xx" command line parameter). ;
;----------------------------------------------------------------------------;
MOV SI, offset DTA_F_Name ;Move FROM DTA file name field
MOV AX,WORD PTR [SI] ;load 1st 2 chars of this file name
CMP AL,'.' ;Is it a "." or ".." directory?
JNE Check_For_Ignore_files ; No, so check for ignore files
JMP Find_Next_File ; Yes, it is so skip this file
Check_For_Ignore_Files:
CMP AX,Ignore_F_Name ;Is this the file name to ignore?
JNE Xtract_DTA_Info ; No, so go ahead + process this file
JMP Find_Next_File ; Yes, so skip this file...
;----------------------------------------------------------------------------;
; Extract info from the DTA (data transfr area) ;
; Extract file name, size and update date and time. ;
;----------------------------------------------------------------------------;
Xtract_DTA_Info:
MOV Files_Found,'Y' ;Indicate at least 1 file was matched!
MOV CX,12 ;Scan 12 characters of filename (max)
; SI= offset DTA_F_Name ;SI already contains loc of DTA_F_NAME
MOV DI, offset Rep_F_Name ;Move to output record file name
Xfer_file_name: ;transfer filename from DTA to Rep_rec
LODSB ;Load one byte from DTA for transfer
OR AL,AL ;See if this=0 (end of file name)
JZ Zero_fill ;If end, then zero fill rest of name
ROL AL,1 ;Do quick and dirty encryption
STOSB ;Else store char in REP_Rec file name
LOOP Xfer_file_name ;continue until done
JMP Short Extract_F_Size ;Go and format file size for output
Zero_fill: ;zero fill remainder of file name
MOV AL,0
REP STOSB ;Store remaining characters
; --------------------------------------------------;
; Extract file size from DTA for display ;
; --------------------------------------------------;
Extract_F_size: ;Format DTA's file size for output
MOV AX,DTA_FS_HIr ;High portion of file size
MOV Rep_FS_Hir,AX ; transfer it onto report file
MOV AX,DTA_FS_Lowr ;lower portion of file size
MOV Rep_FS_Lowr,AX ; transfer it onto report file
; --------------------------------------------------;
; Extract file date from DTA for display ;
; --------------------------------------------------;
MOV AX,DTA_F_date ;Date of last file update
MOV Rep_F_Date,AX ; Transfer file date to report file
; date is in yyyyyyym mmmddddd format (year is offset from 1980)
; --------------------------------------------------;
; Extract file time from DTA for display ;
; --------------------------------------------------;
MOV AX,DTA_F_time ;time of last file update
; time is in hhhhhmmm mmmsssss format (seconds are 0-29 in 2 sec intervl)
MOV Rep_F_Time,AX ; transfer to the report file
; Check if this file is a directory entry rather than a file
TEST DTA_F_attr,00010000B ;Check directory bit of file attribute
JZ Open_the_File ;If not continue with normal process
; Do special handling for directory entries (rather than file entries):
MOV Rep_F_Type,2 ;2 means this is a directory
Finish_with_Zero_Check_Vals: ;Termnate with zeros in chk val fields
MOV Rep_CHK_Sum,0 ;Zero the check value 1 on report file
MOV Rep_XOR_Sum,0 ;Zero the check value 2 (XOR sum)
JMP Write_Rep_Rec ;Skip rest of processing and go write
; this dir entry + find next file
; --------------;
; Open the file ;
; --------------;
Open_the_File:
MOV Rep_F_Type,1 ;1 means this is a file not a dirctry
MOV DX,offset DTA_F_name ;point to file name in DTA
MOV AX,3D00h ;DOS open file (handle) for read cmnd
INT 21h ;invoke DOS
JNC Continue_Open ;If no errors continue processing
; a report that open failed
; This open should never fail...(OS2 can have files open which will cause fail)
MOV File_Error_Flag,'Y' ;Indicate that file had serious error
MOV Rep_F_Type,3 ;3 means open fail on THIS file
JMP SHORT Finish_with_Zero_Check_Vals ;No valid CHK vals avail
Continue_Open:
MOV BX,AX ;Save file handle
XOR BP,BP ;zero out (clear) EOF indicator
; -------------------------------------------;
; Initialize check values for each file. ;
; -------------------------------------------;
MOV DI,BP ;Zero check sum (check val 1)
MOV DX,BP ;Zero XOR sum (check value 2)
; ----------------------------------------------------------------;
; START OF LOOP TO READ AND SCAN RECORDS ;
; ----------------------------------------------------------------;
; REGISTER USAGE CONVENTIONS IN READ_FILE LOOP: ;
; ;
; AL - Each new character read into this register ;
; BP - EOF (End Of File) indicator (flag) ;
; BX - Contains current file handle ;
; CX - number of chars read in -decreasing counter ;
; DI - Contains check value 1 for this file (CHKSUM) ;
; DX - Check value 2 for file and periodically start of buffer ;
; SI - index pointing into file BUFFER ;
; ----------------------------------------------------------------;
Read_File:
PUSH DX ;Save the XOR sum (check value 2)
MOV DX,OFFSET Buffer ;INPUT BUFFER
MOV SI,DX ;SI is for BUFFER reads later
MOV CX,0FC00h ;MAX # of bytes to read
MOV AH,3Fh ;Setup to read from file
INT 21h ;Call DOS
POP DX ;Resume using DX for check val 2
JNC Read_was_OK ;IF neither error nor EOF occurred.
MOV File_Error_Flag,'Y' ; No, we've got a read error
MOV Rep_F_Type,4 ; 4 means read error
JMP SHORT Done_reading ; Write out this REP_REC
Read_was_OK:
OR AX,AX ;Check if ax=0 no records read
JZ Done_reading ;If no records, close this file..
CMP AX,CX ;See of max number or records read
JE Skip_EOF_ind ;If we have compltly filled buffer
MOV BP,SP ; Else put EOF indicator in BP
Skip_EOF_ind: ;Jump here to skip setting EOF
MOV CX,AX ;SAVE # of BYTES read in CX
JCXZ Done_reading ;Quit if nothing read
XOR AH,AH ;Zero upper part of AX for addition
; Innermost read char loop - keep this fast!
NEXT_CHAR:
LODSB ;Get char into AL
XOR DL,AL ;cumulative XOR into DX - Chck val 2
;following instr modified by /2 parm
ROL_op: ROL DX,1 ;Keep shifting to XOR sum to right
;following instr modified by /1 parm
ADD_op: ADD DI,AX ;cumulative check sum - Chck val 1
LOOP NEXT_CHAR ;CONTINUE SCANNING CHARS UNTIL EOB
OR BP,BP ;Check EOF indicator (=77h if EOF)
JNZ Done_reading ;IF EOF, quit this file...
JMP SHORT Read_File ;TRY TO READ SOME MORE
Done_reading: ;Come here on EOF or error reading
MOV AH,3Eh ;Prepare to close the file
INT 21h ;Let DOS close file
MOV Rep_CHK_Sum,DI ;Put check sum (chk val 1) in rep rec
MOV Rep_XOR_Sum,DX ;Do same with XOR sum (check val 2)
ADD Tot_CHK_Sum,DI ;Total check value 1 for all files
ADD Tot_XOR_Sum,DX ;Total check value 2 for all files
;---------------;
; Write Rep_REC ;
;---------------;
Write_Rep_Rec:
MOV DX, offset Rep_rec ;prepare to write output record
MOV CX,25 ;25 chars in Rep_rec
MOV BX,Filespec2_Handle ;Handle for std output device
MOV AH,40h ;DOS Write function
INT 21h
JNC Calc_Global_CHK_data ;If write was OK, then continue
JMP Report_Write_Error ;Else notify user of fatal error
;-----------------------------------------------------------------------;
; CALC GLOBAL CHECK DATA - Calculate global checksum and XOR values for ;
; the report file. This information allows the report file to be ;
; self checking. Any change to it can then be detected. ;
;**Note, this algorithm is different than that used for file checking** ;
;-----------------------------------------------------------------------;
Calc_Global_CHK_Data:
MOV SI,DX ;Get start of buffer to calc chk data
;CX should still contain 25 (rec len)
MOV DX,Rep_Rec_XORval ;Pick up cumulative XOR from before
MOV BX,Rep_Rec_CHKsum ;Get last CHKsum(for entire rep file)
CALL Calc_Sums ;Accumulate check values for this rec
MOV Rep_Rec_XORval,DX ;Save cumulative XOR value
MOV Rep_Rec_CHKsum,BX ;Save cumulative CHKsum
;-------------------------------;
; Search for next matching file ;
;-------------------------------;
Find_Next_File:
MOV AH,4Fh ;Search for next matching file
INT 21h ;Do search
JC Finish_Processing ;If no more matches, terminate.
JMP Format_File_Info ;If no errors, process this file
Finish_Processing: ;Else, Prepare to terminate
;If no files matched the filespec1 and were not ignored (/I:__) then just
;write a one byte zero record to indicate no matches.
CMP Files_Found,'Y' ;Were any files at all checked?
JE Write_Totals_record ; If so, write out totals record
JMP No_Files_Matched ; Else just write zero record
Write_Totals_Record:
; Move cumulative file totals into Rep_REC for display
MOV DI,Tot_CHK_Sum ;Prepare cumulative totals for dsply
MOV DX,Tot_XOR_Sum
MOV Rep_CHK_Sum,DI ;Xfer to coorespnding report fields
MOV Rep_XOR_Sum,DX
; Now save check data for this entire report file as the last 4 bytes:
MOV DX,Rep_Rec_XORval ;Pick up cumulative XOR val
MOV BX,Rep_Rec_CHKsum ;Get cumulative CHKsum value
MOV Rep_FS_Lowr,DX ;Save XOR on file
MOV Rep_FS_HIr,BX ;Save CHKsum
; Write the cumulative file totals and check data line
MOV DX, offset Rep_CHK_SUM ;Write totals rec (only chk+Xor sums)
MOV AH,40h ;Write function
MOV BX,Filespec2_Handle ;Report file handle
MOV CX,8 ;Write only first 8 chars
INT 21h ;Actually write out the totals line
JNC Check_drive_path_changes ;If write, was OK
Report_Write_Error:
MOV DX, OFFSET Write_fail_Msg ;tell user of I/O error
MOV AH,09h ;DOS display string function
INT 21h
;-----------------------------------------------------------------------;
; NORMAL TERMINATION starts here. All termination conditions where at ;
; least some records were matched begin here. ;
;-----------------------------------------------------------------------;
; 1) Restore user back to his original drive and path (if changed) ;
; 2) Close the report file ;
; 3) Set error level of 8 if we had file IO or open problems ;
; 4) Terminate with errorlevel of 0 (all is OK) or 8 ;
;-----------------------------------------------------------------------;
Check_drive_path_changes:
Call Restore_Original_Path ;Set back to original path if changd
Call Restore_Original_Drive ;Set back to original drive if changd
MOV BX,Filespec2_handle ;Prepare to close the report file
MOV AH,3Eh ;DOS Close function
INT 21h
MOV AL,00h ;Plan on termination with 0 errlvl
CMP File_Error_Flag,'Y' ;Did we get a file I/O error ?
JNE End_Execution ; If not, term with 0 error level
MOV AL,08h ; Else, terminate with 8 error level
End_Execution: ;Successful termination of program
MOV AH,4Ch ;terminate with error level in AL
INT 21h
SUBTTL General Purpose subroutines
PAGE
;******************************************************************************;
;** General purpose subroutines follow **;
;******************************************************************************;
;------------------------------------------------------------------------------;
; Restore orginal drive - if disk changed, set back to original disk. ;
;------------------------------------------------------------------------------;
Restore_Original_Drive: ;Set back to original drive if changd
CMP Drive_Spec_Present,'Y' ;Did user overide drive?
JNE Restore_Drive_RET ;If not then return to caller
MOV DL,Old_disk ;get original drive
MOV AH,0Eh ;Set current drive function
INT 21h
Restore_Drive_RET:
RET
;------------------------------------------------------------------------------;
; Restore orginal path - if path changed, set back to original disk. ;
;------------------------------------------------------------------------------;
Restore_Original_Path: ;Set back to orignl path if changed
CMP Path_Present,'Y' ;Did user overide path (Directory)
JNE Restore_Path_RET ;If not, return to caller
MOV AH,3Bh ;Change current directory function
MOV DX,offset Old_path ;Original path
INT 21h ;Set path back to original
Restore_Path_RET:
RET
;---------------------------------------------------;
; C A L C _ S U M S - Calculate check values ;
;---------------------------------------------------;
; This is a special version for CFcompC + CHKFILEC. ;
;---------------------------------------------------;
; INPUT: SI = pointer to file BUFFER to scan ;
; CX = # of characters to read ;
; DX = cumulative XOR sum - check value 1 ;
; BX = cumulative CHK sum - check value 2 ;
; ;
;Register conventions: ;
; ;
; AL - Each new character read into this register ;
; CX - number of chars read in -decreasing counter ;
; BX - Contains checksum for this file ;
; DX - XOR check value ;
; SI - index pointing into file BUFFER ;
; ;
; None of above registers are saved and restored. ;
; --------------------------------------------------;
Calc_Sums:
XOR AH,AH ;Zero upper part of AX for addition
Grab_next_char:
LODSB ;Get char into AL
ROR DX,1 ;Keep shifting to XOR sum to left
XOR DL,AL ;cumulative XOR into DX
SUB BX,AX ;cumulative check subtraction
LOOP Grab_Next_Char ;CONTINUE SCANNING CHARS UNTIL EOB
RET ;All done calculating sums!
SUBTTL Definition of Data structures
PAGE
;******************************************************************************;
;** Definition of Data areas follow **;
;******************************************************************************;
File_Error_Flag DB 'N' ;='Y' indicates file IO or open error
;Report file record description:
Rep_Rec EQU $ ;Name for the entire output record
Rep_F_Type DB 0 ;Indicates if its a file (1) or dir(2)
;or file with open err(3) or IO err(4)
Rep_F_Name DB 12 DUP (0) ;12 spaces reserved for filename
Rep_CHK_Sum DW 0 ;Check sum: 16 bits
Rep_XOR_Sum DW 0 ;Exclusive OR sum
Rep_FS_Lowr DW 0 ;File size lower part of double word
Rep_FS_HIr DW 0 ;File size: upper part of double word
Rep_F_Date DW 0 ;Date of last file update:
Rep_F_Time DW 0 ;Time of last file update
Rep_Rec_XORval DW 0 ;Global cumulative XOR value(rep rec)
Rep_Rec_CHKsum DW 0 ;Global cumulative CHK value(rep rec)
Old_Path DB '\' ;Force 1st char of save area to = '\'
DB 64 DUP (0) ;Save area to restore original path
Old_Disk DB 0 ;Save area for original drive spec
Drive_Spec_Present DB 0 ;Set = to "Y" if drive spec present
Path_Present DB 0 ;Set = to "Y" if path specified
Tot_CHK_Sum DW 0 ;total of all check sums (all files)
Tot_XOR_Sum DW 0 ;total of exclusive or sums
Ignore_F_Name DW ' ' ;ignore file names starting with this
Filespec2_handle DW 0 ;Handle for the report file
Files_Found DB 'N' ;Indicates in any files matched:Y or N
Write_fail_Msg DB 'File2 write failed',CR,LF,'$'
SUBTTL INIT data and code which is also input BUFFER
PAGE
;******************************************************************************;
;** Definition of file buffer Data areas and code follow: **;
;** All the following storage will be overlaid when records are read in **;
;******************************************************************************;
Buffer label byte ;All storage + code following is in
; the input file buffer.
; address must be less than 3F0 hex.
; ----------------------------------------------------------------------------;
; Initialization code - parse parms + put out msgs and find intial file match ;
; ----------------------------------------------------------------------------;
Parse_parms_Print_Header: ;Parse input parameters + print header
MOV SI,80h ;Parameter area in PSP
MOV CL,[SI] ;Get # of chars in input parm
XOR CH,CH ;Clear upper byte of char count
OR CL,CL ;Check for 0 chars (NO INPUT)
MOV BP,128 ;Error level code for syntax error
JZ Display_Syntax_Msg ;IF no parms, put out help information
INC SI ;Point to 1st character
CLD ;FORWARD DIRECTION
Del_Spaces:
LODSB ;Get byte at DS:SI and inc SI
CMP AL,' ' ;Is it a space?
JNE Set_File_names ;If not we have a file name..
LOOP Del_Spaces ;continue checking until last char
MOV BP,128 ;Error level code for syntax error
JMP SHORT Display_Syntax_Msg ;Explain syntax to user
Syntax_Err_Exit: ;Come here on syntax error
MOV AH,09h ;DOS display string function
INT 21h
CALL Wait_For_Key ;Beep + force user to hit a key{
Display_Syntax_Msg:
MOV DX, OFFSET Syntax_Msg ;Prepare ERROR Message
MOV AH,09h ;DOS display string function
INT 21h
Call Restore_Original_Drive ;Set back to original drive if changd
MOV AX,BP ;Get error level in AL from lower BP
MOV AH,4Ch ; terminate with errorlevel in AL
INT 21h
;---------------------------------------------------------------------------;
; Conventions for command line parsing: ;
; SI points to next char to be checked in the parm field at DS:80 ;
; CX is count of characters left to be scanned ;
; BP points to start of filespec1 for find next processing ;
;---------------------------------------------------------------------------;
;----------------------------------------;
; Parse filespec1 and xfer in msg field ;
;----------------------------------------;
Set_File_Names:
CMP BYTE PTR [SI],':' ;Check for presence of drive spec
JNZ Read_file_spec
AND AL,5Fh ;Capitalize drive letter
SUB AL,'A' ;Convert to numeric form
MOV New_Drive,AL ;Save num drive - change to it later
MOV Drive_spec_present,'Y' ;Indicate user is overriding drive
MOV AH,19h ;DOS get current drive function
INT 21h
MOV Old_disk,AL ;Save current disk
ADD SI,2 ;adjust pointers and
SUB CX,2 ; counters to skip drive spec
Read_file_spec:
DEC SI ;point back to 1ST letter of filespec
MOV BP,SI ;Save a copy of filespec start
MOV DI, offset User_File_Spec ;prep to transfer file name to msg
Scan_To_File_Spec_End:
; start scanning the file specification and transfer into output field
LODSB ;Get next char of file spec
CMP AL,' ' ;check valid separator character
JBE File_Spec_End_Found
CMP AL,' ' ;check valid separator character
JE File_Spec_End_Found
STOSB ;Store char as part of User_file_spec
LOOP Scan_To_File_Spec_End
INC SI ;Adjust BX if no separator char found
File_Spec_End_Found:
MOV BX,SI
DEC BX ;= next char loc after filespec
MOV BYTE PTR [BX],00 ;zero terminate the filespec: ASCIIZ
PUSH AX ;Save last char examined
MOV AX,CRLF ;Put out carriage return line feed
STOSW ; combination as a single word
MOV AL,LF ;Include extra line feed
STOSB
POP AX ;Restore last character examined
;---------------------------------------------------------------------------;
; Parse filespec2: (Not a called subroutine - just a code module) ;
; Input: ;
; SI points to next char to be checked in the parm field at DS:80 ;
; CX is count of characters left to be scanned ;
; ;
; Returns: ;
; DI points to byte after last char in filespec ;
; Filespec is zero terminated in the parameter area ;
;---------------------------------------------------------------------------;
Parse_Filespec2: ;Extract and zero terminate filename
OR CL,CL ;Check for 0 chars (NO INPUT)
JZ Bad_filespec2 ;If no parms, display error message
Del_Spaces2:
LODSB ;Get byte at DS:SI and inc SI
CMP AL,' ' ;Is it a space?
JNE Get_Filespec2 ;If not, we should have a file name..
LOOP Del_Spaces2 ;Continue checking until last char
Bad_Filespec2:
MOV DX, OFFSET Bad_file2_Msg ;tell user filespec2 is needed
MOV BP,32 ;Terminate with 32 (20h) err lvl
JMP Syntax_Err_Exit ;Display error msg + correct syntax
;--------------------------------------------;
; Parse file spec and zero byte terminate it ;
;--------------------------------------------;
Get_Filespec2:
DEC SI ;point back to 1ST letter of filespec
MOV File2_Start,SI ;Save a copy of filespec2 start
Scan_to_filespec2_end:
; start scanning the file specification and transfer into output field
LODSB ;Get next char of file spec
CMP AL,' ' ;Check valid separator character
JBE Filespec2_End_Found
CMP AL,'/' ;Check for valid separator
JE Filespec2_End_Found
CMP AL,',' ;Check for valid separator
JE Filespec2_End_Found
LOOP Scan_to_filespec2_end
INC SI ;Adjust SI if no separator char found
Filespec2_end_found:
DEC CX ;Correct the char remaining count
; SI is pointing 2 characters past end of filespec at this time
MOV DI,SI
DEC DI ;DI points to 1st char after filespec2
MOV BYTE PTR [DI],00 ;zero terminate filespec2: ASCIIZ
;---------------------------------------------------;
;Check parameter characters left. ;
;At this point we begin the scan for the /x type ;
;Parameters. (if any). ;
;---------------------------------------------------;
Check_parm_chars_left: ;Check if enough chars left for a parm
CMP CX,01 ;Check if we out of chars to scan
JA Parm_Scan ; if not continue chcking for /parms
JMP Open_Filespec2 ; If so, cont with next step of init
Parm_Scan: ;Check for presence of a /_ parm
CMP AL,'/' ;check for "/" parm character
JE Parm_found
CMP AL,' ' ;check for blanks
JNE Unrecog_parm ;If other than blank its illegal...
LODSB ;Keep checking next character
LOOP Parm_Scan
JMP short Open_Filespec2 ;Continue with initialization...
Parm_Found: ;Check if parm is valid
DEC CX ;Adjust chars remaining counter
JCXZ Unrecog_parm ;IF no chars left then parm is invalid
LODSB ;Get next char
DEC CX ;Adjust chars remaining counter
CMP AL,'2' ;Is it alternate chk val 2 (XOR) parm?
JE X2_parm ;exclusive or parm detected (/2)
CMP AL,'1' ;Is it alternate Chk val 1 (Sum) parm?
JE C1_parm ;/1 parameter detected..
AND AL,5Fh ;Capitalize char
CMP AL,'T' ;Is it the "Totals wanted" parm?
JE T_parm ;T parameter detected
CMP AL,'D' ;Is it Directory display parm?
JE D_parm ;D parameter detected..
CMP AL,'I' ;Is it Ignore file parm?
JE I_parm ;I parameter detected.. else its...
Unrecog_parm: ; an illegal paramter:
MOV DX, offset Bad_Parm_MSG ;indicate illegal parm was found
MOV BP,128 ;Error level code for syntax error
JMP Syntax_ERR_Exit ;terminate with error level set
;T parm is maintained for compatibility with CHKFILE only...it is ignored
T_parm: ;This parameter has no effect
LODSB ;Keep checking next character
JMP SHORT Check_Parm_chars_left ;Check for additional parms
X2_parm:
MOV WORD PTR [ROL_op],0CAD1h ;patch ROL op code into ROR DX,1 op
LODSB ;Keep checking next character
JMP SHORT Check_Parm_chars_left ;Check for additional parms
C1_parm: ;Use of alt CHK sum algor(/1 parm)
MOV WORD PTR [ADD_op],0C729h ;patch ADD op code into SUB DI,AX op
LODSB ;Keep checking next character
JMP SHORT Check_Parm_chars_left ;Check for additional parms
D_parm:
MOV WORD PTR [File_Attrib],0017h ;Change file attrib to incl DIRs
LODSB ;Keep checking next character
JMP SHORT Check_Parm_chars_left ;Check for additional parms
I_parm:
CMP CX,03 ;We must have at least 3 chars left
JB Unrecog_parm ;If not, this is a bad parameter
LODSB ;Check next character
CMP AL,':' ; it should be ':'
JNE Unrecog_parm ;If not, its bad parm time again..
SUB CX,03 ;Adjust chrs remaining counter
LODSW ;Get file prefix to ignore
; Now capitalize the file name prefix, only if lower case alphabetic
CMP AL,'a' ;could this be a lower case alpha?
JB Check_2nd_char ;If not go ahead and check other char
CMP AL,'z' ;could this be a lower case alpha?
JA Check_2nd_char ;If not go ahead and check 2nd char
AND AL,5Fh ;Bump character into uppercase
Check_2nd_char: ;Now check the 2nd file ignore char
CMP AH,'a' ;could this be a lower case alpha?
JB I_store ;If not go ahead and store the char
CMP AH,'z' ;could this be a lower case alpha?
JA I_store ;If not go ahead and store the char
AND AH,5Fh ;Bump character into uppercase
I_store:
MOV Ignore_F_Name,AX ;Store file prefix (for ignore)
LODSB ;Keep checking next character
JMP Check_Parm_chars_left ;Check for additional parms
Invalid_path:
MOV DX,offset Bad_path_MSG ;Indicate problem with path
MOV BP,64 ;Errorlevel for bad drive or path
JMP Syntax_Err_Exit ;Report error+displ correct syntax
;--------------------------------------;
; Open the report file (filespec2): ;
;--------------------------------------;
Open_Filespec2:
MOV DX,File2_Start ;DX contains filespec2 start
MOV AH,3Ch ;DOS create and truncate file func
XOR CX,CX ;Set CX=0, means normal file attrib
INT 21h ;invoke DOS
JNC Filespec2_Open_OK ;If no errors continue processing
MOV DX, OFFSET F2_open_fail ;tell user filespec2 open failed
MOV BP,32 ; terminate with 32 error level
JMP Syntax_Err_Exit ;Display error followed by syntax
Filespec2_Open_Ok:
MOV Filespec2_handle,AX ;Save the file handle
;--------------------------------------------------------------;
; Set system default disk drive to that specified in filespec1 ;
;--------------------------------------------------------------;
Set_Filespec1_New_Drive:
CMP Drive_spec_present,'Y' ;Did user override drive spec?
JNE Check_for_DIR ; No, then we don't need to change it
MOV DL,New_Drive ; Else get numeric drive spec + chng
MOV AH,0Eh ; DOS select disk function
INT 21h ; Set to drive in filespec1
JNC Check_For_DIR ; Was the disk drive specified OK?
JMP Invalid_Path ; If drive specified is invalid..
Check_for_DIR: ;See if PATH included in filespec1
MOV CX,BX ;End of filespec1 + 1
SUB CX,BP ;Calc length of filespec1
PUSH CX ;Save length for use later
STD ;Prepare to scan filespec1 backwards
MOV DI,BX ;Start from end
DEC DI ; of filespec1
MOV AL,'\' ;Scan filespec1 for presence of "\"
REPNE SCASB ;Scan to last \ from end of filespec1
CLD ;Reset direction flag to forward
JNZ Display_Heading ;IF, no path found in filespec1
MOV Path_Present,'Y' ;Set flag to indicate path present
INC DI ;Point to "\" character
MOV BYTE PTR [DI],0 ;Zero terminate the PATH (clobber \)
;Determine current directory
MOV SI,offset Old_path+1 ;Place to store original directory
XOR DL,DL ;Zero DL in order to use default drive
MOV AH,47h ;Get current directory (path) func
INT 21h
JC Invalid_path ;IF function failed(will never happen)
; prepare to set to user's specified file path (directory)
MOV DX,BP ;Begining of dir in parm area
CMP DI,BP ;Is \ 1st + only compnnt of dir stng?
JNE Not_Root_Dir ;If \ is only char, this is root dir
MOV DX, offset Root_Dir ; so set directory to root directory
Not_Root_Dir:
MOV AH,3Bh ;Set current directory function
INT 21h
JC Invalid_path ;IF function failed
INC DI ;Point to start of filename1 (path+1)
MOV BP,DI ;Set new filename start (skip path)
;----------------------------------------------------------------------------;
; Display the start message and the heading for the file list ;
;----------------------------------------------------------------------------;
Display_Heading:
MOV DX,OFFSET Start_MSG ;Put out main banner msg for output
MOV AH,40h ;DOS DISPLAY STRING FUNCTION
MOV CX,SM_End-Start_MSG ;# of chars in start msg
MOV BX,1 ;Handle for std output device
INT 21h
MOV DX,OFFSET User_File_Spec ;Tell user what files we're checking
MOV AH,40h ;DOS write file funct (std output)
POP CX ;Get length of filespec1
ADD CX,3 ;add extra chars to length (CRLF LF)
INT 21h
;----------------------------------------------------------------------------;
; Find first occurance of a file to match the possible wildcards in filespec1;
;----------------------------------------------------------------------------;
Find_First_File:
MOV DX,BP ;DX points to filename of filespec1
MOV AH,4Eh ;DOS find first command (use 80H DTA)
MOV CX,File_attrib ;Set file attrib
INT 21h ;Invoke DOS
JNC Done_FFF ;If no carry, then all is OK..
No_Files_Matched: ;Come here when no files checked
Call Restore_Original_Path ;Set back to original path if changd
Call Restore_Original_Drive ;Set back to original drive if changd
; Report that no files were matched to the user
MOV DX, OFFSET No_CHK_Msg ;Tell users no files matched
MOV AH,09h ;DOS display string function
INT 21h
; Write 1 byte record indicating no files matched
MOV AH,40h ;DOS write file function
MOV BX,Filespec2_handle ;Report file, file handle
MOV CX,1 ;Write 1 byte zero record
MOV DX,OFFSET Zero_Byte ;single hex zero to write
INT 21h ;Write 1 byte of zero to report file
JNC ClOSE_Report_File ;If write was OK, close file + finish
JMP Report_Write_Error ;Notify user of fatal write error
Close_Report_File:
MOV AH,3Eh ;DOS Close function
INT 21h ;Close the report file
MOV AX,4C04h ; terminate with 04 error level
INT 21h
Done_FFF:
RET
;---------------------------------------------------;
; W A I T F O R K E Y ;
;---------------------------------------------------;
; 1) Send out a BEEP ;
; 2) Determine screen attribute (screen colors) ;
; 3) Determine what line cursor is on ;
; 4) Put out message to hit any key on that line ;
; 5) Wait for any keypress ;
; 6) Erase message using current screen attribute ;
; 7) Position currsor back at start of current line.;
; --------------------------------------------------;
; *** ALL REGISTERS MAY BE CORRUPTED EXCEPT BP *** ;
; --------------------------------------------------;
Wait_For_Key: ;Force user to notice error
PUSH BP ;Save the only needed register
; Produce a beep to alert the user: (use BIOS TTY func to write an ASCII BELL)
MOV AX,0E07h ;BIOS func (0Eh) to write (07H) beep
XOR BH,BH ;Select page zero for output
INT 10h ;BIOS video function (0Eh=write char)
;Find out what attribute is being used for display
MOV AH,08h ;read attrib + char function
INT 10h ;Call BIOS
PUSH AX ;Save AH=attribute byte
;Find out what line the cursor is on
MOV AH,03h ;Read cursor position function
INT 10h ;BIOS video services
PUSH DX ;DH contains row (line #) Save it!
; Position cursor to current line + column 28: (TO BIOS row 27)
MOV AH,02 ;BIOS int 10h set cursor position func
XOR BH,BH ;Set page to zero
;DH contains current row
MOV DL,1Bh ;Set cusor current row and col 27
INT 10h ;BIOS video services
; Put -Hit any key- message out with inverse video attribute type on
; XOR BH,BH ;Set page to zero (BH is still 0)
MOV BL,0F0h ;Inverse video attribute
MOV CX,1 ;Character count
MOV SI,offset Hit_Key_Msg ;The hit-any-key message
Display_next_video_char:
MOV AH,09h ;BIOS int 10h write attrib + char func
LODSB ;Get next character for output
PUSH SI ;Save SI (int 10h may corrupt it)
INT 10h ;Put character and attribute out
INC DX ;Advance cursor position
MOV AH,02 ;Adv cursor function
INT 10h ; advance the cursor (BIOS)
POP SI ;Restore saved SI
CMP SI,offset Hit_key_Msg_end ;are we at end of message?
JB Display_next_video_char ; If not get next char for display
; Else, wait for key press by user
; Wait for user to hit any key
XOR AX,AX
INT 16h ;Wait for user to hit a key
; Erase HIT ANY KEY message
POP DX ;DH=current line number
POP BX ;BH=user's screen attribute
MOV AH,06h ;INIT window function
XOR AL,AL ;Zero AL to clear window
MOV CH,DH ;Current row (y coor upr lft)
MOV CL,00 ;Start in first char position
MOV DL,79 ;Last char pos - blank entire line
INT 10h ;Blank out line
; Position cursor to start of blanked line
MOV AH,02 ;BIOS int 10h set cursor position func
XOR DL,DL ;DH=cur line, DL=0: first char pos
XOR BX,BX ;Use video page zero
INT 10h ;BIOS video services
POP BP
RET ;Return to caller
; --------------------------------------------------;
; Initialization DATA STORAGE ;
; --------------------------------------------------;
Root_dir DB '\' ;Zero terminated root dir string
Zero_Byte DB 0 ;This must immed. follow Root_Dir
File_Attrib DW 0007h ;File attribute (RO, hidden + sys)
File2_start DW 0007h ;File attribute (RO, hidden + sys)
New_Drive DB 0 ;Drive to change to in filespec1
Start_MSG DB CR,LF,"CHKFILEC 1.0 ",BOX," PCDATA TOOLKIT (c) 1990"
DB " Ziff Communications Co.",CR,LF
DB "PC Magazine ",BOX," Wolfgang Stiller - Checking: "
SM_End LABEL BYTE ;End of the Start message
Bad_Path_MSG DB 'Invalid path/drive on filespec1.',CR,LF,'$'
Bad_Parm_MSG DB 'Unrecognized parameter detected.',cr,lf,lf,'$'
Syntax_Msg DB "CHKFILEC 1.0 ",BOX," PCDATA TOOLKIT Copyright (c) 1990"
DB " Ziff Communications Co.",CR,LF
DB "PC Magazine ",BOX," Wolfgang Stiller",CR,LF,CR,LF
DB 'CHKFILEC will read all files which match the specified file '
DB 'name, reporting',CR,LF
DB 'two check values, plus DOS file size, date and time. This'
DB ' information',CR,LF
DB 'is written in compressed, self checking form to a separate'
DB ' report file which',CR,LF
DB 'can be used by CFcompC to validate file integrity.'
DB CR,LF,LF
DB 'Syntax is: CHKFILEC filespec1 filespec2 [/D] [/I:zz] '
DB '[/T] [/1] [/2]',CR,LF,LF
DB ' filespec1 is the file specification for the file(s) to'
DB ' check. Wild cards',CR,LF
DB ' such as * or ? can be used as well as a drive'
DB ' or directory.',CR,LF
DB ' filespec2 is compressed report file of file check data.'
DB CR,LF
DB ' "/D" Display directory entries as well as files.'
DB CR,LF
DB ' "/I:aa" Ignore all files which begin with the 2 '
DB 'chars: aa.',CR,LF
DB ' "/T" Ignored if coded. Totals are always generated.'
DB CR,LF
DB ' "/1" Utilize an alternate check value1 algorithm.'
DB CR,LF
DB ' "/2" Utilize an alternate check value2 algorithm.'
DB CR,LF,'$'
Bad_file2_msg DB '2nd file parameter (report file) is missing or bad.'
DB CR,LF,'$'
F2_Open_fail DB 'Open failed for filespec2 (report file)'
DB CR,LF,'$'
No_CHK_MSG DB 'No files were checked.'
DB CR,LF,'$'
Hit_Key_Msg DB '-Hit any key-'
Hit_Key_MSG_end EQU $
User_file_spec EQU $ ;User specified file spec to check
CSEG EndS
END CHKFILEC