GNU Octave  4.0.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Properties Friends Macros Pages
ddasid.f
Go to the documentation of this file.
1 C Work performed under the auspices of the U.S. Department of Energy
2 C by Lawrence Livermore National Laboratory under contract number
3 C W-7405-Eng-48.
4 C
5  SUBROUTINE ddasid(X,Y,YPRIME,NEQ,ICOPT,ID,RES,JACD,PDUM,H,WT,
6  * jsdum,rpar,ipar,dumsvr,delta,r,yic,ypic,dumpwk,wm,iwm,cj,uround,
7  * dume,dums,dumr,epcon,ratemx,stptol,jfdum,
8  * icnflg,icnstr,iernls)
9 C
10 C***BEGIN PROLOGUE DDASID
11 C***REFER TO DDASPK
12 C***DATE WRITTEN 940701 (YYMMDD)
13 C***REVISION DATE 950808 (YYMMDD)
14 C***REVISION DATE 951110 Removed unreachable block 390.
15 C
16 C
17 C-----------------------------------------------------------------------
18 C***DESCRIPTION
19 C
20 C
21 C DDASID solves a nonlinear system of algebraic equations of the
22 C form G(X,Y,YPRIME) = 0 for the unknown parts of Y and YPRIME in
23 C the initial conditions.
24 C
25 C The method used is a modified Newton scheme.
26 C
27 C The parameters represent
28 C
29 C X -- Independent variable.
30 C Y -- Solution vector.
31 C YPRIME -- Derivative of solution vector.
32 C NEQ -- Number of unknowns.
33 C ICOPT -- Initial condition option chosen (1 or 2).
34 C ID -- Array of dimension NEQ, which must be initialized
35 C if ICOPT = 1. See DDASIC.
36 C RES -- External user-supplied subroutine to evaluate the
37 C residual. See RES description in DDASPK prologue.
38 C JACD -- External user-supplied routine to evaluate the
39 C Jacobian. See JAC description for the case
40 C INFO(12) = 0 in the DDASPK prologue.
41 C PDUM -- Dummy argument.
42 C H -- Scaling factor for this initial condition calc.
43 C WT -- Vector of weights for error criterion.
44 C JSDUM -- Dummy argument.
45 C RPAR,IPAR -- Real and integer arrays used for communication
46 C between the calling program and external user
47 C routines. They are not altered within DASPK.
48 C DUMSVR -- Dummy argument.
49 C DELTA -- Work vector for NLS of length NEQ.
50 C R -- Work vector for NLS of length NEQ.
51 C YIC,YPIC -- Work vectors for NLS, each of length NEQ.
52 C DUMPWK -- Dummy argument.
53 C WM,IWM -- Real and integer arrays storing matrix information
54 C such as the matrix of partial derivatives,
55 C permutation vector, and various other information.
56 C CJ -- Matrix parameter = 1/H (ICOPT = 1) or 0 (ICOPT = 2).
57 C UROUND -- Unit roundoff.
58 C DUME -- Dummy argument.
59 C DUMS -- Dummy argument.
60 C DUMR -- Dummy argument.
61 C EPCON -- Tolerance to test for convergence of the Newton
62 C iteration.
63 C RATEMX -- Maximum convergence rate for which Newton iteration
64 C is considered converging.
65 C JFDUM -- Dummy argument.
66 C STPTOL -- Tolerance used in calculating the minimum lambda
67 C value allowed.
68 C ICNFLG -- Integer scalar. If nonzero, then constraint
69 C violations in the proposed new approximate solution
70 C will be checked for, and the maximum step length
71 C will be adjusted accordingly.
72 C ICNSTR -- Integer array of length NEQ containing flags for
73 C checking constraints.
74 C IERNLS -- Error flag for nonlinear solver.
75 C 0 ==> nonlinear solver converged.
76 C 1,2 ==> recoverable error inside nonlinear solver.
77 C 1 => retry with current Y, YPRIME
78 C 2 => retry with original Y, YPRIME
79 C -1 ==> unrecoverable error in nonlinear solver.
80 C
81 C All variables with "DUM" in their names are dummy variables
82 C which are not used in this routine.
83 C
84 C-----------------------------------------------------------------------
85 C
86 C***ROUTINES CALLED
87 C RES, DMATD, DNSID
88 C
89 C***END PROLOGUE DDASID
90 C
91 C
92  IMPLICIT DOUBLE PRECISION(a-h,o-z)
93  dimension y(*),yprime(*),id(*),wt(*),icnstr(*)
94  dimension delta(*),r(*),yic(*),ypic(*)
95  dimension wm(*),iwm(*), rpar(*),ipar(*)
96  EXTERNAL res, jacd
97 C
98  parameter(lnre=12, lnje=13, lmxnit=32, lmxnj=33)
99 C
100 C
101 C Perform initializations.
102 C
103  mxnit = iwm(lmxnit)
104  mxnj = iwm(lmxnj)
105  iernls = 0
106  nj = 0
107 C
108 C Call RES to initialize DELTA.
109 C
110  ires = 0
111  iwm(lnre) = iwm(lnre) + 1
112  CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
113  IF (ires .LT. 0) go to 370
114 C
115 C Looping point for updating the Jacobian.
116 C
117 300 CONTINUE
118 C
119 C Initialize all error flags to zero.
120 C
121  ierj = 0
122  ires = 0
123  iernew = 0
124 C
125 C Reevaluate the iteration matrix, J = dG/dY + CJ*dG/dYPRIME,
126 C where G(X,Y,YPRIME) = 0.
127 C
128  nj = nj + 1
129  iwm(lnje)=iwm(lnje)+1
130  CALL dmatd(neq,x,y,yprime,delta,cj,h,ierj,wt,r,
131  * wm,iwm,res,ires,uround,jacd,rpar,ipar)
132  IF (ires .LT. 0 .OR. ierj .NE. 0) go to 370
133 C
134 C Call the nonlinear Newton solver for up to MXNIT iterations.
135 C
136  CALL dnsid(x,y,yprime,neq,icopt,id,res,wt,rpar,ipar,delta,r,
137  * yic,ypic,wm,iwm,cj,epcon,ratemx,mxnit,stptol,
138  * icnflg,icnstr,iernew)
139 C
140  IF (iernew .EQ. 1 .AND. nj .LT. mxnj) THEN
141 C
142 C MXNIT iterations were done, the convergence rate is < 1,
143 C and the number of Jacobian evaluations is less than MXNJ.
144 C Call RES, reevaluate the Jacobian, and try again.
145 C
146  iwm(lnre)=iwm(lnre)+1
147  CALL res(x,y,yprime,cj,delta,ires,rpar,ipar)
148  IF (ires .LT. 0) go to 370
149  go to 300
150  ENDIF
151 C
152  IF (iernew .NE. 0) go to 380
153 
154  RETURN
155 C
156 C
157 C Unsuccessful exits from nonlinear solver.
158 C Compute IERNLS accordingly.
159 C
160 370 iernls = 2
161  IF (ires .LE. -2) iernls = -1
162  RETURN
163 C
164 380 iernls = min(iernew,2)
165  RETURN
166 C
167 C------END OF SUBROUTINE DDASID-----------------------------------------
168  END
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:5
std::string dimension(void) const
subroutine ddasid(X, Y, YPRIME, NEQ, ICOPT, ID, RES, JACD, PDUM, H, WT, JSDUM, RPAR, IPAR, DUMSVR, DELTA, R, YIC, YPIC, DUMPWK, WM, IWM, CJ, UROUND, DUME, DUMS, DUMR, EPCON, RATEMX, STPTOL, JFDUM, ICNFLG, ICNSTR, IERNLS)
Definition: ddasid.f:5
subroutine dmatd(NEQ, X, Y, YPRIME, DELTA, CJ, H, IER, EWT, E, WM, IWM, RES, IRES, UROUND, JACD, RPAR, IPAR)
Definition: dmatd.f:5
charNDArray min(char d, const charNDArray &m)
Definition: chNDArray.cc:210