home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
VDH
/
XGABUFUP.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
31KB
|
571 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 XGABUFUP.ASM -- Common Buffer Update Routine for EGA, VGA, BGA
;/*****************************************************************************
;*
;* SOURCE FILE NAME = XGABUFUP.ASM
;*
;* DESCRIPTIVE NAME = Video Device Handler BufferUpdate routine
;*
;*
;* VERSION V2.0
;*
;* DATE
;*
;* DESCRIPTION Common Buffer Update Routine for EGA, VGA, BGA
;* Mainline routine for video buffer read, write,
;* scroll functions.
;*
;* INPUT: STACK FRAME on entry
;*
;* SS:SP ---> bvsip dw BVS IP offset
;* bvscs dw BVS CS selector
;* parmn dw Function number (256)
;* parmnm1 dw Parameter block offset
;* parmnm2 dw Parameter block selector
;* parmnm3 dw Environment buffer offset
;* parmnm4 dw Environment buffer selector
;*
;*
;* PARAMETER BLOCK FORMAT:
;*
;* SIZE DESCRIPTION
;* ---- -----------
;*
;* WORD ParmLength (length of structure - 28 bytes)
;* WORD Flags
;* Bit 0 = 0, do not update physical display buffer
;* Bit 0 = 1, update physical display buffer if possible
;* Bit 1 = 0, logical display buffer update not required
;* Bit 1 = 1, update logical display buffer
;* Bit 2 = 0, use attribute as is
;* Bit 2 = 1, convert attribute to or from CGA format
;* Bit 3 - 15 are reserved and must be OFF
;*
;* NOTE: If bit 0 and 1 are both ON then the LVB will
;* be written first before the PVB is updated.
;* This will ensure that video devices with
;* slower VRAM will benefit from this algorithm.
;*
;* The caller of BufferUpdate routine (BVS) must
;* serialize access to this routine to insure
;* that the LVB and the PVB will not get out of sync.
;*
;* DWORD AppDataAddr (address of application data)
;* DWORD AppCellAddr (address of character, attribute, or cell)
;* WORD Index (BufferUpdate sub-function to be performed)
;* 0 = Read cell types
;* Bit 0 = 0, single cell character
;* (occupies one cell on the screen)
;* Bit 0 = 1, double cell character
;* (occupies two cells on the screen)
;* Bit 1 = 0, leading (or only) cell
;* Bit 1 = 1, trailing cell
;* Bit 2 - 15 are reserved and must be OFF
;* 1 = Read characters from (Row, Col)
;* 2 = Read cells from (Row, Col)
;* 3 = Scroll (Row, Col) through (Row2, Col2) Up
;* 4 = Scroll (Row, Col) through (Row2, Col2) Down
;* 5 = Scroll (Row, Col) through (Row2, Col2) Left
;* 6 = Scroll (Row, Col) through (Row2, Col2) Right
;* 7 = Write cells to (Row, Col)
;* 8 = Write characters to (Row, Col)
;* 9 = Write characters with constant attr to (Row, Col)
;* 10 = Write repeat character to (Row, Col)
;* 11 = Write repeat attribute to (Row, Col)
;* 12 = Write repeat cell to (Row, Col)
;* 13 = Copy LVB Rect to PVB
;* WORD Row (Starting row)
;* WORD Col (Starting column)
;* WORD Row2 (Secondary row)
;* WORD Col2 (Secondary column)
;* WORD RepeatFactor (# of character cells or rows/columns)
;* WORD LogicalBufSel (logical buffer selector - LVB)
;* WORD TouchXLeft (left most column touched by the write)
;* WORD TouchYTop (top most column touched by the write)
;* WORD TouchXRight (right most column touched by the write)
;* WORD TouchYBottom (bottom most column touched by the write)
;* WORD LVBRowOff (row offset of the LVB in PVB coordinates)
;* WORD LVBColOff (column offset of the LVB in PVB coordinates)
;* WORD LVBWidth (width of the LVB in cells)
;* WORD LVBHeight (height of the LVB in cells)
;* BYTE LVBFormatID (format id of the LVB)
;* BYTE LVBAttrCount (number of attributes in the LVB)
;*
;*
;* ENVIRONMENT BUFFER FORMAT:
;*
;* SIZE DESCRIPTION
;* ---- -----------
;* WORD ModeDataOff (offset to mode data structure)
;*
;*
;* MODEDATA STRUCTURE FORMAT:
;*
;* SIZE DESCRIPTION
;* ---- -----------
;* WORD Length (length of mode data structure - 34 bytes)
;* BYTE ModeType
;* Bit 0 = 0, monochrome compatible
;* Bit 0 = 1, other
;* Bit 1 = 0, text mode
;* Bit 1 = 1, graphics mode
;* Bit 2 = 0, enable color burst
;* Bit 2 = 1, disable color burst
;* Bit 3 = 0, VGA compatible modes (0 - 13h)
;* Bit 3 = 1, native mode
;* Bit 4 - 15 are reserved
;* BYTE Color (number of colors as a power of 2)
;* WORD TextCols (number of text columns in current mode)
;* WORD TextRows (number of text rows in current mode)
;* WORD HorizRes (horizontal pel resolution)
;* WORD VertRes (vertical pel resolution)
;* BYTE AttrFormat (attribute format)
;* BYTE NAttributes (number of attributes in a character cell)
;* DWORD BufferAddr (32-bit physical address of PVB)
;* DWORD BufferLength (length of PVB in current mode)
;* DWORD FullBufSize (size of buffer required for screen save)
;* DWORD PartBufSize (size of buffer for popup save)
;* DWORD ExtDataAddr (extended mode data structure address)
;*
;* EXIT-NORMAL: AX = 0
;* EXIT-ERROR: AX = error code, ERROR_VIO_COL
;* ERROR_VIO_INVALID_LENGTH
;* ERROR_VIO_INVALID_PARMS
;* ERRPR_VIO_MODE
;* ERROR_VIO_ROW
;* ERROR_VIO_INTERNAL_RESOURCE
;*
;* EFFECTS: All other registers are preserved
;*
;* INTERNAL REFERENCES: None
;*
;* EXTERNAL REFERENCES: ReadCellTypes in XGAREAD.ASM
;* ReadCharStr in XGAREAD.ASM
;* ReadCellStr in XGAREAD.ASM
;* ScrollUp in XGASCROL.ASM
;* ScrollDown in XGASCROL.ASM
;* ScrollLeft in XGASCROL.ASM
;* ScrollRight in XGASCROL.ASM
;* WriteCellStr in XGAWRITE.ASM
;* WriteCharStr in XGAWRITE.ASM
;* WriteCharStrAttr in XGAWRITE.ASM
;* WriteNChar in XGAWRITE.ASM
;* WriteNAttr in XGAWRITE.ASM
;* WriteNCell in XGAWRITE.ASM
;* LVBToPVB in XGASCROL.ASM
;*
;* FUNCTIONS BUFFERUPDATE
;* SetupPhysBuf
;* SetGenParms
;*
;* NOTES: Ring 2 conforming code, executable in either
;* privilege level 2 or 3 in protect mode.
;* LINKAGE: Far Call from Base Video Subsystem (BVSCALLS.DLL)
;*
;* STRUCTURES NONE
;*
;* EXTERNAL FUNCTIONS
;*
;* NONE
;* PSEUDOCODE
;*
;* Begin BufferUpdate
;* Preset return code to ERROR_VIO_MODE
;* If text mode
;* Preset return code to ERROR_VIO_INVALID_LENGTH
;* If correct parameter length
;* Preset return code to ERROR_VIO_INVALID_PARMS
;* If valid reserved flags AND
;* If valid video buffer flags AND
;* If valid function number AND
;* If valid index number
;* Call Read/Write/Scroll routines
;* Endif
;* Endif
;* Endif
;* End BufferUpdate
;*
;* CHANGE ACTIVIY =
;* DATE FLAG APAR CHANGE DESCRIPTION
;* -------- ---------- ----- --------------------------------------
;* mm/dd/yy @Vr.mpppxx xxxxx xxxxxxx
;* 03/25/89 @P1 D132 TPL, DCR 132 changes
;* 05/22/89 @T30 D511 TPL, DCR 511 changes
;* 07/05/89 @B15 B702527 WKB, Performance enhancements,
;* 07/15/89 @T39 B784056 TPL, Remove hardware dependencies in VDHINIT,
;* 01/23/89 @T52 D704 TPL, DCR 704 work
;* 01/29/91 MS01 TPL, Rollover MS's runtime check for CGA
;* speedup
;*****************************************************************************/
.xlist
INCLUDE bvscb.inc ; ;@T52
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
.286p ; 286 protect mode instructions
EXTRN BVHINSTANCE:WORD ;@T52
_DATA SEGMENT WORD PUBLIC 'DATA' ;@T39;@T52
;/*
;** Global data
;*/
PUBLIC PVB ;@T52
PVB dd BVHINSTANCE ;@T52
_DATA ENDS ;@T52
EXTRN _PhysToUVirt : NEAR ; Allocate PVB selector ;@B15
EXTRN _FreePhysToUVirt : NEAR ; Deallocate PVB selector ;@B15
R2CSEG SEGMENT WORD PUBLIC 'CODE'
ASSUME CS:R2CSEG,DS:NOTHING,ES:NOTHING
EXTRN ReadCellTypes : NEAR ;
EXTRN ReadCharStr : NEAR ; VioReadCharStr
EXTRN ReadCellStr : NEAR ; VioReadCellStr
EXTRN ScrollUp : NEAR ; VioScrollUp
EXTRN ScrollDown : NEAR ; VioScrollDn
EXTRN ScrollLeft : NEAR ; VioScrollLt
EXTRN ScrollRight : NEAR ; VioScrollRt
EXTRN WriteCellStr : NEAR ; VioWriteCellStr
EXTRN WriteCharStr : NEAR ; VioWriteCharStr
EXTRN WriteCharStrAttr : NEAR ; VioWriteCharStrAttr
EXTRN WriteNChar : NEAR ; VioWriteNChar
EXTRN WriteNAttr : NEAR ; VioWriteNAttr
EXTRN WriteNCell : NEAR ; VioWriteNCell
EXTRN LVBToPVB : NEAR ;@P1
PUBLIC DispTbl
DispTbl DW ReadCellTypes ; table for EGA format LVB
DW ReadCharStr ; Read characters
DW ReadCellStr ; Read character/attribute 's
DW ScrollUp ; Scroll window up
DW ScrollDown ; Scroll window down
DW ScrollLeft ; Scroll window left
DW ScrollRight ; Scroll window right
DW WriteCellStr ; Write character/attribute 's
DW WriteCharStr ; Write characters
DW WriteCharStrAttr ; Write characters with attr
DW WriteNChar ; Write character N times
DW WriteNAttr ; Write attribute N times
DW WriteNCell ; Write cell N times
DW LVBToPVB ; Copy the LVB to the PVB @P1
PUBLIC BUFFERUPDATE
BUFFERUPDATE PROC FAR
;/*
;** This mainline routine checks all high level errors before
;** control is transfer to the worker routine.
;** On entry to each worker routine, the following registers
;** are setup:
;** DS:SI -> Parameter block buffer
;** ES:DI -> Mode data structure in the environment buffer
;** SS:BP -> Parameter stack frame
;**
;** All registers are preserved
;*/
sub sp, bottomdest-PVB_Sel+2; Allocate storage for: PVB selector @P1
; Scroll parms
push bp ; Save caller's BP
mov bp, sp ; Establish parameter addressability
pusha ; Save all registers
push ds ;
push es ;
les di, [bp].EnvBufParm ; ES:DI -> environment buffer
add di, es:[di].ModeDataOff ; ES:DI -> mode data structure
mov ax, ERROR_VIO_MODE ; Preset invalid mode error
test es:[di].ModeType, GRAPHICS_MODE
.if <z> ; Text mode?
lds si, [bp].ParmBuf ; DS:SI -> parameter buffer
mov ax, ERROR_VIO_INVALID_LENGTH ; Preset error code
.if <[si].ParmLength ae LogicalBufSel+2>; Valid parm length? @P1
mov ax, ERROR_VIO_INVALID_PARMS ; Preset error code
test [si].Flags, RESERVED_FLAGS ;
.if <z> AND ; Valid reserved flags?
test [si].Flags, PVB_SEL_BIT + LVB_SEL_BIT
.if <nz> AND ; Either bit is ON?
.if <[bp].FuncNumHi e 0> AND ; Correct function #?
.if <[bp].FuncNumLo e FUNC_NUM> AND ;
.if <[si].FuncIndex be MAX_INDEX> ; Invalid index?
sub ax, ax ; Clear return code
test [si].Flags, PVB_SEL_BIT ;
.if <nz> ; Asked for PVB update?
call SetupPhysBuf ; Go get PVB as needed
.endif ;
.if <zero ax> ; No error?
cld ;
mov bx, [si].FuncIndex ;
shl bx, 1 ; Word align jump table
call cs:DispTbl[bx] ; Dispatch to handler
.endif ;
.endif ;
.endif ;
.endif ;
mov [bp-2], ax ;
pop es ;
pop ds ;
popa ;
pop bp ;
add sp, bottomdest ; Deallocate local storage @P1
ret 12 ;
BUFFERUPDATE ENDP
;/****************************************************************************
;*
;* FUNCTION NAME = SetupPhysBuf
;*
;* DESCRIPTION =
;*
;* INPUT = AX = 0
;* DS:SI -> parameter block
;* ES:DI -> environment buffer (mode data)
;*
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = AX = 0
;* RETURN-ERROR = AX = ERROR_VIO_INTERNAL_RESOURCE
;*
;****************************************************************************/
PUBLIC SetupPhysBuf
SetupPhysBuf PROC NEAR
mov bx, _DATA ; ;@T52
mov ds, bx ; Setup global data
lds bx, ds:PVB ; Gain access to instance data ;@T52
;/*
;** If PVBSelector in NULL, indicating that the current process does
;** not have a PVB selector allocated then _PhysToUVirt is called
;** to allocate one. If there is a PVB selector then the current
;** PVB size along with its physical address will be checked against
;** those contained in the environment buffer to see if anything has
;** changed due to a prior set mode. If any of these fields changed
;** then the current PVB selector will be deallocated and a new one
;** will be allocated based on it new size and/or physical address.
;*/
mov si, es:[di].BufferaddrLo ; Get the physical address and
mov dx, es:[di].BufferAddrHi ; PVB size of the current
mov cx, ds:[bx].bvhi_PVBSel ; ;@T52
verw cx ; BUGBUG replace this with the
; VerifyW macro
.if <nz> OR ; Write acess?
.if <ds:[bx].bvhi_PVBAddrLo ne si> OR; Anything different ;@T52
.if <ds:[bx].bvhi_PVBAddrHi ne dx> OR; due to mode change? ;@T52
mov si, es:[di].BufferLenLo ;
.if <ds:[bx].bvhi_PVBSizeLo ne si> ; ;@T52
push bx ; Save data offset ;@T52
mov ax, es:[di].BufferLenLo ; ;@T52
mov ds:[bx].bvhi_PVBSizeLo, ax ; ;@T52
push ax ; PVB buffer length ;@T52
mov ds:[bx].bvhi_PVBAddrHi, dx ; ;@T52
mov si, es:[di].BufferaddrLo ;
mov ds:[bx].bvhi_PVBAddrLo, si ; ;@T52
push ds ; Address of returned
lea ax,ds:[bx].bvhi_PVBOffset ; selector:offset ;@T52
push ax ; ;@T30;@T52
push dx ; PVB address
push si ;
.if <ncxz> ; PVB selector already exists?
push cx ; Deallocate it 1st
call _FreePhysToUVirt ;
add sp, 2 ; Balance stack
.endif ;
call _PhysToUVirt ; Allocate new PVB selector
add sp, 10 ; Balance
pop bx ; Restore data offset ;@T52
les di, [bp].EnvBufParm ; Re-setup mode data address
add di, es:[di].ModeDataOff ; from the environment block
mov cx, ds:[bx].bvhi_PVBSel ; Setup PVB selector ;@T52
.endif ;
.if <zero ax> ; No error encountered?
mov [bp].PVB_Sel, cx ; Put PVB selector on stack
lds si, [bp].ParmBuf ; Re-setup parameter block addr
.else ; Error encountered!
mov ds:[bx].bvhi_PVBSizelo, 0 ; Clear the necessary ;@T52
mov ds:[bx].bvhi_PVBSel, 0 ; per process fields ;@T52
mov ax, ERROR_VIO_INTERNAL_RESOURCE
.endif ;
ret
SetupPhysBuf ENDP
;/****************************************************************************
;*
;* FUNCTION NAME = SetGenParms
;*
;* DESCRIPTION =
;*
;* Set general parameters used by all buffer update functions
;*
;* SetGenParms sets up basic information relating to LVB substitution.
;* The routine sets up the boundaries for the write based on whether
;* the LVB has been superceeded by passed parameters.
;*
;* INPUT SS:BP - local data storage area
;* DS:SI - user passed parameter block
;* ES:DI - mode data structure
;*
;* OUTPUT Carry Clear
;* AX - index of right most row in LVB
;* CX - index of bottom most column in LVB
;* [bp].minrow - index of top most row in LVB (PVB coordinates)
;* [bp].mincol - index of left most col in LVB (PVB coordinates)
;* [bp].maxrow - index of bottom most row in LVB (PVB coordinates)
;* [bp].maxcol - index of right most col in LVB (PVB coordinates)
;* [bp].lvb_width - width of the LVB in cells
;* [bp].lvb_height - height of the LVB in cells
;* [bp].PVB_SEL - PVB selector if PVB write, else 0
;* [bp].LVB_SEL - LVB selector if LVB write, else 0
;*
;* Carry Set
;* PVB format == LVB format == CGA format
;*
;* USES AX,CX,DX,FLAGS
;*
;* PSEUDOCODE
;*
;* if !(parmflags & USEPVB)
;* PVB_SEL = 0
;*
;* if (parmflags & USELVB)
;* LVB_SEL = parmLVB
;* else
;* LVB_SEL = 0
;*
;* cellsize = modeattrcnt + 1
;* if (US format PVB and LVB) &&
;* (Read or Write [not scroll or lvbtopvb])
;* Indicate US buffer type
;* return
;*
;* if (parmlength >= LVBHeight)
;* mincol = parmLVBColOff
;* maxcol = parmLVBWidth + mincol
;* minrow = parmLVBRowOff
;* maxrow = parmLVBHeight + minrow
;* lvb_width = parmLVBWidth
;* lvb_height = parmLVBHeight
;* if (parmlength >= LVBAttrCount)
;* if (parmAttrCount == 3)
;* cellsize = 4
;* else
;* cellsize = 2
;* else
;* mincol = 0
;* maxcol = modeCols - 1
;* minrow = 0
;* maxrow = modeRows - 1
;* lvb_width = modeCols
;* lvb_height = modeRows
;*
;* RETURN-NORMAL = NONE
;* RETURN-ERROR = NONE
;*
;****************************************************************************/
PUBLIC SetGenParms
SetGenParms PROC ;@P1 begin
test [si].Flags, PVB_SEL_BIT ;
.if <z> ; Do not update PVB?
mov [bp].PVB_Sel,0 ; do not use PVB selector
.endif ;
test [si].Flags, LVB_SEL_BIT
.if <nz> ; Update LVB?
mov ax, [si].LogicalBufSel ; yes, use LVB
mov [bp].LVB_Sel,ax ; save the LVB selector
.else
mov [bp].LVB_Sel,0 ; do not use LVB selector
.endif
cmp word ptr es:[di].AttrFormat,WorldFMTATTR; Special format?
.if <e> ; Yes, use three byte attributes
mov [bp].cellsize,WorldCellSize
.else
mov [bp].cellsize,DefaultCellSize
cmp ds:[si].ParmLength,LogicalBufSel+2
.if <e> ; Everything US normal
mov ax,ds:[si].FuncIndex ; write or read (not scroll)
.if <ax be I_ReadCellStr> or
.if <ax ae I_WrtCellStr> and
.if <ax be I_WrtNCell>
stc
jmp short sgpx
.endif
.endif
.endif
cmp ds:[si].ParmLength,LVBFormatID ; Did the caller specify LVB info?
.if <ae> ; Yes, use callers information
mov cx,ds:[si].LVBColOff ; (cx) = left most column
mov [bp].mincol,cx ; store left most column
mov dx,ds:[si].LVBWidth ; (dx) = number of columns
mov [bp].lvb_width,dx ; store number of columns
add cx,dx ; (cx) = right most column + 1
dec cx ; (cx) = right most column
mov [bp].maxcol,cx ; store right most column
mov ax,ds:[si].LVBRowOff ; (ax) = top most row
mov [bp].minrow,ax ; store top most row
mov dx,ds:[si].LVBHeight ; (dx) = number of rows
mov [bp].lvb_height,dx ; store number of rows
add ax,dx ; (ax) = bottom most row + 1
dec ax ; (ax) = bottom most row
mov [bp].maxrow,ax ; store bottom most row
cmp ds:[si].ParmLength,LVBAttrCount + 1 ; Is the parm present?
.if <ae> and near ; Yes, attribute count is included
cmp word ptr ds:[si].LVBFormatID,WorldFMTATTR ; Special format?
.if <e> near ; Yes, use three byte attributes
mov [bp].cellsize,WorldCellSize
.else
mov [bp].cellsize,DefaultCellSize
.endif
.else ; Use default screen group information
mov [bp].mincol,0 ; store left most column
mov cx,es:[di].TextCols ; (ax) = number of columns
mov [bp].lvb_width,cx ; store number of columns
dec cx ; (ax) = right most column
mov [bp].maxcol,cx ; store right most column
mov [bp].minrow,0 ; store top most row
mov ax,es:[di].TextRows ; (ax) = number of rows
mov [bp].lvb_height,ax ; store number of rows
dec ax ; (ax) = bottom most row
mov [bp].maxrow,ax ; store bottom most row
.endif
clc
sgpx: ret
SetGenParms ENDP ;@P1 end
R2CSEG ENDS
END