From: Allamarein on
I would get random (maybe it is more correct 'pseudorandom') numbers
with distribution [0,1]
I try this wrong code:

PROGRAM RANDOMIZE
IMPLICIT NONE
INTEGER :: SEED
REAL :: HARVEST
REAL, DIMENSION(4,4) :: HARVEYS

CALL RANDOM_NUMBER(HARVEST)
CALL RANDOM_NUMBER(HARVEYS)

OPEN(20, file='random.dat')
1 FORMAT(4F6.2)
DO i=1,4
WRITE(20,1) harveys(i,1), harveys(i,2), harveys(i,3), harveys(i,
4)
WRITE(*,1) harveys(i,1), harveys(i,2), harveys(i,3), harveys(i,
4)
END DO
WRITE(20,1) harvest
WRITE(*,1) harvest
WRITE (20)

read(*,*)
END PROGRAM

When it runs, it provide me random.dat.
I can run RANDOMIZE as many times as I like, but random.dat ALWAYS
contains these data:

0.70 0.91 0.35 0.88
0.28 0.30 0.55 0.13
0.66 0.48 0.61 0.93
0.81 0.99 0.97 0.76
0.98

Obviously the printed result on the screen is the same
How should I should my code?
From: ndl_91 on
On 19 juin, 12:15, Allamarein <matteo.diplom...(a)gmail.com> wrote:
> I would get random (maybe it is more correct 'pseudorandom') numbers
> with distribution [0,1]
> I try this wrong code:
> ...
> When it runs, it provide me random.dat.
> I can run RANDOMIZE as many times as I like, but random.dat  ALWAYS
> contains these data:
>
>   0.70  0.91  0.35  0.88
>   0.28  0.30  0.55  0.13
>   0.66  0.48  0.61  0.93
>   0.81  0.99  0.97  0.76
>   0.98
>
> Obviously the printed result on the screen is the same
> How should I should  my code?

Hi.
You need to save the seed to avoid standard initialisation. You can
try this way.
Hope it helps.
Ndl

module m_random
implicit none
character(len=64), parameter, private :: fic_seed="my_seed.dat"
!
contains
!
subroutine reset_seed(iseed)
implicit none
integer, intent(in) :: iseed
call random_seed(iseed)
end subroutine reset_seed
!
subroutine save_seed()
implicit none
integer :: n, I_unit_seed
integer, dimension(:), allocatable :: last_seed
call random_seed(size=n)
allocate(last_seed(n))
call random_seed(get=last_seed)
!!$ write(6,*) "last_seed=",last_seed
call get_unit(I_unit_seed)

open(unit=I_unit_seed,file=trim(adjustl(fic_seed)),status="unknown",form="unformatted")
write(I_unit_seed) n
write(I_unit_seed) last_seed
close(I_unit_seed)
deallocate(last_seed)
end subroutine save_seed
!
subroutine load_seed()
implicit none
integer :: n, I_unit_seed
integer :: iseed
logical :: L_present
integer, dimension(:), allocatable :: last_seed
!
call get_unit(I_unit_seed)

open(unit=I_unit_seed,file=trim(adjustl(fic_seed)),status="old",form="unformatted",err=100)
write(6,*) "Loading seed file"
read(I_unit_seed) n
allocate(last_seed(n))
read(I_unit_seed) last_seed
close(I_unit_seed)
call random_seed(put=last_seed)
deallocate(last_seed)
return
!
100 continue
write(6,*) "Creating seed"
iseed=0
call reset_seed(iseed)
end subroutine load_seed
!
subroutine get_unit(Num_Fich)
implicit none
integer :: Num_Fich
logical :: ouvert
ouvert=.true.
Num_Fich=10
do while (Num_Fich < 100)
Num_Fich=Num_Fich+1
inquire(unit=Num_Fich,opened=ouvert)
if (.not.ouvert) exit
enddo
if (ouvert) then
write(6,*) "Pas d unite logique libre"
stop 'get_unit'
endif
end subroutine get_unit
!
end module m_random
!
PROGRAM RANDOMIZE
use m_random
IMPLICIT NONE
integer :: i
INTEGER :: SEED
REAL :: HARVEST
REAL, DIMENSION(4,4) :: HARVEYS
!
call load_seed()
!
CALL RANDOM_NUMBER(HARVEST)
CALL RANDOM_NUMBER(HARVEYS)

1 FORMAT(4F6.2)
DO i=1,4
WRITE(6,1) harveys(i,1), harveys(i,2), harveys(i,3), harveys(i,4)
END DO
WRITE(6,1) harvest
!
call save_seed()
!
END PROGRAM RANDOMIZE


From: Tobias Burnus on
Allamarein wrote:
> I would get random (maybe it is more correct 'pseudorandom') numbers
> with distribution [0,1]
>
> I can run RANDOMIZE as many times as I like, but random.dat ALWAYS
> contains these data:

Well, there are two different philosophies: One is, that one should get
by default the same sequence of pseudo-random numbers as this makes
programs more deterministic. The other one is that one always wants to
have different numbers, matching some "true" random results.

As neither of the choices is better, the standard did not specify what a
compiler has to do. You can use RANDOM_SEED to get different
pseudo-random numbers, cf. for instance:
http://gcc.gnu.org/onlinedocs/gfortran/RANDOM_005fSEED.html

Under Linux, one can also use /dev/random to get random numbers are less
predictable (contrary to, e.g., /dev/urandom, which are also pure
pseudo-random numbers).

Tobias
From: Richard Maine on
Tobias Burnus <burnus(a)net-b.de> wrote:

> Well, there are two different philosophies: One is, that one should get
> by default the same sequence of pseudo-random numbers as this makes
> programs more deterministic. The other one is that one always wants to
> have different numbers, matching some "true" random results.
>
> As neither of the choices is better, the standard did not specify what a
> compiler has to do.

More like because the person who wrote the words in that bit of the
standard was sloppy about making sure that he actually wrote what he
intended to, and the oversight did not get corrected during review. Said
person later tried to fix it by a retroactive "correction" to the
standard, but it was way too late for that, considering that multiple
implementations already were in use and the only data supporting the
claim that this was done in error was his word about his personal
intentions in writing it.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
From: steve on
On Jun 19, 6:06 am, ndl_91 <nicolas.lardj...(a)gmail.com> wrote:
> On 19 juin, 12:15, Allamarein <matteo.diplom...(a)gmail.com> wrote:
>
>
>
> > I would get random (maybe it is more correct 'pseudorandom') numbers
> > with distribution [0,1]
> > I try this wrong code:
> >  ...
> > When it runs, it provide me random.dat.
> > I can run RANDOMIZE as many times as I like, but random.dat  ALWAYS
> > contains these data:
>
> >   0.70  0.91  0.35  0.88
> >   0.28  0.30  0.55  0.13
> >   0.66  0.48  0.61  0.93
> >   0.81  0.99  0.97  0.76
> >   0.98
>
> > Obviously the printed result on the screen is the same
> > How should I should  my code?
>
> Hi.
> You need to save the seed to avoid standard initialisation. You can
> try this way.
> Hope it helps.
> Ndl
>
> module m_random
>   implicit none
>   character(len=64), parameter, private :: fic_seed="my_seed.dat"
>   !
> contains
>   !
>   subroutine reset_seed(iseed)
>     implicit none
>     integer, intent(in) :: iseed
>     call random_seed(iseed)
>   end subroutine reset_seed

Unfortunately, your code is invalid. In the above,
iseed is the SIZE argument to random_seed via positional
argument association. SIZE is an intent(out) variable.

--
steve