Computes a starting step size to be used in solving initial value problems in ordinary differential equations.
It is based on an estimate of the local lipschitz constant for the differential equation (lower bound on a norm of the jacobian) , a bound on the differential equation (first derivative), and a bound on the partial derivative of the equation with respect to the independent variable. (all approximated near the initial point a)
Note
Subroutine hstart also uses the me%stepsize_method%norm
function for computing vector norms
Note
This routine is from DDEABM.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(rk_variable_step_class), | intent(inout) | :: | me | |||
real(kind=wp), | intent(in) | :: | a |
the initial point of integration. |
||
real(kind=wp), | intent(in) | :: | b |
a value of the independent variable used to define
the direction of integration. a reasonable choice is to
set |
||
real(kind=wp), | intent(in), | dimension(me%n) | :: | y |
the vector of initial values of the |
|
real(kind=wp), | intent(in), | dimension(me%n) | :: | yprime |
the vector of derivatives of the |
|
real(kind=wp), | intent(in), | dimension(me%n) | :: | etol |
the vector of error tolerances corresponding to
the |
|
real(kind=wp), | intent(out) | :: | h |
appropriate starting step size to be attempted by the differential equation method. |
subroutine hstart(me,a,b,y,yprime,etol,h) implicit none class(rk_variable_step_class),intent(inout) :: me real(wp),intent(in) :: a !! the initial point of integration. real(wp),intent(in) :: b !! a value of the independent variable used to define !! the direction of integration. a reasonable choice is to !! set `b` to the first point at which a solution is desired. !! you can also use `b`, if necessary, to restrict the length !! of the first integration step because the algorithm will !! not compute a starting step length which is bigger than !! `abs(b-a)`, unless `b` has been chosen too close to `a`. !! (it is presumed that hstart has been called with `b` !! different from `a` on the machine being used. also see the !! discussion about the parameter `small`.) real(wp),dimension(me%n),intent(in) :: y !! the vector of initial values of the `neq` solution !! components at the initial point `a`. real(wp),dimension(me%n),intent(in) :: yprime !! the vector of derivatives of the `neq` !! solution components at the initial point `a`. !! (defined by the differential equations in subroutine `me%f`) real(wp),dimension(me%n),intent(in) :: etol !! the vector of error tolerances corresponding to !! the `neq` solution components. it is assumed that all !! elements are positive. following the first integration !! step, the tolerances are expected to be used by the !! integrator in an error test which roughly requires that !! `abs(local error) <= etol` for each vector component. real(wp),intent(out) :: h !! appropriate starting step size to be attempted by the !! differential equation method. real(wp),dimension(me%n) :: spy !! work array which provide the routine with needed storage space. real(wp),dimension(me%n) :: pv !! work array which provide the routine with needed storage space. real(wp),dimension(me%n) :: yp !! work array which provide the routine with needed storage space. real(wp),dimension(me%n) :: sf !! work array which provide the routine with needed storage space. real(wp),parameter :: small = epsilon(1.0_wp) real(wp),parameter :: big = huge(1.0_wp) real(wp),parameter :: relper = small**0.375_wp integer :: j, k, lk real(wp) :: absdx, da, delf, dely,& dfdub, dfdxb,& dx, dy, fbnd,& srydpb, tolexp, tolmin, tolp, tolsum, ydpb integer :: morder !! the order of the formula which will be used by !! the initial value method for taking the first integration !! step. morder = me%order() dx = b - a absdx = abs(dx) ! compute an approximate bound (dfdxb) on the partial ! derivative of the equation with respect to the ! independent variable. protect against an overflow. ! also compute a bound (fbnd) on the first derivative ! locally. da = sign(max(min(relper*abs(a),absdx),100.0_wp*small*abs(a)),dx) if (da == zero) da = relper*dx call me%f(a+da,y,sf) yp = sf - yprime delf = me%stepsize_method%norm(yp) dfdxb = big if (delf < big*abs(da)) dfdxb = delf/abs(da) fbnd = me%stepsize_method%norm(sf) ! compute an estimate (dfdub) of the local lipschitz ! constant for the system of differential equations. this ! also represents an estimate of the norm of the jacobian ! locally. three iterations (two when neq=1) are used to ! estimate the lipschitz constant by numerical differences. ! the first perturbation vector is based on the initial ! derivatives and direction of integration. the second ! perturbation vector is formed using another evaluation of ! the differential equation. the third perturbation vector ! is formed using perturbations based only on the initial ! values. components that are zero are always changed to ! non-zero values (except on the first iteration). when ! information is available, care is taken to ensure that ! components of the perturbation vector have signs which are ! consistent with the slopes of local solution curves. ! also choose the largest bound (fbnd) for the first ! derivative. ! ! perturbation vector size is held ! constant for all iterations. compute ! this change from the ! size of the vector of initial ! values. dely = relper*me%stepsize_method%norm(y) if (dely == zero) dely = relper dely = sign(dely,dx) delf = me%stepsize_method%norm(yprime) fbnd = max(fbnd,delf) if (delf == zero) then ! cannot have a null perturbation vector spy = zero yp = 1.0_wp delf = me%stepsize_method%norm(yp) else ! use initial derivatives for first perturbation spy = yprime yp = yprime end if dfdub = zero lk = min(me%n+1,3) do k = 1, lk ! define perturbed vector of initial values pv = y + yp * (dely/delf) if (k == 2) then ! use a shifted value of the independent variable ! in computing one estimate call me%f(a+da,pv,yp) pv = yp - sf else ! evaluate derivatives associated with perturbed ! vector and compute corresponding differences call me%f(a,pv,yp) pv = yp - yprime end if ! choose largest bounds on the first derivative ! and a local lipschitz constant fbnd = max(fbnd,me%stepsize_method%norm(yp)) delf = me%stepsize_method%norm(pv) if (delf >= big*abs(dely)) then ! protect against an overflow dfdub = big exit end if dfdub = max(dfdub,delf/abs(dely)) if (k == lk) exit ! choose next perturbation vector if (delf == zero) delf = 1.0_wp do j = 1, me%n if (k == 2) then dy = y(j) if (dy == zero) dy = dely/relper else dy = abs(pv(j)) if (dy == zero) dy = delf end if if (spy(j) == zero) spy(j) = yp(j) if (spy(j) /= zero) dy = sign(dy,spy(j)) yp(j) = dy end do delf = me%stepsize_method%norm(yp) end do ! compute a bound (ydpb) on the norm of the second derivative ydpb = dfdxb + dfdub*fbnd ! define the tolerance parameter upon which the starting step ! size is to be based. a value in the middle of the error ! tolerance range is selected. tolmin = big tolsum = zero do k = 1, me%n tolexp = log10(etol(k)) tolmin = min(tolmin,tolexp) tolsum = tolsum + tolexp end do tolp = 10.0_wp**(0.5_wp*(tolsum/me%n + tolmin)/(morder+1)) ! compute a starting step size based on the above first and ! second derivative information ! ! restrict the step length to be not bigger ! than abs(b-a). (unless b is too close to a) h = absdx if (ydpb == zero .and. fbnd == zero) then ! both first derivative term (fbnd) and second ! derivative term (ydpb) are zero if (tolp < 1.0_wp) h = absdx*tolp elseif (ydpb == zero) then ! only second derivative term (ydpb) is zero if (tolp < fbnd*absdx) h = tolp/fbnd else ! second derivative term (ydpb) is non-zero srydpb = sqrt(0.5_wp*ydpb) if (tolp < srydpb*absdx) h = tolp/srydpb end if ! further restrict the step length to be not bigger than 1/dfdub if (h*dfdub > 1.0_wp) h = 1.0_wp/dfdub ! finally, restrict the step length to be not ! smaller than 100*small*abs(a). however, if ! a=0. and the computed h underflowed to zero, ! the algorithm returns small*abs(b) for the step length. h = max(h,100.0_wp*small*abs(a)) if (h == zero) h = small*abs(b) ! now set direction of integration h = sign(h,dx) end subroutine hstart