home *** CD-ROM | disk | FTP | other *** search
- title MOVBITS subroutine
- page 80,132
- .radix 10
- ;******************************************************************************
- ;* *
- ;* MOVBITS SUBROUTINE FOR USE IN TURBO PASCAL *
- ;* *
- ;* TURBO PASCAL DECLARATION-- procedure movbits(targseg,targoff,targbit, *
- ;* srcseg,srcoff,srcbit,nobits:integer); external 'movbits.bin'; *
- ;* *
- ;* targseg -- segment address of target area *
- ;* targoff -- offset to first byte of target area *
- ;* targbit -- starting bit number in target area, numbered from 0, *
- ;* e.g., bit 0 is msb of byte at targseg:targoff, bit 15 *
- ;* is lsb of byte at targseg:targoff+1, etc. *
- ;* *
- ;* srcseg -- segment address of source area *
- ;* srcoff -- offset to first byte of source area *
- ;* srcbit -- starting bit number in source area, numbered from 0, *
- ;* same scheme as targbit *
- ;* *
- ;* nobits -- number of bits to move from source area to target area *
- ;* *
- ;* ALTERNATE T. P. DECLARATION-- procedure movbits(targptr:byteptr;targbit:*
- ;* integer;srcptr:byteptr;srcbit,nobits:integer); external 'movbits.bin'; *
- ;* *
- ;* targptr -- a variable declared of type ^byte loaded by the ptr func- *
- ;* tion with the segment and offset values desired, or a call *
- ;* to the function addr with the desired area as the param- *
- ;* eter, giving the target area address *
- ;* targbit -- same as above *
- ;* srcptr -- same as targptr for the source area *
- ;* srcbit -- same as above *
- ;* nobits -- same as above *
- ;* *
- ;* TYPICAL CALLING SEQUENCES-- *
- ;* movbits(seg(videoram),ofs(videoram),133,seg(plotdata),ofs(plotdata), *
- ;* 0,400); *
- ;* movbits(addr(outfield),56,addr(infield),7,400); *
- ;* *
- ;* BREAK-DOWN OF CASES IN PARAMETERS-- *
- ;* *
- ;* case 0: nobits is 0 *
- ;* case 1: targbit and srcbit are multiples of 8 *
- ;* case 2: targbit and srcbit are congruent modulo 8, i.e., they *
- ;* resolve to the same relative bit number in a byte *
- ;* case 3: none of the above *
- ;* *
- ;* CODING AND CHANGE LOG-- *
- ;* *
- ;* 15 OCT 1985 -- coding and initial testing finished *
- ;* 23 OCT 1985 -- alternate calling sequence tested and documented *
- ;* 1 JAN 1986 -- correct typos in comments *
- ;* 2 JAN 1986 -- short jumps used where possible *
- ;* 4 JAN 1986 -- change page parameters and print on Oki 82. *
- ;* *
- ;******************************************************************************
- subttl SYMBOLIC ASSIGNMENTS AND EQUATES
- page
- NPARMS = 7 ;number of parameters
- NBPUSH = 24 ;number of bytes pushed upon entry (no. pushes * 2)
- ;
- ;
- ;
- wsw0 equ word ptr[bp] ;define location of work space word
- wsb0 equ byte ptr[bp] ;define location of work space bytes too
- wsb1 equ byte ptr[bp+1] ;note that these just share the same
- ;area as the word above
- ;
- ;
- ;
- nobits equ word ptr[bp+NBPUSH+2] ;define location of parameters on stack
- srcbit equ word ptr[bp+NBPUSH+4] ;note that upon entry the return ip is
- srcoff equ word ptr[bp+NBPUSH+6] ;on top of stack from push done by near
- srcseg equ word ptr[bp+NBPUSH+8] ;call so the displacements start at +2
- targbit equ word ptr[bp+NBPUSH+10]
- targoff equ word ptr[bp+NBPUSH+12]
- targseg equ word ptr[bp+NBPUSH+14]
- ;
- ;
- ;
- subttl CODE AREA
- page
- codeseg segment byte public 'CODE'
- assume cs:codeseg ;dummy assume since cs will contain seg addr
- ;of Turbo Pascal code and not codeseg
- org 0h ;start code at 0 since external procedures to be
- ;called from Turbo Pascal don't need a program
- ;segment prefix of 100h bytes
- ;
- ; push things onto stack upon entry
- ;
- movbits000:
- jmp short movbits010 ;jump around id string
- db 'movbits.bin' ;identifying string constant
- movbits010:
- push ax ;push general regs
- push bx
- push cx
- push dx
- push bp ;push base pointer reg
- push si ;push index regs
- push di
- push ds ;push segment regs, except cs
- push ss
- push es
- pushf ;push processor flags
- pushf ;push it again to get some work space
- ;
- ; set up the base pointer to access work space and parameter values
- ; on the stack
- ;
- mov bp,sp ;get current value of stack pointer into bp reg
- ;
- ; now look at nobits to see if it is zero, if not then set up a few
- ; regs with values needed by the other cases
- ;
- mov ax,nobits ;get number of bits to move into ax
- or ax,ax ;or with itself to set flag bits
- jnz movbits015 ;if it's not zero, then continue
- jmp mvbcase0 ;else it's zero, so we have case 0
- ;
- ; clear direction flag, and load up segment and index regs to
- ; address the effective source and target bytes
- ;
- movbits015:
- cld ;make sure we auto-increment string ops
- mov ax,targseg ;get seg addr of target
- mov es,ax ;put it in es reg
- mov di,targoff ;get offset to target into di
- mov ax,targbit ;get target bit no.
- mov bx,ax ;make a copy of it
- and bx,111b ;make it modulo 8
- mov targbit,bx ;and put it back into parameter area
- mov cl,3 ;load shift count
- shr ax,cl ;divide by 8 to get displacement to byte
- ;with the target bit
- add di,ax ;add this extra offset to targoff
- mov ax,srcseg ;get seg addr of source to ax
- mov ds,ax ;put it in ds reg
- mov si,srcoff ;get offset to source into si
- mov ax,srcbit ;get source bit no.
- mov bx,ax ;make a copy of it
- and bx,111b ;make it modulo 8
- mov srcbit,bx ;and put it back into parameter area
- ;
- ; henceforth, targbit and srcbit are modulo 8 values, this is done
- ; because after the addresses of the effective bytes are calculated
- ; and put into the index regs, we don't need the 16 bit values but we
- ; do require their modulo 8 values (often called the relative bit no.)
- ;
- shr ax,cl ;divide by 8
- add si,ax ;add this to srcoff
- ;
- ; now look at the other parameters and determine which case we have
- ;
- mov ax,targbit ;get target bit no. modulo 8
- mov bx,srcbit ;get source bit no. modulo 8
- cmp al,bl ;compare the two three bit values
- je movbits020 ;if they are equal, then decide between
- ;case 1 and 2
- jmp mvbcase3 ;if they aren't equal, it must be case 3
- movbits020:
- or al,al ;set flag bits
- jz mvbcase1 ;if it's zero, then we have case 1
- jmp short mvbcase2 ;else jump to case 2
- mvbcase0:
- ;
- ; since nobits is zero, we have nothing to move
- ;
- jmp movbits999 ;return to caller via exit code
- subttl CASE 1--targbit and srcbit are multiples of 8
- page
- mvbcase1:
- ;
- ; if targbit and srcbit are multiples of 8, we can move bytes
- ; without any shifting, the last byte moved may need masking
- ;
- ;
- mov cx,nobits ;get no. bits to move
- cmp cx,8 ;compare it with 8
- jl movbits100 ;if moving less than 8 bits, it's a one byte
- ;operation, so treat it as the last byte
- shr cx,1 ;else divide by 8 to get no. bytes to move
- shr cx,1
- shr cx,1
- rep movsb ;move all whole bytes involved
- mov cx,nobits ;get total no. bits to move back to cx
- and cl,111b ;get no. of bits to move in last source byte
- jz movbits110 ;if it's zero, then we have moved all the
- ;bytes with the rep movsb above, so return
- movbits100:
- lodsb ;get last or only source byte to al reg
- mov ah,al ;save it in ah
- push es ;put target seg addr on stack
- pop ds ;and transfer it to ds
- mov si,di ;get destination index to si
- lodsb ;get last or only target byte into al
- mov bx,0ffh ;get a mask of 00ffh into bx
- ror bx,cl ;build a zeroing mask byte in bh
- and ah,bh ;clear low order bits in source byte
- ;that will come from target byte
- xor bh,0ffh ;invert the built up mask
- and al,bh ;clear high order bits in target
- ;byte will come from source byte
- or al,ah ;or the two together
- stosb ;store al to target area
- movbits110:
- jmp movbits999 ;return to caller via exit code
- subttl CASE 2--targbit and srcbit are congruent modulo 8
- page
- mvbcase2:
- ;
- ; if targbit and srcbit are congruent modulo 8 and not multiples of 8,
- ; then the first byte will need masking, the intermediate bytes can be
- ; moved without shifting bits, and the last byte may need masking
- ;
- lodsb ;get the first source byte to al
- mov ah,al ;save it in ah
- push ds ;put ds on stack
- push es ;and es too
- pop ds ;and pop them back this way to swap them
- pop es
- xchg di,si ;swap index regs
- lodsb ;get the target byte to al, ah already
- ;has corresponding source byte
- push ds ;do this again
- push es ;to swap ds and es back
- pop ds
- pop es
- xchg di,si ;swap index regs back too
- dec di ;decrement destination index so that it
- ;points to target byte just loaded
- ;
- ; clear source byte so as to preserve high order bits in first
- ; target byte
- ;
- mov cx,srcbit ;get source bit no. modulo 8
- mov bh,0ffh ;get a mask of ffh into bh
- shr bh,cl ;bring zeroes in from left
- and ah,bh ;clear high order bits in source byte
- ;
- ; see if all bits down to least significant will participate,
- ; if not, then it's a partial move
- ;
- mov dx,8 ;load constant 8 = no. bits in a byte
- sub dx,cx ;subtract source relative bit no. from 8
- ;giving the no. bits that would need to
- ;be moved to cover the whole byte
- cmp nobits,dx ;compare with total no. bits to be moved
- je movbits200 ;if they are equal, then it's a one byte
- ;move and whole byte is covered, so skip
- ;the zeroing on right
- jg movbits210 ;if we're moving more bits than what
- ;it takes to cover this byte, then jump
- ;ahead to store this first byte and arm
- ;for intermediate and last bytes
- sub dx,nobits ;else calculate the no. bits that will be
- mov cl,dl ;zeroed on right and put it in cl for shift
- mov ch,0ffh ;get a mask of ffh into ch
- shl ch,cl ;bring zeroes in on right
- and bh,ch ;zero low order bits in preliminary mask
- and ah,bh ;zero low order bits in source byte
- movbits200:
- xor bh,0ffh ;invert the mask that prepared the source byte
- ;on left and right
- and al,bh ;zero bits in target byte that will come from
- ;source byte
- or al,ah ;or the haves and havenots together
- stosb ;store al into target area
- jmp short movbits230;and leave
- ;
- ; store a covered byte (all bits from targbit down to 7 on right are
- ; moved) and adjust nobits
- ;
- movbits210:
- xor bh,0ffh ;invert the mask that zeroed the source byte
- ;on the left
- and al,bh ;and use it to zero target byte on right
- or al,ah ;or the haves and havenots together
- stosb ;and store al in destination area
- mov cx,nobits ;get total no. bits to move
- sub cx,dx ;subtract the no. bits moved giving number
- ;remaining to be moved
- mov nobits,cx ;and put it back to memory
- ;
- ; take care of the intermediate bytes
- ;
- cmp cx,8 ;compare no. bits remaining to be moved
- ;with 8
- jl movbits220 ;if moving less than 8 bits, it's a one byte
- ;operation, so treat it as the last byte
- shr cx,1 ;else divide by 8 to get no. bytes to move
- shr cx,1
- shr cx,1
- rep movsb ;move all whole bytes involved
- mov cx,nobits ;get remaining no. bits to move back to cx
- and cl,111b ;get no. of bits to move in last source byte
- jz movbits230 ;if it's zero, then we have moved all the
- ;bytes with the rep movsb above, so return
- movbits220:
- lodsb ;else get last source byte to al reg
- mov ah,al ;save it in ah
- push es ;put target seg addr on stack
- pop ds ;and bring it back to ds
- mov si,di ;get destination index to si
- lodsb ;get last target byte into al
- mov bx,0ffh ;get a mask of 00ffh into bx
- ror bx,cl ;bring ones in from left
- and ah,bh ;clear low order bits in source byte
- ;that will not be moved to target byte
- xor bh,0ffh ;invert the built up mask
- and al,bh ;clear high order bits in target byte
- ;that will come from source byte
- or al,ah ;or the two together
- stosb ;store al to target area
- movbits230:
- jmp movbits999 ;return to caller
- subttl CASE 3--none of the above
- page
- ;
- ; since none of the above cases were met, we must shift all bytes moved
- ; and first and last bytes all will need masking, intermediate bytes
- ; in target will come from shifted words in source area
- ;
- ; the technique used here is to shift the source area, byte by byte
- ; as it is loaded into regs, so that it will be congruent to the
- ; target byte
- ;
- mvbcase3:
- mov ax,srcbit ;get source bit no. modulo 8
- mov bx,targbit ;get target bit no. modulo 8
- sub bx,ax ;subtract source relative bit no. from
- ;target relative bit no. giving amount
- ;to shift the source bytes; if positive,
- ;then to right, if negative, then to left
- jg movbits300 ;if positive (bx > ax), then jump around
- ;neg instruction; difference can not be 0
- neg bl ;make the left shift amount positive
- movbits300:
- mov wsw0,bx ;move the sign bit in bh and shift
- ;amount in bl to work space word 0
- lodsw ;get the first source byte pair to al,ah
- xchg ah,al ;swap them because word is stored lsb,msb
- dec si ;decrement source index so that the word
- ;string slides along one byte at a time
- ;rather than the two bytes that lodsw
- ;implies
- mov cl,bl ;put the shift amount into reg for shr ax,cl
- ;or shl ax,cl below
- test bh,80h ;test the sign bit of computed shift amount
- jnz movbits310 ;if a left shift is indicated, jump around
- ;right shift code
- shr ah,cl ;shift bits to right, bringing zeroes
- ;into high order bits of ah
- dec si ;for a right series, the first byte pair in
- ;source area provides bits for both the first
- ;and second bytes in target area, so decrement
- ;once more to get back to it
- jmp short movbits320;jump around left shift code
- movbits310:
- shl ax,cl ;shift bits to left so that bits from al
- ;(the second byte) move up on bits in
- ;ah from the right
- ;
- ; ah contains a shifted source byte that now is congruent to target
- ; byte, i.e, the bits to be moved from source are lined up to the
- ; positions they will replace in the target; srcbit isn't the true
- ; relative bit no. of source now, so we use targbit instead; this
- ; same idea is used with the intermediate and last bytes
- ;
- movbits320:
- push ds ;put ds on stack
- push es ;and es too
- pop ds ;and pop them back this way to swap them
- pop es
- xchg di,si ;swap index regs
- lodsb ;get the target byte to al
- push ds ;do this again
- push es ;to swap ds and es back
- pop ds
- pop es
- xchg di,si ;swap index regs back too
- dec di ;decrement destination index so that it
- ;points to target byte just loaded
- ;
- ; clear source byte so as to preserve high order bits in first
- ; target byte
- ;
- mov cx,targbit ;get target bit no. modulo 8
- mov bh,0ffh ;get a mask of ffh into bh
- shr bh,cl ;bring zeroes in from left
- and ah,bh ;clear high order bits in source byte
- ;
- ; see if all bits down to least significant will participate,
- ; if not, then it's a partial move
- ;
- mov dx,8 ;load constant 8 = no. bits in a byte
- sub dx,cx ;subtract target relative bit no. from 8
- ;giving the no. bits that would need to
- ;be moved to cover the whole byte
- cmp nobits,dx ;compare with total no. bits to be moved
- je movbits330 ;if they are equal, then it's a one byte
- ;move and whole byte is covered, so skip
- ;the zeroing on right
- jg movbits340 ;if we're moving more bits than what
- ;it takes to cover this byte, then jump
- ;ahead to store this first byte and arm
- ;for intermediate and last bytes
- ;
- ; we arrive here if nobits<8-targbit (the no. needed to cover the
- ; whole byte down to bit 7)
- ;
- sub dx,nobits ;else calculate the no. bits that will be
- mov cl,dl ;zeroed on right and put it in cl for shift
- mov ch,0ffh ;get a mask of ffh into ch
- shl ch,cl ;bring zeroes in on right
- and bh,ch ;zero low order bits in preliminary mask
- and ah,bh ;zero low order bits in source byte
- movbits330:
- xor bh,0ffh ;invert the mask that prepared the source byte
- ;on left and right
- and al,bh ;zero bits in target byte that will come from
- ;source byte
- or al,ah ;or the haves and havenots together
- stosb ;store al into target area
- jmp movbits360 ;and leave the scene
- ;
- ; store a covered byte and adjust nobits
- ;
- movbits340:
- xor bh,0ffh ;invert the mask that zeroed the source byte
- ;on the left
- and al,bh ;and use it to zero target byte on right
- or al,ah ;or the haves and havenots together
- stosb ;and store al in destination area
- mov cx,nobits ;get total no. bits to move
- sub cx,dx ;subtract the no. bits moved giving number
- ;remaining to be moved
- mov nobits,cx ;and put it back to memory
- ;
- ; take care of the intermediate bytes
- ;
- cmp cx,8 ;compare no. bits remaining to be moved
- ;with 8
- jl movbits350 ;if moving less than 8 bits in last byte,
- ;skip the intermediate move loops
- shr cx,1 ;else divide by 8 to get no. bytes to move
- shr cx,1
- shr cx,1
- mov dl,wsb0 ;get the calculated shift amount, left or
- ;right as we are about to determine
- test wsb1,80h ;test sign bit of calculated shift amount
- ;to determine if it's a left or right series
- jnz movbits346 ;jump around right shift code if bit is 1
- movbits343:
- mov bx,cx ;make a copy of loop counter
- lodsw ;get a byte pair from source area
- xchg ah,al ;swap them because word is stored lsb,msb
- dec si ;move pair along by one, not two, bytes
- mov cl,dl ;get shift amount back
- shr ax,cl ;shift to right into al
- stosb ;put byte in al away in target area
- mov cx,bx ;get loop counter back
- loop movbits343 ;loop until all intermediate bytes have been
- ;moved
- jmp short movbits348;jump around left shift code
- movbits346:
- mov bx,cx ;make a copy of loop counter
- lodsw ;get a byte pair from source area
- xchg ah,al ;swap them
- dec si ;move pair along by one, not two, bytes
- mov cl,dl ;get shift amount back
- shl ax,cl ;shift to left into ah
- mov al,ah ;put shifted source byte into al for store
- stosb ;put byte in al away in target area
- mov cx,bx ;get loop counter back
- loop movbits346 ;loop until all intermediate bytes have been
- ;moved
- movbits348:
- mov cx,nobits ;get no. bits to move back to cx
- and cx,111b ;calculate no. bits to move out of last
- ;source byte
- jz movbits360 ;if it's zero, then we have moved all the
- ;bytes with the code above, so return
- movbits350:
- mov dl,wsb0 ;else get the calculated shift amount to dl
- xchg cl,dl ;cl gets source shift amount and dl gets
- ;no. bits to move in last byte
- lodsw ;get last source byte pair to al,ah
- xchg ah,al ;swap them since they are stored lsb,msb
- test wsb1,80h ;test sign bit of calculated shift amount
- ;to determine if it's a left or right series
- jnz movbits352 ;jump around right shift code if bit is 1
- shr ax,cl ;shift to right into al
- mov ah,al ;put it in ah for later
- jmp short movbits354;jump around left shift code
- movbits352:
- shl ax,cl ;shift to left into ah
- movbits354:
- mov cl,dl ;cl now gets count of no. ones to bring
- ;in from left in mask built below
- push es ;put target seg addr on stack
- pop ds ;and bring it back to ds
- mov si,di ;get destination index to si
- lodsb ;get last target byte into al
- mov bx,0ffh ;get a mask of 00ffh into bh,bl
- ror bx,cl ;bring some ones in from left
- and ah,bh ;clear low order bits in source byte
- ;that will come from target byte
- xor bh,0ffh ;invert the built up mask
- and al,bh ;clear high order bits in target byte
- ;that will come from source byte
- or al,ah ;or the two together
- stosb ;store al to target area
- movbits360:
- jmp short movbits999;return to caller
- subttl RETURN TO CALLER
- page
- ;
- ; pop things back from stack before exit
- ;
- movbits999:
- popf ;pop the work space word off of stack
- popf ;pop the flags
- pop es ;pop segment regs
- pop ss
- pop ds
- pop di ;pop index regs
- pop si
- pop bp ;pop base pointer
- pop dx ;pop general regs
- pop cx
- pop bx
- pop ax
- ret NPARMS*2;remove arguments from stack and do a near return
- ;
- ;
- ;
- codeseg ends
- end movbits000