I am guessing you did not initialize buffer(), and it is probably filled with nulls and so if you print it it looks like there are no spaces. Try adding
buffer=' '
before you set character 80.
If that is not the problem, if you can provide a simple working example program that produces the problem that would be useful.
I’ve just played a bit more with the above code, and it seems like the unexpected behavior occurs when we just use a SAVE-ed pointer variable for an allocatable character string (without null()). So possibly, the management of some meta-data of the SAVE-ed pointer variable has a compiler bug, and so a strange behavior later…?
The codes I tried are below: one is with the main program, and the other is with a subroutine (to avoid exceptional behaviors of the main program). I also wonder whether Gfortran does not automatically save all variables in the main program (in the 1st code)…?
It’s an “as if”. Without this bug, one wouldn’t be able to say if the variable is effectively saved (i.e. static) or not, since the variables in the main are alive during the entire life of the program.
My (current) understanding is that all variables declared at the top of the main program are always SAVE-ed, and I can experiment it with a derived type with FINAL routines, something like:
module test_m
implicit none
type foo_t
contains
final :: fin
end type
contains
subroutine fin(this)
type(foo_t) :: this
print *, "final called"
end
end module
program main
use test_m
implicit none
type(foo_t) :: f !! (*1)
print *, "main start"
call sub()
print *, "main end"
contains
subroutine sub()
!! type(foo_t) :: f !! (*2)
end
end program
Results with gfortran-15 + Mac M1:
$ gfortran-15 test.f90 (with (*1) uncommented)
main start
main end
$ gfortran-15 test.f90 (with (*2) uncommented)
main start
final called
main end
However, I remember having read that some compilers (GCC?) do not SAVE them automatically, so a bit confused… (maybe I guess it was about usual subroutines etc, rather than the main program). And I agree that if there is a compiler bug, the apparent behavior of SAVE etc may be irregular and do not necessarily follow the expected behavior.
Anyway, I think the 2nd program above (on the Compiler explorer) is more clear (than the 1st one) because local variables are not automatically SAVE-ed in subroutines.
I am also afraid whether a similar bug can possibly occur for allocatable arrays (or array pointers) + SAVE with gfortran-15 (if the reason for the bug is related), but not tried yet (I guess the above bug is specific for characters, but not sure…)
I’m not sure your case *1 definitely prove that the variable in the main is saved. If the compiler doesn’t save the variable but instead choses the “as if” route (allocating the variable on the stack at the begining of the execution), then not deallocating it before the program ends is actually the correct way to proceed.
EDIT: the snippet below shows that with gfortran 15.1 the main variables are not placed at all in the same memory area, depending on wether they are explicitely saved or not. This is a strong hint that when not saved, they are dynamically allocated at the begining of the execution:
program main
implicit none
integer :: i
integer, save :: j
print*, "main not saved", loc(i)
print*, "main saved", loc(j)
call sub()
contains
subroutine sub()
integer :: i
integer, save :: j
print*, "sub not saved", loc(i)
print*, "sub saved", loc(j)
end
end program
Execution with gfortran 15.1:
main not saved 140720694142972
main saved 4210756
sub not saved 140720694142396
sub saved 4210760
The behavior is the same with ifx and flang. In contrast, nvfortran seems to save all the main variables.