Passing element of an optional array as optional scalar argument

I have a question for the Fortran Standard gurus. Can one element of an optional array argument be passed over as an optional scalar argument to a subroutine? For example:

        subroutine optnl_array(array)
            integer, intent(in), optional :: array(10)
            call optnl_scalar(array(5)) ! Is this legal?
        end subroutine optnl_array
        subroutine optnl_scalar(s)
            integer, intent(in), optional :: s
            if (present(s)) then
                print *, 'S is present, ',s
            else
                print *, 'S not present'
            endif
        end subroutine

This could sometimes be useful when refactoring old libraries (which have settings as integer arrays, and should be then set as scalars in derived types in modernized versions).

at this Godbolt link it seems like compilers have different behavior. I think what differentiate them is how they treat array(5) when .not.present(array): is it a legit expression to be used inside the subroutine according to the standard?

1 Like

Not sure what the correct behaviour should be but I thought you had to do something like

if (present(array)) Then
  Call optnl_scalar(array(5))
end if

before you could safely access anything in array. You probably don’t need the present tests inside optnl_scalar then. I think most compilers should throw an error on your call to optnl_scalar when array is not present or at least give you a warning about a potential error. I always use a present test with optional arguments just to be safe.

1 Like

Based on an Intel Fortran forum thread from 2015, the answer to your question is in dispute. Some posters think passing an element of the optional-but-not-present array is not legal, and that is what I thought, but Intel’s compiler team thinks it is. I suggest not doing this if portability is desired. Maybe the standards committee could be asked for an interpretation?

1 Like

Also, to me this is another example of why I would like more fine grain control over TKR rules. Maybe an attribute on a dummy argument type declaration that would override the TKR restrictions and allow you to pass a scalar or maybe a new set of commands (say an allow, disallow and require command) that would specify what is allowed wrt TKR, what is disallowed, and what is required.

You could pass the whole array as an optional argument and an index, as in the following code:

module m
implicit none
contains
subroutine optnl_array(array)
integer, intent(in), optional :: array(10)
call optnl_scalar(5, array)
end subroutine optnl_array

subroutine optnl_scalar(i,s)
integer, intent(in) :: i ! index of element of s
integer, intent(in), optional :: s(:)
if (present(s)) then
   if (i > 0 .and. i <= size(s)) print*,"i, s(i) =", i, s(i)
else
   print*, "for i=", i," s(i) is unavailable"
end if
end subroutine optnl_scalar
end module m
!
program main
use m
implicit none
integer :: array(10), i
array = [(3*i, i=1,10)]
call optnl_array(array)
call optnl_array()
end program main

output:

 i, s(i) =           5          15
 for i=           5  s(i) is unavailable

In stdlib, maybe the optval function could be extended so that

result = optval(x, indx, default)

returns x(@indx) when x is present, using the syntax of Fortran 2023.

@FedericoPerini ,

No, it does not conform to the standard but the onus lies on the program author; the processor is not required to detect and report the nonconformance.

Starting Fortran 2008, an option that conforms to the standard and which you may consider is as follows:

subroutine optnl_array(array)
   integer, intent(in), optional :: array(10)
   integer, allocatable :: a
   if ( present(array) ) a = array(5) 
   call optnl_scalar( a ) ! An unallocated object can be passed as an OPTIONAL argument
end subroutine optnl_array

subroutine optnl_scalar(s)
   integer, intent(in), optional :: s 
   ..
4 Likes

I believe the call is conforming. The key question is whether array(5) as an actual argument is a reference, and if we look at the definition of that (F2018 3.120.1) we see, “appearance of a data object designator (9.1) in a context requiring its value at that point during execution”, which is not the case here. Therefore it does not need to be checked for presence before appearing as an actual argument in the call.

2 Likes

Thanks @rwmsu @Beliavsky @FortranFan @sblionel for the insights.

@rwmsu, I pass optional arguments on to other subroutines pretty often in my codes, so I can avoid checking for present(whatever), but the caveat is that the optional argument in the nested call is always the same as in the parent subroutine, and in this trivial case, everything always works.

@sblionel @Beliavsky: interesting! so basically using an allocatable can be used like in C++ one would check for a non-null pointer. Another interesting twist is if I add the request for value input in optnl_scalar: then, all compilers segfault, because like said, the value at array(5) cannot be accessed upstream:

subroutine optnl_scalar(s)
   integer, intent(in), value, optional :: s
end subroutine optnl_scalar

@FortranFan, I will mark yours as the “Solution” because it represents the practical approach to achieve that in a processor-agnostic way, although I think I better avoid this kind of approach altogether: too easy to get wrong.

That conclusion is surprising and the reasoning appears to be correct. If the argument array is not present, then the expression (array(5)) would not be allowed as an actual argument while array(5) would be allowed. This is consistent with the fact that the expression (array) would not be allowed, while the simple array would be.

What about the situation where the final dummy argument is not optional? In this case, if that final dummy argument is referenced, then it would be a programmer error, whereas if it is not referenced, then it is legal, right?

I should clarify that while the programmer doesn’t need to add a check, the compiler almost certainly needs to do one in order to pass the indication of absence.

The standard does not permit passing a not-present data entity to a non-optional dummy argument. “It shall not be supplied as an actual argument corresponding to a nonoptional dummy argument other than as the argument of the intrinsic function PRESENT or as an argument of a function reference that is a constant expression.” (F2018 15.5.2.12p3(4)) Processors are not required to check for this.

The argument that it is conforming is pretty convincing. But I will note that a couple of other examples mentioned in that forum thread still don’t work correctly in ifx if that’s the case.

In the example below, the assumed shape and derived type cases lead to segmentation faults when compiled with ifx.

Are there any compilers that do support all three of these cases?

program main
  type t
    integer :: a
    integer :: b
  end type
  call optional_explicit_shape()
  call optional_assumed_shape()
  call optional_type()
contains
  subroutine optional_explicit_shape(x)
    integer, intent(in), optional :: x(10)
    call optional_scalar(x(5))
  end subroutine

  subroutine optional_assumed_shape(x)
    integer, intent(in), optional :: x(:)
    call optional_scalar(x(5))
  end subroutine

  subroutine optional_type(x)
    type(t), intent(in), optional :: x
    call optional_scalar(x%b)
  end subroutine

  subroutine optional_scalar(x)
    integer, intent(in), optional :: x
    if (present(x)) then
      print *, 'S is present, ', x
    else
      print *, 'S not present'
    endif
  end subroutine
end
1 Like

Sorry it is not. Elsewhere the standard states an array element itself is data-ref which is a data-object-reference, one among the three kinds of references mentioned in the standard.

And the standard is clear an absent optional argument cannot be referenced and this makes the code nonconforming.

A “data reference” is an “appearance of a data object designator (9.1) in a context requiring its value at that point during execution”. That doesn’t say a data-ref is a “data reference”, despite the similarity of the terms.

@kargl @sblionel I’ve been advised to read the section on optional inputs on page 331 of the current draft and I read:

To my understanding, this is saying that if my array is not present, I cannot use any selectors on it (I guess array(), string_array()(), coarray()[], struct%variable…) as actual arguments to another subroutine/function, so it seems to lean towards the “non-conforming” side, although I don’t have the technical expertise to judge whether there are caveats in the word “actual” of “actual argument”…

@FedericoPerini ,

Toward the secure practice of Fortran, it will be better I feel to see as not “lean towards” but view it as clear-cut nonconformant situation. And you may notice gfortran faces an issue with it and encounters segmentation fault, if what I notice on Windows is generally reproducible elsewhere:

module m
contains
   subroutine sub( a )
      integer, intent(in), optional :: a(10)
      call sub2( a(5) )
   end subroutine
   subroutine sub2( a )
      integer, intent(in), optional :: a
      if ( present(a) ) print *, a
   end subroutine
end module
   use m
   call sub()
end 
C:\temp>gfortran -ffree-form p.f -o p.exe

C:\temp>p.exe

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x484603fa
..

If you feel otherwise, that is you think the code might be conformant and therefore a processor can be expected to not throw run-time errors on it as seen above, you may want to open an issue at GCC Bugzilla and work with the GCC volunteers on gfortran development to help reach out to J3 committee for a clear take on this.

As you can envision, that will be a good, overall enhancement for the secure practice of Fortran with OPTIONAL arguments and beneficial to many other practitioners also.

1 Like

Thank you @kargl, this strengthens my assumption that the example is actually non-conforming.

For the sake of curiosity: I’ve googled subobject selector and there is only one meaningful result, from one Fortran compiler manual, which seems to match my interpretation of what a subobject selector is.

1 Like

Does this interpretation of the standard behavior also extend to compound object components? It would be great if the standard clarified the text as deemed necessary to enforce this behavior across all compiler implementations. This behavior could eliminate quite a few extra lines of redundant coding for optional argument presence.

Finding the relevant section in the standard is difficult, so I just did a quick test, and it looks like at least three compilers allow passing components of optional objects as actual arguments to other procedures that accept them as optional arguments. Compiler Explorer

Thanks @FortranFan. It fails in LFortran also, I opened up an issue for it: Nested optional arguments don't compile · Issue #2463 · lfortran/lfortran · GitHub.

1 Like

I don’t see why not, and also don’t see the need for additional words. As is often the case, one has to dig through a few levels to resolve the question. If this were a case that multiple compilers were getting wrong, maybe a note under OPTIONAL might be handy.

1 Like