GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
ddasic.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 ddasic (X, Y, YPRIME, NEQ, ICOPT, ID, RES, JAC, PSOL,
6 * H, WT, NIC, IDID, RPAR, IPAR, PHI, SAVR, DELTA, E, YIC, YPIC,
7 * PWK, WM, IWM, HMIN, UROUND, EPLI, SQRTN, RSQRTN, EPCONI,
8 * STPTOL, JFLG, ICNFLG, ICNSTR, NLSIC)
9C
10C***BEGIN PROLOGUE DDASIC
11C***REFER TO DDASPK
12C***DATE WRITTEN 940628 (YYMMDD)
13C***REVISION DATE 941206 (YYMMDD)
14C***REVISION DATE 950714 (YYMMDD)
15C
16C-----------------------------------------------------------------------
17C***DESCRIPTION
18C
19C DDASIC is a driver routine to compute consistent initial values
20C for Y and YPRIME. There are two different options:
21C Denoting the differential variables in Y by Y_d, and
22C the algebraic variables by Y_a, the problem solved is either:
23C 1. Given Y_d, calculate Y_a and Y_d', or
24C 2. Given Y', calculate Y.
25C In either case, initial values for the given components
26C are input, and initial guesses for the unknown components
27C must also be provided as input.
28C
29C The external routine NLSIC solves the resulting nonlinear system.
30C
31C The parameters represent
32C
33C X -- Independent variable.
34C Y -- Solution vector at X.
35C YPRIME -- Derivative of solution vector.
36C NEQ -- Number of equations to be integrated.
37C ICOPT -- Flag indicating initial condition option chosen.
38C ICOPT = 1 for option 1 above.
39C ICOPT = 2 for option 2.
40C ID -- Array of dimension NEQ, which must be initialized
41C if option 1 is chosen.
42C ID(i) = +1 if Y_i is a differential variable,
43C ID(i) = -1 if Y_i is an algebraic variable.
44C RES -- External user-supplied subroutine to evaluate the
45C residual. See RES description in DDASPK prologue.
46C JAC -- External user-supplied routine to update Jacobian
47C or preconditioner information in the nonlinear solver
48C (optional). See JAC description in DDASPK prologue.
49C PSOL -- External user-supplied routine to solve
50C a linear system using preconditioning.
51C See PSOL in DDASPK prologue.
52C H -- Scaling factor in iteration matrix. DDASIC may
53C reduce H to achieve convergence.
54C WT -- Vector of weights for error criterion.
55C NIC -- Input number of initial condition calculation call
56C (= 1 or 2).
57C IDID -- Completion code. See IDID in DDASPK prologue.
58C RPAR,IPAR -- Real and integer parameter arrays that
59C are used for communication between the
60C calling program and external user routines.
61C They are not altered by DNSK
62C PHI -- Work space for DDASIC of length at least 2*NEQ.
63C SAVR -- Work vector for DDASIC of length NEQ.
64C DELTA -- Work vector for DDASIC of length NEQ.
65C E -- Work vector for DDASIC of length NEQ.
66C YIC,YPIC -- Work vectors for DDASIC, each of length NEQ.
67C PWK -- Work vector for DDASIC of length NEQ.
68C WM,IWM -- Real and integer arrays storing
69C information required by the linear solver.
70C EPCONI -- Test constant for Newton iteration convergence.
71C ICNFLG -- Flag showing whether constraints on Y are to apply.
72C ICNSTR -- Integer array of length NEQ with constraint types.
73C
74C The other parameters are for use internally by DDASIC.
75C
76C-----------------------------------------------------------------------
77C***ROUTINES CALLED
78C DCOPY, NLSIC
79C
80C***END PROLOGUE DDASIC
81C
82C
83 IMPLICIT DOUBLE PRECISION(a-h,o-z)
84 dimension y(*),yprime(*),id(*),wt(*),phi(neq,*)
85 dimension savr(*),delta(*),e(*),yic(*),ypic(*),pwk(*)
86 dimension wm(*),iwm(*), rpar(*),ipar(*), icnstr(*)
87 EXTERNAL res, jac, psol, nlsic
88C
89 parameter(lcfn=15)
90 parameter(lmxnh=34)
91C
92C The following parameters are data-loaded here:
93C RHCUT = factor by which H is reduced on retry of Newton solve.
94C RATEMX = maximum convergence rate for which Newton iteration
95C is considered converging.
96C
97 SAVE rhcut, ratemx
98 DATA rhcut/0.1d0/, ratemx/0.8d0/
99C
100C
101C-----------------------------------------------------------------------
102C BLOCK 1.
103C Initializations.
104C JSKIP is a flag set to 1 when NIC = 2 and NH = 1, to signal that
105C the initial call to the JAC routine is to be skipped then.
106C Save Y and YPRIME in PHI. Initialize IDID, NH, and CJ.
107C-----------------------------------------------------------------------
108C
109 mxnh = iwm(lmxnh)
110 idid = 1
111 nh = 1
112 jskip = 0
113 IF (nic .EQ. 2) jskip = 1
114 CALL dcopy (neq, y, 1, phi(1,1), 1)
115 CALL dcopy (neq, yprime, 1, phi(1,2), 1)
116C
117 IF (icopt .EQ. 2) THEN
118 cj = 0.0d0
119 ELSE
120 cj = 1.0d0/h
121 ENDIF
122C
123C-----------------------------------------------------------------------
124C BLOCK 2
125C Call the nonlinear system solver to obtain
126C consistent initial values for Y and YPRIME.
127C-----------------------------------------------------------------------
128C
129 200 CONTINUE
130 CALL nlsic(x,y,yprime,neq,icopt,id,res,jac,psol,h,wt,jskip,
131 * rpar,ipar,savr,delta,e,yic,ypic,pwk,wm,iwm,cj,uround,
132 * epli,sqrtn,rsqrtn,epconi,ratemx,stptol,jflg,icnflg,icnstr,
133 * iernls)
134C
135 IF (iernls .EQ. 0) RETURN
136C
137C-----------------------------------------------------------------------
138C BLOCK 3
139C The nonlinear solver was unsuccessful. Increment NCFN.
140C Return with IDID = -12 if either
141C IERNLS = -1: error is considered unrecoverable,
142C ICOPT = 2: we are doing initialization problem type 2, or
143C NH = MXNH: the maximum number of H values has been tried.
144C Otherwise (problem 1 with IERNLS .GE. 1), reduce H and try again.
145C If IERNLS > 1, restore Y and YPRIME to their original values.
146C-----------------------------------------------------------------------
147C
148 iwm(lcfn) = iwm(lcfn) + 1
149 jskip = 0
150C
151 IF (iernls .EQ. -1) GO TO 350
152 IF (icopt .EQ. 2) GO TO 350
153 IF (nh .EQ. mxnh) GO TO 350
154C
155 nh = nh + 1
156 h = h*rhcut
157 cj = 1.0d0/h
158C
159 IF (iernls .EQ. 1) GO TO 200
160C
161 CALL dcopy (neq, phi(1,1), 1, y, 1)
162 CALL dcopy (neq, phi(1,2), 1, yprime, 1)
163 GO TO 200
164C
165 350 idid = -12
166 RETURN
167C
168C------END OF SUBROUTINE DDASIC-----------------------------------------
169 END
subroutine ddasic(x, y, yprime, neq, icopt, id, res, jac, psol, h, wt, nic, idid, rpar, ipar, phi, savr, delta, e, yic, ypic, pwk, wm, iwm, hmin, uround, epli, sqrtn, rsqrtn, epconi, stptol, jflg, icnflg, icnstr, nlsic)
Definition ddasic.f:9