Strange pointer error with Intel ifort

Here is the small routine with the problem:

   subroutine mmap_flatraces_t_init(this,ns)
      use iso_c_binding
      class(mmap_flatraces_t), intent(out) :: this
      integer(i64),            intent(in)  :: ns

      call this%x%create( FMMAP_SCRATCH, "", ns, mold=0.0 )
      call c_f_pointer( this%x%cptr(), this%flatraces ) ! <--- error here
   end subroutine mmap_flatraces_t_init

And the error message when executing c_f_pointer():
forrtl: severe (408): fort: (7): Attempt to use pointer FLATRACES when it is not associated with a target

But that’s the point, I want to associate this%flatraces, and it is not associated before that and doesn’t have to be… I don’t understand what happens. Compiler bug?

Here is the definition of the derived type:

   type mmap_flatraces_t
      type(fmmap_t) :: x
      real, pointer, contiguous :: flatraces(:) => null()
      integer(i64) :: i = 0
   contains
      procedure :: init => mmap_flatraces_t_init
      final     :: mmap_flatraces_t_final
   end type
1 Like

Trying to associate the pointer to a fake variable before the call:

   subroutine mmap_flatraces_t_init(this,ns)
      use iso_c_binding
      class(mmap_flatraces_t), intent(out) :: this
      integer(i64),            intent(in)  :: ns
      real, target :: foo(1)

      call this%x%create( FMMAP_SCRATCH, "", ns, mold=0.0 )
      this%flatraces => foo
      call c_f_pointer( this%x%cptr(), this%flatraces )
   end subroutine mmap_flatraces_t_init

Now I have this error upon exiting the routine :
Boundary Run-Time Check Failure for variable 'nesca_data_types_mp_mmap_flatraces_t_init_$FOO'

This is crazy…

1 Like

My mistake… I stupidly forgot giving the shape !

call c_f_pointer( this%x%cptr(), this%flatraces, [ns] )

is ok.

I would expect at least a compilation warning in such a case.

1 Like

It seems that instead of processing the absence of the shape as an error, the intel compiler (whatever the version) applies an extension that preserves the shape and bounds of the Fortran pointer:
call c_f_pointer( cptr, p )
with p having a rank>0 is equivalent to
call c_f_pointer( cptr, p, shape=shape(p), ubound=ubound(p) )

I find this error prone !

    use iso_c_binding

    real, target :: a(100)
    real, pointer, contiguous :: p(:)

    a = [(i,i=1,100)]

    p(0:2) => a
    print*, p

    call c_f_pointer( c_loc(a(98)), p )   ! non standard conforming
    print*, lbound(p), ubound(p)
    print*, p

end

results in:

   1.000000       2.000000       3.000000    
           0           2
   98.00000       99.00000       100.0000    

I don’t think it is possible in the general case, to tell if the cptr is pointing to a scalar or array. But I guess one could assume that is what the user wanted from the fptr argument, and give an error “missing shape argument; argument fptr is a rank-1 array” or something like that.

Edit: I see other compilers do this:

GCC:

> gfortran --version
GNU Fortran (SUSE Linux) 7.5.0
Copyright (C) 2017 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

> gfortran test_c_f_pointer.f90
test_c_f_pointer.f90:11:36:

     call c_f_pointer( c_loc(a(98)), p )   ! non standard conforming
                                    1
Error: Expected SHAPE argument to C_F_POINTER with array FPTR at (1)
>

NAG:

> nagfor test_c_f_pointer.f90
NAG Fortran Compiler Release 7.2(Shin-Urayasu) Build 7203
Error: test_c_f_pointer.f90, line 11: No specific match for reference to generic C_F_POINTER
[NAG Fortran Compiler error termination, 1 error]

flang:

error: Semantic errors in /app/example.f90
/app/example.f90:11:5: error: SHAPE= argument to C_F_POINTER() must appear when FPTR= is an array
      call c_f_pointer( c_loc(a(98)), p )   ! non standard conforming
      ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Compiler returned: 1

nvfortran:

NVFORTRAN-S-0074-Illegal number or type of arguments to c_f_pointer - keyword argument fptr (/app/example.f90: 11)
  0 inform,   0 warnings,   1 severes, 0 fatal for MAIN
Compiler returned: 2

Kind of cryptic warning with nvfortran.

1 Like

Exactly, it seems that all compilers but the intel one, do report a compilation error on my code example.