LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zsbmv.f
Go to the documentation of this file.
1*> \brief \b ZSBMV
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 ZSBMV( UPLO, N, K, ALPHA, A, LDA, X, INCX, BETA, Y,
12* INCY )
13*
14* .. Scalar Arguments ..
15* CHARACTER UPLO
16* INTEGER INCX, INCY, K, LDA, N
17* COMPLEX*16 ALPHA, BETA
18* ..
19* .. Array Arguments ..
20* COMPLEX*16 A( LDA, * ), X( * ), Y( * )
21* ..
22*
23*
24*> \par Purpose:
25* =============
26*>
27*> \verbatim
28*>
29*> ZSBMV performs the matrix-vector operation
30*>
31*> y := alpha*A*x + beta*y,
32*>
33*> where alpha and beta are scalars, x and y are n element vectors and
34*> A is an n by n symmetric band matrix, with k super-diagonals.
35*> \endverbatim
36*
37* Arguments:
38* ==========
39*
40*> \verbatim
41*> UPLO - CHARACTER*1
42*> On entry, UPLO specifies whether the upper or lower
43*> triangular part of the band matrix A is being supplied as
44*> follows:
45*>
46*> UPLO = 'U' or 'u' The upper triangular part of A is
47*> being supplied.
48*>
49*> UPLO = 'L' or 'l' The lower triangular part of A is
50*> being supplied.
51*>
52*> Unchanged on exit.
53*>
54*> N - INTEGER
55*> On entry, N specifies the order of the matrix A.
56*> N must be at least zero.
57*> Unchanged on exit.
58*>
59*> K - INTEGER
60*> On entry, K specifies the number of super-diagonals of the
61*> matrix A. K must satisfy 0 .le. K.
62*> Unchanged on exit.
63*>
64*> ALPHA - COMPLEX*16
65*> On entry, ALPHA specifies the scalar alpha.
66*> Unchanged on exit.
67*>
68*> A - COMPLEX*16 array, dimension( LDA, N )
69*> Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
70*> by n part of the array A must contain the upper triangular
71*> band part of the symmetric matrix, supplied column by
72*> column, with the leading diagonal of the matrix in row
73*> ( k + 1 ) of the array, the first super-diagonal starting at
74*> position 2 in row k, and so on. The top left k by k triangle
75*> of the array A is not referenced.
76*> The following program segment will transfer the upper
77*> triangular part of a symmetric band matrix from conventional
78*> full matrix storage to band storage:
79*>
80*> DO 20, J = 1, N
81*> M = K + 1 - J
82*> DO 10, I = MAX( 1, J - K ), J
83*> A( M + I, J ) = matrix( I, J )
84*> 10 CONTINUE
85*> 20 CONTINUE
86*>
87*> Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
88*> by n part of the array A must contain the lower triangular
89*> band part of the symmetric matrix, supplied column by
90*> column, with the leading diagonal of the matrix in row 1 of
91*> the array, the first sub-diagonal starting at position 1 in
92*> row 2, and so on. The bottom right k by k triangle of the
93*> array A is not referenced.
94*> The following program segment will transfer the lower
95*> triangular part of a symmetric band matrix from conventional
96*> full matrix storage to band storage:
97*>
98*> DO 20, J = 1, N
99*> M = 1 - J
100*> DO 10, I = J, MIN( N, J + K )
101*> A( M + I, J ) = matrix( I, J )
102*> 10 CONTINUE
103*> 20 CONTINUE
104*>
105*> Unchanged on exit.
106*>
107*> LDA - INTEGER
108*> On entry, LDA specifies the first dimension of A as declared
109*> in the calling (sub) program. LDA must be at least
110*> ( k + 1 ).
111*> Unchanged on exit.
112*>
113*> X - COMPLEX*16 array, dimension at least
114*> ( 1 + ( N - 1 )*abs( INCX ) ).
115*> Before entry, the incremented array X must contain the
116*> vector x.
117*> Unchanged on exit.
118*>
119*> INCX - INTEGER
120*> On entry, INCX specifies the increment for the elements of
121*> X. INCX must not be zero.
122*> Unchanged on exit.
123*>
124*> BETA - COMPLEX*16
125*> On entry, BETA specifies the scalar beta.
126*> Unchanged on exit.
127*>
128*> Y - COMPLEX*16 array, dimension at least
129*> ( 1 + ( N - 1 )*abs( INCY ) ).
130*> Before entry, the incremented array Y must contain the
131*> vector y. On exit, Y is overwritten by the updated vector y.
132*>
133*> INCY - INTEGER
134*> On entry, INCY specifies the increment for the elements of
135*> Y. INCY must not be zero.
136*> Unchanged on exit.
137*> \endverbatim
138*
139* Authors:
140* ========
141*
142*> \author Univ. of Tennessee
143*> \author Univ. of California Berkeley
144*> \author Univ. of Colorado Denver
145*> \author NAG Ltd.
146*
147*> \ingroup complex16_lin
148*
149* =====================================================================
150 SUBROUTINE zsbmv( UPLO, N, K, ALPHA, A, LDA, X, INCX, BETA, Y,
151 $ INCY )
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*16 ALPHA, BETA
161* ..
162* .. Array Arguments ..
163 COMPLEX*16 A( LDA, * ), X( * ), Y( * )
164* ..
165*
166* =====================================================================
167*
168* .. Parameters ..
169 COMPLEX*16 ONE
170 parameter( one = ( 1.0d+0, 0.0d+0 ) )
171 COMPLEX*16 ZERO
172 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
173* ..
174* .. Local Scalars ..
175 INTEGER I, INFO, IX, IY, J, JX, JY, KPLUS1, KX, KY, L
176 COMPLEX*16 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( 'ZSBMV ', 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 ZSBMV
344*
345 END
subroutine zsbmv(uplo, n, k, alpha, a, lda, x, incx, beta, y, incy)
ZSBMV
Definition zsbmv.f:152
subroutine xerbla(srname, info)
Definition cblat2.f:3285