@andrew_4619,
Welcome, glad you have joined here in addition to the Intel forum!
From your comments, it appears you have Windows SDK installed and perhaps also Microsoft Windows C / C++ compiler via Microsoft Visual Studio application. Is that correct? If yes, a quick workaround you can use is the “command prompt” shortcuts made available via the Visual Studio installer. You likely know of them via Start → Programs and the folder for Visual Studio 201X. You can pick one of the prompts corresponding to your target platform, say 'x64 Native Tools Command Prompt for VS 201X". Will that be an option? If yes, things can be made much simpler by using the Microsoft Linker ‘link.exe’.
The usual libraries needed are ‘libcmt.lib’ and perhaps ‘user32.lib’.
Here’s a ‘Hello World’ example built with gfortran and Microsoft linker:
module IWinAPI_m
use, intrinsic :: iso_c_binding, only : c_char, c_null_char, c_int, c_ptr, C_NULL => c_null_ptr, c_loc
interface
function MessageBox(hWnd, lpText, lpCaption, uType) result(RetVal) &
bind(C, name="MessageBoxA")
!DIR$ ATTRIBUTES STDCALL :: MessageBox
! Microsoft Windows API function prototype
! https://docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-messagebox
! int MessageBox( HWND hWnd, LPCTSTR lpText, LPCTSTR lpCaption, UINT uType);
import :: c_ptr, c_int
! Argument List
type(c_ptr), intent(in), value :: HWnd
type(c_ptr), intent(in), value :: lpText
type(c_ptr), intent(in), value :: lpCaption
integer(c_int), intent(in), value :: uType
!.. Function result
integer(kind=c_int) :: RetVal
!GCC$ ATTRIBUTES STDCALL :: MessageBox
end function MessageBox
end interface
! Mnemonics
type :: MsgBoxFlags
integer(c_int) :: ABORTRETRYIGNORE = int(Z"00000002", kind=c_int)
integer(c_int) :: CANCELTRYCONTINUE = int(Z"00000006", kind=c_int)
integer(c_int) :: HELP = int(Z"00004000", kind=c_int)
integer(c_int) :: OK = int(Z"00000000", kind=c_int)
integer(c_int) :: OKCANCEL = int(Z"00000001", kind=c_int)
integer(c_int) :: RETRYCANCEL = int(Z"00000005", kind=c_int)
integer(c_int) :: YESNO = int(Z"00000004", kind=c_int)
integer(c_int) :: YESNOCANCEL = int(Z"00000003", kind=c_int)
integer(c_int) :: ICONEXCLAMATION = int(Z"00000030", kind=c_int)
end type
type(MsgBoxFlags), parameter, public :: MB = MsgBoxFlags()
contains
function WinMain( hInstance, hPrevInstance, lpCmdLine, nShowCmd ) result(RetVal) &
bind(C, name="WinMain")
!DIR$ ATTRIBUTES STDCALL :: WinMain
!GCC$ ATTRIBUTES STDCALL :: WinMain
! the entry point for any Windows program
! https://docs.microsoft.com/en-us/windows/win32/learnwin32/winmain--the-application-entry-point
! int WINAPI WinMain(HINSTANCE hInstance,
! HINSTANCE hPrevInstance,
! LPSTR lpCmdLine,
! int nShowCmd)
! Argument List
type(c_ptr), intent(in), value :: hInstance
type(c_ptr), intent(in), value :: hPrevInstance
character(kind=c_char, len=1), intent(in) :: lpCmdLine(*)
integer(c_int), intent(in), value :: nShowCmd
!.. Function result
integer(kind=c_int) :: RetVal
! Local variables
integer(c_int) :: uType
character(kind=c_char,len=:), allocatable, target :: Text
character(kind=c_char,len=:), allocatable, target :: Caption
Caption = c_char_"Fortran WinMain Function" // c_null_char
Text = c_char_"Hello World!" // c_null_char
uType = ior( MB%ICONEXCLAMATION, MB%OK)
RetVal = MessageBox( C_NULL, c_loc(Text), c_loc(Caption), uType )
return
end function WinMain
end module IWinAPI_m
Compilation and link steps:
** Visual Studio 2019 Developer Command Prompt v16.6.4
** Copyright (c) 2020 Microsoft Corporation
[vcvarsall.bat] Environment initialized for: ‘x64’
C:\Program Files (x86)\Microsoft Visual Studio\2019\Professional>cd\temp
C:\Temp>gfortran -c -std=f2018 p.f90
C:\Temp>link p.o libcmt.lib user32.lib /subsystem:windows /out:p.exe
Microsoft (R) Incremental Linker Version 14.26.28806.0
Copyright (C) Microsoft Corporation. All rights reserved.
C:\Temp>p.exe
C:\Temp>
Here’s the program output: