I’ve modified the code a bit, such that the result variable (b) and the intent(out)-variable (err) in fun1() are always defined, and also initialized err before calling fun1() optionally (the line marked by *):
program main
use iso_fortran_env, only: dp => real64
implicit none
call test_fun1()
contains
function fun1(a, err) result(b)
real(dp), intent(in) :: a
character(:), allocatable, intent(out) :: err
real(dp) :: b(2)
if (a > 2) then
b(:) = -1
err = "a bigger than 2"
return
endif
b(:) = 1
err = "OK"
end function
subroutine test_fun1()
real(dp) :: a, b(2)
character(:), allocatable :: err
!! err = "dummy" !! (*)
a = 3
b = fun1(a, err)
if (allocated(err)) then
print *, 'err is allocated'
print *, 'next line tries to print err'
print *, len(err), len_trim(err)
print *, err
endif
print *, b
end subroutine
end program
Then, if the line (*) is commented out, using Gfortran12 + Ubuntu22,
$ gfortran test.f90 && ./a.out
err is allocated
next line tries to print err
0 0
-1.0000000000000000 -1.0000000000000000
while if the line (*) is uncommented,
err is allocated
next line tries to print err
5 5
a big
-1.0000000000000000 -1.0000000000000000
The result also changes on an old MacMini, or with -fsanitize=address. It seems like the length of err is “retained” before and after the call (so 5 chars are printed when “dummy” is set). If err is not defined before the call, some garbage value will be “retained”, so resulting an undefined behavior (-> accessing invalid memory if the random value is large or negative)?