summaryrefslogtreecommitdiff
path: root/gcc/fortran/intrinsic.texi
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/fortran/intrinsic.texi')
-rw-r--r--gcc/fortran/intrinsic.texi70
1 files changed, 53 insertions, 17 deletions
diff --git a/gcc/fortran/intrinsic.texi b/gcc/fortran/intrinsic.texi
index 35f200cb031..db4d748c876 100644
--- a/gcc/fortran/intrinsic.texi
+++ b/gcc/fortran/intrinsic.texi
@@ -10173,9 +10173,12 @@ end program
Restarts or queries the state of the pseudorandom number generator used by
@code{RANDOM_NUMBER}.
-If @code{RANDOM_SEED} is called without arguments, it is initialized to
-a default state. The example below shows how to initialize the random
-seed based on the system's time.
+If @code{RANDOM_SEED} is called without arguments, it is initialized
+to a default state. The example below shows how to initialize the
+random seed with a varying seed in order to ensure a different random
+number sequence for each invocation of the program. Note that setting
+any of the seed values to zero should be avoided as it can result in
+poor quality random numbers being generated.
@item @emph{Standard}:
Fortran 95 and later
@@ -10203,20 +10206,53 @@ the @var{SIZE} argument.
@item @emph{Example}:
@smallexample
-SUBROUTINE init_random_seed()
- INTEGER :: i, n, clock
- INTEGER, DIMENSION(:), ALLOCATABLE :: seed
-
- CALL RANDOM_SEED(size = n)
- ALLOCATE(seed(n))
-
- CALL SYSTEM_CLOCK(COUNT=clock)
-
- seed = clock + 37 * (/ (i - 1, i = 1, n) /)
- CALL RANDOM_SEED(PUT = seed)
-
- DEALLOCATE(seed)
-END SUBROUTINE
+subroutine init_random_seed()
+ implicit none
+ integer, allocatable :: seed(:)
+ integer :: i, n, un, istat, dt(8), pid, t(2), s
+ integer(8) :: count, tms
+
+ call random_seed(size = n)
+ allocate(seed(n))
+ ! First try if the OS provides a random number generator
+ open(newunit=un, file="/dev/urandom", access="stream", &
+ form="unformatted", action="read", status="old", iostat=istat)
+ if (istat == 0) then
+ read(un) seed
+ close(un)
+ else
+ ! Fallback to XOR:ing the current time and pid. The PID is
+ ! useful in case one launches multiple instances of the same
+ ! program in parallel.
+ call system_clock(count)
+ if (count /= 0) then
+ t = transfer(count, t)
+ else
+ call date_and_time(values=dt)
+ tms = (dt(1) - 1970) * 365_8 * 24 * 60 * 60 * 1000 &
+ + dt(2) * 31_8 * 24 * 60 * 60 * 1000 &
+ + dt(3) * 24 * 60 * 60 * 60 * 1000 &
+ + dt(5) * 60 * 60 * 1000 &
+ + dt(6) * 60 * 1000 + dt(7) * 1000 &
+ + dt(8)
+ t = transfer(tms, t)
+ end if
+ s = ieor(t(1), t(2))
+ pid = getpid() + 1099279 ! Add a prime
+ s = ieor(s, pid)
+ if (n >= 3) then
+ seed(1) = t(1) + 36269
+ seed(2) = t(2) + 72551
+ seed(3) = pid
+ if (n > 3) then
+ seed(4:) = s + 37 * (/ (i, i = 0, n - 4) /)
+ end if
+ else
+ seed = s + 37 * (/ (i, i = 0, n - 1 ) /)
+ end if
+ end if
+ call random_seed(put=seed)
+end subroutine init_random_seed
@end smallexample
@item @emph{See also}: