Sunteți pe pagina 1din 15

 

 
 
 
LightBox For Visual Basic 6 
Version 2 
Helping to reduce information‐overload 
 
By William Sengdara 
Programmer 
January 2010 
 
 

 
 
Appreciation note: This code proudly runs on top of Tanner Helland’s excellent code for  
Real-Time Image Blending/Transparency (VB6)
http://www.tannerhelland.com/490/image‐blending‐transparency/! 
http://www.tannerhelland.com   
Introduction 
My first encounter with selective ‘Black outs’ in dialogs was on the world wide web. Let me explain. 
Some of the savvy web sites I tend to visit, such as Information Technology websites, make use of input 
dialogs with a difference. The big difference here is that these dialogs were displayed in front of a 
darkened background webpage. I later learned about a script called LightBox. 

Suffice to say, this simple act means that focus and attention moves from the cluttered web page behind 
and naturally to the dialog in front. 

I encountered the same thing on Microsoft Windows Vista as well. One example that immediately 
comes to mind is that whenever I attempted to make changes to my desktop, such as the color scheme, 
the desktop would slightly black out until the procedure completed etc. 

Clearly there is Zen in reducing information overload in decision making in input/interaction 
dialogs. 

I see this as an extremely beautiful idea in this world of information overload and so, I have decided to 
implement it in my applications. What follows is a small study in implementing ‘black out’ in software 
interface windows and dialogs.   
Selective black‐out  
 

We will consider the application below.  

 
Figure 1 Our sample application running 

 
Figure 2 After clicking the Show Login button, our blackout code was called prior 
 
Figure 3 Parent form is blacked out, child form is also blacked out 

 
How it all works 
The application demonstrated here is written in VB 6. Although I am only able to provide the source 
code in VB 6, the principle is the same regardless of the language in use. Also, I am not trying to provide 
a complete solution, just a simple foundation.  

Normally, you would display your dialog in this way 

frmParent.show vbmodal, frmChild

But with our Black out class, first we need to spread the alpha blended image over frmParent before 
calling show() : 

Dim bl As CBlackOut
Set bl = New CBlackOut
bl.spreadOver frmParent
frmParent.show vbmodal, frmChild
bl.wipeAway
 

To implement our ‘black out’, we just need to, behind the scenes in a CBlackout class: 

1. Create 3 picturebox controls dynamically 
2. picDst is where we alphablend the final image, picSrc1 is where we paint a snapshot of the 
parent form, picSrc2 is used for coloring the snapshot (vbApplicationWorkspace) 
3. We take a snapshot of the parent form and paint this to picSrc1 
4. We use Tanner Helland’s real‐time alphablending code to blend picSrc1 with picSrc2 
5. We paint the resulting picture onto picDst 
6. We move picDst over the client area of frmParent 
7. After the required form has been displayed over frmParent, we have to destroy the 3 picturebox 
controls
Option Explicit

'*************************************************************************
' Save this as a Class in VB 6
' save as CBlackOut
'
' If you are a web developer, then you will probably be familiar with
' LighBox, and its variants - a javascript code that allows you to
' overlay a background over a window
'
' I decided to create a similar concept in VB 6
' The first attempt overlaid a form over the parent form
' This had issues because of restrictions on modal dialogs etc
' This implementation overlays a picturebox over the parent form,
' creates a snapshot of the form and uses Tanner Helland's real-time
' drawing code to alphablend vbApplicationWorkspace color with the image of
' the form
'
' issues: kinda slow when the form is large
'
' Author: William Sengdara
' Creted: March 22, 2011
'*************************************************************************

'************************************************************************************************
' Alphablend code by Tanner Helland
'************************************************************************************************
'Real-time drawing class for VB6
'Published in 2010 by Tanner Helland
'
'This class is every graphics programmers dream - it does all the dirty API work required for
real-time
' graphics, and all you have to do is call a few very simple routines. The format is simple; the
only
' variables required are the picture boxes you want to process, and an array to hold the DIB
information.
' Many comments are included, though the routines should be self-explanatory.
'
'This source code has been released under a BSD license. You may read more about this license at:
' http://creativecommons.org/licenses/BSD/
'
'If you would like to make a donation to help offset the cost of maintaining this code and the
site on which it resides, please visit:
' http://www.tannerhelland.com/programming-directory/
'...and click the "Donate" button at the top of the page.
'
'While no payment will ever be required to use or distribute this source code, donations are
GREATLY appreciated!
'
'Comments and questions regarding this source code can be submitted via this contact form:
' http://www.tannerhelland.com/contact/
'
'***Start Alphablend code by Tanner
Helland*******************************************************

'Stripped down bitmap information


Private Type Bitmap
bmType As Long
bmWidth As Long
bmHeight As Long
bmWidthBytes As Long
bmPlanes As Integer
bmBitsPixel As Integer
bmBits As Long
End Type

'Call to transfer an object's properties into a custom variable


Private Declare Function GetObject Lib "gdi32" Alias "GetObjectA" (ByVal hObject As Long, ByVal
nCount As Long, ByRef lpObject As Any) As Long

'Standard pixel data


Private Type RGBQUAD
rgbBlue As Byte
rgbGreen As Byte
rgbRed As Byte
rgbAlpha As Byte
End Type

'Full-size bitmap header


Private Type BITMAPINFOHEADER
bmSize As Long
bmWidth As Long
bmHeight As Long
bmPlanes As Integer
bmBitCount As Integer
bmCompression As Long
bmSizeImage As Long
bmXPelsPerMeter As Long
bmYPelsPerMeter As Long
bmClrUsed As Long
bmClrImportant As Long
End Type

'Extended header for 8-bit images


Private Type BITMAPINFO
bmHeader As BITMAPINFOHEADER
bmColors(0 To 255) As RGBQUAD
End Type

'Used to ensure quality stretching of color images


Private Declare Function SetStretchBltMode Lib "gdi32" (ByVal hdc As Long, ByVal nStretchMode As
Long) As Long

'DIB section interfaces


Private Declare Function GetDIBits Lib "gdi32" (ByVal hdc As Long, ByVal hBitmap As Long, ByVal
nStartScan As Long, ByVal nNumScans As Long, lpBits As Any, lpBI As BITMAPINFO, ByVal wUsage As
Long) As Long
Private Declare Function StretchDIBits Lib "gdi32" (ByVal hdc As Long, ByVal x As Long, ByVal y
As Long, ByVal dX As Long, ByVal dy As Long, ByVal SrcX As Long, ByVal SrcY As Long, ByVal
SrcWidth As Long, ByVal SrcHeight As Long, lpBits As Any, lpBitsInfo As BITMAPINFO, ByVal wUsage
As Long, ByVal dwRop As Long) As Long

'***End Alphablend code by Tanner Helland


*********************************************************

Private Declare Function GetClientRect Lib "User32" (ByVal hWnd As Long, lpRect As RECT) As Long
Private Declare Function MoveWindow Lib "User32" (ByVal hWnd As Long, ByVal x As Long, ByVal y As
Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal bRepaint As Long) As Long
Private Declare Function ClientToScreen Lib "User32" (ByVal hWnd As Long, lpPoint As POINTAPI) As
Long
Private Declare Function SetForegroundWindow Lib "User32" (ByVal hWnd As Long) As Long

'API
Private Declare Function ReleaseDC Lib "user32.dll" (ByVal hWnd As Long, ByVal hdc As Long) As
Long
Private Declare Function OpenClipboard Lib "user32.dll" (ByVal hWnd As Long) As Long
Private Declare Function EmptyClipboard Lib "user32.dll" () As Long
Private Declare Function SetClipboardData Lib "user32.dll" (ByVal wFormat As Long, ByVal hMem As
Long) As Long
'if you have problems with this function add the Alias "SetClipboardDataA"
Private Declare Function CloseClipboard Lib "user32.dll" () As Long
Private Declare Function SelectObject Lib "gdi32.dll" (ByVal hdc As Long, ByVal hObject As Long)
As Long
Private Declare Function DeleteDC Lib "gdi32.dll" (ByVal hdc As Long) As Long
Private Declare Function BitBlt Lib "gdi32.dll" (ByVal hDestDC As Long, ByVal x As Long, ByVal y
As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long,
ByVal ySrc As Long, ByVal dwRop As Long) As Long
Private Declare Function CreateDC Lib "gdi32.dll" Alias "CreateDCA" (ByVal lpDriverName As
String, ByVal lpDeviceName As String, ByVal lpOutput As String, lpInitData As DEVMODE) As Long
Private Declare Function CreateCompatibleBitmap Lib "gdi32.dll" (ByVal hdc As Long, ByVal nWidth
As Long, ByVal nHeight As Long) As Long
Private Declare Function CreateCompatibleDC Lib "gdi32.dll" (ByVal hdc As Long) As Long
Private Declare Function GetDesktopWindow Lib "User32" () As Long

Private Type RECT


Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
Private Type POINTAPI
x As Long
y As Long
End Type

Dim pt As POINTAPI
Dim rc As RECT

Private Type ClientInfo


max_width As Long
max_height As Long
client_width As Long
client_height As Long
pos_x As Long
pos_y As Long
End Type

Private Const CCHDEVICENAME = 32


Private Const CCHFORMNAME = 32
Private Const SRCCOPY = &HCC0020 ' (DWORD) destination = source

Private Type DEVMODE


dmDeviceName As String * CCHDEVICENAME
dmSpecVersion As Integer
dmDriverVersion As Integer
dmSize As Integer
dmDriverExtra As Integer
dmFields As Long
dmOrientation As Integer
dmPaperSize As Integer
dmPaperLength As Integer
dmPaperWidth As Integer
dmScale As Integer
dmCopies As Integer
dmDefaultSource As Integer
dmPrintQuality As Integer
dmColor As Integer
dmDuplex As Integer
dmYResolution As Integer
dmTTOption As Integer
dmCollate As Integer
dmFormName As String * CCHFORMNAME
dmUnusedPadding As Integer
dmBitsPerPel As Long
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
End Type

' create 3 pictureBox controls dynamically

' these are their IDs


Const PICBOX_ID_DST As String = "picBlackOut"
Const PICBOX_ID_SRC1 As String = "picBlackOutSrc1"
Const PICBOX_ID_SRC2 As String = "picBlackOutSrc2"

' These are the 3 pictureBox controls to be created dynamically


Dim m_picDst As PictureBox
Dim m_picSrc1 As PictureBox
Dim m_picSrc2 As PictureBox

' we keep the parent form


Dim m_form As Form

' function spreadOver


' Overlays an image of the form onto a picturebox name picDst
' which we shall create dynamically
' but first, we need to take a snapshot of the client area of
' the form and paint it onto picSrc1.
' Then we use Tanner Helland's alphablend code to blend the
' picSrc1.picture with picSrc2.picture (there is no image in
' picSrc2, it is only the color vbApplicationWorkSpace)
' Then we paint the resulting image onto picDst
'
' param: frm
' The form to overlay the alphablended image over
Public Function spreadOver(frm As Form)
Set m_form = frm

Set m_picDst = m_form.Controls.Add("VB.PictureBox", PICBOX_ID_DST)


Set m_picSrc1 = m_form.Controls.Add("VB.PictureBox", PICBOX_ID_SRC1)
Set m_picSrc2 = m_form.Controls.Add("VB.PictureBox", PICBOX_ID_SRC2)

With m_picDst
.BackColor = vbWindowBackground
.AutoRedraw = True
.BorderStyle = 0
.ScaleMode = 0 'vbPixels
.Visible = False
.ZOrder
End With
With m_picSrc1
.BorderStyle = 0
.ScaleMode = 0 'vbPixels
.AutoRedraw = True
.Visible = False
.Move 0, 0, frm.ScaleWidth, frm.ScaleHeight
End With
' this is to hold the appWorkspace color only
With m_picSrc2
.AutoRedraw = True
.BackColor = vbApplicationWorkspace
.ScaleMode = 0 'vbPixels
.BorderStyle = 0
.Move 0, 0, frm.ScaleWidth, frm.ScaleHeight
.Picture = .Image
.Refresh
End With

' take a snapshot of the client area of this from


' then paint it over picSrc1
CaptureClientImage m_form, 0, 0, m_form.ScaleWidth / Screen.TwipsPerPixelX,
m_form.ScaleHeight / Screen.TwipsPerPixelY, m_picSrc1

' adjust the scales so picSrc1 is same metrics as picSrc2


' or else Tanner Helland's code will crash
m_picDst.Move 0, 0, m_picSrc1.ScaleWidth, m_picSrc1.ScaleHeight
m_picSrc2.Move 0, 0, m_picSrc1.ScaleWidth, m_picSrc1.ScaleHeight

' now we need to alphablend picSrc1 and picSrc2


' using Tanner Holland's class
DrawTransparency m_picSrc1, m_picSrc2, m_picDst, 80

' show the picture box over the client


coverClientArea m_form, m_picDst
m_picDst.Visible = True
End Function

' function wipeAway


' destroys all the controls we used
'
Public Function wipeAway()
m_form.Controls.Remove PICBOX_ID_DST
m_form.Controls.Remove PICBOX_ID_SRC1
m_form.Controls.Remove PICBOX_ID_SRC2

Set m_picDst = Nothing


Set m_picSrc1 = Nothing
Set m_picSrc2 = Nothing
End Function

' Microsoft code for


' Screen Capture Procedure, coordinates are expressed in pixels
' adapted to capture only
' the client area and paint to picDst
Private Sub CaptureClientImage(frm As Form, Left As Long, Top As Long, _
Width As Long, Height As Long, picDst As PictureBox)
picDst.Visible = False
picDst.Move 0, 0, frm.Width, frm.Height
BitBlt picDst.hdc, 0, 0, Width, Height, frm.hdc, Left, Top, SRCCOPY
picDst.Visible = True
picDst.Picture = picDst.Image
picDst.Refresh
End Sub

Private Sub coverClientArea(client As Form, pic As PictureBox)


Dim pt As POINTAPI

pt.x = 0
pt.y = 0
rc.Left = 0
rc.Bottom = 0
rc.Right = 0
rc.Top = 0
GetClientRect client.hWnd, rc
ClientToScreen client.hWnd, pt
pic.Move 0, 0, client.ScaleWidth, client.ScaleHeight
End Sub
'Real-Time Image Transparency by Tanner Helland
' http://www.tannerhelland.com
'
'Real-time image transparency isn't nearly as difficult as you may think.
' In fact, this program provides a function that does all the messy work
' for you, including the use of DIB sections to gather and set pixel data.
'
'The way the function is currently written, it is assumed that the
' source images and destination image are all the same size. Some changes
' would need to be made if these images were different sizes (due to the
' bizarre way DIBs function). If you attempt to alpha-blend two images of
' differing sizes, the current function will force the second image to the
' size of the first. FYI!
'
'Visit www.tannerhelland.com for more real-time VB graphics effects.
' scalewidth must be match

'Draw an alpha blend from two source picture boxes into a destination picture box.
'The transparency value is a simple percentage from 1 to 100
Public Sub DrawTransparency(srcPic1 As PictureBox, srcPic2 As PictureBox, _
dstPic As PictureBox, _
ByVal lvlTransparency As Byte)

On Local Error GoTo bail

'These arrays will hold both image's pixel data


Dim ImageDataSrc1() As Byte, ImageDataSrc2() As Byte, ImageDataDst() As Byte

'Coordinate variables
Dim x As Long, y As Long

'Image dimensions
Dim iWidth As Long, iHeight As Long

'Instantiate a FastDrawing class and gather the first source image's data
iWidth = GetImageWidth(srcPic1)
iHeight = GetImageHeight(srcPic1)
GetImageData2D srcPic1, ImageDataSrc1()

'Now do it for the second source image


iWidth = GetImageWidth(srcPic2)
iHeight = GetImageHeight(srcPic2)
GetImageData2D srcPic2, ImageDataSrc2()

'Last but not least, do it for the destination picturebox


iWidth = GetImageWidth(srcPic2)
iHeight = GetImageHeight(srcPic2)
GetImageData2D dstPic, ImageDataDst()

'These variables will hold temporary pixel color values


Dim R As Byte, G As Byte, B As Byte
Dim R2 As Byte, G2 As Byte, B2 As Byte

'Build a look-up table to increase speed


Dim LookUp(0 To 255, 0 To 255) As Byte
Dim invTransparency As Byte
invTransparency = 100 - lvlTransparency
For x = 0 To 255
For y = 0 To 255
'Mix all possible color values based on simple weighted averaging
LookUp(x, y) = CByte(((invTransparency * x) + (lvlTransparency * y)) \ 100)
Next y
Next x

'Now run a quick loop through the image, adjusting pixel values with the look-up tables
Dim QuickX As Long
For x = 0 To iWidth - 1
QuickX = x * 3
For y = 0 To iHeight - 1
'Grab red, green, and blue from the source images
R = ImageDataSrc1(QuickX + 2, y)
G = ImageDataSrc1(QuickX + 1, y)
B = ImageDataSrc1(QuickX, y)
R2 = ImageDataSrc2(QuickX + 2, y)
G2 = ImageDataSrc2(QuickX + 1, y)
B2 = ImageDataSrc2(QuickX, y)
'Use our source values to calculate a new, transparent color
ImageDataDst(QuickX + 2, y) = LookUp(R, R2)
ImageDataDst(QuickX + 1, y) = LookUp(G, G2)
ImageDataDst(QuickX, y) = LookUp(B, B2)
Next y
Next x

'Draw the new image data to the screen


SetImageData2D dstPic, iWidth, iHeight, ImageDataDst()

Exit Sub

bail:
Err.Clear
dstPic.BackColor = vbApplicationWorkspace
End Sub

'Get the image width (via API - always accurate, unlike PictureBox.ScaleWidth)
Public Function GetImageWidth(SrcPictureBox As PictureBox) As Long
Dim bm As Bitmap
GetObject SrcPictureBox.Image, Len(bm), bm
GetImageWidth = bm.bmWidth
End Function

'Get the image height (via API - always accurate)


Public Function GetImageHeight(SrcPictureBox As PictureBox) As Long
Dim bm As Bitmap
GetObject SrcPictureBox.Image, Len(bm), bm
GetImageHeight = bm.bmHeight
End Function

'Get the stream length of an image (via API - always accurate)


Public Function GetImageStreamLength(SrcPictureBox As PictureBox) As Long
Dim bm As Bitmap
GetObject SrcPictureBox.Image, Len(bm), bm
GetImageStreamLength = (bm.bmWidth * (bm.bmHeight + 1)) * 3
End Function

'Get an image's pixel information into an array dimensioned (x * 3 + bgr, y), with the option to
get it in its true orientation
Public Sub GetImageData2D(SrcPictureBox As PictureBox, ImageData() As Byte, Optional ByVal
CorrectOrientation As Boolean = False)
Dim bm As Bitmap
'Get the picture box information
GetObject SrcPictureBox.Image, Len(bm), bm
'Build a correctly sized array
Erase ImageData()
'Generate a correctly-dimensioned array (for 2-dimensional access)
Dim ArrayWidth As Long
ArrayWidth = (bm.bmWidth * 3) - 1
ArrayWidth = ArrayWidth + (bm.bmWidth Mod 4) '4-bit alignment
ReDim ImageData(0 To ArrayWidth, 0 To bm.bmHeight) As Byte
ReDim tmpData(0 To ArrayWidth, 0 To bm.bmHeight) As Byte

'Create a temporary header to pass to the GetDIBits call


Dim bmi As BITMAPINFO
bmi.bmHeader.bmWidth = bm.bmWidth
bmi.bmHeader.bmHeight = bm.bmHeight
bmi.bmHeader.bmSize = 40 'Size, in bytes, of the header
bmi.bmHeader.bmPlanes = 1 'Number of planes (always one for this instance)
bmi.bmHeader.bmBitCount = 24 'Bits per pixel (always 24 for this instance)
bmi.bmHeader.bmCompression = 0 'Compression :standard/none or RLE

'Get the image data into our array


If CorrectOrientation = False Then
GetDIBits SrcPictureBox.hdc, SrcPictureBox.Image, 0, bm.bmHeight, ImageData(0, 0), bmi, 0
Else
GetDIBits SrcPictureBox.hdc, SrcPictureBox.Image, 0, bm.bmHeight, tmpData(0, 0), bmi, 0
End If

'This code is to orient the image data correctly in the array (i.e. (0,0) as top-left,
(max,max) as bottom right)
' (if this option is enabled, we must set the DIB height to negative in the SetImageData
routine below)
If CorrectOrientation = True Then

Dim x As Long, y As Long, z As Long


Dim QuickVal As Long
For x = 0 To bm.bmWidth - 1
QuickVal = x * 3
For y = 0 To bm.bmHeight - 1
For z = 0 To 2
ImageData(QuickVal + z, y) = tmpData(QuickVal + z, bm.bmHeight - y)
Next z
Next y
Next x

End If

'Save memory...?
Erase tmpData

End Sub

'Set an image's pixel information from an array dimensioned (x * 3 + bgr, y)


Public Sub SetImageData2D(DstPictureBox As PictureBox, OriginalWidth As Long, OriginalHeight As
Long, ImageData() As Byte, Optional ByVal CorrectOrientation As Boolean = False)
Dim bm As Bitmap
'Get the picture box information
GetObject DstPictureBox.Image, Len(bm), bm
'Create a temporary header to pass to the StretchDIBits call
Dim bmi As BITMAPINFO
bmi.bmHeader.bmWidth = OriginalWidth
If CorrectOrientation = False Then
bmi.bmHeader.bmHeight = OriginalHeight
Else
bmi.bmHeader.bmHeight = -OriginalHeight
End If
bmi.bmHeader.bmSize = 40 'Size, in bytes, of the header
bmi.bmHeader.bmPlanes = 1 'Number of planes (always one for this instance)
bmi.bmHeader.bmBitCount = 24 'Bits per pixel (always 24 for this instance)
bmi.bmHeader.bmCompression = 0 'Compression :standard/none or RLE
'Assume color images and set the corresponding best stretch mode
SetStretchBltMode DstPictureBox.hdc, 3&
'Send the array to the picture box and draw it accordingly
StretchDIBits DstPictureBox.hdc, 0, 0, bm.bmWidth, bm.bmHeight, 0, 0, OriginalWidth,
OriginalHeight, ImageData(0, 0), bmi, 0, vbSrcCopy
'Since this doesn't automatically initialize AutoRedraw, we have to do it manually
If DstPictureBox.AutoRedraw = True Then
DstPictureBox.Picture = DstPictureBox.Image
DstPictureBox.Refresh
End If
'Always good to manually halt for external processes after heavy API usage
DoEvents
End Sub

'Get an image's pixel information into an array dimensioned (r/g/b, x, y)


Public Sub GetImageData(SrcPictureBox As PictureBox, ImageData() As Byte)
Dim bm As Bitmap
'Get the picture box information
GetObject SrcPictureBox.Image, Len(bm), bm
'Build a correctly sized array
Erase ImageData()
ReDim ImageData(0 To 2, 0 To bm.bmWidth - 1, 0 To bm.bmHeight - 1)
'Create a temporary header to pass to the GetDIBits call
Dim bmi As BITMAPINFO
bmi.bmHeader.bmWidth = bm.bmWidth
bmi.bmHeader.bmHeight = bm.bmHeight
bmi.bmHeader.bmSize = 40 'Size, in bytes, of the header
bmi.bmHeader.bmPlanes = 1 'Number of planes (always one for this instance)
bmi.bmHeader.bmBitCount = 24 'Bits per pixel (always 24 for this instance)
bmi.bmHeader.bmCompression = 0 'Compression :standard/none or RLE
'Get the image data into our array
GetDIBits SrcPictureBox.hdc, SrcPictureBox.Image, 0, bm.bmHeight, ImageData(0, 0, 0), bmi, 0
End Sub

'Set an image's pixel information from an array dimensioned (r/g/b, x, y)


Public Sub SetImageData(DstPictureBox As PictureBox, OriginalWidth As Long, OriginalHeight As
Long, ImageData() As Byte)
Dim bm As Bitmap
'Get the picture box information
GetObject DstPictureBox.Image, Len(bm), bm
'Create a temporary header to pass to the StretchDIBits call
Dim bmi As BITMAPINFO
bmi.bmHeader.bmWidth = OriginalWidth
bmi.bmHeader.bmHeight = OriginalHeight
bmi.bmHeader.bmSize = 40 'Size, in bytes, of the header
bmi.bmHeader.bmPlanes = 1 'Number of planes (always one for this instance)
bmi.bmHeader.bmBitCount = 24 'Bits per pixel (always 24 for this instance)
bmi.bmHeader.bmCompression = 0 'Compression :standard/none or RLE
'Assume color images and set the corresponding best stretch mode
SetStretchBltMode DstPictureBox.hdc, 3&
'Send the array to the picture box and draw it accordingly
StretchDIBits DstPictureBox.hdc, 0, 0, bm.bmWidth, bm.bmHeight, 0, 0, OriginalWidth,
OriginalHeight, ImageData(0, 0, 0), bmi, 0, vbSrcCopy
'Since this doesn't automatically initialize AutoRedraw, we have to do it manually
If DstPictureBox.AutoRedraw = True Then
DstPictureBox.Picture = DstPictureBox.Image
DstPictureBox.Refresh
End If
'Always good to manually halt for external processes after heavy API usage
DoEvents
End Sub

'Get an image's pixel data into a one-dimesional array (stream)


Public Sub GetImageDataStream(SrcPictureBox As PictureBox, ImageData() As Byte)
Dim bm As Bitmap
'Get the picture box information
GetObject SrcPictureBox.Image, Len(bm), bm
'Build a correctly sized array - in this case, designed as a stream
Erase ImageData()
ReDim ImageData(0 To GetImageStreamLength(SrcPictureBox))
'Create a temporary header to pass to the GetDIBits call
Dim bmi As BITMAPINFO
bmi.bmHeader.bmWidth = bm.bmWidth
bmi.bmHeader.bmHeight = bm.bmHeight
bmi.bmHeader.bmSize = 40 'Size, in bytes, of the header
bmi.bmHeader.bmPlanes = 1 'Number of planes (always one for this instance)
bmi.bmHeader.bmBitCount = 24 'Bits per pixel (always 24 for this instance)
bmi.bmHeader.bmCompression = 0 'Compression :standard/none or RLE
'Get the image data into our array
GetDIBits SrcPictureBox.hdc, SrcPictureBox.Image, 0, bm.bmHeight, ImageData(0), bmi, 0
End Sub

'Set an image's data from a one-dimensional array (stream)


Public Sub SetImageDataStream(DstPictureBox As PictureBox, OriginalWidth As Long, OriginalHeight
As Long, ImageData() As Byte)
Dim bm As Bitmap
'Get the picture box information
GetObject DstPictureBox.Image, Len(bm), bm
'Create a temporary header to pass to the StretchDIBits call
Dim bmi As BITMAPINFO
bmi.bmHeader.bmWidth = OriginalWidth
bmi.bmHeader.bmHeight = OriginalHeight
bmi.bmHeader.bmSize = 40 'Size, in bytes, of the header
bmi.bmHeader.bmPlanes = 1 'Number of planes (always one for this instance)
bmi.bmHeader.bmBitCount = 24 'Bits per pixel (always 24 for this instance)
bmi.bmHeader.bmCompression = 0 'Compression :standard/none or RLE
'Send the array to the picture box and draw it accordingly
StretchDIBits DstPictureBox.hdc, 0, 0, bm.bmWidth, bm.bmHeight, 0, 0, OriginalWidth,
OriginalHeight, ImageData(0), bmi, 0, vbSrcCopy
'Since this doesn't automatically initialize AutoRedraw, we have to do it manually
If DstPictureBox.AutoRedraw = True Then
DstPictureBox.Picture = DstPictureBox.Image
DstPictureBox.Refresh
End If
'Always good to manually halt for external processes after heavy API usage
DoEvents
End Sub

' sample usage


'
'Private Sub Command1_Click()
' Dim bl As CBlackOut
'
' Set bl = New CBlackOut
' bl.spreadOver Me
' MsgBox "This is a message box.", vbInformation
' bl.wipeAway
'End Sub
Private Sub Class_Initialize()

End Sub

Private Sub Class_Terminate()


On Error Resume Next

Set m_picDst = Nothing


Set m_picSrc1 = Nothing
Set m_picSrc2 = Nothing
End Sub

S-ar putea să vă placă și