[comp.sys.ibm.pc] Here is HOW to do TSR with

jchvr@ihlpb.ATT.COM (Schipaanboord) (08/04/88)

This is not a full tutorial but rather an adaptation of some ASM code
that was psted a while back. I took it and now you can use it to make 
Lattice-C programs into TSR. It might work for other C compilers but
since I do not have them I cannot try. firstis the ASM code and
second the C routines to save screen etc. Use or abuse it at your own risk!!

Even if you do not use this, you can read the ASM file to know all that
you should do in order to make a TSR. I have used this code succesfully
in a POPup visual agenda, notebook and action item reminder (yes yet
another one).

FILE: TSR.ASM
page    60,132
; Copyright 1987 by Thomas Brandenborg. All Rights Reserved
; Written for uploading to Compuserve Forums by
;
;       Thomas Brandenborg
;       Lundbyesgade 11
;       DK-8000 Aarhus C
;       DENMARK
;
; Modified to work under Lattice-C S model version 2.14
; might work under newer versions as well
; H.F. van Rietschote
;
;	You write cpopup() in Lattice-C and you have a popup
;	go and become TSR after calling intdos() with ax=0x3100 and dx=_TSIZE
;	but after this no more MALLOC(), also not indirect ia fopen() etc.
;	allowed.

DGROUP	GROUP	DATA
DATA	SEGMENT	WORD	PUBLIC	'DATA'
	ASSUME	DS:DGROUP
DATA	ENDS

;==============================================================================
; DEFINE BIOS DATA SEGMENT OFFSETS
;==============================================================================

BiosData	segment at 40h
		org     17h
KbFlag		label   byte		    ;current shift status bits
		org     18h

KbFlag1	 	label   byte    	    ;current key status of toggle keys
BiosData        ends

;==============================================================================
; DEFINE OFFSETS WITHIN BIOS EXTRA DATA SEGMENT
;==============================================================================

BiosXX          segment at 50h
		org     0
StatusByte      label   byte            ;PrtSc status
BiosXX          ends

ErrPrtSc        equ     -1              ;err during last PrtSc
InPrtSc         equ     1               ;PrtSc in progress

;==============================================================================
; DEFINE OFFSETS WITHIN OUR PSP
;==============================================================================

PGROUP		GROUP	PROG
PROG		SEGMENT	BYTE PUBLIC 'PROG'
		public	tsr,ErrBeep,Bleep
		extrn	cpopup:near
		assume	cs:PGROUP, ds:nothing, es:nothing, ss:nothing

;==============================================================================
; IDENTIFICATION CODES FOR THIS TSR (MUST BE UNIQUE FOR EACH CO-EXISTING TSR)
; HIGH BYTE OF GetId MUST NOT MATCH ANY AH REQUEST CODES FOR INT16H.
;==============================================================================

GetId           equ     'tc'		    ;INT16h AX val to get MyId
MyId            equ     'TC'		    ;ID of this TSR
SetAlarm	equ	'al'		    ; set alarm, BX= # of min. to wait

;==============================================================================
; FLAGS AND PTRS FOR RESIDENT HANDLING
;==============================================================================

TsrMode         db      0		       ;bits for various modes
InInt08         equ     1 SHL 0		 ;timer0 tick handler
InInt09         equ     1 SHL 1		 ;keyboard handler
InInt13         equ     1 SHL 2		 ;BIOS disk I/O
InInt28         equ     1 SHL 3		 ;INT28 handler
In28Call        equ     1 SHL 4		 ;we have issued INT28
InPopup         equ     1 SHL 5		 ;popup routine activated
NewDos          equ     1 SHL 6		 ;DOS 2.x in use
InDosClr        equ     1 SHL 7		 ;InDos=0 at popup time

KeyMode         db      0		       ;bits for hotkey status
HotIsShift      equ     1 SHL 0		 ;hotkey is shift state
InHotMatch      equ     1 SHL 1		 ;so far keys match hotkey seq
HotKeyOn        equ     1 SHL 2		 ;full hotkey pressed

InDosPtr        label   dword		   ;seg:off of InDos flag
InDosOff        dw      0
InDosSeg        dw      0

CritErrPtr      label   dword		   ;seg:off of CritErr flag
CritErrOff      dw      0
CritErrSeg      dw      0

;==============================================================================
; DATA FOR INT09H HANDLER TO CHECK FOR HOTKEY COMBINATION
;==============================================================================

; ------------  EQU'S FOR BIT SHIFTS WITHIN KEYBOARD FLAGS

InsState        equ     80h
CapsState       equ     40h
NumState        equ     20h
ScrollState     equ     10h
AltShift        equ     08h
CtlShift        equ     04h
LeftShift       equ     02h
RightShift      equ     01h

InsShift        equ     80h
CapsShift       equ     40h
NumShift        equ     20h
ScrollShift     equ     10h
HoldState       equ     08h

; ------------  SCAN CODES FOR VARIOUS SHIFT KEYS

LeftDown        equ     42		      ;scan code of left shift key
LeftUp          equ     LeftDown OR 80h
RightDown       equ     54		      ;scan code of right shift key
RightUp         equ     RightDown OR 80h
AltDown         equ     56		      ;scan code of alt key
AltUp           equ     AltDown OR 80h
CtlDown         equ     29		      ;scan code of ctrl key
CtlUp           equ     CtlDown OR 80h

; ------------  MISC KEYBOARD DATA

KbData          equ     60h		     ;keyboard data input

;==============================================================================
; TO USE A SHIFT KEY COMBINATION AS HOT KEY:
;  -    SET THE FLAG HotIsShift IN KeyMode
;  -    DEFINE THE SHIFT STATUS BITS IN THE VARIABLE HotKeyShift
;
; TO USE A SERIES OF SCAN CODES AS HOT KEY:
;       CLEAR THE FLAG HotIsShift IN KeyMode
;  -    INSERT THE MAKE AND BREAK SCAN CODES IN THE HotKeySeq STRING
;       NOTE:   WITH THIS DEMO IMPLEMENTATION YOU SHOULD NOT USE A HOT KEY
;               SEQUENCE WHICH PRODUCES A KEY IN THE BIOS KEYBOARD QUEUE,
;               SINCE THE KEY IS NOT REMOVED BEFORE CALLING THE POPUP ROUTINE.
;
; NOTE: HOTKEY TYPE AND CONTENTS OF HOTKEY VARIABLES MAY BE CHANGED AT RUN TIME
;==============================================================================

HotKeyShift     db      LeftShift OR RightShift ;shift state IF HotIsShift=FF

; HotKeySeq       db      LeftDown,LeftUp,LeftDown,LeftUp
HotKeySeq       db      LeftDown,LeftUp,RightDown,RightUp
HotKeyLen       equ     $-HotKeySeq
HotIndex        db      0		       ;# key in seq to compare next
BetweenKeys     db      0		       ;timeout count between keys
KeyTimeOut      equ     10		      ;more ticks means not a hotkey

;==============================================================================
; DATA FOR INT08H HANDLER TO CHECK FOR POPUP
;==============================================================================

SafeWait        db      0		       ;count-down for safe popup
MaxWait         equ     8		       ;wait no more 8/18 sec
MinLeft		dw	0			; minutes left until alarm
TicksDone	dw	0			; Ticks counted in this minute
Bleeping	dw	0			; 1 means we are bleeping

;==============================================================================
; PROCESS & SYSTEM DATA
;==============================================================================

OurSS           dw      0		       ;stack for popup routine
OurSP           dw      0
OurES		dw	0
OurBP		dw	0
OurDS		dw	0
DSLattice	dw	0		; DS as in Lattice-C

OldSS           dw      0		       ;old stack seg
OldSP           dw      0		       ;old stack off
OldES		dw	0
OldBP		dw	0
OldDS		dw	0

OurPSP          dw      0		       ;our PSP seg
OldPSP          dw      0		       ;old PSP seg

OldDTA          label   dword		   ;seg:off of old DTA area
OldDTAOff       dw      0
OldDTASeg       dw      0

OurDTA          label   dword		   ;seg:off of our DTA
OurDTAOff       dw      0
OurDTASeg       dw      0

OldBreak        db      0		       ;old ctrl-break state
OldExtErr       dw      3 dup (0)               ;AX,BX,CX of ext err

;==============================================================================
; LOCATIONS FOR SAVED INTERRUPT VECTORS
;==============================================================================

OldInt08        label   dword		   ;Timer0 loaded before this
OldInt08Off     dw      0
OldInt08Seg     dw      0

OldInt09        label   dword		   ;Kb handler loadde before this
OldInt09Off     dw      0
OldInt09Seg     dw      0

OldInt13        label   dword		   ;BIOS diskette I/O
OldInt13Off     dw      0
OldInt13Seg     dw      0

OldInt16        label   dword		   ;BIOS kb Q-handler
OldInt16Off     dw      0
OldInt16Seg     dw      0

OldInt1B        label   dword		   ;^break of process we steal
OldInt1BOff     dw      0
OldInt1BSeg     dw      0

OldInt1C        label   dword		   ;timer tick of process we steal
OldInt1COff     dw      0
OldInt1CSeg     dw      0

OldInt21        label   dword		   ;DOS function dispatcher
OldInt21Off     dw      0
OldInt21Seg     dw      0

OldInt23        label   dword		   ;^C of process we steal
OldInt23Off     dw      0
OldInt23Seg     dw      0

OldInt24        label   dword		   ;crit err of process we steal
OldInt24Off     dw      0
OldInt24Seg     dw      0

OldInt28        label   dword		   ;DOS idles loaded before this
OldInt28Off     dw      0
OldInt28Seg     dw      0

;==============================================================================
; SPEAKER/TONE GENERATION DATA
;==============================================================================

PB0port         equ     61h		     ;port for speaker bit
ErrLen1         equ     10		      ;# outer err beep cycles
ErrLen2         equ     80		      ;# inner err beep cycles
ErrLow          equ     100		     ;low tone wait in err beep
ErrHi           equ     40		      ;hi tone wait in err beep

;==============================================================================
; ErrBeep - PRODUCE ERROR-INDICATING SOUND ON SPEAKER
;==============================================================================

ErrBeep         proc    near
		assume  ds:nothing, es:nothing, ss:nothing

		push	bp
		push    ax		      ;save regs used
		push    bx
		push    cx
		push    dx

		mov     cx,ErrLen1              ;# mix-cycles for beep

ErrBeep1:       mov     dx,ErrLow               ;wait time for half-cycle
		mov     bx,ErrLen2              ;len of one tone
		call    DoTone		  ;output low err tone
		mov     dx,ErrHi		;wait time for half-cycle
		mov     bx,ErrLen2              ;len of one tone
		call    DoTone		  ;output low err tone

		loop    ErrBeep1		;loop for some time

		pop     dx
		pop     cx		      ;restore regs
		pop     bx
		pop     ax
		pop	bp
		ret
ErrBeep         endp

;==============================================================================
; DoTone - OUTPUT ONE TONE ON THE SPEAKER
;
; INPUT:        DX:     LOOP WAIT TIME FOR HALF CYCLE IN TONE
;               BX:     NUMBER OF CYCLES FOR TONE DURATION
; OUTPUT:       NONE
; REGS:         ALL PRESERVED
;==============================================================================

Bleep		proc	near			; short bleep for in "C"
		assume  ds:nothing, es:nothing, ss:nothing

		push	bp
		push	dx
		push	bx
		mov     dx,ErrLow               ;wait time for half-cycle
		mov     bx,ErrLen2              ;len of one tone
		call	DoTone
		pop	bx
		pop	dx
		pop	bp
		ret
Bleep		endp

DoTone          proc    near
		assume  ds:nothing, es:nothing, ss:nothing

		push    ax		      ;save regs used
		push    bx
		push    cx
		in      al,PB0port              ;get PB0 reg pattern
		mov     ah,al		   ;save it

DoTone1:        and     al,0fch		 ;mask off speaker bit
		out     PB0port,al              ;pull!
		mov     cx,dx		   ;half cycle in counter
DoTone2:        loop    DoTone2		 ;leave there for half a cycle
		or      al,2		    ;turn on speaker bit
		out     PB0port,al              ;push!
		mov     cx,dx		   ;half cycle in counter
DoTone3:        loop    DoTone3		 ;leave there for half a cycle

		dec     bx		      ;count down tone duration
		jnz     DoTone1		 ;go through full tone

		mov     al,ah		   ;AL=original PB0 reg value
		out     PB0port,al              ;restore

		pop     cx		      ;restore regs
		pop     bx
		pop     ax
		ret
DoTone          endp

;==============================================================================
; TestSafe - CHECK IF THIS IS A SAFE TIME TO DO A POP UP
;
; RETURN CLC IF SAFE TO POP UP, CY IF NOT SAFE.
;
; CHECK IF ANY INTs ARE IN CRITICAL AREAS (InInt09 & InInt13)
; CHECK IF WE ARE IN AN OUR OWN INT28 CALL (In28Call)
; CHECK 8259A PIC ISR REGISTER FOR MISSING EOIs
; CHECK IF DOS IS STABLE FOR POP UP
; CHECK IF A PRINT SCREEN IS IN PROGRESS
;==============================================================================

TestSafe        proc    near
		assume  ds:nothing, es:nothing

		push    ax		      ;save regs used
		push    bx
		push    ds

; ------------  CHECK INTs TO SEE IF THEY WERE INTERRUPTED AT BAD TIMES

		test    TsrMode,InInt09 OR InInt13 OR In28Call
		jnz     NotSafe		 ;jump if any INTs are chopped

; ------------  CHECK THE 8259A PIC ISR REGISTER FOR NON-EOIed HW INTs

		mov     al,00001011b            ;tell 8259A we want the ISR
		out     20h,al		  ;8259A command reg
		nop
		nop
		nop		             ;now, ISR should be ready
		in      al,20h		  ;AL=mask of active INTs
		or      al,al		   ;test all (IRQ0 *did* EOI)
		jnz     NotSafe		 ;jump if active INTs

; ------------  NOW, ENSURE THAT DOS WAS NOT INTERRUPTED

		assume  ds:nothing

		lds     bx,InDosPtr             ;now, DS:BX=InDos
		mov     al,byte ptr [bx]        ;get InDos to AL
		lds     bx,CritErrPtr           ;now, DS:BX=CritErr
		or      al,byte ptr [bx]        ;both flags zero?
		jz      DosSafe		 ;YES - DOS is really idle
		test    TsrMode,InInt28         ;is this an INT28h
		jz      NotSafe		 ;NO - not safe, should be idle
		cmp     al,1		    ;YES - one InDos entry only?
		ja      NotSafe		 ;NO - jump if more than one
DosSafe:

; ------------  CHECK TO SEE IF A PRINT SCREEN IS IN PROGRESS

		mov     ax,BiosXX
		mov     ds,ax		   ;move DS to BIOS extra data seg
		assume  ds:BiosXX

		cmp     StatusByte,InPrtSc      ;print screen in progress?
		je      NotSafe		 ;YES - jump if prtsc

; ------------  SEEMS TO BE A SAFE TIME FOR POPUP

IsSafe:         clc		             ;CLC=safe to popup
		jmp     short ExitSafe          ;end this then

; ------------  APPARENTLY THIS IS JUST NOT THE TIME TO DO A POPUP

NotSafe:        stc		             ;CY=don't popup now

; ------------  RETURN TO CALLER WITH CARRY SET/CLEAR

ExitSafe:       pop     ds		      ;restore regs
		pop     bx
		pop     ax
		ret
TestSafe        endp

;==============================================================================
; OurInt08 - TSR INT08H HANDLER TO WATCH FOR HOTKEY AND SAFE POPUP TIMES
;
; CALL OldInt08
; CHECK FOR RE-ENTRANCE INTO CRITICAL INT08 CODE
; SET InInt08 FLAG
; CHECK FOR TIMEOUT BETWEEN KEYS IN HOTKEY SEQUENCE
; CHECK IF HOTKEY WAS PRESSED
; CHECK IF ALREADY InPopup OR InInt28
; CHECK IF SAFE TIME FOR SYSTEM TO POPUP
; UPDATE FLAGS AND CALL POPUP IF SAFE
; GIVE ERROR BEEP IF POPUP WAS UNSAFE FOR A LONG TIME
; RESET InInt08 FLAG
; DO IRET
;==============================================================================

; ------------  NEAR JUMP DESTINATION FOR FAST IRET'S

Exit08:         iret		            ;IRET (!)

; ------------  ACTUAL INT08 ENTRY POINT

OurInt08        proc    far
		assume  ds:nothing, es:nothing, ss:nothing

		pushf		           ;simulate INT08
		cli		             ;in case others forgot it
		call    OldInt08		;call TSRs loaded before us

; -- see if waiting for alarm

		cmp	MinLeft,0	; see if we are waiting for alarm
		je	NoAlarm
		inc	TicksDone	; one more tick done
		cmp	TicksDone,1092
		jne	NoMinute
		dec	MinLeft		; one less minute to wait
		mov	TicksDone,0	; reset count
NoMinute:	cmp	MinLeft,1	; is this last minute, if so bleep
		jne	NoBleep
		inc	Bleeping	; we only bleep every 2 seconds
		cmp	Bleeping,37	; 37  is little more than 2 second
		jne	NoBleep
		call	ErrBeep
		mov	Bleeping,0	; wait 2 second until next bleep
NoBleep:

; ------------  ENSURE NO RECURSION INTO CRITICAL INT08 CODE

NoAlarm:	sti		             ;we'll manage INTs

		test    TsrMode,InInt08         ;already in here somewhere?
		jnz     Exit08		  ;YES - don't re-enter
		or      TsrMode,InInt08         ;tell people we are here

		push    ax		      ;need a few regs in this code

; ------------  COUNT DOWN TIME-OUT BETWEEN KEYS IN HOTKEY SEQUENCE

		test    KeyMode,InHotMatch      ;are we in a key match?
		jz      TestHot08               ;NO - don't care then
		dec     BetweenKeys             ;count down timeout val
		jnz     TestHot08               ;jump if no timeout yet
		mov     HotIndex,0              ;start match from beginning
		and     KeyMode,not InHotMatch  ;just so we know it next time

; ------------  CHECK FOR POSSIBLE POPUP ACTIONS

TestHot08:      test    KeyMode,HotKeyOn        ;has hotkey been pressed?
		jz      ExitInt08               ;NO - jump if no fun here

		test    TsrMode,InInt28 OR InPopup
		jnz     ExitInt08               ;jmp if not alr in business

; ------------  HOTKEY PRESSED, CHECK TO SEE IF IT IS SAFE TO POPUP

		cmp     SafeWait,0              ;first time we find hotkey?
		ja      TestSafe08              ;NO - wait has alr been set
		mov     SafeWait,MaxWait        ;# ticks to wait at most

TestSafe08:     call    TestSafe		;now, CY clear if popup is safe
		jc      NotSafe08               ;jump if popup is bad idea

; ------------  SEEMS SAFE TO POPUP AT THIS TIME, SO DO!

		xor     al,al		   ;fast zero
		mov     SafeWait,al             ;don't count any more
		and     KeyMode,not HotKeyOn    ;clear hotkey status
		or      TsrMode,InPopup         ;tell'em we enter popup routine
		and     TsrMode,not InInt08     ;OK to enter critical INT08
		call    InitPopup               ;do actual popup
		or      TsrMode,InInt08         ;back in INT08 code here
		and     TsrMode,not InPopup     ;not in popup code any more
		mov     SafeWait,al             ;in case of hotkey during popup
		and     KeyMode,not HotKeyOn    ;clear hotkey status

		jmp     short ExitInt08         ;finally done

; ------------  UNSAFE POPUP TIME, COUNT DOWN SafeWait

NotSafe08:      dec     SafeWait		;count down waiter
		jnz     ExitInt08               ;jump if still no timeout

; ------------  NO SAFE TIMES FOUND FOR QUITE SOME TIME, ERROR

		and     KeyMode,not HotKeyOn    ;might as well clear hotkey
		call    ErrBeep		 ;do an error beep

; ------------  NORMAL INT08H EXIT, RESET InInt08

ExitInt08:      pop     ax		      ;restore regs used
		and     TsrMode,not InInt08     ;clear that flag
		iret		            ;straight back
OurInt08        endp

;==============================================================================
; OurInt09 - TSR INT09H HANDLER TO WATCH FOR HOTKEY
;
; SAVE SCAN CODE
; CALL OldInt09
; CHECK FOR RECURSION INTO CRITICAL INT09 CODE
; SET InInt09 FLAG
; CHECK IF HOTKEY ALREADY SET
; DETERMINE HOTKEY TYPE (SHIFT STATE OR KEY SEQENCE)
; CHECK SHIFT STATE IF HotIsShift
; COMPARE FOR KEY MATCH IF (NOT HotIsShift)
; SET HotKeyOn IF HOTKEY PRESSED
; RESET InInt09 FLAG
; DO IRET
;==============================================================================

; ------------  NEAR JUMP DESTINATION FOR EARLY EXITS

Exit09:         pop     bx		      ;restore regs
		pop     ax
		iret		            ;flags restored from stack

; ------------  ACTUAL INT09 ENTRY POINT

OurInt09        proc    far
		assume  ds:nothing, es:nothing, ss:nothing

		push    ax		      ;save regs used
		push    bx

; ------------  READ SCAN CODE, IN CASE SEQUENCE MATCHING SELECTED

		in      al,KbData               ;Al=key, preserved by BIOS

; ------------  CALL BIOS TO PERFORM IT'S DUTIES

		pushf		           ;simulate INT (CLI alr set)
		cli		             ;in case others forgot it
		call    OldInt09		;call BIOS/earlier TSRs

; ------------  ENSURE NO RECURSION INTO CRITICAL INT09 CODE

		sti		             ;we'll manage INTs

		test    TsrMode,InInt09         ;alr in business?
		jnz     Exit09		  ;YES - skip test till clear
		or      TsrMode,InInt09         ;tell them we arrived here

; ------------  DETERMINE HOT KEY TYPE SELECTED

		test    KeyMode,HotKeyOn        ;already hotkey there?
		jnz     ExitInt09               ;YES - no double hotkeys here

		test    KeyMode,HotIsShift      ;shift state type hotkey?
		jz      CompSeq09               ;NO - go compare sequence

; ------------  COMPARE CURRENT SHIFT STATUS AGAINST HOTKEY

		push    ds		      ;save current ds
		mov     ax,BiosData             ;move DS to BIOS data seg
		mov     ds,ax		   ;DS can now access keyb vars
		assume  ds:BiosData             ;tell MASM about our DS
		mov     al,KbFlag               ;get BIOS shift state bits
		pop     ds		      ;restore
		assume  ds:nothing              ;last thing we know about him

		and     al,HotKeyShift          ;isolate relevant bits
		cmp     al,HotKeyShift          ;our shift state in effect?
		jne     ExitInt09               ;NO - not that shift state
		or      KeyMode,HotKeyOn        ;YES - flag hotkey
		jmp     short ExitInt09         ;now we can be proud to leave

; ------------  MATCH KEY IN SCAN CODE SEQUENCE

CompSeq09:      mov     bl,HotIndex             ;next scan code to match
		xor     bh,bh		   ;must be word
		cmp     al,HotKeySeq[bx]        ;does key match?
		je      HotMatch09              ;YES - jump if match
		mov     HotIndex,bh             ;search from start next time
		and     KeyMode,not InHotMatch  ;current no match
		jmp     short ExitInt09         ;now end this

; ------------  KEY MACTHED NEXT SCAN CODE IN HotKeySeq

HotMatch09:     inc     bl		      ;new code at next pass
		cmp     bl,HotKeyLen            ;did we match whole sequence?
		jae     HotHit09		;YES - jump if full sequence
		mov     HotIndex,bl             ;NO - save new count
		mov     BetweenKeys,KeyTimeOut  ;reset counter between keys
		or      KeyMode,InHotMatch      ;we are in a match now
		jmp     short ExitInt09         ;time to end this

; ------------  KEY MATCHED ALL SCAN CODES IN HOTKEY SEQUENCE

HotHit09:       or      KeyMode,HotKeyOn        ;say hotkey was pressed
		mov     HotIndex,bh             ;match 1st code next time
		and     KeyMode,not InHotMatch  ;that's the end of a match

; ------------  EXIT FROM INT09H, RESET InInt09 FLAG

ExitInt09:      and     TsrMode,not InInt09     ;tell'em we left this code
		pop     bx		      ;restore regs
		pop     ax
		iret		            ;flags restored from stack
OurInt09        endp

;==============================================================================
; OurInt13 - SET InInt13 FLAG TO SAY THAT WE ARE IN AN INT13H
;==============================================================================

OurInt13        proc    far
		assume  ds:nothing, es:nothing, ss:nothing

		pushf		           ;save flags we use
		or      TsrMode,InInt13         ;remember we are in BIOS now
		popf		            ;restore flags

		pushf		           ;simulate INT13
		cli		             ;just in case others forgot
		call    OldInt13		;let BIOS handle it all

		pushf		           ;BIOS uses flag return
		and     TsrMode, not InInt13    ;tell people we left INT13h
		popf

		ret     2		       ;throw flags off stack
OurInt13        endp

;==============================================================================
; OurInt16 - TSR INT16H HANDLER, INT28 CHAIN INTERFACE
;
; INPUT:	AX = SetAlarm
;               BX = # of minutes to wait (0= no wait)
; OUTPUT:	nothing
;
; INPUT:        AX = GetId
; OUTPUT:       AX = MyId
; REGS:         AX LOST, ALL OTHERS PRESERVED
; DESCRIPTION:  DETERMINE IF TSR WITH THIS ID IS ALREADY IN MEMORY
;
; INPUT:        AH = 00
; OUTPUT:       AX = NEXT KEY FROM BUFFER
; REGS;         AX LOST, ALL OTHERS PRESERVED
; DESCRIPTION:  RETURN A KEY FROM KEYBOARD BUFFER, WAIT TILL KEY IS PRESSED
;
; INPUT:        AH = 02
; OUTPUT:       AX = KEY FROM BUFFER IN ANY
;               ZF = NO KEYS IN BUFFER (AX PRESERVED)
;               NZ = KEY IN BUFFER (RETURNED IN AX, KEY STILL IN BUFFER)
; DESCRIPTION:  CHECK BUFFER FOR ANY PENDING KEYS, RETURN KEY IF ANY
;
; NOTE: ALL OTHER AX REQUEST CODES ARE PASSED ON TO BIOS INT16H HANDLER.
;
; NOTE: DURING INT28 POPUP (InPopup AND NOT InDosClr) FUNCTIONS AH=0 AND
;       AH=1 WILL ISSUE INT28, UNLESS InDos HAS FROM VALUE AT POPUP OR
;       CritErr HAS BEEN SET.
;==============================================================================

OurInt16        proc    far
		assume  ds:nothing, es:nothing, ss:nothing

		sti		             ;we'll manage INTs
		pushf		           ;save callers flags
		cmp	ax,SetAlarm	; set alarm called ?
		jne	NotAlarm
		mov	MinLeft,bx	; bx holds number of minutes to wait
		xor	bx,bx
		mov	TicksDone, bx	; ticksdone = 0
		mov	Bleeping, bx	; bleeping = 0
		popf
		iret			; return to caller

NotAlarm:	cmp     ax,GetId		;return ID request?
		jne     NotId16		 ;NO - jump if not

; ------------  TSR DIAGNOSTIC REQUEST, RETURN SPECIAL VALUE TO SAY WE ARE HERE

		mov     ax,MyId		 ;ID val returned in AX
		popf		            ;restore flags
		iret		            ;return to caller

; ------------  PASS CONTROL TO BIOS, FLAGS ON STACK

GoBios16:       popf		            ;restore flags at INT time
		jmp     OldInt16		;continue in the woods

; ------------  REGULAR BIOS INT16 REQUEST, CHECK FOR ANY FANCY ACTIONS

NotId16:        test    TsrMode,InPopup         ;are we in a popup?
		jz      GoBios16		;NO - leave rest with BIOS
		test    TsrMode,InDosClr        ;InDos clear at popup?
		jnz     GoBios16		;YES - no need to signal INT28

		popf		            ;restore original flags
		push    bx		      ;we need a few regs here
		push    cx
		push    si
		push    ds
		pushf		           ;original flags back on stack

; ------------  GET REQUEST CODE TO BH ENHANCED BIT TO BL

		mov     bh,ah		   ;BH=function request code
		and     bh,not 10h              ;zap enhanced kybd bit
		cmp     bh,1		    ;any function above 1?
		ja      ExitBios16              ;YES - leave rest with BIOS

		mov     bl,ah		   ;BL used for enhanced bit
		and     bl,10h		  ;BL=value of enhanced bit

; ------------  GET InDos To CL, CritErr to CH, SETUP REGS

		assume  ds:nothing

		lds     si,InDosPtr             ;DS:[SI]=InDos
		mov     cl,byte ptr [si]        ;CL=InDos value
		lds     si,CritErrPtr           ;ES:[SI]=CritErr
		mov     ch,byte ptr [si]        ;CH=CritErr value

		mov     si,ax		   ;save AX call value

		mov     ax,cs		   ;move DS here, now we got it
		mov     ds,ax
		assume  ds:PGROUP		 ;everybody should know

; ------------  CHECK KEYBOARD BUFFER, ORIGINAL FLAGS ON STACK

Wait16:         mov     ah,1		    ;AH=1=test buffer status
		or      ah,bl		   ;maintain enhanced bit value

		popf		            ;restore original flags
		pushf		           ;simulate INT
		cli		             ;in case others forgot
		call    OldInt16		;now, ZF set if no keys
		pushf		           ;save result flags
		jnz     TestSkip16              ;jump if a key was found

; ------------  NO KEY FOUND, CALL INT28 IF DOS InDos ALLOWS

		cmp     cx,0001h		;CritErr=0, InDos=1 ?
		jne     NextKey16               ;NO - wait for next key
		or      TsrMode,In28Call        ;tell people we called this INT
		int     28h		     ;now take your chance
		and     TsrMode,not In28Call    ;end of that call

; ------------  TEST BUFFER AGAIN IF INT16.00, IRET IF INT16.01

NextKey16:      or      bh,bh		   ;is this a wait for key?
		jz      Wait16		  ;YES - then go wait for it!
		mov     ax,si		   ;restore original AX contents
		jmp     short Exit16            ;NO - exit with status we got

; ------------  KEY IN BUFFER, IF CTRL-C WE MAY HAVE TO SKIP IT, FLAGS ON STACK

TestSkip16:     cmp     al,3		    ;is this Ctrl-C?
		jne     TestExit16              ;NO - determine exit method
		test    cx,not 0001h            ;anything but InDos=1?
		jz      TestExit16              ;NO - determine exit method

; ------------  SKIP CTRL-C IN KEYBOARD BUFFER

		mov     ah,bl		   ;AH=0 + enhanced bit
		popf		            ;restore original INTs
		pushf		           ;save again
		pushf		           ;simulate INT
		cli		             ;simulate properly!
		call    OldInt16		;now, key should be gone
		jmp     short Wait16            ;do as if nothing had happened

; ------------  KEY IN AX, IRET IF INT16.01, LEAVE WITH BIOS IF INT16.00

TestExit16:     or      bh,bh		   ;is this a wait for key?
		jnz     Exit16		  ;NO - do fast return
		mov     ax,si		   ;YES - restore AX code

; ------------  PASS CONTROL TO BIOS, FLAGS & REGS ON STACK

		assume  ds:nothing

ExitBios16:     popf		            ;restore work flags
		pop     ds		      ;restore regs
		pop     si
		pop     cx
		pop     bx
		cli		             ;should look like an INT
		jmp     OldInt16		;leave rest with BIOS

; ------------  RETURN FROM INT16, FLAGS & REGS ON STACK

		assume  ds:nothing

Exit16:         popf		            ;restore proper flags
		pop     ds		      ;restore regs
		pop     si
		pop     cx
		pop     bx
		ret     2		       ;IRET, without flags restore

OurInt16        endp

;==============================================================================
; OurInt21 - INT21 FILTER TO THROW DANGEROUS DOS CALLS ON CRITICAL STACK
;
; CHECK IF InPopup AND InDosClr
; CHECK FUNCTION USES CONSOLE STACK
; SET CritErr IN DOS IF CONSOLE STACK USED
; CALL OldInt21
; RESTORE CritErr IF CRITICAL STACK USED
;==============================================================================

OurInt21        proc    far
		assume  ds:nothing, es:nothing

		pushf		           ;save calling flags
		sti

		test    TsrMode,InPopup         ;are we in a popup?
		jz      GoDos21		 ;NO - don't worry then
		test    TsrMode,InDosClr        ;console stack idle?
		jnz     GoDos21		 ;YES - nothing fancy then

; ------------  THIS IS 2ND CALL INTO DOS, SEE IF USING CONSOLE STACK

		cmp     ah,0ch		  ;any function 00-0C?
		jbe     UseCrit21               ;YES - use critical stack
		test    TsrMode,NewDos          ;NO - is this DOS 3.x?
		jnz     GoDos21		 ;YES - no other to worry about
		cmp     ah,50h		  ;set PSP function?
		je      UseCrit21               ;YES - use critical stack
		cmp     ah,51h		  ;get PSP function?
		jne     GoDos21		 ;NO - leave it with DOS

; ------------  FORCE USE OF CRITICAL STACK FOR THIS CALL

UseCrit21:      assume  ds:nothing              ;nothing to say about DS

		push    si		      ;save regs
		push    ds
		lds     si,CritErrPtr           ;now, DS:[SI]=InDos
		mov     byte ptr [si],-1        ;FF=use crit stack now
		pop     ds		      ;restore regs
		pop     si

		popf		            ;retsore flags setting
		pushf		           ;simulate INT
		cli		             ;in case others forgot
		call    OldInt21		;flags already on stack

		push    si		      ;save regs
		push    ds
		lds     si,CritErrPtr           ;now, DS:[SI]=InDos
		mov     byte ptr [si],0         ;0=back to default stack
		pop     ds		      ;restore regs
		pop     si

		ret     2		       ;IRET throw old flags

; ------------  PASS CONTROL TO DOS, FLAGS ON STACK

GoDos21:        popf		            ;restore original flags
		cli		             ;just in case someone forgot
		jmp     OldInt21		;let DOS handle the rest
OurInt21        endp

;==============================================================================
; OurInt24 - SAFE DOS CRITICAL ERROR HANDLER
;
; IF DOS 3.X, FAIL THE SYSTEM CALL
; IF NOT DOS 3.X, IGNORE ERROR
;==============================================================================

OurInt24        proc    far
		assume  ds:nothing, es:nothing, ss:nothing
		mov     al,3		    ;AL=3=fail system call
		test    TsrMode,NewDos          ;are we using DOS 3.x?
		jnz     Exit24		  ;YES - OK to use AL=3
		xor     al,al		   ;NO - have to ignore err then
Exit24:         iret		            ;return to DOS
OurInt24        endp

;==============================================================================
; OurInt28 - TSR INT28H HANDLER, ALLOWS POPUP DURING DOS IDLE CALLS
;
; CALL OldInt28
; CHECK FOR RECURSION INTO CRITICAL INT28 CODE (& OTHER INTs AS WELL)
; SET InInt28 FLAG
; CHECK FOR HOTKEY
; CHECK IF SAFE TO POPUP
; DO POPUP IF SAFE AT THIS TIME
; RESET InInt28 FLAG
; DO IRET
;==============================================================================

; ------------  NEAR JUMP DESTINATION FOR FAST IRET'S

Exit28:         iret		            ;IRET (!)

; ------------  ACTUAL INT28 ENTRY POINT

OurInt28        proc    far
		assume  ds:nothing, es:nothing, ss:nothing

		pushf
		cli		             ;in case others forgot it
		call    OldInt28		;call TSRs loaded before this

; ------------  ENSURE NO RECURSION ON CRITICAL INT28 CODE

		sti		             ;we'll manage INT's after this
		test    TsrMode,InInt08 OR InInt28 OR In28Call OR InPopup
		jnz     Exit28		  ;exit fast if already going
		or      TsrMode,InInt28         ;tell'em we are here

; ------------  CHECK FOR POSSIBLE POPUP ACTIONS

		test    KeyMode,HotKeyOn        ;any hotkeys pressed?
		jz      ExitInt28               ;NO - don't check any more then

; ------------  HOTKEY WAS PRESSED, ENSURE IT'S SAFE TO DO POPUP

		call    TestSafe		;now, CY clear if popup is OK
		jc      ExitInt28               ;jump if not to popup

; ------------  SEEMS OK TO DO POPUP, SO DO!

		and     KeyMode,not HotKeyOn    ;clear hotkey status
		or      TsrMode,InPopup         ;tell'em we enter popup routine
		and     TsrMode,not InInt28     ;OK to enter critical INT28
		call    InitPopup               ;then do popup
		or      TsrMode,InInt28         ;back in INT28 code here
		and     TsrMode,not InPopup     ;not in popup code any more
		and     KeyMode,not HotKeyOn    ;clear hotkeys during popup

; ------------  NORMAL INT28H EXIT, RESET InInt28 FLAG

ExitInt28:      and     TsrMode,not InInt28     ;tell'em we left this code
		iret		            ;we have nothing more to say
OurInt28        endp

;==============================================================================
; NopInt - DUMMY IRET INSTRUCTION USED BY EMPTY INT HANDLERS
;==============================================================================

NopInt:         iret		            ;immediate return

;==============================================================================
; InitPopup - PREPARES SYSTEM FOR POPUP, THEN CALLS Popup, THEN RESTORES
;
; ESTABLISH INTERNAL WORK STACK
; SAVE CPU REGS
; UPDATE InDosClr FLAG WITH CURRENT VALUE OF InDos
; SAVE PROCESS RELATED SYSTEM INFO
; SAVE USER INTERRUPT VECTORS
; INSERT SAFE USER INTERRUPT VECTORS
; CALL POPUP ROUTINE
; RESTORE USER INTERRUPT VECTORS
; RESTORE PROCESS AND SYSTEM INFO
; CLEAR InDosClr FLAG TO PREVENT UNSAFE INT28 CALLs
; RESTORE CPU REGS
;==============================================================================

InitPopup       proc    near
		assume  ds:nothing, es:nothing, ss:nothing

; ------------  SWITCH TO PSP INTERNAL STACK

		mov     OldSS,ss		;save current stack frame
		mov     OldSP,sp
		mov	OldES,es
		mov	OldBP,bp
		mov	OldDS,ds

		cli		             ;always CLI for the old chips
		mov     ss,OurSS		;move SS here
		mov     sp,OurSP		;move SP into position
		mov	es,OurES
		mov	bp,OurBP
		mov	ax,OurDS
		mov	ds,ax
		assume	ds:nothing, es:nothing, ss:nothing
		sti		             ;OK guys

; ------------  SAVE ALL REGS

		push    ax
		push    bx
		push    cx
		push    dx
		push    bp
		push    si
		push    di
		push    ds
		push    es

;               mov     ax,cs
;               mov     ds,ax		   ;mov DS here
;               assume  ds:PGROUP		 ;tell MASM that
;
; ------------  TAG VALUE OF InDos FLAG AT TIME OF POPUP

		or      TsrMode,InDosClr        ;assume InDos=0
		les     si,InDosPtr             ;now, ES:[SI]=InDos
		cmp     byte ptr es:[si],1      ;InDos set? (>2 impossible)
		jb      InDosSaved              ;NO - jump if all clear DOS
		and     TsrMode,not InDosClr    ;clear flag for popup InDos
InDosSaved:

; ------------  SAVE DOS 3.X EXTENDED ERROR INFO

		test    TsrMode,NewDos          ;really DOS 3.x?
		jz      Dos3Saved               ;NO - jump if not 3.x

		mov     ah,59h		  ;to get err info from DOS
		xor     bx,bx		   ;BX must be zero
		push    ds		      ;save DS (killed by DOS)
		int     21h		     ;ext err info in AX,BX,CX
		pop     ds		      ;restore
		mov     OldExtErr[0],ax         ;save
		mov     OldExtErr[2],bx
		mov     OldExtErr[4],cx

Dos3Saved:

; ------------  SAVE CURRENT BREAK STATE, RELAX BREAK CHECKING

		mov     ax,3302h		;to swap DL with BREAK value
		xor     dl,dl		   ;DL=0=relax checking
		int     21h		     ;current level in DL
		mov     OldBreak,dl             ;save current level

; ------------  SAVE CURRENT USER INT VECTORS

		mov     ax,351bh		;BIOS ctrl-break int
		int     21h		     ;ES:BX=vector
		mov     OldInt1BOff,bx          ;save it
		mov     OldInt1BSeg,es

		mov     ax,351ch		;BIOS timer tick
		int     21h		     ;ES:BX=vector
		mov     OldInt1COff,bx          ;save it
		mov     OldInt1CSeg,es

		mov     ax,3523h		;DOS ctrl-C
		int     21h		     ;ES:BX=vector
		mov     OldInt23Off,bx          ;save it
		mov     OldInt23Seg,es

		mov     ax,3524h		;DOS crit err handler
		int     21h		     ;ES:BX=vector
		mov     OldInt24Off,bx          ;save it
		mov     OldInt24Seg,es

; ------------  INSERT DUMMY IRET INTO DANGEROUS VECTORS

		mov     dx,offset NopInt        ;now, DS:DX=dunny iret
		mov     ax,251bh		;BIOS ctrlk-break handler
		int     21h		     ;set to IRET
		mov     ax,251ch		;BIOS timer tick
		int     21h		     ;set to IRET
		mov     ax,2523h		;DOS ctrl-C handler
		int     21h		     ;set to IRET

; ------------  ESTABLISH SAFE CRITICAL ERROR HANDLER

		mov     dx,offset OurInt24      ;now, DS:DX=safe crit err
		mov     ax,2524h		;to set crit err handler
		int     21h

; ------------  SAVE CURRENT DTA AREA, SET OUR DEFAULT DTA

		mov     ah,2fh		  ;to obtain current DTA from DOS
		int     21h		     ;DTA addr now in ES:BX
		mov     OldDTAOff,bx            ;save it
		mov     OldDTASeg,es

		push    ds		      ;save DS for a while
		lds     dx,OurDTA               ;DS:DX=our DTA addr
		mov     ah,1ah		  ;to set DTA via DOS
		int     21h		     ;set that addr
		pop     ds		      ;restore DS

; ------------  SAVE CURRENT PSP, ESTABLISH OURS INSTEAD

		mov     ax,5100h		;to get PSP from DOS
		int     21h		     ;current PSP now in BX
		mov     OldPSP,bx               ;save it
		mov     bx,OurPSP               ;het our PSP instead
		mov     ax,5000h		;to set our PSP
		int     21h

; ------------  CALL USER POPUP ROUTINE

		call    Popup		   ;finally!

; ------------  RESTORE TO SAVED CURRENT PROCESS

		mov     bx,OldPSP               ;new current process in BX
		mov     ax,5000h		;to set PSP via DOS
		int     21h		     ;restore original PSP

; ------------  RESTORE SAVED DTA

		push    ds		      ;save DS for a while
		lds     dx,OldDTA               ;DS:DX=our DTA addr
		mov     ah,1ah		  ;to set DTA via DOS
		int     21h		     ;set that addr
		pop     ds		      ;restore DS

; ------------  RESTORE SAVED INTERRUPT VECTORS

		push    ds		      ;save for a while
		assume  ds:nothing              ;be careful about MASM

		lds     dx,OldInt1B             ;BIOS ctrl-break handler
		mov     ax,251bh
		int     21h

		lds     dx,OldInt1C             ;BIOS timer tick
		mov     ax,251ch
		int     21h

		lds     dx,OldInt23             ;DOS ctrl-C
		mov     ax,2523h
		int     21h

		lds     dx,OldInt24             ;DOS crit err handler
		mov     ax,2524h
		int     21h

		pop     ds		      ;restore data seg DS
		assume  ds:PGROUP

; ------------  RESTORE SAVED BREAK CHECKING LEVEL

		mov     ax,3301h		;to set break check level
		mov     dl,OldBreak             ;get saved break state
		int     21h

; ------------  RESTORE DOS 3.X SPECIFIC SYSTEM INFO

		test    TsrMode,NewDos          ;using DOS 3.x
		jz      Dos3Restored            ;NO - jump if old DOS 2
		mov     dx,offset OldExtErr     ;DS:DX=3 words of ext err
		mov     ax,5d0ah		;to set ext err info
		int     21h
Dos3Restored:

; ------------  RESET InDosSet FLAG VALUE TO PREVENT UNSAFE INT28

		or      TsrMode,InDosClr        ;now we only care that InDos=0

; ------------  RESTORE USER REGS

		pop     es
		pop     ds
		pop     di
		pop     si
		pop     bp
		pop     dx
		pop     cx
		pop     bx
		pop     ax
		assume  ds:nothing

; ------------  RETURN TO USER STACK

		cli		             ;always CLI for the old chips
		mov     ss,OldSS		;restore SS
		mov     sp,OldSP		;restore SP
		mov	es,OldES
		mov	bp,OldBP
		mov	ds,OldDS
		assume	ss:nothing, es:nothing, ds:nothing
		sti		             ;OK guys

		ret
InitPopup       endp

;==============================================================================
; Popup - POPUP USER ROUTINE
;
; ALL REGISTERS EXCEPT SS:SP AND DS MAY BE CHANGED.
; DS IS PRESET TO THE TSR DATA SEGMENT.
;
; NOTE: UPON ENTRY TO THIS ROUTINE ALL DOS FUNCTIONS MAY BE CALLED.
;       IF POPUP WAS DONE ON INT28, WITH CritErr==1, ALL DOS FUNCTIONS
;       THAT WOULD NORMALLY USE THE CONSOLE STACK, WILL GO TO THE CRITICAL
;       STACK, HENCE PREVENTING FURTHER POPUP DURING THE DOS CALL.
;       (HOWEVER, MOST TSRs WOULD NOT POPUP ANYWAY, SINCE InDos==2).
;
;       ADDRESSES OF THE InDos AND CritErr ARE STORED IN THE DOUBLE WORDS
;       InDosPtr AND CritErrPtr.
;
;       AT ENTRY CritErr FLAG IS 0 (ZERO), InDos NO GREATER THAN 1 (ONE).
;==============================================================================

Popup           proc    near
		assume  ds:PGROUP, es:nothing, ss:nothing

		mov	MinLeft,0		; turn off alarms
		push	ds

		cli				; for old chips
		mov     ss,OurSS
		mov	es,OurES
		mov	bp,OurBP
		mov	ax,DSLattice
		mov	ds,ax
		assume	ds:nothing, ss:nothing, es:nothing
		sti				; ok

		call	cpopup

		pop	ds
		assume	ds:PGROUP
		ret
Popup           endp

;==============================================================================
; NON-RESIDENT MESSAGES FOR INIT
;==============================================================================

BannerMsg       label   byte
db      13,10
db      '<<<<<<  TSR INSTALLED  >>>>>>',13,10
db      '$'

SecondMsg       label   byte
db      'VA already loaded.',13,10
db      '$'

HotKeyMsg       label   byte
db      'Hit <Left Shift> <Right Shift> to pop up!',13,10,10
db      '$'

Dos1Msg label   byte
db      'OOPS!',7,13,10
db      'Must use DOS release 2.00 or later!',13,10,10
db      '$'

BadDosMsg       label   byte
db      'OOPS!',7,13,10
db      'Did not recognize DOS version!',13,10,10
db      '$'

; ------------  DOS ERROR LEVEL EXIT CODES

xOk             equ     0		       ;normal, OK exit
xSecond         equ     1		       ;TSR already loaded
xBadDos         equ     2		       ;CritErr flag not found

;==============================================================================
; Init - INITIALIZE TSR APPLICATION, ENTERED UPON DOS LOAD
;
; DISPLAY BANNER, INITIALIZE SYSTEM DATA, CHECK IF ALREADY LOADED,
; HOOK INTO INTERRUPT CHAIN, TERMINATE, BUT STAY RESIDENT.
;==============================================================================

;Init            proc    near
tsr		proc	near
		assume  ds:nothing, es:nothing, ss:nothing

; ------------  SAVE STUFF FOR RETURNING

		mov	OurSP,sp
		mov     OurSS,ss
		mov	OurES,es
		mov	OurBP,bp

		push	bp
		push	ds
		assume	ds:nothing
		mov	DSLattice,ds	; save DS for later in popup()

		mov     ax,cs
		mov     ds,ax		; mov DS here
		assume  ds:PGROUP	; tell MASM that
		mov	OurDS,ds

		mov     dx,offset BannerMsg
		mov     ah,9
		int     21h		     ;display programme banner

; ------------  USE INT16H DIAGNOSTIC TO SEE IF TSR ALREADY INSTALLED

		mov     ax,GetId		;INT16h diagnostic request
		int     16h		     ;now, AX=MyId if installed
		cmp     ax,MyId		 ;TSR already installed?
		jne     CheckDos		;NO - jump if not installed

; ------------  TSR ALREADY INSTALLED, DISPLAY MSG, EXIT

		mov     dx,offset SecondMsg
		mov     ah,9
		int     21h		     ;display alr installed msg
		mov     dx,offset HotKeyMsg
		mov     ah,9
		int     21h		     ;be kind & disp hot key
		mov     ax,4c00h + xSecond      ;error level in AL
		int     21h		     ;abot now

; ------------  IDIOT IS RUNNING DOS 1, LEAVE THE OLD FASHION WAY!

Dos1:           mov     dx,offset Dos1Msg
		mov     ah,9
		int     21h		     ;display msg about DOS 1
		int     20h		     ;no err level for DOS 1

; ------------  ENSURE DOS VERSION IS NEWER THAN 2.00

CheckDos:       or      TsrMode,NewDos          ;assume using DOS 3.x
		mov     ah,30h		  ;to get DOS version number
		int     21h		     ;version is AL.AH
		cmp     al,2		    ;release 2 or newer?
		jb      Dos1		    ;NO - jump if DOS 1 in use
		ja      DosFlags		;jump if DOS 3.x
		and     TsrMode,not NewDos      ;now, say we use DOS 2.x

; ------------  INITIALIZE PTRS TO DOS FLAGS - 1ST InDos

DosFlags:       mov     ax,3400h		;to get InDos ptr
		int     21h		     ;ES:BX=seg:off of InDos
		mov     InDosOff,bx             ;save ptr
		mov     InDosSeg,es

; ------------  WE NEED CritErr TO USE PSP FUNCTIONS IN DOS 2.X (CHIPs WAY)

		xor     dl,dl		   ;DL=0=this is 1st scan
		mov     CritErrSeg,es           ;DOS seg still in ES
CritScan:       mov     di,bx		   ;start search at InDos
		mov     cx,2000h		;search max 1000h words
		mov     ax,3e80h		;opcode CMP BYTE PTR [CritErr]
		cld		             ;better serach forward

CritScan2:      repne   scasw		   ;search till found or end
		jne     NoCritFound             ;jump if CMP not found
						;ES:[DI-2] at:
						;       CMP BYTE PTR [CritErr]
						;       JNZ ...
						;       MOV SP,stack addr
		cmp     byte ptr es:[di][5],0bch ;really CMP SP there?
		jne     CritScan2               ;NO - scan again if not
		mov     ax,word ptr es:[di]     ;now, AX=CritErr offset
		mov     CritErrOff,ax           ;save it
		jmp     short InitData          ;OK to end this now

NoCritFound:    or      dl,dl		   ;was this1 st scan?
		jnz     BadDos		  ;NO - CritErr not founbd at all
		inc     dl		      ;DL=1=this is 2nd scan
		inc     bx		      ;try scan at odd/even offset
		jmp     CritScan		;scan again

; ------------  COULD NOT LOCATE DOS CritErr FLAG - THAT'S AN ERROR

BadDos:         mov     dx,offset BadDosMsg
		mov     ah,9
		int     21h		     ;display msg about that
		mov     ax,4c00h + xBadDos      ;err level in AL
		int     21h		     ;OK to use 4C (DOS >= 2)

; ------------  INITIALIZE SYSTEM DATA VARIABLES

InitData:				       ;store position for stack

		mov     ax,5100h		;to get current PSP from DOS
		int     21h		     ;PSP now in BX
		mov     OurPSP,bx               ;save our PSP

		mov     ah,2fh		  ;to get current DTA from DOS
		int     21h		     ;now, ES:BX=current DTA
		mov     OurDTAOff,bx            ;save it
		mov     OurDTASeg,es

		and     KeyMode,not HotIsShift  ;hotkey is not shift state
		or      TsrMode,InDosClr        ;will prevent unsafe INT28s

; ------------  SAVE VECTORS FOR OUR MONITOR INTERRUPTS

		mov     ax,3508h		;BIOS timer0 tick handler
		int     21h		     ;ES:BX=vector
		mov     OldInt08Off,bx
		mov     OldInt08Seg,es

		mov     ax,3509h		;BIOS kb HW handler
		int     21h		     ;ES:BX=vector
		mov     OldInt09Off,bx
		mov     OldInt09Seg,es

		mov     ax,3513h		;BIOS disk I/O service
		int     21h		     ;ES:BX=vector
		mov     OldInt13Off,bx
		mov     OldInt13Seg,es

		mov     ax,3516h		;BIOS kb read
		int     21h		     ;ES:BX=vector
		mov     OldInt16Off,bx
		mov     OldInt16Seg,es

		mov     ax,3521h		;DOS functions dispatcher
		int     21h		     ;ES:BX=vector
		mov     OldInt21Off,bx
		mov     OldInt21Seg,es

		mov     ax,3528h		;DOS idle hook
		int     21h		     ;ES:BX=vector
		mov     OldInt28Off,bx
		mov     OldInt28Seg,es

; ------------  ESTABLISH IRET INT23 TO PREVENT BREAK DURING VECTOR FIX

		mov     dx,offset NopInt        ;DS:DX=dummy vector to set
		mov     ax,2523h		;to set ^C handler through DOS
		int     21h		     ;now, no break will occur

; ------------  SAVE VECTORS FOR OUR MONITOR INTERRUPTS

		mov     ax,2508h		;to set our INT08h handler
		mov     dx,offset OurInt08      ;DS:DX=new vector
		int     21h		     ;let DOS set vector

		mov     ax,2509h		;to set our INT09h handler
		mov     dx,offset OurInt09      ;DS:DX=new vector
		int     21h		     ;let DOS set vector

		mov     ax,2513h		;to set our INT13h handler
		mov     dx,offset OurInt13      ;DS:DX=new vector
		int     21h		     ;let DOS set vector

		mov     ax,2516h		;to set our INT16h handler
		mov     dx,offset OurInt16      ;DS:DX=new vector
		int     21h		     ;let DOS set vector

		mov     ax,2521h		;to set our INT21h handler
		mov     dx,offset OurInt21      ;DS:DX=new vector
		int     21h		     ;let DOS set vector

		mov     ax,2528h		;to set our INT28h handler
		mov     dx,offset OurInt28      ;DS:DX=new vector
		int     21h		     ;let DOS set vector

; ------------  DISLAY MSG ABOUT HOW WELL THIS IS ALL RUNNING

		mov     dx,offset HotKeyMsg
		mov     ah,9
		int     21h		     ;disp hot key

; ------------  RETURN TO LATTICE-C

		pop	ds
		assume	ds:nothing
		pop	bp
		ret

tsr		endp

PROG		ends
		end


FILE: IBM.C
#include	"va.h"
#include	"vadef.h"
#include	"edit.h"

#if MSDOS & LATTICE

#define	CDCGA	0			/* color graphics card		*/
#define	CDMONO	1			/* monochrome text card		*/

/* getboard:	Determine which type of display board is attached.
		Current known types include:

		CDMONO	Monochrome graphics adapter
		CDCGA	Color Graphics Adapter
		CDEGA	Extended graphics Adapter
*/

/* getboard:	Detect the current display adapter
		if MONO		set to MONO
		   CGA		set to CGA
		   EGA		set to CGA
*/

	int boardSEG;	/* Segment of screen memory */
static	int mode;	/* mode of screen image */
static	int xcursor;	/* xcoord. of cursor */
static	int ycursor;	/* ycoord. of cursor */
static	int page;	/* display page nr */
static	int curch;	/* cursor h value */
static	int curcl;	/* cursor l value */
static	byte screen[16384];	/* old screen */
static	byte lowmem[30];	/* 0000:0449h 30 bytes video stuff */

int getboard()
{	union REGS rg;

	int type;	/* board type to return */

	type = CDCGA;
	int86(0x11, &rg, &rg);
	if ((((rg.x.ax >> 4) & 3) == 3))
		type = CDMONO;

	switch (type) {
		case CDCGA:
			boardSEG = 0xb800;
			break;
		case CDMONO:
			boardSEG = 0xb000;
			break;
	}
}/*getboard*/

getpage()
{	union REGS rg;

	rg.h.ah = 0xf;
	int86(0x10,&rg,&rg);	/* get current display page and mode */
	page = rg.h.bh;
	mode = rg.h.al;
}/*getpage*/

putpage()
{	union REGS rg;

	/* check mode only if diff then set */
	rg.h.ah = 0xf;
	int86(0x10,&rg,&rg);
	if (rg.h.al == mode) {
		/* nothing */
	} else {
		rg.h.ah = 0;
		rg.h.al = mode;
		int86(0x10,&rg,&rg);	/* set mode */
	}

	/* set display page if different */
	rg.h.ah = 0xf;
	int86(0x10,&rg,&rg);
	if (rg.h.bh == page) {
		/* nothing */
	} else {	
		rg.h.ah = 0x5;
		rg.h.al = page;
		int86(0x10,&rg,&rg);	/* set active page */
	}
}/*putpage*/

putcursor()
{	union REGS rg;

	rg.h.ah = 0x1;
	rg.h.ch = curch;
	rg.h.cl = curcl;
	int86(0x10,&rg,&rg);	/* set cursor size */

	rg.h.ah = 0x2;
	rg.h.bh = page;
	rg.h.dh = ycursor;
	rg.h.dl = xcursor;
	int86(0x10,&rg,&rg);	/* set cursor position */
}/*putcursor*/

getcursor()
{	union REGS rg;

	rg.h.ah = 0x3;
	rg.h.bh = page;
	int86(0x10,&rg,&rg);	/* get cursor position and size */
	curch = rg.h.ch;
	curcl = rg.h.cl;
	xcursor = rg.h.dl;
	ycursor = rg.h.dh;
}/*getcursor*/

/* getlowmem*/
getlowmem()
{
	peek(0,0x449,lowmem,30);
}/*getlowmem*/

/* putlowmem */
putlowmem()
{
	poke(0,0x449,lowmem,30);
}/*putlowmem*/

/* copy current screen into screen[] */
pushscreen()
{
	getlowmem();
	getboard();
	peek(boardSEG,0,screen,16384);
	getpage();	/* get display page and mode */
	getcursor();
}/*getscreen*/

/* fill current screen with contents of screen[] */
popscreen()
{
	putpage();	/* put display page and mode */
	putcursor();	
	poke(boardSEG,0,screen,16384);
	putlowmem();
}/*putscreen*/

/* called from note with empty note, we must insert original screen */
insscreen()
{	register int	r,c;
	register char *ptr,*lptr;
	int	ch,len;

	switch (mode) {
		case 0:
		case 1:
			len = 40;
			break;
		case 2:
		case 3:
		case 7:
			len = 80;
			break;
		default:
			TTbeep();
			return;
	}
	ptr = screen;
	for (r=0; r<25; r++) {
		for (c=0; c<len; c++) {
			ch = *ptr;
			ptr += 2;
			/* blank out non printables */
			if (ch =='\r') ch = ' ';
			if ( (ch < ' ') || (ch > '~') ) ch = ' ';
			inschar(ch);
		}
		/* take of trailing spaces */
		lptr = &(editroot->curline->line[len-1]);
		for (c=len-1; c>=0; c--) {
			if (*lptr != ' ') break;
			(editroot->curline->length)--;
			*lptr = '\0';
			lptr--;
		}
		goeol();
		inschar('\r');
	}
}/*insscreen*/
#endif