MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
SmoothingFunctions.f90
Go to the documentation of this file.
2  use kindmodule, only: dp, i4b
3  use constantsmodule, only: dzero, dhalf, done, dtwo, dthree, dfour, &
5  implicit none
6 
7 contains
8 
9  !> @ brief SCurve
10  !!
11  !! Computes the S curve for smooth derivatives between x=0 and x=1
12  !! from mfusg smooth subroutine in gwf2wel7u1.f
13  !<
14  subroutine sscurve(x, range, dydx, y)
15  real(DP), intent(in) :: x
16  real(DP), intent(in) :: range
17  real(DP), intent(inout) :: dydx
18  real(DP), intent(inout) :: y
19  !--local variables
20  real(DP) :: s
21  real(DP) :: xs
22  ! -- code
23  !
24  s = range
25  if (s < dprec) s = dprec
26  xs = x / s
27  if (xs < dzero) xs = dzero
28  if (xs <= dzero) then
29  y = dzero
30  dydx = dzero
31  elseif (xs < done) then
32  y = -dtwo * xs**dthree + dthree * xs**dtwo
33  dydx = -dsix * xs**dtwo + dsix * xs
34  else
35  y = done
36  dydx = dzero
37  end if
38  return
39  end subroutine sscurve
40 
41  !> @ brief sCubicLinear
42  !!
43  !! Computes the s curve where dy/dx = 0 at x=0; and dy/dx = 1 at x=1.
44  !! Smooths from zero to a slope of 1.
45  !<
46  subroutine scubiclinear(x, range, dydx, y)
47  real(DP), intent(in) :: x
48  real(DP), intent(in) :: range
49  real(DP), intent(inout) :: dydx
50  real(DP), intent(inout) :: y
51  !--local variables
52  real(DP) :: s
53  real(DP) :: xs
54  ! -- code
55  !
56  s = range
57  if (s < dprec) s = dprec
58  xs = x / s
59  if (xs < dzero) xs = dzero
60  if (xs <= dzero) then
61  y = dzero
62  dydx = dzero
63  elseif (xs < done) then
64  y = -done * xs**dthree + dtwo * xs**dtwo
65  dydx = -dthree * xs**dtwo + dfour * xs
66  else
67  y = done
68  dydx = dzero
69  end if
70  return
71  end subroutine scubiclinear
72 
73  !> @ brief sCubic
74  !!
75  !! Nonlinear smoothing function returns value between 0-1; cubic function
76  !<
77  subroutine scubic(x, range, dydx, y)
78  real(DP), intent(inout) :: x
79  real(DP), intent(inout) :: range
80  real(DP), intent(inout) :: dydx
81  real(DP), intent(inout) :: y
82  !--local variables
83  real(DP) :: s, aa, bb
84  real(DP) :: cof1, cof2, cof3
85  ! -- code
86  !
87  dydx = dzero
88  y = dzero
89  if (range < dprec) range = dprec
90  if (x < dprec) x = dprec
91  s = range
92  aa = -dsix / (s**dthree)
93  bb = -dsix / (s**dtwo)
94  cof1 = x**dtwo
95  cof2 = -(dtwo * x) / (s**dthree)
96  cof3 = dthree / (s**dtwo)
97  y = cof1 * (cof2 + cof3)
98  dydx = (aa * x**dtwo - bb * x)
99  if (x <= dzero) then
100  y = dzero
101  dydx = dzero
102  else if ((x - s) > -dprec) then
103  y = done
104  dydx = dzero
105  end if
106  return
107  end subroutine scubic
108 
109  !> @ brief sLinear
110  !!
111  !! Linear smoothing function returns value between 0-1
112  !<
113  subroutine slinear(x, range, dydx, y)
114  real(DP), intent(inout) :: x
115  real(DP), intent(inout) :: range
116  real(DP), intent(inout) :: dydx
117  real(DP), intent(inout) :: y
118  !--local variables
119  real(DP) :: s
120  ! -- code
121  !
122  dydx = dzero
123  y = dzero
124  if (range < dprec) range = dprec
125  if (x < dprec) x = dprec
126  s = range
127  y = done - (s - x) / s
128  dydx = done / s
129  if (y > done) then
130  y = done
131  dydx = dzero
132  end if
133  return
134  end subroutine slinear
135 
136  !> @ brief sQuadratic
137  !!
138  !! Nonlinear quadratic smoothing function returns value between 0-1
139  !<
140  subroutine squadratic(x, range, dydx, y)
141  real(DP), intent(inout) :: x
142  real(DP), intent(inout) :: range
143  real(DP), intent(inout) :: dydx
144  real(DP), intent(inout) :: y
145  !--local variables
146  real(DP) :: s
147  ! -- code
148  !
149  dydx = dzero
150  y = dzero
151  if (range < dprec) range = dprec
152  if (x < dprec) x = dprec
153  s = range
154  y = (x**dtwo) / (s**dtwo)
155  dydx = dtwo * x / (s**dtwo)
156  if (y > done) then
157  y = done
158  dydx = dzero
159  end if
160  return
161  end subroutine squadratic
162 
163  !> @ brief sChSmooth
164  !!
165  !! Function to smooth channel variables during channel drying
166  !<
167  subroutine schsmooth(d, smooth, dwdh)
168  real(DP), intent(in) :: d
169  real(DP), intent(inout) :: smooth
170  real(DP), intent(inout) :: dwdh
171  !
172  ! -- local variables
173  real(DP) :: s
174  real(DP) :: diff
175  real(DP) :: aa
176  real(DP) :: ad
177  real(DP) :: b
178  real(DP) :: x
179  real(DP) :: y
180  ! -- code
181  !
182  smooth = dzero
183  s = dem5
184  x = d
185  diff = x - s
186  if (diff > dzero) then
187  smooth = done
188  dwdh = dzero
189  else
190  aa = -done / (s**dtwo)
191  ad = -dtwo / (s**dtwo)
192  b = dtwo / s
193  y = aa * x**dtwo + b * x
194  dwdh = (ad * x + b)
195  if (x <= dzero) then
196  y = dzero
197  dwdh = dzero
198  else if (diff > -dem14) then
199  y = done
200  dwdh = dzero
201  end if
202  smooth = y
203  end if
204  return
205  end subroutine schsmooth
206 
207  !> @ brief sLinearSaturation
208  !!
209  !! Linear saturation function returns value between 0-1
210  !<
211  function slinearsaturation(top, bot, x) result(y)
212  ! -- return
213  real(dp) :: y
214  ! -- dummy variables
215  real(dp), intent(in) :: top
216  real(dp), intent(in) :: bot
217  real(dp), intent(in) :: x
218  ! -- local
219  real(dp) :: b
220  ! -- code
221  !
222  b = top - bot
223  if (x < bot) then
224  y = dzero
225  else if (x > top) then
226  y = done
227  else
228  y = (x - bot) / b
229  end if
230  return
231  end function slinearsaturation
232 
233  !> @ brief sCubicSaturation
234  !!
235  !! Nonlinear cubic saturation function returns value between 0-1
236  !<
237  function scubicsaturation(top, bot, x, eps) result(y)
238  ! -- return
239  real(dp) :: y
240  ! -- dummy variables
241  real(dp), intent(in) :: top
242  real(dp), intent(in) :: bot
243  real(dp), intent(in) :: x
244  real(dp), intent(in), optional :: eps
245  ! -- local
246  real(dp) :: teps
247  real(dp) :: w
248  real(dp) :: b
249  real(dp) :: s
250  real(dp) :: cof1
251  real(dp) :: cof2
252  ! -- code
253  !
254  if (present(eps)) then
255  teps = eps
256  else
257  teps = dem2
258  end if
259  w = x - bot
260  b = top - bot
261  s = teps * b
262  cof1 = done / (s**dtwo)
263  cof2 = dtwo / s
264  if (w < dzero) then
265  y = dzero
266  else if (w < s) then
267  y = -cof1 * (w**dthree) + cof2 * (w**dtwo)
268  else if (w < (b - s)) then
269  y = w / b
270  else if (w < b) then
271  y = done + cof1 * ((b - w)**dthree) - cof2 * ((b - w)**dtwo)
272  else
273  y = done
274  end if
275 
276  return
277  end function scubicsaturation
278 
279  !> @ brief sQuadraticSaturation
280  !!
281  !! Nonlinear quadratic saturation function returns value between 0-1
282  !<
283  function squadraticsaturation(top, bot, x, eps) result(y)
284  ! -- return
285  real(dp) :: y
286  ! -- dummy variables
287  real(dp), intent(in) :: top
288  real(dp), intent(in) :: bot
289  real(dp), intent(in) :: x
290  real(dp), optional, intent(in) :: eps
291  ! -- local
292  real(dp) :: teps
293  real(dp) :: b
294  real(dp) :: br
295  real(dp) :: bri
296  real(dp) :: av
297  ! -- code
298  !
299  if (present(eps)) then
300  teps = eps
301  else
302  teps = dem6
303  end if
304  b = top - bot
305  if (b > dzero) then
306  if (x < bot) then
307  br = dzero
308  else if (x > top) then
309  br = done
310  else
311  br = (x - bot) / b
312  end if
313  av = done / (done - teps)
314  bri = done - br
315  if (br < teps) then
316  y = av * dhalf * (br * br) / teps
317  elseif (br < (done - teps)) then
318  y = av * br + dhalf * (done - av)
319  elseif (br < done) then
320  y = done - ((av * dhalf * (bri * bri)) / teps)
321  else
322  y = done
323  end if
324  else
325  if (x < bot) then
326  y = dzero
327  else
328  y = done
329  end if
330  end if
331 
332  return
333  end function squadraticsaturation
334 
335  !> @ brief sQuadraticSaturation
336  !!
337  !! van Genuchten saturation function returns value between 0-1
338  !<
339  function svangenuchtensaturation(top, bot, x, alpha, beta, sr) result(y)
340  ! -- return
341  real(dp) :: y
342  ! -- dummy variables
343  real(dp), intent(in) :: top
344  real(dp), intent(in) :: bot
345  real(dp), intent(in) :: x
346  real(dp), intent(in) :: alpha
347  real(dp), intent(in) :: beta
348  real(dp), intent(in) :: sr
349  ! -- local
350  real(dp) :: b
351  real(dp) :: pc
352  real(dp) :: gamma
353  real(dp) :: seff
354  ! -- code
355  !
356  b = top - bot
357  pc = (dhalf * b) - x
358  if (pc <= dzero) then
359  y = dzero
360  else
361  gamma = done - (done / beta)
362  seff = (done + (alpha * pc)**beta)**gamma
363  seff = done / seff
364  y = seff * (done - sr) + sr
365  end if
366 
367  return
368  end function svangenuchtensaturation
369 
370  !> @ brief Derivative of the quadratic saturation function
371  !!
372  !! Derivative of nonlinear smoothing function returns value between 0-1;
373  !<
374  function squadraticsaturationderivative(top, bot, x, eps) result(y)
375  ! -- return
376  real(dp) :: y
377  ! -- dummy variables
378  real(dp), intent(in) :: top
379  real(dp), intent(in) :: bot
380  real(dp), intent(in) :: x
381  real(dp), optional, intent(in) :: eps
382  ! -- local
383  real(dp) :: teps
384  real(dp) :: b
385  real(dp) :: br
386  real(dp) :: bri
387  real(dp) :: av
388  ! -- code
389  !
390  if (present(eps)) then
391  teps = eps
392  else
393  teps = dem6
394  end if
395  b = top - bot
396  if (x < bot) then
397  br = dzero
398  else if (x > top) then
399  br = done
400  else
401  br = (x - bot) / b
402  end if
403  av = done / (done - teps)
404  bri = done - br
405  if (br < teps) then
406  y = av * br / teps
407  elseif (br < (done - teps)) then
408  y = av
409  elseif (br < done) then
410  y = av * bri / teps
411  else
412  y = dzero
413  end if
414  y = y / b
415 
416  return
417  end function squadraticsaturationderivative
418 
419  !> @ brief sQSaturation
420  !!
421  !! Nonlinear smoothing function returns value between 0-1
422  !<
423  function sqsaturation(top, bot, x, c1, c2) result(y)
424  ! -- return
425  real(dp) :: y
426  ! -- dummy variables
427  real(dp), intent(in) :: top
428  real(dp), intent(in) :: bot
429  real(dp), intent(in) :: x
430  real(dp), intent(in), optional :: c1
431  real(dp), intent(in), optional :: c2
432  ! -- local
433  real(dp) :: w
434  real(dp) :: b
435  real(dp) :: s
436  real(dp) :: cof1
437  real(dp) :: cof2
438  ! -- code
439  !
440  ! -- process optional variables
441  if (present(c1)) then
442  cof1 = c1
443  else
444  cof1 = -dtwo
445  end if
446  if (present(c2)) then
447  cof2 = c2
448  else
449  cof2 = dthree
450  end if
451  !
452  ! -- calculate head difference from bottom (w),
453  ! calculate range (b), and
454  ! calculate normalized head difference from bottom (s)
455  w = x - bot
456  b = top - bot
457  s = w / b
458  !
459  ! -- divide cof1 and cof2 by range to the power 3 and 2, respectively
460  cof1 = cof1 / b**dthree
461  cof2 = cof2 / b**dtwo
462  !
463  ! -- calculate fraction
464  if (s < dzero) then
465  y = dzero
466  else if (s < done) then
467  y = cof1 * w**dthree + cof2 * w**dtwo
468  else
469  y = done
470  end if
471  !
472  ! -- return
473  return
474  end function sqsaturation
475 
476  !> @ brief sQSaturationDerivative
477  !!
478  !! Nonlinear smoothing function returns value between 0-1
479  !<
480  function sqsaturationderivative(top, bot, x, c1, c2) result(y)
481  ! -- return
482  real(dp) :: y
483  ! -- dummy variables
484  real(dp), intent(in) :: top
485  real(dp), intent(in) :: bot
486  real(dp), intent(in) :: x
487  real(dp), intent(in), optional :: c1
488  real(dp), intent(in), optional :: c2
489  ! -- local
490  real(dp) :: w
491  real(dp) :: b
492  real(dp) :: s
493  real(dp) :: cof1
494  real(dp) :: cof2
495  ! -- code
496  !
497  !
498  ! -- process optional variables
499  if (present(c1)) then
500  cof1 = c1
501  else
502  cof1 = -dtwo
503  end if
504  if (present(c2)) then
505  cof2 = c2
506  else
507  cof2 = dthree
508  end if
509  !
510  ! -- calculate head difference from bottom (w),
511  ! calculate range (b), and
512  ! calculate normalized head difference from bottom (s)
513  w = x - bot
514  b = top - bot
515  s = w / b
516  !
517  ! -- multiply cof1 and cof2 by 3 and 2, respectively, and then
518  ! divide by range to the power 3 and 2, respectively
519  cof1 = cof1 * dthree / b**dthree
520  cof2 = cof2 * dtwo / b**dtwo
521  !
522  ! -- calculate derivative of fraction with respect to x
523  if (s < dzero) then
524  y = dzero
525  else if (s < done) then
526  y = cof1 * w**dtwo + cof2 * w
527  else
528  y = dzero
529  end if
530  !
531  ! -- return
532  return
533  end function sqsaturationderivative
534 
535  !> @ brief sSlope
536  !!
537  !! Nonlinear smoothing function returns a smoothed value of y that has the value
538  !! yi at xi and yi + (sm * dx) for x-values less than xi and yi + (sp * dx) for
539  !! x-values greater than xi, where dx = x - xi.
540  !<
541  function sslope(x, xi, yi, sm, sp, ta) result(y)
542  ! -- return
543  real(dp) :: y
544  ! -- dummy variables
545  real(dp), intent(in) :: x
546  real(dp), intent(in) :: xi
547  real(dp), intent(in) :: yi
548  real(dp), intent(in) :: sm
549  real(dp), intent(in) :: sp
550  real(dp), optional, intent(in) :: ta
551  ! -- local
552  real(dp) :: a
553  real(dp) :: b
554  real(dp) :: dx
555  real(dp) :: xm
556  real(dp) :: xp
557  real(dp) :: ym
558  real(dp) :: yp
559  !
560  ! -- set smoothing variable a
561  if (present(ta)) then
562  a = ta
563  else
564  a = dem8
565  end if
566  !
567  ! -- calculate b from smoothing variable a
568  b = a / (sqrt(dtwo) - done)
569  !
570  ! -- calculate contributions to y
571  dx = x - xi
572  xm = dhalf * (x + xi - sqrt(dx + b**dtwo - a**dtwo))
573  xp = dhalf * (x + xi + sqrt(dx + b**dtwo - a**dtwo))
574  ym = sm * (xm - xi)
575  yp = sp * (xi - xp)
576  !
577  ! -- calculate y from ym and yp contributions
578  y = yi + ym + yp
579  !
580  ! -- return
581  return
582  end function sslope
583 
584  !> @ brief sSlopeDerivative
585  !!
586  !! Derivative of nonlinear smoothing function that has the value yi at xi and
587  !! yi + (sm * dx) for x-values less than xi and yi + (sp * dx) for x-values
588  !! greater than xi, where dx = x - xi.
589  !<
590  function sslopederivative(x, xi, sm, sp, ta) result(y)
591  ! -- return
592  real(dp) :: y
593  ! -- dummy variables
594  real(dp), intent(in) :: x
595  real(dp), intent(in) :: xi
596  real(dp), intent(in) :: sm
597  real(dp), intent(in) :: sp
598  real(dp), optional, intent(in) :: ta
599  ! -- local
600  real(dp) :: a
601  real(dp) :: b
602  real(dp) :: dx
603  real(dp) :: mu
604  real(dp) :: rho
605  !
606  ! -- set smoothing variable a
607  if (present(ta)) then
608  a = ta
609  else
610  a = dem8
611  end if
612  !
613  ! -- calculate b from smoothing variable a
614  b = a / (sqrt(dtwo) - done)
615  !
616  ! -- calculate contributions to derivative
617  dx = x - xi
618  mu = sqrt(dx**dtwo + b**dtwo - a**dtwo)
619  rho = dx / mu
620  !
621  ! -- calculate derivative from individual contributions
622  y = dhalf * (sm + sp) - dhalf * rho * (sm - sp)
623  !
624  ! -- return
625  return
626  end function sslopederivative
627 
628  !> @ brief sQuadratic0sp
629  !!
630  !! Nonlinear smoothing function returns a smoothed value of y that uses a
631  !! quadratic to smooth x over range of xi - epsilon to xi + epsilon.
632  !! Simplification of sQuadraticSlope with sm = 0, sp = 1, and yi = 0.
633  !! From Panday et al. (2013) - eq. 35 - https://dx.doi.org/10.5066/F7R20ZFJ
634  !<
635  function squadratic0sp(x, xi, tomega) result(y)
636  ! -- return
637  real(dp) :: y
638  ! -- dummy variables
639  real(dp), intent(in) :: x
640  real(dp), intent(in) :: xi
641  real(dp), optional, intent(in) :: tomega
642  ! -- local
643  real(dp) :: omega
644  real(dp) :: epsilon
645  real(dp) :: dx
646  !
647  ! -- set smoothing interval
648  if (present(tomega)) then
649  omega = tomega
650  else
651  omega = dem6
652  end if
653  !
654  ! -- set smoothing interval
655  epsilon = dhalf * omega
656  !
657  ! -- calculate distance from xi
658  dx = x - xi
659  !
660  ! -- evaluate smoothing function
661  if (dx < -epsilon) then
662  y = xi
663  else if (dx < epsilon) then
664  y = (dx**dtwo / (dfour * epsilon)) + dhalf * dx + (epsilon / dfour) + xi
665  else
666  y = x
667  end if
668  !
669  ! -- return
670  return
671  end function squadratic0sp
672 
673  !> @ brief sQuadratic0spDerivative
674  !!
675  !! Derivative of nonlinear smoothing function returns a smoothed value of y
676  !! that uses a quadratic to smooth x over range of xi - epsilon to xi + epsilon.
677  !! Simplification of sQuadraticSlope with sm = 0, sp = 1, and yi = 0.
678  !! From Panday et al. (2013) - eq. 35 - https://dx.doi.org/10.5066/F7R20ZFJ
679  !<
680  function squadratic0spderivative(x, xi, tomega) result(y)
681  ! -- return
682  real(dp) :: y
683  ! -- dummy variables
684  real(dp), intent(in) :: x
685  real(dp), intent(in) :: xi
686  real(dp), optional, intent(in) :: tomega
687  ! -- local
688  real(dp) :: omega
689  real(dp) :: epsilon
690  real(dp) :: dx
691  !
692  ! -- set smoothing interval
693  if (present(tomega)) then
694  omega = tomega
695  else
696  omega = dem6
697  end if
698  !
699  ! -- set smoothing interval
700  epsilon = dhalf * omega
701  !
702  ! -- calculate distance from xi
703  dx = x - xi
704  !
705  ! -- evaluate smoothing function
706  if (dx < -epsilon) then
707  y = 0
708  else if (dx < epsilon) then
709  y = (dx / omega) + dhalf
710  else
711  y = 1
712  end if
713  !
714  ! -- return
715  return
716  end function squadratic0spderivative
717 
718  !> @ brief sQuadraticSlope
719  !!
720  !! Quadratic smoothing function returns a smoothed value of y that has the value
721  !! yi at xi and yi + (sm * dx) for x-values less than xi and yi + (sp * dx) for
722  !! x-values greater than xi, where dx = x - xi.
723  !<
724  function squadraticslope(x, xi, yi, sm, sp, tomega) result(y)
725  ! -- return
726  real(dp) :: y
727  ! -- dummy variables
728  real(dp), intent(in) :: x
729  real(dp), intent(in) :: xi
730  real(dp), intent(in) :: yi
731  real(dp), intent(in) :: sm
732  real(dp), intent(in) :: sp
733  real(dp), optional, intent(in) :: tomega
734  ! -- local
735  real(dp) :: omega
736  real(dp) :: epsilon
737  real(dp) :: dx
738  real(dp) :: c
739  !
740  ! -- set smoothing interval
741  if (present(tomega)) then
742  omega = tomega
743  else
744  omega = dem6
745  end if
746  !
747  ! -- set smoothing interval
748  epsilon = dhalf * omega
749  !
750  ! -- calculate distance from xi
751  dx = x - xi
752  !
753  ! -- evaluate smoothing function
754  if (dx < -epsilon) then
755  y = sm * dx
756  else if (dx < epsilon) then
757  c = dx / epsilon
758  y = dhalf * epsilon * (dhalf * (sp - sm) * (done + c**dtwo) + (sm + sp) * c)
759  else
760  y = sp * dx
761  end if
762  !
763  ! -- add value at xi
764  y = y + yi
765  !
766  ! -- return
767  return
768  end function squadraticslope
769 
770  !> @ brief sQuadraticSlopeDerivative
771  !!
772  !! Derivative of quadratic smoothing function returns a smoothed value of y
773  !! that has the value yi at xi and yi + (sm * dx) for x-values less than xi and
774  !! yi + (sp * dx) for x-values greater than xi, where dx = x - xi.
775  !<
776  function squadraticslopederivative(x, xi, sm, sp, tomega) result(y)
777  ! -- return
778  real(dp) :: y
779  ! -- dummy variables
780  real(dp), intent(in) :: x
781  real(dp), intent(in) :: xi
782  real(dp), intent(in) :: sm
783  real(dp), intent(in) :: sp
784  real(dp), optional, intent(in) :: tomega
785  ! -- local
786  real(dp) :: omega
787  real(dp) :: epsilon
788  real(dp) :: dx
789  real(dp) :: c
790  !
791  ! -- set smoothing interval
792  if (present(tomega)) then
793  omega = tomega
794  else
795  omega = dem6
796  end if
797  !
798  ! -- set smoothing interval
799  epsilon = dhalf * omega
800  !
801  ! -- calculate distance from xi
802  dx = x - xi
803  !
804  ! -- evaluate smoothing function
805  if (dx < -epsilon) then
806  y = sm
807  else if (dx < epsilon) then
808  c = dx / epsilon
809  y = dhalf * ((sp - sm) * c + (sm + sp))
810  else
811  y = sp
812  end if
813  !
814  ! -- return
815  return
816  end function squadraticslopederivative
817 
818 end module smoothingmodule
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dfour
real constant 4
Definition: Constants.f90:80
real(dp), parameter dem8
real constant 1e-8
Definition: Constants.f90:110
real(dp), parameter dem14
real constant 1e-14
Definition: Constants.f90:114
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:67
real(dp), parameter dem4
real constant 1e-4
Definition: Constants.f90:106
real(dp), parameter dem6
real constant 1e-6
Definition: Constants.f90:108
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
real(dp), parameter dem5
real constant 1e-5
Definition: Constants.f90:107
real(dp), parameter dprec
real constant machine precision
Definition: Constants.f90:119
real(dp), parameter dem2
real constant 1e-2
Definition: Constants.f90:104
real(dp), parameter dtwo
real constant 2
Definition: Constants.f90:78
real(dp), parameter dsix
real constant 6
Definition: Constants.f90:81
real(dp), parameter dthree
real constant 3
Definition: Constants.f90:79
real(dp), parameter done
real constant 1
Definition: Constants.f90:75
This module defines variable data types.
Definition: kind.f90:8
real(dp) function svangenuchtensaturation(top, bot, x, alpha, beta, sr)
@ brief sQuadraticSaturation
subroutine slinear(x, range, dydx, y)
@ brief sLinear
real(dp) function squadraticsaturation(top, bot, x, eps)
@ brief sQuadraticSaturation
real(dp) function slinearsaturation(top, bot, x)
@ brief sLinearSaturation
real(dp) function scubicsaturation(top, bot, x, eps)
@ brief sCubicSaturation
real(dp) function squadraticslope(x, xi, yi, sm, sp, tomega)
@ brief sQuadraticSlope
real(dp) function sslope(x, xi, yi, sm, sp, ta)
@ brief sSlope
subroutine scubiclinear(x, range, dydx, y)
@ brief sCubicLinear
real(dp) function squadraticslopederivative(x, xi, sm, sp, tomega)
@ brief sQuadraticSlopeDerivative
real(dp) function squadraticsaturationderivative(top, bot, x, eps)
@ brief Derivative of the quadratic saturation function
subroutine squadratic(x, range, dydx, y)
@ brief sQuadratic
real(dp) function sslopederivative(x, xi, sm, sp, ta)
@ brief sSlopeDerivative
real(dp) function sqsaturationderivative(top, bot, x, c1, c2)
@ brief sQSaturationDerivative
subroutine schsmooth(d, smooth, dwdh)
@ brief sChSmooth
real(dp) function squadratic0spderivative(x, xi, tomega)
@ brief sQuadratic0spDerivative
subroutine sscurve(x, range, dydx, y)
@ brief SCurve
real(dp) function sqsaturation(top, bot, x, c1, c2)
@ brief sQSaturation
real(dp) function squadratic0sp(x, xi, tomega)
@ brief sQuadratic0sp
subroutine scubic(x, range, dydx, y)
@ brief sCubic