Commit 50efa772 by Janne Blomqvist

Improve RANDOM_SEED example.

2013-05-22  Janne Blomqvist  <jb@gcc.gnu.org>

	* intrinsic.texi (RANDOM_SEED): Improve example.

From-SVN: r199182
parent c0602ab8
2013-05-22 Janne Blomqvist <jb@gcc.gnu.org>
* intrinsic.texi (RANDOM_SEED): Improve example.
2013-05-21 Tobias Burnus <burnus@net-b.de> 2013-05-21 Tobias Burnus <burnus@net-b.de>
PR fortran/57035 PR fortran/57035
......
...@@ -10173,9 +10173,12 @@ end program ...@@ -10173,9 +10173,12 @@ end program
Restarts or queries the state of the pseudorandom number generator used by Restarts or queries the state of the pseudorandom number generator used by
@code{RANDOM_NUMBER}. @code{RANDOM_NUMBER}.
If @code{RANDOM_SEED} is called without arguments, it is initialized to If @code{RANDOM_SEED} is called without arguments, it is initialized
a default state. The example below shows how to initialize the random to a default state. The example below shows how to initialize the
seed based on the system's time. 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}: @item @emph{Standard}:
Fortran 95 and later Fortran 95 and later
...@@ -10203,20 +10206,53 @@ the @var{SIZE} argument. ...@@ -10203,20 +10206,53 @@ the @var{SIZE} argument.
@item @emph{Example}: @item @emph{Example}:
@smallexample @smallexample
SUBROUTINE init_random_seed() subroutine init_random_seed()
INTEGER :: i, n, clock implicit none
INTEGER, DIMENSION(:), ALLOCATABLE :: seed integer, allocatable :: seed(:)
integer :: i, n, un, istat, dt(8), pid, t(2), s
CALL RANDOM_SEED(size = n) integer(8) :: count, tms
ALLOCATE(seed(n))
call random_seed(size = n)
CALL SYSTEM_CLOCK(COUNT=clock) allocate(seed(n))
! First try if the OS provides a random number generator
seed = clock + 37 * (/ (i - 1, i = 1, n) /) open(newunit=un, file="/dev/urandom", access="stream", &
CALL RANDOM_SEED(PUT = seed) form="unformatted", action="read", status="old", iostat=istat)
if (istat == 0) then
DEALLOCATE(seed) read(un) seed
END SUBROUTINE 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 @end smallexample
@item @emph{See also}: @item @emph{See also}:
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment