1 *> \brief \b ZSPMV computes a matrix-vector product for complex vectors using a complex symmetric packed matrix
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZSPMV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zspmv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zspmv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspmv.f">
21 * SUBROUTINE ZSPMV( UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY )
23 * .. Scalar Arguments ..
25 * INTEGER INCX, INCY, N
26 * COMPLEX*16 ALPHA, BETA
28 * .. Array Arguments ..
29 * COMPLEX*16 AP( * ), X( * ), Y( * )
38 *> ZSPMV performs the matrix-vector operation
40 *> y := alpha*A*x + beta*y,
42 *> where alpha and beta are scalars, x and y are n element vectors and
43 *> A is an n by n symmetric matrix, supplied in packed form.
51 *> UPLO is CHARACTER*1
52 *> On entry, UPLO specifies whether the upper or lower
53 *> triangular part of the matrix A is supplied in the packed
54 *> array AP as follows:
56 *> UPLO = 'U' or 'u' The upper triangular part of A is
59 *> UPLO = 'L' or 'l' The lower triangular part of A is
68 *> On entry, N specifies the order of the matrix A.
69 *> N must be at least zero.
75 *> ALPHA is COMPLEX*16
76 *> On entry, ALPHA specifies the scalar alpha.
82 *> AP is COMPLEX*16 array, dimension at least
83 *> ( ( N*( N + 1 ) )/2 ).
84 *> Before entry, with UPLO = 'U' or 'u', the array AP must
85 *> contain the upper triangular part of the symmetric matrix
86 *> packed sequentially, column by column, so that AP( 1 )
87 *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
88 *> and a( 2, 2 ) respectively, and so on.
89 *> Before entry, with UPLO = 'L' or 'l', the array AP must
90 *> contain the lower triangular part of the symmetric matrix
91 *> packed sequentially, column by column, so that AP( 1 )
92 *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
93 *> and a( 3, 1 ) respectively, and so on.
99 *> X is COMPLEX*16 array, dimension at least
100 *> ( 1 + ( N - 1 )*abs( INCX ) ).
101 *> Before entry, the incremented array X must contain the N-
103 *> Unchanged on exit.
109 *> On entry, INCX specifies the increment for the elements of
110 *> X. INCX must not be zero.
111 *> Unchanged on exit.
116 *> BETA is COMPLEX*16
117 *> On entry, BETA specifies the scalar beta. When BETA is
118 *> supplied as zero then Y need not be set on input.
119 *> Unchanged on exit.
124 *> Y is COMPLEX*16 array, dimension at least
125 *> ( 1 + ( N - 1 )*abs( INCY ) ).
126 *> Before entry, the incremented array Y must contain the n
127 *> element vector y. On exit, Y is overwritten by the updated
134 *> On entry, INCY specifies the increment for the elements of
135 *> Y. INCY must not be zero.
136 *> Unchanged on exit.
142 *> \author Univ. of Tennessee
143 *> \author Univ. of California Berkeley
144 *> \author Univ. of Colorado Denver
147 *> \date September 2012
149 *> \ingroup complex16OTHERauxiliary
151 * =====================================================================
152 SUBROUTINE ZSPMV( UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY )
154 * -- LAPACK auxiliary routine (version 3.4.2) --
155 * -- LAPACK is a software package provided by Univ. of Tennessee, --
156 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
159 * .. Scalar Arguments ..
161 INTEGER INCX, INCY, N
162 COMPLEX*16 ALPHA, BETA
164 * .. Array Arguments ..
165 COMPLEX*16 AP( * ), X( * ), Y( * )
168 * =====================================================================
172 PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ) )
174 PARAMETER ( ZERO = ( 0.0D+0, 0.0D+0 ) )
176 * .. Local Scalars ..
177 INTEGER I, INFO, IX, IY, J, JX, JY, K, KK, KX, KY
178 COMPLEX*16 TEMP1, TEMP2
180 * .. External Functions ..
184 * .. External Subroutines ..
187 * .. Executable Statements ..
189 * Test the input parameters.
192 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
194 ELSE IF( N.LT.0 ) THEN
196 ELSE IF( INCX.EQ.0 ) THEN
198 ELSE IF( INCY.EQ.0 ) THEN
202 CALL XERBLA( 'ZSPMV ', INFO )
206 * Quick return if possible.
208 IF( ( N.EQ.0 ) .OR. ( ( ALPHA.EQ.ZERO ) .AND. ( BETA.EQ.ONE ) ) )
211 * Set up the start points in X and Y.
216 KX = 1 - ( N-1 )*INCX
221 KY = 1 - ( N-1 )*INCY
224 * Start the operations. In this version the elements of the array AP
225 * are accessed sequentially with one pass through AP.
227 * First form y := beta*y.
229 IF( BETA.NE.ONE ) THEN
231 IF( BETA.EQ.ZERO ) THEN
242 IF( BETA.EQ.ZERO ) THEN
249 Y( IY ) = BETA*Y( IY )
258 IF( LSAME( UPLO, 'U' ) ) THEN
260 * Form y when AP contains the upper triangle.
262 IF( ( INCX.EQ.1 ) .AND. ( INCY.EQ.1 ) ) THEN
268 Y( I ) = Y( I ) + TEMP1*AP( K )
269 TEMP2 = TEMP2 + AP( K )*X( I )
272 Y( J ) = Y( J ) + TEMP1*AP( KK+J-1 ) + ALPHA*TEMP2
279 TEMP1 = ALPHA*X( JX )
283 DO 70 K = KK, KK + J - 2
284 Y( IY ) = Y( IY ) + TEMP1*AP( K )
285 TEMP2 = TEMP2 + AP( K )*X( IX )
289 Y( JY ) = Y( JY ) + TEMP1*AP( KK+J-1 ) + ALPHA*TEMP2
297 * Form y when AP contains the lower triangle.
299 IF( ( INCX.EQ.1 ) .AND. ( INCY.EQ.1 ) ) THEN
303 Y( J ) = Y( J ) + TEMP1*AP( KK )
306 Y( I ) = Y( I ) + TEMP1*AP( K )
307 TEMP2 = TEMP2 + AP( K )*X( I )
310 Y( J ) = Y( J ) + ALPHA*TEMP2
317 TEMP1 = ALPHA*X( JX )
319 Y( JY ) = Y( JY ) + TEMP1*AP( KK )
322 DO 110 K = KK + 1, KK + N - J
325 Y( IY ) = Y( IY ) + TEMP1*AP( K )
326 TEMP2 = TEMP2 + AP( K )*X( IX )
328 Y( JY ) = Y( JY ) + ALPHA*TEMP2