Sei sulla pagina 1di 33

Computational Physics

Rubin H. Landau, Manuel J. Pez and Cristian C. Bordeianu


2007 WILEY-VCH Verlag GmbH & Co

479

Fortran 95 Codes
(Alphabetic order modified somewhat to avoid awkward continuations.)


Listing C.1: decay.f95

!
decay . f 9 0 : Spontaneous r a d i o a c t i v e decay s i m u l a t i o n
!
Program decay
I m p l i c i t none
Real * 8 : : r , ranDom , lambda
I n t e g e r : : i , j , h , n l e f t , nloop , s t a r t , seed
! S e t params ( decay r a t e , i n i t i a l no o f atoms , seed ) , p l a n t seed
lambda = 0 . 0 1
s t a r t = 1000
seed = 11168
h = 1
nloop = s t a r t
nleft = start
open ( 6 , F i l e = decay.dat )
! open output file
! loop over t i m e s and over atoms
Do j = 1 , 10000
Do i = 1 , n l e f t
r = ranDom ( seed )
I f ( r <= lambda ) then
nloop = nloop 1
Endif
End Do
! atom loop Ends
n l e f t = nloop
Write ( 6 , * ) h , , r e a l ( n l e f t ) / s t a r t
h = h + 1
I f ( n l e f t == 0 ) goto 30
End Do
30 c l o s e ( 6 )
Stop data saved in decay.dat
End Program decay

Computationyal Physics. Problem Solving with Computers (2nd edn).


Rubin H. Landau, Manuel Jos Pez, Cristian C. Bordeianu
Copyright 2007 WILEY-VCH Verlag GmbH & Co. KGaA, Weinheim
ISBN: 978-3-527-40626-5

480

C Fortran 95 Codes
Listing C.2: bessel.f95


!

b e s s e l . f 9 5 : Computation s p h e r i c a l B e s s e l f u n c t i o n s by r e c u r r e n c e

Program b e s s e l
I m p l i c i t none
Real * 8 : : step , x , xmin , xmax , up , Down, t1 , t 2
I n t e g e r : : order , s t a r t
xmin = 0 . 2 5
xmax = 4 0 . 0
step = 0.1
order = 10
s t a r t = 50
open ( 6 , F i l e = bessel.dat , S t a t u s = Unknown ) ! open output f i l e
Do x = xmin , xmax , s t e p
t 1 = Down( x , order , s t a r t )
t 2 = up ( x , order )
wr i t e ( 6 , 5 0 ) x , t1 , t 2
End Do
Close ( 6 )
50 Format ( f 1 5 . 1 0 , f 1 5 . 1 0 , f 1 5 . 1 0 )
Stop data saved in bessel.dat
End Program b e s s e l
! c a l c u l a t e using Downward r e c u r s i o n
Function Down( x , order , s t a r t )
I m p l i c i t none
I n t e g e r : : k , order , s t a r t
Real * 8 : : Down, s c a l e , x , j ( 1 0 0 )
! the a r b i t r a r y s t a r t
j ( s t a r t + 1) = 1
j ( start ) = 1
Do k = s t a r t , 2 , 1
j ( k 1 ) = ( ( 2 * k 1 . 0 ) /x ) * j ( k ) j ( k + 1 )
End Do
! s c a l e so t h a t j ( 1 ) = s i n ( x ) /x
s c a l e = ( s i n ( x ) /x ) / j ( 1 )
Down = j ( order + 1 ) * s c a l e
Return
End
! c a l c u l a t e using upward r e c u r s i o n
Function up ( x , order )
I m p l i c i t none
I n t e g e r : : k , order
Real * 8 : : up , x , one , two , t h r
one = s i n ( x ) /x
two = ( s i n ( x ) x * cos ( x ) ) /( x * x )
Do k = 1 , ( order 1 )
t h r = ( ( 2 * k + 1 . 0 ) /x ) * two one
one = two
two = t h r
End Do
up = t h r
Return
End

481

Listing C.3: diff.f95

! d i f f . f 9 0 : Forward , c e n t r a l and e x t r a p o l a t e d d i f f e r e n t i a t i o n
Program d i f f
I m p l i c i t none
Real * 8 : : f , h , r e s u l t ( 3 ) , x , xmin , xmax , x s t e p
open ( 6 , F i l e = diff.dat , S t a t u s = Unknown )
h
= 1 . e 5
xmin
= 0.0
xmax
= 7.0
xstep = 0 . 0 1
Do x = xmin , xmax , x s t e p
r e s u l t ( 1 ) = ( f ( x+h ) f ( x ) ) /h
r e s u l t ( 2 ) = ( f ( x+h/2) f ( xh /2) ) /h
r e s u l t ( 3 ) = ( 8 * ( f ( x+h/4) f ( xh/4) ) ( f ( x+h /2) f ( xh/2) ) ) / ( 3 * h )
wr i t e ( 6 , 2 0 ) x , r e s u l t ( 1 ) , r e s u l t ( 2 ) , r e s u l t ( 3 )
End Do
20 Format ( F5 . 3 , TR4 , F10 . 8 , TR4 , F10 . 8 , TR4 , F10 . 8 )
close (6)
Stop data saved in diff.dat
End Program d i f f
! function to i n t e g r a t e
Function f ( x )
I m p l i c i t none
Real * 8 f , x
f = cos ( x )
Return
End

482

C Fortran 95 Codes
Listing C.4: eqheat.f95, label


!

eqheat . f 9 0 : S o l u t i o n o f h e a t e q u a t i o n using with f i n i t e d i f f s

Program h e a t
I m p l i c i t none
Double p r e c i s i o n : : cons , ro , sph , thk , u ( 1 0 1 , 2 )
I n t e g e r : : i , k , max
open ( 9 , FILE = eqheat.dat , S t a t u s = Unknown )
sph = 0 . 1 1 3
! s p e c i f i c heat iron
thk = 0 . 1 2
! thermal c o n d u c t i v i t y i r o n
ro = 7 . 8
! density for iron
cons = thk /( sph * ro )
max = 30000
! number o f i t e r a t i o n s
! t = 0 , a l l p o i n t s a t 100 C
Do i = 1 , 100
u( i , 1) = 100.0
End Do
Do i = 1 , 2
! Endpoints always zero
u(1 , i ) = 0.0
u(101 , i ) = 0.0
End Do
! loop over time
Do k = 1 , max
! loop over space
Do i = 2 , 100
u ( i , 2 ) = u ( i , 1 ) + cons * ( u ( i + 1 , 1 ) + u ( i 1 , 1 ) 2 * u ( i , 1 ) )
End Do
I f ( (Mod( k , 1 0 0 0 ) == 0 ) . or . ( k == 1 ) ) then ! every 1000 s t e p s
Do i = 1 , 1 0 1 , 2
wr i t e ( 9 , 2 2 ) u ( i , 2 )
End Do
Write ( 9 , 2 2 )
EndIf
! new v a l u e s > old
Do i = 2 , 100
u( i , 1) = u( i , 2)
End Do
End Do
22 format ( f 1 0 . 6 )
close (9)
Stop data saved in eqheat.dat (for gnuplot)
End Program h e a t

483

Listing C.5: eqstring.f95


!

e q s t r i n g . f 9 0 : S o l u t i o n o f wave e q u a t i o n using time s t e p p i n g

Program e q s t r i n g
I m p l i c i t none
Real * 8 : : x ( 1 0 1 , 3 )
I n t e g e r : : i , j , k , max
max = 100
open ( 9 , FILE = eqstring.dat , S t a t u s = Unknown )
Do i = 1 , 101
Do j = 1 , 3
x ( i , j ) = 0.0
End Do
End Do
! initialize
Do

i = 1 , 80
x ( i , 1) = 0.00125* i
End Do
Do i = 8 1 , 101
x ( i , 1) = 0.1 0. 005* ( i 81)
End Do
! f i r s t time s t e p
i = 2 , 100
x ( i , 2 ) = x ( i , 1 ) + 0 . 5 * ( x ( i +1 , 1 ) + x ( i 1, 1 ) 2 . * x ( i , 1 ) )
End Do
! o t h e r time s t e p s
Do k = 1 , max
Do i = 2 , 100
x ( i , 3 ) = 2 . * x ( i , 2 ) x ( i , 1 ) + ( x ( i + 1 , 2 ) + x ( i 1 ,2) 2 . * x ( i , 2 ) )
End Do
Do i = 1 , 101
x ( i , 1) = x ( i , 2)
! new > old
x ( i , 2) = x ( i , 3)
End Do
I f ( modulo ( k , 1 0 ) == 0 ) then
! output data every 10 s t e p s
Do i = 1 , 101
wr i t e ( 9 , 1 1 ) x ( i , 3 )
End Do
write ( 9 , * )
Endif
End Do
11 format ( e12 . 6 )
close (9)
Stop data saved in eqstring.dat (for gnuplot)
End Program e q s t r i n g
Do

484

C Fortran 95 Codes


!

Listing C.6: exp-bad.f95


expbad . f 9 0 : c a l c u l a t i n g exp( x ) as a f i n i t e sum , bad a l g o r i t h m

Program expbad
I m p l i c i t none
! min = accuracy , x step , max i n x , up numer , down denomin .
Real * 8 : : down , min , max , step , sum , up , x
Integer : : i , j
min = 1E 10
max = 1 0 .
step = 0.1
open ( 6 , F i l e = exp-bad.dat , S t a t u s = Unknown )
! summation
Do x = 0 , max , s t e p
sum = 1
i = 0
down = 1
up = 1
! while loop may never s t o p
Do while ( ( sum == 0 ) . or . ( abs ( ( up/down) /sum ) > min ) )
i = i + 1
down = 1
up = 1
Do j = 1 , i
up
= up * x
down = down * j
End Do
sum = sum + up/down
End Do
w r i t e ( 6 , * ) x , sum
End Do
close (6)
Stop data saved in exp-bad.dat
End Program expbad



!

Listing C.7: exp-good.f95


expgood . f 9 0 : c a l c u l a t e e^ x as a f i n i t e sum , good a l g o r i t h m

Program expgood
I m p l i c i t none
Real * 8 : : element , min , max , step , sum , x
Integer : : n
min = 1E 10
max = 1 0 .
step = 0.1
open ( 6 , F i l e = exp-good.dat , S t a t u s = Unknown )
! summation
Do x = 0 , max , s t e p
sum
= 1
element = 1

485

n = 0
! while loop may never s t o p
Do while ( ( abs ( element/sum ) > min ) . or . ( sum . eq . 0 ) )
n = n + 1
element = element * ( x ) /n
sum
= sum + element
End Do
w r i t e ( 6 , * ) x , sum
End Do
close (6)
Stop data saved in exp-good.dat
End Program expgood

Listing C.8: fit.f95


! f i t . f 9 5 : L e a s t square f i t
Program f i t

I m p l i c i t none
Integer : : i
Real * 8 : : s , sx , sy , sxx , sxy , d e l t a , i n t e r , s l o p e
Real * 8 : : x ( 1 2 ) , y ( 1 2 ) , d ( 1 2 )
Data y /328 , 1 8 7 , 8 2 1 , 7 8 , 8 8 , 6 , 5 , 8 2 , 2 , 0 . 1 , 8 4 , 1/ ! y v a l u e s
Do i = 1 , 12
! values x
x ( i ) = i *10 5
End Do
! input d e lt a y
Do i = 1 , 12
d( i ) = 1.
End Do
s = 0.0;
sx = 0 . ;
sy = 0 .
sxx = 0 .
sxy = 0 .
! c a l c u l a t e sums
Do i = 1 , 12
s = s
+
1 / ( d ( i ) *d ( i ) )
sx
= sx +
x ( i ) / (d( i ) *d( i ) )
sy
= sy +
y ( i ) / (d( i ) *d( i ) )
sxx = sxx + x ( i ) * x ( i ) / ( d ( i ) * d ( i ) )
sxy = sxy + x ( i ) * y ( i ) / ( d ( i ) * d ( i ) )
End Do
! calculate coefficients
d e l t a = s * sxx sx * sx
slope =
( s * sxy sx * sy ) / d e l t a
i n t e r = ( sxx * sy sx * sxy ) / d e l t a
w r i t e ( * , * ) intercept = , i n t e r
w r i t e ( * , * ) slope = , s l o p e
w r i t e ( * , * ) correlation = , sx/ s q r t ( sxx * s )
Stop fit
End Program f i t

486

C Fortran 95 Codes


!
!
!
!
!
!
!
!

Listing C.9: gauss.f95


gauss . f 9 0 : P o i n t s and weights f o r Gaussian quadrature
r e s c a l e s t h e gauss l e g e n d r e g r i d p o i n t s and weights
npts
number o f p o i n t s
j o b = 0 r e s c a l l i n g uniformly between ( a , b )
1 f o r i n t e g r a l ( 0 , b ) with 50% p o i n t s i n s i d e ( 0 , ab /( a + b ) )
2 f o r i n t e g r a l ( a , i n f ) with 50% i n s i d e ( a , b + 2 a )
x, w
output g r id p o i n t s and weights .

s u b r o u t i n e gauss ( npts , job , a , b , x , w)


I n t e g e r : : npts , job , m, i , j
Real * 8 : : x ( npts ) , w( npts ) , a , b , x i
Real * 8 : : t , t1 , pp , p1 , p2 , p3 , a j
Real * 8 : : eps , pi , zero , two , one , h a l f , q u a r t e r
parameter ( p i = 3 . 1 4 1 5 9 2 6 5 3 5 8 9 7 9 3 2 3 8 4 6 2 6 4 3 3 8 3 2 8 , eps = 3 . 0 E 1 4 )
parameter ( zero = 0 . d0 , one = 1 . d0 , two = 2 . d0 )
parameter ( h a l f = 0 . 5 d0 , q u a r t e r = 0 . 2 5 d0 )
m = ( npts + 1 ) /2
Do i = 1 , m
t = cos ( p i * ( i q u a r t e r ) /( npts + h a l f ) )
10 continue
p1 = one
p2 = zero
a j = zero
Do j = 1 , npts
p3 = p2
p2 = p1
a j = a j + one
p1 = ( ( two * a j one ) * t * p2 ( a j one ) * p3 ) / a j
End Do
pp = npts * ( t * p1 p2 ) /( t * t one )
t1 = t
t = t 1 p1/pp
I f ( abs ( t t 1 ) > eps ) goto 10
x( i ) = t
x ( npts + 1 i ) = t
w( i ) = two / ( ( one t * t ) * pp * pp )
w( npts + 1 i ) = w( i )
End Do
! r e s c a l e grid points
s e l e c t case ( j o b )
! s c a l e t o ( a , b ) uniformly
case ( 0 )
Do i = 1 , npts
x ( i ) = x ( i ) * ( b a ) /two + ( b + a ) /two
w( i ) = w( i ) * ( b a ) /two
End Do
! s c a l e t o ( 0 , b ) with 50% p o i n t s i n s i d e ( 0 , ab /( a + b ) )
case ( 1 )
Do i = 1 , npts
xi = x ( i )
x ( i ) = a * b * ( one + x i ) /( b + a ( b a ) * x i )
w( i ) = w( i ) * two * a * b * b / ( ( b + a (ba ) * x i ) * ( b + a ( ba ) * x i ) )

487

End Do
! s c a l e t o ( a , i n f ) with 50% i n s i d e ( a , b + 2 a )
case ( 2 )
Do i = 1 , npts
xi = x ( i )
x ( i ) = ( b * x i + b + a + a ) /( one x i )
w( i ) = w( i ) * two * ( a + b ) / ( ( one x i ) * ( one x i ) )
End Do
End s e l e c t
Return
End



!

Listing C.10: int10d.f95


i n t 10d . f 9 0 : Ten dimensional i n t e g r a t i o n using Monte Carlo

Program i n t 1 0 d
I m p l i c i t none
In t e g e r : : m = 16 , k
Real * 8 : : s , i n t e g ( 1 6 )

! number o f t r i a l s

s = 0.
Do k = 1 , m
c a l l montecarlo ( i n t e g , k ) ;
s = s + integ (k )
End Do
w r i t e ( * , * ) s/m
End Program i n t 1 0 d
s u b r o u t i n e montecarlo ( i n t e g , k )
I m p l i c i t none
I n t e g e r : : i , j , k , max = 65536
Real * 8 : : x , y , sum , ranDom , i n t e g ( 1 6 )
x = 0.
y = 0.
sum = 0 .
Do i = 1 , max
x = 0

! reset x
! sum 10 x v a l u e s

Do j = 1 , 10
x = x + ranDom ( )
End Do
! square and sum up
y = y + x*x
sum = sum + y/ i ;
End Do
i n t e g ( k ) = sum/max
write ( * , * ) k , integ ( k )
End

488

C Fortran 95 Codes
Listing C.11: harmos.f95


!
!

harmos . f 9 0 : S o l v e s t dependent Schro eqtn f o r Gaussian wavepacket


i n harmonic o s c i l l a t o r p o t e n t i a l we l l

Program harmos
I m p l i c i t None
Real * 8 : : psr ( 7 5 0 , 2 ) , p s i ( 7 5 0 , 2 ) , v ( 7 5 0 ) , p2 ( 7 5 0 )
Real * 8 : : pi , dx , k0 , dt , x
Complex : : exc , z i
I n t e g e r : : max , i , j , n
Open ( 9 , FILE = harmos.dat , S t a t u s = Unknown )
pi
= 3 . 1 4 1 5 9 2 6 5 3 5 8 9 7 9 3 2 3 8 5 E0
zi
= cmplx ( 0 . , 1 . )
dx
= 0.02
k0
= 3 * pi
! i n i t i a l momentum
dt
= dx * dx / 4 .
max
= 750
Do i = 1 , max
Do j = 1 , 2
psi ( i , j ) = 0.
psr ( i , j ) = 0 .
End Do
End Do
! i n i t i a l conditions
x
= 7.5
Do i = 1 , max
exc = exp ( z i * k0 * x )
psr ( i , 1 ) = r e a l ( exc * exp ( 0 . 5 * ( x / 0 . 5 ) * * 2 ) ) ! r e a l wave Function
p s i ( i , 1 ) = aimag ( exc * exp ( 0 . 5 * ( x / 0 . 5 ) * * 2 ) ) ! imag wave Function
v( i )
= 5.* x*x
! potential
x
= x + dx
End Do
! propagate s o l u t i o n in time
Do n = 1 , 20000
Do i = 2 , max 1
! r e a l p a r t psr and t h e p r o b a b i l i t y p2
psr ( i , 2 ) = psr ( i , 1 ) dt * ( p s i ( i + 1 , 1 ) + p s i ( i 1 , 1 ) &
2 . * p s i ( i , 1 ) ) /( dx * dx ) + dt * v ( i ) * p s i ( i , 1 )
p2 ( i ) = psr ( i , 1 ) * psr ( i , 2 ) + p s i ( i , 1 ) * p s i ( i , 1 )
End Do
Do i = 2 , max 1 ! imag p a r t
p s i ( i , 2 ) = p s i ( i , 1 ) + dt * ( psr ( i + 1 , 2 ) + psr ( i 1 , 2 ) &
2 . * psr ( i , 2 ) ) /( dx * dx ) dt * v ( i ) * psr ( i , 2 )
End Do
! output ea 2000 s t e p s
I f ( ( n == 1 ) . or . ( modulo ( n , 2 0 0 0 ) == 0 ) ) Then
Do i = 2 , max 1 , 10
Write ( 9 , 1 1 ) p2 ( i ) + 0 . 0 0 1 5 * v ( i )
End Do
Write ( 9 , * )
EndIf
Do i = 1 , max ! new > old
psi ( i , 1) = psi ( i , 2)
psr ( i , 1 ) = psr ( i , 2 )
End Do

489

End Do
11 Format ( E12 . 6 )
Close ( 9 )
Stop data saved in harmos.dat (for gnuplot)
End

Listing C.12: lagrange.f95


!

l a g r a n g e . f : Langrange i n t e r p o l a t i o n o f c r o s s t a b l e

Program l a g r a n g e
I m p l i c i t none
Real * 8 : : i n t e r , x , x i n ( 9 ) , yin ( 9 )
Integer : : i , e
e = 9
open ( 6 , F i l e = lagrange.dat , S t a t u s = Unknown )
! Input data
data x i n /0 , 8 5 , 5 8 0 , 7 5 8 , 8 0 0 , 1 2 8 5 , 8 5 0 , 7 9 5 , 82/
data yin / 1 8 . 6 , 1 6 , 8 5 , 8 3 . 5 , 5 8 . 8 , 1 9 . 9 , 1 0 . 8 , 8 8 . 2 5 , 4 . 7 /
! Calculate f ( x )
Do i = 0 , 1000
x = i *0.2
w r i t e ( 6 , * ) x , i n t e r ( xin , yin , e , x )
End Do
Close ( 6 )
Stop data saved in lagrange.dat
End Program l a g r a n g e
! Evaluate i n t e r p o l a t i o n function ( x )
Function i n t e r ( xin , yin , e , x )
I m p l i c i t none
Integer : : i , j , e
Real * 8 : : i n t e r , lambda ( 9 ) , x i n ( 9 ) , yin ( 9 ) , x
inter = 0
Do i = 1 , e
lambda ( i ) = 1
Do j = 1 , e
I f ( i . neqv . j ) then
lambda ( i ) = lambda ( i ) * ( ( x x i n ( j ) ) /( x i n ( i ) x i n ( j ) ) )
Endif
End Do
i n t e r = i n t e r + ( yin ( i ) * lambda ( i ) )
End Do
Return
End

490

C Fortran 95 Codes
Listing C.13: integ.f95

! i n t e g r a t e . f 9 0 : I n t e g r a t e exp( x ) using trap , Simp and Gauss r u l e s


!
Need t o add i n Gauss . f 9 5

Program i n t e g r a t e
I m p l i c i t none
Real * 8 : : t r a p e z , simpson , quad , r1 , r2 , r 3
Real * 8 : : theo , vmin , vmax
Integer : : i

! declarations

theo = 0 . 6 3 2 1 2 0 5 5 8 8 2 9
! t h e o r e t i c a l r e s u l t , i n t e g r a t i o n range
vmin = 0 .
vmax = 1 .
open ( 6 , F i l e = integ.dat , S t a t u s = Unknown )
! c a l c u l a t e i n t e g r a l using both methods f o r s t e p s = 3 . . 5 0 1
Do i = 3 , 501 , 2
r 1 = t r a p e z ( i , vmin , vmax )
r 1 = abs ( r 1 theo )
r 2 = simpson ( i , vmin , vmax )
r 2 = abs ( r 2 theo )
r 3 = quad ( i , vmin , vmax )
r 3 = abs ( r 3 theo )
w r i t e ( 6 , * ) i , r1 , r2 , r 3
End Do
close (6)
Stop data saved in integ.dat
End Program i n t e g r a t e
! Function we want t o i n t e g r a t e
Function f ( x )
I m p l i c i t none
Real * 8 : : f , x
f = exp ( x )
Return
End
Function t r a p e z ( i , min , max ) ! t r a p e z o i d r u l e
I m p l i c i t none
Integer : : i , n
Real * 8 : : f , i n t e r v a l , min , max , t r a p e z , x
trapez = 0
i n t e r v a l = ( ( max min ) / ( i 1 ) )
Do n = 2 , ( i 1 )
! sum midpoints
x = in t e rv al * (n 1)
trapez = trapez + f ( x ) * in t e rv al
End Do
t r a p e z = t r a p e z + 0 . 5 * ( f ( min ) + f ( max ) ) * i n t e r v a l ! add Endpoints
Return
End
! Simpson r u l e
Function simpson ( i , min , max )
I m p l i c i t none
Integer : : i , n
Real * 8 : : f , i n t e r v a l , min , max , simpson , x
simpson = 0
i n t e r v a l = ( ( max min ) / ( i 1 ) )

491

n = 2 , ( i 1) , 2
x = in t e rv al * (n 1)
simpson = simpson + 4 * f ( x )
End Do
Do n = 3 , ( i 1 ) , 2
x = in t e rv al * (n 1)
simpson = simpson + 2 * f ( x )
End Do
simpson = simpson + f ( min ) + f ( max )
simpson = simpson * i n t e r v a l /3
Return
End
Do

Function quad ( i , min , max )


I m p l i c i t none
Real * 8 : : w( 1 0 0 0 ) , x ( 1 0 0 0 )
Real * 8 : : f , min , max , quad
I n t e g e r : : i , job , n
quad = 0
job = 0
c a l l gauss ( i , job , min , max , x , w)
Do n = 1 , i
quad = quad + f ( x ( n ) ) *w( n )
End Do
Return
End

! loop f o r odd p o i n t s

! loop f o r even p o i n t s

! add t h e Endpoints

! uses Gauss p o i n t s

Listing C.14: limit.f95

!
l i m i t . f 9 0 : determines t h e machine p r e c i s i o n
!
Program l i m i t
! determines t h e machine p r e c i s i o n
I m p l i c i t none
Integer : : I , N
Real * 8 : : eps , one
N = 60
eps = 1 .
one = 1 . 0

! number o f i t e r a t i o n s N
! s e t i n i t i a l values
! add eps t o one and p r i n t r e s u l t

Do

I = 1, N
eps = eps / 2
one = 1 + eps
w r i t e ( * , * ) I , one , eps
End Do
Stop limit
End Program l i m i t

492

C Fortran 95 Codes
Listing C.15: LaplaceSOR.f95


!

LaplaceSOR . f 9 0 :

S o l v e Laplace eq with f i n i t e d i f f e r e n c e s c SOR

Program LaplaceSOR
I m p l i c i t none
I n t e g e r : : max = 4 0 , i , j , i t e r
Real * 8 : : t o l , omega , r , p ( 4 0 , 4 0 )
Open ( 6 , FILE = laplaceR.dat , S t a t u s = Unknown )
omega = 1 . 8

! Data f i l e
! SOR parameter
! c l e a r the array

Do i = 1 , max
Do j = 1 , max
p( i , j ) = 0
End Do
End Do
! p [ i ] [ 0 ] = 100 V
Do i = 1 , max
p( i , 1) = + 100.0
End Do
tol = 1.0
i t e r =1

! tolerance
! iterations

Do while ( ( t o l
tol = 0.0

>

0 . 0 0 0 0 0 1 ) . and . ( i t e r

Do i = 2 , ( max 1 )

<= 1 4 0 ) )
! x direction

! y direction
Do j = 2 , ( max 1 )
r = omega * ( p ( i , j + 1 ) + p ( i , j 1 ) + p ( i + 1 , j ) + &
p ( i 1 , j ) 4 . * p ( i , j ) ) / 4 . 0
p( i , j ) = p( i , j ) + r
I f ( abs ( r ) > t o l ) then
t o l = abs ( r )
Endif
End Do
iter = iter + 1
End Do
End Do
! wr i t e data gnuplot 3D format
Do i = 1 , max
Do j = 1 , max
write ( 6 , * ) p ( i , j )
End Do
write ( 6 , * )
End Do
close (6)
Stop data stored in laplaceR.dat (for gnuplot)
End Program LaplaceSOR

493

Listing C.16: Newton_cd.f95

! Newton_cd . f 9 0 : NewtonRaphson r o o t f i n d e r , c e n t r a l d i f f d e r i v a t i v e
!
Program Newton_cd

I m p l i c i t none
I n t e g e r : : i t , imax = 10
! Maximum number o f i t e r a t i o n s p e r m i t t e d
Real * 8 : : x , dx = 1 e 2 , eps = 1 e 6 , f1 , df , F
! x guess , must be c l o s e t o r o o t
x = 2.
Do i t = 0 , imax
f1
= F(x)
write ( * , * ) i t , x , f1

! Compute Function value

! Central d iffe re n ce derivative


df = ( F ( x + dx /2) F ( x dx /2) ) /dx
dx
=
f 1 /df
x =
x + dx
! New guess
! Check f o r convergence
I f ( abs ( F ( x ) ) <= eps
) then
w r i t e ( * , * ) eps
Stop
Endif
End Do
End Program Newton_cd
Function F ( x )
I m p l i c i t none
Real * 8 : : x , F
F = 2 * cos ( x ) x
End

Listing C.17: Newton_fd.f95

!
Newton_fd . f 9 0 : NewtonRaphson r o o t f i n d e r , forward d i f f d e r i v a t i v e
!
Program NewtonRHL_fd
I m p l i c i t none
I n t e g e r : : i t , imax = 10
! Max number i t e r a t i o n s
Real * 8 : : x , dx = 1 e 2 , eps = 1 e 6 , df , F
! Guess must be c l o s e
x = 2.
Do i t = 1 , imax
df = ( F ( x + dx ) F ( x ) ) /dx
dx
=
F ( x ) /df
x =
x + dx
write ( * , * ) i t , x , F ( x )
I f ( abs ( F ( x ) ) <= eps
w r i t e ( * , * ) eps
Stop
Endif

) then

! Forward d i f f e r e n c e d e r i v a t i v e

! New guess
! Check f o r convergence

494

C Fortran 95 Codes
End Do
End
! Find zero o f t h i s f u n c t i o n
function F ( x )
I m p l i c i t none
Real * 8 : : x , F
F = 2 * cos ( x ) x
End

Listing C.18: overflow.f95


!

overflow . f 9 0 : determine overflow and underflow l i m i t s

Program overflow
I m p l i c i t none
Integer : : I , N
Real * 8 : : under , over
N = 1024
! number o f i t e r a t i o n s , may need b i g g e r
under = 1 .
! s e t i n i t i a l values
over
= 1.
Do I = 1 , N
! c a l c underflow and overflow , output t o s c r e e n
under = under / 2
over = over * 2
w r i t e ( * , * ) I , over , under
End Do
Stop overflow
End Program overflow

Listing C.19: pond.f95


!

pond . f 9 0 :

p i v i a MonteCarlo i n t e g r a t i o n ( throwing s t o n e s )

Program pond
I m p l i c i t none
Real * 8 : : area , x , y , ranDom
I n t e g e r : : i , max , p i
max = 2000
! open f i l e , s e t i n i t i a l value , seed g e n e r a t o r
Open ( 6 , F i l e = pond.dat , S t a t u s = Unknown )
pi = 0
! e x e cu t e
Do i = 1 , max
x = ranDom ( ) * 2 1
y = ranDom ( ) * 2 1
I f ( ( x * x + y * y ) <= 1 ) then
pi = pi + 1
Endif
a r e a = 4 . * p i /Real ( i )
write ( 6 , * ) i , area
End Do
close (6)
Stop data saved in pond.dat
End Program pond

495

Listing C.20: qmc.f95


!

qmc . f 9 0 : Feynman path i n t e g r a l f o r ground s t a t e wave Function

Program qmc
I m p l i c i t none
I n t e g e r : : i , j , max , element , prop ( 1 0 0 )
Real * 8 : : change , ranDom , energy , newE , oldE , out , path ( 1 0 0 )
max = 250000
open ( 9 , FILE = qmc.dat , S t a t u s = Unknown )
! i n i t i a l path and p r o b a b i l i t y
Do j = 1 , 100
path ( j ) = 0 . 0
prop ( j ) = 0
End Do
! f i n d energy o f i n i t i a l path
oldE = energy ( path , 1 0 0 )
! p i ck random element , change by random
Do i = 1 , max
element = ranDom ( ) * 1 0 0 + 1
change
= ( ( ranDom ( ) 0 . 5 ) * 2 )
path ( element ) = path ( element ) + change
newE = energy ( path , 1 0 0 )
! f i n d new energy
! Metropolis algorithm
I f ( ( newE > oldE ) .AND. ( exp ( newE + oldE ) < ranDom ( ) ) ) then
path ( element ) = path ( element ) change
EndIf
! add up p r o b a b i l i t i e s
Do j = 1 , 100
element = path ( j ) * 1 0 + 50
prop ( element ) = prop ( element ) + 1
End Do
oldE = newE
End Do
! wr i t e output data t o f i l e
Do j = 1 , 100
out = prop ( j )
w r i t e ( 9 , * ) j 5 0 , out/max
End Do
close (9)
Stop data saved in qmc.dat
End Program qmc
! Function c a l c u l a t e s energy o f t h e system
Function energy ( array , max )
I m p l i c i t none
I n t e g e r : : i , max
Real * 8 : : energy , a r r a y ( max )
energy = 0
Do i = 1 , ( max 1 )
energy = energy + ( a r r a y ( i + 1 ) a r r a y ( i ) ) * * 2 + a r r a y ( i ) * * 2
End Do
Return
End

496

C Fortran 95 Codes
Listing C.21: rk4.f95


!

rk4 . f 9 0 :

4 th order rk s o l u t i o n f o r harmonic o s c i l l a t o r

Program o s c i l l a t o r
I m p l i c i t none
! n : number o f e q u a t i o n s , min/max i n x , d i s t : l e n g t h o f x s t e p s
! y ( 1 ) : i n i t i a l position , y ( 2 ) : i n i t i a l v e locit y
Real * 8 : : d i s t , min1 , max1 , x , y ( 5 )
Integer : : n
n = 2
min1 = 0 . 0 ; max1 = 1 0 . 0
dist = 0.1
y(1) = 1.0;
y(2) = 0.
open ( 6 , F i l e = rk4.dat , S t a t u s = Unknown )
! Do n s t e p s rk a l g o r i t h m
Do x = min1 , max1 , d i s t
c a l l rk4 ( x , d i s t , y , n )
write ( 6 , * ) x , y ( 1 )
End Do
close (6)
Stop data saved in rk4.dat
End Program o s c i l l a t o r
! End o f main Program
s u b r o u t i n e rk4 ( x , xstep , y , n )
! rk4 s u b r o u t i n e
I m p l i c i t none
Real * 8 : : deriv , h , x , xstep , y ( 5 )
Real * 8 , dimension ( 5 ) : : k1 , k2 , k3 , k4 , t1 , t2 , t 3
Integer : : i , n
h = xstep /2.0
Do i = 1 , n
k1 ( i ) = x s t e p * d e r i v ( x , y , i )
t 1 ( i ) = y ( i ) + 0 . 5 * k1 ( i )
End Do
Do i = 1 , n
k2 ( i ) = x s t e p * d e r i v ( x + h , t1 , i )
t 2 ( i ) = y ( i ) + 0 . 5 * k2 ( i )
End Do
Do i = 1 , n
k3 ( i ) = x s t e p * d e r i v ( x + h , t2 , i )
t 3 ( i ) = y ( i ) + k3 ( i )
End Do
Do i = 1 , n
k4 ( i ) = x s t e p * d e r i v ( x + xstep , t3 , i )
y ( i ) = y ( i ) + ( k1 ( i ) + ( 2 . * ( k2 ( i ) + k3 ( i ) ) ) + k4 ( i ) ) / 6 . 0
End Do
Return
End
! Function Returns d e r i v a t i v e s
Function d e r i v ( x , temp , i )
I m p l i c i t none
Real * 8 : : deriv , x , temp ( 2 )
Integer : : i
I f ( i == 1 ) d e r i v = temp ( 2 )
I f ( i == 2 ) d e r i v = temp ( 1 )
Return
End

497

Listing C.22: rk45.f95


!

rk45 . f 9 0 : ODE s o l v e r v i a v a r i a b l e s t e p s i z e rk , Tol = e r r o r

Program Rk45
I m p l i c i t none
Real * 8 : : h , t , s , hmin , hmax , Tol = 2 * 1 E 7 , Tmin = 0 . , &
Tmax = 1 0 .
Real * 8 , dimension ( 2 ) : : y , FReturn , ydumb , k1 , k2 , k3 , k4 , &
k5 , k6 , e r r
I n t e g e r : : i , Ntimes = 10
Open ( 6 , FILE = rk45.dat , S t a t u s = Unknown )
y (1) = 3.0 ; y (2) = 5.0
h = ( Tmax Tmin ) / Ntimes
hmin = h/64
hmax = h * 6 4
t = Tmin

! initialize
! t e n t a t i v e number o f s t e p s
! minimum and maximum s t e p s i z e

! output t o f i l e
Do while ( t < Tmax)
write ( * , * ) t , y ( 1 ) , y ( 2 )
write ( 6 , * ) t , y ( 1 )
I f ( ( t + h ) > Tmax ) then
h = Tmax t ! t h e l a s t s t e p
EndIf
! e v a l u a t e both RHSs and Return i n F
c a l l f ( t , y , FReturn )
Do i = 1 , 2
k1 ( i ) = h * FReturn ( i )
ydumb( i ) = y ( i ) + k1 ( i ) /4
End Do
c a l l f ( t + h/4 , ydumb, FReturn )
Do i = 1 , 2
k2 ( i ) = h * FReturn ( i )
ydumb( i ) = y ( i ) + 3 * k1 ( i ) /32 + 9 * k2 ( i ) /32
End Do
c a l l f ( t + 3 * h/8 , ydumb , FReturn )
Do i = 1 , 2
k3 ( i ) = h * FReturn ( i )
ydumb( i ) = y ( i ) + 1 9 3 2 * k1 ( i ) /2197 7 2 0 0 * k2 ( i ) / 2 1 9 7 . &
+ 7 2 9 6 * k3 ( i ) /2197
End Do
c a l l f ( t + 1 2 * h /13 , ydumb , FReturn )
Do i = 1 , 2
k4 ( i ) = h * FReturn ( i )
ydumb( i ) = y ( i ) + 4 3 9 * k1 ( i ) /216 8 * k2 ( i ) &
+ 3 6 8 0 * k3 ( i ) /513 845 * k4 ( i ) /4104
End Do
c a l l f ( t + h , ydumb , FReturn )
Do i = 1 , 2
k5 ( i ) = h * FReturn ( i )
ydumb( i ) = y ( i ) 8 * k1 ( i ) /27 + 2 * k2 ( i ) 3 5 4 4 * k3 ( i ) /2565 &
+ 1 8 5 9 * k4 ( i ) /4104 1 1 * k5 ( i ) /40
End Do
c a l l f ( t + h/2 , ydumb, FReturn )

498

C Fortran 95 Codes
Do i = 1 , 2
k6 ( i ) = h * FReturn ( i )
e r r ( i ) = abs ( k1 ( i ) /360 1 2 8 * k3 ( i ) /4275 2 1 9 7 * k4 ( i ) /75240 &
+ k5 ( i ) / 5 0 . + 2 * k6 ( i ) /55 )
End Do
I f ( ( e r r ( 1 ) < Tol ) . or . ( e r r ( 2 ) < Tol ) . or . ( h <= 2 * hmin ) ) then
! a c c e p t approximation
Do i = 1 , 2
y ( i ) = y ( i ) + 2 5 * k1 ( i ) / 2 1 6 . + 1 4 0 8 * k3 ( i ) / 2 5 6 5 . &
+ 2 1 9 7 * k4 ( i ) / 4 1 0 4 . k5 ( i ) / 5 .
End Do
t = t + h
Endif
I f ( ( e r r ( 1 ) == 0 ) . or . ( e r r ( 2 ) == 0 ) ) then
s = 0 ! t r a p d i v i s i o n by 0
else
s = 0 . 8 4 * Tol * h/ e r r ( 1 ) * * 0 . 2 5
! step size scalar
Endif
I f ( ( s < 0 . 7 5 ) . and . ( h > 2 * hmin ) ) then
h =
h / 2 . ! reduce s t e p
e l s e I f ( ( s > 1 . 5 ) . and . ( 2 * h < hmax ) ) then
h = h*2.
! increase step
Endif
! End loop
End Do
close (6)
StopData stored in rk45.dat
End Program Rk45
! PLACE YOUR FUNCTION HERE
subroutine f ( t ,
y , FReturn )
I m p l i c i t none ; Real * 8 t , y ( 2 ) , FReturn ( 2 )
FReturn ( 1 ) = y ( 2 ) ! RHS o f f i r s t e q u a t i o n
FReturn ( 2 ) = 1 0 0 * y ( 1 ) 2 * y ( 2 ) + 1 0 * s i n ( 3 * t ) ! RHS o f 2nd e q u a t i o n
Return
End

Listing C.23: random.f95


!

ranDom . f 9 0 : simple random number g e n e r a t o r , not f o r s e r i o u s work

Program random
I m p l i c i t none
I n t e g e r : : i , number , old , seed , x , y
! s e t parameters ( seed f o r g e n e r a t o r , number o f g e n e r a t e d numbers )
seed = 11
number = 1000
! open output f i l e , seed number g e n e r a t o r
open ( 6 , FILE = ranDom.dat , S t a t u s = Unknown )
old = seed
! execution
Do i = 1 , number
x = modulo ( ( 5 7 * old + 1 ) , 2 5 6 )

499

y = modulo ( ( 5 7 * x + 1 ) , 2 5 6 )
write ( 6 , * ) x , y
old = y
End Do
close (6)
Stop data saved in ranDom.dat
End Program random

Listing C.24: scatt.f95


!
!
!

s c a t t . f90 :
s c a t t e r i n g phase s h i f t i n p space from d e l t a s h e l l
p o t e n t i a l , LU decomposition with p a r t i a l p i v o t i n g .
uses gauss . f ,
LUfactor , LUSolve ( i n cl u d e d )

Program s c a t t
I n t e g e r : : n , S i z e , i , j , Row, Column
Double P r e c i s i o n : : b , Pot
Parameter ( S i z e = 3 0 0 , p i = 3 . 1 4 1 5 9 2 6 5 3 5 8 9 7 9 3 2 3 8 4 6 2 6 , b = 1 0 . 0 )
Double P r e c i s i o n : : lambda , s c a l e , ko , Temp
Double P r e c i s i o n : : F ( S i z e , S i z e ) , k ( S i z e ) , w( S i z e ) ,D( S i z e ) , r ( S i z e )
Double P r e c i s i o n : : V( S i z e ) , L ( S i z e , S i z e ) ,U( S i z e , S i z e ) , P ( S i z e , S i z e )
Integer : : PivotInfo ( Size )
! E n t e r p o t e n t i a l s t r e n g t h lambda
Write ( *
Read ( * ,
Write ( *
Read ( * ,
Write ( *
Read ( * ,
Write ( *
Read ( * ,

, * ) enter
* ) lambda
, * ) enter
*) scale
, * ) enter
* ) ko
, * ) enter
*) n

lambda
scaling factor
ko
grid size

! S e t up Gaussian i n t e g r a t i o n p o i n t s and weights


! on i n t e r v a l [ 0 , i n f ] with t h e mid p o i n t a t scale
! S e t l a s t element i n k a r r a y t o ko
c a l l gauss ( n , 2 , 0d0 , s c a l e , k , w)
!
S e t up D m a t r i x
Do i = 1 , n
D( i ) = 2 . 0 d0/ p i *w( i ) * k ( i ) * k ( i ) /( k ( i ) * k ( i ) ko * ko )
End Do
D( n + 1 ) = 0 . 0
Do j = 1 , n
D( n + 1 ) = D( n + 1 ) + w( j ) * ko * ko /( k ( j ) * k ( j ) ko * ko )
End Do
D( n + 1 ) = D( n + 1 ) * ( 2 . 0 d0/ p i )
! S e t up F m a t r i x and V v e c t o r
Do i = 1 , n
Do j = 1 , n
Pot = b * b * lambda * SIN ( b * k ( i ) ) * SIN ( b * k ( j ) )
Pot = Pot /( k ( i ) * b * k ( j ) * b )
F ( i , j ) = Pot *D( j )
I f ( i == j ) then
F ( i , j ) = F ( i , j ) + 1 . 0 d0

500

C Fortran 95 Codes
Endif
End Do
V( i ) = Pot
End Do
!
LU f a c t o r i z a t i o n . Put LU f a c t o r s o f F i n corresponding m a t r i x
!
( not e f f i c i e n t but easy ) . S t o r e p a r t i a l p i v o t i n g i n f o
!
c a l l LUfactor ( F , n , S i z e , L , U, P i v o t I n f o )
! P i v o t and s o l v e
!
Set P to i d e n t i t y matrix
Do Row = 1 , n + 1
Do Column = 1 , n + 1
P (Row, Column ) = 0
I f (Row . EQ . Column ) P (Row, Column ) = 1
End Do
End Do
! In t e r ch a n g e rows t o g e t t r u e P m a t r i x
Do Row = 1 , n
Do Column = 1 , n
Temp = P (Row, Column )
P (Row, Column ) = P ( P i v o t I n f o (Row) , Column )
P ( P i v o t I n f o (Row) , Column ) = Temp
End Do
End Do
c a l l LUSolve ( V, L , U, n , S i z e , P i v o t I n f o , r )
! output r e s u l t s
w r i t e ( * , * ) ko * ko , DATAN( r ( n ) * ko )
End Program s c a t t
!
LU f a c t o r i z a t i o n , p a r t i a l p i v o t i n g o f A i n Ax = b
s u b r o u t i n e LUfactor (A, n , S i z e , L , U, P i v o t I n f o )
I n t e g e r : : n , Column , CurrentPivotRow , CurrentRow , SwapCol , Row
I n t e g e r : : ElimCol , S i z e
Double P r e c i s i o n : : A( S i z e , S i z e ) , L ( S i z e , S i z e ) , U( S i z e , S i z e )
Integer : : PivotInfo ( Size )
Double P r e c i s i o n : : CurrentPivotValue , Swap
Do Column = 1 , n 1
CurrentPivotRow = Column
C u r r e n t P i v o t V al u e = A( CurrentPivotRow , Column )
! Determine row f o r l a r g e s t p i v o t
Do CurrentRow = Column + 1 , n
I f ( DABS(A( CurrentRow , Column ) ) . GT . C u r r e n t P i v o t V a lu e ) Then
C u r r e n t P i v o t V a l ue = DABS(A( CurrentRow , Column ) )
CurrentPivotRow = CurrentRow
Endif
End Do
P i v o t I n f o ( Column ) = CurrentPivotRow
! Swap rows so l a r g e s t value a t p i v o t
Do SwapCol = Column , n
Swap = A( Column , SwapCol )
A( Column , SwapCol ) = A( P i v o t I n f o ( Column ) , SwapCol )
A( P i v o t I n f o ( Column ) , Swapcol ) = Swap
End Do
!
! Gauss Elimin , upper t r i a n g u l a r A, unpivoted lower t r i a n g u l a r L
!
Do Row = Column + 1 , n

501

L (Row, Column ) = A(Row, Column ) /A( Column , Column )


Do ElimCol = Column + 1 , n
A(Row, ElimCol ) = A(Row, ElimCol ) &
L (Row, Column ) *A( Column , ElimCol )
End Do
End Do
End Do
! Ensure bottom r i g h t not pivoted t o 0
PivotInfo (n) = n
Do Row = 2 , n 1
! Now p i v o t t h e L
DO Column = 1 , Row 1
Swap = L (Row, Column )
L (Row, Column ) = L ( P i v o t I n f o (Row) , Column )
L ( P i v o t I n f o (Row) , Column ) = Swap
End Do
End Do
! Clean up L and U
Do Column = 1 , n
Do Row = 1 , Column
U(Row, Column ) = A(Row, Column )
L (Row, Column ) = 0
I F (Row . EQ . Column ) L (Row, Column ) = 1
End Do
Do Row = Column + 1 , n
U(Row, Column ) = 0
End Do
End Do
Return
End
! P a r t o f an LU decomposition + p a r t i a l p i v o t i n g t o s o l v e Ax = b
S u b r o u t i n e LUSolve ( b , L , U, n , S i z e , P i v o t I n f o , x )
I n t e g e r : : n , S i z e , Row, Column
Double P r e c i s i o n : : b ( S i z e ) , x ( S i z e )
Integer : : PivotInfo ( Size )
Double P r e c i s i o n : : L ( S i z e , S i z e ) , U( S i z e , S i z e )
Double P r e c i s i o n : : Temp
Do Row = 1 , n
! In t e r ch a n g e rows o f b f o r p i v o t i n g
Temp = b (Row)
b (Row) = b ( P i v o t I n f o (Row) )
b ( P i v o t I n f o (Row) ) = Temp
End Do
!
S o l v e Ly = b , where y = Ux , by forward e l i m i n a t i o n
Do Row = 2 , n
DO Column = 1 , Row 1
b (Row) = b (Row) L (Row, Column ) * b ( Column )
End Do
b (Row) = b (Row) /L (Row, Row)
End Do
!
S o l v e Ux = y by back s u b s t i t u t i o n
x ( n ) = b ( n ) /U( n , n )
Do Row = n 1 , 1 , 1
x (Row) = b (Row)
Do Column = Row + 1 , n
x (Row) = x (Row) U(Row, Column ) * x ( Column )
End Do

502

C Fortran 95 Codes
x (Row) = x (Row) /U(Row, Row)
End Do
Return
End



!
!

Listing C.25: slit.f95


s l i t . f 9 0 : S o l v e s time dependent S c h r o e d i n g e r e q u a t i o n f o r a
two dimensional Gaussian wavepacket e n t e r i n g a s l i t

Program s l i t
I m p l i c i t none
Real * 8 : : psr ( 9 1 , 9 1 , 2 ) , p s i ( 9 1 , 9 1 , 2 ) , v ( 9 1 , 9 1 ) , p2 ( 9 1 , 9 1 )
Real * 8 : : a1 , a2 , dt , dx , k0x , k0y , x0 , y0 , x , y
I n t e g e r i , j , k , max , n , time
Complex exc , z i
! i n p u t p o s i t i v e i n t p r o p o r t i o n a l t o time f o r p l o t
, * ) Enter a positive Integer from 1(initial time)
, * ) to 800 to get wave packet position at that time
* ) time
, * ) processing data for time , time
FILE = slit.dat , S t a t u s = Unknown )
! i n i t i a l i z e c o n s t a n t s and wave p a ck e t
zi
= cmplx ( 0 . 0 , 1 . 0 )
dx
= 0.2
dt
= 0 . 0 0 2 5 / ( dx * dx )
! i n i t i a l momentum , p o s i t i o n
k0x = 0 . 0 ;
k0y = 2 . 5
x0
= 0.0;
y0
= 7.0
max = 90
! cl e a r the arrays
Do i = 1 , 91
Do j = 1 , 91
Do k = 1 , 2
psi ( i , j , k) = 0.0
psr ( i , j , k ) = 0 . 0
End Do
End Do
End Do
! i n i t i a l wave f u n c t i o n
y
= 9.0
Do j = 1 , max + 1
x = 9 . 0 d0
Do i = 1 , max + 1
exc
= exp ( z i * ( k0x * x + k0y * y ) )
a1 = exp ( 0 . 5 * ( ( ( x x0 ) ) * * 2 + ( ( y y0 ) ) * * 2 ) )
psr ( i , j , 1 ) = r e a l ( a1 * exc )
! re al part
p s i ( i , j , 1 ) = aimag ( a1 * exc )
! imaginay p a r t
x
= x + dx
End Do
y = y + dx
End Do
! s e t p o t e n t i a l s l i t width : 50 40 = 10 u n i t s
Do j = 1 , max + 1
write ( *
write ( *
read ( * ,
write ( *
open ( 9 ,

503

Do

i = 1 , max + 1
I f ( ( j == 3 5 ) . and . ( ( i < 4 0 ) . or . ( i > 5 1 ) ) ) then
v( i , j ) = 0.5
else
v( i , j ) = 0.0
Endif
End Do
End Do
! propagate p s i through time
Do n = 1 , time
! compute r e a l wave p a ck e t and p r o b a b i l i t y
Do j = 2 , max
Do i = 2 , max
a2 = v ( i , j ) * p s i ( i , j , 1 ) + 2 . 0 d0 * dt * p s i ( i , j , 1 )
a1 = p s i ( i +1 , j , 1 ) + p s i ( i 1, j , 1 ) + p s i ( i , j + 1 , 1 ) + p s i ( i , j 1 ,1)
psr ( i , j , 2 ) = psr ( i , j , 1 ) dt * a1 + 2 . 0 * a2
I f ( n == time ) then
p2 ( i , j ) = psr ( i , j , 1 ) * psr ( i , j , 1 ) + p s i ( i , j , 1 ) * p s i ( i , j , 1 )
Endif
End Do
psr ( 1 , j , 2 )
= psr ( 2 , j , 2 ) ! a t x edges d e r i v a t i v e =0
psr ( max + 1 , j , 2 ) = psr ( max , j , 2 )
End Do
! imaginary p a r t o f p s i
Do j = 2 , max
Do i = 2 , max
a2 = v ( i , j ) * psr ( i , j , 2 ) + 2 . 0 * dt * psr ( i , j , 2 )
a1 = psr ( i +1 , j , 2 ) + psr ( i 1, j , 2 ) + psr ( i , j 1 ,2) + psr ( i , j + 1 , 2 )
p s i ( i , j , 2 ) = p s i ( i , j , 1 ) + dt * a1 2 . 0 * a2
End Do
psi (1 , j , 2)
= p s i ( 2 , j , 2 ) ! a t x edges d e r i v a t i v e =0
p s i ( max + 1 , j , 2 ) = p s i ( max , j , 2 )
End Do
! new > old
Do j = 1 , max + 1
Do i = 1 , max + 1
psi ( i , j , 1) = psi ( i , j , 2)
psr ( i , j , 1 ) = psr ( i , j , 2 )
End Do
End Do
End Do
! wr i t e p r o b a b i l i t i e s & p o t e n t i a l s c a l e d by 0 . 0 2 5 ( t o f i t )
Do j = 2 , max , 3
Do i = 2 , max , 2
wr i t e ( 9 , 1 1 ) p2 ( i , j ) + v ( i , j )
End Do
write ( 9 , * )
End Do
11 format ( E12 . 6 )
close (9)
Stop data saved in slit.dat
End

504

C Fortran 95 Codes

Listing C.26: soliton.f95

! s o l i t o n . f 9 0 : S o l v e s t h e KdeV Equation v i a f i n i t e d i f f e r e n c e s
!
Program s o l i t o n
I m p l i c i t None
Real * 8 : : ds , dt , max , mu, eps , u ( 1 3 1 , 3 )
parameter ( ds = 0 . 4 , dt = 0 . 1 , max = 2 0 0 0 , mu = 0 . 1 , eps = 0 . 2 )
! d e l t a t , d e l t a x , time s t e p s , mu and eps from KdeV e q u a t i o n
Real * 8 : : a1 , a2 , a3 , f a c , time
Integer : : i , j , k
open ( 9 , FILE = soliton.dat , S t a t u s = Unknown )
! I n i t i a l condition
Do i = 1 , 131
u ( i , 1 ) = 0 . 5 * ( 1 . tanh ( 0 . 2 * ds * ( i 1 ) 5 . ) )
End Do
! Endpoints
u(1 , 2) = 1.
u(1 , 3) = 1.
u(131 , 2) = 0.
u(131 , 3) = 0.
f a c = mu* dt /( ds * * 3 . )
time = dt
! f i r s t step
Do i = 2 , 130
a1 = eps * dt * ( u ( i + 1 , 1 ) + u ( i , 1 ) + u ( i 1 , 1 ) ) /( ds * 6 . d0 )
I f ( ( i > 2 ) . and . ( i <= 1 2 9 ) ) then
a2 = u ( i + 2 , 1 ) + 2 . * u ( i 1 , 1 ) 2 . * u ( i + 1 , 1 ) u ( i 2 , 1 )
Endif
I f ( ( i == 2 ) . or . ( i == 1 3 0 ) ) then
a2 = u ( i 1 , 1 ) u ( i + 1 , 1 )
Endif
a3 = u ( i + 1 , 1 ) u ( i 1 , 1 )
u ( i , 2 ) = u ( i , 1 ) a1 * a3 f a c * a2 / 3 . d0
End Do
! a l l other times
Do j = 1 , max
Do i = 2 , 130
a1 = eps * dt * ( u ( i + 1 , 2 ) + u ( i , 2 ) + u ( i 1 , 2 ) ) / ( 3 . d0 * ds )
I f ( ( i > 2 ) . and . ( i <= 1 2 9 ) ) then
a2 = u ( i + 2 , 2 ) + 2 . d0 * u ( i 1 ,2) 2 . d0 * u ( i + 1 , 2 ) u ( i 2 ,2)
Endif
I f ( ( i == 2 ) . or . ( i == 1 3 0 ) ) then
a2 = u ( i 1 , 2 ) u ( i + 1 , 2 )
Endif
a3 = u ( i + 1 , 2 ) u ( i 1 , 2 )
u ( i , 3 ) = u ( i , 1 ) a1 * a3 2 . d0 * f a c * a2 / 3 . d0
u ( 1 , 3 ) = 1 . d0
End Do
! new > old
Do k = 1 , 131
u(k , 1) = u(k , 2)
u(k , 2) = u(k , 3)
End Do
! output every 200 time s t e p s

505

I f ( modulo ( j , 2 0 0 ) == 0 ) then
Do k = 1 , 131
wr i t e ( 9 , 2 2 ) u ( k , 3 )
End Do
wr i t e ( 9 , 2 2 )
EndIf
time = time + dt
End Do
22
format ( f 1 0 . 6 )
close (9)
Stop data saved in soliton.dat (for gnuplot)
End Program s o l i t o n

Listing C.27: Spline.f95

! s p l i n e . f 9 0 : Cubic S p l i n e f i t , based on " Numerical Recipes in C "


Program s p l i n e
I m p l i c i t none
!
!
!
!
!
!

i n p u t a r r a y x [ n ] , y [ n ] r e p r e s e n t s t a b u l a t i o n Function y ( x )
with x0 < x1 . . . < x ( n 1 ) . n = # o f t a b u l a t e d p o i n t s
output yout f o r given xout ( here xout v i a loop a t End )
yp1 and ypn : 1 s t d e r i v a t i v e s a t Endpoints , e v a l u a t e d i n t e r n a l l y
y2 [ n ] i s a r r a y o f second d e r i v a t i v e s
( s e t t i n g yp1 or ypn > 0 . 9 9 e30 produces n a t u r a l s p l i n e )
Real * 8 : : xout , yout , h , b , a , N f i t , p , qn , s i g , un , yp1 , ypn , x ( 9 )
REAL * 8 : : y ( 9 ) , y2 ( 9 ) , u ( 9 )
I n t e g e r : : klo , khi , k , n , i
! Save data , i n p u t data
open ( 9 , FILE = Spline.dat , S t a t u s = Unknown )
open ( 1 0 , FILE = Input.dat , S t a t u s = Unknown )
! e n t e r your own data here !
data x / 0 . , 1 . 2 , 2 . 5 , 3 . 7 , 5 . , 6 . 2 , 7 . 5 , 8 . 7 , 9 . 9 /
data y / 0 . , 0 . 9 3 , 0 . 6 , 0 . 5 3 , 0 . 9 6 , 0 . 0 8 , 0 . 9 4 , 0 . 6 6 , 0.46 /
n = 9
Do i = 1 , n
write ( 1 0 , * ) x ( i ) , y ( i )
End Do
Nfit = 3000;
! e n t e r t h e d e s i r e d number o f p o i n t s t o f i t
yp1 = ( y ( 2 ) y ( 1 ) ) /( x ( 2 ) x ( 1 ) ) ( y ( 3 ) y ( 2 ) ) /( x ( 3 ) x ( 2 ) ) &
+ ( y ( 3 ) y ( 1 ) ) /( x ( 3 ) x ( 1 ) )
! 1 s t deriv
ypn = ( y ( n 1) y ( n 2) ) /( x ( n 1) x ( n 2) ) ( y ( n 2) &
y ( n 3) ) /( x ( n 2)x ( n 3) ) + ( y ( n 1)y ( n 3) ) /( x ( n 1)x ( n 3) )
I f ( yp1 > 0 . 9 9 e30 ) then
y2 ( 1 ) = 0 . 0
u(1) = 0.0
else
y2 ( 1 ) = ( 0 . 5 )
u ( 1 ) = ( 3 . 0 / ( x ( 2 ) x ( 1 ) ) ) * ( ( y ( 2 ) y ( 1 ) ) /( x ( 2 ) x ( 1 ) ) yp1 )
Endif
! decomposition loop ; y2 , u a r e temps

506

C Fortran 95 Codes
Do i = 2 , n 1
s i g = ( x ( i ) x ( i 1 ) ) /( x ( i + 1 ) x ( i 1 ) ) ;
p = s i g * y2 ( i 1 ) + 2 . 0
y2 ( i ) = ( s i g 1 . 0 ) /p
u ( i ) = ( y ( i +1)y ( i ) ) /( x ( i +1)x ( i ) ) ( y ( i )y ( i 1) ) /( x ( i ) x ( i 1) )
u ( i ) = ( 6 . 0 * u ( i ) /( x ( i +1) x ( i 1) ) s i g * u ( i 1) ) /p ;
End Do
! t e s t for natural
! e l s e e v a l u a t e second d e r i v a t i v e
I f ( ypn > 0 . 9 9 e30 ) then
qn = 0 . 0
un = 0 .
else
qn = 0 . 5
un = ( 3 / ( x ( n 1) x ( n 2) ) ) * ( ypn ( y ( n 1)y ( n 2) ) &
/( x ( n 1) x ( n 2) ) )
y2 ( n 1 ) = ( un qn * u ( n 2 ) ) /( qn * y2 ( n 2 ) + 1 . 0 )
Endif
! back s u b s t i t u t i o n
Do k = n 2 , 1 , 1
y2 ( k ) = y2 ( k ) * y2 ( k + 1 ) + u ( k )
End Do
! s p l i n t ( i n i t i a l i z a t i o n ) Ends
! Parameters determined , Begin * s p l i n e * f i t
! loop over xout v a l u e s
Do i = 1 , N f i t
xout = x ( 1 ) + ( x ( n ) x ( 1 ) ) * ( i ) /( N f i t )
klo = 0
khi = n 1
! B is e ct io n algor for place in t a b le
! klo , khi b r a c k e t xout
Do while ( khi k l o > 1 )
k = ( khi + k l o ) / 2 . 0
I f ( x ( k ) > xout ) then
khi = k
else
klo = k
Endif
End Do
h = x ( khi ) x ( k l o )
I f ( x ( k ) > xout ) then
khi = k
else
klo = k
Endif
h = x ( khi ) x ( k l o )
a = ( x ( khi ) xout ) /h
b = ( xout x ( k l o ) ) /h
yout = ( a * y ( k l o ) +b * y ( khi ) &
+ ( ( a * a * aa ) * y2 ( k l o ) +( b * b * bb ) * y2 ( khi ) ) * h * h/6)
! wr i t e data i n gnuplot 2D format
w r i t e ( 9 , * ) xout , yout
End Do
Stop data stored in Spline.dat
End Program s p l i n e

507


!
!

Listing C.28: sqwell.f95


s q we l l . f 9 0 : S o l v e s t h e t dependent S c h r o e d i n g e r e q u a t i o n f o r a
Gaussian wavepacket i n a i n f i n i t e square we l l p o t e n t i a l

Program s q we l l
I m p l i c i t None
Real * 8 : : psr ( 7 5 1 , 2 ) , p s i ( 7 5 1 , 2 ) , p2 ( 7 5 1 )
Real * 8 : : dx , k0 , dt , x , p i
I n t e g e r : : i , j , n , max
Complex exc , z i
Common / v a l u e s /dx , dt
open ( 9 , FILE = sqwell.dat , S t a t u s = Unknown )
max
= 750
pi
= 3.14159265358979323846
zi
= CMPLX( 0 . 0 , 1 . 0 )
dx
= 0.02
k0
= 1 7 . 0 * pi
dt
= dx * dx

! cl e a r the arrays

Do i = 1 , 751
Do j = 1 , 2
psr ( i , j ) = 0 . 0
psi ( i , j ) = 0.0
p2 ( i ) = 0 . 0
End Do
End Do
! i n i t i a l conditions
= 0.0
i = 1 , max + 1
exc
= exp ( z i * k0 * x )
psr ( i , 1 ) = r e a l ( exc * exp ( 0 . 5 * ( 2 . 0 * ( x 5 . 0 ) ) * * 2 ) ) ! r e a l p a r t
p s i ( i , 1 ) = aimag ( exc * exp ( 0 . 5 * ( 2 . 0 * ( x 5 . 0 ) ) * * 2 ) )
! imag
x
= x + dx
End Do
! propagate s o l u t i o n through time
Do n = 1 , 6000
Do i = 2 , max ! r e a l p a r t & prob
psr ( i , 2 ) = psr ( i , 1 ) dt * ( p s i ( i + 1 , 1 ) + p s i ( i 1 , 1 )&
2 . 0 * p s i ( i , 1 ) ) / ( 2 . 0 * dx * dx )
p2 ( i )
= psr ( i , 1 ) * psr ( i , 2 ) + p s i ( i , 1 ) * p s i ( i , 1 )
End Do
Do i = 2 , max
! imaginary p a r t
p s i ( i , 2 ) = p s i ( i , 1 ) + dt * ( psr ( i + 1 , 2 ) + psr ( i 1 , 2 )&
2 . 0 * psr ( i , 2 ) ) / ( 2 . 0 * dx * dx )
End Do
! s e l e c t i v e printout
I f (Mod( n , 3 0 0 ) == 0 ) then
Do i = 1 , max + 1 , 15
wr i t e ( 9 , 1 1 ) p2 ( i )
End Do
write ( 9 , * )
Endif
! new s o l t n > old
x
Do

508

C Fortran 95 Codes
Do

i = 1 , max + 1
psi ( i , 1) = psi ( i , 2)
psr ( i , 1 ) = psr ( i , 2 )
End Do
End Do
11 format ( E12 . 6 )
close (9)
Stop data saved in sqwell.dat
End

Listing C.29: tune.f95


!

tune . f 9 0 : m a t r i x a l g e b r a program t o be tuned f o r performace

Program

tune

parameter ( ldim = 2 0 5 0 )
I m p l i c i t Double p r e c i s i o n ( a h , o z )
dimension ham( ldim , ldim ) , c o e f ( ldim ) , sigma ( ldim )
! s e t up H and s t a r t i n g v e c t o r
Do i = 1 , ldim
Do j = 1 , ldim
I f ( abs ( j i ) > 1 0 ) then
ham( j , i ) = 0 .
else
ham( j , i ) = 0 . 3 * * Abs ( j i )
EndIf
End Do
ham( i , i ) = i
coef ( i ) = 0.
End Do
coef ( 1 ) = 1.
! start iterating
err = 1.
iter = 0
20
I f ( i t e r < 15 . and . e r r >1. e 6) then
iter = iter + 1
! compute c u r r e n t energy & normalize
ener = 0 .
ovlp = 0 .
Do
i = 1 , ldim
ovlp = ovlp + c o e f ( i ) * c o e f ( i )
sigma ( i ) = 0 .
Do
j = 1 , ldim
sigma ( i ) = sigma ( i ) + c o e f ( j ) * ham ( j , i )
End Do
ener = ener + c o e f ( i ) * sigma ( i )
End Do
ener = ener/ovlp
Do
I = 1 , ldim
c o e f ( i ) = c o e f ( i ) / S q r t ( ovlp )
sigma ( i ) = sigma ( i ) / S q r t ( ovlp )
End Do
! compute update and e r r o r norm
err = 0.
Do i = 1 , ldim

509

I f ( i == 1 ) goto 23
s t e p = ( sigma ( i ) ener * c o e f ( i ) ) /( ener ham( i , i ) )
coef ( i ) = coef ( i ) + step
err = err + step **2
23 End Do
err = sqrt ( err )
w r i t e ( * , (1x, i2, 7f10.5) ) i t e r , ener , e r r , c o e f ( 1 )
goto 20
Endif
Stop
End Program tune

Listing C.30: twodsol.f95


!

twodsol . f 9 0 :

S o l v e s t h e s i n e Gordon e q u a t i o n f o r a 2D s o l i t o n

Program twodsol
I m p l i c i t none
Double p r e c i s i o n : : u ( 2 0 1 , 2 0 1 , 3 )
Integer : : nint
Open ( 9 , FILE = twodsol.dat , S t a t u s = UNKNOW )
write ( * , * )
Enter an Integer from 1 to 100
w r i t e ( * , * ) this number is proportional to time
write ( * , * )
time = 0 is for the Integer = 1
read ( * , * ) n i n t
w r i t e ( * , * ) working with input = , n i n t
ca l l i n i t i a l (u)
! initialize
! output f o r t p r o p o r t i o n a l t o n i n t
c a l l solution (u , nint )
Stop
End Program twodsol
! i n i t i a l i z e c o n s t a n t s and s o l i t o n
Subroutine i n i t i a l ( u)
I m p l i c i t none
Integer : : i , j , k
Double p r e c i s i o n : : u ( 2 0 1 , 2 0 1 , 3 ) , dx , dy , dt , xx , yy , dts , time
Common / v a l u e s / dx , dy , dt , time , d t s
Do i = 1 , 2 0 1 ! c l e a r a r r a y s
Do j = 1 , 201
Do k = 1 , 3
u( i , j , k) = 0.0
End Do
End Do
End Do
dx = 1 4 . 0 / 2 0 0 . ! i n i t i a l c o n d i t i o n
dy = dx
dt = dx/ s q r t ( 2 . 0 )
d t s = ( dt/dx ) * * 2
yy = 7 . 0
time = 0 . 0
Do i = 1 , 201
xx = 7 . 0
Do j = 1 , 201

510

C Fortran 95 Codes
u ( i , j , 1 ) = 4 . 0 * Datan ( 3 . s q r t ( xx * xx + yy * yy ) )
xx = xx + dx
End Do
yy = yy + dy
End Do
Return
End
! s o l v e SGE , i n i t i a l c o n d i t i o n s i n i n i t i a l
Subroutine s o lu t io n ( u , nint )
I m p l i c i t none
Double p r e c i s i o n : : u ( 2 0 1 , 2 0 1 , 3 ) , dx , dy , dt , time , a2 , zz , dts , a1
I n t e g e r : : l , m, mm, k , j , i , n i n t
Common/ v a l u e s / dx , dy , dt , time , d t s
time = time + dt
! 2nd i t e r a t i o n uses d phi/dt ( t =0) = 0 (G( x , y , 0 ) = 0 )
! d U/dx = 0 a t x0 , x0 , y0 and y0
Do l = 2 , 200
Do m = 2 , 200
a2 = u (m+1 , l , 1 ) + u (m 1, l , 1 ) + u (m, l +1 , 1 ) + u (m, l 1, 1 )
u (m, l , 2 ) = 0 . 5 * ( d t s * a2 dt * dt * DSIN ( 0 . 2 5 * a2 ) )
End Do
End Do
! t h e b o r d e r s i n 2nd i t e r a t i o n
Do mm = 2 , 200
u (mm, 1 , 2 ) = u (mm, 2 , 2 )
u (mm, 2 0 1 , 2 ) = u (mm, 2 0 0 , 2 )
u ( 1 , mm, 2 ) = u ( 2 , mm, 2 )
u ( 2 0 1 , mm, 2 ) = u ( 2 0 0 , mm, 2 )
End Do
! t h e s t i l l undefined terms
u(1 , 1 , 2) = u(2 , 1 , 2)
u(201 , 1 , 2) = u(200 , 1 , 2)
u ( 1 , 201 , 2) = u ( 2 , 201 , 2)
u ( 201 , 201 , 2) = u( 200 , 201 , 2)
! 3 rd and f o l l o w i n g i t e r a t i o n s use your input , loop up t o n i n t
Do k = 1 , n i n t
Do l = 2 , 200
Do m = 2 , 200
a1 = u (m+1 , l , 2 ) + u (m 1, l , 2 ) + u (m, l + 1 , 2 ) + u (m, l 1, 2 )
u (m, l , 3 ) = u (m, l , 1 ) + d t s * a1 dt * dt * DSIN ( 0 . 2 5 * a1 )
u (m, 1 , 3 ) = u (m, 2 , 3 )
u (m, 2 0 1 , 3 ) = u (m, 2 0 0 , 3 )
End Do
End Do
Do mm = 2 , 200
u (mm, 1 , 3 ) = u (mm, 2 , 3 )
u (mm, 2 0 1 , 3 ) = u (mm, 2 0 0 , 3 )
u ( 1 , mm, 3 ) = u ( 2 , mm, 3 )
u ( 2 0 1 , mm, 3 ) = u ( 2 0 0 , mm, 3 )
End Do
u(1 , 1 , 3) = u(2 , 1 , 3)
u(201 , 1 , 3) = u(200 , 1 , 3)
u ( 1 , 201 , 3) = u ( 2 , 201 , 3)
u ( 2 0 1 , 201 , 3) = u ( 2 0 0 , 201 , 3)
! new > old
Do l = 1 , 201
Do m = 1 , 201

511

u ( l , m, 1 ) = u ( l , m, 2 )
u ( l , m, 2 ) = u ( l , m, 3 )
End Do
End Do
! Output s o l u t i o n a t time p r o p o r t i o n a l t o n i n t
I f ( k == n i n t ) then
Do i = 1 , 2 0 1 , 5
Do j = 1 , 2 0 1 , 5
zz = DSIN ( u ( i , j , 3 ) / 2 . 0 )
w r i t e ( 9 , * ) zz
End Do
! need blank l i n e s t o s e p a r a t e s p a t i a l rows f o r 3D
write ( 9 , * )
End Do
Endif
time = time + dt
End Do
Return
End

Listing C.31: walk.f95

! walk . f 9 0 : RanDom walk s i m u l a t i o n


Program walk
I m p l i c i t none
Real * 8 : : ranDom , r o o t 2 , x , y , r ( 1 : 1 0 0 0 0 )
I n t e g e r : : i , j , max
max
= 10000
! s e t parameters ( # o f s t e p s )
r o o t 2 = 1 . 4 1 4 2 1 3 5 6 2 3 7 3 0 9 5 0 4 8 8 E0
open ( 6 , FILE = walk.dat , S t a t u s = Unknown )
! open f i l e
! c l e a r array
Do j = 1 , max
r( j) = 0
End Do
! average over 100 t r i a l s
Do j = 1 , 100
x = 0.
y = 0.
Do i = 1 , max
x = x + ( ranDom ( ) 0 . 5 ) * 2 . 0 * r o o t 2
y = y + ( ranDom ( ) 0 . 5 ) * 2 . 0 * r o o t 2
r ( i ) = r ( i ) + Sqrt ( x*x + y*y)
End Do
End Do
! output data f o r p l o t o f r vs . s q r t (N)
Do i = 1 , max
Write ( 6 , * ) S q r t ( Real ( i ) ) , , r ( i ) /100
End Do
close (6)
Stop data saved in walk.dat
End Program walk

Potrebbero piacerti anche