Questions similar to this appear on the Be Communities MicroStation Programming Forum. This problem appeared in the VBA discussion group.
Q
How do I find the native Window handle (a Win32 HWND
) of a MicroStation view or dialog?
A MicroStation is a Windows application. MicroStation itself is a window, and each view and dialog within MicroStation is also a window. MicroStation VBA doesn't have a way to get a view or dialog window handle. However, you can get a window handle using MDL functions that are part of MicroStation. This article tells you how to use MDL functions to obtain a window handle.
Each Windows' window has a unique ID, assigned by Windows.
That unique ID is the Win32 HWND
handle.
A Win32 HWND
is useful to a programmer,
because once you have that handle, you can do things with a window or extract information about that window.
For more information about Windows programming, visit the Microsoft Developer Network web site.
There is no way to obtain a Win32 HWND
through VBA, but we can borrow the necessary function from
the MicroStation Development Library (MDL).
To use an MDL function, you must first Declare
it.
The declaration informs the VBA compiler of the function's name and the library (DLL
file) where it can be found.
External function declarations should be placed near the top of your VBA module, before any implementation code …
Declare PtrSafe Function mdlWindow_nativeWindowHandleGet Lib "stdmdlbltin.dll" ( _ ByRef nativeHandleP As LongPtr, _ ByVal windowP As LongPtr, _ ByVal type_ As Long) As LongPtr
For more information about the Declare
statement, see the VBA documentation.
It's common to use this technique to call Microsoft Win32
functions.
MicroStation CONNECT is a 64-bit app. and uses VBA 7.1, while MicroStation V8i is a 32-bit app. and uses VBA 6.5.
Microsoft introduced
additional VBA reserved words for VBA 7.1
(e.g. PtrSafe
) to accommodate 64-bit programming.
This code is provided by LA Solutions Ltd as an example. LA Solutions Ltd does not warrant the code fit for any particular purpose.
The example uses two MDL functions: mdlWindow_viewWindowGet
and mdlWindow_nativeWindowHandleGet
.
mdlWindow_viewWindowGet
converts a zero-based MicroStation view index to an MDL window pointer.
mdlWindow_nativeWindowHandleGet
converts the MDL window pointer to a Win32 HWND
.
The declaration of mdlWindow_nativeWindowHandleGet
corrects the documented MDL declaration.
If you use the MDL Declare
statement your code will cause MicroStation to exit spontaneously.
Option Explicit
' ---------------------------------------------------------------------
' MDL function declarations
' ---------------------------------------------------------------------
' The declaration below, taken from the MDL docs, is incorrect:
' Declare PtrSafe Function mdlWindow_nativeWindowHandleGet Lib "stdmdlbltin.dll" ( _
' ByVal nativeHandleP As Long, ByVal windowP As Long, ByVal type_ As Long) As Long
' This is the correct declaration for MicroStation CONNECT:
#If Win64 Then
Declare PtrSafe Function mdlWindow_nativeWindowHandleGet Lib "stdmdlbltin.dll" ( _
ByRef nativeHandleP As LongPtr, _
ByVal windowP As LongPtr, _
ByVal type_ As Long) As LongPtr
Declare PtrSafe Function mdlWindow_viewWindowGet Lib "stdmdlbltin.dll" ( _
ByVal viewNum As Long) As LongPtr ' Returns a pointer to a structure
#Else
Declare Function mdlWindow_nativeWindowHandleGet Lib "stdmdlbltin.dll" ( _
ByRef nativeHandleP As Long, _
ByVal windowP As LongPtr, _
ByVal type_ As Long) As Long
Declare Function mdlWindow_viewWindowGet Lib "stdmdlbltin.dll" ( _
ByVal viewNum As Long) As Long ' Returns a pointer to a structure
#End If
' ---------------------------------------------------------------------
' GetViewWindowHandle
' Gets a Win32 HWND handle to a MicroStation view window
' Note that VBA (and a MicroStation user) numbers views starting a 1,
' but the MDL functions used here are zero-based
' ---------------------------------------------------------------------
#If Win64 Then
Function GetViewWindowHandle(ByVal viewNum As Integer) As LongPtr
GetViewWindowHandle = 0
' MDL view number must be between 0 and 7, VBA uses 1..8
Debug.Assert viewNum <= 8 And 0 < viewNum
Const HANDLETYPE_HWND As Long = 0
Dim window As LongPtr ' Address of a Window 64-bit
Dim hwnd As LongPtr
window = mdlWindow_viewWindowGet(viewNum - 1)
Debug.Print "Window address " & CStr(window)
mdlWindow_nativeWindowHandleGet hwnd, window, HANDLETYPE_HWND
Debug.Print "HWND of View " & CStr(viewNum) & "=" & CStr(hwnd)
GetViewWindowHandle = hwnd
End Function
#Else
Function GetViewWindowHandle(ByVal viewNum As Integer) As Long
GetViewWindowHandle = 0
' MDL view number must be between 0 and 7, VBA uses 1..8
Debug.Assert viewNum <= 8 And 0 < viewNum
Const HANDLETYPE_HWND As Long = 0
Dim window As Long ' Address of a Window 32-bit
Dim hwnd As Long
window = mdlWindow_viewWindowGet(viewNum - 1)
Debug.Print "Window address " & CStr(window)
mdlWindow_nativeWindowHandleGet hwnd, window, HANDLETYPE_HWND
Debug.Print "HWND of View " & CStr(viewNum) & "=" & CStr(hwnd)
GetViewWindowHandle = hwnd
End Function
#End If
Test the above code …
' ---------------------------------------------------------------------
' Main entry point: start your code here
' ---------------------------------------------------------------------
Public Sub Main()
Const viewNum As Integer = 1 ' One-based: 1-8
' Test GetWindowHandle
#If Win64 Then
Dim hwnd As LongPtr
hwnd = GetViewWindowHandle(viewNum)
Debug.Print "View [" & CStr(viewNum) & "] handle " & CStr(hwnd)
#Else
Dim hwnd As Long
hwnd = GetViewWindowHandle(viewNum)
Debug.Print "View [" & CStr(viewNum) & "] handle " & CStr(hwnd)
#End If
End Sub