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

📄 nammgr.asm

📁 Dos6.0
💻 ASM
📖 第 1 页 / 共 4 页
字号:
;Entry:
;	pbBuf - ptr to a buffer
;	oNam  - symbol's name table offset into mrsCur.tNam
;     The following data is referenced:
;	if oRsNam is <> 0, then we use that to fetch name table segment,
;	else mrsCur.bdlNam contains current module's name table segment.
;Exit:
;	AX - # of ASCII chars in mrsCur.tNam.oNam.name
;		These chars are copied into the given buffer.
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
cProc	CopyONamPb,<PUBLIC,FAR,NODATA>,<SI,DI,DS>
	parmW	pbBuf			
	parmW	oNam			
cBegin
	DbChk	ConStatStructs
	DbChk	tNam
	DbChk	oNam,oNam		; sanity check on input oNam
	mov	si,[oNam] 		; SI = tNam.oNam
					;NOTE - this works because tNam
					;is a far heap ( ES:0 => tNam )
	call	FetchPNam		; bx points to desired mrs
	GETSEG	DS,PTRRS[bx.BDL_seg],,<SIZE,LOAD> ;[14][10][6]
	push	SS			;callers pb segment
	pop	ES			;ES = callers pb segment
	mov	di,[pbBuf]		
	sub	cx,cx			;CX=0
	mov	cl,NM_SIZE[si]		;# of ASCII bytes in oNam
	mov	ax,cx			;return cbW to caller
	add	si,NM_NAME		;SI = tNam.oNam.name
	rep	movsb			;copy tNam.oNam.nam to pb
cEnd

;***
;CopyONamBd		cbW = CopyONamBd(oNamW,pBdW)
;Purpose:
;	Use oNam to determine the symbol's size and then use that size to
;	allocate a heap entry for pBd.	The ASCII chars in the symbol name
;	are then copied to the heap entry.  pBd must point to an un-initialized
;	Bd (ie - Bd doesn't currently own a heap entry)!
;Entry:
;     The stack contains the following parameters (PLM calling convention)
;	ParmW - symbol's name table offset
;	ParmW - ptr to uninitialized Bd
;Exit:
;	AX =  0 if Bd allocation was unsucessful
;	   =  mrsCur.tNam.oNam.cb if Bd allocation was sucessful
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
cProc	CopyONamBd,<PUBLIC,NEAR,NODATA>,<SI,DI>
	parmW	oNam		;symbol's offset into tNam
	parmW	pBd		;ptr to uninitialized Bd
cBegin
	DbChk	ConStatStructs
	DbChk	tNam
	DbChk	oNam,[oNam]		;sanity check on input oNam
	mov	si,[oNam] 		;SI = tNam.oNam
					;NOTE - this works because tNam
					;is a far heap ( ES:0 => tNam )
	sub	cx,cx			;CX=0
	GETSEG	ES,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
	mov	cl,ES:NM_SIZE[si]	;# of ASCII bytes in oNam
	push	cx			;save & pass to BdAlloc

	mov	ax,IT_NO_OWNERS 	;pass bdType to BdAlloc
	cCall	BdAlloc,<pBd,cx,ax>	;allocate a Bd to copy oNam to
	pop	cx
	or	ax,ax			;was the allocation sucessful
	je	CopyONamBdExit		;brif unsucessful
	push	DS			;ES = DGROUP (for the 'rep movsb')
	pop	ES
	GETSEG	DS,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
					;refresh - BdAlloc could have moved it
assumes DS,NOTHING
	mov	ax,cx			;return mrsCur.tNam.oNam.cbW to caller
	add	si,NM_NAME		;SI = tNam.oNam.name (source ptr)
	mov	di,[pBd]		;ptr to Bd to copy to
	mov	di,ES:[di.BD_pb]	;ptr to buf to copy oNam to (dest ptr)
	rep	movsb			;copy tNam.oNam.nam to pb
	push	ES			;DS = DGROUP (for the 'rep movsb')
	pop	DS
assumes DS,DATA
CopyONamBdExit:
cEnd

;***
;GetVarNamChar		ushort = GetVarNamChar(oNamW)
;Purpose:
;	Given an oNam, the logical first char of the name for use in 
;	determining the default type of a variable by that name (i.e.,
;	bypass a leading 'FN' in the name).
;	For versions supporting DEF FN's, also return a flag indicating 
;	whether the name starts with 'FN' or not.
;Entry:
;	oNamW - symbol's name table offset into mrsCur.tNam
;Exit:
;	AL - logical first char of variable name, forced to upper case
;	ife FV_QB4LANG
;		AH - 0 if name doesn't start with 'FN', non-zero if it does
;	endif
;Uses:
;	none.
;Preserves:
;	DX, ES
;Exceptions:
;	none.
;****************************************************************************
cProc	GetVarNamChar,<PUBLIC,NEAR,NODATA>,<ES>
	parmW	oNam
cBegin
	DbChk	oNam,[oNam]		;sanity check on input oNam
	DbChk	tNam
	DbChk	ConStatStructs
	GETSEG	es,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
	mov	bx,[oNam]
	add	bx,NM_NAME		;add table start ptr to offset
	mov	al,es:[bx]		;fetch first char of name
	and	al,0DFh			;force to upper case
	xor	ah,ah
	cmp	al,'F'
	jnz	GetVarChar_Exit		;brif doesn't start with 'FN'

	mov	cl,es:[bx-(NM_NAME - NM_SIZE)] ; fetch length of name
	cmp	cl,2			; long enough to be a DEF FN name?
	jbe	GetVarChar_Exit 	; brif not

	mov	cl,es:[bx+1]		;fetch second char of name
	and	cl,0DFh			;force to upper case
	cmp	cl,'N'
	jnz	GetVarChar_Exit		;brif doesn't start with 'FN'

	mov	al,es:[bx+2]		;fetch third char of name
	and	al,0DFh			;force to upper case
	inc	ah			;set "found 'FN'" flag
GetVarChar_Exit:
cEnd


;***
;FlagOfONam		FlagW = FlagOfONam(oNamW)
;Purpose:
;	To get a symbols flag byte from the symbol table.
;Entry:
;     The stack contains the following parameters (PLM calling convention)
;	ParmW - symbol's name table offset
;     The following globals are referenced
;	mrsCur.bdlNam => current module's name table
;Exit:
;	AX = tNam.oNam.flags
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
cProc	FlagOfONam,<PUBLIC,NEAR,NODATA>,<DS>
	parmW	oNam		;symbol's offset into tNam
cBegin
	DbChk	oNam,[oNam]		;sanity check on input oNam
	DbChk	tNam
	DbChk	ConStatStructs
	GETSEG	ds,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
	mov	bx,oNam 		;bx = tNam.oNam
					;NOTE - this works because tNam
					;is a far heap ( DS:0 => tNam )
	sub	ax,ax			;AH=0 - for returning a ushort
	mov	al,NM_FLAGS[bx] 	;get the flag byte
cEnd

;***
;SetONamMask, SetONamSpace, CheckONamSpace
;Purpose:
;	To selectively set individual bits in a symbols FLAG byte.
;	For SetONamSpace, 
;		sets the 2 "name space" bits of the flags byte to some
;      		NMSP_ value. Returns 0 if no error, or ER_DD if either of
;		those bits were already set.
;	For CheckONamSpace,
;		catches the error where a given bit is already set, but
;		doesn't actually set the namespace.
;Entry:
;     The stack contains the following parameters (PLM calling convention)
;	ParmW - symbol's name table offset
;	ParmB - mask to be ORed with symbols FLAG byte
;     The following globals are referenced
;	mrsCur.bdlNam => current module's name table
;Exit:
;	tNam.oNam.flags = tNam.oNam.flags OR maskW
;	For SetONamSpace, AX = 0 if no error, else AX = ER_DD.
;			  PSW.Z set if no error 
;	dl = old value of oNams flags before the new bit was set.
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
PUBLIC	CheckONamSpace		
CheckONamSpace: 		
	mov	ch,0FFH 	; don't set namespace bits
	SKIP2_PSW		
PUBLIC	SetONamSpace
SetONamSpace:
	mov	ch,0		; do set namespace bits
	mov	cl,0FFH 	; do check for errors
	SKIP2_PSW
PUBLIC	SetONamMask
SetONamMask:
	xor	cx,cx
cProc	SetONamMaskGen,<NEAR,NODATA>,<DS>
	parmW	oNam		;symbol's offset into tNam
	parmB	orMask		;bit mask - value to be ORed with NM_FLAGS
cBegin
	DbChk	ConStatStructs
	DbChk	tNam
	GETSEG	ds,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
	mov	bx,[oNam] 		;bx = tNam.oNam
					;NOTE - this works because tNam
					;is a far heap ( ES:0 => tNam )
	DbChk	oNam,bx			;sanity check on input oNam
	mov	dh,[orMask]
	jcxz	NMSP_Okay

	xor	ax,ax			;assume no error for SetONamSpace retval
	mov	dl,NM_FLAGS[bx]		;fetch flags as they were on entry
	and	dl,NMSP_MASK		;had one of the NMSP_ bits been set?
	jz	NMSP_Okay		;  brif not

	cmp	dl,dh			;were those bits same as input?
	jz	NMSP_Okay		;  brif so

	mov	al,ER_DD
	xor	dh,dh			;don't alter table if error
NMSP_Okay:
	or	ch,ch			; want to actually modify flag bits?
	jnz	@F			; brif not - - - exit

	mov	dl,NM_FLAGS[bx] 	;return old value in dl
	or	NM_FLAGS[bx],dh 	;set all MASKed bits
@@:					
	or	ax,ax			;set PSW flags
cEnd

;***
;ResetONamMask		ResetONamMask
;Purpose:
;	To selectively reset individual bits in a symbols FLAG byte.
;Entry:
;	AL = mask to be NANDed with symbols FLAG byte
;	BX = symbol's name table offset
;     The following globals are referenced
;	mrsCur.bdlNam => current module's name table
;Exit:
;	tNam.oNam.flags = tNam.oNam.flags OR maskW
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
cProc	ResetONamMask,<PUBLIC,NEAR,NODATA>,<DS>
cBegin
	DbChk	ConStatStructs
	DbChk	tNam
	DbChk	oNam,bx			;sanity check on input oNam
	GETSEG	ds,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
	not	al			;invert the mask
	or	al,NM_fLineNum		;don't let anyone reset this flag
	and	NM_FLAGS[bx],al 	;reset all MASKed bits
cEnd

;***
;ResetONamMaskTmp
;Purpose:
;	C code access to ResetONamMask
;Entry:
;     The stack contains the following parameters (PLM calling convention)
;	mask to be NANDed with symbols FLAG byte
;	symbol's name table offset
;     The following globals are referenced
;	mrsCur.bdlNam => current module's name table
;Exit:
;	tNam.oNam.flags = tNam.oNam.flags OR maskW
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
cProc	ResetONamMaskTmp,<PUBLIC,NEAR,NODATA>
	parmW	oNam
	parmB	nandMask
cBegin
	mov	al,[nandMask]
	mov	bx,[oNam]
	call	ResetONamMask
cEnd

;***
;ResetTNamMask		ResetTNamMask(maskW)
;Purpose:
;	Resets the all but the selected flag bits in all symbols of 
;	mrsCur.tNam (the symbol's flags are ANDed with the given byte mask).
;
;	Note that we handle the NMSP_ enumerated bits specially to ensure
;	that the NMSP_SUB constant is never changed.
;Entry:
;	AL - mask to be ANDed with all symbol FLAG bytes
;     The following globals are referenced
;	mrsCur.bdlNam => current module's name table
;Exit:
;	none.
;Uses:
;	none
;Exceptions:
;	none
;***************************************************************************
cProc	ResetTNamMask,<PUBLIC,NEAR,NODATA>,<SI,DS>
cBegin
	DbChk	ConStatStructs
	DbChk	tNam
	GETSEG	ds,[mrsCur.MRS_bdlNam_seg],,<SIZE,LOAD> ;[6]
	xor	si,si			;SI=0 - make GetNextONam return
					;	FirstONam
	or	al,NM_fLineNum+NM_fLineNumLabel ;don't let anyone reset these

	;if NMSP_SUB is set for a name, leave it alone, otherwise, allow
	;caller to reset either both NMSP_ bits or neither
	mov	ah,al
	mov	cl,NMSP_SUB
NextTNamMask:
	call	GetNextONam		;SI = pNextONam
	je	ResetTNamMaskExit	;brif no more oNams
	test	BYTE PTR NM_FLAGS[si],080H
	jnz	NextTNam_Cont		;brif NMSP_Variable or _Constant set
					;  (need this because NMSP_'s are
					;   enumerated - - see .errnz's above)
	or	al,cl			;don't mask off NMSP_SUB flag
NextTNam_Cont:
	and	NM_FLAGS[si],al 	;reset all MASKed bits
	mov	al,ah
	jmp	NextTNamMask		;loop till all oNam's visited
ResetTNamMaskExit:
cEnd

;***
;GetNextoNam
;Purpose:
;	To get the next oNam in tNam
;Entry:
;	DS - tNam segment
;	SI - current oNam - if 0 then return 1st oNam
;	DS:CurONamHdr - current tNam 1st char index
;
;Exit:
;	PSW - IF zero flag set then no more valid oNam's exist
;	SI - next oNam
;	NextONamHdr  - next tNam 1st char index
;Uses:
;	dx
;***************************************************************************
	PUBLIC	GetNextONam
GetNextONam:
	or	si,si			;should we initialize
	jne	NextoNam		;brif initialization not desired
	mov	word ptr DS:CurONamHdr,tNam - 2  
					;offset of 1st valid chain header-2
NextChain:
	mov	dx,DS:CurONamHdr	;offset of current tNam chain header
	inc	dx			;word ptr to next chain header
	inc	dx
	cmp	dx,LineNumHdrLast	;check for the end of tNam header tbl
	mov	DS:CurONamHdr,dx	;update
	ja	GotNextoNam		;brif all chain headers visited

	mov	si,dx			;start with 1st symbol in cur chain
NextoNam:
	mov	si,[si] 		;ptr to next symbol in cur hdr chain

⌨️ 快捷键说明

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