GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
ddasid.f
Go to the documentation of this file.
1C Work performed under the auspices of the U.S. Department of Energy
2C by Lawrence Livermore National Laboratory under contract number
3C W-7405-Eng-48.
4C
5 SUBROUTINE ddasid(X,Y,YPRIME,NEQ,ICOPT,ID,RES,JACD,PDUM,H,WT,
6 * JSDUM,RPAR,IPAR,DUMSVR,DELTA,R,YIC,YPIC,DUMPWK,WM,IWM,CJ,UROUND,
7 * DUME,DUMS,DUMR,EPCON,RATEMX,STPTOL,JFDUM,
8 * ICNFLG,ICNSTR,IERNLS)
9C
10C***BEGIN PROLOGUE DDASID
11C***REFER TO DDASPK
12C***DATE WRITTEN 940701 (YYMMDD)
13C***REVISION DATE 950808 (YYMMDD)
14C***REVISION DATE 951110 Removed unreachable block 390.
15C
16C
17C-----------------------------------------------------------------------
18C***DESCRIPTION
19C
20C
21C DDASID solves a nonlinear system of algebraic equations of the
22C form G(X,Y,YPRIME) = 0 for the unknown parts of Y and YPRIME in
23C the initial conditions.
24C
25C The method used is a modified Newton scheme.
26C
27C The parameters represent
28C
29C X -- Independent variable.
30C Y -- Solution vector.
31C YPRIME -- Derivative of solution vector.
32C NEQ -- Number of unknowns.
33C ICOPT -- Initial condition option chosen (1 or 2).
34C ID -- Array of dimension NEQ, which must be initialized
35C if ICOPT = 1. See DDASIC.
36C RES -- External user-supplied subroutine to evaluate the
37C residual. See RES description in DDASPK prologue.
38C JACD -- External user-supplied routine to evaluate the
39C Jacobian. See JAC description for the case
40C INFO(12) = 0 in the DDASPK prologue.
41C PDUM -- Dummy argument.
42C H -- Scaling factor for this initial condition calc.
43C WT -- Vector of weights for error criterion.
44C JSDUM -- Dummy argument.
45C RPAR,IPAR -- Real and integer arrays used for communication
46C between the calling program and external user
47C routines. They are not altered within DASPK.
48C DUMSVR -- Dummy argument.
49C DELTA -- Work vector for NLS of length NEQ.
50C R -- Work vector for NLS of length NEQ.
51C YIC,YPIC -- Work vectors for NLS, each of length NEQ.
52C DUMPWK -- Dummy argument.
53C WM,IWM -- Real and integer arrays storing matrix information
54C such as the matrix of partial derivatives,
55C permutation vector, and various other information.
56C CJ -- Matrix parameter = 1/H (ICOPT = 1) or 0 (ICOPT = 2).
57C UROUND -- Unit roundoff.
58C DUME -- Dummy argument.
59C DUMS -- Dummy argument.
60C DUMR -- Dummy argument.
61C EPCON -- Tolerance to test for convergence of the Newton
62C iteration.
63C RATEMX -- Maximum convergence rate for which Newton iteration
64C is considered converging.
65C JFDUM -- Dummy argument.
66C STPTOL -- Tolerance used in calculating the minimum lambda
67C value allowed.
68C ICNFLG -- Integer scalar. If nonzero, then constraint
69C violations in the proposed new approximate solution
70C will be checked for, and the maximum step length
71C will be adjusted accordingly.
72C ICNSTR -- Integer array of length NEQ containing flags for
73C checking constraints.
74C IERNLS -- Error flag for nonlinear solver.
75C 0 ==> nonlinear solver converged.
76C 1,2 ==> recoverable error inside nonlinear solver.
77C 1 => retry with current Y, YPRIME
78C 2 => retry with original Y, YPRIME
79C -1 ==> unrecoverable error in nonlinear solver.
80C
81C All variables with "DUM" in their names are dummy variables
82C which are not used in this routine.
83C
84C-----------------------------------------------------------------------
85C
86C***ROUTINES CALLED
87C RES, DMATD, DNSID
88C
89C***END PROLOGUE DDASID
90C
91C
92 IMPLICIT DOUBLE PRECISION(a-h,o-z)
93 dimension y(*),yprime(*),id(*),wt(*),icnstr(*)
94 dimension delta(*),r(*),yic(*),ypic(*)
95 dimension wm(*),iwm(*), rpar(*),ipar(*)
96 EXTERNAL res, jacd
97C
98 parameter(lnre=12, lnje=13, lmxnit=32, lmxnj=33)
99C
100C
101C Perform initializations.
102C
103 mxnit = iwm(lmxnit)
104 mxnj = iwm(lmxnj)
105 iernls = 0
106 nj = 0
107C
108C Call RES to initialize DELTA.
109C
110 ires = 0
111 iwm(lnre) = iwm(lnre) + 1
112 CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
113 IF (ires .LT. 0) GO TO 370
114C
115C Looping point for updating the Jacobian.
116C
117300 CONTINUE
118C
119C Initialize all error flags to zero.
120C
121 ierj = 0
122 ires = 0
123 iernew = 0
124C
125C Reevaluate the iteration matrix, J = dG/dY + CJ*dG/dYPRIME,
126C where G(X,Y,YPRIME) = 0.
127C
128 nj = nj + 1
129 iwm(lnje)=iwm(lnje)+1
130 CALL dmatd(neq,x,y,yprime,delta,cj,h,ierj,wt,r,
131 * wm,iwm,res,ires,uround,jacd,rpar,ipar)
132 IF (ires .LT. 0 .OR. ierj .NE. 0) GO TO 370
133C
134C Call the nonlinear Newton solver for up to MXNIT iterations.
135C
136 CALL dnsid(x,y,yprime,neq,icopt,id,res,wt,rpar,ipar,delta,r,
137 * yic,ypic,wm,iwm,cj,epcon,ratemx,mxnit,stptol,
138 * icnflg,icnstr,iernew)
139C
140 IF (iernew .EQ. 1 .AND. nj .LT. mxnj) THEN
141C
142C MXNIT iterations were done, the convergence rate is < 1,
143C and the number of Jacobian evaluations is less than MXNJ.
144C Call RES, reevaluate the Jacobian, and try again.
145C
146 iwm(lnre)=iwm(lnre)+1
147 CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
148 IF (ires .LT. 0) GO TO 370
149 GO TO 300
150 ENDIF
151C
152 IF (iernew .NE. 0) GO TO 380
153
154 RETURN
155C
156C
157C Unsuccessful exits from nonlinear solver.
158C Compute IERNLS accordingly.
159C
160370 iernls = 2
161 IF (ires .LE. -2) iernls = -1
162 RETURN
163C
164380 iernls = min(iernew,2)
165 RETURN
166C
167C------END OF SUBROUTINE DDASID-----------------------------------------
168 END
charNDArray min(char d, const charNDArray &m)
Definition chNDArray.cc:207
subroutine ddasid(x, y, yprime, neq, icopt, id, res, jacd, pdum, h, wt, jsdum, rpar, ipar, dumsvr, delta, r, yic, ypic, dumpwk, wm, iwm, cj, uround, dume, dums, dumr, epcon, ratemx, stptol, jfdum, icnflg, icnstr, iernls)
Definition ddasid.f:9
subroutine dmatd(neq, x, y, yprime, delta, cj, h, ier, ewt, e, wm, iwm, res, ires, uround, jacd, rpar, ipar)
Definition dmatd.f:7
subroutine dnsid(x, y, yprime, neq, icopt, id, res, wt, rpar, ipar, delta, r, yic, ypic, wm, iwm, cj, epcon, ratemx, maxit, stptol, icnflg, icnstr, iernew)
Definition dnsid.f:8