PRINT deferred variable in FUNCTION

! These lines constitute file gag.f90
! gfortran gag.f90
! ./a.out
! HANG!
MODULE no_can_do_mod
IMPLICIT NONE
CONTAINS
FUNCTION no_can_do () RESULT (sResult)
CHARACTER(:), ALLOCATABLE :: sResult
sResult = ‘Ei’
! Comment out this next line and the program works.
PRINT ‘(A)’, sResult
! How should I have suspected that behavior?
END FUNCTION no_can_do
END MODULE no_can_do_mod

PROGRAM gag
USE non_can_do_mod
PRINT ‘(A)’, no_can_do ()
END PROGRAM gag

If printing occurs within function f, the behavior of print*,f() is undefined, since recursive I/O is not allowed in Fortran, and instead you should write

y = f()
print*,y

See the previous thread https://fortran-lang.discourse.group/t/gfortran-bug-on-a-simple-program.

The previous one you referenced is rather poorly named. Is there anything you might suggest that would have directly sent me to there? I don’t care to muddy the water with duplicates.

I have misunderstood any great value of appending RESULT (sResult) to a function definition. I must accept the rules, for sure.

Sure makes internal debugging of a function more obtrusive.

Thanks for helping me.

If the printing in the function is of an error message and you want to stop the program at that point, you could use error stop, as demonstrated at FortranTip/recursive_io.f90 at main · Beliavsky/FortranTip · GitHub

There isn’t much. The main feature that it enables is to allow direct recursion within the function (i.e. to have the function reference itself). Some programmers prefer the use of the result clause anyway, despite its (slight) verbosity.

This restriction has been in fortran since f66 I think, and everyone has tripped over it at some time or another, particularly while debugging. Note that it is the actual i/o that causes the problem, not the i/o statement itself, so if there is complicated branch logic that only triggers the i/o rarely (e.g. an error message), the error can lie latent, just waiting for the worst possible time to reveal itself. The restriction has actually been somewhat relaxed in the later standard revisions. It is now allowed to do i/o to distinct units within the call tree; even that was not allowed up through f77 (and maybe f90).

Since Fortran is a 67-70 years old language, there are usually multiple ways to do the same thing —and often, one of those causes less friction than the others.

In this case, the friction comes when thinking about when to use the result suffix of the function-stmt and when not —it’s, like thinking about when to put :: after the type definition or if attribute statements (other than public|private) should be used.

If you use the result suffix, then besides being useful for recursion purposes, the result name can be shorter, e.g.:

function some_complex_condition(input) result(cond)
    logical :: cond
    ...
    cond = assert1(...)
    if (cond) return
    cond = assert2(...)
    if (cond) return
    ...
end function

And you can also get into complicated stuff, e.g.:

pure function some_string_manipulation(input) result(output)
    character(*), intent(in) :: input(:)
    character(len(input)) :: output(size(input))
    ...
end function

The choice seems to be never use I/O in a function or never call a function in an I/O statement but regardless it would be nice if there was someway to detect you are called from an I/O statement so you could terminate. The most irritating part is compilers that cause a hang. An actual failure is preferable.

It is so natural to write error messages from a function call it is a significant issue. And some compilers do allow recursive I/O; and even ones that allow different I/O units (which improves things considerably are not immune from the problem. If I use stderr for the messages and assume that calls are writing to a file or stdout the problem is avoided most of the time, but then you use a function in a write statement writing to stderr and cause a problem anyway.

All the solutions have their own issues or prevent functions from being pure, etc. It still might be useful to have a wiki page that shows how appending to a stack of messages, returning an error string with the function, passing in a user type that contains a message,… and various work-arounds might be useful.

I recently traced a hanging code compiled with gfortran where it looked like it was hanging when writing to stderr even though called from a write statement writing to stdout, That should be allowed now. But it actually was because there was a flush of stdout. So all I/O can be an issue, not just an explicit WriTE or PRINT. At least on the platform I am wrting this from this hangs with gfortran:

write(stdout,*)hangit()
contains
function hangit()
flush(stdout)
end function hangit
end

that is, a flush statement flushing the file being written to. Probably is technically undefined, but something I had not personally run across before.
I r

2 Likes

You can give the function an optional argument for the unit number to which output is written, as in the code below. If the argument is not supplied, the function writes to standard output.

module m
use iso_fortran_env, only: output_unit
implicit none
contains
function f(outu) result(s)
character (len=:), allocatable :: s
integer, intent(in), optional :: outu
integer :: outu_
if (present(outu)) then
   outu_ = outu
else
   outu_ = output_unit
end if
s = "ab"
write (outu_, *) s
end function f
end module m
!
program main
use m
implicit none
integer :: outu
open (newunit=outu, file="temp.txt", action="write", status="replace")
print*,f(outu=outu) ! works
print*,"returned from 'f(outu=outu)'"
print*,f() ! fails
end program main
1 Like

I like that, where you could write to stderr normally, but if in an I/O statement writing to stderr you could specify stdout and/or a log file. That works for newer standards where I/O is allowed recursively as long as separate units are involved. Just no good way to enforce it being used when you use the function in an I/O statement. If an I/O statement was required to report it was in an I/O statement recursively and what unit was being used it would work. I tried getting the real path to stdout and doing a link to it and then opening that link file with a newunit= but it was too cumbersome and not very portable so I gave up on that. This suggestion seems to be the best at the moment without some new feature to let you auto-detect you are being called from an I/O statement.

It took a while for that rule to sink in with appreciation of a reason for it. I do not think I will make that error again. Seems easy enough to refrain from citing a function as a I/O statement argument. I cannot trust myself to remember which functions are free of I/O.

I do wonder why Fortran does not require all the expressions be evaluated
first, which perhaps naively I think would resolve the problem. A kludge
I have not seen fail (yet?) is to write to an internal file and then
print the internal file, which seems to imply such an approach would
resolve the issue.

A function writing to a different unit (such as stderr) is now allowed nested in a WRITE()
so the kludges in the sample below are standard-conforming.

And it appears to be a common extension that recursive I/O does not cause
a hang, as not all programming environments hang. Even if not allowed,
crashing would be so preferable to hanging, but I am not sure the hang
itself would be regarded as a bug or not if reported as you have to do
something not standard-conforming to invoke it; but most developers will
fix an ICE even if it is caused by non-conforming code, changing it to
a reportable error instead.

Admittedly, something like “print *, func1(func2(func3()))” where everyone does I/O
would also have to be addressed.

module no_can_do_mod
use, intrinsic :: iso_fortran_env, only : stderr=>ERROR_UNIT
implicit none
contains

   function no_can_do () result (sresult)
   character(:), allocatable :: sresult
      sresult = 'NoCanDo'
      print '(A)', 'NO_CAN_DO_MESSAGE'
   end function no_can_do

   ! same as no_can_do accept writes to stderr
   function can_do () result (sresult)
   character(:), allocatable :: sresult
      sresult = 'CanDo'
      ! assuming calling I/O is not writing to stderr
      write(stderr,'(A)') 'CAN_DO_MESSAGE'
   end function can_do

end module no_can_do_mod
program gag
use no_can_do_mod
implicit none
character(len=255) :: line
character(len=*),parameter :: it='(*(g0,1x))'
  ! kludge 1:
   ! avoid recursive I/O causing hang by writing to
   ! "different" unit (ie. internal file)
   write(line,it),no_can_do()
   print it, trim(line)
  ! kludge 2:
   ! procedure writes to stderr, print to stdout
   ! so OK if nested functions are avoided as well
   print it, can_do()
end program gag

One extra reason not do I/O (or other impure things) in functions is because it doesn’t play well with optimizations like function elimination.

Consider the gfortran optimization flag -faggressive-function-elimination:

Functions with identical argument lists are eliminated within statements, regardless of whether these functions are marked PURE or not. For example, in

a = f(b,c) + f(b,c)

there will only be a single call to f. This option only works if -ffrontend-optimize is in effect.

-ffrontend-optimize will be enabled with any -O option except -O0 and -Og:

module testmod

    implicit none

contains

    function timestwo(x) result(xx)
        real :: x, xx
        xx = x * 2
        print *, x, xx
    end function
end module

program testprog
    use testmod
    implicit none
    real :: x, z

    x = 1
    z = timestwo(x) + timestwo(x)
    print *, z
end program

Run:

gfortran -O test.f90 -o test && ./test
   1.00000000       2.00000000    
   1.00000000       2.00000000    
   4.00000000
gfortran -O -faggressive-function-elimination test.f90 -o test && ./test
   1.00000000       2.00000000    
   4.00000000

I always knew this was permissible and that it could happen, but it is the first time that I have seen it actually happen :slight_smile: Very cool. The option -faggressive-function-elimination seems not to be enabled by any of the “popular” O-levels, even -Ofast.

1 Like

This could also happen even without the compiler option if the function is declared as pure. Of course, one cannot easily determine that because the print statement would need to be removed, so some other way to determine the number of function calls would need to be devised.