home *** CD-ROM | disk | FTP | other *** search
- ;****************************************************************************
- ;*
- ;* SuperVGA Test Library
- ;*
- ;* Copyright (C) 1993 Kendall Bennett.
- ;* All rights reserved.
- ;*
- ;* Filename: $RCSfile: svga16.asm $
- ;* Version: $Revision: 1.2 $
- ;*
- ;* Language: 80386 Assembler
- ;* Environment: IBM PC (MS DOS)
- ;*
- ;* Description: This source file contains code to initialise the SuperVGA
- ;* for bank switching and extended page flipping.
- ;*
- ;* It also contains code to draw pixels, clear the display
- ;* and perform page flipping for SuperVGA 16 color video modes.
- ;*
- ;* $Id: svga16.asm 1.2 1993/03/07 04:05:36 kjb Exp $
- ;*
- ;* Revision History:
- ;* -----------------
- ;*
- ;* $Log: svga16.asm $
- ;* Revision 1.2 1993/03/07 04:05:36 kjb
- ;* Bug fixes.
- ;*
- ;* Revision 1.1 1993/03/03 10:25:25 kjb
- ;* Initial revision
- ;*
- ;****************************************************************************
-
- IDEAL
- JUMPS
- P386 ; Use 386 instructions
-
- INCLUDE "model.mac" ; Memory model macros
-
- header svga16
-
- INCLUDE "MGRAPH.EQU" ; Include Equates for Mgraph Routines
-
- CRTC EQU 3D4h ; Port of CRTC registers
- VGABufferSeg EQU 0A000h ; Segment of VGA display memory
- FIRSTMODE EQU grEGA_320x200x16
- MAXMODE EQU grSVGA_1280x1024x16
-
- begcodeseg svga16
-
- ; Globals used by driver
-
- OldBIOSMode db 0 ; Old video mode before graphics
- Old50Lines db 0 ; 1 if old mode was 50 line VGA
- CntDriver dw 0 ; Graphics driver number
- CntMode dw 0 ; Graphics mode number
- CntChipID dw 0 ; Graphics driver chip ID
- CntColors dw gr16Color ; This is a 16 color driver
-
- ; The following information held in the status status area changes depending
- ; on which mode the driver is set up to be used in:
-
- StatusArea:
-
- XRes dw 0 ; Device resolution in x direction - 1
- YRes dw 0 ; Device resolution in y direction - 1
- BytesPerLine dw 0 ; Number of bytes in a line
- PageSize dd 0 ; Graphics page size
-
- MaxPage dw 0 ; Maximum number of video pages
- OriginOffset dw 0 ; Offset of 0,0 into buffer
-
- ; Here we set up a series of tables that can be used to fill in the start of
- ; the status area for each mode supported by this driver, and the address's
- ; of the routines required for each particular driver mode:
-
- ModeTabStart:
-
- ModeEGA_320x200x16 dw 319 ; XRes
- dw 199 ; YRes
- dw 40 ; BytesPerLine
- ModeEGA_640x200x16 dw 639 ; XRes
- dw 199 ; YRes
- dw 80 ; BytesPerLine
- ModeEGA_640x350x16 dw 639 ; XRes
- dw 349 ; YRes
- dw 80 ; BytesPerLine
- ModeVGA_640x400x16 dw 639 ; XRes
- dw 399 ; YRes
- dw 80 ; BytesPerLine
- ModeVGA_640x480x16 dw 639 ; XRes
- dw 479 ; YRes
- dw 80 ; BytesPerLine
- ModeSVGA_800x600: dw 799 ; XRes
- dw 599 ; YRes
- dw 100 ; BytesPerLine
- ModeSVGA_1024x768: dw 1023 ; XRes
- dw 767 ; YRes
- dw 128 ; BytesPerLine
- ModeSVGA_1280x1024: dw 1279 ; XRes
- dw 1023 ; YRes
- dw 160 ; BytesPerLine
- ModeTabSize = ($-ModeSVGA_1280x1024) ; Size of table in bytes
-
- INCLUDE "SV_PORTS.ASM"
- INCLUDE "SV_BANKS.ASM"
- INCLUDE "SV_MODES.ASM"
- INCLUDE "SV_PAGE.ASM"
- INCLUDE "SV_MAXPG.ASM"
-
- ;----------------------------------------------------------------------------
- ; int _initSuperVGA(int driver,int chipID,int mode,int memory)
- ;----------------------------------------------------------------------------
- ; Routine to initialise the bank switching code for the SuperVGA, and setup
- ; internal tables of information about the video mode. If the video mode
- ; is not supported, we return -1.
- ;
- ; The value returned is a status number, where bit 0 represents extended
- ; page flipping is available, bit 1 that separate read/write banks are
- ; available.
- ;----------------------------------------------------------------------------
- procstart __initSuperVGA
-
- ARG driver:WORD, ChipID:WORD, mode:WORD, memory:WORD
-
- enter 0,0
- push si
- push di
-
- ; Save the driver number and chip ID for later
-
- mov ax,[ChipID]
- mov [CntChipID],ax
- mov ax,[driver]
- mov [CntDriver],ax
-
- ; Load the Status area with info for the currently selected mode:
-
- mov ax,[mode]
- mov [CntMode],ax
- cmp ax,MAXMODE ; AX := desired mode
- jg @@Invalid ; invalid if greater than maximum
- cmp ax,FIRSTMODE
- jl @@Invalid ; invalid if less than first mode
- cmp ax,grVGA_640x480x16
- jle @@ValidVGAMode
- cmp ax,grSVGA_800x600x16
- jl @@Invalid ; Mode is invalid
-
- add ax,grVGA_640x480x16 - grSVGA_800x600x16 + 1
- jmp @@LoadValues
-
- @@ValidVGAMode:
- sub ax,FIRSTMODE
-
- @@LoadValues:
- mov cx,ModeTabSize ; Put size of table into cx
- mul cl ; AX := Mode * ModeTabSize
- mov si,ax
- lea si,[ModeTabStart + si]
- push cs
- pop es ; Set up es to point to code seg
- lea di,[StatusArea] ; DI := Start of status area
-
- cld
- rep movs [BYTE es:di],[BYTE es:si]
-
- mov ax,[driver]
- mov bx,[mode]
- call loadSVGAMode ; Load the SuperVGA video mode
- or ax,ax
- jz @@Invalid ; Mode not supported on this adapter!
-
- mov [maxpage],0 ; Clear maxpage variable
- call SetupBanks ; Setup SuperVGA bank switching
- call [InitSVGA] ; Initialise the SuperVGA
- call SetupPaging ; Setup SuperVGA page flipping
- mov ax,0 ; Assume no paging available
- jc @@NoFlip
- mov ax,1 ; Flipping available
-
- @@NoFlip:
- push ax ; Save flag for later
-
- ; Determine the number of pages available for the mode and the video page
- ; size.
-
- xor ebx,ebx
- mov bx,[memory]
- or ax,ax
- jnz @@ExtendedFlip
-
- cmp [mode],grSVGA_800x600x16
- jge @@Done ; Don't calculate for SVGA modes then
- mov bx,256 ; Extended flipping not available
-
- @@ExtendedFlip:
- shl ebx,10 ; EBX := video memory in bytes
- mov ax,[mode]
- call numPages ; Calculate the number of video pages
- dec ax
- mov [MaxPage],ax ; Save maximum page number
- mov [DWORD pageSize],ebx
- mov [WORD bytesPerLine],cx
-
- @@Done:
- pop ax ; AX := extended page flipping flag
- mov bx,[TwoBanks]
- shl bx,1
- or ax,bx ; Set the two banks flag
- jmp @@Exit
-
- @@Invalid:
- mov ax,-1 ; Return failure!
-
- @@Exit:
- pop di
- pop si
- leave
- ret
-
- procend __initSuperVGA
-
- ;----------------------------------------------------------------------------
- ; int _setSuperVGAMode(void);
- ;----------------------------------------------------------------------------
- ; Routine sets the system into the SuperVGA graphics mode setup by the
- ; initSuperVGA routine. Note that this routine remembers if the EGA/VGA
- ; 43/50 line mode was set.
- ;
- ; If the video mode was not correctly set, we return false.
- ;----------------------------------------------------------------------------
- procstart __setSuperVGAMode
-
- push bp ; INT 10h Kills this!!!
- push si ; so save all regs...
- push di
- push ds
-
- mov ah,0Fh ; Get current video mode service
- int 10h
- mov [OldBIOSMode],al ; Save old video mode
- mov [Old50Lines],0 ; Default to non-50 line mode
-
- mov ax,1130h ; AH := INT 10h function number
- ; AL := Get character gen information
- mov bh,00 ; Get contents of INT 1Fh
- xor dl,dl ; Clear dl
- int 10h ; Determine number of lines (in dl)
- cmp dl,49 ; 50 line mode?
- jne @@SetMode ; No, must have been 25 lines
- mov [Old50Lines],1 ; Yes, 50 line mode was on
-
- @@SetMode:
- mov ax,[CntDriver]
- mov bx,[CntMode]
- call loadSVGAMode ; AX,BX := correct values for mode
- int 10h ; Set the video mode
-
- mov ax,40h
- mov es,ax
- xor ax,ax
- cmp [BYTE es:49h],3 ; Mode is still text mode, did not set
- jbe @@Exit
-
- call [InitSVGA] ; Initialise bank switching on SuperVGA's
- mov ax,1 ; Mode was correctly set
-
- @@Exit:
- pop ds
- pop di ; Restore regs
- pop si
- pop bp ; Restore bp (after INT 10 trashes it)
- ret
-
- procend __setSuperVGAMode
-
- ;----------------------------------------------------------------------------
- ; void restoreMode(void)
- ;----------------------------------------------------------------------------
- ; Routine restores the original video mode that was set before graphics mode
- ; was entered.
- ;----------------------------------------------------------------------------
- procstart _restoreMode
-
- push bp ; INT 10h kills bp sometimes
- push si ; Save all regs...
- push di
-
- call [ExitSVGA] ; Uninitialise the SuperVGA
-
- mov ah,0 ; Set video mode service
- mov al,[OldBIOSMode] ; Get old BIOS mode number
- int 10h ; Set the video mode
-
- cmp [Old50Lines],0 ; Was 50 line mode set?
- je @@Exit ; No, don't set it up
-
- ; Load video BIOS 8x8 characters into alphanumeric character generator
-
- mov ax,1112h ; AH := INT 10h function number
- ; AL := 8x8 character set load
- mov bl,0 ; BL := block to load
- int 10h ; load 8x8 characters into RAM
-
- @@Exit:
- pop di ; Restore regs
- pop si
- pop bp ; Restore bp
- ret
-
- procend _restoreMode
-
- ;----------------------------------------------------------------------------
- ; void _getVideoInfo(int *xres,int *yres,int *bytesperline,int *maxpage)
- ;----------------------------------------------------------------------------
- ; Returns information about the currently selected video mode. The video
- ; mode must have been set for this info to be entirely valid.
- ;----------------------------------------------------------------------------
- procstart __getVideoInfo
-
- ARG _xres:DWORD, _yres:DWORD, _bytesperline:DWORD, _maxpage:DWORD
-
- enter 0,0
-
- les bx,[_xres]
- mov ax,[xres]
- mov [es:bx],ax ; Return the x resolution
-
- les bx,[_yres]
- mov ax,[yres]
- mov [es:bx],ax ; Return the y resolution
-
- les bx,[_bytesperline]
- mov ax,[bytesperline]
- mov [es:bx],ax ; Return the bytes per line value
-
- les bx,[_maxpage]
- mov ax,[maxpage]
- mov [es:bx],ax ; Return the maximum page number
-
- leave
- ret
-
- procend __getVideoInfo
-
- ;----------------------------------------------------------------------------
- ; void putPixel(int x,int y,int color)
- ;----------------------------------------------------------------------------
- ; Routine sets the value of a pixel in native VGA graphics modes.
- ;
- ; Entry: x - X coordinate of pixel to draw
- ; y - Y coordinate of pixel to draw
- ; color - Color of pixel to draw
- ;
- ;----------------------------------------------------------------------------
- procstart _putPixel
-
- ARG x:WORD, y:WORD, color:WORD
-
- push bp ; Set up stack frame
- mov bp,sp
-
- ; Compute the pixel's address in video buffer
-
- mov ax,[y]
- mov bx,[x]
- mul [BytesPerLine] ; DX:AX := y * BytesPerLine
-
- mov cl,bl ; CL := low-order byte of x
-
- shr bx,3 ; BX := x/8
- add bx,ax
- adc dx,0 ; DX:BX := y*BytesPerLine + x/8
- add bx,[OriginOffset] ; DX:BX := byte offset in video buffer
- adc dx,[BankOffset]
-
- cmp dl,[BYTE CurBank]
- je @@NoChange
-
- mov ax,dx
- call [NewBank]
-
- @@NoChange:
- mov ax,VGABufferSeg
- mov es,ax ; ES:BX := byte address of pixel
-
- mov ah,1 ; AH := unshifted bit mask
- and cl,7 ; CL := x & 7
- xor cl,7 ; CL := # bits to shift left
-
- ; set Graphics Controller Bit Mask register
-
- shl ah,cl ; AH := bit mask in proper postion
- mov dx,3CEh ; GC address register port
- mov al,8 ; AL := Bit Mask Register number
- out dx,ax
-
- ; set Graphics Controller Mode register
-
- mov ax,0205h ; AL := Mode register number
- ; AH := Write mode 2 (bits 0,1)
- ; Read mode 0 (bit 3)
- out dx,ax
-
- ; set data rotate/Function Select register
-
- mov ax,3 ; AL := Data Rotate/Func select reg #
- out dx,ax
-
- ; set the pixel value
-
- mov al,[es:bx] ; latch one byte from each bit plane
- mov ax,[color] ; AL := pixel value
- mov [es:bx],al ; update all bit planes
-
- ; restore default Graphics Controller registers
-
- mov ax,0FF08h ; default bit mask
- out dx,ax
-
- mov ax,0005 ; default mode register
- out dx,ax
-
- mov ax,0003 ; default function select
- out dx,ax
-
- pop bp
- ret
-
- procend _putPixel
-
- ;----------------------------------------------------------------------------
- ; void clear(void)
- ;----------------------------------------------------------------------------
- ; Routine to clear the screen. Works even if the display contains more than
- ; one bank, so will work for 1024x768 and 1280x1024 video modes.
- ;----------------------------------------------------------------------------
- procstart _clear
-
- push bp ; Set up stack frame
- mov bp,sp
- push si ; Save registers
- push di
-
- ; Setup graphics controller
-
- mov dx,3CEh ; DX := Graphics Controller I/O port
-
- mov ah,0 ; AH := Background color
- xor al,al ; AL := 0 (Set/Reset register number)
- out dx,ax ; load set/reset register
-
- mov ax,0F01h ; AH := 1111b (mask for Enable set/reset)
- ; AL := 1 (enable Set/reset reg number)
- out dx,ax ; load enable set/reset reg
-
- mov ax,[YRes]
- inc ax
- mul [BytesPerLine] ; DX:AX := number of bytes to fill
- mov bx,ax ; BX := bytes in last bank to fill
- mov dh,dl ; DH := number of full banks to fill
-
- mov ax,VGABufferSeg
- mov es,ax
- mov di,[OriginOffset] ; ES:DI -> video buffer
- mov al,[BYTE BankOffset]; AL := starting bank number
- cld ; Moves go up in memory
-
- or dh,dh ; More than one bank to fill?
- jz @@SingleBank ; No, only fill a single bank
-
- ; Fill all of the full 64k banks first
-
- @@OuterLoop:
- call [NewBank]
- mov cx,4000h ; Need to set 4000h double words per bank
- rep stosd
- inc al
- dec dh
- jnz @@OuterLoop
-
- ; Now fill the last partial bank
-
- @@SingleBank:
- call [NewBank]
- mov cx,bx
- shr cx,2 ; CX := number of double words to set
- rep stosd
-
- ; Restore graphics controller
-
- mov dx,3CEh ; DX := Graphics Controller I/O port
- xor ax,ax ; AH := 0, AL := 0
- out dx,ax ; Restore default Set/Reset register
-
- inc ax ; AH := 0, AL := 1
- out dx,ax ; Restore enable Set/Reset register
-
- pop di
- pop si
- pop bp
- ret
-
- procend _clear
-
- ;----------------------------------------------------------------------------
- ; void _copyTest(void)
- ;----------------------------------------------------------------------------
- ; Routine to copy the top half of video memory to the bottom half of
- ; video memory. To ensure that we a moving across a bank boundary in
- ; 16 color modes, we copy the data to the second video page.
- ;----------------------------------------------------------------------------
- procstart __copyTest
-
- push si ; Save registers
- push di
- push ds
-
- mov ax,[YRes]
- inc ax
- shr ax,1 ; AX := (Yres+1) / 2
- mul [BytesPerLine]
- mov cx,ax ; CX := Number of bytes to move
-
- ; Set up graphics controller
-
- mov dx,3CEh ; DX := Graphics Controller address port
- mov ax,0105h ; AH := 1 (read mode 0, write mode 1)
- ; AL := 5 (Mode register number)
- out dx,ax ; Set up mode
-
- mov di,[WORD PageSize] ; ES:DI := offset into destination buffer
- mov al,[BYTE PageSize+2]
- add di,cx
- adc al,0
- call [NewBank] ; Set the read/write bank number
-
- xor si,si ; DS:SI := offset into source buffer
- xor al,al
- call [ReadBank] ; Set the read bank number
-
- mov ax,VGABufferSeg
- mov ds,ax ; DS:SI -> source buffer
- mov es,ax ; ES:DI -> destination buffer
- cld ; Moves go up in memory
-
- rep movsb ; Move all data in bank FAST!
-
- ; Restore default graphics controller state
-
- mov ax,0005h ; default mode register value
- out dx,ax
-
- pop ds
- pop di
- pop si
- ret
-
- procend __copyTest
-
- ;----------------------------------------------------------------------------
- ; void setActivePage(int which)
- ;----------------------------------------------------------------------------
- ; Routine to set the video page for active output.
- ;
- ; Entry: page - Page number of page to use
- ;
- ;----------------------------------------------------------------------------
- procstart _setActivePage
-
- ARG which:WORD
-
- push bp ; Set up stack frame
- mov bp,sp
-
- ; Calculate 18 bit address of page in video memory
-
- xor eax,eax
- mov ax,[which] ; EAX := page number
- mul [PageSize] ; EDX:EAX := result
- mov [OriginOffset],ax ; Save video buffer offset
- shr eax,16
- mov [BankOffset],ax ; Save video bank offset
-
- pop bp
- ret
-
- procend _setActivePage
-
- ;----------------------------------------------------------------------------
- ; void setVisualPage(int which)
- ;----------------------------------------------------------------------------
- ; Routine to set the visible video page.
- ;
- ; Entry: page - Page number of page to use
- ;
- ;----------------------------------------------------------------------------
- procstart _setVisualPage
-
- ARG which:WORD
-
- push bp ; Set up stack frame
- mov bp,sp
- push si
-
- ; Calculate 18 bit address of page in video memory
-
- xor eax,eax
- mov ax,[which] ; EAX := page number
- mul [PageSize] ; EDX:EAX := result
- mov bx,ax ; BX := bottom 16 bits of address
- shr eax,16
- push ax ; Save top 2 bits of address
-
- ; Wait for display enable to be active (active low), to be sure that
- ; both halves of the start address will take place in one frame. We
- ; preload a few values here to save time after the DE has been
- ; detected.
-
- mov cl,0Ch ; CL := Start Address High register
- mov ch,bh ; CH := high byte of new address
- mov bh,bl ; BH := low byte of new address
- mov bl,0Dh ; BL := Start Address Low register
- mov dx,03DAh ; DX := video status port
-
- @@WaitDE:
- in al,dx
- test al,1
- jnz @@WaitDE ; Wait for Display Enable
-
- cli
- pop si ; SI := Bits 16+ for SuperVGA's
- call [NewPage] ; Program the start address
- sti
-
- ; Now wait for the start of the vertical sync, to ensure that the old
- ; page will be invisible before anything is drawn on it.
-
- mov dx,03DAh ; DX := video status port
- @@WaitStartVert:
- in al,dx ; Wait for start of vertical retrace
- test al,8
- jz @@WaitStartVert
-
- @@Exit:
- pop si
- pop bp
- ret
-
- procend _setVisualPage
-
- ;----------------------------------------------------------------------------
- ; void setBank(int bank)
- ;----------------------------------------------------------------------------
- ; Sets the current read and write bank to the specified 64k bank number.
- ;----------------------------------------------------------------------------
- procstart _setBank
-
- ARG bank:WORD
-
- enter 0,0
-
- mov al,[BYTE bank]
- cmp al,[BYTE CurBank]
- je @@NoChange
-
- call [NewBank]
-
- @@NoChange:
- leave
- ret
-
- procend _setBank
-
- ;----------------------------------------------------------------------------
- ; void setReadBank(int bank)
- ;----------------------------------------------------------------------------
- ; Sets the current read bank to the specified 64k bank. If you wish to set
- ; the read and write banks separately, call setBank() first, followed by
- ; setReadBank().
- ;----------------------------------------------------------------------------
- procstart _setReadBank
-
- ARG bank:WORD
-
- enter 0,0
-
- mov al,[BYTE bank]
- call [ReadBank]
-
- leave
- ret
-
- procend _setReadBank
-
- endcodeseg svga16
-
- END
-