You are on page 1of 19

Random

Numbers (2/3)
Non-uniform Distribu/ons
Sebas4ano Pila4
spila&@ictp.it
Room: 245 2nd Floor

/afs/ictp/public/s/spila&/Lecture_RN2.pdf

OPTIONAL ARGUMENTS AND KEYWORDS


Subrou&nes and func&ons can have op&onal arguments.
By default, values are assigned by order.
Formal names used in the procedure can be used as keyword to make explicit assignment.
Use of keyword is compulsory if op&onal argument is skipped in the middle of argument list.
MODULE TESTFUNCTION!
implicit none!
public :: testfunc!
contains!

PROGRAM TESTOPTIONALARGUMENTS!
USE TESTFUNCTION!
IMPLICIT NONE!
REAL :: mya,myc!
INTEGER :: myb!
!

real function testfunc(a, b, c) result(foo)!


implicit none!
real,
intent(in) :: a!
integer, intent(in), optional :: b!
real,
intent(in), optional :: c!

!
mya = 2.0!
myb = 2!
myc = 3.5!
!
PRINT*,
PRINT*,
PRINT*,
PRINT*,
PRINT*,

"f(a)
"f(a,b)
"f(a,c)
"f(a,b,c)
"f(a,b,c)

=
=
=
=
=

",
",
",
",
",

testfunc(mya)!
testfunc(mya,
testfunc(mya,
testfunc(mya,
testfunc(mya,

!
if (present(b)) then!
foo = a**b!
else!
foo = a!
end if!

myb)!
c = myc)!
myb, myc)!
c = myc, b = myb)!

!
END PROGRAM!

user$./a.out
f(a) = 5.000000
f(a,b) = 7.000000
f(a,c) = 5.500000
f(a,b,c) = 7.500000
f(a,b,c) = 7.500000

if (present(c)) then!
foo = foo + c!
else!
foo = foo + 3.0!
end if!
end function testfunc!
!
END MODULE!

GENERIC INTERFACE FOR RANDOM NUMBER GENERATOR IN F90 >


(here details for Intel Fortran Compiler)

CALL RANDOM_SEED ([size] [, put] [, get])


size (Output; op/onal) Must be scalar and of type integer. Set to the number of





integers (N) that the processor uses to hold the value of the seed.
put (Input; op/onal) Must be an integer array of rank one and size greater





than or equal to N. It is used to reset the value of the seed.
get (Output; op/onal) Must be an integer array of rank one and size greater





than or equal to N. It is set to the current value of the seed.
No more than one argument can be specied.
If no argument is specied ( CALL RANDOM_SEED()) a random number based on the date
and &me is assigned to the seed (Intel).
You can determine the size of the array the processor uses to store the seed by calling
RANDOM_SEED with the size argument.

CALL RANDOM_NUMBER (R)


R (Output) Must be of type real. It can be a scalar or an array
variable. It is set to contain pseudorandom numbers from the uniform
distribu/on within the range 0 <= x < 1.

PROGRAM IntrinsicRNG!
IMPLICIT NONE!
INTEGER :: i, usedsize!
INTEGER, ALLOCATABLE, DIMENSION(:) :: myseed, copyseed !
seed for random number generator!
REAL
:: R
!
random number
!
REAL, ALLOCATABLE, DIMENSION(:)
:: Rarray
!
random array!

WRITE(6,*) "Current value of seed"!


DO i = 1, usedsize!
WRITE(6,"(I12)") copyseed(i)!
END DO!
!

CALL RANDOM_SEED( PUT = myseed )


! RE-initialize the
seed with initial values!
WRITE(6,*) "The seed has been re-initialized"!
ALLOCATE(Rarray(4))!
CALL RANDOM_NUMBER( Rarray )
! we get a random
array of dim 4!
WRITE(6,"(A20,4F12.8)") "Random array: ", Rarray!

CALL RANDOM_SEED( SIZE = usedsize )


! ask the dimension
used for the seed!
WRITE(6,*) "The dimension of the seed is = ", usedsize!
ALLOCATE(myseed(usedsize))!
!
! we define "our" seed!
DO i = 1, usedsize!
myseed(i) = 1234*i - 543*i!
END DO!
! write "our" seed on screen!
WRITE(6,*) "Our choice of the seed is: "!
DO i = 1, usedsize!
WRITE(6,"(I12)") myseed(i)!
END DO!
!
CALL RANDOM_SEED( PUT = myseed )
!CALL RANDOM_SEED()

! initialize the seed!


! default seed is used!

!
DO i = 1, 4!
CALL RANDOM_NUMBER( R )!
WRITE(6,"(A20,I3,A6,F12.8)") "Random Number ",i," is = ",
R!
END DO!
!
ALLOCATE(copyseed(usedsize))!
CALL RANDOM_SEED( GET = copyseed ) !query current seed!
!
! write on screen the current seed!

!
END PROGRAM!

We learned how to generate random numbers


between [0,1)
Can get other uniform distribu&ons,
uniform x in [a,b):

x=a+(b-a)u where u is a r.n. in [0,1)

Non-uniform random numbers

Q: How can we get a random number x distributed with


a probability distribu&on f(x) in the interval [xmin,xmax]
from a uniform random number u?

Transforma4on method
Create random numbers with distribu&on f(x)
f(x)dx: probability of producing r.n. between x and x+dx
We need a rela&on in the form x = G(u)
u is a uniform random number [0:1)
Take the inverse,
u = G-1(x)
and dieren&ate,
du = [G-1(x)] dx = f(x) dx

Note: inverse
=> G-1(G(x)) = x

Transforma4on method
x
1

Integrate, u = G (x) =

f ( x)dx

x min

We obtain the func&onal rela&on between u and x.

We need to integrate f(x)


THEN: we need to invert the func&on to get G(u).

Transforma4on method
Example 1: Exponen&al distribu&on:
x

f (x) = e x

u=

f ( x)dx = 1 e x

Inver&ng

Sample uniform r.n in [0:1): u (e.g., using linear congruent generator or beger)
Calculate: x = -log(1-u)

x is in (0:oo) distributed according to e-x

Example 2: Lorentzian distribu&on:

Inver&ng

Transforma4on method
Example 3: Gaussian distribu&on (Box-Muller method)
Impossible to invert u=G-1(x) in 1-d but possible in 2-d

2D Gaussian distribu&on:
in polar coordinates:

R 2
1
f (x, y)dxdy =
2 exp
2 RdRd
2
2

R 2
integra&ng from 0 to R (and over ): u = exp 2 +1
2



inver&ng, we
nd:

R = 2 2 log(1 u)

Extract r.n. from uniform distribu&on: u


R
Calculate
Extract r.n. from uniform distribu&on: u
Calculate = 2u

R = 2 2 log(1 u)

= 2u'
x = Rsin
x and y are Gaussian random variables

y = Rcos

Rejec4on method
If the inverse of the integral cannot be found
Less ecient (because of rejec&ons)
works only if the func&on has a nite bound
1) generate a random number x uniformly distributed in [xmin,xmax).
2) generate another r.n., call it r, in [0,1)
3) If: r < f(x) /fmax accept x
otherwise: reject and go to step 1

fmax= max(f(x))

How to generate a histogram:


If you have a distribu&on of a variable x between [xmin,xmax]:
1-Divide the x range into bins: x=(xmin-xmax)/Nbin Nbin: # of bins
2-Create an array for the histogram H[1:Nbins] (ini&alize to 0)
3-Each &me you generate x check which bin it falls into.
4-H[bin]=H[bin]+1
N
5-Normalize,
bin

NTOT = H[i]
i=1

H[bin] = H[bin]/( NTOT x )

Homework
Write a program with:
1) A func&on that generates Gaussian random numbers with = 0.5

(and mean = 0) using transforma&on method
2) The main program:
ini&alizes the seed
Generates an histogram with 60 bins, x in the range [-3:3]. Sample 200000 points.
Write the histogram in output le (60 lines)

Then, plot the data using gnuplot, save the plot on a postscript le
Send to spila&@ictp.it: the program code and the postscript le





(or send the histogram le with 60 lines instead of the postscript)





Gnuplot:
On terminal enter gnuplot
Plowng a func&on:
gnuplot> f(x) =exp(x)
gnuplot> plot f(x)
Plowng from a data le:
gnuplot> plot data.dat u 1:2 w linespoints, f(x)
Crea&ng output ps le:
gnuplot> set terminal postscript
gnuplot> set output data.ps
gnuplot> replot

Program output
1:2
2/(22gaussian.out
2)u1/2


e
xp(-
x
)/(2
exp(-x**2 / (2.*0.5**2)) /(0.5*(2.*acos(-1.))**0.5)

0.9

0.8

0.7

0.6

0.5

0.4

0.3

0.2

0.1

0
-3

-2

-1

Rejec4on method
Example: number of agempts required to return a valid value.
Probability to generate a number
between x and x+dx:
Probability that it is accepted:

Total calls =

Rejec4on method
Example: Gaussian distribu&on
-rst need to choose a nite range, e.g. 6 standard
devia&ons from the middle
For =1,
Total calls=

You might also like