NAG Library Routine Document
D02NMF
1 Purpose
D02NMF is a reverse communication routine for integrating stiff systems of explicit ordinary differential equations.
2 Specification
SUBROUTINE D02NMF ( |
NEQ, LDYSAV, T, TOUT, Y, YDOT, RWORK, RTOL, ATOL, ITOL, INFORM, YSAV, SDYSAV, WKJAC, NWKJAC, JACPVT, NJCPVT, IMON, INLN, IRES, IREVCM, 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) |
|
3 Description
D02NMF is a general purpose routine for integrating the initial value problem for a stiff system of explicit ordinary differential equations,
An outline of a typical calling program is given below:
! Declarations
call linear algebra setup routine
call integrator setup routine
IREVCM=0
1000 CALL D02NMF(NEQ, LDYSAV, T, TOUT, Y, YDOT, RWORK, RTOL, &
ATOL, ITOL, INFORM, YSAVE, SDYSAV, WKJAC, NWKJAC, &
JACPVT, NJCPVT, IMON, INLN, IRES, IREVCM, ITASK, &
ITRACE, IFAIL)
IF (IREVCM.GT.0) 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(IRECVM.EQ.1.OR.IREVCM.GE.3.AND.IREVCM.LE.5) THEN
evaluate the derivative (iii)
ELSE IF(IREVCM.EQ.10) THEN
indicates an unsuccessful step
ENDIF
GO TO 1000
ENDIF
! 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 (sub)program on an intermeditate return () from D02NMF; these are denoted (i), (ii) and (iii) above.
The following sections describe in greater detail exactly what is required of each of these operations.
(i) Supply the Jacobian Matrix
You 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
D02NSF).
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 the function
is defined by
It is the Jacobian matrix
that you must supply as follows:
where
,
and
are located in
,
and
respectively and the array
Y contains the current values of the dependent variables. 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, 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 timestep may be obtained by calling real function
D02ZAF as follows:
IFAIL = 1
ERRLOC = D02ZAF(NEQ,RWORK(51+NEQ),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
D02NBF for details on what optional input can be made.
If
Y is changed, then
IMON must be set to
before return to D02NMF. If either of the values of HMIN or HMAX are changed, then
IMON must be set
before return to D02NMF. If HNEXT is changed, then
IMON must be set to
before return to D02NMF.
In addition you can force D02NMF to evaluate the residual vector
by setting
and
and then returning to D02NMF; 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 Derivative
This operation must evaluate the derivative vector for the explicit ordinary differential equation system defined by
where
is located in
.
Hereafter in this document this operation will be referred to as FCN.
4 References
5 Parameters
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.
- 1: NEQ – INTEGERInput
On initial entry: the number of differential equations to be solved.
Constraint:
.
- 2: LDYSAV – INTEGERInput
On initial entry: an upper bound on the maximum number of differential equations to be solved during the integration.
Constraint:
.
- 3: T – REAL (KIND=nag_wp)Input/Output
On initial entry:
, the value of the independent variable. The input value of
T is used only on the first call as the initial point of the integration.
On final exit: the value at which the computed solution
is returned (usually at
TOUT).
- 4: TOUT – REAL (KIND=nag_wp)Input
On initial entry: the next value of
at which a computed solution is desired. For the initial
, the input value of
TOUT is used to determine the direction of integration. Integration is permitted in either direction (see also
ITASK).
Constraint:
.
- 5: Y(NEQ) – REAL (KIND=nag_wp) arrayInput/Output
On initial entry: the values of the dependent variables (solution). On the first call the first
NEQ elements of
must contain the vector of initial values.
On final exit: the computed solution vector evaluated at
T (usually
).
- 6: YDOT(NEQ) – REAL (KIND=nag_wp) arrayInput/Output
On intermediate re-entry: must be set to the derivatives as defined under the description of
IREVCM.
On final exit: the time derivatives of the vector at the last integration point.
- 7: RWORK() – REAL (KIND=nag_wp) arrayCommunication Array
On initial entry: must be the same array as used by one of the method setup routines
D02MVF,
D02NVF or
D02NWF, and by one of the storage setup routines
D02NTF,
D02NUF or
D02NVF. The contents of
RWORK must not be changed between any call to a setup routine and the first call to D02NMF.
On intermediate re-entry: elements of
RWORK must be set to quantities as defined under the description of
IREVCM.
On intermediate exit:
contains information for JAC, FCN and MONITR operations as described in
Section 3 and the parameter
IREVCM.
- 8: RTOL() – REAL (KIND=nag_wp) arrayInput
-
Note: the dimension of the array
RTOL
must be at least
if
or
, and at least
otherwise.
On initial entry: the relative local error tolerance.
Constraint:
for all relevant
(see
ITOL).
- 9: ATOL() – REAL (KIND=nag_wp) arrayInput
-
Note: the dimension of the array
ATOL
must be at least
if
or
, and at least
otherwise.
On initial entry: the absolute local error tolerance.
Constraint:
for all relevant
(see
ITOL).
- 10: ITOL – INTEGERInput
On initial entry: a value to indicate the form of the local error test.
ITOL indicates to D02NMF whether to interpret either or both of
RTOL or
ATOL as a vector or a scalar. The error test to be satisfied is
, where
is defined as follows:
ITOL | RTOL | ATOL | |
1 | scalar | scalar | |
2 | scalar | vector | |
3 | vector | scalar | |
4 | vector | vector | |
is an estimate of the local error in , computed internally, and the choice of norm to be used is defined by a previous call to an integrator setup routine.
Constraint:
, , or .
- 11: INFORM() – INTEGER arrayCommunication Array
- 12: YSAV(LDYSAV,SDYSAV) – REAL (KIND=nag_wp) arrayCommunication Array
- 13: SDYSAV – INTEGERInput
On initial entry: the second dimension of the array
YSAV as declared in the (sub)program from which D02NMF is called. An appropriate value for
SDYSAV is described in the specifications of the integrator setup routines
D02NVF and
D02NWF. This value must be the same as that supplied to the integrator setup routine.
- 14: WKJAC(NWKJAC) – REAL (KIND=nag_wp) arrayInput/Output
On intermediate re-entry: elements of the Jacobian as defined under the description of
IREVCM. If a numerical Jacobian was requested then
WKJAC is used for workspace.
On intermediate exit:
the Jacobian is overwritten.
- 15: NWKJAC – INTEGERInput
On initial entry: the dimension of the array
WKJAC as declared in the (sub)program from which D02NMF is called. The actual size depends on the linear algebra method used. An appropriate value for
NWKJAC is described in the specifications of the linear algebra setup routines
D02NSF,
D02NTF and
D02NUF for full, banded and sparse matrix linear algebra respectively. This value must be the same as that supplied to the linear algebra setup routine.
- 16: JACPVT(NJCPVT) – INTEGER arrayCommunication Array
- 17: NJCPVT – INTEGERInput
On initial entry: the dimension of the array
JACPVT as declared in the (sub)program from which D02NMF is called. The actual size depends on the linear algebra method used. An appropriate value for
NJCPVT is described in the specifications of the linear algebra setup routines
D02NTF and
D02NUF for banded and sparse matrix linear algebra respectively. This value must be the same as that supplied to the linear algebra setup routine. When full matrix linear algebra is chosen, the array
JACPVT is not used and hence
NJCPVT should be set to
.
- 18: IMON – INTEGERInput/Output
On intermediate exit:
used to pass information between D02NMF and the MONITR operation (see
Section 3). With
,
IMON contains a flag indicating under what circumstances the return from D02NMF occurred:
- Exit from D02NMF after caused an early termination (this facility could be used to locate discontinuities).
- The current step failed repeatedly.
- Exit from D02NMF after a call to the internal nonlinear equation solver.
- The current step was successful.
On intermediate re-entry: may be reset to determine subsequent action in D02NMF.
- Integration is to be halted. A return will be made from D02NMF to the calling (sub)program with .
- Allow D02NMF to continue with its own internal strategy. The integrator will try up to three restarts unless .
- Return to the internal nonlinear equation solver, where the action taken is determined by the value of INLN.
- Normal exit to D02NMF to continue integration.
- Restart the integration at the current time point. The integrator will restart from order when this option is used. The solution Y, provided by the MONITR operation (see Section 3), will be used for the initial conditions.
- Try to continue with the same step size and order as was to be used before entering the MONITR operation (see Section 3). HMIN and HMAX may be altered if desired.
- Continue the integration but using a new value of HNEXT and possibly new values of HMIN and HMAX.
- 19: INLN – INTEGERInput/Output
On intermediate re-entry: with
and
,
INLN specifies the action to be taken by the internal nonlinear equation solver. By setting
and returning to D02NMF, the residual vector is evaluated and placed in
, for
and then the MONITR operation (see
Section 3) is invoked again. At present this is the only option available:
INLN must not be set to any other value.
On intermediate exit:
contains a flag indicating the action to be taken, if any, by the internal nonlinear equation solver.
- 20: IRES – INTEGERInput/Output
On intermediate exit:
with
,
,
,
or
,
IRES contains the value
.
On intermediate re-entry: should be unchanged unless one of the following actions is required of D02NMF in which case
IRES should be set accordingly.
- Indicates to D02NMF that control should be passed back immediately to the calling (sub)program with the error indicator set to .
- Indicates to D02NMF that an error condition has occurred in the solution vector, its time derivative or in the value of . The integrator will use a smaller time step to try to avoid this condition. If this is not possible D02NMF returns to the calling (sub)program with the error indicator set to .
- Indicates to D02NMF to stop its current operation and to enter the MONITR operation (see Section 3) immediately.
- 21: IREVCM – INTEGERInput/Output
On initial entry: must contain .
On intermediate re-entry: should remain unchanged.
On intermediate exit:
indicates what action you must take before re-entering. The possible exit values of
IREVCM are
,
,
,
,
,
or
, which should be interpreted as follows:
- , , and
- Indicates that an FCN operation (see Section 3) is required: must be supplied, where
is located in , for .
For or ,
should be placed in location , for .
For ,
should be placed in location , for .
For ,
should be placed in location , for .
- Indicates that a JAC operation (see Section 3) is required: the Jacobian matrix must be supplied.
If full matrix linear algebra is being used, then the th element of the Jacobian must be stored in .
If banded matrix linear algebra is being used then the th element of the Jacobian must be stored in , where and ; here and are the number of subdiagonals and superdiagonals, respectively, in the band.
If sparse matrix linear algebra is being used then
D02NRF must be called to determine which column of the Jacobian is required and where it should be stored.
CALL D02NRF(J, IPLACE, INFORM)
will return in
J the number of the column of the Jacobian that is required and will set
or
. If
, then the
th element of the Jacobian must be stored in
; otherwise it must be stored in
.
- Indicates that a MONITR operation (see Section 3) can be performed.
- Indicates that the current step was not successful, due to error test failure or convergence test failure. The only information supplied to you on this return is the current value of the independent variable , located in . No values must be changed before re-entering D02NMF; this facility enables you to determine the number of unsuccessful steps.
On final exit:
indicated the user-specified task has been completed or an error has been encountered (see the descriptions for
ITASK and
IFAIL).
Constraint:
, , , , , , or .
- 22: ITASK – INTEGERInput
On initial entry: the task to be performed by the integrator.
- Normal computation of output values of at (by overshooting and interpolating).
- Take one step only and return.
- Stop at the first internal integration point at or beyond and return.
- Normal computation of output values of at but without overshooting . TCRIT must be specified as an option in one of the integrator setup routines before the first call to the integrator, or specified in the optional input routine before a continuation call. TCRIT (e.g., see D02NVF) may be equal to or beyond TOUT, but not before it in the direction of integration.
- Take one step only and return, without passing TCRIT (e.g., see D02NVF). TCRIT must be specified under .
Constraint:
.
- 23: ITRACE – INTEGERInput
On initial entry: the level of output that is printed by the integrator.
ITRACE may take the value
,
,
,
or
.
- is assumed and similarly if , then is assumed.
- No output is generated.
- Only warning messages are printed on the current error message unit (see X04AAF).
- Warning messages are printed as above, and on the current advisory message unit (see X04ABF) output is generated which details Jacobian entries, the nonlinear iteration and the time integration. The advisory messages are given in greater detail the larger the value of ITRACE.
- 24: IFAIL – INTEGERInput/Output
On initial entry:
IFAIL must be set to
,
. If you are unfamiliar with this parameter you should refer to
Section 3.3 in the Essential Introduction for details.
For environments where it might be inappropriate to halt program execution when an error is detected, the value
is recommended. If the output of error messages is undesirable, then the value
is recommended. Otherwise, because for this routine the values of the output parameters may be useful even if
on exit, the recommended value is
.
When the value is used it is essential to test the value of IFAIL on exit.
On final exit:
unless the routine detects an error or a warning has been flagged (see
Section 6).
6 Error Indicators and Warnings
If on entry
or
, explanatory error messages are output on the current error message unit (as defined by
X04AAF).
Errors or warnings detected by the routine:
On entry, the integrator detected an illegal input, or that a linear algebra and/or integrator setup routine has not been called prior to the call to the integrator. If
, the form of the error will be detailed on the current error message unit (see
X04AAF).
-
The maximum number of steps specified has been taken (see the description of optional inputs in the integrator setup routines and the optional input continuation routine,
D02NZF).
-
With the given values of
RTOL and
ATOL no further progress can be made across the integration range from the current point
T. The components
contain the computed values of the solution at the current point
T.
-
There were repeated error test failures on an attempted step, before completing the requested task, but the integration was successful as far as
T. The problem may have a singularity, or the local error requirements may be inappropriate.
-
There were repeated convergence test failures on an attempted step, before completing the requested task, but the integration was successful as far as
T. This may be caused by an inaccurate Jacobian matrix or one which is incorrectly computed.
Some error weight
became zero during the integration (see the description of
ITOL). Pure relative error control
was requested on a variable (the
th) which has now vanished. The integration was successful as far as
T.
The FCN operation (see
Section 3) set the error flag
continually despite repeated attempts by the integrator to avoid this.
-
Not used for this integrator.
-
A singular Jacobian has been encountered. This error exit is unlikely to be taken when solving explicit ordinary differential equations. You should check the problem formulation and Jacobian calculation.
-
An error occurred during Jacobian formulation or back-substitution (a more detailed error description may be directed to the current error message unit, see
X04AAF).
The FCN operation (see
Section 3) signalled the integrator to halt the integration and return by setting
. Integration was successful as far as
T.
The MONITR operation (see
Section 3) set
and so forced a return but the integration was successful as far as
T.
-
The requested task has been completed, but it is estimated that a small change in
RTOL and
ATOL is unlikely to produce any change in the computed solution. (Only applies when you are not operating in one step mode, that is when
or
.)
-
The values of
RTOL and
ATOL are so small that D02NMF is unable to start the integration.
7 Accuracy
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 of the documents for
D02NBF (full matrix),
D02NCF (banded matrix) or
D02NDF (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).
9 Example
This example solves the well-known stiff Robertson problem
over the range
with initial conditions
and
and with scalar error control (
). The integration proceeds until
is passed, providing
interpolation at intervals of
through a MONITR operation. The integration method used is the BDF method (setup routine
D02NVF) with a modified Newton method. The Jacobian is a full matrix, which is specified using the setup routine
D02NSF; this Jacobian is to be calculated numerically.
9.1 Program Text
Program Text (d02nmfe.f90)
9.2 Program Data
Program Data (d02nmfe.d)
9.3 Program Results
Program Results (d02nmfe.r)