Dr. Dobb's is part of the Informa Tech Division of Informa PLC

This site is operated by a business or businesses owned by Informa PLC and all copyright resides with them. Informa PLC's registered office is 5 Howick Place, London SW1P 1WG. Registered in England and Wales. Number 8860726.


Channels ▼
RSS

Web Development

Saving and Restoring VGA Screens


JUL91: SAVING AND RESTORING VGA SCREENS

SAVING AND RESTORING VGA SCREENS

Register programming without pain

Ben Myers

Ben is a founder and partner in Spirit of Performance, a Harvard, Mass. firm that publishes Personal Measure, a package that measures application performance and resource utilization. He also designs and programs custom benchmarks of hardware and software. He can be reached at MCI Mail ID 357-1400.


When IBM announced the PS/2s with Video Gate Array (VGA) controllers, software developers were cautioned to program only to VGA BIOS specifications. Those who heeded IBM's warning were rewarded with painfully slow graphics routines. Today, many VGA cards conform both to IBM's BIOS specification and to the lower-level VGA register specification. This means that neither performance nor standardization need to be sacrificed.

VGA is fundamentally an extension of the older Enhanced Graphics Adapter (EGA) specification. However, VGA's square pixels allow a square to be truly square and circles to be truly round. New BIOS calls are also defined for configuration data, status information, and extra graphics modes. VGA adds an additional write mode for register-level operations, a palette of 256K colors, a 4:3 screen aspect ratio, and improved split-screen and panning capabilities. Finally, in common with the less successful MCGA on the IBM PS/2 Models 25 and 30, VGA offers a 256-color mode, 320 x 200 pixels in size.

In finding out how VGA adapters really work, I turned to Richard Wilton's fine Programmer's Guide to PC & PS/2 Video Systems (see bibliography) and worked out how to fill an entire screen with a single color using repeated STOSB instructions. The result was an honest benchmark of adapter performance whose timings differed by no more than a few percent for the same adapter on an 8-MHz 80286 and a 33-MHz 80386. It was interesting to discover that some brands of adapters left random unfilled dots on the screen when subjected to the high data rate generated by STOSB on the faster PC, apparently due to occasional misses on critical bus timings. This meant I had to write an adapter integrity test that filled the screen with one color and read it all back, to make sure that the color really had gotten into the video adapter memory.

After finishing the adapter integrity test, I realized I had almost everything necessary to save an entire screen and restore it again, so I tinkered some more and came up with Read_VGA_Plane and Write_VGA_Plane (see Listing One, page 79), both of which operate on one plane at a time. Wilton's book provides little help for figuring out how to read individual VGA bit planes, but Bradley Dyck Kliewer's otherwise unremarkable EGA/ VGA, A Programmer's Reference Guide contained some reference information on all the VGA registers, including a good description of the important Read Map Select Register.

Quick Overview of VGA

Saving and subsequently restoring a VGA screen image exploits a small fraction of the registers and capabilities built into the adapter.

For VGA mode 12h (640x480, 16 colors), the memory inside a VGA adapter is organized into four planes of bits (see Figure 1). The VGA buffer begins at address A000:0000 in PC memory and is organized horizontally. That is, the contents of a single byte are displayed horizontally, followed by the next byte, and the next, all on a one-pixel-wide scan line. The last byte of a scan line (pixels 632 - 639, numbering from zero) is followed in memory by the first byte (pixels 0 - 7) of the next scan line. Each single byte in PC VGA memory corresponds to 4 (!) bytes on the VGA card, one in each plane. To allow 16 colors to be displayed from a single plane of memory, VGA registers must be programmed to write into some or all bit planes on the adapter. This allows a single byte of data to be used to manipulate bit values in any of the four planes.

When software wants to write data in a given color, the VGA treats the color number as a set of four binary bits, one for each plane. Plane O is the "blue" plane, plane 1 is "green," and plane 2 is "red." Finally, plane 3 controls the intensity of the bits displayed. Mixing red, green, blue, and intensity data together gives the 16 colors for VGA graphics. For example, the color yellow, value OEh, is derived from an intensity bit, a red bit, and a green bit. The VGA palette registers provide a level of indirection for color. They allow for remapping of the 16 colors into any one of 256 possible hues.

When working at the BIOS level, use interrupt 10h to write text and to set individual pixels in any one of the 16 colors in the current palette. This method works, albeit slowly.

Working at the register level requires "programming" the VGA registers, which is nothing more than putting values there to tell the adapter how to operate on the bit patterns that will be written into PC memory later on. The primitive VGA operations read, write, and update data in the adapter planes. Updates are further subdivided into AND, OR, and XOR that combine a "latched" VGA planar byte with a byte in memory.

Updating data in the VGA adapter planes is more complex than simply writing or reading it. It requires that the data in the adapter planes be latched one byte at a time, updated, and written back. A typical latching operation merely moves data from PC VGA memory to a PC register, for example, mov al, ds[si], where ds = AOOOh, and si points to a byte in VGA memory. The simple step of accessing memory in the PC's VGA buffer area forces the VGA controller to respond by reading data out of its planes into the VGA memory area.

Saving and Restoring Screen Images

Of all the VGA registers, only the Graphics Controller registers and the Sequencer Address registers are used to save and restore a VGA graphic screen. The Graphics Controller registers are accessed through port 03CEh. There are nine of them, numbered from O to 8. To change the value of any one of them, write its index number to port 03CEh, followed by the value to which it will be set. The VGA controller accepts two consecutive bytes in the same OUT instruction, so often no more than three instructions are needed to set up a register. The code fragment in Example 1 programs register 5, the mode register, with a 0 value.

Example 1: Programming register 5

  mov   dx,3CEh   Graphics controller I/O port
  mov   ax,0005h  Register 5, value of zero
  out   dx,ax     Write the value out to register 5

There are five Sequencer Address Registers at port 03C4h. They are accessed just like the Graphics Controller registers. See Table 1 for a summary of the registers and values needed to manage screen images.

Table 1: VGA registers used to save and restore screens

  Port  Index  Bits  Name/Purpose
  ---------------------------------------------------------------------

  03C4               Sequencer Address Registers
          2          Map Mask Register, determines which adapter planes
                        will be affected by subsequent operations
                 0   1 = operate on plane 0
                 1   1 = operate on plane 1
                 2   1 = operate on plane 2
                 3   1 = operate on plane 3
  O3CE               Graphics Controller Registers
          1          Enable Set/Reset Register, chooses planes to be
                        accessed in write mode 0
                0-3  1 in bit position enables use of corresponding
                        memory plane for write mode 0

          3          Data Rotate/Function Select Register, rotates data
                        written by CPU, then selects function for
                        combining CPU data with planar data
                0-2  rotate count
                3-4  function select
                     00 - overwrite with CPU data
                     01 - AND data with latch contents
                     10 - OR data with latch contents
                     11 - XOR data with latch contents
          4          Read Map Select Register, determines which bit plane
                       will be read.  Note that unlike the Enable
                       Set/Reset Register, this is a raw value that
                       designates a SINGLE plane in the range 0 to 3.
          5          Mode Register
                0-1  Write Mode (0, 1, 2, or 3)
                 2   Used for diagnostics
                 3   Read Mode (0 or 1)
                4-5  Control mapping of CPU data to planes
                 6   Controls 256 color mode

The savedemo Program

The GRFSAVE1 unit (Listing Two, page 79) is derived from software built into the package my company developed, with functions we use in place of both Borland and Microsoft's graphics libraries.

GRFSAVE1 uses the same manifest constants as in the QuickPascal MS-Graph unit, but it could rely on the Turbo Pascal BGI constants just as easily. The program savedemo (Listing Three, page 80) fills the screen with circles, saves the contents of the screen, fills the screen with clipped rectangles, then restores the previous screen. In between each visible screen operation, savedemo pauses for up to five seconds so you can see what it has done.

How Read_VGA_Plane Works

The Read_VGA_Plane procedure is by far the simpler of the matched pair of MASM video plane handling routines. It accepts a plane number and byte count from the calling program and fills an externally defined array with the bits from the adapter plane. The plane number, in the range O to 3, corresponds to the number of the bit plane on the VGA adapter. The byte count is simply the total number of bytes in the adapter plane. Since register programming is the same for VGA and EGA graphics modes, varying the byte count allows Read_VGA_Plane to work with any EGA or VGA color mode.

The VGA Graphics Controller I/O port, 03CEh, provides access to a set of registers that determine how the VGA card operates. It is necessary to program only two graphics controller registers to read from a given video plane. The Mode Register (graphics controller register number 5) must be set in read mode O to read bytes from a given individual plane. Then, the Read Map Select Register (register 4) must be set up with the number of the bit plane to be read. A single out instruction will do in either case, feeding a pair of bytes that select the register number and pass the value to be loaded into the register. Once the byte count (CX register) and the array address (ES:DI) have been set up, a repeated byte move (REP MOVSB) reads each byte from the bit plane. If you encounter the VGA bus timing problems described earlier, use a slower byte-at-a-time loop instead. Once the bit plane has been moved, the mode register is reset to its normal default of read mode 1, and the read map select register to its default.

How Write_VGA_Plane Works

Reading and writing VGA adapter planes are not symmetrical operations, and Write_VGA_Plane does more work than its counterpart. It accepts the same calling parameters as Read_VGA_Plane, but the array is on the sending side of a data move, and the video adapter plane is the destination.

Four Graphics Controller I/O registers must be set up, along with the Map Mask Register in the Sequencer register (port 03C4h) group. The Mode Register is again set to 0, for write mode 0. The Enable Set/Reset Register (graphics register 1) must contain a O mask value to enable all bit planes. The Data Rotate/ Function Select Register (graphics register 3) must be initialized to replace bits in the selected bit plane with data from memory. Then the Bit Mask Register (graphics register 8) is filled with bits to allow all bits in memory to replace the corresponding bits in the bit plane. Finally, the Map Mask Register (sequencer I/O register 2) must contain a bit that tells which plane to write. Bit 0 indicates plane 0, bit 1 is for plane 1, and so on.

With the adapter registers properly initialized, Write_VGA_Plane initializes CX, ES, and DI for yet another repeated move of data from the saved array to adapter memory in the PC. Since all of the necessary VGA registers have been programmed, the VGA adapter properly disposes of each byte of data within the proper bit plane. Write_VGA_Plane then resets the register sit used back to the normal default values.

A Monochrome Bonus

The GRFSAVE1 unit consists of six functions and procedures. HeapFunc simply overrides the runtime error that results when the requested amount of heap space is not available to the calling program after a GetMem call. Init_Screen_Save is a simple bridge between the calling program and the unit. It takes the plane size and number of planes for the current graphics mode from the calling program. These calculations could also be done more tidily within the GRFSAVE1 unit.

The Save_Screen function saves the entire screen on behalf of the calling program and returns a count of the number of planes saved. If the plane count is 0, this means that no planes were saved due to lack of heap space. The calling program can then take appropriate action. Restore_Screen restores the complete screen image only if it has been saved completely by Save_Screen. Saving and restoring a monochrome graphics screen image is much less intricate than operating on a multiplanar color screen. This can be accomplished without any register-level programming. GRFSAVE1 provides a bonus in that it also handles popular monochrome graphics formats, such as CGA monochrome, EGA monochrome, VGA monochrome, and Hercules graphics mode.

savedemo does little except generate a pair of VGA graphic images to be handled with the screen save and restore operations. But, it lets you see Save_Screen and Restore_Screen do the job. Presently, savedemo does a slow fade from the image being replaced to the image being restored, because Restore_Screen replaces one video adapter plane at a time. To restore with an overall top to bottom effect, it would be necessary to redesign the logic of Restore_Screen to operate on each full scan line in sequence, restoring each of its four planes.

What Next?

You can readily modify the procedures here to allow calling by C programs. Just adjust the stack frame handling to handle the C calling convention.

The Super VGA modes (800 x 600 pixels) built into most manufacturers' VGA cards work much like VGA except that more bits of data must be saved. For 800 x 600 screens, each plane occupies 60,000 bytes of data, or 240,000 bytes total. The 1024 x 768 resolution beyond Super VGA is implemented inconsistently among various VGA cards, but a graphic screen requires 98,204 bytes to save each bit plane! With this much data, or even the mere 28,808 bytes-per-bit plane for plain vanilla VGA, one must consider how to conserve memory. One possibility is to compress data prior to saving the bit plane and reconstitute it before restoring it.

Another tactic, which may or may not be combined with image compression, is to save a screen image to expanded memory if it is available. Alternatively, you can copy a VGA plane to a file and then read it back when restoring the image. Or add the logic to save and restore only a part of the screen. This comes in handy when doing drop-down or pop-up menus over a graphic image. Partial screen saves are generally much quicker than regenerating that part of the screen image from scratch.

Microsoft's QuickPascal provides the _GetImage and _PutImage procedures to save and restore a screen image. Borland's BGI offers the similarly named GetImage and PutImage. Even if you end up using those library functions instead of the ones in this article, you can now see that there is nothing magical about programming VGA registers.

Bibliography

Kliewer, Bradley Dyck. EGA/VGA, A Programmer's Reference Guide. New York McGraw-Hill, 1988.

Personal System/2 and Personal Computer BIOS Interface Technical Reference (IBM Publication 84X1514). International Business Machines Corporation 1987 (since superceded by another publication).

Wilton, Richard. Programmer's Guide to PC and PS/2 Video Systems. Redmond, Wash.: Microsoft Press, 1987.


_SAVING AND RESTORING VGA SCREENS_
by Ben Myers


[LISTING ONE]
<a name="018a_000f">

  PAGE 80,132
  TITLE EGA/VGA screen save/restore  (Turbo Pascal 4.0+ or Quick Pascal 1.0)
; GRFSAVE.ASM -
;  (C)Copyright 1989-1990 Spirit of Performance, Inc.
;  All rights reserved. Unauthorized use or copying prohibited by law.

CODE   SEGMENT WORD PUBLIC
       ASSUME  CS:CODE
       PUBLIC  Write_VGA_Plane ; Write video plane from caller's memory.
       PUBLIC  Read_VGA_Plane  ; Read video plane, move it to caller's memory.

; procedure Write_VGA_Plane (Plane, Count : word; var Plane_Array );
; procedure Read_VGA_Plane  (Plane, Count : word; var Plane_Array );
; Parameters:  Plane       - Graphics plane number to move ( range 0-3 )
;          Count       - Byte count to move
;              Plane_Array - Array for video plane values

Plane_Array  EQU  DWORD PTR [bp+06h]
Count         EQU  WORD  PTR [bp+0Ah]
Plane         EQU  WORD  PTR [bp+0Ch]

Write_VGA_Plane PROC FAR
       push  bp                 ; Save Turbo's BP
       mov   bp,sp              ; Set up stack frame
       mov   bx,ds              ; Save Turbo's DS
       mov   di,0A000h          ; EGA/VGA buffer segment:offset, A000:0000
       mov   es,di
       xor   di,di              ; ES:DI is start of video buffer
       mov   dx,3CEh           ; DX = Graphics Controller I/O Port
       mov   ax,0005h           ; AH = 00h (Read mode 0, write mode 0)
            ; AL = Mode register number (5)
       out   dx,ax              ; load Mode register
       mov   ax,0001h           ; AH = 00h (mask for Enable Set/Reset),
            ; also the default for modes 12h and 10h
            ; AL = Enable Set/Reset register number (1)
       out   dx,ax              ; load Enable Set/Reset register
       mov   ax,0003h           ; AH = Replace bit planes with memory,
            ; no bit rotation, also the default
            ; AL = Data Rotate/Function Select register
            ; number (3)
       out   dx,ax              ; load Data Rotate/Function Select register
            ; AL = Bit Mask Register (8)
       mov   ax,0FF08h          ; AH = bit mask
       out   dx,ax              ; Set bit mask register for all bits
       mov   dx,3C4h           ; DX = Sequencer I/O Port
       mov   cx,ss:Plane        ; Get Plane number from caller
       and   cl,03h             ; Force it to range 0 to 3
       mov   ah,1               ; Set up AH with bit number of plane to restore
       shl   ah,cl              ; where bit 0 = plane 0, etc.
       mov   al,02h             ; AL = Map Mask Register number (2)
       out   dx,ax              ; load Map Mask register with plane number
       mov   cx,ss:Count        ; byte count to move (size of plane for
            ; EGA/VGA card in current mode )
       lds   si,ss:Plane_Array  ; Addr of array to restore plane values from
       rep movsb                ; Move the data
; Or replace the above instruction by the slower but equivalent loop construct
; below in the event that your VGA card doesn't respond properly.
@@:
;       lodsb                    ; Get a byte from save area plane
;       stosb                    ; Form a byte for current plane
;       loop  @B                 ; Do next byte, until all have been done.

; Now reset the VGA registers used back to the defaults expected.
       mov   dx,3CEh           ; DX = Graphics Controller I/O Port
       mov   ax,0001           ; AH = 0 (default Enable Set/Reset Value)
            ; AL = Enable Set/Reset register number (1)
       out   dx,ax              ; restore default Enable Set/Reset register
       mov   dx,3C4h           ; DX = Sequencer I/O port
            ; AH = all planes enabled
       mov   ax,0F02h           ; AL = Map Mask Register number (2)
       out   dx,ax              ; restore Map Mask register to do all planes.
       mov   ds,bx              ; Restore Turbo's DS
       pop   bp                 ; Restore Turbo's BP
       ret   8                  ; Remove params & return to call
Write_VGA_Plane ENDP

; procedure Read_VGA_Plane (Plane, Count : word; var Plane_Array );

Read_VGA_Plane PROC FAR
       push  bp                 ; Save Turbo's BP
       mov   bp,sp              ; Set up stack frame
       mov   bx,ds              ; Save Turbo's DS
       mov   si,0A000h          ; EGA/VGA buffer segment:offset, A000:0000
       mov   ds,si
       xor   si,si              ; DS:SI is start of video buffer
       mov   dx,3CEh           ; DX = Graphics Controller I/O Port
       mov   ax,0005h           ; AH = 00h (Read mode 0, write mode 0)
            ; AL = 5 (Mode register number)
       out   dx,ax              ; load Mode register
;;     int   3         ; Enable breakpoint for debugging.
       mov   ax,ss:Plane        ; Get Plane number
       mov   ah,al              ; AH = color plane to get
       mov   al,04h           ; AL = Read Map Select Register number (4)
       out   dx,ax           ; load Read Map Select register
       mov   cx,ss:Count        ; byte count to move (size of plane for
            ; EGA/VGA card in current mode )
       les   di,ss:Plane_Array  ; Address of array to store plane values.
       rep movsb                ; Move the data from video buffer to save area
; Or replace the above instruction by the slower but equivalent loop construct
; below in the event that your VGA card doesn't respond properly.
@@:
;       lodsb                    ; Get a byte from plane of video buffer
;       stosb                    ; Save it.
;       loop  @B                 ; Do next byte, until all have been done.

; Now reset the VGA registers used back to the defaults expected.
       mov   ax,1005h           ; AH = 10h, defaults for modes 12h and 10h
            ; AL = Mode register number (5)
       out   dx,ax              ; restore default mode register
       mov   ax,0004h           ; AL = Read Map Select Register number (4)
       out   dx,ax           ; load Read Map Select register default value
       mov   ds,bx              ; Restore Turbo's DS
       pop   bp                 ; Restore Turbo's BP
       ret   8                  ; Remove params & return to call
Read_VGA_Plane ENDP
CODE   ENDS
       END




<a name="018a_0010">
<a name="018a_0011">
[LISTING TWO]
<a name="018a_0011">

{
 GRFSAVE1.PAS - Unit to save and restore graphics screens
 Version 1.40 (03-19-90)   --depends on MSgraph Unit for
              manifest constants indentifying graphics modes.
 procedure Write_VGA_Plane (Plane, Count : word; var Plane_Array );
 procedure Read_VGA_Plane  (Plane, Count : word; var Plane_Array );
 Parameters:  Plane       - Graphics plane number to move ( range 0-3 )
         Count       - Byte count to move
         Plane_Array - Array for video plane values
 (C)Copyright 1989-1990 Spirit of Performance, Inc.
 All rights reserved. Unauthorized use or copying prohibited by law.
}

{$R-,S-,I-,D+,F+,V-,B-,N-,L+ }

UNIT GRFSAVE;

INTERFACE
USES MsGraph;

const
  Max_Planes = 4;

procedure Init_Screen_Save ( Plane_Size : longint; Number_Of_Planes : word );
Function  HeapFunc ( Size: word ) : integer;
function  Save_Screen ( Mode : integer ) : integer;
procedure Restore_Screen;
procedure Write_VGA_Plane (Plane, Count : word; var Plane_Array );
procedure Read_VGA_Plane  (Plane, Count : word; var Plane_Array );

IMPLEMENTATION

var
{ Video plane size and number of planes in bytes }
{ ****** When video plane size gets above 64K, need to change below }
    Video_Plane_Size    : word;  { in bytes }
    Number_GPlanes      : word;
    Plane_Counter       : word;
    Plane_Ptrs          : array [1..Max_Planes] of pointer;
    Planes_Saved        : integer;
    Saved_Graphics_Mode : integer;
    Monochrome_Buffer   : ARRAY[ 0..$7FFF ] OF byte ABSOLUTE $B800:$0000;
    VGA_Buffer          : ARRAY[ 0..$7FFF ] OF byte ABSOLUTE $A000:$0000;

procedure Init_Screen_Save;
  { Initialize unit with parameters }
  begin
    Video_Plane_Size := Plane_Size;
    Number_GPlanes := Number_Of_Planes;
  end;

Function HeapFunc;
{ Simple heap error function overrides run time error to avoid program
  abort.  }
begin
  HeapFunc := 1;  { return an error indicator to caller }
end;

{$L d:\tpsource\GRFSAVE.obj }
procedure Write_VGA_Plane; external;
procedure Read_VGA_Plane;  external;

function Save_Screen;
{ Saves graphics planes for current graphics mode.
  Returns number of planes saved, in case caller cares.
}

  begin
    Saved_Graphics_Mode := Mode;
    Planes_Saved := 0;
    HeapError := @HeapFunc;
    case Saved_Graphics_Mode of
      _HRes16Color,    { 640 x 200, 16 color }
      _EResColor  ,    { 640 x 350, 4 or 16 color }
      _VRes16Color:    { 640 x 480, 16 color }
      for Plane_Counter := 1 to Number_GPlanes do
   begin
     { Get memory to save a plane }
     GetMem( Plane_Ptrs[Plane_Counter], Video_Plane_Size);
     if Plane_Ptrs[Plane_Counter] <> nil then
       { Move the plane if GetMem succeeded }
       begin
         Read_VGA_Plane (Plane_Counter-1, Video_Plane_Size,
               Plane_Ptrs[Plane_Counter]^ );
         inc ( Planes_Saved );
       end;
   end;
      _HResBW  ,    { 640 x 200, BW }
      _HercMono:    { 720 x 348, BW for HGC }
   begin
     GetMem( Plane_Ptrs[1], Video_Plane_Size);
     if Plane_Ptrs[Plane_Counter] <> nil then
       begin
         Move ( Monochrome_Buffer, Plane_Ptrs[1]^, Video_Plane_Size );
         Planes_Saved := 1;
       end;
   end;
      _EResNoColor,    { 640 x 350, BW }
      _VRes2Color :    { 640 x 480, BW }
   begin
     GetMem( Plane_Ptrs[1], Video_Plane_Size);
     if Plane_Ptrs[Plane_Counter] <> nil then
       begin
         Move ( VGA_Buffer, Plane_Ptrs[1]^, Video_Plane_Size );
         Planes_Saved := 1;
       end;
   end;
    end; {case Saved_Graphics_Mode}
    if Planes_Saved <> Number_GPlanes then
      { Unsuccessful, so reset count of planes saved }
      Planes_Saved := 0;
    Save_Screen := Planes_Saved;
  end;

procedure Restore_Screen;
  begin
    if Planes_Saved <> 0 then
      case Saved_Graphics_Mode of
   _HRes16Color,    { 640 x 200, 16 color }
   _EResColor  ,    { 640 x 350, 4 or 16 color }
   _VRes16Color:    { 640 x 480, 16 color }
     for Plane_Counter := 1 to Number_GPlanes do
     if Plane_Ptrs[Plane_Counter] <> nil then
       Write_VGA_Plane (Plane_Counter-1, Video_Plane_Size,
             Plane_Ptrs[Plane_Counter]^ );
   _HResBW  ,    { 640 x 200, BW }
   _HercMono:    { 720 x 348, BW for HGC }
     Move ( Plane_Ptrs[1]^, Monochrome_Buffer, Video_Plane_Size );
   _EResNoColor,    { 640 x 350, BW }
   _VRes2Color :    { 640 x 480, BW }
     Move ( Plane_Ptrs[1]^, VGA_Buffer, Video_Plane_Size );
      end; {case Saved_Graphics_Mode}
  end;
END.





<a name="018a_0012">
<a name="018a_0013">
[LISTING THREE]
<a name="018a_0013">

PROGRAM savedemo;
{ savedemo.PAS - Demonstrate EGA/VGA graphics screen save/restore
  Version 1.00, 19 Mar 1990
  Uses for Microsoft Graphics Interface and selected MASM functions.
  (c)Copyright 1989-1990 Spirit of Performance, Inc.
}

USES
    DOS, MSGraph, Crt, GrfSave1;
type
  TimeRec = record
    Hour          : word;
    Minute        : word;
    Second        : word;
    FracSec       : word;
    Floating_Time : real;
end;

var
  Start_Time : TimeRec;
  Stop_Time  : TimeRec;

Function Elapsed_Time ( Stop_Time, Start_Time : TimeRec ) : real;

const
  R3600 : real = 3600.0;
  R60   : real = 60.0;
  R100  : real = 100.0;

begin   { Elapsed_Time }
  with Start_Time do
    begin
      Floating_Time := (Hour * R3600) + (Minute * R60) + Second
        + (FracSec / R100);
    end;
  if Stop_Time.Hour < Start_Time.Hour then inc(Stop_Time.Hour, 24);
  with Stop_Time do
    begin
      Floating_Time := (Hour * R3600) + (Minute * R60) + Second
        + (FracSec / R100);
    end;
  Elapsed_Time := Stop_Time.Floating_Time - Start_Time.Floating_Time;
end;    { Elapsed_Time }

TYPE
    ViewPortType = record
    x1, y1, x2, y2 : word;
    end;
VAR
    errorcode       : Integer;
    x,y             : Integer;
    maxx, maxy      : Integer; { Maximum addressable pixels }
    c               : Char;
    vc                : _VideoConfig;
    CurrentView     : ViewPortType;
    lCount          : longint;
    OldExitProc     : Pointer;  { Saves exit procedure address }
    Plane_Count     : integer;
var
    Video_Plane_Size : longint;
    Number_GPlanes   : word;
CONST
    Version_ID     : string = ( 'Version 1.00, 19 Mar 1990' );
    Patterns       : Array [0..11] of _FillMask =
    (
     (0,0,0,0,0,0,0,0),
     ($FF,$FF,$FF,$FF,$FF,$FF,$FF,$FF),
     ($FF, 0, $FF, 0, $FF, 0, $FF, 0),
     ($44, $88, $11, $22, $44, $88, $11, $22),
     ($77, $EE, $DD, $BB, $77, $EE, $DD, $BB),
     ($77, $BB, $DD, $EE, $77, $BB, $DD, $EE),
     ($88, $44, $22, $11, $88, $44, $22, $11),
     ($11, $AA, $44, $AA, $11, $AA, $44, $AA),
     ($55, $AA, $55, $AA, $55, $AA, $55, $AA),
     ($F0, $0F, $F0, $0F, $F0, $0F, $F0, $0F),
     (1, 0, 0, 0, 1, 0, 0, 0),
     (5, 0, 5, 0, 5, 0, 5, 0));

  CleanUp_Reqd : Boolean = TRUE;

{$F+}
procedure MyExitProc;
{ Procedure to clean up on early program termination }
begin
  ExitProc := OldExitProc; { Restore exit procedure address }
  if CleanUp_Reqd then
  begin    { Restore original video mode. }
    errorcode := _SetVideoMode( _DefaultMode );
  end;
end; { MyExitProc }
{$F-}

Procedure GetViewSettings (var ReqView : ViewPortType);
begin
    ReqView := CurrentView;
end;

Procedure SetView (xa, ya, xb, yb : word);
begin
  _SetViewPort(xa, ya, xb, yb);
  _SetClipRgn (xa, ya, xb, yb);
  with CurrentView do
    begin
      x1 := xa;  y1 := ya;
      x2 := xb;  y2 := yb;
    end;
end;

procedure FullPort;
{ Set the view port to the entire screen }
begin
  SetView(0, 0, maxx, maxy);
end; { FullPort }

procedure MainWindow(Header : string);

{ Make a default window and view port for demos }
begin
  _SetTextColor(vc.numcolors-1);           { Reset the colors }
  _SetBkColor(0);
  _SetColor(vc.numcolors-1);
  _ClearScreen(_GClearScreen);             { Clear the screen }
  FullPort;                                { Full screen view port }
  _SetTextPosition( 1, (vc.NumTextCols - length(Header)) div 2);
  _OutText(Header);        { Draw the header text }
  { Move the edges in to leave room for text at top and bottom }
  SetView(0, vc.NumYPixels div vc.NumTextRows + 1 , maxx,
          maxy-(vc.NumYPixels div vc.NumTextRows)-1);
end; { MainWindow }

procedure StatusLine(Msg : string);
{ Display a status line at the bottom of the screen }
begin
  FullPort;
  _SetLineStyle($FFFF);
  _SetFillMask(Patterns[0]);
  _SetColor(0);                   { Set the drawing color to black }
  _Rectangle(_GFillInterior,
      0, vc.NumYPixels-(vc.NumYPixels div vc.NumTextRows+1),
      maxx, maxy);     { Erase old status line }
  _SetTextPosition( vc.NumTextRows,
         (vc.NumTextCols - length(Msg)) div 2);
  _SetTextColor(vc.numcolors-1);  { Set the color for header }
  _SetBkColor(0);
  _OutText(Msg);        { Write the status message }
  { Go back to the main window }
   SetView(0, vc.NumYPixels div vc.NumTextRows +1 , vc.NumXPixels,
         vc.NumYPixels-(vc.NumYPixels div vc.NumTextRows+1));
  _SetTextPosition( 1, 1 );
end; { StatusLine }

procedure WaitToGo; { Wait for user to abort program or continue }
const
  Esc = #27;
var
  Ch : char;
begin
  StatusLine('Esc aborts or press a key...');
  with Start_Time do GetTime ( Hour, Minute, Second, FracSec );
  repeat
  with Stop_Time do GetTime ( Hour, Minute, Second, FracSec );
  { Wait for keypress no more then 5 seconds, then go on without it }
  until KeyPressed or (Elapsed_Time ( Stop_Time, Start_Time ) > 5.0);
  if Keypressed then
  begin
    Ch := ReadKey;
    if Ch = #0 then Ch := readkey;      { trap function keys }
    if Ch = Esc then
      Halt(0);                           { terminate program }
  end;
end; { WaitToGo }

procedure DrawRectangles;
{ Draw rectangles on the screen }
var
  MaxSize : word;
  XCenter, YCenter : word;
  ViewInfo  : ViewPortType;
  YMax, XMax : word;
  jCount : word;

begin  { DrawRectangles }
  MainWindow('Draw Rectangles');
  StatusLine('');
  GetViewSettings(ViewInfo);
  with ViewInfo do
  begin
    XMax := (x2-x1-1);
    YMax := (y2-y1-1);
  end;
  MaxSize := XMax shr 1;
  XCenter := XMax shr 1;
  YCenter := YMax shr 1;
  for lCount := 1 to MaxSize do
  begin
    _SetColor(lCount mod vc.numcolors);
    _Rectangle(_GBorder, XCenter+lCount, YCenter+lCount,
          XCenter-LCount, YCenter-LCount);
  end;
  WaitToGo;
end; { DrawRectangles }

procedure DrawCircles;
{ Draw concentric circles on the screen }
var
  MaxRadius : word;
  XCenter, YCenter : word;
  ViewInfo  : ViewPortType;
  YMax, XMax : word;

begin  { DrawCircles }
  MainWindow('Draw Circles');
  StatusLine('');
  GetViewSettings(ViewInfo);
  with ViewInfo do
  begin
    XMax := (x2-x1-1);
    YMax := (y2-y1-1);
  end;
  MaxRadius := XMax shr 1;
  XCenter := XMax shr 1;
  YCenter := YMax shr 1;
  for lCount := 1 to MaxRadius do
  begin
    _SetColor(lCount mod vc.numcolors);
    _Ellipse(_GBorder, XCenter + lCount, YCenter + lCount,
             XCenter - lCount, YCenter - lCount);
  end;
  WaitToGo;
end; { DrawCircles }

BEGIN
    OldExitProc := ExitProc;    { save previous exit proc }
    ExitProc := @MyExitProc;    { insert our exit proc in chain }
    _GetVideoConfig( vc );
    DirectVideo := FALSE;   { No direct writes allowed in graphics modes }

    { Set graphics mode with highest resolution. }
    if (_SetVideoMode( _MaxResMode) = 0) then
   Halt( 1 );
    _GetVideoConfig( vc );
    if vc.mode <> _HercMono then
      begin
   Video_Plane_Size := vc.numxpixels div 8;
   Video_Plane_Size := Video_Plane_Size * vc.numypixels;
      end
    else
      Video_Plane_Size := 32768;
    if vc.numcolors = 2 then
      Number_GPlanes := 1   { B&W modes have 1 plane only }
    else
      Number_GPlanes := 4;  { Assume that color modes have 4 planes }
    Init_Screen_Save (Video_Plane_Size, Number_GPlanes);

    _SetColor( vc.numcolors-1 );
    DrawRectangles;
    Plane_Count := Save_Screen (vc.mode); { Save the first screen }
    DrawCircles;
    Restore_Screen;                       { Restore the rectangles }
    WaitToGo;                             { Wait before terminating }

    { Restore original video mode. }
    errorcode := _SetVideoMode( _DefaultMode );
    CleanUp_Reqd := FALSE;
END.


Copyright © 1991, Dr. Dobb's Journal


Related Reading


More Insights






Currently we allow the following HTML tags in comments:

Single tags

These tags can be used alone and don't need an ending tag.

<br> Defines a single line break

<hr> Defines a horizontal line

Matching tags

These require an ending tag - e.g. <i>italic text</i>

<a> Defines an anchor

<b> Defines bold text

<big> Defines big text

<blockquote> Defines a long quotation

<caption> Defines a table caption

<cite> Defines a citation

<code> Defines computer code text

<em> Defines emphasized text

<fieldset> Defines a border around elements in a form

<h1> This is heading 1

<h2> This is heading 2

<h3> This is heading 3

<h4> This is heading 4

<h5> This is heading 5

<h6> This is heading 6

<i> Defines italic text

<p> Defines a paragraph

<pre> Defines preformatted text

<q> Defines a short quotation

<samp> Defines sample computer code text

<small> Defines small text

<span> Defines a section in a document

<s> Defines strikethrough text

<strike> Defines strikethrough text

<strong> Defines strong text

<sub> Defines subscripted text

<sup> Defines superscripted text

<u> Defines underlined text

Dr. Dobb's encourages readers to engage in spirited, healthy debate, including taking us to task. However, Dr. Dobb's moderates all comments posted to our site, and reserves the right to modify or remove any content that it determines to be derogatory, offensive, inflammatory, vulgar, irrelevant/off-topic, racist or obvious marketing or spam. Dr. Dobb's further reserves the right to disable the profile of any commenter participating in said activities.

 
Disqus Tips To upload an avatar photo, first complete your Disqus profile. | View the list of supported HTML tags you can use to style comments. | Please read our commenting policy.