Basic EGA/VGA Graphics in Protected OS/2 Using VIO (Complete) (59136)



The information in this article applies to:

  • Microsoft BASIC Compiler for MS-DOS and OS/2 6.0
  • Microsoft BASIC Compiler for MS-DOS and OS/2 6.0b
  • Microsoft Basic Professional Development System (PDS) for MS-DOS and MS OS/2 7.0
  • Microsoft Basic Professional Development System (PDS) for MS-DOS and MS OS/2 7.1

This article was previously published under Q59136

SUMMARY

It is possible to do EGA and VGA graphics in OS/2 protected mode using VIO calls for the graphics. This is done by getting the physical video buffer and modifying it (with POKE or BLOAD). The code example below provides several common graphics routines using VIO calls.

MORE INFORMATION

Basic's graphics statements (SCREEN, PSET, LINE, etc.) do not support EGA or VGA high resolution graphics modes in OS/2 protected mode. This is because Basic writes directly to the hardware for EGA and VGA graphics. Basic directly supports CGA graphics (SCREEN modes 1 and 2) in OS/2 protected mode.

For better graphics control than is provided by the program below, OS/2 Presentation Manager (PM) provides a wide range of graphics functions in the GPI (Graphics Programming Interface) calls. For information on how to program for OS/2 PM using Basic, contact Microsoft Technical Support and ask for the application note "Basic OS/2 Presentation Manager Toolkit Supplement."

Code Example

The following code example provides several different graphics routines for EGA and VGA graphics under OS/2 protected mode. Color is supported only for mode 13 (256 colors). This is because EGA color requires modifying the hardware registers. To do this, a program must have an IOPL segment.

The following are the compile (BC) and LINK commands for the program:
   BC /o/AH/Lp os2graph;
   LINK os2graph;

'This program contains routines that allow high-resolution
'(EGA/VGA) graphics to be used in OS/2 protected mode in the
'full screen groups. These routines manipulate the physical
'screen buffer. This requires that the screen group be in the
'foreground and locked during any drawing.
'
'Color is supported in mode 13 (320 x 200, 256 colors), but EGA
'color requires manipulating hardware registers. To do this,
'an IOPL segment is required. With some versions of the OS/2
'SDK, the example program, MANDEL.C, illustrates register-based
'programming for EGA modes. In modes other than 13, the color
'parameter is a simple Boolean for setting the pixel on or off.
'
'NOTE: Text output is not supported with these routines.
'      Input works but is not echoed.
'
'The following is a brief summary of the important routines:
'
'     VioScreen   Set the screen mode (EGA & VGA only)
'     VioCLS      Clear graphics screen
'     VioPSET     Set pixel
'     VioLine     Draw line
'     VioBox      Fill box
'     VioBSAVE    BSAVE graphics screen
'     VioBLOAD    BLOAD graphics screen
'     DrawCircle  Draw circle outline
'     FillCircle  Fill circle
'
'NOTE: The above routines use the global variables in COMMON.
'
'NOTE: These routines cannot be used in a text window.

DEFINT A-Z

'************ Type definitions ***************

TYPE PhysBufData
     bufstart AS LONG        'Starting address
     buflength AS LONG       'Length of buffer
     selector1 AS INTEGER    'First selector (segment)
     selector2 AS INTEGER    'Second   "        "
END TYPE

TYPE VIOMODEINFO
     cb AS INTEGER           'Length of mode info
     fbType AS STRING * 1    'type (graphics/text,color/mono)
     colors  AS STRING * 1   '# of colors (2,4,16,256)
     col AS INTEGER          'Text resolution
     row AS INTEGER
     hres AS INTEGER         'Graphics resolution
     vres AS INTEGER
END TYPE

'************* External VIO routines (in OS2.LIB) ***************

DECLARE FUNCTION VioSetMode (_
   SEG vmi AS VIOMODEINFO,_
   BYVAL hvio AS INTEGER)

DECLARE FUNCTION VioGetPhysBuf (_
   SEG pbd AS PhysBufData,_
   BYVAL vh AS INTEGER)

DECLARE FUNCTION VioScrLock (_
   BYVAL waitlock AS INTEGER,_
   SEG status AS INTEGER,_
   BYVAL hvio AS INTEGER)

DECLARE FUNCTION VioScrUnLock (_
   BYVAL hvio AS INTEGER)

'***************** Internal utility functions ****************

DECLARE FUNCTION Aspect# ()
DECLARE FUNCTION FollowCircle# (r%, iy%)

'***** Global variables for mode information and buffer data
COMMON SHARED /VioState/ vmi   AS VIOMODEINFO,_
                         pbd   AS PhysBufData,_
                         vmode AS INTEGER

'***** Module code to show simple graphics demo.

   INPUT "Screen mode:  ", mode%    'Prompt user for mode/color
   INPUT "Color to use: ", clr%

   CALL VioScreen(mode%)            'Set screen mode
   CALL VioCLS                      'Clear graphics screen

   CALL VioBox(1,1,10,10,clr%)      'Draw box in specified color
   CALL DrawCircle(100,100,50,clr%) 'Draw circle
   CALL FillCircle(150,150,30,clr%) 'Fill circle

   FOR i%=0 to 255
      CALL VioLine(i%+1,49,i%+25,25,i%)   'Show palette (13 only)
   NEXT

   nx = vmi.hres / 2 : ny = vmi.vres / 2  'Initialize points for loop
   WHILE nx<>0                            'Loop until new x is 0
     CALL VioLine(ox,oy,nx,ny,c)          'Line from old pt to new pt
     ox = nx : oy = ny                    'Old pt = new pt

     'NOTE: Text output not shown and input is not echoed.

     INPUT "X:",nx                        'Input x (invisible)
     INPUT "Y:",ny                        'Input y (invisible)
     INPUT "C:",c                         'Input color (invisible)
   WEND
END

'VioScreen sets the OS/2 full-screen screen group into the
'desired mode. The modes correspond to the standard MS-DOS
'EGA and VGA graphics modes available in Basic.
'
'NOTE: The mode must be set before any of the graphics routines
'      below are executed.
'
'ALSO NOTE: CGA graphics (SCREEN 1 and 2) are supported directly
'           with Basic's standard graphics statements so are not
'           supported with VioScreen and other routines below.
'
'ALSO NOTE: Hercules graphics are not supported.
DEFINT A-Z
SUB VioScreen(mode%)

  vmode = mode%                 'Set global vmode

  vmi.cb       = LEN(vmi)       'Set default values (most common)
  vmi.fbType   = CHR$(3)        'Display mode type  -> graphics+color
  vmi.colors   = CHR$(4)        'Displayable colors -> 16
  vmi.col      = 80             'Text resolution
  vmi.row      = 25
  vmi.hres     = 640            'Graphics resolution
  vmi.vres     = 200
  pbd.bufstart = &HA0000        'Physical address of video buffer
  denom        = 8              'denominator for buflength (pixels/byte)

  SELECT CASE vmode             'Set differences from defaults
     CASE 7
        vmi.col       = 40
        vmi.hres      = 320
     CASE 8                     'No differences for mode 8
     CASE 9
        vmi.row       = 43
        vmi.vres      = 350
     CASE 10
        vmi.colors    = CHR$(0) 'Mono mode
        vmi.fbtype    = CHR$(2) 'Graphics, no color
        vmi.row       = 43
        vmi.vres      = 350
     CASE 11
        vmi.colors    = CHR$(1) '2 colors
        vmi.row       = 60
        vmi.vres      = 480
     CASE 12
        vmi.row       = 60
        vmi.vres      = 480
     CASE 13
        vmi.colors    = CHR$(8) '256 colors
        vmi.col       = 40
        vmi.hres      = 320
        denom         = 1       'one pixel per byte
     CASE ELSE
        PRINT "Illegal VIO Mode! Program Terminated."
        END                     'End program if illegal mode
  END SELECT

  'Compute buffer length -> horiz * vert / pixels per byte
  pbd.buflength = 1& * vmi.hres * vmi.vres \ denom

  b = VioSetMode(vmi,0)
END SUB

'VioCLS clears graphics screen.
SUB VioCLS
   IF vmode = 0 THEN EXIT SUB               'No graphics mode selected
   b = VioScrLock(1, status, 0)             'Lock screen
      IF VioGetPhysBuf(pbd, 0) = 0 THEN     'Get buffer
          DEF SEG = pbd.selector1           'Set screen seg
          FOR index& = 0 TO pbd.buflength-1
             POKE index&, 0                 'Set all bytes to 0
          NEXT index&
          DEF SEG                           'Set seg back
      END IF
   b = VioScrUnLock(0)                      'Unlock screen
END SUB

'VioPSET sets the specified pixel to given color
'
'NOTE: Mode 13 supports 256 colors. Others only have on/off.
'      This is because EGA color control requires IOPL privileges.
DEFINT A-Z
SUB VioPSET(x%, y%, colr%)
  IF vmode = 0 THEN EXIT SUB          'No graphics mode selected

  IF (x% >= 1 AND x% <= vmi.hres) AND_      'X in range
     (y% >= 1 AND y% <= vmi.vres) THEN      'Y in range
        b = VioScrLock(1, status, 0)        'Lock screen
          IF VioGetPhysBuf(pbd, 0) = 0 THEN 'Get buffer
             DEF SEG = pbd.selector1        'set screen seg
             CALL PokeIt(x%, y%, colr%)     'dev-ind POKE
             DEF SEG                        'set seg back
          END IF
        b = VioScrUnLock(0)                 'Unlock screen
  END IF
END SUB

'VioLine draws a line specified by points with given color
'
'NOTE: Mode 13 supports 256 colors. Others only have on/off.
'      This is because EGA color control requires IOPL privileges.
'
'ALSO NOTE: Code is complicated by optimizing for speed for
'           horizontal lines and lines with integer deltas.
DEFINT A-Z
SUB VioLine(px0%, py0%, px1%, py1%, colr%)

  IF vmode = 0 THEN EXIT SUB          'No graphics mode selected

  x0 = px0% : x1 = px1%               'Set params to work vars
  y0 = py0% : y1 = py1%

  IF (x0 >= 1 AND x0 <= vmi.hres) AND_    'Check ranges
     (y0 >= 1 AND y0 <= vmi.vres) AND_
     (x1 >= 1 AND x1 <= vmi.hres) AND_
     (y1 >= 1 AND y1 <= vmi.vres) THEN

     IF y0 > y1 THEN                      'Order points
        SWAP y0, y1
        SWAP x0, x1
     END IF

     IF ABS(y1 - y0) > ABS(x1 - x0) THEN  'Find denom for deltas
        denom = ABS(y1 - y0)              'denom -> max (dy,dx)
     ELSE
        denom = ABS(x1 - x0)
     END IF

     IF denom <> 0 THEN                 'If max(dx,dy) <> 0
        dx! = (x1 - x0) / denom         '  IEEE deltas
        dy! = (y1 - y0) / denom
        dxi = dx!      : dyi = dy!      '  integer deltas
        xs! = x0 + 0.5 : ys! = y0 + 0.5 '  IEEE indexes
        xi  = x0       : yi  = y0       '  integer indexes
     ELSE                               'Else
        CALL VioPSET(x0, y0, colr%)     '  0-length-line -> VioPSET
     END IF

     b = VioScrLock(1, status, 0)            'Lock screen
        IF VioGetPhysBuf(pbd, 0) = 0 THEN    'Get buffer
            DEF SEG = pbd.selector1          'Set screen seg
            IF (y0 = y1) THEN                'Optimize for horiz line

               IF x0 > x1 THEN SWAP x0, x1   'Order x values

               FOR xi = x0 TO x1
                  IF (vmode <> 13     AND_   'Optimize for non-13
                     (xi-1) MOD 8 = 0 AND_   'byte-aligned lines
                     xi + 7 <= x1)    THEN   'with length >= 8

                       Offset& = (1& * (y0-1) * vmi.hres_
                                     + (xi-1)) \ 8

                       IF colr% THEN         'If colr <> 0
                          POKE Offset&, &HFF '  set all bits on
                       ELSE                  'else
                          POKE Offset&, 0    '  set all bits off
                       END IF
                       xi = xi + 7           'Move to next byte
                  ELSE
                       CALL PokeIt(xi, y0, colr%) 'dev-ind POKE
                  END IF                          'for indiv bits
               NEXT
            ELSE
               IF (dxi = dx!) AND (dyi = dy!) THEN 'Opt for int dx/y
                  WHILE yi <= y1
                     CALL PokeIt(xi, yi, colr%)
                     xi = xi + dxi
                     yi = yi + dyi
                  WEND
               ELSE                               'Slow IEEE loop
                  WHILE ys! <= y1
                     xi=INT(xs!)
                     yi=INT(ys!)
                     CALL PokeIt(xi, yi, colr%)
                     xs! = xs! + dx!
                     ys! = ys! + dy!
                  WEND
               END IF
            END IF
            DEF SEG                               'set seg back
        END IF
     b = VioScrUnLock(0)                          'unlock screen
  END IF
END SUB

'VioBox fills a box specified by points with given color
'
'NOTE: Mode 13 supports 256 colors. Others only have on/off.
'      This is because EGA color control requires IOPL privileges.
'
'ALSO NOTE: Code is complicated by optimizing for speed for
'           byte-aligned sections of boxes with length >= 8.
DEFINT A-Z
SUB VioBox(px0%, py0%, px1%, py1%, colr%)

  IF vmode = 0 THEN EXIT SUB          'No graphics mode selected

  x0 = px0% : x1 = px1%               'Set params to work vars
  y0 = py0% : y1 = py1%

  IF (x0 >= 1 AND x0 <= vmi.hres) AND_       'Check ranges
     (y0 >= 1 AND y0 <= vmi.vres) AND_
     (x1 >= 1 AND x1 <= vmi.hres) AND_
     (y1 >= 1 AND y1 <= vmi.vres) THEN

     IF x0 > x1 THEN SWAP x0, x1             'Order x & y values
     IF y0 > y1 THEN SWAP y0, y1

     b = VioScrLock(1, status, 0)            'Lock screen
        IF VioGetPhysBuf(pbd, 0) = 0 THEN    'Get buffer
            DEF SEG = pbd.selector1          'Set screen seg
            FOR yi = y0 TO y1
               FOR xi = x0 TO x1
                  IF (vmode <> 13     AND_   'Optimize for non-13
                     (xi-1) MOD 8 = 0 AND_   'byte-aligned lines
                     xi + 7 <= x1)    THEN   'with length >= 8

                       Offset& = (1& * (yi-1) * vmi.hres_
                                     + (xi-1)) \ 8

                       IF colr% THEN         'If colr <> 0
                          POKE Offset&, &HFF '  set all bits on
                       ELSE                  'else
                          POKE Offset&, 0    '  set all bits off
                       END IF
                       xi = xi + 7           'Move to next byte
                  ELSE
                       CALL PokeIt(xi, yi, colr%) 'dev-ind POKE
                  END IF                          'for indiv bits
               NEXT xi
            NEXT yi
            DEF SEG                               'set seg back
        END IF
     b = VioScrUnLock(0)                          'unlock screen
  END IF
END SUB

'VioBSAVE is a quick way to save graphics to a file.
'
'NOTE: Works for single-plane MS-DOS BLOADed files.
SUB VioBSAVE(filename$)
   IF vmode = 0 THEN EXIT SUB            'No graphics mode selected
   b = VioScrLock(1, status, 0)          'Lock screen
   IF VioGetPhysBuf(pbd, 0) = 0 THEN     'Get buffer
       DEF SEG = pbd.selector1           'Set screen seg
       BSAVE filename$, 0, pbd.buflength 'BSAVE graphics screen
       DEF SEG                           'Set seg back
    END IF
    b = VioScrUnLock(0)                  'Unlock screen
END SUB

'VioBLOAD is a quick way to load graphics from a file.
'
'NOTE: Works with single-plane MS-DOS BSAVEd files.
SUB VioBLOAD(filename$)
   IF vmode = 0 THEN EXIT SUB           'No graphics mode selected
   b = VioScrLock(1, status, 0)         'Lock screen
      IF VioGetPhysBuf(pbd, 0) = 0 THEN 'Get buffer
         DEF SEG = pbd.selector1        'Set screen seg
         BLOAD filename$, 0             'BLOAD graphics screen
         DEF SEG                        'Set seg back
      END IF
   b = VioScrUnLock(0)                  'Unlock screen
END SUB

'DrawCircle draws the outline of a circle with given color
'centered on the specified point and radius.
'
'NOTE: This routine is not efficient because it uses VioLine instead
'      of doing all I/O in on VioScrLock/Unlock session.
SUB DrawCircle (x%, y%, r%, c%)
  IF vmode = 0 THEN EXIT SUB          'No graphics mode selected

  ix0# = x% : ix1# = x%
  ar# = r% * Aspect

  FOR iy% = -1 * INT(-1 * (y% - ar# + 0.1))_   '0.1 for exact matches
         TO -1 * INT(-1 * (y% + ar#))          '-INT(-z) -> roundup z
     dx# = FollowCircle(r%, iy% - y%)          'x offset

     CALL VioLine (INT(ix0#), iy%, x% - dx#, iy%, c%)  'Left edge
     CALL VioLine (INT(ix1#), iy%, x% + dx#, iy%, c%)  'Right edge

     ix0# = x% - dx#                           'Left x
     ix1# = x% + dx#                           'Right x
  NEXT
END SUB

'FillCircle fills a circle with given color centered on the
'specified point and radius.
'
'NOTE: This routine is not efficient because it uses VioLine instead
'      of doing all I/O in on VioScrLock/Unlock session.
SUB FillCircle (x%, y%, r%, c%)
  IF vmode = 0 THEN EXIT SUB          'No graphics mode selected

  ar# = r% * Aspect                   'Adjust radius for aspect

  FOR iy% = -1 * INT(-1 * (y% - ar# + 0.1))_
              TO INT(y% + ar# - 0.1)
     dx# = FollowCircle(r%, iy% - y%) 'Get x offsets from center

     CALL VioLine (x% - dx#, iy%, x% + dx#, iy%, c%)
  NEXT
END SUB

'FollowCircle gives the x offsets for the given scan line (y value).
'The return value is used to draw the circle by plotting points
'center +/- x offset
'
'If scan line is outside circle, 0 is returned.
FUNCTION FollowCircle# (r%, dy%)
  ay# = dy% / Aspect               'Adjust y for aspect
  IF (r% * r% < ay# * ay#) THEN
    FollowCircle# = 0              'Outside circle -> 0
  ELSE
    FollowCircle# = ((r% * r%) - (ay# * ay#)) ^ (.5)   'x offset
  END IF
END FUNCTION

'Aspect returns the aspect ratio for current mode (used with circles)
FUNCTION Aspect#
  Aspect# = 4 * (vmi.vres / vmi.hres) / 3    'Formula from QBX Help
END FUNCTION

'PokeIt is a device independent POKE routine which pokes the color
'specified in mode 13 or POKEs the position on or off for any other
'mode.
'
'NOTE: Color is supported only in mode 13. This is because EGA color
'      requires modifying the hardware registers. This requires an
'      IOPL segment and should be done in assembly.
SUB PokeIt(x%, y%, colr%)

   IF vmode = 13 THEN                                 'Mode 13
      POKE 1& * vmi.hres * (y%-1) + (x%-1), colr%     'POKE colr
   ELSE
      Offset& = (1& * (y%-1) * vmi.hres + (x%-1)) \ 8 'Offset of byte
      Bit%    = 2^(7 - ((x-1) MOD 8))                 'Bit to set

      IF colr% THEN                                   'IF colr<>0
         POKE Offset&, Bit% OR PEEK(Offset&)          '  set pixel on
      ELSE                                            'ELSE
         POKE Offset&, NOT(Bit%) AND PEEK(Offset&)    '  set pixel off
      END IF
   END IF

END SUB
				

Modification Type:MajorLast Reviewed:12/12/2003
Keywords:kbcode KB59136