LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ zspr()

subroutine zspr ( character uplo,
integer n,
complex*16 alpha,
complex*16, dimension( * ) x,
integer incx,
complex*16, dimension( * ) ap )

ZSPR performs the symmetrical rank-1 update of a complex symmetric packed matrix.

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

Purpose:
!> !> ZSPR performs the symmetric rank 1 operation !> !> A := alpha*x*x**H + A, !> !> where alpha is a complex scalar, x is an n element vector 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]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,out]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. On exit, the array !> AP is overwritten by the upper triangular part of the !> updated matrix. !> 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. On exit, the array !> AP is overwritten by the lower triangular part of the !> updated matrix. !> Note that the imaginary parts of the diagonal elements need !> not be set, they are assumed to be zero, and on exit they !> are set to zero. !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 129 of file zspr.f.

130*
131* -- LAPACK auxiliary routine --
132* -- LAPACK is a software package provided by Univ. of Tennessee, --
133* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
134*
135* .. Scalar Arguments ..
136 CHARACTER UPLO
137 INTEGER INCX, N
138 COMPLEX*16 ALPHA
139* ..
140* .. Array Arguments ..
141 COMPLEX*16 AP( * ), X( * )
142* ..
143*
144* =====================================================================
145*
146* .. Parameters ..
147 COMPLEX*16 ZERO
148 parameter( zero = ( 0.0d+0, 0.0d+0 ) )
149* ..
150* .. Local Scalars ..
151 INTEGER I, INFO, IX, J, JX, K, KK, KX
152 COMPLEX*16 TEMP
153* ..
154* .. External Functions ..
155 LOGICAL LSAME
156 EXTERNAL lsame
157* ..
158* .. External Subroutines ..
159 EXTERNAL xerbla
160* ..
161* .. Executable Statements ..
162*
163* Test the input parameters.
164*
165 info = 0
166 IF( .NOT.lsame( uplo, 'U' ) .AND.
167 $ .NOT.lsame( uplo, 'L' ) ) THEN
168 info = 1
169 ELSE IF( n.LT.0 ) THEN
170 info = 2
171 ELSE IF( incx.EQ.0 ) THEN
172 info = 5
173 END IF
174 IF( info.NE.0 ) THEN
175 CALL xerbla( 'ZSPR ', info )
176 RETURN
177 END IF
178*
179* Quick return if possible.
180*
181 IF( ( n.EQ.0 ) .OR. ( alpha.EQ.zero ) )
182 $ RETURN
183*
184* Set the start point in X if the increment is not unity.
185*
186 IF( incx.LE.0 ) THEN
187 kx = 1 - ( n-1 )*incx
188 ELSE IF( incx.NE.1 ) THEN
189 kx = 1
190 END IF
191*
192* Start the operations. In this version the elements of the array AP
193* are accessed sequentially with one pass through AP.
194*
195 kk = 1
196 IF( lsame( uplo, 'U' ) ) THEN
197*
198* Form A when upper triangle is stored in AP.
199*
200 IF( incx.EQ.1 ) THEN
201 DO 20 j = 1, n
202 IF( x( j ).NE.zero ) THEN
203 temp = alpha*x( j )
204 k = kk
205 DO 10 i = 1, j - 1
206 ap( k ) = ap( k ) + x( i )*temp
207 k = k + 1
208 10 CONTINUE
209 ap( kk+j-1 ) = ap( kk+j-1 ) + x( j )*temp
210 ELSE
211 ap( kk+j-1 ) = ap( kk+j-1 )
212 END IF
213 kk = kk + j
214 20 CONTINUE
215 ELSE
216 jx = kx
217 DO 40 j = 1, n
218 IF( x( jx ).NE.zero ) THEN
219 temp = alpha*x( jx )
220 ix = kx
221 DO 30 k = kk, kk + j - 2
222 ap( k ) = ap( k ) + x( ix )*temp
223 ix = ix + incx
224 30 CONTINUE
225 ap( kk+j-1 ) = ap( kk+j-1 ) + x( jx )*temp
226 ELSE
227 ap( kk+j-1 ) = ap( kk+j-1 )
228 END IF
229 jx = jx + incx
230 kk = kk + j
231 40 CONTINUE
232 END IF
233 ELSE
234*
235* Form A when lower triangle is stored in AP.
236*
237 IF( incx.EQ.1 ) THEN
238 DO 60 j = 1, n
239 IF( x( j ).NE.zero ) THEN
240 temp = alpha*x( j )
241 ap( kk ) = ap( kk ) + temp*x( j )
242 k = kk + 1
243 DO 50 i = j + 1, n
244 ap( k ) = ap( k ) + x( i )*temp
245 k = k + 1
246 50 CONTINUE
247 ELSE
248 ap( kk ) = ap( kk )
249 END IF
250 kk = kk + n - j + 1
251 60 CONTINUE
252 ELSE
253 jx = kx
254 DO 80 j = 1, n
255 IF( x( jx ).NE.zero ) THEN
256 temp = alpha*x( jx )
257 ap( kk ) = ap( kk ) + temp*x( jx )
258 ix = jx
259 DO 70 k = kk + 1, kk + n - j
260 ix = ix + incx
261 ap( k ) = ap( k ) + x( ix )*temp
262 70 CONTINUE
263 ELSE
264 ap( kk ) = ap( kk )
265 END IF
266 jx = jx + incx
267 kk = kk + n - j + 1
268 80 CONTINUE
269 END IF
270 END IF
271*
272 RETURN
273*
274* End of ZSPR
275*
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: