Non-associated procedure pointer as optional argument

Hello Fortran community,

I’ve stumbled upon an unexpected gfortran runtime error stop when using a non-associated procedure pointer as optional argument to a subroutine

module m

  abstract interface
    ! Just a function interface
    subroutine my_fun(x)
        real, intent(in) :: x
    end subroutine my_fun   
  end interface   

  contains

  ! Optional function argument
  subroutine with_fun(sub)
     procedure(my_fun), optional :: sub
     print *, present(sub)
  end subroutine   

end module m

program p
  use m

  procedure(my_fun), pointer :: ptr => null()

  call with_fun()        ! no runtime error 
  call with_fun(sub=ptr) ! runtime error

end  
  • The error is triggered usin -fcheck=all
  • It is not triggered when a data pointer is passed rather than a procedure pointer.

I believe it is of course correct to check this when the procedure argument is not optional, but probably it should not be, when optional (this is what happens for variable pointers)

Do you think this issue may be submitted to the GNU bugzilla? IMHO this is a minor bug related to an overlooked check that may be worthwhile of lifting.

Here I’ve put an example that shows no error triggered on the data, error triggered on the null() procedure.

All gfortran versions seem to be affected by this issue, so most likely there is a Standard-related reason that check is still in place.

1 Like

My reading of the standard suggests that no error should be issued. Here’s what the standard says:

15.5.2.13 Argument presence and restrictions on arguments not present
14 1 A dummy argument or an entity that is host associated with a dummy argument is not present if the dummy
15 argument
16 • does not correspond to an actual argument,
17 • corresponds to an actual argument that is not present, or
18 • does not have the ALLOCATABLE or POINTER attribute, and corresponds to an actual argument that
19 – has the ALLOCATABLE attribute and is not allocated, or
20 – has the POINTER attribute and is disassociated;
21 otherwise, it is present.

There is no distinction made between being a data pointer or a procedure pointer. In your example, the dummy does not have ALLOCATBLE nor POINTER, and is associated with an actual argument that is a disassociated pointer, therefore the dummy argument is not present. As all you do is call PRESENT on the dummy, that is permitted.

2 Likes

Does it make a difference if the pointer is disassociated with ptr=>null() or with nullify(ptr)?

1 Like

No, these are the same.

FWIW, ifx, with -check all enabled, gives no error and displays F in both cases.

2 Likes

Thank you @sblionel @RonShepard for confirming the case with your comments! yes that was also my interpretation. I have filed a ticket at the GNU Bugzilla.

1 Like