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

Integrate C-DLL in Fortran Code

Dave12
Novice
2,432 Views

I am trying to integrate a DLL into a Fortran program. A dynamic link is to be created. The DLL is provided to me, it was written in C. I have already read many forum posts, but unfortunately cannot really apply the answers to my code.
I use the ifort compiler and VS 2019. I have added the location of the DLL under "Properties->Linker->Input->Additional Dependencies". Now I am trying to call the subroutine DISCON from the DLL of the same name as follows:

  ! ------------------------ defining the contoller variables 
    !real(C_FLOAT), allocatable  :: ctrl_avrSWAP(*)               
    real(C_FLOAT), allocatable :: ctrl_avrSWAP(:)                    
    integer(C_INT)              :: ctrl_aviFAIL                    
    character(kind=C_CHAR)      :: ctrl_accINFILE(50)              
    character(kind=C_CHAR)      :: ctrl_avcOUTNAME(51)           
    character(kind=C_CHAR)      :: ctrl_avcMSG(49)              
    
    
    ! ------------------------- including the controller-.dll 
    interface 
 subroutine DISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG )  bind (C, NAME='DISCON') 
            import
            
             real(C_FLOAT),          intent(inout) :: avrSWAP(*)      
             integer(C_INT),         intent(inout) :: aviFAIL        
             character(kind=C_CHAR), intent(in)    :: accINFILE(*)      
             character(kind=C_CHAR), intent(in)    :: avcOUTNAME(*)     
             character(kind=C_CHAR), intent(inout) :: avcMSG(*)        
    
       end subroutine DISCON  
    end interface 
    
    
allocate(ctrl_avrSWAP(1000))
ctrl_avrSWAP = 0.0
ctrl_avrSWAP(4) = 0.1

! ------------------------- Call the controller ------------
call DISCON(ctrl_avrSWAP,ctrl_aviFAIL,ctrl_accINFILE,ctrl_avcOUTNAME,ctrl_avcMSG)
! ----------------------------------------------------------

Then I try to call it in the code excerpt with example values and get the error:

Error LNK2019: Reference to unlisted external symbol "DISCON" in function "MAIN_STRUCTURE". main_structure.obj

 

Any answer is very much apprechiated.

0 Kudos
1 Solution
FortranFan
Honored Contributor III
2,230 Views

@Dave12 ,

Re: your question, "If I understood correctly LoadLibrary needs the DLL as input and would output some kind of an .h-file?" if you go through the example at the hyperlink(s) pointing to Microsoft documentation, you will see the answer is no.

If you're working with Fortran as you indicate in your original post, then you will set up everything programmatically and when your program runs, at that time your code will allow a dynamic run-time linking with the C++ DLL you receive, your code then fetches a C pointer to the procedure address (e.g., DISCON), the code then sets up a Fortran procedure pointer, and then the procedure from the C++ DLL gets used via this Fortran procedure pointer. 

Say whoever hands you the C++ Dll has the following "brilliant" code for DISCON in their library:

 

#include <iostream>
using namespace std;

extern "C" {
  void DISCON(float *, int *, const char *, const char *, char *);
}
 
extern "C" void DISCON(float* avrSWAP, int* aviFAIL, const char* accINFILE, const char* avcOUTNAME, char * avcMSG)
{
   std::cout << "In DISCON:\n";
   std::cout << "accINFILE: " << accINFILE << "\n";
   std::cout << "avcOUTNAME: " << avcOUTNAME << "\n";
   std::sprintf(avcMSG, "Hello World!");
   *avrSWAP = 99.0;
   *aviFAIL = 42;
   return;
}

 

Here's a simple illustrative example of a Fortran program that uses the above only with the DLL file i.e., no LIB file:

 

! A simple unit test toward the external procedure in a C++ Dll
   
   use, intrinsic :: iso_c_binding, only : c_float, c_int, c_char, c_null_char
   use DISCON_m, only : SetupDISCON, DISCON

   ! ------------------------ defining the contoller variables 
   real(c_float), allocatable :: ctrl_avrSWAP(:)                    
   integer(c_int)             :: ctrl_aviFAIL                    
   character(kind=c_char,len=50) :: ctrl_accINFILE
   character(kind=c_char,len=51) :: ctrl_avcOUTNAME           
   character(kind=c_char,len=49) :: ctrl_avcMSG              
   
   call SetupDISCON() !<-- important

   ctrl_accINFILE = c_char_"Test_accINFILE" // c_null_char
   ctrl_avcOUTNAME = c_char_"Test_avcOUTNAME" // c_null_char
   ctrl_avcMSG = c_null_char
   ctrl_avrSWAP = [ 0.0_c_float ]
   ctrl_aviFAIL = 0_c_int

   ! Consume the method from the C++ Dll
   call DISCON( ctrl_avrSWAP, ctrl_aviFAIL, ctrl_accINFILE, ctrl_avcOUTNAME, ctrl_avcMSG )
   print *, "In Fortran Main:"
   print *, "avrSWAP : ", ctrl_avrSWAP(1)
   print *, "ctrl_aviFAIL : ", ctrl_aviFAIL
   print *, "ctrl_avcMSG : ", ctrl_avcMSG
   
end

 

The program above when run can produce the following output:

 

In DISCON:
accINFILE: Test_accINFILE
avcOUTNAME: Test_avcOUTNAME
 In Fortran Main:
 avrSWAP :  99.00000
 ctrl_aviFAIL :  42
 ctrl_avcMSG : Hello World!

 

Now, note the Fortran program above is **helped** by 3 Fortran modules.

First, a module to manage the details with the C++ Dll, called DISCONDll.dll for illustration:

 

module DISCON_m
! Module to define Fortran interfaces of procedures to be consumed from C++ Dll(s) 

   use, intrinsic :: iso_c_binding, only : c_float, c_int, c_char
   use DllHelper_m, only : DllHelper_t

   private
   
   abstract interface 
      subroutine IDISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) bind(C)
      ! Assumes the C++ function prototype is as follows:
      ! extern "C" void DISCON(float *, int *, const char *, const char *, char *)
         import :: c_float, c_int, c_char
         real(c_float),          intent(inout) :: avrSWAP(*)      
         integer(c_int),         intent(inout) :: aviFAIL        
         character(kind=c_char), intent(in)    :: accINFILE(*)      
         character(kind=c_char), intent(in)    :: avcOUTNAME(*)     
         character(kind=c_char), intent(inout) :: avcMSG(*)        
      end subroutine IDISCON  
   end interface
   
   ! Program variables
   type(DllHelper_t), save :: DISCONDll
   procedure(IDISCON), pointer, save, protected, public :: DISCON => null()
   
   public :: SetupDISCON
   
contains

   subroutine SetupDISCON()
   
      use, intrinsic :: iso_c_binding, only : c_funptr, c_associated, c_f_procpointer
   
      type(c_funptr) :: pDISCON
      integer :: irc
   
      call DISCONDll%Load( "DISCONDll.dll", irc )
      if ( irc /= 0 ) then
         stop "Failed to load DISCON.dll"
      end if
   
      pDISCON = DISCONDll%GetFunPtr( "DISCON" )
      if ( .not. c_associated(pDISCON) ) then
         stop "Failed to get the address of DISCON procedure"
      end if
      call c_f_procpointer( cptr=pDISCON, fptr=DISCON )

      if ( .not. associated(DISCON) ) then
         stop "DISCON is not associated."
      end if
   
   end subroutine
   
end module

 

Then another module for a helper "class" for working with DLLs generally on Windows:

 

module DllHelper_m
! Purpose    : Helper module and type to work with Dlls on Windows
! Author     : FortranFan
! Reference  : Using Run-Time Dynamic Linking
!              https://docs.microsoft.com/en-us/windows/win32/dlls/using-run-time-dynamic-linking
! Description:
! This module defines a public type, DllHelper_t, to work with DLLs on Windows.  This type has
!  - Load method with an Dll name as input to load the DLL
!  - GetFunPtr to dispatch a C function pointer for an exported procedure in the Dll; the proc
!    name string is the input
!  - a finalizer that frees up the Dll when the object is destroyed.
!

   use, intrinsic :: iso_c_binding, only : c_char, c_funptr, c_null_funptr
   use IWINApi_m, only : HMODULE, NULL_HANDLE, BOOL, LoadLibrary, GetProcAddress, FreeLibrary

   private

   type, public :: DllHelper_t
      private
      character(kind=c_char, len=:), allocatable :: m_DllName
      integer(HMODULE) :: m_DllHandle = NULL_HANDLE
   contains
      final :: FreeDll
      procedure, pass(this) :: Load => LoadDll
      procedure, pass(this) :: GetFunPtr
   end type
   
contains
    
   subroutine FreeDll( this )
   ! Unload the DLL and free up its resources
      type(DllHelper_t), intent(inout) :: this

      ! Local variables
      integer(BOOL) :: iret

      if ( this%m_DllHandle /= NULL_HANDLE ) then
         iret = FreeLibrary( this%m_DllHandle )
      end if
      this%m_DllHandle = NULL_HANDLE
      
      return
        
   end subroutine 

   subroutine LoadDll( this, DllName, iret )
   ! Load the DLL and set up its handle

      class(DllHelper_t), intent(inout) :: this
      character(kind=c_char, len=*), intent(in) :: DllName
      integer(BOOL), intent(inout) :: iret

      iret = 0
      this%m_DllHandle = LoadLibrary( DllName )
      if ( this%m_DllHandle == NULL_HANDLE ) then
         iret = 1 !<-- TODO: replace with GetLastError
      end if
      
      return
        
   end subroutine 

   function GetFunPtr( this, ProcName ) result(FunPtr)
   ! Get the function pointer

      class(DllHelper_t), intent(inout) :: this
      character(kind=c_char, len=*), intent(in) :: ProcName
      ! Function result
      type(c_funptr) :: FunPtr

      FunPtr = GetProcAddress( this%m_DllHandle, ProcName )
      
      return
        
   end function 

end module 

 

And a third one to work with the Windows APIs provided by Microsoft:

 

module IWinAPI_m
! Purpose    : Interfaces toward Microsoft Windows API functions
! Author     : FortranFan
! Reference  : Microsoft Documentation
!
! Description:
! This module defines the interfaces and type aliases toward Windows APIs.
!
   
   use, intrinsic :: iso_c_binding, only : c_char, c_int, c_intptr_t, c_funptr

   implicit none

   !.. Public by default
   public

   !.. Mnemonics for types in Windows API functions
   integer(c_int), parameter :: HMODULE = c_intptr_t  !.. A handle to a module; base address in memory
   integer(HMODULE), parameter :: NULL_HANDLE = int( 0, kind=kind(NULL_HANDLE) )
   integer(c_int), parameter :: BOOL = c_int

   interface

      function LoadLibrary(lpLibName) bind(C, name='LoadLibraryA') result(RetVal)
      !DIR$ ATTRIBUTES STDCALL :: LoadLibrary
      ! https://docs.microsoft.com/en-us/windows/win32/api/libloaderapi/nf-libloaderapi-loadlibrarya
      ! HMODULE LoadLibraryA( [in] LPCSTR lpLibFileName );

         import :: c_char, HMODULE

         !.. Argument list
         character(kind=c_char, len=1), intent(in) :: lpLibName(*)
         !.. Function result
         integer(HMODULE) :: RetVal

      end function LoadLibrary

      function FreeLibrary(lpLibHandle) bind(C, NAME='FreeLibrary') result(RetVal)
      !DIR$ ATTRIBUTES STDCALL :: FreeLibrary
      ! https://docs.microsoft.com/en-us/windows/win32/api/libloaderapi/nf-libloaderapi-freelibrary
      ! BOOL FreeLibrary( [in] HMODULE hLibModule );

         import :: HMODULE, BOOL

         !.. Argument list
         integer(HMODULE), value :: lpLibHandle
         !.. Function result
         integer(BOOL) :: RetVal

      end function FreeLibrary

      function GetProcAddress(lpLibHandle, lpProcName) bind(C, name='GetProcAddress') result(RetVal)
      !DIR$ ATTRIBUTES STDCALL :: GetProcAddress
      ! https://docs.microsoft.com/en-us/windows/win32/api/libloaderapi/nf-libloaderapi-getprocaddress
      ! FARPROC GetProcAddress( [in] HMODULE hModule, [in] LPCSTR  lpProcName );

         import :: HMODULE, c_char, c_funptr

         !.. Argument list
         integer(HMODULE), intent(in), value      :: lpLibHandle
         character(kind=c_char,len=1), intent(in) :: lpProcName(*)
         !.. Function result
         type(c_funptr) :: RetVal

      end function GetProcAddress

   end interface

end module IWinAPI_m

 

Attached also here is a Visual Studio solution for illustration purposes only, meaning it is not intended as the final answer to your problem by any means.  Rather it is only meant to show you a way run-time dynamic-linking can work with a C++ DLL and a Fortran program.  You can then walk through it and adapt it to your situation as you see fit.

In Visual Studio, a Rebuild selection with the attached file when unzipped to a folder (say C:\temp) can produce the following output:

Build started...
1>------ Build started: Project: DISCONDll, Configuration: Debug x64 ------
1>Dllmain.cpp
1>DISCON.cpp
1>Generating Code...
1>   Creating library Debug\x64\DISCONDll.lib and object Debug\x64\DISCONDll.exp
1>DISCON.vcxproj -> C:\Temp\DISCON\Debug\x64\DISCONDll.dll
2>------ Build started: Project: TestDISCON (IFORT), Configuration: Debug x64 ------
2>Copy C:\Temp\DISCON\Debug\x64\DISCONDll.dll" to Debug\x64
2>C:\Temp\DISCON\Debug\x64\DISCONDll.dll
2>1 File(s) copied
2>Compiling resources...
2>ForMain.rc
2>Microsoft (R) Windows (R) Resource Compiler Version 10.0.10011.16384
2>Copyright (C) Microsoft Corporation.  All rights reserved.
2>Compiling with Intel® Fortran Compiler Classic 2021.6.0 [Intel(R) 64]...
2>IWinAPI.f90
2>DllHelper.f90
2>DISCON.f90
2>C:\Temp\DISCON\sor\DISCON.f90: warning #6178: The return value of this FUNCTION has not been defined.   [FUNPTR]
2>TestDISCON.f90
2>Linking...
2>Embedding manifest...
2>
2>Build log written to  "file://C:\Temp\TestDISCON\Debug\x64\TestDISCON_BuildLog.htm"
2>TestDISCON - 0 error(s), 1 warning(s)
========== Build: 2 succeeded, 0 failed, 0 up-to-date, 0 skipped ==========

View solution in original post

11 Replies
Dave12
Novice
2,423 Views

Smal correction: The DLL is created by C++ code

0 Kudos
mecej4
Honored Contributor III
2,402 Views

If you build the DLL from sources, the build process should generate an import library along with the DLL. That import library should be among the "additional libraries" to be linked in when you build your Fortran program.

 

If you do not have the import library, ask the provider of the DLL for it. If that is not possible, you can try to make do by generating the import library yourself, but this will involve trial and error, and possibly frustrating crashes in the process. The details are covered in the Mixed Language Programming section of the IFort documentation. The VS utility Dumpbin is quite useful in this process, but again it requires reading, learning and getting used to its command options.

0 Kudos
Dave12
Novice
2,380 Views

Thanks for you answer.

Is it always necessary to have the DLL and the LIB to include the subroutine as I intended? The provider of the LIB told me that in the particular case of the DLL no additional library is needed. Might that be the case or is it more of a "programming issue"?

0 Kudos
mecej4
Honored Contributor III
2,378 Views

Whether an import library is needed or not depends on the linker. The linker can itself generate such a library from a DEF file, or the compilers can arrange to have directives in your C/Fortran sources cause a library to be produced. Some linkers, such as the GNU linker used by Gfortran, can directly link to the DLL without needing an import library.

0 Kudos
FortranFan
Honored Contributor III
2,356 Views

@Dave12 ,

In situations where you have a supplier who provides you with a Windows DLL but not the LIB file and who may then have a workflow of introducing more exported functions in said DLL whilst not maintaining their ordinal numbers in the export table, a suggested approach will be for you to consider dynamically linking with this DLL at run-time using Microsoft's LoadLibrary API and fetching the function addresses of interest using the GetProcAddress API.  This is as opposed to what your original post suggests which is an attempt to statically link in the external procedure.

With the above approach, in Fortran you can load the DLL Handle returned by LoadLibrary API into a suitable size integer compatible with Microsoft's C++ API, then use that to get the procedure address of "DISCON" function you can store into a type c_funptr from ISO_C_BINDING.  Then employ C_F_PROCPOINTER to transfer the procedure address to a Fortran procedure pointer.  You can then consume "DISCON" in your Fortran code via this pointer.

Here, the interface you show in the original post is better defined as an "ABSTRACT INTERFACE" and you can then define the procedure pointer mentioned in the previous paragraph to have the same interface.

 

abstract interface 
   subroutine IDISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) bind(C) 
      import
      real(C_FLOAT),          intent(inout) :: avrSWAP(*)      
      integer(C_INT),         intent(inout) :: aviFAIL        
      character(kind=C_CHAR), intent(in)    :: accINFILE(*)      
      character(kind=C_CHAR), intent(in)    :: avcOUTNAME(*)     
      character(kind=C_CHAR), intent(inout) :: avcMSG(*)        
   end subroutine IDISCON  
end interface
 
..
type(c_funptr) :: pDISCON
procedure(IDISCON), pointer :: DISCON
..
pDISCON = GetProcAddress( .. )
call c_f_procpointer( cptr=pDISCON, fptr=DISCON )
! Error checking for null handle and null address, etc. elided
..
call DISCON( .. )  

 

 

Dave12
Novice
2,295 Views

Hello @FortranFan 

Thanks a lot for your answer.

I am not sure how to deal with the LoadLibrary and the GetProcAddress statements. If I understood correctly LoadLibrary needs the DLL as input and would output some kind of an .h-file? That again would be the input argument of GetProcAddress ? Acctually a .h file was delivered to me, too. They weren't sure if I would need it.

Tanks again for your support and best regards

0 Kudos
jimdempseyatthecove
Honored Contributor III
2,276 Views

If you click on the hyperlinks you will find the documentation (and examples of use) for Microsoft Visual Studio runtime functions. What you won't get is the interface (aka API) for the DLL you intend to load. You will need that from the DLL provider (or other source).

 

Additional suggestions to FortranFan's advice is for you to pay particular interest as to if the arguments are passed by value of passed by reference. See this.

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor III
2,231 Views

@Dave12 ,

Re: your question, "If I understood correctly LoadLibrary needs the DLL as input and would output some kind of an .h-file?" if you go through the example at the hyperlink(s) pointing to Microsoft documentation, you will see the answer is no.

If you're working with Fortran as you indicate in your original post, then you will set up everything programmatically and when your program runs, at that time your code will allow a dynamic run-time linking with the C++ DLL you receive, your code then fetches a C pointer to the procedure address (e.g., DISCON), the code then sets up a Fortran procedure pointer, and then the procedure from the C++ DLL gets used via this Fortran procedure pointer. 

Say whoever hands you the C++ Dll has the following "brilliant" code for DISCON in their library:

 

#include <iostream>
using namespace std;

extern "C" {
  void DISCON(float *, int *, const char *, const char *, char *);
}
 
extern "C" void DISCON(float* avrSWAP, int* aviFAIL, const char* accINFILE, const char* avcOUTNAME, char * avcMSG)
{
   std::cout << "In DISCON:\n";
   std::cout << "accINFILE: " << accINFILE << "\n";
   std::cout << "avcOUTNAME: " << avcOUTNAME << "\n";
   std::sprintf(avcMSG, "Hello World!");
   *avrSWAP = 99.0;
   *aviFAIL = 42;
   return;
}

 

Here's a simple illustrative example of a Fortran program that uses the above only with the DLL file i.e., no LIB file:

 

! A simple unit test toward the external procedure in a C++ Dll
   
   use, intrinsic :: iso_c_binding, only : c_float, c_int, c_char, c_null_char
   use DISCON_m, only : SetupDISCON, DISCON

   ! ------------------------ defining the contoller variables 
   real(c_float), allocatable :: ctrl_avrSWAP(:)                    
   integer(c_int)             :: ctrl_aviFAIL                    
   character(kind=c_char,len=50) :: ctrl_accINFILE
   character(kind=c_char,len=51) :: ctrl_avcOUTNAME           
   character(kind=c_char,len=49) :: ctrl_avcMSG              
   
   call SetupDISCON() !<-- important

   ctrl_accINFILE = c_char_"Test_accINFILE" // c_null_char
   ctrl_avcOUTNAME = c_char_"Test_avcOUTNAME" // c_null_char
   ctrl_avcMSG = c_null_char
   ctrl_avrSWAP = [ 0.0_c_float ]
   ctrl_aviFAIL = 0_c_int

   ! Consume the method from the C++ Dll
   call DISCON( ctrl_avrSWAP, ctrl_aviFAIL, ctrl_accINFILE, ctrl_avcOUTNAME, ctrl_avcMSG )
   print *, "In Fortran Main:"
   print *, "avrSWAP : ", ctrl_avrSWAP(1)
   print *, "ctrl_aviFAIL : ", ctrl_aviFAIL
   print *, "ctrl_avcMSG : ", ctrl_avcMSG
   
end

 

The program above when run can produce the following output:

 

In DISCON:
accINFILE: Test_accINFILE
avcOUTNAME: Test_avcOUTNAME
 In Fortran Main:
 avrSWAP :  99.00000
 ctrl_aviFAIL :  42
 ctrl_avcMSG : Hello World!

 

Now, note the Fortran program above is **helped** by 3 Fortran modules.

First, a module to manage the details with the C++ Dll, called DISCONDll.dll for illustration:

 

module DISCON_m
! Module to define Fortran interfaces of procedures to be consumed from C++ Dll(s) 

   use, intrinsic :: iso_c_binding, only : c_float, c_int, c_char
   use DllHelper_m, only : DllHelper_t

   private
   
   abstract interface 
      subroutine IDISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) bind(C)
      ! Assumes the C++ function prototype is as follows:
      ! extern "C" void DISCON(float *, int *, const char *, const char *, char *)
         import :: c_float, c_int, c_char
         real(c_float),          intent(inout) :: avrSWAP(*)      
         integer(c_int),         intent(inout) :: aviFAIL        
         character(kind=c_char), intent(in)    :: accINFILE(*)      
         character(kind=c_char), intent(in)    :: avcOUTNAME(*)     
         character(kind=c_char), intent(inout) :: avcMSG(*)        
      end subroutine IDISCON  
   end interface
   
   ! Program variables
   type(DllHelper_t), save :: DISCONDll
   procedure(IDISCON), pointer, save, protected, public :: DISCON => null()
   
   public :: SetupDISCON
   
contains

   subroutine SetupDISCON()
   
      use, intrinsic :: iso_c_binding, only : c_funptr, c_associated, c_f_procpointer
   
      type(c_funptr) :: pDISCON
      integer :: irc
   
      call DISCONDll%Load( "DISCONDll.dll", irc )
      if ( irc /= 0 ) then
         stop "Failed to load DISCON.dll"
      end if
   
      pDISCON = DISCONDll%GetFunPtr( "DISCON" )
      if ( .not. c_associated(pDISCON) ) then
         stop "Failed to get the address of DISCON procedure"
      end if
      call c_f_procpointer( cptr=pDISCON, fptr=DISCON )

      if ( .not. associated(DISCON) ) then
         stop "DISCON is not associated."
      end if
   
   end subroutine
   
end module

 

Then another module for a helper "class" for working with DLLs generally on Windows:

 

module DllHelper_m
! Purpose    : Helper module and type to work with Dlls on Windows
! Author     : FortranFan
! Reference  : Using Run-Time Dynamic Linking
!              https://docs.microsoft.com/en-us/windows/win32/dlls/using-run-time-dynamic-linking
! Description:
! This module defines a public type, DllHelper_t, to work with DLLs on Windows.  This type has
!  - Load method with an Dll name as input to load the DLL
!  - GetFunPtr to dispatch a C function pointer for an exported procedure in the Dll; the proc
!    name string is the input
!  - a finalizer that frees up the Dll when the object is destroyed.
!

   use, intrinsic :: iso_c_binding, only : c_char, c_funptr, c_null_funptr
   use IWINApi_m, only : HMODULE, NULL_HANDLE, BOOL, LoadLibrary, GetProcAddress, FreeLibrary

   private

   type, public :: DllHelper_t
      private
      character(kind=c_char, len=:), allocatable :: m_DllName
      integer(HMODULE) :: m_DllHandle = NULL_HANDLE
   contains
      final :: FreeDll
      procedure, pass(this) :: Load => LoadDll
      procedure, pass(this) :: GetFunPtr
   end type
   
contains
    
   subroutine FreeDll( this )
   ! Unload the DLL and free up its resources
      type(DllHelper_t), intent(inout) :: this

      ! Local variables
      integer(BOOL) :: iret

      if ( this%m_DllHandle /= NULL_HANDLE ) then
         iret = FreeLibrary( this%m_DllHandle )
      end if
      this%m_DllHandle = NULL_HANDLE
      
      return
        
   end subroutine 

   subroutine LoadDll( this, DllName, iret )
   ! Load the DLL and set up its handle

      class(DllHelper_t), intent(inout) :: this
      character(kind=c_char, len=*), intent(in) :: DllName
      integer(BOOL), intent(inout) :: iret

      iret = 0
      this%m_DllHandle = LoadLibrary( DllName )
      if ( this%m_DllHandle == NULL_HANDLE ) then
         iret = 1 !<-- TODO: replace with GetLastError
      end if
      
      return
        
   end subroutine 

   function GetFunPtr( this, ProcName ) result(FunPtr)
   ! Get the function pointer

      class(DllHelper_t), intent(inout) :: this
      character(kind=c_char, len=*), intent(in) :: ProcName
      ! Function result
      type(c_funptr) :: FunPtr

      FunPtr = GetProcAddress( this%m_DllHandle, ProcName )
      
      return
        
   end function 

end module 

 

And a third one to work with the Windows APIs provided by Microsoft:

 

module IWinAPI_m
! Purpose    : Interfaces toward Microsoft Windows API functions
! Author     : FortranFan
! Reference  : Microsoft Documentation
!
! Description:
! This module defines the interfaces and type aliases toward Windows APIs.
!
   
   use, intrinsic :: iso_c_binding, only : c_char, c_int, c_intptr_t, c_funptr

   implicit none

   !.. Public by default
   public

   !.. Mnemonics for types in Windows API functions
   integer(c_int), parameter :: HMODULE = c_intptr_t  !.. A handle to a module; base address in memory
   integer(HMODULE), parameter :: NULL_HANDLE = int( 0, kind=kind(NULL_HANDLE) )
   integer(c_int), parameter :: BOOL = c_int

   interface

      function LoadLibrary(lpLibName) bind(C, name='LoadLibraryA') result(RetVal)
      !DIR$ ATTRIBUTES STDCALL :: LoadLibrary
      ! https://docs.microsoft.com/en-us/windows/win32/api/libloaderapi/nf-libloaderapi-loadlibrarya
      ! HMODULE LoadLibraryA( [in] LPCSTR lpLibFileName );

         import :: c_char, HMODULE

         !.. Argument list
         character(kind=c_char, len=1), intent(in) :: lpLibName(*)
         !.. Function result
         integer(HMODULE) :: RetVal

      end function LoadLibrary

      function FreeLibrary(lpLibHandle) bind(C, NAME='FreeLibrary') result(RetVal)
      !DIR$ ATTRIBUTES STDCALL :: FreeLibrary
      ! https://docs.microsoft.com/en-us/windows/win32/api/libloaderapi/nf-libloaderapi-freelibrary
      ! BOOL FreeLibrary( [in] HMODULE hLibModule );

         import :: HMODULE, BOOL

         !.. Argument list
         integer(HMODULE), value :: lpLibHandle
         !.. Function result
         integer(BOOL) :: RetVal

      end function FreeLibrary

      function GetProcAddress(lpLibHandle, lpProcName) bind(C, name='GetProcAddress') result(RetVal)
      !DIR$ ATTRIBUTES STDCALL :: GetProcAddress
      ! https://docs.microsoft.com/en-us/windows/win32/api/libloaderapi/nf-libloaderapi-getprocaddress
      ! FARPROC GetProcAddress( [in] HMODULE hModule, [in] LPCSTR  lpProcName );

         import :: HMODULE, c_char, c_funptr

         !.. Argument list
         integer(HMODULE), intent(in), value      :: lpLibHandle
         character(kind=c_char,len=1), intent(in) :: lpProcName(*)
         !.. Function result
         type(c_funptr) :: RetVal

      end function GetProcAddress

   end interface

end module IWinAPI_m

 

Attached also here is a Visual Studio solution for illustration purposes only, meaning it is not intended as the final answer to your problem by any means.  Rather it is only meant to show you a way run-time dynamic-linking can work with a C++ DLL and a Fortran program.  You can then walk through it and adapt it to your situation as you see fit.

In Visual Studio, a Rebuild selection with the attached file when unzipped to a folder (say C:\temp) can produce the following output:

Build started...
1>------ Build started: Project: DISCONDll, Configuration: Debug x64 ------
1>Dllmain.cpp
1>DISCON.cpp
1>Generating Code...
1>   Creating library Debug\x64\DISCONDll.lib and object Debug\x64\DISCONDll.exp
1>DISCON.vcxproj -> C:\Temp\DISCON\Debug\x64\DISCONDll.dll
2>------ Build started: Project: TestDISCON (IFORT), Configuration: Debug x64 ------
2>Copy C:\Temp\DISCON\Debug\x64\DISCONDll.dll" to Debug\x64
2>C:\Temp\DISCON\Debug\x64\DISCONDll.dll
2>1 File(s) copied
2>Compiling resources...
2>ForMain.rc
2>Microsoft (R) Windows (R) Resource Compiler Version 10.0.10011.16384
2>Copyright (C) Microsoft Corporation.  All rights reserved.
2>Compiling with Intel® Fortran Compiler Classic 2021.6.0 [Intel(R) 64]...
2>IWinAPI.f90
2>DllHelper.f90
2>DISCON.f90
2>C:\Temp\DISCON\sor\DISCON.f90: warning #6178: The return value of this FUNCTION has not been defined.   [FUNPTR]
2>TestDISCON.f90
2>Linking...
2>Embedding manifest...
2>
2>Build log written to  "file://C:\Temp\TestDISCON\Debug\x64\TestDISCON_BuildLog.htm"
2>TestDISCON - 0 error(s), 1 warning(s)
========== Build: 2 succeeded, 0 failed, 0 up-to-date, 0 skipped ==========
Dave12
Novice
2,203 Views

@FortranFan 

Thanks a lot for all your effort! I will do some more tests, but the DLL was loaded successfully and I got the output as well. So the solution seems to work.

0 Kudos
Dave12
Novice
1,881 Views

Hello again,

since the program should run on Linux as well, it is necessary to read in .so-files.  The environment regarding my previous question did not change. The C++ file that was converted to a DLL is now provided as a .so-file. Unfortunately, my research did not generate any useful solutions on how this can be done. 

I would be very grateful for any ideas.

 

0 Kudos
Arjen_Markus
Honored Contributor I
1,876 Views

I have not studied your original question and the discussion that followed in detail, but on Linux a .so library can be treated in the same way as a static library, that is:

ifort -o myprogram myprogram.f90 mylib.so

It does assume that your program "knows" the names of the routines/functions in the .so file, but that is where the C binding is good for. On Windows you need a so-called import library (at least with some compilers) and I see the solution was instead to explicitly load the library. Unless you have a pressing need to load one library for one calculation and another library for another calculation, I think the simplest solution is to link against the .so library as shown above.

The equivalents of LoadLibrary etc. on Linux are functions like dlopen() and dlsym(), if memory serves.

0 Kudos
Reply