stepsize_class Derived Type

type, public :: stepsize_class

Algorithms for adjusting the step size for variable-step Runge-Kutta integrators.


Inherited by

type~~stepsize_class~~InheritedByGraph type~stepsize_class stepsize_class type~rk_variable_step_class rk_variable_step_class type~rk_variable_step_class->type~stepsize_class stepsize_method type~rkf108_class rkf108_class type~rkf108_class->type~rk_variable_step_class type~rkf1210_class rkf1210_class type~rkf1210_class->type~rk_variable_step_class type~rkf1412_class rkf1412_class type~rkf1412_class->type~rk_variable_step_class type~rkf78_class rkf78_class type~rkf78_class->type~rk_variable_step_class type~rkf89_class rkf89_class type~rkf89_class->type~rk_variable_step_class type~rkv89_class rkv89_class type~rkv89_class->type~rk_variable_step_class

Components

Type Visibility Attributes Name Initial
real(kind=wp), private :: hmax = huge(one)

maximum allowed step size

real(kind=wp), private :: hmin = two*epsilon(one)

minimum allowed step size

real(kind=wp), private :: hfactor_reject = 1.0e-3_wp

minimum allowed factor for decreasing step size after rejected step

real(kind=wp), private :: hfactor_accept = 100.0_wp

maximum allowed factor for increasing step size after accepted step

integer, private :: accept_mode = 1

method to determine if step is accepted [1,2]

integer, private :: max_attempts = 100

maximum number of attempts to decrease step size before giving up

logical, private :: relative_err = .false.

to use tol*h in the hfactor equation

real(kind=wp), private :: safety_factor = 0.9_wp

for hfactor equation (>0)

integer, private :: p_exponent_offset = 0

p + this value in the exponent (0 or 1)

procedure(norm_func), private, nopass, pointer :: norm => maxval_func

routine for computing the norm of the state


Type-Bound Procedures

procedure, public :: initialize => stepsize_class_constructor

  • private pure subroutine stepsize_class_constructor(me, hmin, hmax, hfactor_reject, hfactor_accept, norm, accept_mode, relative_err, safety_factor, p_exponent_offset, max_attempts)

    Constructor for a stepsize_class.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(stepsize_class), intent(inout) :: me
    real(kind=wp), intent(in), optional :: hmin

    minimum allowed step size (>0)

    real(kind=wp), intent(in), optional :: hmax

    maximum allowed step size (>0)

    real(kind=wp), intent(in), optional :: hfactor_reject

    minimum allowed factor for decreasing step size after rejected step (>0)

    real(kind=wp), intent(in), optional :: hfactor_accept

    maximum allowed factor for decreasing step size after accepted step (>0)

    procedure(norm_func), optional :: norm

    the user-specified function

    integer, intent(in), optional :: accept_mode

    method to determine if step is accepted [1,2]

    logical, intent(in), optional :: relative_err

    to use tol*h in the hfactor equation

    real(kind=wp), intent(in), optional :: safety_factor

    for hfactor equation (>0)

    integer, intent(in), optional :: p_exponent_offset

    p + this value in the exponent (0 or 1)

    integer, intent(in), optional :: max_attempts

    max step size change attempts after rejected step

procedure, public :: compute_stepsize

  • private pure subroutine compute_stepsize(me, h, tol, err, p, hnew, accept)

    Compute the new step size using the specific method.

    Arguments

    Type IntentOptional Attributes Name
    class(stepsize_class), intent(in) :: me
    real(kind=wp), intent(in) :: h

    current step size (<>0)

    real(kind=wp), intent(in) :: tol

    abs error tolerance (>0)

    real(kind=wp), intent(in) :: err

    truncation error estimate (>0)

    integer, intent(in) :: p

    order of the method

    real(kind=wp), intent(out) :: hnew

    new step size (<>0)

    logical, intent(out) :: accept

    if the step is accepted

procedure, public :: destroy => destroy_stepsize_class

Source Code

    type,public :: stepsize_class

        !! Algorithms for adjusting the step size for variable-step
        !! Runge-Kutta integrators.

        private

        real(wp) :: hmax           = huge(one)        !! maximum allowed step size
        real(wp) :: hmin           = two*epsilon(one) !! minimum allowed step size
        real(wp) :: hfactor_reject = 1.0e-3_wp        !! minimum allowed factor for decreasing step size after rejected step
        real(wp) :: hfactor_accept = 100.0_wp         !! maximum allowed factor for increasing step size after accepted step
        integer  :: accept_mode    = 1                !! method to determine if step is accepted [1,2]
        integer  :: max_attempts   = 100              !! maximum number of attempts to decrease step size before giving up

        ! the `hfactor` equation is:
        !
        ! if (relative_err) then
        !     hfactor = safety_factor * abs(tol*h/err)**(one/real(p+p_exponent_offset,wp))
        ! else
        !     hfactor = safety_factor * abs(tol/err)**(one/real(p+p_exponent_offset,wp))
        ! end if

        logical  :: relative_err      = .false. !! to use `tol*h` in the `hfactor` equation
        real(wp) :: safety_factor     = 0.9_wp  !! for `hfactor` equation (>0)
        integer  :: p_exponent_offset = 0       !! p + this value in the exponent (0 or 1)

        procedure(norm_func),nopass,pointer :: norm => maxval_func
            !! routine for computing the norm of the state

        contains

        private

        procedure,public :: initialize => stepsize_class_constructor
        procedure,public :: compute_stepsize
        procedure,public :: destroy => destroy_stepsize_class

    end type stepsize_class