Giter Site home page Giter Site logo

Comments (29)

jvdp1 avatar jvdp1 commented on May 25, 2024 3

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.

from stdlib.

certik avatar certik commented on May 25, 2024 3

It's in experimental, so we can rename it if we want to.

If we all sort all available names based on how we like them, I think there is a "voting system" that allows to select candidates that "most people are ok with". If I am just judging from the above, it seems nobody is very strongly against optval. It seems some people like default while others are opposed. The same with opt_default. I prefer optval over opt_default also.

from stdlib.

ivan-pi avatar ivan-pi commented on May 25, 2024 2

Of the options above I find optval the most meaningful. The name default is too general and does not confer well the meaning of the function - to process an optional value.

from stdlib.

certik avatar certik commented on May 25, 2024 2

Note: if j3-fortran/fortran_proposals#22 gets accepted, then this:

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

becomes just

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

Everybody: if you like the language proposal, make sure you add +1 to it.

from stdlib.

marshallward avatar marshallward commented on May 25, 2024 1

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.

from stdlib.

certik avatar certik commented on May 25, 2024 1

@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!

from stdlib.

nshaffer avatar nshaffer commented on May 25, 2024 1

The name should be as short as possible without being cryptic. This is because in practice, the function will often be called as part of a larger expression, e.g., the mylog examples upthread. The longer the function name, the more it obscures the expression it appears in.

from stdlib.

milancurcic avatar milancurcic commented on May 25, 2024 1

defval is problematic because def may mean "define" for many people, like me. optval is my favorite of any short names.

from stdlib.

certik avatar certik commented on May 25, 2024

from stdlib.

marshallward avatar marshallward commented on May 25, 2024

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...)

from stdlib.

nshaffer avatar nshaffer commented on May 25, 2024

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.

from stdlib.

jvdp1 avatar jvdp1 commented on May 25, 2024

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.

from stdlib.

milancurcic avatar milancurcic commented on May 25, 2024

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

from stdlib.

certik avatar certik commented on May 25, 2024

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?

from stdlib.

marshallward avatar marshallward commented on May 25, 2024

@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 :).

from stdlib.

certik avatar certik commented on May 25, 2024

I like optval.

from stdlib.

nshaffer avatar nshaffer commented on May 25, 2024

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.

from stdlib.

marshallward avatar marshallward commented on May 25, 2024

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.

from stdlib.

certik avatar certik commented on May 25, 2024

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

from stdlib.

certik avatar certik commented on May 25, 2024

(@jvdp1 the rest of the options are listed at #62 (comment), if you like any of them better.)

from stdlib.

zbeekman avatar zbeekman commented on May 25, 2024

I too like opt_default better but am sufficiently happy with optval.

from stdlib.

marshallward avatar marshallward commented on May 25, 2024

Hopefully I won't be shot for saying this, but I think that I also prefer opt_default.

from stdlib.

milancurcic avatar milancurcic commented on May 25, 2024

Sorry I missed this. I like default best, optval second, and opt_default last.

from stdlib.

certik avatar certik commented on May 25, 2024

Another idea is defval. Or shorter versions: dval, oval, darg, oarg, or even shorter: dv, ov, da, oa.

from stdlib.

certik avatar certik commented on May 25, 2024

I agree, just few days ago I was thinking the same thing, that defval feels like define value.

from stdlib.

fiolj avatar fiolj commented on May 25, 2024

I started to look into the source code. Would be advisable to put into a single preprocessed format?
It is straigthforward, and a simple rewriting seems to work well. Additionally we already can add complex numbers (I don't know enough to add an implementation for ucs chars)

from stdlib.

nshaffer avatar nshaffer commented on May 25, 2024

@fiolj I submitted the PR before we'd come to any consensus about preprocessing. If you want to refactor it to use fypp templating, go for it. Same goes for adding complex cases (just be sure to add corresponding tests). I wouldn't bother with UCS yet.

from stdlib.

jvdp1 avatar jvdp1 commented on May 25, 2024

@fiolj I think it is a good idea to use a preprocessed format for optval. I suggest that you submit a PR.

Regarding complex numbers, I would suggest to add them to all modules (i.e. also in stdlib_experimental_stats and in stdlib_experimenal_io). S the whole library will support complex numbers. Would it be possible? I can help if needed. If a PR is open about complex, I think it should be in a different PR than the one about optval.

from stdlib.

milancurcic avatar milancurcic commented on May 25, 2024

Implemented in stdlib_optval.

from stdlib.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.