For those of us that use GDI+, we know that it has a major issue loading bitmaps that contain alpha data. Maybe not a major concern, because GDI basically ignores the alpha channel in most every function in its arsenal. But unfortunately, the GdipGetImageFlags function may not be useful in all cases. What if you render to a DIB and supply a pixel color to be made transparent? Maybe that color exists, maybe not; therefore, maybe transparency exists in the DIB, maybe it doesn't. This routine is not restricted for GDI+ users only. GDI users may find it useful as well.
So, let's say we have access to 32bpp pixel data and want to know if it contains transparency and if so, how is that transparency interpreted. The function below can be of big help. Read the comments I've sprinkled about the function and you should have no issues.
There are very specific, rare cases, when the logic used can fail. Those are addressed in the function's comments. This is a function I plan on using in new projects moving forward. Here are some scenarios that can be avoided. Offer an option to ignore the alpha channel in these cases:
- Steganography: If known to exist & alpha channel used for data only, image will be displayed correctly, but hidden data is lost
- All black image: Image displayed correctly
- VB picture object. Unless known it contains a valid alpha channel, ignore it. VB picture objects can produce dirty alpha channels. VB has no direct support of alpha channels. And unless a valid channel was purposely added to the picture object, it is otherwise invalid.
Simple Transparency as used here. Alpha values are either 0 or 255. Those that are 0 have RGB values also zero. Can also be considered premultiplied RGB compnents against the alpha channel
Complex Transparency as used here. Mix of alpha values that range from 0 to 255. Alpha values of zero can have non-zero RGB values. RGB components may or may not be premultiplied against the alpha channel.
The function is provided below
The declarations are here
Edited: Different interpretations you may want to consider.
1. Let's say you passed mask bits to the function and the function returns acuError. That indicates the mask was interpreted as invalid. This can happen for 3 primary reasons: a) it is invalid, any of the masks use more than 8 bits, b) the R,G,B masks combined use less than 24 bits & no alpha mask provided, leaving the routine to assume the alpha mask uses 9+ bits, or c) the alpha mask spans over one of the other masks. In a really malformatted file, I guess it would be possible to supply a mask for just one component and none for the others. In any of these cases, the likelihood that an alpha channel is used is slim to none. May want to interpret acuError in these cases as acuOpaque or acuOpaqueAssumed. That is my plan.
2. Though acuOpaqueAssumed is not included in the acuMask_AlphaBlendFriendly, this does not mean AlphaBlend cannot be used with the pixel data. acuOpaqueAssumed simply means that the pixel data has all zero alpha values along with non-zero RGB values. Alphablend can be used as long as the blend function of that API doesn't include the alpha channel (AC_SRC_ALPHA)
3. Interpreting acuAllBlack depends on whether it is expected or not. Is it possible to create a 100% transparent image? Sure. Can an all black 32bpp image exist? Sure. Are either any use? Highly doubtful. But maybe your app wants an invisible image to be applied to some control? Maybe acuAllBlack can indicate a empty DIB (no image data)? If acuAllBlack is unexpected, really a simple decision: is it better to display an invisible image or a black image or report it as 'invalid'? Your choice
Just FYI: If you don't care how the alpha channel is used, only that it is used, then you can create your own function that would be extremely fast. And it is easy to do. Simply look at the alpha channel only and it should be in use if one of these conditions apply. Once known, abort your loop.
a. Any alpha value is in the range: 1-254 inclusively
b. Any mix of 0 & 255 alpha values. Assumption: All zero alpha values <> 100% transparent image
Pseudo-code follows. Same gotchas apply as above, i.e., steganography, dirty alpha channel, etc.
So, let's say we have access to 32bpp pixel data and want to know if it contains transparency and if so, how is that transparency interpreted. The function below can be of big help. Read the comments I've sprinkled about the function and you should have no issues.
There are very specific, rare cases, when the logic used can fail. Those are addressed in the function's comments. This is a function I plan on using in new projects moving forward. Here are some scenarios that can be avoided. Offer an option to ignore the alpha channel in these cases:
- Steganography: If known to exist & alpha channel used for data only, image will be displayed correctly, but hidden data is lost
- All black image: Image displayed correctly
- VB picture object. Unless known it contains a valid alpha channel, ignore it. VB picture objects can produce dirty alpha channels. VB has no direct support of alpha channels. And unless a valid channel was purposely added to the picture object, it is otherwise invalid.
Simple Transparency as used here. Alpha values are either 0 or 255. Those that are 0 have RGB values also zero. Can also be considered premultiplied RGB compnents against the alpha channel
Complex Transparency as used here. Mix of alpha values that range from 0 to 255. Alpha values of zero can have non-zero RGB values. RGB components may or may not be premultiplied against the alpha channel.
The function is provided below
Code:
Public Function ValidateAlphaChannelEx( _
ByVal PixelPointer As Long, _
ByVal PixelCount As Long, _
Optional ByVal MaskPointer As Long, _
Optional ByVal MaskCount As Long) As AlphaChannelUsage
' Method determines if the alhpa channel is used and how it is used
' Only supports 32 bpp pixel data. Passing any other format will result in a crash
' Assumption is that you will only call this routine to test 32 bpp data
' Notes:
' 1. If function returns values less than 2 (acuOpaque). The result should be handled manually:
' - acError indicates bad mask information passed
' - acuAllBlack indicates all color values are exactly zero. 100% transparent or 100% black?
' - acuOpaqueAssumed indicates all alpha values are zero, but all RGB values are not zero
' 2. If dirty alpha values are passed, the return value may not be valid. Dirty alpha
' values can occur when images are drawn on a 32bpp surface and the alpha bytes are
' ignored. Can also occur if steganography is used in the image and the alpha byte
' is used for that purpose.
' 3. It is possible that acuPremultipliedRGB can be wrong in a specific scenario: every RGB
' component is less than it's alpha value on purpose but the image's RGB components
' were NOT premultiplied against the alpha values. This specific case should be very
' rare and the routine assumes premultiplication, as no way of knowing thru code
' Parameters...
' PixelPointer :: i.e., VarPtr(pixelArray(0)), pointer returned from GdipBitmapLockBits, CreateDIBSection
' Note: The pixel data pointed to by PixelPointer must be 32 bit per pixel format
' and the pixel data must be contiguous from PixelPointer to PixelPointer+PixelCount-1
' the stride must be positive not negative. If negative, ensure pointer adjusted for a
' positive stride. Function does not care if pixel data is right-side up or not
' PixelCount :: amount of pixel data to process, i.e., Width * Height
' MaskPointer :: optional and if not provided, bytes are assumed to be in DIB format
' Note: BitmapInfoHeader & its later versions allow masks to be included
' If provided, a minimum of 3 masks (R,G,B) expected and maximum of 4 masks (Alpha)
' Expect the pointer to the masks to be consecutive 4 byte values: R,G,B,Alpha
' MaskCount :: must be one of these values: 0, 3, 4
' Mask information is generally valid only if the image has not yet been loaded into a GDI
' bitmap/DIB or a GDI+ image object, i.e., you are manually parsing a bitmap file.
' If it has already been loaded correctly, then the format of the PixelPointer you passed
' will already be in what this routine considers default:
' Defaults: Red=&HFF0000, Green=&HFF00, Blue=&HFF, Alpha=&HFF000000
' Unless masks use less than 8 bits each, the only important mask is the Alpha mask, the
' routine below does not care if pixel format is RGB,BGR,GBR,GRB,etc
ValidateAlphaChannelEx = acuError ' default return value
If PixelPointer = 0& Or PixelCount < 1& Then Exit Function
Dim lMasks(0 To 3) As Long, lShifts(0 To 3) As Long ' BGRA masks
Dim lPtr As Long, bAlpha As Long, lFormat As Long
Dim lColor As Long, lPrevColor As Long
Dim bData() As Long, tSA As SafeArray
Const ZEROES As Long = 256&
' ///// Step 1: validate passed masks are valid and/or apply default masks
If MaskPointer Then
If (MaskCount = 3& Or MaskCount = 4&) Then
CopyMemory lMasks(0), ByVal MaskPointer, MaskCount * 4& ' get RGB masks
lColor = (lMasks(0) Or lMasks(1) Or lMasks(2)) ' see if any are actually set
If lColor Then
If lMasks(3) = 0& Then ' apply default alpha if needed
lMasks(3) = lColor Xor -1&
ElseIf (lMasks(3) And lColor) Then ' see if alpha overlaps RGB mask
Exit Function
End If
End If
End If
End If
' if no mask information provided, default values will be used
If lColor = 0& Then
lMasks(0) = &HFF0000: lMasks(1) = &HFF00&: lMasks(2) = &HFF: lMasks(3) = &HFF000000
End If
For lPtr = 0& To 3& ' validate masks within 8 bit boundary
lShifts(lPtr) = lMasks(lPtr) And -lMasks(lPtr)
If ((lMasks(lPtr) \ lShifts(lPtr)) And &HFF) > 255 Then Exit Function ' invalid mask
Next
' ///// Step 2: setup an overlay onto the passed pixel pointer
With tSA
.cbElements = 4&
.cDims = 1
.pvData = PixelPointer
.pvBounds.cElements = PixelCount
End With
CopyMemory ByVal VarPtrArray(bData), VarPtr(tSA), 4&
On Error GoTo ExitRoutine
' ///// Step 3: test the alpha channel
lPrevColor = bData(0) Xor 1& ' force a no-match at start of loop
For lPtr = 0& To PixelCount - 1&
lColor = bData(lPtr) ' get 32bit color
If Not lColor = lPrevColor Then ' and extact the alpha byte
If lColor = 0& Then
lFormat = lFormat Or ZEROES ' entire value is zero
' all zeroes indicates 100% transparent or 100% black image
' mix of zero & non-zero alpha values indicates transparency
Else
bAlpha = (lColor And lMasks(3)) \ lShifts(3) And &HFF
If bAlpha = 0& Then
If (lColor And Not lMasks(3)) Then ' RGB value is non-zero
If (lFormat And Not ZEROES) > acuOpaque Then
' at least one other alpha value was > 0 and < 255
' since this alpha is zero & RGB non-zero. Done:
lFormat = acuComplexTransparency: Exit For
End If
lFormat = lFormat Or acuOpaqueAssumed ' keep going, maybe all alphas are zero
End If
ElseIf bAlpha = 255& Then
If (lFormat And acuOpaqueAssumed) Then
' already seen alpha zero & non-zero RGB. Here we have 255 alpha. Done:
lFormat = acuComplexTransparency: Exit For
End If
lFormat = lFormat Or acuOpaque
' else if any RGB values > alpha then not-premultiplied
ElseIf bAlpha < (lColor And lMasks(0)) \ lShifts(0) And &HFF Then
lFormat = acuComplexTransparency: Exit For ' definitly ARGB
ElseIf bAlpha < (lColor And lMasks(2)) \ lShifts(2) And &HFF Then
lFormat = acuComplexTransparency: Exit For ' definitly ARGB
ElseIf bAlpha < (lColor And lMasks(1)) \ lShifts(1) And &HFF Then
lFormat = acuComplexTransparency: Exit For ' definitly ARGB
Else
lFormat = lFormat Or acuPremultipliedRGB ' likely pARGB, but not sure yet
End If
End If
lPrevColor = lColor
End If
Next
' ///// Step 4: Analyze result
If (lFormat And acuPremultipliedRGB) Then
ValidateAlphaChannelEx = acuPremultipliedRGB
ElseIf lFormat = ZEROES Then
ValidateAlphaChannelEx = acuAllBlack
ElseIf lFormat = (ZEROES Or acuOpaque) Then
ValidateAlphaChannelEx = acuSimpleTransparency
Else
ValidateAlphaChannelEx = (lFormat And Not ZEROES)
End If
ExitRoutine:
' ///// Step 5: Clean up
CopyMemory ByVal VarPtrArray(bData), 0&, 4&
End Function
Code:
Private Declare Function VarPtrArray Lib "msvbvm60.dll" Alias "VarPtr" (ByRef ptr() As Any) As Long
Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (ByRef Destination As Any, ByRef Source As Any, ByVal length As Long)
Private Type SafeArrayBound ' OLE structure
cElements As Long
lLbound As Long
End Type
Private Type SafeArray
cDims As Integer
fFeatures As Integer
cbElements As Long
cLocks As Long
pvData As Long
pvBounds As SafeArrayBound ' single dimension usage
End Type
Public Enum AlphaChannelUsage
acuError = &H80000000 ' invalid Mask information passed to ValidateAlphaChannelEx
acuAllBlack = 0 ' image can be interpreted as 100% black or 100% transparent
acuOpaqueAssumed = 1 ' all alpha values are zero, assuming image is not meant to be 100% transparent
acuOpaque = 2 ' alpha channel is used, but all alpha values are 255
acuSimpleTransparency = 4 ' alpha channel is used and contains simple transparency only
acuComplexTransparency = 8 ' alpha channel is used and contains complex transparency
acuPremultipliedRGB = 16 ' R,G,B components are multiplied against the alpha channel
acuMask_HasTransparency = acuSimpleTransparency Or acuComplexTransparency Or acuPremultipliedRGB
acuMask_AlphaBlendFriendly = acuOpaque Or acuSimpleTransparency Or acuPremultipliedRGB
acuMask_Opaque = acuOpaque Or acuOpaqueAssumed
End Enum
1. Let's say you passed mask bits to the function and the function returns acuError. That indicates the mask was interpreted as invalid. This can happen for 3 primary reasons: a) it is invalid, any of the masks use more than 8 bits, b) the R,G,B masks combined use less than 24 bits & no alpha mask provided, leaving the routine to assume the alpha mask uses 9+ bits, or c) the alpha mask spans over one of the other masks. In a really malformatted file, I guess it would be possible to supply a mask for just one component and none for the others. In any of these cases, the likelihood that an alpha channel is used is slim to none. May want to interpret acuError in these cases as acuOpaque or acuOpaqueAssumed. That is my plan.
2. Though acuOpaqueAssumed is not included in the acuMask_AlphaBlendFriendly, this does not mean AlphaBlend cannot be used with the pixel data. acuOpaqueAssumed simply means that the pixel data has all zero alpha values along with non-zero RGB values. Alphablend can be used as long as the blend function of that API doesn't include the alpha channel (AC_SRC_ALPHA)
3. Interpreting acuAllBlack depends on whether it is expected or not. Is it possible to create a 100% transparent image? Sure. Can an all black 32bpp image exist? Sure. Are either any use? Highly doubtful. But maybe your app wants an invisible image to be applied to some control? Maybe acuAllBlack can indicate a empty DIB (no image data)? If acuAllBlack is unexpected, really a simple decision: is it better to display an invisible image or a black image or report it as 'invalid'? Your choice
Just FYI: If you don't care how the alpha channel is used, only that it is used, then you can create your own function that would be extremely fast. And it is easy to do. Simply look at the alpha channel only and it should be in use if one of these conditions apply. Once known, abort your loop.
a. Any alpha value is in the range: 1-254 inclusively
b. Any mix of 0 & 255 alpha values. Assumption: All zero alpha values <> 100% transparent image
Pseudo-code follows. Same gotchas apply as above, i.e., steganography, dirty alpha channel, etc.
Code:
Dim bSimple As Byte, p As Long
For p = 0 To [nrPixels] - 1
... extract AlphaValue with appropriate mask (if applicable)
Select Case [AlphaValue]
Case 0: If (bSimple And 2) Then Exit For
bSimple = bSimple Or 1
Case 255: If (bSimple And 1) Then Exit For
bSimple = bSimple Or 2
Case Else: Exit For
End Select
Next p
If p = [nrPixels] Then ' no alpha else alpha is used