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

◆ zsymv()

subroutine zsymv ( character uplo,
integer n,
complex*16 alpha,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( * ) x,
integer incx,
complex*16 beta,
complex*16, dimension( * ) y,
integer incy )

ZSYMV computes a matrix-vector product for a complex symmetric matrix.

Download ZSYMV + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZSYMV  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 matrix.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>           On entry, UPLO specifies whether the upper or lower
!>           triangular part of the array A is to be referenced as
!>           follows:
!>
!>              UPLO = 'U' or 'u'   Only the upper triangular part of A
!>                                  is to be referenced.
!>
!>              UPLO = 'L' or 'l'   Only the lower triangular part of A
!>                                  is to be referenced.
!>
!>           Unchanged on exit.
!> 
[in]N
!>          N is INTEGER
!>           On entry, N specifies the order of the matrix A.
!>           N must be at least zero.
!>           Unchanged on exit.
!> 
[in]ALPHA
!>          ALPHA is COMPLEX*16
!>           On entry, ALPHA specifies the scalar alpha.
!>           Unchanged on exit.
!> 
[in]A
!>          A is COMPLEX*16 array, dimension ( LDA, N )
!>           Before entry, with  UPLO = 'U' or 'u', the leading n by n
!>           upper triangular part of the array A must contain the upper
!>           triangular part of the symmetric matrix and the strictly
!>           lower triangular part of A is not referenced.
!>           Before entry, with UPLO = 'L' or 'l', the leading n by n
!>           lower triangular part of the array A must contain the lower
!>           triangular part of the symmetric matrix and the strictly
!>           upper triangular part of A is not referenced.
!>           Unchanged on exit.
!> 
[in]LDA
!>          LDA is INTEGER
!>           On entry, LDA specifies the first dimension of A as declared
!>           in the calling (sub) program. LDA must be at least
!>           max( 1, N ).
!>           Unchanged on exit.
!> 
[in]X
!>          X is COMPLEX*16 array, dimension at least
!>           ( 1 + ( N - 1 )*abs( INCX ) ).
!>           Before entry, the incremented array X must contain the N-
!>           element vector x.
!>           Unchanged on exit.
!> 
[in]INCX
!>          INCX is INTEGER
!>           On entry, INCX specifies the increment for the elements of
!>           X. INCX must not be zero.
!>           Unchanged on exit.
!> 
[in]BETA
!>          BETA is COMPLEX*16
!>           On entry, BETA specifies the scalar beta. When BETA is
!>           supplied as zero then Y need not be set on input.
!>           Unchanged on exit.
!> 
[in,out]Y
!>          Y is COMPLEX*16 array, dimension at least
!>           ( 1 + ( N - 1 )*abs( INCY ) ).
!>           Before entry, the incremented array Y must contain the n
!>           element vector y. On exit, Y is overwritten by the updated
!>           vector y.
!> 
[in]INCY
!>          INCY is 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 154 of file zsymv.f.

156*
157* -- LAPACK auxiliary routine --
158* -- LAPACK is a software package provided by Univ. of Tennessee, --
159* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160*
161* .. Scalar Arguments ..
162 CHARACTER UPLO
163 INTEGER INCX, INCY, LDA, N
164 COMPLEX*16 ALPHA, BETA
165* ..
166* .. Array Arguments ..
167 COMPLEX*16 A( LDA, * ), X( * ), Y( * )
168* ..
169*
170* =====================================================================
171*
172* .. Parameters ..
173 COMPLEX*16 ONE
174 parameter( one = ( 1.0d+0, 0.0d+0 ) )
175 COMPLEX*16 ZERO
176 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
177* ..
178* .. Local Scalars ..
179 INTEGER I, INFO, IX, IY, J, JX, JY, KX, KY
180 COMPLEX*16 TEMP1, TEMP2
181* ..
182* .. External Functions ..
183 LOGICAL LSAME
184 EXTERNAL lsame
185* ..
186* .. External Subroutines ..
187 EXTERNAL xerbla
188* ..
189* .. Intrinsic Functions ..
190 INTRINSIC max
191* ..
192* .. Executable Statements ..
193*
194* Test the input parameters.
195*
196 info = 0
197 IF( .NOT.lsame( uplo, 'U' ) .AND.
198 $ .NOT.lsame( uplo, 'L' ) ) THEN
199 info = 1
200 ELSE IF( n.LT.0 ) THEN
201 info = 2
202 ELSE IF( lda.LT.max( 1, n ) ) THEN
203 info = 5
204 ELSE IF( incx.EQ.0 ) THEN
205 info = 7
206 ELSE IF( incy.EQ.0 ) THEN
207 info = 10
208 END IF
209 IF( info.NE.0 ) THEN
210 CALL xerbla( 'ZSYMV ', 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 A are
233* accessed sequentially with one pass through the triangular part
234* of A.
235*
236* First form y := beta*y.
237*
238 IF( beta.NE.one ) THEN
239 IF( incy.EQ.1 ) THEN
240 IF( beta.EQ.zero ) THEN
241 DO 10 i = 1, n
242 y( i ) = zero
243 10 CONTINUE
244 ELSE
245 DO 20 i = 1, n
246 y( i ) = beta*y( i )
247 20 CONTINUE
248 END IF
249 ELSE
250 iy = ky
251 IF( beta.EQ.zero ) THEN
252 DO 30 i = 1, n
253 y( iy ) = zero
254 iy = iy + incy
255 30 CONTINUE
256 ELSE
257 DO 40 i = 1, n
258 y( iy ) = beta*y( iy )
259 iy = iy + incy
260 40 CONTINUE
261 END IF
262 END IF
263 END IF
264 IF( alpha.EQ.zero )
265 $ RETURN
266 IF( lsame( uplo, 'U' ) ) THEN
267*
268* Form y when A is stored in upper triangle.
269*
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 DO 50 i = 1, j - 1
275 y( i ) = y( i ) + temp1*a( i, j )
276 temp2 = temp2 + a( i, j )*x( i )
277 50 CONTINUE
278 y( j ) = y( j ) + temp1*a( j, j ) + alpha*temp2
279 60 CONTINUE
280 ELSE
281 jx = kx
282 jy = ky
283 DO 80 j = 1, n
284 temp1 = alpha*x( jx )
285 temp2 = zero
286 ix = kx
287 iy = ky
288 DO 70 i = 1, j - 1
289 y( iy ) = y( iy ) + temp1*a( i, j )
290 temp2 = temp2 + a( i, j )*x( ix )
291 ix = ix + incx
292 iy = iy + incy
293 70 CONTINUE
294 y( jy ) = y( jy ) + temp1*a( j, j ) + alpha*temp2
295 jx = jx + incx
296 jy = jy + incy
297 80 CONTINUE
298 END IF
299 ELSE
300*
301* Form y when A is stored in lower triangle.
302*
303 IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
304 DO 100 j = 1, n
305 temp1 = alpha*x( j )
306 temp2 = zero
307 y( j ) = y( j ) + temp1*a( j, j )
308 DO 90 i = j + 1, n
309 y( i ) = y( i ) + temp1*a( i, j )
310 temp2 = temp2 + a( i, j )*x( i )
311 90 CONTINUE
312 y( j ) = y( j ) + alpha*temp2
313 100 CONTINUE
314 ELSE
315 jx = kx
316 jy = ky
317 DO 120 j = 1, n
318 temp1 = alpha*x( jx )
319 temp2 = zero
320 y( jy ) = y( jy ) + temp1*a( j, j )
321 ix = jx
322 iy = jy
323 DO 110 i = j + 1, n
324 ix = ix + incx
325 iy = iy + incy
326 y( iy ) = y( iy ) + temp1*a( i, j )
327 temp2 = temp2 + a( i, j )*x( ix )
328 110 CONTINUE
329 y( jy ) = y( jy ) + alpha*temp2
330 jx = jx + incx
331 jy = jy + incy
332 120 CONTINUE
333 END IF
334 END IF
335*
336 RETURN
337*
338* End of ZSYMV
339*
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:
Here is the caller graph for this function: