source: branches/ignacio/FLEXPART_9.1.8/src/erf.f90 @ 18

Last change on this file since 18 was 18, checked in by igpis, 10 years ago

add verbose mode to version 9.1.7.1

File size: 5.2 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22! To be used, if the non-standard Fortran function erf does not exist on
23! your machine
24!
25!aus:  Numerical Recipes (FORTRAN) / Chapter 6.
26!
27!6.1  FUNCTION GAMMLN
28!6.2  FUNCTION GAMMP   <6.2:GSER/6.2:GCF/6.1:GAMMLN>
29!6.2  FUNCTION GAMMQ   <6.2:GSER/6.2:GCF/6.1:GAMMLN>
30!6.2  SUBROUTINE GSER    <6.1:GAMMLN>
31!6.2  SUBROUTINE GCF     <6.1:GAMMLN>
32!6.2  FUNCTION ERF     <6.2:GAMMP/6.2:GSER/6.2:GCF/6.1:GAMMLN>
33!6.2  FUNCTION ERFC    <6.2.:GAMMP/6.2:GAMMQ/6.2:GSER/
34!                       6.2:GCF/6.1:GAMMLN>
35!6.2  FUNCTION ERFCC
36
37function gammln(xx)
38
39  use par_mod, only: dp
40
41  implicit none
42
43  integer :: j
44  real(kind=dp) :: x,tmp,ser,xx,gammln
45  real(KIND=dp) :: cof(6) = (/ &
46       76.18009173_dp, -86.50532033_dp, 24.01409822_dp, &
47       -1.231739516_dp, .120858003e-2_dp, -.536382e-5_dp    /)
48  real(KIND=dp) :: stp = 2.50662827465_dp
49  real(KIND=dp) :: half = 0.5_dp, one = 1.0_dp, fpf = 5.5_dp
50
51  x=xx-one
52  tmp=x+fpf
53  tmp=(x+half)*log(tmp)-tmp
54  ser=one
55  do j=1,6
56    x=x+one
57    ser=ser+cof(j)/x
58  end do
59  gammln=tmp+log(stp*ser)
60end function gammln
61
62function gammp(a,x)
63
64  use par_mod, only: dp
65
66  implicit none
67
68  real(KIND=dp) :: a, x, gln, gamser, gammp, gammcf
69
70  if(x .lt. 0. .or. a .le. 0.) then
71     print*, 'gammp'
72     stop
73  end if
74  if(x.lt.a+1.)then
75    call gser(gamser,a,x,gln)
76    gammp=gamser
77  else
78    call gcf(gammcf,a,x,gln)
79    gammp=1.-gammcf
80  endif
81end function gammp
82
83function gammq(a,x)
84
85  use par_mod, only: dp
86
87  implicit none
88
89  real(KIND=dp) :: a, x, gln, gamser, gammq, gammcf
90
91  if(x.lt.0..or.a.le.0.) then
92     print*, 'gammq'
93     stop
94  end if
95  if(x.lt.a+1.)then
96    call gser(gamser,a,x,gln)
97    gammq=1.-gamser
98  else
99    call gcf(gammcf,a,x,gln)
100    gammq=gammcf
101  endif
102end function gammq
103
104subroutine gser(gamser,a,x,gln)
105
106  use par_mod, only: dp
107
108  implicit none
109
110  integer :: n
111  real(KIND=dp) :: gamser, a, x, gln, ap, summ, del
112  real(KIND=dp), external :: gammln
113
114  integer,parameter :: itmax=100
115  real,parameter    :: eps=3.e-7
116
117  gln=gammln(a)
118  if(x.le.0.)then
119    if(x.lt.0.) then
120       print*, 'gser'
121       stop
122    end if
123    gamser=0.
124    return
125  endif
126  ap=a
127  summ=1./a
128  del=summ
129  do n=1,itmax
130    ap=ap+1.
131    del=del*x/ap
132    summ=summ+del
133    if(abs(del).lt.abs(summ)*eps)go to 1
134  end do
135  print*, 'gser: a too large, itmax too small'
136  stop
1371   gamser=summ*exp(-x+a*log(x)-gln)
138end subroutine gser
139
140subroutine gcf(gammcf,a,x,gln)
141
142  use par_mod, only: dp
143
144  implicit none
145
146  integer :: n
147  real(KIND=4) :: gammcf, x, a, gln, gold, a0, a1, b0, b1, fac, an, anf, ana, g
148  real(KIND=dp), external :: gammln
149
150  integer,parameter :: itmax=100
151  real,parameter    :: eps=3.e-7
152
153  gln=gammln(a)
154  gold=0.
155  a0=1.
156  a1=x
157  b0=0.
158  b1=1.
159  fac=1.
160  do n=1,itmax
161    an=real(n)
162    ana=an-a
163    a0=(a1+a0*ana)*fac
164    b0=(b1+b0*ana)*fac
165    anf=an*fac
166    a1=x*a0+anf*a1
167    b1=x*b0+anf*b1
168    if(a1.ne.0.)then
169      fac=1./a1
170      g=b1*fac
171      if(abs((g-gold)/g).lt.eps)go to 1
172      gold=g
173    endif
174  end do
175  print*, 'gcf: a too large, itmax too small'
176  stop
1771   gammcf=exp(-x+a*alog(x)-gln)*g
178end subroutine gcf
179
180function erf(x)
181
182  use par_mod, only: dp
183
184  implicit none
185
186  real(KIND=dp) :: x, erf
187  real(KIND=dp), external :: gammp
188
189  if(x.lt.0.)then
190    erf=-gammp(.5,x**2)
191  else
192    erf=gammp(.5,x**2)
193  endif
194end function erf
195
196function erfc(x)
197
198  use par_mod, only: dp
199
200  implicit none
201
202  real(KIND=dp) :: x, erfc
203  real(KIND=dp), external :: gammp, gammq
204
205  if(x.lt.0.)then
206    erfc=1.+gammp(.5,x**2)
207  else
208    erfc=gammq(.5,x**2)
209  endif
210end function erfc
211
212function erfcc(x)
213
214  use par_mod, only: dp
215
216  implicit none
217
218  real(KIND=dp) :: x, z, t, erfcc
219
220  z=abs(x)
221  t=1./(1.+0.5*z)
222  erfcc=t*exp(-z*z-1.26551223+t*(1.00002368+t*(.37409196+ &
223       t*(.09678418+t*(-.18628806+t*(.27886807+t*(-1.13520398+ &
224       t*(1.48851587+t*(-.82215223+t*.17087277)))))))))
225  if (x.lt.0.) erfcc=2.-erfcc
226end function erfcc
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG