home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
VDH
/
WDHREAD.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
16KB
|
426 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 WDHREAD.ASM -- Buffer Read Routines for Windowable sessions
;/*****************************************************************************
;*
;* SOURCE FILE NAME = WDHREAD.ASM
;*
;* DESCRIPTIVE NAME = Buffer Read Routines for Windowable sessions
;*
;*
;* VERSION V2.0
;*
;* DATE
;*
;* DESCRIPTION Buffer Read Routines for Windowable sessions
;*
;* FUNCTIONS ReadCellTypes, ReadCharStr,
;* ReadCellStr, LocateBuffAddr
;*
;* NOTES NONE
;*
;* STRUCTURES NONE
;*
;* EXTERNAL REFERENCES NONE
;*
;* EXTERNAL FUNCTIONS
;*
;* NONE
;*
;* CHANGE ACTIVIY =
;* DATE FLAG APAR CHANGE DESCRIPTION
;* -------- ---------- ----- --------------------------------------
;* mm/dd/yy @Vr.mpppxx xxxxx xxxxxxx
;* 09/14/94 @95837 WKB, pmwinp.inc -> pmwinx.inc
;****************************************************************************/
.286c ; 286 protect mode instructions
.xlist
include pmwinx.inc ;@95837
include pmaviop.inc
INCLUDE struc.inc ; Structure macro
INCLUDE error2.inc ; Subsystem error equates
INCLUDE vdhstruc.inc ; Buffer update data structures
INCLUDE vdhequ.inc ; Buffer update equates
.list
R2CSEG SEGMENT WORD PUBLIC 'CODE'
ASSUME CS:R2CSEG,DS:NOTHING,ES:NOTHING
;/****************************************************************************
;*
;* SUBROUTINE NAME: ReadCellTypes
;*
;* DESCRIPTIVE NAME: Video device handler read cell types
;*
;* FUNCTION: Process read cell types sub-function.
;*
;* ENTRY POINT: ReadCellTypes
;* LINKAGE: Near Call from BUFFERUPDATE routine
;*
;* INPUT:
;*
;* AX = 0
;* SS:BP ---> Stack frame (see VDHSTRUC.INC)
;* DS:SI ---> Parameter block buffer (see WDHBUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see WDHBUFUP.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 (net used in this call)
;* WORD RepeatFactor (input and output length)
;* WORD LogicalBufSel
;*
;* OUTPUT:
;* The valid cell type for this OS/2 release is a word of zero.
;*
;* EXIT-NORMAL: AX = 0
;*
;* EXIT-ERROR: AX = Error from LocateBuffAddr
;*
;* EFFECTS: All
;*
;* INTERNAL REFERENCES: LocateBuffAddr
;*
;* EXTERNAL REFERENCES: None
;*
;****************************************************************************/
PUBLIC ReadCellTypes
ReadCellTypes PROC NEAR
mov bx, 1 ; Set indicator for word move
call LocateBuffAddr ; On exit: BX = sel, AX = off
.if <nc> ; Continue?
shr cx, 1 ; Adjust for word move
les di, [si].AppDataAddr ; Setup destination address
sub ax, ax ; Clear return code
rep stosw ; Transfer zeros to user buffer
.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 WDHBUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see WDHBUFUP.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
sub bx, bx ; Set indicator for byte move
call LocateBuffAddr ; Setup LVB, PVB selectors
.if <nc> ; Continue?
les di, [si].AppDataAddr ; Setup destination address
mov ds, bx ; Setup source selector
mov si, ax ; Setup source offset
.repeat ;
movsb ; Transfer chars to destination
inc si ;
.loop ;
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 WDHBUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see WDHBUFUP.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 ; Set indicator for word move
call LocateBuffAddr ; On exit: BX = sel, AX = off
.if <nc> ; Continue?
shr cx, 1 ; Adjust for word move
les di, [si].AppDataAddr ; Setup destination address
mov ds, bx ; Setup source selector
mov si, ax ; Setup source offset
rep movsw ; Transfer cells to destination
sub ax, ax ; Clear return code
.endif ;
ret ;
ReadCellStr ENDP
;/****************************************************************************
;*
;* SUBROUTINE NAME: LocateBuffAddr
;*
;* 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: LocateBuffAddr
;* LINKAGE: Near Call from ReadCharacters, ReadCells,
;* RepeatAttribute,
;*
;*
;* INPUT:
;*
;* AX = 0
;* BX = Type of transfer
;* 0 - byte transfer (character or attribute only)
;* 1 - word transfer (character cell - char/attr pair)
;* SS:BP ---> Stack frame (see VDHSTRUC.INC)
;* DS:SI ---> Parameter block buffer (see WDHBUFUP.ASM)
;* ES:DI ---> Mode data in environment buffer (see WDHBUFUP.ASM)
;*
;* OUTPUT: AX = source buffer offset
;* BX = source buffer selector
;* CX = adjusted repeat factor
;* DX = offset to the end of source buffer
;* DS:[SI].RepeatFactor = # of bytes to be transfered
;* CY = 1 Error encountered
;*
;* 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_COL
;* AX = ERROR_VIO_ROW
;*
;* EFFECTS: AX, BX, CX, DX, CY
;*
;* INTERNAL REFERENCES: None
;*
;* EXTERNAL REFERENCES: None
;*
;****************************************************************************/
PUBLIC LocateBuffAddr
LocateBuffAddr PROC NEAR
;/*
;** Validate row, column value based on the current text mode setting.
;** Make sure CY is set if validation fails.
;*/
mov cx, es:[di].TextCols ; Get column value from EnvBuf
.if <cx a [si].Col> ; Valid input column value?
mov cx, es:[di].TextRows ; Get row value from EnvBuf
.if <cx a [si].Row> ; Valid input row value?
;/*
;** Minimum transfer count for either character or attribute is 1 and
;** the minimum transfer count for a cell is 2.
;** Transfer will not take place if minimum transfer count is not met.
;** This is determine by the request type indicated in BX on entry.
;*/
mov cx, [si].RepeatFactor ; Get repeat factor
.if <cx a bx> ; Pass minimum requirement?
;/*
;** Calculate the starting offset within the PVB or LVB based on the
;** starting row, column value.
;*/
mov ax, [si].Row ; Buffer offset = (parm row
mul es:[di].TextCols ; * screen columns + parm
add ax, [si].Col ; column) * 2
add ax, ax ; AX = buffer offset
.if <[bp].Retrace eq 4>
add ax,ax
.endif
;/*
;** Determine how many bytes left to the end of the video buffer.
;** Length = size of PVB - video buffer offset
;*/
mov dx, es:[di].BufferLenLo
sub dx, ax ; Calculate eob length
;/*
;** For either character or attribute only transfer, cut the end of
;** buffer length in half to allow for proper determination of buffer
;** overflow condition.
;*/
.if <zero bx> ; Byte transfer request?
shr dx, 1 ; Adjust end of buffer length
.if <[bp].Retrace eq 4>
shr dx,1
.endif
.endif
;/*
;** If overflow condition occurs, use the adjusted end-of-buffer
;** length as the repeat factor count.
;*/
.if <cx a dx> ; Over flow buffer?
mov cx, dx ; Repeat factor = eob length
.endif
mov [si].RepeatFactor, cx
;/*
;** Setup BX with the LVB selector.
;*/
mov bx, [si].LogicalBufSel ; Use LVB only
clc
.else
sub ax, ax ; Clear return code
mov [si].RepeatFactor, ax ; Indicate no-op
stc ; Force exit condition
.endif
.else
mov ax, ERROR_VIO_ROW
stc
.endif
.else
mov ax, ERROR_VIO_COL
stc
.endif
ret
LocateBuffAddr ENDP
R2CSEG ENDS
END