📄 nhlhcore.asm
字号:
; Create the new heap entry from the empty space.
MOV DI,SI ;[DI] = what will be string END entry
ADD DI,LH_STD_HDR_LEN+1 ;[DI] = what will be heap END entry
ADD DI,AX ;[DI] = new entry being created
LH_SS_FINISH_UP:
; When we get here:
; SI points to new string space end location
; DI points to new (or enlarged) free heap entry
; AX = size of new (or enlarged) free heap entry
; Define the new string space end entry and its pointer.
MOV [SI],0FFFFH ;set string end entry
MOV [b$STRING_END],SI ;set string end pointer
MOV [b$STRING_FREE],SI ;set free string pointer
; Define the new heap END entry and its pointer.
ADD SI,LH_STD_HDR_LEN+1 ;point to new END entry
MOV [SI].LHTYPE,LOW LH_END ;define the entry type
MOV [b$HEAP_END],SI ;define the heap end pointer
; Update header for new or enlarged free heap entry and set
; b$HEAP_FREE to point to it.
MOV [DI].LHTYPE,LOW LH_FREE ;set heap entry type
MOV [DI].LHLEN,AX ;set free heap entry length
MOV [SI+1],AX ;set free heap entry backlength
MOV [b$HEAP_FREE],DI ;set heap free entry pointer
LH_SS_RETURN:
POP DI ;restore registers...
POP SI
POP AX
RET ;return with new heap free entry
;***
; B$LH_SCAN -Scan the entire local heap area for an entry of the
; requested amount of storage. Adjacent unallocated
; entries are combined before tested for allocation.
;
; Inputs: BX - amount of heap storage to allocate.
; DL - type of heap entry to allocate.
; CL - if DL=LH_FILE, file number
; CX - if DL=LH_ARRAY, array descriptor offset
; [b$HEAP_FIRST] - pointer to first entry to test
;
; Outputs: CF=0 - allocation was successful.
; SI - pointer to data in allocated entry.
; CF=1 - allocation failed.
;
; Start the scan with the entry pointed by [b$HEAP_FIRST].
;****
B$LH_SCAN:
MOV SI,[b$HEAP_FIRST] ;starting point of scan
; No pending unallocated entries. If END entry, then failed.
; If FREE entry, then jump to try to combine subsequent ones.
LH_SCAN_NEXT:
CMP [SI].LHTYPE,LOW LH_END ;test if last local heap entry
JE LH_SCAN_FAIL ;if so, then allocation failed
CMP [SI].LHTYPE,LOW LH_FREE ;test if entry is unallocated
JE LH_SCAN_FREE ;if so, jump to scan for next free entries
SUB SI,[SI].LHLEN ;move pointer to the next entry
JMP SHORT LH_SCAN_NEXT ;and try again
; Pending unallocated entry. Test the next entry. If END, try
; a final allocation attempt. If allocated, attempt allocation
; and continue scan if it fails. If FREE, combine the two entries
; and loop back. Keep size of free entry in AX until allocation.
LH_SCAN_FREE:
MOV AX,[SI].LHLEN ;get size of first free block
LH_SCAN_NEXT_FREE:
MOV DI,SI ;get copy of present scan pointer
SUB DI,AX ;now points to following entry
CMP [DI].LHTYPE,LOW LH_END ;test if next entry is END
JE LH_SCAN_TRY ;if so, try a final allocation
CMP [DI].LHTYPE,LOW LH_FREE ;test if next entry is FREE
JNE LH_SCAN_TRY ;if not, try allocation, but continue
ADD AX,[DI].LHLEN ;add for length of both FREE entries
JMP SHORT LH_SCAN_NEXT_FREE ;and loop to try again
; Try to allocate from the entry at [SI]. If failure, point
; past the allocated entry at [DI] and continue scan if not at
; heap end. If at heap end, return with failure.
LH_SCAN_TRY:
MOV [SI].LHLEN,AX ;set the new length of the combined block
SUB SI,AX ;point to next block (one after backlength)
MOV [SI+1],AX ;set the backlength
ADD SI,AX ;return pointer to start of combined block
CMP AX,BX ;test entry against allocation needed
JAE LH_ALC ;if enough room, finish allocation
CMP [DI].LHTYPE,LOW LH_END ;test if at end of heap
JE LH_SCAN_FAIL ;if so, then just fail
SUB DI,[DI].LHLEN ;point to entry after allocated one
MOV SI,DI ;move pointer to continue scan
JMP SHORT LH_SCAN_NEXT ;and jump to continue it
; Allocate not possible, return with carry set for failure.
LH_SCAN_FAIL:
MOV [b$HEAP_FREE],SI ;set free entry to last unallocated one
STC ;carry set for failure
RET ;and return to caller
; B$LH_ALC_FREE - test if free heap entry can allocate the
; requested amount of storage
; Inputs: BX - amount of heap storage to allocate.
; DL - type of heap entry to allocate.
; CL - if DL=LH_FILE, file number
; CX - if DL=LH_ARRAY, array descriptor offset
; [b$HEAP_FREE] - pointer to entry to test
; Outputs: CF=0 - allocation was successful.
; SI - pointer to data in allocated entry.
; CF=1 - allocation failed.
; Test if free local heap entry is unallocated and large enough.
; If so, then allocate it, otherwise fail.
B$LH_ALC_FREE:
MOV SI,[b$HEAP_FREE] ;point to free local heap entry
CMP [SI].LHTYPE,LOW LH_FREE ;test if free entry is unallocated
JNE LH_ALC_FAIL ;if not free, then jump to fail
MOV AX,[SI].LHLEN ;get length of the entry
CMP AX,BX ;test if entry is large enough
JAE LH_ALC ;if so, then jump to allocate
LH_ALC_FAIL:
STC ;set carry to note failure
RET ;return to caller
; There wasn't enough room to split entry and allocate a new FREE
; entry. Allocate the whole entry instead of splitting it.
LH_ALC_ALL:
ADD BX,AX ;change requested block size to whole entry
JMP SHORT LH_ALC_EXACT ;allocate whole block
; The entry at [SI] can be allocated. If the entry is larger than
; the size needed, split it into two entries with the higher one
; used in the allocation.
LH_ALC:
JE LH_ALC_EXACT ;if exact allocation, then no split needed
SUB AX,BX ;size of remainder block
CMP AX,LH_STD_HDR_LEN ;is there enough room for new header?
JB LH_ALC_ALL ;allocate whole entry if not enough room
SUB SI,BX ;point to header of new remainder entry
MOV [SI].LHTYPE,LOW LH_FREE ;set type for FREE entry
MOV [SI].LHLEN,AX ;put size into new entry header
SUB SI,AX ;point to next entry (byte before backlength)
MOV [SI+1],AX ;put in backlength for the present entry
ADD SI,AX ;point back to remainder block
ADD SI,BX ;point back to newly allocated block
LH_ALC_EXACT:
; Clear the new heap entry to zeroes.
PUSH CX ;save registers for clear...
PUSH DI
PUSH ES
PUSH DS
POP ES ;set ES = DS
MOV DI,SI ;copy pointer to header of allocated block
SUB DI,BX ;point to header of previous block
MOV [b$HEAP_FREE],DI ;free entry is now previous block
INC DI ;now point to data of block to be allocated
XOR AX,AX ;value to set entry locations
MOV CX,BX ;get size of entry in bytes
SHR CX,1 ;convert size to words
REP STOSW ;clear the entry
POP ES
POP DI ;restore registers...
POP CX
; Finish by setting the header values
MOV [SI].LHTYPE,DL ;set the heap entry type
MOV [SI].LHLEN,BX ;set the heap entry length
SUB SI,BX ;point to next entry (byte before backlength)
MOV [SI+1],BX ;set the backlength
ADD SI,BX ;set point back to entry header
CMP [SI].LHTYPE,LOW LH_FILE ;test if FILE entry
JNE LH_ALC_NOT_FILE ;if not, then branch
MOV [SI].LHFNUM,CL ;set file number
JMP SHORT LH_ALC_EXIT
LH_ALC_NOT_FILE:
MOV [SI].LHBAKP,CX ;all entries have backpointers except fdb's
LH_ALC_EXIT:
SUB SI,BX ;point to previous entry
ADD SI,3 ;set to start of entry data (past backlength)
RET ;return with carry clear
page
;***
; B$LHDALC_CPCT -- deallocate heap entry and compact heap. Added with [44].
;
;Purpose:
; Deallocates heap entry, and then compacts local heap, so that no
; no "holes" develop in the heap.
;
;Entry/Exit/Uses/Exceptions:
; Same as B$LHDALC/B$LH_CPCT.
;
;******************************************************************************
cProc B$LHDALC_CPCT,<PUBLIC,NEAR>
cBegin
CALL B$LHDALC ; deallocate heap entry
cEnd <nogen> ; fall into B$LH_CPCT
;***
; B$LH_CPCT - compact local heap space
; Purpose:
; Compacts all allocated local heap entries to the top of
; the local heap space. The backpointers in the ARRAY and FILE
; entries are adjusted appropriately to reflect their movement.
; The remaining unallocated space is made into the free entry.
; NOTE: The scan (and compaction) moves from high memory to low.
;
; Inputs:
; None
; Outputs:
; [b$HEAP_FREE] points to the new free heap entry.
; Exceptions:
; B$ERR_SSC - nontrappable error if compaction finds corruption
; in the local heap space structure.
;****
B$LH_CPCT PROC NEAR
PUSH ES
PUSH DS
POP ES ;Set ES = DS
PUSH AX ;save registers used...
PUSH BX
PUSH CX
PUSH SI
PUSH DI
MOV SI,[b$HEAP_FIRST] ;pointer to heap scan
; Skip over leading allocated entries which can be ignored since
; they will not be moved. While skipping, an END entry implies
; no compaction need to be done. Check all allocated entries.
B$LH_CPCT_SKIP:
CMP [SI].LHTYPE,LOW LH_END ;test for end of local heap
JE B$LH_CPCT_DONE ;if so, no compact, just return
CALL B$LH_PTR_CHECK ;check entry at [SI] for consistency
CMP [SI].LHTYPE,LOW LH_FREE ;test if leading allocated entry
JE B$LH_CPCT_FIRST_FREE ;if not, then skipping is over
SUB SI,[SI].LHLEN ;point to next entry
JMP SHORT B$LH_CPCT_SKIP ;and try again
; First unallocated heap entry found. Initialize compacted pointer DI.
B$LH_CPCT_FIRST_FREE:
MOV DI,SI ;SI=scan pointer - DI=compacted pointer
; Unallocated heap entry just advances the scan pointer SI.
B$LH_CPCT_NEXT_FREE:
SUB SI,[SI].LHLEN ;point to entry after unallocated one
; Process the entry at [SI]. First check consistency of entry.
B$LH_CPCT_NEXT:
; If END entry, compaction is done - jump to finish up.
CMP [SI].LHTYPE,LOW LH_END ;test for END entry
JE B$LH_CPCT_SETUP_FREE ;jump to set up free entry
; If FREE entry, jump to advance scan pointer SI.
CALL B$LH_PTR_CHECK ;check entry at [SI]
CMP [SI].LHTYPE,LOW LH_FREE ;test for FREE entry
JE B$LH_CPCT_NEXT_FREE ;jump to advance scan pointer
; Allocated entry - adjust the entry backpointers to reflect
; its new location at [DI].
MOV AX,DI ;set to new entry location
SUB AX,SI ;subtract to get adjustment factor
CALL B$LHADJ ;adjust the entry using the factor in AX
; Move the entry from [SI] to [DI] with direction flag SET.
MOV CX,[SI].LHLEN ;get length of entry in bytes
SHR CX,1 ;make the length in words
DEC SI ;point to word address in source
DEC DI ;point to word address in destination
STD ;all strings move down in memory
REP MOVSW ;move the entry to its new location
CLD ;restore direction flag
INC SI ;point back to byte in source
INC DI ;also in destination
; Now make the space between the moved entry and the next entry
; a free heap entry. This will ensure heap consistency and
; allow routines called during the middle of compaction to
; walk the heap.
MOV [DI].LHTYPE,LOW LH_FREE ;set type of FREE entry
MOV [DI].LHLEN,AX ;set size of new entry
MOV [SI+1],AX ;also set backlength of new entry
JMP SHORT B$LH_CPCT_NEXT ;try again (SI and DI are already adjusted)
; Compaction is done - set up the unused space as a FREE entry and
; point to it for the next allocation.
B$LH_CPCT_SETUP_FREE:
MOV AX,DI ;get length of remaining entry...
SUB AX,SI ;by the difference of the pointers
JZ B$LH_CPCT_NO_FREE ;if no entry left, then jump
MOV [DI].LHTYPE,LOW LH_FREE ;set type of FREE entry
MOV [DI].LHLEN,AX ;set size of new entry
MOV [SI+1],AX ;also set backlength of new entry
B$LH_CPCT_NO_FREE:
MOV [b$HEAP_FREE],DI ;new entry for next allocation
; Restore registers and return.
B$LH_CPCT_DONE:
POP DI ;restore registers...
POP SI
POP CX
POP BX
POP AX
B$LH_CPCT_EXIT:
POP ES
RET ;return to caller
B$LH_CPCT ENDP
;***
; B$LHDALC - deallocate heap entry
; Purpose:
; To deallocate the heap entry whose data area is pointed by SI.
;
; Inputs:
; SI = pointer to heap entry data area
; Outputs:
; None.
; Modifies:
; ES, if interpreter version
; Exceptions:
; None.
;****
B$LHDALC PROC NEAR
PUSH ES
PUSH DS
POP ES ;Set ES = DS
PUSH AX ;save registers...
PUSH SI
CALL B$LH_PTR_FROM_DATA ;get entry pointer from SI data pointer
XOR AX,AX ;set flag for entry deallocation
CALL B$LHADJ ;call to deallocate all string data in entry
MOV [SI].LHTYPE,LOW LH_FREE ;set array type to FREE
POP SI ;restore registers...
POP AX
POP ES
RET ;return to caller
B$LHDALC ENDP
;***
; B$LHADJ - delete/adjust a heap entry
; Function:
; Deallocates or adjusts the heap entry pointed by SI.
; If AX=0, all string data referenced by descriptors within
; the entry is deallocated.
; If AX<>0, all backpointers referenced within the entry are
; adjusted by the value of AX.
;
; NOTE: In QB versions, B$LHDALC can call this routine to deallocate [23]
; NOTE: an entry in the variable heap while the local heap is active. [23]
; NOTE: This causes no problems in this routine as it is now, because [23]
; NOTE: we'll never have an LH_FILE or LH_ARRAY entry in the variable [23]
; NOTE: heap. [23]
;
; Inputs:
; AX = adjustment value
; AX=0 - deallocate all entry string data.
; AX<>0 - adjust all entry backpointers.
; SI = address of heap entry.
; DS = segment that heap is in
; ES = segment that state vars are in
; Outputs:
; None.
; Modifies:
; None.
; Exceptions:
; None.
;****
assumes ES,DGROUP
assumes DS,NOTHING
B$LHADJ PROC NEAR
PUSH BX ;save registers...
PUSH CX
CMP [SI].LHTYPE,LOW LH_FILE ;test if entry is FILE
JNE ADJLHP_NOT_FILE ;if not, then jump [23]
ASSERT_NOT_VARHEAP NH_TEXT
LEA BX,[SI+3] ;point to 1 word past heap header
SUB BX,[SI].LHLEN ;point at heap entry data
CMP BX,ES:[b$PTRFIL] ;are we moving PTRFIL?
JNZ NotPtrFil ;brif not
ADD ES:[b$PTRFIL],AX ;adjust if moving ptrfil
NotPtrFil:
; Entry is FILE - deallocate/adjust the fielded string backpointer
; if it exists.
CMP WORD PTR [SI].LHPLEN,0 ;test if fielded string is null
JZ ADJLHP_EXIT ;if so, then just return
MOV BX,[SI].LHPOFF ;get offset of fielded string data
ADD [BX-2],AX ;add adjustment to the string backpointer
OR AX,AX ;test if deallocation was requested
; JNZ ADJLHP_QUIT ;if just adjustment, then jump
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -