18 function f1d(x)
result(fx)
20 real(dp),
intent(in) :: x
45 pure logical function is_close(a, b, rtol, atol, symmetric)
47 real(dp),
intent(in) :: a
48 real(dp),
intent(in) :: b
49 real(dp),
intent(in),
optional :: rtol
50 real(dp),
intent(in),
optional :: atol
51 logical(LGP),
intent(in),
optional :: symmetric
53 real(dp) :: lrtol, latol
54 logical(LGP) :: lsymmetric
63 if (.not.
present(rtol))
then
68 if (.not.
present(atol))
then
73 if (.not.
present(symmetric))
then
76 lsymmetric = symmetric
81 is_close = abs(a - b) <= max(lrtol * max(abs(a), abs(b)), latol)
84 is_close = (abs(a - b) <= (latol + lrtol * abs(b)))
91 integer(I4B),
intent(in) :: a
92 integer(I4B),
intent(in) :: n
93 integer(I4B),
intent(in),
optional :: d
103 mo = a - n * floor(real(a - ld) / n)
109 real(dp),
intent(in) :: a
110 real(dp),
intent(in) :: n
111 real(dp),
intent(in),
optional :: d
121 mo = a - n * floor((a - ld) / n)
134 procedure(
f1d),
pointer,
intent(in) :: f
139 real(dp) :: a, b, c, t
140 real(dp) :: aminusb, cminusb
141 real(dp) :: fa, fb, fc, fm, ft
142 real(dp) :: faminusfb, fcminusfb
143 real(dp) :: phi, philo, phihi
144 real(dp) :: racb, rcab, rbca
145 real(dp) :: tol, tl, tlc
146 real(dp) :: xi, xm, xt
159 if (fa ==
dzero)
then
162 else if (fb ==
dzero)
then
170 if (sign(ft, fa) == ft)
then
189 if (dabs(fb) < dabs(fa))
then
193 tol =
dtwo * epsm * dabs(xm) + epsa
194 tl = tol / dabs(cminusb)
195 if ((tl > 5d-1) .or. (fm ==
dzero))
then
199 xi = aminusb / cminusb
200 phi = faminusfb / fcminusfb
203 if ((phi > philo) .and. (phi < phihi))
then
204 racb = fa / fcminusfb
205 rcab = fc / faminusfb
206 rbca = fb / (fc - fa)
207 t = racb * (rcab - rbca * (c - a) / aminusb)
257 procedure(
f1d),
pointer,
intent(in) :: f
262 real(dp) :: a, b, c, d, e, s, p, q
263 real(dp) :: fa, fb, fc, r, tol1, xm
275 if (fa ==
dzero)
then
278 else if (fb ==
dzero)
then
284 if (fa * (fb / dabs(fb)) .ge.
dzero) &
285 call pstop(1,
'f(ax) and f(bx) do not have different signs,')
296 if (.not. (dabs(fc) .ge. dabs(fb)))
then
305 tol1 =
dtwo * eps * dabs(b) +
dhalf * tol
307 if ((dabs(xm) .le. tol1) .or. (fb .eq.
dzero))
then
313 if ((dabs(e) .ge. tol1) .and. (dabs(fa) .gt. dabs(fb)))
then
319 p = s * (
dtwo * xm * q * (q - r) - (b - a) * (r -
done))
327 if (p .le.
dzero)
then
334 if (((
dtwo * p) .ge. (
dthree * xm * q - dabs(tol1 * q))) .or. &
335 (p .ge. dabs(
dhalf * s * q)))
then
349 if (dabs(d) .le. tol1)
then
350 if (xm .le.
dzero)
then
360 rs = (fb * (fc / dabs(fc))) .gt.
dzero
373 real(dp),
intent(in) :: x
383 pure function arange(start, stop, step)
result(array)
385 real(dp),
intent(in) :: start, stop
386 real(dp),
intent(in),
optional :: step
387 real(dp),
allocatable :: array(:)
392 if (
present(step))
then
401 n = ceiling((stop - start) / step)
404 array(i + 1) = start + step * i
414 pure function linspace(start, stop, num)
result(array)
416 real(dp),
intent(in) :: start, stop
417 integer(I4B),
intent(in) :: num
418 real(dp),
allocatable :: array(:)
423 allocate (array(num))
432 array(i) = start + range * (i - 1) / (num - 1)
This module contains simulation constants.
real(dp), parameter dsame
real constant for values that are considered the same based on machine precision
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lenhugeline
maximum length of a huge line
real(dp), parameter dprecsqrt
real(dp), parameter dhalf
real constant 1/2
real(dp), parameter dzero
real constant zero
real(dp), parameter dprec
real constant machine precision
integer(i4b), parameter maxcharlen
maximum length of char string
@ vsummary
write summary output
real(dp), parameter dtwo
real constant 2
real(dp), parameter dthree
real constant 3
real(dp), parameter done
real constant 1
subroutine pstop(status, message)
Stop the program, optionally specifying an error status code.
This module defines variable data types.
real(dp) function, public zero_ch(x0, x1, f, epsa)
Compute zeros on an interval using Chadrupatla's method.
pure integer(i4b) function mod_offset_int(a, n, d)
Modulo with offset for integer values.
pure real(dp) function mod_offset_dbl(a, n, d)
Modulo with offset for double precision values.
real(dp) function, public get_perturbation(x)
Calculate a numerical perturbation given the value of x.
pure real(dp) function, dimension(:), allocatable, public linspace(start, stop, num)
Return evenly spaced reals over the given interval.
real(dp) function, public zero_br(ax, bx, f, tol)
Compute a zero of the function f(x) in the interval (x0, x1).
pure real(dp) function, dimension(:), allocatable, public arange(start, stop, step)
Return reals separated by the given step over the given interval.
pure logical function, public is_close(a, b, rtol, atol, symmetric)
Check if a real value is approximately equal to another.