GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dnsd.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 dnsd(X,Y,YPRIME,NEQ,RES,PDUM,WT,RPAR,IPAR,
6 * DUMSVR,DELTA,E,WM,IWM,CJ,DUMS,DUMR,DUME,EPCON,
7 * S,CONFAC,TOLNEW,MULDEL,MAXIT,IRES,IDUM,IERNEW)
8C
9C***BEGIN PROLOGUE DNSD
10C***REFER TO DDASPK
11C***DATE WRITTEN 891219 (YYMMDD)
12C***REVISION DATE 900926 (YYMMDD)
13C***REVISION DATE 950126 (YYMMDD)
14C
15C
16C-----------------------------------------------------------------------
17C***DESCRIPTION
18C
19C DNSD solves a nonlinear system of
20C algebraic equations of the form
21C G(X,Y,YPRIME) = 0 for the unknown Y.
22C
23C The method used is a modified Newton scheme.
24C
25C The parameters represent
26C
27C X -- Independent variable.
28C Y -- Solution vector.
29C YPRIME -- Derivative of solution vector.
30C NEQ -- Number of unknowns.
31C RES -- External user-supplied subroutine
32C to evaluate the residual. See RES description
33C in DDASPK prologue.
34C PDUM -- Dummy argument.
35C WT -- Vector of weights for error criterion.
36C RPAR,IPAR -- Real and integer arrays used for communication
37C between the calling program and external user
38C routines. They are not altered within DASPK.
39C DUMSVR -- Dummy argument.
40C DELTA -- Work vector for DNSD of length NEQ.
41C E -- Error accumulation vector for DNSD of length NEQ.
42C WM,IWM -- Real and integer arrays storing
43C matrix information such as the matrix
44C of partial derivatives, permutation
45C vector, and various other information.
46C CJ -- Parameter always proportional to 1/H (step size).
47C DUMS -- Dummy argument.
48C DUMR -- Dummy argument.
49C DUME -- Dummy argument.
50C EPCON -- Tolerance to test for convergence of the Newton
51C iteration.
52C S -- Used for error convergence tests.
53C In the Newton iteration: S = RATE/(1 - RATE),
54C where RATE is the estimated rate of convergence
55C of the Newton iteration.
56C The calling routine passes the initial value
57C of S to the Newton iteration.
58C CONFAC -- A residual scale factor to improve convergence.
59C TOLNEW -- Tolerance on the norm of Newton correction in
60C alternative Newton convergence test.
61C MULDEL -- A flag indicating whether or not to multiply
62C DELTA by CONFAC.
63C 0 ==> do not scale DELTA by CONFAC.
64C 1 ==> scale DELTA by CONFAC.
65C MAXIT -- Maximum allowed number of Newton iterations.
66C IRES -- Error flag returned from RES. See RES description
67C in DDASPK prologue. If IRES = -1, then IERNEW
68C will be set to 1.
69C If IRES < -1, then IERNEW will be set to -1.
70C IDUM -- Dummy argument.
71C IERNEW -- Error flag for Newton iteration.
72C 0 ==> Newton iteration converged.
73C 1 ==> recoverable error inside Newton iteration.
74C -1 ==> unrecoverable error inside Newton iteration.
75C
76C All arguments with "DUM" in their names are dummy arguments
77C which are not used in this routine.
78C-----------------------------------------------------------------------
79C
80C***ROUTINES CALLED
81C DSLVD, DDWNRM, RES
82C
83C***END PROLOGUE DNSD
84C
85C
86 IMPLICIT DOUBLE PRECISION(a-h,o-z)
87 dimension y(*),yprime(*),wt(*),delta(*),e(*)
88 dimension wm(*),iwm(*), rpar(*),ipar(*)
89 EXTERNAL res
90C
91 parameter(lnre=12, lnni=19)
92C
93C Initialize Newton counter M and accumulation vector E.
94C
95 m = 0
96 DO 100 i=1,neq
97100 e(i)=0.0d0
98C
99C Corrector loop.
100C
101300 CONTINUE
102 iwm(lnni) = iwm(lnni) + 1
103C
104C If necessary, multiply residual by convergence factor.
105C
106 IF (muldel .EQ. 1) THEN
107 DO 320 i = 1,neq
108320 delta(i) = delta(i) * confac
109 ENDIF
110C
111C Compute a new iterate (back-substitution).
112C Store the correction in DELTA.
113C
114 CALL dslvd(neq,delta,wm,iwm)
115C
116C Update Y, E, and YPRIME.
117C
118 DO 340 i=1,neq
119 y(i)=y(i)-delta(i)
120 e(i)=e(i)-delta(i)
121340 yprime(i)=yprime(i)-cj*delta(i)
122C
123C Test for convergence of the iteration.
124C
125 delnrm=ddwnrm(neq,delta,wt,rpar,ipar)
126 IF (delnrm .LE. tolnew) GO TO 370
127 IF (m .EQ. 0) THEN
128 oldnrm = delnrm
129 ELSE
130 rate = (delnrm/oldnrm)**(1.0d0/m)
131 IF (rate .GT. 0.9d0) GO TO 380
132 s = rate/(1.0d0 - rate)
133 ENDIF
134 IF (s*delnrm .LE. epcon) GO TO 370
135C
136C The corrector has not yet converged.
137C Update M and test whether the
138C maximum number of iterations have
139C been tried.
140C
141 m=m+1
142 IF(m.GE.maxit) GO TO 380
143C
144C Evaluate the residual,
145C and go back to do another iteration.
146C
147 iwm(lnre)=iwm(lnre)+1
148 CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
149 IF (ires .LT. 0) GO TO 380
150 GO TO 300
151C
152C The iteration has converged.
153C
154370 RETURN
155C
156C The iteration has not converged. Set IERNEW appropriately.
157C
158380 CONTINUE
159 IF (ires .LE. -2 ) THEN
160 iernew = -1
161 ELSE
162 iernew = 1
163 ENDIF
164 RETURN
165C
166C
167C------END OF SUBROUTINE DNSD-------------------------------------------
168 END
double precision function ddwnrm(neq, v, rwt, rpar, ipar)
Definition ddwnrm.f:6
subroutine dnsd(x, y, yprime, neq, res, pdum, wt, rpar, ipar, dumsvr, delta, e, wm, iwm, cj, dums, dumr, dume, epcon, s, confac, tolnew, muldel, maxit, ires, idum, iernew)
Definition dnsd.f:8
subroutine dslvd(neq, delta, wm, iwm)
Definition dslvd.f:6