Question about assumed type arrays and C_NULL_PTR

I’m trying to write a consistent C-interop interface to a C function with a prototype similar to this

int cfun( int index. const void * ivals1, const void *ivals2, const void *ivals3)

This function is expecting either INT32 or INT64 integer arrays.

I implemented the C interop interface with assumed type arrays as follows

Function cfun_c(index, ivals1, ivals2, ivals3) BIND(C, NAME="cfun")
     Import :: C_INT
     Integer(C_INT),    VALUE :: index
     Type(*),                Intent(IN) :: ivals1(*)
     Type(*),                Intent(IN) :: ivals2(*)
     Type(*),                Intent(IN) :: ivals3(*)
     Integer(C_INT)                     :: cfun_c
 End Function cfun_c

I then try to call this function from Fortran with C_NULL_PTR passed to the ival2, and ival3 arrays.

ie

Subroutine ffun(index, ivals1,  ierr)
    Integer(C_INT), Intent(IN) :: index
    Type(*),        Intent(IN) :: ivals1(*)
    Integer(C_INT). Intent(OUT) :: ierr
    ierr = cfun_c(index, ivals1, C_NULL_PTR, C_NULL_PTR)
 End Subroutine ffun

Intel oneAPI 2023.2 classic C and ifort do not appear to recognize the C_NULL_PTR passed to the assume type arrays as an actual NULL. However, I get no compile errors but the underlying C function returns an error code (-1 with no other explanation). I tried creating a single element TYPE(C_PTR) array thinking it might be something to do with passing a scalar to the assumed type array but that also does not work. If I replace the ival2 and ival3 assumed type arrays in my C-interop interfaces with

Type(C_PTR), VALUE :: ivals2
Type(C_PTR), VALUE :: ivals3

the function works as expected. So questions.

  1. Why does passing either a scalar C_NULL_PTR or a single element array of TYPE(C_PTR) set to C_NULL_PTR to the assumed type arrays not work. Unfortunately, the available info on using assumed type is very sparse and is of little help with this problem. Assumed type appears to work great as long as you don’t try to pass a NULL ptr. My (very limited) knowledge of assumed type led me to believe this should work.

  2. Can someone point me to some documentation that would explain what the actual limitations of assumed type are.

  3. I haven’t tried another compiler yet but is this maybe a bug in the Intel compilers

Thanks

Some general suggestions first:

  1. Use a Fortran 2018 processor.
  2. Author the interface in Fortran to match what the function expects; if integer arrays, inform the Fortran processor as such. That is, make it easy for the processor and any reader of the code.
  3. Use the enhanced semantics with Fortran 2018 with OPTIONAL attribute on arguments.

A silly example:

  • C function
#include <stdio.h>

int foo(const int n, const void* a)
{
   printf("In foo: n = %d\n", n);
   int *x = (int *)a;
   if (x != NULL) {
      for (int i=0; i < n; i++) printf("%d ", x[i]);
      printf("\n");
   } else {
      printf("a is NULL.\n");
   }
   return 0;
}
  • Fortran caller
   use, intrinsic :: iso_c_binding, only : c_int
   interface
      function foo(n, a) result(r) bind(C, name="foo")
         import :: c_int
         ! Argument list
         integer(c_int), intent(in), value :: n
         integer(c_int), intent(in), optional :: a(*)  !<-- Note the type and the attribute
         ! Function result
         integer(c_int) :: r
      end function 
   end interface
   integer(c_int) :: r
   integer(c_int) :: x(3)
   x = [ 1, 2, 3 ]
   r = foo( 42 )
   r = foo( size(x, kind=c_int), x )
end
  • Program response with a Fortran 2018 processor and a companion C processor:
C:\temp>cl /c /W3 /EHsc c.c
Microsoft (R) C/C++ Optimizing Compiler Version 19.36.32537 for x64
Copyright (C) Microsoft Corporation.  All rights reserved.

c.c

C:\temp>ifort /c /free /standard-semantics p.f
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.10.0 Build 20230609_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.


C:\temp>link c.obj p.obj /subsystem:console /out:p.exe
Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\temp>p.exe
In foo: n = 42
a is NULL.
In foo: n = 3
1 2 3
1 Like
  1. TKR semantics in Fortran; the onus is on the program author.

  2. Modern Fortran Explained and/or 18-007r1 document as the proxy for the Fortran standard.

The C function is expecting a pointer. When calling the function with C_NULL_PTR like this, the compiler is definitely not passing a null pointer, but rather a non-null address to a static memory location that contains a null pointer. This is not same thing, and the C function is messed.

In this case you can indeed safely pass C_NULL_PTR. In the case you would want to pass an array, you would have to pass C_LOC(ivals2)

1 Like

My understanding of assumed type is that it was introduced because using Type(C_PTR) was considered cumbersome in some situations and that assumed type would function more like a true C void pointer. Therefore, I was expecting it to act the same way as a C pointer would. I understand the TKR rules but neither intel or gfortran 13 issue any error trying to pass C_NULL_PTR to an assumed type array. The following program illustrates the issue. I’m just trying to avoid the extra step of creating C pointers for ival1, etc using C_LOC and passing the explicit pointers. The description of assumed type in MFE is practically useless and doesn’t cover this case and I have better things to do than wade through a lot of poorly written extraneous verbage in the standard just to find that this situation is not covered. What we need is someone or someones to come out with a Modern Fortran Handbook much like the Fortran 95 an Fortran 2003 ones that describes what the rules for using things like this actually are in a form that cuts through the standard BS.

test_atnp.f90

 Program test_atnp

   USE ISO_FORTRAN_ENV
   USE ISO_C_BINDING

   Implicit NONE

   Integer :: ivals(5), ierr1, ierr2, ierr3, isize

   Interface
     Function cfun1_c(isize, ivals1, ivals2, ivals3) BIND(C, NAME="cfun")
       IMPORT :: C_INT
       Integer(C_INT), VALUE :: isize
       Type(*),        Intent(IN) :: ivals1(*)
       Type(*),        Intent(IN) :: ivals2(*)
       Type(*),        Intent(IN) :: ivals3(*)
       Integer(C_INT)             :: cfun1_c
     End Function
   End Interface

   Interface
     Function cfun2_c(isize, ivals1, ivals2, ivals3) BIND(C, NAME="cfun")
       IMPORT :: C_INT, C_PTR
       Integer(C_INT), VALUE      :: isize
       Type(*),        Intent(IN) :: ivals1(*)
       Type(C_PTR),    VALUE      :: ivals2
       Type(C_PTR),    VALUE      :: ivals3
       Integer(C_INT)             :: cfun2_c
     End Function
   End Interface

   ivals = [1, 2, 3, 4, 5]
   isize = 5

   Print *,''
   Print *,' *** Calling ffun1 with assumed type interface'
   Print *,''

   Call ffun1(isize, ivals, ierr1)
   Print *,''
   Print *,' ffun1 ierr = ', ierr1

   Print *,''
   Print *,' *** Calling ffun2 with type(c_ptr) interface'
   Print *,''

   Call ffun2(isize, ivals, ierr2)
   Print *,''
   Print *,' ffun2 ierr = ', ierr2

   Print *,''
   Print *,' *** Calling ffun3 with C_NULL_PTR in an array interface'
   Print *,''

   Call ffun3(isize, ivals, ierr3)
   Print *,''
   Print *,' ffun2 ierr = ', ierr3

   STOP

Contains

   Subroutine ffun1(isize, ivals, ierr)
     Integer, Intent(IN)  :: isize
     Type(*), Intent(IN)  :: ivals(*)
     Integer, Intent(OUT) :: ierr

     ierr = cfun1_c(isize, ivals, C_NULL_PTR, C_NULL_PTR)

   End Subroutine ffun1

   Subroutine ffun2(isize, ivals, ierr)
     Integer, Intent(IN)  :: isize
     Type(*), Intent(IN)  :: ivals(*)
     Integer, Intent(OUT) :: ierr

     ierr = cfun2_c(isize, ivals, C_NULL_PTR, C_NULL_PTR)

   End Subroutine ffun2

   Subroutine ffun3(isize, ivals, ierr)
     Integer, Intent(IN)  :: isize
     Type(*), Intent(IN)  :: ivals(*)
     Integer, Intent(OUT) :: ierr

     Type(C_PTR) :: NULL_PTR(1)
     NULL_PTR = C_NULL_PTR
     ierr = cfun1_c(isize, ivals, NULL_PTR, NULL_PTR)

   End Subroutine ffun3

End Program test_atnp

cfun.c

#include <stdlib.h>
#include <stdio.h>
#include <stdint.h>
#include <string.h>

extern int cfun(int isize, const void *ival1, const void *ival2, const void *ival3);

int cfun(int isize, const void *ival1, const void *ival2, const void *ival3)
{

  int i;
  size_t ist;
  int *iv1;
  int ierr;

  ist = (size_t) isize;
  iv1 = malloc(ist*sizeof(int));
  memcpy(iv1, ival1, (ist*sizeof(int)));
  printf(" ival1 array values\n");
  printf("\n");

  ierr = 0;
  for (i=0; i<isize; i++) {
     printf(" %d\n", iv1[i]);
  }
  if (ival2 == NULL) {
    printf("\n ival2 is null\n");
    ierr = ierr+1;
  }
  if (ival3 == NULL) {
    printf("\n ival3 is null\n");
    ierr = ierr+2;
  }
  if (ierr == 0) {
    printf("\n **** NULL pointers not recognized ****\n");
  }

  return(ierr);
}

To me, a TYPE(C_PTR) is actually a C void pointer.

I don’t understand either, as the rank rule is apparently is not honoured.

Anyway, the central point is that when you pass C_NULL_PTR as an actual argument to a dummy argument that has not the VALUE attribute; you definitely don’t pass a null pointer, but a pointer to a null pointer.

I’ve tried the above code (with test_atnp.f90 and cfun.c) on Ubuntu22 + gfortran-12 cfun.c test_atnp.f90, then I get this error:

test_atnp.f90:68:34:

   68 |      ierr = cfun1_c(isize, ivals, C_NULL_PTR, C_NULL_PTR)
      |                                  1
Error: Rank mismatch in argument ‘ivals2’ at (1) (rank-1 and scalar)
test_atnp.f90:68:46:

   68 |      ierr = cfun1_c(isize, ivals, C_NULL_PTR, C_NULL_PTR)
      |                                              1
Error: Rank mismatch in argument ‘ivals3’ at (1) (rank-1 and scalar)

I haven’t tried Gfortran-13, but is the result different…?

By the way, I’ve tried using optional also (as in the example by FortranFan), and it seems to work with gfortran-12. So I guess even for type(*), when the actual argument is absent, null pointers are sent to the optional dummy argument(s). (Below is a slightly modified code, where cfun1_opt_c() is given optional for ivalsN).

test_f.f90

Program test_atnp
   USE ISO_FORTRAN_ENV
   USE ISO_C_BINDING
   Implicit NONE

   Integer :: ivals(5), ierr2, ierr3, ierr1_opt, isize

   Interface

     Function cfun1_c(isize, ivals1, ivals2, ivals3) BIND(C, NAME="cfun")
       IMPORT :: C_INT
       implicit none
       Integer(C_INT), VALUE      :: isize
       Type(*),        Intent(IN) :: ivals1(*), ivals2(*),  ivals3(*)  !<-- no optional
       Integer(C_INT)             :: cfun1_c
     End Function

     Function cfun1_opt_c(isize, ivals1, ivals2, ivals3) BIND(C, NAME="cfun")
       IMPORT :: C_INT
       implicit none
       Integer(C_INT), VALUE         :: isize
       Type(*), Intent(IN), optional :: ivals1(*), ivals2(*), ivals3(*)  !<-- optional
       Integer(C_INT)                :: cfun1_opt_c
     End Function

     Function cfun2_c(isize, ivals1, ivals2, ivals3) BIND(C, NAME="cfun")
       IMPORT :: C_INT, C_PTR
       implicit none
       Integer(C_INT), VALUE      :: isize
       Type(*),        Intent(IN) :: ivals1(*)
       Type(C_PTR),    VALUE      :: ivals2, ivals3
       Integer(C_INT)             :: cfun2_c
     End Function

   End Interface

   ivals = [1, 2, 3, 4, 5]
   isize = 5

   Print *
   Print *,'---- Calling ffun2 with type(c_ptr) interface ----'
   Print *

   Call ffun2(isize, ivals, ierr2)
   Print *,''
   Print *,' ffun2 ierr = ', ierr2

   Print *
   Print *,'---- Calling ffun3 with C_NULL_PTR in an array interface ----'
   Print *

   Call ffun3(isize, ivals, ierr3)
   Print *
   Print *,' ffun3 ierr = ', ierr3

   Print *
   Print *,'---- Calling ffun1_opt with an optional array interface ----'
   Print *

   Call ffun1_opt(isize, ivals, ierr1_opt)
   Print *,''
   Print *,' ffun1_opt ierr = ', ierr1_opt

Contains

  Subroutine ffun2(isize, ivals, ierr)
     Integer, Intent(IN)  :: isize
     Type(*), Intent(IN)  :: ivals(*)
     Integer, Intent(OUT) :: ierr

     ierr = cfun2_c(isize, ivals, C_NULL_PTR, C_NULL_PTR)

   End Subroutine

   Subroutine ffun3(isize, ivals, ierr)
     Integer, Intent(IN)  :: isize
     Type(*), Intent(IN)  :: ivals(*)
     Integer, Intent(OUT) :: ierr

     Type(C_PTR) :: NULL_PTR(1)
     NULL_PTR = C_NULL_PTR

     !! NG: passing the address of NULL_PTR(:) array to cfun() in C.
     ierr = cfun1_c(isize, ivals, NULL_PTR, NULL_PTR)

   End Subroutine

   Subroutine ffun1_opt(isize, ivals, ierr)
     Integer, Intent(IN)  :: isize
     Type(*), Intent(IN)  :: ivals(*)
     Integer, Intent(OUT) :: ierr

     !! (L-1) positional arguments only (where ivals2 and ivals3 are omitted)
     ierr = cfun1_opt_c( isize, ivals )

     !! (L-2) use keyword arguments (where ivals2 is omitted)
     !! ierr = cfun1_opt_c( isize= isize, ivals1= ivals, ivals3= ivals )

   End Subroutine

End Program

test_c.c

#include <stdio.h>

int cfun(
    int isize,
    const void *ival1,
    const void *ival2,
    const void *ival3 )
{
  int i, ierr = 0;

  if (ival1)
  {
      printf("ival1 array values\n\n");
      for (i = 0; i < isize; i++) printf("  %d\n", ((int*) ival1)[i]);
      ierr++;
  }
  if (ival2)
  {
      printf("ival2 array values\n\n");
      for (i = 0; i < isize; i++) printf("  %d\n", ((int*) ival2)[i]);
      ierr++;
  }
  if (ival3)
  {
      printf("ival3 array values\n\n");
      for (i = 0; i < isize; i++) printf("  %d\n", ((int*) ival3)[i]);
      ierr++;
  }

  printf("\n  number of non-null pointers = %d\n", ierr);
  return ierr;
}

Result (Ubuntu22):

$ gfortran-12 test_c.c test_f.f90

 ---- Calling ffun2 with type(c_ptr) interface ----

ival1 array values

  1
  2
  3
  4
  5

  number of non-null pointers = 1
 
  ffun2 ierr =            1

 ---- Calling ffun3 with C_NULL_PTR in an array interface ----

ival1 array values

  1
  2
  3
  4
  5
ival2 array values

  0
  0
  -1149143776
  32767
  185058958
ival3 array values

  0
  0
  -1149143776
  32767
  185058958

  number of non-null pointers = 3

  ffun3 ierr =            3

 ---- Calling ffun1_opt with an optional array interface ----

ival1 array values

  1
  2
  3
  4
  5

  number of non-null pointers = 1
 
  ffun1_opt ierr =            1

If I use keyword arguments like (L-2), the result seems reasonable, so probably the code (+ gfortran-12) is working as expected for this usage?

 ---- Calling ffun1_opt with an optional array interface ----
ival1 array values

  1
  2
  3
  4
  5
ival3 array values

  1
  2
  3
  4
  5

  number of non-null pointers = 2
 
  ffun1_opt ierr =            2

Is it something that is guaranteed by the standard, or is it just a common implementation?

I checked gfortan-13 again and it doesn’t issue an error (thought I might have mixed gcc and ifort). This is on a Linux Mint (Ubuntu 22) system. I actually thought about using optional arguments because I have a vague memory of reading something about using C_NULL_PTR as a “place holder” for optional arguments was allowed (but don’t quote me on that) but decided that was an unneeded complication. I actually had all Type(C_PTR), VALUE in my original interfaces but was just trying to see if assumed shape arrays worked the way I presumed they did. Apparently, for the case of trying to pass a NULL ptr they don’t. On the positive side they work like a champ for directly passing data to the C function without an intervening (cptr = C_LOC(array)) so I’ve started using them as my default method for C-interop interfaces.

I would also like to know it exactly :grin: Though I’ve seen this kind of usage several times before (on the net), I’ve no idea whether it is guaranteed to work or not…

Hmm, interesting…

For fortran-only code, then PRESENT(dummy) is required to work for optional arguments associated either with missing or with unallocated actual arguments. I do not know the answer when the called routine is written in C. As a practical matter, testing for a null address seems to work for all the fortran compilers I use, but I don’t know if that behavior is mandated anywhere in the fortran standard. Anyone know if there is something in the ISO_Fortran_binding.h header file that can be used on the C side to simulate the fortran PRESENT() intrinsic?

As I mentioned above, the facility with OPTIONAL attribute is indeed a standard feature introduced starting Fortran 2018:

  • 18-007r1 document toward Fortran 2018 states in its Introduction, “An interoperable procedure can have dummy data objects that are … optional …”

  • WG5 document N161 (albeit an unofficial one wrt WG5 or PL22.3) on “The new features of Fortran 2018” by John Reid, August 2, 2018 mentions in section 2 “Further interoperability of Fortran with C” the following:

  • In chapter 21 of “Modern Fortran Explained, Incorporating Fortran 2018”, section 21.2 goes into the same in further detail.

Readers are requested to note I will state as such if I make a nonstandard suggestion.

2 Likes

That statement covers only the situation with missing actual arguments. Do you know if the unallocated actual argument case is also required by the standard to be mapped to a null pointer?

Fortran 2008 published circa Nov. 2010 introduced, “A null pointer or unallocated allocatable can be used to denote an absent nonallocatable nonpointer optional argument.”

I understand that statement in the context of fortran null pointers and fortran subprograms, but what about the C null pointer aspect with C interoperability in f2018? Do those two sentences in the standard together cover the null pointer situation that is being discussed here?

Thanks for everyones input. After playing around some more with my code I’ve decided to go the optional argument route suggested by @PierU. I was hesitant at first to use optional arguments since I initially thought it would affect a LOT (and by a lot I mean over 100) of routines. However, after reviewing the target C code I’m trying to interact with it appears that only a few routine actually need NULL pointers passed to them to trigger if an argument is used in the C code so optional in this case makes sense. I still think though that irrespective of TKR and other rules you should be able to pass a NULL pointer to assumed type arrays etc and have it end up on the C side of things as a NULL pointer and not a void **ptr which appears to be whats happening.

It was @FortranFan , not me (that said, talking about disinformation while it’s just a mistake is a bit exaggerated)

The reason is the way Fortran have been passing arguments for decades. It would be nonsense to make an exception to this strongly established rule just for c_null_ptr

I marked this post as the solution, let me know if some other message in this thread should be marked as the solution instead, since there are multiple.

I suggest moving the above post by FortranFan to the following thread, with a link to this thread (and possibly lock this thread because already “solved”).

The issue instead on this forum is some admins, especially @Beliavsky , are overeager in editing some posts without authorization and permission.

I believe moderators delete some posts partly because other user(s) flagged the post to have some issues (e.g., violating CoC). If you think there is some issues with CoC, I think it can be discussed in the above dedicated thread. IMHO, the mechanism of this kind of forum is not the same as some unmoderated ones (like comp.lang.fortran).

(This post of mine is not related to the thread topic (C_NULL_PTR), so please delete it anytime!)

1 Like

Maybe the OP would have corrected the misattribution of good will if he hadn’t been directly accused of “disinformation”, which is a pretty strong accusation that implies voluntary lying.

1 Like