stdlib icon indicating copy to clipboard operation
stdlib copied to clipboard

Increment

Open Beliavsky opened this issue 3 years ago • 13 comments

Many other languages allow i += 1 instead of i = i + 1. When you are incrementing a variable with a long name, or an array section, or a component of a derived type, it is possible to write i = j + 1 by mistake, where it was intended that i be incremented. Therefore I suggest that stdlib have an elemental increment subroutine that works with real and integer types, so that

call increment(i,inc)

has the same meaning as

i = i + inc

I got this idea from Nim, where you can write inc(i,1) instead of i = i + 1

Beliavsky avatar Sep 27 '21 16:09 Beliavsky

I like it. Some ideas:

  • Make the name even shorter, because this subroutine would compete with the already short i = i + 1 (yes, trivial and not the most fair example). Perhaps incr or inc like in Nim. I suggest incr because inc sounds to me like "include".
  • Make the second argument optional, so that incr(i) increments by 1 by default.
  • Have a decrement analog called decr.

What module would this belong to?

milancurcic avatar Sep 27 '21 16:09 milancurcic

  • Make the second argument optional, so that incr(i) increments by 1 by default.

In practice I would prefer to implement this as two functions to avoid an if for the optional argument check (even if a smart compiler might be able to eliminate this):

interface incr
  module procedure incr_by_one
  module procedure incr_by_many
end interface

elemental subroutine incr_by_one(i)
  integer, intent(inout) :: i
  i = i + 1
end subroutine
elemental subroutine incr_by_many(i,inc)
  integer, intent(inout) :: i
  integer, intent(in) :: inc ! maybe other name like `step` 
  i = i + inc
end subroutine

ivan-pi avatar Sep 27 '21 17:09 ivan-pi

In practice I would prefer to implement this as two functions to avoid an if for the optional argument check (even if a smart compiler might be able to eliminate this):

I wonder if this is necessary... If speed is crucial and the compiler fails to optimise this if, you're probably better off without the function call.

At the end of the day it will not matter if we implement this with an interface or with an optional argument. But IMHO the code is more clean by using optval... and stdlib should be clean to be an good example for other developers. However I would run a quick test first.

Carltoffel avatar Sep 28 '21 19:09 Carltoffel

There is a difference in the API between interfaces and a procedure with an optional argument. For example

integer :: val
integer, allocatable :: step
val = 1
call incr(val, step)

would be perfectly valid with the optional argument strategy, while it produces an uninitialized memory access with interfaces. A similar situation occurs if user code passes an optional argument to the second argument. The workaround for interface based implementation for those two cases would be

call incr(val, optval(step, 1))

This are arguably corner-cases seldom encountered for a simple function like incr. Still, the optional argument implementation seems more predictable in my opinion.

awvwgk avatar Sep 28 '21 19:09 awvwgk

What module would this belong to?

It could go into the same submodule as gcd e.g. stdlib_math_basic or if there are more routines like incr and decr in a submodule specifically for "helper routines" e.g. stdlib_math_helper.

Carltoffel avatar Sep 28 '21 20:09 Carltoffel

I am aware of the thread which showed little to no performance penalty of optval if the right compiler flags were used. Still, for the reasons just mentioned by @awvwgk (optional compiler warnings) I lean slightly towards the interface version. In my own codes I generally try to use interface resolution instead of optional arguments, even if this comes at a cost of code duplication. Maybe I am just paranoid, and the compiler can check for presence of arguments at the same stage as the interface resolution happens.

A discussion of interface resolution vs optional arguments would be a good topic for the Fortran Best Practices minibook.

ivan-pi avatar Sep 28 '21 20:09 ivan-pi

I am aware of the thread which showed little to no performance penalty of optval if the right compiler flags were used. Still, for the reasons just mentioned by @awvwgk (optional compiler warnings) I lean slightly towards the interface version.

This thread showed little or no performance penalty if link-time optimization is used (gfortran -flto or ifort -ipo). But in practice those flags cannot always be applied.

From recent experience it can raise compiler bugs -- for example here. Also, I seem to recall once finding that I couldn't use lto when linking to another library (netcdf) that had been compiled without lto.

I'm not opposed to these syntatic-sugar type routines, but agree care is required to manage the trade-offs, including when promoting one or other coding-style.

gareth-nx avatar Oct 03 '21 04:10 gareth-nx

Maybe we can follow the style of the intrinsic functions :). For example, try the following codes.

program main
implicit none

call test_optional(1)
call test_optional(2)
call test_optional()

contains

subroutine test_optional(a)
    integer, intent(in), optional :: a
    integer :: b(3,5)
    print*, size(b,dim=a)
end subroutine

end program main
  • gfortran 11.2
    • Debug(-g): 3 5 15
    • Release(-O2): same as Debug
  • ifort 2021.3.0
    • same as gfortran 11.2
  • ifx 2021.3.0
    • Debug(-g): 3 5 (forrtl: severe (174): SIGSEGV, segmentation fault occurred)
    • Release(-O2): same as gfortran 11.2
program main
implicit none

call test_allocatable()

contains

subroutine test_allocatable()
    integer, allocatable  :: a
    integer :: b(3,5)
    print*, size(b,dim=a)
end subroutine

end program main
  • gfortran 11.2
    • Debug(-g): Program received signal SIGSEGV
    • Relase(-O2): Program received signal SIGSEGV
  • ifort 2021.3.0
    • same as gfortran 11.2
  • ifx 2021.3.0
    • Debug(-g): Program received signal SIGSEGV
    • Release(-O2): Program returned: 0; Program stdout: 0

If we ignore the results of ifx (beta), size is as expected for optional argument, but fails for allocatable variable. I don't know whether the Fortran standard gives description of size(or other intrinsic functions) for optional arguments or not. :)

qin-tain avatar Oct 06 '21 14:10 qin-tain

I'm having difficultly seeing the benefit of using call incr(i) over i = i + 1. Additionally adding more functions with such short names I feel might compound the issues I'm already experiencing with naming over index, min, max, etc.

To me this situation might be better solved by pushing for the addition of += and the like to the Fortran Standard

trippalamb avatar Apr 07 '22 18:04 trippalamb

You might be right about the +=. And for i = i+1 there is no real benefit. But imagine you want to increment e.g. adjoint%radicals(domain%grid(i):domain%grid(i+1)).

Carltoffel avatar Apr 07 '22 20:04 Carltoffel

Even in that case there isn't a benefit as you still have to make the subroutine call to call incr() on another line.

trippalamb avatar Apr 08 '22 22:04 trippalamb

I want to increment the field, not i.

Carltoffel avatar Apr 09 '22 03:04 Carltoffel

I can see why in that case there would be benefit to an increment subroutine if there were no other solution to simplifying the surrounding logic, but I suspect there may be better alternatives to avoiding that situation to begin with. If it is truly only the one time (making a reworking of the surrounding logic a waste of time),

adjoint%radicals(domain%grid(i):domain%grid(i+1)) = adjoint%radicals(domain%grid(i):domain%grid(i+1)) +1

Is not any more difficult to read that you dealing with something that nested to begin with. In such (hopefully very few) cases that it cannot be avoided and the need to make increment logic exhaustively clear, an increment subroutine takes very little time to write and has very little risk of being written incorrectly.

I don't want to lose sight of my main point though. I am putting forward that I think there is more harm than good in adding an increment subroutine especially with one that will take up another short and potentially useful (depending on the field and context) variable name. Especially when it is only useful in what I believe would be edge cases in well constructed code logic. And additionally it doesn't fully solve what I would see as the whole problem.

While as described it could solve decrementing, I think using incr(i, -1) is counter intuitive, and using decr(i) would just compound the issue of taking up more short variable names. That is without taking into account that the similar solutions of *=, and /= (and potentially **= and //= [concatenation equals, not root equals]) would be absent which further makes the choice unintuitive.

trippalamb avatar Apr 10 '22 14:04 trippalamb