LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
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 of 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 of 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 *> \date November 2011
140 *
141 *> \ingroup double_blas_level1
142 *
143 * =====================================================================
144  SUBROUTINE dtrsv(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
145 *
146 * -- Reference BLAS level1 routine (version 3.4.0) --
147 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
148 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149 * November 2011
150 *
151 * .. Scalar Arguments ..
152  INTEGER incx,lda,n
153  CHARACTER diag,trans,uplo
154 * ..
155 * .. Array Arguments ..
156  DOUBLE PRECISION a(lda,*),x(*)
157 * ..
158 *
159 * =====================================================================
160 *
161 * .. Parameters ..
162  DOUBLE PRECISION zero
163  parameter(zero=0.0d+0)
164 * ..
165 * .. Local Scalars ..
166  DOUBLE PRECISION temp
167  INTEGER i,info,ix,j,jx,kx
168  LOGICAL nounit
169 * ..
170 * .. External Functions ..
171  LOGICAL lsame
172  EXTERNAL lsame
173 * ..
174 * .. External Subroutines ..
175  EXTERNAL xerbla
176 * ..
177 * .. Intrinsic Functions ..
178  INTRINSIC max
179 * ..
180 *
181 * Test the input parameters.
182 *
183  info = 0
184  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
185  info = 1
186  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
187  + .NOT.lsame(trans,'C')) THEN
188  info = 2
189  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
190  info = 3
191  ELSE IF (n.LT.0) THEN
192  info = 4
193  ELSE IF (lda.LT.max(1,n)) THEN
194  info = 6
195  ELSE IF (incx.EQ.0) THEN
196  info = 8
197  END IF
198  IF (info.NE.0) THEN
199  CALL xerbla('DTRSV ',info)
200  return
201  END IF
202 *
203 * Quick return if possible.
204 *
205  IF (n.EQ.0) return
206 *
207  nounit = lsame(diag,'N')
208 *
209 * Set up the start point in X if the increment is not unity. This
210 * will be ( N - 1 )*INCX too small for descending loops.
211 *
212  IF (incx.LE.0) THEN
213  kx = 1 - (n-1)*incx
214  ELSE IF (incx.NE.1) THEN
215  kx = 1
216  END IF
217 *
218 * Start the operations. In this version the elements of A are
219 * accessed sequentially with one pass through A.
220 *
221  IF (lsame(trans,'N')) THEN
222 *
223 * Form x := inv( A )*x.
224 *
225  IF (lsame(uplo,'U')) THEN
226  IF (incx.EQ.1) THEN
227  DO 20 j = n,1,-1
228  IF (x(j).NE.zero) THEN
229  IF (nounit) x(j) = x(j)/a(j,j)
230  temp = x(j)
231  DO 10 i = j - 1,1,-1
232  x(i) = x(i) - temp*a(i,j)
233  10 continue
234  END IF
235  20 continue
236  ELSE
237  jx = kx + (n-1)*incx
238  DO 40 j = n,1,-1
239  IF (x(jx).NE.zero) THEN
240  IF (nounit) x(jx) = x(jx)/a(j,j)
241  temp = x(jx)
242  ix = jx
243  DO 30 i = j - 1,1,-1
244  ix = ix - incx
245  x(ix) = x(ix) - temp*a(i,j)
246  30 continue
247  END IF
248  jx = jx - incx
249  40 continue
250  END IF
251  ELSE
252  IF (incx.EQ.1) THEN
253  DO 60 j = 1,n
254  IF (x(j).NE.zero) THEN
255  IF (nounit) x(j) = x(j)/a(j,j)
256  temp = x(j)
257  DO 50 i = j + 1,n
258  x(i) = x(i) - temp*a(i,j)
259  50 continue
260  END IF
261  60 continue
262  ELSE
263  jx = kx
264  DO 80 j = 1,n
265  IF (x(jx).NE.zero) THEN
266  IF (nounit) x(jx) = x(jx)/a(j,j)
267  temp = x(jx)
268  ix = jx
269  DO 70 i = j + 1,n
270  ix = ix + incx
271  x(ix) = x(ix) - temp*a(i,j)
272  70 continue
273  END IF
274  jx = jx + incx
275  80 continue
276  END IF
277  END IF
278  ELSE
279 *
280 * Form x := inv( A**T )*x.
281 *
282  IF (lsame(uplo,'U')) THEN
283  IF (incx.EQ.1) THEN
284  DO 100 j = 1,n
285  temp = x(j)
286  DO 90 i = 1,j - 1
287  temp = temp - a(i,j)*x(i)
288  90 continue
289  IF (nounit) temp = temp/a(j,j)
290  x(j) = temp
291  100 continue
292  ELSE
293  jx = kx
294  DO 120 j = 1,n
295  temp = x(jx)
296  ix = kx
297  DO 110 i = 1,j - 1
298  temp = temp - a(i,j)*x(ix)
299  ix = ix + incx
300  110 continue
301  IF (nounit) temp = temp/a(j,j)
302  x(jx) = temp
303  jx = jx + incx
304  120 continue
305  END IF
306  ELSE
307  IF (incx.EQ.1) THEN
308  DO 140 j = n,1,-1
309  temp = x(j)
310  DO 130 i = n,j + 1,-1
311  temp = temp - a(i,j)*x(i)
312  130 continue
313  IF (nounit) temp = temp/a(j,j)
314  x(j) = temp
315  140 continue
316  ELSE
317  kx = kx + (n-1)*incx
318  jx = kx
319  DO 160 j = n,1,-1
320  temp = x(jx)
321  ix = kx
322  DO 150 i = n,j + 1,-1
323  temp = temp - a(i,j)*x(ix)
324  ix = ix - incx
325  150 continue
326  IF (nounit) temp = temp/a(j,j)
327  x(jx) = temp
328  jx = jx - incx
329  160 continue
330  END IF
331  END IF
332  END IF
333 *
334  return
335 *
336 * End of DTRSV .
337 *
338  END