Which compilers initialize real/integer variables to zero by default?

I know that we shouldn’t rely on this behavior (e.g.).

But I’m just curious if there is a list or something of which compilers (and platform/architecture, compiler version, etc., if they matter) do initialize to zero.

In my brief experiment, ifort 2021.5.0 appears to do so and gfortran 11.3.0 does not.

No, ifort does not. If you’re seeing zeroes, it’s a coincidence, not deliberate. You can ask ifort to zero-init if you want, but it’s not the default behavior, and I strongly advise against using it.

4 Likes

Thanks @sblionel . So with ifort if I run enough times I should eventually see nonzero from a program like this? (So far I haven’t.)

program zero
  real :: a
  real :: b(100)

  print *, a
  print *, b
end program zero

You can ask ifort to zero-init if you want, but it’s not the default behavior, and I strongly advise against using it.

Agreed, not interested in using it, just curious.

“Enough times”? No. That program is so small that the compiler doesn’t do much at all with it. In the current version, scalar variables are allocated on the stack, which could have random values, and arrays are allocated statically, which tend to be zero at start. This is not initialization, and there are many situations where even arrays won’t be zero to start.

Please - just drop this and properly initialize your variables. Don’t go hunting for a compiler that fixes your mistakes.

1 Like

Please - just drop this and properly initialize your variables. Don’t go hunting for a compiler that fixes your mistakes.

I thought I made this clear but apparently not. I am not interested in such a compiler or compiler options. I know to initialize my variables. This question was purely out of curiosity.

Not sure about anyone doing it by default; as that could be a very expensive operation when large arrays are declared; but I do not know of a compiler that does not have related options; including flagging uninitialized variables in at least simple cases. For example, gfortran was
the following options:

   -finit-local-zero
   -finit-derived
   -finit-integer=n
   -finit-real=<zero|inf|-inf|nan|snan>
   -finit-logical=<true|false>
   -finit-character=n
       The -finit-local-zero option instructs the compiler to initialize
       local "INTEGER", "REAL", and "COMPLEX" variables to zero, "LOGICAL"
       variables to false, and "CHARACTER" variables to a string of null
       bytes.  Finer-grained initialization options are provided by the
       -finit-integer=n, -finit-real=<zero|inf|-inf|nan|snan> (which also
       initializes the real and imaginary parts of local "COMPLEX"
       variables), -finit-logical=<true|false>, and -finit-character=n
       (where n is an ASCII character value) options.

As mentioned, setting to zero is generally not recommended; but setting real values to NAN and doing things like building with logical TRUE, then logical FALSE, or making sure nothing changes if set -finit-character to different values is a part of some QA procedures I have seen; under the assumption that results should not change if everything is only used when initialized.

Similarly I have seen QA procedures that require running codes with default scalar sizes set to 32 and then to 64; but with implicit none in more recent times (near) universally available that catches less than it used to. Sometimes it is not practical, sometimes it helps detect numeric sensitivities that should be dealt with, … mileage varies quite a bit on that one.

Thanks for this additional explanation.

I will say I was inspired to post this question after overhearing a conversation about a much larger program where the authors were relying on ifort’s behavior (according to them) to (effectively) initialize arrays to zero and complaining how gfortran did not do this. And this wasn’t the first time I’ve heard such a claim.

And with my small program, even if it was “not initialization”, the results were qualitatively consistent with their claim, since I get zeroes with ifort but not with gfortran (random values for the scalar and the array elements).

Are there some rules of thumb for when such behavior will occur with ifort? Again I am not looking to rely on this behavior, I am just curious.

OK. If you enable any options that make procedures recursive by default, you’ll get everything on the stack. Even though Fortran 2018 makes recursive the default, ifort currently does this only if you also say -standard-semantics. Enabling parallelism will also do this.

Here’s an example demonstrating it. I used separate files to prevent interprocedural optimization

t1.f90

integer :: a1
call foo (a1)
end

t2.f90

subroutine foo (a1)
integer :: a1, a2(10)
call bar (a1, a2)
return
end subroutine foo

t3.f90

subroutine bar (a1, a2)
integer :: a1, a2(10)
print *, a1
print *, a2
return
end

D:\Projects>ifort /c /standard-semantics t1.f90 t2.f90 t3.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.

D:\Projects>ifort t1.obj t2.obj t3.obj
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.9.0 Build 20230302_000000
Copyright (C) 1985-2023 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32532.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t1.exe
-subsystem:console
t1.obj
t2.obj
t3.obj

D:\Projects>t1.exe
 40896
 0 0 510470210 5094 -757820720 358
 -757780560 358 0 0

Were their arrays very small? @lionel provides a much more rigorous example, and fixed-size arrays might (depending on size and compiler options) provide very different results but even this simple program immediately starts showing non-zero values using a very simple loop. The last time I remember seeing a compiler that initialized to zero by default was when I had an argument about depending on this with a colleague too, but that was a long time ago when he was developing on a VAX/VMS system and we needed the resulting code to work on a platform where setting to zero was definitely not the default. It has been too long, but as I remember it
the default on a VAX/VMS F77 compiler was zero.

program zero
 implicit none
integer,allocatable :: b(:)
integer :: i
integer :: counts
   do i=1,1000000000
      if(allocated(b))deallocate(b)
      allocate(b(i))
      counts=count(b.ne.0)
      if(counts.ne.0)then
         b=pack(b,b.ne.0)
         write(*,'(*(g0,1x))')'counts=',counts,'out of',i,'sample', b(1:min(size(b),10))
      endif
   enddo
end program zero

on your platform when does this first find a non-zero value?

Yes, the VAX compiler put all variables in a static image section that started out as zero. (I want to say it was called .BSS, but that might be from a later platform.) Of course, this compiler didn’t know about recursion or stack-allocated variables until I added those late in its development (along with “Cray pointers”.)

When we came out with DEC Fortran 90 on MIPS and then Alpha, a lot of people migrating from VAX found that variables were no longer zero-initialized, and were also not SAVEd by default. We had to add compiler options to allow users to select them for compatibility.

Nice to know it really did that; thanks for the confirmation. The memories are a bit blurry:>.

I practice trying to forget things that were once true but no longer are; but things like SCOPE2 and COS still keep popping up now and then. Just has a discussion about how something used to run much quicker than someone thought was possible long ago who was re-validating some old results. The old speed was partly because we could assign certain regions of the files to memory and different devices and because of the file structure on old Cray COS platforms that we had speeds near what he is getting now (it is an I/O bound code). I had to dredge up memories of how the COS ASSIGN command worked and how files were open and positioned external of processes that used them and probably got some of it wrong but he got the idea. There were a lot of interesting approaches in the past. Things are boringly homogeneous in some ways now; but it general modern standardization is a good thing.

We had a LOT of code that considered that VAX F77 behavior “standard FORTRAN”, so I was part of those discussions both with DEC and in-house, but it was a long time ago. One fellow in particular refused to change “his” code and adamantly wanted the compilers “fixed” on several other platforms when he first had to run where zero was not the default value.

I am aware of a program that adds implicit none to all procedures and explicitly declares all values to have an initialization value specified via a module of parameter constants including zero, nan, and inf variables set appropriately. By setting every variable they are all implicitly SAVEd, simulating this old behavior. Long story, but the code is not public and it will intentionally stay that way. Adding declarations for everything (sans an initialization value) is particularly handy for updating the old code. I think fpt and spag can do that but I know of no option to additionally assign a value to every variable. Since they do not have such an option I suspect the demand for it is low, and that compiler options suffice for those that do want it. As noted, there are lots of related switches on several compilers. Note that initializing that way simulates initializing to zero at start-up, but does not on subsequent calls.

But in general regarding the OPs original question, the odds are very high those people that think things are initialized to zero have been very lucky if it has not caused incorrect results. Tiny arrays could get away with that for a long time on a lot of machines. I am not sure about MSWindows platforms and was thinking they might be an exception and give zero as a quirk, not as a Fortran feature(?)

The tail wagging the dog.

There is a long time poster over in comp.lang.fortran who, for almost 20 years now, has complained about this zero-initialization feature. He refuses to update his codes to conform to standard fortran, and now he is down to using a single fortran compiler that works correctly with his codes. For the last few years, he has “threatened” to convert his code from fortran to C if this feature is not fixed, as if that language conversion would somehow be easier than simply fixing his fortran code in the first place.

It is interesting how people can fixate on a single path, ignoring the many possible alternative paths along the way. I think we all do this, it is human nature.

1 Like