GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dslvk.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 dslvk (NEQ, Y, TN, YPRIME, SAVR, X, EWT, WM, IWM,
6 * RES, IRES, PSOL, IERSL, CJ, EPLIN, SQRTN, RSQRTN, RHOK,
7 * RPAR, IPAR)
8C
9C***BEGIN PROLOGUE DSLVK
10C***REFER TO DDASPK
11C***DATE WRITTEN 890101 (YYMMDD)
12C***REVISION DATE 900926 (YYMMDD)
13C***REVISION DATE 940928 Removed MNEWT and added RHOK in call list.
14C
15C
16C-----------------------------------------------------------------------
17C***DESCRIPTION
18C
19C DSLVK uses a restart algorithm and interfaces to DSPIGM for
20C the solution of the linear system arising from a Newton iteration.
21C
22C In addition to variables described elsewhere,
23C communication with DSLVK uses the following variables..
24C WM = Real work space containing data for the algorithm
25C (Krylov basis vectors, Hessenberg matrix, etc.).
26C IWM = Integer work space containing data for the algorithm.
27C X = The right-hand side vector on input, and the solution vector
28C on output, of length NEQ.
29C IRES = Error flag from RES.
30C IERSL = Output flag ..
31C IERSL = 0 means no trouble occurred (or user RES routine
32C returned IRES < 0)
33C IERSL = 1 means the iterative method failed to converge
34C (DSPIGM returned IFLAG > 0.)
35C IERSL = -1 means there was a nonrecoverable error in the
36C iterative solver, and an error exit will occur.
37C-----------------------------------------------------------------------
38C***ROUTINES CALLED
39C DSCAL, DCOPY, DSPIGM
40C
41C***END PROLOGUE DSLVK
42C
43 INTEGER NEQ, IWM, IRES, IERSL, IPAR
44 DOUBLE PRECISION Y, TN, YPRIME, SAVR, X, EWT, WM, CJ, EPLIN,
45 1 sqrtn, rsqrtn, rhok, rpar
46 dimension y(*), yprime(*), savr(*), x(*), ewt(*),
47 1 wm(*), iwm(*), rpar(*), ipar(*)
48C
49 INTEGER IFLAG, IRST, NRSTS, NRMAX, LR, LDL, LHES, LGMR, LQ, LV,
50 1 LWK, LZ, MAXLP1, NPSL
51 INTEGER NLI, NPS, NCFL, NRE, MAXL, KMP, MITER
52 EXTERNAL RES, PSOL
53C
54 parameter(lnre=12, lncfl=16, lnli=20, lnps=21)
55 parameter(llocwp=29, llciwp=30)
56 parameter(lmiter=23, lmaxl=24, lkmp=25, lnrmax=26)
57C
58C-----------------------------------------------------------------------
59C IRST is set to 1, to indicate restarting is in effect.
60C NRMAX is the maximum number of restarts.
61C-----------------------------------------------------------------------
62 DATA irst/1/
63C
64 liwp = iwm(llciwp)
65 nli = iwm(lnli)
66 nps = iwm(lnps)
67 ncfl = iwm(lncfl)
68 nre = iwm(lnre)
69 lwp = iwm(llocwp)
70 maxl = iwm(lmaxl)
71 kmp = iwm(lkmp)
72 nrmax = iwm(lnrmax)
73 miter = iwm(lmiter)
74 iersl = 0
75 ires = 0
76C-----------------------------------------------------------------------
77C Use a restarting strategy to solve the linear system
78C P*X = -F. Parse the work vector, and perform initializations.
79C Note that zero is the initial guess for X.
80C-----------------------------------------------------------------------
81 maxlp1 = maxl + 1
82 lv = 1
83 lr = lv + neq*maxl
84 lhes = lr + neq + 1
85 lq = lhes + maxl*maxlp1
86 lwk = lq + 2*maxl
87 ldl = lwk + min0(1,maxl-kmp)*neq
88 lz = ldl + neq
89 CALL dscal (neq, rsqrtn, ewt, 1)
90 CALL dcopy (neq, x, 1, wm(lr), 1)
91 DO 110 i = 1,neq
92 110 x(i) = 0.d0
93C-----------------------------------------------------------------------
94C Top of loop for the restart algorithm. Initial pass approximates
95C X and sets up a transformed system to perform subsequent restarts
96C to update X. NRSTS is initialized to -1, because restarting
97C does not occur until after the first pass.
98C Update NRSTS; conditionally copy DL to R; call the DSPIGM
99C algorithm to solve A*Z = R; updated counters; update X with
100C the residual solution.
101C Note: if convergence is not achieved after NRMAX restarts,
102C then the linear solver is considered to have failed.
103C-----------------------------------------------------------------------
104 nrsts = -1
105 115 CONTINUE
106 nrsts = nrsts + 1
107 IF (nrsts .GT. 0) CALL dcopy (neq, wm(ldl), 1, wm(lr),1)
108 CALL dspigm (neq, tn, y, yprime, savr, wm(lr), ewt, maxl, maxlp1,
109 1 kmp, eplin, cj, res, ires, nres, psol, npsl, wm(lz), wm(lv),
110 2 wm(lhes), wm(lq), lgmr, wm(lwp), iwm(liwp), wm(lwk),
111 3 wm(ldl), rhok, iflag, irst, nrsts, rpar, ipar)
112 nli = nli + lgmr
113 nps = nps + npsl
114 nre = nre + nres
115 DO 120 i = 1,neq
116 120 x(i) = x(i) + wm(lz+i-1)
117 IF ((iflag .EQ. 1) .AND. (nrsts .LT. nrmax) .AND. (ires .EQ. 0))
118 1 GO TO 115
119C-----------------------------------------------------------------------
120C The restart scheme is finished. Test IRES and IFLAG to see if
121C convergence was not achieved, and set flags accordingly.
122C-----------------------------------------------------------------------
123 IF (ires .LT. 0) THEN
124 ncfl = ncfl + 1
125 ELSE IF (iflag .NE. 0) THEN
126 ncfl = ncfl + 1
127 IF (iflag .GT. 0) iersl = 1
128 IF (iflag .LT. 0) iersl = -1
129 ENDIF
130C-----------------------------------------------------------------------
131C Update IWM with counters, rescale EWT, and return.
132C-----------------------------------------------------------------------
133 iwm(lnli) = nli
134 iwm(lnps) = nps
135 iwm(lncfl) = ncfl
136 iwm(lnre) = nre
137 CALL dscal (neq, sqrtn, ewt, 1)
138 RETURN
139C
140C------END OF SUBROUTINE DSLVK------------------------------------------
141 END
subroutine dslvk(neq, y, tn, yprime, savr, x, ewt, wm, iwm, res, ires, psol, iersl, cj, eplin, sqrtn, rsqrtn, rhok, rpar, ipar)
Definition dslvk.f:8
subroutine dspigm(neq, tn, y, yprime, savr, r, wght, maxl, maxlp1, kmp, eplin, cj, res, ires, nre, psol, npsl, z, v, hes, q, lgmr, wp, iwp, wk, dl, rhok, iflag, irst, nrsts, rpar, ipar)
Definition dspigm.f:9