I’m trying to implement a wrapper for Windows virtual terminal processing, so you can print out coloured text to the stdout. However, I have to make a C pointer to a Fortran variable and pass that pointer to a Win32 procedure to be modified by it. This procedure requires that pointer to be of LPDWORD type. For those not familiar with Win32 typedefs, LPDWORD is a long pointer to DWORD (i.e a 64bit pointer to an unsigned int). But so far I’ve only managed to make a type(C_PTR) to the variable. Since these types are different, ifort refuses to compile the module.
Here’s the function:
EDIT - Including the whole source.
module vtprocessing
use IFWINTY
use ISO_C_BINDING
use kernel32
implicit none
contains
function activate() result(success)
integer(HANDLE) :: hStdOut
logical :: success
integer(DWORD), pointer :: dwMode
integer(DWORD) :: ENABLE_VIRTUAL_TERMINAL_PROCESSING = 4
integer(LPDWORD) :: lpMode
type(C_PTR) :: ptr_to_dwMode
integer(BOOL) :: get, set
! Get the STDOUT's handle
hStdOut = GetStdHandle(STD_OUTPUT_HANDLE)
! Needs to be a 64bit pointer to dwMode (&dwMode)
ptr_to_dwMode = c_loc(dwMode)
! If accessing STDOUT handle failed,
if(hStdOut == INVALID_HANDLE_VALUE) then
success = .false.
else
! Get the console mode, lpMode is supposed to be &dwMode.
! GetConsoleMode(hStdOut, &dwMode)
get = GetConsoleMode(hStdOut, ptr_to_dwMode )
! error occurs here --------------------------.^
if (get /= FALSE) then
! dwMode |= ENABLE_VIRTUAL_TERMINAL_PROCESSING
dwMode = ior(dwMode, ENABLE_VIRTUAL_TERMINAL_PROCESSING)
! Set the console mode, to enable virtual terminal processing.
set = SetConsoleMode(hStdOut, dwMode)
! If setting the new console mode, failed
if(set /= FALSE) then
success = .true.
end if
end if
end if
end function activate
end module vtprocessing
c_loc’s returns can only be assigned to a type(C_PTR) type variable. GetConsoleMode requires an integer(LPDWORD) type variable. In C world, these two are identical (You could technically pass any 64bit pointer where the argument is LPDWORD). I think Fortran having more strict type system prohibits this. How can I get around this?
P.S. I’m new to Fortran and here’s an equivalent C wrapper for reference.
Hi, thanks for the suggestion, but I don’t think that library (module?) will work on Windows. In Windows simply appending or prepending colour codes and escape sequences won’t print out colours. Because Windows’s cmd.exe is insensitive to these ANSI escapes by default. You first have to enable the virtual terminal processing in the current instance of cmd.exe (like sensitizing it to the colour codes and escapes) in order for them to work. This is exactly what I’m trying to accomplish. The library you pointed didn’t seem to interface with Win32 (I went through the source, and didn’t see any platform specific header guards or any interfaces to win32 functions). He/She probably didn’t consider Windows support when making that library.
Hey, well I honestly I don’t know how he managed, I stumbled on this library by pure chance as it was the dependency of another lib I was testing, and when running the unit tests using fpm I saw the nice outputs: this is a cmd windows output, I compiled using ifort
Look into interoperability in Fortran in C with BIND(C) clause and also into intrinsic module ISO_C_BINDING that provides various named constants and interfaces (function prototypes) for utilities which help toward interoperating in Fortran with C. Here’re a couple of sources (link and link) that might serve as a quick start guides.
In particular, try out the named constant c_intptr_t.
integer(kind=c_intptr_t) can help you interoperate with LPDWORD Windows data type on Windows OS
What is unclear in your activate() function is at which point dwMode (which is a Fortran pointer) is initialised? Between the declaration and the c_loc() call I can see nothing. But maybe you haven’t put the whole code?
EDIT
You are maybe taking the problem on the wrong side… In Fortran, by default all arguments are passed by reference, that is by address. In a = somefunction(x,y), the function receives the addresses of x and y, you don’t need to explicitely get them.
About the GetConsoleMode() function: is it a C function, or a Fortran wrapper?
Thanks again. I tried it too and It does work on my machine as well. I’m honestly lost on how that was possible. I always leverage win32 to print coloured outputs. Hell, even in Python, I write win32 wrappers using the ctypes (wintypes, windll) for this instead of using colourama. But this implementation seems mysteriously straightforward and elegant (and in pure Fortran too).
All this aside, the reason I was trying to do this is to learn Fortran, using a library isn’t going to help in that regard. I’m going make this work lol.
I’ll give more details here (but the function is complete) dwMode is a uint32_t variable. Whose address (which will be of type LPDWORD) needs to be passed to the GetConsoleMode() function, which will modify the value at the address of dwMode. So, once the function exits, dwMode will be storing the value of the current console mode.
What I was doing (or at least I thought I was doing) is to get the address of dwMode using c_loc() and pass that pointer to the GetConsoleMode() function. (C ish way). But Fortran says the types are incompatible. Return type of c_loc is type(C_PTR) but GetConsoleMode expects a integer(LPDWORD) type. This is where I’m lost.
And yes, all the three GetConsoleMode(), SetConsoleMode() & GetStdHandle() are C functions from Win32, not my wrappers!.
As, you say all arguments are passed by references in Fortran, will declaring integer(DWORD) :: dwMode and passing just dwMode to GetConsoleMode() will suffice? (I’m assuming Fortran will pass the address of dwMode to GetConsoleMode() so the callee can write to that address).
Does this also imply that when you pass a variable to a function from the caller’s stack, it will get modified in place by the callee (C’s equivalent of passing the pointer of a variable from caller’s stack to the calee??)
Edit: What remains unclear for me is whether the functions you are calling: GetStdHandle, GetConsoleMode, and SetConsoleMode have defined interfaces, or are they external procedures? Are these routines from the kernel32 module provided by the Intel library modules?
Yes, but the fact that you can call them directly from Fortran without any trick probably means that your IDE (Visual Studio?) provides Fortran interfaces to them. Which is confirmed by the fact that the compiler complains about the type mismatch for the arguments (without interface no argument check is performed).
Since you’re ok with Intel-specific solution toward working Windows OS APIs, one thing you can consider is perusing kernel32.f90 file in your C:\Program Files (x86)\Intel\oneAPI\compiler\XXX\windows\compiler\include folder (where XXX = 2023.1.0 for example for latest Intel oneAPI 2023.1 version).
In kernel32.f90, you will find Intel’s declaration of the Fortran interface to GetConsoleMode for example is as follows:
FUNCTION GetConsoleMode( &
hConsoleHandle, &
lpMode)
import
integer(BOOL) :: GetConsoleMode ! BOOL
!DEC$ ATTRIBUTES DEFAULT, STDCALL, DECORATE, ALIAS:'GetConsoleMode' :: GetConsoleMode
integer(HANDLE) hConsoleHandle ! HANDLE hConsoleHandle
integer(LPDWORD) lpMode ! LPDWORD lpMode
END FUNCTION
END INTERFACE
Given above, you can simply consider doing the following in your code:
function activate() result(success)
integer(HANDLE) :: hStdOut
logical :: success
integer(LPDWORD) :: lpMode !<-- Notice this
! https://learn.microsoft.com/en-us/windows/console/setconsolemode
integer(LPDWORD), parameter :: ENABLE_VIRTUAL_TERMINAL_PROCESSING = int(Z'0004', kind=LPDWORD)
type(C_PTR) :: ptr_to_dwMode
integer(BOOL) :: get, set
! Get the STDOUT's handle
hStdOut = GetStdHandle(STD_OUTPUT_HANDLE)
! Needs to be a 64bit pointer to dwMode (&dwMode)
ptr_to_dwMode = c_loc(dwMode)
! If accessing STDOUT handle failed,
if(hStdOut == INVALID_HANDLE_VALUE) then
success = .false.
else
! Get the console mode, lpMode is supposed to be &dwMode.
! GetConsoleMode(hStdOut, &dwMode)
get = GetConsoleMode(hStdOut, lpMode)
..
lpMode = ior(lpMode, ENABLE_VIRTUAL_TERMINAL_PROCESSING)
! Set the console mode, to enable virtual terminal processing.
set = SetConsoleMode(hStdOut, lpMode)
..
and consume the lpMode object in subsequent instructions directly such as with enabling virtual terminal processing (IOR instruction) and the SetConsoleMode invocation.
You could also just call your existing C procedure, by adding the corresponding interface:
interface
function ActivateVirtualTerminalEscapes() bind(c,name="ActivateVirtualTerminalEscapes")
import BOOL
integer(BOOL) :: ActivateVirtualTerminalEscapes
end function
end interface
integer(BOOL) :: istat
istat = ActivateVirtualTerminalEscapes() ! istat := 1 if success, 0 if failure
Thank you. I was indeed using the kernel32 module from Intel. Unfortunately, the code you suggest terminates with a access violation at
I placed breakpoints in all 3 lines where a win32 function is invoked and the first one worked fine (GetStdHandle(STD_OUTPUT_HANDLE) implying that the C FFI is working fine. But when the debugger hit the second breakpoint get = GetConsoleMode(hStdOut, lpMode) Visual Studio throws a runtime access violation exception from kernel32.dll. So, there’s something wrong with the way Fortran passing the address of lpMode to GetConsoleMode() function.
Thank you. Appreciate the help. I tried this, but didn’t work. Anyways I’m going to stop messing around with this for a while. I’m spending too much time on this. FFIs pretty advanced stuff and I guess that I shouldn’t have touched it without at least developing moderate literacy in Fortran.
Last, but not least I learned a lot from you all. And thank you all for all the help.
Microsoft’s API documentation as shown here basically indicates lpMode is a pointer to a DWORD. But separately the Microsoft developer network documentation and toolsets inform the coder that such a pointer is a 32-bit word with a 32-bit application (e.g., what is built using IA32 from Intel / x86 toolsets from Microsoft on Windows OS) whereas it’s a 64-bit word on a 64-bit application i.e., the ones built using Intel 64 from Intel / x64 toolsets from Microsoft on Windows OS.
Intel’s ifwinty.90 takes care of this via its own INT_PTR_KIND function, so Intel Fortran customers don’t need to sweat such details. They can simply USE the constants and interfaces from IFWINTY, kernel32 modules, etc. and move on.
On the other hand, Fortran standard offers an alternate option such that the declaration could instead have been like so where c_intptr_t is a named constant toward a suitable integer KIND for the pointer object from ISO_C_BINDING intrinsic module: