Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

press button with SendMessage API

1,306 views
Skip to first unread message

bart.sm...@gmail.com

unread,
Oct 8, 2013, 11:14:43 AM10/8/13
to
Trying to do a button click of an external application with the SendMessage API, but sofar not been able to make it work.

Code I have tried sofar is along these lines (with various variations):


Private Const WM_LBUTTONDOWN As Long = &H201
Private Const WM_LBUTTONUP As Long = &H202

Private Declare Function SendMessage _
Lib "user32" _
Alias "SendMessageA" (ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
lParam As Any) As Long

Private Declare Function FindWindow _
Lib "user32" _
Alias "FindWindowA" _
(ByVal lpClassName As String, _
ByVal lpWindowName As String) As Long

Private Declare Function GetWindowRect Lib "user32" _
(ByVal hwnd As Long, _
lpRect As RECT) As Long

Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type


Sub ButtonClick(lHwnd As Long, _
Optional strClassName As String, _
Optional strWindowTitle As String)

Dim DaWord As Long
Dim lLeft As Long
Dim lTop As Long
Dim lRight As Long
Dim lBottom As Long

If Len(strClassName) > 0 Then
lHwnd = FindWindow(strClassName, strWindowTitle)
End If

GetWindowCoordinates lHwnd, lLeft, lTop, lRight, lBottom

'Centers the click and 15 is twips per pixel
DaWord = MakeDWord(((lRight - lLeft) / 15) / 2, ((lBottom - lTop) / 15) / 2)
'this doesn't work
SendMessage lHwnd, WM_LBUTTONDOWN, 1&, ByVal DaWord
SendMessage lHwnd, WM_LBUTTONUP, 1&, ByVal DaWord

End Sub

Private Function MakeDWord(ByVal LoWord As Integer, ByVal HiWord As Integer) As Long
MakeDWord = (HiWord * &H10000) Or (LoWord And &HFFFF&)
End Function

Sub GetWindowCoordinates(lHwnd As Long, _
lLeft As Long, lTop As Long, _
lRight As Long, lBottom As Long)

Dim RC As RECT

GetWindowRect lHwnd, RC

lLeft = RC.Left
lTop = RC.Top
lRight = RC.Right
lBottom = RC.Bottom

End Sub


I can achieve the button click with the mouse_event API, but I thought using SendMessage would be a bit neater.

Any suggestions?


RBS

Deanna Earley

unread,
Oct 8, 2013, 11:23:41 AM10/8/13
to
On 08/10/2013 16:14, bart.sm...@gmail.com wrote:
> Trying to do a button click of an external application with the SendMessage API, but sofar not been able to make it work.
>
> Code I have tried sofar is along these lines (with various variations):
>
> 'Centers the click and 15 is twips per pixel
> DaWord = MakeDWord(((lRight - lLeft) / 15) / 2, ((lBottom - lTop) / 15) / 2)
> 'this doesn't work
> SendMessage lHwnd, WM_LBUTTONDOWN, 1&, ByVal DaWord
> SendMessage lHwnd, WM_LBUTTONUP, 1&, ByVal DaWord
>
> I can achieve the button click with the mouse_event API, but I thought using SendMessage would be a bit neater.

You haven't shown how you call ButtonClick but if it's with the parent
window, then your sending a click to the window itself, not the button.

If you want to stick with the SendMessage then you need to find the
button in the parent window and send it to that.

However...

The correct method is to use CBT/Active Accessability to enumerate the
windows, then the controls on that window, and perform the actual action.

--
Deanna Earley (dee.e...@icode.co.uk)
iCatcher Development Team
http://www.icode.co.uk/icatcher/

iCode Systems

(Replies direct to my email address will be ignored. Please reply to the
group.)

bart.sm...@gmail.com

unread,
Oct 8, 2013, 11:30:46 AM10/8/13
to
I am running ButtonClick with the right parameters, so the handle of the actual button or the correct button class name and caption.
Don't think the problem is there.

RBS

Mayayana

unread,
Oct 8, 2013, 11:58:07 AM10/8/13
to
|I am running ButtonClick with the right parameters, so the handle of the
actual button or the correct button class name and caption.
| Don't think the problem is there.

If you want to use AA, this should work. Set a
reference to Active Accessibility (oleacc.dll). It's
pre-installed since Win2000 and later versions of it
provide nothing very relevant, so you don't need
to worry about support.

' declares: -------------------------------
Public Const OBJID_WINDOW = &H0&
Public Type UUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(0 To 7) As Byte
End Type

Public Declare Function AccessibleObjectFromWindow Lib "oleacc" (ByVal hWnd
As Long, ByVal dwId As Long, riid As UUID, ppvObject As Object) As Long


Public ACCID As UUID

'-----------------------------------------------
' at some point in code set up the ACCID variable:
With ACCID
.Data1 = &H618736E0
.Data2 = &H3C3D
.Data3 = &H11CF
.Data4(0) = &H81
.Data4(1) = &HC
.Data4(2) = &H0
.Data4(3) = &HAA
.Data4(4) = &H0
.Data4(5) = &H38
.Data4(6) = &H9B
.Data4(7) = &H71
End With
'-----------------------------------------------

' 0-success. 1-iaccessible not avail for this window. 2-no default action.
'-- LNumChild should be 0 unless object in question is part of an array,
'-- such as a menu item.
Public Function DoDefAction(LhWnd As Long, LNumChild As Long) As Long
Dim LRet As Long
Dim V1 As Variant
Dim AccOb As IAccessible
On Error Resume Next
LRet = AccessibleObjectFromWindow(ByVal LhWnd, OBJID_WINDOW, ACCID, AccOb)
If (LRet <> 0) Then
DoDefAction = 1 ' probably not available for this window.
Exit Function
End If

If LNumChild = 0 Then
AccOb.accDoDefaultAction
Else
V1 = CVar(LNumChild)
AccOb.accDoDefaultAction V1
End If
DoDefAction = 0 ' either worked or not supported.
Set AccOb = Nothing
End Function


Deanna Earley

unread,
Oct 8, 2013, 12:01:20 PM10/8/13
to
On 08/10/2013 16:30, bart.sm...@gmail.com wrote:
> I am running ButtonClick with the right parameters, so the handle of the actual button or the correct button class name and caption.
> Don't think the problem is there.

But FindWindow (from the code you pasted) only finds top level windows.
What is giving you the hWnd for the button itself?

If you're passing the window title and class, then it will always fail
as your code never recurses to find the button.

bart.sm...@gmail.com

unread,
Oct 8, 2013, 12:06:39 PM10/8/13
to
Thanks, will give that a try.

RBS

bart.sm...@gmail.com

unread,
Oct 8, 2013, 12:08:24 PM10/8/13
to
I got the handle of the button with FindWindow and it looks fine as checked with
WinSpy.exe (freeware).

RBS

Deanna Earley

unread,
Oct 8, 2013, 12:17:28 PM10/8/13
to
On 08/10/2013 17:08, bart.sm...@gmail.com wrote:
> I got the handle of the button with FindWindow and it looks fine as checked with
> WinSpy.exe (freeware).

But FindWindow will never find your button, it only looks for top level
windows for which the button wouldn't be.

bart.sm...@gmail.com

unread,
Oct 8, 2013, 12:24:40 PM10/8/13
to
OK, will double-check that in a bit.

RBS

bart.sm...@gmail.com

unread,
Oct 8, 2013, 12:48:46 PM10/8/13
to
Have checked and indeed FindWindow didn't find that window, so that was the problem. Thanks for clearing that up. I can get the handle with a recursive GetWindow, so that should hopefully fix this then.

RBS

Eduardo

unread,
Oct 8, 2013, 3:05:48 PM10/8/13
to
<bart.sm...@gmail.com> escribió en el mensaje
news:10130817-bf14-4bab...@googlegroups.com...

> Trying to do a button click of an external application with the
> SendMessage API, but sofar not been able to make it work.

Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type

Private Type POINTAPI
x As Long
Y As Long
End Type

Private Declare Sub mouse_event Lib "user32" (ByVal dwFlags As Long, _
ByVal dx As Long, ByVal dy As Long, ByVal cButtons As Long, _
ByVal dwExtraInfo As Long)
Private Declare Function GetCursorPos Lib "user32" (lpPoint As _
POINTAPI) As Long
Private Declare Function SetCursorPos Lib "user32" (ByVal x As Long, _
ByVal Y As Long) As Long
Private Declare Function ClientToScreen Lib "user32.dll" (ByVal hWnd As
Long, _
ByRef lpPoint As POINTAPI) As Long
Private Declare Function GetWindowRect Lib "user32" (ByVal hWnd As Long, _
lpRect As RECT) As Long
Private Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex _
As Long) As Long
Private Declare Function GetMessageExtraInfo Lib "user32" () As Long

Private Const MOUSEEVENTF_ABSOLUTE = &H8000 ' absolute move
Private Const MOUSEEVENTF_LEFTDOWN = &H2 ' left button down
Private Const MOUSEEVENTF_LEFTUP = &H4 ' left button up
Private Const MOUSEEVENTF_MOVE = &H1 ' mouse move

Private Const SM_CXSCREEN = 0 'X Size of screen
Private Const SM_CYSCREEN = 1 'Y Size of Screen
Private Const SM_CYMENU As Long = 15


Public Sub ClickOnWindow(nHwnd As Long, nX As Long, nY As Long)
Dim iRectWindow As RECT
Dim iM As POINTAPI
Dim iP As POINTAPI

iP.x = nX
iP.Y = nY
ClientToScreen nHwnd, iP

GetCursorPos iM
GetWindowRect nHwnd, iRectWindow

mouse_event MOUSEEVENTF_ABSOLUTE Or MOUSEEVENTF_MOVE, _
iP.x * (&HFFFF& / GetSystemMetrics(SM_CXSCREEN)), _
iP.Y * (&HFFFF& / GetSystemMetrics(SM_CYSCREEN)), 0, _
GetMessageExtraInfo()
mouse_event MOUSEEVENTF_LEFTDOWN, 0, 0, 0, GetMessageExtraInfo()
mouse_event MOUSEEVENTF_LEFTUP, 0, 0, 0, GetMessageExtraInfo()
SetCursorPos iM.x, iM.Y
End Sub


CoderX

unread,
Oct 8, 2013, 6:23:01 PM10/8/13
to

"Deanna Earley" <dee.e...@icode.co.uk> wrote in message
news:l3181p$kab$1...@speranza.aioe.org...
> The correct method is to use CBT/Active Accessability to enumerate the
> windows, then the controls on that window, and perform the actual action.

Ewww? That's a whole lot of work if the OP isn't working with a web
browser.

FindWindow to get the parent
FiindWindowEx to get the child hWnd
SendMessageByNum (typesafe version of SendMessage where lParam is declared
as Long and not As Any)

That's worked for me for years!

To the OP, you don't need to do all that WindowRect stuff. The hWnd will
suffice, as that is where the message will go.

Can I ask what app you are attempting to manipulate? It might help. You
can use a WindowSpy program or Spy++ to get the window class names.


ObiWan

unread,
Oct 9, 2013, 3:53:38 AM10/9/13
to

> I got the handle of the button with FindWindow and it looks fine as
> checked with WinSpy.exe (freeware).

as for "winspy"; have a look at this tool

http://www.mcafee.com/us/downloads/free-tools/showin.aspx

it's currently distributed by McAfee although in a past it was
available "elsewhere" and... I used it quite extensively; just give it
a spin, I think you'll want to keep it in your toolbox ;-)

Deanna Earley

unread,
Oct 9, 2013, 4:21:53 AM10/9/13
to
On 08/10/2013 17:48, bart.sm...@gmail.com wrote:
> Have checked and indeed FindWindow didn't find that window, so that
> was the problem.

And that's why you should ALWAYS check your return values.
That would have immediately shown the problem before you'd even posted.

RB Smissaert

unread,
Oct 9, 2013, 9:12:16 AM10/9/13
to
Yes, fully agree there and won't make same mistake again.

RBS


"Deanna Earley" <dee.e...@icode.co.uk> wrote in message
news:l333mv$dnr$1...@speranza.aioe.org...

Mayayana

unread,
Oct 9, 2013, 9:25:12 AM10/9/13
to
| > I got the handle of the button with FindWindow and it looks fine as
| > checked with WinSpy.exe (freeware).
|
| as for "winspy"; have a look at this tool
|
| http://www.mcafee.com/us/downloads/free-tools/showin.aspx
|

Why not Spy++? Does that only come with VS
and not VB?



RB Smissaert

unread,
Oct 9, 2013, 9:26:17 AM10/9/13
to
Thanks, will have a look at that.

RBS

"ObiWan" <alb.20.t...@spamgourmet.com> wrote in message
news:20131009095...@deathstar.mil...

Deanna Earley

unread,
Oct 9, 2013, 9:55:21 AM10/9/13
to
It was a visual Studio specific tool, and is a bit long in the tooth now.
While it works, it can be clunky and annoying :)
I've not used any others though.

I did try Winspector a while ago and it seemed to kill off a random VB6
IDE process every time it started up :)

bart.sm...@gmail.com

unread,
Oct 9, 2013, 10:44:30 AM10/9/13
to
> FindWindow to get the parent
> FindWindowEx to get the child hWnd

I am currently using a recurrent Sub with GetWindow to get that window handle,
but the above method looks a bit neater and will try that one.

RBS

GS

unread,
Oct 9, 2013, 11:39:11 AM10/9/13
to
<FWIW>
I use a stand-alone EXE for my app user guides instead of CHMs. I
manage these so they behave like 'in process' components even though
they're not 'in process'. I use modified code from Karl's 'FindPart'
demo, which uses SendMessage to load, display, and unload at shutdown
all as would be expected using a CHM. I even display context sensitive
help using SendMessage. It impliments very clean/neat coding that works
great with VB6 apps or VBA addins!

Might be worth a 'look see' on Karl's site if it might be worth your
time.

--
Garry

Free usenet access at http://www.eternal-september.org
Classic VB Users Regroup!
comp.lang.basic.visual.misc
microsoft.public.vb.general.discussion


MikeD

unread,
Oct 9, 2013, 4:06:07 PM10/9/13
to


"GS" <g...@somewhere.net> wrote in message news:l33tb2$plo$1...@dont-email.me...
> <FWIW>
> I use a stand-alone EXE for my app user guides instead of CHMs. I
> manage these so they behave like 'in process' components even though
> they're not 'in process'. I use modified code from Karl's 'FindPart'
> demo, which uses SendMessage to load, display, and unload at shutdown
> all as would be expected using a CHM. I even display context sensitive
> help using SendMessage. It impliments very clean/neat coding that works
> great with VB6 apps or VBA addins!
>
> Might be worth a 'look see' on Karl's site if it might be worth your
> time.
>


What does any of that have to do with what the OP asked?

GS

unread,
Oct 9, 2013, 5:25:19 PM10/9/13
to
The OP asked...

"I can achieve the button click with the mouse_event API, but I thought
using SendMessage would be a bit neater.

Any suggestions?"

bart.sm...@gmail.com

unread,
Oct 10, 2013, 4:59:50 AM10/10/13
to
> SendMessageByNum (typesafe version of SendMessage where lParam is declared
as Long and not As Any)

Could you show me your code, both the API declaration and the actual button click?
Not been able yet to do the button click with SendMessage.

RBS

RB Smissaert

unread,
Oct 10, 2013, 9:27:52 AM10/10/13
to
I didn't explain that clear enough.
I can press the button with SendMessage, but only if I put the coordinates
in that last argument of SendMessage.
It won't work if I pass it a zero. I did declare As Long in the SendMessage
declaration.

RBS


<bart.sm...@gmail.com> wrote in message
news:74b829d8-e964-4876...@googlegroups.com...

MikeB

unread,
Oct 10, 2013, 9:41:31 AM10/10/13
to

"CoderX" <co...@x.com> wrote in message news:l320ka$pp7$1...@dont-email.me...
>
> "Deanna Earley" <dee.e...@icode.co.uk> wrote in message
> news:l3181p$kab$1...@speranza.aioe.org...
>> The correct method is to use CBT/Active Accessability to enumerate the
>> windows, then the controls on that window, and perform the actual action.
>
> Ewww? That's a whole lot of work if the OP isn't working with a web
> browser.
>
> FindWindow to get the parent
> FiindWindowEx to get the child hWnd
> SendMessageByNum (typesafe version of SendMessage where lParam is declared
> as Long and not As Any)
>
> That's worked for me for years!
>
> To the OP, you don't need to do all that WindowRect stuff. The hWnd will
> suffice, as that is where the message will go.
>

When you are trying to suppress the security warning in Outlook, you have to
have the rect and position the mouse over the rect and use mouseclick
instead of sendmessage to button click. Something within outlook determines
that it was an actual mouseclick, otherwise, no cigar.

bart.sm...@gmail.com

unread,
Oct 10, 2013, 10:03:38 AM10/10/13
to
It is not for Outlook, but another external app, that is specialist software and not available to the general public.

RBS

CoderX

unread,
Oct 10, 2013, 4:14:03 PM10/10/13
to

"MikeB" <m.by...@frontier.com> wrote in message
news:l36aqb$7b3$1...@dont-email.me...
>
> When you are trying to suppress the security warning in Outlook, you have
> to
> have the rect and position the mouse over the rect and use mouseclick
> instead of sendmessage to button click. Something within outlook
> determines
> that it was an actual mouseclick, otherwise, no cigar.
>

To be fair, I've never tried to manipulate Outlook with API. I've tickered
with other apps and could manipulate control text and simulate clicks with
SendMessage and never needed to provide coordinates. But, the actual button
had it own window handle. If memory serves, outlook uses toolbars, which
has it's own handle, which the actual button in the toolbar do not. In that
case, yes, I could see where the coordinates would be required. However, it
was my understanding the OP was able to obtain a window handle for the
button in question, in which case coordinates would be irrelevant.

That's why I asked about the app. I wanted to run Spy++ on it to see what
the story was.


CoderX

unread,
Oct 10, 2013, 4:23:09 PM10/10/13
to

<bart.sm...@gmail.com> wrote in message
news:74b829d8-e964-4876...@googlegroups.com...
Let me ask you this, just so I understand your situation. The button you
want to click...do you have an actual window handle for it, or do you have
the handle for it's parent (for example, like a button inside a toolbar
control). Based on the post from MikeB, it's important to know which. My
code make the assumption you have the hWnd to the actual button or control
you want to click. I get you can't share the app, but if you could explain
the control hierarchy, it could help.

For example, if I wanted to click the OK button inside a message box, I
would use FindWindow to get the message box based on its class name, and
then use FindWindowEx to get the handle of the actual button, where I would
send the WM_LB* messages. But if I opened WordPag and wanted to click one
of the buttons in the toolbar, I would use FindWindow to get the WordPad
window, FindWindowEx to get the toolbar control and then SendMessage the
click messages using coordinates in the lParam, as the buttons in the
toolbar itself have no window handle.

Make sense?


Mayayana

unread,
Oct 10, 2013, 5:04:34 PM10/10/13
to
For what it's worth, I tested your code with a settings window
in Irfan View. It worked fine, given the window handle obtained
via Spy++. But a test of AA AccDoDefaultAction did not work.
Looking at my notes I see that I've found in the past that AA is
very undependable on that score. I hadn't remembered that.

So it seems that your code is fine if you just make sure
you have the right hWnd. If the button is actually a window,
and is actually type button, and you can uniquely ID it with
class name and window text, it should be easy to find it by
enumerating child windows.


GS

unread,
Oct 10, 2013, 5:43:20 PM10/10/13
to
Well.., if you talk about the apps in MS Office then those commandbars
all have ContolIDs for every control. Most all of the MSO built-in
commandbars have a FindControl method you can use via automation. You
can even get a ref to a control using its caption to iterate a
commandbar's Controls collection. Once you get a fully qualified ref to
a control just fire its Execute method. This applies to pre-ribbons
versions. You can do the same for Ribbon controls but the
process/method is slightly different. Note that commandbar

Eduardo

unread,
Oct 10, 2013, 6:55:18 PM10/10/13
to

"Mayayana" <maya...@invalid.nospam> escribió en el mensaje
news:l374r4$161$1...@dont-email.me...

> For what it's worth, I tested your code... ...It worked fine...

I tested it and it worked fine as long as the application clicked is active
(active window).


CoderX

unread,
Oct 10, 2013, 7:56:09 PM10/10/13
to

"GS" <g...@somewhere.net> wrote in message news:l3771p$d8b$1...@dont-email.me...
>
> Well.., if you talk about the apps in MS Office then those commandbars all
> have ContolIDs for every control. Most all of the MSO built-in commandbars
> have a FindControl method you can use via automation. You can even get a
> ref to a control using its caption to iterate a commandbar's Controls
> collection. Once you get a fully qualified ref to a control just fire its
> Execute method. This applies to pre-ribbons versions. You can do the same
> for Ribbon controls but the process/method is slightly different. Note
> that commandbar

Okay?

I understand this, having written a few add-ins over the years. The OP is
talking about cross process manipulation of a control in another process, so
all the in-process stuff you just descibed doesn't apply here.


GS

unread,
Oct 10, 2013, 11:09:59 PM10/10/13
to
Well that is kind of my point! We can access the libs to get
methods/properties and so makes this easy to do. Bart would be further
ahead if he had better info about the app he's trying to manipulate.
This was the point for my out-of-process explanation in an earlier
post. I have the info I need about the EXE I'm manipulating and so
makes the task fairly clean/simple to code for. In Bart's case it'd
almost be easier to write his own procedure to substitute what the
button does if that were feasible, but he's probably dealing with an
internal process. Too bad there isn't a command line alternative!

bart.sm...@gmail.com

unread,
Oct 11, 2013, 5:46:30 AM10/11/13
to
> RBS Let me ask you this, just so I understand your situation. The button you want to click...do you have an actual window handle for it, or do you have the handle for it's parent (for example, like a button inside a toolbar control).

I do have the window handle of that button, but as said I can't do the click via SendMessage unless I supply the coordinates in the last argument.
In case it is relevant, this is the class name of that button:
WindowsForms10.Window.8.app.0.218f99c

RBS

bart.sm...@gmail.com

unread,
Oct 11, 2013, 6:09:58 AM10/11/13
to
Just to make clear, this is the code I use to send the button click:

Private Declare Function SendMessageLong _
Lib "user32" _
Alias "SendMessageA" (ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
lParam As Long) As Long

Public Declare Function FindWindow _
Lib "user32" _
Alias "FindWindowA" _
(ByVal lpClassName As String, _
ByVal lpWindowName As String) As Long

Private Const WM_LBUTTONDOWN As Long = &H201
Private Const WM_LBUTTONUP As Long = &H202
Private Const WM_RBUTTONDOWN As Long = &H204
Private Const WM_RBUTTONUP As Long = &H205
Private Const MK_LBUTTON As Long = &H1
Private Const MK_RBUTTON As Long = &H2

Private Declare Function GetWindowRect Lib "user32" _
(ByVal hwnd As Long, _
lpRect As RECT) As Long

Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type


Sub ButtonClick(lHwnd As Long, _
Optional strClassName As String, _
Optional strWindowTitle As String, _
Optional bRightButton As Boolean)

Dim DaWord As Long
Dim lLeft As Long
Dim lTop As Long
Dim lRight As Long
Dim lBottom As Long

If Len(strClassName) > 0 Then
lHwnd = FindWindow(strClassName, strWindowTitle)
End If

GetWindowCoordinates lHwnd, lLeft, lTop, lRight, lBottom

'Centers the click and 15 is twips per pixel
DaWord = MakeDWord(((lRight - lLeft) / 15) / 2, ((lBottom - lTop) / 15) / 2)

If bRightButton Then
'this doesn't work
SendMessageLong lHwnd, WM_RBUTTONDOWN, MK_RBUTTON, ByVal DaWord
SendMessageLong lHwnd, WM_RBUTTONUP, MK_RBUTTON, ByVal DaWord
Else
SendMessageLong lHwnd, WM_LBUTTONDOWN, MK_LBUTTON, ByVal DaWord
SendMessageLong lHwnd, WM_LBUTTONUP, MK_LBUTTON, ByVal DaWord
End If

End Sub

Private Function MakeDWord(ByVal LoWord As Integer, ByVal HiWord As Integer) As Long
MakeDWord = (HiWord * &H10000) Or (LoWord And &HFFFF&)
End Function

Sub GetWindowCoordinates(lHwnd As Long, _
lLeft As Long, lTop As Long, _
lRight As Long, lBottom As Long)

Dim RC As RECT

GetWindowRect lHwnd, RC

lLeft = RC.Left
lTop = RC.Top
lRight = RC.Right
lBottom = RC.Bottom

End Sub


Note that I can't do the right-click, even if I supply the x and y coordinates.


RBS

Deanna Earley

unread,
Oct 11, 2013, 7:21:04 AM10/11/13
to
Remember that themed buttons are rounded so 0,0 will be "outside" the
button.
I thin CoderX is getting at the fact that sending a "clicked" message
rather than a "mouse down here, mouse up here" is cleaner.

GS

unread,
Oct 11, 2013, 8:08:57 AM10/11/13
to
> so all the in-process stuff you just descibed doesn't apply here.

For clarity, I thought this comment deserved a separate reply...

I'm not talking about 'in-process' stuff, PERIOD! I'm talking about
manipulating 'out-of-process' instances of other apps via automation.
This is the mechanism I use to manipulate my AppHelp.EXEs so they
*behave like* an in-process CHM or HLP, even to the point of
implimenting 'in-context' help. I do this using SendMessage!

It should be apparent by my numerous posts in this forum that I also
dev Excel-based apps. I use the AppHelp.EXEs with my Excel addins same
as with my VB6.EXEs. There's nothing 'in-process' about it because the
AppHelp.EXE is a separate process! The fact that you know my addins run
'in-process' with Excel is clouding my point here!

The context of my comments in this topic refer to manipulating other
apps via CreateObject/GetObject. For example, my VB6.EXE frontloaders
prepare an automated instance of Excel for use by my Excel addin (or
addins if the addin supports 'plug-ins'). I entirely customize the
Excel instance via automation to the point that its UI is so highly
modified for my intended use that users may not even know they're
working with Excel. What makes this possible is knowing what libs are
exposed, as well as what properties and methods I can access for my
intended purpose. Again, there's nothing 'in-process' about this!

Finally, (as you know) we can use a hidden automated instance of
another process where its UI and controls are not exposed to our user,
nor does our user have control of said instance for any other reason.

Now I'll admit to making the inference that we can manipulate these
'out-of-process' instances same as if they were 'in-process', but only
with regard to their *behavior* as controlled by our app!

My suggestion about finding info as to what libs/props/methods are
exposed for automation is my first action to take. Command line access
would be a second suggested approach.

Farnsworth

unread,
Oct 11, 2013, 5:59:29 PM10/11/13
to
<bart.sm...@gmail.com> wrote in message
news:7f7ce1ba-d05c-4136...@googlegroups.com...
> 'Centers the click and 15 is twips per pixel
> DaWord = MakeDWord(((lRight - lLeft) / 15) / 2, ((lBottom - lTop) / 15)
> / 2)

The Windows API "always" operates in pixels, so you shouldn't divide by 15,
even if the target app is written in VB with different ScaleMode.

Also, some windows have a non-client area, like a single or few pixels
border, so if you are sending a message with zero coordinates, Windows maybe
confused with what you are trying to say. Typically non-client area gets
WM_NCLBUTTONDOWN when the click happens in that area, so WM_LBUTTONDOWN is
unexpected. For example, if you have a PictureBox on a form, it has 2 Pixels
border that is considered a non-client area.

Spy++ shows both the window rectangle and the client area rectangle. If the
size is not the same for both rectangles, then the window has a non-client
area(border). You can get the same information by calling these API
functions:

GetWindowRect
GetClientRect
ClientToScreen
ScreenToClient

By calling ClientToScreen with point (0,0) and subtract the result from the
upper left corner of the window(which is given by GetWindowRect), you get
the start of the client area relative to the upper left corner of the
window, but you don't need to know this as you are clicking on the center of
the button, so it shouldn't matter.





Farnsworth

unread,
Oct 11, 2013, 6:00:17 PM10/11/13
to
<bart.sm...@gmail.com> wrote in message
news:fede86f6-990a-4ac3...@googlegroups.com...
> I do have the window handle of that button, but as said I can't do the
> click via SendMessage unless I supply the coordinates in the last
> argument.
> In case it is relevant, this is the class name of that button:
> WindowsForms10.Window.8.app.0.218f99c
>
> RBS

That class name is either for another window, or the button is a simulated
button. A .Not app usually have buttons with class name like this:

WindowsForms10.BUTTON.app.0.218f99c

The random numbers on the right are not necessarily the same on each
computer, they could be different based on what version of the .Not library
is installed, even when the EXE file is the same, so they should be ignored.
Also, Delphi.Net use class names like this for buttons:

WindowsForms10.Window.b.218f99c

The non .Net version of Delphi uses "TButton" as a class name, so comparing
for "Button" alone will not work. Here is a function that I use to cover all
situations:

Private Function IsButton(ByRef sClass As String) As Boolean
If InStr(1, sClass, "Button", vbTextCompare) <> 0 Then
IsButton = True
ElseIf UCase(sClass) Like "WINDOWSFORMS*.WINDOW.B.*" Then
' Delphi.Net
IsButton = True
End If
End Function


RB Smissaert

unread,
Oct 11, 2013, 6:21:51 PM10/11/13
to
Looking at WinSpy++ it looks it is the right window, as I can move it and
interact with it in other ways, using the
hwnd via the API.
Maybe it is a simulated button then.
Thanks for the tip.

RBS


"Farnsworth" <nos...@nospam.com> wrote in message
news:l39se6$9c9$1...@speranza.aioe.org...

RB Smissaert

unread,
Oct 11, 2013, 6:28:30 PM10/11/13
to
Thanks, that was a good tip and I can now get the right button click work
properly.
Will now have a look at WM_NCLBUTTONDOWN.
Are you saying I need to use that to be able to use SendMessage with no
coordinates?

RBS

"Farnsworth" <nos...@nospam.com> wrote in message
news:l39sci$906$1...@speranza.aioe.org...

Farnsworth

unread,
Oct 11, 2013, 6:31:28 PM10/11/13
to
"RB Smissaert" <bart.sm...@gmail.com> wrote in message
news:l39u23$f7d$1...@dont-email.me...
> Thanks, that was a good tip and I can now get the right button click work
> properly.
> Will now have a look at WM_NCLBUTTONDOWN.
> Are you saying I need to use that to be able to use SendMessage with no
> coordinates?
>
> RBS

No, you can't use the NC message unless you want to click on a window
border.


RB Smissaert

unread,
Oct 11, 2013, 6:47:15 PM10/11/13
to
OK, thanks.
Is it possible to send the click to a window without passing the coordinates
to SendMessage, as suggested by
CoderX? If so, how do you do it?

RBS


"Farnsworth" <nos...@nospam.com> wrote in message
news:l39u8l$dja$1...@speranza.aioe.org...

Farnsworth

unread,
Oct 11, 2013, 9:21:45 PM10/11/13
to
"RB Smissaert" <bart.sm...@gmail.com> wrote in message
news:l39v57$k5i$1...@dont-email.me...
> OK, thanks.
> Is it possible to send the click to a window without passing the
> coordinates to SendMessage, as suggested by
> CoderX? If so, how do you do it?
>
> RBS

You are using a weird application(Or an app with a skinned look). It's not
using standard Windows buttons even if they look like them. I have never
needed to control one of these apps, so I have never needed to send the
coordinates.




Deanna Earley

unread,
Oct 14, 2013, 4:59:54 AM10/14/13
to
On 12/10/2013 02:21, Farnsworth wrote:
> "RB Smissaert" <bart.sm...@gmail.com> wrote in message
> news:l39v57$k5i$1...@dont-email.me...
>> OK, thanks.
>> Is it possible to send the click to a window without passing the
>> coordinates to SendMessage, as suggested by
>> CoderX? If so, how do you do it?
>
> You are using a weird application(Or an app with a skinned look). It's not
> using standard Windows buttons even if they look like them. I have never
> needed to control one of these apps, so I have never needed to send the
> coordinates.

.Net buttons respond to the same messages as Win32 window classes.

Farnsworth

unread,
Oct 14, 2013, 1:21:13 PM10/14/13
to
"Deanna Earley" <dee.e...@icode.co.uk> wrote in message
news:l3gbq8$j2e$1...@speranza.aioe.org...
> On 12/10/2013 02:21, Farnsworth wrote:
>> "RB Smissaert" <bart.sm...@gmail.com> wrote in message
>> news:l39v57$k5i$1...@dont-email.me...
>>> OK, thanks.
>>> Is it possible to send the click to a window without passing the
>>> coordinates to SendMessage, as suggested by
>>> CoderX? If so, how do you do it?
>>
>> You are using a weird application(Or an app with a skinned look). It's
>> not
>> using standard Windows buttons even if they look like them. I have never
>> needed to control one of these apps, so I have never needed to send the
>> coordinates.
>
> .Net buttons respond to the same messages as Win32 window classes.
>

I know, but the button the OP is describing could be a PictureBox, Image
control, or a third party control as the one that comes with .Net has
"BUTTON" in its class name.


Farnsworth

unread,
Oct 14, 2013, 1:21:27 PM10/14/13
to
"Farnsworth" <nos...@nospam.com> wrote in message
news:l39sci$906$1...@speranza.aioe.org...
After checking the documentation for WM_LBUTTONDOWN, the coordinates are not
relative to the window upper left corner, but to the client area, so sending
(0,0) should work, but I am not sure why it doesn't. Sometimes it requires 2
clicks. The first click is used to give the button the focus, while the
second one does the actual clicking.


Farnsworth

unread,
Oct 14, 2013, 1:34:19 PM10/14/13
to
<bart.sm...@gmail.com> wrote in message
news:fede86f6-990a-4ac3...@googlegroups.com...
You may want to download ManagedSpy from here:

http://msdn.microsoft.com/en-us/magazine/cc163617.aspx

It lets see the list of controls in .Net apps, and their properties.
Strangely, you can also change these properties!


Deanna Earley

unread,
Oct 15, 2013, 3:50:33 AM10/15/13
to
On 14/10/2013 18:21, Farnsworth wrote:
> Sometimes it requires 2 clicks. The first click is used to give the
> button the focus, while the second one does the actual clicking.

I've seen this with the .Net toolstrip controls (which also have a class
of "WindowsForms10.Window.8.app.0.XXXXX"
It winds me up every time I encounter it :)
0 new messages