annotate libcruft/daspk/dnedd.f @ 7162:f2ba4aa9a5f9

[project @ 2007-11-12 19:56:07 by jwe]
author jwe
date Mon, 12 Nov 2007 19:56:08 +0000
parents 8389e78e67d4
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
3911
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
1 C Work performed under the auspices of the U.S. Department of Energy
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
2 C by Lawrence Livermore National Laboratory under contract number
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
3 C W-7405-Eng-48.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
4 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
5 SUBROUTINE DNEDD(X,Y,YPRIME,NEQ,RES,JACD,PDUM,H,WT,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
6 * JSTART,IDID,RPAR,IPAR,PHI,GAMMA,DUMSVR,DELTA,E,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
7 * WM,IWM,CJ,CJOLD,CJLAST,S,UROUND,DUME,DUMS,DUMR,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
8 * EPCON,JCALC,JFDUM,KP1,NONNEG,NTYPE,IERNLS)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
9 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
10 C***BEGIN PROLOGUE DNEDD
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
11 C***REFER TO DDASPK
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
12 C***DATE WRITTEN 891219 (YYMMDD)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
13 C***REVISION DATE 900926 (YYMMDD)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
14 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
15 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
16 C-----------------------------------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
17 C***DESCRIPTION
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
18 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
19 C DNEDD solves a nonlinear system of
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
20 C algebraic equations of the form
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
21 C G(X,Y,YPRIME) = 0 for the unknown Y.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
22 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
23 C The method used is a modified Newton scheme.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
24 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
25 C The parameters represent
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
26 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
27 C X -- Independent variable.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
28 C Y -- Solution vector.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
29 C YPRIME -- Derivative of solution vector.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
30 C NEQ -- Number of unknowns.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
31 C RES -- External user-supplied subroutine
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
32 C to evaluate the residual. See RES description
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
33 C in DDASPK prologue.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
34 C JACD -- External user-supplied routine to evaluate the
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
35 C Jacobian. See JAC description for the case
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
36 C INFO(12) = 0 in the DDASPK prologue.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
37 C PDUM -- Dummy argument.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
38 C H -- Appropriate step size for next step.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
39 C WT -- Vector of weights for error criterion.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
40 C JSTART -- Indicates first call to this routine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
41 C If JSTART = 0, then this is the first call,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
42 C otherwise it is not.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
43 C IDID -- Completion flag, output by DNEDD.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
44 C See IDID description in DDASPK prologue.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
45 C RPAR,IPAR -- Real and integer arrays used for communication
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
46 C between the calling program and external user
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
47 C routines. They are not altered within DASPK.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
48 C PHI -- Array of divided differences used by
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
49 C DNEDD. The length is NEQ*(K+1),where
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
50 C K is the maximum order.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
51 C GAMMA -- Array used to predict Y and YPRIME. The length
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
52 C is MAXORD+1 where MAXORD is the maximum order.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
53 C DUMSVR -- Dummy argument.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
54 C DELTA -- Work vector for NLS of length NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
55 C E -- Error accumulation vector for NLS of length NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
56 C WM,IWM -- Real and integer arrays storing
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
57 C matrix information such as the matrix
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
58 C of partial derivatives, permutation
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
59 C vector, and various other information.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
60 C CJ -- Parameter always proportional to 1/H.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
61 C CJOLD -- Saves the value of CJ as of the last call to DMATD.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
62 C Accounts for changes in CJ needed to
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
63 C decide whether to call DMATD.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
64 C CJLAST -- Previous value of CJ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
65 C S -- A scalar determined by the approximate rate
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
66 C of convergence of the Newton iteration and used
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
67 C in the convergence test for the Newton iteration.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
68 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
69 C If RATE is defined to be an estimate of the
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
70 C rate of convergence of the Newton iteration,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
71 C then S = RATE/(1.D0-RATE).
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
72 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
73 C The closer RATE is to 0., the faster the Newton
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
74 C iteration is converging; the closer RATE is to 1.,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
75 C the slower the Newton iteration is converging.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
76 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
77 C On the first Newton iteration with an up-dated
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
78 C preconditioner S = 100.D0, Thus the initial
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
79 C RATE of convergence is approximately 1.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
80 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
81 C S is preserved from call to call so that the rate
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
82 C estimate from a previous step can be applied to
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
83 C the current step.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
84 C UROUND -- Unit roundoff.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
85 C DUME -- Dummy argument.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
86 C DUMS -- Dummy argument.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
87 C DUMR -- Dummy argument.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
88 C EPCON -- Tolerance to test for convergence of the Newton
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
89 C iteration.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
90 C JCALC -- Flag used to determine when to update
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
91 C the Jacobian matrix. In general:
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
92 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
93 C JCALC = -1 ==> Call the DMATD routine to update
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
94 C the Jacobian matrix.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
95 C JCALC = 0 ==> Jacobian matrix is up-to-date.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
96 C JCALC = 1 ==> Jacobian matrix is out-dated,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
97 C but DMATD will not be called unless
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
98 C JCALC is set to -1.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
99 C JFDUM -- Dummy argument.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
100 C KP1 -- The current order(K) + 1; updated across calls.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
101 C NONNEG -- Flag to determine nonnegativity constraints.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
102 C NTYPE -- Identification code for the NLS routine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
103 C 0 ==> modified Newton; direct solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
104 C IERNLS -- Error flag for nonlinear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
105 C 0 ==> nonlinear solver converged.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
106 C 1 ==> recoverable error inside nonlinear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
107 C -1 ==> unrecoverable error inside nonlinear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
108 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
109 C All variables with "DUM" in their names are dummy variables
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
110 C which are not used in this routine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
111 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
112 C Following is a list and description of local variables which
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
113 C may not have an obvious usage. They are listed in roughly the
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
114 C order they occur in this subroutine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
115 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
116 C The following group of variables are passed as arguments to
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
117 C the Newton iteration solver. They are explained in greater detail
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
118 C in DNSD:
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
119 C TOLNEW, MULDEL, MAXIT, IERNEW
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
120 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
121 C IERTYP -- Flag which tells whether this subroutine is correct.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
122 C 0 ==> correct subroutine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
123 C 1 ==> incorrect subroutine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
124 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
125 C-----------------------------------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
126 C***ROUTINES CALLED
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
127 C DDWNRM, RES, DMATD, DNSD
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
128 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
129 C***END PROLOGUE DNEDD
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
130 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
131 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
132 IMPLICIT DOUBLE PRECISION(A-H,O-Z)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
133 DIMENSION Y(*),YPRIME(*),WT(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
134 DIMENSION DELTA(*),E(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
135 DIMENSION WM(*),IWM(*), RPAR(*),IPAR(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
136 DIMENSION PHI(NEQ,*),GAMMA(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
137 EXTERNAL RES, JACD
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
138 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
139 PARAMETER (LNRE=12, LNJE=13)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
140 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
141 SAVE MULDEL, MAXIT, XRATE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
142 DATA MULDEL/1/, MAXIT/4/, XRATE/0.25D0/
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
143 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
144 C Verify that this is the correct subroutine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
145 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
146 IERTYP = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
147 IF (NTYPE .NE. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
148 IERTYP = 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
149 GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
150 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
151 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
152 C If this is the first step, perform initializations.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
153 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
154 IF (JSTART .EQ. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
155 CJOLD = CJ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
156 JCALC = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
157 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
158 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
159 C Perform all other initializations.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
160 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
161 IERNLS = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
162 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
163 C Decide whether new Jacobian is needed.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
164 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
165 TEMP1 = (1.0D0 - XRATE)/(1.0D0 + XRATE)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
166 TEMP2 = 1.0D0/TEMP1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
167 IF (CJ/CJOLD .LT. TEMP1 .OR. CJ/CJOLD .GT. TEMP2) JCALC = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
168 IF (CJ .NE. CJLAST) S = 100.D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
169 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
170 C-----------------------------------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
171 C Entry point for updating the Jacobian with current
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
172 C stepsize.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
173 C-----------------------------------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
174 300 CONTINUE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
175 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
176 C Initialize all error flags to zero.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
177 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
178 IERJ = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
179 IRES = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
180 IERNEW = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
181 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
182 C Predict the solution and derivative and compute the tolerance
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
183 C for the Newton iteration.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
184 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
185 DO 310 I=1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
186 Y(I)=PHI(I,1)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
187 310 YPRIME(I)=0.0D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
188 DO 330 J=2,KP1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
189 DO 320 I=1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
190 Y(I)=Y(I)+PHI(I,J)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
191 320 YPRIME(I)=YPRIME(I)+GAMMA(J)*PHI(I,J)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
192 330 CONTINUE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
193 PNORM = DDWNRM (NEQ,Y,WT,RPAR,IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
194 TOLNEW = 100.D0*UROUND*PNORM
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
195 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
196 C Call RES to initialize DELTA.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
197 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
198 IWM(LNRE)=IWM(LNRE)+1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
199 CALL RES(X,Y,YPRIME,CJ,DELTA,IRES,RPAR,IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
200 IF (IRES .LT. 0) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
201 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
202 C If indicated, reevaluate the iteration matrix
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
203 C J = dG/dY + CJ*dG/dYPRIME (where G(X,Y,YPRIME)=0).
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
204 C Set JCALC to 0 as an indicator that this has been done.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
205 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
206 IF(JCALC .EQ. -1) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
207 IWM(LNJE)=IWM(LNJE)+1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
208 JCALC=0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
209 CALL DMATD(NEQ,X,Y,YPRIME,DELTA,CJ,H,IERJ,WT,E,WM,IWM,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
210 * RES,IRES,UROUND,JACD,RPAR,IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
211 CJOLD=CJ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
212 S = 100.D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
213 IF (IRES .LT. 0) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
214 IF(IERJ .NE. 0)GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
215 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
216 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
217 C Call the nonlinear Newton solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
218 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
219 TEMP1 = 2.0D0/(1.0D0 + CJ/CJOLD)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
220 CALL DNSD(X,Y,YPRIME,NEQ,RES,PDUM,WT,RPAR,IPAR,DUMSVR,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
221 * DELTA,E,WM,IWM,CJ,DUMS,DUMR,DUME,EPCON,S,TEMP1,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
222 * TOLNEW,MULDEL,MAXIT,IRES,IDUM,IERNEW)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
223 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
224 IF (IERNEW .GT. 0 .AND. JCALC .NE. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
225 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
226 C The Newton iteration had a recoverable failure with an old
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
227 C iteration matrix. Retry the step with a new iteration matrix.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
228 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
229 JCALC = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
230 GO TO 300
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
231 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
232 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
233 IF (IERNEW .NE. 0) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
234 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
235 C The Newton iteration has converged. If nonnegativity of
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
236 C solution is required, set the solution nonnegative, if the
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
237 C perturbation to do it is small enough. If the change is too
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
238 C large, then consider the corrector iteration to have failed.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
239 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
240 375 IF(NONNEG .EQ. 0) GO TO 390
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
241 DO 377 I = 1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
242 377 DELTA(I) = MIN(Y(I),0.0D0)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
243 DELNRM = DDWNRM(NEQ,DELTA,WT,RPAR,IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
244 IF(DELNRM .GT. EPCON) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
245 DO 378 I = 1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
246 378 E(I) = E(I) - DELTA(I)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
247 GO TO 390
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
248 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
249 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
250 C Exits from nonlinear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
251 C No convergence with current iteration
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
252 C matrix, or singular iteration matrix.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
253 C Compute IERNLS and IDID accordingly.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
254 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
255 380 CONTINUE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
256 IF (IRES .LE. -2 .OR. IERTYP .NE. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
257 IERNLS = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
258 IF (IRES .LE. -2) IDID = -11
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
259 IF (IERTYP .NE. 0) IDID = -15
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
260 ELSE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
261 IERNLS = 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
262 IF (IRES .LT. 0) IDID = -10
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
263 IF (IERJ .NE. 0) IDID = -8
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
264 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
265 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
266 390 JCALC = 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
267 RETURN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
268 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
269 C------END OF SUBROUTINE DNEDD------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
270 END