Alpha-Blending with vbDABL
Tutorial


by Peter Kuchnio vbDABL by David Goodlad
Download the Source

Introduction

vbDABL is a very handy library that allows you to perform very fast alpha-blending in DirectDraw. DirectDraw doesn't have hardware support for alpha-blending, to achieve the effect we would have to get the colour of every single pixel in the two images we are trying to blend, then we would have to average them, and finally draw the finished pixel back to the screen.

Ordinarily this procedure would be very slow, however vbDABL is written in C++ and ASM and can handle all of these operations without breaking a sweat. Ths tutorial will explain how to use vbDABL along with clipping and animation (both can be somewhat tricky using the library.) in 16-bit mode.

Note: To get the source to run you are going to have to download it and install vbdabl.dll in your Windows/System folder. The dll is dump and run however, so for compiled apps you can simply place it in the same folder as your executable.

The Code

Linking to vbDABL

Before we can do anything we have to create a link to the vbDABL dll file. We do this with Declare Function:


'Function call for accessing the vbDABL library:
Public Declare Function vbDABLalphablend16 Lib "vbDABL" (ByVal iMode As Integer, 
ByVal bColorKey As Integer, ByRef sPtr As Any, ByRef dPtr As Any,
ByVal iAlphaVal As Integer, ByVal iWidth As Integer, ByVal iHeight As Integer,
ByVal isPitch As Integer, ByVal idPitch As Integer, ByVal iColorKey As Integer)
As Integer


This is the function call that we will be using to perform all of our alpha-blending.

I'm going to gloss over the details of initializing DirectDraw and loading bitmaps into surfaces, you should already know how to do this before reading this tutorial. If you'd like to see the wrapper functions I used, please download the source.

Creating our own Alpha-Blending Functions

Now that we have vbDABL linked we're going to create two of our own drawing subroutines. The first one will be for static images, or for blending an entire surface. The second subroutine will be for drawing animations, when several frames are included on one surface. Both subs will contain support for clipping and it's assumed that we're going to be drawing to the backbuffer. Let's get started, shall we? =)

vbDABLDraw16

This is going to be our static alpha-blending sub. Because we aren't drawing animations, we don't have to worry about the width of each frame in the image and the number of frames it contains. We simply draw the whole surface.


Private Sub vbDABLDraw16(surface As DirectDrawSurface7, srcRECT As RECT, x As Long
, y As Long, AlphaVal As Long, ScreenWidth As Integer, ScreenHeight As Integer,
Optional Clip As Boolean = True)


First our declaration. We're going to pass the sub a surface and a RECT variable which holds the dimensions of our surface. Next we pass it the screen coordinates we'd like to draw the surface. Then we pass an Alpha value, this is a number between 0 (transparent) to 255 (opaque) that tells the function at what translucency level to draw the surface. Finally, we specify our resolution in Screenwidth and ScreenHeight and toggle whether we are clipping or not. The last 3 variables are used for clipping.

Now, we have to declare some more variables:


'Temporary Surface Description
    Dim tempDDSD As DDSURFACEDESC2
    
    'Byte arrays
    'Will be used to store image data when the surfaces
    'being alphablended are locked
    Dim ddsBackArray() As Byte
    Dim ddsForeArray() As Byte



First, we declare a temporary surface description variable to hold information about our surface like its address in memory. Then we create two byte arrays which will be filled later on with the pixel data from both of our surfaces.

We now declare another RECT variable called RectVar. This will be used when we're clipping the surface, as we don't want to actually alter the values of our original rect. If we do, then it will become permanently clipped, which we definately don't want.


'RECT variable to hold altered information about
    'our surface. We don't want to actually change the
    'surface's true RECT.
    Dim RECTvar As RECT
    RECTvar = srcRECT



Next, we're going to clip the surface. Clipping alters the RECT variable so that if part of the surface is offscreen the whole image doesn't disappear like it would normally. There is a full tutorial on clipping in the DirectX7 section, but it isn't too complicated =)


'Clip the RECT if clipping is enabled
    If Clip = True Then
        Dim ScreenRect As RECT
        With ScreenRect
            .Left = x
            .Right = x + (srcRECT.Right - srcRECT.Left)
            .Top = y
            .Bottom = y + (srcRECT.Bottom - srcRECT.Top)
               
            If .Bottom > ScreenHeight Then
                RECTvar.Bottom = RECTvar.Bottom - (.Bottom - ScreenHeight)
                .Bottom = ScreenHeight - 10
            End If
            If .Left < 0 Then
                RECTvar.Left = RECTvar.Left - .Left
                .Left = 0
                x = 0
            End If
            If .Right > ScreenWidth Then
                RECTvar.Right = RECTvar.Right - (.Right - ScreenWidth)
                .Right = ScreenWidth - 10
            End If
            If .Top < 0 Then
                RECTvar.Top = RECTvar.Top - .Top
                .Top = 0
                y = 0
            End If
        End With
    End If



Notice we only clip if clipping has been enabled when we call the subroutine. This isn't too complicated, first we calculate where on the screen the surface is being drawn and its dimensions and store it in ScreenRECT. Next we check the four sides of the surface and subtract from the RECT variable if part of the surface is offscreen. This way only the onscreen part of the surface will be drawn.

Now we have to put in a very important check. We have to make sure that we aren't passing any negative values to vbDABL. If we do, our whole program will crash.


'Check to make sure we aren't passing negative values
    'in our RECT. If we do pass negative values then the app
    'will crash.
    If RECTvar.Right > RECTvar.Left + 3 Then
        'nothing
    Else
        'don't draw anything, quit
        Exit Sub
    End If
    
    If RECTvar.Bottom > RECTvar.Top + 3 Then
        'nothing
    Else
        Exit Sub
    End If



So, we make sure that our RECT variable has a positive width (Right is more than Left) and height (Bottom is more than Top). We also put in a 3 pixel buffer zone, this is to totally ensure that we aren't passing negative values. If you lower the value, this sub will become more prone to crashing (trust me, this was a very big recurring problem in DDCK, 3 pixels is the sweet spot). If our width or height is negative, we simply exit the sub, the whole surface is offscreen and we don't need to draw anything.

Now that we have all of our surface dimensions properly set up in our RECT variable, we can go on to the core of the subroutine, alphablending the two surfaces!

To prepare for that, we have to lock both our surface and the backbuffer:


Dim emptyrect As RECT
    
    'Lock the backbuffer and the surface that we are going to alphablend
    
    'Lock the backbuffer - we pass it an empty rect which means it will
    'lock the whole screen
    ddsBack.Lock emptyrect, Ddsd2, DDLOCK_NOSYSLOCK Or DDLOCK_WAIT, 0
    
    surface.Lock srcRECT, tempDDSD, DDLOCK_NOSYSLOCK Or DDLOCK_WAIT, 0



Emptyrect is exactly that, it's simply an empty RECT variable that we pass to the Lock function when we lock the backbuffer. DirectDraw takes this to mean that we want to lock the whole surface, which we do.

Next we use GetLockedArray to fill our our byte arrays with the pixel data stored in the surfaces:


'Fill our our byte arrays by extracting the necessary data
    'from the surfaces we just locked
    ddsBack.GetLockedArray ddsBackArray
    surface.GetLockedArray ddsForeArray



Now, everything is ready, we have all of the data we need to alpha-blend the two surfaces together =) Before you check out the code, pixel formats in 16-bit mode deserve a bit of an explanation. Depending on the video card, there are two possible formats, 555 mode and 565 mode. In 555 mode, 5 bits are used to represent Red, Green, and Blue (ie: R5G5B5). In 565 mode, however, green is represented by 6 bits, so it becomes R5G6B5.

So, when we're alpha-blending we have to check which pixel format is being used and tell vbDABL whether to use 555 or 565 mode.


Select Case Ddsd2.ddpfPixelFormat.lGBitMask
        Case &H3E0 '555 mode

            vbDABLalphablend16 555, 1, ddsForeArray(RECTvar.Left + RECTvar.Left, 
RECTvar.Top), ddsBackArray(x + x, y), alphaval, (RECTvar.Right - RECTvar.Left),

(RECTvar.Bottom - RECTvar.Top), tempDDSD.lPitch, Ddsd2.lPitch, 0 Case &H7E0 '565 mode vbDABLalphablend16 565, 1, ddsForeArray(RECTvar.Left + RECTvar.Left,
RECTvar.Top), ddsBackArray(x + x, y), alphaval, (RECTvar.Right - RECTvar.Left),
(RECTvar.Bottom -
RECTvar.Top), tempDDSD.lPitch, Ddsd2.lPitch, 0
End Select


So, before we call the dll, we check which pixel format we are under by looking it up in the backbuffer's surface description. Next, we call the actual alpha-blending function. It's relatively simple, since vbDABL does all of the hard work, we just have to make sure we pass it the right parameters. So, we pass it the pixel format, whether we want to use a colour-key or not (1=True), then the byte arrays for our surface and backbuffer. Next we tell it what alpha value we want to draw at, the width and height of the area we are blending, the pitch paramters from our surface descriptions and finally, the colour that is to be made transparent (in this case black, 0).

Our last step is to clean up:


'Now that we are finished alphablending we have
    'to unload the surfaces we just locked
    surface.Unlock srcRECT
    ddsBack.Unlock emptyrect

End Sub



We unlock our surfaces and the subroutine is finished, we have blended two surfaces together and have drawn the result on the backbuffer.

vbDABLDraw16Anim

Now, we have one more subroutine to create, one for drawing alpha-blended animations. The two subroutines are very similar, but for animation we have to play around more with RECTs. Basically we need to take out individual frames from a larger image. We make one assumption here, the frames in the image have to be arranged sequentially in one strip.

In order to draw individual frames, we are going to need two more variables to work with, WidthPerFrame, and CurFrame:


Private Sub vbDABLDraw16Anim(surface As DirectDrawSurface7, srcRECT As RECT,
x As Long, y As Long, alphaval As Long, widthperframe As Integer, framenum
As Integer, ScreenWidth
As Integer, ScreenHeight As Integer, Optional Clip As
Boolean = True)


WidthPerFrame tells us how many pixels across each frame in the animation is. CurFrame specifies what frame we are currently (starting from 0, so an animation with 16 frames would be counted from 0 to 15).

You'll remember this part from the subroutine above:


'Temporary Surface Description
    Dim tempDDSD As DDSURFACEDESC2
    
    'Byte arrays
    'Will be used to store image data when the surfaces
    'being alphablended are locked
    Dim ddsBackArray() As Byte
    Dim ddsForeArray() As Byte
    
    'RECT variable to process each frame
    Dim FrameRECT As RECT
       
    
    'Set up dimensions for each frame
    With FrameRECT
        .Left = widthperframe * framenum
        .Right = FrameRECT.Left + widthperframe
        .Top = 0
        .Bottom = srcRECT.Bottom
    End With



The big difference here is the FrameRECT variable. This is going to store the dimensions of our current frame in the larger image. We get the left position by multiplying the width of each frame by the number of the frame we are on. To get the right position we add the frame width. Top and Bottom stay the same, since we are working with a long strip.

The rest is practically identical except we changed our rect variable from RectVar to FrameRect.


'Clip the RECT if clipping is enabled
    If Clip = True Then
        Dim ScreenRect As RECT
        With ScreenRect
            .Left = x
            .Right = x + widthperframe
            .Top = y
            .Bottom = y + srcRECT.Bottom
    
            If .Bottom > ScreenHeight Then
                FrameRECT.Bottom = FrameRECT.Bottom - (.Bottom - ScreenHeight)
            End If
            If .Left < 0 Then
                FrameRECT.Left = FrameRECT.Left - .Left
                x = 0
            End If
            If .Right > ScreenWidth Then
                FrameRECT.Right = FrameRECT.Right - (.Right - ScreenWidth)
            End If
            If .Top < 0 Then
                FrameRECT.Top = FrameRECT.Top - .Top
                y = 0
            End If
        End With
    End If
   
    'Check to make sure we aren't passing negative values
    'in our RECT. If we do pass negative values then the app
    'will crash.
    If FrameRECT.Right > FrameRECT.Left + 3 Then
        'nothing
    Else
        'don't draw anything, quit
        Exit Sub
    End If
   
    If FrameRECT.Bottom > FrameRECT.Top + 3 Then
       'nothing
    Else
        Exit Sub
    End If
   
    'Double check that our coordinates aren't negative
    If x < 0 Then x = 0
    If y < 0 Then y = 0



One little thing is different, we add a check to make sure our x and y coordinates aren't negative, if they are this will cause a subscript out of range error when we alpha-blend.

The rest is also practically identical, except we switched rect variables:


Dim emptyrect As RECT
   
    'Lock the backbuffer and the surface that we are going to alphablend
   
    'Lock the backbuffer - we pass it an empty rect which means it will
    'lock the whole screen
    ddsBack.Lock emptyrect, Ddsd2, DDLOCK_NOSYSLOCK Or DDLOCK_WAIT, 0
   
    surface.Lock srcRECT, tempDDSD, DDLOCK_NOSYSLOCK Or DDLOCK_WAIT, 0
   
    'Fill our our byte arrays by extracting the necessary data
    'from the surfaces we just locked
    ddsBack.GetLockedArray ddsBackArray
    surface.GetLockedArray ddsForeArray
   
    ''ALPHA-BLENDING
    'Here is where we actually perform the alpha-blending operation
    'in 16-bit mode.
   
    'Depending on the video card, 16-bit mode can have two different
    'pixel formats, 555 mode and 565 mode. In 555 mode we have 5 bits for red,
    '5 bits for green and 5 bits for blue. In 565 mode we have 6 bits for green.
    'We have to check which pixel format we are using before we call
    'the alpha-blend function
    Select Case Ddsd2.ddpfPixelFormat.lGBitMask
        Case &H3E0 '555 mode
            vbDABLalphablend16 555, 1, ddsForeArray(FrameRECT.Left + FrameRECT.Left, 
FrameRECT.Top), ddsBackArray(x + x, y), alphaval, (FrameRECT.Right - FrameRECT.Left),
(FrameRECT.Bottom - FrameRECT.Top), tempDDSD.lPitch, Ddsd2.lPitch, 0 Case &H7E0 '565 mode vbDABLalphablend16 565, 1, ddsForeArray(FrameRECT.Left + FrameRECT.Left,
FrameRECT.Top), ddsBackArray(x + x, y), alphaval, (FrameRECT.Right - FrameRECT.Left),
(FrameRECT.Bottom - FrameRECT.Top), tempDDSD.lPitch, Ddsd2.lPitch, 0 End Select 'Now that we are finished alphablending we have 'to unload the surfaces we just locked surface.Unlock srcRECT ddsBack.Unlock emptyrect End Sub


And that is that =) We now have two very useful subroutines that will let us easily draw alpha-blended, whether they are still or animated.

Putting It All Together

Now comes the easy but rewarding part, we're going to use the two subroutines we created to draw two different images, one is still and scrolls across the screen (to show off vbDABLDraw16 and clipping support), the other is animated but doesn't scroll (although is easily could with a few small modifications).


 'Alpha value for our static surface
    Dim sAlphaVal As Long
    Dim FadeDir As Boolean
    
    Do
        DoEvents
        
        'Fill the backbuffer with black. DDColorFill
        'sub is located in mdVars
        DDColorFill ddsBack, 0, 0, 800, 600, RGB(0, 0, 0)
        
        'Increment alpha-value for sStatic
        If FadeDir = False Then
            sAlphaVal = sAlphaVal + 1
        Else
            sAlphaVal = sAlphaVal - 1
        End If
        
        If sAlphaVal > 255 Then
            FadeDir = True
        End If
        If sAlphaVal < 5 Then
            FadeDir = False
        End If
        
        'Draw our non-animated surface
        vbDABLDraw16 sStatic, sStaticRECT, (cx), 200, sAlphaVal, 800, 600
                
        'Move the surface across the screen
        cx = cx + 5
        If cx > 800 Then cx = -200



First, we declare a variable to hold our alpha value and the direction that we are going to fade in. The second variable will let us fade in and out, so we get a nice pulsing type effect.

Now, we start our loop. The next call is a function call to fill our backbuffer with black, this becomes our background.

The next little bit is simple, depending on the fade directoin we either add or subtract to the alpha value, sAlphaVal. Now we call our subroutine. We pass it the surface, its RECT, x and y coordinates, alpha value, and screen dimensions. Cx is our X coor variable, below our subroutine call we incrememt its values to get it to scroll.


'Draw our animated surface
        vbDABLDraw16Anim sAnimated, sAnimatedRECT, 300, 250, 150, 220, CurFrame,
800, 600 'increment frames CurFrame = CurFrame + 1 If CurFrame > 15 Then CurFrame = 0 'Flip the backbuffer onto the primary surface '(ie: refresh the screen) 'sub located in mdVars DDFlip Loop Until running = False


Now we draw our animated surface. The calls are very similar, the only difference is that we have to specify the frame width and current frame. This animation has 16 frames so we incremement them below to get the animation to loop.

Conclusion

Well, that's it! You should now be able to fully utilize vbDABL for alpha-blending in DirectDraw. Make sure to download the source to see the example in action.