Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Random number in Fortran 90/95

1,663 views
Skip to first unread message

Allamarein

unread,
Jun 19, 2010, 6:15:03 AM6/19/10
to
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?

ndl_91

unread,
Jun 19, 2010, 9:06:06 AM6/19/10
to
On 19 juin, 12:15, Allamarein <matteo.diplom...@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


Tobias Burnus

unread,
Jun 19, 2010, 9:18:21 AM6/19/10
to
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

Richard Maine

unread,
Jun 19, 2010, 11:06:24 AM6/19/10
to
Tobias Burnus <bur...@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

steve

unread,
Jun 19, 2010, 1:56:20 PM6/19/10
to

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

ndl_91

unread,
Jun 19, 2010, 3:14:28 PM6/19/10
to

Thank you for your remark, I wrote this piece of code in a hurry.
Looking at it, SIZE is rather an intent(inout) variable.
Nevertheless, as I understood Allamarein's question, this code could
be a starting point.
Ndl

steve

unread,
Jun 19, 2010, 3:52:39 PM6/19/10
to

Yes, the code is a starting point. Well, Fortran Standard says
that SIZE is an INTENT(OUT) variable. Yes, an INTENT(INOUT)
variable will also work.

--
steve

Allamarein

unread,
Jun 19, 2010, 6:18:21 PM6/19/10
to
I would start from this code, suggested by Tobias's link:

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

If I understood, this subroutine generates a seed based on the actual
time.
When I got a seed, then I can call RANDOM_NUMBER in order to get a
"genuine" random number and I avoid to get the same "random" number at
any run. Perhaps I could this code (always in the website suggested by
Tobias):

program test_random_number
REAL :: r(5,5)
CALL init_random_seed() ! see example of
RANDOM_SEED
CALL RANDOM_NUMBER(r)
end program

Should it work?

Gib Bogle

unread,
Jun 20, 2010, 3:21:33 AM6/20/10
to
Allamarein wrote:
> I would get random (maybe it is more correct 'pseudorandom') numbers
> with distribution [0,1]
...
For some applications it's useful to specify the seed for the RV generator.
Then if you record the seed value you can rerun your simulation later, to
reproduce the results (this doesn't work when multi-processing).

Ian Bush

unread,
Jun 20, 2010, 3:43:57 AM6/20/10
to

Nitpick: This MAY not work when multi-processing. It depends on what
you do, and probably the implementation as well,

Ian

Allamarein

unread,
Jun 20, 2010, 5:28:30 AM6/20/10
to
I found this code:

PROGRAM ranseed

IMPLICIT NONE

! ----- variables for portable seed setting -----
INTEGER :: i_seed
INTEGER, DIMENSION(:), ALLOCATABLE :: a_seed
INTEGER, DIMENSION(1:8) :: dt_seed
! ----- end of variables for seed setting -----
REAL :: r

! ----- Set up random seed portably -----
CALL RANDOM_SEED(size=i_seed)
ALLOCATE(a_seed(1:i_seed))
CALL RANDOM_SEED(get=a_seed)
CALL DATE_AND_TIME(values=dt_seed)
a_seed(i_seed)=dt_seed(8);
a_seed(1)=dt_seed(8)*dt_seed(7)*dt_seed(6)
CALL RANDOM_SEED(put=a_seed)
DEALLOCATE(a_seed)
! ----- Done setting up random seed -----

CALL RANDOM_NUMBER(r)
WRITE(6,*) 'random number is ',r

END PROGRAM ranseed

If I didn't misunderstand the code registers the seed in vector
*a_seed* (in my case SIZE=4, hence *i_seed* = 4)
Then it replaces the first and last position of the original seed with
a muddle coming from my clock.
Therefore I should have a different seed at each run and afterwards a
different random number.
Have I realized?

steve

unread,
Jun 20, 2010, 12:27:28 PM6/20/10
to
On Jun 20, 2:28 am, Allamarein <matteo.diplom...@gmail.com> wrote:
>   ! ----- Set up random seed portably -----
>   CALL RANDOM_SEED(size=i_seed)
>   ALLOCATE(a_seed(1:i_seed))
>   CALL RANDOM_SEED(get=a_seed)
>   CALL DATE_AND_TIME(values=dt_seed)
>   a_seed(i_seed)=dt_seed(8);
> a_seed(1)=dt_seed(8)*dt_seed(7)*dt_seed(6)
>   CALL RANDOM_SEED(put=a_seed)
>   DEALLOCATE(a_seed)

> If I didn't misunderstand the code registers the seed in vector


> *a_seed*  (in my case SIZE=4, hence *i_seed* = 4)
> Then it replaces the first and last position of the original seed with
> a muddle coming from my clock.
> Therefore I should have a different seed at each run and afterwards a
> different random number.
> Have I realized?

dt_seed(8) will be in the range [0:999]. The product of
dt_seed(8)*dt_seed(7)*dt_seed(6) will be the range of
[0:3536460]. If the quality of implement of the PRNG in
your compiler depends on higher bits in the seeds or
has pathlogical behavior for a value of 0, then the above
may not produced the desired effect. I would at least
add 1 to both to prevent the 0 case, and possibly
use the hour, day, and month to increase the ranges
and maybe mix in a little system_clock(count).

--
steve

Gib Bogle

unread,
Jun 20, 2010, 6:04:04 PM6/20/10
to

True. I thought of that as I wrote, but chose laziness.

Uno

unread,
Jun 27, 2010, 6:07:49 PM6/27/10
to
Richard Maine wrote:
> Tobias Burnus <bur...@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.
>

It sounds like an opportunity squandered. I'd be curious what you would
like it to have said.

In C, random numbers are ints between 0 and RAND_MAX. Keith Thompson
writes that it simply underlaid the process that these numbers were to
be random. It's not written in their standard anywhere.

Do pseudorandoms in fortran have to have a flat pdf on [0,1) according
to the fortran standard?
--
Uno

Richard Maine

unread,
Jun 27, 2010, 6:57:30 PM6/27/10
to
Uno <merril...@q.com> wrote:
[about the vagueness in Fortran's definition of random numbers]

> It sounds like an opportunity squandered. I'd be curious what you would
> like it to have said.

I have not bothered to try to craft appropriate words that aren't going
to get used. Nor do I plan to. It seems like a pointless exercise. For
similar reasons, I haven't even wasted much time in thinking about how I
would have liked Fortran's random number stuff to have worked. I don't
even recall for sure exactly what the author of the words in the Fortran
standard said that he intended. There are at least some arguments on
multiple sides (at least 2 - maybe more).

The only thing I have to say that is that I would have liked for
whatever it said to have been unambiguous.

> In C, random numbers are ints between 0 and RAND_MAX. Keith Thompson
> writes that it simply underlaid the process that these numbers were to
> be random. It's not written in their standard anywhere.

Keith is normally more precise than that. I suppose that he might have
been sloppy enough to refer to numbers being "random", but that would at
least minorly surprise me. I'd guess it more likely that you are
misquoting him. Note that "pseudorandom" is not the same thing as
"random."



> Do pseudorandoms in fortran have to have a flat pdf on [0,1) according
> to the fortran standard?

Is there some reason you don't just look in the standard or one of the
references about it instead of asking me? It isn't as though this
particular information isn't in other that the most obvious place or is
stated in other than the most obvious manner.

I often try to give answers to questions of subtle (or even
not-so-subtle) interpretation or of just finding something that is
buried in an obscure place in the standard. Those kinds of questions
take advantage of my experience/expertise/whatever. But I don't see why
I should provide straightforward reading service. If I wanted to make
sure that my answer was actually correct, I'd have to go look it up,
just like you would. On doing so, I do see that my recollection was
correct, but doing the same check as I did is left as an exercise for
the student on the principle of teaching him how to fish.

Uno

unread,
Jun 27, 2010, 8:19:18 PM6/27/10
to
Richard Maine wrote:
> Uno <merril...@q.com> wrote:
> [about the vagueness in Fortran's definition of random numbers]
>> It sounds like an opportunity squandered. I'd be curious what you would
>> like it to have said.
>
> I have not bothered to try to craft appropriate words that aren't going
> to get used. Nor do I plan to. It seems like a pointless exercise. For
> similar reasons, I haven't even wasted much time in thinking about how I
> would have liked Fortran's random number stuff to have worked. I don't
> even recall for sure exactly what the author of the words in the Fortran
> standard said that he intended. There are at least some arguments on
> multiple sides (at least 2 - maybe more).
>
> The only thing I have to say that is that I would have liked for
> whatever it said to have been unambiguous.

Is there something ambiguous about the absence of words?


>
>> In C, random numbers are ints between 0 and RAND_MAX. Keith Thompson
>> writes that it simply underlaid the process that these numbers were to
>> be random. It's not written in their standard anywhere.
>
> Keith is normally more precise than that. I suppose that he might have
> been sloppy enough to refer to numbers being "random", but that would at
> least minorly surprise me. I'd guess it more likely that you are
> misquoting him. Note that "pseudorandom" is not the same thing as
> "random."

No, he's mathematically as helpless as you are. What he said was in
context, but I think I got the gist, and I did consider being an
appropriate editor when I typed it.


>
>> Do pseudorandoms in fortran have to have a flat pdf on [0,1) according
>> to the fortran standard?
>
> Is there some reason you don't just look in the standard or one of the
> references about it instead of asking me? It isn't as though this
> particular information isn't in other that the most obvious place or is
> stated in other than the most obvious manner.
>
> I often try to give answers to questions of subtle (or even
> not-so-subtle) interpretation or of just finding something that is
> buried in an obscure place in the standard. Those kinds of questions
> take advantage of my experience/expertise/whatever. But I don't see why
> I should provide straightforward reading service. If I wanted to make
> sure that my answer was actually correct, I'd have to go look it up,
> just like you would. On doing so, I do see that my recollection was
> correct, but doing the same check as I did is left as an exercise for
> the student on the principle of teaching him how to fish.
>

http://i45.tinypic.com/23v0xsh.png

I find none of this straightforward reading. Whatever comes out of the
can to read a .pdf on ubuntu has a *terrible* search capability.

I've tried to upgrade this capacity but have failed twice.
--
Uno

Jason Riedy

unread,
Jun 28, 2010, 6:04:14 PM6/28/10
to
And Richard Maine writes:
> I often try to give answers to questions of subtle (or even
> not-so-subtle) interpretation or of just finding something that is
> buried in an obscure place in the standard.

Here's one for you, which I cannot find but expect is not specified: Do
you happen to know if the statistical interplay between random numbers
and images are specified? I haven't found anything, and I suspect the
issue was either ignored or so contentious that it wasn't included.

Considering the spec for random_number doesn't mention images or
co-arrays, users could assume a fancy parallel generator. (Or my UPC
background may color my expectations for passing co-arrays to
subroutines.) So many people take parallel random number generation for
granted...

Jason

Richard Maine

unread,
Jun 28, 2010, 6:21:07 PM6/28/10
to
Jason Riedy <ja...@acm.org> wrote:

> And Richard Maine writes:
> > I often try to give answers to questions of subtle (or even
> > not-so-subtle) interpretation or of just finding something that is
> > buried in an obscure place in the standard.
>
> Here's one for you, which I cannot find but expect is not specified: Do
> you happen to know if the statistical interplay between random numbers
> and images are specified? I haven't found anything, and I suspect the
> issue was either ignored or so contentious that it wasn't included.

I haven't been directly involved with much after f2003, and in
particular, with the coarray stuff. (In fact, until I saw your later
mention of coarrays, I didn't pick up what you were talking about when
you said "images". Nothing wrong with your usage; I just haven't been
imersed in it enough that the term makes coarray stuff imediately pop
into my mind. My initial reaction was to wonder why anyone thought the
Fortran standard would say anything about picture images.)

My off-hand guess is that nobody even thought about it, but that's not
based on any real data. It is just the kind of thing I'd have expected
to get overlooked.

glen herrmannsfeldt

unread,
Jun 28, 2010, 6:28:23 PM6/28/10
to
Jason Riedy <ja...@acm.org> wrote:
(snip)


> Here's one for you, which I cannot find but expect is not specified: Do
> you happen to know if the statistical interplay between random numbers
> and images are specified? I haven't found anything, and I suspect the
> issue was either ignored or so contentious that it wasn't included.

(from Fortran 2003)

"Returns one pseudorandom number or an array of pseudorandom
numbers from the uniform distribution over the range 0 x < 1."

(There is a <= in there that may or may not show up.)

It doesn't say anything about the quality if the generated
numbers, other than the range and uniform distribution.

> Considering the spec for random_number doesn't mention images or
> co-arrays, users could assume a fancy parallel generator. (Or my UPC
> background may color my expectations for passing co-arrays to
> subroutines.) So many people take parallel random number generation for
> granted...

I believe co-arrays came in Fortran 2008, so you might look there.
It would seem that two possibilities are a separate generator (seed)
for each image, or a synchronization process for a single generator.
With appropriate seeding the separate generators should generate
a repeatable sequence, where the synchronized single generator
likely won't.

My guess is that this is a quality of implementation issue.
(or user preference, for that matter)

-- glen

GaryScott

unread,
Jun 28, 2010, 6:43:26 PM6/28/10
to
On Jun 28, 5:21 pm, nos...@see.signature (Richard Maine) wrote:
> Jason Riedy <ja...@acm.org> wrote:
> > And Richard Maine writes:
> > > I often try to give answers to questions of subtle (or even
> > > not-so-subtle) interpretation or of just finding something that is
> > > buried in an obscure place in the standard.
>
> > Here's one for you, which I cannot find but expect is not specified: Do
> > you happen to know if the statistical interplay between random numbers
> > and images are specified?  I haven't found anything, and I suspect the
> > issue was either ignored or so contentious that it wasn't included.
>
> I haven't been directly involved with much after f2003, and in
> particular, with the coarray stuff. (In fact, until I saw your later
> mention of coarrays, I didn't pick up what you were talking about when
> you said "images".
snip

So many times, the terminology choices are unfortunate. Maybe it is
the lack of depth of experience of the very small sized committee. I
don't think you choose such terminology that for the vast majority has
the meaning of a "bitmapped" picture image. Maybe a modifier would be
better (execution image?), but then the modifier will get lost as
people get sloppy.

GaryScott

unread,
Jun 28, 2010, 6:45:54 PM6/28/10
to
On Jun 28, 5:28 pm, glen herrmannsfeldt <g...@ugcs.caltech.edu> wrote:
> Jason Riedy <ja...@acm.org> wrote:
>
> (snip)
>
> > Here's one for you, which I cannot find but expect is not specified: Do
> > you happen to know if the statistical interplay between random numbers
> > and images are specified?  I haven't found anything, and I suspect the
> > issue was either ignored or so contentious that it wasn't included.
>
> (from Fortran 2003)
>
>   "Returns one pseudorandom number or an array of pseudorandom
>    numbers from the uniform distribution over the range 0  x < 1."
>
snip

My only issue would be that it should have been more accurately named
such as pseudorandom or PRAND. I would like a "truly" (or whatever
the best you can get is) random sequence generator.

> -- glen

Dan Nagle

unread,
Jun 28, 2010, 6:47:52 PM6/28/10
to
Hello,

On 2010-06-28 18:21:07 -0400, nos...@see.signature (Richard Maine) said:
>
> My off-hand guess is that nobody even thought about it, but that's not
> based on any real data. It is just the kind of thing I'd have expected
> to get overlooked.

There was a proposal for adding a STREAM=
to the rng stuff. It wasn't done because
there was too much to do compared with the number
of folks to do things. I'm not sure whether
there was a consensus on the design,
but that's another matter. It would likely
have been close to what UPC does, if that
was at all agreeable to the committee.

It may still make it into the "More Coarrays" TR
that will come along in a year or so.

--
Cheers!

Dan Nagle

glen herrmannsfeldt

unread,
Jun 28, 2010, 7:00:19 PM6/28/10
to
GaryScott <garyl...@sbcglobal.net> wrote:
(snip on RANDOM_NUMBER)

> snip

> My only issue would be that it should have been more accurately named
> such as pseudorandom or PRAND. I would like a "truly" (or whatever
> the best you can get is) random sequence generator.

Some years ago Intel had a hardware random number generator
based on a noise source and logic to remove any bias that
otherwise would appear. I believe it was in a support chip
for one of the Pentium families, not in the processor itself.

In any case, it seems to have been forgotten by now.

I would guess that the standard wouldn't require a hardware
generator, as not all systems would be able to support it.

It seems, though, that since the standard specifies pseudo-random
that a hardware noise source generator couldn't be used.

-- glen

Richard Maine

unread,
Jun 28, 2010, 7:19:49 PM6/28/10
to
GaryScott <garyl...@sbcglobal.net> wrote:

> I would like a "truly" (or whatever
> the best you can get is) random sequence generator.

That would be a bit out of line for a software standard. The question of
what "truly random" means is perhaps as much philosophical as anything,
but most definitions would rule out anything implemented purely in
software. If it is generated purely by software, then is is
pseudorandom, pretty much by definition. Sounds to me like you are
talking about a spec for a hardware peripheral. Don't hold your breath
for anything even vaguely close in the Fortran standard.

I can't interpret your "or whatever the best you can get is". Maybe that
means you aren't really talking about a hardware peripheral, but instead
are asking for a "good quality" pseudorandom generator, that being all
you can do in software. But as to exactly what the "best" one would
be...If you want the Fortran standard to specify that the best one be
used, you'd first have to get agreement on exactly what would define
such a "best" one. Methinks you are in the wrong group for that (and
that you aren't going to get agreement on a definitive answer anytime
soon.)

Phillip Helbig---undress to reply

unread,
Jun 29, 2010, 1:22:05 AM6/29/10
to
In article <1jksya9.5pgpx31gjknhqN%nos...@see.signature>,
nos...@see.signature (Richard Maine) writes:

> I haven't been directly involved with much after f2003, and in
> particular, with the coarray stuff. (In fact, until I saw your later
> mention of coarrays, I didn't pick up what you were talking about when
> you said "images". Nothing wrong with your usage; I just haven't been
> imersed in it enough that the term makes coarray stuff imediately pop
> into my mind. My initial reaction was to wonder why anyone thought the
> Fortran standard would say anything about picture images.)

I was thinking of executables.

glen herrmannsfeldt

unread,
Jun 29, 2010, 1:29:16 AM6/29/10
to
Richard Maine <nos...@see.signature> wrote:
(snip)


> I haven't been directly involved with much after f2003, and in
> particular, with the coarray stuff. (In fact, until I saw your later
> mention of coarrays, I didn't pick up what you were talking about when
> you said "images". Nothing wrong with your usage; I just haven't been
> imersed in it enough that the term makes coarray stuff imediately pop
> into my mind. My initial reaction was to wonder why anyone thought the
> Fortran standard would say anything about picture images.)

That was my first thought, too. There was some years ago much
discussion on the then-popular PRNGs being used to generate
coordinates in three-dimensions, and not being so random as
one might want. I was still trying to figure that out when
I went to the next page and found what he was asking about.

-- glen

glen herrmannsfeldt

unread,
Jun 29, 2010, 2:02:00 AM6/29/10
to
Richard Maine <nos...@see.signature> wrote:
> GaryScott <garyl...@sbcglobal.net> wrote:

>> I would like a "truly" (or whatever
>> the best you can get is) random sequence generator.

> That would be a bit out of line for a software standard. The question of
> what "truly random" means is perhaps as much philosophical as anything,
> but most definitions would rule out anything implemented purely in
> software. If it is generated purely by software, then is is
> pseudorandom, pretty much by definition. Sounds to me like you are
> talking about a spec for a hardware peripheral. Don't hold your breath
> for anything even vaguely close in the Fortran standard.

You might start on the Wikipedia page for Crypographically secure
pseudorandom number generator. Not that I believe Fortran should
require a CSPRNG, but it does describe some of the problems with
other generators.



> I can't interpret your "or whatever the best you can get is". Maybe that
> means you aren't really talking about a hardware peripheral, but instead
> are asking for a "good quality" pseudorandom generator, that being all
> you can do in software. But as to exactly what the "best" one would
> be...If you want the Fortran standard to specify that the best one be
> used, you'd first have to get agreement on exactly what would define
> such a "best" one. Methinks you are in the wrong group for that (and
> that you aren't going to get agreement on a definitive answer anytime
> soon.)

You might have a good generator with billions of bits of state,
such that it won't repeat within many times the age of the universe,
but you still need a good seed.

My complaint about the Fortran standard version is that it
doesn't provide a way to generate a good seed. That is, with most
generators there are properties that the seed should have, but
there is no way to know that for a given implementation.

-- glen

Dick Hendrickson

unread,
Jun 29, 2010, 11:06:00 AM6/29/10
to
There's some detail in 13.5

"If RANDOM SEED is called in a segment A, and either RANDOM SEED
or RANDOM NUMBER is called in segment B, then segments A and B
shall be ordered. It is processor dependent whether each image
uses a separate random number generator, or if some or all images
use common random number generators. On images that use a common
generator, the interleaving of calls to RANDOM NUMBER in unordered
segments is processor dependent."

Anyhow, it was thought about, but there's a lot of "processor dependent"
in the answer.

Dick Hendrickson

nm...@cam.ac.uk

unread,
Jul 12, 2010, 7:19:25 AM7/12/10
to
In article <88ugeo...@mid.individual.net>,

Dick Hendrickson <dick.hen...@att.net> wrote:
>On 6/28/10 5:04 PM, Jason Riedy wrote:
>> And Richard Maine writes:
>>> I often try to give answers to questions of subtle (or even
>>> not-so-subtle) interpretation or of just finding something that is
>>> buried in an obscure place in the standard.
>>
>> Here's one for you, which I cannot find but expect is not specified: Do
>> you happen to know if the statistical interplay between random numbers
>> and images are specified? I haven't found anything, and I suspect the
>> issue was either ignored or so contentious that it wasn't included.
>>
>> Considering the spec for random_number doesn't mention images or
>> co-arrays, users could assume a fancy parallel generator. (Or my UPC
>> background may color my expectations for passing co-arrays to
>> subroutines.) So many people take parallel random number generation for
>> granted...
>
>There's some detail in 13.5
>
>"If RANDOM SEED is called in a segment A, and either RANDOM SEED
>or RANDOM NUMBER is called in segment B, then segments A and B
>shall be ordered. It is processor dependent whether each image
>uses a separate random number generator, or if some or all images
>use common random number generators. On images that use a common
>generator, the interleaving of calls to RANDOM NUMBER in unordered
>segments is processor dependent."
>
>Anyhow, it was thought about, but there's a lot of "processor dependent"
>in the answer.

As the person who initiated that, I must accept the majority of any
blame! Yes, indeed, it WAS thought about, and I have some track
record to do with parallel random number generation.

The reason that the matter is processor dependent is that there are
three main approaches to parallel pseudo-random number generation:

1) To use the same generator for all threads, possibly with
different initial seeds.

2) To use a proper parallel generator, with pseudo-independence
between the threads.

3) To use a single generator, and for each thread to take numbers
from it as it needs it.

It is not commonly realised, but approach (3) is FAR more reliable
than approach (1) though not, of course, as reliable as approach (2).

There were people who wanted the standard to specify approach (1) and
I and some others objected strongly, not just for that reason, but
because approach (3) is arguably the most appropriate for a shared
memory coarray implementation. So the specification was written to
allow all three, and to leave the matter as 'quality of implementation',
exactly as for serial random numbers and the intrinsic functions.


Regards,
Nick Maclaren.

Jason Riedy

unread,
Jul 12, 2010, 11:10:55 AM7/12/10
to
And Nick Maclaren writes:
> It is not commonly realised, but approach (3) is FAR more reliable
> than approach (1) though not, of course, as reliable as approach (2).

No kidding. I've run into many problems lately with "random" data being
so far from even pseudorandom... Hey, look, we generate a mountain of
duplicate graph edges!

> There were people who wanted the standard to specify approach (1) and
> I and some others objected strongly, not just for that reason, but
> because approach (3) is arguably the most appropriate for a shared
> memory coarray implementation. So the specification was written to
> allow all three, and to leave the matter as 'quality of implementation',
> exactly as for serial random numbers and the intrinsic functions.

And now the burden is on us app/library writers to provide our own for
portable correctness. I know well that the right but difficult / slow
thing is kept as a quality-of-implementation issue, but it sucks for us.
Kinda. I also know that not all parallel generators will look correct
for all uses, so...

But there are parallel benchmarks on their way out that rely on
pseudorandom numbers and utterly ignore parallel PRNG issues. The same
folks who want to ignore the issues also want to make cheating
impossible. Kinda funny, in an "OMFG not *again*" way.

Thanks for all the clarifications!

Jason

nm...@cam.ac.uk

unread,
Jul 12, 2010, 11:15:45 AM7/12/10
to
In article <87wrt0b...@NaN.sparse.dyndns.org>,

Jason Riedy <ja...@acm.org> wrote:
>
>> It is not commonly realised, but approach (3) is FAR more reliable
>> than approach (1) though not, of course, as reliable as approach (2).
>
>No kidding. I've run into many problems lately with "random" data being
>so far from even pseudorandom... Hey, look, we generate a mountain of
>duplicate graph edges!

Yup.

>> There were people who wanted the standard to specify approach (1) and
>> I and some others objected strongly, not just for that reason, but
>> because approach (3) is arguably the most appropriate for a shared
>> memory coarray implementation. So the specification was written to
>> allow all three, and to leave the matter as 'quality of implementation',
>> exactly as for serial random numbers and the intrinsic functions.
>
>And now the burden is on us app/library writers to provide our own for
>portable correctness. I know well that the right but difficult / slow
>thing is kept as a quality-of-implementation issue, but it sucks for us.
>Kinda. I also know that not all parallel generators will look correct
>for all uses, so...

I have tried thinking of how one could specify quality in standardese,
and failed dismally. It could be done for the numerical intrinsics,
but that is an easier task (technically) - the chances of getting
consensus are negligible, though.


Regards,
Nick Maclaren.

0 new messages