Passing `allocatable, optional` to `optional` argument

Consider this example where we pass an allocatable, optional argument to call a optional argument:

  • works with LFortran, Intel-Classic
  • Fails (segfault) with gfortran, ifx, flang-new

My understanding of the standard is that in opt_alloc we should not have to check present(i), because it is an optional argument to the procedure, despite the one more level of pointer dereferencing passing from optional to allocatable, optional. What is the standard-conforming behavior?

module options
   public 
   contains

   subroutine opt(i)
      integer, optional, intent(in) :: i
      print *, 'IS PRESENT? ',present(i)
   end subroutine opt 

   subroutine opt_alloc(i)
      integer, allocatable, optional, intent(in) :: i
      call opt(i)
   end subroutine opt_alloc 

end module options

program p
   use options
   integer, allocatable :: i

   call opt_alloc() ! Failure here
   call opt_alloc(i)
   allocate(i)
   call opt_alloc(i)

end program

some aspects of this are discussed in An unallocated variable passed as an argument is not PRESENT.

According to my understanding, the code is valid and in the first case the argument in opt is not present.

1 Like

Reading An unallocated variable passed as an argument is not PRESENT - #13 by billlong I also interpret that the posted code should be conforming, because i from opt_alloc is the actual argument fed to opt and it is not only not allocated; also not present.

But of course assuming standard conformity, a compiler would have to handle the subtle address difference between present(i) .and. .not.allocated(i) and .not.present(i)

Furthermore, what should it print? LFortran currently prints:

$ lfortran a.f90
IS PRESENT?     F
IS PRESENT?     F
IS PRESENT?     T

Is this correct?

You can enhance the test like this:

   subroutine opt(i)
      integer, optional, intent(in) :: i
      print *, 'Present in opt: ',present(i)
   end subroutine opt

   subroutine opt_alloc(i)
      integer, allocatable, optional, intent(in) :: i
      print *, 'Present in opt_alloc: ',present(i)
      call opt(i)
   end subroutine opt_alloc

Now LFortran prints:

$ lfortran a.f90
Present in opt_alloc:     F
Present in opt:     F
Present in opt_alloc:     T
Present in opt:     F
Present in opt_alloc:     T
Present in opt:     T
1 Like

Yes, that’s exactly the answer I would expect! Another test would be with

   subroutine opt_ptr(i)
      integer, pointer, optional, intent(inout) :: i
      call opt(i)
   end subroutine opt_ptr

it has the same effect. My understanding is that a C equivalent would be:

void opt_alloc(int **i) {
    if (i) { // present
        opt(*i); 
    } else {
        opt(NULL); 
    }
}

so it really should be valid code, even safer with the allocatable that has always a state (while a pointer may be undefined).

1 Like