LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine csbmv ( character  UPLO,
integer  N,
integer  K,
complex  ALPHA,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( * )  X,
integer  INCX,
complex  BETA,
complex, dimension( * )  Y,
integer  INCY 
)

CSBMV

Purpose:
 CSBMV  performs the matrix-vector  operation

    y := alpha*A*x + beta*y,

 where alpha and beta are scalars, x and y are n element vectors and
 A is an n by n symmetric band matrix, with k super-diagonals.
  UPLO   - CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the band matrix A is being supplied as
           follows:

              UPLO = 'U' or 'u'   The upper triangular part of A is
                                  being supplied.

              UPLO = 'L' or 'l'   The lower triangular part of A is
                                  being supplied.

           Unchanged on exit.

  N      - INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
           Unchanged on exit.

  K      - INTEGER
           On entry, K specifies the number of super-diagonals of the
           matrix A. K must satisfy  0 .le. K.
           Unchanged on exit.

  ALPHA  - COMPLEX
           On entry, ALPHA specifies the scalar alpha.
           Unchanged on exit.

  A      - COMPLEX array, dimension( LDA, N )
           Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
           by n part of the array A must contain the upper triangular
           band part of the symmetric matrix, supplied column by
           column, with the leading diagonal of the matrix in row
           ( k + 1 ) of the array, the first super-diagonal starting at
           position 2 in row k, and so on. The top left k by k triangle
           of the array A is not referenced.
           The following program segment will transfer the upper
           triangular part of a symmetric band matrix from conventional
           full matrix storage to band storage:

                 DO 20, J = 1, N
                    M = K + 1 - J
                    DO 10, I = MAX( 1, J - K ), J
                       A( M + I, J ) = matrix( I, J )
              10    CONTINUE
              20 CONTINUE

           Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
           by n part of the array A must contain the lower triangular
           band part of the symmetric matrix, supplied column by
           column, with the leading diagonal of the matrix in row 1 of
           the array, the first sub-diagonal starting at position 1 in
           row 2, and so on. The bottom right k by k triangle of the
           array A is not referenced.
           The following program segment will transfer the lower
           triangular part of a symmetric band matrix from conventional
           full matrix storage to band storage:

                 DO 20, J = 1, N
                    M = 1 - J
                    DO 10, I = J, MIN( N, J + K )
                       A( M + I, J ) = matrix( I, J )
              10    CONTINUE
              20 CONTINUE

           Unchanged on exit.

  LDA    - INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           ( k + 1 ).
           Unchanged on exit.

  X      - COMPLEX array, dimension at least
           ( 1 + ( N - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the
           vector x.
           Unchanged on exit.

  INCX   - INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
           Unchanged on exit.

  BETA   - COMPLEX
           On entry, BETA specifies the scalar beta.
           Unchanged on exit.

  Y      - COMPLEX array, dimension at least
           ( 1 + ( N - 1 )*abs( INCY ) ).
           Before entry, the incremented array Y must contain the
           vector y. On exit, Y is overwritten by the updated vector y.

  INCY   - INTEGER
           On entry, INCY specifies the increment for the elements of
           Y. INCY must not be zero.
           Unchanged on exit.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 154 of file csbmv.f.

154 *
155 * -- LAPACK test routine (version 3.4.0) --
156 * -- LAPACK is a software package provided by Univ. of Tennessee, --
157 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
158 * November 2011
159 *
160 * .. Scalar Arguments ..
161  CHARACTER uplo
162  INTEGER incx, incy, k, lda, n
163  COMPLEX alpha, beta
164 * ..
165 * .. Array Arguments ..
166  COMPLEX a( lda, * ), x( * ), y( * )
167 * ..
168 *
169 * =====================================================================
170 *
171 * .. Parameters ..
172  COMPLEX one
173  parameter ( one = ( 1.0e+0, 0.0e+0 ) )
174  COMPLEX zero
175  parameter ( zero = ( 0.0e+0, 0.0e+0 ) )
176 * ..
177 * .. Local Scalars ..
178  INTEGER i, info, ix, iy, j, jx, jy, kplus1, kx, ky, l
179  COMPLEX temp1, temp2
180 * ..
181 * .. External Functions ..
182  LOGICAL lsame
183  EXTERNAL lsame
184 * ..
185 * .. External Subroutines ..
186  EXTERNAL xerbla
187 * ..
188 * .. Intrinsic Functions ..
189  INTRINSIC max, min
190 * ..
191 * .. Executable Statements ..
192 *
193 * Test the input parameters.
194 *
195  info = 0
196  IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
197  info = 1
198  ELSE IF( n.LT.0 ) THEN
199  info = 2
200  ELSE IF( k.LT.0 ) THEN
201  info = 3
202  ELSE IF( lda.LT.( k+1 ) ) THEN
203  info = 6
204  ELSE IF( incx.EQ.0 ) THEN
205  info = 8
206  ELSE IF( incy.EQ.0 ) THEN
207  info = 11
208  END IF
209  IF( info.NE.0 ) THEN
210  CALL xerbla( 'CSBMV ', info )
211  RETURN
212  END IF
213 *
214 * Quick return if possible.
215 *
216  IF( ( n.EQ.0 ) .OR. ( ( alpha.EQ.zero ) .AND. ( beta.EQ.one ) ) )
217  $ RETURN
218 *
219 * Set up the start points in X and Y.
220 *
221  IF( incx.GT.0 ) THEN
222  kx = 1
223  ELSE
224  kx = 1 - ( n-1 )*incx
225  END IF
226  IF( incy.GT.0 ) THEN
227  ky = 1
228  ELSE
229  ky = 1 - ( n-1 )*incy
230  END IF
231 *
232 * Start the operations. In this version the elements of the array A
233 * are accessed sequentially with one pass through A.
234 *
235 * First form y := beta*y.
236 *
237  IF( beta.NE.one ) THEN
238  IF( incy.EQ.1 ) THEN
239  IF( beta.EQ.zero ) THEN
240  DO 10 i = 1, n
241  y( i ) = zero
242  10 CONTINUE
243  ELSE
244  DO 20 i = 1, n
245  y( i ) = beta*y( i )
246  20 CONTINUE
247  END IF
248  ELSE
249  iy = ky
250  IF( beta.EQ.zero ) THEN
251  DO 30 i = 1, n
252  y( iy ) = zero
253  iy = iy + incy
254  30 CONTINUE
255  ELSE
256  DO 40 i = 1, n
257  y( iy ) = beta*y( iy )
258  iy = iy + incy
259  40 CONTINUE
260  END IF
261  END IF
262  END IF
263  IF( alpha.EQ.zero )
264  $ RETURN
265  IF( lsame( uplo, 'U' ) ) THEN
266 *
267 * Form y when upper triangle of A is stored.
268 *
269  kplus1 = k + 1
270  IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
271  DO 60 j = 1, n
272  temp1 = alpha*x( j )
273  temp2 = zero
274  l = kplus1 - j
275  DO 50 i = max( 1, j-k ), j - 1
276  y( i ) = y( i ) + temp1*a( l+i, j )
277  temp2 = temp2 + a( l+i, j )*x( i )
278  50 CONTINUE
279  y( j ) = y( j ) + temp1*a( kplus1, j ) + alpha*temp2
280  60 CONTINUE
281  ELSE
282  jx = kx
283  jy = ky
284  DO 80 j = 1, n
285  temp1 = alpha*x( jx )
286  temp2 = zero
287  ix = kx
288  iy = ky
289  l = kplus1 - j
290  DO 70 i = max( 1, j-k ), j - 1
291  y( iy ) = y( iy ) + temp1*a( l+i, j )
292  temp2 = temp2 + a( l+i, j )*x( ix )
293  ix = ix + incx
294  iy = iy + incy
295  70 CONTINUE
296  y( jy ) = y( jy ) + temp1*a( kplus1, j ) + alpha*temp2
297  jx = jx + incx
298  jy = jy + incy
299  IF( j.GT.k ) THEN
300  kx = kx + incx
301  ky = ky + incy
302  END IF
303  80 CONTINUE
304  END IF
305  ELSE
306 *
307 * Form y when lower triangle of A is stored.
308 *
309  IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
310  DO 100 j = 1, n
311  temp1 = alpha*x( j )
312  temp2 = zero
313  y( j ) = y( j ) + temp1*a( 1, j )
314  l = 1 - j
315  DO 90 i = j + 1, min( n, j+k )
316  y( i ) = y( i ) + temp1*a( l+i, j )
317  temp2 = temp2 + a( l+i, j )*x( i )
318  90 CONTINUE
319  y( j ) = y( j ) + alpha*temp2
320  100 CONTINUE
321  ELSE
322  jx = kx
323  jy = ky
324  DO 120 j = 1, n
325  temp1 = alpha*x( jx )
326  temp2 = zero
327  y( jy ) = y( jy ) + temp1*a( 1, j )
328  l = 1 - j
329  ix = jx
330  iy = jy
331  DO 110 i = j + 1, min( n, j+k )
332  ix = ix + incx
333  iy = iy + incy
334  y( iy ) = y( iy ) + temp1*a( l+i, j )
335  temp2 = temp2 + a( l+i, j )*x( ix )
336  110 CONTINUE
337  y( jy ) = y( jy ) + alpha*temp2
338  jx = jx + incx
339  jy = jy + incy
340  120 CONTINUE
341  END IF
342  END IF
343 *
344  RETURN
345 *
346 * End of CSBMV
347 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: