`optional` character argument to call a procedure interface: unexpected

I would like to ask for clarification on the following case:

  • I have a procedure interface with several versions in module
  • Another subroutine, which has an optional argument, may call different procedures of the interface whether the argument is present or not.
  • the optional argument is character(len=*)

I find that (with all major compilers! see test program at this link) when the object is not present, the procedure of the interface that assumes it is input is called, while I would expect it is not.

In my example, I am preparing a string:

  • label = value if label is present
  • value if label is not present

With all compilers I always get the = sign, even if label is not present:

   call print_optional(123)
   call print_optional(123,'my_label')

returns

 =123
 my_label=123

I’m surprised: it means that the procedure with the character argument in the interface is always called. I would expect the program to go to the procedure without character argument instead:

123
 my_label=123

Is this a bug across all compilers, or (more likely) I am missing some rules with optional character arguments? Thanks for any advice!

I don’t know how your code should behave, but I would have intuitively written something like:

      character(*), optional, intent(in) :: label
      if (present(label)) then
          print *, opt_string(i,label)
      else
          print *, opt_string(i)
      end if
2 Likes

:smiley: I was about to write the same thing! indeed, the issue being that

subroutine print_optional(i,label)
      integer, intent(in) :: i
      character(*), optional, intent(in) :: label
      print *, opt_string(i,label)
end subroutine print_optional

forces the call to m2 all the time

1 Like

Thank you @vmagnin and @hkvzjal. I searched through the F2023 standard and found this:

An optional dummy argument that is not present is subject to the following restrictions.
[…]
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.

So basically everything that’s not within a if present(x) block is invalid. Bloat, bloat everywhere :thinking:

1 Like

So we should expect a compilation error with your code, isn’t it?

@FedericoPerini ,

I don’t know whether you have some constraints about the code structure, but you could have avoided the issue by directly making print_optional the global interface name itself:

   public :: print_optional
   interface print_optional
     module procedure m1
     module procedure m2
     module procedure i2
   end interface
   [...]

   program test
      use is_optional

      print *, print_optional(123)
      print *, print_optional(123, 'my_label')
      print *, print_optional(123, 456)
   end program

This also saves you quite some code :slight_smile:

1 Like

Just thinking aloud.
The only case that call could be valid is if the argument is optional also in the procedure of the interface being called. Since that is not the case, yes I think the compiler may issue a warning that the procedure may be called with a missing argument. Maybe there is such warning, but I haven’t checked.

Thank you! Yes the issue is that the two come from different packages. I guess the solution is to not use optional upstream, but just have another interface like you’re suggesting.

opt_string() is a generic name for two routines:

  • m1() that has only 1 argument
  • m2() that has 2 required arguments

Remember that the appropriate routine is chosen at compile-time by the compiler.

When you are calling opt_string(123,my_label) with my_label that is absent in the caller routine, then m1() doesn’t fit: a coded absent argument still counts in the argument list. To the compiler, m2() fits. However, since the 2 arguments are required, calling it with a coded absent argument is illegal and results in an undefined behavior at runtime.

3 Likes

Thanks @PierU for the explanation. Yes, I think I understand the rationale for this behavior. Actually, I think the code did not crash by pure chance, because internally a character(len=0) may be treated like an unassociated pointer. In fact, ifort crashes if I try the same with an integer instead of a character argument.

@FedericoPerini ,

Your question here builds off of the earlier one you asked recently. Just as in that other thread, the onus lies on the program author to conform, a processor is not required to detect and report the issue. The program response falls under the processor-dependent category which can include a nasty run-time exception or worse.

For the sake of other readers who may not be as familiar with Fortran when it comes to generic resolution with the so-called overloaded methods, OPTIONAL attribute, etc., here is a somewhat stripped down scenario of what you post:

module m
   generic :: sub => sub1, sub2
contains
   subroutine sub1( n )
      integer, intent(in) :: n
      print *, "sub1: n = ", n
   end subroutine 
   subroutine sub2( n, s )
      integer, intent(in) :: n
      character(len=*), intent(in) :: s
      print *, "sub2: n = ", n, "; s = ", s 
   end subroutine 
end module
module n
   use m, only : sub
contains
   subroutine subn( n, s )
      integer, intent(in) :: n
      character(len=*), intent(in), optional :: s
      call sub( n, s )  !<-- this will resolve to sub2
   end subroutine 
end module
   use n
   call subn( 42 )
end 

and as commented on line 20, the generic resolution rules in the standard will point the compiler to resolve to sub2 when you may seek sub1.

C:\temp>ifort /standard-semantics /free 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.

Microsoft (R) Incremental Linker Version 14.36.32537.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 sub2: n =  42 ; s =

The easiest workaround is as presented by @vmagnin upthread:

   ..
   subroutine subn( n, s )
      integer, intent(in) :: n
      character(len=*), intent(in), optional :: s
      if ( present(s) ) then
         call sub( n, s )
      else
         call sub( n )
      end if
   end subroutine
   .. 
3 Likes

Here is a way to think about generic resolution. Generic resolution in fortran works by identifying which of the several possible specific routines matches the calling sequence. It does not work by selecting one of several specific routines, all of which match, but some match “better” than others.

In your example, you would have two specific routines that match the single-argument call, one with a single argument and the other with a nonpresent optional argument. You are thinking that the single-argument routine is a “better” match, and it should be called, but generic resolution doesn’t work that way.

As you have already determined, you can remove the ambiguity by making both arguments of the two-argument version nonoptional. The compiler can then associate all single-argument calls with the single-argument specific routine, and all two-argument calls with the two-argument specific routine.

However, if you do this, you cannot invoke either the single-argument routine or the two-argument routine with a two argument call with a nonpresent optional actual argument. This is the case where you would need the “bloat” of testing whether or not the optional actual argument is present and invoking the appropriate call with the correct number of arguments. This feature of the language is designed so that you normally don’t have to do that, but if you try hard enough, you can indeed shoot yourself in the foot.

2 Likes