Category : Miscellaneous Language Source Code
Archive   : MTD.ZIP
Filename : LOADTSR.ASM

 
Output of file : LOADTSR.ASM contained in archive : MTD.ZIP
;**
;** Purpose: Sample TSR for Mastering Turbo Debugger
;** Author: (c) 1990 by Tom Swan.
;**
;** To compile:
;** tasm /zi /m loadtsr
;** tlink /v loadtsr common
;**

;----- Equates

TSRInt equ 64h ; TSR's interrupt number
STACK_SIZE equ 100h ; TSR's stack size
CR equ 13 ; ASCII carriage return
LF equ 10 ; ASCII line feed
STDOUT equ 1 ; Standard output handle

;----------------------------------------------------------
; ---- Resident Portion ----
;----------------------------------------------------------

TSR_group GROUP TSR_code, TSR_data, TSR_stack

;----- The TSR's code segment

TSR_code SEGMENT byte public 'TSRCODE'
ASSUME cs:TSR_group, ds:TSR_group

;----- The TSR's Interrupt Service Routine

TSR_isr PROC far

;----- Switch to the TSR's private stack

sti ; Allow interrupt servicing
push ds ; Save ds on current stack
push cs ; Address TSR group with
pop ds ; ds (same as cs)

mov Old_sp, sp ; Save sp and ss in the
mov Old_ss, ss ; TSR's data segment
mov ss, TSR_ss ; Load new stack segment and
mov sp, TSR_sp ; offset values into ss:sp

push ax ; Save other registers
push bx ; used by this TSR
push cx ; on the TSR's stack
push dx

;----- Display message (note the TSR_group override!)

mov bx, STDOUT ; Load DOS handle into bx
mov cx, MESSAGE_LEN ; Load string length into cx
mov dx, offset TSR_group:Message ; Address message
mov ah, 40h ; Call DOS function 40h
int 21h ; to display string

;----- Restore registers saved on TSR's private stack

pop dx
pop cx
pop bx
pop ax

;----- Reset to original stack and restore ds, dx

mov ss, TSR_group:Old_ss ; Restore saved stack
mov sp, TSR_group:Old_sp ; registers to ss:sp
pop ds ; Restore ds from old stack
iret ; Return from interrupt

TSR_isr ENDP
TSR_code ENDS

;----- The TSR's data segment

TSR_data SEGMENT word public 'TSRDATA'

psp dw 0 ; TSR's psp segment address
DOSversion dw 0 ; Major and minor version number
Old_ss dw 0 ; Storage for old stack seg (ss)
Old_sp dw 0 ; Storage for old stack ofs (sp)
TSR_ss dw seg TSR_stack ; TSR's stack seg (ss)
TSR_sp dw STACK_SIZE ; Initial stack ofs (sp)
Message db CR, LF, 'TSR Activated: code-'
MsgCode db '0000:0000 data-'
MsgData db '0000:0000 stack-'
MsgStack db '0000:0000', CR, LF
MESSAGE_LEN = $ - Message

TSR_data ENDS


;----- The TSR's stack segment

TSR_stack SEGMENT word stack 'STACK'
private_stack db STACK_SIZE dup(?)
TSR_stack ENDS

;----------------------------------------------------------
; ---- Transient Portion ----
;----------------------------------------------------------

;----- The TSR loader's code segment

LOADER_code SEGMENT para public 'CODE'
ASSUME cs:LOADER_code, ds:TSR_data, ss:TSR_stack
EXTRN IntToHex:proc

;---- The TSR loader's main procedure

Load_TSR PROC far

mov ax, seg TSR_data ; Initialize ds to address
mov ds, ax ; the TSR's data segment
call CheckVersion ; Abort if DOS version = 1.x
jnc LTSR_10 ; Jump if cf = 0 (no error)
mov al, 1 ; Select error message #1
jmp ErrorExit ; End program if DOS 1.x
LTSR_10:
mov psp, es ; Save psp segment for TSR
push es ; Save PSP address on stack
push ds ; Save TSR data segment

;----- Install interrupt service routine

mov al, TSRInt ; Get current vector for
mov ah, 35h ; the TSR's interrupt number
int 21h ; using DOS function 35h.
mov bx, es ; Copy segment address to bx
or bx, bx ; and test if bx = 0.
jz LTSR_20 ; Jump if vector is not used
pop ds ; Restore TSR data seg to ds
pop es ; Restore PSP address to es
mov al, 2 ; Set error code number
jmp ErrorExit ; And exit with error message
LTSR_20:
mov ax, seg TSR_code ; Set ds to TSR's code
mov ds, ax ; segment.

ASSUME ds:TSR_code

mov dx, offset TSR_isr ; Set dx to TSR's int service
mov al, TSRInt ; routine, and set the
mov ah, 25h ; interrupt vector for TSRint
int 21h ; with DOS function 25h.
pop ds ; Restore TSR data segment

ASSUME ds:TSR_data

;----- Insert TSR addresses into the message string

push ds ; Set es = ds for addressing
pop es ; strings with es:di
mov ax, seg TSR_group ; ax <- TSR group segment
push ax ; Save ax for later
mov bx, offset TSR_isr ; bx <- TSR code offset
mov di, offset MsgCode ; Address code addr in string
call InsertAddress ; Insert ax:bx into string

pop ax ; Restore ax from stack
push ax ; and save ax again
mov bx, size TSR_code ; bx <- TSR data offset
mov di, offset MsgData ; Address data addr in string
call InsertAddress ; Insert ax:bx into string

pop ax ; Restore ax from stack
mov bx, size TSR_code + size TSR_data ; bx=stack ofs
mov di, offset MsgStack ; Address stack addr in str
call InsertAddress ; Insert ax:bx into string

;----- Terminate and stay resident

mov ax, seg LOADER_data ; Initialize ds to loader's
mov ds, ax ; data segment

ASSUME ds:LOADER_data

mov dx, offset doneMsg ; Display "TSR Loaded" message
mov ah, 09h ; by calling DOS print-
int 21h ; string function.
pop ax ; Restore PSP seg addr to ax
mov dx, cs ; dx <- Transient start addr
sub dx, ax ; dx <- Resident size
mov ax, 3100h ; DOS terminate function
int 21h ; Terminate, stay resident
; al = 0 (return code)
Load_TSR ENDP

;---------------------------------------------------------------
; ErrorExit Exit with error message and code in al
;---------------------------------------------------------------
; Input:
; al = error code 1..n
; ds = address of TSR's data segment
; es = psp segment address (DOS 1.x only)
; Output:
; none. program halted.
; Registers:
; none preserved
;---------------------------------------------------------------
ErrorExit PROC near

ASSUME ds:TSR_data

push DOSversion ; Save DOS version on stack
push ax ; Save error code on stack
mov ax, seg LOADER_data ; Initialize ds to loader's
mov ds, ax ; data segment

ASSUME ds:LOADER_data

mov dx, offset errorMsg ; Address "ERROR: " string
mov ah, 09h ; DOS print-string function
int 21h ; Display error lead-in
pop ax ; Restore error code to al
push ax ; Save code again
cmp al, 1 ; Does error code = 1?
jne test2 ; If not, check next code
mov dx, offset errmsg1 ; Address error message 1
jmp Exit ; Display message and exit
test2:
cmp al, 2 ; Error code 2
jne default
mov dx, offset errmsg2
jmp Exit
default:
mov dx, offset defaultmsg ; Default error code

;----- Display message and exit. Error code still in al.

Exit:
mov ah, 09h ; DOS print-string function
int 21h ; Display error message
pop ax ; Restore error code to al
pop bx ; Restore DOS version to bx
cmp bl, 2 ; Is it ver. 2.x or higher?
jb ExitDOS1x ; Jump for versions 1.x

;----- End program for DOS 2.x and higher

mov ah, 4ch ; DOS terminate with code
int 21h ; End with error code in al

;----- End program for DOS 1.x

ExitDOS1x:
push es ; Push es onto stack
xor ax,ax ; Set ax to 0000
push ax ; Push 0000 (stack=es:0000)
retf ; Far return exits program

ErrorExit ENDP

;---------------------------------------------------------------
; CheckVersion Test DOS version
;---------------------------------------------------------------
; Input:
; ds = address of TSR's data segment
; Output:
; TSR_data:DOSversion = version number
; ax = version number
; cf = 0 = DOS version 2.x or higher
; cf = 1 = DOS version 1.x
; Registers:
; ax
;---------------------------------------------------------------
CheckVersion PROC near

ASSUME ds:TSR_data

mov ah, 30h ; DOS get-version function
int 21h ; Get DOS version
mov word ptr DOSversion, ax ; Save in TSR data seg
cmp al, 02h ; Test major revision number
ret ; cf = 0 if al >= 2
; cf = 1 if al < 2
CheckVersion ENDP

;---------------------------------------------------------------
; InsertAddress Insert seg:offset address into a string
;---------------------------------------------------------------
; Input:
; ax = segment address
; bx = offset address
; es:di = address of 9-character string (minimum size)
; Output:
; ax:bx inserted in hex into string at di
; es:di = address of byte after last inserted character
; Registers:
; ax, bx, cx, dx, si, di
;---------------------------------------------------------------
InsertAddress PROC near

push bx ; Save offset value on stack
call IA_10 ; Insert segment into string
inc di ; Skip colon (:)
pop ax ; Restore offset to ax
IA_10:
mov cx, 4 ; Specify minimum of 4 digits
call IntToHex ; Convert ax to hex at es:di
ret ; Return to caller

InsertAddress ENDP
LOADER_code ENDS

;----- TSR loader's data segment

LOADER_data SEGMENT word public 'DATA'

doneMsg db CR,LF,'TSR Loaded',CR,LF,'$'
errorMsg db CR,LF,'ERROR: ', '$'
errmsg1 db 'Requires DOS 2.0 or later',CR,LF,'$'
errmsg2 db 'Interrupt vector in use',CR,LF,'$'
defaultmsg db 'Unknown cause',CR,LF,'$'

LOADER_data ENDS
END Load_TSR


  3 Responses to “Category : Miscellaneous Language Source Code
Archive   : MTD.ZIP
Filename : LOADTSR.ASM

  1. Very nice! Thank you for this wonderful archive. I wonder why I found it only now. Long live the BBS file archives!

  2. This is so awesome! 😀 I’d be cool if you could download an entire archive of this at once, though.

  3. But one thing that puzzles me is the “mtswslnkmcjklsdlsbdmMICROSOFT” string. There is an article about it here. It is definitely worth a read: http://www.os2museum.com/wp/mtswslnk/