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

◆ zspmv()

subroutine zspmv ( character uplo,
integer n,
complex*16 alpha,
complex*16, dimension( * ) ap,
complex*16, dimension( * ) x,
integer incx,
complex*16 beta,
complex*16, dimension( * ) y,
integer incy )

ZSPMV computes a matrix-vector product for complex vectors using a complex symmetric packed matrix

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

Purpose:
!>
!> ZSPMV  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, supplied in packed form.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>           On entry, UPLO specifies whether the upper or lower
!>           triangular part of the matrix A is supplied in the packed
!>           array AP as follows:
!>
!>              UPLO = 'U' or 'u'   The upper triangular part of A is
!>                                  supplied in AP.
!>
!>              UPLO = 'L' or 'l'   The lower triangular part of A is
!>                                  supplied in AP.
!>
!>           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]AP
!>          AP is COMPLEX*16 array, dimension at least
!>           ( ( N*( N + 1 ) )/2 ).
!>           Before entry, with UPLO = 'U' or 'u', the array AP must
!>           contain the upper triangular part of the symmetric matrix
!>           packed sequentially, column by column, so that AP( 1 )
!>           contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
!>           and a( 2, 2 ) respectively, and so on.
!>           Before entry, with UPLO = 'L' or 'l', the array AP must
!>           contain the lower triangular part of the symmetric matrix
!>           packed sequentially, column by column, so that AP( 1 )
!>           contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
!>           and a( 3, 1 ) respectively, and so on.
!>           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 148 of file zspmv.f.

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