⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 gwaevt.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
	PAGE	56,132
	TITLE	GWAEVT Advanced Event Trapping Handler
;***
; GWAEVT Advanced Event Trapping Handler
;
;	Copyright <C> 1986, Microsoft Corporation
;
;Purpose:
;
; BASIC Syntax mapping to included runtime entry points:
;
;
; - ON COM(n) Statement:
;
;      ON COM(n) GOSUB line
;      --------------------
;		|
;	      B$ONCA
;
; - ON SIGNAL(n) Statement:
;
;      ON SIGNAL(n) GOSUB line
;      -----------------------
;		|
;	      B$ONSG
;
; - ON KEY(n) Statement:
;
;      ON KEY(n) GOSUB line
;      --------------------
;		|
;	      B$ONKA
;
; - ON MOUSE(n) Statement:
;
;      ON MOUSE(n) GOSUB line
;      --------------------
;		|
;	      B$ONMO
;
; - ON UEVENT Statement:
;
;      ON UEVENT GOSUB line
;      --------------------
;		|
;	      B$ONUE
;
; - ON PEN Statement:
;
;      ON PEN GOSUB line
;      -----------------
;	       |
;	     B$ONPA
;
; - ON PLAY(n) Statement:
;
;      ON PLAY(n) GOSUB line
;      ---------------------
;		|
;	      B$ONLA
;
; - ON STRIG(n) Statement:
;
;      ON STRIG(n) GOSUB line
;      ----------------------
;		|
;	      B$ONSA
;
; - ON TIMER(n) Statement:
;
;      ON TIMER(n) GOSUB line
;      ----------------------
;		|
;	      B$ONTA
;
;******************************************************************************
	include switch.inc
	INCLUDE rmacros.inc	; Runtime Macro Defintions

	useSeg	_BSS		; Uninitailzed data
	useSeg	_DATA		; Initialized data
	useSeg	EV_TEXT 	; Event handler code
	useSeg	RT_TEXT 	; Runtime Core
	useSeg	ER_TEXT 	; Errors
	UseSeg	INIT_CODE	
	UseSeg	<XIB>		; XIB and XIE must bracket XI!
	UseSeg	<XI>		; initializer segment
	UseSeg	<XIE>		

	INCLUDE seg.inc 	
	INCLUDE baslibma.inc
	INCLUDE intmac.inc
	include event.inc	; oem interface
	include queues.inc	;get queue stuff
	include stack.inc	
	INCLUDE compvect.inc	
	include idmac.inc	

INITIALIZER	B$x?EVTDSPINI	

sBegin	_DATA			
	staticB b$EVTFLG,0	; event occurred flag
	globalW B$PollDispTable,0,NUM_TRAPDEV ;Dispatch table for polling.
					      ;One word per trappable dev.
					      ;Address of B$POL* routine
					      ;for that device if used,
					      ;else zero.
	externB	b$EventFlags	; misc event flags. bits def in CONST.INC

	externD b$run_disp	
	externD b$clr_disp	

	externW	b$pInitKeys1	
	externW	b$pInitKeys2	
	externW	b$pTrapEvent	

sEnd	_DATA			

sBegin	_BSS			

	externW b$cNonQBIFrames ; non qbi frame count

	externW b$cCSubs	; compiler nested sub level
	externD b$EVTRETV	;defined in RTINIT.ASM
	externB	b$inonerr	; defined in RTINIT.ASM
	externW b$TRPTBL	;defined in GWCEVT.ASM
	externW b$TRAP_QUE	;defined in GWCEVT.ASM
	externB b$TRAP_SEM	;defined in GWCEVT.ASM

staticW TRPCUR,,1		; Current trap table address

sEnd	_BSS			

;#*****************************************************************************

	externFP B$IEvSet	;interp routine to set BOS EV flag
	externFP B$IEvReset	;interp routine to reset BOS EV flag
	externFP B$IEvHandler	;interp routine to do event GOSUB
	externFP B$EnsShowOutputScr ;displays output screen
sBegin	RT_TEXT 		
	externFP B$FRAMESETUP	; Set up runtime frame
	externNP B$NearRet	
sEnd	RT_TEXT 		

sBegin	ER_TEXT 		
	externNP B$FrameAFE	; advanced feature error + frame setup
	externNP B$ERR_DNA	; device not available error
	externNP B$ERR_FC	
sEnd	ER_TEXT 		

sBegin	EV_TEXT			; EV_TEXT externals go here

	externNP B$FreeTrap	
	externNP B$StopTrap	
	externNP B$ResetTrap	
	externNP B$OffTrap	
	externNP B$OnTrap	
	externNP B$SetChk	
	externNP B$TrapAddr	
	externNP B$SetContext	;Set context bit in event flags

sEnd	EV_TEXT			

sBegin	INIT_CODE		
assumes	CS,INIT_CODE		

;*** 
;B$x?EVTDSPINI - Make sure event vectors get initialized when necessary.
;
;Purpose:
;	Make sure that event vectors are initialized if events are linked in.
;	Initializes RUN and CLEAR time event dispatch vectors to B$?EVT.
;	Also initializes [b$EVTRETV] vector to B$EVTRET.
;
;Entry:
;	None.
;
;Exit:
;	Appropriate dispatch vectors filled.
;	Sets [b$EVTRETV] to B$EVTRET.
;	Sets [b$pTrapEvent] to B$TrapEvent.
;
;Uses:
;	Per convention.
;
;Exceptions:
;	None.
;
;******************************************************************************
cProc	B$x?EVTDSPINI,<FAR>	
cBegin				; set run and clear init vectors to B$?EVT
	MOV	AX,SEG EV_TEXTBASE ; load EV_TEXT segment into AX
	MOV	WORD PTR [b$run_disp].EV_RVEC,EV_TEXTOFFSET B$?EVTN ; offset
	MOV	WORD PTR [b$clr_disp].EV_CVEC,EV_TEXTOFFSET B$?EVTN ; offset
	MOV	WORD PTR [b$EVTRETV],EV_TEXTOFFSET B$EVTRET ; offset
	MOV	WORD PTR [b$EVTRETV+2],AX ; segment
	MOV	b$pTrapEvent,EV_TEXTOFFSET B$TrapEvent ; for LLSND, LLCOMx.
cEnd				
sEnd	INIT_CODE		

sBegin	EV_TEXT 		
assumes CS,EV_TEXT		

	SUBTTL	TRAP ROUTINES - INIT
;***
; B$?EVT
;
; Purpose:
;  Runtime Entry Point for /O if /V or /W in effect in any module.
;  Always a Runtime Entry Point for non-/O and for EI_QB.
;  Clears Event Trap Table, clears GOSUB dispatch buffer, and initializes
;  keyboard trapping.
;
; Input:
;  NONE
;
; Output:
;  NONE
;
;******************************************************************************
cProc	B$?EVT,<FAR,PUBLIC>,<ES,SI,DI> 
cBegin				
	PUSH	DS		
	POP	ES		;Set ES = DS
	MOV	DI,OFFSET DGROUP:b$TRPTBL

;	Each entry in b$TRPTBL is 5 bytes.  The first byte is a flag byte
;	that must be inited to zero.  The next 4 bytes are the GOSUB address
;	and must be inited to -1 (to indicate no trap handler).

	MOV	CX,NUM_TRAPS	; count of 5-byte entries in b$TRPTBL
IniTrpTblLoop:			
	XOR	AX,AX		; start with zero each time through loop
	STOSB			; Set flag byte to 0
	DEC	AX		; Get a -1
	STOSW			; 2nd and 3rd bytes = -1
	STOSW			; 4th and 5th bytes = -1
	LOOP	IniTrpTblLoop	; keep going until entire table inited


	MOV	[b$TRAP_SEM],CL ;Set no Events in process
	MOV	SI,OFFSET DGROUP:b$TRAP_QUE ;init event gosub dispatch tbl
	mov	ax,(NUM_TRAPS+1)*2  ; room for event dispatches
	MOV	BX,OFFSET DGROUP:b$TRAP_QUE+QUE_HEADER_SIZE
	CALL	B$INITQ		;Init queue descriptor

	STI
	MOV	AL,DISABLE_TRAP ; to disable ctrl-break trapping
	CALL	[b$pInitKeys1]	; Init some keytrapping stuff
	CALL	[b$pInitKeys2]	; Init some more keytrapping stuff
cEnd				

;***
; B$?EVTN
;
; Purpose:
;  Near entry to B$?EVT.
;  Added with [52]
;
; Input:
;  NONE
;
; Output:
;  NONE
;
;******************************************************************************
cProc	B$?EVTN,<NEAR>
cBegin
	call	B$?EVT
cEnd

	SUBTTL Stack for event traps
	PAGE
;Stack for event dispatches in different environments. The notation X->Y means
;that the executing context was X (I for interp, C for comp), and
;->Y means that control was transfered to context Y. SC, DC and RC are
;abbreviations for Source Context, Destination Context, and Runtime Context.
;
;Pushed
;  By  C->C	       I->C			C->I		 I->I
;----  +-----------------------------+	 High	+-----------------------------+
;      |	      |Interp context|	  ^	|	       |Interp context|
; SC   |Far ret addr  |Far ret addr  |	  |	|Far ret addr  |Far ret addr  |
;----  |--------------|--------------|	  |	|--------------|--------------|
;      |Context flag  |Context flag  |	STACKS	|Context flag  |Context flag  |
; RC   |Trap tabl addr|Trap tabl addr|	  |	|Trap tabl addr|Trap tabl addr|
;----  |--------------|--------------|	  |	|--------------|--------------|
;      |Compiler frame|Compiler frame|	  |	|Interp frame  |Interp frame  |
; DC   |Zero	      |Zero	     |	  v	|Zero(?)       |Zero(?)       |
;----  +-----------------------------+	 Low	+-----------------------------+

;Note that the context flag is pushed on the stack even in the COMPILER ONLY
;environment to keep the event frame size the same for all environments.

	SUBTTL Event dispatch execution path
	PAGE
;The flow of control is as follows:
;
;Compiled Code (CC)	 Common runtime (RT)	   Interpreted Code (IC)
;==================	 ===================	   =====================
;
;+------------------------+		       +------------------------------+
;|CC ACTIVE AT EV DISPATCH|		       | IC ACTIVE AT EV DISPATCH     |
;|Comp calls B$EVCK	  |------>+<-----------+ interp detects BOS event flag|
;+------------------------+	  |	       | interp saves context on stack|
;				  |	       | interp calls B$EVCK	      |
;				  v	       +------------------------------+
;		     +--------------------------------+
;		     |	 B$EVCK detects trap request |
;		     |	 if last event in Q,	      | 	+------------+
;		     |	    RT calls interp to	      +<= = = =>+Reset BOS EV|
;		     |	    reset BOS flag	      | 	|FLAG	     |
;		     |	 pushes context flag	      | 	+------------+
;		     |	 pushes trap table address    |
;		     |----------------+---------------|
;		     |if CC handler   |if IC handler  |
;		     | inc contxt flag| 0 context flag|
;*Done for compiler* | builds CC frame| jmps to interp|
;*by the runtime   * | pushes 0 for   |   with ptr to |
;		     |	 B$RETA      |   handler     |
;		     | jmps to CC addr|   context     |
;		     |	 in trap table| 	      |
;		     +--------+--------------+--------+
;+-----------------------+    | 	     |	     +------------------------+
;|   CC EVENT HANDLER	 |    | 	     |	     |	  IC EVENT HANDLER    |
;|handler executes	 |<---+ 	     |	     |interp builds frame     |
;|CC calls B$RETA	 |--------+	     +------>|handler executes	      |
;+-----------------------+	  v		     |interp tears down frame |
;			+--------------------------+ |interp JMPS to B$EVTRET|
;* Done for compiler *	|B$RETA determines EV ret | +----------+-------------+
;*		     *	|tosses return address	   |		|
;*		     *	|cleans off frame	   |		|
;* by the runtime    *	|Runtime JMPS to B$EVTRET |		|
;			+---------+----------------+		|
;				  +<----------------------------+
;				  v
;			+--------------------------+
;			|B$EVTRET		   |
;			|recovers trap table addr  |
;			|recovers context flag	   |
;			|restarts event 	   |
;			|return untrapped brk flag |
;			|returns to caller	   |
;			+---------+----------------+
;+-------------------+		  |		     +------------------------+
;|Comp code continues|<-----------+----------------->|interp BOS proc recovers|
;|execution	     |				     |context and continues   |
;+-------------------+				     +------------------------+
;
	SUBTTL	B$POLLEV/Description of event trapping
	PAGE
;***
;B$POLLEV - Check if a trapable event has occured.
;	 Defunct routine, but the comments are nice.
;Purpose:
;
;      Poll to determine if a trapable event has taken place.
;	 Trapable events are:
;	   data placed in keyboard queue
;	   data placed in any RS232 queue
;	   RS232 error - timeout etc.
;	   light pen
;	   joy stick trigger
;	   music events
;	   timer events
;
;Event and Trapping Mechanisms:
;
;	All events, no matter what generates them, are handled in
;	the same way.  When the event occurs, it will either cause
;	a routine to be called or will be tested by a routine.	This
;	routine will set two different flags.  The first flag that
;	is set is b$EVTFLG.  This flag indicates that at least one
;	event has taken place.	It does not keep track if multiple
;	events have occured since events were last tested or not.
;	At the appropriate time (either after every statement or
;	after every line) the flag will be tested.  If it indicates
;	that an event has taken place, the flag will be cleared and
;	all trappable items will be polled to see if they have an
;	outstanding event.
;
;	The second flag that is set at the time of the event is
;	one that is local to the item that has the event.  This
;	is needed so that each item can properly give its status
;	when it is polled.  Note that polling an individual item
;	will not change the global event flag.
;
;	If for some reason your machine can not suport the global
;	event trapping, always set the flag to indicate that an
;	event has taken place.	Thus, at the end of each statement,
;	the OEM-independent code will poll each of the individual
;	items for its status.  This will produce a degradation in
;	execution time, however.
;
;******************************************************************************

	SUBTTL	B$EVCK - New Stmt Event Trap Dispatch Handler
	PAGE
;***
; B$EVCK - New Stmt Event Trap Dispatch Handler
;
;Purpose:
; Event trap dispatcher. Pass thru here on each new statement. Process Event
; trap if event Enabled and Requested.
;
;Entry:
; None
;
;Exit:
; GOSUBs to event handler, if so indicated.
; [AL] = non-zero if untrapped ctl-Break has been hit (QB only)
; [AH] = non-zero if event was handled (QB only)
;
;******************************************************************************
cProc	B$EVCK,<PUBLIC,FAR>	
cBegin
	XOR	AX,AX		; a Zero to switch with
	XCHG	[b$EVTFLG],AL	; get and reset trapable event flag
	OR	AL,AL		; trapable event occured?

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -