home *** CD-ROM | disk | FTP | other *** search
- ; STRSTACK.ASM
- ; (c) 1989, 1990 Ashok P. Nadkarni
- ;
- ; Functions to implement the string stack object for CMDEDIT. Small Model only.
- ;
-
- INCLUDE common.inc
- INCLUDE general.inc
- STRSTACK_ASM EQU 1
-
-
- CSEG SEGMENT PARA PUBLIC 'CODE'
- CSEG ENDS
-
- DGROUP GROUP CSEG
-
- INCLUDE buffers.inc
-
- CSEG SEGMENT PARA PUBLIC 'CODE'
-
- ASSUME CS:DGROUP, DS:DGROUP, SS:DGROUP, ES:DGROUP
-
- EXTRN stre_cmp:PROC
-
- ;+
- ; FUNCTION : strstk_init
- ;
- ; Initializes a $STRING_STACK descriptor. Note that buffer will contain
- ; overhead as well as the actual data itself.
- ;
- ; Parameters:
- ; BX := address of descriptor
- ; AX := address of buffer
- ; CX := buffer size
- ;
- ; Returns:
- ; AX = 0 if success
- ; else -1
- ;
- ; Register CX destroyed.
- ;-
-
- strstk_init proc near
-
- cmp cx,2 ;Need at least 2 bytes in buffer (sentinel)
- jb @strstk_init_90 ;
- cmp cx,32767 ; and LESS than 32767 (Need to represent
- jnc @strstk_init_90 ; + and - differences between first location
- ; and first location beyond buffer in 16 bits)
- mov [bx].low_end,ax ;starting address
- add cx,ax ;Location after last addressable byte of buffer
- ;Various functions assume byte beyond last
- ;buffer location is addressable without
- ;segment wraparound.
- jc @strstk_init_90 ;Segment wraparound.
- dec cx ;CX->Last byte in buffer
- mov [bx].high_end,cx
- call near ptr strstk_reset
- xor ax,ax ;success
- jmp short @strstk_init_99
- @strstk_init_90: ;Buffer too small or
- mov ax,-1 ; overflow (add ax,cx instruction)
- @strstk_init_99:
- ret
-
- strstk_init endp
-
-
-
- ;+
- ; FUNCTION : strstk_reset
- ;
- ; Resets a specified stack to its initial state. The sentinel at the
- ; bottom of the stack is assumed to be already there.
- ;
- ; Parameters :
- ; BX := address of buffer descriptor
- ;
- ; Returns :
- ; Nothing.
- ;
- ; Registers destroyed:
- ; AX
- ;-
- strstk_reset proc near
- mov ax,[bx].low_end
- xchg ax,bx
- mov word ptr [bx],0 ;header & trailer for sentinel null string
- xchg ax,bx
- inc ax ;
- mov [bx].top,ax ;Stack top (sentinel null)
- mov [bx].cur,ax ;Current string (sentinel null)
- mov [bx].savecur,ax
- mov ax,[bx].high_end ;AX->last byte of buffer
- inc ax ;AX->first byte beyond buffer
- mov [bx].topmark,ax ;No markers
- ret
- strstk_reset endp
-
-
- ;+
- ; FUNCTION: strstk_save_cur
- ;
- ; This function saves the cur pointer in the cursave field of the
- ; descriptor structure. It can then be restored with the
- ; strstk_restore_cur call. It is the caller's responsibility to
- ; ensure that the stack does not change in the meanwhile in such a
- ; way as to invalidate the pointer into it. Generally do not do
- ; anything except move the cur pointer around to access different
- ; strings.
- ;
- ; Parameters :
- ; BX := address of buffer descriptor
- ;
- ; Returns :
- ; Nothing.
- ;
- ; Registers destroyed:
- ; AX
- strstk_save_cur proc near
- mov ax,[bx].cur
- mov [bx].savecur,ax
- ret
- strstk_save_cur endp
-
- ;+
- ; FUNCTION: strstk_restore_cur
- ;
- ; This function restores the cur pointer from the cursave field of the
- ; descriptor structure where it was stored through the
- ; strstk_save_cur call. It is the caller's responsibility to
- ; ensure that the stack does not change in the meanwhile in such a
- ; way as to invalidate the pointer into it. Generally do not do
- ; anything except move the cur pointer around to access different
- ; strings. Also, make sure you do a strstk_save_cur before every
- ; strstk_restore_cur.
- ;
- ; Parameters :
- ; BX := address of buffer descriptor
- ;
- ; Returns :
- ; Nothing.
- ;
- ; Registers destroyed:
- ; AX
- strstk_restore_cur proc near
- mov ax,[bx].savecur
- mov [bx].cur,ax
- ret
- strstk_restore_cur endp
-
-
-
- ;+
- ; FUNCTION : strstk_space
- ;
- ; Returns the available space in the buffer. This is 2 less than the
- ; actual number of bytes remaining since we need space for a header
- ; and a trailer for at least one string.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; CF := 1 if no space in stack even for a header or trailer
- ; 0 otherwise
- ; AX := Available space (length of max string that can be fitted)
- ; if CF = 0, if CF = 1, AX is indeterminate
- ;-
- strstk_space proc near
- mov ax,[bx].topmark ;Points BEYOND last usable byte
- sub ax,[bx].top ;actual space in buffer + 1
- ;Need to deduct 1+2(for header/trailer)
- sub ax,3 ;Don't use multiple 'dec ax' here
- ; since it does not set CF.
- ret
- strstk_space endp
-
-
-
-
- ;+
- ; FUNCTION : strstk_settop
- ;
- ; Sets the current string pointer to point to the newest (top
- ; of stack) string.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; Nothing.
- ;
- ; Register AX destroyed.
- ;-
- strstk_settop proc near
- mov ax,[bx].top
- mov [bx].cur,ax
- ret
- strstk_settop endp
-
-
-
- ;+
- ; FUNCTION : strstk_setbot
- ;
- ; Sets the current string pointer to point to the oldest (bottom
- ; of stack) string. If the stack is not empty, the null string at
- ; the bottom is ignored.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; Nothing.
- ;
- ; Registers AX,DX destroyed.
- ;-
- strstk_setbot proc near
- mov ax,[bx].low_end
- inc ax
- cmp ax,[bx].top ;Is stack empty ?
- je @strstk_setbot_99 ;Yes
- inc ax ;Point ax to header of oldest string
- xchg ax,si ;Store in SI
- mov dl,[si] ;get length of string
- xor dh,dh
- add si,dx ;Point SI to last byte in string
- inc si ;Point SI at trailer
- xchg ax,si ;Restore SI and set AX to point to trailer
- @strstk_setbot_99:
- mov [bx].cur,ax ;Set current pointer
- ret
- strstk_setbot endp
-
-
-
- ;+
- ; FUNCTION : strstk_kill
- ;
- ; Deletes the "current" string from the stack. All strings above it
- ; are moved up. "current" string is updated to point to the string
- ; above the deleted string unless the topmost string was deleted
- ; in which case it is set to top of stack.
- ;
- ; Any markers pointing at the deleted string are updated to
- ; point to the new "current" string. Any markers pointing above
- ; the deleted string updated to keep pointing to their
- ; respective strings even after the latter are moved down.
- ; Naturally, the marks below the deleted string do not change.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; Nothing
- ;
- ; Registers AX,CX,DX destroyed
- ;-
- strstk_kill proc near
- @save si,di
-
- mov si,[bx].cur
- mov ax,[bx].low_end ;When current points to the sentinel string,
- inc ax ; exit without deleting it
- cmp ax,si ;Sentinel current ?
- je @strstk_kill_99 ;Yes, exit
-
- mov cx,[bx].top ;topmost occupied location
- mov dx,cx ;remember it
- sub cx,si ;Num bytes to be moved into vacated positions
-
- xor ax,ax
- mov di,si ;di will be used to point to the header of
- ; the deleted string.
- lodsb ;Get the string length into AX.
- ;At the same time SI now points to header
- ;of the string following the condemned string.
- inc ax
- sub di,ax ;di now points to the condemned string header.
- inc ax
- push ax ;Remember how many bytes are to be removed
- sub dx,ax ;Top of stack is now (length of string + 2)
- mov [bx].top,dx ; below the original top
-
- jcxz @strstk_kill_50 ;If # bytes to be moved is 0, then the
- ;deleted string was at the top of the stack.
- push di ;remember header position
- rep movsb ;Copy CX bytes down into vacated positions
- pop si ;Header position of new "current" string
- ; (same location as header of old current)
- lodsb ;SI points to first byte of string
- xor ah,ah ; and AL = length of new current string.
- add ax,si ;AX now points to trailer of new "current"
- jmp short @strstk_kill_90 ;exit
-
- @strstk_kill_50: ;Deleted element was top of stack
- xchg ax,dx ;ax = top, we want cur to be == top
-
- @strstk_kill_90:
- xchg ax,[bx].cur ;cur = top, ax = old current
- pop cx ;Restore the removed byte count
- ; (counterpart of the 'push ax' above)
- IF WANT_MARKERS
- call strstk_update_marks ;Update marks for strings that were moved
- ; ax == old cur, cx == displacement
- ENDIF
- @strstk_kill_99:
- @restore
- ret
- strstk_kill endp
-
-
-
-
- ;+
- ; FUNCTION : strstk_push
- ;
- ; Pushes a string onto the top of the stack. If the force flag parameter
- ; is set to any value other than 0, one or more strings at the bottom
- ; of the stack are deleted to make room fir the new string. If the force
- ; flag is 0, then an error is returned if there is not sufficient room
- ; in the stack. An error is also returned if the string is bigger than
- ; stack size. The stack is left unaltered for both error conditions.
- ;
- ; Parameters:
- ; BX := address of buffer stack descriptor
- ; AL := Length of string
- ; CX := force flag
- ; DX := address of string to be pushed
- ;
- ; Returns:
- ; Carry flag is set if error (not enough stack space), else it is clear.
- ;
- ; Registers AX,CX,DX destroyed.
- ;-
- strstk_push proc near
- @save si,di
- xor ah,ah ;Clear high byte of length.
- mov si,dx ;SI := source string
- push ax ;save length
- jcxz @strstk_push_10 ;Jump if force flag is 0
- call strstk_makespace ;Make sure enough space, else make space
- pop cx ;restore length
- jc @strstk_push_99 ;Error return by strstk_makespace
- jmp short @strstk_push_20 ;Everything OK, go push string
- @strstk_push_10:
- call near ptr strstk_space ;Find out how much space is left
- pop cx ;Restore string length
- jb @strstk_push_99 ;Not even enough for header/trailer,
- ; error return
- cmp ax,cx ;Enough space on stack ?
- jb @strstk_push_99 ;Nope, error return
- @strstk_push_20: ;OK, copy string onto stack
- mov di,[bx].top ;DI := last occupied location on stack
- inc di ;DI := address of header for new string
- mov ax,cx ;Get length into AL
- stosb ;Store length in header
- rep movsb ;Copy string
- mov [bx].top,di ;New top of stack is trailer of topmost string
- mov [bx].cur,di ;Ditto for current string
- stosb ;Store length in trailer
- clc ;Success return
- @strstk_push_99:
- @restore
- ret
- strstk_push endp
-
-
- ;+
- ; FUNCTION : strstk_fwd_match
- ;
- ; Searches towards the top of the stack, starting from the string
- ; above the current string looking for a string that has the specified
- ; pattern as a prefix. If the pattern length is 0, then the match is
- ; universal and the new current string is simply the one immediately
- ; above the current one. The function can thus be used to move the
- ; cur pointer up the stack one string at a time. If the current
- ; string is at the top of the stack, the cur pointer remains
- ; unchanged.
- ;
- ; Parameters:
- ; BX := address of buffer stack descriptor
- ; AX := Address of pattern
- ; CX := Length of pattern
- ; Returns:
- ; CF = 1 if no match or if at top of stack
- ; = 0 if success
- ;
- ; Registers AX,CX destroyed.
- ;-
- strstk_fwd_match proc near
- @save si,di
- mov si,[bx].cur ;SI:=current ptr
- mov di,AX ;Pattern address
-
- @strstk_fwd_match_10:
- cmp si,[bx].top ;Are we at top of stack ?
- je @strstk_fwd_match_90 ;Yes, error exit
- inc si ;SI:=point to next header
- lodsb
- xor ah,ah ;AX := string length
- cmp ax,cx ;Is the pattern longer than string ?
- jnb @strstk_fwd_match_70 ;If not go try a match
- ;Yes, then try next string
- add si,ax ;Point to trailer
- jmp short @strstk_fwd_match_10 ;and loop back
- @strstk_fwd_match_70: ;OK, see if pattern is the string prefix
- push cx ;Remember pattern length
- push ax ;Remember string length
- call near ptr stre_cmp ;Check if pattern is a prefix
- pop ax ;Restore string length
- mov cx,ax ;Temp storage
- lahf ;Save value returned by stre_cmp
- add si,cx ;SI := trailer
- pop cx ;Restore pattern length
- sahf ;Restore stre_cmp result
- jne @strstk_fwd_match_10 ;No match, loop back
- clc ;No errors
- jmp short @strstk_fwd_match_99
-
- @strstk_fwd_match_90:
- stc ;Error return
- @strstk_fwd_match_99:
- mov [bx].cur,si
- @restore
- ret
- strstk_fwd_match endp
-
-
- ;+
- ; FUNCTION : strstk_bck_match
- ;
- ; Searches towards the bottom of the stack, starting from the string
- ; below the current string looking for a string that has the specified
- ; pattern as a prefix. If the pattern length is 0, then the match is
- ; universal and the new current string is simply the one immediately
- ; below the current one. The function can thus be used to move the
- ; cur pointer down the stack one string at a time. If the current
- ; string is at the bottom of the stack, the cur pointer remains
- ; unchanged.
- ;
- ; Parameters:
- ; BX := address of buffer stack descriptor
- ; AX := Address of pattern
- ; CX := Length of pattern
- ; Returns:
- ; CF = 1 if no match or if at bottom of stack
- ; = 0 if success
- ;
- ; Registers AX,CX destroyed.
- ;-
- strstk_bck_match proc near
- @save si,di
- push bp
- mov bp,sp
- sub sp,2
- sentinel EQU <word ptr [bp-2]>
- push ax ;remember pattern address
- mov di,[bx].low_end ;Buffer bottom
- inc di
- mov si,[bx].cur ;SI:=current pointer
- cmp si,di ;At stack bottom ? ( low_end + 1 == cur)
- je @strstk_bck_match_90 ;If so exit,
- ; (the 'push AX' is cleaned up by unlink)
- mov sentinel,di ;remember sentinel value
-
- pop di ;Restore pattern address
-
- ; Prime for loop below
- xor ah,ah
- mov al,[si] ;AX<-length of current string
- sub si,ax ;SI->start of string
-
- @strstk_bck_match_9:
- ; Loop begin. SI points to the first byte of string last compared. This
- ; cannot be the sentinel string.
- dec si ;SI->header of current string
- dec si ;SI->trailer of previous string
-
- @strstk_bck_match_10:
- ; At this point SI points to the trailer of string to try'n'match
- cmp si,sentinel ;Are we at bottom ?
- je @strstk_bck_match_90 ;Yes, exit
- mov al,[si] ;String length
- xor ah,ah
- sub si,ax ;Point to first byte of string
- cmp ax,cx ;Is the pattern longer than string ?
- jb @strstk_bck_match_9 ;Yes, then try next string
- ;OK, try see if pattern is the string prefix
- push cx ;Remember pattern length
- call near ptr stre_cmp ;Check if pattern is a prefix
- pop cx
- jne @strstk_bck_match_9 ;Not a prefix, go try next one
- xor ax,ax
- mov al,-1[si] ;AX<-length of matched string
- add si,ax ;Point SI to trailer of matched string
- ; Successful match, return with CF clear.
- ; Carry flag is guaranteed clear since no o'flow is possible in
- ; the add si,ax instruction. Hence comment out the following clc.
- ; clc
- jmp short @strstk_bck_match_99
- @strstk_bck_match_90:
- stc ;Error return
-
- @strstk_bck_match_99:
- mov [bx].cur,si ;Update current string pointer
- mov sp,bp
- pop bp
- @restore
- ret
- strstk_bck_match endp
-
-
-
-
- ;+
- ; FUNCTION : strstk_fwd_find,strstk_bck_find
- ;
- ; Searches towards the top/bottom of the stack, starting from the string
- ; above/below the current string looking for a string that is the same
- ; as the specified one. If the current string is at the top/bottom
- ; the stack, the cur pointer remains unchanged.
- ;
- ; Parameters:
- ; BX := address of buffer stack descriptor
- ; AX := Address of string
- ; CX := Length of string
- ; Returns:
- ; CF = 1 if no match or if at top/bottom of stack
- ; = 0 if success
- ;
- ; Registers AX,CX,DX destroyed.
- ;-
- strstk_find proc near
- strstk_fwd_find LABEL near
- push di ;Save di
- push si ;and si
- mov di,offset CSEG:strstk_fwd_match
- jmp short @strstk_find_8
- strstk_bck_find LABEL near
- push di ;Save di
- push si ;and si
- mov di,offset CSEG:strstk_bck_match
- @strstk_find_8:
- mov si,ax ;Save string address in SI
- @strstk_find_10:
- ; Loop start
- mov ax,si ;AX->string
- push cx ;Save string length
- call di ;Look for prefix
- pop cx ;Restore string length
- jc @strstk_find_99 ;Not found
- push cx
- xor cx,cx ;Don't want to copy, just need size
- call near ptr strstk_copy ;AX<-length of current string
- pop cx ;Restore passed length
- cmp ax,cx ;Strings match ?
- jne @strstk_find_10 ;Lengths not same, keep looking
- clc ;Strings same
- @strstk_find_99:
- pop si
- pop di
- ret
- strstk_find endp
-
-
-
- ;+
- ; FUNCTION : strstk_makespace
- ;
- ; Deletes enough strings from the bottom of the stack to make room
- ; for a string of the length specified in AX. If the stack size is
- ; smaller than the requested size, the stack is left unchanged and
- ; an error indication returned. If there is already enough room in
- ; the stack, the stack is left unchanged. In both cases the current
- ; string ptr is updated to point to the top of the stack. Note that
- ; any marks, if present, reduce the space that is available.
- ;
- ; The routine is not very efficient since it keeps calling strstk_kill
- ; rather than deleting the required number in one shot. But it is
- ; more compact.
- ; Parameters:
- ; BX := pointer to buffer descriptor
- ; AX := requested length
- ; Returns:
- ; CF = 1 if error (requested length to large for stack)
- ; = 0 success
- ; Also changes current string pointer to point to top of stack.
- ; Registers AX,CX,DX destroyed.
- ;-
- strstk_makespace proc near
- @save si,di
- xchg ax,si ;Save requested length in SI
- call strstk_size ;AX := size of largest string that can
- ; fit in an empty stack
- cmp ax,si ;Smaller than requested length ?
- jb @strstk_makespace_99 ;Yes, error exit
- call strstk_setbot ;Set current string to bottommost
-
- ;Now keep iterating until enough strings have been deleted. Since we
- ;have already checked that the stack is large enough, the loop below
- ;is guaranteed to terminate.
-
- @strstk_makespace_10:
- ; Note that the strstk_space routine returns a 0 if there are less than
- ; the 2 bytes required for header/trailer. The carry flag must be
- ; checked to distinguish this from the situation where there is room
- ; for a null string (exactly 2 bytes available)
- call near ptr strstk_space ;AX := available space
- jnc @strstk_makespace_70 ;Jump if > 2 bytes available
- @strstk_makespace_65:
- call strstk_kill ;If not delete one more
- jmp short @strstk_makespace_10 ;And keep trying
- @strstk_makespace_70:
- cmp ax,si ;Enough space available ?
- jb @strstk_makespace_65 ;Yes, exit
- @strstk_makespace_99:
- call near ptr strstk_settop
- @restore
- ret
- strstk_makespace endp
-
-
- ;+
- ; FUNCTION : strstk_copy
- ;
- ; Returns a copy of the current stack entry. Stack is unchanged.
- ; If the stack is empty, a 0 length string is returned.
- ; If the user buffer is not large enough, as many characters as
- ; possible are copied into it. AX reflects the length of the actual
- ; string and not just the copied part and the carry flag is set.
- ; Thus this routine can also be used to find the length of the current
- ; string by passing it a zero length buffer.
- ;
- ; Parameters:
- ; BX := pointer to buffer descriptor
- ; AX := starting address of location into which the string
- ; is to be copied
- ; CX := size of buffer
- ;
- ; Returns:
- ; AX = length of current string (ACTUAL LENGTH, NOT COPIED LENGTH)
- ; CF = 0 if the user buffer is large enough
- ; = 1 if user buffer too small
- ; As many chars as possible are returned in the use buffer.
- ; Register CX destroyed.
- ;-
- strstk_copy proc near
- @save si,di
- mov di,ax ;Destination buffer
- mov si,[bx].cur ;SI := trailer of current string
- mov al,[si]
- xor ah,ah ;AX:=length of current string
- sub si,ax ;SI->first byte of string
- cmp cx,ax ;User buffer large enough ?
- jb @strstk_copy_5 ;No, error return
- ;Note empty stack case automatically handled.
- mov cx,ax ;CX<-length of string to copy
- @strstk_copy_5:
- pushf ;Save carry flags
- ; CX == number of bytes to copy
- rep movsb
- popf ;Restore CF
- @restore
- ; Return AX = length of actual string
- ret
- strstk_copy endp
-
-
-
- ;+
- ; FUNCTION : strstk_size
- ;
- ; Returns the maximum size string that can fit in the buffer if all
- ; strings are deleted (but not markers).
- ;
- ; Parameters:
- ; BX := buffer descriptor address
- ;
- ; Returns:
- ; AX := Max string size for buffer if all strings are deleted
- ;
- ; All registers (except AX) are preserved.
- ;-
- strstk_size proc near
- mov ax,[bx].topmark ;Address beyond last available
- ; for strings
- sub ax,[bx].low_end ;bottom of buffer (sentinel header)
- sub ax,4 ;Need 2 for header trailer + 2 for
- ; sentinel
- jnb @strstk_size_99 ;
- xor ax,ax ;No space !
- @strstk_size_99:
- ret
- strstk_size endp
-
-
-
-
-
- ;+
- ; FUNCTION : strstk_prefix
- ;
- ; Compares the passed string to check if it is a prefix of the
- ; current string in the stack.
- ;
- ; Parameters:
- ; BX := buffer descriptor address
- ; AX := address of string
- ; CX := length of string
- ;
- ; Returns:
- ; ZF = 1 if string is prefix
- ; 0 if not
- ;
- ; Register(s) destroyed:
- ;-
- strstk_prefix proc near
- @save si,di
- xchg di,ax ;DI->string
- mov si,[bx].cur ;SI->trailer byte of stack element
- xor ah,ah ;Clear high byte
- mov al,[si] ;AX<-length of string
- cmp ax,cx ;Passed string longer ?
- jb @strstk_prefix_90 ;No, return `not prefix'
- sub si,ax ;SI->start of string
- call near ptr stre_cmp
- ; ZF is set if match occurs, 0 otherwise
- jmp short @strstk_prefix_99
- @strstk_prefix_90:
- inc al ;Set ZF=0 (no match)
- @strstk_prefix_99:
- @restore
- ret
- strstk_prefix endp
-
-
-
-
- ;+
- ; FUNCTION : strstk_compare
- ;
- ; Compares the passed string against the current string in the stack.
- ;
- ; Parameters:
- ; BX := buffer descriptor address
- ; AX := address of string
- ; CX := length of string
- ;
- ; Returns:
- ; ZF = 1 if strings equal
- ; 0 if not equal.
- ;
- ; Register(s) destroyed:
- ;-
- strstk_compare proc near
- @save si,di
- xchg di,ax ;DI->string
- mov si,[bx].cur ;SI->trailer byte of stack element
- xor ah,ah ;Clear high byte
- mov al,[si] ;AX<-length of string
- cmp ax,cx ;Same length?
- jne @strstk_compare_99 ;No, return `not equal'
- jcxz @strstk_compare_99 ;Equal (zero length), ZF
- ; already set
- sub si,ax ;SI->start of string
- call near ptr stre_cmp ;Case-insensitive compare
- ; ZF is set if match occurs, 0 otherwise
- @strstk_compare_99:
- @restore
- ret
- strstk_compare endp
-
-
-
- IF WANT_MARKERS
- ;+
- ; FUNCTION : strstk_update_markers
- ;
- ; This routine is called to update the markers that point to various
- ; strings in the stack. This is necessary when strings are deleted
- ; causing the string positions to change.
- ;
- ; Parameters:
- ; BX := address of stack descriptor
- ; AX := The address of the old (deleted) current string
- ; CX := Number of bytes by which the strings were displaced.
- ;
- ; Returns:
- ; Nothing.
- ; Registers AX is destroyed.
- ;-
- strstk_update_marks proc near
- @save si,di
- xchg ax,si ;Store old current address in SI
- mov di,[bx].topmark ;DI will iterate through the marks
- @strstk_update_marks_20:
- cmp di,[bx].high_end
- jnc @strstk_update_marks_99 ;All done
- mov ax,[di] ;Old address of marked string
- cmp si,ax ;Compare with address of deleted string
- jne @strstk_update_marks_40 ;
- mov ax,[bx].cur ;Mark pointed to deleted string so
- jmp short @strstk_update_marks_50 ;point it to new current
- @strstk_update_marks_40:
- jg @strstk_update_marks_50 ;If mark pointed BELOW, no change
- sub ax,cx ;Else subtract the displacement
- @strstk_update_marks_50:
- stosw ;Store new value back, increment DI to point
- jmp short @strstk_update_marks_20 ; to next mark and loop
-
- @strstk_update_marks_99:
- @restore
- ret
- strstk_update_marks endp
-
-
-
- ;+
- ; FUNCTION : strstk_mark_cur
- ;
- ; Changes the topmost mark to point to the current string. If no marks
- ; exist, one is created.
- ;
- ; Parameters:
- ; BX := address of descriptor.
- ;
- ; Returns:
- ; CF = 1 if error (no room), else 0.
- ; Register AX is destroyed.
- ;-
- strstk_mark_cur proc near
- call strstk_kill_mark
- call strstk_push_mark
- ret
- strstk_mark_cur endp
-
-
- ;+
- ; FUNCTION : strstk_kill_mark
- ;
- ; Deletes the topmost mark on the stack.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; CF = 1 if stack was empty, else 0.
- ; Register AX is destroyed.
- ;-
- strstk_kill_mark proc near
- mov ax,[bx].high_end ;Highest location of buffer
- cmp ax,[bx].topmark ;Marker stack empty ?
- jb @strstk_kill_mark_99 ;Yes
- dec [bx].topmark ;Remove topmost mark by updating
- dec [bx].topmark ; top of stack ptr
- @strstk_kill_mark_99:
- ret
- strstk_kill_mark endp
-
-
- ;+
- ; FUNCTION : strstk_push_mark
- ;
- ; Pushes a marker to the current string onto the marker stack.
- ;
- ; Parameters:
- ; BX := address of descriptor
- ;
- ; Returns:
- ; CF = 1 if error (no room), else 0.
- ; Register AX is destroyed.
- ;-
- strstk_push_mark proc near
- @save di
- mov di,[bx].topmark ;Point to topmost mark
- dec di
- dec di ;Next location to push mark
- cmp di,[bx].top ;Enough room ?
- jle @strstk_push_mark_90 ;Sorry, return error
- mov [bx].topmark,di ;New stack top
- mov ax,[bx].cur ;Address of current string
- stosw ;Store in top marker
- ;Carry is clear
- jmp short @strstk_push_mark_99
- @strstk_push_mark_90:
- stc ;Set error
- @strstk_push_mark_99:
- @restore
- strstk_push_mark endp
-
-
- ;+
- ; FUNCTION : strstk_pop_mark
- ;
- ; Pops the topmost mark off the stack and set the current ptr
- ; to point to its associated string.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; CF = 1 if no marks, else 0.
- ; Register AX is destroyed.
- ;-
- strstk_pop_mark proc near
- call strstk_goto_mark
- call strstk_kill_mark
- ret
- strstk_pop_mark endp
-
-
-
- ;+
- ; FUNCTION : strstk_goto_mark
- ;
- ; Sets the current string pointer to the string associated with the
- ; topmost marker on the marker stack.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; CF = 1 if no markers, else 0.
- ; Register AX is destroyed.
- ;-
- strstk_goto_mark proc near
- mov ax,[bx].high_end
- cmp ax,[bx].topmark
- jb @strstk_goto_mark_99 ;No marks
- mov ax,[bx].topmark
- mov [bx].cur,ax ;Update current string ptr
- @strstk_goto_mark_99:
- ret
- strstk_goto_mark endp
-
-
- ;+
- ; FUNCTION : strstk_purge_marks
- ;
- ; Deletes all marks that point to the sentinel string. The marker
- ; stack is compacted.
- ;
- ; Parameters:
- ; BX := address of buffer descriptor
- ;
- ; Returns:
- ; Nothing.
- ; Register(s) AX,CX are destroyed.
- ;-
- strstk_purge_marks proc near
- @save si,di
- mov cx,[bx].low_end
- inc cx ;CX = sentinel string trailer
- mov di,[bx].high_end
- inc di
- mov si,di
- @strstk_purge_marks_10: ;SI = last marker location examined
- ;DI = last marker location stored
- cmp si,[bx].topmark ;Checked all markers ?
- je @strstk_purge_marks_99 ;Yes, exit
- dec si
- dec si ;Next location to check
- mov ax,[si] ;Marker value
- cmp ax,cx ;Points to sentinel ?
- jg @strstk_purge_marks_10 ;No, go check next
- dec di
- dec di ;DI = next location to store
- mov [di],ax ;Store marker
- jmp short @strstk_purge_marks_10
- @strstk_purge_marks_99:
- mov [bx].topmark,di ;Store new top of marker stack
- @restore
- ret
- strstk_purge_marks endp
-
- ENDIF ;WANT_MARKERS
-
- CSEG ENDS
-
- END