📄 varutil.asm
字号:
TITLE VarUtil.asm - Variable Management utilities in native code
;***
;VarUtil.asm - Variable Management utilities in native code
;
; Copyright (C) 1986-1989, Microsoft Corporation
;
;Purpose:
; Provide utility functions for the variable manager in native code
;
;
;*******************************************************************************
.xlist
include version.inc
VarUtil_ASM = ON ;don't include EXTRNs defined in this file
includeOnce architec
includeOnce conint
includeOnce context
includeOnce executor
includeOnce heap
includeOnce names
includeOnce qbimsgs
includeOnce rtinterp
includeOnce scanner
includeOnce util
includeOnce variable
.list
; .sall
;These assertions are made because MakeVariable returns two sets of error
;codes on the assumptions that the ER_ and MSG_ messages it uses will all
;fit in a single byte.
.erre 255d GT MSG_COM
.erre 255d GT MSG_BadElemRef
.erre 255d GT MSG_UndElem
.erre 255d GT MSG_ASRqd1st
assumes DS,DATA
assumes ES,DATA
assumes SS,DATA
assumes CS,CP
sBegin DATA
globalW oValComMax,0 ;Max oVal for all BLANK Common
; declarations
globalW oTypComMax,0 ;Max oTyp for all BLANK Common
; declarations
staticW oVarPrev,0 ;oVar returned by last call to
; FirstVar or NextVar (for NextVar)
staticW oVarTHash,UNDEFINED ;offset to start of appropriate
; hash table (for NextVar)
staticW iHashCur,0 ;index in appropriate hash table to
; current hash chain (for NextVar)
staticW iHashMax,0 ;max valid index hash index based
; on current context (for NextVar)
;These two flags are used to share COMMON support code
staticB fResetCommon,FALSE
staticB fCreateCommon,TRUE ;FALSE if we just want MakeCommon to
; FIND a COMMON block, not make one
externW pSsCOMcur ;used by AdjustCommon
staticB fQlbCommon,0 ; set if common in quicklibs
externW vm_fVarFound ;these are used by StdSearch
externW vm_fPVCur
externW vm_pVarCur
externW vm_oVarCur
externW vm_oVarTmp
staticW oTypNew,0 ;here instead of localW so StdSearch
; doesn't have to push a frame
staticW oVarShared,0 ;here instead of localW so StdSearch
; doesn't have to push a frame
NMALLOC label BYTE
DB "NMALLOC",0 ;used by B$GetNMALLOC
CB_NMALLOC EQU 7 ;size of NMALLOC string
; Create a public sd to NMALLOC for FindNMalloc to use.
globalW sdNMALLOC,CB_NMALLOC
staticW ,<dataOFFSET NMALLOC>
sEnd DATA
externFP B$ULGetCommon ;finds user library common blocks
externFP B$IRTCLR ; release all compiled AD's & SD's,
; and zero QuickLib vars
externFP B$IERASE ;QB-specific array ERASE routine
externFP B$STDL ;releases a given string (sd)
sBegin CP
;##############################################################################
;# #
;# Table Allocation #
;# #
;##############################################################################
;***
;MakeMrsTVar() - Create module variable table & set up tMV hash table
;Purpose:
; Allocates a buffer of size CBINITMVHASH, with mrsCur.bdVar as the owner.
; Sets up the first CBINITMVHASH bytes as a hash table for the tMV; the
; hash table entries are all initialized to 0.
;
; Also allocates space for typmgr structures, i.e., information regarding
; user-defined types and elements. This space is managed by the typmgr
; component, which, like the varmgr, can grow the vartable and add type
; and element structures and never needs to move or remove these
; structures.
;
; The tMV hash table comes first, followed by CBINIT_TTYP bytes of table
; overhead required by the typmgr. This overhead consistes of an offset
; to the first TYP structure, and a count of TYP structures in the table
; (both of these are initialized to zero). VAR, TYP, and ELEM struct
; space is then allocated by the varmgr and typmgr as required.
;
;Entry:
; mrsCur is set up; it is assumed that the bdVar field does NOT currently
; contain a heap owner.
;
;Exit:
; FALSE is returned if there is insufficient memory,
; else table is successfully allocated.
;
;Exceptions:
; none.
;
;******************************************************************************
cProc MakeMrsTVar,<NEAR,PUBLIC,NODATA>
cBegin MakeMrsTVar
mov bx,dataOFFSET mrsCur.MRS_bdVar
DbChk BdNotOwner,bx ;ensure that given bd isn't an owner now
push bx
PUSHI ax,CBINITMVHASH+CBINIT_TTYP
PUSHI ax,IT_VAR ;alloc a table large enough for tMV
call BdAllocVar ; hash table plus typmgr requirements
or ax,ax
jz MakeMrsTVar_Exit ;brif allocation failed
.erre (CBINITMVHASH+CBINIT_TTYP) GT ET_MAX
;ensure offset to first TYP struct
; is larger than biggest predefined
; oTyp value
mov ax,CBINITMVHASH+CBINIT_TTYP
mov [mrsCur.MRS_oPastLastVar],ax
;initialize to same as cbLogical
push [mrsCur.MRS_bdVar.BD_pb] ;start of hash table
push ax ;CBINITMVHASH+CBINIT_TTYP
call ZeroFill ;initialize module-level hash table
; and typmgr data to zeroes
mov ax,sp ;non-zero == TRUE == success
MakeMrsTVar_Exit:
cEnd MakeMrsTVar
;***
;MakePrsTVar - Put a procedure hash table into mrsCur.bdVar for prsCur
;Purpose:
; To be called when a new prs is created, adds and initializes a hash
; table of size CBINITPVHASH at the end of mrsCur.bdVar, placing the
; offset into bdVar to this hash table into prsCur in the oVarHash field.
;
; NOTE: We only create a prs hash table for those prs's with text tables,
; NOTE: plus DEF FN's (i.e., we DON'T create prs hash tables for
; NOTE: DECLARE's). This saves DGROUP space for user library DECLARE's.
;
;Entry:
; mrsCur is set up; it is assumed that bdVar is a heap owner.
; prsCur is set up; its oVarHash field is assumed to contain garbage
;
;Exit:
; FALSE is returned if there is insufficient memory,
; else table is successfully allocated.
;
;Exceptions:
; none.
;
;******************************************************************************
cProc MakePrsTVar,<FAR,PUBLIC,NODATA>,<SI>
cBegin MakePrsTVar
mov bx,dataOFFSET mrsCur.MRS_bdVar
DbChk BdOwner,bx ;ensure that given bd is an owner
.errnz MRS_bdVar - MRS_bdVar.BD_cbLogical
mov si,[bx]
DbAssertRel grs.GRS_oPrsCur,nz,UNDEFINED,CP,<MakePrsTVar: err 1>
DbAssertRel prsCur.PRS_oVarHash,z,UNDEFINED,CP,<MakePrsTVar: err 2>
xor ax,ax ;in case of error return
cmp si,08000H - CBINITPVHASH
jae MakePrsTVar_Exit ;brif 32k limit on module var table
; exceeded
push bx ;pointer to mrsCur.MRS_bdVar
PUSHI ax,CBINITPVHASH
call BdGrowVar ;allocate space for proc. hash table
or ax,ax
je MakePrsTVar_Exit ;brif error return
mov [prsCur.PRS_oVarHash],si ;input cbLogical, i.e., offset to start
; of procedure hash table
add si,[mrsCur.MRS_bdVar.BD_pb]
push si
PUSHI ax,CBINITPVHASH
call ZeroFill
mov ax,sp ;non-zero == TRUE, i.e., success
MakePrsTVar_Exit:
cEnd MakePrsTVar
;***
;FirstVar - return the pVar and oVar of the first var in the current table
;Purpose:
; This routine is used in conjunction with NextVar (below). It
; returns the oVar and pVar to the first variable in the current
; tPV or tMV, and sets up some static variables for subsequent calls
; to NextVar.
;
;Input:
; none.
;Ouptut:
; if AX = 0, no (more) variables in current table
; else AX = oVar, BX = pVar.
;Modifies:
; none
;***************************************************************************
PUBLIC FirstVar
FirstVar PROC NEAR
mov [iHashMax],CBINITMVHASH ;assume no procedure active
xor ax,ax ;assume no procedure active
cmp [grs.GRS_oPrsCur],UNDEFINED
jz No_Prs_Active
mov ax,[prsCur.PRS_oVarHash]
mov [iHashMax],CBINITPVHASH
No_Prs_Active:
mov [oVarTHash],ax ;module hash table starts at offset 0
mov [iHashCur],-2 ;so shared code will inc to 0
mov dx,[mrsCur.MRS_bdVar.BD_pb]
jmp short End_Of_Hash_Chain ;share code with NextVar, below
FirstVar ENDP
;***
;NextVar - return the pVar and oVar of the next var in the current table
;Purpose:
; This routine is called repetitively to access each variable in
; the current procedure or module variable table (tPV or tMV).
;
; Note: This code is written to account for the fact that heap
; movement can occur between calls.
;Input:
; none.
;Ouptut:
; if AX = 0, no (more) variables in current table
; else AX = oVar, BX = pVar.
;Modifies:
; none
;***************************************************************************
PUBLIC NextVar
NextVar PROC NEAR
DbChk ConStatStructs ;static structs must be active
mov dx,[mrsCur.MRS_bdVar.BD_pb]
NextVar_Clear:
mov bx,[oVarPrev]
DbAssertRel bx,nz,0,CP,<NextVar called w/o FirstVar call first>
add bx,dx ;bx = pVarPrev
mov ax,[bx.VAR_oHashLink] ;ax = oVarNext
and ax,0FFFEH ;mask off low bit
jz End_Of_Hash_Chain ;brif end of this hash chain
mov bx,ax
NextVar_Exit:
add bx,dx ;ax = oVar, bx = pVar
mov [oVarPrev],ax ;update static
ret
End_Of_Hash_Chain: ; callable entry point
; preserves dx, es
;Search the hash table for the start of the next non-empty chain
mov cx,[iHashCur]
mov ax,[oVarTHash]
add ax,dx ;ax points to base of hash table
TryNextChain:
mov bx,ax
inc cx
inc cx ;increment index
cmp cx,[iHashMax] ;have we checked all chains?
jz Next_Var_Done ; brif so - -
DbAssertRel cx,b,iHashMax,CP,<NextVar - iHashCur or iHashMax hosed>
add bx,cx ;bx points to start of next hash chain
mov bx,[bx] ;bx = oVar for first var in chain or
; 0 if chain is empty
or bx,bx
jz TryNextChain ;current chain is empty - try the next
mov [iHashCur],cx
mov ax,bx ;ax = bx = oVar
jmp short NextVar_Exit
ret
Next_Var_Done:
xor ax,ax
ret
NextVar ENDP
;***
;ClearPV, ClearMV - CLEAR all variables in the given procedure
;
;ClearPV:
; Purpose:
; Called via ForEachPrsInPlaceCPSav.
; CLEAR all static variables in the tPV for the given prs.
; Entry:
; SI = pPrs to be cleared (which is NOT prsCur - - - it's in
; the table).
;ClearMV:
; Purpose:
; Called via ForEachCP
; CLEAR all static variables in the tMV for mrsCur
; Entry:
; none.
;
;Exit:
; AX != 0 (needed for ForEachCP)
;******************************************************************************
cProc ClearMV,<NEAR,PUBLIC,NODATA>,<di>
localW oMrsCur
cBegin
mov [iHashMax],CBINITMVHASH
xor cx,cx
jmp short ClearPVorMV ;jump into ClearPV; share exit
cEnd <nogen>
cProc ClearPV,<NEAR,PUBLIC,NODATA>,<di>
localW oMrsCur
cBegin ClearPV
GETRS_SEG es
mov cx,PTRRS[si.PRS_oVarHash]
inc cx
.errnz UNDEFINED - 0FFFFH
jz ClearPV_Exit ;brif no hash table for this prs
dec cx
mov [iHashMax],CBINITPVHASH
mov ax,PTRRS[si.PRS_oMrs]
mov [oMrsCur],ax ;save for use by CbTypOTypOMrs
mov bx,ax
RS_BASE add,ax ; ax = pMrs of given prs
GETRS_SEG es
mov di,sp ; assume prs not in current mrs
cmp bx,[grs.GRS_oMrsCur] ;prs in current mrs?
jnz Clear_GotPMrs ; brif not
ClearPVorMV:
mov dx,[grs.GRS_oMrsCur]
mov [oMrsCur],dx ;save for use by CbTypOTypOMrs
mov ax,dataOFFSET mrsCur
SETSEG_EQ_SS es ; es = ss if far Rs tables
sub di,di ; remember to refresh es == ss
; after any calls that hose es
Clear_GotPMrs:
push si ;preserve for caller
xchg ax,si
mov [oVarTHash],cx ;module hash table starts at offset 0
mov [iHashCur],-2 ;so shared code will inc to 0
mov dx,PTRRS[si.MRS_bdVar.BD_pb] ;dx points to base of var table
DbAssertRel dx,nz,0,CP,<ClearMV/ClearPV: no var table in mrsCur (NULL)>
DbAssertRel dx,nz,UNDEFINED,CP,<ClearMV/ClearPV: no var table in mrsCur>
call End_Of_Hash_Chain ;get first var, ax, = oVar, bx = pVar
Clear_Table_Loop:
SETSEG_EQ_SS es ; assume we want to refresh es == ss
or di,di ; is that assumption correct?
jz Clear_Table_Got_Es ; brif so
GETRS_SEG es
Clear_Table_Got_Es:
or ax,ax
jz Clear_Table_Exit ;brif no more vars in table
mov ax,[bx.VAR_flags] ;cache for multiple tests below
test al,FVFUN
jnz Clear_Table_Next ;brif Function or Def FN entry
test ah,FVVALUESTORED SHR 8
jz Clear_Table_Next ;brif value not stored in entry
test ah,FVCONST SHR 8
jz Clear_Table_Cont ;brif not a CONST
test BPTRRS[si.MRS_flags],FM_VARNEW
jz Clear_Table_Next ;brif we're not discarding this var
; table (don't clear CONST values)
Clear_Table_Cont:
test ah,FVARRAY SHR 8
jz Clear_Not_Array ;brif not an array entry
test BPTRRS[si.MRS_flags],FM_VARNEW
jz @F ;brif we're not discarding var table
and [bx.VAR_value.ASTAT_ad.AD_fFeatures],NOT FADF_STATIC
;tell runtime to deallocate this
;array, not just erase it
@@:
lea ax,[bx.VAR_value.ASTAT_ad]
push dx ; save across call
DbHeapMoveOff ;assert no heap movement here
cCall B$IErase,<ax> ;erase the array
DbHeapMoveOn
pop dx
jmp short Clear_Table_Next
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -