Skip to content

Facilitate default values of optional arguments #62

Closed
@nshaffer

Description

@nshaffer
Contributor

An annoyance with optional arguments is handling their default values. This usually looks something like:

function mylog(x, base) result(y)
    real, intent(in) :: x
    real, intent(in), optional :: base
    real :: y

    real :: base_
    
    base_ = 10.0
    if (present(base)) base_ = base
    
    y = log(x)/log(base_)
end function mylog

I propose to introduce a module that exports a generic function default which will in many cases allow for the elimination of the local copy of the optional argument. The above example could be rewritten

function mylog(x, base) result(y)
    use default_values, only: default
    real, intent(in) :: x
    real, intent(in), optional :: base
    real :: y
    
    y = log(x)/log(default(10.0, base))
end function mylog

This is a convenience, but it's incredibly handy. The module is very simple to write. See, e.g., this CLF post by Beliavsky, where I first learned of this trick. I put this in all my serious codes, as it removes a lot of the tedium and error potential with optional arguments.

I can easily spin up a illustrative PR that can be fleshed out once we've decided how we're going to automate generic interfaces.

Activity

certik

certik commented on Jan 2, 2020

@certik
Member
marshallward

marshallward commented on Jan 2, 2020

@marshallward

I do like this, but the more frustrating issue for me is that I often need to define two variables in the same scope with identical purpose, in this case base_ and base.

This function would let you replace base_ with default(base, 10.0), and is very effective if base_ only appears once or twice. But if you have to do this many times then it may not actually be what you want.

I feel constrained because the optional input is the one which becomes part of the API, and therefore should be the most readable. But it is often the internal variable which will appear the most throughout the function, which can make the function less readable.

But this is still an improvement for lots of cases. I agree with @certik that default is too general of a name to use here. (I should read more carefully...)

nshaffer

nshaffer commented on Jan 2, 2020

@nshaffer
ContributorAuthor

The semantics of optional arguments make the "natural" order a little tricky. If we want the fallback value to come second, callers will have to explicitly make it a keyword arg. That is, consider the two implementations:

default_first(to, x) result(y)
    ! Return first arg if second is not present
    !     default(1, 2) == 2
    !     default(1) == 1 ("x" not present, so we get the fallback value)
    integer, intent(in) :: to ! the fallback value
    integer, intent(in), optional :: x
    integer :: y

    if (present(x)) then
        y = x
    else
        y = to
    end if
end function default_first

versus what is arguably the more natural ordering

default_second(x, to) result(y)
    ! Return second arg if first is not present
    !     default(1, 2) == 1
    !     default(2) (ERROR b/c nothing gets bound to "to", which is non-optional)
    !     default(to=2) == 2 (no error b/c we've explicitly set "to")
    integer, intent(in) :: to ! the fallback value
    integer, intent(in), optional :: x
    integer :: y

    if (present(x)) then
        y = x
    else
        y = to
    end if
end function default_second

So in practice, one would have to write expressions like default(x, to=6.0) in order to make the more natural ordering work. Omitting "to=" would be a compile-time error. It's a few more characters to do it this way, but it does read nicely. If we don't mind imposing mandatory keyword args on users, I'm happy doing it this way.

jvdp1

jvdp1 commented on Jan 2, 2020

@jvdp1
Member

This is a nice option for simple cases.
However, I am afraid a local variable would be needed for many cases if the optional variable is used many times, or if there are many optional variables. These would lead to several

subroutine sub1(var, var1, var2, var3)
    ...., intent(in), optional::var1
    ...., intent(in), optional::var2
    ...., intent(in), optional::var3
    .... default(var1, 0.10) ....
    ... default(var2, .true.) ....
    ...default(var3, 100)....
    ...

For such cases, I would clearly prefer to use local variables. But it would be a nice addition in stdlib.

I can easily spin up a illustrative PR that can be fleshed out once we've decided how we're going to automate generic interfaces.

It seems that a solution for #35 must be found to go forward in many issues.

milancurcic

milancurcic commented on Jan 2, 2020

@milancurcic
Member

I like it! Convenience with no apparent downsides. +1 for name default. I can't think of others.

marshallward

marshallward commented on Jan 2, 2020

@marshallward

Sorry, I misread the very post that I cited in my comment. But I don't think default should be used here. There are lots of uses for that name outside of variable defaults.

certik

certik commented on Jan 2, 2020

@certik
Member

The ultimate fix would be to change the language: j3-fortran/fortran_proposals#22

In the meantime, I think this is a great idea for stdlib to at least make it a little bit easier.

@marshallward regarding a name: yes, I also think it's too general, but from the alternatives that I listed, I like it the most. Do you have some other ideas for a name? Maybe default_arg? Or just optarg.

@nshaffer right. Couldn't using overloaded subroutines somehow make this work?

certik

certik commented on Jan 2, 2020

@certik
Member

@nshaffer this compiles for me with gfortran, but I don't know if it actually works:

module stdlib_default
implicit none

interface default_second
    module procedure default_second_1
    module procedure default_second_2
end interface

contains

    function default_first(to, x) result(y)
    ! Return first arg if second is not present
    !     default(1, 2) == 2
    !     default(1) == 1 ("x" not present, so we get the fallback value)
    real, intent(in) :: to ! the fallback value
    real, intent(in), optional :: x
    real :: y

    if (present(x)) then
        y = x
    else
        y = to
    end if
    end function default_first

    function default_second_1(to) result(y)
    real, intent(in) :: to
    real :: y
    y = to
    end function

    function default_second_2(x, to) result(y)
    real, intent(in) :: x
    real, intent(in) :: to
    real :: y
    y = x
    end function

end module

program A
use stdlib_default, only: default_first, default_second
implicit none

contains

    function mylog(x, base) result(y)
    real, intent(in) :: x
    real, intent(in), optional :: base
    real :: y

    !y = log(x)/log(default_first(10.0, base))
    y = log(x)/log(default_second(base, 10.0))
    end function mylog

end

Edit: it probably does not work, because it will always call the default_second_2 version, even if base is not present.

Edit 2: but this compiles:

program A
implicit none

print *, mylog(16.)
print *, mylog(16., 2.)

contains

    function default_second(x, to) result(y)
    real, intent(in), optional :: x
    real, intent(in) :: to
    real :: y
    if (present(x)) then
        y = x
    else
        y = to
    end if
    end function

    function mylog(x, base) result(y)
    real, intent(in) :: x
    real, intent(in), optional :: base
    real :: y
    y = log(x)/log(default_second(base, 10.0))
    end function mylog

end

and prints:

   1.20411992    
   4.00000000    

I think it works!

marshallward

marshallward commented on Jan 2, 2020

@marshallward

@marshallward regarding a name: yes, I also think it's too general, but from the alternatives that I listed, I like it the most. Do you have some other ideas for a name?

Something that refers to the optional keyword seems like the correct thing here. opt_default captures the behavior, but it is a bit long.

I'm leaning towards optval or something similar but it's not as elegant as default. (optget also feels good to me, but it's perhaps a bit too close to C's getopt.)

I generally feel uncertain about grabbing common keywords like this, which may be prevalent in existing codes or could become part of the language standard in the future.

I'll think on it and post if anything else comes to mind. I guess for now this is just a point of caution :).

certik

certik commented on Jan 2, 2020

@certik
Member

I like optval.

nshaffer

nshaffer commented on Jan 3, 2020

@nshaffer
ContributorAuthor

Edit 2: but this compiles:

program A
implicit none

print *, mylog(16.)
print *, mylog(16., 2.)

contains

    function default_second(x, to) result(y)
    real, intent(in), optional :: x
    real, intent(in) :: to
    real :: y
    if (present(x)) then
        y = x
    else
        y = to
    end if
    end function

    function mylog(x, base) result(y)
    real, intent(in) :: x
    real, intent(in), optional :: base
    real :: y
    y = log(x)/log(default_second(base, 10.0))
    end function mylog

end

and prints:

   1.20411992    
   4.00000000    

I think it works!

Oh, great! Yes, I see. In practice you will never actually call default_second with only one argument, so the dummy arguments will never get bound incorrectly. I will implement it this way.

As for naming, I have a strong preference for default because it matches so well with naming the fallback argument to. I think this outweighs the (negligible) downside of clashing with someone else's variable name or whatever. I think we have to demand that users take some minimal responsibility for being aware of the names they're importing with modules. I'm not going to die on this hill, though. We can hash it out in the PR discussion. Will try to submit today.

marshallward

marshallward commented on Jan 3, 2020

@marshallward

I'm less concerned about the ability of users to adapt than I am about preserving their right to use commonplace words for their own work. (Users can always rename external functions, but I don't think that's something we ought to encourage.) I also think it's perhaps too general to use default for the specific issue of function argument defaults. And as mentioned before, I could also see this becoming a keyword in a future iteration of the language standard.

But I agree that default feels more elegant. And if no one else is concerned about the objections that I've raised then I won't raise them again.

certik

certik commented on Jan 3, 2020

@certik
Member

@milancurcic, @jvdp1, @zbeekman, @ivan-pi, @jacobwilliams what would be your preference for naming this? The top two contenders are default and probably optval.

jvdp1

jvdp1 commented on Jan 3, 2020

@jvdp1
Member

what would be your preference for naming this? The top two contenders are default and probably optval.

Among the two options, I prefer optval. Users can always rename it to default if they prefer this name.

Following @certik 's comment, opt_default has my highest preference, because it is more explicit than optval. But it is a bit long.

19 remaining items

Loading
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment

Metadata

Metadata

Assignees

No one assigned

    Labels

    topic: utilitiescontainers, strings, files, OS/environment integration, unit testing, assertions, logging, ...

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

      Development

      No branches or pull requests

        Participants

        @certik@zbeekman@marshallward@fiolj@milancurcic

        Issue actions

          Facilitate default values of optional arguments · Issue #62 · fortran-lang/stdlib