Blame view

fvn_test/init_random_seed.f90 1.14 KB
27d3b84d6   daniau   git-svn-id: https...
1
2
3
4
5
6
7
8
9
10
11
12
13
  ! As the norm stated for random_seed "If no argument is present, the processor assigns a 
  ! processor-dependent value to the seed."
  ! It seems that there are different possible interpretations for this :
  ! In gfortran a call to random_seed without arguments will initialize to a default value
  ! which will always be the same.
  ! In Portland fortran, a call to random_seed without arguments will initialize with something 
  ! machine and time dependant
  ! Unfortunately as the underlying algorithm are (or at least can be) different in each
  ! compiler, we cannot generalize the use of this initialization provided in gfortran 
  ! documentation
  SUBROUTINE init_random_seed()
      INTEGER :: i, n, clock
      INTEGER, DIMENSION(:), ALLOCATABLE :: seed
8ba5c9c78   wdaniau   1) Updated docume...
14
      logical :: gfortran=.true.
27d3b84d6   daniau   git-svn-id: https...
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
      !
      ! Set gfortran to .true. if using gfortran to obtain the desired behaviour
      !
      if (gfortran) then
          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)
      else
          call random_seed()
      end if
  END SUBROUTINE