Main DVODE class.
communication between the user and the dvode package, for normal situations, is summarized here. this summary describes only a subset of the full set of options available. see the full description under dvode for details, including optional communication, nonstandard options, and instructions for special situations.
first provide a subroutine f
of the form f_func:
which supplies the vector function f by loading ydot(i) with f(i).
next determine (or guess) whether or not the problem is stiff. stiffness occurs when the jacobian matrix df/dy has an eigenvalue whose real part is negative and large in magnitude, compared to the reciprocal of the t span of interest. if the problem is nonstiff, use a method flag mf = 10. if it is stiff, there are four standard choices for mf (21, 22, 24, 25), and dvode requires the jacobian matrix in some form. in these cases (mf > 0), dvode will use a saved copy of the jacobian matrix. if this is undesirable because of storage limitations, set mf to the corresponding negative value (-21, -22, -24, -25). (see full description of mf below.) the jacobian matrix is regarded either as full (mf = 21 or 22), or banded (mf = 24 or 25). in the banded case, dvode requires two half-bandwidth parameters ml and mu. these are, respectively, the widths of the lower and upper parts of the band, excluding the main diagonal. thus the band consists of the locations (i,j) with i-ml <= j <= i+mu, and the full bandwidth is ml+mu+1.
if the problem is stiff, you are encouraged to supply the jacobian directly (mf = 21 or 24), but if this is not feasible, dvode will compute it internally by difference quotients (mf = 22 or 25). if you are supplying the jacobian, provide a subroutine of the form f_jac which supplies df/dy by loading pd as follows (in either case, only nonzero elements need be loaded):
write a main program which calls subroutine dvode once for each point at which answers are desired. this should also provide for possible use of logical unit 6 for output of error messages by dvode. on the first call to dvode, supply arguments as follows:
the output from the first call (or any call) is:
to continue the integration after a successful return, simply reset tout and call dvode again. no other parameters need be reset.
the following are optional calls which the user may make to gain additional capabilities in conjunction with dvode. (the routines xsetun and xsetf are designed to conform to the slatec error handling package.)
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
type(dvode_data_t), | private | :: | dat |
internal data (formerly in common blocks) |
|||
real(kind=wp), | private | :: | etaq | = | zero | ||
real(kind=wp), | private | :: | etaqm1 | = | zero | ||
integer, | private | :: | lunit | = | -1 |
logical unit number for messages. the default is obtained by a call to iumach (may be machine-dependent). |
|
integer, | private | :: | mesflg | = | 1 |
print control flag:
|
|
procedure(f_func), | private, | pointer | :: | f | => | null() | |
procedure(f_jac), | private, | pointer | :: | jac | => | null() | |
procedure(f_dewset), | private, | pointer | :: | dewset | => | null() | |
procedure(f_dvnorm), | private, | pointer | :: | dvnorm | => | null() |
this routine must be called first before using the solver.
Set the function pointers. This must be called before dvode is called.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
procedure(f_func) | :: | f |
the name of the user-supplied subroutine defining the ode system. the system must be put in the first-order form dy/dt = f(t,y), where f is a vector-valued function of the scalar t and the vector y. subroutine f is to compute the function f. it is to have the form subroutine f (neq, t, y, ydot) real(wp) t, y(neq), ydot(neq) where neq, t, and y are input, and the array ydot = f(t,y) is output. y and ydot are arrays of length neq. subroutine f should not alter y(1),...,y(neq). f must be declared external in the calling program. |
|||
procedure(f_jac), | optional | :: | jac |
the name of the user-supplied routine (miter = 1 or 4) to compute the jacobian matrix, df/dy, as a function of the scalar t and the vector y. it is to have the form f_jac, where neq, t, y, ml, mu, and nrowpd are input and the array pd is to be loaded with partial derivatives (elements of the jacobian matrix) in the output. pd must be given a first dimension of nrowpd. t and y have the same meaning as in subroutine f. |
||
procedure(f_dewset), | optional | :: | dewset |
the following subroutine is called just before each internal
integration step, and sets the array of error weights, ewt, as
described under itol/rtol/atol above:
|
||
procedure(f_dvnorm), | optional | :: | dvnorm |
the following is a real function routine which computes the weighted
root-mean-square norm of a vector v:
|
main solver routine.
dvode: variable-coefficient ordinary differential equation solver, with fixed-leading-coefficient implementation.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
integer, | intent(in) | :: | neq |
the size of the ode system (number of first order
ordinary differential equations).
|
||
real(kind=wp), | intent(inout) | :: | y(*) |
a real array for the vector of dependent variables, of
length |
||
real(kind=wp), | intent(inout) | :: | t |
the independent variable. in the input, |
||
real(kind=wp), | intent(in) | :: | tout |
the next value of |
||
integer, | intent(in) | :: | itol |
an indicator for the type of error control.
1 or 2 according as |
||
real(kind=wp), | intent(in) | :: | rtol(*) |
a relative error tolerance parameter, either a scalar or
an array of length |
||
real(kind=wp), | intent(in) | :: | atol(*) |
an absolute error tolerance parameter, either a scalar or
an array of length |
||
integer, | intent(in) | :: | itask |
an index specifying the task to be performed. input only. itask has the following values and meanings: |
||
integer, | intent(inout) | :: | istate |
an index used for input and output to specify the the state of the calculation. |
||
integer, | intent(in) | :: | iopt |
an integer flag to specify whether or not any optional input is being used on this call. the optional input is listed separately below. |
||
real(kind=wp) | :: | rwork(lrw) |
a real working array.
the length of |
|||
integer, | intent(in) | :: | lrw |
the length of the array rwork, as declared by the user. (this will be checked by the solver.) |
||
integer | :: | iwork(liw) |
an integer work array. the length of iwork must be at least: |
|||
integer, | intent(in) | :: | liw |
the length of the array iwork, as declared by the user. (this will be checked by the solver.) |
||
integer, | intent(in) | :: | mf |
method flag. standard values are: |
set the logical unit number, lun
, for
output of messages from dvode, if
the default is not desired.
the default value of lun
is output_unit
.
this call may be made at any time and
will take effect immediately.
reset the logical unit number for error messages.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
integer | :: | lun |
set a flag to control the printing of messages by dvode:
mflag = 0
means do not print. (danger:
this risks losing valuable information.)mflag = 1
means print (the default).this call may be made at any time and will take effect immediately.
reset the error print control flag.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
integer | :: | mflag |
saves and restores the contents of the internal variables used by dvode. dvsrco is useful if one is interrupting a run and restarting later, or alternating between two or more problems solved with dvode.
this routine saves or restores (depending on job
) the contents of the
dvode internal variables.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
type(dvode_data_t), | intent(inout) | :: | sav | |||
integer, | intent(in) | :: | job |
flag indicating to save or restore the data: |
provide derivatives of y, of various
orders, at a specified point t
, if
desired. it may be called only after
a successful return from dvode.
dvindy computes interpolated values of the k-th derivative of the dependent variable vector y, and stores it in dky. this routine is called within the package with k = 0 and t = tout, but may also be called by the user for any k up to the current order. (see detailed instructions in the usage documentation.)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
real(kind=wp), | intent(in) | :: | t |
value of independent variable where answers are desired (normally the same as the t last returned by dvode). for valid results, t must lie between tcur - hu and tcur. (see optional output for tcur and hu.) |
||
integer, | intent(in) | :: | k |
integer order of the derivative desired. k must satisfy 0 <= k <= nqcur, where nqcur is the current order (see optional output). the capability corresponding to k = 0, i.e. computing y(t), is already provided by dvode directly. since nqcur >= 1, the first derivative dy/dt is always available with dvindy. |
||
real(kind=wp), | intent(in) | :: | yh(ldyh,*) |
the history array yh |
||
integer, | intent(in) | :: | ldyh |
column length of yh, equal to the initial value of neq. |
||
real(kind=wp), | intent(out) | :: | dky(*) |
a real array of length neq containing the computed value of the k-th derivative of y(t). |
||
integer, | intent(out) | :: | iflag |
integer flag, returned as 0 if k and t were legal, -1 if k was illegal, and -2 if t was illegal. on an error return, a message is also written. |
this routine computes the step size, h0, to be attempted on the first step, when the user has not supplied a value for this.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
integer, | intent(in) | :: | n |
size of ode system |
||
real(kind=wp), | intent(in) | :: | t0 |
initial value of independent variable |
||
real(kind=wp), | intent(in) | :: | y0(*) |
vector of initial conditions |
||
real(kind=wp), | intent(in) | :: | ydot(*) |
vector of initial first derivatives |
||
real(kind=wp), | intent(in) | :: | tout |
first output value of independent variable |
||
real(kind=wp), | intent(in) | :: | uround |
machine unit roundoff |
||
real(kind=wp), | intent(in) | :: | ewt(*) |
error weights and tolerance parameters as described in the driver routine |
||
integer, | intent(in) | :: | itol |
error weights and tolerance parameters as described in the driver routine |
||
real(kind=wp), | intent(in) | :: | atol(*) |
error weights and tolerance parameters as described in the driver routine |
||
real(kind=wp), | intent(inout) | :: | y(n) |
work array of length n |
||
real(kind=wp), | intent(inout) | :: | temp(n) |
work array of length n |
||
real(kind=wp), | intent(out) | :: | h0 |
step size to be attempted |
||
integer, | intent(out) | :: | niter |
number of iterations (and of f evaluations) to compute h0 |
||
integer, | intent(out) | :: | ier |
the error flag, returned with the value: |
dvstep performs one step of the integration of an initial value problem for a system of ordinary differential equations.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
real(kind=wp), | intent(inout) | :: | y(*) |
an array of length n used for the dependent variable vector. |
||
real(kind=wp), | intent(inout) | :: | yh(ldyh,*) |
an ldyh by lmax array containing the dependent variables and their approximate scaled derivatives, where lmax = maxord + 1. yh(i,j+1) contains the approximate j-th derivative of y(i), scaled by h**j/factorial(j) (j = 0,1,...,nq). on entry for the first step, the first two columns of yh must be set from the initial values. |
||
integer, | intent(in) | :: | ldyh |
a constant integer >= n, the first dimension of yh. n is the number of odes in the system. |
||
real(kind=wp), | intent(inout) | :: | yh1(*) |
a one-dimensional array occupying the same space as yh. |
||
real(kind=wp), | intent(in) | :: | ewt(*) |
an array of length n containing multiplicative weights for local error measurements. local errors in y(i) are compared to 1.0/ewt(i) in various error tests. |
||
real(kind=wp) | :: | savf(*) |
an array of working storage, of length n. also used for input of yh(*,maxord+2) when jstart = -1 and maxord < the current order nq. |
|||
real(kind=wp) | :: | vsav(*) |
a work array of length n passed to subroutine dvnlsd. |
|||
real(kind=wp) | :: | acor(*) |
a work array of length n, used for the accumulated corrections. on a successful return, acor(i) contains the estimated one-step local error in y(i). |
|||
real(kind=wp) | :: | wm(*) |
real work array associated with matrix operations in dvnlsd. |
|||
integer | :: | iwm(*) |
integer work array associated with matrix operations in dvnlsd. |
dvset is called by dvstep and sets coefficients for use there.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me |
this subroutine adjusts the yh
array on reduction of order,
and also when the order is increased for the stiff option (meth = 2).
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
real(kind=wp), | intent(inout) | :: | yh(ldyh,*) | |||
integer, | intent(in) | :: | ldyh |
leading dimension of |
||
integer, | intent(in) | :: | iord |
an integer flag used when meth = 2 to indicate an order increase (iord = +1) or an order decrease (iord = -1). |
subroutine dvnlsd is a nonlinear system solver, which uses functional iteration or a chord (modified newton) method. for the chord method direct linear algebraic system solvers are used. subroutine dvnlsd then handles the corrector phase of this integration package.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
real(kind=wp), | intent(inout) | :: | y(*) |
the dependent variable, a vector of length n |
||
real(kind=wp), | intent(inout) | :: | yh(ldyh,*) |
the nordsieck (taylor) array, ldyh by lmax, input and output. on input, it contains predicted values. |
||
integer, | intent(in) | :: | ldyh |
a constant >= n, the first dimension of yh |
||
real(kind=wp) | :: | vsav(*) |
unused work array. |
|||
real(kind=wp) | :: | savf(*) |
a work array of length n. |
|||
real(kind=wp), | intent(in) | :: | ewt(*) |
an error weight vector of length n |
||
real(kind=wp), | intent(inout) | :: | acor(*) |
a work array of length n, used for the accumulated corrections to the predicted y vector. |
||
integer, | intent(inout) | :: | iwm(*) |
integer work array associated with matrix operations in chord iteration (miter /= 0). |
||
real(kind=wp), | intent(inout) | :: | wm(*) |
real work array associated with matrix operations in chord iteration (miter /= 0). |
||
integer, | intent(inout) | :: | nflag |
input/output flag, with values and meanings as follows: |
dvjac is called by dvnlsd to compute and process the matrix
p = i - h*rl1*j
, where j is an approximation to the jacobian.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
real(kind=wp), | intent(inout) | :: | y(*) |
vector containing predicted values on entry. |
||
real(kind=wp), | intent(in) | :: | yh(ldyh,*) |
the nordsieck array, an |
||
integer, | intent(in) | :: | ldyh |
a constant >= n, the first dimension of |
||
real(kind=wp), | intent(in) | :: | ewt(*) |
an error weight vector of length |
||
real(kind=wp), | intent(in) | :: | ftem(*) | |||
real(kind=wp), | intent(in) | :: | savf(*) |
array containing f evaluated at predicted y. |
||
real(kind=wp), | intent(inout) | :: | wm(*) |
real work space for matrices. in the output, it contains the inverse diagonal matrix if miter = 3 and the lu decomposition of p if miter is 1, 2 , 4, or 5. storage of matrix elements starts at wm(3). storage of the saved jacobian starts at wm(locjs). wm also contains the following matrix-related data: wm(1) = sqrt(uround), used in numerical jacobian step. wm(2) = h*rl1, saved for later use if miter = 3. |
||
integer, | intent(inout) | :: | iwm(*) |
integer work space containing pivot information, starting at iwm(31), if miter is 1, 2, 4, or 5. iwm also contains band parameters ml = iwm(1) and mu = iwm(2) if miter is 4 or 5. |
||
integer, | intent(out) | :: | ierpj |
output error flag, = 0 if no trouble, 1 if the p matrix is found to be singular. |
This routine manages the solution of the linear system arising from
a chord iteration. it is called if miter /= 0
:
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
real(kind=wp), | intent(inout) | :: | wm(*) |
real work space containing the inverse diagonal matrix if miter = 3 and the lu decomposition of the matrix otherwise. storage of matrix elements starts at wm(3). wm also contains the following matrix-related data: wm(1) = sqrt(uround) (not used here), wm(2) = hrl1, the previous value of h*rl1, used if miter = 3. |
||
integer | :: | iwm(*) |
integer work space containing pivot information, starting at iwm(31), if miter is 1, 2, 4, or 5. iwm also contains band parameters ml = iwm(1) and mu = iwm(2) if miter is 4 or 5. |
|||
real(kind=wp), | intent(inout) | :: | x(*) |
the right-hand side vector on input, and the solution vector on output, of length n. |
||
integer, | intent(out) | :: | iersl |
output flag. iersl = 0 if no trouble occurred. iersl = 1 if a singular matrix arose with miter = 3. |
save and recall error message control parameters.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
integer, | intent(in) | :: | ipar |
parameter indicator (1 for |
||
integer | :: | ivalue |
the value to be set for the parameter, if iset = .true. |
|||
logical, | intent(in) | :: | iset |
logical flag to indicate whether to read or write.
if |
write error message with values.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(dvode_t), | intent(inout) | :: | me | |||
character(len=*), | intent(in) | :: | msg |
the message (character array). |
||
integer, | intent(in) | :: | nmes |
the length of msg (number of characters). |
||
integer, | intent(in) | :: | nerr |
the error number (not used). |
||
integer, | intent(in) | :: | level |
the error level: |
||
integer, | intent(in) | :: | ni |
number of integers (0, 1, or 2) to be printed with message. |
||
integer, | intent(in) | :: | i1 |
integer to be printed, depending on |
||
integer, | intent(in) | :: | i2 |
integer to be printed, depending on |
||
integer, | intent(in) | :: | nr |
number of reals (0, 1, or 2) to be printed with message. |
||
real(kind=wp), | intent(in) | :: | r1 |
real to be printed, depending on |
||
real(kind=wp), | intent(in) | :: | r2 |
real to be printed, depending on |
type,public :: dvode_t private type(dvode_data_t) :: dat !! internal data (formerly in common blocks) ! formerly save variables real(wp) :: etaq = zero real(wp) :: etaqm1 = zero integer :: lunit = -1 !! logical unit number for messages. the default is obtained !! by a call to iumach (may be machine-dependent). integer :: mesflg = 1 !! print control flag: !! !! * 1 means print all messages (the default). !! * 0 means no printing. procedure(f_func),pointer :: f => null() procedure(f_jac),pointer :: jac => null() procedure(f_dewset),pointer :: dewset => null() procedure(f_dvnorm),pointer :: dvnorm => null() contains private procedure,public :: initialize !! this routine must be called first before using the solver. procedure,public :: solve => dvode !! main solver routine. procedure,public :: xsetun !! set the logical unit number, `lun`, for !! output of messages from [[dvode]], if !! the default is not desired. !! the default value of `lun` is `output_unit`. !! this call may be made at any time and !! will take effect immediately. procedure,public :: xsetf !! set a flag to control the printing of !! messages by [[dvode]]: !! !! * `mflag = 0` means do not print. (danger: !! this risks losing valuable information.) !! * `mflag = 1` means print (the default). !! !! this call may be made at any time and !! will take effect immediately. procedure,public :: dvsrco !! saves and restores the contents of !! the internal variables used by [[dvode]]. !! [[dvsrco]] is useful if one is !! interrupting a run and restarting !! later, or alternating between two or !! more problems solved with [[dvode]]. procedure,public :: dvindy !! provide derivatives of y, of various !! orders, at a specified point `t`, if !! desired. it may be called only after !! a successful return from [[dvode]]. procedure :: dvhin procedure :: dvstep procedure :: dvset procedure :: dvjust procedure :: dvnlsd procedure :: dvjac procedure :: dvsol procedure :: ixsav procedure :: xerrwd end type dvode_t