source: flexpart.git/src/erf.f90

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

add SPDX-License-Identifier to all .f90 files

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