📄 gwaevt.asm
字号:
JZ NoPolling ; brif not -- don't bother to check traps
MOV SI,OFFSET DGROUP:B$PollDispTable ;point to dispatch table
MOV CX,NUM_TRAPDEV ;number of entries in table
PollLoop:
LODSW ;get next address from table
OR AX,AX ;is entry zero?
JZ SkipCall ;yes, don't try to call it
PUSH CX ;preserve counter across call
CALL AX ;call the poll routine
POP CX ;restore counter
SkipCall:
LOOP PollLoop ;keep going until done
NoPolling:
TEST [b$TRAP_SEM],0FFh ;(faster than CMP)
JNZ TRAP_OEIP ;Brif events
IgnoreIt:
CALL QBEvReset ;Reset interp event flag if neccessary
XOR AH,AH ;event not handled
RET
TRAP_OEIP:
TEST [b$inonerr],0FFh ; Are we in ON ERROR routine?
JNZ IgnoreIt ; brif so -- ignore event
MOV SI,OFFSET DGROUP:b$TRAP_QUE ;get next enabled request
CALL B$GETQ
mov ah,al
CALL B$GETQ
JZ IgnoreIt ; don't process if queue underflow
MOV [TRPCUR],AX ; Save current trap address
mov bx,ax ;[bx]= trap table event addr
XOR SI,SI
CALL B$FreeTrap ;Free Trap Request
CALL B$StopTrap ;Put STOP on Trap
CALL QBEvReset ;Reset interp event flag if neccessary
CALL B$EnsShowOutputScr ;Make sure output screen is active
PUSH b$cCSubs
PUSH BX ;save trap table index
TEST BYTE PTR[BX],TRP_CN ;Is compiler handler active?
JZ CompHandler ;brif so
MOV b$cCSubs,0 ;set interpreted code active
INC BX ; [BX] = ptr to interp handler context
JMP B$IEvHandler ;let interp handle gosub (DOESN'T RETURN)
CompHandler:
MOV DX,[BX+3]
MOV AX,[BX+1] ; [DX:AX] = Trap routine address
cCall B$FRAMESETUP ; Set up the frame
INC WORD PTR [BP].FR_GOSUB ; set gosub count to 1
MOV BX,[TRPCUR] ; Get current trap table address again
INC b$cNonQBIFrames ;bump count of NonQBIframes
XOR AX,AX
PUSH AX ;Push a 00 so RETURN works right
jmp dword ptr[BX+1] ;GOSUB the Trap routine...
cEnd nogen
;***
; QBEvReset - Checks for more trappable events
;
;Purpose:
; Added as part of [19].
; Checks for more queued events. If none, resets QB Event flag.
; It also returns value of b$EventFlags & CNTLC, indicating if untrapped
; Ctl-Break has occurred.
;
;Entry:
; None.
;Exit:
; AX - non-zero if untrapped Ctl-Break has occurred.
;Uses:
; None.
;Exceptions:
; None.
;****
cProc QBEvReset,<NEAR>
cBegin
CLI
XOR AX,AX
CMP [b$TRAP_SEM],AL ;any more events queued?
JNZ MoreEvents ;brif so
CMP [b$EVTFLG],AL ;any events happen since last check?
JNZ MoreEvents ;brif so
CALL B$IEvReset ;reset interpreter BOS flag for events
MoreEvents:
STI
MOV AL,b$EventFlags ; get untrapped break flag
AND AX,CNTLC ; mask out all bits but CNTLC, & clear AH
cEnd
;***
;B$IFindEvHandler - Finds requested event handler context.
;
;Purpose:
; Added as part of revision [24].
; Entry point for QBI Scanner to find QBI context information
; for an event handler. This routine searches for the event
; table for the closest "handler offset" for the requested
; "segment". Note: the seg:off for the interpreter really map
; to an oRs:oTx pair which defines the event handler.
; When a handler matching the specified "segment" is found,
; the entry will be marked as processed by placing FFFF in the
; offset part of the handler context.
;Entry:
; Seg - requested "Segment" to search for in event table.
;Exit:
; AX - smallest "offset" found for requested "segment".
; 0FFFFH if not found.
; DX - DGROUP address of Event table entry.
; Marks processed entries with 0FFFFH.
;Uses:
; Per convention.
;Exceptions:
; None.
;******************************************************************************
cProc B$IFindEvHandler,<PUBLIC,FAR>,<SI,DI>
parmW EvSeg
cBegin
MOV SI,OFFSET DGROUP:b$TRPTBL ;SI = points to event trap table
MOV CX,NUM_TRAPS*5 ;CX = size of trap table
XOR DI,DI ;DI = points to smallest so far
MOV DX,0FFFFH ;DX = smallest
; Walk the event table, looking for QB entries with matching segments
; Return the offset of the smallest such entry, or FFFF if none.
EvFindLoop:
LODSB ;get context byte
XCHG AX,BX ;BL = context byte
LODSW ;AX = Handler offset
TEST BL,TRP_CN ;see if QBI handler
JZ EvFindSkip ;brif not
MOV BX,[SI] ;BX = Handler Seg
CMP BX,EvSeg ;Segment of handler match search seg?
JNZ EvFindSkip ;skip entry if not
CMP AX,DX ;is Handler offset smallest?
JAE EvFindSkip ;brif not
; Table entry is smallest so far encountered. Remember value and address
MOV DI,SI ;point to it.
XCHG DX,AX ;remember lowest so far
EvFindSkip:
LODSW ;skip seg
SUB CX,4
LOOP EvFindLoop ;process next table entry
OR DI,DI ;did we find one?
JZ NoMatch ;brif not
MOV AX,DI ;AX = address of table entry
DEC AX ;back up to point at "offset"
DEC AX
NoMatch:
XCHG AX,DX ;return lowest match in AX addr in DX
cEnd
;***
; B$EVTRET - Return from event trap routine
;
;Purpose:
; Reset STOPped bit, if trap ON, and restore frame pointer to previous frame.
;
;Entry:
; [BX] = Trap table address
; top of stack contains long return address
;
;Exit:
; [AH] = non-zero if event was handled.
; [AL] = non-zero if an untrapped ctrl-break has occurred.
;
;Uses:
;
;Preserves: (optional)
;
;Exceptions:
;
;******************************************************************************
cProc B$EVTRET,<FAR,PUBLIC>
cBegin
CMP [b$cCSubs],0 ;are we returning from a compiled event?
JZ QBIEvRet ;brif not
DEC b$cNonQBIFrames ;adjust count of NonQBIframes
QBIEvRet:
POP BX ;recover trap table address
POP [b$cCSubs] ;Recover context flag
TEST BYTE PTR [BX],TRP_ON ; Is Trap ON?
JZ TRAPRETX ; Brif not.
CALL B$ResetTrap ; else Reset Stopped bit.
TRAPRETX:
MOV AX,0FFh SHL 8 + CNTLC ; return event handled (AH = -1)
AND AL,b$EventFlags ; return whether or not Break has occurred
; (bit CNTLC of b$EventFlags)
cEnd
SUBTTL ON Event GOSUB Statement handler
PAGE
;***
; B$ONCA, B$ONKA, B$ONPA, B$ONLA, B$ONSA, B$ONTA, B$ONSG, B$ONMO, B$ONUE
;
; Syntax: ON [Event] GOSUB line no.
;
; WHERE:
; Event: Arg: traps:
; COM(x) x in [1..NUM_RS232] COM [1..NUM_RS232]
; PEN Light pen.
; STRIG(x) x = <0|2> Trigger <A|B>
; KEY(x) x in [1..NUM_TKEYS] Soft/Cursor/User defined keys
; PLAY(x) x in [1..32] size(music-q) drops below x
; TIMER(n) n in [1..86400] every n seconds
; SIGNAL(n) n in [1..7] DOS signal n
; MOUSE(n) n in [1..5] MOUSE function n
; UEVENT User defined event
;
; Entry:
; parm1 = TIMER: A 4-byte integer. [23]
; PEN: Far ptr to event handler subroutine [23]
; UEVENT: Far ptr to event handler subroutine [40]
; All Others: A 2-byte integer. [23]
; parm2 = Far ptr to event handler subroutine (except for PEN) [23]
;
; Exit:
; The event trap address is saved.
;
;******************************************************************************
;#*****************************************************************************
;
; for those with a single word parameter:
;
cProc B$ONFUN,<FAR,PUBLIC>
parmW placeHolder ; ensure generated exit code matches entries
parmD fpHandler
cBegin <nogen>
DEC BX ; Want base 0.
js on_error ; if original arg is 0 then Ill fun error
CMP BL,CH ;Value [BL] .gt. MAX [CH]?
JNB ON_ERROR ;If so, then Ill fun error.
MOV CH,BL ; Save Event index in [CH]
XCHG AX,CX ; into AX (don't care about CX)
ADD AL,AH ; Final offset in al
LEA BX,[fpHandler] ; parm to settbl
call B$settbl
cEnd
ON_ERROR:
JMP B$ERR_FC
;***
;B$settbl - save ON <event> GOSUB handler address in trap table
;
;Purpose:
;
;
;entry:
; AL contains offset for appropriate event
; BX contains a pointer to fpHandler, on the stack
;
;exit:
;
;
;Uses:
;
;
;Exceptions:
; None.
;****
cProc B$settbl,<NEAR,PUBLIC>,<SI>
cBegin
.erre ID_SSEQDS
MOV SI,BX
CALL B$TrapAddr ; modifies ax & bx only - address in bx
LODSW
MOV [BX+1],AX ; Put (far) handler address in Trap Table
LODSW
MOV [BX+3],AX
CALL B$SetContext ;Set context bit in event flags
CALL B$SetChk ;Set Trap if On+Req and GOSUB <> 0.
cEnd
SUBTTL B$EVNT_SET - Set Event ON, OFF or STOP
PAGE
;***
; B$EVNT_SET - Sets Event ON, OFF or STOP
;
; Entry: [DL] = ON, OFF or STOP Token.
; [CH] = key # if KEY on
; [CL] = Trap table index to Event.
; [BL] = Event subscript.
;
; Exit: Event set in Trap Table, or Error.
; Preserves:
; DI
;****
cProc B$EVNT_SET,<NEAR,PUBLIC>
cBegin
XCHG AL,BL ; [AL] = Event subscript ([BX] = garbage)
ADD AL,CL ; [AL] = Event Trap base + index.
CALL B$TrapAddr ;Get Event addr in Trap Table
DEC DL ; cheap test of ON/OFF/STOP token
.errnz $ON - 0
JS EVON ; brif DL == $ON
.errnz $OFF - 1
JZ EVOFF ; brif DL = $OFF
;default - fall through to EVSTP
DbAssertRelB DL,z,$STOP-1,EV_TEXT,<gwaevt: B$EVNT_SET, invalid input>
;EVENT(n) ON, OFF and STOP (Enable EVENT Trapping)
EVSTP:
JMP B$StopTrap ;STOP TRAP
EVON:
JMP B$OnTrap ;TURN TRAP ON
EVOFF:
JMP B$OffTrap ;TURN TRAP OFF
cEnd <nogen>
SUBTTL unsupported device code
page
; this code consolidated with revision [35].
labelFP <PUBLIC,B$ESG0> ; SIGNAL(n) ON
labelFP <PUBLIC,B$ESG1> ; SIGNAL(n) OFF
labelFP <PUBLIC,B$ESG2> ; SIGNAL(n) STOP
labelFP <PUBLIC,B$ONSG> ; ON SIGNAL(n) GOSUB
labelFP <PUBLIC,B$EMO0> ; MOUSE(n) ON
labelFP <PUBLIC,B$EMO1> ; MOUSE(n) OFF
labelFP <PUBLIC,B$EMO2> ; MOUSE(n) STOP
labelFP <PUBLIC,B$ONMO> ; ON MOUSE(n) GOSUB
labelFP <PUBLIC,B$EUE0> ; UEVENT ON
labelFP <PUBLIC,B$EUE1> ; UEVENT OFF
labelFP <PUBLIC,B$EUE2> ; UEVENT STOP
labelFP <PUBLIC,B$ONUE> ; ON UEVENT GOSUB
cProc AFE_PROC,<FAR>
cBegin
JMP B$FrameAFE ; "advanced feature error" + frame setup
cEnd <nogen>
;***
;B$TrapEvent - An event has been detected. Set event flag
;
;Purpose:
; Moved here with revision [39]
; This routine is called when an event has been detected to
; set the global event flag and notify the interpreter
; that an event has occurred.
;Entry:
;IF (b$EventFlags & InSLEEP)
; AL = trap number
;ELSE
; None.
;ENDIF
;Exit:
; B$EVTFLG = 1
;Uses:
;IF (b$EventFlags & InSLEEP)
; AX
;ELSE
; None.
;ENDIF
;Exceptions:
; None.
;****
cProc B$TrapEvent,<NEAR,PUBLIC>
cBegin
MOV b$EVTFLG,1 ;set global event flag
cCall B$IEvSet ; call interp to set event BOS flag
TEST b$EventFlags,InSLEEP ; in SLEEP statement?
JZ NotSleep ; brif not -- don't do slow stuff
PUSH BX ; save register
CALL B$TrapAddr ; BX = *trap table entry for this event
MOV AL,[BX] ; get trap status
AND AL,TRP_ON or TRP_ST ; mask out all bits but ON and STOP
CMP AL,TRP_ON ; trap on and NOT stopped?
POP BX ; restore register
JNE NotSleep ; brif not enabled -- don't wake up SLEEP
labelNP <PUBLIC,B$Wakeup> ; entry point for keyboard interrupt handler
; forces wakeup of SLEEP
AND b$EventFlags,NOT (InSLEEP OR SLEEPtmr) ; clear flags to exit
; SLEEP statement wait loop
NotSleep:
cEnd
sEnd EV_TEXT
END
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -