Random numbers across systems

Given the standard (is it?) random number generator (RANDOM_NUMBER (The GNU Fortran Compiler)) and the same seed:

  1. Should we expect to obtain the same random sequence in different operating systems?

  2. Across compilers?

  3. Across across different versions of a compiler?

The standard says nothing about the algorithm generating the pseudorandom numbers. Therefore we can expect that the general answer to the three questions is “no”.

In practice, maybe some compilers use the same algorithms / libraries.

The compilers are free to implement a new algorithm that would give a better sequence.

2 Likes

Note that random_seed has a put argument that is a 1D array of integers whose size varies across compilers. There was a related thread Initializing RANDOM_NUMBER .

1 Like

Speaking of initialization, I’ve just found that gfortran (v. 11.2.0) apparently randomly initializes the generator (if random_seed is not used), while ifort (v. 2021.4.0) uses the same initialization. So

program test_rand
  real :: r(10)
  call random_number(r)
  print *, r
end program test_rand

gives different results on each run when compiled with gfortran but identical sequence when built by ifort

As @vmagnin says, the standard is silent on this. gfortran, in particular, has changed its behavior at least once over the years. The uncertainty about this is what prompted the creation of RANDOM_INIT in Fortran 2018 - both gfortran and ifort support it.

The advice about seeds being nonstandard also applies. You can’t even count on the size of the seed being the same across different versions of the same compiler. If you are setting the seed with RANDOM_SEED, make sure you call first to get the seed size.

Here is a code that uses the values of date_and_time to set the seed of random_number and which seems to give independent values each time if you burn off the first 1000 variates. I may post it on FortranTip and would appreciate feedback.

module seed_mod
implicit none
contains
!
subroutine set_random_seed()
integer, parameter   :: ndt = 8
integer              :: nseeds, date_time_values(ndt), max_set
integer, allocatable :: seeds(:)
logical, parameter   :: debug = .false.
call date_and_time(values = date_time_values)
call random_seed(size=nseeds)
allocate (seeds(nseeds), source = 0)
max_set = min(ndt,nseeds)
if (debug) print*,"max_set =",max_set
! use the last values in date_time_values since they change more often
seeds(:max_set) = date_time_values(ndt:ndt-max_set+1:-1)
if (debug) print "(a,*(1x,i0))", "in set_random_seed, seeds =",seeds
call random_seed(put=seeds)
end subroutine set_random_seed
!
subroutine print_random_seeds()
integer :: nseeds
integer, allocatable :: seeds(:)
call random_seed(size=nseeds)
allocate (seeds(nseeds))
call random_seed(get=seeds)
print*,"seeds =",seeds 
end subroutine print_random_seeds
!
end module seed_mod
!
program test_set_random_seed
use seed_mod, only: set_random_seed, print_random_seeds
implicit none
integer, parameter :: nran = 1000
real :: xran(nran)
logical, parameter :: print_seeds = .false.
call set_random_seed()
if (print_seeds) call print_random_seeds()
call random_number(xran)
write (*,"(a15,*(1x,f0.4))") "xran(1:10)",xran(1:10)
write (*,"(a15,*(1x,f0.4))") "xran(991:1000)",xran(991:1000)
end program test_set_random_seed

gfortran output:

c:\fortran\test>a.exe
     xran(1:10) .5292 .8830 .2435 .0774 .1544 .3524 .2895 .5812 .9529 .7764
 xran(991:1000) .1917 .0611 .6513 .6162 .5450 .8984 .4962 .6353 .9901 .1053

c:\fortran\test>a.exe
     xran(1:10) .5292 .8830 .2447 .0556 .9607 .4218 .2414 .9409 .6613 .9757
 xran(991:1000) .1800 .1423 .3696 .1019 .1807 .3361 .1946 .8713 .5052 .9213

c:\fortran\test>a.exe
     xran(1:10) .5292 .8830 .2439 .0551 .9104 .6544 .5278 .0670 .9785 .1740
 xran(991:1000) .1802 .6458 .5914 .3756 .4210 .6753 .1610 .8395 .4214 .5280

c:\fortran\test>a.exe
     xran(1:10) .5292 .8830 .2435 .0334 .1202 .4258 .5692 .5257 .6474 .9413
 xran(991:1000) .6105 .4555 .3365 .4962 .8155 .8455 .2513 .2044 .9953 .9011

c:\fortran\test>a.exe
     xran(1:10) .5292 .8830 .2438 .1759 .7037 .2761 .7876 .7652 .9479 .8877
 xran(991:1000) .6975 .5051 .9856 .8414 .9216 .8496 .1680 .9574 .1016 .2903

With random_init can I get a reproducible sequence everywhere? Did it standardize some procedure? (All this relates to reproducing results which are dependent on rands).

It would be nice to have a “stable random” compiler option to generate a standard sequence given a seed, even if sacrificing performance, to allow reproducible executions.

I’d suggest that if you want absolutely the same sequence everywhere, then you want to supply your own random number generator and supply it with fixed seeds. RANDOM_INIT lets you ask for the same sequence every time you run a specific application, but if you rebuild it, the guarantee is void. The wording in the standard is “In each execution of the program with the same execution environment”, so even the same application may give a different sequence if, say, compiler shareable libraries change.

I’d disagree with @kargl that testing helps, because you may be lulled into thinking that something is fixed when it is not. (This is the “but it worked before!” fallacy.)

The real value of RANDOM_INIT is that it standardizes the request for a different sequence on each run. Prior to this, you were left to implementation-specific tricks such as calling RANDOM_SEED with no arguments. Indeed, this was the motivation for creating it in the first place.

1 Like

You can do this by hardcoding some random integers in a subroutine and allowing the user to provide an offset that is added to each of these to get a seed, as shown in the code below, from the previously cited thread. The “varying” random numbers are generated from a seed that also depends on the time, but the “fixed” variates are generated from a seed that depends only on the offset.

module random_mod
implicit none
contains
subroutine set_random_seed(fixed,offset,nburn_random)
logical, intent(in)           :: fixed        ! if .true., use a fixed seed
integer, intent(in), optional :: offset       ! constant added to generated seeds
integer, intent(in), optional :: nburn_random ! # of variates of RANDOM_NUMBER to burn off
integer, parameter            :: nburn = 100, nseeds_max = 12, seeds_vec(nseeds_max) = [824514020,218904035,384790913, &
                                 510442021,939900036,939295695,826403327,935378387, &
                                 634734772,413176190,91069182,818551196]
integer                       :: i,iburn,nseeds,itime,offset_,nburn_random_
integer, allocatable          :: seed(:)
real(kind=kind(1.0d0))        :: xran,xseed(nburn + nseeds_max)
nburn_random_ = 100
offset_ = 0
if (present(nburn_random)) nburn_random_ = nburn_random
if (present(offset)) offset_ = offset
call random_seed(size=nseeds)
allocate(seed(nseeds))
if (fixed) then
   if (nseeds > nseeds_max) then
      seed(:nseeds_max) = seeds_vec + offset_
      seed(nseeds_max + 1:) = 0 ! NAG says to set the remaining elements of the seed array to zero to indicate zero entropy
   else
      seed = seeds_vec(:nseeds) + offset_
   end if
else ! set seed based on current time
   call system_clock(itime)
   seed = itime
   call random_seed(put=seed)
   call random_number(xseed)
   do i=1,nseeds
      if (i <= nseeds_max) then
         seed(i) = xseed(nburn+i)*1000000000 + offset_
      else
         seed(i) = 0
      end if
   end do
end if
call random_seed(put=seed)
do iburn=1,nburn_random_
   call random_number(xran)
end do
end subroutine set_random_seed
end module random_mod

program xset_random_seed
use random_mod, only: set_random_seed
implicit none
integer, parameter :: dp = kind(1.0d0)
integer, parameter :: n = 5, nburn_random = 100
real(kind=dp)      :: xx(n)
integer            :: ifix,offset,iter
character (len=10) :: labels(0:1) = ["varying","fixed  "]
do offset=0,2
   print*,"offset =",offset
   do ifix=0,1
      call set_random_seed(fixed=(ifix == 1),offset=offset,nburn_random=nburn_random)
      call random_number(xx)
      write (*,"(a12,100f10.4)") trim(labels(ifix)),xx
   end do
end do
end program xset_random_seed

gfortran output:

c:\fortran\test>a.exe
 offset =           0
     varying    0.4081    0.5419    0.3093    0.6581    0.4011
       fixed    0.4354    0.5414    0.0699    0.0361    0.1993
 offset =           1
     varying    0.6550    0.8607    0.6869    0.8850    0.5191
       fixed    0.7603    0.1589    0.2190    0.9923    0.8324
 offset =           2
     varying    0.1805    0.6776    0.0371    0.2762    0.6915
       fixed    0.6144    0.5729    0.3696    0.7675    0.8280

c:\fortran\test>a.exe
 offset =           0
     varying    0.9069    0.5286    0.3049    0.9302    0.5947
       fixed    0.4354    0.5414    0.0699    0.0361    0.1993
 offset =           1
     varying    0.4250    0.4837    0.8747    0.3642    0.6122
       fixed    0.7603    0.1589    0.2190    0.9923    0.8324
 offset =           2
     varying    0.5226    0.6213    0.4804    0.5300    0.9239
       fixed    0.6144    0.5729    0.3696    0.7675    0.8280

c:\fortran\test>a.exe
 offset =           0
     varying    0.9680    0.1145    0.3504    0.0164    0.4973
       fixed    0.4354    0.5414    0.0699    0.0361    0.1993
 offset =           1
     varying    0.2824    0.3550    0.8076    0.6022    0.3057
       fixed    0.7603    0.1589    0.2190    0.9923    0.8324
 offset =           2
     varying    0.8616    0.4010    0.5278    0.4778    0.1063
       fixed    0.6144    0.5729    0.3696    0.7675    0.8280

This is unnecessary with the advent of RANDOM_INIT.

Stdlib does provide a PRNG implementation, which should be allow you to obtain the same random sequence for a given seed (API: stdlib_random – Fortran-lang/stdlib, specs: random – Fortran-lang/stdlib).

1 Like

I think I remember that the GFortran behavior was different under Windows and Linux, and I had to code a procedure using date_and_time() to initialize the seed “randomly” on both platforms. But it was probably in the 2000’s and I don’t know if it is still true.

I do not know about Windows. In Linux, gfortran 4.x still initialized the RNG identically. Versions 7 and above - differently on each run.

Absolutely, but the point I was making was that testing can lead one to make invalid assumptions when the standard doesn’t say something.

1 Like