home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Simtel MSDOS - Coast to Coast
/
simteldosarchivecoasttocoast.iso
/
pcmag
/
vol8n01.zip
/
BCOPY.ASM
next >
Wrap
Assembly Source File
|
1989-01-17
|
50KB
|
1,226 lines
;=============================================================================
; BCOPY 1.0 Background copy utility
;=============================================================================
CODE SEGMENT PARA PUBLIC 'CODE'
ASSUME CS:CODE
ORG 80H
COMMAND_TAIL DB ?
ORG 100H
BEGIN: JMP INITIALIZE
PROGRAM DB "BCOPY 1.0 (c) 1989 Ziff Communications Co.",13,10
DB "PC Magazine ",254," Douglas Boling",13,10
DB "Usage: BCOPY [source [target]][/X][/U]$",26
;-----------------------------------------------------------------------------
; Memory locations required for system overhead.
;-----------------------------------------------------------------------------
INDOS DD 0 ;pointer to INDOS flag
CEF_PTR DD 0 ;pointer to Critical err flag
DOS_VERSION DW 0 ;DOS version number
COUNTER DB 16 ;request flag/timer
DISKFLAG DB 0 ;disk access flag
ACTIVE DB 0 ;background status flag
REMOVE_FLAG DB 0 ;1 = uninstall when q empty
RET_ADDR DW 0 ;saved return addr for calls
SOURCE_HNDL DW 0 ;Source file handle
DEST_HNDL DW 0 ;Destination handle
EMS_FLAG DB 0 ;Use expanded memory
EMS_HANDLE DW 0 ;EMS handle used
DATA_SEGMENT DW 0 ;segment of data buffer
QUEUE_HEAD_PTR DW 0 ;pointer to first file in q
FILE_COUNT DB 0 ;Number of files in queue
DATA_BUFF_START DW OFFSET DATA_BUFFER ;pointer to start of buffer
DATA_BUFF_END DW OFFSET END_OF_DATA ;pointer to end of data buffer
INT8H DD 0 ;int 8h vector (Timer)
INT13H DD 0 ;int 13h vector (Disk)
INT28H DD 0 ;int 28h vector (Idle)
SAVED_DTA DD 0 ;saved pointer to curr DTA
SAVED_PSP DW 0 ;saved segment of curr PSP
SS_REGISTER DW 0 ;SS register
SP_REGISTER DW 0 ;SP register
ERRINFOARRAY DW 6 DUP (0) ;Saved extended error info
ERRINFODS DW 0
ERRINFOES DW 0
DW 3 DUP (0) ;Reserved error table bytes
VECTOR1BH DD 0 ;int 1Bh vector (Break)
VECTOR23H DD 0 ;int 23h vector (Ctrl-C)
VECTOR24H DD 0 ;int 24h vector (Crit err)
;=============================================================================
; TIMERINT receives control when an interrupt 8 is generated.
;=============================================================================
TIMERINT PROC FAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
PUSHF ;call BIOS routine
CALL INT8H
CLI ;make sure interrupts are off
CMP CS:COUNTER,0 ;exit if timer not expired
JG DECTIME
CMP CS:ACTIVE,0 ;See if already active.
JNE TIMER_EXIT
CMP CS:DISKFLAG,0 ;check disk access status
JNE TIMER_EXIT ;exit if disk active.
PUSH ES
PUSH DI
LES DI,INDOS ;retrieve INDOS address
CMP BYTE PTR ES:[DI],0 ;is the INDOS flag clear?
POP DI
POP ES
JNE TIMER_EXIT
CMP CS:FILE_COUNT,0 ;See if any files in queue
JNE TIMER_CONTINUE
CMP CS:REMOVE_FLAG,0 ;See if routine should be
JE TIMER_EXIT ; removed from memory
CALL REMOVE
JNC TIMER_EXIT ;If no error, exit. If error,
JMP SHORT TIMER_SKIP_MAIN ; wait then try again.
TIMER_CONTINUE:
CALL MAIN ;yes, invoke background routine
TIMER_SKIP_MAIN:
MOV CS:COUNTER,17 ;Set sleep counter = 1 sec
DECTIME:
DEC CS:COUNTER ;decrement wait counter
TIMER_EXIT:
IRET
TIMERINT ENDP
;=============================================================================
; IDLE receives control when an interrupt 28h is generated.
;=============================================================================
IDLE PROC FAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
PUSHF ;call DOS routine
CALL INT28H
CLI ;make sure interrupts are off
CMP CS:FILE_COUNT,0 ;See if files in queue
JE IDLE_EXIT ;If not, exit.
CMP CS:COUNTER,8 ;wait at least 1/2 sec between
JA IDLE_EXIT ; calls.
CMP CS:ACTIVE,0 ;See if already active.
JNE IDLE_EXIT
CMP CS:DISKFLAG,0 ;check disk access status
JNE IDLE_EXIT ;exit if flag is raised
PUSH ES
PUSH DI
LES DI,CS:CEF_PTR ;retrieve crit err flag adr
CMP BYTE PTR ES:[DI],0 ;is DOS in crit error state?
POP DI
POP ES
JNE IDLE_EXIT ;yes, don't do anything
CALL MAIN ;Call background routine.
MOV CS:COUNTER,16 ;Set sleep counter
IDLE_EXIT:
IRET
IDLE ENDP
;=============================================================================
; DISKINT receives control when an interrupt 13h is generated.
;=============================================================================
DISKINT PROC FAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
PUSHF ;save flags register
INC CS:DISKFLAG ;set disk access flag
POPF ;restore flags
PUSHF ;call BIOS routine
CALL INT13H
PUSHF ;save flags again
DEC CS:DISKFLAG ;reset disk access flag
POPF ;restore flags
RET 2 ;exit with flags intact
DISKINT ENDP
;=============================================================================
; CRITICALERR receives control when an interrupt 24h is generated.
;=============================================================================
CRITICALERR PROC FAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
XOR AL,AL ;Default to ignore
CMP CS:DOS_VERSION,30AH ;See if before DOS 3.1
JL CRITICAL1
ADD AL,3
CRITICAL1:
IRET
CRITICALERR ENDP
;=============================================================================
; MAIN
;=============================================================================
MAIN PROC NEAR
ASSUME CS:CODE,DS:NOTHING,ES:NOTHING
INC CS:[ACTIVE] ;set program status flag
CLI ;make sure interrupts are off
MOV CS:SS_REGISTER,SS ;save SS and SP registers
MOV CS:SP_REGISTER,SP
PUSH CS ;switch to internal stack
POP SS
MOV SP,OFFSET STACK_SPACE
STI ;enable interrupts
CALL SAVE_REGS ;save all registers
ASSUME DS:CODE
;-----------------------------------------------------------------------------
;Point the interrupt 1Bh, 23h, and 24h vectors to internal handlers.
;-----------------------------------------------------------------------------
MOV AX,351BH ;get and save 1Bh vector
INT 21H
MOV WORD PTR VECTOR1BH,BX
MOV WORD PTR VECTOR1BH[2],ES
MOV AX,251BH ;point interrupt to IRET
MOV DX,OFFSET IDLE_EXIT
INT 21H
MOV AX,3523H ;get and save 23h vector
INT 21H
MOV WORD PTR VECTOR23H,BX
MOV WORD PTR VECTOR23H[2],ES
MOV AX,2523H ;point interrupt to IRET
MOV DX,OFFSET IDLE_EXIT
INT 21H
MOV AX,3524H ;get and save 24h vector
INT 21H
MOV WORD PTR VECTOR24H,BX
MOV WORD PTR VECTOR24H[2],ES
MOV AX,2524H ;point interrupt to internal
PUSH CS
POP DS
MOV DX,OFFSET CRITICALERR ; critical error handler
INT 21H
;-----------------------------------------------------------------------------
;Save and switch to internal PSP
;-----------------------------------------------------------------------------
MOV AH,51H ;Get current PSP
CALL DOSPSPCALL ;Beware DOS 2.0 - 3.0
MOV SAVED_PSP,BX ;save it
PUSH CS
POP BX
MOV AH,50H ;Set internal PSP
CALL DOSPSPCALL
;-----------------------------------------------------------------------------
;Save and switch to internal DTA
;-----------------------------------------------------------------------------
MOV AH,2FH
INT 21H ;Get current DTA
MOV WORD PTR SAVED_DTA,BX ;save it
MOV WORD PTR SAVED_DTA[2],ES
MOV DX,OFFSET COMMAND_TAIL ;use PSP for DTA
MOV AH,1AH ;Set DTA
INT 21H
;-----------------------------------------------------------------------------
;If DOS >= 3.x, save extended error information.
;-----------------------------------------------------------------------------
CMP WORD PTR DOS_VERSION,030AH
JB SKIP_ERR_SAVE
PUSH DS ;save DS
XOR BX,BX ;clear BX for call
MOV AH,59H ;Extended error info
INT 21H ;Call DOS
MOV CS:ERRINFODS,DS ;save returned ES
POP DS ;Restore DS
PUSH BX
MOV BX,OFFSET ERRINFOARRAY ;Save data in registers
MOV [BX],AX ; in this specific order.
POP 2[BX]
MOV 4[BX],CX
MOV 6[BX],DX
MOV 8[BX],SI
MOV 0AH[BX],DI
MOV 0EH[BX],ES
SKIP_ERR_SAVE:
;-----------------------------------------------------------------------------
;If using EMS memory, save EMS mapping context and map our page.
;-----------------------------------------------------------------------------
CMP EMS_FLAG,0
JE EMS_SAVE_SKIP
MOV AH,47H ;Save mapping context
MOV DX,EMS_HANDLE
INT 67H
OR AH,AH
JNE JMP_CLEAN_UP
MOV AX,4400H ;Map page
XOR BX,BX
MOV DX,EMS_HANDLE
INT 67H
OR AH,AH
JNE JMP_CLEAN_UP
EMS_SAVE_SKIP:
MOV ES,DATA_SEGMENT
MOV DS,DATA_SEGMENT
ASSUME DS:NOTHING
;-----------------------------------------------------------------------------
;Check flags in queue to determine if starting a copy or in the middle of one.
;-----------------------------------------------------------------------------
MOV SI,CS:QUEUE_HEAD_PTR ;Get pointer to filename
MOV AX,[SI+2] ;Get source file flags
OR AH,AH ;See if source file open
JNE OPEN_DEST ;Yes, check destination file
;-----------------------------------------------------------------------------
;Search for source file.
;-----------------------------------------------------------------------------
FIND_SOURCE:
ADD SI,6 ;move pointer to filename
MOV DX,SI ;Copy queue pointer
XOR CX,CX ;Search for normal files.
MOV AH,4EH ;assume find first
OR AL,AL ;See if first search.
JE FIND1ST ;Yes, find first.
INC AH ;No, change cmd to find next.
FIND1ST:
INT 21H ;Call DOS
JNC OPEN_FILE
JMP PURGE_FROM_QUEUE ;If file not found, purge
;-----------------------------------------------------------------------------
;Attempt to open source file.
;-----------------------------------------------------------------------------
OPEN_FILE:
XOR DL,DL ;indicate source file
CALL GETPATHFILE ;combine path and filename
MOV DX,CS:DATA_BUFF_START ;point to filename
MOV AX,3D00H ;open, read only access
INT 21H
JNC GOOD_OPEN
;error in file open.
CMP AX,4 ;See if too many open files.
JNE OPEN1
JMP_CLEAN_UP:
JMP CLEAN_UP ;If so, try again later
OPEN1:
JMP PURGE_FROM_QUEUE ;Else, bad filename.
GOOD_OPEN:
MOV SOURCE_HNDL,AX ;Save handle for source file
MOV SI,CS:QUEUE_HEAD_PTR ;Get queue ptr, indicate that
MOV WORD PTR [SI+2],0101H ; 1st file opened.
;-----------------------------------------------------------------------------
;Create destination file.
; Note: open dest assumes SI points to the first entry in the queue.
;-----------------------------------------------------------------------------
OPEN_DEST:
MOV AX,[SI+4] ;Get destination file flags
OR AL,AL ;See if destination file open
JNE READ_FILE ;Dest file open, copy data.
CALL GET_DEST_NAME ;Gen filename from queue
MOV AH,3CH ;create destination file
XOR CX,CX ;normal attributes
INT 21H
JNC GOOD_CREATE_DEST
OPEN_DEST_ERR:
CMP AX,4 ;See if too many files
JE JMP_CLEAN_UP ;If so, wait till later
JMP SHORT PURGE_FROM_QUEUE ;If other error, purge file
GOOD_CREATE_DEST:
MOV CS:DEST_HNDL,AX ;Save destination handle
MOV SI,CS:QUEUE_HEAD_PTR ;Get pointer to filename
MOV BYTE PTR [SI+4],1 ;Set destination file open
;-----------------------------------------------------------------------------
;Files are open, read from destination file into data buffer.
;-----------------------------------------------------------------------------
READ_FILE:
MOV CX,CS:DATA_BUFF_END ;Find end of buffer
SUB CX,CS:DATA_BUFF_START ;Get size of buffer
SUB CX,4
MOV BX,CS:SOURCE_HNDL ;Get handle
MOV DX,CS:DATA_BUFF_START ;Point to data buffer
MOV AH,3FH ;Read file
INT 21H ;Call DOS
JNC WRITE_FILE ;If no error, continue
MOV DI,1 ;If error, close files,
JMP SHORT CLOSE_FILES ; erase dest, and purge.
;-----------------------------------------------------------------------------
;Write data to file.
;-----------------------------------------------------------------------------
WRITE_FILE:
MOV SI,CX ;Save num of bytes requested
MOV CX,AX ;Write number of bytes read.
MOV AH,40H ;Write file
MOV BX,CS:DEST_HNDL ;To destination
INT 21H ;Call DOS
JC WRITE_BAD
XOR DI,DI ;Use DI as disk full flag
CMP AX,CX ;Make sure all bytes written
JE CHECK_FOR_EOF ;If not, disk full.
WRITE_BAD:
INC DI ;set flag to delete file
JMP SHORT CLOSE_FILES
;-----------------------------------------------------------------------------
;If copy complete, close files
;-----------------------------------------------------------------------------
CHECK_FOR_EOF:
CMP SI,AX ;see if at end of file.
JE CLEAN_UP ;No, skip close
CLOSE_FILES:
MOV SI,CS:QUEUE_HEAD_PTR ;Get queue ptr, indicate that
MOV WORD PTR [SI+3],0 ;Indicate files closed.
MOV BX,CS:SOURCE_HNDL
MOV AH,3EH ;Close source file
INT 21H
MOV BX,CS:DEST_HNDL
MOV AH,3EH ;Close destination file
INT 21H
OR DI,DI ;See if error during write.
JE SHORT CLEAN_UP ; If so, delete and purge.
CALL GET_DEST_NAME ;Gen dest file name again
MOV AH,41H ;Delete partial dest file
INT 21H ; (DX still points to name.)
;-----------------------------------------------------------------------------
;Purge file name from queue.
;-----------------------------------------------------------------------------
PURGE_FROM_QUEUE:
MOV DI,CS:QUEUE_HEAD_PTR ;Get queue pointer
MOV SI,DS:[DI] ;Get pointer to next file
PURGE_FILE_LOOP:
CMP WORD PTR DS:[SI],0FFFFH ;See if good file
JE PURGE_DONE
MOV CX,DS:[SI] ;Compute length of entry
SUB CX,SI
MOV BX,DI ;save pointer to entry
REP MOVSB ;Copy queue entry
MOV DS:[BX],DI ;Update pointer
JMP PURGE_FILE_LOOP
PURGE_DONE:
MOV WORD PTR DS:[DI],0FFFFH ;copy end pointer
INC DI
INC DI
MOV CS:DATA_BUFF_START,DI ;Update start of data buffer.
DEC CS:FILE_COUNT
;-----------------------------------------------------------------------------
;Clean up DOS for return to forground task. Start with extended error info.
;-----------------------------------------------------------------------------
CLEAN_UP:
PUSH CS
POP DS
ASSUME DS:CODE
CMP WORD PTR DOS_VERSION,30AH
JB SKIP_ERR_RESTORE
MOV AX,5D0AH ;Restore ext error info
MOV DX,OFFSET ERRINFOARRAY ;point to saved info
INT 21H
SKIP_ERR_RESTORE:
;-----------------------------------------------------------------------------
;If using EMS memory, restore EMS mapping context.
;-----------------------------------------------------------------------------
CMP EMS_FLAG,0
JE EMS_RESTORE_SKIP
MOV AH,48H ;Restore mapping context
MOV DX,EMS_HANDLE
INT 67H
EMS_RESTORE_SKIP:
;-----------------------------------------------------------------------------
;Restore PSP and DTA
;-----------------------------------------------------------------------------
MOV BX,SAVED_PSP ;save it
MOV AH,50H ;Set PSP
CALL DOSPSPCALL
PUSH ES
LES DX,[SAVED_DTA]
MOV AH,1AH ;Set DTA
INT 21H
POP ES
;-----------------------------------------------------------------------------
;Reset the displaced interrupt 1Bh, 23h, and 24h vectors.
;-----------------------------------------------------------------------------
PUSH DS
MOV AX,2524H ;reset int 24h vector
LDS DX,CS:[VECTOR24H]
INT 21H
MOV AX,2523H ;reset int 24h vector
LDS DX,CS:[VECTOR23H]
INT 21H
MOV AX,251BH ;reset int 1Bh vector
LDS DX,CS:[VECTOR1BH]
INT 21H
POP DS
;-----------------------------------------------------------------------------
;Restore register values, switch back to original stack, and return to caller.
;-----------------------------------------------------------------------------
MAIN_EXIT:
CALL RESTORE_REGS ;Restore registers
ASSUME DS:NOTHING
CLI ;make sure interrupts are off
MOV SS,CS:SS_REGISTER ;switch to original stack
MOV SP,CS:SP_REGISTER
STI ;interrupts on
DEC CS:[ACTIVE] ;clear program status flag
RET ;Return to interrupt routine
MAIN ENDP
;-----------------------------------------------------------------------------
; GETPATHFILE copies the path from the queue and appends the filename from the
; DTA assumed to be at offset 80h.
; Entry: ES:SI - ASCIIZ path (can include filename.)
; DL - 0 = Source file, always append filename from DTA.
; 1 = Destination file, append filename only if path specified.
; Exit: CF clear - file opened.
; CF set - error on file open.
;-----------------------------------------------------------------------------
GETPATHFILE PROC NEAR
ASSUME CS:CODE
PUSH AX
MOV CX,75 ;Max length of string
MOV DI,CS:DATA_BUFF_START ;Copy name to data buffer
GETPATHFILE0:
LODSB ;Get a byte
STOSB ;Store a byte
OR AL,AL ;are we at the end?
JNE GETPATHFILE0 ;No, loop back
OR DL,DL ;See if source or dest file
JE GETPATHFILE1
CMP BYTE PTR ES:[DI-2],"\" ;Is the a path specification?
JNE GETPATHFILE_EXIT ;No, don't append src filename
GETPATHFILE1:
STD ;scan backwards
MOV CX,15 ;Find last \ in filename
MOV AL,"\"
DEC DI ;Back up before 0
REPNE SCASB
CLD
INC DI ;move DI past \
INC DI
PUSH DS
PUSH CS
POP DS
MOV SI,OFFSET COMMAND_TAIL+1EH
MOV CX,13 ;copy filename found
REP MOVSB
POP DS
GETPATHFILE_EXIT:
POP AX
RET
GETPATHFILE ENDP
;-----------------------------------------------------------------------------
; GET DEST NAME creates the destination file name from the queue.
; Exit: DX - points to fully specified destination filename.
;-----------------------------------------------------------------------------
GET_DEST_NAME PROC NEAR
ASSUME CS:CODE
MOV DI,CS:QUEUE_HEAD_PTR ;Get pointer to filename
ADD DI,6 ;point to file names
XOR AL,AL ;search for end of 1st name
MOV CX,75
REPNE SCASB
MOV SI,DI ;copy pointer
MOV DL,1 ;indicate destination file
CALL GETPATHFILE
MOV DX,CS:DATA_BUFF_START ;point to filename
RET
GET_DEST_NAME ENDP
;-----------------------------------------------------------------------------
; DOSPSPCALL modifies critical error flag on PSP calls to DOS is using 2.x
;-----------------------------------------------------------------------------
DOSPSPCALL PROC NEAR
ASSUME CS:CODE
CMP WORD PTR CS:[DOS_VERSION],30AH ;See if DOS < 3.1
JAE DOSPSPCALL_OK ;no, just call DOS
PUSH DS
PUSH DI
LDS DI,CS:CEF_PTR ;retrieve crit err flag adr
INC BYTE PTR [DI] ;Set DOS in crit error state
POP DI
POP DS
INT 21H ;Call DOS
PUSH DS
PUSH DI
LDS DI,CS:CEF_PTR ;retrieve crit err flag adr
DEC BYTE PTR [DI] ;Set DOS in crit error state
POP DI
POP DS
RET
DOSPSPCALL_OK:
INT 21H ;Call DOS
RET
DOSPSPCALL ENDP
;-----------------------------------------------------------------------------
; SAVEREGS saves all the registers used in the interrupt routines and sets DS.
;-----------------------------------------------------------------------------
SAVE_REGS PROC NEAR
POP CS:[RET_ADDR] ;Get address to return to
PUSH AX ;save all registers
PUSH BX
PUSH CX
PUSH DX
PUSH BP
PUSH SI
PUSH DI
PUSH DS
PUSH ES
PUSH CS ;Set DS = CS
POP DS
ASSUME DS:CODE
JMP WORD PTR [RET_ADDR] ;Return
SAVE_REGS ENDP
;-----------------------------------------------------------------------------
;RESTOREREGS restores register values.
;-----------------------------------------------------------------------------
RESTORE_REGS PROC NEAR
POP RET_ADDR ;Save return address
POP ES ;restore registers
POP DS
ASSUME DS:NOTHING
POP DI
POP SI
POP BP
POP DX
POP CX
POP BX
POP AX
JMP WORD PTR CS:[RET_ADDR] ;Return
RESTORE_REGS ENDP
;-----------------------------------------------------------------------------
; REMOVE deallocates the memory block addressed by ES and restores the
; interrupt vectors displaced on installation.
; Entry: ES - segment to release
; Exit: CF clear - program uninstalled
; CF set - can't uninstall
;-----------------------------------------------------------------------------
REMOVE PROC NEAR
ASSUME CS:CODE
INC CS:ACTIVE
CALL SAVE_REGS ;Save registers
ASSUME DS:CODE
;
;Make sure none of the vectors has been altered.
;
MOV AL,8 ;check interrupt 8 vector
CALL CHECKVECTOR
JNE REMOVE_ERROR
MOV AL,13H ;check interrupt 13h vector
CALL CHECKVECTOR
JNE REMOVE_ERROR
MOV AL,28H ;check interrupt 28h vector
CALL CHECKVECTOR
JNE REMOVE_ERROR
;
;If using EMS memory, release it.
;
CMP EMS_FLAG,0
JE SKIP_REMOVE_EMS
MOV AH,45H ;Deallocate pages
MOV DX,EMS_HANDLE
INT 67H
OR AH,AH
JNE REMOVE_ERROR
SKIP_REMOVE_EMS:
;
;Release the memory occupied by the program.
;
PUSH CS
POP ES
MOV AH,49H ;free memory given to
INT 21H ; original program block
JC REMOVE_ERROR ;branch on error
;
;Restore the interrupt 8, 13h, and 28h vectors.
;
PUSH DS ;save DS
ASSUME DS:NOTHING
MOV AX,2508H ;restore interrupt 8 vector
LDS DX,ES:[INT8H]
INT 21H
MOV AX,2513H ;restore interrupt 13h vector
LDS DX,ES:[INT13H]
INT 21H
MOV AX,2528H ;restore interrupt 28h vector
LDS DX,ES:[INT28H]
INT 21H
POP DS ;restore DS
ASSUME DS:CODE
;
;Destroy the ASCII fingerprint that identifies the code and exit.
;
NOT WORD PTR [BEGIN] ;destroy fingerprint
CLC ;clear CF for exit
REMOVE_EXIT:
DEC ACTIVE
CALL RESTORE_REGS
RET ;exit with CF intact
;
;The program can't be uninstalled. Set CF and exit.
;
REMOVE_ERROR: STC
JMP REMOVE_EXIT
REMOVE ENDP
;-----------------------------------------------------------------------------
; CHECKVECTOR is called by REMOVE to compare the segment pointed to by an
; interrupt vector against a segment value supplied by the caller.
; Entry: AL - interrupt number
; Exit: ZF clear - segments do not match
; ZF set - segments match
;-----------------------------------------------------------------------------
CHECKVECTOR PROC NEAR
PUSH CS
POP CX
MOV AH,35H ;get vector
INT 21H
MOV AX,ES ;transfer segment to AX
CMP AX,CX ;compare
RET
CHECKVECTOR ENDP
;-----------------------------------------------------------------------------
; FINALINSTALL is called to setup the data queue and to TSR.
;-----------------------------------------------------------------------------
FINALINSTALL PROC NEAR
ASSUME CS:CODE,DS:CODE,ES:CODE
MOV DI,[QUEUE_HEAD_PTR]
MOV ES,DATA_SEGMENT
MOV SI,OFFSET END_OF_CODE ;point to filenames
CALL PUTINQUEUE ;Load files in queue
MOV DATA_BUFF_START,DI ;Set start of data buffer
INC FILE_COUNT ;Inc file count
;
;Terminate and remain resident in memory.
;
DEC ACTIVE ;allow background task
MOV AX,3100H ;terminate with ERRORLEVEL = 0
MOV DX,(OFFSET END_OF_DATA-OFFSET CODE+15) SHR 4
CMP EMS_FLAG,0
JE FINAL_INSTALL1
MOV DX,(OFFSET DATA_BUFFER-OFFSET CODE+15) SHR 4
FINAL_INSTALL1:
INT 21H
FINALINSTALL ENDP
;-----------------------------------------------------------------------------
; PUTINQUEUE is called copy the fully qualified filenames into the queue.
; Entry: ES:DI - Points to open entry in queue.
; DS:SI - Points to entry to put in queue.
;-----------------------------------------------------------------------------
PUTINQUEUE PROC NEAR
ASSUME CS:CODE,DS:CODE
MOV BX,DI ;save pointer
MOV DX,2 ;move two asciiz strings
ADD DI,DX ;move past pointer
XOR AX,AX
STOSW ;initialize file flags
STOSW
COPY_LOOP1:
LODSB ;Copy filename
STOSB
CMP AL,0
JNE COPY_LOOP1
DEC DL ;decriment name counter
JNE COPY_LOOP1
MOV ES:[BX],DI ;point to next available
MOV WORD PTR ES:[DI],0FFFFH ; space in queue
INC DI
INC DI
RET
PUTINQUEUE ENDP
;=============================================================================
; Buffer space to be used once the program is resident.
;=============================================================================
PC = $
PC = PC + 256
STACK_SPACE = PC ;stack for resident routine
DATA_BUFFER = PC ;Buffer for data
PC = PC + 4096
END_OF_DATA = PC
;=============================================================================
; INITIALIZE
;=============================================================================
ERRMSG1 DB "Source file not found$"
ERRMSG2 DB "Bad target path$"
ERRMSG3 DB "Can't install$"
ERRMSG4 DB "Dup. file names$"
ERRMSG5 DB "Bad Switch$"
ERRMSG6 DB "(Already installed)$"
ERRMSG7 DB "EMS driver error$"
ERRMSG8 DB "Deinstall queued$"
OTHER_SEG DW 0 ;Segment of installed code
ALRDY_INSTALLED DB 0 ;bcopy already installed flag
DEF_DISK DB ? ;Default disk drive
EMS_HEADER DB "EMMXXXX0" ;EMS driver header
INITIALIZE PROC NEAR
ASSUME CS:CODE, DS:CODE
MOV DX,OFFSET PROGRAM
CALL MESSAGE
CLD ;clear DF
;-----------------------------------------------------------------------------
;Get DOS version.
;-----------------------------------------------------------------------------
MOV AH,30H ;Get DOS version
INT 21H
XCHG AL,AH ;Put version in proper order
MOV DOS_VERSION,AX ;Save DOS version
;-----------------------------------------------------------------------------
;Get default disk drive.
;-----------------------------------------------------------------------------
MOV AH,19H ;Get default disk
INT 21H
INC AL
MOV DEF_DISK,AL
;-----------------------------------------------------------------------------
;See if a copy is already resident in memory. If no copy, install.
;-----------------------------------------------------------------------------
NOT WORD PTR [BEGIN] ;initialize fingerprint
MOV BX,600H ;zero BX for start
MOV AX,CS ;keep CS value in AX
FIND_COPY:
INC BX ;increment search segment value
MOV ES,BX
CMP AX,BX ;not installed if current
JE FIND_COPY1 ; segment is looped back to
MOV SI,OFFSET BEGIN ;search this segment for ASCII
MOV DI,SI ; fingerprint
MOV CX,16
REPE CMPSB
JNE FIND_COPY ;loop back if not found
INC ALRDY_INSTALLED ;Clear installed flag
MOV DX,OFFSET ERRMSG6
CALL MESSAGE
FIND_COPY1:
INC ES:[ACTIVE] ;Don't let background active
MOV OTHER_SEG,ES ;save installed code segment
PUSH CS
POP ES
;-----------------------------------------------------------------------------
;Parse the command line for remove switch.
;-----------------------------------------------------------------------------
MOV DI,OFFSET COMMAND_TAIL ;Point SI to command line text
MOV CL,[DI] ;Get length of command line.
OR CL,CL
JNZ SWITCHES
JMP TERMINATE
SWITCHES:
XOR CH,CH
INC DI
PUSH CX ;Save pointer for later use.
PUSH DI
SWITCHES1:
MOV AL,"/" ;Put switch in AL
REPNE SCASB ;Scan for cmd line switches
JNE PARSE
MOV AH,[DI]
AND AH,0DFH ;Convert to caps
CMP AH,"U" ;See if uninstall switch
JE SWITCHES2
CMP AH,"X" ;See if expanded memory switch
JE SWITCHES3
MOV DX,OFFSET ERRMSG5 ;Illegal switch
ADD SP,4 ;Clean up stack
JMP DISP_ERROR
SWITCHES2:
PUSH ES
MOV ES,OTHER_SEG
INC ES:[REMOVE_FLAG] ;Set uninstall flag
POP ES
MOV DX,OFFSET ERRMSG8
CALL MESSAGE
JMP SWITCHES1
SWITCHES3:
CMP ALRDY_INSTALLED,0
JE SWITCHES4
MOV DX,OFFSET ERRMSG5
CALL MESSAGE
JMP SWITCHES1
SWITCHES4:
INC EMS_FLAG ;Set expanded memory flag
JMP SWITCHES1
;-----------------------------------------------------------------------------
;Parse the command line and create a complete filespec.
;-----------------------------------------------------------------------------
PARSE: POP SI ;Get back pointer to cmd line
POP CX
MOV DI,OFFSET END_OF_CODE ;save fully specified name
CALL PARSE_FILENAME ; in a safe place.
PUSH DI ;save 2nd file pointer
DEC SI
CALL PARSE_FILENAME ;process 2nd filename
POP SI
;-----------------------------------------------------------------------------
;Verify that source file exists.
;-----------------------------------------------------------------------------
MOV DX,OFFSET END_OF_CODE ;point to source filename
MOV CX,00 ;normal file search
MOV AH,4EH ;Find first
INT 21H
MOV DX,SI ;get 2nd file pointer
JNC VERIFY_DEST
MOV DX,OFFSET ERRMSG1 ;File not found
JMP DISP_ERROR ;Print error msg and terminate
;-----------------------------------------------------------------------------
;Determine if the destination specification is a path or a complete filename.
;See if path by setting default path to destination.
;-----------------------------------------------------------------------------
VERIFY_DEST: PUSH DX
MOV DX,[SI] ;Get destination disk
MOV SI,OFFSET END_OF_CODE + 300
MOV [SI],DX ;Save current path in
MOV BYTE PTR [SI+2],"\" ; safe place.
ADD SI,3
SUB DL,40H ;Convert to hex
MOV AH,47H ;Get current directory
INT 21H
POP DX
JC VERIFY_ERROR
MOV AH,3BH ;Set path to destination
INT 21H
JC VERIFY1
MOV DX,SI ;Point DX to saved path
SUB DX,3
MOV AH,3BH ;Restore path
INT 21H
CMP BYTE PTR [DI-2],"\"
JE VERIFY_DONE
MOV WORD PTR [DI-1],005CH ;Append \ to indicate path
JMP SHORT VERIFY_DONE
;-----------------------------------------------------------------------------
;Try failed, search for file.
;-----------------------------------------------------------------------------
VERIFY1: MOV CX,0 ;Normal search
MOV AH,4EH ;Find first
INT 21H
JNC VERIFY_DONE ;file found, were done.
CMP AX,3 ;check for bad path
JNE VERIFY_DONE ;path found, must be file
VERIFY_ERROR:
MOV DX,OFFSET ERRMSG2 ;bad path, print path
JMP SHORT DISP_ERROR ; not found.
VERIFY_DONE:
;-----------------------------------------------------------------------------
;Check to see if the filenames are the same.
;-----------------------------------------------------------------------------
MOV SI,OFFSET END_OF_CODE
MOV DI,DX
MOV CX,DX ;Compute length of name
SUB CX,SI
REPE CMPSB ;compare strings
JE SAME_NAMES
MOV AX,005CH
CMP [DI-2],AX ;See if dest is path
JNE COMPARE_NAMES1
MOV DI,SI ;Scan source for \. If not
REPNE SCASB ; found, src and dest are
JE COMPARE_NAMES1 ; in the same directory.
SAME_NAMES:
MOV DX,OFFSET ERRMSG4 ;Same, print error message
JMP SHORT DISP_ERROR
COMPARE_NAMES1:
CMP ALRDY_INSTALLED,0 ;see if bcopy installed
JE INSTALL
;-----------------------------------------------------------------------------
;Add new file names to installed code's queue and terminate.
;-----------------------------------------------------------------------------
LOAD_FILES:
MOV SI,OFFSET END_OF_CODE ;point to file names
PUSH DS
MOV DS,OTHER_SEG ;point ES to installed code
ASSUME DS:NOTHING
LOAD_QUEUE1:
CMP DS:[ACTIVE],1 ;Wait till background not
JNE LOAD_QUEUE1 ; active.
MOV DI,DS:[QUEUE_HEAD_PTR] ;Get start of queue.
MOV ES,DS:[DATA_SEGMENT]
LOAD_QUEUE2:
MOV AX,0FFFFH
CMP ES:[DI],AX ;Is queue empty?
JE LOAD_QUEUE3 ;yes, continue
MOV DI,ES:[DI] ;Get pointer to next file
JMP LOAD_QUEUE2
LOAD_QUEUE3:
POP DS ;restore DS
ASSUME DS:CODE
CALL PUTINQUEUE ;copy filenames into queue
MOV ES,OTHER_SEG
MOV ES:[DATA_BUFF_START],DI
INC ES:FILE_COUNT
;-----------------------------------------------------------------------------
;Enable background task and terminate.
;-----------------------------------------------------------------------------
TERMINATE:
DEC ES:[ACTIVE] ;enable background task.
MOV AX,4C00H ;Terminate with RC = 0.
INT 21H
;=============================================================================
;Display error message and exit with Return Code = 1.
;=============================================================================
DISP_ERROR: CALL MESSAGE
MOV ES,OTHER_SEG ;point ES to installed code
DEC ES:[ACTIVE] ;enable background task.
MOV AX,4C01H ;Exit RC = 1
INT 21H
;=============================================================================
;Install. Get address of INDOS flag.
;=============================================================================
INSTALL:
MOV AH,34H ;get address from DOS
INT 21H
MOV WORD PTR INDOS,BX ;store it
MOV WORD PTR INDOS[2],ES
;-----------------------------------------------------------------------------
;Find and save the address of the DOS critical error flag.
;-----------------------------------------------------------------------------
MOV AX,3E80H ;CMP opcode
MOV CX,2000H ;max search length
MOV DI,BX ;start at INDOS address
CEFS1: REPNE SCASW ;do the search
JCXZ CEFS2 ;branch if search failed
CMP BYTE PTR ES:[DI+5],0BCH ;verify this is it
JE CEFSFOUND ;branch if it is
JMP CEFS1 ;resume loop if it's not
CEFS2: MOV CX,2000H ;search again
INC BX ;search odd addresses this time
MOV DI,BX
CEFS3: REPNE SCASW ;look for the opcode
JCXZ CEFSNOTFOUND ;not found if loop expires
CMP BYTE PTR ES:[DI+5],0BCH ;verify this is it
JE CEFSFOUND
JMP CEFS3
CEFSNOTFOUND:
MOV DX,OFFSET ERRMSG3 ;Critical error flag not found
JMP SHORT DISP_ERROR
CEFSFOUND: MOV AX,ES:[DI] ;get flag offset address
MOV WORD PTR CEF_PTR,AX ;store it
MOV WORD PTR CEF_PTR[2],ES
;-----------------------------------------------------------------------------
;Set up EMS memory if necessary.
;-----------------------------------------------------------------------------
PUSH CS
POP DATA_SEGMENT ;assume no ems memory
CMP EMS_FLAG,0
JE SKIP_EMS_SETUP
;Test for the EMS driver.
PUSH ES ;Test for ems driver
PUSH DI
MOV AX,3567H ;Get EMS vector
INT 21H
MOV DI,0AH ;Using the segment from the
MOV SI,OFFSET EMS_HEADER ; 67h vector, look at offset
MOV CX,8 ; 0ah. Compare the next 8
CLD ; bytes with the expected
REPE CMPSB ; EMS header. If they are
POP DI ; the same, EMS driver
POP ES ; found.
JE EMS_FOUND
EMS_ERROR:
MOV DX,OFFSET ERRMSG7 ;EMS driver error
JMP DISP_ERROR
EMS_FOUND:
STC
MOV AH,40H ;Check status
INT 67H
OR AH,AH
JNE EMS_ERROR
MOV AH,41H ;Get page frame segment
INT 67H
OR AH,AH
JNE EMS_ERROR
MOV DATA_SEGMENT,BX ;Save seg of EMS page frame
MOV AH,43H ;Get page frame segment
MOV BX,1 ;request 1 page
INT 67H
OR AH,AH
JNE EMS_ERROR
MOV EMS_HANDLE,DX ;Save EMS handle
MOV AX,4400H ;Map page
XOR BX,BX ;map page 1
MOV DX,EMS_HANDLE ;identify user
INT 67H
OR AH,AH
JNE EMS_ERROR
MOV DATA_BUFF_END,4096 ;set buffer parameters
MOV DATA_BUFF_START,0
SKIP_EMS_SETUP:
;-----------------------------------------------------------------------------
;Initialize pointers needed for queue.
;-----------------------------------------------------------------------------
MOV BX,DATA_BUFF_START ;initialize queue
MOV QUEUE_HEAD_PTR,BX
;-----------------------------------------------------------------------------
;Set interrupt 8h, 13h, and 28h vectors to internal handlers.
;-----------------------------------------------------------------------------
MOV AX,3508H ;interrupt 8
INT 21H
MOV WORD PTR INT8H,BX
MOV WORD PTR INT8H[2],ES
MOV AX,2508H
MOV DX,OFFSET TIMERINT
INT 21H
MOV AX,3513H ;interrupt 13h
INT 21H
MOV WORD PTR INT13H,BX
MOV WORD PTR INT13H[2],ES
MOV AX,2513H
MOV DX,OFFSET DISKINT
INT 21H
MOV AX,3528H ;interrupt 28h
INT 21H
MOV WORD PTR INT28H,BX
MOV WORD PTR INT28H[2],ES
MOV AX,2528H
MOV DX,OFFSET IDLE
INT 21H
;-----------------------------------------------------------------------------
;Deallocate the program's environment block.
;-----------------------------------------------------------------------------
MOV AX,DS:[2CH] ;get environment segment
MOV ES,AX
MOV AH,49H ;free it
;;; INT 21H
PUSH CS ;reset ES to the code segment
POP ES
JMP FINALINSTALL ;Jump to code above data area
INITIALIZE ENDP
;======================================================================
; Send message to screen
;----------------------------------------------------------------------
CRLF$ DB 13,10,"$"
MESSAGE PROC NEAR
ASSUME CS:CODE,DS:CODE
MOV AH,9
INT 21H
MOV DX,OFFSET CRLF$
MOV AH,9
INT 21H
RET
MESSAGE ENDP
;======================================================================
; PARSE_FILENAME creates a proper pathname for a filename
; Entry: SI - pointer to asciiz filename
; DI - pointer to buffer to hold resulting pathname
;-----------------------------------------------------------------------------
PARSE_FILENAME PROC NEAR
ASSUME CS:CODE,DS:CODE,ES:CODE
PARSE0:
CALL SCANFORSEP ;Scan till character found
LAHF ;Save return flags
CMP AL,0DH ;See if carrage return or
JE PARSE01 ; command switch.
CMP AL,"/"
JE PARSE01
SAHF
JC PARSE0
JMP SHORT PARSE02
PARSE01:
MOV WORD PTR [SI-1],0 ;If so, fake a null file name
PARSE02:
;Look for disk specification
DEC SI ;backup to before 1st char
CMP BYTE PTR 1[SI],":" ;see if disk specified
JE PARSE1
MOV AL,DEF_DISK ;Get default disk
MOV DL,AL ;save default disk number
ADD AL,40H ;Convert to ascii
MOV AH,":"
JMP SHORT PARSE2
PARSE1:
LODSW ;Get disk specified
AND AL,0DFH ;convert to caps
MOV DL,AL
SUB DL,40H ;convert to binary
PARSE2:
STOSW ;Load disk specification
;Look for directory specification.
MOV BX,DI ;save start of path
MOV AL,"\"
CMP BYTE PTR [SI],AL ;See if starting from root
JE PARSE3 ;yes, skip append of path
STOSB ;Start at root
PUSH SI ;save current pointer
MOV SI,DI ;point to dest buffer
MOV AH,47H ;Get default path
INT 21H
MOV CX,64 ;Max 64 char in path
MOV AL,0
REPNE SCASB ;scan for end of path
DEC DI ;move back before zero
POP SI
CMP CX,63 ;If no path, don't append an
JGE PARSE3 ; extra \.
PARSE21:
CALL SCANFORSEP ;Get first char of name.
JC PARSE5 ;If no name, skip append
DEC SI ;Backup so char can be reread
MOV AL,"\" ;If name, seperate from path
STOSB ; with a \.
PARSE3:
;Look for filename specification.
MOV CX,75 ;max 75 characters in a name
XOR AH,AH ;Clear last char holder
PARSE4:
CALL SCANFORSEP ;Get character, if seperator
JC PARSE5 ; char, exit.
STOSB ;Good char, copy to dest.
CMP AX,".." ;See if last 2 chars are same
JNE PARSE41
STD ;scan backwards
SUB DI,4 ;First, backup past '\..'
MOV AL,"\" ;Look for directory sep
PUSH CX
MOV CX,DI ;compute length of path
SUB CX,BX
REPNE SCASB ;Now, past last directory
POP CX
CLD ;scan forwards again
INC DI ;Move back past \
PARSE41:
MOV AH,AL ;save last character read.
LOOP PARSE4
PARSE5:
XOR AL,AL ;Terminate string with 0
STOSB
RET
PARSE_FILENAME ENDP
;-----------------------------------------------------------------------------
; SCANFORSEP looks for file seperator characters.
; Entry: DS:SI - pointer to character to compare
; Exit: CF clear - good character
; CF set - file seperator character detected
; AL - character read.
;-----------------------------------------------------------------------------
SCANFORSEP PROC NEAR
LODSB ;Get character
CMP AL," " ;Look for file delimiters
JLE SCANFOR1 ; space, comma, semicolon,
CMP AL,"," ; equal sign, or tab. Or any
JE SCANFOR1 ; characters with ASCII
CMP AL,";" ; values less than 20 or
JE SCANFOR1 ; greater than 127.
CMP AL,"="
JE SCANFOR1
CMP AL,"a" ;Convert all letters to caps
JB SCANFOR_END
CMP AL,"z"
JA SCANFOR_END
AND AL,0DFH ;convert to caps
SCANFOR_END:
CLC ;clear flag
RET
SCANFOR1:
STC ;set found flag
RET
SCANFORSEP ENDP
END_OF_CODE = $
CODE ENDS
END BEGIN