Result attribute

This post seeks confirmation if I understood the result attribute well enough.

Milan Curci’s Modern Fortran introduces the result attribute by comparison of

! the following is listing 3.5:
integer function sum(a, b)
  integer, intent(in) :: a,b
  sum = a + b
end function sum  

with

! the following is listing 3.6:
integer function sum(a, b) result(res)
  integer, intent(in) :: a,b
  res = a + b
end function sum  

including the statement

The advantage to using the result attribute may not be obvious from this example [listing 3.6 vs. listing 3.5, ndlr] because the name of the function (sum) is already quite short, …

In context with earlier listings in chapter 03 Reusable code with functions and subroutines, I would paraphrase the function of listing 3.6 as:

The inclusion of either definition 3.5, or 3.6 causes the main program to use sum as defined by this (local / user defined) function; because for the main program, the local definition in its very file file is of higher hierarchy than Fortran’s intrinsic sum function. However – contrasting to 3.5 – with the later listing 3.6, within the user defined function, the sum is computed as res, i.e. now equally independent from Fortran’s intrinsic sum function, too.

My question hence: is paraphrasing listing 3.6 this way an acceptable one?

1 Like

I had to try this to find out and it seems that the answer is no–even inside the function definition from listing 3.6, invoking sum would mean invoking the external function recursively, and not the intrinsic one.

It’s unfortunate, and I regret it, that I shadowed the intrinsic sum for this minimal example. It’s possible that it created more confusion than clarity.

1 Like

@nbehrnd ,

FYI, see this.

1 Like

If the question is whether the result() clause allows one to use the intrinsic sum() within the user function sum(), then the answer is no. Not even if you declare intrinsic :: sum within the function, you still cannot do that. That is because any references to sum() within the function are assumed to be recursive references to itself.

That is the main purpose of the result() clause, its allows a function to directly reference itself in expressions within the body of the function.

1 Like

Then I have to re-read the text up to listing 3.6 because when writing my question here, I did not consider recursion (as e.g., in the example in the Fortran wiki as related to the result attribute):

 program ackermann
   integer :: ack
   write(*,*) ack(3, 12)
 end program ackermann

 recursive function ack(m, n) result(a)
   integer, intent(in) :: m,n
   integer :: a
   if (m == 0) then
     a=n+1
   else if (n == 0) then
     a=ack(m-1,1)
   else
     a=ack(m-1, ack(m, n-1))
   end if
 end function ack

Then, result attribute were like an anchor (or seed?) to start/initiate the computation of Fibonacci, or of factorial n!, which (less Fortran idiomatic) possibly could be defined differently, too; perhaps vaguely similar to the array computations split into a) dh(1) = h(1) - h(grid_size) for one element alone, followed by b) a block

do concurrent (i = 2:grid_size)
  dh(i) = h(i) - h(i-1)
end do

for the every subsequent element to consider.

If one wants to call the function recursively, result(...) must be used. Otherwise, the name of the result variable shadows the name of the function, and one cannot refer to the function inside itself.

2 Likes

@FortranFan The example you point to provides an glimpse of what is possible. As such, it goes considerably beyond Milan’s book about Writing procedures that operate both on scalars and arrays (chapter 3) with a bridge like

program subroutine_example
  implicit none

  print *, sum(3, 5)
  print *, sum([1, 2],3)
  print *, sum(1, [2, 3, 4])
  print *, sum([1, 2, 3], [2, 3, 4])

contains

pure elemental integer function sum(a, b)
  integer, intent(in) :: a, b
  sum = a + b
end function sum  

end program subroutine_example

because your example requires solid insight where/how Fortran’s implementation of sin can/could/should be improved .plus. the mathematics. Hence for me, this taps more into the field of Fortran development rather than grateful use of what generations of computer scientists and committee members identified as «good, we use this implementation».

This becomes evident e.g., in manual (pen and paper) calculation of factorials. I get this point, it is a prerequisite to access the next round of the algorithm.

No idea what you mean by your last sentence, “'this taps more into the field of Fortran development rather than grateful use of what generations of computer scientists and committee members identified as «good, we use this implementation»”

As to the rest of your comments here, you now appear to convey with a statement such as “Writing procedures that operate both on scalars and arrays” that your interest is in ELEMENTAL procedures whereas with your original post it appeared you were interested in something else viz. " The inclusion of either definition 3.5, or 3.6 causes the main program to use sum as defined by this (local / user defined) function; because for the main program , the local definition in its very file file is of higher hierarchy than Fortran’s intrinsic sum function"

As to my example, you can try to not read much into the mathematics or Fortran implementations of the trigonometric function but simply note by controlling the subscope via a BLOCK construct or some such mechanism and also the intrinsic attribute, you can flirt with danger or confusion to a casual reader of the program and direct the main program to invoke an override of an intrinsic or the intrinsic function itself. Another silly example along somewhat similar lines, here indulging in (mis)use of generic interface and resolution, is:

module m
   interface sum
      module procedure my_sum
   end interface
contains
   elemental integer function my_sum(a, b)
      integer, intent(in) :: a, b
      my_sum = sum( [ a, b ] ) !<-- this is for illustration purposes only; don't think it's any wise!
   end function
end module
   use m
   print *, sum([1,2],[3,4])
end