Yes. Complicated.
Premise:
I am running an Access database that needs info retrieved via FTP. It runs ftp.exe using a WScriptExec object and reads the stdOut to determine the date and time a directory was created (the name is the date and time in format 'd.yymmdd.hhmmss' so I just send an ls d.*
to the server). The code works except I want the window not to show up or at least be hidden faster.
Objective:
Find and manipulate the WScriptExec window by finding its handle (I inherently have the ProcessID, which is worthless apparently). No, I don't-want-to/cannot-in-this-application use .Run and output to a file. I may need to manipulate a window like this later and want to know how to do it without workarounds like "use this other method".
What I've Tried:
- FindWindow("Console,MSDOS,pretty much any made up class I could think of since I don't know class types", "C:\WINDOWS\system32\ftp.exe, C:\WINDOWS\system32\cmd.exe, ftp.exe, cmd.exe, pretty much every window title you can imagine")
All of these with vbNullString in the other argument. Getting 0 returned for everything I've tried.
- FindWindowLike
from this link. Getting 0 returned for everything I've tried. I modified it to popup every window it finds and did not see a window title that sounds right. So I'm assuming the title is not the caption shown in the WScriptExec command prompt window.
- GetForegroundWindow
. Returns my Access DB window, even after AppActivate objExec.ProcessID
.
Just FYI, how I'm calling the WScriptExec object:
Set objExec = objShell.Exec("cmd /c ftp -n ftp.server.location")
(I have tried without cmd /c
as well; both work )
This question may be a little old but I figure that this answer may still be able to help. (Tested with Excel VBA, have not been able to test with Access)
Very similar to usncahill's answer but instead of sleeping or waiting for the window to load it will continue to loop and look for the hwnd and execute as soon as it's found.
My below script takes the ProcessID from the Exec object to find the window's Hwnd. With the Hwnd you can then set the window's show state.
From my testing with Excel 2007 VBA, in most cases I never even see the window... In some cases it might be visible for a few milliseconds but would only appear a quick flicker or blink... Note: I had better results using SW_MINIMIZE than I did with SW_HIDE, but you can play around with it.
I added the TestRoutine Sub to show an example of how to use the 'HideWindow' function. The 'HideWindow' function uses the 'GetHwndFromProcess' function to get the window hwnd from the ProcessID.
Place the below into a Module...
Option Explicit
' ShowWindow() Commands
Public Const SW_HIDE = 0
Public Const SW_MINIMIZE = 6
'GetWindow Constants
Public Const GW_CHILD = 5
Public Const GW_HWNDFIRST = 0
Public Const GW_HWNDLAST = 1
Public Const GW_HWNDNEXT = 2
Public Const GW_HWNDPREV = 3
Public Const GW_OWNER = 4
' API Functions
Public Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
Public Declare Function GetWindow Lib "user32" (ByVal hwnd As Long, ByVal wCmd As Long) As Long
Public Declare Function GetDesktopWindow Lib "user32" () As Long
Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Sub TestRoutine()
Dim objShell As Object
Dim oExec As Object
Dim strResults As String
Set objShell = CreateObject("WScript.Shell")
Set oExec = objShell.Exec("CMD /K")
Call HideWindow(oExec.ProcessID)
With oExec
.StdIn.WriteLine "Ping 127.0.0.1"
.StdIn.WriteLine "ipconfig /all"
.StdIn.WriteLine "exit"
Do Until .StdOut.AtEndOfStream
strResults = strResults & vbCrLf & .StdOut.ReadLine
DoEvents
Loop
End With
Set oExec = Nothing
Debug.Print strResults
End Sub
Function HideWindow(iProcessID)
Dim lngWinHwnd As Long
Do
lngWinHwnd = GetHwndFromProcess(CLng(iProcessID))
DoEvents
Loop While lngWinHwnd = 0
HideWindow = ShowWindow(lngWinHwnd, SW_MINIMIZE)
End Function
Function GetHwndFromProcess(p_lngProcessId As Long) As Long
Dim lngDesktop As Long
Dim lngChild As Long
Dim lngChildProcessID As Long
On Error Resume Next
lngDesktop = GetDesktopWindow()
lngChild = GetWindow(lngDesktop, GW_CHILD)
Do While lngChild <> 0
Call GetWindowThreadProcessId(lngChild, lngChildProcessID)
If lngChildProcessID = p_lngProcessId Then
GetHwndFromProcess = lngChild
Exit Do
End If
lngChild = GetWindow(lngChild, GW_HWNDNEXT)
Loop
On Error GoTo 0
End Function
ShowWindow function: http://msdn.microsoft.com/en-us/library/windows/desktop/ms633548%28v=vs.85%29.aspx
GetWindow function: http://msdn.microsoft.com/en-us/library/windows/desktop/ms633515%28v=vs.85%29.aspx
GetDesktopWindow function: http://msdn.microsoft.com/en-us/library/windows/desktop/ms633504%28v=vs.85%29.aspx
GetWindowThreadProcessId function: http://msdn.microsoft.com/en-us/library/windows/desktop/ms633522%28v=vs.85%29.aspx
If you need more information on how the API's work, a quick google search will provide you with a ton of information.
I hope that this can help... Thank You.