Calling C++ from Fortran

It’s possible but involves much more tedious wrapping. Here’s an earlier thread from this forum: Issues interfacing between C++ and Fortran - #4 by FortranFan

If you know a function may raise an exception you need to use the try-block to catch any exceptions, and convert them to “Fortran” error handling → integer status flag and an optional error message output arguments.

Yeah, I guess the program becomes much more tedious, particularly if the number of interface blocks becomes greater. But for this simple case, the length of code might be still “tolerable” though tedious (I mean, as compared to the full example in the linked page).

(PS: I am also making practice how to interface fortran and C++, so I would appreciate it if you let me know any weird or risky parts in the code.)

// rand.hpp
#include <random>

struct Myrand
{
    std::default_random_engine re;
    std::normal_distribution<double> norm {0, 1};
    Myrand( int seed ) : re( (size_t) seed ) {}
};

extern "C" {
    Myrand* rand_init( int seed );
    void rand_fin( Myrand* rng );
    void rand_normal_vec( Myrand* rng, int n, double xarr[] );
}

// rand.cpp
#include "rand.hpp"

extern "C"
{
Myrand* rand_init( int seed ) { return new Myrand( seed ); }
void rand_fin( Myrand* rng ) { delete rng; }

void rand_normal_vec( Myrand* rng, int n, double xarr[] )
{
    for (int i = 0; i < n; i++)
        xarr[i] = rng->norm( rng->re );
}
}

// rand_main.cpp
#include <iostream>
#include "rand.hpp"

int main() {
    Myrand* rng;
    double xarr[5];

    rng = rand_init( 123 );
    rand_normal_vec( rng, 5, xarr );
    rand_fin( rng );

    for (auto x : xarr) printf("x = %20.17f\n", x);
}

// rand_main.f90
module rng_mod
    use iso_c_binding
    interface
        function rand_init( seed ) result( rng ) bind(c); import
            integer(c_int), value :: seed
            type(c_ptr) :: rng
        end
        subroutine rand_fin( rng ) bind(c); import
            type(c_ptr), value :: rng
        end
        subroutine rand_normal_vec( rng, n, xarr ) bind(c); import
            type(c_ptr), value :: rng
            integer(c_int), value :: n
            real(c_double) :: xarr(*)
        end
    endinterface
end

program main
    use rng_mod
    implicit none
    type(c_ptr) :: rng
    real(c_double) :: xarr( 5 )

    rng = rand_init( 123 )
    call rand_normal_vec( rng, 5, xarr )
    call rand_fin( rng )

    print "('x = ', *(/,f20.17))", xarr(:)
end

and

$ g++-10 rand.cpp rand_main.cpp  && ./a.out
x = -0.33123158705896499
x = -1.23528624425248634
x =  0.00063767003311241
x =  0.76479682740326793
x = -0.65051166422731588

$ g++-10 rand.cpp rand_main.f90 -lgfortran && ./a.out
x = 
-0.33123158705896499
-1.23528624425248634
 0.00063767003311241
 0.76479682740326793
-0.65051166422731588

(and I wonder why the Fortran version prints one additional blank line at the end of output)

Hey @septc,

Here are a few comments/observations:

  • The file exporting the “C” interface should be a valid header file in both C and C++ (the Google C++ Style Guidelines recommends using the extension .h for C++). Use the #ifdef __cplusplus#endif preprocessor fences to achieve this.
  • Any standard or other C++ headers that are required belong in the file where they are used (see rule Include What You Use).
  • The struct declaration should also be part of the extern "C" block. Use a forward declaration to keep the C++ internals hidden. If your struct is a standard layout type and is also trivially copyable I’m guessing that you could also define it directly from the C header (hence exposing it), but you would still need a preprocessor fence for the constructor.
  • Prefer C++-style casts; see Item 27 in Scott Meyers’ Effective C++ book or the section on Casting from the Google C++ Style Guide.
  • Use a #define guard to prevent multiple inclusion.

The attached programs and output can be found in the folded boxes:

Source code
// rand.h
#ifndef RAND_H_
#define RAND_H_

#ifdef __cplusplus
extern "C" {
#endif

struct Myrand_;
typedef struct Myrand_ Myrand;

Myrand* rand_init( int seed );
void rand_destroy( Myrand* rng );
void rand_normal_vec( Myrand* rng, int n, double xarr[] );

// just to check the C++ type-traits
int is_myrand_standard_layout(void);
int is_myrand_trivial(void);

#ifdef __cplusplus
}
#endif

#endif  // RAND_H_
// rand.cpp
#include "rand.h"

#include <random>
#include <span>  /* requires C++ 20 */
#include <type_traits>

struct Myrand_
{
    std::default_random_engine re;
    std::normal_distribution<double> norm{ 0, 1 }; // default member initializer

    // member initializer list
    Myrand_( int seed ) : re( static_cast<size_t>( seed )) {}
};

extern "C" {

Myrand* rand_init( int seed ) { 
    return new Myrand( seed ); 
}

void rand_destroy( Myrand* rng ) { 
    delete rng;  /* apparently it's safe to delete nullptr */
}

void rand_normal_vec( Myrand* rng, int n, double xarr[] ) {

    std::span<double> xarr_{ xarr, static_cast<size_t>( n )};

    for (auto &x : xarr_)
        x = rng->norm( rng->re );
}

// these two type-trait functions must be in the same scope as
// as the definition of the struct for the template specialization
// to work

int is_myrand_standard_layout(void) {
    return std::is_standard_layout<Myrand>::value;
}
int is_myrand_trivial(void) {
    return std::is_trivial<Myrand>::value;
}

} // extern "C"
// rand_main.cpp
#include <iostream>

#include "rand.h"

int main() {

	std::cout << "rand test in C++\n";

    double xarr[5];
    
    Myrand* rng;
    rng = rand_init( 123 );
    
    // inspect type traits
    std::cout << "standard_layout: " << (is_myrand_standard_layout() > 0 ? "true" : "false") << '\n';
    std::cout << "trivial: " << (is_myrand_trivial() > 0 ? "true" : "false") << '\n';

    rand_normal_vec( rng, 5, xarr );
    rand_destroy( rng );

    for (auto x : xarr) printf("x = %20.17f\n", x);

}
// rand_main.c
#include <stdio.h>

#include "rand.h"

int main() {

	printf("%s\n", "rand test in C");

    double xarr[5];
    
    Myrand* rng;
    rng = rand_init( 123 );

    // inspect type traits
    printf("standard_layout: %s\n", is_myrand_standard_layout() > 0 ? "true" : "false" );
    printf("trivial: %s\n", is_myrand_trivial() > 0 ? "true" : "false");

    rand_normal_vec( rng, 5, xarr );
    rand_destroy( rng );

    for (int i = 0; i < 5; i++) printf("x = %20.17f\n", xarr[i]);

}
! rand_main.f90
program rand_main

   use, intrinsic :: iso_c_binding
   implicit none

   interface
      function rand_init( seed ) result( rng ) bind(c)
         import c_int, c_ptr
         integer(c_int), intent(in), value :: seed
         type(c_ptr) :: rng
      end function
      subroutine rand_destroy( rng ) bind(c)
         import c_ptr
         type(c_ptr), value :: rng
      end subroutine
      subroutine rand_normal_vec( rng, n, xarr ) bind(c)
         import c_double, c_int, c_ptr
         type(c_ptr), intent(in), value :: rng
         integer(c_int), intent(in), value :: n
         real(c_double), intent(out) :: xarr(*)
      end subroutine
   end interface

   integer, parameter :: n = 5
   real(c_double) :: xarr(n)
   type(c_ptr) :: rng

   write(*,*) "rand test in Fortran"

   rng = rand_init( 123 )
   call rand_normal_vec( rng, n, xarr)
   call rand_destroy( rng )

   write(*,"('x = ', *(/,f20.17))") xarr

end program
Output
$ g++ -Wall -std=c++20 rand.cpp rand_main.cpp && ./a.out
rand test in C++
standard_layout: true
trivial: false
x = -0.48793321042401627
x =  2.00113514698362227
x = -0.12054663647017420
x =  0.32619634620344024
x = -0.08608913806489053
$ g++ -Wall -std=c++20 -c rand.cpp
$ gcc -Wall -c rand_main.c
$ g++ rand.o rand_main.o && ./a.out
rand test in C
standard_layout: true
trivial: false
x = -0.48793321042401627
x =  2.00113514698362227
x = -0.12054663647017420
x =  0.32619634620344024
x = -0.08608913806489053
$ gfortran rand.o rand_main.f90 -lstdc++ && ./a.out
 rand test in Fortran
x = 
-0.48793321042401627
 2.00113514698362227
-0.12054663647017420
 0.32619634620344024
-0.08608913806489053

(since there is no static memory in this case, I used gfortran as the linker)

2 Likes

Maybe you can use ranlib. Some people modernized it if Fortran 77 does not fit to your needs.