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

◆ dsyr()

subroutine dsyr ( character uplo,
integer n,
double precision alpha,
double precision, dimension(*) x,
integer incx,
double precision, dimension(lda,*) a,
integer lda )

DSYR

Purpose:
!> !> DSYR performs the symmetric rank 1 operation !> !> A := alpha*x*x**T + A, !> !> where alpha is a real 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. !>
[in]N
!> N is INTEGER !> On entry, N specifies the order of the matrix A. !> N must be at least zero. !>
[in]ALPHA
!> ALPHA is DOUBLE PRECISION. !> On entry, ALPHA specifies the scalar alpha. !>
[in]X
!> X is DOUBLE PRECISION array, dimension at least !> ( 1 + ( n - 1 )*abs( INCX ) ). !> Before entry, the incremented array X must contain the n !> element vector x. !>
[in]INCX
!> INCX is INTEGER !> On entry, INCX specifies the increment for the elements of !> X. INCX must not be zero. !>
[in,out]A
!> A is DOUBLE PRECISION 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 ). !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!> !> Level 2 Blas routine. !> !> -- Written on 22-October-1986. !> Jack Dongarra, Argonne National Lab. !> Jeremy Du Croz, Nag Central Office. !> Sven Hammarling, Nag Central Office. !> Richard Hanson, Sandia National Labs. !>

Definition at line 131 of file dsyr.f.

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