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.
You described the situation rather well. There is no other way I am aware off 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.
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).
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.
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 )
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.
来源:https://stackoverflow.com/questions/37723973/fortran-2003-2008-elegant-default-arguments