19

In fortran, we can define default arguments. However, if an optional argument is not present, it can also not be set. When using arguments as keyword arguments with default values, this leads to awkward constructs like

PROGRAM PDEFAULT 

  CALL SUB
  CALL SUB(3)

CONTAINS 
  SUBROUTINE SUB(VAL)
    INTEGER, OPTIONAL :: VAL
    INTEGER :: AVAL ! short for "actual val"

    IF(PRESENT(VAL)) THEN
       AVAL = VAL
    ELSE 
       AVAL = -1   ! default value 
    END IF

    WRITE(*,'("AVAL is ", I0)') AVAL
  END SUBROUTINE SUB

END PROGRAM PDEFAULT

Personally, I often ran into the problem of accidentially typing VAL instead of AVAL, i.e. the disconnect between the variable name in the interface, and the initialized value used in the code can introduce runtime bugs – let alone that this manner of initialization is rather verbose.

Is there some more elegant way of using optional arguments with a default value?

Example It would feel more natural to write something like

IF(NOT(PRESENT(VAL))) VAL = -1 

because it avoids the VAL vs AVAL confusion. But it isn't valid, presumably because Fortran passes arguments by reference and thus if VAL is not present in the CALL statement, no memory is associated with VAL and VAL = -1 would cause a segfault.

kdb
  • 4,098
  • 26
  • 49
  • 1
    Curious detail: Neither GFortran nor Intel Fortran provide any kind of compilation time warning, when using an optional argument without protecting it by `present()`. Both will simply fail with a segfault at runtime. – kdb Oct 05 '20 at 07:40

7 Answers7

15

You described the situation rather well. There is no other way I am aware of and that is standard conforming. The pattern with a local variable named similarly is what people often use. The other option is to just put if (present()) else everywhere, but that is awkward.

The point is that they are optional arguments, not default arguments. Fortran doesn't have default arguments. The may have been better, but that is not what the committee members have chosen in the 80s when preparing Fortran 90.

8

While also looking into this, I found out that you can in fact do something like the proposed example using the OPTIONAL and VALUE attributes (at least with gfortran, not sure how different compilers might handle it). E.g.:

PROGRAM PDEFAULT 

  CALL SUB
  CALL SUB(3)

CONTAINS 
  SUBROUTINE SUB(VAL)
    INTEGER, OPTIONAL,VALUE :: VAL

    IF(.NOT. PRESENT(VAL)) VAL = -1 ! default value

    WRITE(*,'("VAL is ", I0)') VAL
  END SUBROUTINE SUB

END PROGRAM PDEFAULT

This was implemented in version 4.9 of gfortran. And here's the relevant explanation in the documentation for argument passing conventions:

For OPTIONAL dummy arguments, an absent argument is denoted by a NULL pointer, except for scalar dummy arguments of type INTEGER, LOGICAL, REAL and COMPLEX which have the VALUE attribute. For those, a hidden Boolean argument (logical(kind=C_bool),value) is used to indicate whether the argument is present.

I also found this discussion interesting as historical context.

Maybe somebody more knowledgeable might have comments on whether doing this is a bad idea (aside from being compiler dependent), but at least at face value it seems like a nice workaround.

Note that this behavior is not part of the Fortran standard, and depends on the implementation of a given compiler. For example, the example code segfaults when using ifort (version 16.0.2).

Gabe
  • 649
  • 5
  • 6
  • 3
    I _believe_ this is not valid Fortran (which isn't to say it won't do what one wants in practice with some compilers/runtimes). If `val` is not present then referencing/defining it is not allowed. This is the `if` statement. The restrictions given by the standard on the use of non-present dummy arguments make no mention of the `value` attribute. The "definable anonymous copy" applies only in the case of a present dummy argument with the `value` attribute. [Hopefully someone can show I'm wrong, though.] – francescalus Oct 19 '16 at 09:53
  • Hm, I think you are right. In the morning I was worried that for a short time but than the bugzilla thread convinced me. However nowhere on that page they suggest that referencing the argument is allowed if it is not present. – Vladimir F Героям слава Oct 19 '16 at 10:42
  • I agree that the behavior it's not required nor part of the standard. My understanding from the bugzilla discussion is that the standard allows for both `OPTIONAL` and `VALUE` attributes, but there are no guidelines to how it should be implemented. Since in gfortran arguments with the `VALUE` attribute are passed by value, I gather that when optional arguments are missing the variable is still allocated but simply not initialized (and thus why they needed a hidden argument). – Gabe Oct 19 '16 at 19:13
  • 2
    Also, I did test the code with ifort and it segfaults. I'll clarify in the answer that it's not part of the standard and is implementation dependent. – Gabe Oct 19 '16 at 19:15
  • 4
    The part of this that is not standard is assigning to VAL when it is not present. In my own codes I have used the technique in the original post, I will comment that "default values for omitted optional arguments" is a feature under consideration for the next revision of the standard (currently referred to as F202X). – Steve Lionel Jun 17 '18 at 18:09
3

The Fortran standard lib (https://github.com/fortran-lang/stdlib) provides a function called optval that is used in stdlib_logger for example:

subroutine add_log_file( self, filename, unit, action, position, status, stat )
    ...
    character(*), intent(in), optional :: action
    ...
    character(16)  :: aaction
    ...
    aaction = optval(action, 'write')
    ...
end subroutine add_log_file

So their way of representing the "actual" value is a prepended a.

IMHO, I like the option with an appended _, since the optional values are visually marked as such in the call signature.

MuellerSeb
  • 796
  • 6
  • 11
  • Nice. It is good to mention that one can write such a function oneself, it just contains the already discussed if conditional, no new magic. – Vladimir F Героям слава Oct 02 '20 at 08:05
  • 1
    I looked at the source code of this library. My takeaway is, that is mostly is a good demonstration of why Fortran needs type-generic ("template") programming... – kdb Oct 02 '20 at 08:58
1

Whilst I certainly wouldn't advocate doing so in most situations (and indeed you can't in some situations), one may sometimes use an interface to provide a single entry point for multiple routines with different required arguments rather than using an optional argument. For example your code could be written like

MODULE subs
  implicit none
  public :: sub

  interface sub
    module procedure sub_default
    module procedure sub_arg
  end interface
 contains
  SUBROUTINE SUB_arg(VAL)
    INTEGER :: VAL
    WRITE(*,'("VAL is ", I0)') VAL
  END SUBROUTINE SUB_arg

  SUBROUTINE SUB_default
     integer, parameter :: default = 3
     CALL SUB_arg(default)
  END SUBROUTINE SUB_default
END MODULE SUBS

PROGRAM test
   use subs, only: sub
   call sub
   call sub(5)
END PROGRAM TEST

Again, I don't recommend this approach, but I thought I should include it anyway as an alternative way of providing something that looks like a default.

d_1999
  • 854
  • 6
  • 16
  • Why would you not recommend this? This is a reasonable way to go, especially when there are many optional arguments that interact with each other. Or when the procedure is already generic, so this solution would add little extra boiler plate. – knia May 20 '22 at 10:03
1

Another possibility is to use an associate block which associates the local variable name with a variable of the same name as the optional argument eg.

SUBROUTINE SUB(VAL)
INTEGER, OPTIONAL :: VAL
INTEGER :: AVAL ! short for "actual val"

IF (PRESENT(VAL)) THEN
    AVAL = VAL
ELSE 
    AVAL = -1   ! default value 
END IF

ASSOCIATE (VAL => AVAL)
    WRITE(*,'("VAL is ", I0)') VAL
END ASSOCIATE

END SUBROUTINE SUB

Not ideal but allows you to use the same variable name for the argument and in the body of the routine. I shudder to think of the amount of untidy code I've written coping with the lack of default values for optional arguments - roll on F202X.

nocaster60
  • 21
  • 3
  • This certainly has some appealing features, but perhaps you could expand in the answer on the limitations of this approach in more general cases? – francescalus Jul 05 '19 at 13:52
  • The limitations are those of using the associate statement - restrictions on allocatable and pointer variables. Also, if the argument is INTENT(OUT) (or no expressed intent) there will need to be a corresponding IF (PRESENT(VAL)) VAL = AVAL after the associate bock. It's all a bit messy though. Default values for optional arguments would have been so much better. – nocaster60 Jul 05 '19 at 18:43
  • Would you be willing to [edit] those points into your answer? – francescalus Jul 06 '19 at 01:34
0

I hope Fortran to support a popular syntax like

subroutine mysub( x, val = -1 )
integer, optional :: val

or in a more Fortran style

subroutine mysub( x, val )
integer, optional :: val = -1     !! not SAVE attribute intended

but this seems not supported (as of 2016). So some workaround needs to be done by the users' side...

In my case, after trial-and-errors, I settled down to attaching one underscore to the optional dummy argument, so doing something like (*)

subroutine mysub( x, val_)
integer, optional :: val_
integer val

Other people seem to like the opposite pattern (i.e., dummy variable => sep, local variable => sep_, see split() in StringiFor, for example). As seen in this line, the shortest way to set the default value is

val = -1 ; if (present(val_)) val = val_

But because even this line is somewhat verbose, I usually define a macro like

#define optval(x,opt,val) x = val; if (present(opt)) x = opt

in a common header file and use it as

subroutine mysub( x, val_, eps_ )
    integer :: x
    integer, optional :: val_
    real, optional :: eps_
    integer  val
    real     eps
    optval( val, val_, -1 )
    optval( eps, eps_, 1.0e-5 )    

    print *, "x=", x, "val=", val, "eps=", eps
endsubroutine

...
call mysub( 100 )
call mysub( 100, val_= 3 )
call mysub( 100, val_= 3, eps_= 1.0e-8 )

However, I believe this is still far from elegant and no more than an effort to make it slightly less error-prone (by using the desired variable name in the body of the subroutine).


Another workaround for a very "big" subroutine might be to pass a derived type that contains all the remaining keyword arguments. For example,

#define getkey(T) type(T), optional :: key_; type(T) key; if (present(key_)) key = key_

module mymod
    implicit none

    type mysub_k
        integer  :: val = -1
        real     :: eps = 1.0e-3
    endtype
contains

subroutine mysub( x, seed_, key_ )
    integer :: x
    integer, optional :: seed_
    integer :: seed
    getkey(mysub_k)   !! for all the remaining keyword arguments
    optval( seed, seed_, 100 )    

    print *, x, seed, key% val, key% eps
endsubroutine

endmodule

program main
    use mymod, key => mysub_k

    call mysub( 10 )
    call mysub( 20, key_= key( val = 3 ) )
    call mysub( 30, seed_=200, key_= key( eps = 1.0e-8 ) )  ! ugly...
endprogram

This might be a bit close to what is done by some dynamic languages under the hood, but this is again far from elegant in the above form...


(*) I know it is often considered ugly to use CPP macros, but IMO it depends on how they are used; if they are restricted to limited extensions of Fortran syntax, I feel it is reasonable to use (because there is no metaprogramming facility in Fortran); on the other hand, defining program-dependent constants or branches should probably be avoided. Also, I guess it would be more powerful to use Python etc to make more flexible preprocessors (e.g., PreForM.py and fypp and so on), e.g., to allow a syntax like subroutine sub( val = -1 )

roygvib
  • 7,218
  • 2
  • 19
  • 36
  • The first solution is what I posted in the original question -- changing the naming convention doesn't really make it a new pattern. The second solution is sadly invalid code, once there is more than one optional argument, as fortran doesn't allow mixing declaration and execution code – while for a single optional argument the use of a macro probably isn't enough gain to justify the obscurity. – kdb Jun 14 '16 at 15:33
  • Hi, because the current Fortran standards do not allow any real "solution" (as suggested by Vladimir below), there is no other way but to use a local variable with similar name, and I thought you were looking for some systematic (less error-prone) workarounds. RE the second point, the above code is valid (you can try it) and you can also add other usual optional variables in front of key_ as well. The point is that setkey() should come after all other declarations, but this is natural because this type of keyword arguments come after all optional arguments usually. – roygvib Jun 14 '16 at 15:44
  • Also, my purpose is simply to present my practice, never to advocate its usage. More importantly, my intention is to highlight how the current Fortran syntax is limited in some parts and enforce the user to write a rather verbose/lengthy code. – roygvib Jun 14 '16 at 15:49
  • [I added more codes for mixing optional and "keyword" arguments, but after all, these are rather ugly (I won't use the second one, although I often use the first optval() one).] – roygvib Jun 14 '16 at 16:30
  • 2
    Adding something that fills this purpose is one of the items under consideration for "F202X". No syntax has been proposed as of yet. – Steve Lionel Jun 17 '18 at 18:10
0

Here is an elegant (i.e., short, clear, standard-conforming) solution:

  subroutine sub(val)
    integer, optional :: val

    write(*,'("aval is ", i0)') val_or_default(val, default=-1)
  end subroutine

  integer function val_or_default(val, default)
    integer, optional, intent(in) :: val
    integer, intent(in) :: default

    if (present(val)) then  ! False if `val` is is not present in `sub`.
      val_or_default = val
    else
      val_or_default = default
    endif
  end function

This uses the fact that optional arguments can still be passed to a function, even when they are not present, so long as the corresponding dummy argument is also optional.

There is at least one generic implementation of val_or_default on GitHub for all intrinsic data types. (They call it optval.)

knia
  • 463
  • 6
  • 16