! 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 logical :: gfortran=.false. ! ! 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