LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zspmv.f
Go to the documentation of this file.
1*> \brief \b ZSPMV computes a matrix-vector product for complex vectors using a complex symmetric packed matrix
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZSPMV + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zspmv.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zspmv.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zspmv.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE ZSPMV( UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER INCX, INCY, N
26* COMPLEX*16 ALPHA, BETA
27* ..
28* .. Array Arguments ..
29* COMPLEX*16 AP( * ), X( * ), Y( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> ZSPMV performs the matrix-vector operation
39*>
40*> y := alpha*A*x + beta*y,
41*>
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.
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] UPLO
50*> \verbatim
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:
55*>
56*> UPLO = 'U' or 'u' The upper triangular part of A is
57*> supplied in AP.
58*>
59*> UPLO = 'L' or 'l' The lower triangular part of A is
60*> supplied in AP.
61*>
62*> Unchanged on exit.
63*> \endverbatim
64*>
65*> \param[in] N
66*> \verbatim
67*> N is INTEGER
68*> On entry, N specifies the order of the matrix A.
69*> N must be at least zero.
70*> Unchanged on exit.
71*> \endverbatim
72*>
73*> \param[in] ALPHA
74*> \verbatim
75*> ALPHA is COMPLEX*16
76*> On entry, ALPHA specifies the scalar alpha.
77*> Unchanged on exit.
78*> \endverbatim
79*>
80*> \param[in] AP
81*> \verbatim
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.
94*> Unchanged on exit.
95*> \endverbatim
96*>
97*> \param[in] X
98*> \verbatim
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-
102*> element vector x.
103*> Unchanged on exit.
104*> \endverbatim
105*>
106*> \param[in] INCX
107*> \verbatim
108*> INCX is INTEGER
109*> On entry, INCX specifies the increment for the elements of
110*> X. INCX must not be zero.
111*> Unchanged on exit.
112*> \endverbatim
113*>
114*> \param[in] BETA
115*> \verbatim
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.
120*> \endverbatim
121*>
122*> \param[in,out] Y
123*> \verbatim
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
128*> vector y.
129*> \endverbatim
130*>
131*> \param[in] INCY
132*> \verbatim
133*> INCY is 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 hpmv
148*
149* =====================================================================
150 SUBROUTINE zspmv( UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY )
151*
152* -- LAPACK auxiliary routine --
153* -- LAPACK is a software package provided by Univ. of Tennessee, --
154* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155*
156* .. Scalar Arguments ..
157 CHARACTER UPLO
158 INTEGER INCX, INCY, N
159 COMPLEX*16 ALPHA, BETA
160* ..
161* .. Array Arguments ..
162 COMPLEX*16 AP( * ), X( * ), Y( * )
163* ..
164*
165* =====================================================================
166*
167* .. Parameters ..
168 COMPLEX*16 ONE
169 parameter( one = ( 1.0d+0, 0.0d+0 ) )
170 COMPLEX*16 ZERO
171 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
172* ..
173* .. Local Scalars ..
174 INTEGER I, INFO, IX, IY, J, JX, JY, K, KK, KX, KY
175 COMPLEX*16 TEMP1, TEMP2
176* ..
177* .. External Functions ..
178 LOGICAL LSAME
179 EXTERNAL lsame
180* ..
181* .. External Subroutines ..
182 EXTERNAL xerbla
183* ..
184* .. Executable Statements ..
185*
186* Test the input parameters.
187*
188 info = 0
189 IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
190 info = 1
191 ELSE IF( n.LT.0 ) THEN
192 info = 2
193 ELSE IF( incx.EQ.0 ) THEN
194 info = 6
195 ELSE IF( incy.EQ.0 ) THEN
196 info = 9
197 END IF
198 IF( info.NE.0 ) THEN
199 CALL xerbla( 'ZSPMV ', info )
200 RETURN
201 END IF
202*
203* Quick return if possible.
204*
205 IF( ( n.EQ.0 ) .OR. ( ( alpha.EQ.zero ) .AND. ( beta.EQ.one ) ) )
206 $ RETURN
207*
208* Set up the start points in X and Y.
209*
210 IF( incx.GT.0 ) THEN
211 kx = 1
212 ELSE
213 kx = 1 - ( n-1 )*incx
214 END IF
215 IF( incy.GT.0 ) THEN
216 ky = 1
217 ELSE
218 ky = 1 - ( n-1 )*incy
219 END IF
220*
221* Start the operations. In this version the elements of the array AP
222* are accessed sequentially with one pass through AP.
223*
224* First form y := beta*y.
225*
226 IF( beta.NE.one ) THEN
227 IF( incy.EQ.1 ) THEN
228 IF( beta.EQ.zero ) THEN
229 DO 10 i = 1, n
230 y( i ) = zero
231 10 CONTINUE
232 ELSE
233 DO 20 i = 1, n
234 y( i ) = beta*y( i )
235 20 CONTINUE
236 END IF
237 ELSE
238 iy = ky
239 IF( beta.EQ.zero ) THEN
240 DO 30 i = 1, n
241 y( iy ) = zero
242 iy = iy + incy
243 30 CONTINUE
244 ELSE
245 DO 40 i = 1, n
246 y( iy ) = beta*y( iy )
247 iy = iy + incy
248 40 CONTINUE
249 END IF
250 END IF
251 END IF
252 IF( alpha.EQ.zero )
253 $ RETURN
254 kk = 1
255 IF( lsame( uplo, 'U' ) ) THEN
256*
257* Form y when AP contains the upper triangle.
258*
259 IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
260 DO 60 j = 1, n
261 temp1 = alpha*x( j )
262 temp2 = zero
263 k = kk
264 DO 50 i = 1, j - 1
265 y( i ) = y( i ) + temp1*ap( k )
266 temp2 = temp2 + ap( k )*x( i )
267 k = k + 1
268 50 CONTINUE
269 y( j ) = y( j ) + temp1*ap( kk+j-1 ) + alpha*temp2
270 kk = kk + j
271 60 CONTINUE
272 ELSE
273 jx = kx
274 jy = ky
275 DO 80 j = 1, n
276 temp1 = alpha*x( jx )
277 temp2 = zero
278 ix = kx
279 iy = ky
280 DO 70 k = kk, kk + j - 2
281 y( iy ) = y( iy ) + temp1*ap( k )
282 temp2 = temp2 + ap( k )*x( ix )
283 ix = ix + incx
284 iy = iy + incy
285 70 CONTINUE
286 y( jy ) = y( jy ) + temp1*ap( kk+j-1 ) + alpha*temp2
287 jx = jx + incx
288 jy = jy + incy
289 kk = kk + j
290 80 CONTINUE
291 END IF
292 ELSE
293*
294* Form y when AP contains the lower triangle.
295*
296 IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
297 DO 100 j = 1, n
298 temp1 = alpha*x( j )
299 temp2 = zero
300 y( j ) = y( j ) + temp1*ap( kk )
301 k = kk + 1
302 DO 90 i = j + 1, n
303 y( i ) = y( i ) + temp1*ap( k )
304 temp2 = temp2 + ap( k )*x( i )
305 k = k + 1
306 90 CONTINUE
307 y( j ) = y( j ) + alpha*temp2
308 kk = kk + ( n-j+1 )
309 100 CONTINUE
310 ELSE
311 jx = kx
312 jy = ky
313 DO 120 j = 1, n
314 temp1 = alpha*x( jx )
315 temp2 = zero
316 y( jy ) = y( jy ) + temp1*ap( kk )
317 ix = jx
318 iy = jy
319 DO 110 k = kk + 1, kk + n - j
320 ix = ix + incx
321 iy = iy + incy
322 y( iy ) = y( iy ) + temp1*ap( k )
323 temp2 = temp2 + ap( k )*x( ix )
324 110 CONTINUE
325 y( jy ) = y( jy ) + alpha*temp2
326 jx = jx + incx
327 jy = jy + incy
328 kk = kk + ( n-j+1 )
329 120 CONTINUE
330 END IF
331 END IF
332*
333 RETURN
334*
335* End of ZSPMV
336*
337 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zspmv(uplo, n, alpha, ap, x, incx, beta, y, incy)
ZSPMV computes a matrix-vector product for complex vectors using a complex symmetric packed matrix
Definition zspmv.f:151