ROMS
Loading...
Searching...
No Matches
erf_mod Module Reference

Functions/Subroutines

real(r8) function, public erf (x)
 
real(r8) function, public erfc (x)
 
real(r8) function, public erfcc (x)
 
real(r8) function gammln (xx)
 
real(r8) function, public gammp (a, x)
 
real(r8) function, public gammq (a, x)
 
subroutine gser (gamser, a, x, gln)
 
subroutine gcf (gammcf, a, x, gln)
 
real(r8) function aerf (arg)
 

Function/Subroutine Documentation

◆ aerf()

real(r8) function erf_mod::aerf ( real(r8), intent(in) arg)
private

Definition at line 409 of file erf.F.

410!
411!=======================================================================
412! !
413! The error function has been taken in approximate form from !
414! Abramowitz and Stegun, page 299. !
415! !
416! Reference: !
417! !
418! Abramowitz, M. and I.A. Stegun, 1972: Handbook of Mathematical !
419! Functions with Formulas, Graphs, and Mathematical Tables, !
420! National Bureau of Standards, Applied Mathematics Series !
421! 55, US Goverment Printing Office, Washington, D.C. !
422! !
423!=======================================================================
424!
425! Imported variable declarations.
426!
427 real(r8), intent(in) :: arg
428!
429! Local variable declarations.
430!
431 real(r8), parameter :: a1 = +0.254829592_r8
432 real(r8), parameter :: a2 = -0.284496736_r8
433 real(r8), parameter :: a3 = -1.421413741_r8
434 real(r8), parameter :: a4 = -1.453152027_r8
435 real(r8), parameter :: a5 = +1.061405429_r8
436 real(r8), parameter :: p = +0.3275911_r8
437
438 real(r8) :: big, c, my_sign, t, y
439 real(r8) :: value
440!
441!-----------------------------------------------------------------------
442! Compute approximated error function.
443!-----------------------------------------------------------------------
444!
445 big=20.0_r8
446 my_sign=1.0_r8
447
448 IF (arg.lt.0.0_r8) THEN
449 my_sign=-1.0
450 ELSE
451 my_sign=1.0_r8
452 END IF
453
454 IF (arg.eq.0.0_r8) THEN
455 value=0.0_r8
456 RETURN
457 END IF
458!
459! Polynomial approximation.
460!
461 y=abs(arg)
462 t=1.0_r8/(1.0_r8+p*y)
463 c=t*(a1+t*(a2+t*(a3+t*(a4+a5*t))))
464 IF (y*y.lt.big) THEN
465 value=my_sign*(1.0_r8-c*exp(-y*y))
466 ELSE
467 value=my_sign
468 END IF
469
470 RETURN

◆ erf()

real(r8) function, public erf_mod::erf ( real(r8), intent(in) x)

Definition at line 42 of file erf.F.

43!
44!=======================================================================
45! !
46! This routine computes the error function, ERF(x). !
47! !
48!=======================================================================
49!
50! Imported variable declarations.
51!
52 real(r8), intent(in) :: x
53!
54! Local variable declarations.
55!
56 real(r8) :: value
57!
58!-----------------------------------------------------------------------
59! Compute error function in terms of the incomplete gamma function,
60! P(a,x).
61!-----------------------------------------------------------------------
62!
63 IF (x.lt.0.0_r8) THEN
64 value=-gammp(0.5_r8, x**2)
65 ELSE
66 value= gammp(0.5_r8, x**2)
67 ENDIF
68
69 RETURN

References gammp().

Referenced by analytical_mod::ana_nlminitial_tile().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ erfc()

real(r8) function, public erf_mod::erfc ( real(r8), intent(in) x)

Definition at line 72 of file erf.F.

73!
74!=======================================================================
75! !
76! This routine computes the complementary error function, ERFC(x). !
77! !
78!=======================================================================
79!
80! Imported variable declarations.
81!
82 real(r8), intent(in) :: x
83!
84! Local variable declarations.
85!
86 real(r8) :: value
87!
88!-----------------------------------------------------------------------
89! Compute complementary error function in terms of the incomplete
90! gamma functions, P(a,x) and Q(a,x).
91!-----------------------------------------------------------------------
92!
93 IF (x.lt.0.0_r8) THEN
94 value=1.0_r8+gammp(0.5_r8, x**2)
95 ELSE
96 value=gammq(0.5_r8, x**2)
97 endif
98
99 RETURN

References gammp(), and gammq().

Here is the call graph for this function:

◆ erfcc()

real(r8) function, public erf_mod::erfcc ( real(r8), intent(in) x)

Definition at line 102 of file erf.F.

103!
104!=======================================================================
105! !
106! This routine computes the complementary error function, ERFCC(x), !
107! with fractional error everywhere less than 1.2E-7. !
108! !
109!=======================================================================
110!
111! Imported variable declarations.
112!
113 real(r8), intent(in) :: x
114!
115! Local variable declarations.
116!
117 real(r8) :: t, value, z
118!
119!-----------------------------------------------------------------------
120! Compute complementary error function based on Chebyshev fitting to
121! an inspired guess.
122!-----------------------------------------------------------------------
123!
124 z=abs(x)
125 t=1.0_r8/(1.0_r8+0.5_r8*z)
126 value=t*exp(-z*z-1.26551223_r8+ &
127 & t*(1.00002368_r8+ &
128 & t*(0.37409196_r8+ &
129 & t*(0.09678418_r8+ &
130 & t*(-0.18628806_r8+ &
131 & t*(0.27886807_r8+ &
132 & t*(-1.13520398_r8+ &
133 & t*(1.48851587_r8+ &
134 & t*(-0.82215223_r8+ &
135 & t*.17087277)))))))))
136 IF (x.lt.0.0_r8) value=2.0-value
137
138 RETURN

◆ gammln()

real(r8) function erf_mod::gammln ( real(r8), intent(in) xx)
private

Definition at line 141 of file erf.F.

142!
143!=======================================================================
144! !
145! This routine computes the natural logarithm of the gamma function, !
146! LN(Gamma(xx)). The natural logarithm is computed to avoid floating- !
147! point overflow. !
148! !
149!=======================================================================
150!
151! Imported variable declarations.
152!
153 real(r8), intent(in) :: xx
154!
155! Local variable declarations.
156!
157 integer :: j
158
159 real(r8) :: ser, tmp, x, y
160 real(r8) :: value
161 real(r8), save, dimension(6) :: cof = &
162 & (/ 76.18009172947146_r8, &
163 & -86.50532032941677_r8, &
164 & 24.01409824083091_r8, &
165 & -1.231739572450155_r8, &
166 & 0.1208650973866179E-2_r8, &
167 & -0.5395239384953E-5_r8 /)
168 real(r8), save :: stp = 2.5066282746310005_r8
169!
170!-----------------------------------------------------------------------
171! Compute natural logarithm of the gamma function.
172!-----------------------------------------------------------------------
173!
174 x=xx
175 y=x
176 tmp=x+5.5_r8
177 tmp=(x+0.5_r8)*log(tmp)-tmp
178 ser=1.000000000190015_r8
179 DO j=1,6
180 y=y+1.d0
181 ser=ser+cof(j)/y
182 END DO
183 value=tmp+log(stp*ser/x)
184
185 RETURN

References mod_kinds::r8.

Referenced by gcf(), and gser().

Here is the caller graph for this function:

◆ gammp()

real(r8) function, public erf_mod::gammp ( real(r8), intent(in) a,
real(r8), intent(in) x )

Definition at line 188 of file erf.F.

189!
190!=======================================================================
191! !
192! This routine computes the incomplete gamma function, P(a,x). !
193! !
194!=======================================================================
195!
196 USE mod_param
197 USE mod_scalars
198 USE mod_iounits
199!
200! Imported variable declarations.
201!
202 real(r8), intent(in) :: a, x
203!
204! Local variable declarations.
205!
206 real(r8) :: gammcf, gamser, gln
207 real(r8) :: value
208!
209!-----------------------------------------------------------------------
210! Compute incompleate gamma fucntion, P(a.x).
211!-----------------------------------------------------------------------
212!
213 IF ((x.lt.0.0_r8).or.(a.le.0.0_r8)) THEN
214 WRITE (stdout,10) a, x
215 10 FORMAT (/,' GAMMAP - gamma function negative argument,', &
216 & ' a = ',1pe13.6,' x = ',1pe13.6)
217 exit_flag=8
218 END IF
219
220 IF (x.lt.a+1.0_r8) THEN
221 CALL gser (gamser, a, x, gln)
222 value=gamser ! series representation
223 ELSE
224 CALL gcf (gammcf, a, x, gln)
225 value=1.0_r8-gammcf ! continued fraction representation
226 ENDIF
227
228 RETURN
integer stdout
integer exit_flag

References mod_scalars::exit_flag, gcf(), gser(), and mod_iounits::stdout.

Referenced by erf(), and erfc().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ gammq()

real(r8) function, public erf_mod::gammq ( real(r8), intent(in) a,
real(r8), intent(in) x )

Definition at line 231 of file erf.F.

232!
233!=======================================================================
234! !
235! This routine computes the incomplete gamma function complement, !
236! Q(a,x)=1-P(a,x). !
237! !
238!=======================================================================
239!
240 USE mod_param
241 USE mod_scalars
242 USE mod_iounits
243!
244! Imported variable declarations.
245!
246 real(r8), intent(in) :: a, x
247!
248! Local variable declarations.
249!
250 real(r8) :: gammcf, gamser, gln
251 real(r8) :: value
252!
253!-----------------------------------------------------------------------
254! Compute incompleate gamma fucntion, Q(a,x)=1-P(a.x).
255!-----------------------------------------------------------------------
256!
257 IF ((x.lt.0.0_r8).or.(a.le.0.0_r8)) THEN
258 WRITE (stdout,10) a, x
259 10 FORMAT (/,' GAMMAQ - gamma function negative argument,', &
260 & ' a = ',1pe13.6,' x = ',1pe13.6)
261 exit_flag=8
262 END IF
263
264 IF (x.lt.a+1.0_r8) THEN
265 CALL gser (gamser, a, x, gln)
266 value=1.0_r8-gamser ! series representation
267 ELSE
268 CALL gcf (gammcf, a, x, gln)
269 value=gammcf ! continued fraction representation
270 ENDIF
271
272 RETURN

References mod_scalars::exit_flag, gcf(), gser(), and mod_iounits::stdout.

Referenced by erfc().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ gcf()

subroutine erf_mod::gcf ( real(r8), intent(out) gammcf,
real(r8), intent(in) a,
real(r8), intent(in) x,
real(r8), intent(out) gln )
private

Definition at line 342 of file erf.F.

343!
344!=======================================================================
345! !
346! This routine computes the incomplete gamma function P(a,x) !
347! evaliuated by its series representation as gamser. !
348! !
349!=======================================================================
350!
351 USE mod_param
352 USE mod_scalars
353 USE mod_iounits
354!
355! Imported variable declarations.
356!
357 real(r8), intent(in) :: a, x
358 real(r8), intent(out) :: gammcf, gln
359!
360! Local variable declarations.
361!
362 logical :: Converged
363
364 integer, parameter :: ITMAX = 100 ! number of iterations
365 integer :: i
366
367 real(r8), parameter :: EPS = 3.0e-7_r8 ! relative accuracy
368 real(r8), parameter :: FPMIN = 1.0e-30_r8 ! smallest number
369 real(r8) :: an, b, c, d, del, h
370!
371!-----------------------------------------------------------------------
372! Compue incomplete gamma function evaluated by its continued fraction
373! representation.
374!-----------------------------------------------------------------------
375!
376 gln=gammln(a)
377 b=x+1.0_r8-a
378 c=1.0_r8/fpmin
379 d=1.0_r8/b
380 h=d
381 converged=.false.
382 DO i=1,itmax
383 an=-real(i,r8)*(real(i,r8)-a)
384 b=b+2.0_r8
385 d=an*d+b
386 IF (abs(d).lt.fpmin) d=fpmin
387 c=b+an/c
388 IF (abs(c).lt.fpmin) c=fpmin
389 d=1.0_r8/d
390 del=d*c
391 h=h*del
392 IF (abs(del-1.0_r8).lt.eps) THEN
393 converged=.true.
394 EXIT
395 END IF
396 END DO
397 IF (converged) THEN
398 gammcf=exp(-x+a*log(x)-gln)*h
399 ELSE
400 WRITE (stdout,10) itmax
401 10 FORMAT (/,' GCF - Gamma function not converged, ITMAX = ', &
402 & i4.4,/,8x,'a is too large')
403 exit_flag=8
404 END IF
405
406 RETURN

References mod_scalars::exit_flag, gammln(), and mod_iounits::stdout.

Referenced by gammp(), and gammq().

Here is the call graph for this function:
Here is the caller graph for this function:

◆ gser()

subroutine erf_mod::gser ( real(r8), intent(out) gamser,
real(r8), intent(in) a,
real(r8), intent(in) x,
real(r8), intent(out) gln )
private

Definition at line 275 of file erf.F.

276!
277!=======================================================================
278! !
279! This routine computes the incomplete gamma function P(a,x) !
280! evaliuated by its series representation as gamser. !
281! !
282!=======================================================================
283!
284 USE mod_param
285 USE mod_scalars
286 USE mod_iounits
287!
288! Imported variable declarations.
289!
290 real(r8), intent(in) :: a, x
291 real(r8), intent(out) :: gamser, gln
292!
293! Local variable declarations.
294!
295 logical :: Converged
296 integer, parameter :: ITMAX = 100
297 integer :: i
298
299 real(r8), parameter :: EPS =3.0e-7_r8
300 real(r8) :: ap, del, my_sum
301!
302!-----------------------------------------------------------------------
303! Compue incomplete gamma function by its series representation.
304!-----------------------------------------------------------------------
305!
306 gln=gammln(a)
307 IF (x.le.0.0_r8) THEN
308 IF (x.lt.0.0) THEN
309 WRITE (stdout,10) x
310 10 FORMAT (/,' GSER - gamma function negative argument, x = ', &
311 & 1pe13.6)
312 exit_flag=8
313 END IF
314 gamser=0.0_r8
315 RETURN
316 END IF
317 ap=a
318 my_sum=1.0_r8/a
319 del=my_sum
320 converged=.false.
321 DO i=1,itmax
322 ap=ap+1.0_r8
323 del=del*x/ap
324 my_sum=my_sum+del
325 IF (abs(del).lt.abs(my_sum)*eps) THEN
326 converged=.true.
327 EXIT
328 END IF
329 END DO
330 IF (converged) THEN
331 gamser=my_sum*exp(-x+a*log(x)-gln)
332 ELSE
333 WRITE (stdout,20) itmax
334 20 FORMAT (/,' GSER - Gamma function not converged, ITMAX = ', &
335 & i4.4,/,8x,'a is too large')
336 exit_flag=8
337 END IF
338
339 RETURN

References mod_scalars::exit_flag, gammln(), and mod_iounits::stdout.

Referenced by gammp(), and gammq().

Here is the call graph for this function:
Here is the caller graph for this function: