MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
MathUtil.f90
Go to the documentation of this file.
2  use kindmodule, only: dp, i4b, lgp
3  use errorutilmodule, only: pstop
7 
8  implicit none
9  private
10  public :: f1d, is_close, mod_offset, zero_ch, zero_br, &
12 
13  interface mod_offset
14  module procedure :: mod_offset_int, mod_offset_dbl
15  end interface mod_offset
16 
17  interface
18  function f1d(x) result(fx)
19  import dp
20  real(dp), intent(in) :: x
21  real(dp) :: fx
22  end function
23  end interface
24 
25 contains
26 
27  !> @brief Check if a real value is approximately equal to another.
28  !!
29  !! By default the determination is symmetric in a and b, as in
30  !! Python's math.isclose, with relative difference scaled by a
31  !! factor of the larger absolute value of a and b. The formula
32  !! is: abs(a - b) <= max(rtol * max(abs(a), abs(b)), atol).
33  !!
34  !! If symmetric is set to false the test is asymmetric in a and
35  !! b, with b taken to be the reference value, and the alternate
36  !! formula (abs(a - b) <= (atol + rtol * abs(b))) is used. This
37  !! is the approach taken by numpy.allclose.
38  !!
39  !! Defaults for rtol and atol are DSAME and DZERO, respectively.
40  !! If a or b are near 0 (especially if either is 0), an absolute
41  !! tolerance suitable for the particular case should be provided.
42  !! For a justification of a zero absolute tolerance default see:
43  !! https://peps.python.org/pep-0485/#absolute-tolerance-default
44  !<
45  pure logical function is_close(a, b, rtol, atol, symmetric)
46  ! dummy
47  real(dp), intent(in) :: a !< first real
48  real(dp), intent(in) :: b !< second real (reference value if asymmetric)
49  real(dp), intent(in), optional :: rtol !< relative tolerance (default=DSAME)
50  real(dp), intent(in), optional :: atol !< absolute tolerance (default=DZERO)
51  logical(LGP), intent(in), optional :: symmetric !< toggle (a)symmetric comparison
52  ! local
53  real(dp) :: lrtol, latol
54  logical(LGP) :: lsymmetric
55 
56  ! check for exact equality
57  if (a == b) then
58  is_close = .true.
59  return
60  end if
61 
62  ! process optional arguments
63  if (.not. present(rtol)) then
64  lrtol = dsame
65  else
66  lrtol = rtol
67  end if
68  if (.not. present(atol)) then
69  latol = dzero
70  else
71  latol = atol
72  end if
73  if (.not. present(symmetric)) then
74  lsymmetric = .true.
75  else
76  lsymmetric = symmetric
77  end if
78 
79  if (lsymmetric) then
80  ! "weak" symmetric test, https://peps.python.org/pep-0485/#which-symmetric-test
81  is_close = abs(a - b) <= max(lrtol * max(abs(a), abs(b)), latol)
82  else
83  ! asymmetric, https://numpy.org/doc/stable/reference/generated/numpy.isclose.html
84  is_close = (abs(a - b) <= (latol + lrtol * abs(b)))
85  end if
86  end function is_close
87 
88  !> @brief Modulo with offset for integer values.
89  pure function mod_offset_int(a, n, d) result(mo)
90  ! -- dummy
91  integer(I4B), intent(in) :: a !< dividend
92  integer(I4B), intent(in) :: n !< divisor
93  integer(I4B), intent(in), optional :: d !< offset
94  integer(I4B) :: mo
95  ! -- local
96  integer(I4B) :: ld
97 
98  if (present(d)) then
99  ld = d
100  else
101  ld = 0
102  end if
103  mo = a - n * floor(real(a - ld) / n)
104  end function mod_offset_int
105 
106  !> @brief Modulo with offset for double precision values.
107  pure function mod_offset_dbl(a, n, d) result(mo)
108  ! -- dummy
109  real(dp), intent(in) :: a !< dividend
110  real(dp), intent(in) :: n !< divisor
111  real(dp), intent(in), optional :: d !< offset
112  real(dp) :: mo
113  ! -- local
114  real(dp) :: ld
115 
116  if (present(d)) then
117  ld = d
118  else
119  ld = 0
120  end if
121  mo = a - n * floor((a - ld) / n)
122  end function mod_offset_dbl
123 
124  !> @brief Compute zeros on an interval using Chadrupatla's method
125  !!
126  !! A zero of the function f{x} is computed in the interval (x0, x1)
127  !! given tolerance epsa using Chandrupatla's method. FORTRAN code based
128  !! generally on pseudocode in Scherer, POJ (2013) "Computational Physics:
129  !! Simulation of Classical and Quantum Systems," 2nd ed., Springer, New York.
130  !<
131  function zero_ch(x0, x1, f, epsa) result(z)
132  ! -- dummy
133  real(dp) :: x0, x1
134  procedure(f1d), pointer, intent(in) :: f
135  real(dp) :: epsa
136  real(dp) :: z
137  ! -- local
138  real(dp) :: epsm
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
147 
148  epsm = epsilon(x0)
149  b = x0
150  a = x1
151  c = x1
152  aminusb = a - b
153  fb = f(b)
154  fa = f(a)
155  fc = f(c)
156  t = 5d-1
157 
158  ! check whether a or b is the solution
159  if (fa == dzero) then
160  z = a
161  return
162  else if (fb == dzero) then
163  z = b
164  return
165  end if
166 
167  do while (.true.)
168  xt = a - t * aminusb
169  ft = f(xt)
170  if (sign(ft, fa) == ft) then
171  c = a
172  fc = fa
173  a = xt
174  fa = ft
175  else
176  c = b
177  b = a
178  a = xt
179  fc = fb
180  fb = fa
181  fa = ft
182  end if
183  aminusb = a - b
184  cminusb = c - b
185  faminusfb = fa - fb
186  fcminusfb = fc - fb
187  xm = a
188  fm = fa
189  if (dabs(fb) < dabs(fa)) then
190  xm = b
191  fm = fb
192  end if
193  tol = dtwo * epsm * dabs(xm) + epsa
194  tl = tol / dabs(cminusb)
195  if ((tl > 5d-1) .or. (fm == dzero)) then
196  z = xm
197  return
198  end if
199  xi = aminusb / cminusb
200  phi = faminusfb / fcminusfb
201  philo = done - dsqrt(done - xi)
202  phihi = dsqrt(xi)
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)
208  if (t < tl) then
209  t = tl
210  else
211  tlc = done - tl
212  if (t > tlc) then
213  t = tlc
214  end if
215  end if
216  else
217  t = 5d-1
218  end if
219  end do
220  end function
221 
222  !> @brief Compute a zero of the function f(x) in the interval (x0, x1).
223  !!
224  !! A zero of the function f(x) is computed in the interval ax,bx.
225  !!
226  !! Input:
227  !!
228  !! ax left endpoint of initial interval
229  !! bx right endpoint of initial interval
230  !! f function subprogram which evaluates f(x) for any x in
231  !! the interval ax,bx
232  !! tol desired length of the interval of uncertainty of the
233  !! final result (.ge.0.)
234  !!
235  !! Output:
236  !!
237  !! zero_br abscissa approximating a zero of f in the interval ax,bx
238  !!
239  !! it is assumed that f(ax) and f(bx) have opposite signs
240  !! this is checked, and an error message is printed if this is not
241  !! satisfied. zero_br returns a zero x in the given interval
242  !! ax,bx to within a tolerance 4*macheps*abs(x)+tol, where macheps is
243  !! the relative machine precision defined as the smallest representable
244  !! number such that 1.+macheps .gt. 1.
245  !! this function subprogram is a slightly modified translation of
246  !! the algol 60 procedure zero given in richard brent, algorithms for
247  !! minimization without derivatives, prentice-hall, inc. (1973).
248  !!
249  !! This subroutine was obtained by the authors of MODFLOW 6 from
250  !! netlib.org with the understanding that it is freely available. It
251  !! has subsequently undergone minor modification to suit the current
252  !! application.
253  !<
254  function zero_br(ax, bx, f, tol) result(z)
255  ! -- dummy
256  real(dp) :: ax, bx
257  procedure(f1d), pointer, intent(in) :: f
258  real(dp) :: tol
259  real(dp) :: z
260  ! -- local
261  real(dp) :: eps
262  real(dp) :: a, b, c, d, e, s, p, q
263  real(dp) :: fa, fb, fc, r, tol1, xm
264  logical(LGP) :: rs
265 
266  eps = epsilon(ax)
267  tol1 = eps + done
268 
269  a = ax
270  b = bx
271  fa = f(a)
272  fb = f(b)
273 
274  ! check if a or b is the solution
275  if (fa == dzero) then
276  z = a
277  return
278  else if (fb == dzero) then
279  z = b
280  return
281  end if
282 
283  ! check that f(ax) and f(bx) have opposite sign
284  if (fa * (fb / dabs(fb)) .ge. dzero) &
285  call pstop(1, 'f(ax) and f(bx) do not have different signs,')
286 
287  rs = .true. ! var reset
288  do while (.true.)
289  if (rs) then
290  c = a
291  fc = fa
292  d = b - a
293  e = d
294  end if
295 
296  if (.not. (dabs(fc) .ge. dabs(fb))) then
297  a = b
298  b = c
299  c = a
300  fa = fb
301  fb = fc
302  fc = fa
303  end if
304 
305  tol1 = dtwo * eps * dabs(b) + dhalf * tol
306  xm = dhalf * (c - b)
307  if ((dabs(xm) .le. tol1) .or. (fb .eq. dzero)) then
308  z = b
309  return
310  end if
311 
312  ! see if a bisection is forced
313  if ((dabs(e) .ge. tol1) .and. (dabs(fa) .gt. dabs(fb))) then
314  s = fb / fa
315  if (a .ne. c) then
316  ! inverse quadratic interpolation
317  q = fa / fc
318  r = fb / fc
319  p = s * (dtwo * xm * q * (q - r) - (b - a) * (r - done))
320  q = (q - done) * (r - done) * (s - done)
321  else
322  ! linear interpolation
323  p = dtwo * xm * s
324  q = done - s
325  end if
326 
327  if (p .le. dzero) then
328  p = -p
329  else
330  q = -q
331  end if
332  s = e
333  e = d
334  if (((dtwo * p) .ge. (dthree * xm * q - dabs(tol1 * q))) .or. &
335  (p .ge. dabs(dhalf * s * q))) then
336  d = xm
337  e = d
338  else
339  d = p / q
340  end if
341  else
342  d = xm
343  e = d
344  end if
345 
346  a = b
347  fa = fb
348 
349  if (dabs(d) .le. tol1) then
350  if (xm .le. dzero) then
351  b = b - tol1
352  else
353  b = b + tol1
354  end if
355  else
356  b = b + d
357  end if
358 
359  fb = f(b)
360  rs = (fb * (fc / dabs(fc))) .gt. dzero
361  end do
362  end function zero_br
363 
364  !> @brief Calculate a numerical perturbation given the value of x
365  !!
366  !! Calculate a perturbation value to use for a numerical derivative
367  !! calculation. Taken from the book "Solving Nonlinear Equations with
368  !! Newton's Method" 2003, by C.T. Kelley. Method also used in the
369  !! SWR Process for MODFLOW-2005.
370  !<
371  function get_perturbation(x) result(res)
372  use constantsmodule, only: dprecsqrt, done
373  real(dp), intent(in) :: x !< value that will be perturbed by the result
374  real(dp) :: res !< calculated perturbation value
375  res = dprecsqrt * max(abs(x), done) * sign(done, x)
376  end function get_perturbation
377 
378  !> @brief Return reals separated by the given step over the given interval.
379  !!
380  !! This function is designed to behave like NumPy's arange.
381  !! Adapted from https://stackoverflow.com/a/65839162/6514033.
382  !<
383  pure function arange(start, stop, step) result(array)
384  ! dummy
385  real(dp), intent(in) :: start, stop
386  real(dp), intent(in), optional :: step
387  real(dp), allocatable :: array(:)
388  ! local
389  real(dp) :: lstep
390  integer(I4B) :: i, n
391 
392  if (present(step)) then
393  lstep = step
394  else
395  lstep = done
396  end if
397 
398  if (step <= 0) then
399  allocate (array(0))
400  else
401  n = ceiling((stop - start) / step)
402  allocate (array(n))
403  do i = 0, n - 1
404  array(i + 1) = start + step * i
405  end do
406  end if
407  end function arange
408 
409  !> @brief Return evenly spaced reals over the given interval.
410  !!
411  !! This function is designed to behave like NumPy's linspace.
412  !! Adapted from https://stackoverflow.com/a/57211848/6514033.
413  !<
414  pure function linspace(start, stop, num) result(array)
415  ! dummy
416  real(dp), intent(in) :: start, stop
417  integer(I4B), intent(in) :: num
418  real(dp), allocatable :: array(:)
419  ! local
420  real(dp) :: range
421  integer(I4B) :: i
422 
423  allocate (array(num))
424  range = stop - start
425 
426  if (num == 0) return
427  if (num == 1) then
428  array(1) = start
429  return
430  end if
431  do i = 1, num
432  array(i) = start + range * (i - 1) / (num - 1)
433  end do
434  end function linspace
435 
436 end module mathutilmodule
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dsame
real constant for values that are considered the same based on machine precision
Definition: Constants.f90:122
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenhugeline
maximum length of a huge line
Definition: Constants.f90:16
real(dp), parameter dprecsqrt
Definition: Constants.f90:121
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:68
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter dprec
real constant machine precision
Definition: Constants.f90:120
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:47
@ vsummary
write summary output
Definition: Constants.f90:188
real(dp), parameter dtwo
real constant 2
Definition: Constants.f90:79
real(dp), parameter dthree
real constant 3
Definition: Constants.f90:80
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine pstop(status, message)
Stop the program, optionally specifying an error status code.
Definition: ErrorUtil.f90:24
This module defines variable data types.
Definition: kind.f90:8
real(dp) function, public zero_ch(x0, x1, f, epsa)
Compute zeros on an interval using Chadrupatla's method.
Definition: MathUtil.f90:132
pure integer(i4b) function mod_offset_int(a, n, d)
Modulo with offset for integer values.
Definition: MathUtil.f90:90
pure real(dp) function mod_offset_dbl(a, n, d)
Modulo with offset for double precision values.
Definition: MathUtil.f90:108
real(dp) function, public get_perturbation(x)
Calculate a numerical perturbation given the value of x.
Definition: MathUtil.f90:372
pure real(dp) function, dimension(:), allocatable, public linspace(start, stop, num)
Return evenly spaced reals over the given interval.
Definition: MathUtil.f90:415
real(dp) function, public zero_br(ax, bx, f, tol)
Compute a zero of the function f(x) in the interval (x0, x1).
Definition: MathUtil.f90:255
pure real(dp) function, dimension(:), allocatable, public arange(start, stop, step)
Return reals separated by the given step over the given interval.
Definition: MathUtil.f90:384
pure logical function, public is_close(a, b, rtol, atol, symmetric)
Check if a real value is approximately equal to another.
Definition: MathUtil.f90:46