source: flexpart.git/src/erf.f90 @ 3481cc1

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 3481cc1 was 3481cc1, checked in by Ignacio Pisso <ip@…>, 4 years ago

move license from headers to a different file

  • Property mode set to 100644
File size: 3.5 KB
Line 
1! To be used, if the non-standard Fortran function erf does not exist on
2! your machine
3!
4!aus:  Numerical Recipes (FORTRAN) / Chapter 6.
5!
6!6.1  FUNCTION GAMMLN
7!6.2  FUNCTION GAMMP   <6.2:GSER/6.2:GCF/6.1:GAMMLN>
8!6.2  FUNCTION GAMMQ   <6.2:GSER/6.2:GCF/6.1:GAMMLN>
9!6.2  SUBROUTINE GSER    <6.1:GAMMLN>
10!6.2  SUBROUTINE GCF     <6.1:GAMMLN>
11!6.2  FUNCTION ERF     <6.2:GAMMP/6.2:GSER/6.2:GCF/6.1:GAMMLN>
12!6.2  FUNCTION ERFC    <6.2.:GAMMP/6.2:GAMMQ/6.2:GSER/
13!                       6.2:GCF/6.1:GAMMLN>
14!6.2  FUNCTION ERFCC
15
16function gammln(xx)
17
18  use par_mod, only: dp
19
20  implicit none
21
22  integer :: j
23  real :: x,tmp,ser,xx,gammln
24  real :: cof(6) = (/ &
25       76.18009173_dp, -86.50532033_dp, 24.01409822_dp, &
26       -1.231739516_dp, .120858003e-2_dp, -.536382e-5_dp    /)
27  real :: stp = 2.50662827465_dp
28  real :: half = 0.5_dp, one = 1.0_dp, fpf = 5.5_dp
29
30  x=xx-one
31  tmp=x+fpf
32  tmp=(x+half)*log(tmp)-tmp
33  ser=one
34  do j=1,6
35    x=x+one
36    ser=ser+cof(j)/x
37  end do
38  gammln=tmp+log(stp*ser)
39end function gammln
40
41function gammp(a,x)
42
43  implicit none
44
45  real :: a, x, gln, gamser, gammp, gammcf
46
47  if(x .lt. 0. .or. a .le. 0.) then
48     print*, 'gammp'
49     stop
50  end if
51  if(x.lt.a+1.)then
52    call gser(gamser,a,x,gln)
53    gammp=gamser
54  else
55    call gcf(gammcf,a,x,gln)
56    gammp=1.-gammcf
57  endif
58end function gammp
59
60function gammq(a,x)
61
62  implicit none
63
64  real :: a, x, gln, gamser, gammq, gammcf
65
66  if(x.lt.0..or.a.le.0.) then
67     print*, 'gammq'
68     stop
69  end if
70  if(x.lt.a+1.)then
71    call gser(gamser,a,x,gln)
72    gammq=1.-gamser
73  else
74    call gcf(gammcf,a,x,gln)
75    gammq=gammcf
76  endif
77end function gammq
78
79subroutine gser(gamser,a,x,gln)
80
81  implicit none
82
83  integer :: n
84  real :: gamser, a, x, gln, ap, summ, del
85  real, external :: gammln
86
87  integer,parameter :: itmax=100
88  real,parameter    :: eps=3.e-7
89
90  gln=gammln(a)
91  if(x.le.0.)then
92    if(x.lt.0.) then
93       print*, 'gser'
94       stop
95    end if
96    gamser=0.
97    return
98  endif
99  ap=a
100  summ=1./a
101  del=summ
102  do n=1,itmax
103    ap=ap+1.
104    del=del*x/ap
105    summ=summ+del
106    if(abs(del).lt.abs(summ)*eps)go to 1
107  end do
108  print*, 'gser: a too large, itmax too small'
109  stop
1101   gamser=summ*exp(-x+a*log(x)-gln)
111end subroutine gser
112
113subroutine gcf(gammcf,a,x,gln)
114
115  implicit none
116
117  integer :: n
118  real :: gammcf, a, x, gln, gold, a0, a1, b0, b1, fac, an, anf, ana, g
119  real, external :: gammln
120
121  integer,parameter :: itmax=100
122  real,parameter    :: eps=3.e-7
123
124  gln=gammln(a)
125  gold=0.
126  a0=1.
127  a1=x
128  b0=0.
129  b1=1.
130  fac=1.
131  do n=1,itmax
132    an=real(n)
133    ana=an-a
134    a0=(a1+a0*ana)*fac
135    b0=(b1+b0*ana)*fac
136    anf=an*fac
137    a1=x*a0+anf*a1
138    b1=x*b0+anf*b1
139    if(a1.ne.0.)then
140      fac=1./a1
141      g=b1*fac
142      if(abs((g-gold)/g).lt.eps)go to 1
143      gold=g
144    endif
145  end do
146  print*, 'gcf: a too large, itmax too small'
147  stop
1481   gammcf=exp(-x+a*alog(x)-gln)*g
149end subroutine gcf
150
151function erf(x)
152
153  implicit none
154
155  real :: x, erf
156  real, external :: gammp
157
158  if(x.lt.0.)then
159    erf=-gammp(.5,x**2)
160  else
161    erf=gammp(.5,x**2)
162  endif
163end function erf
164
165function erfc(x)
166
167  implicit none
168
169  real :: x, erfc
170  real, external :: gammp, gammq
171
172  if(x.lt.0.)then
173    erfc=1.+gammp(.5,x**2)
174  else
175    erfc=gammq(.5,x**2)
176  endif
177end function erfc
178
179function erfcc(x)
180
181  implicit none
182
183  real :: x, z, t, erfcc
184
185  z=abs(x)
186  t=1./(1.+0.5*z)
187  erfcc=t*exp(-z*z-1.26551223+t*(1.00002368+t*(.37409196+ &
188       t*(.09678418+t*(-.18628806+t*(.27886807+t*(-1.13520398+ &
189       t*(1.48851587+t*(-.82215223+t*.17087277)))))))))
190  if (x.lt.0.) erfcc=2.-erfcc
191end function erfcc
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG