home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
VDH
/
XGAREAD.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
41KB
|
791 lines
;*DDK*************************************************************************/
;
; COPYRIGHT (C) Microsoft Corporation, 1989
; COPYRIGHT Copyright (C) 1995 IBM Corporation
;
; The following IBM OS/2 WARP source code is provided to you solely for
; the purpose of assisting you in your development of OS/2 WARP device
; drivers. You may use this code in accordance with the IBM License
; Agreement provided in the IBM Device Driver Source Kit for OS/2. This
; Copyright statement may not be removed.;
;*****************************************************************************/
PAGE 60,132
TITLE XGAREAD.ASM -- Common Buffer Read Routines for EGA, VGA, BGA
;/*****************************************************************************
;*
;* SOURCE FILE NAME = XGAREAD.ASM
;*
;* DESCRIPTIVE NAME = BUFFERUPDATE read routines
;*
;*
;* VERSION V2.0
;*
;* DATE
;*
;* DESCRIPTION Common Buffer Read Routines for EGA, VGA, BGA
;*
;* FUNCTIONS ReadCellTypes
;* ReadCharStr
;* ReadCellStr
;* SetBuffAddr
;* FastBuffAddr
;* CalcTouchRect
;*
;* NOTES NONE
;*
;* STRUCTURES NONE
;*
;* EXTERNAL REFERENCES
;*
;* NONE
;*
;* EXTERNAL FUNCTIONS
;*
;* NONE
;*
;* CHANGE ACTIVIY =
;* DATE FLAG APAR CHANGE DESCRIPTION
;* -------- ---------- ----- --------------------------------------
;* mm/dd/yy @Vr.mpppxx xxxxx xxxxxxx
;* 03/25/89 @P1 TPL, DCR 132 changes
;* 06/25/89 @T37 B703759 TPL, DCR 132 fix
;* 01/29/91 MS00 TPL, Convert IFDEF to IF
;* 01/29/91 MS01 TPL, Rollover MS's runtime
;* check for CGA speedup
;* 04/11/91 D1348 D1348 NAKADA, Enable DBCS support in Vio-Window
;*****************************************************************************/
.286c ; 286 protect mode instructions
.xlist
INCLUDE struc.inc ; Structure macro
INCLUDE error2.inc ; Subsystem error equates
INCLUDE vdhstruc.inc ; Buffer update data structures
INCLUDE vdhctl.inc ; Conditional Assembly Control ;MS01
INCLUDE vdhequ.inc ; Buffer update equates
INCLUDE xgamac.inc ;@P1
.list
EXTRN SetGenParms:NEAR ; Set up general buffer update parms @P1
IF VDHCGA AND (1 - CGA_ALWAYS_FAST) ; IF VDHCGA AND NOT CGA_ALWAYS_FAST ;MS01
;/*
;** If CGA video memory accesses may need to wait for retrace,
;** these routines are necessary. (See MAKEFILE)
;*/
extrn CGA_REP_MOVSW:far ;@P1
extrn CGA_REP_STOSW:far ;@P1
extrn CGA_REP_MOVSB_INCSI_LOOP:far ;@P1
extrn CGA_REP_MOVSW_STOSW_LOOP:far ;@P1
extrn CGA_REP_INCDI_STOSB_LOOP:far ;@P1
extrn CGA_REP_STOSB_INCDI_LOOP:far ;@P1
extrn CGA_REP_LODSB_STOSW_LOOP:far ;@P1
extrn CGA_REP_MOVSB_INCDI_LOOP:far ;@P1
extrn CGA_REP_MOVSW_ADDSI2_LOOP:far ;@P1
ENDIF ;VDHCGA ;MS00
IFDEF D1348 ;See whether it is of DBCS or not.
extrn ReadCellTypesWrld:near
IFDEF MSKK ;DBCS bits read
extrn ReadCharStrWrld:near
extrn ReadCellStrWrld:near
ENDIF
ENDIF ;D1348
R2CSEG SEGMENT WORD PUBLIC 'CODE'
ASSUME CS:R2CSEG,DS:NOTHING,ES:NOTHING
;/****************************************************************************
;*
;* SUBROUTINE NAME: ReadCellTypes ReadCellTypes3
;*
;* DESCRIPTIVE NAME: Video device handler read cell types
;*
;* FUNCTION: Process read cell types sub-function.
;*
;* ENTRY POINT: ReadCellTypes
;* LINKAGE: Near Call from BUFFERUPDATE rouinte
;*
;* INPUT:
;*
;* AX = 0
;* SS:BP ---> Stack frame (see VDHSTRUC.INC)
;* DS:SI ---> Parameter block buffer (see XGABUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see XGABUFUP.ASM)
;*
;* PARAMETER BLOCK FORMAT:
;*
;* SIZE DESCRIPTION
;* ---- -----------
;*
;* WORD Parameter length
;* WORD Flags (source data buffer - LVB, PVB)
;* DWORD Application data address (target data buffer)
;* DWORD Application data2 address (not used in this call)
;* WORD Index (0)
;* WORD Starting row (source row)
;* WORD Starting column (source column)
;* WORD Secondary row (not used in this call)
;* WORD Secondary column (not used in this call)
;* WORD RepeatFactor (input and output length)
;* WORD LogicalBufSel
;*
;* OUTPUT:
;*
;* EXIT-NORMAL: AX = 0
;*
;* EXIT-ERROR: AX = Error from LocateBuffAddr
;*
;* EFFECTS: All
;*
;* INTERNAL REFERENCES: LocateBuffAddr
;*
;* EXTERNAL REFERENCES: None
;*
;****************************************************************************/
PUBLIC ReadCellTypes
PUBLIC ReadCellTypes3 ;@P1
ReadCellTypes PROC NEAR
ReadCellTypes3: ;@P1
IFDEF D1348 ;CheckCharType of DBCS
mov bx,0 ; Operation in terms of cells
ELSE ;D1348
mov bx, 1 ; Set indicator for word move
ENDIF ;D1348
call SetBuffAddr ; On exit: BX = sel, AX = off @P1
.if <nc> ; Continue?
shr cx, 1 ; Adjust for word move
les di, [si].AppDataAddr ; Setup destination address @P1
IFDEF D1348 ;CheckCharType of DBCS
.if <bit <[bp].flgDBCS> and anyDBCS> and
.if <[bp].j_funcindx eq WorldFmtIndx>
mov ds,bx ; Use LVB as source
mov si,ax ; Setup source offset
call ReadCellTypesWrld
sub ax,ax ; Clear return code
.else
ENDIF ;D1348
sub ax, ax ; Clear return code @P1
rep stosw ; Transfer zeros to user buffer @P1
IFDEF D1348
.endif
ENDIF ;D1348
.endif ;
ret
ReadCellTypes ENDP
;/****************************************************************************
;*
;* SUBROUTINE NAME: ReadCharStr
;*
;* DESCRIPTIVE NAME: Video device handler read characters
;*
;* FUNCTION: Process read characters sub-function.
;* The characters are read from either PVB or LVB
;* starting at the specified row, column location.
;* Line wrap occurs if the end of a line is reached.
;* Read function is terminated if the end of PVB or
;* LVB is reached. The characters read are placed
;* in the specified buffer and the number of chars
;* read is returned in the RepeatFactor field of
;* the parameter block.
;*
;* ENTRY POINT: ReadCharStr
;* LINKAGE: Near Call from BUFFERUPDATE routine
;*
;* INPUT:
;*
;* AX = 0
;* SS:BP ---> Stack frame (see VDHSTRUC.INC)
;* DS:SI ---> Parameter block buffer (see XGABUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see XGABUFUP.ASM)
;*
;* PARAMETER BLOCK FORMAT:
;*
;* SIZE DESCRIPTION
;* ---- -----------
;*
;* WORD Parameter length
;* WORD Flags (source data buffer - LVB, PVB)
;* DWORD Application data address (target data buffer)
;* DWORD Application data2 address (not used in this call)
;* WORD Index (1)
;* WORD Starting row (source row)
;* WORD Starting column (source column)
;* WORD Secondary row (not used in this call)
;* WORD Secondary column (not used in this call)
;* WORD RepeatFactor (input and output length)
;* WORD LogicalBufSel
;*
;* OUTPUT: Application data buffer = characters read
;* RepeatFactor = number of characters read
;*
;* EXIT-NORMAL: AX = 0
;*
;* EXIT-ERROR: AX = Error from LocateBuffAddr
;*
;* EFFECTS: All registers
;*
;* INTERNAL REFERENCES: LocateBuffAddr
;*
;* EXTERNAL REFERENCES: None
;*
;****************************************************************************/
PUBLIC ReadCharStr
ReadCharStr PROC NEAR
mov bx, 0 ; Move in terms of Cell count
call SetBuffAddr ; On exit: BX = sel, AX = off @P1
.if <nc> ; Continue?
.if <nonzero bx> ; LVB flag set? @P1
les di, [si].AppDataAddr ; Setup destination address @P1
mov ds, bx ; Use LVB as source @P1
mov si, ax ; Setup source offset @P1
.if <[bp].cellsize e WorldCellSize> near @P1
.repeat ; @P1
movsb ; Transfer chars to destination
add si, 3 ; skip the attribute bytes @P1
.loop ; @P1
.else ; @P1
.repeat ; @P1
movsb ; Transfer chars to destination
inc si ; skip the attribute byte @P1
.loop ; @P1
.endif ; @P1
.else ; read from PVB @P1
les di, [si].AppDataAddr ; Setup destination address @P1
mov bx, [bp].PVB_Sel ; Use PVB as source @P1
.if <nonzero bx> ; @P1
mov ds, bx ; Setup source selector @P1
mov si, [bp].PVBOff ; Setup source offset @P1
REP_MOVSB_INCSI_LOOP ; Use the above macro so CGA can
; use the same set of sources
.endif ; @P1
.endif ; @P1
sub ax,ax ; Clear return code
.endif ;
ret
ReadCharStr ENDP
;/****************************************************************************
;*
;* SUBROUTINE NAME: ReadCellStr
;*
;* DESCRIPTIVE NAME: Video device handler read cells
;*
;* FUNCTION: Process read cells sub-function.
;* The cells are read from either PVB or LVB starting
;* at the specified row, column location. Line wrap
;* occurs if the end of a line is reached. Read
;* function is terminated if the end of PVB or LVB
;* is reached. The cells read are placed in the
;* specified buffer and the number of cells read
;* is returned in the RepeatFactor field of the
;* parameter block.
;*
;* ENTRY POINT: ReadCellStr
;* LINKAGE: Near Call from BUFFERUPDATE routine
;*
;* INPUT:
;*
;* AX = 0
;* SS:BP ---> Stack frame (see VDHSTRUC.INC)
;* DS:SI ---> Parameter block buffer (see XGABUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see XGABUFUP.ASM)
;*
;* PARAMETER BLOCK FORMAT:
;*
;* SIZE DESCRIPTION
;* ---- -----------
;*
;* WORD Parameter length
;* WORD Flags (source data buffer - LVB, PVB)
;* DWORD Application data address (target data buffer)
;* DWORD Application data2 address (not used in this call)
;* WORD Index (2)
;* WORD Starting row (source row)
;* WORD Starting column (source column)
;* WORD Secondary row (not used in this call)
;* WORD Secondary column (not used in this call)
;* WORD RepeatFactor (input and output length)
;* WORD LogicalBufSel
;*
;* OUTPUT: Application data buffer = character cells read
;* RepeatFactor = sum of char/attr pairs read
;*
;* EXIT-NORMAL: AX = 0
;*
;* EXIT-ERROR: AX = Error from LocateBuffAddr
;*
;* EFFECTS: All
;*
;* INTERNAL REFERENCES: LocateBuffAddr
;*
;* EXTERNAL REFERENCES: None
;*
;****************************************************************************/
PUBLIC ReadCellStr
ReadCellStr PROC NEAR
mov bx, 1 ; Move in terms of buffer length
call SetBuffAddr ; On exit: BX = sel, AX = off @P1
.if <nc> ; Continue?
shr cx, 1 ; Adjust for word move
les di, [si].AppDataAddr ; Setup destination address @P1
.if <nonzero bx> ; LVB flag set? @P1
mov ds, bx ; Setup source selector @P1
mov si, ax ; Setup source offset @P1
rep movsw ; Transfer cells to destination @P1
.else ; @P1
mov bx, [bp].PVB_Sel ; Use PVB as source @P1
.if <nonzero bx> ; @P1
mov ds, bx ; Setup source selector @P1
mov si, [bp].PVBOff ; Setup source offset @P1
.if <[bp].cellsize e WorldCellSize> ;@P1
shr cx, 1 ; Adjust for dword move @P1
xor ax,ax ; (ax) = final word of attribute @P1
REP_MOVSW_STOSW_LOOP; Use macro so CGA can use the same
; sources as everyone else @P1
.else ; @P1
REP_MOVSW ; Use macro so CGA can use the same
; sources as everyone else @P1
.endif ; @P1
.endif ; @P1
.endif ; @P1
xor ax,ax ; set a good return code
.endif
ret
ReadCellStr ENDP
;/****************************************************************************
;*
;* SUBROUTINE NAME: SetBuffAddr
;*
;* DESCRIPTIVE NAME: Video device handler locate video buffer addr
;*
;* FUNCTION: Determine the source/target buffer address for the
;* read/write function based on the information in the
;* parameter buffer and the mode data buffer.
;*
;* ENTRY POINT: SetBuffAddr
;* LINKAGE: Near Call
;*
;* INPUT:
;*
;* AX = 0
;* BX = Type of transfer
;* 0 - the RepeatFactor is a count of cells or characters
;* !0 - the RepeatFactor is a user buffer length
;* SS:BP ---> Stack frame (see VDHSTRUC.INC)
;* DS:SI ---> Parameter block buffer (see XGABUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see XGABUFUP.ASM)
;*
;* OUTPUT: AX = LVB offset
;* BX = LVB selector OR 0 if LVB not requested
;* CX = adjusted LVB repeat factor
;* DS:[SI].RepeatFactor = # of bytes to be transfered
;* CY = 1 Error encountered
;* [BP].PVB_Sel - Selector to the PVB or 0
;* [BP].LVB_Sel - Selector to the LVB or 0
;* [BP].cellsize - number of bytes per cell in LVB
;* [BP].FirstRow - number of cells or bytes in first row
;* [BP].RowLength - number of cells or bytes in later rows
;* [BP].LVBCount - number of cells or bytes to move, LVB
;* [BP].LVBOff - offset for read or write in LVB
;* [BP].PVBSkip - number of bytes to next row in PVB
;* [BP].PVBCount - number of cells or bytes to move, PVB
;* [BP].PVBOff - offset for read or write in LVB
;*
;* EXIT-NORMAL: CY = clear
;*
;* EXIT-ERROR: CY = set
;* AX = 0 if RepeatFactor = 0 for char or attr move
;* = 0 or 1 for cell move
;* AX = ERROR_VIO_INVALID_PARMS
;*
;* EFFECTS: AX, BX, CX, DX, CY
;*
;* INTERNAL REFERENCES: None
;*
;* EXTERNAL REFERENCES: None
;*
;* PSEUDOCODE
;*
;* if !( (mincol <= parmcol <= maxcol) &&
;* (minrow <= parmrow <= maxrow) )
;* exit with error
;*
;* PVBSkip = (modeRows - lvb_width) * cellsize
;* RowLength = lvb_width * cellsize
;* LVBOff = (parmrow - minrow) * lvb_width +
;* (parmcol - mincol) * cellsize
;* PVBOff = (parmrow * modeCols + parmcol) * cellsize
;* BytesLeft = lvb_width * lvb_height * cellsize - LVBOff
;* if (Read/Write Buffer Cells length)
;* if (parmcount > BytesLeft)
;* parmcount = BytesLeft
;* LVBCount = parmcount
;* PVBCount = parmcount
;* else (Read/Write Chars or Cell count)
;* CellsLeft = BytesLeft/CellSize
;* if (parmcount > CellsLeft)
;* parmcount = CellsLeft
;* LVBCount = parmcount
;* PVBCount = parmcount
;*
;* if (cellsize == 4)
;* PVBOff = PVBOff / 2
;* if (Read/Write Buffer Cells length)
;* PVBCount = parmcount/2
;*
;****************************************************************************/
PUBLIC SetBuffAddr ;@P1 begin
SetBuffAddr PROC NEAR
call SetGenParms ; set general parameters for all
.if <c> ; US default values
jmp FastBuffAddr ; do fast version of the calculations
.endif
;/*
;** Possible bizarre LVB. (cx) = maxcolumn, (ax) = maxrow
;*/
.if <cx b ds:[si].Col> or
mov cx,[bp].mincol
.if <cx a ds:[si].Col> ; No, return error
mov ax,ERROR_VIO_COL
jmp sbaerr
.endif
.if <ax b ds:[si].Row> or ; Is the column coordinate valid?
mov ax,[bp].minrow
.if <ax a ds:[si].Row> ; No, exit with error
mov ax,ERROR_VIO_ROW
jmp sbaerr
.endif
.if <nonzero bx>
mov ax,[bp].cellsize ; cell size must be a power of 2
dec ax ; (ax) = bitmask for MOD
xor ax,-1 ; (ax) = bitmask for round down
and ds:[si].RepeatFactor,ax
.endif
.if <ds:[si].RepeatFactor e 0> ; check for NOP read or write
xor ax,ax ; zero length writes and reads are
jmp sbaerr ; valid, but do nothing
.endif
mov ax,[bp].maxcol ; calculate the number of cells
sub ax,ds:[si].Col ; in the first row of the read or
inc ax ; or write
mov [bp].FirstRow,ax
mov ax,es:[di].TextCols ; calculate number of bytes per row
sub ax,[bp].lvb_width ; skipped when moving from PVB line
shl ax,1 ; to PVB line
mov [bp].PVBSkip,ax
mov cx,[bp].lvb_width ; caluculate the Row Length of the LVB
shl cx,1 ; in bytes in a two byte cell LVB
mov [bp].RowLength,cx
; (cx) = bytes per LVB row
mov ax,ds:[si].Row ; calculate offset into the LVB
sub ax,[bp].minrow
mul cx
mov cx,ds:[si].Col
sub cx,[bp].mincol
shl cx,1
add ax,cx
mov [bp].LVBOff,ax
mov ax,ds:[si].Row ; calculate the PVB offset
mul es:[di].TextCols
add ax,ds:[si].Col
shl ax,1
mov [bp].PVBOff,ax
mov ax,[bp].lvb_width ; calculate longest possible write/read
mul [bp].lvb_height
shl ax,1
sub ax,[bp].LVBOff ; (ax) = longest write in bytes
cmp [bp].cellsize,DefaultCellSize ; Is this the default Cell Size?
.if <nz>
or bx,bx ; Is this a cell or char count?
.if <z> ; Yes, calculate cell or char count
shr ax,1 ; (ax) = longest write in cells
shr [bp].RowLength,1 ; convert row length to cells
.if <ax b ds:[si].RepeatFactor> ; truncate the length if needed
mov ds:[si].RepeatFactor,ax
.else
mov ax,ds:[si].RepeatFactor
.endif
mov [bp].LVBCount,ax
mov [bp].PVBCount,ax
.else
shl ax,1 ; (ax) = longest write in bytes
IFDEF D1348 ;support of 64K PS
.if <nc> and ; if 64K, CY is set
ENDIF ;D1348
.if <ax b ds:[si].RepeatFactor> ; truncate the length if needed
mov ds:[si].RepeatFactor,ax
.else
mov ax,ds:[si].RepeatFactor
.endif
mov [bp].LVBCount,ax ; byte count for 4 byte cell LVB
shr ax,1
mov [bp].PVBCount,ax; byte count for 2 byte cell PVB
shl [bp].FirstRow,2 ; Adjust LVB first row length
shl [bp].RowLength,1 ; Adjust LVB row length for cell size
.endif
shl [bp].LVBOff,1 ; Adjust LVB start offset for cell size
.else
or bx,bx ; Is this a cell or char count?
.if <z> ; Yes, calculate cell or char count
shr ax,1 ; (ax) = longest write in cells
shr [bp].RowLength,1 ; convert row length to cells
.else
shl [bp].FirstRow,1 ; Adjust LVB first row length
.endif
.if <ax b ds:[si].RepeatFactor> ; truncate the length if needed
mov ds:[si].RepeatFactor,ax
.else
mov ax,ds:[si].RepeatFactor
.endif
mov [bp].LVBCount,ax
mov [bp].PVBCount,ax
.endif
cmp ds:[si].ParmLength,LVBRowOff; Does caller want the touch rect?
.if <ae> ; Yes, return the Touch Rect
call CalcTouchRect
.endif
mov bx,[bp].LVB_Sel ; (bx) = LVB or 0
mov ax,[bp].LVBOff ; (ax) = offset into LVB
mov cx,[bp].LVBCount ; (cx) = LVB repeat count
clc
sbax: ret
sbaerr: stc
jmp sbax
SetBuffAddr ENDP ;@P1 end
;/****************************************************************************
;*
;* FUNCTION NAME = FastBuffAddr
;*
;* DESCRIPTION = Set buffer addresses for US case
;*
;* FastBuffAddr takes advantage of the fact the the PVB and LVB are
;* both the same size and format. It calculates all of the end values
;* that SetBuffAddr does, but does it for the CGA format LVB/PVB only.
;*
;* INPUT = SS:BP - local data storage area
;* DS:SI - user passed parameter block
;* ES:DI - environment data
;* BX - 0 if write in cells, !0 if write in bytes
;* [bp].cellsize - number of bytes per cell
;*
;* OUTPUT =
;*
;* Carry Clear
;* AX = LVB offset
;* BX = LVB selector OR 0 if LVB not requested
;* CX = adjusted LVB repeat factor
;* DS:[SI].RepeatFactor = # of bytes to be transfered
;* CY = 1 Error encountered
;* [BP].PVB_Sel - Selector to the PVB or 0
;* [BP].LVB_Sel - Selector to the LVB or 0
;* [BP].cellsize - number of bytes per cell in LVB
;* [BP].FirstRow - number of cells or bytes in first row
;* [BP].RowLength - number of cells or bytes in later rows
;* [BP].LVBCount - number of cells or bytes to move, LVB
;* [BP].LVBOff - offset for read or write in LVB
;* [BP].PVBSkip - number of bytes to next row in PVB
;* [BP].PVBCount - number of cells or bytes to move, PVB
;* [BP].PVBOff - offset for read or write in LVB
;*
;* Carry Set
;* AX = error code
;*
;* USES AX,BX,CX,DX,FLAGS
;*
;* RETURN-NORMAL = NONE
;* RETURN-ERROR = NONE
;*
;****************************************************************************/
Public FastBuffAddr ;@P1 begin
FastBuffAddr PROC
mov cx,ds:[si].Col
mov ax,es:[di].TextCols
.if <cx ae ax> ; No, return error
mov ax,ERROR_VIO_COL
jmp sbaerr
.endif
mov [bp].RowLength,ax
sub ax,cx
mov [bp].FirstRow,ax
mov ax,ds:[si].Row
.if <ax ae es:[di].TextRows> ; No, return error
mov ax,ERROR_VIO_ROW
jmp sbaerr
.endif
mul es:[di].TextCols ; calculate the LVB/PVB offset
add ax,cx
shl ax,1
mov [bp].PVBOff,ax
mov [bp].LVBOff,ax
mov cx,ax ; (cx) = offset of beginning of write
mov ax,es:[di].TextCols ; calculate longest possible write/read
mul es:[di].TextRows ; calculate longest possible write/read
shl ax,1
sub ax,cx ; (ax) = longest write in bytes
or bx,bx ; Is this a cell or char count?
.if <z> ; Yes, calculate cell or char count
shr ax,1 ; (ax) = longest write in cells
.else
and ds:[si].RepeatFactor,0FFFEh
shl [bp].FirstRow,1 ; Adjust LVB first row length
shl [bp].RowLength,1; convert row length to bytes
.endif
.if <ax b ds:[si].RepeatFactor> ; truncate the length if needed
mov ds:[si].RepeatFactor,ax
.else
mov ax,ds:[si].RepeatFactor
.endif
mov [bp].LVBCount,ax
mov [bp].PVBCount,ax
.if <zero ax>
jmp fbaerr
.endif
mov [bp].PVBSkip,0
mov bx,[bp].LVB_Sel ; (bx) = LVB or 0
mov ax,[bp].LVBOff ; (ax) = offset into LVB
mov cx,[bp].LVBCount ; (cx) = LVB repeat count
clc
fbax: ret
fbaerr: stc
jmp fbax
FastBuffAddr ENDP ;@P1 end
;/****************************************************************************
;*
;* FUNCTION NAME = CalcTouchRect
;*
;* DESCRIPTION = Calculate the rectangle touched by the given function
;*
;* CalcTouchRect calculate the tightest rectangle that includes all of
;* the cells that may have been changed by the given call.
;*
;* INPUT =
;*
;* SS:BP - local data storage area
;* DS:SI - user passed parameter block
;* BX - 0 if write in cells, !0 if write in bytes
;* [bp].LVBCount - number of units to write, LVB
;* [bp].mincol - left most column of LVB
;* [bp].maxcol - right most column of LVB
;* [bp].FirstRow - number of units to write first row of LVB
;* [bp].RowLength - number of units per row, LVB
;* [bp].cellsize - number of bytes per cell
;*
;* OUTPUT = ds:si-> Touchxxx - set to reflect rectangle affected
;*
;* USES AX,CX,DX,FLAGS
;*
;* ds:si - 2nd attribute pointer
;* es:di - LVB pointer
;* cx - attr count
;*
;* RETURN-NORMAL = NONE
;* RETURN-ERROR = NONE
;*
;****************************************************************************/
Public CalcTouchRect ;@P1 begin
CalcTouchRect PROC
cmp ds:[si].FuncIndex,MIN_WRT_INDEX ; Is this a write?
.if <ae> ; Yes, return the Touch Rect
mov cx,ds:[si].Row
mov ds:[si].TouchYTop,cx
mov ax,[bp].LVBCount ; (ax) = read or write count
.if <ax a [bp].FirstRow>; multiple row write
mov dx,[bp].mincol
mov ds:[si].TouchXLeft,dx
mov dx,[bp].maxcol
mov ds:[si].TouchXRight,dx
;/*
;** This calculation is complicated.
;** ax = number of units to be written
;** ax-FirstRow give the number of units in 2nd
;** and later rows
;** ((ax-FirstRow - 1)/RowLength) + 1 = # of rows beyond 1st
;*/
xor dx,dx ; (dx:ax) = (ax) = w count
sub ax,[bp].FirstRow; (ax) = w count for 2nd+ rows
dec ax ; zero index bytes in the last row
div [bp].RowLength ; (ax) = # rows written - 1
inc ax ; (ax) = # of 2nd+ rows written
add cx,ax ; (cx) = bottom row written
mov ds:[si].TouchYBottom,cx
.else ; single row write
mov ds:[si].TouchYBottom,cx
mov dx,ds:[si].Col
mov ds:[si].TouchXLeft,dx
.if <nonzero bx>
mov cx,[bp].cellsize
shr cx,1
shr ax,cl
.endif
dec ax ; a 1 cell write has same lf,rt col
add ax,dx ; (ax) = right most column
mov ds:[si].TouchXRight,ax
.endif
.else ; read call, no data affected
mov ds:[si].TouchYTop,-1
mov ds:[si].TouchXLeft,-1
mov ds:[si].TouchXRight,-1
mov ds:[si].TouchYBottom,-1
.endif
ret
CalcTouchRect ENDP ;@P1 end
R2CSEG ENDS
END