annotate libcruft/daspk/dnedk.f @ 3911:8389e78e67d4

[project @ 2002-04-28 02:15:38 by jwe]
author jwe
date Sun, 28 Apr 2002 02:15:39 +0000
parents
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 DNEDK(X,Y,YPRIME,NEQ,RES,JACK,PSOL,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
6 * H,WT,JSTART,IDID,RPAR,IPAR,PHI,GAMMA,SAVR,DELTA,E,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
7 * WM,IWM,CJ,CJOLD,CJLAST,S,UROUND,EPLI,SQRTN,RSQRTN,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
8 * EPCON,JCALC,JFLG,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 DNEDK
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***REVISION DATE 940701 (YYMMDD)
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-----------------------------------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
18 C***DESCRIPTION
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
19 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
20 C DNEDK solves a nonlinear system of
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
21 C algebraic equations of the form
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
22 C G(X,Y,YPRIME) = 0 for the unknown Y.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
23 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
24 C The method used is a matrix-free Newton scheme.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
25 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
26 C The parameters represent
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 at x.
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 after successful step.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
31 C NEQ -- Number of equations to be integrated.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
32 C RES -- External user-supplied subroutine
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
33 C to evaluate the residual. See RES description
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
34 C in DDASPK prologue.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
35 C JACK -- External user-supplied routine to update
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
36 C the preconditioner. (This is optional).
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
37 C See JAC description for the case
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
38 C INFO(12) = 1 in the DDASPK prologue.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
39 C PSOL -- External user-supplied routine to solve
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
40 C a linear system using preconditioning.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
41 C (This is optional). See explanation inside DDASPK.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
42 C H -- Appropriate step size for this step.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
43 C WT -- Vector of weights for error criterion.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
44 C JSTART -- Indicates first call to this routine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
45 C If JSTART = 0, then this is the first call,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
46 C otherwise it is not.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
47 C IDID -- Completion flag, output by DNEDK.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
48 C See IDID description in DDASPK prologue.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
49 C RPAR,IPAR -- Real and integer arrays used for communication
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
50 C between the calling program and external user
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
51 C routines. They are not altered within DASPK.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
52 C PHI -- Array of divided differences used by
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
53 C DNEDK. The length is NEQ*(K+1), where
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
54 C K is the maximum order.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
55 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
56 C is K+1, where K is the maximum order.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
57 C SAVR -- Work vector for DNEDK of length NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
58 C DELTA -- Work vector for DNEDK of length NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
59 C E -- Error accumulation vector for DNEDK of length NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
60 C WM,IWM -- Real and integer arrays storing
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
61 C matrix information for linear system
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
62 C solvers, and various other information.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
63 C CJ -- Parameter always proportional to 1/H.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
64 C CJOLD -- Saves the value of CJ as of the last call to DITMD.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
65 C Accounts for changes in CJ needed to
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
66 C decide whether to call DITMD.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
67 C CJLAST -- Previous value of CJ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
68 C S -- A scalar determined by the approximate rate
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
69 C of convergence of the Newton iteration and used
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
70 C in the convergence test for the Newton iteration.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
71 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
72 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
73 C rate of convergence of the Newton iteration,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
74 C then S = RATE/(1.D0-RATE).
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
75 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
76 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
77 C iteration is converging; the closer RATE is to 1.,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
78 C the slower the Newton iteration is converging.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
79 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
80 C On the first Newton iteration with an up-dated
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
81 C preconditioner S = 100.D0, Thus the initial
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
82 C RATE of convergence is approximately 1.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
83 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
84 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
85 C estimate from a previous step can be applied to
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
86 C the current step.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
87 C UROUND -- Unit roundoff.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
88 C EPLI -- convergence test constant.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
89 C See DDASPK prologue for more details.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
90 C SQRTN -- Square root of NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
91 C RSQRTN -- reciprical of square root of NEQ.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
92 C EPCON -- Tolerance to test for convergence of the Newton
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
93 C iteration.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
94 C JCALC -- Flag used to determine when to update
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
95 C the Jacobian matrix. In general:
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
96 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
97 C JCALC = -1 ==> Call the DITMD routine to update
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
98 C the Jacobian matrix.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
99 C JCALC = 0 ==> Jacobian matrix is up-to-date.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
100 C JCALC = 1 ==> Jacobian matrix is out-dated,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
101 C but DITMD will not be called unless
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
102 C JCALC is set to -1.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
103 C JFLG -- Flag showing whether a Jacobian routine is supplied.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
104 C KP1 -- The current order + 1; updated across calls.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
105 C NONNEG -- Flag to determine nonnegativity constraints.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
106 C NTYPE -- Identification code for the DNEDK routine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
107 C 1 ==> modified Newton; iterative linear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
108 C 2 ==> modified Newton; user-supplied linear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
109 C IERNLS -- Error flag for nonlinear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
110 C 0 ==> nonlinear solver converged.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
111 C 1 ==> recoverable error inside non-linear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
112 C -1 ==> unrecoverable error inside non-linear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
113 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
114 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
115 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
116 C in DNSK:
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
117 C TOLNEW, MULDEL, MAXIT, IERNEW
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
118 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
119 C IERTYP -- Flag which tells whether this subroutine is correct.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
120 C 0 ==> correct subroutine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
121 C 1 ==> incorrect subroutine.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
122 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
123 C-----------------------------------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
124 C***ROUTINES CALLED
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
125 C RES, JACK, DDWNRM, DNSK
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
126 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
127 C***END PROLOGUE DNEDK
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
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
130 IMPLICIT DOUBLE PRECISION(A-H,O-Z)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
131 DIMENSION Y(*),YPRIME(*),WT(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
132 DIMENSION PHI(NEQ,*),SAVR(*),DELTA(*),E(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
133 DIMENSION WM(*),IWM(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
134 DIMENSION GAMMA(*),RPAR(*),IPAR(*)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
135 EXTERNAL RES, JACK, PSOL
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
136 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
137 PARAMETER (LNRE=12, LNJE=13, LLOCWP=29, LLCIWP=30)
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 SAVE MULDEL, MAXIT, XRATE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
140 DATA MULDEL/0/, MAXIT/4/, XRATE/0.25D0/
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
141 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
142 C Verify that this is the correct subroutine.
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 IERTYP = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
145 IF (NTYPE .NE. 1) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
146 IERTYP = 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
147 GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
148 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
149 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
150 C If this is the first step, perform initializations.
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 IF (JSTART .EQ. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
153 CJOLD = CJ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
154 JCALC = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
155 S = 100.D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
156 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
157 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
158 C Perform all other initializations.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
159 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
160 IERNLS = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
161 LWP = IWM(LLOCWP)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
162 LIWP = IWM(LLCIWP)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
163 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
164 C Decide whether to update the preconditioner.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
165 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
166 IF (JFLG .NE. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
167 TEMP1 = (1.0D0 - XRATE)/(1.0D0 + XRATE)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
168 TEMP2 = 1.0D0/TEMP1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
169 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
170 IF (CJ .NE. CJLAST) S = 100.D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
171 ELSE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
172 JCALC = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
173 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
174 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
175 C Looping point for updating preconditioner with current stepsize.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
176 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
177 300 CONTINUE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
178 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
179 C Initialize all error flags to zero.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
180 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
181 IERPJ = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
182 IRES = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
183 IERSL = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
184 IERNEW = 0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
185 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
186 C Predict the solution and derivative and compute the tolerance
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
187 C for the Newton iteration.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
188 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
189 DO 310 I=1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
190 Y(I)=PHI(I,1)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
191 310 YPRIME(I)=0.0D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
192 DO 330 J=2,KP1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
193 DO 320 I=1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
194 Y(I)=Y(I)+PHI(I,J)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
195 320 YPRIME(I)=YPRIME(I)+GAMMA(J)*PHI(I,J)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
196 330 CONTINUE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
197 EPLIN = EPLI*EPCON
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
198 TOLNEW = EPLIN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
199 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
200 C Call RES to initialize DELTA.
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 IWM(LNRE)=IWM(LNRE)+1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
203 CALL RES(X,Y,YPRIME,CJ,DELTA,IRES,RPAR,IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
204 IF (IRES .LT. 0) GO TO 380
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 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
207 C If indicated, update the preconditioner.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
208 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
209 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
210 IF(JCALC .EQ. -1)THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
211 IWM(LNJE) = IWM(LNJE) + 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
212 JCALC=0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
213 CALL JACK (RES, IRES, NEQ, X, Y, YPRIME, WT, DELTA, E, H, CJ,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
214 * WM(LWP), IWM(LIWP), IERPJ, RPAR, IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
215 CJOLD=CJ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
216 S = 100.D0
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
217 IF (IRES .LT. 0) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
218 IF (IERPJ .NE. 0) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
219 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
220 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
221 C Call the nonlinear Newton solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
222 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
223 CALL DNSK(X,Y,YPRIME,NEQ,RES,PSOL,WT,RPAR,IPAR,SAVR,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
224 * DELTA,E,WM,IWM,CJ,SQRTN,RSQRTN,EPLIN,EPCON,
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
225 * S,TEMP1,TOLNEW,MULDEL,MAXIT,IRES,IERSL,IERNEW)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
226 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
227 IF (IERNEW .GT. 0 .AND. JCALC .NE. 0) THEN
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 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
230 C preconditioner. Retry the step with a new preconditioner.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
231 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
232 JCALC = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
233 GO TO 300
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
234 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
235 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
236 IF (IERNEW .NE. 0) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
237 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
238 C The Newton iteration has converged. If nonnegativity of
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
239 C solution is required, set the solution nonnegative, if the
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
240 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
241 C large, then consider the corrector iteration to have failed.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
242 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
243 IF(NONNEG .EQ. 0) GO TO 390
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
244 DO 360 I = 1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
245 360 DELTA(I) = MIN(Y(I),0.0D0)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
246 DELNRM = DDWNRM(NEQ,DELTA,WT,RPAR,IPAR)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
247 IF(DELNRM .GT. EPCON) GO TO 380
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
248 DO 370 I = 1,NEQ
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
249 370 E(I) = E(I) - DELTA(I)
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
250 GO TO 390
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
251 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
252 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
253 C Exits from nonlinear solver.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
254 C No convergence with current preconditioner.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
255 C Compute IERNLS and IDID accordingly.
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
256 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
257 380 CONTINUE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
258 IF (IRES .LE. -2 .OR. IERSL .LT. 0 .OR. IERTYP .NE. 0) THEN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
259 IERNLS = -1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
260 IF (IRES .LE. -2) IDID = -11
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
261 IF (IERSL .LT. 0) IDID = -13
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
262 IF (IERTYP .NE. 0) IDID = -15
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
263 ELSE
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
264 IERNLS = 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
265 IF (IRES .EQ. -1) IDID = -10
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
266 IF (IERPJ .NE. 0) IDID = -5
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
267 IF (IERSL .GT. 0) IDID = -14
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
268 ENDIF
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
269 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
270 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
271 390 JCALC = 1
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
272 RETURN
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
273 C
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
274 C------END OF SUBROUTINE DNEDK------------------------------------------
8389e78e67d4 [project @ 2002-04-28 02:15:38 by jwe]
jwe
parents:
diff changeset
275 END