LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ctbsv.f
Go to the documentation of this file.
1 *> \brief \b CTBSV
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 CTBSV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
12 *
13 * .. Scalar Arguments ..
14 * INTEGER INCX,K,LDA,N
15 * CHARACTER DIAG,TRANS,UPLO
16 * ..
17 * .. Array Arguments ..
18 * COMPLEX A(LDA,*),X(*)
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> CTBSV 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 band matrix, with ( k + 1 )
33 *> diagonals.
34 *>
35 *> No test for singularity or near-singularity is included in this
36 *> routine. Such tests must be performed before calling this routine.
37 *> \endverbatim
38 *
39 * Arguments:
40 * ==========
41 *
42 *> \param[in] UPLO
43 *> \verbatim
44 *> UPLO is CHARACTER*1
45 *> On entry, UPLO specifies whether the matrix is an upper or
46 *> lower triangular matrix as follows:
47 *>
48 *> UPLO = 'U' or 'u' A is an upper triangular matrix.
49 *>
50 *> UPLO = 'L' or 'l' A is a lower triangular matrix.
51 *> \endverbatim
52 *>
53 *> \param[in] TRANS
54 *> \verbatim
55 *> TRANS is CHARACTER*1
56 *> On entry, TRANS specifies the equations to be solved as
57 *> follows:
58 *>
59 *> TRANS = 'N' or 'n' A*x = b.
60 *>
61 *> TRANS = 'T' or 't' A**T*x = b.
62 *>
63 *> TRANS = 'C' or 'c' A**H*x = b.
64 *> \endverbatim
65 *>
66 *> \param[in] DIAG
67 *> \verbatim
68 *> DIAG is CHARACTER*1
69 *> On entry, DIAG specifies whether or not A is unit
70 *> triangular as follows:
71 *>
72 *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
73 *>
74 *> DIAG = 'N' or 'n' A is not assumed to be unit
75 *> triangular.
76 *> \endverbatim
77 *>
78 *> \param[in] N
79 *> \verbatim
80 *> N is INTEGER
81 *> On entry, N specifies the order of the matrix A.
82 *> N must be at least zero.
83 *> \endverbatim
84 *>
85 *> \param[in] K
86 *> \verbatim
87 *> K is INTEGER
88 *> On entry with UPLO = 'U' or 'u', K specifies the number of
89 *> super-diagonals of the matrix A.
90 *> On entry with UPLO = 'L' or 'l', K specifies the number of
91 *> sub-diagonals of the matrix A.
92 *> K must satisfy 0 .le. K.
93 *> \endverbatim
94 *>
95 *> \param[in] A
96 *> \verbatim
97 *> A is COMPLEX array of DIMENSION ( LDA, n ).
98 *> Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
99 *> by n part of the array A must contain the upper triangular
100 *> band part of the matrix of coefficients, supplied column by
101 *> column, with the leading diagonal of the matrix in row
102 *> ( k + 1 ) of the array, the first super-diagonal starting at
103 *> position 2 in row k, and so on. The top left k by k triangle
104 *> of the array A is not referenced.
105 *> The following program segment will transfer an upper
106 *> triangular band matrix from conventional full matrix storage
107 *> to band storage:
108 *>
109 *> DO 20, J = 1, N
110 *> M = K + 1 - J
111 *> DO 10, I = MAX( 1, J - K ), J
112 *> A( M + I, J ) = matrix( I, J )
113 *> 10 CONTINUE
114 *> 20 CONTINUE
115 *>
116 *> Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
117 *> by n part of the array A must contain the lower triangular
118 *> band part of the matrix of coefficients, supplied column by
119 *> column, with the leading diagonal of the matrix in row 1 of
120 *> the array, the first sub-diagonal starting at position 1 in
121 *> row 2, and so on. The bottom right k by k triangle of the
122 *> array A is not referenced.
123 *> The following program segment will transfer a lower
124 *> triangular band matrix from conventional full matrix storage
125 *> to band storage:
126 *>
127 *> DO 20, J = 1, N
128 *> M = 1 - J
129 *> DO 10, I = J, MIN( N, J + K )
130 *> A( M + I, J ) = matrix( I, J )
131 *> 10 CONTINUE
132 *> 20 CONTINUE
133 *>
134 *> Note that when DIAG = 'U' or 'u' the elements of the array A
135 *> corresponding to the diagonal elements of the matrix are not
136 *> referenced, but are assumed to be unity.
137 *> \endverbatim
138 *>
139 *> \param[in] LDA
140 *> \verbatim
141 *> LDA is INTEGER
142 *> On entry, LDA specifies the first dimension of A as declared
143 *> in the calling (sub) program. LDA must be at least
144 *> ( k + 1 ).
145 *> \endverbatim
146 *>
147 *> \param[in,out] X
148 *> \verbatim
149 *> X is COMPLEX array of dimension at least
150 *> ( 1 + ( n - 1 )*abs( INCX ) ).
151 *> Before entry, the incremented array X must contain the n
152 *> element right-hand side vector b. On exit, X is overwritten
153 *> with the solution vector x.
154 *> \endverbatim
155 *>
156 *> \param[in] INCX
157 *> \verbatim
158 *> INCX is INTEGER
159 *> On entry, INCX specifies the increment for the elements of
160 *> X. INCX must not be zero.
161 *> \endverbatim
162 *
163 * Authors:
164 * ========
165 *
166 *> \author Univ. of Tennessee
167 *> \author Univ. of California Berkeley
168 *> \author Univ. of Colorado Denver
169 *> \author NAG Ltd.
170 *
171 *> \date November 2011
172 *
173 *> \ingroup complex_blas_level2
174 *
175 *> \par Further Details:
176 * =====================
177 *>
178 *> \verbatim
179 *>
180 *> Level 2 Blas routine.
181 *>
182 *> -- Written on 22-October-1986.
183 *> Jack Dongarra, Argonne National Lab.
184 *> Jeremy Du Croz, Nag Central Office.
185 *> Sven Hammarling, Nag Central Office.
186 *> Richard Hanson, Sandia National Labs.
187 *> \endverbatim
188 *>
189 * =====================================================================
190  SUBROUTINE ctbsv(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
191 *
192 * -- Reference BLAS level2 routine (version 3.4.0) --
193 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
194 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
195 * November 2011
196 *
197 * .. Scalar Arguments ..
198  INTEGER incx,k,lda,n
199  CHARACTER diag,trans,uplo
200 * ..
201 * .. Array Arguments ..
202  COMPLEX a(lda,*),x(*)
203 * ..
204 *
205 * =====================================================================
206 *
207 * .. Parameters ..
208  COMPLEX zero
209  parameter(zero= (0.0e+0,0.0e+0))
210 * ..
211 * .. Local Scalars ..
212  COMPLEX temp
213  INTEGER i,info,ix,j,jx,kplus1,kx,l
214  LOGICAL noconj,nounit
215 * ..
216 * .. External Functions ..
217  LOGICAL lsame
218  EXTERNAL lsame
219 * ..
220 * .. External Subroutines ..
221  EXTERNAL xerbla
222 * ..
223 * .. Intrinsic Functions ..
224  INTRINSIC conjg,max,min
225 * ..
226 *
227 * Test the input parameters.
228 *
229  info = 0
230  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
231  info = 1
232  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
233  + .NOT.lsame(trans,'C')) THEN
234  info = 2
235  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
236  info = 3
237  ELSE IF (n.LT.0) THEN
238  info = 4
239  ELSE IF (k.LT.0) THEN
240  info = 5
241  ELSE IF (lda.LT. (k+1)) THEN
242  info = 7
243  ELSE IF (incx.EQ.0) THEN
244  info = 9
245  END IF
246  IF (info.NE.0) THEN
247  CALL xerbla('CTBSV ',info)
248  return
249  END IF
250 *
251 * Quick return if possible.
252 *
253  IF (n.EQ.0) return
254 *
255  noconj = lsame(trans,'T')
256  nounit = lsame(diag,'N')
257 *
258 * Set up the start point in X if the increment is not unity. This
259 * will be ( N - 1 )*INCX too small for descending loops.
260 *
261  IF (incx.LE.0) THEN
262  kx = 1 - (n-1)*incx
263  ELSE IF (incx.NE.1) THEN
264  kx = 1
265  END IF
266 *
267 * Start the operations. In this version the elements of A are
268 * accessed by sequentially with one pass through A.
269 *
270  IF (lsame(trans,'N')) THEN
271 *
272 * Form x := inv( A )*x.
273 *
274  IF (lsame(uplo,'U')) THEN
275  kplus1 = k + 1
276  IF (incx.EQ.1) THEN
277  DO 20 j = n,1,-1
278  IF (x(j).NE.zero) THEN
279  l = kplus1 - j
280  IF (nounit) x(j) = x(j)/a(kplus1,j)
281  temp = x(j)
282  DO 10 i = j - 1,max(1,j-k),-1
283  x(i) = x(i) - temp*a(l+i,j)
284  10 continue
285  END IF
286  20 continue
287  ELSE
288  kx = kx + (n-1)*incx
289  jx = kx
290  DO 40 j = n,1,-1
291  kx = kx - incx
292  IF (x(jx).NE.zero) THEN
293  ix = kx
294  l = kplus1 - j
295  IF (nounit) x(jx) = x(jx)/a(kplus1,j)
296  temp = x(jx)
297  DO 30 i = j - 1,max(1,j-k),-1
298  x(ix) = x(ix) - temp*a(l+i,j)
299  ix = ix - incx
300  30 continue
301  END IF
302  jx = jx - incx
303  40 continue
304  END IF
305  ELSE
306  IF (incx.EQ.1) THEN
307  DO 60 j = 1,n
308  IF (x(j).NE.zero) THEN
309  l = 1 - j
310  IF (nounit) x(j) = x(j)/a(1,j)
311  temp = x(j)
312  DO 50 i = j + 1,min(n,j+k)
313  x(i) = x(i) - temp*a(l+i,j)
314  50 continue
315  END IF
316  60 continue
317  ELSE
318  jx = kx
319  DO 80 j = 1,n
320  kx = kx + incx
321  IF (x(jx).NE.zero) THEN
322  ix = kx
323  l = 1 - j
324  IF (nounit) x(jx) = x(jx)/a(1,j)
325  temp = x(jx)
326  DO 70 i = j + 1,min(n,j+k)
327  x(ix) = x(ix) - temp*a(l+i,j)
328  ix = ix + incx
329  70 continue
330  END IF
331  jx = jx + incx
332  80 continue
333  END IF
334  END IF
335  ELSE
336 *
337 * Form x := inv( A**T )*x or x := inv( A**H )*x.
338 *
339  IF (lsame(uplo,'U')) THEN
340  kplus1 = k + 1
341  IF (incx.EQ.1) THEN
342  DO 110 j = 1,n
343  temp = x(j)
344  l = kplus1 - j
345  IF (noconj) THEN
346  DO 90 i = max(1,j-k),j - 1
347  temp = temp - a(l+i,j)*x(i)
348  90 continue
349  IF (nounit) temp = temp/a(kplus1,j)
350  ELSE
351  DO 100 i = max(1,j-k),j - 1
352  temp = temp - conjg(a(l+i,j))*x(i)
353  100 continue
354  IF (nounit) temp = temp/conjg(a(kplus1,j))
355  END IF
356  x(j) = temp
357  110 continue
358  ELSE
359  jx = kx
360  DO 140 j = 1,n
361  temp = x(jx)
362  ix = kx
363  l = kplus1 - j
364  IF (noconj) THEN
365  DO 120 i = max(1,j-k),j - 1
366  temp = temp - a(l+i,j)*x(ix)
367  ix = ix + incx
368  120 continue
369  IF (nounit) temp = temp/a(kplus1,j)
370  ELSE
371  DO 130 i = max(1,j-k),j - 1
372  temp = temp - conjg(a(l+i,j))*x(ix)
373  ix = ix + incx
374  130 continue
375  IF (nounit) temp = temp/conjg(a(kplus1,j))
376  END IF
377  x(jx) = temp
378  jx = jx + incx
379  IF (j.GT.k) kx = kx + incx
380  140 continue
381  END IF
382  ELSE
383  IF (incx.EQ.1) THEN
384  DO 170 j = n,1,-1
385  temp = x(j)
386  l = 1 - j
387  IF (noconj) THEN
388  DO 150 i = min(n,j+k),j + 1,-1
389  temp = temp - a(l+i,j)*x(i)
390  150 continue
391  IF (nounit) temp = temp/a(1,j)
392  ELSE
393  DO 160 i = min(n,j+k),j + 1,-1
394  temp = temp - conjg(a(l+i,j))*x(i)
395  160 continue
396  IF (nounit) temp = temp/conjg(a(1,j))
397  END IF
398  x(j) = temp
399  170 continue
400  ELSE
401  kx = kx + (n-1)*incx
402  jx = kx
403  DO 200 j = n,1,-1
404  temp = x(jx)
405  ix = kx
406  l = 1 - j
407  IF (noconj) THEN
408  DO 180 i = min(n,j+k),j + 1,-1
409  temp = temp - a(l+i,j)*x(ix)
410  ix = ix - incx
411  180 continue
412  IF (nounit) temp = temp/a(1,j)
413  ELSE
414  DO 190 i = min(n,j+k),j + 1,-1
415  temp = temp - conjg(a(l+i,j))*x(ix)
416  ix = ix - incx
417  190 continue
418  IF (nounit) temp = temp/conjg(a(1,j))
419  END IF
420  x(jx) = temp
421  jx = jx - incx
422  IF ((n-j).GE.k) kx = kx - incx
423  200 continue
424  END IF
425  END IF
426  END IF
427 *
428  return
429 *
430 * End of CTBSV .
431 *
432  END