GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dnedk.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 dnedk(X,Y,YPRIME,NEQ,RES,JACK,PSOL,
6 * H,WT,JSTART,IDID,RPAR,IPAR,PHI,GAMMA,SAVR,DELTA,E,
7 * WM,IWM,CJ,CJOLD,CJLAST,S,UROUND,EPLI,SQRTN,RSQRTN,
8 * EPCON,JCALC,JFLG,KP1,NONNEG,NTYPE,IERNLS)
9C
10C***BEGIN PROLOGUE DNEDK
11C***REFER TO DDASPK
12C***DATE WRITTEN 891219 (YYMMDD)
13C***REVISION DATE 900926 (YYMMDD)
14C***REVISION DATE 940701 (YYMMDD)
15C
16C
17C-----------------------------------------------------------------------
18C***DESCRIPTION
19C
20C DNEDK solves a nonlinear system of
21C algebraic equations of the form
22C G(X,Y,YPRIME) = 0 for the unknown Y.
23C
24C The method used is a matrix-free Newton scheme.
25C
26C The parameters represent
27C X -- Independent variable.
28C Y -- Solution vector at x.
29C YPRIME -- Derivative of solution vector
30C after successful step.
31C NEQ -- Number of equations to be integrated.
32C RES -- External user-supplied subroutine
33C to evaluate the residual. See RES description
34C in DDASPK prologue.
35C JACK -- External user-supplied routine to update
36C the preconditioner. (This is optional).
37C See JAC description for the case
38C INFO(12) = 1 in the DDASPK prologue.
39C PSOL -- External user-supplied routine to solve
40C a linear system using preconditioning.
41C (This is optional). See explanation inside DDASPK.
42C H -- Appropriate step size for this step.
43C WT -- Vector of weights for error criterion.
44C JSTART -- Indicates first call to this routine.
45C If JSTART = 0, then this is the first call,
46C otherwise it is not.
47C IDID -- Completion flag, output by DNEDK.
48C See IDID description in DDASPK prologue.
49C RPAR,IPAR -- Real and integer arrays used for communication
50C between the calling program and external user
51C routines. They are not altered within DASPK.
52C PHI -- Array of divided differences used by
53C DNEDK. The length is NEQ*(K+1), where
54C K is the maximum order.
55C GAMMA -- Array used to predict Y and YPRIME. The length
56C is K+1, where K is the maximum order.
57C SAVR -- Work vector for DNEDK of length NEQ.
58C DELTA -- Work vector for DNEDK of length NEQ.
59C E -- Error accumulation vector for DNEDK of length NEQ.
60C WM,IWM -- Real and integer arrays storing
61C matrix information for linear system
62C solvers, and various other information.
63C CJ -- Parameter always proportional to 1/H.
64C CJOLD -- Saves the value of CJ as of the last call to DITMD.
65C Accounts for changes in CJ needed to
66C decide whether to call DITMD.
67C CJLAST -- Previous value of CJ.
68C S -- A scalar determined by the approximate rate
69C of convergence of the Newton iteration and used
70C in the convergence test for the Newton iteration.
71C
72C If RATE is defined to be an estimate of the
73C rate of convergence of the Newton iteration,
74C then S = RATE/(1.D0-RATE).
75C
76C The closer RATE is to 0., the faster the Newton
77C iteration is converging; the closer RATE is to 1.,
78C the slower the Newton iteration is converging.
79C
80C On the first Newton iteration with an up-dated
81C preconditioner S = 100.D0, Thus the initial
82C RATE of convergence is approximately 1.
83C
84C S is preserved from call to call so that the rate
85C estimate from a previous step can be applied to
86C the current step.
87C UROUND -- Unit roundoff.
88C EPLI -- convergence test constant.
89C See DDASPK prologue for more details.
90C SQRTN -- Square root of NEQ.
91C RSQRTN -- reciprical of square root of NEQ.
92C EPCON -- Tolerance to test for convergence of the Newton
93C iteration.
94C JCALC -- Flag used to determine when to update
95C the Jacobian matrix. In general:
96C
97C JCALC = -1 ==> Call the DITMD routine to update
98C the Jacobian matrix.
99C JCALC = 0 ==> Jacobian matrix is up-to-date.
100C JCALC = 1 ==> Jacobian matrix is out-dated,
101C but DITMD will not be called unless
102C JCALC is set to -1.
103C JFLG -- Flag showing whether a Jacobian routine is supplied.
104C KP1 -- The current order + 1; updated across calls.
105C NONNEG -- Flag to determine nonnegativity constraints.
106C NTYPE -- Identification code for the DNEDK routine.
107C 1 ==> modified Newton; iterative linear solver.
108C 2 ==> modified Newton; user-supplied linear solver.
109C IERNLS -- Error flag for nonlinear solver.
110C 0 ==> nonlinear solver converged.
111C 1 ==> recoverable error inside non-linear solver.
112C -1 ==> unrecoverable error inside non-linear solver.
113C
114C The following group of variables are passed as arguments to
115C the Newton iteration solver. They are explained in greater detail
116C in DNSK:
117C TOLNEW, MULDEL, MAXIT, IERNEW
118C
119C IERTYP -- Flag which tells whether this subroutine is correct.
120C 0 ==> correct subroutine.
121C 1 ==> incorrect subroutine.
122C
123C-----------------------------------------------------------------------
124C***ROUTINES CALLED
125C RES, JACK, DDWNRM, DNSK
126C
127C***END PROLOGUE DNEDK
128C
129C
130 IMPLICIT DOUBLE PRECISION(a-h,o-z)
131 dimension y(*),yprime(*),wt(*)
132 dimension phi(neq,*),savr(*),delta(*),e(*)
133 dimension wm(*),iwm(*)
134 dimension gamma(*),rpar(*),ipar(*)
135 EXTERNAL res, jack, psol
136C
137 parameter(lnre=12, lnje=13, llocwp=29, llciwp=30)
138C
139 SAVE muldel, maxit, xrate
140 DATA muldel/0/, maxit/4/, xrate/0.25d0/
141C
142C Verify that this is the correct subroutine.
143C
144 iertyp = 0
145 IF (ntype .NE. 1) THEN
146 iertyp = 1
147 GO TO 380
148 ENDIF
149C
150C If this is the first step, perform initializations.
151C
152 IF (jstart .EQ. 0) THEN
153 cjold = cj
154 jcalc = -1
155 s = 100.d0
156 ENDIF
157C
158C Perform all other initializations.
159C
160 iernls = 0
161 lwp = iwm(llocwp)
162 liwp = iwm(llciwp)
163C
164C Decide whether to update the preconditioner.
165C
166 IF (jflg .NE. 0) THEN
167 temp1 = (1.0d0 - xrate)/(1.0d0 + xrate)
168 temp2 = 1.0d0/temp1
169 IF (cj/cjold .LT. temp1 .OR. cj/cjold .GT. temp2) jcalc = -1
170 IF (cj .NE. cjlast) s = 100.d0
171 ELSE
172 jcalc = 0
173 ENDIF
174C
175C Looping point for updating preconditioner with current stepsize.
176C
177300 CONTINUE
178C
179C Initialize all error flags to zero.
180C
181 ierpj = 0
182 ires = 0
183 iersl = 0
184 iernew = 0
185C
186C Predict the solution and derivative and compute the tolerance
187C for the Newton iteration.
188C
189 DO 310 i=1,neq
190 y(i)=phi(i,1)
191310 yprime(i)=0.0d0
192 DO 330 j=2,kp1
193 DO 320 i=1,neq
194 y(i)=y(i)+phi(i,j)
195320 yprime(i)=yprime(i)+gamma(j)*phi(i,j)
196330 CONTINUE
197 eplin = epli*epcon
198 tolnew = eplin
199C
200C Call RES to initialize DELTA.
201C
202 iwm(lnre)=iwm(lnre)+1
203 CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
204 IF (ires .LT. 0) GO TO 380
205C
206C
207C If indicated, update the preconditioner.
208C Set JCALC to 0 as an indicator that this has been done.
209C
210 IF(jcalc .EQ. -1)THEN
211 iwm(lnje) = iwm(lnje) + 1
212 jcalc=0
213 CALL jack (res, ires, neq, x, y, yprime, wt, delta, e, h, cj,
214 * wm(lwp), iwm(liwp), ierpj, rpar, ipar)
215 cjold=cj
216 s = 100.d0
217 IF (ires .LT. 0) GO TO 380
218 IF (ierpj .NE. 0) GO TO 380
219 ENDIF
220C
221C Call the nonlinear Newton solver.
222C
223 CALL dnsk(x,y,yprime,neq,res,psol,wt,rpar,ipar,savr,
224 * delta,e,wm,iwm,cj,sqrtn,rsqrtn,eplin,epcon,
225 * s,temp1,tolnew,muldel,maxit,ires,iersl,iernew)
226C
227 IF (iernew .GT. 0 .AND. jcalc .NE. 0) THEN
228C
229C The Newton iteration had a recoverable failure with an old
230C preconditioner. Retry the step with a new preconditioner.
231C
232 jcalc = -1
233 GO TO 300
234 ENDIF
235C
236 IF (iernew .NE. 0) GO TO 380
237C
238C The Newton iteration has converged. If nonnegativity of
239C solution is required, set the solution nonnegative, if the
240C perturbation to do it is small enough. If the change is too
241C large, then consider the corrector iteration to have failed.
242C
243 IF(nonneg .EQ. 0) GO TO 390
244 DO 360 i = 1,neq
245 360 delta(i) = min(y(i),0.0d0)
246 delnrm = ddwnrm(neq,delta,wt,rpar,ipar)
247 IF(delnrm .GT. epcon) GO TO 380
248 DO 370 i = 1,neq
249 370 e(i) = e(i) - delta(i)
250 GO TO 390
251C
252C
253C Exits from nonlinear solver.
254C No convergence with current preconditioner.
255C Compute IERNLS and IDID accordingly.
256C
257380 CONTINUE
258 IF (ires .LE. -2 .OR. iersl .LT. 0 .OR. iertyp .NE. 0) THEN
259 iernls = -1
260 IF (ires .LE. -2) idid = -11
261 IF (iersl .LT. 0) idid = -13
262 IF (iertyp .NE. 0) idid = -15
263 ELSE
264 iernls = 1
265 IF (ires .EQ. -1) idid = -10
266 IF (ierpj .NE. 0) idid = -5
267 IF (iersl .GT. 0) idid = -14
268 ENDIF
269C
270C
271390 jcalc = 1
272 RETURN
273C
274C------END OF SUBROUTINE DNEDK------------------------------------------
275 END
charNDArray min(char d, const charNDArray &m)
Definition chNDArray.cc:207
double precision function ddwnrm(neq, v, rwt, rpar, ipar)
Definition ddwnrm.f:6
subroutine dnedk(x, y, yprime, neq, res, jack, psol, h, wt, jstart, idid, rpar, ipar, phi, gamma, savr, delta, e, wm, iwm, cj, cjold, cjlast, s, uround, epli, sqrtn, rsqrtn, epcon, jcalc, jflg, kp1, nonneg, ntype, iernls)
Definition dnedk.f:9
subroutine dnsk(x, y, yprime, neq, res, psol, wt, rpar, ipar, savr, delta, e, wm, iwm, cj, sqrtn, rsqrtn, eplin, epcon, s, confac, tolnew, muldel, maxit, ires, iersl, iernew)
Definition dnsk.f:8
function gamma(x)
Definition gamma.f:3