home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
VDH
/
VDHIOPL.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
87KB
|
2,434 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 VDHIOPL.ASM -- Video Device Handler Ring 2 Routines
;/*****************************************************************************
;*
;* SOURCE FILE NAME = VDHIOPL.asm
;*
;* DESCRIPTIVE NAME = Video device handler ring 2 routines
;*
;*
;* VERSION V2.0
;*
;* DATE
;*
;* DESCRIPTION This module contains routines that run at ring 2 in
;* order to directly access the hardware ( via IN and OUT
;* instructions ).
;*
;* FUNCTIONS ACCESSBLINK
;* ACCESSCLUT
;* ACCESSCURSORPOS
;* ACCESSCURSORTYPE
;* ACCESSDISPLAYMASK
;* ACCESSHARDWARE
;* ACCESSOVERSCAN
;* ACCESSREGISTER
;* ACCESSUNDERSCORE
;* ACCESSVIDEOENABLE
;* CHARFONTEND
;* GetMonitorID
;* QUERY132
;* SET132
;* SETMAPMASK
;* VGAWait
;* _CharFontBegin
;* _DPRINTF
;* _HardwareColor
;* _HardwareColumns
;* _Query8514A
;* _QueryXGA
;* inchr
;* putchar
;*
;* 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/09/89 @D184 D184 STJ, Identify additional displays for 8514/A
;* 04/14/89 @S4 B701111 STJ, Remove negative logic,
;* 05/10/89 @C21 B701513 CJJ, Don't turn Video signal back on and reenable
;* @C21 reading of VideoEnable for VGA,
;* 06/29/89 @T39 B784056 TPL, Remove hardware dependencies in VDHINIT,
;* 07/31/89 @B705063 B705063 WKB, Decrease interrupt latency period as per spec
;* 08/08/89 @B19 B785016 WKB, Included OEM VGA enhancements, B785017 also.
;* 08/17/89 @S24 B706605 STJ, Restore undocumented 8514/A AI interfaces,
;* 09/11/89 @T47 B707464 TPL, Save/restore 3xBox (graphics) bit planes,
;* 09/13/89 @S28 B700010 STJ, Retain external clocking on VGA,
;* 09/14/89 @T49 B707543 TPL, Workaround for a 486 bug,
;* 10/25/89 @TL3 B708718 TPL, Setup bit mask register on restore,
;* 12/18/89 @tb25 AR05401 TLB, Don't do fixvgabug and sequencer enable unless
;* @tb25 in restore,
;* 04/03/90 @T57 B788756 TPL, Do not clear reserve bit when hidding cursor,
;* 06/08/90 @S28f B789810 TPL, Do not preserve External Clock bit,
;* 06/14/90 @B72 B713826 WKB, Correct underscore problem from VioGetState,
;* 07/23/90 @T72 D1295 TPL, DCR 1295 - Support recognition of XGA device
;* 09/13/90 @D1085 D1085 WKB, DCR 1085 - Support 132 columns on appropriate h/w
;* 09/20/90 @B716255 B716255 TPL, Return XGA present for Kauai-HS
;* 10/17/90 @B717771 B717771 WKB, Reduce interrupt latency period,
;* 01/29/91 @MS00 MS00 TPL, Convert IFDEF to IF
;* 01/29/91 @MS02 MS02 TPL, OEM 132 column support (NOT ROLLOVERED YET)
;* @MS03 MS03 TPL, Remove unused CHARFONTEND2 entry point
;* @MS04 MS04 TPL, Paradise VGA cursor fix
;* @MS05 MS05 TPL, Logic to switch IDC translation mode for
;* cursor programming
;* @MS06 MS06 TPL, Read-Modify-Write logic added in AccessRegister
;* @MS07 MS07 TPL, Debug logic added
;* @MS27 MS27 TPL, add OEM detection logic
;* 09/25/91 @B726706 B726706 WKB, OEM changes
;* @B726719 B726719 WKB, OEM changes
;* 02/12/92 @T81 B732894 TPL, Use kernel IoDelay macro,
;* 03/01/92 @B726708 B726708 TRM, Compaq OEM fix
;* 03/25/92 @DRW Skip sequencer 7 'fixups' for Tseng-based adapters
;* 04/09/93 @RAD 60272 YEE, Use POS regs 108-10f for Radius
;*****************************************************************************/
.286p
;/*
;** Include files
;*/
include struc.inc ; Structured assembly macros
include vdh.inc ; Definitions
include vdhctl.inc ; Conditional assembly control
;/*
;** IF VDHCGA OR (VDHVGA AND NOT VDHINIT) ;@MS00
;** IF VDHCGA OR (VDHVGA AND (1 - VDHINIT)) ;@MS00
;** OEMFlags not added to BVHINIT. ;@MS00
;*/
IFE VDHINIT ; IF NOT VDHINIT ;@MS00
include vdhequ.inc ; OEMFlags bit definitions ;@MS27
extrn _OEMFlags:word ; OEM specific features ;@MS27
ENDIF ; NOT VDHINIT ;@MS00
IF VDHINIT ; IF VDHINIT ;@RAD
extrn _machinetype:word ;@RAD
ENDIF ; VDHINIT ;@RAD
IF VDHVGA AND (1 - VDHINIT) ;@DRW
TSENG_ADAPTER EQU 3 ; ;@DRW
extrn _SVGAPresent:word ; SVGA adapter type ;@DRW
ENDIF
include iodelay.inc ; IODelay macro ;@T81
R2SEG SEGMENT DWORD PUBLIC 'CODE' ;@T81
ASSUME CS: R2SEG, DS: DGROUP
IF VDHINIT ; Start of @T72 ;@MS00
;/***************************************************************************
;*
;* FUNCTION NAME = QueryXGA
;*
;* DESCRIPTION = Query XGA configuration
;* Search until the 1st XGA adapter found beginning from
;* the planar and then slot 1 to 8. Once an XGA adapter
;* is found, query which display is attached.
;*
;* LINKAGE: CALL FAR
;*
;* INPUT = NONE
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = AL = display type ( Color8514, Color8512_8513, etc)
;* AH = memory size ( 0 - 512k, 1 - 1MB )
;* RETURN-ERROR = AX = VDHERROR_NO_ADAPTER
;*
;**************************************************************************/
PUBLIC _QueryXGA
_QueryXGA PROC FAR
; STACK FRAME for saving data @RAD
SlotValue EQU <[bp-1]> ; BYTE @RAD
RadiusValue EQU <[bp-2]> ; BYTE @RAD
STACKBLOCK EQU 2 ;@RAD
push bp ;@RAD
mov bp,sp ;@RAD
sub sp,STACKBLOCK ; set up stack size @RAD
sub di,di ; Assume XGA not present ;@B716255
cli ; Disable interrupt
in al, 94h ; Read planar POS
mov bl, al ; Save planar setting
mov al, 0DFh ;
out 94h, al ; Put planar into setup mode
mov dx, 100h ;
in ax, dx ; Get POS ID
.if <ax ae 8FD8h> and ; XGA on planar? ;D89
.if <ax be 8FDBh> ;D89
mov di, 8000h ; Indicate XGA found ;@B716255
call GetMonitorID ; On return: AX = Monitor ID value
mov cx, ax ;
mov al, bl ;
out 94h, al ; Restore planar setting
;
; Duplicate code because the else leg was getting too big for a jmp short @RAD
;
sti ; @RAD
mov ax, cx ; Return VIO monitor ID value @RAD
or ax, di ; and XGA present bit @RAD
mov sp, bp ; restore stack @RAD
pop bp ; restore value @RAD
ret ; found it, now go away @RAD
.endif ; @RAD
; Now look through card slots for XGA @RAD
mov al, bl ;
out 94h, al ; Restore planar setting
kIODelay ; @D1085 ;@T81
in al, 96h ; Read card slot setting
mov BYTE PTR SlotValue,al ; Save card slot setting @RAD
mov cx, 08h ; Start with card slot 0 (bit 0-3)
.repeat ; Search up to 8 card slots for an
mov al, cl ; XGA with a display attached
out 96h, al ; Put card slot into setup mode
kIODelay ; @D1085 ;@T81
in ax, dx ; Get POS ID from slot
.if <_machinetype eq 0> ; family 1 machine @RAD
.if <ax lt 8FD8h> or ; didn't find XGA @RAD
.if <ax gt 8FDBh> ; didn't find XGA @RAD
add dx, cx ; go to radius pos regs 108-10f @RAD
in al, dx ; Get original value @RAD
mov BYTE PTR RadiusValue,al ; save it @RAD
mov al, cl ; start again, this time for......@RAD
out dx, al ; Put card into setup mode @RAD
kIODelay ; @D1085 @RAD
mov dx, 100h ; restore dx @RAD
in ax, dx ; Get POS ID from slot @RAD
.endif ; end search for Radius @RAD
.endif ; end family1 machine test @RAD
.if <ax ae 8FD8h> and ;D89
.if <ax be 8FDBh> ;D89
mov di, 8000h ; Indicate XGA found ;@B716255
call GetMonitorID ; On return: AX = Monitor ID value
.else
sub ax, ax ;D89
.endif ; AX = 0 means no display
.if <_machinetype eq 0> ; we clobbered a fam1 pos register@RAD
mov bx, ax ; save Monitor ID @RAD
mov al, BYTE PTR RadiusValue ; get value to restore @RAD
mov dx, 100h ; restore dx @RAD
add dx, cx ; get POS register to restore @RAD
out dx, al ; restore POS value @RAD
mov dx, 100h ; restore dx @RAD
mov ax, bx ; restore Monitor ID @RAD
.endif ; end test @RAD
.until <nonzero ax> or ; XGA found
inc cx ; Next slot
.until <cx a 0Fh> ; Search all 8 slots?
mov cx, ax ;
mov al,BYTE PTR SlotValue ; Restore card slot setting @RAD
out 96h, al ; Restore card slot setting
sti
mov ax, cx ; Return VIO monitor ID value
or ax, di ; and XGA present bit ;@B716255
mov sp, bp ; restore stack @RAD
pop bp ; restore value @RAD
ret
_QueryXGA ENDP
Monitor_Table label word
public Monitor_Table
db VDHERROR_NO_ADAPTER ; 0000
db VDHERROR_NO_ADAPTER ; 0001
db VDHERROR_NO_ADAPTER ; 0010
db VDHERROR_NO_ADAPTER ; 0011
db VDHERROR_NO_ADAPTER ; 0100 5081
db VDHERROR_NO_ADAPTER ; 0101 Buffalo
db VDHERROR_NO_ADAPTER ; 0110
db VDHERROR_NO_ADAPTER ; 0111 Boston
db VDHERROR_NO_ADAPTER ; 1000
db 0Bh ; 1001 8604, 8507
db 09h ; 1010 8514
db 0Ch ; 1011 8515 (Dallas)
db VDHERROR_NO_ADAPTER ; 1100
db 03h ; 1101 8503
db 04h ; 1110 8513, 8512
db VDHERROR_NO_ADAPTER ; 1111 No monitor attached
GetMonitorID PROC NEAR
public GetMonitorID
mov dx, 102h ;
in al, dx ; Read POS 102
and ax, 0Eh ; IODA is located in bit 1-3
shl ax, 03h ; Use bit 1-3 to form IO address
mov dx, 210Ah ; Base IO address
or dx, ax ; Form Device IO address (21xA)
mov al, 52h ;
out dx, al ; Index to Monitor ID address
inc dx ; Device Data address
in al, dx ; Get Monitor ID bits
and ax, 0Fh ; Clear the unwanted bits
mov si, OFFSET Monitor_Table; Setup offset to Monitor ID table
add si, ax ; Form index into the Monitor ID table
mov al, BYTE PTR cs:[si] ; Return VIO Monitor ID
ret
GetMonitorID ENDP
ENDIF ;VDHINIT ; End of @T72 ;@MS00
IF VDHVGA OR VDH8514A ;@MS00
;/***************************************************************************
;*
;* FUNCTION NAME = Query8514A
;*
;* DESCRIPTION = Query 8514/A configuration.
;* Verify presence of 8514/A adapter, query memory size,
;* and query display type.
;*
;* LINKAGE: CALL FAR
;*
;* INPUT = NONE
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = AL = display type ( Color8514, Color8512_8513, etc)
;* AH = memory size ( 0 - 512k, 1 - 1MB )
;* RETURN-ERROR =
;* AX = VDHERROR_NO_ADAPTER
;*
;**************************************************************************/
PUBLIC _Query8514A
_Query8514A PROC FAR
mov cx, VDHERROR_NO_ADAPTER ; Initialize cx = 8514/A not found
mov dx, 9AE9h ; High byte of status reg ;@D184
in al, dx ; Read 8514 Queue Status Reg ;@D184
test al, 20h ;@D184
.if < z > ; Not busy
mov dx, 92E8h
mov ax, 5555h
out dx, ax
kIODelay ;@D1085 ;@T81
in ax, dx
.if < ax eq 5555h > ; 8514 found
mov dx, 42E8h
in al, dx ; Get display info
mov ah, al
and al, 70h
.if < al ne 70h > ; Display attached to 8514/A
.if < al eq 10h > ;@D184
mov cl, Mono8507_8604 ; 8514/A with 8507/8604 ;@D184
.endif ;@D184
.if < al eq 20h > ;@D184
mov cl, Color8514 ; 8514/A with 8514
.endif
.if < al eq 30h > ;@D184
mov cl, Color8515 ; 8514/A with 8515 ;@D184
.endif ;@D184
.if < al eq 50h > ;@D184
mov cl, Mono8503 ; 8514/A with 8503
.endif
.if < al eq 60h >
mov cl, Color8512_8513 ; 8514/A with 8512/3
.endif
test ah, 80h ; 512k or 1MB ?
.if < nz >
mov ch, MEM_1MB
.endif
.endif
.endif
.endif
mov ax, cx
ret
_Query8514A ENDP
ENDIF ;VDHVGA OR VDH8514A ;@MS00
IF VDH8514A ;Start of @S24 changes ;@MS00
;/***************************************************************************
;*
;* FUNCTION NAME = AccessDisplayMask
;*
;* DESCRIPTION = Set or read physical display mask
;* AccessDisplayMask is called to query or set the physical
;* display mask setting.
;*
;* LINKAGE: CALL FAR
;*
;* INPUT = (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD DisplayMask ( far pointer to dword )
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = Display mask is set or returned
;* RETURN-ERROR = NONE
;*
;**************************************************************************/
PUBLIC ACCESSDISPLAYMASK
ACCESSDISPLAYMASK PROC FAR
enter 2, 0 ; Allocate 1 word temporary storage
push es
push di
les di, ParameterPacket ; es:di = underscore scan line
.if < Direction eq SET >
mov dx,02EAh ; Set address
mov al,BYTE PTR es:[di].DisplayMask
out dx,al ;Set the mask
.else
sub ax,ax
mov dx,02EAh ; Set address
in al,dx ; Get the mask
mov WORD PTR es:[di].DisplayMask,ax
sub ax,ax
mov WORD PTR es:[di].DisplayMask+2,ax
.endif
pop di
pop es
leave
ret 6
ACCESSDISPLAYMASK ENDP
;/***************************************************************************
;*
;* FUNCTION NAME = AccessCLUT for 8514/A
;*
;* DESCRIPTION = Set or read physical color lookup table.
;* AccessCLUT is called to query or set the physical
;* color lookup table.
;*
;* LINKAGE: CALL FAR
;*
;* INPUT = (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD ColorLookupTable ( far pointer to structure )
;* DWORD DataArea ( far pointer to table )
;* WORD FirstEntry
;* WORD NumEntries
;*
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = Color lookup table is altered or queried
;* RETURN-ERROR = NONE
;*
;**************************************************************************/
paldata equ 02EDh ; Palette data Register ;@S24
paladdr equ 02ECh ; Palette Address Register ;@S24
rpaladdr equ 02EBh ; Palette Address Register ;@S24
PUBLIC ACCESSCLUT
ACCESSCLUT PROC FAR
push bp
mov bp, sp
push es
push di
les di, ParameterPacket ; es:di = palette packet
mov cx,WORD PTR es:[di].NumEntries ; # of RBGx entries
mov ax, WORD PTR es:[di].FirstEntry ; starting reg
les di, DWORD PTR es:[di].DataArea
cld
.if < Direction eq SET >
push ds
push si
mov si,es
mov ds,si
mov si,di
.repeat
mov dx,paladdr ; Palette address reg
cli
out dx,al ; Put out address
mov dx,paldata ; Point to data reg for RGB triplet
inc ax ; set next palette address
push ax
lodsb
shr al,1
shr al,1 ; Reduce to hardware range
out dx,al ; Put out the red
lodsb
shr al,1
shr al,1 ; Reduce to hardware range
xchg AH,AL ; Blue is first in the definition
lodsb
shr al,1
shr al,1 ; Reduce to hardware range
out dx,al ; Put out the green
xchg ah,al ; Get the blue back
out dx,al ; Put out the blue
sti
lodsb ; Discard extra byte
pop ax
.loop ; Go back for more
pop si
pop ds
.else ; Read the color registers
.repeat
mov dx,rpaladdr ; Palette read address reg
cli
out dx,al ; Put out address
mov dx,paldata ; Point to data reg for RGB triplet
inc ax ; set next palette address
push ax ; save palette address
in al,dx ; do triplet - get RED
shl al,1 ; Align Data
shl al,1 ; Align Data
stosb ; save RED
in al,dx ; - get GREEN
shl al,1 ; Align Data
shl al,1 ; Align Data
xchg ah,al ; keep GREEN
in al,dx ; - get BLUE
sti
shl al,1 ; Align Data
shl al,1 ; Align Data
stosb ; save BLUE
xchg ah,al ; restore GREEN
stosb ; save GREEN
mov al,0 ; Setup 4th byte
stosb
pop ax ; restore palette address
.loop
.endif
pop di
pop es
pop bp
ret 6
ACCESSCLUT ENDP
ELSE ;VDH8514A ; End of @S24 changes ;@MS00
IF VDHVGA ; Read/write hardware ;@MS00
;/***************************************************************************
;*
;* FUNCTION NAME = _HardwareColumns
;*
;* DESCRIPTION = Get number of text columns in current mode
;* _HardwareColumns is called by routines who need to know
;* whether the current mode has 40, 80 or 132 character
;* columns.
;*
;* INPUT = NONE
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = AX = Number of character columns ( 40, 80 or 132 )
;* RETURN-ERROR = NONE
;*
;**************************************************************************/
PUBLIC _HardwareColumns
_HardwareColumns PROC FAR
;/*
;** Determine number of character columns by reading Sequencer register
;** Dot Clock bit (b3) of Clocking Mode Register: 0 = 80 col, 1 = 40 col
;*/
mov dx, SeqAddressPort ;Sequencer address register
mov al, IndClockModeReg ;Clocking Mode index
cli
out dx, al
mov dx, SeqDataPort ;Sequencer data register
in al, dx
test al, 8 ;Check Dot Clock bit
.if < z >
IFE VDHINIT ; NOT VDHINIT ;MS?? - BEGIN
sti
mov dx, MiscOutputRegRead
in al, dx
mov dx, CRTCtlAddressReg
.if <BIT al and NOT_MONO> ; Color VGA?
add dx, ColorAdjustment
.endif
cli
mov ax, 01h ; Index to the Horizontal Display
out dx, al ; Enable End Register
kIODelay ; ;@T81
inc dx ; Read the Horizontal Display
in al, dx ; Enable End Register content
inc al ; Convert to 1 base
ELSE
mov ax, 80
ENDIF ;NOT VDHINIT ;MS?? - END
.else
mov ax, 40 ;40 column mode
.endif
sti
ret
_HardwareColumns ENDP
;/***************************************************************************
;*
;* SUBROUTINE NAME: _HardwareColor
;*
;* DESCRIPTIVE NAME: Determine if current mode is color or monochrome
;*
;* FUNCTION: _HardwareColor is called by routines who need to know
;* whether the current mode is color or monochrome.
;*
;* ENTRY POINT: _HardwareColor
;* LINKAGE: CALL FAR
;*
;* INPUT: NONE
;*
;* EXIT-NORMAL: AX = 1 - color, 0 - monochrome
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;****************************************************************************/
PUBLIC _HardwareColor
_HardwareColor PROC FAR
;/*
;** Determine whether color or monochrome mode to determine which
;** ports should be used. This is done by checking the
;** I/O Address Select bit (b0) of the Miscellaneous Output Register:
;** b0: 0 = Monochrome emulation mode, 1 = Color emulation mode
;*/
mov dx, MiscOutputRegRead ; Read Miscellaneous Output Register
in al, dx
and ax, 1 ; Return 1 - color, 0 - monochrome
ret
_HardwareColor ENDP
;/**************************************************************************
;*
;* SUBROUTINE NAME: SET132
;*
;* DESCRIPTIVE NAME: Enable display adapter for 132 column mode.
;*
;* FUNCTION: SET132 is called by routines who need to set the
;* state of the display adapter into 132 column mode.
;*
;* ENTRY POINT: SET132
;* LINKAGE: CALL FAR
;*
;* INPUT: NONE
;* INPUT: (Passed on stack)
;* WORD Comp_reg (POS ID)
;* WORD Direction ( 1 = SET, 0 = CLEAR )
;*
;* EXIT-NORMAL: Display adapter enabled for 132 column mode.
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;****************************************************************************/
PUBLIC SET132 ;@D1085
SET132 PROC FAR ;@D1085
;@D1085
enter 4,0 ;@D1085
;@D1085
mov ax, ss:[bp+6] ;@D1085
mov dx, ss:[bp+8] ;@D1085
.if < ax eq 1 > ;@D1085
mov al,11h ;@D1085
.else ;@D1085
mov al,1h ;@D1085
.endif ;@D1085
;@D1085
out dx, al ;@D1085
;@D1085
leave ;@D1085
ret 4 ;@D1085
;@D1085
SET132 ENDP ;@D1085
;/****************************************************************************
;*
;* SUBROUTINE NAME: QUERY132
;*
;* DESCRIPTIVE NAME: Inspect Adapter for ability to support 132
;* column mode.
;*
;* FUNCTION: QUERY132 is called by routines who need know
;* whether 132 column mode is supported.
;*
;* ENTRY POINT: QUERY132
;* LINKAGE: CALL FAR
;*
;* INPUT: NONE
;*
;* EXIT-NORMAL: AX = Address of instance data register.
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;****************************************************************************/
PUBLIC QUERY132 ;@D1085
QUERY132 PROC FAR ;@D1085
;@D1085
push bx ;@T81
mov dx, 2170h ; start from the 8th ;@D1085
; instance OpMode Reg. ;@D1085
.repeat ;@D1085
in al, dx ; get the OpMode setting;@D1085
.if < al b 0F0h > ; valid value? ;@D1085
;@D1085
xchg ah, al ; save it in AH ;@D1085
;@D1085
mov al, 1h ; now enable it for ;@D1085
out dx, al ; VGA decode ;@D1085
;@D1085
kIODelay bx ;@D1085,@T81
;@D1085
in al, dx ; read the value back ;@D1085
;@D1085
.if < al eq 1 > ; VGA mode set? ;@D1085
mov al, 11h ; now enable SVGA to ;@D1085
out dx, al ; 132 column mode ;@D1085
;@D1085
kIODelay bx ;@D1085,@T81
;@D1085
in al, dx ; read mode setting ;@D1085
xchg ah, al ; AL = original value ;@D1085f
.if < ah eq 11h > ; 132 col mode is set? ;@D1085f
out dx, al ; restore original SVGA ;@D1085
mov ax, dx ; setting and return ;@D1085
; SVGA found ;@D1085f
.else ;@D1085
out dx, al ; restore original XGA ;@D1085f
sub ax, ax ; setting and return ;@D1085f
.endif ; non-found ;@D1085
.else ;@D1085
sub ax, ax ; indicate non-found ;@D1085
.endif ;@D1085
.else ;@D1085
sub ax, ax ; indicate non-found ;@D1085
.endif ;@D1085
;@D1085
sub dx, 10h ; next configuration ;@D1085
.until <nonzero ax> or ;@D1085
.until <dx b 2100h> ;@D1085
;@D1085
pop bx ;@T81
ret ;@D1085
;@D1085
QUERY132 ENDP ;@D1085
ENDIF ;VDHVGA ;@MS00
IF VDHEGA OR VDHVGA ;@T72,@MS00
;/****************************************************************************
;*
;* SUBROUTINE NAME: SetMapMask
;*
;* DESCRIPTIVE NAME: Address select a bit plane to read or write
;*
;* FUNCTION: SetMapMask is called by SaveRestorePVB in order to address
;* a specific bit plane in graphics mode during a 3xBox
;* display buffer save or restore
;*
;* ENTRY POINT: SetMapMask
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD ReadMapMask ( 0 - 3, 4 = write )
;* WORD WriteMapMask ( 1, 2, 4, or 8 )
;*
;* EXIT-NORMAL: Bit plane selected for read or write
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC SETMAPMASK
SETMAPMASK PROC FAR
;/*
;** ENTRY: SS:SP = offset selector mas
;*/
push bp
mov bp, sp
push dx
push ax
cli
.if < ReadMap eq 0 > or
.if < MapMask eq 1 >
;/*
;** Set graphics mode register just for the first bit plane
;*/
mov dx, GraphAddressPort
mov ax, 0001h ; Start from Set/Reset regs. ;@T47
.repeat ; ;@T47
out dx, al ; Setup address port ;@T47
inc dx ; Index to data port ;@T47
inc ax ; Index to next address port ;@T47
xchg al,ah ; ;@T47
out dx,al ; Clear Graphics register ;@T47
dec dx ; Back to address port ;@T47
xchg al,ah ; ;@T47
cmp al,6 ; ;@T47
.until <z> ; ;@T47
.if < MapMask eq 1 > ; 1st write request? ;@TL3
mov al,8 ; ;@TL3
out dx,al ; Index to Bit Mask register ;@TL3
inc dx ; ;@TL3
mov al,0ffh ; ;@TL3
out dx,al ; Allow write to all bits ;@TL3
.endif ; ;@TL3
.endif ; ;@T47
.if < ReadMap ne WriteFunction >
;/*
;** Reading from display buffer, address select specified bit plane
;*/
mov dx, SeqAddressPort
mov al, 02h ; Memory map register in sequencer
out dx, al
inc dx
mov al, 0Fh
out dx, al ; Memory map = 00001111
;/*
;** Address select specified bit plane to read
;*/
mov dx, GraphAddressPort
mov al, 04h ; Read map select register
out dx, al
inc dx
mov al, ReadMap
out dx, al ; Read map select = 0, 1, 2, 3
.else
;/*
;** Writing to display buffer, address select specified bit plane
;*/
mov dx, SeqAddressPort
mov al, 02h ; Memory map register in sequencer
out dx, al
inc dx
mov al, MapMask
out dx, al ; Memory map
.endif
sti
pop ax
pop dx
pop bp
ret 4 ; Remove 2 words from stack
SETMAPMASK ENDP
ENDIF ; VDHEGA OR VDHVGA ;@T72,@MS00
;@T39 IFDEF FONT_SUPPORT ;@S4
;/*****************************************************************************
;*
;* SUBROUTINE NAME: _CharFontBegin
;*
;* DESCRIPTIVE NAME: Address the font buffer
;*
;* FUNCTION: _CharFontBegin is called by routines in order to address
;* the font buffer for writing or reading
;*
;* ENTRY POINT: _CharFontBegin
;* LINKAGE: CALL FAR
;*
;* INPUT: NONE
;*
;* EXIT-NORMAL: Font buffer is address selected at A0000
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC _CharFontBegin
_CharFontBegin PROC FAR
push dx
mov dx, GraphAddressPort
mov ax, 0204h
cli
out dx, ax ; Read Map Select register
mov ax, 0005h
out dx, ax ; Graphics Mode register
mov ax, 0406h
out dx, ax ; Graphics Misc register
mov dx, SeqAddressPort
mov ax, 0402h ; write font to bp only bit plane 0
out dx, ax ; Write Map Select
mov ax, 0404h
out dx, ax ; Turn on odd/even
sti
pop dx
ret
_CharFontBegin ENDP
;/*****************************************************************************
;*
;* SUBROUTINE NAME: CharFontEnd
;*
;* DESCRIPTIVE NAME: Deselect font buffer
;*
;* FUNCTION: CharFontEnd and CharFontEnd2 are called following
;* completion of accessing the font buffer.
;*
;* ENTRY POINTS: CharFontEnd, CharFontEnd2
;* LINKAGE: CALL FAR
;*
;* INPUT: NONE
;*
;* EXIT-NORMAL: font buffer address is deselected
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC CHARFONTEND
CHARFONTEND PROC FAR
push bp
mov bp, sp
mov cx, 0A06h ; Setup mono buffer with chaining
.if < ColorMonoMode eq COLOR >
or cx, 0400h ; Setup color buffer
.endif
pop bp
push ax
mov dx, GraphAddressPort
mov ax, 0004h
cli
out dx, ax ; Read Map Select register
mov ax, 1005h
out dx, ax ; Graphics Mode register
mov ax, cx
out dx, ax ; Graphics Misc register
mov dx, SeqAddressPort
mov ax, 0302h
out dx, ax ; Write Map Select
mov ax, 0004h
out dx, ax ; Turn off odd/even
sti
pop ax
ret 2
CHARFONTEND ENDP
;@T39 ENDIF FONT_SUPPORT
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessCursorPos
;*
;* DESCRIPTIVE NAME: Set or read physical cursor position
;*
;* FUNCTION: AccessCursorPos is called to determine or set the
;* physical cursor location
;*
;* ENTRY POINT: AccessCursorPos
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD CursorPositiion ( far pointer to structure )
;* WORD Row
;* WORD Column
;*
;* EXIT-NORMAL: Cursor position set or returned
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSCURSORPOS
ACCESSCURSORPOS PROC FAR
enter 2, 0 ; Allocate 1 word temporary storage
push es
push di
les di, ParameterPacket ; es:di = cursor position packet
.if < ColorMode eq TRUE > ; Determine port address fixup
mov ColorMonoFixup, ColorAdjustment
.else
mov ColorMonoFixup, MonoAdjustment
.endif
;/*
;** Address Cursor Location Low Register in CRT Controller Registers
;*/
mov dx, CRTCtlAddressReg ; CRT Controller Address Register
add dx, ColorMonoFixup
mov al, IndCursorLowLoc ; Address Cursor Location Low Register
cli
out dx, al
push dx ; Remember CRT Controller Address
; Register Port
;/*
;** Set/Read Cursor Location Low Register
;*/
mov dx, CRTCtlDataReg ; CRT Controller Data Register
add dx, ColorMonoFixup ; Port address fixup
.if < Direction eq SET >
push dx
mov ax, CharacterColumns ; Number of columns this mode
mul WORD PTR es:[di].CursorRow ; Row * # of screen columns
add ax, WORD PTR es:[di].CursorColumn ; (Row * # of screen columns)+Column
pop dx
out dx, al ; Cursor Location Low value in AL
.else
in al, dx ; Cursor Location Low value in AL
mov cl, al ; Save low byte of cursor location
.endif
pop dx ; Get CRT Controller Address
; Register Port
.if < Direction eq SET >
push ax ; Save the cursor location
.endif
;/*
;** Address Cursor Location High Register in CRT Controller Registers
;*/
mov al, IndCursorHighLoc ; Address Cursor Location High Register
out dx, al
;/*
;** Set/Read Cursor Location High Register
;*/
mov dx, CRTCtlDataReg ; CRT Controller Data Register
add dx, ColorMonoFixup ; Port address fixup
.if < Direction eq SET >
pop ax ; Retrieve the location
xchg al, ah ; Put high byte into low byte
out dx, al ; Cursor Location High value in AL
.else
in al, dx ; Cursor Location High value in AL
;/*
;** Calculate the cursor position parameters using the register value
;*/
mov ah, al ; Put high byte in AH
mov al, cl ; Put low byte in AL
xor dx, dx ; Word division
div CharacterColumns ; # of screen columns
mov WORD PTR es:[di].CursorRow, ax
mov WORD PTR es:[di].CursorColumn, dx
.endif
sti
pop di
pop es
leave ; Deallocate temorary storage
ret 10
ACCESSCURSORPOS ENDP
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessCursorType
;*
;* DESCRIPTIVE NAME: Set or read physical cursor type
;*
;* FUNCTION: AccessCursorType is called to determine or set the
;* physical cursor type
;*
;* ENTRY POINT: AccessCursorType
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD CursorType ( far pointer to structure )
;* WORD TopScanLine
;* WORD BottomScanLine
;* WORD Width
;* WORD Attribute
;*
;* EXIT-NORMAL: Cursor type is set or returned
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSCURSORTYPE
ACCESSCURSORTYPE PROC FAR
enter 2, 0 ; Allocate 1 word temporary storage
push es
push di
les di, ParameterPacket ; es:di = cursor type packet
.if < ColorMode eq TRUE > ; Determine port address fixup
mov ColorMonoFixup, ColorAdjustment
.else
mov ColorMonoFixup, MonoAdjustment
.endif
;/*
;** Address Cursor Start Register in CRT Controller Registers
;*/
mov dx, CRTCtlAddressReg ; CRT Controller Address Register
add dx, ColorMonoFixup
IF VDHVGA AND (1 - VDHINIT) ; VDHVGA AND NOT VDHINIT ;@MS04
.if < Direction eq SET > ;@MS04
push ds ;@MS04
mov ax,seg _OEMFlags ;@MS04
mov ds,ax ;@MS04
mov al,BYTE PTR es:[di].CursorTopScanLine ;@MS04
test ds:word ptr[_OEMFlags],PARADISE_VGA ;@MS04
pop ds ;@MS04
.if < nz > and ;@MS04
.if < al ne 0 > ;@MS04
mov al,IndMaxScanLine ;@MS04
out dx,al ;@MS04
inc dx ;@MS04
in al,dx ; Get char cell size ;@MS04
and al,CHAR_SCANLINES ;@MS04
dec dx ;@MS04
mov ah,BYTE PTR es:[di].CursorBottomScanLine ;@MS04
.if < al eq ah > ;@MS04
dec BYTE PTR es:[di].CursorBottomScanLine ;@MS04
dec BYTE PTR es:[di].CursorTopScanLine ;@MS04
.endif ;@MS04
.endif ;@MS04
.endif ;@MS04
ENDIF ;VDHVGA AND NOT VDHINIT
mov al, IndCursorStart ; Address Cursor Start Register
cli
out dx, al
push dx ; Remember CRT Controller Address Register port
;/*
;** Set/Read Cursor Start Register
;*/
mov dx, CRTCtlDataReg ; CRT Controller Data Register
add dx, ColorMonoFixup ; Port address fixup
IF VDHVGA ; Read/write hardware ;@MS00
in al, dx ; Read reserved bits
ELSE
;@MS00
xor al, al ; Zero reserved bits
ENDIF ;VDHVGA ;@MS00
.if < Direction eq SET >
and al, 11000000B ; Clear bits we will set
or al, BYTE PTR es:[di].CursorTopScanLine ; Get value
.if <<WORD PTR es:[di].CursorAttribute> eq -1 > ; Hidden cursor?
IF VDHVGA ;VGA: b5 turns off cursor, OTHERS: b5 & b6 turns off cursor ;@MS00
or al, 00100000B ; Flip cursor off bit
ELSE ;@MS00
or al, 00111111B ; Flip cursor off bits ;@T57
ENDIF ;VDHVGA ;@MS00
.endif
out dx, al ; Cursor Start value in AL
.else
IF VDHVGA ; Read/write hardware ;@MS00
test al, 00100000B ; Check cursor off bit
.if < nz >
mov WORD PTR es:[di].CursorAttribute, -1 ; Cursor is hidden
.else
mov WORD PTR es:[di].CursorAttribute, 0 ; Cursor is not hidden
.endif
mov WORD PTR es:[di].CursorWidth, 1 ; Cursor width is always 1 column
and ax, 00011111B ; Isolate scan line begin (top)
mov WORD PTR es:[di].CursorTopScanLine, ax
ENDIF ;VDHVGA ;@MS00
.endif
pop dx ; Get CRT Controller Address Register port
;/*
;** Address Cursor End Register in CRT Controller Registers
;*/
mov al, IndCursorEnd ; Address Cursor End Register
out dx, al
;/*
;** Set/Read Cursor End Register
;*/
mov dx, CRTCtlDataReg ; CRT Controller Data Register
add dx, ColorMonoFixup ; Port address fixup
IF VDHVGA ; Read/write hardware ;@MS00
in al, dx ; Read reserved bits
ELSE ;@MS00
xor al, al ; Zero reserved bits
ENDIF ;VDHVGA ;@MS00
.if < Direction eq SET >
and al, 11100000B ; Clear bits we will set
or al, BYTE PTR es:[di].CursorBottomScanLine
out dx, al ; Cursor End value in AL
.else
IF VDHVGA ; Read/write hardware ;@MS00
and ax, 00011111B ; Isolate scan line end (bottom)
mov WORD PTR es:[di].CursorBottomScanLine, ax
ENDIF ;VDHVGA ;@MS00
.endif
sti
pop di
pop es
leave ; Deallocate temorary storage
ret 8
ACCESSCURSORTYPE ENDP
IF BLINK_SUPPORT ;@S4 ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessBlink
;*
;* DESCRIPTIVE NAME: Set or read physical blink vs. BG intensity
;*
;* FUNCTION: AccessBlink is called to query or set the physical
;* blink versus background intensity setting
;*
;* ENTRY POINT: AccessBlink
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD Blink ( far pointer to word )
;*
;* EXIT-NORMAL: Blink vs. BG intensity is set or returned
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSBLINK
ACCESSBLINK PROC FAR
push bp
mov bp, sp
push es
push di
les di, ParameterPacket ;es:di = Blink setting
;/*
;** Address Attribute Mode Control Register in Attribute Controller Registers
;*/
@SetAttAddressPort ; Attribute Address Register
mov al, IndAttModeCtl ; Address Attribute Mode Control Reg.
out dx, al ; Set up for get mode ctl color
;/*
;** Set/Read Attribute Mode Control Register
;*/
mov dx, AttDataReadPort ; Read current mode ctl setting
IF VDHVGA ; Read/write hardware ;@MS00
in al, dx ; Read reserved bits
ELSE ;@MS00
xor al, al ; Zero reserved bits
ENDIF ;VDHVGA ;@MS00
.if < Direction eq SET >
and al, 11110111B ; Select background intensity
.if < <WORD PTR es:[di].Blink> eq 0 >
or al, 00001000B ; Enable blink
.endif
mov dx, AttDataWritePort ; Set the hardware
out dx, al
IF VDHVGA ; Read/write hardware ;@MS00
.else
test al, 00001000B ; Check setting
.if < z >
mov WORD PTR es:[di].Blink, 1 ; Report background intensity
.else
mov WORD PTR es:[di].Blink, 0 ; Report blink enable
.endif
ENDIF ;VDHVGA ;@MS00
.endif
@VideoOn
sti
pop di
pop es
pop bp
ret 8
ACCESSBLINK ENDP
ENDIF ;BLINK SUPPORT ;@MS00
IF OVERSCAN_SUPPORT ;@S4 ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessOverscan
;*
;* DESCRIPTIVE NAME: Set or read physical border color
;*
;* FUNCTION: AccessOverscan is called to query or set the physical
;* overscan color
;*
;* ENTRY POINT: AccessOverscan
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD Overscan ( far pointer to word )
;*
;* EXIT-NORMAL: Overscan color is set or returned
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSOVERSCAN
ACCESSOVERSCAN PROC FAR
push bp
mov bp, sp
push es
push di
les di, ParameterPacket ; es:di = Overscan color
;/*
;** Address Overscan Color Register in Attribute Controller Registers
;*/
@SetAttAddressPort ; Attribute Address Register
mov al, IndOverscanColor ; Address Overscan Color Register
out dx, al ; Set up for get mode ctl color
;/*
;** Set/Read Overscan Color Register
;*/
.if < Direction eq SET >
mov al, BYTE PTR es:[di].Overscan
mov dx, AttDataWritePort ; Set the hardware
out dx, al
IF VDHVGA ; Read/write hardware ;@MS00
.else
mov dx, AttDataReadPort ; Read current setting
in al, dx
xor ah,ah ;@B72
mov WORD PTR es:[di].Overscan, ax ;@B72
ENDIF ;VDHVGA ;@MS00
.endif
@VideoOn
sti
pop di
pop es
pop bp
ret 8
ACCESSOVERSCAN ENDP
ENDIF ;OVERSCAN_SUPPORT ;@MS00
IF UNDERSCORE_SUPPORT ;@S4 ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessUnderscore
;*
;* DESCRIPTIVE NAME: Set or read physical underscore scan line no.
;*
;* FUNCTION: AccessUnderscore is called to query or set the physical
;* underscore scan line
;*
;* ENTRY POINT: AccessUnderscore
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD Underscore ( far pointer to word )
;*
;* EXIT-NORMAL: Underscore scan line is set or returned
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSUNDERSCORE
ACCESSUNDERSCORE PROC FAR
enter 2, 0 ; Allocate 1 word of temporary storage
push es
push di
les di, ParameterPacket ; es:di = underscore scan line
.if < ColorMode eq TRUE > ; Determine port address fixup
mov ColorMonoFixup, ColorAdjustment
.else
mov ColorMonoFixup, MonoAdjustment
.endif
;/*
;** Address Underline Location Register in CRT Controller Registers
;*/
mov dx, CRTCtlAddressReg ; CRT Controller Address Register
add dx, ColorMonoFixup ; Port address fixup
mov al, IndUnderlineLoc ; Address Underline Location Register
cli
out dx, al
;/*
;** Set/Read Underline Location Register
;*/
mov dx, CRTCtlDataReg ; CRT Controller Data Register
add dx, ColorMonoFixup ; Port address fixup ;@B72
IF VDHVGA ; Read/write hardware ;@MS00
in al, dx ; Read reserved bits
ELSE ;@MS00
xor al, al ; Zero reserved bits
ENDIF ;VDHVGA ;@MS00
.if < Direction eq SET >
and al, 11100000B ; Clear bits we will set
or al, BYTE PTR es:[di].Underscore ; Set the hardware
out dx, al
IF VDHVGA ; Read/write hardware ;@MS00
.else
and al, 00011111B ; Isolate underscore scan line
xor ah,ah ;@B72
mov WORD PTR es:[di].Underscore, ax ;@B72
ENDIF ;VDHVGA ;@MS00
.endif
sti
pop di
pop es
leave ; Deallocate temporary storage
ret 8
ACCESSUNDERSCORE ENDP
ENDIF ;UNDERSCORE_SUPPORT ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessVideoEnable
;*
;* DESCRIPTIVE NAME: Set or read physical video enable
;*
;* FUNCTION: AccessVideoEnable is called to query or set the physical
;* video enable setting.
;*
;* ENTRY POINT: AccessVideoEnable
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD VideoEnable ( far pointer to word )
;*
;* EXIT-NORMAL: Video enable is set or returned
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSVIDEOENABLE
ACCESSVIDEOENABLE PROC FAR
push bp
mov bp, sp
push es
push di
les di, ParameterPacket ; es:di = underscore scan line
cli ; clear interrupts
IF VDHEGA OR VDHVGA ;@MS00
@SetAttAddressPort ; Set the Attribute Address Port
IF VDHVGA ;@C21 ;@MS00
.if < Direction eq GET > ;@C21
mov dx,AttDataReadPort ;@C21
in al,dx ;@C21
mov WORD PTR es:[di].VideoEnable, 0 ;Disabled @C21
test al, 20h ;@C21
.if < nz > ;@C21
inc WORD PTR es:[di].VideoEnable ;Enabled @C21
.endif ;@C21
.else ;@C21
ENDIF ;VDHVGA ;@C21 ;@MS00
sub ax,ax ; Preset Disable video
.if < <WORD PTR es:[di].VideoEnable> ne ax >
mov al, 20h ; Set Enable video
.endif
out dx, al ; Write to the port
IF VDHVGA ;@C21 ;@MS00
.endif ;@C21
ENDIF ;VDHVGA ;@C21 ;@MS00
ENDIF ;VDHEGA OR VDHVGA ;@MS00
sti
pop di
pop es
pop bp
ret 8
ACCESSVIDEOENABLE ENDP
IF VDHVGA ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessCLUT for VGA
;*
;* DESCRIPTIVE NAME: Set or read physical color lookup table
;*
;* FUNCTION: AccessCLUT is called to query or set the physical
;* color lookup table.
;*
;* ENTRY POINT: AccessCLUT
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* WORD Direction ( GET or SET )
;* DWORD ColorLookupTable ( far pointer to structure )
;* DWORD DataArea ( far pointer to table )
;* WORD FirstEntry
;* WORD NumEntries
;*
;* EXIT-NORMAL: Color lookup table is altered or queried
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSCLUT
ACCESSCLUT PROC FAR
push bp
mov bp, sp
push es
push di
les di, ParameterPacket ; es:di = palette packet
mov cx,WORD PTR es:[di].NumEntries ; # of triplets ;@B705063
mov ax, WORD PTR es:[di].FirstEntry ; starting reg ;@B705063
les di, DWORD PTR es:[di].DataArea
.if < Direction eq SET > ;@B705063
mov dx, PELAddressWrite ;@B705063
cli ;@B705063
out dx, al ;@B705063
mov dx, PELDataRegister ; Get data register ;@B705063
.repeat ;@B705063
cli ;@B705063
mov al, BYTE PTR es:[di] ;@B705063
out dx, al ; Set register value ;@B705063
inc di ;@B705063
mov al, BYTE PTR es:[di] ;@B705063
out dx, al ; Set register value ;@B705063
inc di ;@B705063
mov al, BYTE PTR es:[di] ;@B705063
out dx, al ; Set register value ;@B705063
sti ;@B705063
inc di ;@B705063
.loop ;@B705063
.else ;@B705063
cld ;@B705063
mov dx, PELAddressRead ;@B705063
cli ;@B705063
out dx, al ;@B705063
mov dx, PELDataRegister ; Get data register ;@B705063
IFE VDHINIT
push ds
mov ax, seg _OEMFlags
mov ds, ax
mov ah, 3Fh ; Default 6-bit DAC
.if <bit [_OEMFlags] and STARDUST_VGA>
mov ah, 0FFh ; VGA has 8-bit DAC
.endif
pop ds
ELSE
mov ah, 3Fh
ENDIF
.repeat ;@B705063
cli ;@B705063
in al, dx ; Set register value ;@B705063
and al, ah ; Isolate color ( x bits ) ;@B705063
stosb ;@B705063
in al, dx ; Set register value ;@B705063
and al, ah ; Isolate color ( x bits ) ;@B705063
stosb ;@B705063
in al, dx ; Set register value ;@B705063
sti ;@B705063
and al, ah ; Isolate color ( x bits ) ;@B705063
stosb ;@B705063
.loop ;@B705063
.endif
pop di
pop es
pop bp
ret 6
ACCESSCLUT ENDP
ENDIF ;VDHVGA ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessHardware
;*
;* DESCRIPTIVE NAME: Set or read physical indexed registers
;*
;* FUNCTION: AccessHardware is called to query or set the physical
;* indexed registers - Sequencers, Attributes, CRTs, or
;* Graphics
;*
;* ENTRY POINT: AccessHardware
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* DWORD RegAddress ( far pointer to structure )
;* WORD RegAddressPort
;* WORD RegDataPort
;* WORD RegColorAdjust
;* WORD RegFlags
;* WORD DataType ( BYTES or WORDS )
;* WORD Direction ( GET or SET )
;* DWORD RegData ( far pointer to structure )
;* DWORD DataArea ( far pointer to data table )
;* WORD FirstEntry
;* WORD NumEntries
;*
;* EXIT-NORMAL: Indexed registers are altered or queried
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSHARDWARE
ACCESSHARDWARE PROC FAR
push bp
mov bp, sp
push es
push di
push ds
push si
les di, ParameterPacket ; es:di = data packet
lds si, AddressPacket ; ds:di = address packet
mov bx, WORD PTR es:[di].FirstEntry ; Get starting reg
mov cx, WORD PTR es:[di].NumEntries ; Get number of regs
les di, DWORD PTR es:[di].DataArea
.if < ds:[si].RegFlags eq Attributes_CMD >
;/*
;** To access the attribute address register, an 'in' must be issued to
;** the Attribute Controller at address 03BA for mono or 03DA for color.
;*/
mov dx, AttCtlInitializeReg ; Feature Control Register - init AttCtl flip-flop
.if < ColorMode eq TRUE >
add dx, ColorAdjustment
.endif
.endif
push dx ;@B19
HARDWARE_REG:
cli ;@B717771
.if < ds:[si].RegFlags eq Attributes_CMD >
pop dx ;@B19
in al, dx ; Read port to reset flip-flop
push dx ;@B19
.endif
mov dx, ds:[si].RegAddressPort ; Address Register
.if < ColorMode eq TRUE >
add dx, ds:[si].RegColorAdjust
.endif
mov al, bl ; Address Palette Reg ( 00 - 0F )
IF VDHVGA ;@B19 ;@MS00
; wait for vertical retrace to avoid glitching VRAM ;@B19
.if <al EQ 10h> AND ;@B19
.if <dx EQ AttAddressPort> ;@B19
call VGAWait ;@B19
.endif ;@B19
ENDIF ;VDHVGA ;@B19 ;@MS00
out dx, al ; Set up for get palette reg
mov dx, ds:[si].RegDataPort ; Address Register
.if < ColorMode eq TRUE >
add dx, ds:[si].RegColorAdjust
.endif
.if < Direction eq SET >
mov al, BYTE PTR es:[di]
out dx, al
.else
IF VDHVGA ; Read/write hardware ;@MS00
in al, dx
.if < WordByte eq WORDS >
xor ah, ah
mov WORD PTR es:[di], ax
.else
mov BYTE PTR es:[di], al
.endif
ENDIF ;VDHVGA ;@MS00
.endif
inc bx
.if < WordByte eq WORDS >
inc di ; Point to next byte
.endif
inc di ; Point to next byte
sti ;@B717771
loop HARDWARE_REG
pop dx ;@B19
cli ;@B717771
.if < ds:[si].RegFlags eq Sequencers_CMD > AND ; @tb25
.if < Direction eq SET > ; @tb25
IF VDHVGA AND (1 - VDHINIT) ;@DRW
push ds ;@DRW
mov ax, seg _SVGAPresent
mov ds, ax
cmp _SVGAPresent, TSENG_ADAPTER ;@DRW
pop ds ;@DRW
je @F ;@DRW
@FixVGABug
@@:
ENDIF ;VDHVGA ;@MS00
mov dx, SeqAddressPort ; Sequencer address port
mov al, 0 ; Reset register index
out dx, al
mov dx, SeqDataPort ; Sequencer data port
mov al, 3 ; Enable Sequencers again
out dx, al
.endif
sti
pop si
pop ds
pop di
pop es
pop bp
ret 14
ACCESSHARDWARE ENDP
IF VDHVGA ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: VGAWait
;*
;* DESCRIPTIVE NAME: wait for video retrace before a write to port
;* 3C0h, register 10h
;*
;* FUNCTION:
;*
;* ENTRY POINT: VGAWait
;* LINKAGE: CALL NEAR
;*
;* INPUT: none
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC VGAWait
VGAWait PROC NEAR ;@B19
sti
push ax
push cx
push dx
mov dx, FeatureControlWrite
.if < ColorMode eq TRUE >
add dx, 20h ; use color ports
.endif
xor cx,cx ; time out in case a card never sets this bit
VGAWait1:
in al,dx
test al,8 ; look for retrace bit
loopnz VGAWait1 ; wait for retrace to end
xor cx,cx ; time out in case a card never sets this bit
VGAWait2:
sti
nop
nop ; 486 work around ;@T49
cli
in al,dx
test al,8 ; look for retrace bit
loopz VGAWait2 ;wait for retrace to begin again
pop dx
pop cx
pop ax
ret
VGAWait ENDP
ENDIF ;VDHVGA ;@MS00
ENDIF ;VDH8514A ;@MS00
;/*****************************************************************************
;*
;* SUBROUTINE NAME: AccessRegister
;*
;* DESCRIPTIVE NAME: Set or read physical non-indexed register
;*
;* FUNCTION: AccessRegister is called to query or set the physical
;* non-indexed register specified
;*
;* ENTRY POINT: AccessRegister
;* LINKAGE: CALL FAR
;*
;* INPUT: (Passed on stack)
;* DWORD RegAddress ( far pointer to structure )
;* WORD RegAddressPort
;* WORD RegDataPort
;* WORD RegColorAdjust
;* WORD RegFlags
;* WORD Direction ( GET or SET or SETWORD )
;* DWORD RegData ( far pointer to data )
;*
;* EXIT-NORMAL: Non-indexed register is altered or queried
;*
;* INTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: NONE
;*
;*****************************************************************************/
PUBLIC ACCESSREGISTER
ACCESSREGISTER PROC FAR
push bp
mov bp, sp
push es
push di
push ds
push si
les di, ParameterPacket ; es:di = data packet
lds si, AddressPkt ; ds:si = address packet
mov dx, ds:[si].RegDataPort ; Register port
cli
.if < Direction eq SET >
IF VDHEGA OR VDHVGA ;@MS00
.if < ds:[si].RegDataPort eq MiscOutputRegWrite >
push dx ; Save register address
mov dx, SeqAddressPort ; Sequencer address port
mov al, 0 ; Reset register index
out dx, al
mov dx, SeqDataPort ; Sequencer data port
inc al ; Synchronous reset
out dx, al
pop dx ; Retrieve register address
mov al, BYTE PTR es:[di] ; Set miscoutput register
out dx, al
IF VDHVGA AND (1 - VDHINIT) ;@DRW
push ds ;@DRW
mov ax, seg _SVGAPresent ;@DRW
mov ds, ax ;@DRW
cmp _SVGAPresent, TSENG_ADAPTER ;@DRW
pop ds ;@DRW
je @F ;@DRW
@FixVGABug
@@:
ENDIF ;VDHVGA ;@MS00
mov dx, SeqAddressPort ; Sequencer address port
mov al, 0 ; Reset register index
out dx, al
mov dx, SeqDataPort ; Sequencer data port
mov al, 3 ; Normal operation
out dx, al
.else
ENDIF ;VDHEGA OR VDHVGA ;@MS00
mov al, BYTE PTR es:[di]
out dx, al
IF VDHEGA OR VDHVGA ;@MS00
.endif
ENDIF ;VDHEGA OR VDHVGA ;@MS00
.else
.if < Direction eq SETWORD >
mov ax, word ptr es:[di]
out dx,ax
.else ; < Direction eq GET >
in al, dx
stosb
.endif
.endif
sti
pop si
pop ds
pop di
pop es
pop bp
ret 10
ACCESSREGISTER ENDP
IF DEBUG ;@MS07 - BEGIN
;/*
;** Equates for com port
;*/
COM1_DAT= 03f8H ; base for COM1
COM2_DAT= 02f8H ; base for COM2
R_IEN = 1 ; Interrupt enable
R_IER = 2 ; interrupt ID
R_LCR = 3 ; line control registers
R_MCR = 4 ; modem control register
R_LSR = 5 ; line status register
R_MSR = 6 ; modem status regiser
R_DLL = 0 ; divisor latch least sig
R_DLM = 1 ; divisor latch most sig
;/*
;** Exactly one of the next two lines should be uncommented to select por
;*/
;UR_DAT = COM2_DAT ; select COM2 = 02f8H
UR_DAT = COM1_DAT ; select COM1 = 03f8H
UR_IEN = UR_DAT+1 ; Interrupt enable
UR_IER = UR_DAT+2 ; interrupt ID
UR_LCR = UR_DAT+3 ; line control registers
UR_MCR = UR_DAT+4 ; modem control register
UR_LSR = UR_DAT+5 ; line status register
UR_MSR = UR_DAT+6 ; modem status regiser
UR_DLL = UR_DAT ; divisor latch least sig
UR_DLM = UR_DAT+1 ; divisor latch most sig
;/***************************************************************************
;*
;* FUNCTION NAME = DPRINTF - Debug Printf
;*
;* DESCRIPTION =
;*
;* Dprintf is a kernel debug print formatting package.
;* This version is a hastily stripped version of another routine
;* with the same name.
;*
;* Due to difficulties passing variable length argument lists
;* through a call gate transition, only one argument, a zero
;* terminated string is passed to this routine. The string
;* will be sent to either COM1 or COM2 depending on the definition
;* of UR_DAT.
*
;* About the only intelligent thing this routine can do is process
;* XON/XOFF characters from the equipment attached to the debug
;* port so that the output will not overrun the recieving device.
;* However after recieving an XOFF, this routine will simply spin
;* in a loop waiting for XON. Using equipment/software on that
;* can keep up on the debug port is recommended.
;*
;* The format string is an ASCIZ string which can contain
;* literal characters.
;*
;* Literal characters
;* - any character not part of a format specification. Special
;* non-printing characters are:
;* \n - CRLF
;* \t - tab
;* \b - bell
;* \\ - \
;*
;* WARNINGS
;* As befitting a debug routine, DPRINTF does not have a whole lot
;* of "failsafe" code in it.
;*
;* INPUT = (sp+6 ) = segment of string
;* (sp+4 ) = offset of string
;* (sp+2 ) = seg of return address
;* (sp ) = offset of return address
;*
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = NONE
;* RETURN-ERROR = NONE
;*
;**************************************************************************/
Public _DPRINTF
_DPRINTF PROC far
push bp
mov bp,sp
push ds
push es
push di
push si
push dx
push cx
push bx
push ax
cld
;/*
;** Change string address to far ptr on stac
;*/
add bp,6
mov si,[bp]
add bp,2
mov ax,[bp]
push ax
pop ds
;/*
;** Scan format string for next character
;**
;** (ds:si) = address of format string
;** (ss:bp) = address of next argument
;*/
public dpf1
dpf1: lodsb ; (al) = format string byte
and al,al
je dpf3 ; all done
cmp al,'\'
jnz dpf2 ; got the character
;/*
;** it's an "\" escape code - crack the argument characte
;*/
lodsb
and al,al
je dpf3 ; all done, ignore hanging \
xchg ah,al
mov al,0Ch
cmp ah,'n'
jne dpf1$5 ; not \n
mov al,0dH
call putchar
mov al,0aH
jmp SHORT dpf2 ; print LF
dpf1$5: cmp ah,'t'
mov al,9
je dpf2 ; is \t
cmp ah,'b'
mov al,7
je dpf2 ; is \b
xchg ah,al
dpf2: call putchar
jmp dpf1
;/*
;** have the end of the format string - exit
;*/
dpf3: pop ax
pop bx
pop cx
pop dx
pop si
pop di
pop es
pop ds
pop bp
ret 4 ; pop 4 bytes after return address
_DPRINTF ENDP
;/***************************************************************************
;*
;* FUNCTION NAME = inchr
;*
;* DESCRIPTION = input character
;*
;* INPUT = NONE
;* OUTPUT = 'z' set if no character
;* 'z' clear if char
;* (al) = char
;* RETURN-NORMAL = NONE
;* RETURN-ERROR = NONE
;*
;**************************************************************************/
inchr PROC NEAR
mov dx,UR_LSR
in al,dx
and al,1
jz inchr1
mov dx,UR_DAT
in al,dx
and al,07fh
inchr1: ret
inchr ENDP
;/***************************************************************************
;*
;* FUNCTION NAME = putchar
;*
;* DESCRIPTION = put a character on the console
;*
;* INPUT = (al) = character
;* OUTPUT = NONE
;*
;* RETURN-NORMAL = NONE
;* RETURN-ERROR = NONE
;*
;**************************************************************************/
putchar PROC NEAR
pushf
cli
push dx
push cx
push bx
push ax ; (al) = character
;/*
;** see if CTL-Q or CTL-S
;*/
pushf
cli
call inchr
jz putc3 ; no characters incomming
cmp al,19 ; ctl-S?
jnz putc3 ; no, ignore
;/*
;** have ctl-s. wait till we see ctl-Q
;*/
putc2: call inchr
jz putc2
cmp al,17
jnz putc2
putc3: popf
mov dx,UR_LSR
putc4: in al,dx
test al,020h
jz putc4
;/*
;** ready. crank it out!
;*/
mov dx,UR_DAT
pop ax
out dx,al
pop bx
pop cx
pop dx
popf
ret
putchar ENDP
ENDIF ;DEBUG ;@MS07 - END
R2SEG ENDS
END