home *** CD-ROM | disk | FTP | other *** search
- ;======================================================================
- ; SAFARI - Staying Away From Abort, Retry, Ignore
- ; A resident interrupt handler for the DOS critical error handler
- ; Tested in PC-DOS 2.0 to 3.31
- ;----------------------------------------------------------------------
- CSEG SEGMENT PARA PUBLIC 'CODE'
-
- ASSUME CS:CSEG,DS:NOTHING,ES:NOTHING,SS:NOTHING
-
- ORG 100H ;SKIP TO END OF THE PSP
- ENTPT: JMP INITIALIZE ;COM FILE ENTRY ALWAYS AT 100H
-
- COPYRIGHT DB "SAFARI 1.0 (c) Ziff Communications Co.$"
- PROGRAMMER DB "Robert L. Hummel"
-
- ;----------------------------------------------------------------------
- ; Program data area. Bufferes at end of resident code.
- ;----------------------------------------------------------------------
- BOX_ATTR EQU 4FH ;Window color: 70 for b/w
- BCOL EQU 0 ;Window top left column
- BROW EQU 4 ;Window top left row
- NCOL EQU 46 ;Width of window
- NROW EQU 15 ;Length of window
-
- DISPLAY_PAGE DB 0 ;Hold current value
- CURSOR_POS DW 0 ;Hold current value
-
- OLD_INT_24 DD 0 ;Address of original Handler
- DI_REG DB 0,0 ;Local storage for error codes
- AX_REG DB 0,0 ; as low-byte, hi-byte
- ATTR_BYTE DB 0 ;From device header
-
- ; Strings encoded as col, row, ASCIIZ
-
- HEADER DB BCOL,BROW,"<< SAFARI Critical Error Handler >>",0
- DISK_ERR DB BCOL+1,BROW+1,"System Reports A Disk Error",0
- CHAR_DEV_ERR DB BCOL+1,BROW+1,"System Reports A Character Device Error",0
- BAD_FAT_ERR DB BCOL+1,BROW+1,"System Reports A Bad FAT",0
-
- ERR_TABLE DW ERR0,ERR1,ERR2,ERR3,ERR4,ERR5,ERR6,ERR7
- DW ERR8,ERR9,ERRA,ERRB,ERRC
- ERR0 DB BCOL+1,BROW+2
- DB "Attempt To Write On Write-Protected Diskette",0
- ERR1 DB BCOL+1,BROW+2,"Unknown Or Bad Unit",0
- ERR2 DB BCOL+1,BROW+2,"Drive Not Ready",0
- ERR3 DB BCOL+1,BROW+2,"Unknown Command",0
- ERR4 DB BCOL+1,BROW+2,"Data Error (CRC)",0
- ERR5 DB BCOL+1,BROW+2,"Bad Request Structure Length",0
- ERR6 DB BCOL+1,BROW+2,"Seek Error",0
- ERR7 DB BCOL+1,BROW+2,"Unknown media type",0
- ERR8 DB BCOL+1,BROW+2,"Sector Not Found",0
- ERR9 DB BCOL+1,BROW+2,"Printer Out Of Paper",0
- ERRA DB BCOL+1,BROW+2,"Write Fault",0
- ERRB DB BCOL+1,BROW+2,"Read Fault",0
- ERRC DB BCOL+1,BROW+2,"General Failure",0
-
- DRIVE_MSG DB BCOL+1,BROW+3,"On Drive "
- DRIVE_NAME DB "A:",0
-
- READ_OPER DB BCOL+1,BROW+4,"During A Read Operation",0
- WRITE_OPER DB BCOL+1,BROW+4,"During A Write Operation",0
-
- AREA_MSG DB BCOL+1,BROW+5,"Error Localized In",0
- AREA_TABLE DW DOS_AREA,FAT_AREA,DIR_AREA,DATA_AREA
- DOS_AREA DB BCOL+1,BROW+6,"DOS Area",0
- FAT_AREA DB BCOL+1,BROW+6,"File Allocation Table",0
- DIR_AREA DB BCOL+1,BROW+6,"Directory Area",0
- DATA_AREA DB BCOL+1,BROW+6,"Data Area",0
-
- REG_BLK1 DB BCOL+1,BROW+ 8,"AX=0000 BX=0000 CX=0000 DX=0000",0
- REG_BLK2 DB BCOL+1,BROW+ 9,"DS=0000 SI=0000 ES=0000 DI=0000",0
- REG_BLK3 DB BCOL+1,BROW+10,"CS:IP=0000:0000",0
-
- ;======================================================================
- ; Control is passed here by the jump we inserted into the DOS Int 24 handler
- ;----------------------------------------------------------------------
- INT_24 PROC FAR
-
- STI ;Allow Interrupts
-
- PUSH AX ;Save used registers
- PUSH DS
-
- MOV DS,BP ;Get Device Header attribute
- MOV AX,[SI+4] ; byte before changing BP
- MOV CS:ATTR_BYTE,AH
-
- POP DS ;Restore
- POP AX
-
- PUSH BP ;Access to stack
- MOV BP,SP ;Before we push anything
-
- MOV WORD PTR CS:AX_REG,AX ;Error status
- MOV WORD PTR CS:DI_REG,DI ;Error code in lower half
-
- PUSHF ;Save the state of the machine
- PUSH ES ; because we're gonna make
- PUSH DS ; a mess of it
- PUSH DI
- PUSH SI
- PUSH DX
- PUSH CX
- PUSH BX
- PUSH AX
-
- MOV AX,CS ;Set up access to local data
- MOV DS,AX
- MOV ES,AX
-
- ASSUME DS:CSEG, ES:CSEG ;Tell the assembler
- ;----------------------------------------------------------------------
- ; Save the details of the current screen for later restoration.
- ;----------------------------------------------------------------------
- MOV AH,0FH ;Get current video mode fn
- INT 10H ;Thru BIOS
- MOV DISPLAY_PAGE,BH ;Save current page
-
- MOV AH,3 ;Get cursor position fn
- INT 10H ;Thru BIOS
- MOV CURSOR_POS,DX ;Save position for
- ;restoration on exit
- ;----------------------------------------------------------------------
- ; Save section of screen we will be writing over.
- ;----------------------------------------------------------------------
- MOV BH,DISPLAY_PAGE
- CLD ;String moves forward
- MOV DI,OFFSET SCREEN_BUFFER ;Destination for save
- MOV CX,NROW ;Row loop
- MOV DH,BROW ;Init row pointer
- ROW_LOOP1:
- PUSH CX ;Prepare for...
- MOV CX,NCOL ;...column loop
- MOV DL,BCOL ;Column Pointer
- COL_LOOP1:
- MOV AH,2 ;Position cursor fn
- INT 10H ;Thru BIOS
-
- MOV AH,8 ;Get char & attribute fn
- INT 10H ;Thru BIOS
-
- STOSW ;ES:[di]<-ax ; di+=2
-
- INC DL ;Next column
- LOOP COL_LOOP1 ;Close Inner loop
-
- POP CX ;Return to outer loop
- INC DH ;Next row
- LOOP ROW_LOOP1 ;Close Outer loop
-
- ;----------------------------------------------------------------------
- ; Clear a window (box) for our information on the screen.
- ;----------------------------------------------------------------------
- MOV AH,6 ;Scroll window fn
- MOV AL,0 ;Scroll entire window
- MOV CH,BROW ;Upper row
- MOV CL,BCOL ;Left column
- MOV DH,BROW + NROW - 1 ;Bottom row is lower
- MOV DL,BCOL + NCOL - 1 ;Right column
- MOV BH,BOX_ATTR ;Window color
- INT 10H ;Thru BIOS
-
- ;----------------------------------------------------------------------
- ; Say who we are and give some information as to what happened.
- ;----------------------------------------------------------------------
- MOV SI,OFFSET HEADER
- CALL WR_STRING
- ;----------------------------------------------------------------------
- ; if ( AH:7 == 0 )
- ; disk_error
- ; else if ( ATTR_BYTE:7 == 0 )
- ; bad_fat
- ; else
- ; character_device
- ;----------------------------------------------------------------------
- MOV SI,OFFSET DISK_ERR ;AH IS ERROR, DI OK
- TEST AX_REG[1],80H ;Hi bit=0 if disk error
- JZ HARD_ERROR ;Print and examine AL
-
- MOV SI,OFFSET CHAR_DEV_ERR ;Check Header for Bad Fat err
- TEST ATTR_BYTE,80H
- JNZ DI_CODE ;else non-block device
-
- MOV SI,OFFSET BAD_FAT_ERR
- HARD_ERROR:
- CALL WR_STRING
-
- MOV AL,AX_REG[0] ;Failing drive code
- ADD AL,'A' ; convert to ascii
- MOV DRIVE_NAME,AL ; and put in display string
- MOV SI,OFFSET DRIVE_MSG ;In drive...
- CALL WR_STRING
-
- MOV SI,OFFSET READ_OPER ;Say what operation
- TEST AX_REG[1],1 ;0=Read, 1=Write
- JZ A20
- MOV SI,OFFSET WRITE_OPER
- A20:
- CALL WR_STRING
-
- MOV SI,OFFSET AREA_MSG ;Say what area
- CALL WR_STRING
-
- XOR BH,BH ;Leaving the area bits one
- MOV BL,AX_REG[1] ; position to the left is the
- AND BL,6 ; same as multiplying by two
- MOV SI,AREA_TABLE[BX] ;Offset into pointer table
- DI_CODE:
- CALL WR_STRING
- ;Interpret code in DI
- XOR BH,BH
- MOV BL,DI_REG ;Get error code
- SHL BX,1 ;Make offset into table (*2)
- MOV SI,ERR_TABLE[BX]
- CALL WR_STRING
-
- ;----------------------------------------------------------------------
- ; Perform a rudimentary traceback. Display the available registers of the
- ; original Int 21 and the program location it was called from.
- ;----------------------------------------------------------------------
- MOV DI,OFFSET REG_BLK1 + 5 ;Put digits here
- MOV AX,[BP+8] ;Point to word on stack
- CALL HEX4 ;Convert to ascii in string
- ADD DI,8 ;Point to next location
- MOV AX,[BP+10] ;...continue the process
- CALL HEX4
- ADD DI,8
- MOV AX,[BP+12]
- CALL HEX4
- ADD DI,8
- MOV AX,[BP+14]
- CALL HEX4
- MOV SI,OFFSET REG_BLK1
- CALL WR_STRING
-
- MOV DI,OFFSET REG_BLK2 + 5 ;Repeat for 2nd set of REGS
- MOV AX,[BP+22]
- CALL HEX4
- ADD DI,8
- MOV AX,[BP+16]
- CALL HEX4
- ADD DI,8
- MOV AX,[BP+24]
- CALL HEX4
- ADD DI,8
- MOV AX,[BP+18]
- CALL HEX4
- MOV SI,OFFSET REG_BLK2
- CALL WR_STRING
-
- MOV DI,OFFSET REG_BLK3 + 8 ;Repeat for CS and IP
- MOV AX,[BP+28]
- CALL HEX4
- ADD DI,5
- MOV AX,[BP+26]
- CALL HEX4
- MOV SI,OFFSET REG_BLK3
- CALL WR_STRING
-
- MOV BH,DISPLAY_PAGE ;Position for the ARI? msg
- MOV DH,BROW + 12 ;DH=row
- MOV DL,BCOL ;DL=col
-
- MOV AH,2 ;Set cursor posn fn
- INT 10H ;Thru BIOS
-
- ;----------------------------------------------------------------------
- ; Restore the state of the machine when Int 24 occured
- ;----------------------------------------------------------------------
- POP AX
- POP BX
- POP CX
- POP DX
- POP SI
- POP DI
- POP DS
- POP ES
- POPF
- POP BP
- ASSUME DS:NOTHING, ES:NOTHING
-
- ;----------------------------------------------------------------------
- ; Here is the original Int 24 handler splice. Simulate an interrupt
- ;----------------------------------------------------------------------
- PUSHF ;Push the flags
- CLI ;Disable interrupts
- PUSH CS ;Push the CS register
- MOV DI,OFFSET CS:RET_TARGET ;Get addr of next instr.
- PUSH DI ; on stack too.
- MOV DI,WORD PTR CS:DI_REG ;Restore register
- PREFIX:
- DB 5 DUP(?) ;First 5 bytes of old 24h
- JMP DWORD PTR CS:OLD_INT_24 ;Transfer control to old 24h
-
- ;----------------------------------------------------------------------
- ; IRET transfers control here. Again, save the machine state and set up
- ; registers to acess data.
- ;----------------------------------------------------------------------
- RET_TARGET:
- PUSHF
- PUSH ES
- PUSH DS
- PUSH BP
- PUSH DI
- PUSH SI
- PUSH DX
- PUSH CX
- PUSH BX
- PUSH AX
-
- MOV AX,CS
- MOV DS,AX
- MOV ES,AX
- ASSUME DS:CSEG, ES:CSEG ;Tell the assembler
-
- ;----------------------------------------------------------------------
- ; Restore the screen to original state.
- ;----------------------------------------------------------------------
- MOV BH,DISPLAY_PAGE ;Just to be sure, reset page
- MOV AH,2 ;Set cursor position fn
- MOV DH,BROW ;Top of window
- MOV DL,BCOL ;Column
- INT 10H ;Thru BIOS
-
- MOV SI,OFFSET SCREEN_BUFFER ;Origin for restoration
- MOV CX,NROW ;Row loop
- MOV DH,BROW ;Init row pointer
- ROW_LOOP2:
- PUSH CX ;Prepare for...
- MOV CX,NCOL ;...column loop
- MOV DL,BCOL ;Column Pointer
- COL_LOOP2:
- PUSH CX ;Need for write-char fn
-
- MOV AH,2 ;Position cursor fn
- INT 10H ;Thru BIOS
-
- LODSW ;AX <- [SI]
- ;AH=ATTR AL=CHAR
- MOV BL,AH ;Put attribute where needed
- MOV AH,9 ;Write char fn
- MOV CX,01 ;Write one copy of char
- INT 10H ;Thru BIOS
-
- INC DL ;Next column
- POP CX ;Restore Counter
- LOOP COL_LOOP2 ;Close Inner loop
-
- POP CX ;Return to outer loop
- INC DH ;Next row
- LOOP ROW_LOOP2 ;Close Outer loop
-
- MOV AH,2 ;Set Cursor position fn
- MOV DX,CURSOR_POS ;Restore old cursor position
- INT 10H ;Thru BIOS
-
- POP AX
- POP BX
- POP CX
- POP DX
- POP SI
- POP DI
- POP BP
- POP DS
- POP ES
- POPF
- IRET ;And we return too
-
- INT_24 ENDP
-
- ;======================================================================
- ; All access to the BIOS video interrupt comes through here. Some BIOSs
- ; destroy BP during a INT 10h call.
- ;----------------------------------------------------------------------
- VIDEO PROC NEAR
-
- PUSH BP
- INT 10H
- POP BP
- RET
-
- VIDEO ENDP
-
- ;======================================================================
- ; HEX4 - Convert the AX register to hexidecimal digits.
- ; The characters produced are stored at ES:DI.
- ; All regs preserved.
- ;----------------------------------------------------------------------
- HEX4 PROC NEAR
- PUSH AX
- PUSH BX
- PUSH CX
-
- MOV BX,AX
- STD ;String ptr decrement
- ADD DI,3 ;Point to end of string
- MOV CX,4
- H10:
- MOV AL,BL ;Want lower half
- AND AL,0FH ; of this byte
- ADD AL,90H ;Convert AL to ASCII
- DAA
- ADC AL,40H
- DAA
- STOSB ;Store at ES:DI
- SHR BX,1
- SHR BX,1
- SHR BX,1
- SHR BX,1
- LOOP H10
-
- POP CX
- POP BX
- POP AX
- INC DI
- CLD
- RET
- HEX4 ENDP
- ;======================================================================
- ; WR_STRING - write string to console at specified location.
- ; The first two bytes of the string contain the column and row of the
- ; display location. The remainder of the string is ASCIIZ.
- ; AX is destroyed, all other registers are preserved.
- ;----------------------------------------------------------------------
- WR_STRING PROC NEAR
-
- PUSH BX
- PUSH DX
- PUSH SI
-
- MOV BH,DISPLAY_PAGE
- MOV DX,[SI] ;DH=row, DL=col
- MOV AH,2 ;Set cursor posn fn
- INT 10H ;Thru BIOS
- INC SI ;Point to start of string
- INC SI
- NEXT_CHAR:
- LODSB ;Load char in AL from DS:SI
- OR AL,AL ;If char is 0
- JZ END_STRING ;End of ASCIIZ string
- MOV AH,0EH ;Else, write TTY
- INT 10H ;Thru BIOS
- JMP SHORT NEXT_CHAR
- END_STRING:
- POP SI
- POP DX
- POP BX
- RET
-
- WR_STRING ENDP
-
- ;======================================================================
- PC = $
-
- SCREEN_BUFFER = PC
- PC = PC + NROW * NCOL * 2
-
- LASTBYTE = PC
-
- ;======================================================================
- ; Initialization Procedure
- ; Patch command.com to load our handler as the new default
- ;----------------------------------------------------------------------
- INITIALIZE PROC NEAR
- ASSUME CS:CSEG,DS:CSEG,ES:CSEG,SS:CSEG ;Set by loader.
-
- MOV AH,9
- MOV DX,OFFSET COPYRIGHT
- INT 21H
- ;----------------------------------------------------------------------
- ; Get the current address of Int 24 and save
- ;----------------------------------------------------------------------
- MOV AH,35H ;Get Int vector
- MOV AL,24H ;For this Int
- INT 21H ;Result in ES:BX
- ASSUME ES:NOTHING
- CMP BYTE PTR ES:[BX],0EAH ;If code is jump
- JNE NOT_INSTALLED
-
- MOV AX,4C01H ;Terminate with error
- INT 21H
- NOT_INSTALLED:
- MOV WORD PTR OLD_INT_24[0],BX ;offset
- MOV WORD PTR OLD_INT_24[2],ES ;segment
-
- ;----------------------------------------------------------------------
- ; Copy the first five bytes of the DOS Int 24 handler to our handler.
- ;----------------------------------------------------------------------
- MOV CX,5 ;Move 5 bytes
- PUSH ES ;From old handler (DS:SI)
- POP DS
- ASSUME DS:NOTHING
- MOV SI,BX
-
- PUSH CS ;To a safe place (ES:DI)
- POP ES
- ASSUME ES:CSEG
- MOV DI,OFFSET PREFIX
- REP MOVSB
-
- ;----------------------------------------------------------------------
- ; Build our jump command inside the original Int 24 handler to
- ; pass control immediately to our handler.
- ;----------------------------------------------------------------------
- PUSH DS ;Point ES to
- POP ES ; the old handler
- ASSUME ES:NOTHING
- MOV DI,BX ;Write to ES:DI
- MOV AL,0EAH ;Opcode for far jump
- STOSB
- MOV AX,OFFSET INT_24 ;Offset of our handler
- STOSW
- MOV AX,CS
- STOSW
- ADD WORD PTR CS:OLD_INT_24,5 ;Point after jump
-
- ;----------------------------------------------------------------------
- ; Terminate and stay resident.
- ;----------------------------------------------------------------------
- MOV AX,3100H
- MOV DX,(OFFSET LASTBYTE - OFFSET CSEG + 15) SHR 4
- INT 21H
-
- INITIALIZE ENDP
-
- CSEG ENDS
- END ENTPT
-