home *** CD-ROM | disk | FTP | other *** search
- PAGE 60,132
- TITLE CHKFILE - High performance file checker
- SUBTTL General program description and use of common storage
- ; ----------------------------------------------------------------------------;
- ; CHKFILE - 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: ;
- ; CHKFILE will read files and then characterize them with unique ;
- ; check values, update date, update time and file size. This ;
- ; data can be used to validate file integrity by determining if ;
- ; the file has undergone any changes. The output can be ;
- ; redirected to a file which may be compared later using program ;
- ; CFcomp. ;
- ;-----------------------------------------------------------------------------;
- ;Syntax: ;
- ; ;
- ;CHKFILE [d:] [path] filename [/D] [/I:aa] [/T] [/1] [/2] ;
- ; ;
- ; filename specifies the files to be read and checked. Wild card chars ;
- ; such as * or ? can be used as well as a drive or directory. ;
- ; "/D" Display directory entries as well as regular files ;
- ; "/I:aa" Ignore files beginning with characters aa (must be 2 chars).;
- ; "/T" Generate cumulative total file check values for all files ;
- ; checked (both check value 1 and value 2). ;
- ; "/1" Utilizes an alternate algorithm for check value 1. ;
- ; "/2" Utilizes an alternate algorithm for check value 2. ;
- ; ;
- ; CHKFILE entered with no filename will produce a display of the correct ;
- ; syntax. ;
- ;-----------------------------------------------------------------------------;
- ;Remarks: ;
- ; CHKFILE 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. CHKFILE will read all files independent of whether they have ;
- ; the hidden or the system attribute set. CHKFILE produces a report ;
- ; line for each file (and optionally directory) matching the primary ;
- ; file specification. CHKFILE will report for each file in the current ;
- ; or specified directory the following information: 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 DOS standard ;
- ; output device and may be redirected to a file. The check values and ;
- ; the file size are displayed as hex digits, for compactness of output. ;
- ; ;
- ; If CHKFILE 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. This ;
- ; capability exists to make it more difficult for a destructive program ;
- ; to modify a file and then to find and patch the CHKFILE output file to ;
- ; mask this change. Since this protection is only minimal, it is best to ;
- ; store the file containing CHKFILE's output off-line on a floppy. ;
- ; ;
- ; It is recommended that the "/T" option be used anytime CHKFILE is ;
- ; checking more than a single file. "/T" will generate a totals line as ;
- ; the last line of output. This line will contain a cumulative check ;
- ; value 1 and check value 2. Specifying the /T option makes it easy to ;
- ; "eyeball" CHKFILE reports to see if any files have changed by comparing ;
- ; the totals lines on two reports. The totals line also helps CFcomp to ;
- ; give you more information. If you have renamed some files but made no ;
- ; other changes, CFcomp can recognize this. CHKFILE can be used several ;
- ; ways. One possibility is to use it directly to check files, and then ;
- ; manually record the check values and file size for later comparison. ;
- ; This may be useful when sending or transmitting files, to verify that ;
- ; the file was not damaged enroute. Another possibility is to redirect ;
- ; the output of CHKFILE. For example: ;
- ; "CHKFILE *.* /D /T /I:$$ >$$A", ;
- ; will check all files and subdirectory entries in the current directory, ;
- ; produce a totals line, ignore all file names beginning with $$ and ;
- ; write the output to a file called $$A. This command can be repeated at ;
- ; a later date. By using CFcomp to compare the two files containing ;
- ; redirected output, a report will be produced showing all changes to any ;
- ; of the files in that directory. ;
- ; ;
- ; If the entry being checked is a directory entry, CHKFILE will report: ;
- ; "Dir." in the check value fields. ;
- ; ;
- ; If CHKFILE was unable to open a file in order to read it, it will ;
- ; report "Open fail" in the check value fields. ;
- ; ;
- ; If CHKFILE failed to read a file, "Read fail" will appear in the check ;
- ; value fields for that file. If this happens it is normally due to ;
- ; insufficient file handles (increase the FILES=nnnn number in your ;
- ; CONFIG.SYS file) or due to failed access on a network. ;
- ; ;
- ; CHKFILE 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 was detected on a file. ;
- ; 64 - (40H) Program failure due to invalid path or drive specified. ;
- ; 128 - (80H) Syntax error or missing parameters on program initiation. ;
- ; ;
- ;-----------------------------------------------------------------------------;
- ; CHKFILE will report for each file in the current or specified directory ;
- ; the following information: ;
- ; Name of file, 16 bit check sum (0 to 64K), 16 bit XOR result, DOS time ;
- ; and date stamps of the file, and file size in hex bytes ;
- ; Format for report lines: ;
- ; 1 2 3 4 5 6 ;
- ;123456789012345678901234567890123456789012345678901234567890 ;
- ;File Name + Check Check File Update Update ;
- ;Extension: Val1: Val2: Size: Date: Time: ;
- ;------------ ---- ---- -------- -------- -------- ;
- ;filename.ext xxxx yyyy FileSize mm/dd/yy hh:mm:ss ;
- ; 1 1 1 1 1 1 ;
- ; 1 1 1 1 1 1__Time of last file update ;
- ; 1 1 1 1 1__________ Date of last update ;
- ; 1 1 1 1____________________ Size of file in bytes-hex ;
- ; 1 1 1___________________________ Check value 1 (SUM) -HEX ;
- ; 1 1________________________________ Check value 2 (XOR) -HEX ;
- ; 1_________________________________________ Name of the file ;
- ; ;
- ; ----------------------------------------------------------------------------;
- ; ;
- ; Total record length for output file (DSP_REC) is 51 bytes. ;
- ; ;
- ; ** See DSP_REC definition for detail on field descriptions ** ;
- ; ;
- ; 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. ;
- ; ----------------------------------------------------------------------------;
- ;Sample output: ;
- ; ;
- ;CHKFILE 1.0 ■ PCDATA TOOLKIT (c) 1990 Ziff Communications Co. ;
- ;PC Magazine ■ Wolfgang Stiller checking: *.* ;
- ; ;
- ;File Name + Check Check File Update Update ;
- ;Extension: Val1: Val2: Size: Date: Time: ;
- ;---------- ---- ---- ----- ------ ------ ;
- ;IBMBIO.COM 03E6 A98D 5654 03/18/87 12:00:00 ;
- ;IBMDOS.COM FC1B 941D 75CF 03/17/87 12:00:00 ;
- ;ERRORFIL.TST Read fail 75512 04/01/89 10:11:10 ;
- ;DOS Dir. 12/01/87 23:33:48 ;
- ;Total======> 1DFF F677 ;
- ; ;
- ;Notes: CHKFILE always displays the filespec it is checking. In this ;
- ; case it is checking "*.*" all files. The final line of output: ;
- ; "Total======>" indicates that the /T parameter was specified. ;
- ; The presence of directory DOS indicates the /D parameter was ;
- ; specified. IBMBIO.COM and IBMDOS.COM are two hidden system ;
- ; files. These illustrate normal output from CHKFILE. CHKFILE was ;
- ; unable to read ERRORFIL.TST. It was however able to display the ;
- ; information from the directory concerning this file. ;
- ; ----------------------------------------------------------------------------;
-
- ;---------------------------------------------------------------;
- ; Constants: ;
- ;---------------------------------------------------------------;
- BOX EQU 254 ;Small box character code
- CR EQU 0Dh
- LF EQU 0Ah
- CRLF EQU 0A0Dh ;Carriage return line feed.
- REP_Rec_Len EQU 51 ;Length of display record
-
- 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 -CHKFILE- **;
- ;******************************************************************************;
- ORG 100h ; THIS IS A COM TYPE PROGRAM
- CHKFILE:
- CALL Parse_parms_Displ_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 check value1 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;
- ; beginning 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 one file found
- MOV CX,12 ;Scan 12 characters of filename
- ; SI= offset DTA_F_Name ;SI already contains loc of DTA_F_NAME
- MOV DI, offset REP_F_Name ;Move to report 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 Blank_fill ;If end, then blank fill rest of name
- STOSB ;Else store char in REPRec file name
- LOOP Xfer_file_name ;continue until done
- JMP Short Format_f_size ;Go and format file size for REPort
-
- Blank_fill: ;blank fill remainder of file name
- MOV AL,' '
- REP STOSB ;Store remaining characters
-
- ; --------------------------------------------------;
- ; Extract file size from DTA for display ;
- ; --------------------------------------------------;
- Format_F_size: ;Format DTA's file size for output
- MOV DI,offset REP_F_Size ;Display formatted file size
- MOV SI,offset DTA_FS_HIr+1 ;End of DTA file size area
- MOV CX,4 ;process 4 bytes (2 words) file size
- XOR DX,DX ;DX=0 means only leading zeros so far
-
- Get_byte_to_Hex_Convert: ;Conv each byte to 2 HEX ASCII digits
- MOV AH,BYTE PTR [SI] ;Pick up char from end of DTA F size
- CALL Convert_Hex_ASCII ;Convert 4 bit hex to ASCII displcode
- DEC SI ;Get prior byte in DTA file size
- LOOP Get_Byte_to_Hex_Convert ;Do all four bytes
-
- ; --------------------------------------------------;
- ; Extract file date from DTA for display ;
- ; --------------------------------------------------;
- MOV AX,[DTA_F_date] ;Date of last file update
- ; date is in yyyyyyym mmmddddd format (year is offset from 1980)
- MOV DX,AX ;Save a copy of file date
- MOV BL,10 ;Put 10 in BL for decimal conversion
- ;MONTH
- MOV CL,5 ;Prepare to shift right 5 bits
- ROR AX,CL ;Move month to right of word
- AND AX,0Fh ;only month remains
- MOV DI,offset REP_F_MM ;Point to month field in REP_rec
- Call Convert_Dec_ASCII ;Convert 2 decimal digits to ASCII
-
- ;DAY
- MOV AX,DX ;Restore copy of DTA date
- AND AX,1fh ;Extract day portion of date
- MOV DI,OFFSET REP_F_DD ;Point to day field in REP rec
- Call Convert_Dec_ASCII ;Convert 2 decimal digits to ASCII
-
- ;YEAR
- MOV AX,DX ;Restore copy of DTA date
- MOV CL,7
- ROL AX,CL ;Bring year of date to right of AX
- AND AX,7Fh ;MASK off right 7 bits of YEAR
- ADD AX,80 ;Year is years after 1980
- CMP AX,100 ;Are we in the next century?
- JB Transfer_year ;IF not go ahead and display YY
- SUB AX,100 ;Otherwise adjust the year
- Transfer_year:
- MOV DI,OFFSET REP_F_YY ;Point to year field in REP_REC
- Call Convert_Dec_ASCII ;Convert 2 decimal digits to ASCII
-
-
- ; --------------------------------------------------;
- ; 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)
-
- ;HOURS
- MOV DX,AX ;Create a copy of the time
- MOV CL,5 ;Shift for hour bits
- ROL AX,CL ;hours are on the right of AX
- AND AX,1Fh ;Only hours remain in AX
- MOV DI,OFFSET REP_F_HH ;Point so we can mov to hour field
- Call Convert_Dec_ASCII ;Convert 2 decimal digits to ASCII
-
- ;Minutes
- MOV AX,DX ;Restore copy of the time
- MOV CL,5
- ROR AX,CL ;Minutes are rightmost in AX
- AND AX,3Fh ;Mask off minutes
- MOV DI,OFFSET REP_F_MI ;Point to minutes in output field
- Call Convert_Dec_ASCII ;Convert 2 decimal digits to ASCII
-
- ;Seconds
- MOV AX,DX ;Restore copy of the time
- AND AX,1Fh ;Only seconds remain after MASKing
- ROL AX,1 ;Multiply secs by 2
- MOV DI,OFFSET REP_F_SS ;Point so we can mov to hour field
- Call Convert_Dec_ASCII ;Convert 2 decimal digits to ASCII
-
-
- ; 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 DI,offset REP_CHK_Sum ;prep to place msg in chk sum field
- MOV AX,'iD' ;Store "Dir." in report record
- STOSW ; to indicate this is a directory
- MOV AX,'.r' ; entry rather than a normal file.
- STOSW
- MOV CX,5 ;Now blank fill the remainder of
- MOV AL,' ' ; the REPort record chk val 2
- REP STOSB
- JMP Write_REP_Rec ;Skip rest of processing and go print
- ; this dir entry + find next file
-
- ; Do special handling for files which would not open or got an I/O error:
- ; SI points to 9 char message containing type of error which occured
- Error_on_File: ;Place error msg in chkval1+2 fields
- MOV DI,offset REP_CHK_Sum ;prep to place msg in chk val 1 field
- MOV CX,9 ;Transfer 9 characters
- REP MOVSB ;Copy error msg into report record
- MOV File_Err_Flag,'Y' ;Indicate we encountered a file error
- JMP Write_REP_Rec ;Skip rest of processing and go print
-
- ; --------------;
- ; Open the file ;
- ; --------------;
- Open_the_File:
- 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
- ; This open should never fail...(OS2 can have files open which will cause fail)
- MOV SI,OFFSET Open_Err_Msg ;Error message to place in REP_rec
- JMP SHORT Error_on_File ;Finish processing this file with
- ; a report that open failed
- Continue_Open:
- MOV BX,AX ;Save file handle
- XOR BP,BP ;zero out (clear) EOF indicator
- ; zero indicates more info to read.
-
- ; -------------------------------------------;
- ; Initialize check values 1 + 2 for each file;
- ; -------------------------------------------;
- Init_CHK_XOR_Sums:
- MOV DI,BP ;Zero check sum init for each file
- MOV DX,BP ;Zero check value 2 (XOR value)
-
-
- ; ----------------------------------------------------------------;
- ; 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 check value 2 (XOR sum)
- 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 chk val 2 (XOR)
- JNC Read_was_OK ;Did an error occur on read?
- MOV AH,3Eh ; NO, so issue DOS close file func
- INT 21h ; Let DOS close file
- MOV SI,OFFSET Read_Err_Msg ; Point to error message to write
- JMP SHORT Error_on_File ; write err msg on 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 chk val 2 (XOR) into DX
- ;following instr modified by /2 parm
- ROL_op: ROL DX,1 ;Keep shifting to XOR sum to left
- ;following instr modified by /1 parm
- ADD_op: ADD DI,AX ;cumulative check sum (check value 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
-
- Call Convert_Sums_for_Display ;Convert check values for display
-
- ADD Tot_CHK_Sum,BX ;Total the check val1s for all files
- ADD Tot_XOR_Sum,CX ;Total the chk val2s for all files
-
- ;---------------;
- ; PRINT REP_REC ;
- ;---------------;
- Write_REP_Rec:
- MOV DX, offset REP_rec ;prepare to print REPort record
- MOV CX,REP_Rec_Len ;51 chars in REP_rec
- MOV BX,1 ;Handle for std REPort device
- MOV AH,40h ;DOS display string function
- INT 21h
-
- ;-------------------------------;
- ; 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, open new file
-
- Finish_Processing: ;Else, Prepare to terminate
- CMP Files_Found,'Y' ;Did we check at least one file?
- JE Totals_Processing ; If so, go do totals processing
- JMP No_Files_Found ; Else terminate with 04 Err lvl
-
- Totals_Processing:
- CMP Totals_Wanted,'Y' ;Check if user requested totals line
- JNE Check_drive_path_changes ;If not then just quit
-
- ; Move cumulative file totals into REP_REC for display
- MOV DI,Tot_CHK_Sum ;Prepare cumulative totals for dsply
- MOV DX,Tot_XOR_Sum
- Call Convert_Sums_for_Display ;Place cum totals in REPort record
- MOV DI, offset REP_F_Name ;prepare to place "File totals:"
- MOV SI, offset Totals_MSG ; message in place of file name.
- MOV CX,12 ;12 characters of name to copy
- REP MOVSB ;Copy the literal into filename field
- MOV word ptr [REP_F_Size-1],CRLF ;Car retrn LF to terminate record
- ; Write the cumulative file totals line
- MOV DX, offset REP_rec
- MOV AH,40h
- MOV BX,1 ;File handle of std output
- MOV CX,24 ;print 24 chars of REPrec only
- INT 21h ;Actually write out the totals line
-
- 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 AL,00h ;Plan on termination with 0 errlvl
- CMP File_Err_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 **;
- ;******************************************************************************;
-
- Convert_Sums_for_Display:
- ;------------------------------------------------------------------------------;
- ; Convert Check values (1 + 2) to ASCII hex characters and store in REP_REC ;
- ;------------------------------------------------------------------------------;
- ;Input: DI contains check value 1 (16 bit checksum type field) ;
- ; DX contains 16 bit check value 2 (hash type XOR field) ;
- ;Output: REP_Rec will contain display versions of both check values. ;
- ; AX,BX,CX,DX and DI will be corrupted. BX,CX will contain CHK val 1 + 2;
- ;------------------------------------------------------------------------------;
- MOV BX,DI ;save checksum (check value 1) in BX
- MOV CX,DX ;save XOR (chk value 2) in CX
- MOV DL,1 ;DX<>0 turns leading 0 suppression off
- MOV DI,OFFSET REP_CHK_Sum ;Field for hex ASCII characters
- MOV AH,BH ;Upper byte of chk val 1 (checksum)
- CALL Convert_Hex_ASCII ;Convert to 2 hex ASCII characters
- MOV AH,BL ;Lower byte of checksum
- CALL Convert_Hex_ASCII ;Convert to 2 hex ASCII characters
- INC DI ;Skip over space + into chkval2 (XOR)
- MOV AH,CH ;Upper byte of chkval2 (XOR)
- CALL Convert_Hex_ASCII ;Convert to 2 hex ASCII characters
- MOV AH,CL ;lower byte of chkval2 (XOR)
- CALL Convert_Hex_ASCII ;Convert to 2 hex ASCII characters
- RET
-
-
- ;------------------------------------------------------------------------------;
- ; CONVERT HEX ASCII - Convert hex byte (8 bits) to 2 ascii display bytes ;
- ;------------------------------------------------------------------------------;
- Convert_Hex_ASCII:
- CALL Convert_Hex_Nyble_ASCII ;Convert nyble (4 bits) to hex ASCII
- CALL Convert_Hex_Nyble_ASCII ;Convert nyble (4 bits) to hex ASCII
- RET ;RETURN to caller
-
- ;------------------------------------------------------------------------------;
- ; CONVERT HEX NYBLE ASCII - Convert hex digit (4 bits) to 1 ascii display byte ;
- ;------------------------------------------------------------------------------;
- ;Input: AH upper 4 bits contain hex to be converted. DI points to report record;
- ; DX should be set to zero for leading zero suppression. ;
- ;Output: 1 byte in report record will contain ASCII display code of HEX byte. ;
- ; AH be shifted 4 bits to left. AL will contain ASCII version of HEX. ;
- ; DI will be incremented twice. DX will be = SP if nonzero output ;
- ;------------------------------------------------------------------------------;
- Convert_Hex_Nyble_ASCII:
- XOR AL,AL ;Zero out AL
- ROL AX,1 ;Move half byte (hex digit) into AL
- ROL AX,1
- ROL AX,1
- ROL AX,1 ;AL now contains a hex digit
- OR AL,AL ;Is this a zero?
- JE Leading_Zero_check ;If so check if this is leading zero
- MOV DX,SP ;Set non 0 to indicate non 0 found
- Continue_hex_check:
- CMP AL,9 ;Is digit 0 to 9 or A to F ?
- JA Hex_alpha_digit ;If hex A to F, do special conversion
- ADD AL,'0' ;Convert hex digit to ascii display
- STOSB ;store in display field (REP_F_size)
- RET
- Hex_alpha_digit: ;Convert hex A to F to ASCII display
- ADD AL,'A'-10
- STOSB ;store in display field (REP_F_size)
- RET
- Leading_Zero_Check: ;Check and blank out leading zeros
- OR DX,DX ;Have non zeros been detected yet?
- JNZ Continue_hex_check ;If so then do normal processing
- MOV AL,' ' ;Else put out a leading blank
- STOSB
- RET
-
-
- ;------------------------------------------------------------------------------;
- ; CONVERT DEC ASCII - Convert 2 decimal digits to 2 ascii display bytes ;
- ;------------------------------------------------------------------------------;
- ;Input: BL contains 10. AX contains decimal number 0 to 99 to be converted. ;
- ; DI points to destination to store result ;
- ; Both digits will be stored at location pointed to by DI. ;
- ;------------------------------------------------------------------------------;
- Convert_DEC_ASCII:
- DIV BL ;Divide by 10
- ADD AX,'00' ;Convert to ASCII digits
- STOSW
- RET
-
-
- ;------------------------------------------------------------------------------;
- ; 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
-
- SUBTTL Definition of Data structures
- PAGE
- ;******************************************************************************;
- ;** Definition of Data areas follow **;
- ;******************************************************************************;
- File_Err_Flag DB 'N' ;='Y' if a file had open or read error
- Open_Err_Msg DB 'Open fail'
- Read_Err_Msg DB 'Read fail'
- REP_Rec EQU $ ;Name for the entire REPort record
- REP_F_Name DB 12 DUP (' ') ;12 spaces reserved for filename
- DB ' '
- REP_CHK_Sum DB 4 DUP ('0') ;Check value 1 (chksum): 4 hex digits
- DB ' '
- REP_XOR_Sum DB 4 DUP ('0') ;Check value 2 (XOR) - 4 hex digits
- DB ' '
- REP_F_Size DB 8 DUP ('0') ;Size of file: 8 Hex digits
- DB ' '
- REP_F_MM DB 'MM' ;Date of last file update:
- DB '/'
- REP_F_DD DB 'DD'
- DB '/'
- REP_F_YY DB 'YY'
- DB ' '
- REP_F_HH DB 'HH' ;Time of last file update
- DB ':'
- REP_F_MI DB 'MI' ;MInutes
- DB ':'
- REP_F_SS DB 'SS'
- DB CR,LF ;End of REP_Rec (REPort record) descr
-
- 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
- Totals_wanted DB 0 ;"Y" if totals desired on report
- Tot_CHK_Sum DW 0 ;total of all chk val 1s (all files)
- Tot_XOR_Sum DW 0 ;total of all check value 2s
- Totals_MSG DB 'Total======>'
- Ignore_F_Name DW ' ' ;ignore file names starting with this
- Files_Found DB 'N' ;Indicates if any files check at all
- 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.
- ; Actual max is 3C0 to leave room
- ; for the stack.
-
- ; ----------------------------------------------------------------------------;
- ; Initialization code - parse parms + put out msgs and find intial file match ;
- ; ----------------------------------------------------------------------------;
- Parse_parms_Displ_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 ;Cont checking until last character
- 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 ;Put error level in AL from 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 filespec for find next processing ;
- ;---------------------------------------------------------------------------;
-
- ;----------------------------------------;
- ; Parse file spec 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 DL,AL ;Save a copy of numeric drive spec
- 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
- MOV AH,0Eh ;DOS select disk function
- INT 21h ;Set to user specified drive
- JNC Good_Disk_Specified ;Was the disk drive specified OK?
- JMP Invalid_Path ; If drive specified is invalid..
- Good_Disk_Specified: ; Drive is valid
- 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 for valid separator
- 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
- Check_parm_chars_left: ;Check if enough chars left for a parm
- CMP CX,01 ;Check if we're out of chars to scan
- JA Parm_Scan ; if not continue chcking for /parms
- JMP Check_for_DIR ; If so, skip ahead to directory proc
- 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 Check_for_DIR ;see if directory incl in filespec
-
- 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 XOR "/2" parm?
- JE X2_parm ;XOR:chk val2 parm detected
- CMP AL,'1' ;Is it alternate Check Sum "/1" parm?
- JE C1_parm ;/1 alternate chk val 1 parm 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:
- MOV Totals_Wanted,'Y' ;Indicate users wants total line
- LODSB ;Keep checking next character
- JMP SHORT Check_Parm_chars_left ;Check for additional parms
-
- X2_parm: ;/2 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: ;/1 parm (alternate chksum)
- 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 ;Display error msg + correct syntax
-
- Check_for_DIR: ;See if PATH included in filespec
- MOV CX,BX ;End of filespec + 1
- SUB CX,BP ;Calc length of filespec
- PUSH CX ;Save length of filespec for use later
- STD ;Prepare to scan filespec backwards
- MOV DI,BX ;Start from end
- DEC DI ; of filespec
- MOV AL,'\' ;Scan filespec for presence of "\"
- REPNE SCASB ;Scan to last \ from end of filespec
- CLD ;Reset direction flag to forward
- JNZ Display_Heading ;IF, no path found in filespec
- 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 ;beginning of dir in parm area
- CMP DI,BP ;Is \ 1 and only compon of dir string?
- 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 filename (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 ;47 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 filespec
- ADD CX,3 ;add extra chars to length (CRLF LF)
- INT 21h
- MOV DX,OFFSET Header_MSG ;Put out header message for output
- MOV AH,40h ;DOS DISPLAY STRING FUNCTION
- MOV CX,149 ;total of 149 chars in header
- INT 21h
-
- ;----------------------------------------------------------------------------;
- ; Find first occurance of a file to match the possible wildcards in filespec ;
- ;----------------------------------------------------------------------------;
- Find_First_File:
- MOV DX,BP ;DX points to filename
- 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_Found: ;Come here if no files matched
- Call Restore_Original_Path ;Set back to original path if changd
- Call Restore_Original_Drive ;Set back to original drive if changd
- 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 cursor back at start of current line. ;
- ; --------------------------------------------------;
- ; *** ALL REGISTERS MAY BE CORRUPTED EXCEPT AX *** ;
- ; --------------------------------------------------;
- Wait_For_Key: ;Force user to notice error
- PUSH AX ;Save 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 cursor 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 AX ;Restore only need register
- RET ;Return to caller
-
-
- ; --------------------------------------------------;
- ; Initialization DATA STORAGE ;
- ; --------------------------------------------------;
- Root_dir DB '\',0 ;Zero terminated root dir string
- File_Attrib DW 0007h ;File attribute (RO, hidden + sys)
- Start_MSG DB CR,LF,"CHKFILE 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
- Header_MSG DB 'File Name + Check Check File Update Update'
- DB CR,LF
- DB 'Extension: Val1: Val2: Size: Date: Time:'
- DB CR,LF
- DB '---------- ---- ---- ----- ------ ------'
- DB CR,LF
- Bad_Path_MSG DB 'Invalid path/drive.',CR,LF,'$'
- Bad_Parm_MSG DB 'Unrecognized parameter detected.',cr,lf,lf,'$'
- Syntax_Msg DB "CHKFILE 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 'CHKFILE 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 'can be used by CFcomp to validate file integrity.'
- DB CR,LF,LF
- DB 'Syntax is: CHKFILE [d:] [path] filename [/D] [/I:zz] '
- DB '[/T] [/1] [/2]',CR,LF,LF
- DB ' "filename" specifies the files to check. Wild card'
- DB ' characters such',CR,LF
- DB ' as * or ? may be used.',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" Totals line will be written.'
- 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,'$'
-
- 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 CHKFILE