Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29277 Discussions

Centering popup windows in secondary monitor

michael_green
Beginner
1,342 Views

Hi All,

I want to have my popup windows centered over their parent window regardless of which monitor the parent window is currently on. The method I have found from Web searching depends on functions such as MonitorFromWindow, part of the MSDN Multiple Display Monitors Reference. But I can't find a way to link to these functions. For example:

integer*4, parameter:: MONITOR_DEFAULTNEAREST = 2
interface
   integer*4 function MonitorFromWindow(hWnd,Flags)
      integer*4,intent(in):: hWnd,Flags
   end function
end interface

hMonitor = MonitorFromWindow(hWndParent,MONITOR_DEFAULTNEAREST)

The linker gives me "Unresolved external symbol ...", etc

Any suggestions?

 

Many thanks in advance,

Mike

 

0 Kudos
11 Replies
andrew_4619
Honored Contributor III
1,342 Views

Ifort has already got interfaces for that.

it is in the module user32

so you can add "use user32" to our source to get the interface.

If you open user32.f90 you will see what the interface to make it work looks like.. There are a lot of things such as call convention etc you need to get right.

INTERFACE 
FUNCTION MonitorFromWindow( &
        hwnd, &
        dwFlags)
use ifwinty
  integer(HANDLE) :: MonitorFromWindow ! HMONITOR
    !DEC$ ATTRIBUTES DEFAULT, STDCALL, DECORATE, ALIAS:'MonitorFromWindow' :: MonitorFromWindow
  integer(HANDLE) hwnd ! HWND hwnd
  integer(DWORD) dwFlags ! DWORD dwFlags
 END FUNCTION
END INTERFACE

 

0 Kudos
JVanB
Valued Contributor II
1,342 Views

There's a lot of stuff wrong with your interface body. First off, don't declare any Windows data types as INTEGER*4 because many types change according as you are compiling for 32-bit or 64-bit Windows. The hwnd dummy argument to MonitorFromWindow is typed as HWND, which, if we search for "Windows data types msdn", we find is an alias for HANDLE which in ifort we prefer to conventionally refer to as INTEGER(HANDLE), where HANDLE = C_INTPTR_T. This makes it INTEGER*4 for 32-bit Windows and INTEGER*8 for 64-bit Windows.

Also the result variable of MonitorFromWindow is typed as HMONITOR, which we find out from the Windows data types page is also an alias for HANDLE, thus INTEGER(HANDLE). The dwFlags is typed as DWORD which an alias for unsigned LONG, so in ifort we generally let DWORD = C_LONG and type dwFlag as INTEGER(DWORD) which is ultimately INTEGER*4 in all versions of Windows.

Then there is the problem that MonitorFromWindow is typed as a C function in msdn, so unadorned dummy arguments actually have the VALUE attribute. Also, like most Win32 API functions, its interface is STDCALL, which is different from the default ABI for ifort, so you have to tell the compiler to compose the correct calling sequence and to get the name mangling right. One way is to use C binding, declare its name, and tell ifort that it is STDCALL via an attribute. Putting all this together, we get something like:

module M
   use ISO_C_BINDING, only: HANDLE => C_INTPTR_T, DWORD => C_LONG
   implicit none
   integer(DWORD), parameter :: &
      MONITOR_DEFAULTTONULL = int(Z'00000000', DWORD), &
      MONITOR_DEFAULTTOPRIMARY = int(Z'00000001', DWORD), &
      MONITOR_DEFAULTTONEAREST = int(Z'00000002',DWORD)
   interface
      function MonitorFromWindow(hwnd,dwFlags) &
         bind(C,name='MonitorFromWindow')
         import
         implicit none
!DEC$ ATTRIBUTES STDCALL :: MonitorFromWindow
         integer(HANDLE) MonitorFromWindow
         integer(HANDLE), value :: hwnd
         integer(DWORD), value :: dwFlags
      end function MonitorFromWindow
   end interface
   interface
      function GetConsoleWindow() bind(C,name='GetConsoleWindow')
         import
         implicit none
!DEC$ ATTRIBUTES STDCALL :: GetConsoleWindow
         integer(HANDLE) GetConsoleWindow
      end function GetConsoleWindow
   end interface
end module M

program P
   use M
   implicit none
   integer(HANDLE) hWndParent, hMonitor

   hWndParent = GetConsoleWindow()
   hMonitor = MonitorFromWindow(hWndParent,MONITOR_DEFAULTTONEAREST)
   write(*,*) hWndParent, hMonitor
end program P

Although this works with ifort (we have to remind ifort to link with user32.lib) there is a much simpler solution: ifort already provides the interfaces and named constants we need to do the work the modlule M in the example above. Instead, it's recommended that you forget about module M above and replace 'use M' with 'use IFWIN' and it will still work, even taking care of reminding ifort to link with user32.lib!

I take that back: for some reason ifort doesn't seem to supply an interface for GetConsoleWindow, so you would need to copy miine if you wanted to use my example. But IFWIN has most of the Win32 API stuff you need in it, so that should normally be your first source for resolving these interfacing issues.

 

0 Kudos
michael_green
Beginner
1,342 Views

Thanks for replies.

First, I have been using User32 and ifwin from the start but they did nothing.

I have a lot to learn here, so please forgive me if I miss obvious things ... I tried module M, but it won't compile and I don't know what to do about it. I get:

The BIND(C) attribute for this symbol conflicts with a DEC$ ATTRIBUTES ALIAS, DECORATE, STDCALL, C, [NO_]MIXED_STR_LEN_ARG or REFERENCE attribute for this symbol. [MONITORFROMWINDOW]

Please can you help.

Many thanks

Mike

0 Kudos
JVanB
Valued Contributor II
1,342 Views

ifort only started allowing !DEC$ ATTRIBUTES STDCALL with BIND(C) in the latest version (11/14) so if you can't upgrade, your best bet is probably to try to get USE IFWIN to work. Here, let me try to compose a working example with IFWIN:

module M
   interface
      function GetConsoleWindow()
         use ifwin, only: HANDLE
         implicit none
!DEC$ ATTRIBUTES STDCALL, DECORATE, ALIAS: 'GetConsoleWindow' :: GetConsoleWindow
         integer(HANDLE) GetConsoleWindow
      end function GetConsoleWindow
   end interface
end module M

program P
   use IFWIN
   use M
   implicit none
   integer(HANDLE) hWndParent, hMonitor

   hWndParent = GetConsoleWindow()
   hMonitor = MonitorFromWindow(hWndParent,MONITOR_DEFAULTTONEAREST)
   write(*,*) hWndParent, hMonitor
end program P

I am starting to see what you mean. The above works fine in 64-bit mode, but fails for some reason in 32-bit mode. Even though ifwin.mod and user32.mod are in the INCLUDE path.

echo %include%
C:\Program Files (x86)\Intel\Composer XE 2015\compiler\include;C:\Program Files
(x86)\Intel\Composer XE 2015\compiler\include\ia32;C:\Program Files (x86)\Micros
oft Visual Studio 10.0\\Intel Fortran\Microsoft Files\VC\atlmfc\include;C:\Progr
am Files (x86)\Microsoft Visual Studio 10.0\\Intel Fortran\Microsoft Files\VC\in
clude;C:\Program Files (x86)\Microsoft Visual Studio 10.0\\include;C:\Program Fi
les (x86)\Intel\Composer XE 2015\mkl\include;

The error message is:

Monitor2.f90(19): error #6404: This name does not have a type, and must have an
explicit type.   [MONITORFROMWINDOW]
   hMonitor = MonitorFromWindow(hWndParent,MONITOR_DEFAULTTONEAREST)
--------------^
compilation aborted for Monitor2.f90 (code 1)

I don't use 32-bit mode all that much, so I don't know what is wrong here.

 

0 Kudos
JVanB
Valued Contributor II
1,342 Views

OK, I have found what appears to be the problem. In user32.f90, at line 5447 just after SetLastErrorEx and before MonitorFromPoint, it says:

!DEC$ IF DEFINED(_M_IA64) .OR. DEFINED(_M_AMD64) .OR. DEFINED(__x86_64__)

And at line 5720 just after GetListBoxInfo and before DdeSetQualityOfService is the matching:

!DEC$ ENDIF

Although I can find the symbols SetLastErrorEx and DdeSetQualityOfService in the 32-bit version of user32.mod, I have not been able to find any of the symbols from MonitorFromPoint to GetListBoxInfo inclusive, although I searched for several. Coincidence? I think not!

 

0 Kudos
andrew_4619
Honored Contributor III
1,342 Views

It would seem there is some brokenness in user32 interfaces as RO has found, The code below works:

    subroutine test4()
        use GutilsDefs, only: ghwndMain ! handle to main window
        use Ifwin, only: MONITOR_DEFAULTTONEAREST, handle ! fials to find MONITORFROMWINDOW if put here
        !use user32, only: MonitorFromWindow              ! also fials to find MONITORFROMWINDOW
        implicit none  
        INTERFACE 
            FUNCTION MonitorFromWindow( hwnd, dwFlags)
                use ifwinty
                integer(HANDLE) :: MonitorFromWindow ! HMONITOR
                !DEC$ ATTRIBUTES DEFAULT, STDCALL, DECORATE, ALIAS:'MonitorFromWindow' :: MonitorFromWindow
                integer(HANDLE) hwnd ! HWND hwnd
                integer(DWORD) dwFlags ! DWORD dwFlags
            END FUNCTION
       END INTERFACE
       integer(handle) :: hMonitor

       hMonitor = MonitorFromWindow(ghwndMain,MONITOR_DEFAULTTONEAREST)
    end subroutine test4

The interface was just copy/pasted from user32.f90

0 Kudos
Steven_L_Intel1
Employee
1,342 Views

How very odd. I have seen issues like this before - it's not clear why such conditionalization was added. I will ask that it be removed.

0 Kudos
JVanB
Valued Contributor II
1,342 Views

Outside of the block mentioned, I checked user32.f90, kernel32.f90, and gdi32.f90 and found similar conditionalization, sometimes where the condition was reversed (marked _M_IX86)

user32.f90
GetMouseMovePointsEx
TrackMouseEvent _M_IX86
RegisterDeviceNotification
UnregisterDeviceNotification
BroadcastSystemMessage _M_IX86
InSendMessageEx
AnimateWindow
FlashWindowEx
GetClipboardSequenceNumber
GetMenuInfo
SetMenuInfo
EndMenu
GetProcessDefaultLayout
SetProcessDefaultLayout
GetGuiResources
EnumDisplaySettingsEx
EnumDisplayDevices

kernel32.f90
CreateFiber _M_IX86
DeleteFiber _M_IX86
ConvertThreadToFiber _M_IX86
SwitchToFiber _M_IX86
SwitchToThread _M_IX86
SetThreadIdealProcessor _M_IX86
TryEnterCriticalSection _M_IX86
SignalObjectAndWait _M_IX86
CreateWaitableTimer _M_IX86
OpenWaitableTimer _M_IX86
SetWaitableTimer _M_IX86
CancelWaitableTimer _M_IX86
FindFirstFileEx _M_IX86
CopyFileEx _M_IX86
GetCalendarInfo
SetCalendarInfo
EnumCalendarInfoEx
EnumDateFormatsEx
IsValidLanguageGroup
GetSystemDefaultUILanguage
GetUserDefaultUILanguage
EnumSystemLanguageGroups
EnumLanguageGroupLocales
EnumUILanguages

gdi32.f90
SetLayout
GetLayout
ColorCorrectPalette

BTW, looking at my include path back in Quote #5, some of the pathnames have double backslashes in them. placed there seemingly by ipsxe-comp-vars.bat . Are they supposed to be there?

 

0 Kudos
Steven_L_Intel1
Employee
1,342 Views

There are some of these that are legitimate - old 16-bit APIs not supported on x64. But I'll check them all out.

0 Kudos
Steven_L_Intel1
Employee
1,342 Views

I have escalated the problem for user32.f90 as issue DPD200365480. I've attached a revised source for user32 here - you can add it to your project if you want to use it. (This also adds GetClassLongPtr and SetClassLongPtr which have been asked about before.)

We have an ongoing project to add missing routines, and we'll be working on that over time. (We'll also remove inappropriate conditionalizations.)

0 Kudos
Steven_L_Intel1
Employee
1,342 Views

Oh, as for the double backslashes - VS sometimes adds these - they appear to be harmless.

0 Kudos
Reply