GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
ddasik.f
Go to the documentation of this file.
1C Work perfored 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 ddasik(X,Y,YPRIME,NEQ,ICOPT,ID,RES,JACK,PSOL,H,WT,
6 * JSKIP,RPAR,IPAR,SAVR,DELTA,R,YIC,YPIC,PWK,WM,IWM,CJ,UROUND,
7 * EPLI,SQRTN,RSQRTN,EPCON,RATEMX,STPTOL,JFLG,
8 * ICNFLG,ICNSTR,IERNLS)
9C
10C***BEGIN PROLOGUE DDASIK
11C***REFER TO DDASPK
12C***DATE WRITTEN 941026 (YYMMDD)
13C***REVISION DATE 950808 (YYMMDD)
14C***REVISION DATE 951110 Removed unreachable block 390.
15C
16C
17C-----------------------------------------------------------------------
18C***DESCRIPTION
19C
20C
21C DDASIK 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 An initial value for Y and initial guess for YPRIME are input.
26C
27C The method used is a Newton scheme with Krylov iteration and a
28C linesearch algorithm.
29C
30C The parameters represent
31C
32C X -- Independent variable.
33C Y -- Solution vector at x.
34C YPRIME -- Derivative of solution vector.
35C NEQ -- Number of equations to be integrated.
36C ICOPT -- Initial condition option chosen (1 or 2).
37C ID -- Array of dimension NEQ, which must be initialized
38C if ICOPT = 1. See DDASIC.
39C RES -- External user-supplied subroutine
40C to evaluate the residual. See RES description
41C in DDASPK prologue.
42C JACK -- External user-supplied routine to update
43C the preconditioner. (This is optional).
44C See JAC description for the case
45C INFO(12) = 1 in the DDASPK prologue.
46C PSOL -- External user-supplied routine to solve
47C a linear system using preconditioning.
48C (This is optional). See explanation inside DDASPK.
49C H -- Scaling factor for this initial condition calc.
50C WT -- Vector of weights for error criterion.
51C JSKIP -- input flag to signal if initial JAC call is to be
52C skipped. 1 => skip the call, 0 => do not skip call.
53C RPAR,IPAR -- Real and integer arrays used for communication
54C between the calling program and external user
55C routines. They are not altered within DASPK.
56C SAVR -- Work vector for DDASIK of length NEQ.
57C DELTA -- Work vector for DDASIK of length NEQ.
58C R -- Work vector for DDASIK of length NEQ.
59C YIC,YPIC -- Work vectors for DDASIK, each of length NEQ.
60C PWK -- Work vector for DDASIK of length NEQ.
61C WM,IWM -- Real and integer arrays storing
62C matrix information for linear system
63C solvers, and various other information.
64C CJ -- Matrix parameter = 1/H (ICOPT = 1) or 0 (ICOPT = 2).
65C UROUND -- Unit roundoff.
66C EPLI -- convergence test constant.
67C See DDASPK prologue for more details.
68C SQRTN -- Square root of NEQ.
69C RSQRTN -- reciprical of square root of NEQ.
70C EPCON -- Tolerance to test for convergence of the Newton
71C iteration.
72C RATEMX -- Maximum convergence rate for which Newton iteration
73C is considered converging.
74C JFLG -- Flag showing whether a Jacobian routine is supplied.
75C ICNFLG -- Integer scalar. If nonzero, then constraint
76C violations in the proposed new approximate solution
77C will be checked for, and the maximum step length
78C will be adjusted accordingly.
79C ICNSTR -- Integer array of length NEQ containing flags for
80C checking constraints.
81C IERNLS -- Error flag for nonlinear solver.
82C 0 ==> nonlinear solver converged.
83C 1,2 ==> recoverable error inside nonlinear solver.
84C 1 => retry with current Y, YPRIME
85C 2 => retry with original Y, YPRIME
86C -1 ==> unrecoverable error in nonlinear solver.
87C
88C-----------------------------------------------------------------------
89C
90C***ROUTINES CALLED
91C RES, JACK, DNSIK, DCOPY
92C
93C***END PROLOGUE DDASIK
94C
95C
96 IMPLICIT DOUBLE PRECISION(a-h,o-z)
97 dimension y(*),yprime(*),id(*),wt(*),icnstr(*)
98 dimension savr(*),delta(*),r(*),yic(*),ypic(*),pwk(*)
99 dimension wm(*),iwm(*), rpar(*),ipar(*)
100 EXTERNAL res, jack, psol
101C
102 parameter(lnre=12, lnje=13, llocwp=29, llciwp=30)
103 parameter(lmxnit=32, lmxnj=33)
104C
105C
106C Perform initializations.
107C
108 lwp = iwm(llocwp)
109 liwp = iwm(llciwp)
110 mxnit = iwm(lmxnit)
111 mxnj = iwm(lmxnj)
112 iernls = 0
113 nj = 0
114 eplin = epli*epcon
115C
116C Call RES to initialize DELTA.
117C
118 ires = 0
119 iwm(lnre) = iwm(lnre) + 1
120 CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
121 IF (ires .LT. 0) GO TO 370
122C
123C Looping point for updating the preconditioner.
124C
125 300 CONTINUE
126C
127C Initialize all error flags to zero.
128C
129 ierpj = 0
130 ires = 0
131 iernew = 0
132C
133C If a Jacobian routine was supplied, call it.
134C
135 IF (jflg .EQ. 1 .AND. jskip .EQ. 0) THEN
136 nj = nj + 1
137 iwm(lnje)=iwm(lnje)+1
138 CALL jack (res, ires, neq, x, y, yprime, wt, delta, r, h, cj,
139 * wm(lwp), iwm(liwp), ierpj, rpar, ipar)
140 IF (ires .LT. 0 .OR. ierpj .NE. 0) GO TO 370
141 ENDIF
142 jskip = 0
143C
144C Call the nonlinear Newton solver for up to MXNIT iterations.
145C
146 CALL dnsik(x,y,yprime,neq,icopt,id,res,psol,wt,rpar,ipar,
147 * savr,delta,r,yic,ypic,pwk,wm,iwm,cj,sqrtn,rsqrtn,
148 * eplin,epcon,ratemx,mxnit,stptol,icnflg,icnstr,iernew)
149C
150 IF (iernew .EQ. 1 .AND. nj .LT. mxnj .AND. jflg .EQ. 1) THEN
151C
152C Up to MXNIT iterations were done, the convergence rate is < 1,
153C a Jacobian routine is supplied, and the number of JACK calls
154C is less than MXNJ.
155C Copy the residual SAVR to DELTA, call JACK, and try again.
156C
157 CALL dcopy (neq, savr, 1, delta, 1)
158 GO TO 300
159 ENDIF
160C
161 IF (iernew .NE. 0) GO TO 380
162 RETURN
163C
164C
165C Unsuccessful exits from nonlinear solver.
166C Set IERNLS accordingly.
167C
168 370 iernls = 2
169 IF (ires .LE. -2) iernls = -1
170 RETURN
171C
172 380 iernls = min(iernew,2)
173 RETURN
174C
175C----------------------- END OF SUBROUTINE DDASIK-----------------------
176 END
charNDArray min(char d, const charNDArray &m)
Definition chNDArray.cc:207
subroutine ddasik(x, y, yprime, neq, icopt, id, res, jack, psol, h, wt, jskip, rpar, ipar, savr, delta, r, yic, ypic, pwk, wm, iwm, cj, uround, epli, sqrtn, rsqrtn, epcon, ratemx, stptol, jflg, icnflg, icnstr, iernls)
Definition ddasik.f:9
subroutine dnsik(x, y, yprime, neq, icopt, id, res, psol, wt, rpar, ipar, savr, delta, r, yic, ypic, pwk, wm, iwm, cj, sqrtn, rsqrtn, eplin, epcon, ratemx, maxit, stptol, icnflg, icnstr, iernew)
Definition dnsik.f:8