To put some background context, I need a thread safe random number generator for use in multithreaded Fortran code that needs to be cross compiler, and cross platform compatible. The best way to achieve this is to stick with the language standards. So I wanted to wrap the C++11 random number generators in a function I can call from fortran so I have one random number generator per thread each with it's own state object.
So I created a small C++ class with 3 C function bindings.
#include <random>
#include <iostream>
class random {
    std::mt19937_64 engine;
    std::uniform_real_distribution<double> dist;
    public:
    random(uint64_t seed) : engine(seed), dist(0.0, 1.0) {};
    double get_number() {
        return dist(engine);
    }
};
extern "C" {
    void *random_construct(int seed) {
        return new class random(static_cast<uint64_t> (seed));
    }
    double random_get_number(void *r) {
        return static_cast<class random *> (r)->get_number();
    }
    void random_destroy(void *r) {
        delete static_cast<class random *> (r);
    }
}
A Fortran interface
  MODULE random
  USE, INTRINSIC :: iso_c_binding
  IMPLICIT NONE
  INTERFACE
     TYPE (C_PTR) FUNCTION random_construct(seed)                          &
 &   BIND(C, NAME='random_construct')
     USE, INTRINSIC :: iso_c_binding
     IMPLICIT NONE
     INTEGER (C_INT), VALUE :: seed
     END FUNCTION
  END INTERFACE
  INTERFACE
     REAL (C_DOUBLE) FUNCTION random_get_number(r)                         &
 &   BIND(C, NAME='random_get_number')
     USE, INTRINSIC :: iso_c_binding
     IMPLICIT NONE
     TYPE (C_PTR), VALUE :: r
     END FUNCTION
  END INTERFACE
  INTERFACE
     SUBROUTINE random_destroy(r)                                          &
 &   BIND(C, NAME='random_destroy')
     USE, INTRINSIC :: iso_c_binding
     IMPLICIT NONE
     TYPE (C_PTR), VALUE :: r
     END SUBROUTINE
  END INTERFACE
  END MODULE
And a small program to test this.
   PROGRAM random_test
   USE random
   IMPLICIT NONE
   TYPE (C_PTR) :: rand_object
   INTEGER      :: count
   CALL SYSTEM_CLOCK(count)
   rand_object = random_construct(count)
   WRITE(*,*) random_get_number(rand_object)
   CALL random_destroy(rand_object)
   WRITE(*,*) random_get_number(rand_object)  ! Expected to segfault.
   END PROGRAM
Running this shows my destroy function does not appear to be working correctly since calls after my destroy function are still generating random numbers.
If I change my test program to
   PROGRAM random_test
   USE random
   IMPLICIT NONE
   TYPE (C_PTR), ALLOCATABLE :: rand_object
   INTEGER                   :: count
   CALL SYSTEM_CLOCK(count)
   rand_object = random_construct(count)
   WRITE(*,*) random_get_number(rand_object)
   DEALLOCATE (rand_object)
   WRITE(*,*) random_get_number(rand_object)
   END PROGRAM
Now it's producing the behavior I would have expected and segfaults after the DEALLOCATE. Now my gut reaction says this shouldn't work since I would never try to allocate memory in one language and deallocate it in another. But is there any reason why it shouldn't? The C++ object is a POD type so its memory should be continuous. Then as long as Fortran has the right memory address, it should be able to trivially deallocate it. Is there something I'm missing here?
