home *** CD-ROM | disk | FTP | other *** search
- Page 60,132
- ;----------------------------------------------------------------------
- ; RECORDER.ASM - A resident program which counts file operations.
- ; Run it once to install and initialize it. Run it again later to
- ; view a list of files which have been accessed. The table
- ; shows how many disk accesses have been made while reading and
- ; writing to the file.
- ;
- ; SYNTAX: RECORDER [n] [/R]
- ; USE n to specify the maximum number of files (default=200)
- ; Use /R to reset the file table.
- ;----------------------------------------------------------------------
- CSEG SEGMENT
- ASSUME CS:CSEG,DS:NOTHING
- ORG 100H ;Beginning for .COM programs
- START: JMP INITIALIZE ;Initialization code is at end
-
- ;-----------------------------------------------------------------------
- ; Data area used by this program
- ;-----------------------------------------------------------------------
- COPYRIGHT DB "RECORDER 1.0 (c) 1988 Ziff Communications Co."
- PROGRAMMER DB 13,10,"PC Magazine ",254," Tom Kihlken$",1AH
-
- FULL_MESS DB "*Table is saturated*$"
- OLDINT21 DD ? ;Old DOS function interrupt vector
- OLDINT13 DD ? ;Old BIOS disk I/O interrupt vector
- NUM_FILES DW 200 ;Default size of the table
- FILE_TABLE_END DW ?
- LAST_FILE DW ?
- LAST_HANDLE DW ?
-
- ;--to help count spaces-012345678901234567890123456789012345678901-----
- HEADER DB " File Name Total Read Write EXEC$"
-
- CURRENT_FILE DB 11 DUP (?)
- CURRENT_HANDLE DW ?
- FUNCTION_ID DW ?
- BUSY_FLAG DB 0
- BIOS_IO_COUNT DW 0 ;Counts disk accesses made by BIOS
-
- HANDLE_TABLE EQU OFFSET INITIALIZE
- FILE_TABLE EQU HANDLE_TABLE + NUM_HANDLES * 4
- NUM_HANDLES EQU 30
- ENTRY_SIZE EQU 20
-
- ;-----------------------------------------------------------------------
- ; Interrupt 13 (Diskette I/O) This routine counts disk sector accesses.
- ;-----------------------------------------------------------------------
- NEWINT13 PROC FAR
- ASSUME DS:NOTHING, ES:NOTHING
- CMP AH,2 ;Is function lower than 2?
- JB DONT_COUNT ;If yes, then ignore it
- CMP AH,4 ;Is function higher than 4?
- JA DONT_COUNT ;If yes, then ignore it
- INC CS:BIOS_IO_COUNT;Add sectors count to total
- DONT_COUNT:
- JMP CS:OLDINT13 ;Continue with disk interrupt
- NEWINT13 ENDP
-
- ;-----------------------------------------------------------------------
- ; Interrupt 21 (DOS functions) This routine counts file accesses.
- ;-----------------------------------------------------------------------
- NEWINT21 PROC FAR
- ASSUME DS:NOTHING, ES:NOTHING
-
- PUSHF ;Save callers flags
- STI ;Get interrupts back on
- CMP CS:BUSY_FLAG,0 ;Are we busy now?
- JNE OLD_DOS ;If busy, just pass it to DOS
- CMP AH,4BH ;Is it the EXEC function?
- JE EXEC ;Handle EXEC specially
- CMP AH,0EH ;Is it below 0EH?
- JBE OLD_DOS ;If yes, ignore it
- CMP AH,31H ;Is it TSR function?
- JE OLD_DOS ;Dont intercept this call
- CMP AH,45H ;Is it above 45H?
- JB INTERCEPT_IT ;If yes, then ignore it
- OLD_DOS:
- POPF ;Recover callers flags
- CLI
- JMP CS:OLDINT21 ;Allow interrupt to proceed
- EXEC:
- PUSH AX ;Save these registers
- PUSH BX
- PUSH CX
- PUSH SI
- PUSH DI
- PUSH DS
- PUSH ES
- MOV CS:BUSY_FLAG,1 ;Set the busy flag
- MOV SI,OFFSET PARSE_STRING ;Point to parse routine
- CALL ENTER_FILENAME ;Search file table for the file
- JC EXEC_CONTINUE
- INC WORD PTR DS:[SI+12]
- INC WORD PTR DS:[SI+18]
- EXEC_CONTINUE:
- MOV CS:BUSY_FLAG,0 ;Not busy any more
- POP ES ;Restore the registers
- POP DS
- POP DI
- POP SI
- POP CX
- POP BX
- POP AX
- JMP OLD_DOS
- INTERCEPT_IT:
- MOV BUSY_FLAG,1 ;Ignore any other calls
- MOV FUNCTION_ID,AX ;Save the function ident.,
- MOV BIOS_IO_COUNT,0
- CLI
- CALL CS:OLDINT21 ;Do the DOS function
- STI ;Reenable interrupts
- PUSHF ;Save DOS result flags
- PUSH AX ;Save these registers
- PUSH BX
- PUSH CX
- PUSH DX
- PUSH SI
- PUSH DI
- PUSH DS
- PUSH ES
- JNC CHECK_FUNCTION ;If no error, continue
- JMP POP_RET ;Otherwise just return
- CHECK_FUNCTION:
- MOV CX,FUNCTION_ID
- SUB CH,0FH ;Is it 0Fh?
- JZ READ_FCB
- DEC CH ;Is it 10h?
- JZ WRITE_FCB
- SUB CH,4 ;Is it 14h?
- JZ READ_FCB
- DEC CH ;Is it 15h?
- JZ WRITE_FCB
- DEC CH ;Is it 16h?
- JZ READ_FCB
- SUB CH,0BH ;Is it 21h?
- JZ READ_FCB
- DEC CH ;Is it 22h?
- JZ WRITE_FCB
- DEC CH ;Is it 23h?
- JZ READ_FCB
- SUB CH,4 ;Is it 27h?
- JZ READ_FCB
- DEC CH ;Is it 28h?
- JZ WRITE_FCB
- JMP SHORT NOT_FCB_FUNCTN
- READ_FCB:
- MOV BX,14 ;Index for the read column
- JMP SHORT INC_FCB_COUNT
- WRITE_FCB:
- MOV BX,16 ;Index for the write column
- INC_FCB_COUNT:
- MOV SI,OFFSET PARSE_FCB
- CALL ENTER_FILENAME ;Search file table for the file
- JC JUMP_POP_RET ;Quit if file not in table
- MOV AX,BIOS_IO_COUNT;This many disk operations made
- ADD CS:[SI][BX],AX ;Add it to the indexed column
- ADD CS:[SI+12],AX ;Add it to the total
- JMP POP_RET
-
- ; If it was not a FCB function, see if it was handle I/O
-
- NOT_FCB_FUNCTN:
- SUB CH,14H ;Is it 3Ch?
- JE NEW_HANDLE
- DEC CH ;Is it 3Dh?
- JE NEW_HANDLE
- DEC CH ;Is it 3Eh?
- JE WRITE_HANDLE
- DEC CH ;Is it 3Fh?
- JE READ_HANDLE
- DEC CH ;Is it 40h?
- JE WRITE_HANDLE
- SUB CH,2 ;Is it 42h?
- JE READ_HANDLE
- SUB CH,2 ;Is it 44h?
- JE IO_CONTROL
- JMP POP_RET
- NEW_HANDLE:
- CMP AX,5 ;Is it a standard handle?
- JGE GOOD_HANDLE ;If not, then record it
- JUMP_POP_RET:
- JMP POP_RET ;Jump to the return
- READ_HANDLE:
- MOV CX,14 ;Index for the read column
- JMP SHORT INC_DEV_COUNT
- IO_CONTROL:
- CMP CL,2 ;Is it a read request?
- JE READ_HANDLE ;Treat it as a read
- CMP CL,3 ;Is it a write request?
- JNE JUMP_POP_RET ;If not read or write, ignore it
- WRITE_HANDLE:
- MOV CX,16 ;Index for the write column
- INC_DEV_COUNT:
- CMP BX,5 ;Is it a standard handle?
- JB JUMP_POP_RET ;If it is, then ignore it
- PUSH CX ;Put index on the stack
-
- ; Now search the handle table for the handle in BX.
-
- CALL ADD_PSP ;Add in the current PSP segment
- MOV DI,HANDLE_TABLE ;Point to the handle table
- MOV CX,NUM_HANDLES ;Search the entire table
- HANDLE_LOOP:
- CMP BX,CS:[DI] ;Is it a match?
- JE HANDLE_MATCH ;If it is, we've found it
- ADD DI,4 ;If not, look at next entry
- LOOP HANDLE_LOOP
- POP BX ;Restore the stack
- JMP SHORT POP_RET ;Return if handle was not found
-
- ; If the handle is being closed, then the entry is deleted.
-
- HANDLE_MATCH:
- CMP BYTE PTR FUNCTION_ID+1,3EH ;Closing this file?
- JNE NOT_CLOSE
- MOV WORD PTR CS:[DI],0
- NOT_CLOSE:
- MOV DI,CS:[DI+2] ;Get pointer to file table entry
- POP BX ;Get the index back
- MOV AX,BIOS_IO_COUNT ;Get the sector count
- ADD CS:[DI][BX],AX ;Add it to selected column
- ADD CS:[DI+12],AX ;And also to the total column
- JMP SHORT POP_RET
- GOOD_HANDLE:
- MOV CURRENT_HANDLE,AX ;Save the handle
- MOV SI,OFFSET PARSE_STRING ;Point to parse routine
- CALL ENTER_FILENAME ;Add the file to the table
- JC JUMP_POP_RET ;If table is full, return
- MOV AX,BIOS_IO_COUNT;Get number of sectors
- ADD DS:[SI+12],AX ;Add to the total column
- ADD DS:[SI+14],AX ;Add to the read column
-
- ; Now enter this new handle to the handle table
-
- MOV DI,LAST_HANDLE ;Get location of last entry
- ADD DI,4 ;Advance it one position
- CMP DI,HANDLE_TABLE+NUM_HANDLES*4
- JNE KEEP_GOING
- MOV DI,HANDLE_TABLE
- KEEP_GOING:
- MOV LAST_HANDLE,DI ;Now this is the last handle
- MOV BX,CURRENT_HANDLE ;Get handle back
- CALL ADD_PSP ;Add in the current PSP segment
- MOV CS:[DI],BX ;Store the handle
- MOV CS:[DI+2],SI ;Store location in file table
- POP_RET:
- MOV CS:BUSY_FLAG,0 ;Not busy any more
- POP ES ;Restore all registers
- POP DS
- POP DI
- POP SI
- POP DX
- POP CX
- POP BX
- POP AX
- POPF ;Recover DOS result flags
- STI ;Return with interrupts on
- RET 2 ;Return with these flags
- NEWINT21 ENDP
-
- ;-----------------------------------------------------------------------
- ; ENTER_FILENAME adds the file at DS:DX to the table.
- ; It returns with DS:SI pointing to the entry. If CF=1, then the name
- ; was not in the table and no more entries could be added.
- ;-----------------------------------------------------------------------
- ASSUME DS:NOTHING, ES:CSEG
- ENTER_FILENAME PROC NEAR
- CLD ;String moves forward
- PUSH CS ;Set up the ES register
- POP ES
-
- MOV DI,OFFSET CURRENT_FILE
- MOV AL," " ;Fill with blanks
- MOV CX,11 ;11 letters in name
- REP STOSB
-
- CALL SI ;Call the parse routine
-
- ; Now search the file table for the current filename
- CLD
- PUSH CS
- POP DS ;Set DS to this segment
- ASSUME DS:CSEG
- MOV CX,NUM_FILES ;Try all entries
- MOV SI,FILE_TABLE ;Setup for a string compare
- SEARCH_LOOP:
- MOV DI,OFFSET CURRENT_FILE
- PUSH CX ;Save the loop counter
- PUSH SI ;Save the source also
- MOV CX,11 ;Compare 11 characters
- REPE CMPSB ;Do they all match?
- POP SI
- POP AX ;Recover loop counter
- JCXZ CLEAR_RETURN ;If matched, return CF=0
- ADD SI,ENTRY_SIZE ;Point to next name in table
- MOV CX,AX ;Get loop counter back to CX
- LOOP SEARCH_LOOP
- MOV DI,LAST_FILE ;Get location of last entry
- CMP DI,-1 ;Is table saturated?
- JE TABLE_FULL ;If yes, then return
-
- MOV CX,NUM_FILES ;Loop through file table
- FIND_OLDEST:
- ADD DI,ENTRY_SIZE ;Point to next entry in table
- CMP DI,FILE_TABLE_END
- JB NO_WRAP
- MOV DI,FILE_TABLE
- NO_WRAP:
- MOV AX,[DI+12] ;Get total for this record
- CMP AX,1 ;Is it less than one?
- JBE FOUND_OLDEST ;If it is, then we'll use it
- LOOP FIND_OLDEST ;Search entire table for a space
- MOV LAST_FILE,-1 ;If none found, table is full
- TABLE_FULL:
- STC ;Carry flag indicates table full
- RET
-
- ; At this point ES:DI points to newest table entry
-
- FOUND_OLDEST:
- MOV LAST_FILE,DI
- PUSH DI
- CLD ;String moves forward
- MOV SI,OFFSET CURRENT_FILE
- MOV CX,11 ;Copy the filename to table
- REP MOVSB ;Move the string in
- XOR AX,AX
- INC DI ;Point to the totals column
- STOSW ;Set total column to zero
- STOSW ;Set open column to zero
- STOSW ;Set read column to zero
- STOSW ;Set write column to zero
- STOSW
- POP SI
- CLEAR_RETURN:
- CLC ;Indicates sucessful return
- RET
- ENTER_FILENAME ENDP
-
- ;-----------------------------------------------------------------------
- ; This subroutine parses a filename from the FCB at DS:DX
- ;-----------------------------------------------------------------------
- ASSUME DS:NOTHING, ES:CSEG
- PARSE_FCB PROC NEAR
- INC DX ;Point to filename in FCB
- MOV SI,DX ;Get address in index register
- ADD SI,8 ;Point to file extension
- MOV DI,OFFSET CURRENT_FILE+8 ;DI Points to extension
- MOV CX,3
- COPY_EXT_1:
- LODSB ;Get a letter of the extension
- CALL UPPER_CASE ;Make it upper case
- STOSB ;Store it in current file
- LOOP COPY_EXT_1
- SUB SI,3
- JMP SHORT COPY_NAME ;Finish copying the name
- RET
- PARSE_FCB ENDP
-
- ;-----------------------------------------------------------------------
- ;This routine parses an ASCII filename from DS:DX and places it at
- ; CURRENT_FILE
- ;-----------------------------------------------------------------------
- PARSE_STRING PROC NEAR
- ASSUME DS:NOTHING, ES:CSEG
- MOV SI,DX ;Get address in index register
- LOOK_FOR_DOT:
- LODSB ;Next letter of name
- OR AL,AL ;Is it the last letter
- JZ COPY_NAME1 ;If yes, begin to copy the name
- CMP AL,"." ;Is this the dot?
- JNE LOOK_FOR_DOT
- GOT_THE_DOT:
- PUSH SI ;Now SI points to the extension
- MOV DI,OFFSET CURRENT_FILE+8 ;DI points to extension
- MOV CX,3
- COPY_EXTENSION:
- LODSB ;Next letter of the extension
- OR AL,AL ;Is it the last letter?
- JZ END_COPY
- CALL UPPER_CASE ;Convert letter to upper case
- STOSB ;And store it
- LOOP COPY_EXTENSION
- END_COPY:
- POP SI ;Recover location of name
- COPY_NAME1:
- DEC SI
- COPY_NAME:
- DEC SI
- STD ;Copy name right to left
- MOV CX,8 ;Eight letters in filename
- MOV DI,OFFSET CURRENT_FILE+7 ;Point to end of name
- NAME_LOOP:
- CMP SI,DX ;At start of name yet?
- JB PARSE_DONE ;If yes, then quit copying
- LODSB ;Get letter of name
- CMP AL,"\" ;At path specification?
- JE PARSE_DONE ;If yes, then quit copying
- CMP AL,"/" ;At path specification?
- JE PARSE_DONE ;If yes, then quit copying
- CMP AL,":" ;At drive specification?
- JE PARSE_DONE ;If yes, then quit copying
- CMP AL," " ;Is this letter a space?
- JE SKIP_SPACE ;Don't copy any spaces
- CALL UPPER_CASE ;Convert letters to upper case
- STOSB ;Store the letter
- SKIP_SPACE:
- CMP SI,0FFFFH ;Did SI wrap around segment?
- JE PARSE_DONE ;If yes, then quit copying
- LOOP NAME_LOOP ;Loop through entire name
- PARSE_DONE:
- RET ;Done parsing the name
- PARSE_STRING ENDP
-
- ;-----------------------------------------------------------------------
- ; This subroutine converts the letter in AL to upper case.
- ;-----------------------------------------------------------------------
- UPPER_CASE PROC NEAR
- ASSUME DS:NOTHING, ES:NOTHING
- CMP AL,"a" ;Is it lower case?
- JB NO_CHANGE ;If not, don't change it
- CMP AL,"z" ;Is it a letter?
- JA NO_CHANGE ;If not, don't change it
- AND AL,11011111B ;This convert to upper case
- NO_CHANGE: RET
- UPPER_CASE ENDP
-
- ;-----------------------------------------------------------------------
- ; This subroutine adds the current PSP segment address to the handle
- ; in BX. This creates a unique number for each open handle.
- ;-----------------------------------------------------------------------
- ADD_PSP PROC NEAR
- ASSUME DS:NOTHING, ES:NOTHING
- PUSH BX ;Save the starting handle
- MOV AH,51H ;Get current PSP
- INT 21H
- POP AX ;Get back starting handle
- ADD BX,AX ;And add it to the PSP
- RET
- ADD_PSP ENDP
-
- ;-----------------------------------------------------------------------
- ; This subroutine zeros out the file and handle tables.
- ; on entry DS points to the tables segment.
- ;-----------------------------------------------------------------------
- RESET_TABLE PROC NEAR
- ASSUME DS:NOTHING, ES:NOTHING
- PUSH DS
- POP ES
- MOV DI,FILE_TABLE
- MOV CX,DS:NUM_FILES
- XOR AX,AX
- ZERO_FILES:
- STOSW ;Erase the old filename
- ADD DI,10
- STOSW ;Zero the total count
- ADD DI,ENTRY_SIZE-14
- LOOP ZERO_FILES
- MOV DI,HANDLE_TABLE ;Point to the handle table
- MOV CX,NUM_HANDLES ;Number of entries in it.
- ZERO_HANDLES:
- XOR AX,AX
- STOSW
- MOV AX,FILE_TABLE
- STOSW
- LOOP ZERO_HANDLES ;Zero the handle table entries
- MOV LAST_FILE,FILE_TABLE
- MOV LAST_HANDLE,HANDLE_TABLE
- RET
- RESET_TABLE ENDP
-
- ;-----------------------------------------------------------------------
- ; To install, store existing interrupt vectors and replace them with the
- ; new ones. Then exit and remain resident.
- ;-----------------------------------------------------------------------
- INSTALL:
- ASSUME CS:CSEG, DS:CSEG, ES:NOTHING
- CALL LOAD_PARAMS
- JCXZ NO_DIGITS
- XOR AX,AX ;Clear AX for the total
- GET_DIGIT:
- MOV BL,DS:[SI] ;Get next letter
- SUB BL,30H ;Convert ascii to integer
- JC NOT_A_DIGIT ;Was it below a 0?
- CMP BL,9 ;Was it above a 9?
- JA NOT_A_DIGIT ;Ignore if not 0-9
- MOV BH,10
- MUL BH ;Times 10 for next digit
- XOR BH,BH
- ADD AX,BX ;Add in the new digit
- NOT_A_DIGIT:
- INC SI
- LOOP GET_DIGIT ;Look at all characters
- OR AX,AX ;Did we get anything
- JZ NO_DIGITS
- CMP AX,2000 ;Above the upper limit?
- JBE SIZE_OK
- MOV AX,2000
- SIZE_OK:
- MOV NUM_FILES,AX
- NO_DIGITS:
- MOV AX,3513H ;Get BIOS disk I/O vector
- INT 21H
- MOV WORD PTR [OLDINT13] ,BX
- MOV WORD PTR [OLDINT13+2],ES
- MOV DX, OFFSET NEWINT13
- MOV AX, 2513H
-
- INT 21H ;DOS function to change vector
- MOV AX,3521H ;Get DOS function vector
- INT 21H
- MOV WORD PTR [OLDINT21] ,BX
- MOV WORD PTR [OLDINT21+2],ES
- MOV DX, OFFSET NEWINT21
- MOV AX, 2521H
- INT 21H ;DOS function to change vector
-
- ;-----------------------------------------------------------------------
- ; Deallacote our copy of the enviornment.
- ; Exit using INT 27H. Leave code and space for the tables resident.
- ;-----------------------------------------------------------------------
-
- CALL RESET_TABLE ;Clear out the file table
- MOV AX,DS:[002CH] ;Get segment of enviornment
- MOV ES,AX ;Put it into ES
- MOV AH,49H ;Release enviornment segment
- INT 21H
-
- MOV AX,NUM_FILES ;Get number of files
- MOV BX,ENTRY_SIZE ;Times size of each entry
- MUL BX
- ADD AX,FILE_TABLE ;Add in beginning of table
- MOV FILE_TABLE_END,AX
- ADD AX,15
- MOV CL,4
- SHR AX,CL
- MOV DX,AX ;Leave this much resident
- MOV AX,3100H
- INT 21H ;Terminate and stay resident
-
- ;-----------------------------------------------------------------------
- ; Here is the code used to initialize RECORDER.COM. First determine
- ; if RECORDER is already installed.
- ;-----------------------------------------------------------------------
- ASSUME CS:CSEG, DS:CSEG, ES:NOTHING
- EVEN ;Align to an even byte boundry
-
- INITIALIZE:
- ASSUME DS:CSEG, ES:NOTHING
- MOV DX,OFFSET COPYRIGHT
- CALL STRING_CRLF ;Display the string
-
- ; Search for a previously installed copy of RECORDER
-
- NOT WORD PTR START ;Modify to avoid false match
- XOR BX,BX ;Start search at segment zero
- MOV AX,CS ;Compare to this code segment
- NEXT_SEGMENT:
- INC BX ;Look at next segment
- CMP AX,BX ;Until reaching this segment
- MOV ES,BX
- JNE NOT_FOUND
- JMP INSTALL
- NOT_FOUND:
- MOV SI,OFFSET START ;Setup to compare strings
- MOV DI,SI
- MOV CX,16 ;16 bytes must match
- REP CMPSB ;Compare DS:SI to ES:DI
- OR CX,CX
- JNZ NEXT_SEGMENT ;If no match, try next segment
-
- ; When all 16 bytes match, an installed copy already exists and
- ; ES points to resident code segment. Display the file table
-
- PUSH ES
- POP DS ;DS also points to table
- ASSUME DS:NOTHING, ES:NOTHING
-
- MOV DI,FILE_TABLE ;Point to the table
- MOV CX,DS:NUM_FILES ;Number of entries in table
- ZERO_LOOP:
- MOV BYTE PTR [DI+11],0 ;Zero the displayed byte
- ADD DI,ENTRY_SIZE ;Move to next entry
- LOOP ZERO_LOOP ;Do entire table
-
- CALL NEW_LINE
- MOV DX,OFFSET HEADER;Point to header text
- CALL STRING_CRLF ;Display the string
- MOV CX,DS:NUM_FILES ;Number of entries in table
- FILE_LOOP:
- PUSH CX
- MOV DI,FILE_TABLE ;Point to the table
- XOR AX,AX
- MOV CX,DS:NUM_FILES ;Number of entries in table
- FIND_BIGGEST:
- CMP [DI+12],AX
- JBE NOT_BIGGER
- CMP BYTE PTR [DI+11],0
- JNE NOT_BIGGER
- MOV SI,DI
- MOV AX,[DI+12]
- NOT_BIGGER:
- ADD DI,ENTRY_SIZE
- LOOP FIND_BIGGEST
-
- CMP BYTE PTR [SI+11],1
- JE LAST_ONE
- MOV BYTE PTR [SI+11],1
- MOV DX,SI
- ADD SI,12
- CMP WORD PTR [SI],0
- JZ LAST_ONE
- MOV AH,40H
- MOV BX,1
- MOV CX,8 ;8 letters in name
- INT 21H
- PUSH DX
- MOV AL,"." ;Display a dot
- CALL DISPLAY_CHAR
- POP DX
- ADD DX,8 ;Now point to extension
- MOV AH,40H
- MOV CX,3 ;3 letters in extension
- INT 21H
- LODSW
- PUSH AX ;Save the total
- CALL NUMBER_OUT ;Display the totals column
- LODSW
- CALL NUMBER_OUT
- LODSW
- CALL NUMBER_OUT
- LODSW
- CALL NUMBER_OUT
- CALL NEW_LINE
- POP AX ;Recover the total count
- POP CX
- LOOP FILE_LOOP
- CMP AX,2 ;Was the last total less than 2?
- JB LAST_ONE ;If yes, table is not full yet.
- CALL NEW_LINE
- MOV DX,OFFSET FULL_MESS
- CALL STRING_CRLF ;Display the string
- LAST_ONE:
- CALL LOAD_PARAMS
- JCXZ NO_PARAMS
- SCAN_PARAMS:
- MOV AL,CS:[SI]
- OR AL,32 ;Convert it to lower case
- CMP AL,"r" ;Is it the R parameter?
- JE SLASH_R ;If yes, then reset the table
- INC SI
- LOOP SCAN_PARAMS ;Look at all parameters
- NO_PARAMS:
- MOV AX,4C00H
- INT 21H
- SLASH_R:
- CALL RESET_TABLE
- JMP NO_PARAMS
-
- ;-----------------------------------------------------------------------
- ; NUMBER_OUT Outputs the number in AX to the standard output device
- ;-----------------------------------------------------------------------
- NUMBER_OUT PROC NEAR
- PUSH AX ;Save the number
- MOV AL," " ;Send a space
- CALL DISPLAY_CHAR ;Write the character
- MOV AL," " ;Send another space
- CALL DISPLAY_CHAR ;Write the character
- POP AX
- XOR CX,CX ;Indicates no digit yet
-
- MOV BX,10000 ;Get 10000's digit
- CALL DIVIDE_OUT ;Display it
- MOV BX,1000 ;Get 1000's digit
- CALL DIVIDE_OUT ;Display it
- MOV BX,100 ;Get 100's digit
- CALL DIVIDE_OUT ;Display it
- MOV BX,10 ;Get 10's digit
- CALL DIVIDE_OUT ;Display it
-
- ADD AL,30H ;Get 1's digit
- CALL DISPLAY_CHAR ;Display the last character
- RET
- NUMBER_OUT ENDP
-
- ;-----------------------------------------------------------------------
- ; This divides AX by BX and displays the result. Remainder is in AX.
- ;-----------------------------------------------------------------------
- DIVIDE_OUT PROC NEAR
- XOR DX,DX
- DIV BX ;Divide to get this digit
- PUSH DX ;Save the remainder
- OR CX,AX
- OR CX,CX ;Any digits yet?
- JNZ NOT_A_SPACE
- MOV AL," "-30H
- NOT_A_SPACE:
- ADD AL,30H ;Convert it to ASCII
- PUSH CX
- CALL DISPLAY_CHAR ;Write the character
- POP CX
- POP AX ;Get the remainder back
- RET
- DIVIDE_OUT ENDP
-
- ;-----------------------------------------------------------------------
- ; DISPLAY_CHAR outputs the character in AL to the standard output device
- ;-----------------------------------------------------------------------
- DISPLAY_CHAR PROC NEAR
- MOV DL,AL ;Get the character into DL
- MOV AH,02 ;DOS string output function
- INT 21H
- RET
- DISPLAY_CHAR ENDP
-
- ;-----------------------------------------------------------------------
- ; STRING_CR displays a string followed by a CR and LF
- ; Entry point NEW_LINE displays only the CR and LF
- ;-----------------------------------------------------------------------
- STRING_CRLF PROC NEAR
- MOV AH,9 ;Display string function
- INT 21H
- NEW_LINE:
- MOV AL,13 ;The carriage return
- CALL DISPLAY_CHAR ;Send it
- MOV AL,10 ;The line feed
- CALL DISPLAY_CHAR ;Send it
- RET
- STRING_CRLF ENDP
-
- ;-----------------------------------------------------------------------
- ; This subroutine sets DI to the command line and CX to the byte count
- ;-----------------------------------------------------------------------
- LOAD_PARAMS PROC NEAR
- MOV SI,80H ;Point to parameter area
- MOV CL,CS:[SI] ;Get number of chars into CL
- XOR CH,CH ;Make it a word
- INC SI ;Point to first character
- CLD ;String searchs forward
- RET
- LOAD_PARAMS ENDP
-
- CSEG ENDS
- END START
-