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

◆ csyr()

subroutine csyr ( character uplo,
integer n,
complex alpha,
complex, dimension( * ) x,
integer incx,
complex, dimension( lda, * ) a,
integer lda )

CSYR performs the symmetric rank-1 update of a complex symmetric matrix.

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

Purpose:
!>
!> CSYR   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.
!> 
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
!>           On entry, ALPHA specifies the scalar alpha.
!>           Unchanged on exit.
!> 
[in]X
!>          X is COMPLEX 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]A
!>          A is COMPLEX 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. On exit, the
!>           upper triangular part of the array A is overwritten by the
!>           upper triangular part of the updated matrix.
!>           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. On exit, the
!>           lower triangular part of the array A is overwritten by the
!>           lower triangular part of the updated matrix.
!> 
[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.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 132 of file csyr.f.

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