Error in interface block: syntax error

Here is code taken from wikibooks: wikibooks

real function tester(a)
    real, intent (in), optional :: a
    if (present(a)) then
        tester = a
    else
        tester = 0.0
    end if
end function 

program main
    interface
        function tester(a)
            real function tester(a)
            real, intent (in), optional :: a
        end function 
    end interface

    print *, "[no args] tester()   :", tester()    ! yields: 0.0
    print *, "[   args] tester(1.0):", tester(1.0) ! yields: 1.0
end program

Here is the error:

gfortran -o optional_arg.x optional_arg.f90
optional_arg.f90:13:25:

13 | real function tester(a)
| 1
Error: Syntax error in data declaration at (1)

real function tester(a)
    real, intent (in), optional :: a
    if (present(a)) then
        tester = a
    else
        tester = 0.0
    end if
end function 

program main
    interface
        real function tester(a)
            real, intent (in), optional :: a
        end function 
    end interface

    print *, "[no args] tester()   :", tester()    ! yields: 0.0
    print *, "[   args] tester(1.0):", tester(1.0) ! yields: 1.0
end program

wikibook is wrong.

1 Like

I think (not sure) the correct one is:

real function tester(a)
    real, intent (in), optional :: a
    if (present(a)) then
        tester = a
    else
        tester = 0.0
    end if
end function

program main
    interface
        function tester(a)
            real :: tester ! this one!!
            real, intent (in), optional :: a
        end function
    end interface

    print *, "[no args] tester()   :", tester()    ! yields: 0.0
    print *, "[   args] tester(1.0):", tester(1.0) ! yields: 1.0
end program

with the output:

gfortran -o optional_arg.x optional_arg.f90 && ./optional_arg.x
[no args] tester() : 0.00000000
[ args] tester(1.0): 1.00000000

I checked the integer version of the above program:

integer function tester(a)
    real, intent (in), optional :: a
    if (present(a)) then
        tester = a
    else
        tester = 0
    end if
end function

program main
    interface
        function tester(a)
            integer :: tester ! this one
            real, intent (in), optional :: a
        end function
    end interface

    print *, "[no args] tester()   :", tester()    ! yields: 0
    print *, "[   args] tester(1.0):", tester(1.0) ! yields: 1
end program

output:

gfortran -o optional_arg_integer.x optional_arg_integer.f90 && ./optional_arg_integer.x
[no args] tester() : 0
[ args] tester(1.0): 1

So the
statement integer :: tester
is needed, otherwise syntax error comes.

thank you @Euler-37
bests!

They’re both equivalent.

real function tester(a)

is just syntax sugar for

function tester(a)
    real :: tester
1 Like

I don’t really like how the chapter shows advanced features of procedures but almost does not use modules and does most with interface blocks.

2 Likes

Inadvertently or intentionally, someone at Wikibooks can confuse the heck out of a new reader and post an example like so:

module tester_m
   interface
      module function tester(a) result(r) bind(C, name="TESTER")
          real, intent (in), optional :: a
          real :: r
      end function 
   end interface
end module tester_m

submodule(tester_m) tester_sm
contains
   module function tester(a) result(r) bind(C, name="TESTER")
      real, intent (in), optional :: a
      if (present(a)) then
        r = a
      else
        r = 0.0
      end if
   end function 
end submodule tester_sm

program main
   interface
      function tester(a) result(r)  bind(C, name="TESTER")
          real, intent (in), optional :: a
          real :: r
      end function 
   end interface
   print *, "[no args] tester()   :", tester()    ! yields: 0.0
   print *, "[   args] tester(1.0):", tester(1.0) ! yields: 1.0
end program

And get an rating of “almost evil” with the duplication of interfaces and names and the “cheating” with the global name! :stuck_out_tongue_winking_eye:

+1 to that Wikibooks example for eschewing implicit none though!