LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dtrsv.f
Go to the documentation of this file.
1*> \brief \b DTRSV
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE DTRSV(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
12*
13* .. Scalar Arguments ..
14* INTEGER INCX,LDA,N
15* CHARACTER DIAG,TRANS,UPLO
16* ..
17* .. Array Arguments ..
18* DOUBLE PRECISION A(LDA,*),X(*)
19* ..
20*
21*
22*> \par Purpose:
23* =============
24*>
25*> \verbatim
26*>
27*> DTRSV solves one of the systems of equations
28*>
29*> A*x = b, or A**T*x = b,
30*>
31*> where b and x are n element vectors and A is an n by n unit, or
32*> non-unit, upper or lower triangular matrix.
33*>
34*> No test for singularity or near-singularity is included in this
35*> routine. Such tests must be performed before calling this routine.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] UPLO
42*> \verbatim
43*> UPLO is CHARACTER*1
44*> On entry, UPLO specifies whether the matrix is an upper or
45*> lower triangular matrix as follows:
46*>
47*> UPLO = 'U' or 'u' A is an upper triangular matrix.
48*>
49*> UPLO = 'L' or 'l' A is a lower triangular matrix.
50*> \endverbatim
51*>
52*> \param[in] TRANS
53*> \verbatim
54*> TRANS is CHARACTER*1
55*> On entry, TRANS specifies the equations to be solved as
56*> follows:
57*>
58*> TRANS = 'N' or 'n' A*x = b.
59*>
60*> TRANS = 'T' or 't' A**T*x = b.
61*>
62*> TRANS = 'C' or 'c' A**T*x = b.
63*> \endverbatim
64*>
65*> \param[in] DIAG
66*> \verbatim
67*> DIAG is CHARACTER*1
68*> On entry, DIAG specifies whether or not A is unit
69*> triangular as follows:
70*>
71*> DIAG = 'U' or 'u' A is assumed to be unit triangular.
72*>
73*> DIAG = 'N' or 'n' A is not assumed to be unit
74*> triangular.
75*> \endverbatim
76*>
77*> \param[in] N
78*> \verbatim
79*> N is INTEGER
80*> On entry, N specifies the order of the matrix A.
81*> N must be at least zero.
82*> \endverbatim
83*>
84*> \param[in] A
85*> \verbatim
86*> A is DOUBLE PRECISION array, dimension ( LDA, N )
87*> Before entry with UPLO = 'U' or 'u', the leading n by n
88*> upper triangular part of the array A must contain the upper
89*> triangular matrix and the strictly lower triangular part of
90*> A is not referenced.
91*> Before entry with UPLO = 'L' or 'l', the leading n by n
92*> lower triangular part of the array A must contain the lower
93*> triangular matrix and the strictly upper triangular part of
94*> A is not referenced.
95*> Note that when DIAG = 'U' or 'u', the diagonal elements of
96*> A are not referenced either, but are assumed to be unity.
97*> \endverbatim
98*>
99*> \param[in] LDA
100*> \verbatim
101*> LDA is INTEGER
102*> On entry, LDA specifies the first dimension of A as declared
103*> in the calling (sub) program. LDA must be at least
104*> max( 1, n ).
105*> \endverbatim
106*>
107*> \param[in,out] X
108*> \verbatim
109*> X is DOUBLE PRECISION array, dimension at least
110*> ( 1 + ( n - 1 )*abs( INCX ) ).
111*> Before entry, the incremented array X must contain the n
112*> element right-hand side vector b. On exit, X is overwritten
113*> with the solution vector x.
114*> \endverbatim
115*>
116*> \param[in] INCX
117*> \verbatim
118*> INCX is INTEGER
119*> On entry, INCX specifies the increment for the elements of
120*> X. INCX must not be zero.
121*>
122*> Level 2 Blas routine.
123*>
124*> -- Written on 22-October-1986.
125*> Jack Dongarra, Argonne National Lab.
126*> Jeremy Du Croz, Nag Central Office.
127*> Sven Hammarling, Nag Central Office.
128*> Richard Hanson, Sandia National Labs.
129*> \endverbatim
130*
131* Authors:
132* ========
133*
134*> \author Univ. of Tennessee
135*> \author Univ. of California Berkeley
136*> \author Univ. of Colorado Denver
137*> \author NAG Ltd.
138*
139*> \ingroup trsv
140*
141* =====================================================================
142 SUBROUTINE dtrsv(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
143*
144* -- Reference BLAS level2 routine --
145* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
146* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
147*
148* .. Scalar Arguments ..
149 INTEGER INCX,LDA,N
150 CHARACTER DIAG,TRANS,UPLO
151* ..
152* .. Array Arguments ..
153 DOUBLE PRECISION A(LDA,*),X(*)
154* ..
155*
156* =====================================================================
157*
158* .. Parameters ..
159 DOUBLE PRECISION ZERO
160 parameter(zero=0.0d+0)
161* ..
162* .. Local Scalars ..
163 DOUBLE PRECISION TEMP
164 INTEGER I,INFO,IX,J,JX,KX
165 LOGICAL NOUNIT
166* ..
167* .. External Functions ..
168 LOGICAL LSAME
169 EXTERNAL lsame
170* ..
171* .. External Subroutines ..
172 EXTERNAL xerbla
173* ..
174* .. Intrinsic Functions ..
175 INTRINSIC max
176* ..
177*
178* Test the input parameters.
179*
180 info = 0
181 IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
182 info = 1
183 ELSE IF (.NOT.lsame(trans,'N') .AND.
184 + .NOT.lsame(trans,'T') .AND.
185 + .NOT.lsame(trans,'C')) THEN
186 info = 2
187 ELSE IF (.NOT.lsame(diag,'U') .AND.
188 + .NOT.lsame(diag,'N')) THEN
189 info = 3
190 ELSE IF (n.LT.0) THEN
191 info = 4
192 ELSE IF (lda.LT.max(1,n)) THEN
193 info = 6
194 ELSE IF (incx.EQ.0) THEN
195 info = 8
196 END IF
197 IF (info.NE.0) THEN
198 CALL xerbla('DTRSV ',info)
199 RETURN
200 END IF
201*
202* Quick return if possible.
203*
204 IF (n.EQ.0) RETURN
205*
206 nounit = lsame(diag,'N')
207*
208* Set up the start point in X if the increment is not unity. This
209* will be ( N - 1 )*INCX too small for descending loops.
210*
211 IF (incx.LE.0) THEN
212 kx = 1 - (n-1)*incx
213 ELSE IF (incx.NE.1) THEN
214 kx = 1
215 END IF
216*
217* Start the operations. In this version the elements of A are
218* accessed sequentially with one pass through A.
219*
220 IF (lsame(trans,'N')) THEN
221*
222* Form x := inv( A )*x.
223*
224 IF (lsame(uplo,'U')) THEN
225 IF (incx.EQ.1) THEN
226 DO 20 j = n,1,-1
227 IF (x(j).NE.zero) THEN
228 IF (nounit) x(j) = x(j)/a(j,j)
229 temp = x(j)
230 DO 10 i = j - 1,1,-1
231 x(i) = x(i) - temp*a(i,j)
232 10 CONTINUE
233 END IF
234 20 CONTINUE
235 ELSE
236 jx = kx + (n-1)*incx
237 DO 40 j = n,1,-1
238 IF (x(jx).NE.zero) THEN
239 IF (nounit) x(jx) = x(jx)/a(j,j)
240 temp = x(jx)
241 ix = jx
242 DO 30 i = j - 1,1,-1
243 ix = ix - incx
244 x(ix) = x(ix) - temp*a(i,j)
245 30 CONTINUE
246 END IF
247 jx = jx - incx
248 40 CONTINUE
249 END IF
250 ELSE
251 IF (incx.EQ.1) THEN
252 DO 60 j = 1,n
253 IF (x(j).NE.zero) THEN
254 IF (nounit) x(j) = x(j)/a(j,j)
255 temp = x(j)
256 DO 50 i = j + 1,n
257 x(i) = x(i) - temp*a(i,j)
258 50 CONTINUE
259 END IF
260 60 CONTINUE
261 ELSE
262 jx = kx
263 DO 80 j = 1,n
264 IF (x(jx).NE.zero) THEN
265 IF (nounit) x(jx) = x(jx)/a(j,j)
266 temp = x(jx)
267 ix = jx
268 DO 70 i = j + 1,n
269 ix = ix + incx
270 x(ix) = x(ix) - temp*a(i,j)
271 70 CONTINUE
272 END IF
273 jx = jx + incx
274 80 CONTINUE
275 END IF
276 END IF
277 ELSE
278*
279* Form x := inv( A**T )*x.
280*
281 IF (lsame(uplo,'U')) THEN
282 IF (incx.EQ.1) THEN
283 DO 100 j = 1,n
284 temp = x(j)
285 DO 90 i = 1,j - 1
286 temp = temp - a(i,j)*x(i)
287 90 CONTINUE
288 IF (nounit) temp = temp/a(j,j)
289 x(j) = temp
290 100 CONTINUE
291 ELSE
292 jx = kx
293 DO 120 j = 1,n
294 temp = x(jx)
295 ix = kx
296 DO 110 i = 1,j - 1
297 temp = temp - a(i,j)*x(ix)
298 ix = ix + incx
299 110 CONTINUE
300 IF (nounit) temp = temp/a(j,j)
301 x(jx) = temp
302 jx = jx + incx
303 120 CONTINUE
304 END IF
305 ELSE
306 IF (incx.EQ.1) THEN
307 DO 140 j = n,1,-1
308 temp = x(j)
309 DO 130 i = n,j + 1,-1
310 temp = temp - a(i,j)*x(i)
311 130 CONTINUE
312 IF (nounit) temp = temp/a(j,j)
313 x(j) = temp
314 140 CONTINUE
315 ELSE
316 kx = kx + (n-1)*incx
317 jx = kx
318 DO 160 j = n,1,-1
319 temp = x(jx)
320 ix = kx
321 DO 150 i = n,j + 1,-1
322 temp = temp - a(i,j)*x(ix)
323 ix = ix - incx
324 150 CONTINUE
325 IF (nounit) temp = temp/a(j,j)
326 x(jx) = temp
327 jx = jx - incx
328 160 CONTINUE
329 END IF
330 END IF
331 END IF
332*
333 RETURN
334*
335* End of DTRSV
336*
337 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dtrsv(uplo, trans, diag, n, a, lda, x, incx)
DTRSV
Definition dtrsv.f:143