home *** CD-ROM | disk | FTP | other *** search
/ Planet Source Code Jumbo …e CD Visual Basic 1 to 7 / 5_2007-2008.ISO / data / Zips / Multiple_C208148912007.psc / MyCapture / Client / cDIBSection.cls < prev    next >
Text File  |  2003-11-12  |  21KB  |  597 lines

  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 = "cDIBSection"
  10. Attribute VB_GlobalNameSpace = False
  11. Attribute VB_Creatable = True
  12. Attribute VB_PredeclaredId = False
  13. Attribute VB_Exposed = False
  14. Option Explicit
  15.  
  16.  
  17. Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" ( _
  18.     lpvDest As Any, lpvSource As Any, ByVal cbCopy As Long)
  19.  
  20. Private Type SAFEARRAYBOUND
  21.     cElements As Long
  22.     lLbound As Long
  23. End Type
  24. Private Type SAFEARRAY2D
  25.     cDims As Integer
  26.     fFeatures As Integer
  27.     cbElements As Long
  28.     cLocks As Long
  29.     pvData As Long
  30.     Bounds(0 To 1) As SAFEARRAYBOUND
  31. End Type
  32. Private Declare Function VarPtrArray Lib "msvbvm50.dll" Alias "VarPtr" (Ptr() As Any) As Long
  33.  
  34. Private Type RGBQUAD
  35.     rgbBlue As Byte
  36.     rgbGreen As Byte
  37.     rgbRed As Byte
  38.     rgbReserved As Byte
  39. End Type
  40. Private Type BITMAPINFOHEADER '40 bytes
  41.     biSize As Long
  42.     biWidth As Long
  43.     biHeight As Long
  44.     biPlanes As Integer
  45.     biBitCount As Integer
  46.     biCompression As Long
  47.     biSizeImage As Long
  48.     biXPelsPerMeter As Long
  49.     biYPelsPerMeter As Long
  50.     biClrUsed As Long
  51.     biClrImportant As Long
  52. End Type
  53. Private Type BITMAPINFO
  54.     bmiHeader As BITMAPINFOHEADER
  55.     bmiColors As RGBQUAD
  56. End Type
  57. Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long
  58. Private Declare Function CreateDCAsNull Lib "gdi32" Alias "CreateDCA" (ByVal lpDriverName As String, lpDeviceName As Any, lpOutput As Any, lpInitData As Any) As Long
  59. Private Declare Function GetDesktopWindow Lib "user32" () As Long
  60. ' Note - this is not the declare in the API viewer - modify lplpVoid to be
  61. ' Byref so we get the pointer back:
  62. Private Declare Function CreateDIBSection Lib "gdi32" _
  63.     (ByVal hdc As Long, _
  64.     pBitmapInfo As BITMAPINFO, _
  65.     ByVal un As Long, _
  66.     lplpVoid As Long, _
  67.     ByVal handle As Long, _
  68.     ByVal dw As Long) As Long
  69. Private Declare Function BitBlt Lib "gdi32" (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
  70. Private Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long
  71. Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
  72. Private Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long
  73. Private Declare Function LoadImage Lib "user32" Alias "LoadImageA" (ByVal hInst As Long, ByVal lpsz As String, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As Long
  74. Private Const BI_RGB = 0&
  75. Private Const BI_RLE4 = 2&
  76. Private Const BI_RLE8 = 1&
  77. Private Const DIB_RGB_COLORS = 0 '  color table in RGBs
  78.  
  79. Private Type BITMAP
  80.     bmType As Long
  81.     bmWidth As Long
  82.     bmHeight As Long
  83.     bmWidthBytes As Long
  84.     bmPlanes As Integer
  85.     bmBitsPixel As Integer
  86.     bmBits As Long
  87. End Type
  88. Private Declare Function GetObjectAPI Lib "gdi32" Alias "GetObjectA" (ByVal hObject As Long, ByVal nCount As Long, lpObject As Any) As Long
  89. Private Declare Function timeGetTime Lib "winmm.dll" () As Long
  90. Private Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
  91.  
  92. ' Clipboard functions:
  93. Private Declare Function OpenClipboard Lib "user32" (ByVal hwnd As Long) As Long
  94. Private Declare Function CloseClipboard Lib "user32" () As Long
  95. Private Declare Function SetClipboardData Lib "user32" (ByVal wFormat As Long, ByVal hMem As Long) As Long
  96. Private Declare Function EmptyClipboard Lib "user32" () As Long
  97. Private Const CF_BITMAP = 2
  98. Private Const CF_DIB = 8
  99.  
  100. Private Const BITMAPTYPE As Integer = &H4D42
  101. Private Type BITMAPFILEHEADER
  102.    bfType As Integer '- type  ="BM" i.e &H4D42 - 2
  103.    bfSize As Long ' - size in bytes of file - 6
  104.    bfReserved1 As Integer ' - reserved, must be 0 - 8
  105.    bfReserved2 As Integer ' - reserved, must be 0 - 10
  106.    bfOffBits As Long ' offset from this structure to the bitmap bits - 14
  107. End Type
  108.  
  109. Private Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
  110. Private Declare Function ReadFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Any) As Long
  111. Private Declare Function WriteFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, lpOverlapped As Any) As Long
  112. Private Declare Function SetFilePointer Lib "kernel32" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
  113. Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
  114. Private Const INVALID_HANDLE_VALUE = -1
  115. Private Const CREATE_ALWAYS = 2
  116. Private Const GENERIC_READ = &H80000000
  117. Private Const GENERIC_WRITE = &H40000000
  118. Private Const FILE_ATTRIBUTE_ARCHIVE = &H20
  119. Private Const FILE_ATTRIBUTE_COMPRESSED = &H800
  120. Private Const FILE_ATTRIBUTE_DIRECTORY = &H10
  121. Private Const FILE_ATTRIBUTE_HIDDEN = &H2
  122. Private Const FILE_ATTRIBUTE_NORMAL = &H80
  123. Private Const FILE_ATTRIBUTE_READONLY = &H1
  124. Private Const FILE_ATTRIBUTE_SYSTEM = &H4
  125. Private Const FILE_ATTRIBUTE_TEMPORARY = &H100
  126. Private Const FILE_BEGIN = 0
  127. Private Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long
  128. Private Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
  129. Private Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long
  130. Private Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long
  131. Private Const GMEM_FIXED = &H0
  132. Private Const GMEM_ZEROINIT = &H40
  133. Private Const GPTR = (GMEM_FIXED Or GMEM_ZEROINIT)
  134. Private Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H100
  135. Private Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H2000
  136. Private Const FORMAT_MESSAGE_FROM_HMODULE = &H800
  137. Private Const FORMAT_MESSAGE_FROM_STRING = &H400
  138. Private Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
  139. Private Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200
  140. Private Const FORMAT_MESSAGE_MAX_WIDTH_MASK = &HFF
  141. Private Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" (ByVal dwFlags As Long, lpSource As Any, ByVal dwMessageId As Long, ByVal dwLanguageId As Long, ByVal lpBuffer As String, ByVal nSize As Long, Arguments As Long) As Long
  142.  
  143.  
  144. ' Handle to the current DIBSection:
  145. Private m_hDIb As Long
  146. ' Handle to the old bitmap in the DC, for clear up:
  147. Private m_hBmpOld As Long
  148. ' Handle to the Device context holding the DIBSection:
  149. Private m_hDC As Long
  150. ' Address of memory pointing to the DIBSection's bits:
  151. Private m_lPtr As Long
  152. ' Type containing the Bitmap information:
  153. Private m_tBI As BITMAPINFO
  154.  
  155.  
  156. Public Function CopyToClipboard( _
  157.         Optional ByVal bAsDIB As Boolean = True _
  158.     ) As Boolean
  159. Dim lhDCDesktop As Long
  160. Dim lHDC As Long
  161. Dim lhBmpOld As Long
  162. Dim hObj As Long
  163. Dim lFmt As Long
  164. Dim b() As Byte
  165. Dim tBI As BITMAPINFO
  166. Dim lptr As Long
  167. Dim hDibCopy As Long
  168.  
  169.    lhDCDesktop = CreateDCAsNull("DISPLAY", ByVal 0&, ByVal 0&, ByVal 0&)
  170.     If (lhDCDesktop <> 0) Then
  171.         lHDC = CreateCompatibleDC(lhDCDesktop)
  172.         If (lHDC <> 0) Then
  173.             If (bAsDIB) Then
  174.                MsgBox "I don't know how to put a DIB on the clipboard! Copy as bitmap instead!!!"
  175.                 ' Create a duplicate DIBSection and copy
  176.                 ' to the clipboard:
  177.                 'LSet tBI = m_tBI
  178.                 'hDibCopy = CreateDIBSection( _
  179.                 '        lhDC, _
  180.                 '        m_tBI, _
  181.                 '        DIB_RGB_COLORS, _
  182.                 '        lPtr, _
  183.                 '        0, 0)
  184.                 'If (hDibCopy <> 0) Then
  185.                 '    lhBmpOld = SelectObject(lhDC, hObj)
  186.                 '    BitBlt lhDC, 0, 0, Width, Height, m_hDC, 0, 0, vbSrcCopy
  187.                 '    SelectObject lhDC, lhBmpOld
  188.                 '    lFmt = CF_DIB
  189.                 '
  190.                 '     '....
  191.                                     
  192.                 'Else
  193.                 '    hObj = 0
  194.                 'End If
  195.             Else
  196.                 ' Create a compatible bitmap and copy to
  197.                 ' the clipboard:
  198.                 hObj = CreateCompatibleBitmap(lhDCDesktop, Width, Height)
  199.                 If (hObj <> 0) Then
  200.                     lhBmpOld = SelectObject(lHDC, hObj)
  201.                     PaintPicture lHDC
  202.                     SelectObject lHDC, lhBmpOld
  203.                     lFmt = CF_BITMAP
  204.                     ' Now set the clipboard to the bitmap:
  205.                     If (OpenClipboard(0) <> 0) Then
  206.                         EmptyClipboard
  207.                         If (SetClipboardData(lFmt, hObj) <> 0) Then
  208.                             CopyToClipboard = True
  209.                         End If
  210.                         CloseClipboard
  211.                     End If
  212.                 End If
  213.             End If
  214.             DeleteDC lHDC
  215.         End If
  216.     End If
  217. End Function
  218.  
  219. Public Function CreateDIB( _
  220.         ByVal lHDC As Long, _
  221.         ByVal lWidth As Long, _
  222.         ByVal lheight As Long, _
  223.         ByRef hDib As Long _
  224.     ) As Boolean
  225.     With m_tBI.bmiHeader
  226.         .biSize = Len(m_tBI.bmiHeader)
  227.         .biWidth = lWidth
  228.         .biHeight = lheight
  229.         .biPlanes = 1
  230.         .biBitCount = 24
  231.         .biCompression = BI_RGB
  232.         .biSizeImage = BytesPerScanLine * .biHeight
  233.     End With
  234.     hDib = CreateDIBSection( _
  235.             lHDC, _
  236.             m_tBI, _
  237.             DIB_RGB_COLORS, _
  238.             m_lPtr, _
  239.             0, 0)
  240.     CreateDIB = (hDib <> 0)
  241. End Function
  242. Public Function CreateFromPicture( _
  243.         ByRef picThis As StdPicture _
  244.     )
  245. Dim lHDC As Long
  246. Dim lhDCDesktop As Long
  247. Dim lhBmpOld As Long
  248. Dim tBMP As BITMAP
  249.     
  250.     GetObjectAPI picThis.handle, Len(tBMP), tBMP
  251.     If (Create(tBMP.bmWidth, tBMP.bmHeight)) Then
  252.         lhDCDesktop = CreateDCAsNull("DISPLAY", ByVal 0&, ByVal 0&, ByVal 0&)
  253.         If (lhDCDesktop <> 0) Then
  254.             lHDC = CreateCompatibleDC(lhDCDesktop)
  255.             DeleteDC lhDCDesktop
  256.             If (lHDC <> 0) Then
  257.                 lhBmpOld = SelectObject(lHDC, picThis.handle)
  258.                 LoadPictureBlt lHDC
  259.                 SelectObject lHDC, lhBmpOld
  260.                 DeleteObject lHDC
  261.             End If
  262.         End If
  263.     End If
  264. End Function
  265. Public Function Create( _
  266.         ByVal lWidth As Long, _
  267.         ByVal lheight As Long _
  268.     ) As Boolean
  269.     ClearUp
  270.     m_hDC = CreateCompatibleDC(0)
  271.     If (m_hDC <> 0) Then
  272.         If (CreateDIB(m_hDC, lWidth, lheight, m_hDIb)) Then
  273.             m_hBmpOld = SelectObject(m_hDC, m_hDIb)
  274.             Create = True
  275.         Else
  276.             DeleteObject m_hDC
  277.             m_hDC = 0
  278.         End If
  279.     End If
  280. End Function
  281. Public Property Get BytesPerScanLine() As Long
  282.     ' Scans must align on dword boundaries:
  283.     BytesPerScanLine = (m_tBI.bmiHeader.biWidth * 3 + 3) And &HFFFFFFFC
  284. End Property
  285.  
  286. Public Property Get Width() As Long
  287.     Width = m_tBI.bmiHeader.biWidth
  288. End Property
  289. Public Property Get Height() As Long
  290.     Height = m_tBI.bmiHeader.biHeight
  291. End Property
  292.  
  293. Public Sub LoadPictureBlt( _
  294.         ByVal lHDC As Long, _
  295.         Optional ByVal lSrcLeft As Long = 0, _
  296.         Optional ByVal lSrcTop As Long = 0, _
  297.         Optional ByVal lSrcWidth As Long = -1, _
  298.         Optional ByVal lSrcHeight As Long = -1, _
  299.         Optional ByVal eRop As RasterOpConstants = vbSrcCopy _
  300.     )
  301.     If lSrcWidth < 0 Then lSrcWidth = m_tBI.bmiHeader.biWidth
  302.     If lSrcHeight < 0 Then lSrcHeight = m_tBI.bmiHeader.biHeight
  303.     BitBlt m_hDC, 0, 0, lSrcWidth, lSrcHeight, lHDC, lSrcLeft, lSrcTop, eRop
  304. End Sub
  305.  
  306.  
  307. Public Sub PaintPicture( _
  308.         ByVal lHDC As Long, _
  309.         Optional ByVal lDestLeft As Long = 0, _
  310.         Optional ByVal lDestTop As Long = 0, _
  311.         Optional ByVal lDestWidth As Long = -1, _
  312.         Optional ByVal lDestHeight As Long = -1, _
  313.         Optional ByVal lSrcLeft As Long = 0, _
  314.         Optional ByVal lSrcTop As Long = 0, _
  315.         Optional ByVal eRop As RasterOpConstants = vbSrcCopy _
  316.     )
  317.     If (lDestWidth < 0) Then lDestWidth = m_tBI.bmiHeader.biWidth
  318.     If (lDestHeight < 0) Then lDestHeight = m_tBI.bmiHeader.biHeight
  319.     BitBlt lHDC, lDestLeft, lDestTop, lDestWidth, lDestHeight, m_hDC, lSrcLeft, lSrcTop, eRop
  320. End Sub
  321.  
  322. Public Property Get hdc() As Long
  323.     hdc = m_hDC
  324. End Property
  325. Public Property Get hDib() As Long
  326.     hDib = m_hDIb
  327. End Property
  328. Public Property Get DIBSectionBitsPtr() As Long
  329.     DIBSectionBitsPtr = m_lPtr
  330. End Property
  331. Public Sub RandomiseBits( _
  332.         Optional ByVal bGray As Boolean = False _
  333.     )
  334. Dim bDib() As Byte
  335. Dim x As Long, y As Long
  336. Dim lC As Long
  337. Dim tSA As SAFEARRAY2D
  338. Dim xEnd As Long
  339.     
  340.     ' Get the bits in the from DIB section:
  341.     With tSA
  342.         .cbElements = 1
  343.         .cDims = 2
  344.         .Bounds(0).lLbound = 0
  345.         .Bounds(0).cElements = m_tBI.bmiHeader.biHeight
  346.         .Bounds(1).lLbound = 0
  347.         .Bounds(1).cElements = BytesPerScanLine()
  348.         .pvData = m_lPtr
  349.     End With
  350.     CopyMemory ByVal VarPtrArray(bDib()), VarPtr(tSA), 4
  351.  
  352.     ' random:
  353.     Randomize Timer
  354.     
  355.     xEnd = (Width - 1) * 3
  356.     If (bGray) Then
  357.         For y = 0 To m_tBI.bmiHeader.biHeight - 1
  358.             For x = 0 To xEnd Step 3
  359.                 lC = Rnd * 255
  360.                 bDib(x, y) = lC
  361.                 bDib(x + 1, y) = lC
  362.                 bDib(x + 2, y) = lC
  363.             Next x
  364.         Next y
  365.     Else
  366.         For x = 0 To xEnd Step 3
  367.             For y = 0 To m_tBI.bmiHeader.biHeight - 1
  368.                 bDib(x, y) = 0
  369.                 bDib(x + 1, y) = Rnd * 255
  370.                 bDib(x + 2, y) = Rnd * 255
  371.             Next y
  372.         Next x
  373.     End If
  374.     
  375.     ' Clear the temporary array descriptor
  376.    ' This is necessary under NT4.
  377.    CopyMemory ByVal VarPtrArray(bDib), 0&, 4
  378.     
  379. End Sub
  380.  
  381. Public Sub ClearUp()
  382.     If (m_hDC <> 0) Then
  383.         If (m_hDIb <> 0) Then
  384.             SelectObject m_hDC, m_hBmpOld
  385.             DeleteObject m_hDIb
  386.         End If
  387.         DeleteObject m_hDC
  388.     End If
  389.     m_hDC = 0: m_hDIb = 0: m_hBmpOld = 0: m_lPtr = 0
  390. End Sub
  391.  
  392. Public Function Resample( _
  393.         ByVal lNewHeight As Long, _
  394.         ByVal lNewWidth As Long _
  395.     ) As cDIBSection
  396. Dim cDIB As cDIBSection
  397.     Set cDIB = New cDIBSection
  398.     If cDIB.Create(lNewWidth, lNewHeight) Then
  399.         If (lNewWidth <> m_tBI.bmiHeader.biWidth) Or (lNewHeight <> m_tBI.bmiHeader.biHeight) Then
  400.             ' Change in size, do resample:
  401.             ResampleDib cDIB
  402.         Else
  403.             ' No size change so just return a copy:
  404.             cDIB.LoadPictureBlt m_hDC
  405.         End If
  406.         Set Resample = cDIB
  407.     End If
  408. End Function
  409.  
  410. Private Function ResampleDib(ByRef cDibTo As cDIBSection) As Boolean
  411. Dim bDibFrom() As Byte
  412. Dim bDibTo() As Byte
  413.  
  414. Dim tSAFrom As SAFEARRAY2D
  415. Dim tSATo As SAFEARRAY2D
  416.  
  417.     ' Get the bits in the from DIB section:
  418.     With tSAFrom
  419.         .cbElements = 1
  420.         .cDims = 2
  421.         .Bounds(0).lLbound = 0
  422.         .Bounds(0).cElements = m_tBI.bmiHeader.biHeight
  423.         .Bounds(1).lLbound = 0
  424.         .Bounds(1).cElements = BytesPerScanLine()
  425.         .pvData = m_lPtr
  426.     End With
  427.     CopyMemory ByVal VarPtrArray(bDibFrom()), VarPtr(tSAFrom), 4
  428.  
  429.     ' Get the bits in the to DIB section:
  430.     With tSATo
  431.         .cbElements = 1
  432.         .cDims = 2
  433.         .Bounds(0).lLbound = 0
  434.         .Bounds(0).cElements = cDibTo.Height
  435.         .Bounds(1).lLbound = 0
  436.         .Bounds(1).cElements = cDibTo.BytesPerScanLine()
  437.         .pvData = cDibTo.DIBSectionBitsPtr
  438.     End With
  439.     CopyMemory ByVal VarPtrArray(bDibTo()), VarPtr(tSATo), 4
  440.  
  441. Dim xScale As Single
  442. Dim yScale As Single
  443.  
  444. Dim x As Long, y As Long, xEnd As Long, xOut As Long
  445.  
  446. Dim fX As Single, fY As Single
  447. Dim ifY As Long, ifX As Long
  448. Dim dX As Single, dy As Single
  449. Dim r As Long, r1 As Single, r2 As Single, r3 As Single, r4 As Single
  450. Dim g As Long, g1 As Single, g2 As Single, g3 As Single, g4 As Single
  451. Dim b As Long, b1 As Single, b2 As Single, b3 As Single, b4 As Single
  452. Dim ir1 As Long, ig1 As Long, ib1 As Long
  453. Dim ir2 As Long, ig2 As Long, ib2 As Long
  454.  
  455.     xScale = (Width - 1) / cDibTo.Width
  456.     yScale = (Height - 1) / cDibTo.Height
  457.     
  458.     xEnd = cDibTo.Width - 1
  459.         
  460.     For y = 0 To cDibTo.Height - 1
  461.         
  462.         fY = y * yScale
  463.         ifY = Int(fY)
  464.         dy = fY - ifY
  465.         
  466.         For x = 0 To xEnd
  467.             fX = x * xScale
  468.             ifX = Int(fX)
  469.             dX = fX - ifX
  470.             
  471.             ifX = ifX * 3
  472.             ' Interpolate using the four nearest pixels in the source
  473.             b1 = bDibFrom(ifX, ifY): g1 = bDibFrom(ifX + 1, ifY): r1 = bDibFrom(ifX + 2, ifY)
  474.             b2 = bDibFrom(ifX + 3, ifY): g2 = bDibFrom(ifX + 4, ifY): r2 = bDibFrom(ifX + 5, ifY)
  475.             b3 = bDibFrom(ifX, ifY + 1): g3 = bDibFrom(ifX + 1, ifY + 1): r3 = bDibFrom(ifX + 2, ifY + 1)
  476.             b4 = bDibFrom(ifX + 3, ifY + 1): g4 = bDibFrom(ifX + 4, ifY + 1): r4 = bDibFrom(ifX + 5, ifY + 1)
  477.             
  478.             ' Interplate in x direction:
  479.             ir1 = r1 * (1 - dy) + r3 * dy: ig1 = g1 * (1 - dy) + g3 * dy: ib1 = b1 * (1 - dy) + b3 * dy
  480.             ir2 = r2 * (1 - dy) + r4 * dy: ig2 = g2 * (1 - dy) + g4 * dy: ib2 = b2 * (1 - dy) + b4 * dy
  481.             ' Interpolate in y:
  482.             r = ir1 * (1 - dX) + ir2 * dX: g = ig1 * (1 - dX) + ig2 * dX: b = ib1 * (1 - dX) + ib2 * dX
  483.             
  484.             ' Set output:
  485.             If (r < 0) Then r = 0
  486.             If (r > 255) Then r = 255
  487.             If (g < 0) Then g = 0
  488.             If (g > 255) Then g = 255
  489.             If (b < 0) Then b = 0
  490.             If (b > 255) Then
  491.                 b = 255
  492.             End If
  493.             xOut = x * 3
  494.             bDibTo(xOut, y) = b
  495.             bDibTo(xOut + 1, y) = g
  496.             bDibTo(xOut + 2, y) = r
  497.             
  498.         Next x
  499.         
  500.     Next y
  501.  
  502.     ' Clear the temporary array descriptor
  503.     ' This is necessary under NT4.
  504.     CopyMemory ByVal VarPtrArray(bDibFrom), 0&, 4
  505.     CopyMemory ByVal VarPtrArray(bDibTo), 0&, 4
  506.  
  507.  
  508. End Function
  509.  
  510.  
  511. Public Function SavePicture(ByVal sFileName As String) As Boolean
  512. Dim tBH As BITMAPFILEHEADER
  513. Dim tRGBQ As RGBQUAD
  514. Dim hFile As Long
  515. Dim lBytesWritten As Long
  516. Dim lSize As Long
  517. Dim lR As Long
  518. Dim bErr As Boolean
  519. Dim hMem As Long, lptr As Long
  520. Dim lErr As Long
  521.  
  522.    ' Prepare the BITMAPFILEHEADER
  523.    With tBH
  524.       .bfType = BITMAPTYPE
  525.       .bfOffBits = 14 + Len(m_tBI.bmiHeader)
  526.       .bfSize = .bfOffBits + m_tBI.bmiHeader.biSizeImage
  527.    End With
  528.    hFile = CreateFile(sFileName, _
  529.                  GENERIC_READ Or GENERIC_WRITE, _
  530.                   ByVal 0&, _
  531.                   ByVal 0&, _
  532.                   CREATE_ALWAYS, _
  533.                   FILE_ATTRIBUTE_NORMAL, _
  534.                   0)
  535.    lErr = Err.LastDllError
  536.    If (hFile = INVALID_HANDLE_VALUE) Then
  537.       ' error
  538.       Err.Raise 17, App.EXEName & ".cDIBSection256", ApiError(lErr)
  539.    Else
  540.       
  541.       ' Writing the BITMAPFILEINFOHEADER is somewhat painful
  542.       ' due to non-byte alignment of structure...
  543.       hMem = GlobalAlloc(GPTR, 14)
  544.       lptr = GlobalLock(hMem)
  545.       CopyMemory ByVal lptr, tBH.bfType, 2
  546.       CopyMemory ByVal lptr + 2, tBH.bfSize, 4
  547.       CopyMemory ByVal lptr + 6, 0&, 4
  548.       CopyMemory ByVal lptr + 10, tBH.bfOffBits, 4
  549.       lSize = 14
  550.       lR = WriteFile(hFile, ByVal lptr, lSize, lBytesWritten, ByVal 0&)
  551.       GlobalUnlock hMem
  552.       GlobalFree hMem
  553.       
  554.       ' Add the BITMAPINFOHEADER:
  555.       bErr = FileErrHandler(lR, lSize, lBytesWritten)
  556.       If Not bErr Then
  557.          lSize = Len(m_tBI.bmiHeader)
  558.          lR = WriteFile(hFile, m_tBI.bmiHeader, lSize, lBytesWritten, ByVal 0&)
  559.          bErr = FileErrHandler(lR, lSize, lBytesWritten)
  560.       End If
  561.       ' There is no palette for a truecolour DIB
  562.       
  563.       If Not bErr Then
  564.          ' Its easy to write the bitmap data, though...
  565.          lSize = m_tBI.bmiHeader.biSizeImage
  566.          lR = WriteFile(hFile, ByVal m_lPtr, lSize, lBytesWritten, ByVal 0&)
  567.          bErr = FileErrHandler(lR, lSize, lBytesWritten)
  568.       End If
  569.       
  570.       
  571.       CloseHandle hFile
  572.       'SavePicture = Not (bErr)
  573.    End If
  574.  
  575. End Function
  576.  
  577. Function ApiError(ByVal e As Long) As String
  578.     Dim s As String, c As Long
  579.     s = String(256, 0)
  580.     c = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM Or _
  581.                       FORMAT_MESSAGE_IGNORE_INSERTS, _
  582.                       0, e, 0&, s, Len(s), ByVal 0)
  583.     If c Then ApiError = Left$(s, c)
  584. End Function
  585.  
  586. Private Function FileErrHandler(ByVal lR As Long, ByVal lSize As Long, ByVal lBytes As Long) As Boolean
  587.    If (lR = 0) Or Not (lSize = lBytes) Then
  588.       'Err.Raise
  589.       FileErrHandler = True
  590.    End If
  591. End Function
  592.  
  593.  
  594. Private Sub Class_Terminate()
  595.     ClearUp
  596. End Sub
  597.