GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dnsid.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 dnsid(X,Y,YPRIME,NEQ,ICOPT,ID,RES,WT,RPAR,IPAR,
6 * DELTA,R,YIC,YPIC,WM,IWM,CJ,EPCON,RATEMX,MAXIT,STPTOL,
7 * ICNFLG,ICNSTR,IERNEW)
8C
9C***BEGIN PROLOGUE DNSID
10C***REFER TO DDASPK
11C***DATE WRITTEN 940701 (YYMMDD)
12C***REVISION DATE 950713 (YYMMDD)
13C
14C
15C-----------------------------------------------------------------------
16C***DESCRIPTION
17C
18C DNSID solves a nonlinear system of algebraic equations of the
19C form G(X,Y,YPRIME) = 0 for the unknown parts of Y and YPRIME
20C in the initial conditions.
21C
22C The method used is a modified Newton scheme.
23C
24C The parameters represent
25C
26C X -- Independent variable.
27C Y -- Solution vector.
28C YPRIME -- Derivative of solution vector.
29C NEQ -- Number of unknowns.
30C ICOPT -- Initial condition option chosen (1 or 2).
31C ID -- Array of dimension NEQ, which must be initialized
32C if ICOPT = 1. See DDASIC.
33C RES -- External user-supplied subroutine to evaluate the
34C residual. See RES description in DDASPK prologue.
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 DELTA -- Residual vector on entry, and work vector of
40C length NEQ for DNSID.
41C WM,IWM -- Real and integer arrays storing matrix information
42C such as the matrix of partial derivatives,
43C permutation vector, and various other information.
44C CJ -- Matrix parameter = 1/H (ICOPT = 1) or 0 (ICOPT = 2).
45C R -- Array of length NEQ used as workspace by the
46C linesearch routine DLINSD.
47C YIC,YPIC -- Work vectors for DLINSD, each of length NEQ.
48C EPCON -- Tolerance to test for convergence of the Newton
49C iteration.
50C RATEMX -- Maximum convergence rate for which Newton iteration
51C is considered converging.
52C MAXIT -- Maximum allowed number of Newton iterations.
53C STPTOL -- Tolerance used in calculating the minimum lambda
54C value allowed.
55C ICNFLG -- Integer scalar. If nonzero, then constraint
56C violations in the proposed new approximate solution
57C will be checked for, and the maximum step length
58C will be adjusted accordingly.
59C ICNSTR -- Integer array of length NEQ containing flags for
60C checking constraints.
61C IERNEW -- Error flag for Newton iteration.
62C 0 ==> Newton iteration converged.
63C 1 ==> failed to converge, but RATE .le. RATEMX.
64C 2 ==> failed to converge, RATE .gt. RATEMX.
65C 3 ==> other recoverable error (IRES = -1, or
66C linesearch failed).
67C -1 ==> unrecoverable error (IRES = -2).
68C
69C-----------------------------------------------------------------------
70C
71C***ROUTINES CALLED
72C DSLVD, DDWNRM, DLINSD, DCOPY
73C
74C***END PROLOGUE DNSID
75C
76C
77 IMPLICIT DOUBLE PRECISION(a-h,o-z)
78 dimension y(*),yprime(*),wt(*),r(*)
79 dimension id(*),delta(*), yic(*), ypic(*)
80 dimension wm(*),iwm(*), rpar(*),ipar(*)
81 dimension icnstr(*)
82 EXTERNAL res
83C
84 parameter(lnni=19, llsoff=35)
85C
86C
87C Initializations. M is the Newton iteration counter.
88C
89 lsoff = iwm(llsoff)
90 m = 0
91 rate = 1.0d0
92 rlx = 0.4d0
93C
94C Compute a new step vector DELTA by back-substitution.
95C
96 CALL dslvd (neq, delta, wm, iwm)
97C
98C Get norm of DELTA. Return now if norm(DELTA) .le. EPCON.
99C
100 delnrm = ddwnrm(neq,delta,wt,rpar,ipar)
101 fnrm = delnrm
102 IF (fnrm .LE. epcon) RETURN
103C
104C Newton iteration loop.
105C
106 300 CONTINUE
107 iwm(lnni) = iwm(lnni) + 1
108C
109C Call linesearch routine for global strategy and set RATE
110C
111 oldfnm = fnrm
112C
113 CALL dlinsd (neq, y, x, yprime, cj, delta, delnrm, wt, lsoff,
114 * stptol, iret, res, ires, wm, iwm, fnrm, icopt, id,
115 * r, yic, ypic, icnflg, icnstr, rlx, rpar, ipar)
116C
117 rate = fnrm/oldfnm
118C
119C Check for error condition from linesearch.
120 IF (iret .NE. 0) GO TO 390
121C
122C Test for convergence of the iteration, and return or loop.
123C
124 IF (fnrm .LE. epcon) RETURN
125C
126C The iteration has not yet converged. Update M.
127C Test whether the maximum number of iterations have been tried.
128C
129 m = m + 1
130 IF (m .GE. maxit) GO TO 380
131C
132C Copy the residual to DELTA and its norm to DELNRM, and loop for
133C another iteration.
134C
135 CALL dcopy (neq, r, 1, delta, 1)
136 delnrm = fnrm
137 GO TO 300
138C
139C The maximum number of iterations was done. Set IERNEW and return.
140C
141 380 IF (rate .LE. ratemx) THEN
142 iernew = 1
143 ELSE
144 iernew = 2
145 ENDIF
146 RETURN
147C
148 390 IF (ires .LE. -2) THEN
149 iernew = -1
150 ELSE
151 iernew = 3
152 ENDIF
153 RETURN
154C
155C
156C------END OF SUBROUTINE DNSID------------------------------------------
157 END
double precision function ddwnrm(neq, v, rwt, rpar, ipar)
Definition ddwnrm.f:6
subroutine dlinsd(neq, y, t, yprime, cj, p, pnrm, wt, lsoff, stptol, iret, res, ires, wm, iwm, fnrm, icopt, id, r, ynew, ypnew, icnflg, icnstr, rlx, rpar, ipar)
Definition dlinsd.f:9
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
subroutine dslvd(neq, delta, wm, iwm)
Definition dslvd.f:6