Passing allocated C_PTR to Fortran array to C

[亡魂溺海] 提交于 2020-01-04 09:31:47

问题


I'm having trouble with segfaults from accessing an array in C, which is allocated in the Fortran file below. There are a few artefacts of debugging, such as the fact that the file writes don't write anything meaningful and I initialise a variable i that I never use.

However, I've found the following:

  • Not initialising i (but still declaring it): no segfault
  • Not opening the file in C: no segfault
  • Not printing HESS (not HESS_COPY) elsewhere in the code: no segfault
  • Declaring and initialising i with a different name: segfault

Does anyone know what might give rise to this behaviour? The segfault itself occurs at the line ARRAY_PTR = C_LOC(HESS_COPY(1, 1)). I am compiling using gfortran and gcc with debug flags (no optimisation).

valgrind says that there is an invalid write (the top two files are the ones I show below):

 Invalid write of size 8
    at 0xBEEA3E: get_pointer (modsparsehess.f90:34)
    by 0xA75D7A: print_hess (sparse_hessian_c.c:108)
    by 0x866C95: quench_ (quench.f:316)
    by 0x7F2DBE: mc_ (mc.F:368)
    by 0x4B65E2: mcruns_ (mcruns.f:62)
    by 0x459245: MAIN__ (main.F:430)
    by 0x45A33F: main (main.F:21)
  Address 0x87 is not stack'd, malloc'd or (recently) free'd

C file

#include <stdio.h>

void get_pointer(double ** hessian);

void print_hess(int *arr_size) {
   // Create a pointer to handle the hessian
   double **hessian;
   int i;
   i = 0;
   get_pointer(hessian);

   printf("%8.3f", **hessian);
   // Open a file for writing
   FILE *fptr = fopen("hessian_out", "w");  
   // Print the hessian
   fprintf(fptr, "\n");
   fclose(fptr);
}

Fortran file

MODULE MODSPARSEHESS
USE, INTRINSIC :: ISO_C_BINDING
USE MODHESS, ONLY: HESS

INTERFACE
   SUBROUTINE PRINT_HESSIAN(DIMENSIONS) BIND(C, NAME='print_hess')
      USE, INTRINSIC :: ISO_C_BINDING
      INTEGER(C_INT) :: DIMENSIONS
   END SUBROUTINE PRINT_HESSIAN
END INTERFACE

CONTAINS

   SUBROUTINE GET_POINTER_IN_C(ARRAY_PTR) BIND(C, NAME='get_pointer')
   !  C signature: void get_pointer(double ** hessian);
      USE, INTRINSIC :: ISO_C_BINDING
      IMPLICIT NONE

   ! Arguments
      TYPE(C_PTR), INTENT(OUT)            :: ARRAY_PTR
   ! Local variables
      REAL(C_DOUBLE), DIMENSION(:,:), &
      ALLOCATABLE, TARGET                 :: HESS_COPY

   ! Copy the hessian into HESS_COPY
      IF (.NOT. ALLOCATED(HESS_COPY)) THEN
        ALLOCATE(HESS_COPY(SIZE(HESS, 1), SIZE(HESS, 2)))
      END IF
      HESS_COPY(:, :) = HESS(:, :)

   ! Now get the pointer
      ARRAY_PTR = C_LOC(HESS_COPY(1, 1))

   END SUBROUTINE GET_POINTER_IN_C
END MODULE MODSPARSEHESS

回答1:


The variable HESS_COPY is a local, unsaved, allocatable variable of the Fortran procedure GET_POINTER_IN_C.

Consequently, whenever the procedure begins execution it is always unallocated. The test of its allocation status in the first executable statement of that procedure is therefore superfluous.

Consequently also, at the end of execution of the procedure that unsaved local variable is automatically deallocated. The C_LOC reference towards the end of the procedure therefore obtains the address of an object that is about to cease existing.

The C code then works with the address of an object that does not exist, and the program fails.

If the HESS_COPY variable was saved local or saved module variable it would continue to exist between procedure invocations.

(All module variables are saved as of Fortran 2008, previous language revisions formally required explicit specific of SAVE for the relevant module variables if the module was not continuously being referenced in an active scope.)

(As an aside, the rules of the language, as of Fortran 2003, also mean that the allocated test, the allocate statement and the subsequent assignment can simply be replaced by the single statement HESS_COPY = HESS.)


Further, in the C code, an attempt is being made to return information in a pointer that does not exist. In the original code, hessian is declared as a pointer to a pointer to double - note the two levels of indirection. Without some sort of initialization the first level of indirection will be pointing "randomly" in memory, the Fortran code will then be trying to store its result in that random location.

As an alternative, consider:

#include <stdio.h>

void get_pointer(double ** hessian);

void print_hess(int *arr_size) {
   // A pointer to double (one level of indirection).
   double *hessian;

   // Pass the address of that pointer.
   get_pointer(&hessian);

   // print the value of the double being pointed at.
   printf("%8.3f\n", *hessian);

   // print the value of the next double in the array
   // (assuming that there is more than one).
   printf("%8.3f\n", *(hessian+1));
   // (or equivalently, `hessian[1]`)
}

The Fortran pointer method referred to by Vladimir F in the comments requires two Fortran procedures - one similar to the one that you have that allocates a Fortran pointer and copies the data, the second that deallocates that pointer. Each call to the allocation procedure needs to be matched with a corresponding call to the deallocation procedure, passing the same pointer. Something along the lines of:

   SUBROUTINE GET_POINTER(ARRAY_PTR) BIND(C, NAME='get_pointer')
   !  C signature: void get_pointer(double **);
      USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_LOC, C_PTR, C_DOUBLE

      TYPE(C_PTR), INTENT(OUT) :: ARRAY_PTR
      REAL(C_DOUBLE), POINTER :: HESS_COPY(:,:)

      ! See also the SOURCE= specifier.
      ALLOCATE(HESS_COPY(SIZE(HESS,1), SIZE(HESS,2))
      HESS_COPY = HESS
      ARRAY_PTR = C_LOC(HESS_COPY)
   END SUBROUTINE GET_POINTER

   SUBROUTINE RELEASE_POINTER(ARRAY_PTR) BIND(C, NAME='release_pointer')
   ! C signature: void release_pointer(double*);
     USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_F_POINTER, C_DOUBLE

     TYPE(C_PTR), INTENT(IN), VALUE :: ARRAY_PTR
     REAL(C_DOUBLE), POINTER :: HESS_COPY(:,:)

     CALL C_F_POINTER(ARRAY_PTR, HESS_COPY, SHAPE(HESS))
     DEALLOCATE(HESS_COPY)
   END SUBROUTINE RELEASE_POINTER


来源:https://stackoverflow.com/questions/28351919/passing-allocated-c-ptr-to-fortran-array-to-c

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!