C function calling from PGF

I am trying to convert a project that runs in ifort over to PG visual fortran. After fixing a few compiling and linking errors, I have an executable that crashes on a C-function call. This function call works in ifort, so I was wondering if someone might be able to quickly spot why it isn’t working here:

SUBROUTINE RD_FOO_2 ( fname, lpatch, pSrf, pVS)

use geom_h
use vsection_h
character*(*) fname
integer :: lpatch
type(gspline_t), dimension(:) :: pSrf
type(vsection_t), dimension(:) :: pVS

END SUBROUTINE RD_FOO_2

There is another C-function that calls the same file (fname) and returns a bunch of integers - and that is working fine. I read through the faq’s on inter-language operability and it sounded like the problem may be with dynamically allocating the dimension(:)?

Hi bjk777,

Where’s the call to the C function? What’s the prototype for it?

Are you passing fname to the C function? If so, are you handling the hidden string length argument?

Note, you may consider using the F2003 ISO C Binding since it’s the standard method for C and Fortran inter-language calling.

  • Mat

Mat- The fname handling is working as it is used in a previous function to access the same file and the output from that function is valid. Can I send the code sections to your email rather than posting them here?

Normally I would, but I’m away at a conference this week. Though, if you send the code to PGI Customer Service (trs@pgroup.com) they should be able to help.

Thanks,
Mat

The C function expects a C-style character argument, which is a pointer to a null-terminated array of char. Fortran doesn’t use C-style character; in fact, Fortran stores character strings without null-termination, and passes a hidden argument corresponding to the dummy argument character string length.

Also, the Fortran interface specifies assumed-shape arrays, which have no correspondence in a C function. The Fortran interface for the arrays should use assumed-size arrays “(*)”, not assumed-shape “(:)”.

Below I show a Fortran program calling a C function passing an array of derived type and a character string.

The Fortran program:

        module mm
         type dt
          sequence
          integer :: m1, m2
         end type
         type mt
          sequence
          real :: r1, r2
         end type
        end module
        program p
         use mm
         interface
          subroutine sub1( c, x, y, n ) bind(c)
           use mm  
           type(dt) :: x(*)
           type(mt) :: y(*)
           character*(*) :: c
           integer, value :: n
          end subroutine
         end interface

         type(dt), allocatable :: xx(:)
         type(mt), allocatable :: yy(:)
         character*(20) :: str
         integer :: n, i

         n = 10
         allocate(xx(n), yy(n))
         do i = 1, n
          xx(i)%m1 = i
          xx(i)%m2 = i+1 
          yy(i)%r1 = i*10
          yy(i)%r2 = i*20
         enddo
         str = "notastring"
         call sub1( str, xx, yy, n )
        end program

Note the interface to sub1. The ‘bind(c)’ tells the compiler that ‘sub1’ is a C function. The array arguments are assumed shape: ‘()’ bounds. The integer argument ‘n’ is marked as a ‘value’ argument, so it is passed by value, as scalar arguments are for C functions. The character string ‘c’ is 'character(*)’. The C function being called is:

#include <stdio.h>
typedef struct{
        int m1, m2;
    }dt;  
typedef struct{
        float r1, r2;
    }mt;  

void sub1( char* c, dt* x, mt* y, int n, int len )
{
    int i;
    printf( "sub1, n = %d\n", n );

    for( i = 0; i < n; ++i )
        printf( "  x[%d].m1=%4d  .m2=%4d\n", i, x[i].m1, x[i].m2 );
    for( i = 0; i < n; ++i )
        printf( "  y[%d].r1=%4.0f  .r2=%4.0f\n", i, y[i].r1, y[i].r2 );

    printf( "len = %d\n", len );
    printf( "string=>%.*s<\n", len, c );
}

Here, ‘n’ comes in as a value argument. Note the extra argument, ‘len’. This is the hidden argument passed by Fortran to hold the length of character string dummy arguments. The argument ‘c’ is a pointer to an array of char, but it is not null-terminated, as C strings are. There may (or may not) be a null byte at the end of the string. In this case, the program makes sure to only use the first ‘len’ characters of the string.
I built this using pgf90 for the Fortran and pgcc for the C (I also tried gcc for the C program and got the same results). The output is:

sub1, n = 10
  x[0].m1=   1  .m2=   2
  x[1].m1=   2  .m2=   3
  x[2].m1=   3  .m2=   4
  x[3].m1=   4  .m2=   5
  x[4].m1=   5  .m2=   6
  x[5].m1=   6  .m2=   7
  x[6].m1=   7  .m2=   8
  x[7].m1=   8  .m2=   9
  x[8].m1=   9  .m2=  10
  x[9].m1=  10  .m2=  11
  y[0].r1=  10  .r2=  20
  y[1].r1=  20  .r2=  40
  y[2].r1=  30  .r2=  60
  y[3].r1=  40  .r2=  80
  y[4].r1=  50  .r2= 100
  y[5].r1=  60  .r2= 120
  y[6].r1=  70  .r2= 140
  y[7].r1=  80  .r2= 160
  y[8].r1=  90  .r2= 180
  y[9].r1= 100  .r2= 200
len = 20
string=>notastring          <