LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
ztrsv.f
Go to the documentation of this file.
1 *> \brief \b ZTRSV
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 ZTRSV(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 * COMPLEX*16 A(LDA,*),X(*)
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> ZTRSV solves one of the systems of equations
28 *>
29 *> A*x = b, or A**T*x = b, or A**H*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**H*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 COMPLEX*16 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 COMPLEX*16 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 *> \endverbatim
122 *
123 * Authors:
124 * ========
125 *
126 *> \author Univ. of Tennessee
127 *> \author Univ. of California Berkeley
128 *> \author Univ. of Colorado Denver
129 *> \author NAG Ltd.
130 *
131 *> \date November 2011
132 *
133 *> \ingroup complex16_blas_level2
134 *
135 *> \par Further Details:
136 * =====================
137 *>
138 *> \verbatim
139 *>
140 *> Level 2 Blas routine.
141 *>
142 *> -- Written on 22-October-1986.
143 *> Jack Dongarra, Argonne National Lab.
144 *> Jeremy Du Croz, Nag Central Office.
145 *> Sven Hammarling, Nag Central Office.
146 *> Richard Hanson, Sandia National Labs.
147 *> \endverbatim
148 *>
149 * =====================================================================
150  SUBROUTINE ztrsv(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
151 *
152 * -- Reference BLAS level2 routine (version 3.4.0) --
153 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
154 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155 * November 2011
156 *
157 * .. Scalar Arguments ..
158  INTEGER INCX,LDA,N
159  CHARACTER DIAG,TRANS,UPLO
160 * ..
161 * .. Array Arguments ..
162  COMPLEX*16 A(lda,*),X(*)
163 * ..
164 *
165 * =====================================================================
166 *
167 * .. Parameters ..
168  COMPLEX*16 ZERO
169  parameter(zero= (0.0d+0,0.0d+0))
170 * ..
171 * .. Local Scalars ..
172  COMPLEX*16 TEMP
173  INTEGER I,INFO,IX,J,JX,KX
174  LOGICAL NOCONJ,NOUNIT
175 * ..
176 * .. External Functions ..
177  LOGICAL LSAME
178  EXTERNAL lsame
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL xerbla
182 * ..
183 * .. Intrinsic Functions ..
184  INTRINSIC dconjg,max
185 * ..
186 *
187 * Test the input parameters.
188 *
189  info = 0
190  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
191  info = 1
192  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
193  + .NOT.lsame(trans,'C')) THEN
194  info = 2
195  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
196  info = 3
197  ELSE IF (n.LT.0) THEN
198  info = 4
199  ELSE IF (lda.LT.max(1,n)) THEN
200  info = 6
201  ELSE IF (incx.EQ.0) THEN
202  info = 8
203  END IF
204  IF (info.NE.0) THEN
205  CALL xerbla('ZTRSV ',info)
206  RETURN
207  END IF
208 *
209 * Quick return if possible.
210 *
211  IF (n.EQ.0) RETURN
212 *
213  noconj = lsame(trans,'T')
214  nounit = lsame(diag,'N')
215 *
216 * Set up the start point in X if the increment is not unity. This
217 * will be ( N - 1 )*INCX too small for descending loops.
218 *
219  IF (incx.LE.0) THEN
220  kx = 1 - (n-1)*incx
221  ELSE IF (incx.NE.1) THEN
222  kx = 1
223  END IF
224 *
225 * Start the operations. In this version the elements of A are
226 * accessed sequentially with one pass through A.
227 *
228  IF (lsame(trans,'N')) THEN
229 *
230 * Form x := inv( A )*x.
231 *
232  IF (lsame(uplo,'U')) THEN
233  IF (incx.EQ.1) THEN
234  DO 20 j = n,1,-1
235  IF (x(j).NE.zero) THEN
236  IF (nounit) x(j) = x(j)/a(j,j)
237  temp = x(j)
238  DO 10 i = j - 1,1,-1
239  x(i) = x(i) - temp*a(i,j)
240  10 CONTINUE
241  END IF
242  20 CONTINUE
243  ELSE
244  jx = kx + (n-1)*incx
245  DO 40 j = n,1,-1
246  IF (x(jx).NE.zero) THEN
247  IF (nounit) x(jx) = x(jx)/a(j,j)
248  temp = x(jx)
249  ix = jx
250  DO 30 i = j - 1,1,-1
251  ix = ix - incx
252  x(ix) = x(ix) - temp*a(i,j)
253  30 CONTINUE
254  END IF
255  jx = jx - incx
256  40 CONTINUE
257  END IF
258  ELSE
259  IF (incx.EQ.1) THEN
260  DO 60 j = 1,n
261  IF (x(j).NE.zero) THEN
262  IF (nounit) x(j) = x(j)/a(j,j)
263  temp = x(j)
264  DO 50 i = j + 1,n
265  x(i) = x(i) - temp*a(i,j)
266  50 CONTINUE
267  END IF
268  60 CONTINUE
269  ELSE
270  jx = kx
271  DO 80 j = 1,n
272  IF (x(jx).NE.zero) THEN
273  IF (nounit) x(jx) = x(jx)/a(j,j)
274  temp = x(jx)
275  ix = jx
276  DO 70 i = j + 1,n
277  ix = ix + incx
278  x(ix) = x(ix) - temp*a(i,j)
279  70 CONTINUE
280  END IF
281  jx = jx + incx
282  80 CONTINUE
283  END IF
284  END IF
285  ELSE
286 *
287 * Form x := inv( A**T )*x or x := inv( A**H )*x.
288 *
289  IF (lsame(uplo,'U')) THEN
290  IF (incx.EQ.1) THEN
291  DO 110 j = 1,n
292  temp = x(j)
293  IF (noconj) THEN
294  DO 90 i = 1,j - 1
295  temp = temp - a(i,j)*x(i)
296  90 CONTINUE
297  IF (nounit) temp = temp/a(j,j)
298  ELSE
299  DO 100 i = 1,j - 1
300  temp = temp - dconjg(a(i,j))*x(i)
301  100 CONTINUE
302  IF (nounit) temp = temp/dconjg(a(j,j))
303  END IF
304  x(j) = temp
305  110 CONTINUE
306  ELSE
307  jx = kx
308  DO 140 j = 1,n
309  ix = kx
310  temp = x(jx)
311  IF (noconj) THEN
312  DO 120 i = 1,j - 1
313  temp = temp - a(i,j)*x(ix)
314  ix = ix + incx
315  120 CONTINUE
316  IF (nounit) temp = temp/a(j,j)
317  ELSE
318  DO 130 i = 1,j - 1
319  temp = temp - dconjg(a(i,j))*x(ix)
320  ix = ix + incx
321  130 CONTINUE
322  IF (nounit) temp = temp/dconjg(a(j,j))
323  END IF
324  x(jx) = temp
325  jx = jx + incx
326  140 CONTINUE
327  END IF
328  ELSE
329  IF (incx.EQ.1) THEN
330  DO 170 j = n,1,-1
331  temp = x(j)
332  IF (noconj) THEN
333  DO 150 i = n,j + 1,-1
334  temp = temp - a(i,j)*x(i)
335  150 CONTINUE
336  IF (nounit) temp = temp/a(j,j)
337  ELSE
338  DO 160 i = n,j + 1,-1
339  temp = temp - dconjg(a(i,j))*x(i)
340  160 CONTINUE
341  IF (nounit) temp = temp/dconjg(a(j,j))
342  END IF
343  x(j) = temp
344  170 CONTINUE
345  ELSE
346  kx = kx + (n-1)*incx
347  jx = kx
348  DO 200 j = n,1,-1
349  ix = kx
350  temp = x(jx)
351  IF (noconj) THEN
352  DO 180 i = n,j + 1,-1
353  temp = temp - a(i,j)*x(ix)
354  ix = ix - incx
355  180 CONTINUE
356  IF (nounit) temp = temp/a(j,j)
357  ELSE
358  DO 190 i = n,j + 1,-1
359  temp = temp - dconjg(a(i,j))*x(ix)
360  ix = ix - incx
361  190 CONTINUE
362  IF (nounit) temp = temp/dconjg(a(j,j))
363  END IF
364  x(jx) = temp
365  jx = jx - incx
366  200 CONTINUE
367  END IF
368  END IF
369  END IF
370 *
371  RETURN
372 *
373 * End of ZTRSV .
374 *
375  END
subroutine ztrsv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
ZTRSV
Definition: ztrsv.f:151
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62