Computational Physics Applications

download Computational Physics Applications

of 33

description

fortran code for a lot of problems in physics

Transcript of Computational Physics Applications

  • Computationyal Physics. Problem Solving with Computers (2nd edn).Rubin H. Landau, Manuel Jos Pez, Cristian C. BordeianuCopyright 2007 WILEY-VCH Verlag GmbH & Co. KGaA, WeinheimISBN: 978-3-527-40626-5

    479

    CFortran 95 Codes

    (Alphabetic order modified somewhat to avoid awkward continuations.)

    Listing C.1: decay.f95

    ! decay . f90 : Spontaneous rad ioac t iv e decay s imulat ion!Program decay

    Imp l i c i t noneReal *8 : : r , ranDom , lambdaIn t ege r : : i , j , h , n l e f t , nloop , s t a r t , seed

    ! Se t params ( decay rate , i n i t i a l no of atoms , seed ) , p lant seedlambda = 0 . 01s t a r t = 1000seed = 11168h = 1nloop = s t a r tn l e f t = s t a r topen ( 6 , F i l e = decay.dat ) ! open output file

    ! loop over t imes and over atomsDo j = 1 , 10000

    Do i = 1 , n l e f tr = ranDom( seed )I f ( r

  • 480 C Fortran 95 Codes

    Listing C.2: bessel.f95

    ! b e s se l . f95 : Computation sphe r i ca l Besse l funct ions by recurrence

    Program besse l

    Imp l i c i t noneReal *8 : : step , x , xmin , xmax , up , Down, t1 , t 2In t ege r : : order , s t a r t

    xmin = 0 . 25xmax = 40 . 0s tep = 0 . 1order = 10s t a r t = 50open ( 6 , F i l e = bessel.dat , S t a tus = Unknown ) ! open output f i l eDo x = xmin , xmax , s tep

    t1 = Down( x , order , s t a r t )t2 = up( x , order )write ( 6 , 50) x , t1 , t 2

    End DoClose ( 6 )50 Format ( f15 . 1 0 , f15 . 1 0 , f15 . 1 0 )Stop data saved in bessel.dat

    End Program besse l! c a l cu l a t e using Downward recurs ion

    Function Down( x , order , s t a r t )Imp l i c i t noneIn t ege r : : k , order , s t a r tReal *8 : : Down, sca le , x , j ( 100 )

    ! the a rb i t r a r y s t a r tj ( s t a r t + 1) = 1j ( s t a r t ) = 1Do 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 tha t j ( 1 ) = s in ( x )/xs c a l e = ( s in ( x )/x )/ j ( 1 )Down = j ( order + 1) * s c a l eReturn

    End

    ! c a l cu l a t e using upward recurs ionFunction up( x , order )

    Imp l i c i t noneIn t ege r : : k , orderReal *8 : : up , x , one , two , throne = s in ( x )/xtwo = ( s in ( x ) x * cos ( x ) ) /(x * x )Do k = 1 , ( order 1)

    thr = ( ( 2 * k + 1 . 0 )/x ) * two oneone = twotwo = thr

    End Doup = thrReturn

    End

  • 481

    Listing C.3: diff.f95

    ! d i f f . f90 : Forward , c en t r a l and ext rapolated d i f f e r e n t i a t i o n

    Program d i f f

    Imp l i c i t noneReal *8 : : f , h , r e su l t ( 3 ) , x , xmin , xmax , xstep

    open ( 6 , F i l e = diff.dat , S t a tus = Unknown )h = 1 . e5xmin = 0 . 0xmax = 7 . 0xstep = 0 . 01Do x = xmin , xmax , xstep

    r e su l t ( 1 ) = ( f ( x+h ) f ( x ) )/hr e su l t ( 2 ) = ( f ( x+h/2) f ( xh/2) )/hr e su l t ( 3 ) = ( 8 * ( f ( x+h/4)f ( xh/4) ) ( f ( x+h/2)f ( xh/2) ) ) /(3*h )write ( 6 , 20) x , r e su l t ( 1 ) , r e su l t ( 2 ) , r e su l t ( 3 )

    End Do20 Format ( F5 . 3 , TR4 , F10 . 8 , TR4 , F10 . 8 , TR4 , F10 . 8 )

    c lose ( 6 )Stop data saved in diff.dat

    End Program d i f f! funct ion to i n t e g r a t e

    Function f ( x )Imp l i c i t noneReal *8 f , xf = cos ( x )Return

    End

  • 482 C Fortran 95 Codes

    Listing C.4: eqheat.f95, label

    ! eqheat . f90 : Solut ion of heat equat ion using with f i n i t e d i f f s

    Program heat

    Imp l i c i t noneDouble pre c i s ion : : cons , ro , sph , thk , u (101 , 2 )In t ege r : : i , k , max

    open ( 9 , FILE = eqheat.dat , S t a tus = Unknown )sph = 0.113 ! s p e c i f i c heat i ronthk = 0 . 12 ! thermal conduct iv i ty i ronro = 7 . 8 ! dens i ty for i roncons = thk/( sph * ro )max = 30000 ! number of i t e r a t i o n s

    ! t = 0 , a l l poin t s at 100 CDo i = 1 , 100

    u ( i , 1 ) = 100 .0End DoDo i = 1 , 2 ! Endpoints always zero

    u ( 1 , i ) = 0 . 0u (101 , i ) = 0 . 0

    End Do! loop over time

    Do k = 1 , max! loop over space

    Do i = 2 , 100u( i , 2 ) = u ( i , 1 ) + cons * ( u ( i + 1 , 1 ) + u ( i 1 , 1 ) 2*u( i , 1 ) )

    End DoI f ( (Mod(k , 1000) == 0) . or . ( k == 1) ) then ! every 1000 stepsDo i = 1 , 101 , 2

    write ( 9 , 22) u ( i , 2 )End DoWrite ( 9 , 22)EndIf

    ! new values > oldDo i = 2 , 100

    u ( i , 1 ) = u ( i , 2 )End Do

    End Do22 format ( f10 . 6 )c lose ( 9 )Stop data saved in eqheat.dat (for gnuplot)

    End Program heat

  • 483

    Listing C.5: eqstring.f95

    ! eqs t r ing . f90 : Solut ion of wave equat ion using time stepping

    Program eqs t r ing

    Imp l i c i t noneReal *8 : : x ( 101 , 3 )In t ege r : : i , j , k , max

    max = 100open ( 9 , FILE = eqstring.dat , S t a tus = Unknown )Do i = 1 , 101

    Do j = 1 , 3x ( i , j ) = 0 . 0

    End DoEnd Do

    ! i n i t i a l i z eDo i = 1 , 80

    x ( i , 1 ) = 0 . 00125* iEnd DoDo i = 81 , 101

    x ( i , 1 ) = 0 . 1 0 . 0 0 5 * ( i 81)End Do

    ! f i r s t t ime stepDo 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

    ! other time stepsDo k = 1 , max

    Do i = 2 , 100x ( i , 3 ) = 2 . * x ( i , 2 ) x ( i , 1 ) + ( x ( i +1 ,2 ) + x ( i 1 ,2) 2 . * x ( i , 2 ) )

    End DoDo i = 1 , 101

    x ( i , 1 ) = x ( i , 2 ) ! new > oldx ( i , 2 ) = x ( i , 3 )

    End DoI f (modulo ( k , 10) == 0) then

    ! output data every 10 stepsDo i = 1 , 101

    write ( 9 , 11) x ( i , 3 )End Dowrite ( 9 , * )

    EndifEnd Do

    11 format ( e12 . 6 )c lose ( 9 )Stop data saved in eqstring.dat (for gnuplot)

    End Program eqs t r ing

  • 484 C Fortran 95 Codes

    Listing C.6: exp-bad.f95

    ! expbad . f90 : c a l cu l a t i n g exp( x ) as a f i n i t e sum, bad algorithm

    Program expbad

    Imp l i c i t none! min = accuracy , x step , max in x , up numer , down denomin .

    Real *8 : : down, min , max, step , sum, up , xIn t ege r : : i , j

    min = 1E 10max = 10 .s tep = 0 . 1open ( 6 , F i l e = exp-bad.dat , S t a tus = Unknown )

    ! summationDo x = 0 , max , s tep

    sum = 1i = 0down = 1up = 1

    ! while loop may never stopDo while ( ( sum == 0) . or . ( abs ( ( up/down)/sum) > min) )

    i = i + 1down = 1up = 1

    Do j = 1 , iup = up* xdown = down* j

    End Dosum = sum + up/down

    End Dowrite ( 6 , * ) x , sum

    End Doc lose ( 6 )Stop data saved in exp-bad.dat

    End Program expbad

    Listing C.7: exp-good.f95

    ! expgood . f90 : c a l cu l a t e e^ x as a f i n i t e sum, good algorithm

    Program expgood

    Imp l i c i t noneReal *8 : : element , min , max , step , sum, xIn t ege r : : n

    min = 1E 10max = 10 .s tep = 0 . 1open ( 6 , F i l e = exp-good.dat , S t a tus = Unknown )

    ! summationDo x = 0 , max , s tep

    sum = 1element = 1

  • 485

    n = 0! while loop may never stop

    Do while ( ( abs ( element/sum) > min ) . or . (sum . eq . 0 ) )n = n + 1element = element*(x )/nsum = sum + element

    End Dowrite ( 6 , * ) x , sum

    End Doc lose ( 6 )Stop data saved in exp-good.dat

    End Program expgood

    Listing C.8: fit.f95

    ! f i t . f95 : Least square f i t

    Program f i t

    Imp l i c i t noneIn t ege r : : iReal *8 : : s , sx , sy , sxx , sxy , de l ta , in t e r , s lopeReal *8 : : x ( 1 2 ) , y ( 1 2 ) , d ( 1 2 )

    Data y /328 , 187 , 821 , 78 , 88 , 6 , 5 , 82 , 2 , 0 . 1 , 84 , 1/ ! y valuesDo i = 1 , 12 ! values x

    x ( i ) = i *10 5End Do

    ! input de l t a yDo i = 1 , 12

    d( i ) = 1 .End Dos = 0 . 0 ; sx = 0 . ; sy = 0 .sxx = 0 .sxy = 0 .

    ! c a l cu l a t e sumsDo 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! c a l cu l a t e c o e f f i c i e n t s

    de l t a = s * sxx sx * sxslope = ( s * sxy sx * sy ) / de l t ai n t e r = ( sxx * sy sx * sxy ) / de l t awrite ( * , * ) intercept = , i n t e rwrite ( * , * ) slope = , s lopewrite ( * , * ) correlation = , sx/sqr t ( sxx * s )Stop fit

    End Program f i t

  • 486 C Fortran 95 Codes

    Listing C.9: gauss.f95

    ! gauss . f90 : Poin t s and weights for Gaussian quadrature! r e s c a l e s the gauss legendre grid poin t s and weights!! npts number of poin t s! j ob = 0 r e s c a l l i n g uniformly between ( a , b )! 1 for i n t e g r a l ( 0 , b ) with 50% points in s ide ( 0 , ab/( a + b ) )! 2 for i n t e g r a l ( a , i n f ) with 50% ins ide ( a , b + 2a )! x , w output grid poin t s and weights .

    subrout ine gauss ( npts , job , a , b , x , w)

    In t ege r : : npts , job , m, i , jReal *8 : : x ( npts ) , w( npts ) , a , b , x iReal *8 : : t , t1 , pp , p1 , p2 , p3 , a jReal *8 : : eps , pi , zero , two , one , ha l f , quar terparameter ( pi = 3.14159265358979323846264338328 , eps = 3 . 0E 14)parameter ( zero = 0 . d0 , one = 1 . d0 , two = 2 . d0 )parameter ( ha l f = 0 . 5 d0 , quarter = 0 . 25d0 )

    m = ( npts + 1) /2Do i = 1 , m

    t = cos ( pi * ( i quarter ) /( npts + ha l f ) )10 continue

    p1 = onep2 = zeroa j = zeroDo j = 1 , npts

    p3 = p2p2 = p1a j = a j + onep1 = ( ( two* a j one ) * t *p2 ( a j one ) *p3 )/a j

    End Dopp = npts * ( t *p1 p2 ) /( t * t one )t1 = tt = t1 p1/ppI f ( abs ( t t 1 ) > eps ) goto 10x ( i ) = tx ( npts + 1 i ) = tw( i ) = two/( ( one t * t ) *pp*pp)w( npts + 1 i ) = w( i )

    End Do! r e s c a l e grid poin t s

    s e l e c t case ( j ob )! s c a l e to ( a , b ) uniformly

    case ( 0 )Do i = 1 , npts

    x ( i ) = x ( i ) * ( b a )/two + ( b + a )/twow( i ) = w( i ) * ( b a )/two

    End Do! s c a l e to ( 0 , b ) with 50% points in s ide ( 0 , ab/( a + b ) )

    case ( 1 )Do i = 1 , npts

    x i = 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 to ( a , i n f ) with 50% ins ide ( a , b + 2a )

    case ( 2 )Do i = 1 , npts

    x i = 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 DoEnd s e l e c tReturn

    End

    Listing C.10: int10d.f95

    ! in t 10d . f90 : Ten dimensional i n t e g r a t i on using Monte Carlo

    Program int10d

    Imp l i c i t noneIn t ege r : : m = 16 , k ! number of t r i a l sReal *8 : : s , in teg ( 1 6 )

    s = 0 .Do k = 1 , m

    c a l l montecarlo ( integ , k ) ;s = s + in teg ( k )

    End Dowrite ( * , * ) s/m

    End Program int10d

    subrout ine montecarlo ( integ , k )Imp l i c i t noneIn t ege r : : i , j , k , max = 65536Real *8 : : x , y , sum, ranDom , in teg ( 1 6 )x = 0 .y = 0 .sum = 0 .Do i = 1 , max

    x = 0 ! r e s e t x! sum 10 x values

    Do j = 1 , 10x = x + ranDom ( )

    End Do! square and sum up

    y = y + x *xsum = sum + y/ i ;

    End Dointeg ( k ) = sum/maxwrite ( * , * ) k , in teg ( k )

    End

  • 488 C Fortran 95 Codes

    Listing C.11: harmos.f95

    ! harmos . f90 : Solves t dependent Schro eqtn for Gaussian wavepacket! in harmonic o s c i l l a t o r po t en t i a l well

    Program harmos

    Imp l i c i t NoneReal *8 : : psr ( 750 , 2 ) , ps i ( 750 , 2 ) , v ( 750 ) , p2 (750 )Real *8 : : pi , dx , k0 , dt , xComplex : : exc , z iIn t ege r : : max , i , j , n

    Open ( 9 , FILE = harmos.dat , S t a tus = Unknown )pi = 3.1415926535897932385 E0z i = cmplx ( 0 . , 1 . )dx = 0 . 02k0 = 3 * pi ! i n i t i a l momentumdt = dx*dx/4.max = 750Do i = 1 , max

    Do j = 1 , 2ps i ( i , j ) = 0 .psr ( i , j ) = 0 .

    End DoEnd Do

    ! i n i t i a l condi t ionsx = 7 . 5Do 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 Functionps i ( i , 1 ) = aimag ( exc * exp ( 0 . 5 * ( x /0 . 5 ) * * 2 ) ) ! imag wave Functionv ( i ) = 5 . * x *x ! po t en t i a lx = x + dx

    End Do! propagate so lu t ion in time

    Do n = 1 , 20000Do i = 2 , max 1 ! r e a l par t psr and the probab i l i t y p2

    psr ( i , 2 ) = psr ( i , 1 ) dt * ( ps i ( i + 1 , 1 ) + ps i ( i 1 , 1 ) & 2 . * ps i ( i , 1 ) ) /(dx*dx ) + dt *v ( i ) * ps i ( i , 1 )

    p2 ( i ) = psr ( i , 1 ) * psr ( i , 2 ) + ps i ( i , 1 ) * ps i ( i , 1 )End DoDo i = 2 , max 1 ! imag part

    ps i ( i , 2 ) = ps 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 steps

    I f ( ( n == 1) . or . ( modulo (n , 2000) == 0) ) ThenDo i = 2 , max 1 , 10

    Write ( 9 , 11) p2 ( i ) + 0 . 0015*v ( i )End DoWrite ( 9 , * )

    EndIfDo i = 1 , max ! new > old

    ps i ( i , 1 ) = ps i ( i , 2 )psr ( i , 1 ) = psr ( i , 2 )

    End Do

  • 489

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

    End

    Listing C.12: lagrange.f95

    ! lagrange . f : Langrange in t e rpo l a t i on of cross t ab le

    Program lagrange

    Imp l i c i t noneReal *8 : : in t e r , x , xin ( 9 ) , yin ( 9 )In t ege r : : i , e

    e = 9open ( 6 , F i l e = lagrange.dat , S t a tus = Unknown )

    ! Input datadata xin /0 , 85 , 580 , 758 , 800 , 1285 , 850 , 795 , 82/data yin /18 .6 , 16 , 85 , 83 . 5 , 58 . 8 , 19 . 9 , 10 . 8 , 88 . 25 , 4 . 7 /

    ! Calcula te f ( x )Do i = 0 , 1000

    x = i * 0 . 2write ( 6 , * ) x , i n t e r ( xin , yin , e , x )

    End DoClose ( 6 )Stop data saved in lagrange.dat

    End Program lagrange! Evaluate i n t e rpo l a t i on funct ion ( x )

    Function in t e r ( xin , yin , e , x )Imp l i c i t noneIn t ege r : : i , j , eReal *8 : : in t e r , lambda ( 9 ) , xin ( 9 ) , yin ( 9 ) , xi n t e r = 0Do i = 1 , e

    lambda ( i ) = 1Do j = 1 , e

    I f ( i . neqv . j ) thenlambda ( i ) = lambda ( i ) * ( ( x xin ( j ) ) /( xin ( i ) xin ( j ) ) )

    EndifEnd Doin t e r = in t e r + ( yin ( i ) * lambda ( i ) )

    End DoReturn

    End

  • 490 C Fortran 95 Codes

    Listing C.13: integ.f95

    ! i n t e g r a t e . f90 : In t eg ra t e exp(x ) using trap , Simp and Gauss ru le s! Need to add in Gauss . f95

    Program in t e g r a t e

    Imp l i c i t noneReal *8 : : t rapez , simpson , quad , r1 , r2 , r3 ! dec la ra t ion sReal *8 : : theo , vmin , vmaxIn t ege r : : i

    theo = 0.632120558829 ! t h e o r e t i c a l r e su l t , i n t e g r a t i on rangevmin = 0 .vmax = 1 .open ( 6 , F i l e = integ.dat , S t a tus = Unknown )

    ! c a l cu l a t e i n t e g r a l using both methods for s teps = 3 . . 5 0 1Do i = 3 , 501 , 2

    r1 = t rapez ( i , vmin , vmax)r1 = abs ( r1 theo )r2 = simpson ( i , vmin , vmax)r2 = abs ( r2 theo )r3 = quad ( i , vmin , vmax)r3 = abs ( r3 theo )write ( 6 , * ) i , r1 , r2 , r3

    End Doc lose ( 6 )Stop data saved in integ.dat

    End Program in t e g r a t e! Function we want to i n t e g r a t e

    Function f ( x )Imp l i c i t noneReal *8 : : f , xf = exp ( x )Return

    End

    Function t rapez ( i , min , max) ! t rapezoid ruleImp l i c i t noneIn t ege r : : i , nReal *8 : : f , i n t e rva l , min , max, trapez , xt rapez = 0in t e rv a l = ( (max min ) / ( i 1) )Do n = 2 , ( i 1) ! sum midpoints

    x = in t e rv a l * ( n 1)t rapez = t rapez + f ( x ) * i n t e rv a l

    End Dotrapez = t rapez + 0 . 5 * ( f (min ) + f (max) ) * i n t e rv a l ! add EndpointsReturn

    End! Simpson rule

    Function simpson ( i , min , max)Imp l i c i t noneIn t ege r : : i , nReal *8 : : f , i n t e rva l , min , max, simpson , xsimpson = 0in t e rv a l = ( (max min ) / ( i 1) )

  • 491

    Do n = 2 , ( i 1) , 2 ! loop for odd poin tsx = in t e rv a l * ( n 1)simpson = simpson + 4* f ( x )

    End DoDo n = 3 , ( i 1) , 2 ! loop for even poin ts

    x = in t e rv a l * ( n 1)simpson = simpson + 2* f ( x )

    End Dosimpson = simpson + f (min ) + f (max) ! add the Endpointssimpson = simpson* i n t e rv a l /3Return

    End

    Function quad ( i , min , max) ! uses Gauss poin t sImp l i c i t noneReal *8 : : w(1000 ) , x ( 1000 )Real *8 : : f , min , max , quadIn t ege r : : i , job , nquad = 0job = 0c a l l gauss ( i , job , min , max , x , w)Do n = 1 , i

    quad = quad + f ( x ( n ) ) *w(n )End DoReturn

    End

    Listing C.14: limit.f95

    ! l im i t . f90 : determines the machine pre c i s ion!Program l im i t ! determines the machine pre c i s ion

    Imp l i c i t noneIn t ege r : : I , NReal *8 : : eps , one

    N = 60 ! number of i t e r a t i o n s Neps = 1 . ! s e t i n i t i a l valuesone = 1 . 0

    ! add eps to one and pr in t r e su l tDo I = 1 , N

    eps = eps / 2one = 1 + epswrite ( * , * ) I , one , eps

    End DoStop limit

    End Program l im i t

  • 492 C Fortran 95 Codes

    Listing C.15: LaplaceSOR.f95

    ! LaplaceSOR . f90 : Solve Laplace eq with f i n i t e d i f f e r en ce s c SOR

    Program LaplaceSOR

    Imp l i c i t noneIn t ege r : : max = 40 , i , j , i t e rReal *8 : : to l , omega , r , p (40 , 40)

    Open ( 6 , FILE = laplaceR.dat , S t a tus = Unknown ) ! Data f i l eomega = 1 . 8 ! SOR parameter

    ! c l e a r the arrayDo i = 1 , max

    Do j = 1 , maxp( i , j ) = 0

    End DoEnd Do

    ! p [ i ] [ 0 ] = 100 VDo i = 1 , max

    p ( i , 1 ) = + 100 .0End Dot o l = 1 . 0 ! t o l e rancei t e r =1

    ! i t e r a t i o n sDo while ( ( t o l > 0 . 000001 ) . and . ( i t e r t o l ) then

    t o l = abs ( r )Endif

    End Doi t e r = i t e r + 1

    End DoEnd Do

    ! write data gnuplot 3D formatDo i = 1 , max

    Do j = 1 , maxwrite ( 6 , * ) p ( i , j )

    End Dowrite ( 6 , * )

    End Doc lose ( 6 )Stop data stored in laplaceR.dat (for gnuplot)

    End Program LaplaceSOR

  • 493

    Listing C.16: Newton_cd.f95

    ! Newton_cd . f90 : NewtonRaphson root f inder , c e n t r a l d i f f de r iva t iv e!Program Newton_cd

    Imp l i c i t noneIn t ege r : : i t , imax = 10 ! Maximum number of i t e r a t i o n s permit tedReal *8 : : x , dx = 1e 2 , eps = 1e 6 , f1 , df , F

    ! x guess , must be c lose to rootx = 2 .Do i t = 0 , imax

    f1 = F ( x ) ! Compute Function valuewrite ( * , * ) i t , x , f1

    ! Cent ra l d i f f e r en ce de r iva t iv edf = ( F ( x + dx/2) F ( x dx/2) )/dxdx = f1/dfx = x + dx ! New guess

    ! Check for convergenceI f ( abs ( F ( x ) )

  • 494 C Fortran 95 Codes

    End DoEnd

    ! Find zero of th i s funct ionfunct ion F ( x )

    Imp l i c i t noneReal *8 : : x , FF = 2* cos ( x ) x

    End

    Listing C.18: overflow.f95

    ! overflow . f90 : determine overflow and underflow l im i t s

    Program overflow

    Imp l i c i t noneIn t ege r : : I , NReal *8 : : under , overN = 1024 ! number of i t e r a t i on s , may need biggerunder = 1 . ! s e t i n i t i a l valuesover = 1 .Do I = 1 , N ! c a l c underflow and overflow , output to screen

    under = under / 2over = over * 2write ( * , * ) I , over , under

    End DoStop overflow

    End Program overflow

    Listing C.19: pond.f95

    ! pond . f90 : pi via MonteCarlo i n t e g r a t i on ( throwing stones )

    Program pond

    Imp l i c i t noneReal *8 : : area , x , y , ranDomIn t ege r : : i , max, pi

    max = 2000! open f i l e , s e t i n i t i a l value , seed generator

    Open ( 6 , F i l e = pond.dat , S t a tus = Unknown )pi = 0

    ! executeDo i = 1 , max

    x = ranDom ( ) *2 1y = ranDom ( ) *2 1I f ( ( x * x + y*y )

  • 495

    Listing C.20: qmc.f95

    ! qmc . f90 : Feynman path in t e g r a l for ground s t a t e wave Function

    Program qmc

    Imp l i c i t noneIn t ege r : : i , j , max , element , prop (100 )Real *8 : : change , ranDom , energy , newE, oldE , out , path (100 )

    max = 250000open ( 9 , FILE = qmc.dat , S t a tus = Unknown )

    ! i n i t i a l path and probab i l i t yDo j = 1 , 100

    path ( j ) = 0 . 0prop ( j ) = 0

    End Do! f ind energy of i n i t i a l path

    oldE = energy ( path , 100)! pick random element , change by random

    Do i = 1 , maxelement = ranDom ( ) *100 + 1change = ( ( ranDom ( ) 0 . 5 ) * 2 )path ( element ) = path ( element ) + changenewE = energy ( path , 100) ! f ind new energy

    ! Metropolis algorithm

    I f ( ( newE > oldE ) .AND. ( exp ( newE + oldE ) < ranDom ( ) ) ) thenpath ( element ) = path ( element ) change

    EndIf! add up p r o b a b i l i t i e s

    Do j = 1 , 100element = path ( j ) *10 + 50prop ( element ) = prop ( element ) + 1

    End DooldE = newE

    End Do! write output data to f i l e

    Do j = 1 , 100out = prop ( j )write ( 9 , * ) j 50 , out/max

    End Doc lose ( 9 )Stop data saved in qmc.dat

    End Program qmc! Function ca l cu l a t e s energy of the system

    Function energy ( array , max )Imp l i c i t noneIn t ege r : : i , maxReal *8 : : energy , array (max)energy = 0Do i = 1 , (max 1)

    energy = energy + ( array ( i + 1) array ( i ) ) * * 2 + array ( i ) * * 2End Do

    ReturnEnd

  • 496 C Fortran 95 Codes

    Listing C.21: rk4.f95

    ! rk4 . f90 : 4 th order rk so lu t ion for harmonic o s c i l l a t o r

    Program o s c i l l a t o r

    Imp l i c i t none! n : number of equat ions , min/max in x , d i s t : length of x s teps! y ( 1 ) : i n i t i a l pos i t ion , y ( 2 ) : i n i t i a l v e l o c i t yReal *8 : : d is t , min1 , max1 , x , y ( 5 )In t ege r : : n

    n = 2min1 = 0 . 0 ; max1 = 10 . 0d i s t = 0 . 1y ( 1 ) = 1 . 0 ; y ( 2 ) = 0 .open ( 6 , F i l e = rk4.dat , S t a tus = Unknown )

    ! Do n steps rk algorithmDo x = min1 , max1 , d i s t

    c a l l rk4 ( x , d is t , y , n )write ( 6 , * ) x , y ( 1 )

    End Doc lose ( 6 )Stop data saved in rk4.dat

    End Program o s c i l l a t o r ! End of main Program

    subrout ine rk4 ( x , xstep , y , n ) ! rk4 subrout ineImp l i c i t noneReal *8 : : deriv , h , x , xstep , y ( 5 )Real * 8 , dimension ( 5 ) : : k1 , k2 , k3 , k4 , t1 , t2 , t 3In t ege r : : i , nh = xstep /2.0Do i = 1 , n

    k1 ( i ) = xstep * deriv ( x , y , i )t 1 ( i ) = y ( i ) + 0 . 5 * k1 ( i )

    End DoDo i = 1 , n

    k2 ( i ) = xstep * deriv ( x + h , t1 , i )t 2 ( i ) = y ( i ) + 0 . 5 * k2 ( i )

    End DoDo i = 1 , n

    k3 ( i ) = xstep * deriv ( x + h , t2 , i )t 3 ( i ) = y ( i ) + k3 ( i )

    End DoDo i = 1 , n

    k4 ( i ) = xstep * deriv ( x + xstep , t3 , i )y ( i ) = y ( i ) + ( k1 ( i ) + ( 2 . * ( k2 ( i ) + k3 ( i ) ) ) + k4 ( i ) ) /6.0

    End DoReturn

    End! Function Returns de r iva t iv e s

    Function deriv ( x , temp , i )Imp l i c i t noneReal *8 : : deriv , x , temp ( 2 )In t ege r : : iI f ( i == 1) deriv = temp ( 2 )I f ( i == 2) deriv = temp ( 1 )Return

    End

  • 497

    Listing C.22: rk45.f95

    ! rk45 . f90 : ODE so lve r via var i ab l e s tep s ize rk , Tol = e r ror

    Program Rk45

    Imp l i c i t noneReal *8 : : h , t , s , hmin , hmax , Tol = 2*1E 7 , Tmin = 0 . , &

    Tmax = 10 .Real * 8 , dimension ( 2 ) : : y , FReturn , ydumb, k1 , k2 , k3 , k4 , &

    k5 , k6 , e r rIn t ege r : : i , Ntimes = 10

    Open ( 6 , FILE = rk45.dat , S t a tus = Unknown )! i n i t i a l i z e

    y ( 1 ) = 3 . 0 ; y ( 2 ) = 5 . 0h = (Tmax Tmin ) / Ntimes ! t e n t a t i v e number of s tepshmin = h/64hmax = h*64 ! minimum and maximum step s izet = Tmin

    ! output to f i l eDo while ( t < Tmax)

    write ( * , * ) t , y ( 1 ) , y ( 2 )write ( 6 , * ) t , y ( 1 )I f ( ( t + h ) > Tmax ) then

    h = Tmax t ! the l a s t s tepEndIf

    ! evaluate both RHSs and Return in Fc a l l f ( t , y , FReturn )Do i = 1 , 2

    k1 ( i ) = h* FReturn ( i )ydumb( i ) = y ( i ) + k1 ( i ) /4

    End Doc 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 Doc a l l f ( t + 3*h/8 , ydumb, FReturn )Do i = 1 , 2

    k3 ( i ) = h* FReturn ( i )ydumb( i ) = y ( i ) + 1932*k1 ( i ) /2197 7200* k2 ( i ) /2197. &

    + 7296* k3 ( i ) /2197End Doc a l l f ( t + 12*h/13 , ydumb, FReturn )Do i = 1 , 2

    k4 ( i ) = h* FReturn ( i )ydumb( i ) = y ( i ) + 439* k1 ( i ) /2168*k2 ( i ) &

    + 3680* k3 ( i ) /513845* k4 ( i ) /4104End Doc a l l f ( t + h , ydumb, FReturn )Do i = 1 , 2k5 ( i ) = h* FReturn ( i )ydumb( i ) = y ( i ) 8* k1 ( i ) /27 + 2* k2 ( i ) 3544* k3 ( i ) /2565 &

    + 1859* k4 ( i ) /4104 11* k5 ( i ) /40End Doc a l l f ( t + h/2 , ydumb, FReturn )

  • 498 C Fortran 95 Codes

    Do i = 1 , 2k6 ( i ) = h* FReturn ( i )e r r ( i ) = abs ( k1 ( i ) /360 128* k3 ( i ) /4275 2197*k4 ( i ) /75240 &

    + k5 ( i ) /50. + 2* k6 ( i ) /55 )End DoI f ( ( e r r ( 1 ) < Tol ) . or . ( e r r ( 2 ) < Tol ) . or . ( h 2*hmin) ) then

    h = h/2 . ! reduce s tepelse I f ( ( s > 1 . 5 ) . and . ( 2 * h < hmax) ) then

    h = h * 2 . ! in c rease s tepEndif

    ! End loopEnd Doc lose ( 6 )StopData stored in rk45.dat

    End Program Rk45! PLACE YOUR FUNCTION HERE

    subrout ine f ( t , y , FReturn )Imp l i c i t none ; Real *8 t , y ( 2 ) , FReturn ( 2 )FReturn ( 1 ) = y ( 2 ) ! RHS of f i r s t equat ionFReturn ( 2 ) = 100*y ( 1 ) 2*y ( 2 ) + 10* s in ( 3 * t ) ! RHS of 2nd equat ionReturn

    End

    Listing C.23: random.f95

    ! ranDom . f90 : simple random number generator , not for se r ious work

    Program random

    Imp l i c i t noneIn t ege r : : i , number , old , seed , x , y

    ! s e t parameters ( seed for generator , number of generated numbers )seed = 11number = 1000! open output f i l e , seed number generatoropen ( 6 , FILE = ranDom.dat , S t a tus = Unknown )old = seed

    ! execut ionDo i = 1 , number

    x = modulo ( ( 5 7 * old + 1) , 256)

  • 499

    y = modulo ( ( 5 7 * x + 1) , 256)write ( 6 , * ) x , yold = y

    End Doc lose ( 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 in p space from de l t a sh e l l! po t en t i a l , LU decomposition with p a r t i a l p ivot ing .! uses gauss . f , LUfactor , LUSolve ( included )

    Program s c a t t

    In t ege r : : n , Size , i , j , Row, ColumnDouble Pre c i s ion : : b , PotParameter ( S ize = 300 , pi = 3.1415926535897932384626 , b = 10 . 0 )Double Pre c i s ion : : lambda , sca le , ko , TempDouble Pre c i s ion : : F ( Size , S ize ) , k ( S ize ) , w( S ize ) ,D( S ize ) , r ( S ize )Double Pre c i s ion : : V( S ize ) ,L ( Size , S ize ) ,U( Size , S ize ) , P ( Size , S ize )In t ege r : : P ivot In fo ( S ize )

    ! Enter po t en t i a l s t rength lambdaWrite ( * , * ) enter lambdaRead ( * , * ) lambdaWrite ( * , * ) enter scaling factorRead ( * , * ) s c a l eWrite ( * , * ) enter koRead ( * , * ) koWrite ( * , * ) enter grid sizeRead ( * , * ) n

    ! Se t up Gaussian in t e g r a t i on poin t s and weights! on in t e rv a l [ 0 , i n f ] with the mid point at scale

    ! Se t l a s t element in k array to koc a l l gauss (n , 2 , 0d0 , sca le , k , w)

    ! Se t up D matrixDo i = 1 , n

    D( i ) = 2 . 0 d0/pi *w( i ) *k ( i ) * k ( i ) /(k ( i ) *k ( i ) ko*ko )End DoD(n + 1) = 0 . 0Do j = 1 , n

    D(n + 1) = D(n + 1) + w( j ) *ko *ko/(k ( j ) * k ( j ) ko *ko )End DoD(n + 1) = D(n + 1) * ( 2 . 0 d0/pi )

    ! Se t up F matrix and V vectorDo i = 1 , n

    Do j = 1 , nPot = 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

    EndifEnd DoV( i ) = Pot

    End Do! LU f a c t o r i z a t i o n . Put LU fa c t o r s of F in corresponding matrix! ( not e f f i c i e n t but easy ) . S tore p a r t i a l p ivot ing in fo!c a l l LUfactor ( F , n , Size , L , U, Pivot In fo )

    ! Pivot and solve! Se t P to id en t i t y matrix

    Do Row = 1 , n + 1Do Column = 1 , n + 1

    P(Row, Column) = 0I f (Row .EQ. Column) P (Row, Column) = 1

    End DoEnd Do

    ! Interchange rows to get t rue P matrixDo Row = 1 , n

    Do Column = 1 , nTemp = P(Row, Column)P(Row, Column) = P( Pivot In fo (Row) , Column)P( Pivot In fo (Row) , Column) = Temp

    End DoEnd Doc a l l LUSolve (V, L , U, n , Size , P ivot In fo , r )

    ! output r e su l t swrite ( * , * ) 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 on , p a r t i a l p ivot ing of A in Ax = bsubrout ine LUfactor (A, n , Size , L , U, Pivot In fo )

    In t ege r : : n , Column , CurrentPivotRow , CurrentRow , SwapCol , RowIn t ege r : : ElimCol , S izeDouble Pre c i s ion : : A( Size , S ize ) , L ( Size , S ize ) , U( Size , S ize )In t ege r : : P ivot In fo ( S ize )Double Pre c i s ion : : CurrentPivotValue , SwapDo Column = 1 , n 1

    CurrentPivotRow = ColumnCurrentPivotValue = A( CurrentPivotRow , Column)

    ! Determine row for l a r g e s t pivotDo CurrentRow = Column + 1 , n

    I f ( DABS(A(CurrentRow , Column) ) .GT. CurrentPivotValue ) ThenCurrentPivotValue = DABS(A( CurrentRow , Column) )CurrentPivotRow = CurrentRow

    EndifEnd DoPivot In fo (Column) = CurrentPivotRow

    ! Swap rows so l a r g e s t value at pivotDo SwapCol = Column , n

    Swap = A(Column , SwapCol )A(Column , SwapCol ) = A( Pivot In fo (Column) , SwapCol )A( Pivot In fo (Column) , Swapcol ) = Swap

    End Do!! Gauss Elimin , upper t r i angu la r A, unpivoted lower t r i angu la 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 DoEnd Do

    End Do! Ensure bottom r igh t not pivoted to 0

    Pivot In fo (n ) = nDo Row = 2 , n 1

    ! Now pivot the LDO Column = 1 , Row 1

    Swap = L(Row, Column)L(Row, Column) = L( Pivot In fo (Row) , Column)L( Pivot In fo (Row) , Column) = Swap

    End DoEnd Do

    ! Clean up L and UDo Column = 1 , n

    Do Row = 1 , ColumnU(Row, Column) = A(Row, Column)L(Row, Column) = 0IF (Row .EQ. Column) L(Row, Column) = 1

    End DoDo Row = Column + 1 , n

    U(Row, Column) = 0End Do

    End DoReturn

    End

    ! Par t of an LU decomposition + p a r t i a l p ivot ing to solve Ax = bSubrout ine LUSolve ( b , L , U, n , Size , P ivot In fo , x )

    In t ege r : : n , Size , Row, ColumnDouble Pre c i s ion : : b ( S ize ) , x ( S ize )In t ege r : : P ivot In fo ( S ize )Double Pre c i s ion : : L ( Size , S ize ) , U( Size , S ize )Double Pre c i s ion : : TempDo Row = 1 , n ! Interchange rows of b for pivot ing

    Temp = b (Row)b (Row) = b ( Pivot In fo (Row) )b ( Pivot In fo (Row) ) = Temp

    End Do! Solve Ly = b , where y = Ux, by forward e l im ina t ion

    Do Row = 2 , nDO Column = 1 , Row 1

    b (Row) = b (Row) L(Row, Column) *b (Column)End Dob (Row) = b (Row)/L(Row, Row)

    End Do! Solve Ux = y by back sub s t i t u t i on

    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 DoReturn

    End

    Listing C.25: slit.f95

    ! s l i t . f90 : Solves time dependent Schroedinger equat ion for a! two dimensional Gaussian wavepacket enter ing a s l i t

    Program s l i t

    Imp l i c i t noneReal *8 : : psr ( 91 , 91 , 2 ) , ps i ( 91 , 91 , 2 ) , v ( 91 , 91) , p2 (91 , 91)Real *8 : : a1 , a2 , dt , dx , k0x , k0y , x0 , y0 , x , yIn t ege r i , j , k , max , n , timeComplex exc , z i

    ! input pos i t iv e in t proport ional to time for plotwrite ( * , * )Enter a positive Integer from 1(initial time)write ( * , * )to 800 to get wave packet position at that timeread ( * , * ) t imewrite ( * , * )processing data for time , t imeopen ( 9 , FILE = slit.dat , S t a tus = Unknown )

    ! i n i t i a l i z e constants and wave packetz i = cmplx ( 0 . 0 , 1 . 0 )dx = 0 . 2dt = 0 .0025/( dx*dx )

    ! i n i t i a l momentum, pos i t i onk0x = 0 . 0 ; k0y = 2 . 5x0 = 0 . 0 ; y0 = 7 . 0max = 90

    ! c l e a r the arraysDo i = 1 , 91

    Do j = 1 , 91Do k = 1 , 2

    ps i ( i , j , k ) = 0 . 0psr ( i , j , k ) = 0 . 0

    End DoEnd Do

    End Do! i n i t i a l wave funct ion

    y = 9 . 0Do j = 1 , max + 1

    x = 9 . 0 d0Do 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 ) ! r e a l par tps i ( i , j , 1 ) = aimag ( a1 * exc ) ! imaginay partx = x + dx

    End Doy = y + dx

    End Do! se t po t en t i a l s l i t width : 50 40 = 10 un i t s

    Do j = 1 , max + 1

  • 503

    Do i = 1 , max + 1I f ( ( j == 35) . and . ( ( i < 40) . or . ( i > 51) ) ) then

    v ( i , j ) = 0 . 5else

    v ( i , j ) = 0 . 0Endif

    End DoEnd Do

    ! propagate ps i through timeDo n = 1 , time

    ! compute r e a l wave packet and probab i l i t yDo j = 2 , max

    Do i = 2 , maxa2 = v ( i , j ) * ps i ( i , j , 1 ) + 2 . 0 d0* dt * ps i ( i , j , 1 )

    a1 = psi ( i +1 , j , 1 ) + ps i ( i 1, j , 1 ) +ps i ( i , j +1 ,1 ) + ps i ( i , j 1 ,1)psr ( i , j , 2 ) = psr ( i , j , 1 ) dt * a1 + 2 . 0 * a2I f (n == time ) then

    p2 ( i , j ) = psr ( i , j , 1 ) * psr ( i , j , 1 ) + ps i ( i , j , 1 ) * ps i ( i , j , 1 )Endif

    End Dopsr ( 1 , j , 2 ) = psr ( 2 , j , 2 ) ! a t x edges de r iva t iv e =0psr (max + 1 , j , 2 ) = psr (max, j , 2 )

    End Do! imaginary par t of ps i

    Do j = 2 , maxDo 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 )ps i ( i , j , 2 ) = ps i ( i , j , 1 ) + dt * a1 2 . 0 * a2

    End Dopsi ( 1 , j , 2 ) = ps i ( 2 , j , 2 ) ! a t x edges de r iva t iv e =0ps i (max + 1 , j , 2 ) = ps i (max, j , 2 )

    End Do! new > old

    Do j = 1 , max + 1Do i = 1 , max + 1

    psi ( i , j , 1 ) = ps i ( i , j , 2 )psr ( i , j , 1 ) = psr ( i , j , 2 )

    End DoEnd Do

    End Do! write p r o b ab i l i t i e s & po t en t i a l sca led by 0 .025 ( to f i t )

    Do j = 2 , max , 3Do i = 2 , max, 2

    write ( 9 , 11)p2 ( i , j ) + v ( i , j )End Dowrite ( 9 , * )

    End Do11 format ( E12 . 6 )c lose ( 9 )Stop data saved in slit.dat

    End

  • 504 C Fortran 95 Codes

    Listing C.26: soliton.f95

    ! s o l i t on . f90 : Solves the KdeV Equation via f i n i t e d i f f e r en ce s!Program so l i t on

    Imp l i c i t NoneReal *8 : : ds , dt , max , mu, eps , u (131 , 3 )parameter ( ds = 0 . 4 , dt = 0 . 1 , max = 2000 , mu = 0 . 1 , eps = 0 . 2 )

    ! de l t a t , d e l t a x , t ime steps , mu and eps from KdeV equat ionReal *8 : : a1 , a2 , a3 , fac , t imeIn t ege r : : i , j , k

    open ( 9 , FILE = soliton.dat , S t a tus = Unknown )! I n i t i a l condi t ion

    Do i = 1 , 131u ( 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 . )t ime = dt

    ! f i r s t s t epDo 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 2) . and . ( i old

    Do k = 1 , 131u(k , 1 ) = u (k , 2 )u( k , 2 ) = u (k , 3 )

    End Do! output every 200 time steps

  • 505

    I f (modulo ( j , 200) == 0) thenDo k = 1 , 131

    write ( 9 , 22)u ( k , 3 )End Dowrite ( 9 , 22)

    EndIftime = time + dt

    End Do22 format ( f10 . 6 )c lose ( 9 )Stop data saved in soliton.dat (for gnuplot)

    End Program so l i t on

    Listing C.27: Spline.f95

    ! sp l ine . f90 : Cubic Spl ine f i t , based on " Numerical Recipes in C "

    Program sp l ine

    Imp l i c i t none

    ! input array x [n ] , y [ n ] rep re sen t s t abu la t ion Function y ( x )! with x0 < x1 . . . < x (n 1) . n = # of tabulated poin ts! output yout for given xout ( here xout via loop at End)! yp1 and ypn : 1 s t de r iva t iv e s at Endpoints , evaluated in t e rn a l l y! y2 [n ] i s array of second der iva t iv e s! ( s e t t i n g yp1 or ypn > 0 . 99 e30 produces natura l sp l ine )

    Real *8 : : xout , yout , h , b , a , Nfit , p , qn , sig , un , yp1 , ypn , x ( 9 )REAL*8 : : y ( 9 ) , y2 ( 9 ) , u ( 9 )In t ege r : : klo , khi , k , n , i

    ! Save data , input dataopen ( 9 , FILE = Spline.dat , S t a tus = Unknown )open (10 , FILE = Input.dat , S t a tus = Unknown )

    ! en ter 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 . 93 , 0 . 6 , 0 . 53 , 0 . 96 , 0 . 08 , 0 . 94 , 0 . 66 , 0.46 /n = 9

    Do i = 1 , nwrite ( 10 , * ) x ( i ) , y ( i )

    End DoNfi t = 3000 ;

    ! en ter the des ired number of poin ts to f i typ1 = (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 derivypn = ( y (n1) y (n2) ) /(x ( n1) x (n2) ) ( y ( n2) &

    y (n3) ) /(x ( n2)x (n3) ) + ( y ( n1)y (n3) ) /(x (n1)x (n3) )I f ( yp1 > 0 . 99 e30 ) then

    y2 ( 1 ) = 0 . 0u ( 1 ) = 0 . 0

    elsey2 ( 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 are temps

  • 506 C Fortran 95 Codes

    Do i = 2 , n 1s ig = ( x ( i ) x ( i 1) ) /(x ( i + 1) x ( i 1) ) ;p = s ig * y2 ( i 1) + 2 . 0y2 ( i ) = ( s ig 1 . 0 ) /pu( 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 ig *u ( i 1) )/p ;

    End Do! t e s t for natura l

    ! else evaluate second de r iva t iv eI f ( ypn > 0 . 99 e30 ) then

    qn = 0 . 0un = 0 .else

    qn = 0 . 5un = (3/( x (n1) x (n2) ) ) * ( ypn ( y ( n1)y (n2) ) &

    /(x (n1) x (n2) ) )y2 ( n 1) = (un qn*u (n 2) ) /(qn * y2 (n 2) + 1 . 0 )

    Endif! back sub s t i t u t i on

    Do k = n 2 , 1 , 1y2 ( k ) = y2 ( k ) * y2 ( k + 1) + u (k )

    End Do ! sp l i n t ( i n i t i a l i z a t i o n ) Ends

    ! Parameters determined , Begin * sp l ine * f i t! loop over xout values

    Do i = 1 , Nf i txout = x ( 1 ) + ( x ( n ) x ( 1 ) ) * ( i ) /( Nf i t )klo = 0khi = n 1

    ! B i se c t ion algor for place in t ab le! klo , khi bracke t xout

    Do while ( khi klo > 1)k = ( khi + klo ) /2.0I f ( x ( k ) > xout ) then

    khi = kelse

    klo = kEndif

    End Doh = x ( khi ) x ( klo )I f ( x ( k ) > xout ) then

    khi = kelse

    klo = kEndifh = x ( khi ) x ( klo )a = ( x ( khi ) xout )/hb = ( xout x ( klo ) )/hyout = ( a *y ( klo )+b*y ( khi ) &

    + ( ( a * a *aa ) * y2 ( klo ) +(b*b *bb ) * y2 ( khi ) ) *h*h/6)! write data in gnuplot 2D format

    write ( 9 , * ) xout , youtEnd DoStop data stored in Spline.dat

    End Program sp l ine

  • 507

    Listing C.28: sqwell.f95

    ! sqwell . f90 : Solves the tdependent Schroedinger equat ion for a! Gaussian wavepacket in a i n f i n i t e square well po t en t i a l

    Program sqwell

    Imp l i c i t NoneReal *8 : : psr ( 751 , 2 ) , ps i ( 751 , 2 ) , p2 (751 )Real *8 : : dx , k0 , dt , x , piIn t ege r : : i , j , n , maxComplex exc , z i

    Common /values/dx , dt

    open ( 9 , FILE = sqwell.dat , S t a tus = Unknown )max = 750pi = 3.14159265358979323846z i = CMPLX( 0 . 0 , 1 . 0 )dx = 0 . 02k0 = 17 . 0 * pidt = dx*dx

    ! c l e a r the arraysDo i = 1 , 751

    Do j = 1 , 2psr ( i , j ) = 0 . 0ps i ( i , j ) = 0 . 0p2 ( i ) = 0 . 0

    End DoEnd Do

    ! i n i t i a l condi t ionsx = 0 . 0Do 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 par tps i ( i , 1 ) = aimag ( exc * exp ( 0 . 5 * ( 2 . 0 * ( x 5 . 0 ) ) * * 2 ) ) ! imagx = x + dx

    End Do! propagate so lu t ion through time

    Do n = 1 , 6000Do i = 2 , max ! r e a l par t & prob

    psr ( i , 2 ) = psr ( i , 1 ) dt * ( ps i ( i + 1 , 1 ) + ps i ( i 1 , 1 )& 2 . 0 * ps i ( i , 1 ) ) / ( 2 . 0 * dx*dx )

    p2 ( i ) = psr ( i , 1 ) * psr ( i , 2 ) + ps i ( i , 1 ) * ps i ( i , 1 )End DoDo i = 2 , max ! imaginary part

    ps i ( i , 2 ) = ps 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 pr in tout

    I f (Mod(n , 300) == 0) thenDo i = 1 , max + 1 , 15

    write ( 9 , 11) p2 ( i )End Dowrite ( 9 , * )

    Endif! new so l tn > old

  • 508 C Fortran 95 Codes

    Do i = 1 , max + 1ps i ( i , 1 ) = ps i ( i , 2 )psr ( i , 1 ) = psr ( i , 2 )

    End DoEnd Do

    11 format ( E12 . 6 )c lose ( 9 )Stop data saved in sqwell.dat

    End

    Listing C.29: tune.f95

    ! tune . f90 : matrix a lgebra program to be tuned for performace

    Program tune

    parameter ( ldim = 2050)Imp l i c i t Double pre c i s ion ( a h , o z )dimension ham( ldim , ldim ) , coe f ( ldim ) , sigma ( ldim )

    ! s e t up H and s t a r t i n g vectorDo i = 1 , ldim

    Do j = 1 , ldimI f ( abs ( j i ) > 10) thenham( j , i ) = 0 .

    elseham( j , i ) = 0 . 3 * *Abs( j i )

    EndIfEnd Doham( i , i ) = icoe f ( i ) = 0 .

    End Docoef ( 1 ) = 1 .

    ! s t a r t i t e r a t i n ge r r = 1 .i t e r = 0

    20 I f ( i t e r < 15 . and . e r r >1.e6) theni t e r = i t e r + 1

    ! compute current energy & normalizeener = 0 .ovlp = 0 .Do i = 1 , ldim

    ovlp = ovlp + coef ( i ) * coe f ( i )sigma ( i ) = 0 .Do j = 1 , ldim

    sigma ( i ) = sigma ( i ) + coef ( j ) *ham( j , i )End Doener = ener + coef ( i ) * sigma ( i )

    End Doener = ener/ovlpDo I = 1 , ldim

    coef ( i ) = coef ( i )/Sqrt ( ovlp )sigma ( i ) = sigma ( i )/Sqrt ( ovlp )

    End Do! compute update and e r ror norm

    err = 0 .Do i = 1 , ldim

  • 509

    I f ( i == 1) goto 23step = ( sigma ( i ) ener * coe f ( i ) ) /( ener ham( i , i ) )coe f ( i ) = coef ( i ) + s tepe r r = e r r + step * *2

    23 End Doer r = sqr t ( e r r )

    write ( * , (1x, i2, 7f10.5) ) i t e r , ener , err , coe f ( 1 )goto 20

    EndifStop

    End Program tune

    Listing C.30: twodsol.f95

    ! twodsol . f90 : Solves the s ine Gordon equat ion for a 2D so l i t on

    Program twodsol

    Imp l i c i t noneDouble pre c i s ion : : u (201 , 201 , 3 )In t ege r : : n in t

    Open ( 9 , FILE = twodsol.dat , S t a tus = UNKNOW )write ( * , * ) Enter an Integer from 1 to 100write ( * , * ) this number is proportional to timewrite ( * , * ) time = 0 is for the Integer = 1read ( * , * ) n in twrite ( * , * )working with input = , n in tc a l l i n i t i a l (u ) ! i n i t i a l i z e

    ! output for t proport ional to n in tc a l l so lu t ion (u , n in t )Stop

    End Program twodsol! i n i t i a l i z e constants and so l i t on

    Subrout ine i n i t i a l (u)Imp l i c i t none

    In t ege r : : i , j , kDouble pre c i s ion : : u (201 , 201 , 3 ) , dx , dy , dt , xx , yy , dts , t ime

    Common /values/ dx , dy , dt , time , dtsDo i = 1 , 201 ! c l e a r arrays

    Do j = 1 , 201Do k = 1 , 3

    u ( i , j , k ) = 0 . 0End Do

    End DoEnd Dodx = 14 . 0/200 . ! i n i t i a l condi t iondy = dxdt = dx/sqr t ( 2 . 0 )dts = ( dt/dx ) * * 2yy = 7 . 0time = 0 . 0Do i = 1 , 201

    xx = 7 . 0Do j = 1 , 201

  • 510 C Fortran 95 Codes

    u( i , j , 1 ) = 4 . 0 * Datan ( 3 . sqr t ( xx * xx + yy*yy ) )xx = xx + dx

    End Doyy = yy + dy

    End DoReturn

    End! solve SGE, i n i t i a l condi t ions in i n i t i a l

    Subrout ine so lu t ion (u , n in t )Imp l i c i t noneDouble pre c i s ion : : u (201 , 201 , 3 ) , dx , dy , dt , time , a2 , zz , dts , a1In t ege r : : l , m, mm, k , j , i , n in tCommon/values/ dx , dy , dt , time , dtstime = 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 at x0 , x0 , y0 and y0

    Do l = 2 , 200Do m = 2 , 200

    a2 = u(m+1 , l , 1 ) + u(m1, l , 1 ) + u (m, l +1 , 1 ) + u (m, l 1, 1 )u(m, l , 2 ) = 0 . 5 * ( dts * a2 dt * dt *DSIN ( 0 . 2 5 * a2 ) )

    End DoEnd Do

    ! the borders in 2nd i t e r a t i o nDo mm = 2 , 200

    u (mm, 1 , 2 ) = u (mm, 2 , 2 )u (mm, 201 , 2 ) = u (mm, 200 , 2 )u ( 1 , mm, 2) = u ( 2 , mm, 2)u (201 , mm, 2) = u (200 , mm, 2)

    End Do! the 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 )

    ! 3rd and fol lowing i t e r a t i o n s use your input , loop up to n in tDo k = 1 , n in t

    Do l = 2 , 200Do m = 2 , 200

    a1 = u(m+1 , l , 2 ) + u (m1, l , 2 ) + u (m, l +1 ,2 ) + u (m, l 1, 2 )u (m, l , 3 ) = u(m, l , 1 ) + dts * a1 dt * dt *DSIN ( 0 . 2 5 * a1 )u (m, 1 , 3 ) = u (m, 2 , 3 )u (m, 201 , 3 ) = u (m, 200 , 3 )

    End DoEnd DoDo mm = 2 , 200

    u(mm, 1 , 3 ) = u (mm, 2 , 3 )u(mm, 201 , 3 ) = u (mm, 200 , 3 )u ( 1 , mm, 3) = u ( 2 , mm, 3)u(201 , mm, 3) = u (200 , mm, 3)

    End Dou( 1 , 1 , 3 ) = u ( 2 , 1 , 3 )u (201 , 1 , 3 ) = u(200 , 1 , 3 )u ( 1 , 201 , 3 ) = u ( 2 , 201 , 3 )u (201 , 201 , 3 ) = u (200 , 201 , 3 )! new > oldDo 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 DoEnd Do

    ! Output so lu t ion at time proport ional to n in tI f ( k == nin t ) thenDo i = 1 , 201 , 5

    Do j = 1 , 201 , 5zz = DSIN (u ( i , j , 3 ) /2 . 0 )write ( 9 , * ) zz

    End Do! need blank l i n e s to separate s p a t i a l rows for 3D

    write ( 9 , * ) End Do

    Endiftime = time + dt

    End DoReturn

    End

    Listing C.31: walk.f95

    ! walk . f90 :RanDom walk s imulat ion

    Program walk

    Imp l i c i t noneReal *8 : : ranDom , root2 , x , y , r ( 1 : 1 0 0 00 )In t ege r : : i , j , max

    max = 10000 ! s e t parameters (# of s teps )root2 = 1.4142135623730950488 E0open ( 6 , FILE = walk.dat , S t a tus = Unknown ) ! open f i l e

    ! c l e a r arrayDo j = 1 , max

    r ( j ) = 0End Do

    ! average over 100 t r i a l sDo j = 1 , 100

    x = 0 .y = 0 .Do i = 1 , max

    x = x + ( ranDom ( ) 0 . 5 ) * 2 . 0 * root2y = y + ( ranDom ( ) 0 . 5 ) * 2 . 0 * root2r ( i ) = r ( i ) + Sqrt ( x *x + y*y )

    End DoEnd Do

    ! output data for plot of r vs . sq r t (N)Do i = 1 , max

    Write ( 6 , * ) Sqr t ( Real ( i ) ) , , r ( i ) /100End Doc lose ( 6 )Stop data saved in walk.dat

    End Program walk