From: Dee Earley on
On 06/10/2009 17:46, xytsrm wrote:
> "Dee Earley" wrote:
>> The text box contents are not the "caption" which si why FindWindow*
>> won't see it.
>> You need to enumerate them all (EnumWindows()) and check for one that
>> looks like the one you want, possibly extracting and checking the text
>> manually.
>
> Actually the property in the textbox is not "caption", it's "name", but as
> some have suggested the name is not exposed and needs to be enumerated, or
> perhaps can be found through Winspector.

Sorry, I used "Caption" as that is what Spy++ labeled it as, presumably
for statics and plain windows where that text is the caption.

The point is that the "name" for VB created textboxes is blank and is
not the contents of the textbox.

--
Dee Earley (dee.earley(a)icode.co.uk)
i-Catcher Development Team

iCode Systems
From: Dee Earley on
On 08/10/2009 08:21, Eduardo wrote:
> Nobody escribi�:
>> "Eduardo" <mm(a)mm.com> wrote in message news:hajk12$6d9$1(a)aioe.org...
>>> I don't know if with EnumChildWindows they also appear ordered this way.
>>
>> Yes they are. Quote from the remarks section: "A child window that is
>> moved or repositioned in the Z order during the enumeration process
>> will be properly enumerated. The function does not enumerate a child
>> window that is destroyed before being enumerated or that is created
>> during the enumeration process."
>
> OK. I like the GetWindow method because it's easier.
>
> And about the problems... they don't specify how they could happen, but
> I suspect that for looking for form's controls handles in a fast loop
> when you are not removing or adding controls or changing the Zorder, it
> should be fine; and also for finding a textbox (it's a guess).

Yes, IF they don't change, move, shutdown, get reused, get rubbed up
against by the nearest cat, shot, hung, drawn or quartered.

It's much easier to use a reliable method rather than one that is
documented as causing problems...

--
Dee Earley (dee.earley(a)icode.co.uk)
i-Catcher Development Team

iCode Systems
From: Eduardo on
It wasn't hard to fix the "problem":

Option Explicit

Private Declare Function GetWindow Lib "USER32" (ByVal hwnd _
As Long, ByVal wFlag As Long) As Long
Private Declare Function GetWindowText Lib "USER32" Alias _
"GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As _
String, ByVal cch As Long) As Long
Private Declare Function FindWindow Lib "USER32" Alias _
"FindWindowA" (ByVal lpClassName As String, ByVal _
lpWindowName As String) As Long
Private Declare Function GetClassName Lib "USER32" Alias _
"GetClassNameA" (ByVal hwnd As Long, ByVal _
lpClassName As String, ByVal nMaxCount As Long) As Long

Private Const GW_HWNDNEXT = 2&
Private Const GW_CHILD = 5&


Private Function GetFirstTextBoxHandle(nFormCaption As String, _
Optional nTextboxText As String) As Long

Dim iHwnd As Long
Dim iSize As Long
Dim iClass As String
Dim iText As String
Dim iCount As Long

iHwnd = FindWindow(vbNullString, nFormCaption)
If iHwnd Then
iHwnd = GetWindow(iHwnd, GW_CHILD)
Do While iHwnd
iClass = Space(64)
iSize = GetClassName(iHwnd, iClass, Len(iClass))
If iSize > 0 Then
iClass = Left(iClass, iSize)
If Left(iClass, 7) = "Thunder" Then
If Right(iClass, 7) = "TextBox" Then
If nTextboxText <> "" Then
iText = Space(100)
GetWindowText iHwnd, iText, 100&
iText = Left(iText, InStr(iText, _
Chr(0)) - 1)
If iText = nTextboxText Then
GetFirstTextBoxHandle = iHwnd
Exit Function
End If
Else
GetFirstTextBoxHandle = iHwnd
Exit Function
End If
End If
End If
iCount = iCount + 1
If iCount > 500 Then Exit Function
End If
iHwnd = GetWindow(iHwnd, GW_HWNDNEXT)
Loop
End If
End Function

Private Sub Command1_Click()
MsgBox GetFirstTextBoxHandle("OtherForm1", "Text1")
End Sub


From: Eduardo on
Sorry, again:

Option Explicit

Private Declare Function GetWindow Lib "USER32" (ByVal hwnd _
As Long, ByVal wFlag As Long) As Long
Private Declare Function GetWindowText Lib "USER32" Alias _
"GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As _
String, ByVal cch As Long) As Long
Private Declare Function FindWindow Lib "USER32" Alias _
"FindWindowA" (ByVal lpClassName As String, ByVal _
lpWindowName As String) As Long
Private Declare Function GetClassName Lib "USER32" Alias _
"GetClassNameA" (ByVal hwnd As Long, ByVal _
lpClassName As String, ByVal nMaxCount As Long) As Long

Private Const GW_HWNDNEXT = 2&
Private Const GW_CHILD = 5&


Private Function GetFirstTextBoxHandle(nFormCaption As String, _
Optional nTextboxText As String) As Long

Dim iHwnd As Long
Dim iSize As Long
Dim iClass As String
Dim iText As String
Dim iCount As Long

iHwnd = FindWindow(vbNullString, nFormCaption)
If iHwnd Then
iHwnd = GetWindow(iHwnd, GW_CHILD)
Do While iHwnd
iClass = Space(64)
iSize = GetClassName(iHwnd, iClass, Len(iClass))
If iSize > 0 Then
iClass = Left(iClass, iSize)
If Left(iClass, 7) = "Thunder" Then
If Right(iClass, 7) = "TextBox" Then
If nTextboxText <> "" Then
iText = Space(100)
GetWindowText iHwnd, iText, 100&
iText = Left(iText, InStr(iText, _
Chr(0)) - 1)
If iText = nTextboxText Then
GetFirstTextBoxHandle = iHwnd
Exit Function
End If
Else
GetFirstTextBoxHandle = iHwnd
Exit Function
End If
End If
End If
End If
iHwnd = GetWindow(iHwnd, GW_HWNDNEXT)
iCount = iCount + 1
If iCount > 500 Then Exit Function
Loop
End If
End Function

Private Sub Command1_Click()
MsgBox GetFirstTextBoxHandle("OtherForm1", "Text1")
End Sub
From: mayayana on
I wonder about the difference, too. MS doesn't
provide any technical explanation for their
statement. But for what it's worth, I find the
EnumChildWindows method fairly simple. It just
requires writing a small callback function and
using a bas-global variable. Also, there seems
to be another important difference: According
to the docs it seems that GetWindow only goes
down one level, while EnumChildWindows seems
to return the entire hierarchy before quitting.
That's not always relevant, but in many cases a
window that's expected to be 1 level down might
actually be 2 or 3 levels down, nested in intermediary
windows.

The following is a snippet
that I wrote for finding an IE browser window
in a given folder window hierarchy. The full enum was
needed in that case because different Windows versions
have different folder window structures.

I edited this code slightly to produce a sample
function that returns an hWnd based on part
of any window class name:


' GetWindowByClass function is called to set the enum going.
' The EnumChildProc takes it from there. It checks
' the class name of each window. Returning 0
' stops the enum. So this example of EnumChildProc
' runs until either all child windows have been
' processed or a match has been found. That all
' happens before the last line of GetWindowByClass.
' By that point the variable HCur is either 0 or the
' hWnd of a window with matching classname.

Private Function GetWindowByClass(ByVal TophWnd As Long, sClass As String)
As Long
Dim LRet As Long
HCur = 0 'module-level variable.
GetWindowByClass = 0
sClassName = sClass 'module-level variable.
LRet = EnumChildWindows(TophWnd, AddressOf EnumChildProc, 0)
GetWindowByClass = HCur '-- either 0 or hWnd.
End Function

Public Function EnumChildProc(ByVal hWnd As Long, lParam As Long) As Long
Dim s2 As String
s2 = GetWinClass(hWnd)
If InStr(1, s2, sClassName, 1) > 0 Then
HCur = hWnd
EnumChildProc = 0
Else
EnumChildProc = 1
End If
End Function

Public Function GetWinClass(ByVal H1 As Long) As String
Dim sBuf As String
Dim LRet As Long
On Error Resume Next
GetWinClass = ""
sBuf = String$(256, 0)
LRet = GetClassName(H1, sBuf, Len(sBuf))
If (LRet > 0) Then GetWinClass = Left$(sBuf, LRet)
End Function




First  |  Prev  |  Next  |  Last
Pages: 1 2 3 4 5 6 7
Prev: Centralised MsgBox
Next: Updating the VB EXE