cBMPparser.cls
上传用户:jnjasmy
上传日期:2015-01-04
资源大小:637k
文件大小:14k
源码类别:

GDI/图象编程

开发平台:

Visual Basic

  1. VERSION 1.0 CLASS
  2. BEGIN
  3.   MultiUse = -1  'True
  4.   Persistable = 0  'NotPersistable
  5.   DataBindingBehavior = 0  'vbNone
  6.   DataSourceBehavior  = 0  'vbNone
  7.   MTSTransactionMode  = 0  'NotAnMTSObject
  8. END
  9. Attribute VB_Name = "cBMPparser"
  10. Attribute VB_GlobalNameSpace = False
  11. Attribute VB_Creatable = True
  12. Attribute VB_PredeclaredId = False
  13. Attribute VB_Exposed = False
  14. Option Explicit
  15. ' No APIs are declared public. This is to prevent possibly, differently
  16. ' declared APIs, or different versions of the same API, from conflciting
  17. ' with any APIs you declared in your project. Same rule for UDTs.
  18. Private Type SafeArrayBound
  19.     cElements As Long
  20.     lLbound As Long
  21. End Type
  22. Private Type SafeArray
  23.     cDims As Integer
  24.     fFeatures As Integer
  25.     cbElements As Long
  26.     cLocks As Long
  27.     pvData As Long
  28.     rgSABound(0 To 1) As SafeArrayBound ' reusable UDT for 1 & 2 dim arrays
  29. End Type
  30. Private Type BITMAP
  31.     bmType As Long
  32.     bmWidth As Long
  33.     bmHeight As Long
  34.     bmWidthBytes As Long
  35.     bmPlanes As Integer
  36.     bmBitsPixel As Integer
  37.     bmBits As Long
  38. End Type
  39. Private Type BITMAPINFOHEADER
  40.     biSize As Long
  41.     biWidth As Long         ' +4 from .biSize
  42.     biHeight As Long        ' +8
  43.     biPlanes As Integer     ' +12
  44.     biBitCount As Integer   ' +14
  45.     biCompression As Long   ' +16
  46.     biSizeImage As Long     ' +20
  47.     biXPelsPerMeter As Long ' +24
  48.     biYPelsPerMeter As Long ' +28
  49.     biClrUsed As Long       ' +32
  50.     biClrImportant As Long  ' 40th byte
  51. End Type
  52. Private Type BITMAPINFO
  53.     bmiHeader As BITMAPINFOHEADER
  54.     bmiPalette As Long
  55. End Type
  56. ' used to transfer a stdPicture bmp,jpg,wmf to a DIB
  57. Private Declare Function GetGDIObject Lib "gdi32.dll" Alias "GetObjectA" (ByVal hObject As Long, ByVal nCount As Long, ByRef lpObject As Any) As Long
  58. Private Declare Function VarPtrArray Lib "msvbvm60.dll" Alias "VarPtr" (Ptr() As Any) As Long
  59. Private Declare Function GetDC Lib "user32.dll" (ByVal hwnd As Long) As Long
  60. Private Declare Function ReleaseDC Lib "user32.dll" (ByVal hwnd As Long, ByVal hDC As Long) As Long
  61. Private Declare Sub FillMemory Lib "kernel32.dll" Alias "RtlFillMemory" (ByRef Destination As Any, ByVal Length As Long, ByVal Fill As Byte)
  62. Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" (ByRef Destination As Any, ByRef Source As Any, ByVal Length As Long)
  63. Private Declare Function CreateCompatibleDC Lib "gdi32.dll" (ByVal hDC As Long) As Long
  64. Private Declare Function DeleteDC Lib "gdi32.dll" (ByVal hDC As Long) As Long
  65. Private Declare Function SelectObject Lib "gdi32.dll" (ByVal hDC As Long, ByVal hObject As Long) As Long
  66. 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
  67. Private Declare Function GetDIBits Lib "gdi32.dll" (ByVal aHDC As Long, ByVal hBitmap As Long, ByVal nStartScan As Long, ByVal nNumScans As Long, ByRef lpBits As Any, ByRef lpBI As BITMAPINFO, ByVal wUsage As Long) As Long
  68. Public Function LoadStream(inStream() As Byte, cHost As c32bppDIB, _
  69.                             Optional ByVal streamOffset As Long = 0, _
  70.                             Optional ByVal streamLength As Long = 0) As Boolean
  71.     ' PURPOSE: Test passed stream for being a 32bpp bitmap.
  72.     ' If not 32bpp, then the stream is converted to a stdPicture and the contents
  73.     ' of that object are drawn to the 32bpp.
  74.     
  75.     ' With the exception of wmf, emf & 32bpp. This class does not handle transparency.
  76.     ' Therefore, the stream should have been passed to the png, gif & icon parsers
  77.     ' first.
  78.     
  79.     ' Parameters.
  80.     ' inStream() :: the byte array containing the image
  81.     ' cHost :: an initialized c32bppDIB
  82.     ' streamOffset :: array position for 1st byte in the stream
  83.     ' streamLength :: size of stream that contains the image
  84.     '   - If zero, then size is UBound(inStream)-streamOffset+1
  85.     
  86.     ' IMPORTANT: the array offset & length are not checked in this class.
  87.     '   They were checked before this class was called. If this class is to
  88.     '   be pulled out and put in another project, ensure you include the
  89.     '   validation shown in c32bppDIB.LoadPicture_Stream
  90.     
  91.     Dim lValue As Long, iValue As Integer
  92.     Dim x As Long, y As Long, lScanWidth As Long
  93.     Dim Offset As Long, iBitCount As Integer
  94.     Dim aDIB() As Byte, tSA As SafeArray
  95.     Dim bAlpha As Boolean
  96.     
  97.     ' manually parse the bitmap header.
  98.     ' Why? because VB's LoadPicture will convert the image into a screen
  99.     ' compatible bitmap; where if screen resolution was less than true color,
  100.     ' a 32bpp image would end up being 24bp or less vs 32bpp
  101.     CopyMemory iValue, inStream(streamOffset), 2&   ' get 1st 2 bytes of the stream
  102.     If iValue = &H4D42 Then                         ' is it a bmp magic number
  103.         CopyMemory iBitCount, inStream(streamOffset + 28), 2& ' bit count
  104.         CopyMemory x, inStream(streamOffset + 18), 4& ' width
  105.         CopyMemory y, inStream(streamOffset + 22), 4& ' height
  106.         
  107.         ' validate size
  108.         ' width must be at least 1 pixel & height must be a least 1 pixel
  109.         If x < 1 Or y = 0& Then Exit Function ' -Y indicates top down DIB
  110.         
  111.         On Error Resume Next
  112.         CopyMemory Offset, inStream(streamOffset + 10), 4& ' start of image
  113.         ' validate enough bytes exist for the image
  114.         lValue = (streamOffset + streamLength) - (iparseByteAlignOnWord(iBitCount, x) * Abs(y) + Offset)
  115.         If Err Then     ' should some overflow occur
  116.             Err.Clear
  117.             lValue = -1&
  118.         End If
  119.         If lValue >= 0& Then              ' is array big enough?
  120.             If iBitCount = 32 Then       ' else we will allow VB to convert it for us
  121.                                          ' because it doesn't contain transparency anyway
  122.                 CopyMemory lValue, inStream(streamOffset + 30&), 4& ' compression
  123.                 If lValue = 0& Then         ' manually handle no-compression bitmaps
  124.                                             ' else allow VB to convert the bitmap
  125.                     cHost.InitializeDIB x, Abs(y)
  126.                     With tSA
  127.                         .cbElements = 1
  128.                         .cDims = 2
  129.                         .pvData = cHost.BitsPointer
  130.                         .rgSABound(0).cElements = cHost.Height
  131.                         .rgSABound(1).cElements = cHost.scanWidth
  132.                     End With
  133.                     CopyMemory ByVal VarPtrArray(aDIB), VarPtr(tSA), 4&
  134.                     
  135.                     lScanWidth = cHost.scanWidth
  136.                     If y < 0& Then ' the dib is top down vs bottom up
  137.                         ' flip the DIB
  138.                         y = -y
  139.                         For lValue = 0& To y - 1&
  140.                             ' start of scan line in source image
  141.                             x = lScanWidth * (y - lValue - 1&) + Offset
  142.                             ' copy to upside down scan line on our DIB
  143.                             CopyMemory aDIB(0&, lValue), inStream(x), lScanWidth
  144.                         Next
  145.                     Else    ' bottom up dib; simply copy bits
  146.                         CopyMemory ByVal cHost.BitsPointer, inStream(streamOffset + Offset), cHost.Height * lScanWidth
  147.                     End If
  148.                     
  149.                     ' see if 32bpp is premulitplied or not
  150.                     iparseValidateAlphaChannel aDIB(), True, bAlpha, lValue
  151.                     CopyMemory ByVal VarPtrArray(aDIB), 0&, 4& ' remove overlay
  152.                     ' set other properties
  153.                     cHost.Alpha = bAlpha
  154.                     cHost.ImageType = lValue
  155.                     LoadStream = True
  156.                 End If
  157.             End If
  158.             
  159.         End If
  160.     End If
  161.     On Error GoTo 0
  162.     
  163.     If cHost.Handle = 0& Then ' we didn't process the image above, try VB's LoadPicture
  164.     
  165.         On Error Resume Next
  166.         Dim tPic As StdPicture
  167.         Set tPic = iparseArrayToPicture(inStream(), streamOffset, streamLength)
  168.         If Err Then
  169.             Err.Clear
  170.         Else
  171.             LoadStream = ConvertstdPicTo32bpp(tPic, 0&, cHost, iBitCount)
  172.         End If
  173.     
  174.     End If
  175. End Function
  176. Public Function ConvertstdPicTo32bpp(stdPic As StdPicture, ByVal Handle As Long, cHost As c32bppDIB, ByVal bitCount As Integer) As Boolean
  177.     ' stdPic is passed from cHost.LoadPicture_StdPicture and Handle=0&
  178.     '   in this case stdPic can be a bmp, jpg, gif, wmf, emf
  179.     ' Handle is passed from chost.LoadPicture_ByHandle and stdPic is Nothing
  180.     '   in this case, Handle only references a bitmap
  181.     Dim tSA As SafeArray, tObj As BITMAP, tBMPI As BITMAPINFO
  182.     Dim cX As Long, cY As Long
  183.     Dim tDC As Long, bAlpha As Boolean, iType As Long
  184.     Dim aDIB() As Byte
  185.     Dim bmpDC As Long, bmpOld As Long
  186.     If stdPic Is Nothing Then
  187.         If Handle = 0& Then Exit Function ' couldn't convert image
  188.         If GetGDIObject(Handle, Len(tObj), tObj) = 0& Then Exit Function
  189.         cX = tObj.bmWidth
  190.         cY = Abs(tObj.bmHeight)
  191.     ElseIf stdPic.Type = vbPicTypeNone Then
  192.         Exit Function
  193.     Else
  194.         ' get the picture's width & height & initialize DIB
  195.         cX = ConvertHimetrix2Pixels(stdPic.Width, True)
  196.         cY = ConvertHimetrix2Pixels(stdPic.Height, False)
  197.         Handle = 0&
  198.     End If
  199.     
  200.     cHost.InitializeDIB cX, cY
  201.     tDC = cHost.LoadDIBinDC(True)
  202.     
  203.     ' WMF/EMFs are kinda weird, but here is a neat trick to determine if it
  204.     ' has transparency. Fill the entire image with white, then when it is
  205.     ' rendered, any "transparent" areas were not drawn over, left the
  206.     ' alpha byte as 255. Those areas that are drawn over are changed to zero.
  207.     If Handle = 0& Then
  208.         If stdPic.Type = vbPicTypeEMetafile Or stdPic.Type = vbPicTypeMetafile Then
  209.             FillMemory ByVal cHost.BitsPointer, cY * cHost.scanWidth, 255
  210.         End If
  211.     
  212.         ' render the stdPic to the host's dc
  213.         stdPic.Render tDC + 0&, 0&, 0&, cX + 0&, cY + 0&, _
  214.             0, stdPic.Height, stdPic.Width, -stdPic.Height, ByVal 0&
  215.     Else
  216.         ' bitmap checks. Here we can process a 32bpp bitmap loaded into a stdPicture
  217.         ' or loaded from LoadImage API with full confidence if carrying over alpha
  218.         If tObj.bmBitsPixel = 32 Then       ' if image is 32bpp then
  219.             If tObj.bmBits = 0& Then        ' allow GetDIBits to transfer for us
  220.                 With tBMPI.bmiHeader
  221.                     .biBitCount = 32
  222.                     .biHeight = cY
  223.                     .biWidth = cX
  224.                     .biPlanes = 1
  225.                     .biSize = 40
  226.                 End With
  227.                 If GetDIBits(tDC, Handle, 0, tBMPI.bmiHeader.biHeight, ByVal cHost.BitsPointer, tBMPI, 0) = 0 Then
  228.                     tObj.bmBitsPixel = 0&   ' flag to allow BitBlt when this failed
  229.                 End If
  230.             Else                ' if we have a bits pointer, simply copy data
  231.                 CopyMemory ByVal cHost.BitsPointer, ByVal tObj.bmBits, tObj.bmWidthBytes * tObj.bmHeight
  232.             End If
  233.         End If
  234.         If Not tObj.bmBitsPixel = 32& Then          ' use BitBlt
  235.             bmpDC = CreateCompatibleDC(tDC)         ' create a dc & blt, image is not 32bpp
  236.             bmpOld = SelectObject(bmpDC, Handle)
  237.             BitBlt tDC, 0, 0, cX, cY, bmpDC, 0, 0, vbSrcCopy
  238.             SelectObject bmpDC, bmpOld
  239.             DeleteDC bmpDC
  240.         End If
  241.     End If
  242.     ' unmanage the DC if needed
  243.     cHost.LoadDIBinDC False
  244.     
  245.     ' map our array to the host's DIB
  246.     With tSA
  247.         .cbElements = 1 ' as byte array
  248.         .cDims = 2      ' as 1 dimensional
  249.         .pvData = cHost.BitsPointer
  250.         .rgSABound(0).cElements = cY
  251.         .rgSABound(1).cElements = cHost.scanWidth
  252.     End With
  253.     CopyMemory ByVal VarPtrArray(aDIB), VarPtr(tSA), 4& ' apply overlay
  254.     
  255.     If Handle = 0& Then  ' processing wmf, emf
  256.         If stdPic.Type = vbPicTypeEMetafile Or stdPic.Type = vbPicTypeMetafile Then
  257.             ' as mentioned above, any transparent pixels will have alpha value = 255
  258.             For cY = 0& To cHost.Height - 1&
  259.                 For cX = 3& To cHost.scanWidth - 1& Step 4&
  260.                     If aDIB(cX, cY) = 255 Then    ' 100% transparent
  261.                         CopyMemory aDIB(cX - 3&, cY), 0&, 4& ' make bits transparent
  262.                         bAlpha = True
  263.                     Else                        ' 100% opaque
  264.                         aDIB(cX, cY) = 255 ' was 255, now 0, change back to 255
  265.                     End If
  266.                 Next
  267.             Next
  268.         Else    ' jpg or non-alpha bitmap; should no longer get here.
  269.                 ' Most recent update should pass non-wmf/emf by Handle vs stdPicture object
  270.             ' validate first that it has no alpha bytes
  271.             If bitCount = 0 Then
  272.                 ' when called from cHost.LoadPicture_Resource then no BitCount is known
  273.                 Dim tBMP As BITMAP
  274.                 GetGDIObject stdPic.Handle, Len(tBMP), tBMP
  275.                 bitCount = tBMP.bmBitsPixel
  276.             End If
  277.             ' Note: I have experienced 32bpp & 24bpp stdPicture.Rendering onto a 32bpp DIB
  278.             ' and writing in the alpha channel. These stdPictures did not use an alpha
  279.             ' channel, and this is a bug of some sort with stdPicture or VB not fully
  280.             ' supporting 32bpp DIBs.  The -1& below forces next routine to fill the
  281.             ' alpha channel with 255 cHost.ImageType = vbPicTypeBitmap
  282.             iparseValidateAlphaChannel aDIB(), True, False, -1&
  283.         End If
  284.         iType = stdPic.Type
  285.     ElseIf tObj.bmBitsPixel = 32& Then
  286.         iparseValidateAlphaChannel aDIB(), True, bAlpha, iType
  287.     Else
  288.         iparseValidateAlphaChannel aDIB(), True, False, -1&
  289.         iType = imgBitmap
  290.     End If
  291.     CopyMemory ByVal VarPtrArray(aDIB), 0&, 4&  ' remove overlay
  292.     cHost.Alpha = bAlpha
  293.     cHost.ImageType = iType
  294.     ConvertstdPicTo32bpp = True
  295. End Function
  296. Private Function ConvertHimetrix2Pixels(vHiMetrix As Long, Horizontally As Boolean) As Long
  297.     ' conversion from Himetrics to Pixels when ScaleX/Y is not available
  298.     If Horizontally Then
  299.         ConvertHimetrix2Pixels = vHiMetrix * 1440 / 2540 / Screen.TwipsPerPixelX
  300.     Else
  301.         ConvertHimetrix2Pixels = vHiMetrix * 1440 / 2540 / Screen.TwipsPerPixelY
  302.     End If
  303. End Function