home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS 1992 June
/
SIMTEL_0692.cdr
/
msdos
/
dskutl
/
dcache.arc
/
DCACHE.ASM
next >
Wrap
Assembly Source File
|
1988-10-11
|
55KB
|
1,036 lines
;==========================================================================
; DCACHE.COM - A fixed disk cache for the IBM Personal Computer.
; PC Magazine, Vol 7 # 17
;--------------------------------------------------------------------------
CODE SEGMENT PARA PUBLIC 'CODE'
ASSUME CS:CODE
ORG 2CH
ENV_SEG DW ? ;Segment of the environment block
ORG 80H
TAIL_LENGTH DB ? ;Length of the command tail
ORG 100H
ENTRY: JMP MAIN_ENTRY
;--------------------------------------------------------------------------
; Data Area
;--------------------------------------------------------------------------
PROGRAM DB 'DCACHE 1.0 (c) 1988 Ziff Communications Co.',13,10
DB 'PC Magazine ',254,' Douglas Boling',13,10,'$',26
ENABLED DB 1 ;0 = cache disabled, 1 = enabled
EMS_FLAG DB 0 ;use EMS ram flag, 1 = use EMS
EMS_HANDLE DW 0 ;handle for EMS memory.
ADDR_MASK DW 001EH ;Default mask set for 64K cache
SIZE_MASK DW 0
EMS_MASK DW 0 ;used to sel. the proper EMS page
DISK_NUM DB 80H ;number of fixed disk to cache
PAGE_SIZE DB 8 ;size of cache page
MAX_HEAD DW ? ;maximum value of head parameter
MAX_SECTOR DW ? ;maximum value of sector
MAX_SEGMENT DW ? ;last segment of data cache
DOSBOFFSET DW ? ;offset of dos data buffer
DOSBSEGMENT DW ? ;sector of dos data buffer
NUM_OF_SEC DB ? ;number of sectors requested
DISK_FUNCT DB ? ;function requested
SECTOR_NUM DW ? ;sector parameter from dos call
HEAD_NUM DB ? ;head parameter
CYLINDER_NUM DW ? ;cylinder parameter
SEGMENT_PTR DW 0 ;pointers into the cache
PAGE_PTR DW 0
LOG_SEC_HIGH DW 0 ;Logical sector number of disk
LOG_SEC_LOW DW 0 ; request.
LAST_BAD_PAGE DW -1 ;stores the last page that
;contained an error
LOOKUPTABLE DW OFFSET DATA_START ;offset of lookup table
CACHE_SEGMENT DW 0 ;segment of cache data
OLD_DISK_INT LABEL DWORD ;old bios interrupt 13h vector
OLD_INT13H DW 2 DUP (?)
;-----------------------------------------------------------------------------
; This routine intercepts the bios disk calls.
; Entry: ah - disk function (All other registers specific to disk read.)
; al - number of sectors es:bx - pointer to data buffer
; ch - Cylinder number dh - Head number
; cl - 7,6 Cyl. high. 5-0 sector number dl - drive number
;-----------------------------------------------------------------------------
DISK_INT PROC FAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
CMP CS:ENABLED,0 ;See if cache enabled
JE SKIP_CACHE
CMP DL,CS:DISK_NUM ;See if the correct disk
JNE SKIP_CACHE
STI ;Allow interrupts
CMP AH,2 ;If any other function besides
JE CACHE_IT ; read or write, reset cache.
CMP AH,3
JE CACHE_IT1
CMP AH,1 ;If just checking the last status
JE SKIP_CACHE ; skip cache, but don't reset.
RESET_CMD:
PUSH ES ;If the command is not a simple
PUSH CS ; read, write, or status, assume
POP ES ; the worst and clear the lookup
ASSUME ES:CODE ; table.
CALL RESET_CACHE
POP ES
ASSUME ES:NOTHING
SKIP_CACHE:
JMP CS:OLD_DISK_INT ;jmp to bios disk routine.
;--------------------------------------------------------------------------
;Compute the logical sector number from the cylinder, head, and sector.
;--------------------------------------------------------------------------
CACHE_IT:
CMP AL,CS:PAGE_SIZE ;For disk read, cache reads of
JA SKIP_CACHE ; a page or less.
CACHE_IT1:
PUSH DS ;save registers
PUSH DI
PUSH SI
PUSHF
PUSH AX
PUSH BX
PUSH CX
PUSH DX
PUSH CS ;set ds to code segment
POP DS
ASSUME DS:CODE
;--------------------------------------------------------------------------
;Store calling parameters.
;--------------------------------------------------------------------------
MOV DOSBOFFSET,BX ;save dos pointer to its data
MOV DOSBSEGMENT,ES ; buffer.
MOV BX,CX ;copy cx
AND BX,003FH ;strip all but the sector number
MOV SECTOR_NUM,BX ;save sector number
MOV HEAD_NUM,DH ;save head number
MOV NUM_OF_SEC,AL ;save the number of sectors needed
MOV DISK_FUNCT,AH ;save function called.
;--------------------------------------------------------------------------
;Compute logical sector number from the cylinder, head, and sector parameters.
;--------------------------------------------------------------------------
XCHG CL,CH ;create full 10 bit cylinder num.
ROL CH,1 ; the top 2 bits are in ch bits
ROL CH,1 ; 7 and 6. roll them into bits
AND CH,03H ; 1 and 2.
MOV CYLINDER_NUM,CX ;save the cylinder number
MOV AX,CX ;copy cylinder number for multiply
MOV BL,DH ;get head number out of dx
MUL MAX_HEAD ;multiply cylinder to make room
XOR BH,BH ;clear high byte of head value
ADD AX,BX ;add in head.
MUL MAX_SECTOR ;multiply by max sector value
ADD AX,SECTOR_NUM ;add sector number
ADC DX,0 ;propigate carry.
MOV LOG_SEC_HIGH,DX ;save logical sector number
MOV LOG_SEC_LOW,AX
;--------------------------------------------------------------------------
;Store values needed later.
;--------------------------------------------------------------------------
MOV BH,AL
SHL BH,1
AND BX,3E00H
MOV PAGE_PTR,BX ;save page index
AND BH,30H
MOV SI,BX ;save page index for cache load
;--------------------------------------------------------------------------
;Point the segment register to the proper DOS memory block
;--------------------------------------------------------------------------
MOV BX,AX ;copy logical sector low
MOV CL,5
SHL BX,CL ;Convert logical sector number to
AND BX,SIZE_MASK ; cache page index
ADD BX,CACHE_SEGMENT
MOV SEGMENT_PTR,BX ;save segment index
MOV BX,AX ;copy logical sector number
MOV DI,LOOKUPTABLE ;use di to point to lookup table
;--------------------------------------------------------------------------
;Check for a read or a write
;--------------------------------------------------------------------------
CMP DISK_FUNCT,2
JNE DISK_WRITE
JMP DISK_READ
;--------------------------------------------------------------------------
;Process bios write calls.
;--------------------------------------------------------------------------
DISK_WRITE:
MOV CL,AL ;See if the write crosses a page
AND CL,07H ; boundry. If > 8, it does.
MOV CH,NUM_OF_SEC
ADD CL,CH
CMP CL,PAGE_SIZE ;If the write crosses a page
JA WRITE_UPDATE_SKP ; boundry, skip the update and
CMP EMS_FLAG,0 ; just purge the cache.
JE WRITE_SKP_EMS
CALL EMS_SETUP ;access the EMS page bx=logsec_low
WRITE_SKP_EMS:
PUSH AX
CALL CHECK_HIT ;Check to see if the data is in
POP AX ; the cache.
JNE EXIT_AND_RESTORE ;If miss, skip all this stuff
;--------------------------------------------------------------------------
;Since the data is in the cache, update just the stuff to be written
;--------------------------------------------------------------------------
XOR CL,CL
MOV DI,PAGE_PTR ;Load the pointers for the data
MOV SI,DOSBOFFSET ; move. ch already contains the
MOV ES,SEGMENT_PTR ; number of sectors to move. cx
MOV DS,DOSBSEGMENT ; then contains the number of
ASSUME DS:NOTHING,ES:NOTHING ; words to move.
CLD
REP MOVSW ;Copy the data to be written into
PUSH CS ; the cache.
POP DS
ASSUME DS:CODE
JMP SHORT EXIT_AND_RESTORE
;--------------------------------------------------------------------------
;If the write crosses a page boundry, just delete the entry from the table.
;--------------------------------------------------------------------------
WRITE_UPDATE_SKP:
MOV SI,AX ;Save logical sector low logical
MOV CL,PAGE_SIZE ; sector high will be fine in dx.
DEC CH
DISK_WRITE1:
CMP CH,CL ;If the number of sectors is less
JA DISK_WRITE2 ; than the page size, decriment
MOV CL,CH ; by the number of sectors
DISK_WRITE2:
PUSH CX
CALL CHECK_HIT ;Check to see if the sector
POP CX
JNE DISK_WRITE3 ;is in table. Purge the tag if
MOV WORD PTR [DI][BX],0FFFFH ;this is a hit.
DISK_WRITE3:
PUSH SI ;Save copy of logical sector num
SUB CH,CL
MOV BL,CL ;Subtract the page size from the
XOR BH,BH ; number of sectors written. Add
ADD SI,BX ; to the logical sector number.
ADC DL,0
MOV AX,SI ;Move logical sector low to ax.
POP BX ;Get sector before add for compare
XOR BX,AX ;If there is no difference in the
TEST BL,08H ; logical page after the inc then
JNZ DISK_WRITE1 ; exit the loop.
;--------------------------------------------------------------------------
;restore the registers for the bios call.
;--------------------------------------------------------------------------
EXIT_TO_BIOS:
POP DX ;jump to the bios interrupt as if
POP CX ; we were not here.
POP BX
POP AX
POPF
MOV ES,DOSBSEGMENT
POP SI
POP DI
POP DS
JMP CS:OLD_DISK_INT
;--------------------------------------------------------------------------
;Exit to bios and restore EMS if necessary
;--------------------------------------------------------------------------
EXIT_AND_RESTORE:
CMP EMS_FLAG,0
JE EXIT_TO_BIOS
MOV AH,48H ;Restore EMS configuration
MOV DX,EMS_HANDLE
INT 67H
OR AH,AH
JE EXIT_TO_BIOS
INT_EMS_ERR:
MOV ENABLED,0 ;EMS error, assume the worst and
JMP SHORT EXIT_TO_BIOS ; disable the cache.
;--------------------------------------------------------------------------
;Process bios read calls.
;--------------------------------------------------------------------------
DISK_READ:
ASSUME DS:CODE
;If using Expanded memory, get the needed segments.
CMP EMS_FLAG,0
JE INT_DOS_MEM
CALL EMS_SETUP
INT_DOS_MEM:
;--------------------------------------------------------------------------
;Convert logical sector number to an index into the lookup table.
;--------------------------------------------------------------------------
XOR CL,CL ;clear sector counter
CALL CHECK_HIT ;see if we have a hit
CMP AX,LAST_BAD_PAGE ;If this page has a bad sector
JE EXIT_AND_RESTORE ; don't fetch it.
MOV WORD PTR [DI][BX],AX ;update the look up table.
;--------------------------------------------------------------------------
;if we need 2 pages, check to see if the other page is in the cache
;--------------------------------------------------------------------------
MOV AX,LOG_SEC_LOW ;Add the number of sectors needed
MOV CH,AL ; to the displacment in the page
AND CH,07H ; if > 8, we need 2 pages.
ADD CH,NUM_OF_SEC
CMP CH,PAGE_SIZE
JLE END_OF_CHK ;we only need 1 page
CMP SI,03000H
JNE CHK_2ND_PAGE
MOV DX,SEGMENT_PTR ;check to see if we are at the
CMP DX,MAX_SEGMENT ; very top of the cache and we
JB CHK_2ND_PAGE
MOV [DI][BX],0FFFFH ;clear lookup table
JMP SHORT EXIT_AND_RESTORE ;skip cache.
;--------------------------------------------------------------------------
;adjust the index into the lookup table to check for the second page.
;--------------------------------------------------------------------------
CHK_2ND_PAGE:
MOV DX,LOG_SEC_HIGH ;we need 2 pages, check to see if
XOR BH,BH ; the other page is in the cache.
MOV BL,NUM_OF_SEC
ADD AX,BX ;Do this by adding the number of
ADC DL,0 ; sectors needed to the starting
CALL CHECK_HIT ; logical sector number.
JE END_OF_CHK ;skip next if second page hit.
MOV WORD PTR [DI][BX],AX ;update the look up table.
MOV AL,PAGE_SIZE
CMP CL,AL ;If we need only the second page,
JNE END_OF_CHK ; adjust the starting pointers
ADD SI,1000H ; into the cache.
XOR AH,AH
ADD LOG_SEC_LOW,AX
ADC LOG_SEC_HIGH,0
END_OF_CHK:
;--------------------------------------------------------------------------
;Now that we have checked for the data in the cahe, jump to the right routine
;--------------------------------------------------------------------------
CMP CL,0 ;check the number of sectors to
JE CACHE_HIT ; read from the disk.
;--------------------------------------------------------------------------
;The request is a cache miss. Load the data needed from the disk to the cache.
;--------------------------------------------------------------------------
CACHE_MISS:
XOR CH,CH
MOV DI,CX ;save the number of sectors needed
;--------------------------------------------------------------------------
;Use the logical sector number to compute the new calling parameters.
;--------------------------------------------------------------------------
XOR CX,CX ;clear a place for the sector num
MOV DX,LOG_SEC_HIGH ;put the logical sector number
MOV AX,LOG_SEC_LOW ; into dx,ax
AND AX,0FFF8H ;clear off the odd sector
JNE SET_REGS ;if the resulting logical sector
OR DX,DX ; number is 0, modify the calling
JNE SET_REGS ; parameters to allow for the
INC AX ; sectors starting at 1.
ADD SI,200H ;si holds the cache target address
DEC DI ;di holds the number of sectors
SET_REGS: ; to fetch.
DIV MAX_SECTOR
OR CX,DX ;save the remainder (sector num)
JNE SET_REGS1 ;Since the sector number can not
MOV CX,MAX_SECTOR ; be zero, check for this and
DEC AX ; correct if necessary.
SET_REGS1:
XOR DX,DX ;remove the remainder
DIV MAX_HEAD
;--------------------------------------------------------------------------
;put cylinder and sector parameters into their proper registers.
;--------------------------------------------------------------------------
MOV DH,DL ;move head to proper register.
XCHG AL,AH ;Put the cylinder number into the
ROR AL,1 ; strange, but required registers
ROR AL,1
OR CX,AX
;--------------------------------------------------------------------------
;Compute data buffer inside cache.
;--------------------------------------------------------------------------
MOV BX,SI ;Point the data buffer for the
MOV ES,SEGMENT_PTR ; call to the proper cache page.
ASSUME ES:NOTHING
;--------------------------------------------------------------------------
;complete the parameters for the bios call.
;--------------------------------------------------------------------------
MOV AX,DI ;get the number of sectors to read
MOV AH,02H ;read data from disk
MOV DL,DISK_NUM ;access the correct disk
;--------------------------------------------------------------------------
;Set up parameters and call real bios int 13h.
;--------------------------------------------------------------------------
PUSH AX
PUSHF
CALL OLD_DISK_INT
POP SI
JC BIOS_ERROR ;if an error ocurred, deal with it
;--------------------------------------------------------------------------
;Cache hit. Transfer the data from the cache to the dos buffer.
;--------------------------------------------------------------------------
CACHE_HIT:
MOV DI,DOSBOFFSET ;Load es:di with the dos data
MOV ES,DOSBSEGMENT ; buffer.
ASSUME ES:NOTHING
MOV CH,NUM_OF_SEC ;Put number of words to transfer
XOR CL,CL ; into cx.
MOV SI,PAGE_PTR ;Load ds:si with the location of
MOV DS,SEGMENT_PTR ; the data in the cache.
ASSUME DS:NOTHING
CLD
REP MOVSW ;Transfer the data from the cache
PUSH CS
POP DS
ASSUME DS:CODE
EXIT_TO_CALLER: ; to the caller of int 13h
;--------------------------------------------------------------------------
;Restore EMS configuration if necessary.
;--------------------------------------------------------------------------
CMP EMS_FLAG,0 ;Check to see if we are using
JE CALLER_EXIT_SKIP ; ems memory.
MOV AH,48H
MOV DX,EMS_HANDLE ;If so, restore the mapping
INT 67H ; context used before this
OR AH,AH ; interrupt.
JE CALLER_EXIT_SKIP
JMP INT_EMS_ERR
CALLER_EXIT_SKIP:
POP DX
POP CX
POP BX
POP AX
POPF
XOR AX,AX ;Clear ax to indicate 0 return
POP SI ; code.
POP DI
POP DS
CLC ;Clear carry to indicate no error.
RET 2 ;Return but keep current flags
;-----------------------------------------------------------------------------
;Error routine
;-----------------------------------------------------------------------------
BIOS_ERROR:
ASSUME DS:CODE
MOV AX,LOG_SEC_LOW ;Get logical sector, convert it
MOV DX,LOG_SEC_HIGH ; into an index into the
MOV DI,LOOKUPTABLE ; lookup table, then erase the
CALL CHECK_HIT ; tag.
MOV WORD PTR [DI][BX],0FFFFH
MOV CX,SI ;See if we were reading 2
CMP CL,PAGE_SIZE ; pages. If so, clear next
JLE BIOS_ERROR1 ; entry in the lookup table.
ADD BX,2
MOV WORD PTR [DI][BX],0FFFFH
BIOS_ERROR1:
MOV LAST_BAD_PAGE,AX
XOR AX,AX
MOV DL,DISK_NUM ;Reset disk system using
PUSHF ; bios int 13 function 0.
CALL OLD_DISK_INT
JMP EXIT_AND_RESTORE
DISK_INT ENDP
;-----------------------------------------------------------------------------
;EMS Setup This routine saves the current state of the EMS driver, then
; loads in the proper EMS page needed for the cache.
;Entry: bx - low word of logical sector number
;-----------------------------------------------------------------------------
EMS_SETUP PROC NEAR
ASSUME DS:CODE
PUSH AX
PUSH DX
MOV CL,5
SHR BX,CL ;Convert logical sector num to
AND BX,EMS_MASK ; a physical EMS page number.
;--------------------------------------------------------------------------
;Save current state of EMS driver
;--------------------------------------------------------------------------
MOV AH,47H ;Save state function
MOV DX,EMS_HANDLE
INT 67H ;call EMS driver
OR AH,AH ;check for error
JNE EMS_SETUP_ERR
;--------------------------------------------------------------------------
;Get the proper EMS pages from the EMS driver.
;--------------------------------------------------------------------------
MOV AX,4400H ;map EMS memory to cache segment
INT 67H
OR AH,AH ;check for EMS error
JNE EMS_SETUP_ERR
POP DX
POP AX
RET
EMS_SETUP_ERR:
ADD SP,6 ;clean up stack
JMP INT_EMS_ERR
EMS_SETUP ENDP
;-----------------------------------------------------------------------------
;Check hit. This routine checks the lookup table for a match.
;Entry: dl,ax logical sector number. Exit: ZF set = hit, ZF clear, miss
; cl = number of sectors to fetch cl = updated number of sectors
; di = base of lookup table
;-----------------------------------------------------------------------------
CHECK_HIT PROC NEAR
ASSUME DS:CODE
AND AX,0FFF8H ;remove the page index.
OR AX,DX ;add in the top 3 bits
MOV BX,AX ;copy the log sec num to bx to
SHR BX,1 ; create the table index.
SHR BX,1
AND BX,ADDR_MASK ;Use the addr mask to limit the
CMP AX,WORD PTR [DI][BX] ; size of the lookup table
JE CHECK_HIT1 ;Check for a hit.
ADD CL,PAGE_SIZE ;cache miss, grab a page of sectors
CHECK_HIT1:
RET
CHECK_HIT ENDP
;-----------------------------------------------------------------------------
;Reset Cache. Routine clears the cache look up table.
;Entry ds - segment of the lookup table, and the lookup table offset
;-----------------------------------------------------------------------------
RESET_CACHE PROC NEAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
PUSH DI
PUSH CX
PUSH AX
MOV AX,0FFFFH
MOV DI,ES:LOOKUPTABLE ;point di to the lookup table
MOV CX,ES:ADDR_MASK ;compute size of the lookup table
SHR CX,1
INC CX
REP STOSW ;write ffff to each entry in the
POP AX ; lookup table.
POP CX
POP DI
RET
RESET_CACHE ENDP
;--------------------------------------------------------------------------
;Safe place to clear lookup table.
;--------------------------------------------------------------------------
INSTALL1:
ASSUME DS:CODE ;DS points to code segment
PUSH CS
POP ES ;point es to lookup table segment
ASSUME ES:NOTHING
CALL RESET_CACHE ;Clear lookup table
POP CX ;get state of enable flag
MOV ENABLED,CL ;Terminate and stay resident
INT 21H ; with 0 return code.
;-------------------------------------------------------------------------
;Data area not needed by resident routine.
;-------------------------------------------------------------------------
EVEN ;start lookup table on even byte
DATA_START = $
;=========================================================================
;Non-resident code.
;-------------------------------------------------------------------------
LOOKUP_SIZE DW 0 ;size of the lookup table
TERM_MEM DW 0 ;amount of memory needed at end.
ALRDY_IN_MEM DB 0 ;flag indicating cache installed.
OTHER_SEG DW 0 ;segment of installed copy
EMS_HEADER DB 'EMMXXXX0' ;Header of EMS driver.
HELP0 DB 13,10,'Options:',13,10
DB '/OFF - Disable Cache',13,10
DB '/ON - Enable Cache',13,10
DB '/U - Uninstall Cache',13,10,'$'
HELP01 DB '/Mx - Set Cache Size To x KB',13,10
DB '/E - Use EMS',13,10
DB '/Hx - Cache Physical Disk x',13,10
DB 'Defaults: /M64 /H0 /ON',13,10,'$'
HELP1 DB 'Invalid Cache Size$'
HELP2 DB 'Already Installed$'
HELP3 DB 'Invalid Command$'
HELP6 DB 'Hard Disk Too Large$'
HELP7 DB 'No EMS Memory$'
HELP8 DB 'EMS Driver Error$'
HELP9 DB 'Invalid Disk$'
HELP10 DB 'Cannot Uninstall$'
MSG1 DB 'Cache Installed',13,10,'$'
MSG2 DB 'Not Enough Memory',13,10,'$'
COMMANDS DB 'oumhe' ;Letters corrsponding to the
COMMANDS_END = $ ; command line switches.
MEM_SIZE_TBL DB '16326412255110204081' ;Numbers corresponding to the
MEM_SIZE_TBL_END = $ ; allowable cache sizes.
JUMPTABLE:
DW OFFSET CACHE_ON_OFF
DW OFFSET UNINSTALL
DW OFFSET CACHE_SIZE
DW OFFSET DISK_SELECT
DW OFFSET EXPANDED_MEM
;-----------------------------------------------------------------------------
;Main. This routine performs the instalation, and modification of the cache.
;-----------------------------------------------------------------------------
MAIN PROC
ASSUME CS:CODE,DS:CODE,ES:CODE,SS:CODE
MAIN_ENTRY:
;-----------------------------------------------------------------------------
;display program header
;-----------------------------------------------------------------------------
MOV DX,OFFSET PROGRAM
MOV AH,9
INT 21H
;-----------------------------------------------------------------------------
;Deallocate environment block
;-----------------------------------------------------------------------------
PUSH ES
MOV ES,ENV_SEG ;Get the segment from the PSP
ASSUME ES:NOTHING
MOV AH,49H ;Call dos release memory function.
INT 21H
POP ES
ASSUME ES:CODE
;-----------------------------------------------------------------------------
;check for other copies of this program in memory.
;-----------------------------------------------------------------------------
FIND_COPIES:
XOR BX,BX ;Start search a segment 0
MOV WORD PTR [ENTRY],BX
MOV AX,CS ;Get current segment
FIND_LOOP:
INC BX ;Check next segment
MOV ES,BX ;Use es as segment pointer
ASSUME ES:NOTHING
CMP AX,BX ;Did we find ourselves?
JE NO_COPIES ;Yes, only 1 copy in memory
MOV SI,OFFSET ENTRY ;SI is the offset pointer
MOV DI,SI ;Look the same place in both segs
MOV CX,16 ;Check 16 bytes
CLD ;Incriment pointers during compare
REPE CMPSB ;Compare bytes
JNE FIND_LOOP ;If no compare, check another seg
INC ALRDY_IN_MEM ;Set already installed flag
;--------------------------------------------------------------------------
;Check for other parameters on the command line.
;--------------------------------------------------------------------------
NO_COPIES:
MOV OTHER_SEG,ES ;Save the segment of the copy
PUSH CS
POP ES
ASSUME ES:CODE
MOV DI,OFFSET TAIL_LENGTH ;Use di to point to command line
MOV AX,1234H ;Set ax to 1234 to indicate if a
FIND_COMMAND: ; command was ever found.
INC DI
DEC TAIL_LENGTH ;If we are at the end of the
JL FIND_COMMAND_DONE ; command line, exit.
CMP BYTE PTR [DI],'?'
JE DISP_HELP
CMP BYTE PTR [DI],'/' ;if / found a command may
JNE FIND_COMMAND ; follow.
;--------------------------------------------------------------------------
;Figure out what the command is, then process it if possible.
;--------------------------------------------------------------------------
DECODE_COMMAND:
MOV SI,OFFSET COMMANDS ;Use si to point to the possible
XOR BX,BX ; command letters.
MOV AL,1[DI] ;Get command from tail
OR AL,20H ;Convert uppercase to lower
DECODE_LOOP:
CMP AL,[SI] ;Search the list of allowable
JE COMMAND_FOUND ; commands.
INC BX ;If the letters don't match,
INC SI ; inc the pointers to the cmd
CMP SI,OFFSET COMMANDS_END ;If the command was not found,
JBE DECODE_LOOP ; display error message.
ILLEGAL_COMMAND:
MOV DX,OFFSET HELP3 ;Command unrecognised.
JMP SHORT HELP_ROUTINE
COMMAND_FOUND:
CMP BL,1 ;Allow only on, off, and remove
JLE COMMAND_FOUND1 ; if cache already installed.
CMP ALRDY_IN_MEM,0
JNE DISP_HELP2
COMMAND_FOUND1:
SAL BX,1 ;Convert bx into an index into
ADD BX,OFFSET JUMPTABLE ; the jump table.
CALL [BX]
JC HELP_ROUTINE ;If the carry flag is set on
JMP SHORT FIND_COMMAND ; return, display error message.
FIND_COMMAND_DONE:
CMP ALRDY_IN_MEM,0 ;If not installed, install.
JE INSTALL_CACHE
CMP AX,1234H ;Were any commands processed?
JE DISP_HELP2 ;No, print already installed msg
TERMINATE:
MOV AX,4C00H ;Terminate with 0 return code.
INT 21H
;-----------------------------------------------------------------------------
;Print help lines.
;-----------------------------------------------------------------------------
DISP_HELP2:
MOV DX,OFFSET HELP2 ;dcache already installed
JMP SHORT HELP_ROUTINE
DISP_HELP6:
MOV DX,OFFSET HELP6 ;Disk too large
HELP_ROUTINE:
PUSH DX ;Save offset to message
MOV AH,2 ;Output a carrage return
MOV DL,10 ; to put a space between
INT 21H ; the messages.
POP DX ;Get back offset.
MOV AH,9 ;DOS print string routine
INT 21H
DISP_HELP:
MOV DX,OFFSET HELP0 ;Display possible commands
MOV AH,9
INT 21H
CMP ALRDY_IN_MEM,1 ;Check already installed flag
JE RETURN_WITH_1
MOV DX,OFFSET HELP01 ;If not already installed, print
MOV AH,9 ; full list of allowable
INT 21H ; command line switches.
RETURN_WITH_1:
MOV AX,4C01H ;Terminate with 1 return code.
INT 21H
;-----------------------------------------------------------------------------
;Install routine. Compute disk parameters, reserve ems memory if needed,
; compute lookup table size, then jump to install1 routine.
;-----------------------------------------------------------------------------
INSTALL_CACHE:
MOV AH,08H ;Read drive parameters
MOV DL,DISK_NUM
INT 13H
JNC GOOD_DRIVE ;Check to insure that a valid
MOV DX,OFFSET HELP9 ; disk has been selected.
JMP SHORT HELP_ROUTINE
GOOD_DRIVE:
MOV DL,DH
XOR DH,DH
INC DX
MOV MAX_HEAD,DX ;save maximum head value
MOV AX,CX
AND CX,003FH
MOV MAX_SECTOR,CX ;save maximum sector value
XCHG AH,AL ;Compute the largest logical
ROL AH,1 ; sector value. If the value is
ROL AH,1 ; larger than 19 bits, display
AND AX,03FFH ; error message and exit.
MUL MAX_HEAD
ADD AX,MAX_HEAD
MUL MAX_SECTOR
ADD AX,MAX_SECTOR
ADC DX,0
CMP DL,8
JAE DISP_HELP6
;-----------------------------------------------------------------------------
;Allocate memory for the cache.
;-----------------------------------------------------------------------------
MOV AX,ADDR_MASK ;Compute amount of memory needed
INC AX ; for the cache. To do this,
INC AX ; multiply the number of entrys
MOV LOOKUP_SIZE,AX ; in the lookup table by the
MOV CL,PAGE_SIZE ; page size and the sector size.
XOR CH,CH
MUL CX
MOV CX,256 ;Correct for computing twice the
MUL CX ; number of lookup table entrys
MOV CX,4 ; by halving the sector size.
MEM_LOOP1: ;Convert requested memory into
SHR DX,1 ; paragraphs.
RCR AX,1
LOOP MEM_LOOP1
;-----------------------------------------------------------------------------
;Check which memory to use.
;-----------------------------------------------------------------------------
CMP EMS_FLAG,1
JNE GET_DOS_MEM
;-----------------------------------------------------------------------------
;Request memory from EMS driver.
;-----------------------------------------------------------------------------
MOV CX,10
EMS_REQ_LOOP1:
SHR DX,1 ;Convert paragraphs to EMS pages.
RCR AX,1 ; Each page is 16K big.
LOOP EMS_REQ_LOOP1
;-----------------------------------------------------------------------------
;Check to see if there is enough EMS memory to hold the cache.
;-----------------------------------------------------------------------------
MOV CX,AX ;save number of ems pages needed
MOV AH,42H
INT 67H
OR AH,AH ;check for error
JNE EMS_ERROR
CMP BX,CX ;compare available pages with need
JAE GET_EMS_SEG
JMP MEMORY_ERROR
;-----------------------------------------------------------------------------
;Find out the segment of the EMS page frame.
;-----------------------------------------------------------------------------
GET_EMS_SEG:
MOV AH,41H ;get page frame address command
INT 67H ;call EMS driver
OR AH,AH ;check for error
JNE EMS_ERROR
MOV CACHE_SEGMENT,BX ;save page frame segment address
MOV MAX_SEGMENT,BX
MOV SIZE_MASK,0
;Request the memory from EMS driver.
MOV AH,43H ;EMS request memory function
MOV BX,CX ;put number of EMS pages in bx
INT 67H ;call EMS driver
OR AH,AH ;check for error
JNE EMS_ERROR
MOV EMS_HANDLE,DX ;save EMS handle.
MOV AX,ADDR_MASK ;Create the EMS mask from the
MOV CL,3 ; addr mask
SHR AX,CL
MOV EMS_MASK,AX
;Compute the amount of resident memory needed.
MOV DX,LOOKUP_SIZE ;Get back size of lookup table
ADD DX,OFFSET DATA_START+15
MOV CL,4
SHR DX,CL ;convert memory into paragraphs
MOV TERM_MEM,DX
JMP SHORT PRINT_INSTALL_MSG
;-----------------------------------------------------------------------------
;Error routines for memory requests.
;-----------------------------------------------------------------------------
EMS_ERROR:
MOV DX,OFFSET HELP8 ;EMS error
JMP HELP_ROUTINE
;-----------------------------------------------------------------------------
;Get memory from DOS. Try to reduce memory for program to see if there is
; enough memory for the cache.
;-----------------------------------------------------------------------------
GET_DOS_MEM:
;-----------------------------------------------------------------------------
;Move the stack to a safe place inside the cache.
;-----------------------------------------------------------------------------
CLI ;Inhibit interrupts during this
MOV BX,SP ; time.
MOV SP,4000H ;Move the stack pointer down
; closer to the code, and well
STI ; with in the cache memory.
;-----------------------------------------------------------------------------
;Check size of cache memory, then reduce current allocation to minimum.
;-----------------------------------------------------------------------------
OR DX,DX ;allow cache size <= 512K
JNE MEMORY_ERROR ; for DOS memory.
MOV BX,OFFSET DATA_START+15 ;compute start of cache
ADD BX,LOOKUP_SIZE
MOV CL,4 ;convert to segment.
SAR BX,CL
MOV DX,CS ;Get the current code segment
ADD DX,BX ;Add the converted offset
MOV CACHE_SEGMENT,DX ;save the cache segment
;-----------------------------------------------------------------------------
;Continue on with allocating the proper amount of DOS memory.
;-----------------------------------------------------------------------------
ADD BX,AX ;Add size of cache.
MOV TERM_MEM,BX ;reduce to amount of memory needed
MOV AH,4AH ; at termination of the program.
INT 21H ;DOS reallocate memory function
JC MEMORY_ERROR ;es already points to code seg.
;-----------------------------------------------------------------------------
;Create size mask from address mask
;-----------------------------------------------------------------------------
MOV CX,ADDR_MASK ;The last part of the DOS memory
XCHG CH,CL ; installation is to create the
SHR CX,1 ; size mask needed.
AND CX,0FC00H ;Create size mask from addr mask
MOV SIZE_MASK,CX
MOV AX,CACHE_SEGMENT
ADD AX,CX ;Add size mask to cache_segment
MOV MAX_SEGMENT,AX ; register to generate max segment
;-----------------------------------------------------------------------------
;Tell user that cache is installed.
;-----------------------------------------------------------------------------
PRINT_INSTALL_MSG:
MOV DX,OFFSET MSG1
MOV AH,9
INT 21H
;-----------------------------------------------------------------------------
;Redirect interrupt vector 13.
;-----------------------------------------------------------------------------
MOV AL,ENABLED ;save the state of the enable flag
PUSH AX
MOV ENABLED,0 ;disable cache until ready to exit
MOV AX,3513H ;Get the old int 13h vector
INT 21H
MOV OLD_INT13H,BX ;Save the old vector
MOV OLD_INT13H[2],ES
MOV DX,OFFSET DISK_INT ;Point int 13h to cache routine.
MOV AX,2513H
INT 21H
;-----------------------------------------------------------------------------
;Terminate but remain resident.
;-----------------------------------------------------------------------------
MOV DX,TERM_MEM ;get amount of memory needed.
MOV AX,3100H ;Terminate but stay resident
JMP INSTALL1 ;jump to location above the
; lookup table so it can be
; cleared.
;-----------------------------------------------------------------------------
;Routine to print installaion error messages.
;-----------------------------------------------------------------------------
MEMORY_ERROR:
MOV DX,OFFSET MSG2 ;Print DOS memory error
MOV AH,9
INT 21H
MOV AX,4C02H ;terminate with rc = 2.
INT 21H
;-----------------------------------------------------------------------------
;Select disk drive to cache
;-----------------------------------------------------------------------------
DISK_SELECT PROC NEAR
MOV DL,2[DI] ;read number after /h
SUB DL,30h ;convert ascii nubmer to binary
JL DISK_SEL_ERR1 ;allow only the numbers 0-9.
CMP DL,9
JA DISK_SEL_ERR1
OR DL,80H ;consider only fixed disks
MOV DISK_NUM,DL ;Store drive number
CLC
RET
DISK_SEL_ERR1:
MOV DX,OFFSET HELP9 ;illegal disk has been selected.
STC
RET
DISK_SELECT ENDP
;-----------------------------------------------------------------------------
;Expanded memory select
;-----------------------------------------------------------------------------
EXPANDED_MEM PROC NEAR
;Test for the EMS driver.
PUSH ES
PUSH DI
MOV AX,3567H ;Get EMS vector
INT 21H
MOV DI,0AH ;Using the segment from the 67h
MOV SI,OFFSET EMS_HEADER ; vector, look at offset 0ah.
MOV CX,8 ; Compare the next 8 bytes with
CLD ; the expected ems header. If
REPE CMPSB ; they are the same, allow ems
POP DI ; option, else, print error msg.
POP ES ;Remember, poping registers does
JNE EMS_NOT_THERE ; not change the flags
;Set ems indicator.
INC EMS_FLAG ;indicate EMS option
CLC
RET ;check for more commands
EMS_NOT_THERE:
MOV DX,OFFSET HELP7 ;display error message and exit
STC
RET
EXPANDED_MEM ENDP
;-----------------------------------------------------------------------------
;Determine the size of the cache.
;-----------------------------------------------------------------------------
CACHE_SIZE PROC NEAR
MOV AX,2[DI] ;get the number after the /m
MOV SI,OFFSET MEM_SIZE_TBL
MOV CX,2
CACHE_SIZE_LOOP1:
CMP AX,[SI] ;Search the size table to find a
JE SIZE_FOUND ; match for the size on the
INC CX ; command line.
ADD SI,2
CMP SI,OFFSET MEM_SIZE_TBL_END
JBE CACHE_SIZE_LOOP1
MOV DX,OFFSET HELP1 ;if size unrecognised, display err
STC
RET
SIZE_FOUND:
XOR BX,BX ;clear register for mask gen.
CACHE_SIZE_LOOP2:
STC ;shift 1's into the low bit of bx
RCL BX,1 ;continue to shift 1's until the
LOOP CACHE_SIZE_LOOP2 ; count id exausted.
SAL BX,1
MOV ADDR_MASK,BX
CLC
RET
CACHE_SIZE ENDP
;-----------------------------------------------------------------------------
;Enable or disable the cache
;-----------------------------------------------------------------------------
CACHE_ON_OFF PROC NEAR
MOV AL,2[DI] ;Get next letter in command line
CMP AL,5AH ;Convert uppercase to lower
JA ON_OFF_SKIP ; case if needed.
ADD AL,20H
ON_OFF_SKIP:
XOR CX,CX
PUSH ES
MOV ES,OTHER_SEG ;Get segment of copy (if any)
ASSUME ES:NOTHING
CMP AL,'f' ;check second letter for on or off
JE CACHE_OFF1
INC CX
CMP AL,'n'
JNE CACHE_ON_OFF_ERR
CACHE_ON1:
CMP ALRDY_IN_MEM,CH ;If initial instalation, don't
JE CACHE_OFF1 ; clear the lookup table here.
CALL RESET_CACHE
CACHE_OFF1:
MOV ES:ENABLED,CL ;Set flag to enable cache
POP ES
CLC
RET
CACHE_ON_OFF_ERR:
POP ES
MOV DX,OFFSET HELP3 ;indicate an illegal command
STC
RET
CACHE_ON_OFF ENDP
;-----------------------------------------------------------------------------
; UNINSTALL deallocates the memory block addressed by ES and restores the
; interrupt 13 vector displaced on installation.
; Exit: CF clear - program uninstalled
; CF set - can't uninstall
;-----------------------------------------------------------------------------
UNINSTALL PROC NEAR
ASSUME DS:CODE
PUSH ES
MOV AX,3513H ;Get int 13 vector
INT 21H
MOV AX,ES ;Compare vector segment with
CMP AX,OTHER_SEG ; segment of installed code.
JNE REMOVE_ERR ;If not the same, can't remove.
;-----------------------------------------------------------------------------
;Release the memory occupied by the program. ES already has proper segment.
;-----------------------------------------------------------------------------
CMP ES:EMS_FLAG,0 ;See if EMS memory or conventional
JE REMOVE_SKIP1
MOV DX,ES:EMS_HANDLE ;If EMS memory, deallocate using
MOV AH,45H ; function 6.
INT 67H
OR AH,AH
JNE REMOVE_ERR
REMOVE_SKIP1:
MOV AH,49H ;DOS free memory function
INT 21H
JC REMOVE_ERR ;If carry, error on removal
;-----------------------------------------------------------------------------
;Restore interrupt 13h vector.
;-----------------------------------------------------------------------------
PUSH DS
LDS DX,ES:[OLD_DISK_INT] ;Get old vector from installed
MOV AX,2513H ; code.
INT 21H ;Set int 13 to old vector.
POP DS
JC REMOVE_ERR ;If error, report and exit.
;-----------------------------------------------------------------------------
;Destroy the ASCII fingerprint that identifies the code and exit.
;-----------------------------------------------------------------------------
NOT WORD PTR ES:[ENTRY]
CLC ;Clear error flag
REMOVE_EXIT:
POP ES
RET
;-----------------------------------------------------------------------------
;The program can't be uninstalled. Set CF and exit.
;-----------------------------------------------------------------------------
REMOVE_ERR:
MOV DX,OFFSET HELP10 ;Point to error message.
STC ;Set error flag
JMP SHORT REMOVE_EXIT
UNINSTALL ENDP
MAIN ENDP
END_OF_PROG = $
CODE ENDS
END ENTRY