GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dlinsd.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 dlinsd (NEQ, Y, T, YPRIME, CJ, P, PNRM, WT, LSOFF,
6 * STPTOL, IRET, RES, IRES, WM, IWM,
7 * FNRM, ICOPT, ID, R, YNEW, YPNEW, ICNFLG,
8 * ICNSTR, RLX, RPAR, IPAR)
9C
10C***BEGIN PROLOGUE DLINSD
11C***REFER TO DNSID
12C***DATE WRITTEN 941025 (YYMMDD)
13C***REVISION DATE 941215 (YYMMDD)
14C***REVISION DATE 960129 Moved line RL = ONE to top block.
15C
16C
17C-----------------------------------------------------------------------
18C***DESCRIPTION
19C
20C DLINSD uses a linesearch algorithm to calculate a new (Y,YPRIME)
21C pair (YNEW,YPNEW) such that
22C
23C f(YNEW,YPNEW) .le. (1 - 2*ALPHA*RL)*f(Y,YPRIME) ,
24C
25C where 0 < RL <= 1. Here, f(y,y') is defined as
26C
27C f(y,y') = (1/2)*norm( (J-inverse)*G(t,y,y') )**2 ,
28C
29C where norm() is the weighted RMS vector norm, G is the DAE
30C system residual function, and J is the system iteration matrix
31C (Jacobian).
32C
33C In addition to the parameters defined elsewhere, we have
34C
35C P -- Approximate Newton step used in backtracking.
36C PNRM -- Weighted RMS norm of P.
37C LSOFF -- Flag showing whether the linesearch algorithm is
38C to be invoked. 0 means do the linesearch, and
39C 1 means turn off linesearch.
40C STPTOL -- Tolerance used in calculating the minimum lambda
41C value allowed.
42C ICNFLG -- Integer scalar. If nonzero, then constraint violations
43C in the proposed new approximate solution will be
44C checked for, and the maximum step length will be
45C adjusted accordingly.
46C ICNSTR -- Integer array of length NEQ containing flags for
47C checking constraints.
48C RLX -- Real scalar restricting update size in DCNSTR.
49C YNEW -- Array of length NEQ used to hold the new Y in
50C performing the linesearch.
51C YPNEW -- Array of length NEQ used to hold the new YPRIME in
52C performing the linesearch.
53C Y -- Array of length NEQ containing the new Y (i.e.,=YNEW).
54C YPRIME -- Array of length NEQ containing the new YPRIME
55C (i.e.,=YPNEW).
56C FNRM -- Real scalar containing SQRT(2*f(Y,YPRIME)) for the
57C current (Y,YPRIME) on input and output.
58C R -- Work array of length NEQ, containing the scaled
59C residual (J-inverse)*G(t,y,y') on return.
60C IRET -- Return flag.
61C IRET=0 means that a satisfactory (Y,YPRIME) was found.
62C IRET=1 means that the routine failed to find a new
63C (Y,YPRIME) that was sufficiently distinct from
64C the current (Y,YPRIME) pair.
65C IRET=2 means IRES .ne. 0 from RES.
66C-----------------------------------------------------------------------
67C
68C***ROUTINES CALLED
69C DFNRMD, DYYPNW, DCOPY
70C
71C***END PROLOGUE DLINSD
72C
73 IMPLICIT DOUBLE PRECISION(a-h,o-z)
74 EXTERNAL res
75 dimension y(*), yprime(*), wt(*), r(*), id(*)
76 dimension wm(*), iwm(*)
77 dimension ynew(*), ypnew(*), p(*), icnstr(*)
78 dimension rpar(*), ipar(*)
79 CHARACTER MSG*80
80C
81 parameter(lnre=12, lkprin=31)
82C
83 SAVE alpha, one, two
84 DATA alpha/1.0d-4/, one/1.0d0/, two/2.0d0/
85C
86 kprin=iwm(lkprin)
87C
88 f1nrm = (fnrm*fnrm)/two
89 ratio = one
90 IF (kprin .GE. 2) THEN
91 msg = '------ IN ROUTINE DLINSD-- PNRM = (R1) )'
92 CALL xerrwd(msg, 40, 901, 0, 0, 0, 0, 1, pnrm, 0.0d0)
93 ENDIF
94 tau = pnrm
95 ivio = 0
96 rl = one
97C-----------------------------------------------------------------------
98C Check for violations of the constraints, if any are imposed.
99C If any violations are found, the step vector P is rescaled, and the
100C constraint check is repeated, until no violations are found.
101C-----------------------------------------------------------------------
102 IF (icnflg .NE. 0) THEN
103 10 CONTINUE
104 CALL dyypnw (neq,y,yprime,cj,rl,p,icopt,id,ynew,ypnew)
105 CALL dcnstr (neq, y, ynew, icnstr, tau, rlx, iret, ivar)
106 IF (iret .EQ. 1) THEN
107 ivio = 1
108 ratio1 = tau/pnrm
109 ratio = ratio*ratio1
110 DO 20 i = 1,neq
111 20 p(i) = p(i)*ratio1
112 pnrm = tau
113 IF (kprin .GE. 2) THEN
114 msg = '------ CONSTRAINT VIOL., PNRM = (R1), INDEX = (I1)'
115 CALL xerrwd(msg, 50, 902, 0, 1, ivar, 0, 1, pnrm, 0.0d0)
116 ENDIF
117 IF (pnrm .LE. stptol) THEN
118 iret = 1
119 RETURN
120 ENDIF
121 GO TO 10
122 ENDIF
123 ENDIF
124C
125 slpi = (-two*f1nrm)*ratio
126 rlmin = stptol/pnrm
127 IF (lsoff .EQ. 0 .AND. kprin .GE. 2) THEN
128 msg = '------ MIN. LAMBDA = (R1)'
129 CALL xerrwd(msg, 25, 903, 0, 0, 0, 0, 1, rlmin, 0.0d0)
130 ENDIF
131C-----------------------------------------------------------------------
132C Begin iteration to find RL value satisfying alpha-condition.
133C If RL becomes less than RLMIN, then terminate with IRET = 1.
134C-----------------------------------------------------------------------
135 100 CONTINUE
136 CALL dyypnw (neq,y,yprime,cj,rl,p,icopt,id,ynew,ypnew)
137 CALL dfnrmd (neq, ynew, t, ypnew, r, cj, wt, res, ires,
138 * fnrmp, wm, iwm, rpar, ipar)
139 iwm(lnre) = iwm(lnre) + 1
140 IF (ires .NE. 0) THEN
141 iret = 2
142 RETURN
143 ENDIF
144 IF (lsoff .EQ. 1) GO TO 150
145C
146 f1nrmp = fnrmp*fnrmp/two
147 IF (kprin .GE. 2) THEN
148 msg = '------ LAMBDA = (R1)'
149 CALL xerrwd(msg, 20, 904, 0, 0, 0, 0, 1, rl, 0.0d0)
150 msg = '------ NORM(F1) = (R1), NORM(F1NEW) = (R2)'
151 CALL xerrwd(msg, 43, 905, 0, 0, 0, 0, 2, f1nrm, f1nrmp)
152 ENDIF
153 IF (f1nrmp .GT. f1nrm + alpha*slpi*rl) GO TO 200
154C-----------------------------------------------------------------------
155C Alpha-condition is satisfied, or linesearch is turned off.
156C Copy YNEW,YPNEW to Y,YPRIME and return.
157C-----------------------------------------------------------------------
158 150 iret = 0
159 CALL dcopy (neq, ynew, 1, y, 1)
160 CALL dcopy (neq, ypnew, 1, yprime, 1)
161 fnrm = fnrmp
162 IF (kprin .GE. 1) THEN
163 msg = '------ LEAVING ROUTINE DLINSD, FNRM = (R1)'
164 CALL xerrwd(msg, 42, 906, 0, 0, 0, 0, 1, fnrm, 0.0d0)
165 ENDIF
166 RETURN
167C-----------------------------------------------------------------------
168C Alpha-condition not satisfied. Perform backtrack to compute new RL
169C value. If no satisfactory YNEW,YPNEW can be found sufficiently
170C distinct from Y,YPRIME, then return IRET = 1.
171C-----------------------------------------------------------------------
172 200 CONTINUE
173 IF (rl .LT. rlmin) THEN
174 iret = 1
175 RETURN
176 ENDIF
177C
178 rl = rl/two
179 GO TO 100
180C
181C----------------------- END OF SUBROUTINE DLINSD ----------------------
182 END
subroutine dcnstr(neq, y, ynew, icnstr, tau, rlx, iret, ivar)
Definition dcnstr.f:6
subroutine dfnrmd(neq, y, t, yprime, r, cj, wt, res, ires, fnorm, wm, iwm, rpar, ipar)
Definition dfnrmd.f:7
subroutine dlinsd(neq, y, t, yprime, cj, p, pnrm, wt, lsoff, stptol, iret, res, ires, wm, iwm, fnrm, icopt, id, r, ynew, ypnew, icnflg, icnstr, rlx, rpar, ipar)
Definition dlinsd.f:9
subroutine dyypnw(neq, y, yprime, cj, rl, p, icopt, id, ynew, ypnew)
Definition dyypnw.f:7
subroutine xerrwd(msg, nmes, nerr, level, ni, i1, i2, nr, r1, r2)
Definition xerrwd.f:4