D02NNF is a reverse communication routine for integrating stiff systems of implicit ordinary differential equations coupled with algebraic equations.
SUBROUTINE D02NNF ( |
NEQ, LDYSAV, T, TOUT, Y, YDOT, RWORK, RTOL, ATOL, ITOL, INFORM, YSAV, SDYSAV, WKJAC, NWKJAC, JACPVT, NJCPVT, IMON, INLN, IRES, IREVCM, LDERIV, ITASK, ITRACE, IFAIL) |
INTEGER |
NEQ, LDYSAV, ITOL, INFORM(23), SDYSAV, NWKJAC, JACPVT(NJCPVT), NJCPVT, IMON, INLN, IRES, IREVCM, ITASK, ITRACE, IFAIL |
REAL (KIND=nag_wp) |
T, TOUT, Y(NEQ), YDOT(NEQ), RWORK(50+4*NEQ), RTOL(*), ATOL(*), YSAV(LDYSAV,SDYSAV), WKJAC(NWKJAC) |
LOGICAL |
LDERIV(2) |
|
D02NNF is a general purpose routine for integrating the initial value problem for a stiff system of implicit ordinary differential equations coupled with algebraic equations, written in the form
An outline of a typical calling program is given below:
! Declarations
call linear algebra setup routine
call integrator setup routine
IREVCM=0
1000 CALL D02NNF(NEQ, NEQMAX, T, TOUT, Y, YDOT, RWORK, RTOL,
ATOL, ITOL, INFORM, YSAVE, NY2DIM, WKJAC, NWKJAC, JACPVT,
NJCPVT, IMON, INLN, IRES, IREVCM, LDERIV,
ITASK, ITRACE, IFAIL)
IF (IREVCM.GT.0) THEN
IF (IREVCM.GT.7 .AND. IREVCM.LT.11) THEN
IF (IREVCM.EQ.8) THEN
supply the Jacobian matrix (i)
ELSE IF (IREVCM.EQ.9) THEN
perform monitoring tasks requested by the user (ii)
ELSE IF (IREVCM.EQ.10) THEN
indicates an unsuccessful step
END IF
ELSE
evaluate the residual (iii)
ENDIF
GO TO 1000
END IF
! post processing (optional linear algebra diagnostic call
! (sparse case only), optional integrator diagnostic call)
STOP
END
There are three major operations that may be required of the calling subroutine on an intermediate return (
) from D02NNF; these are denoted
(i),
(ii) and
(iii).
The following sections describe in greater detail exactly what is required of each of these operations.
(i) |
Supply the Jacobian matrixYou need only provide this facility if the parameter
(or if using sparse matrix linear algebra) in a call to the linear algebra setup routine (see
JCEVAL in D02NUF).
If the Jacobian matrix is to be evaluated numerically by the integrator, then the remainder of section (i) can be ignored. We must define the system of nonlinear equations which is solved internally by the integrator. The time derivative, , has the form
where is the current step size and is a parameter that depends on the integration method in use. The vector is the current solution and the vector depends on information from previous time steps. This means that . The system of nonlinear equations that is solved has the form
but is solved in the form
where is the function defined by
It is the Jacobian matrix that you must supply as follows:
where , and are located in , and respectively and the arrays Y and YDOT contain the current solution and time derivatives respectively. Only the nonzero elements of the Jacobian need be set, since the locations where it is to be stored are preset to zero.
Hereafter in this document this operation will be referred to as JAC. |
(ii) |
Perform tasks requested by you
This operation is essentially a monitoring function and additionally provides the opportunity of changing the current values of Y, YDOT, HNEXT (the step size that the integrator proposes to take on the next step), HMIN (the minimum step size to be taken on the next step), and HMAX (the maximum step size to be taken on the next step).
The scaled local error at the end of a time step may be obtained by calling the real function D02ZAF as follows:
IFAIL = 1
ERRLOC = D02ZAF(NEQ,ROWK(51+NEQMAX),RWORK(51),IFAIL)
! CHECK IFAIL BEFORE PROCEEDING
The following gives details of the location within the array RWORK of variables that may be of interest to you:
Variable |
Specification |
Location |
TCURR |
the current value of the independent variable |
|
HLAST |
last step size successfully used by the integrator |
|
HNEXT |
step size that the integrator proposes to take on the next step |
|
HMIN |
minimum step size to be taken on the next step |
|
HMAX |
maximum step size to be taken on the next step |
|
NQU |
the order of the integrator used on the last step |
|
You are advised to consult the description of
MONITR in D02NGF
for details on what optional input can be made.
If either Y or YDOT are changed, then IMON must be set to before return to D02NNF. If either of the values HMIN or HMAX are changed, then IMON must be set before return to D02NNF. If HNEXT is changed, then IMON must be set to before return to D02NNF.
In addition you can force D02NNF to evaluate the residual vector
by setting and and then returning to D02NNF; on return to this monitoring operation the residual vector will be stored in
, for .
Hereafter in this document this operation will be referred to as MONITR. |
(iii) |
Evaluate the residual
This operation must evaluate the residual
in one case and the reduced residual
in another, where is located in . The form of the residual that is returned is determined by the value of IRES returned by D02NNF. If , then the residual defined by equation (2) above must be returned; if , then the residual returned by equation (1) above must be returned.
Hereafter in this document this operation will be referred to as RESID. |
Note: this routine uses
reverse communication. Its use involves an initial entry, intermediate exits and re-entries, and a final exit, as indicated by the parameter
IREVCM. Between intermediate exits and re-entries,
all parameters other than YDOT, RWORK, WKJAC, IMON, INLN and IRES must remain unchanged.
If on entry
or
, explanatory error messages are output on the current error message unit (as defined by
X04AAF).
The accuracy of the numerical solution may be controlled by a careful choice of the parameters
RTOL and
ATOL, and to a much lesser extent by the choice of norm. You are advised to use scalar error control unless the components of the solution are expected to be poorly scaled. For the type of decaying solution typical of many stiff problems, relative error control with a small absolute error threshold will be most appropriate (that is, you are advised to choose
with
small but positive).
The cost of computing a solution depends critically on the size of the differential system and to a lesser extent on the degree of stiffness of the problem; also on the type of linear algebra being used. For further details see
Section 8 in
D02NGF,
D02NHF and
D02NJF of the documents for
D02NGF (full matrix),
D02NHF (banded matrix) or
D02NJF (sparse matrix).
In general, you are advised to choose the Backward Differentiation Formula option (setup routine
D02NVF) but if efficiency is of great importance and especially if it is suspected that
has complex eigenvalues near the imaginary axis for some part of the integration, you should try the BLEND option (setup routine
D02NWF).
We solve the well-known stiff Robertson problem written as a differential system in implicit form
over the range
with initial conditions
and
and with scalar error control (
). We integrate to the first internal integration point past
(
), using a BDF method (setup routine
D02MVF) and a modified Newton method. We treat the Jacobian as sparse (setup routine
D02NUF) and we calculate it analytically. In this program we also illustrate the monitoring of step failures (
) and the forcing of a return when the component falls below
in the evaluation of the residual by setting
.