?? modparsers.bas
字號:
Attribute VB_Name = "modParsers"
'****************************************************************************
'人人為我,我為人人
'枕善居漢化收藏整理
'發布日期:2007/05/08
'描 述:另類自定義listview控件源碼(支持真彩色圖標)
'網 站:http://www.Mndsoft.com/ (VB6源碼博客)
'網 站:http://www.VbDnet.com/ (VB.NET源碼博客,主要基于.NET2005)
'e-mail :Mndsoft@163.com
'e-mail :Mndsoft@126.com
'OICQ :88382850
' 如果您有新的好的代碼別忘記給枕善居哦!
'****************************************************************************
'
'感謝您使用本站源碼,如果方便的話請給于本站一點支持,謝謝。
'
'本站物品:
'700MB容量的VB.NET源碼光盤(38元包快遞)
'支持支付寶交易:http://auction1.taobao.com/auction/0/item_detail-0db1-a8aba972995270433643e99d2e4ac592.jhtml
'也可以銀行匯款:http://www.mndsoft.com/sale/yh.png
'
'USB電腦遙控器 源碼光盤
'支持支付寶交易:http://auction1.taobao.com/auction/0/item_detail-0db1-dd4a9c3f6a5785231091b01d54af01fd.jhtml
'也可以銀行匯款:http://www.mndsoft.com/sale/yh.png
'
'如果您給于本站一點支持,本站將更好的利用自身優勢為您尋找您需要的代碼!
Option Explicit
' No APIs are declared public. This is to prevent possibly, differently
' declared APIs or different versions, of the same API, from conflciting
' with any APIs you declared in your project. Same rule for UDTs.
Private Type SafeArrayBound
cElements As Long
lLbound As Long
End Type
Private Type SafeArray ' used as DMA overlay on a DIB
cDims As Integer
fFeatures As Integer
cbElements As Long
cLocks As Long
pvData As Long
rgSABound(0 To 1) As SafeArrayBound
End Type
Private Type PictDesc
Size As Long
Type As Long
hHandle As Long
hPal As Long
End Type
Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
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)
' used to create a stdPicture from a byte array
Private Declare Function CreateStreamOnHGlobal Lib "ole32" (ByVal hGlobal As Long, ByVal fDeleteOnRelease As Long, ppstm As Any) As Long
Private Declare Function GlobalAlloc Lib "kernel32" (ByVal uFlags As Long, ByVal dwBytes As Long) As Long
Private Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long
Private Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long
Private Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long
Private Declare Function OleLoadPicture Lib "olepro32" (pStream As Any, ByVal lSize As Long, ByVal fRunmode As Long, riid As Any, ppvObj As Any) As Long
Private Declare Function OleCreatePictureIndirect Lib "olepro32.dll" (lpPictDesc As PictDesc, riid As Any, ByVal fPictureOwnsHandle As Long, iPic As IPicture) As Long
' used to see if DLL exported function exists
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function FreeLibrary Lib "kernel32" (ByVal hLibModule As Long) As Long
Private Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
' GDI32 APIs
Private Declare Function CombineRgn Lib "gdi32.dll" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long
Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
Private Declare Function ExtCreateRegion Lib "gdi32" (lpXform As Any, ByVal nCount As Long, lpRgnData As Any) As Long
Private Declare Function GetRegionData Lib "gdi32.dll" (ByVal hRgn As Long, ByVal dwCount As Long, ByRef lpRgnData As Any) As Long
Private Declare Function GetRgnBox Lib "gdi32.dll" (ByVal hRgn As Long, ByRef lpRect As RECT) As Long
Private Declare Function CreateRectRgn Lib "gdi32.dll" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
' User32 APIs
Private Declare Function SetRect Lib "user32" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Public Function iparseCreateShapedRegion(cHost As c32bppDIB) As Long
'*******************************************************
' FUNCTION RETURNS A HANDLE TO A REGION IF SUCCESSFUL.
' If unsuccessful, function retuns zero.
' The fastest region from bitmap routines around, custom
' designed by LaVolpe. This version modified to create
' regions from alpha masks.
'*******************************************************
' Useful should a region want to be created around the alpha image.
' Tip. Check c32bppDIB.Alpha property before calling this routine.
' -- If Alpha=False: When applying to a Window handle,
' then SetWindowRgn hWnd,0&,True uses no extra system resources
' vs setting the window region to a rectangular region
' declare bunch of variables...
Dim rgnRects() As RECT ' array of rectangles comprising region
Dim rectCount As Long ' number of rectangles & used to increment above array
Dim rStart As Long ' pixel that begins a new regional rectangle
Dim X As Long, Y As Long ' loop counters
Dim lScanWidth As Long ' used to size the DIB bit array
Dim bDib() As Byte ' the DIB bit array
Dim tSA As SafeArray ' array overlay
Dim rtnRegion As Long ' region handle returned by this function
Dim Width As Long, Height As Long
On Error GoTo CleanUp
' Simple sanity checks
Width = cHost.Width
If Width < 1& Then Exit Function
Height = cHost.Height
If cHost.Alpha = False Then
iparseCreateShapedRegion = CreateRectRgn(0&, 0&, Width, Height)
Exit Function
End If
lScanWidth = Width * 4& ' how many bytes per bitmap line?
With tSA ' prepare array overlay
.cbElements = 1 ' byte elements
.cDims = 2 ' two dim array
.pvData = cHost.BitsPointer ' data location
.rgSABound(0).cElements = Height
.rgSABound(1).cElements = lScanWidth
End With
' overlay now
CopyMemory ByVal VarPtrArray(bDib()), VarPtr(tSA), 4&
' start with an arbritray number of rectangles
ReDim rgnRects(0 To Width * 3&)
' reset flag
rStart = -1&
' begin pixel by pixel comparisons
For Y = Height - 1 To 0& Step -1&
' the alpha byte is every 4th byte
For X = 3& To lScanWidth - 1& Step 4&
' test to see if next pixel is 100% transparent
If bDib(X, Y) = 0 Then
If rStart > -1& Then ' we're currently tracking a rectangle,
' so let's close it
' see if array needs to be resized
If rectCount + 1& = UBound(rgnRects) Then _
ReDim Preserve rgnRects(0 To UBound(rgnRects) + Width * 3&)
' add the rectangle to our array
SetRect rgnRects(rectCount + 2&), rStart, Height - Y - 1&, X \ 4, Height - Y
rStart = -1& ' reset flag
rectCount = rectCount + 1& ' keep track of nr in use
End If
Else
' not a target color
If rStart = -1& Then rStart = X \ 4 ' set start point
End If
Next X
If rStart > -1& Then
' got to end of bitmap without hitting another transparent pixel
' but we're tracking so we'll close rectangle now
' see if array needs to be resized
If rectCount + 1& = UBound(rgnRects) Then _
ReDim Preserve rgnRects(0 To UBound(rgnRects) + Width * 3&)
' add the rectangle to our array
SetRect rgnRects(rectCount + 2), rStart, Height - Y - 1, X \ 4, Height - Y
rStart = -1& ' reset flag
rectCount = rectCount + 1& ' keep track of nr in use
End If
Next Y
' remove the array overlay
CopyMemory ByVal VarPtrArray(bDib()), 0&, 4&
On Error Resume Next
' check for failure & engage backup plan if needed
If Not rectCount = 0 Then
' there were rectangles identified, try to create the region in one step
rtnRegion = CreatePartialRegion(rgnRects(), 2&, rectCount + 1&, 0&, Width)
' ok, now to test whether or not we are good to go...
' if less than 2000 rectangles, region should have been created & if it didn't
' it wasn't due O/S restrictions -- failure
If rtnRegion = 0& Then
If rectCount > 2000& Then
' Win98 has limitation of approximately 4000 regional rectangles
' In cases of failure, we will create the region in steps of
' 2000 vs trying to create the region in one step
rtnRegion = CreateWin98Region(rgnRects, rectCount + 1&, 0&, Width)
End If
End If
End If
CleanUp:
Erase rgnRects()
If Err Then ' failure; probably low on resources
If Not rtnRegion = 0& Then DeleteObject rtnRegion
Err.Clear
Else
iparseCreateShapedRegion = rtnRegion
End If
End Function
Private Function CreatePartialRegion(rgnRects() As RECT, lIndex As Long, uIndex As Long, leftOffset As Long, cx As Long) As Long
' Helper function for CreateShapedRegion & CreateWin98Region
' Called to create a region in its entirety or stepped (see CreateWin98Region)
On Error Resume Next
' Note: Ideally contiguous rectangles of equal height & width should be combined
' into one larger rectangle. However, thru trial & error I found that Windows
' does this for us and taking the extra time to do it ourselves
' is too cumbersome & slows down the results.
' the first 32 bytes of a region is the header describing the region.
' Well, 32 bytes equates to 2 rectangles (16 bytes each), so I'll
' cheat a little & use rectangles to store the header
With rgnRects(lIndex - 2) ' bytes 0-15
.Left = 32& ' length of region header in bytes
.Top = 1& ' required cannot be anything else
.Right = uIndex - lIndex + 1& ' number of rectangles for the region
.Bottom = .Right * 16& ' byte size used by the rectangles; can be zero
End With
With rgnRects(lIndex - 1&) ' bytes 16-31 bounding rectangle identification
.Left = leftOffset ' left
.Top = rgnRects(lIndex).Top ' top
.Right = leftOffset + cx ' right
.Bottom = rgnRects(uIndex).Bottom ' bottom
End With
' call function to create region from our byte (RECT) array
CreatePartialRegion = ExtCreateRegion(ByVal 0&, (rgnRects(lIndex - 2&).Right + 2&) * 16&, rgnRects(lIndex - 2&))
If Err Then Err.Clear
End Function
Private Function CreateWin98Region(rgnRects() As RECT, rectCount As Long, leftOffset As Long, cx As Long) As Long
' Fall-back routine when a very large region fails to be created.
' Win98 has problems with regional rectangles over 4000
' So, we'll try again in case this is the prob with other systems too.
' We'll step it at 2000 at a time which is stil very quick
Dim X As Long, Y As Long ' loop counters
Dim win98Rgn As Long ' partial region
Dim rtnRegion As Long ' combined region & return value of this function
Const RGN_OR As Long = 2&
Const scanSize As Long = 2000&
' we start with 2 'cause first 2 RECTs are the header
For X = 2& To rectCount Step scanSize
If X + scanSize > rectCount Then
Y = rectCount
Else
Y = X + scanSize
End If
' attempt to create partial region, scanSize rects at a time
win98Rgn = CreatePartialRegion(rgnRects(), X, Y, leftOffset, cx)
If win98Rgn = 0& Then ' failure
' cleaup combined region if needed
If Not rtnRegion = 0& Then DeleteObject rtnRegion
Exit For ' abort; system won't allow us to create the region
Else
If rtnRegion = 0& Then ' first time thru
rtnRegion = win98Rgn
Else ' already started
' use combineRgn, but only every scanSize times
CombineRgn rtnRegion, rtnRegion, win98Rgn, RGN_OR
DeleteObject win98Rgn
End If
End If
Next
' done; return result
CreateWin98Region = rtnRegion
End Function
?? 快捷鍵說明
復制代碼
Ctrl + C
搜索代碼
Ctrl + F
全屏模式
F11
切換主題
Ctrl + Shift + D
顯示快捷鍵
?
增大字號
Ctrl + =
減小字號
Ctrl + -