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

📄 rterror.asm

📁 Microsoft MS-DOS6.0 完整源代码
💻 ASM
📖 第 1 页 / 共 3 页
字号:
RtError_Initialization	ENDP

PUBLIC	RtErrorCODE
RtErrorCODE PROC NEAR
RtErrorCODE ENDP
	;fall into RtError
PUBLIC	RtError
RtError PROC FAR
	mov	[grs.GRS_otxCur],si	;just as executors save this away prior
					;  to calling runtime ... for error
RtError ENDP				;  recovery
	;fall into RtErrorNoSi
PUBLIC	RtErrorNoSi
RtErrorNoSi PROC FAR
	xor	ah,ah			;so callers only have to set AL
	cmp	al,MSG_GoDirect
	jnz	RtErrorNoSi_Cont1

	mov	ax,FE_GODIRECT
RtErrorNoSi_Cont1:
	xchg	ax,bx
	call	B$RUNERRINFO
	DbHalt	CODE,<B$RUNERRINFO returned when passed a fatal error (2)>
RtErrorNoSi ENDP

;***
;exStOnError, exStResume, exStResume0, exStResumeNext
;
;	Moved to this module as part of revision [18].
;
;****
	EXTRN	SetProgramMode:NEAR	

MakeExe exStOnError,opStOnError
	LODSWTX 			;load oTx of error handler to ax
	mov	bx,[grs.GRS_oMrsCur]
	RS_BASE add,bx			;bx points to mrsCur in the Rs table
	GETRS_SEG es
	mov	PTRRS[bx.MRS_otxHandler],ax  ;save ON ERROR oTx (or UNDEFINED)
	inc	ax
	jz	OnError_GoTo_0		;brif line number 0 specified
OnError_Exit:
	jmp	DispMov 		;ensure es gets restored in dispatch

OnError_GoTo_0:
	cmp	[b$inonerr],0
	jz	OnError_Exit		;brif not in an error handler
					; otxHandler is already set to UNDEFINED
	;ON ERROR GOTO 0 in an error handler - - - cause runtime error.
	mov	al,byte ptr [b$errnum]
	call	RtErrorCODE


MakeExe exStResume,opStResume
	LODSWTX 			;fetch oTx for resume Lab/Ln
	cmp	ax,UNDEFINED
	jz	exStResume0		;brif oTx is UNDEFINED - RESUME 0

	test	[bp+4],08000H		;did error occur in a procedure?
	jnz	Resume_Proc		;  brif so - leave this frame active

	mov	[bp+2],ax		;oTx we want to resume to
	jmp	short exStResume0	;pop back to previous module frame
					;Note that we need to do this so that
					;  a subsequent CLEAR or RUN won't cause
					;  a runtime error.
Resume_Proc:
	push	ax			;ax = oTx to RESUME to (@ module level)
	xor	ax,ax			;tell B$RESUMED to dealloc all string
	mov	[grs.GRS_oTxCur],si	;in case of runtime error
	call	B$RESUMED		;call RT to reset b$inonerr, b$errnum.
					;  if not currently in handler, gives
					;  RT error and doesn't return (note
					;  that AX is a parm to B$RESUMED)
	pop	si			;put oTx to resume at in SI
	jmp	short Resume_Common


MakeExe exStResumeNext,opStResumeNext
	mov	di,sp			;remember this is RESUME NEXT
	jmp	short Resume_Common1
	
MakeExe exStResume0,opStResume0
	xor	di,di			;remember this is RESUME0
Resume_Common1:
	mov	[grs.GRS_oTxCur],si	;in case of runtime error
	DbAssertRel ax,nz,0,CODE,<exStResume<Next|0>: ax == 0>
	call	B$RESUMED		;call RT to reset b$inonerr, b$errnum.
					;  if not currently in handler, gives
					;  RT error and doesn't return (note
					;  that AX is a parm to B$RESUMED)
	mov	sp,bp
	pop	bp	
	pop	si			;oTx part of return address
	mov	[b$curframe],bp
	pop	ax
	call	RsActivateCODE		;activate Rs where error occured
	pop	[pGosubLast]		;update in case any GOSUBs occured and
					;  were not returned from
	or	di,di			;RESUME NEXT, or RESUME [0] ?	
	jz	Resume_Common2		;  brif RESUME [0]

	call	SetProgramMode		;in case of a RETURN from direct mode
					;  must do this prior to call to 
					;  OtxResumeNext to ensure ES setup
					;  for module text table, not directmode
	call	EnStaticStructs		;bring txdCur up to date
	xchg	ax,si
	push	ax			;push otx arg.
	call	OtxResumeNext		;ax = oTx of BOS/BOL of following stmt
	xchg	ax,si
	call	DisStaticStructs
Resume_Common2:	
	call	SetSP			;set SP to where it should be at BOS
					;  based on bp
	mov	sp,ax
Resume_Common:
	call	SetProgramMode		;in case of a RETURN from direct mode
					;  also updates ES & DI for execution
	cmp	[grs.GRS_fDirect],FALSE ;RESUME from Direct Mode?
	jnz	DirectMode_Resume	;  brif so
Disp1:
	DispMac 			; and on with the show.

CantCont_Err:
	mov	al,ER_CN		;"Cant Continue" error
	call	RtErrorCODE


	EXTRN	Cont_Otx:NEAR		;part of exStCont code

DirectMode_Resume:
	cmp	[grs.GRS_otxCONT],UNDEFINED
					;exists context that can be CONTinued?
	jz	CantCont_Err		;  brif not - - issue 'Cant Continue'

	jmp	Cont_Otx		;share code with exStCont

sEnd	CODE
;===============================================================================
subttl	Error Trap Code for Direct Mode Runtime Users
page

sBegin	CP
assumes CS, CP

;***
;CallRtTrap, CallRtTrap_Parm, CallRtTrap_RT, CallRtTrap_CODE
;Purpose:
;	This calls a specified function, trapping runtime errors.
;
;	The current trap handler as set by RtSetTrap is preserved.
;Entry:
;	pFunc = far address of function to call (must be FAR function)
;	si,di	passed to specified function
;	For CallRtTrap_Parm, bx is a parm that must be pushed on the stack,
;		i.e., passed to pFunc.
;Exit:
;	ax =  0 if no runtime error occurred
;	      or
;	      standard error code if runtime error occurred
;	si,di as returned from the specified function if no error.
;	      or garbage
;Exceptions:
;	none
;
;*******************************************************************************
	PUBLIC CallRtTrap_Parm
	PUBLIC CallRtTrap
CallRtTrap_Parm:
	mov	dx,sp			;signal that bx contains a parm to pass
	SKIP2_PSW
CallRtTrap:
	xor	dx,dx			;no parm to pass to pFunc
cProc	CallRtTrap_Common,<FAR>
	parmD	pFunc
cBegin
	call	RtPushHandler		;save current handler on stack
					; NOTE: alters SP
	mov	ax,CPOFFSET CallTrapped
	call	RtSetTrap
	or	dx,dx			;parm to pass to pFunc?
	jz	CallRt_NoParm		;brif not

	push	bx			;pass given parm on to pFunc
CallRt_NoParm:
	call	[pFunc]
	sub	ax,ax			;error code = 0
CallTrapped:
	call	RtPopHandler		;restore caller's handler from stack
					; NOTE: alters SP
cEnd
;start of revision [10]
sEnd	CP

sBegin	RT
assumes CS, RT
cProc	CallRtTrap_RT,<PUBLIC,FAR>
	parmW	pFunc
cBegin
	push	cs
	push	[pFunc]
	call	far ptr CallRtTrap
cEnd
sEnd	RT

sBegin	CODE
assumes CS, CODE
cProc	CallRtTrap_CODE,<PUBLIC,FAR>
	parmW	pFunc
cBegin
	push	cs
	push	[pFunc]
	call	far ptr CallRtTrap
cEnd
sEnd	CODE

sBegin	CP
assumes CS, CP
;end of revision [10]

;***
;RtSetTrap
;Purpose:
;	This is called by a function which is about to make a series
;	of runtime calls, and wants to identify one location to
;	branch to if any of them result in runtime errors.  In BASIC
;	terminology, this is equivalent to doing an ON ERROR GOTO [ax].
;	The handler remains active until RtSetTrap is called again,
;	RtFreeTrap is called, or a runtime error occurs.
;
;	When the handler is branched to, the sp, es and di registers
;	are set as though it had just returned from RtSetTrap.
;	The si and ds registers are set as though it had just returned
;	from the runtime call which resulted in the error.
;	Register al contains the standard QB4 error code.
;
;	NOTE: Internal errors such as String space corrupt ALWAYS cause
;	NOTE: QB4 to print the error message, and terminate.
;Entry:
;	ax = offset into CP segment to error handler
;	bp = value to restore bp to if error is trapped
;	si = value to restore si to if error is trapped (optional)
;	di = value to restore di to if error is trapped (optional)
;Exit:
;	none
;Preserves:
;	bx,cx,dx
;Exceptions:
;	none
;
;*******************************************************************************
PUBLIC	RtSetTrap
RtSetTrap PROC NEAR
;Make sure we aren't over-writing someone else's trap.
;If so, should use RtPushHandler and RtPopHandler
DbAssertRel [errCodeRet.ERRRET_saveSP],e,0,CP,<RtSetTrap: trap already set>
	mov	[errCodeRet.ERRRET_saveBP],bp	;to restore bp on error
	mov	[errCodeRet.ERRRET_saveSI],si	;to restore si on error
	mov	[errCodeRet.ERRRET_saveDI],di	;to restore di on error
	mov	[errCodeRet.ERRRET_retAddr],ax	;return address to handler
DbAssertRel [b$fInt24Err],ne,0,CP,<RtSetTrap: int24 trap already set>	
	mov	[b$fInt24Err],0		; have runtime handle int24 errors
	pop	ax				;ax = ret adr to caller
	mov	[errCodeRet.ERRRET_saveSP],sp	;set SP back to here on error
	jmp	ax				;return to caller
RtSetTrap ENDP

;***
;RtTrapRet
;Purpose:
;	Jumped to from B$IONERR when an error occurs with trap set
;Entry:
;	ax = standard runtime error code
;	cx = errCodeRet.ERRRET_saveSP
;Exit:
;	none
;Exceptions:
;	exits via RtFreeTrap to save code
;
;*******************************************************************************
RtTrapRet PROC FAR

	push	ax			;save error code for return
	push	cx			;save new sp
	push	[b$pend]		;ptr to low word on stack
	dec	cx			;clear range is inclusive...
	dec	cx			;...so adjust to not trash TOS.
	push	cx			;ptr to top of range to clear
	call	B$ClearRange		;free all owners on stack
	pop	cx			;get back new sp
	pop	ax			;recover error code

	;restore bp,si,di,sp as they were on runtime entry
	mov	si,[errCodeRet.ERRRET_saveSI]
	mov	di,[errCodeRet.ERRRET_saveDI]
	mov	bp,[errCodeRet.ERRRET_saveBP]
	mov	sp,cx
	mov	[b$errnum],0			;so ERR is 0 after CHAIN and
						;  RUN <filespec> and to prevent
						;  similar potentially confusing
						;  values of ERR.
	push	[errCodeRet.ERRRET_retAddr]	;set up for near return
	;fall into RtFreeTrap, to free the trap and return to caller with
	;  error code in ax
RtTrapRet ENDP

;***
;RtFreeTrap
;Purpose:
;	Removes the error handler installed by RtSetTrap.  In BASIC
;	terminology, this is equivalent to doing an ON ERROR GOTO 0.
;Entry:
;	none
;Exit:
;	none
;Preserves:
;	AX
;Exceptions:
;	none
;
;*******************************************************************************
PUBLIC	RtFreeTrap
RtFreeTrap PROC NEAR
	mov	[errCodeRet.ERRRET_saveSP],0	;reset, so not used incorrectly
;Comment out this assertion so we can do two RtFreeTrap's in a row
;DbAssertRel [b$fInt24Err],e,0,CP,<RtFreeTrap: int 24 trap not set> 
	mov	[b$fInt24Err],UNDEFINED	; don't have runtime handle int24
					; error processing anymore (trashes
					; any pending int 24 errors)
	ret
RtFreeTrap ENDP

;***
;RtPushHandler
;Purpose:
;	Save the state of the runtime-error-handler (as set by RtSetTrap)
;	on the stack.
;Preserves:
;	ax,bx,dx
;NOTE:
;	Exit SP < Entry SP
;
;*******************************************************************************
PUBLIC	RtPushHandler
RtPushHandler PROC NEAR
	pop	cx			;cx = return address
	push	[b$fInt24Err]		; also save int 24 error handler 
	sub	sp,size ERRRET		;Make space for handler
	push	cx
	push	si
	push	di
	push	es
	mov	si,DATAOFFSET errCodeRet
	mov	cx,size ERRRET/2
	mov	di,sp			;Copy into stack
	add	di,8			;Add 4 pushes above
	push	ss
	pop	es
rep	movsw				;Copy handler into stack frame
	pop	es
	pop	di
	pop	si
	ret
RtPushHandler ENDP

;***
;RtPopHandler
;Purpose:
;	Restore the state of the runtime-error-handler that was saved
;	by RtPushHandler
;Preserves:
;	ax,bx,dx
;NOTE:
;	Exit SP < Entry SP
;
;*******************************************************************************
PUBLIC	RtPopHandler
RtPopHandler PROC NEAR
	push	si
	push	di
	push	es
	mov	di,DATAOFFSET errCodeRet
	mov	cx,size ERRRET/2
	mov	si,sp			;Copy from stack
	add	si,8			;Add 3 pushes above + return addr
	push	ss
	pop	es
rep	movsw				;Copy handler from stack frame
	pop	es
	pop	di
	pop	si
	pop	cx			;Return address
	add	sp,size ERRRET		;Remove space for handler
	pop	[b$fInt24Err]		; also restore int 24 error handler 
	jmp	cx			;Return to caller
RtPopHandler ENDP
sEnd	CP

	end

⌨️ 快捷键说明

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