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