LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ csbmv()

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.

Definition at line 150 of file csbmv.f.

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