|
|
||||||||||||||||||||||||||||||||||||||||||||||||||||||||
Visual Basic Common Control API
Routines SetWindowLong: Add TreeView Check Boxes via API |
||
Posted: | Friday April 17, 1998 | |
Updated: | Monday December 26, 2011 | |
Applies to: | VB4-32, VB5, VB6 using comctl32.ocx | |
Developed with: | VB6, Windows NT4 | |
OS restrictions: | None | |
Author: | Brad Martinez | |
Prerequisites |
This method is intended for Visual Basic 5 or Visual Basic
6 where the Common Control library used is the MSComCtl 5 version (comctl32.ocx). Because the VB6-specific mscomctl.ocx (Common Controls 6)
is a complete implementation of comctl32.dll and not reliant on the version of comctl32.dll installed, this routine may not work when applied
to a listview created from the VB6-specific mscomctl.ocx.
Enhanced Comctl32 functionality is only available to users with comctl32.dll version 4.70 or greater installed. This dll is typically installed with IE3.x or greater. Visual Basic 6 users have extended functionality built-in to the newer mscomctl32.ocx, which does not rely on the Windows comctl32.dll. This code is targeted towards users opting for the older comctl32.ocx using comctl32.dll. |
|
So
I says to Brad "Brad," I says, "I'm working on doing a treeview checkbox demo." Ding goes the mailbox ... and here it is,
using a checkbox in a treeview, courtesy of Brad Martinez, the Mad Coder.
Recent newsgroup postings have asked how to mimic the Advanced Options page displayed in Internet Explorer 4. Initially I thought of using the listview with checks and indents, but after someone suggested that the items on the page were collapsible, I investigated the treeview styles. Sure enough, a TVS_CHECKBOXES style was available. So while it was now easy to display the checkboxes (by calling SetWindowLong), I wanted to do a second request ... selecting/deselecting child item checkboxes, and identifying which nodes were checked and unchecked. API-wise, the treeview, compared to the listview, is a much different beast. Where the listview items are consecutively numbered form 0 to Count -1 (via API) or 1 to Count (using the VB version), treeviews, because of their hierarchical nature, use item identifiers (called hitems) instead of indexes. Luckily for most VB users never advancing past the surface of the controls, this complex system is hidden, and as far as the treeview goes, this is a blessing. But when you have to get under the hood, you soon see that MS obviously gave the task of designing the treeview to Morgan the Maniac. The innards *are* complex. Hopefully, the code below is presented in a relatively well thought-out way in order to guide you through the dark corridors of the API treeview. To keep the code intact while the demo is created, I suggest doing a select all/copy for the entire page, then pasting everything into notepad and extracting the code from there. This will assure that all line breaks occur correctly.
|
BAS Module Code |
The BAS module will contain the base APIs and a subset of generic TreeView functions (those prefaced with "Treeview_"). These correspond by name to their C-macro counterparts, so over time here you will build up pretty much the complete collection. Add the following code to a BAS module: |
|
Option Explicit '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ' Copyright ©1996-2011 VBnet/Randy Birch, All Rights Reserved. ' Some pages may also contain other copyrights by the author. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' ' Distribution: You can freely use this code in your own ' applications, but you may not reproduce ' or publish this code on any web site, ' online service, or distribute as source ' on any media without express permission. '''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''' 'Brad Martinez, http://www.mvps.org/btmtz/
'These are the indices of the treeview
'checkbox state images when the treeview
'TVS_CHECKBOXES style bit is set.
Public Const IIL_UNCHECKED As Long = 1
Public Const IIL_CHECKED As Long = 2
Public Const GWL_STYLE As Long = (-16)
Declare Function GetWindowLong Lib "user32" _
Alias "GetWindowLongA" _
(ByVal hwnd As Long, _
ByVal nIndex As Long) As Long
Declare Function SetWindowLong Lib "user32" _
Alias "SetWindowLongA" _
(ByVal hwnd As Long, _
ByVal nIndex As Long, _
ByVal dwNewLong As Long) As Long
Declare Function SendMessage Lib "user32" _
Alias "SendMessageA" _
(ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Any, _
lParam As Any) As Long
Public Type POINTAPI 'pt
x As Long
y As Long
End Type
Declare Function GetCursorPos Lib "user32" _
(lpPoint As POINTAPI) As Long
Declare Function ScreenToClient Lib "user32" _
(ByVal hwnd As Long, _
lpPoint As POINTAPI) As Long
Declare Function GetAsyncKeyState Lib "user32" _
(ByVal vKey As Long) As Integer
'--------------------------------------------
'style
Public Const TVS_CHECKBOXES As Long = &H100 '>= IE3
'messages
Public Const TV_FIRST As Long = &H1100
Public Const TVM_GETITEM As Long = (TV_FIRST + 12)
Public Const TVM_SETITEM As Long = (TV_FIRST + 13)
Public Const TVM_HITTEST As Long = (TV_FIRST + 17)
Public Type TV_ITEM
mask As Long
hItem As Long
state As Long
stateMask As Long
pszText As String 'Long pointer
cchTextMax As Long
iImage As Long
iSelectedImage As Long
cChildren As Long
lParam As Long
End Type
'TV_ITEM.mask flags
Public Const TVIF_TEXT As Long = &H1
Public Const TVIF_STATE As Long = &H8
Public Const TVIF_HANDLE As Long = &H10
'TV_ITEM.state bit value
Public Const TVIS_STATEIMAGEMASK As Long = &HF000
Public Type TV_HITTESTINFO
pt As POINTAPI
flags As Long
hItem As Long
End Type
'TV_HITTESTINFO.flags value
Public Const TVHT_ONITEMSTATEICON As Long = &H40
'User-defined as the maximum treeview item
'text length. If an item's text exceeds this
'value when calling GetTVItemText there could
'be problems...
Public Const MAX_ITEM = 256
Public Const TVM_GETNEXTITEM As Long = (TV_FIRST + 10)
'TVM_GETNEXTITEM wParam values
Public Enum TVGN_FLAGS
TVGN_ROOT = &H0
TVGN_NEXT = &H1
TVGN_PREVIOUS = &H2
TVGN_PARENT = &H3
TVGN_CHILD = &H4
TVGN_FIRSTVISIBLE = &H5
TVGN_NEXTVISIBLE = &H6
TVGN_PREVIOUSVISIBLE = &H7
TVGN_DROPHILITE = &H8
TVGN_CARET = &H9
#If (WIN32_IE >= &H400) Then
TVGN_LASTVISIBLE = &HA
#End If
End Enum
Public Function IsTVItemChecked(hwndTV As Long, _
hItem As Long) As Boolean
'---------------------------------------------------
'Determines if the current state image of the
'specified treeview item is set to the checked
'checkbox image index.
'
'hwndTV - treeview window handle
'hItem - item's handle whose checkbox state is to be to returned
'
'Returns True if the item's state image is
'set to the checked checkbox index, returns
'False otherwise.
'---------------------------------------------------
Dim tvi As TV_ITEM
'Initialize the struct and get the item's state value.
With tvi
.mask = TVIF_STATE
.hItem = hItem
.stateMask = TVIS_STATEIMAGEMASK
End With
Call TreeView_GetItem(hwndTV, tvi)
'We have to test to see if the treeview
'checked state image *is* set since the logical
'And test on the unchecked image (1) will
'evaluate to True when either checkbox image
'is set.
IsTVItemChecked = (tvi.state And INDEXTOSTATEIMAGEMASK(IIL_CHECKED))
End Function
Public Function IsTVItemCheckedFromClick(hwndTV As Long, _
x As Long, _
y As Long) As Boolean
'---------------------------------------------------
'Determines if the current state image of the
'item under the specified point (if any) is
'set to the checked checkbox image index.
'
'hwndTV - treeview window handle
'x, y - treeview co-ordinates in which
' to retrieve the item from
'
'Returns True if the item's state image is
'set to the checked checkbox index, or False
'otherwise.
'---------------------------------------------------
Dim tvhti As TV_HITTESTINFO
Dim fChecked As Boolean
tvhti.pt.x = x
tvhti.pt.y = y
If TreeView_HitTest(hwndTV, tvhti) Then 'returns an hItem also
fChecked = IsTVItemChecked(hwndTV, tvhti.hItem)
'Since we retrieved the item's handle from
'a treeview co-ordinate as a result of a
'NodeClick event (or MouseUp event, both are
'invoked from a NM_CLICK notification), if
'this co-ordinate is within the area of the
'item's state icon, then the item's checkbox
'image is *in the process* of being toggled,
'but *not yet* toggled. So we'll toggle the
'return value reflecting the soon-to-be-set
'state value.
If (tvhti.flags And TVHT_ONITEMSTATEICON) Then fChecked = Not fChecked
IsTVItemCheckedFromClick = fChecked
End If
End Function
Public Function SetTVItemCheckImage(hwndTV As Long, _
hItem As Long, _
fCheck As Boolean) As Boolean
'---------------------------------------------------
'Set the specified checkbox state for the
'specified item. Returns True if successful,
'returns False otherwise.
'
'hwndTV - treeview window handle
'hItem - item's handle whose checkbox state is to be to set
'fCheck - If True, sets the checkbox state to the checked image,
' if False, sets the unchecked image.
'---------------------------------------------------
Dim tvi As TV_ITEM
With tvi
.mask = TVIF_HANDLE Or TVIF_STATE
.hItem = hItem
.stateMask = TVIS_STATEIMAGEMASK
'As the values for the check constants are 1 for
'unchecked (IIL_UNCHECKED) and 2 for checked
'(IIL_CHECKED), fCheck (which is either True or
'False) can be used directly to toggle the
'INDEXTOIMAGESTATE parameter.
'
'This is accomplished by using the ABS() of
'fCheck (turning True (-1) and False (0)
'into 1 and 0 respectively.) Now, by adding 1,
'the value toggles between 2 and 1 respectively,
'exactly the same as using the IIL_ constants.
'
'Therefore, the single line of code below is
'equivalent to an If..Then statement of:
'
'If fCheck Then
' tvi.state = INDEXTOSTATEIMAGEMASK(IIL_CHECKED)
'Else: tvi.state = INDEXTOSTATEIMAGEMASK(IIL_UNCHECKED)
'End If
'
'See the comments section for code that more
'clearly demonstrates using ABS() to achieve this.
.state = INDEXTOSTATEIMAGEMASK(Abs(fCheck) + 1)
End With
SetTVItemCheckImage = TreeView_SetItem(hwndTV, tvi)
End Function
Public Function GetTVItemText(hwndTV As Long, _
hItem As Long, _
Optional cbItem As Long = MAX_ITEM) As String
'---------------------------------------------
'Returns the text of the specified treeview
'item if successful, returns an empty string
'otherwise.
'
'hwndTV - treeview window handle
'hItem - item's handle whose text is to be to returned
'cbItem - length of the specified item's text.
'---------------------------------------------
Dim tvi As TV_ITEM
With tvi
.mask = TVIF_TEXT
.hItem = hItem
.pszText = String$(cbItem, 0)
.cchTextMax = cbItem
End With
If TreeView_GetItem(hwndTV, tvi) Then
GetTVItemText = GetStrFromBufferA(tvi.pszText)
End If
End Function
Public Function GetStrFromBufferA(item As String) As String
'Returns the string before first null char
'encountered (if any) from an ANSI string.
If InStr(item, vbNullChar) Then
GetStrFromBufferA = Left$(item, InStr(item, vbNullChar) - 1)
Else
'If item had no null char, the Left$ function
'above would return a zero length string ("").
GetStrFromBufferA = item
End If
End Function
Public Function GetTVItemFromNode(hwndTV As Long, _
nod As Node) As Long
'If successful, returns the treeview item
'handle represented by the specified Node,
'returns 0 otherwise.
Dim nodeCur As Node
Dim asNodes() As String
Dim nNodes As Integer
Dim i As Integer
Dim hitemParent As Long
Dim hItem As Long
Set nodeCur = nod
'Cache the node and all of its parent
'node's text in the array
Do While (nodeCur Is Nothing) = False
nNodes = nNodes + 1
ReDim Preserve asNodes(nNodes)
asNodes(nNodes) = nodeCur.Text
Set nodeCur = nodeCur.Parent
Loop
'Get the hItem of the first root in the
'treeview, it will be the first parent
hitemParent = TreeView_GetRoot(hwndTV)
If hitemParent Then
'Walk through the cached node text from
'the root to the specified node (backwards
'through the array)
Do While nNodes
'Get the hItem of the current node
hItem = FindTVItemFromText(hwndTV, _
hitemParent, _
asNodes(nNodes))
If hItem Then
'Make the the current parent's first
'child item the new parent
hitemParent = TreeView_GetChild(hwndTV, hItem)
Else
Exit Function
End If
nNodes = nNodes - 1
Loop
GetTVItemFromNode = hItem
End If
End Function
Public Function FindTVItemFromText(hwndTV As Long, _
ByVal hitemChild As Long, _
sItem As String) As Long
'---------------------------------------------
'Returns the first encountered item handle
'whose text label matches the specified text.
'*Is case sensitive*.
'
'hwndTV - treeview window handle
'hitemChild - first sibling item's handle in which to search
'sItem - specified item's text we're looking for
'
'If the text represented by sItem is found
'hItem is returned, otherwise 0 is returned.
'---------------------------------------------
'Can't find the hItem of an item with no text...
If Len(sItem) = 0 Then Exit Function
Do While hitemChild
'If the current sibling item label
'matches our target text, we're done.
If GetTVItemText(hwndTV, hitemChild, MAX_ITEM) = sItem Then
FindTVItemFromText = hitemChild
Exit Function
End If
'Keep going while we have subsequent
'sibling items
hitemChild = TreeView_GetNextSibling(hwndTV, hitemChild)
Loop
End Function
Public Function TreeView_HitTest(hwnd As Long, _
lpht As TV_HITTESTINFO) As Long
'Determines the location of the specified point
'relative to the client area of a treeview control.
'Returns the handle to the tree-view item that
'occupies the specified point or NULL if no item
'occupies the point.
TreeView_HitTest = SendMessage(hwnd, TVM_HITTEST, 0&, lpht)
End Function
Public Function TreeView_GetItem(hwnd As Long, pitem As TV_ITEM) As Boolean
'Retrieves some or all of a tree-view
'item's attributes. Returns TRUE if
'successful or FALSE otherwise.
TreeView_GetItem = SendMessage(hwnd, TVM_GETITEM, 0&, pitem)
End Function
Public Function TreeView_SetItem(hwnd As Long, pitem As TV_ITEM) As Boolean
'Sets some or all of a tree-view item's
'attributes. Old docs say returns zero if
'successful or - 1 otherwise.
'New docs say returns TRUE if successful,
'or FALSE otherwise!
TreeView_SetItem = SendMessage(hwnd, TVM_SETITEM, 0&, pitem)
End Function
Public Function INDEXTOSTATEIMAGEMASK(iState As Long) As Long
'Prepares the index of a state image so that a
'treeview control or listview control can use the
'index to retrieve the state image for an item.
'Returns the one-based index of the state image
'shifted left twelve bits. A common control
'utility macro.
'This macro is defined in Commctrl.h as:
'#define INDEXTOSTATEIMAGEMASK(i) ((i) << 12)
INDEXTOSTATEIMAGEMASK = iState * (2 ^ 12)
End Function
Public Function TreeView_GetNextItem(hwnd As Long, _
hItem As Long, _
flag As Long) As Long
'Retrieves the tree-view item that bears the
'specified relationship to a specified item.
'Returns the handle to the item if successful
'or 0 otherwise.
TreeView_GetNextItem = SendMessage(hwnd, _
TVM_GETNEXTITEM, _
flag, _
ByVal hItem)
End Function
Public Function TreeView_GetChild(hwnd As Long, hItem As Long) As Long
'Retrieves the first child item. The hitem
'parameter must be NULL. Returns the handle
'to the item if successful or 0 otherwise.
TreeView_GetChild = TreeView_GetNextItem(hwnd, hItem, TVGN_CHILD)
End Function
Public Function TreeView_GetNextSibling(hwnd As Long, _
hItem As Long) As Long
'Retrieves the next sibling item.
'Returns the handle to the item if
'successful or 0 otherwise.
TreeView_GetNextSibling = TreeView_GetNextItem(hwnd, hItem, TVGN_NEXT)
End Function
Public Function TreeView_GetRoot(hwnd As Long) As Long
'Retrieves the topmost or very first item
'of the tree-view control. Returns the handle
'to the item if successful or 0 otherwise.
TreeView_GetRoot = TreeView_GetNextItem(hwnd, 0, TVGN_ROOT)
End Function
|
Form Code |
To a new form add: a treeview (Treeview1), an imagelist bound to the treeview containing any three small bitmaps or icons (16x16), two option buttons (Option1, Option2), two command buttons (Command1, Command2) and a Label (Label1). The frame shown is purely cosmetic. Add the following code to the form: |
|
Option Explicit Private hwndTV As Long Private Sub Form_Load() Dim Node1 As Node Dim Node2 As Node Dim Node3 As Node Dim i As Integer Dim j As Integer Dim k As Integer 'Set some treeview properties, and 'fill up the treeview with two root 'items, each having a child node with 'with four children... With TreeView1 'For convenience... .HideSelection = False .LabelEdit = tvwManual hwndTV = .hwnd 'Use the API to set the checkbox style Call SetTVStyle(hwndTV) For i = 1 To 2 Set Node1 = .Nodes.Add(, tvwLast, , "Root" & i, 1) For j = 1 To 1 Set Node2 = .Nodes.Add(Node1.Index, _ tvwChild, , _ "Root" & i & "Child" & j, 2) For k = 1 To 4 Set Node3 = .Nodes.Add(Node2.Index, _ tvwChild, , _ "Grandchild" & k, 3) Next 'k Node2.Expanded = True Next 'j Node1.Expanded = True Next 'i End With 'Let Label1 reflect the first root Node's text 'and check state. This is subsequently done 'in the NodeClick event, but here on loading, 'a NodeClick is not generated when the treeview 'first appears, even though the first root 'is selected). So we manually call the routine. Call DisplaySelectedNodeState(TreeView1.Nodes(1), False) End Sub Private Function SetTVStyle(hwndTV As Long) As Boolean Dim dwStyle As Long dwStyle = GetWindowLong(hwndTV, GWL_STYLE) 'Set the treeview checkbox style. Note that 'this style is applied across the entire 'treeview - you can not have some items 'allowing checks while others don't. If this 'functionality is needed, you must use your 'own state images to mimic the checkboxes. 'This is not covered in this code example. If dwStyle Then SetTVStyle = CBool(SetWindowLong(hwndTV, _ GWL_STYLE, _ dwStyle Or TVS_CHECKBOXES)) End If End Function Private Sub DisplaySelectedNodeState(sNode As String, _ fIsChecked As Boolean) If fIsChecked Then Label1.Caption = sNode & " is checked" Else: Label1.Caption = sNode & " is unchecked" End If End Sub Private Sub TreeView1_MouseUp(Button As Integer, _ Shift As Integer, _ x As Single, _ y As Single) 'The only way to determine if a Node is checked or 'not is by sending the treeview a TVM_GETITEM 'message and retrieving the Node's checked state. 'In order to send this message, we must have the 'treeview item handle of the Node. The easiest 'way to obtain the Node's item handle is by sending 'the treeview a TVM_HITTEST message with the 'co-ordinates of the mouse when the left button 'is released. Dim nodeSel As Node Dim fChecked As Boolean 'Only perform this if the 'use MouseUp' 'option was selected. If Option2.Value = True Then If Button = vbLeftButton Then 'Get the left-clicked node Set nodeSel = TreeView1.HitTest(x, y) If (nodeSel Is Nothing) = False Then fChecked = IsTVItemCheckedFromClick(hwndTV, _ x / Screen.TwipsPerPixelX, _ y / Screen.TwipsPerPixelY) Call DisplaySelectedNodeState(nodeSel.Text, fChecked) End If '(nodeSel Is Nothing) = False End If 'Button = vbLeftButton End If 'Option2 End Sub Private Sub TreeView1_NodeClick(ByVal Node As ComctlLib.Node) 'We could do things a bit differently here and 'obtain the treeview item handle of the Node with 'the GetTVItemFromNode call, and pass the handle 'directly to the IsTVItemChecked proc. But since 'we don't determine if this event was invoked due 'to a checkbox click (toggling the Node's checkbox 'state), IsTVItemChecked will not return an accurate 'value. Dim fChecked As Boolean Dim hItem As Long Dim pt As POINTAPI 'Only perform this if the 'use node' 'option was selected. If Option1 Then 'If this event was invoked from a left 'mouse button click (if the left mouse 'button was depressed when the NM_CLICK 'message was received by the treeview 'parent window). If GetAsyncKeyState(vbKeyLButton) Then 'Get the current cursor pos in screen 'coords, convert it to treeview coords, 'and get the check state. Call GetCursorPos(pt) Call ScreenToClient(hwndTV, pt) fChecked = IsTVItemCheckedFromClick(hwndTV, pt.x, pt.y) Call DisplaySelectedNodeState(Node.Text, fChecked) End If 'GetAsyncKeyState End If 'Option1 End Sub Private Sub Command1_Click() 'check the children of the selected item Call SetCheckStateOfChildren(TreeView1.SelectedItem, True) End Sub Private Sub Command2_Click() 'uncheck the children of the selected item Call SetCheckStateOfChildren(TreeView1.SelectedItem, False) End Sub Private Sub SetCheckStateOfChildren(nodeParent As Node, _ fCheck As Boolean) Dim nodeChild As Node Dim hItem As Long Set nodeChild = nodeParent.Child Do While (nodeChild Is Nothing) = False 'obtain the item handle of the node hItem = GetTVItemFromNode(hwndTV, nodeChild) 'if a valid handle, set the checked state If hItem Then Call SetTVItemCheckImage(hwndTV, hItem, fCheck) 'if the node has child nodes itself, 'recursively call this routine to set 'the state of those as well If (nodeChild.Child Is Nothing) = False Then Call SetCheckStateOfChildren(nodeChild, fCheck) End If Set nodeChild = nodeChild.Next Loop End Sub |
Comments |
Save and run the project. When a node that has children is
selected, pressing the Check or Uncheck button will cause the checkboxes to set their state accordingly for the child items. Pressing after
selecting an item without children causes no change.
Depending on the option selected, one of either the MouseUp or NodeClick methods will determine the status of the selected node. These two options take different approaches to achieve the same functionality. In the SetTVItemCheckImage function above, the ABS() function was used to determine the state item. The code below demonstrates how using ABS is identical to using an If..Then statement. To create this demo, you'll need the declares in the bas module created above, so it's easiest just to add a new form to the project, add a command button, and paste in the following. Then set the project properties to start at Form2 to test. Private Sub Command1_Click()
'lets us toggle fCheck between True and False
Static fCheck As Boolean
'required for demo
Dim tvi As TV_ITEM
'--------------------------------------
'toggle the flag
fCheck = Not fCheck
'this sets the tvi.state value via the conventional
'If...Then method
If fCheck Then
tvi.state = INDEXTOSTATEIMAGEMASK(IIL_CHECKED)
Else: tvi.state = INDEXTOSTATEIMAGEMASK(IIL_UNCHECKED)
End If
'Click the button twice.
'When fCheck is true, the output from the above will be:
'
'True 8192
'False 4098
Print fCheck, tvi.state,
'--------------------------------------
'now, use the ABS method to set the parameter
tvi.state = INDEXTOSTATEIMAGEMASK(Abs(fCheck) + 1)
'..and again, print out the return values.
'Now the output line will be:
'
'True 8192 2 8192
'False 4098 1 4096
Print Abs(fCheck) + 1, tvi.state
'--------------------------------------
'Therefore, the following line:
'tvi.state = INDEXTOSTATEIMAGEMASK(Abs(fCheck) + 1)
'is equivalent to:
'If fCheck Then
' tvi.state = INDEXTOSTATEIMAGEMASK(IIL_CHECKED)
'Else: tvi.state = INDEXTOSTATEIMAGEMASK(IIL_UNCHECKED)
'End If
'when the values being flipped are 1 and 2
End Sub
|
|
|
|
|||||
|
|||||
|
|||||
Copyright ©1996-2011 VBnet and Randy Birch. All Rights Reserved. |