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

Fortran -> C Interop w/ Derived Types

Krob__Jeff
Beginner
1,645 Views

All,

Got 2 questions in trying to get Fortran & C TYPES/typdefs working.

First, the typedefs in C;

typedef struct                      /* Polygon vertex structure          */
{
  double              x;            /* Vertex x component                */
  double              y;            /* vertex y component                */
} gpc_vertex;

typedef struct                      /* Vertex list structure             */
{
  int                 num_vertices;        /* Number of vertices in list        */
  gpc_vertex         vertex;               /* Vertex               */
} gpc_vertex_list;


Now, the Fortran equivalent TYPES;

  use, intrinsic :: ISO_C_BINDING

  TYPE, BIND(C) :: F_GPC_VERTEX         !    /* Polygon vertex structure          */
    REAL(8) (C_FLOAT) :: x                            !    /* Vertex x component                */
    REAL(8) (C_FLOAT) :: y                            !    /* vertex y component                */
  END TYPE

  TYPE, BIND(C) :: F_GPC_VERTEX_LIST    !    /* Vertex list structure             */
    INTEGER(C_INT) :: num_vertices                    !    /* Number of vertices in list        */
    TYPE (F_GPC_VERTEX) :: vertex                     !    /* Vertex             */
  END TYPE

Now, the compilation errors with the "REAL(8) (C_FLOAT) :: " x & y  with

error #5082: Syntax error, found '(' when expecting one of: :: %FILL , INTEGER REAL COMPLEX TYPE BYTE CHARACTER CLASS DOUBLE DOUBLECOMPLEX ..."

but works with just "REAL (C_FLOAT) :: " ...but the C typdef is a double float. Why will it not allow the REAL(8)?

Two - is the "TYPE (F_GPC_VERTEX) :: vertex" an example of a Type Extension?

Thanks in advance,

Jeff

 

 

0 Kudos
27 Replies
JVanB
Valued Contributor II
1,326 Views

If you wrote up a little program to print out C_FLOAT:

USE ISO_C_BINDING
PRINT *, C_FLOAT
END

You would find that C_FLOAT = 8 . Thus REAL(8)(C_FLOAT) is going to look like REAL(8)(8) to the compiler. You want to get rid of one of those 8's and the one to eliminate is the first is you just have REAL(C_FLOAT) . That way if KIND([DOUBLE PRECISION::]) is not 8, as would be the case by default on Silverfrost's compiler, you would still be declaring a type equivalent to C double.

Your example has nested derived types, not type extension. Look up the EXTENDS attribute in your favorite Fortran documentation.

 

0 Kudos
Steven_L_Intel1
Employee
1,326 Views

Actually, C_FLOAT is 4. C_DOUBLE is what is wanted here. But otherwise, RO is spot on (as usual).

0 Kudos
Krob__Jeff
Beginner
1,326 Views

OK Steve & RO - got it thanks. Along those lines, to pass a TYPE as an argument to a C routine, how would the interface be constructed? For example, I need to call the C routine "gpc_read_polygon( fpread, readholeflag, subject_polygon )". The C-side is like this:

void gpc_read_polygon(FILE *fp, int read_hole_flags, gpc_vertex_list *p)


"FILE *fp" is a pointer for the open file to be read, "read_hole_flags" is just a 1 or 0 but the "gpc_vertex_list *p" is the typedef struct (defined previously above) passed from the Fortran side. So, from what I can guess, the Fortran interface would look something like:

     interface
     SUBROUTINE gpc_read_polygon( fpread, readholeflag, subject_polygon ) &
                        BIND(C, name="gpc_read_polygon")
 
        IMPORT :: c_int,c_float

        implicit none
        integer (C_INT), intent(inout) :: fpread
        integer (C_INT), value           :: readholeflag
        * * * * *                               :: subject_polygon    ! <<<<< what goes here???
     end SUBROUTINE gpc_read_polygon
   end interface

Thanks again,

Jeff

 

0 Kudos
JVanB
Valued Contributor II
1,326 Views

Please copy the dummy argument names from the C documentation verbatim unless they conflict with other names. This makes your interface much more self-documenting. You neglected to mention that the vertex member of struct gpc_vertex_list was a pointer, not directly a struct type. This makes a difference. Also that FILE* fp argument is a C file pointer not a Fortran unit number, so you need a little C helper function to get open that file and get the pointer for you. Maybe ifort has an extension that can do it, but likely that's more problematic. Also I don't know whether the struct pointed at by a FILE* is the same between C compilers, so you might have a problem if the C library used by the gpc library is different from the one used to compile my C example. Perhaps gpc also provides a function to open files and return a FILE* for you already; search for something llike that in the docs.

Here is my translation of your module so far:

module gpc
   use, intrinsic :: ISO_C_BINDING
   implicit none
   TYPE, BIND(C) :: F_GPC_VERTEX
      REAL(C_DOUBLE) :: x ! Stop programming in my blind spot!
      REAL(C_DOUBLE) :: y
   END TYPE F_GPC_VERTEX
   TYPE, BIND(C) :: F_GPC_VERTEX_LIST
      INTEGER(C_INT) :: num_vertices
      TYPE(C_PTR) :: vertex
   END TYPE F_GPC_VERTEX_LIST
   interface
      SUBROUTINE gpc_read_polygon(fp, read_hole_flags, p) &
         BIND(C,name='gpc_read_polygon')
         IMPORT :: C_PTR, C_INT, F_GPC_VERTEX_LIST ! Enough with C_FLOAT!
         implicit none
         TYPE(C_PTR), value :: fp
         integer(C_INT), value :: read_hole_flags
         TYPE(F_GPC_VERTEX_LIST) p
      end SUBROUTINE gpc_read_polygon
   end interface
end module gpc

As mentioned you will need a C helper function or, better, use a helper function from the gpc package to open the file for reading:

#include <stdio.h>

FILE* IOhelper(char * filename)
{
   return fopen(filename,"r");
}

Example of usage:

subroutine sub
   use gpc
   implicit none
   type(C_PTR) :: fp
   interface
      function IOhelper(filename) bind(C,name='IOhelper')
         import
         implicit none
         character(KIND=C_CHAR), intent(in) :: filename(*)
         type(C_PTR) IOhelper
      end function IOhelper
   end interface
   character(80) filename
   TYPE(F_GPC_VERTEX_LIST) p
   integer(C_INT) read_hole_flags

   filename = 'whatever'//C_NULL_CHAR ! Null termination required for fopen
   fp = IOhelper(filename)
   read_hole_flags = 1 ! Or maybe 0
   call gpc_read_polygon(fp, read_hole_flags, p)
! I assume you don't need to look at the contents of that gpc_vertex_list.
! Also I assume that the package manages the memory it points at.
end subroutine sub

All untested :)

 

0 Kudos
Krob__Jeff
Beginner
1,326 Views

OK...thanks for the info.  1) so a file to be read or written in a C routine can only be opened & closed within C & not within Fortran? 2) if the same C routine is called within a Fortran routine but with different arguments, each call to the C routine must have it's own interface definition?

0 Kudos
JVanB
Valued Contributor II
1,326 Views

1) I'm not saying that it's impossible, I can't find any documentation on how you would obtain the FILE* pointer from Fortran. Furthermore, I don't even know whether a FILE* obtained with code compiled on one C compiler can be used with code compiled with another C compiler.

2) Not at all. Normally you want to define just one interface, put its interface block in a module, and USE that module in any scoping unit that will call the C routine. I rewrote your TYPE(F_GPC_VERTEX_LIST) and interface to gpc_read_polygon() from scratch because there were enough errors present already that I thought it best to have a reference point for further discussion in one place rather than keeping track of the edits across the thread.

 

0 Kudos
Krob__Jeff
Beginner
1,326 Views

RO - thanks for all the info...and your patience however, I need some clarification on some code you wrote above. In the definition of the TYPES, you wrote:

  TYPE, BIND(C) :: F_GPC_VERTEX
    REAL(C_DOUBLE) :: x                          
    REAL(C_DOUBLE) :: y                           
  END TYPE

  TYPE, BIND(C) :: F_GPC_VERTEX_LIST
    INTEGER(C_INT) :: num_vertices                
    TYPE(C_PTR) :: vertex              ! <<<< THIS!!!
  END TYPE

in changing the "vertex" from a "TYPE (F_GPC_VERTEX) :: "  to a "TYPE(C_PTR) ::" it looks like it lost it's association to  F_GPC_VERTEX ...which is required. There is code like this:

    *npoly = contour->num_vertices;

    for ( ii = 0; ii < *npoly; ii++ )  {
    px[ii] = contour->vertex[ii].x;
    py[ii] = contour->vertex[ii].y;
    }


I understand how the structure works in C & it's Fortran equiv...but I don't understand how what you wrote works to support what is needed in the gpc library. Also, to make it work in a 'traditional' (non-pointer) way, the "vertex" needs to be an ALLOCATABLE array because it is dynamic in operation as polygon vertex point are added or removed by the operations. Now, I understand allocatable arrays are not allowed with derived types with the BIND attribute...but neither are pointers!!! Does that mean I'm at a dead-end in this project?

 
0 Kudos
JVanB
Valued Contributor II
1,326 Views

Well, I thought I might have had a solution, but there is a problem. I started with an input file, stuff.dat:

3.14159265 2.99792458
0.30103 6.62559
1.38054 1.008

I modified the gpc module file a little:

module gpc
   use, intrinsic :: ISO_C_BINDING
   implicit none
   private
   public F_GPC_VERTEX, F_GPC_VERTEX_LIST, F_GPC_POLYGON, gpc_read_polygon
   TYPE, BIND(C) :: F_GPC_VERTEX
      REAL(C_DOUBLE) :: x
      REAL(C_DOUBLE) :: y
   END TYPE F_GPC_VERTEX
   TYPE, BIND(C) :: F_GPC_VERTEX_LIST
      INTEGER(C_INT) :: num_vertices
      TYPE(C_PTR) :: vertex
   END TYPE F_GPC_VERTEX_LIST
   TYPE, BIND(C) :: F_GPC_POLYGON
      integer(C_INT) num_contours
      type(C_PTR) hole
      type(C_PTR) contour
   END TYPE F_GPC_POLYGON
   interface
      SUBROUTINE gpc_read_polygon(infile_ptr, read_hole_flags, polygon) &
         BIND(C,name='gpc_read_polygon')
         IMPORT :: C_PTR, C_INT, F_GPC_VERTEX_LIST ! Enough with C_FLOAT!
         implicit none
         TYPE(C_PTR), value :: infile_ptr
         integer(C_INT), value :: read_hole_flags
         TYPE(F_GPC_VERTEX_LIST) polygon
      end SUBROUTINE gpc_read_polygon
   end interface
end module gpc

Then I wrote up some interfaces for C library functions:

module MSVCRT
   use ISO_C_BINDING
   implicit none
   private
   public fopen, fclose, malloc, free
! Delete fscanf in actual use
   public fscanf
   interface
      function fopen(filename, mode) bind(C,name='fopen')
         import
         implicit none
         type(C_PTR) fopen
         character(KIND=C_CHAR), intent(IN) :: filename(*)
         character(KIND=C_CHAR), intent(IN) :: mode(*)
      end function fopen

      function fclose(stream) bind(C,name='fclose')
         import
         implicit none
         integer(C_INT) fclose
         type(C_PTR), value :: stream
      end function fclose

! fscanf is only used for the purposes of completing this example
! delete this interface to a variadic function in real use
      function fscanf(stream, format, result) bind(C,name='fscanf')
         import
         implicit none
         integer(C_INT) fscanf
         type(C_PTR),value :: stream
         character(KIND=C_CHAR), intent(IN) :: format(*)
         real(C_DOUBLE) result
      end function fscanf

      function malloc(size) bind(C,name='malloc')
         import
         implicit none
         type(C_PTR) malloc
         integer(C_SIZE_T), value :: size
      end function malloc

      subroutine free(ptr) bind(C,name='free')
         import
         implicit none
         type(C_PTR), value :: ptr
      end subroutine free
   end interface
end module MSVCRT

And a test program:

program P
   use MSVCRT
   use ISO_C_BINDING
   use gpc
   implicit none
   character(KIND=C_CHAR) filename(20)
   character(KIND=C_CHAR) mode(20)
   character(KIND=C_CHAR) C_format(20)
   type(C_PTR) fp
   type(F_GPC_POLYGON) polygon
   integer(C_INT) num_contours
   type(F_GPC_VERTEX_LIST), pointer :: vertex_list(:)
   integer npts
   type(F_GPC_VERTEX), pointer :: vertices(:)
   integer(C_INT) res
   character(20) fmt
   integer i, j

   filename = 'stuff.dat' // C_NULL_CHAR ! NUL-termination required
   mode = 'r' // C_NULL_CHAR
   fp = fopen(filename,mode)
write(*,'(z0)') transfer(fp,0_C_INTPTR_T)
   num_contours = 1
   polygon%num_contours = num_contours
   polygon%hole = C_NULL_PTR ! Not used in my example
!   polygon%contour = malloc(num_contours*C_SIZEOF(vertex_list))
   polygon%contour = malloc(num_contours*C_SIZEOF(F_GPC_VERTEX_LIST(0,C_NULL_PTR)))
write(*,'(z0)') transfer(polygon%contour,0_C_INTPTR_T)
   call C_F_POINTER(polygon%contour,vertex_list,[num_contours])
   do i = 1, num_contours
      npts = 3 ! Or whatever is in your file
      vertex_list(i)%num_vertices = npts
      vertex_list(i)%vertex = malloc(npts*C_SIZEOF(F_GPC_VERTEX(0,0)))
write(*,'(i0,1x,z0)') i,transfer(vertex_list(i)%vertex,0_C_INTPTR_T)
      call C_F_POINTER(vertex_list(i)%vertex,vertices,[npts])
      C_format = '%lf' // C_NULL_CHAR
      do j = 1, npts
         res = fscanf(fp, C_format, vertices(j)%x)
         res = fscanf(fp, C_format, vertices(j)%y)
write(*,'(i0,1x,i0,1x,g0,1x,g0)') i, j, vertices(i)%x,vertices(i)%y
      end do
   end do
   res = fclose(fp)
   fmt = '(2(f8.6))'
   do i = 1, num_contours
      call C_F_POINTER(vertex_list(i)%vertex,vertices,[vertex_list(i)%num_vertices])
      do j = 1, size(vertices)
         write(*,fmt) vertices(j)
      end do
   end do
   do i = 1, polygon%num_contours
      call free(vertex_list(i)%vertex)
   end do
   call free(polygon%contour)
end program P

Unfortunately ifort blew up on that first invocation of fopen(), and gfortran returned NULL, so someone with better knowledge of C is going to have to figure out how to fix that situation.

 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,326 Views

>>Unfortunately ifort blew up on that first invocation of fopen()

Where is the interface to fopen declared?

Jim Dempsey

0 Kudos
JVanB
Valued Contributor II
1,326 Views

@jimdempseyatthecove: First interface body in module MSVCRT above.

 

0 Kudos
JVanB
Valued Contributor II
1,326 Views

GOT IT!!

The problem was that I declared all my character variables as LEN=1, DIMENSION(20), rather than LEN=20. Fixing that,

program P
   use MSVCRT
   use ISO_C_BINDING
   use gpc
   implicit none
   character(LEN=20,KIND=C_CHAR) filename
   character(LEN=20,KIND=C_CHAR) mode
   character(LEN=20,KIND=C_CHAR) C_format
   type(C_PTR) fp
   type(F_GPC_POLYGON) polygon
   integer(C_INT) num_contours
   type(F_GPC_VERTEX_LIST), pointer :: vertex_list(:)
   integer npts
   type(F_GPC_VERTEX), pointer :: vertices(:)
   integer(C_INT) res
   character(20) fmt
   integer i, j

   filename = 'stuff.dat' // C_NULL_CHAR ! NUL-termination required
   mode = 'r' // C_NULL_CHAR
   fp = fopen(filename,mode)
write(*,'(z0)') transfer(fp,0_C_INTPTR_T)
   num_contours = 1
   polygon%num_contours = num_contours
   polygon%hole = C_NULL_PTR ! Not used in my example
!   polygon%contour = malloc(num_contours*C_SIZEOF(vertex_list))
   polygon%contour = malloc(num_contours*C_SIZEOF(F_GPC_VERTEX_LIST(0,C_NULL_PTR)))
write(*,'(z0)') transfer(polygon%contour,0_C_INTPTR_T)
   call C_F_POINTER(polygon%contour,vertex_list,[num_contours])
   do i = 1, num_contours
      npts = 3 ! Or whatever is in your file
      vertex_list(i)%num_vertices = npts
      vertex_list(i)%vertex = malloc(npts*C_SIZEOF(F_GPC_VERTEX(0,0)))
write(*,'(i0,1x,z0)') i,transfer(vertex_list(i)%vertex,0_C_INTPTR_T)
      call C_F_POINTER(vertex_list(i)%vertex,vertices,[npts])
      C_format = '%lf' // C_NULL_CHAR
      do j = 1, npts
         res = fscanf(fp, C_format, vertices(j)%x)
         res = fscanf(fp, C_format, vertices(j)%y)
write(*,'(i0,1x,i0,1x,g0,1x,g0)') i, j, vertices(i)%x,vertices(i)%y
      end do
   end do
   res = fclose(fp)
   fmt = '(2(f8.6))'
   do i = 1, num_contours
      call C_F_POINTER(vertex_list(i)%vertex,vertices,[vertex_list(i)%num_vertices])
      do j = 1, size(vertices)
         write(*,fmt) vertices(j)
      end do
   end do
   do i = 1, polygon%num_contours
      call free(vertex_list(i)%vertex)
   end do
   call free(polygon%contour)
end program P

Led to good output:

7FF7A6F3E2A0
6D1F15BBA0
1 6D1F15DEE0
1 1 3.141592650000000 2.997924580000000
1 2 3.141592650000000 2.997924580000000
1 3 3.141592650000000 2.997924580000000
3.1415932.997925
0.3010306.625590
1.3805401.008000

What an ugly bug :(

 

0 Kudos
Krob__Jeff
Beginner
1,326 Views

RO - THANKS!! I deeply appreciate that! I was concerned that the file pointers were being mangled going back & forth btwn C & Fortran. Now, the next test is to use this as a template but read in two polygon files (Subject & Clip), populate the two created F_GPC_POLYGON polygon structures, feed them through the gpc_polygon_clip routine...and see what comes out the other end.

Ya gots to do what ya gots to do!

Thanks again, Jeff

0 Kudos
JVanB
Valued Contributor II
1,326 Views

Yes, but there are still questions about why the call to fopen with bad inputs caused a crash when it's supposed to just set fp to C_NULL_PTR and set errno to some nonzero value. If you just set mode = 'xyz' // C_NULL_CHAR above it reproduces the crash, here is a minimal example:

module M
   use ISO_C_BINDING
   implicit none
   interface
      function fopen(filename, mode) bind(C,name='fopen')
         import
         implicit none
         type(C_PTR) fopen
         character(KIND=C_CHAR), intent(IN) :: filename
         character(KIND=C_CHAR), intent(IN) :: mode
      end function fopen
   end interface
end module M

program P
   use M
   implicit none
   character(LEN=20,KIND=C_CHAR) filename
   character(LEN=20,KIND=C_CHAR) mode
   type(C_PTR) fp

   filename = 'nonexistent' // C_NULL_CHAR
   mode = 'xyz' // C_NULL_CHAR
   fp = fopen(filename,mode)
   write(*,'(z0)') transfer(fp,0_C_INTPTR_T)
end program P

The above crashes at the fopen invocation. Am I doing something wrong or is ifot corrupting the data structures used by the C runtime library somehow?

Oh, and what about errno? The above doesn't survive long enough to print out errno, but the IFPORT function IERRNO doesn't seem to agree with what the C library considers to be errno:

module M
   use ISO_C_BINDING
   implicit none
   interface
      function errno_address() bind(C,name='_errno')
         import
         implicit none
         type(C_PTR) errno_address
      end function errno_address
   end interface
end module M

program P
   use M
   use IFPORT
   implicit none
   type(C_PTR) address
   integer(C_INT), pointer :: errno
   integer(4) errval1, errval2
   address = errno_address()
   call C_F_POINTER(address, errno)
   errval1 = errno
   errval2 = ierrno()
   write(*,*) 'errno = ', errval1
   write(*,*) 'ierrno() = ', errval2
   errno = 22
   errval1 = errno
   errval2 = ierrno()
   write(*,*) 'errno = ', errval1
   write(*,*) 'ierrno() = ', errval2
end program P

Prints out:

 errno =            0
 ierrno() =            0
 errno =           22
 ierrno() =            0

 

0 Kudos
FortranFan
Honored Contributor II
1,326 Views

Repeat Offender wrote:

.. If you just set mode = 'xyz' // C_NULL_CHAR above it reproduces the crash, ..

In this case, the culprit is the companion C processor (in this case, the one authored by the behemoth in Redmond, WA?)  The crash is reproducible with the simple C example:

#include <stdio.h>

int main()
{
   FILE *fp;

   fp = fopen("file.txt", "xyz");

   if (fp != NULL) {
      printf("fopen returned fp = %p.\n", fp);
   }
   else {
      printf("fopen failed.\n");
   }

   fclose(fp);

   return(0);
}

whereas with GCC, a NULL pointer is returned in fp and code stops gracefully.

When only the first parameter is bogus (e.g., it corresponds to a non-existent file), no crash is noticed, either with C-only code (whether with GCC or Microsoft C/C++ compiler) or with Fortran invoking fopen function interfaced as above using standard interoperability features and compiled with either gfortran or Intel Fortran.

0 Kudos
Krob__Jeff
Beginner
1,326 Views

RO - if I may get back to the original subject for a quick clarification, I noticed you went above & beyond the call by translating gpc_polygon_read to fortran instead of just interfacing to it as was my intention. This raises a question concerning the Fortran TYPE structutres (F_GPC_POLYGON) & C typedef struct (gpc_polygon) interactions. Since the gpc_polygon struct is initialized & populated within gpc_polygon_read, when the result is passed back to the fortran routine, will F_GPC_POLYGON automatically aquire the shape & contents of what was passed from the C routine or does it need to be initialized (memory allocated, etc.) separately and, if so, does that need to be done before gpc_polygon_read is called or just before the F_GPC_POLYGON structure is used in Fortran code?

Thanks again for all your help, Jeff

0 Kudos
JVanB
Valued Contributor II
1,326 Views

@FortranFan -- Thanks for testing this with MSVC++. I tried a further test with gfortran:

module M
   use ISO_C_BINDING
   implicit none
   interface
      function fopen(filename, mode) bind(C,name='fopen')
         import
         implicit none
         type(C_PTR) fopen
         character(KIND=C_CHAR), intent(IN) :: filename
         character(KIND=C_CHAR), intent(IN) :: mode
      end function fopen

      function errno_address() bind(C,name='_errno')
         import
         implicit none
         type(C_PTR) errno_address
      end function errno_address
   end interface
end module M

program P
   use M
   implicit none
   character(LEN=20,KIND=C_CHAR) filename
   character(LEN=20,KIND=C_CHAR) mode
   type(C_PTR) fp

   type(C_PTR) address
   integer(C_INT), pointer :: errno
   integer(4) errval1, errval2
   address = errno_address()
   call C_F_POINTER(address, errno)
   errval1 = errno
   errval2 = ierrno()
   write(*,*) 'errno = ', errval1
   write(*,*) 'ierrno() = ', errval2
   filename = 'nonexistent' // C_NULL_CHAR
   mode = 'xyz' // C_NULL_CHAR
   fp = fopen(filename,mode)
   errval1 = errno
   errval2 = ierrno()
   write(*,'(a,z0)') 'fp = ',transfer(fp,0_C_INTPTR_T)
   write(*,*) 'errno = ', errval1
   write(*,*) 'ierrno() = ', errval2
end program P

with output:

 errno =            2
 ierrno() =            2
fp = 0
 errno =           22
 ierrno() =           22

Showing once again that the gcc fopen() behaves as documented and that gfortran's ierrno() extension is synchronized with the C errno, unlike what was the case with the ierrno() from IFPORT. Indeed, if the mode variable above is modified to something valid so the code doesn't crash with ifort, and USE IFPORT is added, the output we get with ifort is:

 errno =            0
 ierrno() =            0
fp = 0
 errno =            2
 ierrno() =            0

Which shows that IFPORT's ierrno() extension is not synchronized with the C errno. I have been using C interoperability throughout, and seem to be justified in that IFPORT has to a certain extent been obsoleted by this f2003 feature.

Maybe you could find a C forum you could post your C code to and figure out if there is some way to get MSVCRT not to crash when it sees an invalid mode= actual argument. Searching the web I found a few posts about this phenomenon in stackoverflow, but the only cure proposed was to pass a valid mode= argument, which sort of makes fopen() into a loaded gun that could crash your program unexpectedly.

 

0 Kudos
JVanB
Valued Contributor II
1,326 Views

@Jeff K. -- There are several ways to manage memory for these data structures. One way might have been to create parallel Fortran data structures and then use the C_LOC function from the ISO_C_BINDING module and the intrinsic SIZE inquiry function to see how to populate the desired C data structures with data counts and C-style pointers. While this would have made it easier to read and write the data on the Fortran side, it would have necessitated keeping that parallel Fortran data structure in scope as long as the C data structure was active. Also C wouldn't have been able to allocate and deallocate memory within its data structures if this scheme were used.

I showed how Fortran can simply call malloc() and free() from the C standard library to allocate and deallocate memory and then use C_F_POINTER to get good Fortran array pointers that you can use to read and write the arrays. I did this because I didn't want to have to install the whole topical package just to answer this question.

Obviously if gpc_read_polygon() can do the allocation for you and the FILE* pointer that was obtained in my examples above works, that, along with gpc_free_polygon() would be the preferred method of managing memory for you.

The question about whether F_GPC_POLYGON automatically acquires the shape & contents of what was passed from the C routine is kind of thinking about the problem at the wrong level of indirection in my opinion. The structure that you see is exactly what C wrote, with naked pointers, containing only an address, unlike the fat pointers that Fortran provides. To read the arrays pointed at by these naked pointers, you have to get a fat Fortran pointer from them with C_F_POINTER, but the good news is that I showed how to perform exactly that task in my example in Quote #12, so careful study of that example and the ifort documentation and you should be good to go.

 

0 Kudos
Steven_L_Intel1
Employee
1,326 Views

IERRNO in IFPORT does not claim to be the same as C errno.

Returns the number of the last detected error from any routines in the IFPORT module that return error codes.

That's the problem with "portability routines" in that they don't always mean the same thing across implementations. And by the way, in Intel Fortran for Windows, there is no connection whatsoever between Fortran units and C files.

0 Kudos
Krob__Jeff
Beginner
1,326 Views

Continuing the saga...building up to properly interface to the General Polygon Clipper C library, I find I can open a polygon text file in my C routine C_fopen.c but the file pointer is not being returned to the main program to be passed to gpc_read_polygon later. I thought I had all my definitions & interfaces correct...but I guess not ;-).

PROGRAM F2CTest

USE GPC2
use, intrinsic :: ISO_C_BINDING

   interface

     subroutine C_fopen(ifp, filename, mode, ier) &
			bind(C,name='C_fopen')
         import
         implicit none
         type(C_PTR),value   :: ifp
         character(KIND=C_CHAR), intent(IN) :: filename(*)
         character(KIND=C_CHAR), intent(IN) :: mode(*)
         integer(C_int), intent(inout) :: ier
      end subroutine C_fopen

    end interface

character (len=40,KIND=C_CHAR) :: filename
character (len=4,KIND=C_CHAR)  :: mode
character (len=20,KIND=C_CHAR) :: C_format
integer :: ier,readholeflag
real(8) :: result
type(C_PTR) :: ifp


type(C_GPC_POLYGON) C_subject_polygon, C_clip_polygon, C_result_polygon
integer(C_INT) C_num_contours
type(C_GPC_VERTEX_LIST), pointer :: C_contour(:)
integer C_npts
type(C_GPC_VERTEX), pointer :: C_vertex(:)

!*************************************************************************
  OPEN(25,FILE='TESTGPC.TXT',STATUS='UNKNOWN')
  WRITE (25,*)'START TESTGPC'

  C_subject_polygon%num_contours = 0
  C_subject_polygon%hole = C_NULL_PTR
  C_clip_polygon%num_contours = 0
  C_result_polygon%num_contours = 0
  C_contour%num_vertices = 0

filename = 'stuff.dat' // C_NULL_CHAR
mode = 'r'// C_NULL_CHAR
readholeflag = 0
ier = 0

write(25,*)'mode = ',mode
write(25,*)'filename = ',filename

Call C_fopen (ifp, filename, mode, ier)

iifp = transfer(ifp,0_C_INTPTR_T)

write(25,*)'C_fopen ier = ',ier,iifp

!*******************************************
!       coming later...
!CALL gpc_read_polygon( ifp, readholeflag, C_subject_polygon )
!
end
/* fopen example */
#include <stdio.h>

void C_fopen (FILE	*pFile, char *newname, char *mode, int ier)
{

/*---------------------------------------------------------------------*/

  ier = 0;

  printf ("C_fopen: fopen mode = %s \n",mode);
  pFile = fopen (newname,mode);

  if (pFile==NULL)
  {
    printf ("C_fopen: fopen error = %p \n",pFile);
	ier = 9999;
  }

  if (pFile!=NULL)
  {
    printf ("C_fopen: pFile good = %p \n",pFile);
  }

}

The screen prints show the file is being opened properly w/ a good pointer created & no errors.

> C_fopen: fopen mode = r

> C_fopen: pFile good = 1035F4F8

but the print after the call to C_fopen to show the Fortran version of the pointer says;

 C_fopen ier =            0           0

iifp should not be '0' so I can only guess the "type(C_PTR) :: ifp" is not being returned...why?

Thanks in advance,

Jeff

0 Kudos
JVanB
Valued Contributor II
1,129 Views

You are not being careful about the level of indirection in your C interface. You could have just followed the example I posted in Quote #17, which invoked fopen() and got errno directly from Fortran, but instead you had to make it harder on yourself by using a C function to do it.

In your Fortran interface to C_fopen, you are passing ifp by value, which means that it won't be changed upon return. Thus you need to pass ifp by reference, just get rid of that ",value" stuff in that interface body. Also that means you don't get a pointer to a FILE structure (FILE*) in the actual C_fopen function, but a pointer to a pointer (FILE**), thus you should change your declaration there to FILE **pFile. Also the 5 places pFile is referenced in the body of C_fopen() will have to be changed from "pFile" to "*pFile" to dereference that pointer that you received from the Fortran caller.

Also, the Fortran program is correct to pass ier by reference as it does so that it can receive a result through that argument, but that means that ier should be declared as a pointer to int , i.e. int *ier in your C function and the two places where it is referenced you must change "ier" to "*ier" to dereference that pointer. Getting this level of indirection right is tricky until you have traced through function calls in machine language a few times, after that it all makes sense.

 

0 Kudos
Reply