📄 nhlhutil.asm
字号:
;----------------------------------------------------------------------
;Start of code to Grow an existing entry - at this point:
; AX = additional space needed (on top of what current entry has)
; BX = size of existing entry
; CX = total size of entry needed to satisfy users request
; DI = input size request
; SI = pointer to header of entry-to-realloc
;----------------------------------------------------------------------
;growing an entry - STEP 1: try to allocate a block of size to
; accomodate entire entry, then copy
; original entry contents, free original
PUSH AX ;save additional space required
MOV CX,[SI].LHBAKP ;get backpointer
MOV DL,[SI].LHTYPE ;input to B$ILHALC
MOV BX,DI ;input realloc size request
CALL B$ILHALC ;try to alloc a block of size caller requested
MOV DI,SI ;DI = ptr to start of data in new entry
MOV DX,SI ;DX = ptr to start of data in new entry
MOV SI,CX ;SI = backpointer
MOV SI,[SI] ;SI = ptr to start of data in old entry
JC REALC_STEP2 ;brif insufficient memory for whole block
;now just block copy data from old entry to new, & free old entry
PUSH AX ;save additional space required across call
PUSH SI ;save pointer to data in entry across call
PUSH BX ;modified by call to b$LH_I_ADJ
MOV AX,DI
SUB AX,SI ;AX = adjustment factor for backpointers to
; any owners contained in this entry
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
CALL B$LH_I_ADJ ; adjust backpointers to any owners in entry
POP BX
POP SI
POP AX
MOV CX,[SI-2] ;CX = number of bytes in original entry
SUB CX,LH_STD_HDR_LEN+2 ; only copy data, not old header ...
SHR CX,1 ;CX = number of words in original entry
PUSH SI
REP MOVSW ;copy contents of old entry to new
POP SI ;need this ptr for deallocation
CALL B$LHDALC ;deallocate original entry
POP AX ;clean up stack
MOV SI,DX ;return value SI = ptr to start of entry data
DJMP JMP SHORT REALC_TRUE_Exit
;growing an entry - STEP 2: try to allocate a block of the size of
; the additional space required, then
; free this block; if this entry is
; above entry to realloc in memory,
; collapse the Local Heap, split
; resulting free entry, set ptr to higher
; of the two free entries; call
; LH_MOV_DN_RG to move all from free
; ptr to entry to realloc down in memory.
; Change hdr to combine free entry with
; given entry.
REALC_STEP2:
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
POP BX ;additional space required for realloc
PUSH BX ;still want this saved
PUSH CX ;save backpointer to input entry
PUSH AX ;put a word on stack to act as backptr for alloc
MOV CX,SP ;backpointer
MOV DL,[SI].LHTYPE
CALL B$ILHALC ;try to alloc block of additional size required
POP CX ;clean stack
POP BX ;backpointer to input entry
POP DX ;additional space required for realloc
JC JB_REALC_FALSE_Exit ;brif insuff. memory - can't realloc [52]
MOV DI,SI ;DI = ptr to start of data in new entry
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
XCHG SI,DI
CALL B$LHDALC ;now free this entry - keep its hdr ptr in DI
MOV SI,[BX] ;SI = ptr to start of data in entry to realloc
CMP SI,DI ;is entry-to-realloc above free entry?
JA REALC_MOV_DOWN ; brif so - don't need to collapse
;free entry is above entry-to-realloc; must collapse the local heap to
; get it below, then split resulting free entry so we can then 'bubble
; up' a free entry of the size we wish to add to the input entry
CALL B$LH_CPCT ;compact current entries to top of heap
MOV SI,[BX] ;SI = ptr to start of data in input entry
MOV DI,[b$HEAP_FREE] ;DI = pointer to resulting free entry at bottom
MOV AX,[b$HEAP_END]
MOV [b$HEAP_FREE],AX ;no longer a b$HEAP_FREE - - - we'll move it
; all up in memory to realloc a piece of it
REALC_MOV_DOWN:
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
PUSH DX
MOV DX,SI
MOV SI,DI ;hdr pointer for free entry
CALL LH_MOV_DN_RG ;mov all in this range down
POP DX
;Now, DI points to hdr of entry to realloc. If next entry up is
; a free entry of sufficient size, split it (if necessary), and
; tack on the extra amount needed to fulfill reallocation request.
MOV SI,DI
ADD SI,[SI+1] ;SI = pointer to next entry up
CMP [SI].LHTYPE,LOW LH_FREE
JNZ REALC_FALSE_Exit ;brif next entry up is not a free one - fail
MOV AX,[SI].LHLEN
SUB AX,DX ;subtract amount needed from amount free
JB_REALC_FALSE_Exit: ; rel jmp out of range made this necessary
JB REALC_FALSE_Exit ;brif insufficient amount for realloc request
PUSH DI ;save hdr ptr to entry to realloc
CALL B$LH_SPLIT ;split entry
JNC REALC_CONT1 ;brif split succeeded
MOV DI,SI ;will grab all of existing entry
REALC_CONT1:
;now combine entry-to-realloc and free entry pointed to by DI
POP SI ;ptr to hdr for entry to realloc
MOV AX,[DI].LHLEN ;length of free header being added
DbAssertRelB <[SI].LHTYPE>,ne,<LOW LH_FILE>,NH_TEXT,<can't realloc fdb's>
;assuming here that realloc header size is STD
SUB SI,(LH_STD_HDR_LEN - 1)
SUB DI,(LH_STD_HDR_LEN - 1)
MOV CX,LH_STD_HDR_LEN
REP MOVSB ;copy existing header to new (top) location
DEC DI
ADD AX,[DI].LHLEN ;add in size of original entry
MOV [DI].LHLEN,AX ;save new entry size
SUB DI,AX
MOV [DI+1],AX ;save it as the back-length too
MOV SI,DI
ADD SI,3 ;make SI = data ptr for realloc'd entry (retval)
REALC_TRUE_Exit:
MOV AL,1 ;return non-zero in AX for successful realloc
REALC_Exit:
POP DI
RET
REALC_FALSE_Exit:
XOR AX,AX
JMP SHORT REALC_Exit
B$LHREALC ENDP
;***
; B$LHChgBakPtr
; Purpose:
; When the ownership of an LH entry is changed or an owner moves, this
; routine is called to change the back pointer.
; Inputs:
; SI = ptr to data of entry whose owner is being changed.
; CX = new value for the backpointer (i.e., a pointer to the new owner)
; Outputs:
; none. ON exit, the back pointer is modified to point to the new owner.
; Note, however, that the new owner contents are not changed to point
; to this entry; the caller must do that.
; Modifies:
; SI only.
; Exceptions:
; B$ERR_ssc if heap entry is inconsistent.
;****
B$LHChgBakPtr PROC NEAR
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
MOV [SI].LHBAKP,CX ;change back pointer
RET
B$LHChgBakPtr ENDP
;***
; B$ILHADJ - adjust the backpointer for a given heap entry
; Purpose:
; This routine provides a mechanism by which the interpreter call-back
; routine B$IHeapEntryMoved can update the back pointer for a single
; heap entry.
;
; Inputs:
; AX = pointer to start of data for a Local Heap entry.
; DI = adjustment factor (same as B$LHADJ passes to B$IHeapEntryMoved)
; Outputs:
; none.
; Modifies:
; none.
; Exceptions:
; none.
;****
B$ILHADJ PROC NEAR
PUSH SI
MOV SI,AX
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
ADD [SI].LHBAKP,DI
POP SI
RET
B$ILHADJ ENDP
;***
;B$IAdUpd - Adjust string array entry backptr when ad moves
;
;Purpose:
; Added with revision [18].
; QB calls this routine to adjust a string array entry backptr
; when the variable table owning the array moves. The
; variable table is allocated in the local heap.
;Entry:
; pAdStr - pointer to string array descriptor that is moving
; Delta - distance that descriptor is moving
;Exit:
; Array entry backpointer is adjusted
;Uses:
; AX
;Exceptions:
; None.
;****
labelFP <PUBLIC,B_IAdUpd> ;Interpeter Reachable Label
cProc B$IAdUpd,<PUBLIC,FAR>,<SI>
parmW pAdStr
parmW Delta
cBegin
MOV SI,pAdStr ;get AD ptr
CMP [SI].AD_fhd.FHD_hData,0 ; is the array allocated?
JZ AdUpd_Exit ; brif not
MOV SI,[SI].AD_fhd.FHD_oData ;get ptr to array data
CALL B$LH_PTR_FROM_DATA ;[SI] = ptr to heap header
DbAssertRel <WORD PTR[SI].LHBAKP>,Z,pAdStr,NH_TEXT,<Invalid pAD passed to B$ISdUpd>
MOV AX,Delta ;get adjustment value
ADD [SI].LHBAKP,AX ;adjust backptr to reflect new location
AdUpd_Exit:
cEnd
;***
; B$LH_SPLIT - split an entry into two pieces
; Purpose:
; Given a header pointer to an entry and a size (must be a size rounded
; to the current header size) for a new free entry, split the entry
; into a free entry (of exactly the requested size) in high mem., with
; the existing entry in low mem. - - - no heap movement takes place.
;
; Inputs:
; SI = hdr ptr to an entry
; AX = size of new entry to be split off
; ES = DS
; Outputs:
; SI is unchanged but is now the hdr ptr for the new free entry
; DI is the new hdr ptr for the existing entry (lower in mem. than SI)
; PSW.C is clear if successful; if input split-off size was zero, PSW.C
; will be set and the block will be unmodified.
; Modifies:
; DI only
; Exceptions:
; none.
;****
B$LH_SPLIT PROC NEAR
PUSH BX
PUSH CX
MOV DI,SI ;in case AX = 0 on entry
CMP AX,LH_STD_HDR_LEN
JC B$LH_SPLIT_EXIT ;brif wish to split off less than a hdr's worth
MOV CX,LH_STD_HDR_LEN
CMP [SI].LHTYPE,LOW LH_FILE
JNZ B$LH_SPLIT_CONT1
ADD CX,(LH_FDB_HDR_LEN - LH_STD_HDR_LEN)
B$LH_SPLIT_CONT1:
MOV BX,[SI].LHLEN
SUB BX,AX
CMP BX,CX
JC B$LH_SPLIT_EXIT ;brif can't take AX worth from entry and leave
; enough for existing header
SUB SI,CX
INC SI ;SI now points to start of header
MOV DI,SI
SUB DI,AX ;set DI to point to start of new header block
; i.e., new header for existing entry. SI
; points to start of old header block
REP MOVSB ;copy header
DEC SI ;SI = hdr pointer for new (free) entry
MOV [DI],AX ;set back length for new free entry
DEC DI
MOV [SI].LHLEN,AX ;set length of new free entry
MOV [SI].LHTYPE,LOW LH_FREE
MOV CX,[DI].LHLEN
SUB CX,AX ;new length of existing entry
MOV [DI].LHLEN,CX ;update length of existing entry
SUB DI,CX
MOV [DI+1],CX ;set new back length for existing entry
ADD DI,CX ;set DI back as entry hdr ptr for return
CLC ;signal successful return
B$LH_SPLIT_EXIT:
POP CX
POP BX
RET
B$LH_SPLIT ENDP
;***
; B$TglHeapSptNEAR - Toggle near heap support code between near heap & var heap
;
; Purpose:
; Added with revision [23].
; Entry:
; For non-RELEASE use, b$fVarHeapActive is non-zero if the variable
; heap is the currently active heap.
; Exit:
; b$fVarHeapActive is updated.
; Uses:
; ES set to DS on exit, otherwise None.
; Exceptions:
; None
;****
cProc B$TglHeapSptNEAR,<PUBLIC,NEAR>,<AX,CX,SI,DI>
cBegin
SET_ES_TO_DS ;movement code requires ES == DS
MOV CX,CW_SWAP_VARS
MOV SI,OFFSET DGROUP:b$HEAP_FIRST
MOV DI,OFFSET DGROUP:b$HEAP_FIRST_SWAP
TglHeap_Loop:
;exchange [si] with [di], advancing si & di
LODSW
XCHG AX,[DI]
MOV [SI-2],AX
INC DI
INC DI
LOOP TglHeap_Loop
CMP [b$fVarHeapActive],CX
JNZ Set_NR_Flag ;brif flag was true; set it false
INC CX ;set flag true - - var heap now active
DbAssertRel b$HEAP_FIRST,b,b$HEAP_END_SWAP,NH_TEXT,<TglHeapSpt error>
Set_NR_Flag:
MOV [b$fVarHeapActive],CX ;set flag for assertion checking
cEnd
;***
; B$TglHeapSpt - Toggle near heap support code between near heap & var heap
;
; Purpose:
; Added with revision [23].
; This is just a PUBLIC FAR interface to a NEAR routine.
; Entry, Exit, Uses, Exceptions:
; Same as for B$TglHeapSptNEAR, above.
;****
cProc B$TglHeapSpt,<PUBLIC,FAR>
cBegin
CALL B$TglHeapSptNEAR
cEnd
;***
; B$NHCPCT - compact all dynamic space
; Purpose:
; Compacts all allocated strings to the bottom of string space.
; Compacts all allocated heap entries to the top of the local
; heap. All free heap space is given to the string space.
;
; Inputs:
; None.
; Outputs:
; None.
; Modifies:
; None
; Exceptions:
; B$ERR_SSC - nontrappable error if compaction finds corruption
; in string space structure.
;****
B$NHCPCT:
ASSERT_NOT_VARHEAP NH_TEXT
CALL B$STCPCT ;compact the string space
CALL B$LH_CPCT ;compact the local heap space
CALL B$STFromLH ;return free heap entry to string space
RET ;return to caller
SUBTTL B$NHMOVALL - Move ALL of dgroup heaps around
PAGE
;***
;B$NHMOVALL - Move ALL of dgroup heaps around
; Addedm revision [26]
;
;Purpose:
; Move everything in the dgroup above __atopsp up or down. This includes
; EVERYTHING above the stack. (Generally precipitated by the movement of the
; top of stack).
;
;Entry:
; [AX] = Proposed delta to __atopsp. Move everything in the heap to
; fit just above this.
; Carry = Set if moving stack DOWN, else reset.
;
;Exit:
; Carry set on error (out of memory).
; [b$NH_First] Updated.
;
;Uses:
; Per convention.
;
;Preserves:
; AX
;
;Exceptions:
; Branches to B$ERR_OM for out of memory.
;
;******************************************************************************
cProc B$NHMOVALL,<NEAR,PUBLIC>,AX
cBegin
JC NHMOVALL_DOWN ;Jump if we are moving __atopsp DOWN
ASSERT_NOT_VARHEAP NH_TEXT ;Should be local heap at this time
;
; Moving up.
; 1) Move the near heap up by the change delta.
; 2) Move the var heap up to the new _atopsp.
; 3) Chop the var heap trailing free entry off by the move amount.
;
PUSH AX ;Save delta
ADD AX,[b$NH_First];[AX] = proposed phyiscal base of near heap
JC NHMOVALL_EXIT_POP ;Jump if bad error.
MOV CX,[b$NH_Last] ;[CX] = unchanged phyiscal end of near heap
PUSH AX ;Save prposed base
cCall B$NHMOV ;[AX] = resulting phyiscal base of near heap
POP AX ;[AX] = proposed phyiscal base of near heap
JNC NHMOVALL_VARUP ;Jump if not out of memory
CALL [b$pFHRaiseBottom];Ask Far Heap to move out of the way
CALL B$NHMOV ;[AX] = resulting phyiscal base of near heap
NHMOVALL_VARUP:
MOV [b$NH_First],AX
JC NHMOVALL_EXIT_POP ;If didn't work, go return right away
CALL B$TglHeapSptNEAR ; switch context to variable heap
XCHG AX,SI ;[SI] = phyiscal base of near heap
DEC SI ;[SI] = physical top of var heap
CALL LH_MOV ;Move the var heap up.
;SI = offset of new local heap start
MOV SI,[b$HEAP_END] ;[SI] = physical base of var heap
POP BX ;[BX] = distance changed
ADD SI,BX ;[SI] = proposed new physical base of var heap
CALL LHSetEnd ;Set the new physical base
CALL B$TglHeapSptNEAR ; switch context to back to local heap
JMP SHORT NHMOVALL_DONE
NHMOVALL_EXIT_POP: ;Error exit, with register pop
POP AX ;Discard TOS
JMP SHORT NHMOVALL_EXIT
;
; Moving Down
; 1) create a trailing free space entry in the var heap
; 2) Move the var heap down
; 3) Move the near heap down
;
NHMOVALL_DOWN:
ASSERT_NOT_VARHEAP NH_TEXT ;Should be local heap at this time
CALL B$TglHeapSptNEAR ; use var heap pointers
ADD AX,[b$HEAP_END] ;[AX] = proposed new physical heap end
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -