Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations wOOdy-Soft on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

SetParent API paritally disables its new child ? 1

Status
Not open for further replies.

Sheco

Programmer
Jan 3, 2005
5,457
US
I have hit a snag trying to use the SetParent function of the Win32 API to place a normal form inside of an MDI child form.

So my normal form will be a sort of MDI grandchild (don't ask)

Anyway, first I did this:
Code:
Private Sub SetChild(oForm As VB.Form)
  mlOldParent = SetParent(oForm.hwnd, Me.hwnd)
End Sub

This kinda worked. Everything looks good and works good except if I call GetParent() on the child it returns 0 as if it is a top level window instead of a grandchild!

So, I changed the window style of the grandchild window. Now the function looks like this:
Code:
Private Sub SetChild(oForm As VB.Form)
  'Apply the "child" style to the form
  Dim lStyle As Long
  lStyle = GetWindowLong(oForm.hwnd, GWL_STYLE)
  lStyle = lStyle Or WS_CHILD
  SetWindowLong oForm.hwnd, GWL_STYLE, lStyle
  
  'Swap parent here:
  mlOldParent = SetParent(oForm.hwnd, Me.hwnd)
End Sub

Well, that fixed the GetParent() problem, now I can get the handle to the parent window just fine. But now the grandchild window is partially disabled. Mostly disabled even. The title bar is always the inactive color but I can use it to drag it around and clicking the [x] closes it. The buttons on the grandchild won't click but the a click event on the form itself will fire just fine.

So I studied the

MSDN for SetParent()
and decided to add this:

SendMessage Me.hwnd, WM_UPDATEUISTATE, &H40001, 0

But that didn't do anything.

Does anyone have a tip or a hint that might help me?
 
Why do you really need to set the WS_CHILD bit? Just to fix the GetParent problem? If you don't do SetWindowLong, everything goes just fine, as you stated too.

I don't understand why is the return value of the GetParent function so importance to you.
 
Good question.

The reason is that I want the MDI Child to be aware of the grandchild forms contained within it, without adding any code to the grandchildren themselves.

I was thinking of something like a For/Each loop through the VB.Forms collection where I could call GetParent on every form to learn which of them were grandchild forms.

In the alternative I can use the EnumChildWindows API instead of GetParent. This does work but you have to pass a callback function to the API and, unless I am mistaken, a callback function like this must be on a standard module (ie: a .BAS file.) The reason I don't want to do that is that this project already has 13 .BAS, 42 .CLS, and 52 .FRM files...

 
Even why have one more? You just have a callback function which I think can be suitably placed anywhere in one of the 13 modules.

And if this is also unacceptable, you may consider using the GetWindow function in a Do-Loop to enumerate the child windows. This does not require a callback function and can be placed in a form/class module.
 
I am worried about something that I read in the MSDN entry for GetWindow ...
Code:
[b]Remarks[/b]

The EnumChildWindows function is more reliable than calling [b]GetWindow[/b] in a loop. An application that calls GetWindow to perform this task risks being caught in an infinite loop or referencing a handle to a window that has been destroyed.

This warning really bothers me because not only are there over 50 forms in the project, the specific MDI child form that will be the parent of these "grandchild" windows is right up against the max of 254 named controls so more recent edits to he form dynamically add and remove controls. I guess it goes without saying that this app suffers from "too many cooks" syndrome. I am merely the latest in a long line of consultants called in to add this feature or that... The whole mess is held together with baling wire and duct tape.
 
As far as just editing one of the existing .BAS modules, I could do that but then thats one more thing I've got to get by the testers... one more thing that I have to prove that I didn't break.
 
I settled on not setting the WS_CHILD bit and using EnumChildWindows instead. I also tried making the form an MDI Child but this caused the same problem... So in the end the grandchildren remain normal forms.

I decided that adding yet another .BAS for the callback was the way to go given the additional testing that would have been required had I added the callback function to one of the existing ones.

This turned out to be an OK thing to do anyway because it turns out that I have several other helper functions relating to this behavior that all fit together to make a nice .BAS module. The callback populates a module level array that is used by these other helper functions.

Here is the end result:
Code:
Option Explicit
Option Base 0

'modChildForms.bas


'Win32 API function used to verify a handle
Private Declare Function IsWindow Lib "user32" _
        (ByVal hwnd As Long) As Long

'Win32 API function used to change a form's parent window
Private Declare Function SetParent Lib "user32" _
        (ByVal hWndChild As Long, _
        ByVal hWndNewParent As Long) As Long

'VB forms are created from one of these 2 class:
Private Const VB_IDE_FORM_CLASS As String = "ThunderFormDC"
Private Const VB_RUN_FORM_CLASS As String = "ThunderRT6FormDC"

'Pass this API function the handle of a parent window and
'the address of a callback function and Windows will call
'the callback function once for each child window.
'Remember that forms are not the only "windows" ...
'Most controls (ie: textbox, button) are also "windows."
Private Declare Function EnumChildWindows Lib "user32" _
        (ByVal hWndParent As Long, _
        ByVal lpEnumFunc As Long, _
        ByVal lParam As Long) As Long

'Pass this API function the handle to a window and Windows
'returns the name of the class from which it was created.
Private Declare Function GetClassName Lib "user32" _
        Alias "GetClassNameA" _
        (ByVal hwnd As Long, _
        ByVal lpClassName As String, _
        ByVal nMaxCount As Long) As Long

'Pass this API function the handle to a window and Windows
'returns the caption from the title bar.
Private Declare Function GetWindowText Lib "user32" _
        Alias "GetWindowTextA" _
        (ByVal hwnd As Long, _
        ByVal lpString As String, _
        ByVal cch As Long) As Long
        
'This UDT holds a window handle and title bar caption
Public Type VBChildFormType
  hwnd As Long
  TitleBar As String
End Type

Private ChildForms() As VBChildFormType



'-----------------------------------------------------------
' Procedure : LoadChildForm
' Date      : 5/31/2005
' Purpose   : Loads and Shows a VB form as a child form.
'             Returns handle of previous parent.
'-----------------------------------------------------------
Public Function LoadChildForm(frmChild As VB.Form, _
                              hWndParent As Long, _
                              Optional bDesktop As Boolean = False) As Long
  If Not bDesktop And (hWndParent = 0) Then
    Err.Raise vbObjectError + 1, _
              "LoadChildForm", _
              "bDesktop flag must be True if you wish to set " _
              & "this form to be a child of desktop."
    Exit Function
  End If
  
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "LoadChildForm", _
              "Invalid parent window handle."
    Exit Function
  End If
  
  Load frmChild
  LoadChildForm = SetParent(frmChild.hwnd, hWndParent)
  frmChild.Move 200, 200
  frmChild.Show
End Function


'-----------------------------------------------------------
' Procedure : CallBackEnumChildWindows
' Date      : 5/31/2005
' Purpose   : This is the callback for EnumChildWindows().
'             This function is called by the Windows OS once
'             for each child window.
'
'             The only reason this function is Public is so
'             that Windows can use it as a callback.  This
'             function should not be directly called from
'             within this project
'-----------------------------------------------------------
Public Function CallBackEnumChildWindows(ByVal hwnd As Long, _
                                         ByVal lpData As Long) As Long
  'Set return value to 1  (setting it to 0 halts the enumeration)
  CallBackEnumChildWindows = 1
  
  'What type of window is this handle?
  Dim strBuffer As String
  Dim lBufferLen As Long
  strBuffer = String$(256, Chr(0))
  lBufferLen = GetClassName(hwnd, strBuffer, 255)
  strBuffer = Left$(strBuffer, lBufferLen)
  
  'Exit if not a handle to a VB form window
  If (strBuffer <> VB_IDE_FORM_CLASS) And _
     (strBuffer <> VB_RUN_FORM_CLASS) Then
    Exit Function
  End If
  
  'Get the title caption
  strBuffer = String$(256, Chr(0))
  lBufferLen = GetWindowText(hwnd, strBuffer, 255)
  strBuffer = Left$(strBuffer, lBufferLen)
  
  'Configure new UDT
  Dim udtForm As VBChildFormType
  udtForm.hwnd = hwnd
  udtForm.TitleBar = strBuffer
  
  'Add new element to ChildForms() UDT array
  Dim lCount As Long
  Err.Clear
  On Error Resume Next
  lCount = UBound(ChildForms)
  If Err.Number = 9 Then
    ReDim ChildForms(0)
  Else
    ReDim Preserve ChildForms(lCount + 1)
  End If
  Err.Clear
  On Error GoTo 0
  ChildForms(UBound(ChildForms)) = udtForm
End Function


'-----------------------------------------------------------
' Procedure : GetChildForms
' Date      : 5/31/2005
' Purpose   : Returns array of UDT elements.  Each element
'             contains the handle and title caption of one
'             child form.
'-----------------------------------------------------------
Public Function GetChildForms(hWndParent As Long) As VBChildFormType()
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Function
  End If

  Erase ChildForms
  Dim lRet As Long
  lRet = EnumChildWindows(hWndParent, AddressOf CallBackEnumChildWindows, 0)
  
  If lRet = 0 Then Erase ChildForms
  
  GetChildForms = ChildForms
End Function


'-----------------------------------------------------------
' Procedure : CountChildForms
' Date      : 5/31/2005
' Purpose   : Returns the number of child forms.
'-----------------------------------------------------------
Public Function CountChildForms(hWndParent As Long) As Long
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Function
  End If
  
  GetChildForms hWndParent
  
  Err.Clear
  On Error Resume Next
  CountChildForms = UBound(ChildForms)
  If (Err.Number = 0) Then
    'Add 1 because ChildForms is zero based array
    CountChildForms = CountChildForms + 1
  End If
  Err.Clear
  On Error GoTo 0
End Function


'-----------------------------------------------------------
' Procedure : GetChildFormsCollection
' Date      : 5/31/2005
' Purpose   : Returns collection object containing VB Forms
'             that are child forms of the input parameter.
'-----------------------------------------------------------
Public Function GetChildFormsCollection(hWndParent As Long) As Collection
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Function
  End If
  
  Dim lMax As Long
  Dim lCount As Long
  Dim frmTemp As VB.Form
  
  Set GetChildFormsCollection = New Collection
  
  lMax = CountChildForms(hWndParent)
  If (lMax = 0) Then Exit Function
    
  For lCount = 1 To lMax
    'Find the form with matching handle
    For Each frmTemp In VB.Forms
      If (frmTemp.hwnd = ChildForms(lCount - 1).hwnd) Then
        GetChildFormsCollection.Add frmTemp, CStr(ChildForms(lCount - 1).hwnd)
        Exit For
      End If
    Next
  Next
  
  Set frmTemp = Nothing
End Function


'-----------------------------------------------------------
' Procedure : ShowChildForms
' Date      : 5/31/2005
' Purpose   : Makes all child forms visible.
'-----------------------------------------------------------
Public Sub ShowChildForms(hWndParent As Long)
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Sub
  End If
  
  Dim colChildForms As New Collection
  Dim frmTemp As VB.Form
  
  Set colChildForms = GetChildFormsCollection(hWndParent)

  For Each frmTemp In colChildForms
    frmTemp.Show
  Next
  
  Set frmTemp = Nothing
  Set colChildForms = Nothing
End Sub


'-----------------------------------------------------------
' Procedure : HideChildForms
' Date      : 5/31/2005
' Purpose   : Makes all child forms invisible.
'-----------------------------------------------------------
Public Sub HideChildForms(hWndParent As Long)
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Sub
  End If
  
  Dim colChildForms As New Collection
  Dim frmTemp As VB.Form
  
  Set colChildForms = GetChildFormsCollection(hWndParent)

  For Each frmTemp In colChildForms
    frmTemp.Hide
  Next
  
  Set frmTemp = Nothing
  Set colChildForms = Nothing
End Sub


'-----------------------------------------------------------
' Procedure : UnloadChildForms
' Date      : 5/31/2005
' Purpose   : Explicitly unloads all child forms.
'-----------------------------------------------------------
Public Sub UnloadChildForms(hWndParent As Long, _
                            Optional hWndOrigParent As Long = 0)
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Sub
  End If
  
  Dim colChildForms As New Collection
  Dim frmTemp As VB.Form
  
  Set colChildForms = GetChildFormsCollection(hWndParent)

  For Each frmTemp In colChildForms
    If hWndOrigParent Then SetParent frmTemp.hwnd, hWndOrigParent
    Unload frmTemp
  Next
  
  Set frmTemp = Nothing
  Set colChildForms = Nothing
End Sub


'-----------------------------------------------------------
' Procedure : CascadeChildForms
' Date      : 6/1/2005
' Purpose   : Cascades child forms in top left of parent.
'-----------------------------------------------------------
Public Sub CascadeChildForms(hWndParent As Long)
  If Not CBool(IsWindow(hWndParent)) Then
    Err.Raise vbObjectError + 1, _
              "GetChildForms", _
              "Invalid parent window handle."
    Exit Sub
  End If

  Dim lCount As Long
  Dim colChildForms As New Collection
  Dim oForm As VB.Form

  Set colChildForms = GetChildFormsCollection(hWndParent)
  
  For Each oForm In colChildForms
    lCount = lCount + 1
    oForm.WindowState = vbNormal
    oForm.Move (lCount * 200), (lCount * 200)
  Next
  
  Set oForm = Nothing
  Set colChildForms = Nothing
End Sub
 
A minor issue that needs clarification.
[tt]
>The only reason this function is Public is so
>that Windows can use it as a callback. This
>function should not be directly called from
>within this project

>Public Function CallBackEnumChildWindows...
[/tt]
Note that callback functions do not need to be declared always public. They can (and preferably should) be declared private because there is no need for them to be visible outside the module or called directly.

Callback functions in general need two requirements.

1. They must be declared inside a standard module.
2. They must be inside the scope of the procedure where they are referenced using the AddressOf operator.

If you are referencing them in the same module, you should declare them private. However, if you are referencing them outside the module, you must declare them public so that they are visible to the AddressOf operator.

In your case, CallBackEnumChildWindows can be declared private because it is visible to the procedure where EnumChildWindows function is called.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top