1 SUBROUTINE DSYR2
( UPLO
, N
, ALPHA
, X
, INCX
, Y
, INCY
, A
, LDA
)
2 * .. Scalar Arguments
..
4 INTEGER INCX
, INCY
, LDA
, N
6 * .. Array Arguments
..
7 DOUBLE PRECISION A
( LDA
, * ), X
( * ), Y
( * )
13 * DSYR2 performs the symmetric rank
2 operation
15 * A
:= alpha*x*y
' + alpha*y*x' + A
,
17 * where alpha is a scalar
, x and y are n element vectors and A is an n
18 * by n symmetric matrix
.
24 * On entry
, UPLO specifies whether the upper or lower
25 * triangular part of the array A is
to be referenced as
28 * UPLO
= 'U' or
'u' Only the upper triangular part of A
29 * is
to be referenced
.
31 * UPLO
= 'L' or
'l' Only the lower triangular part of A
32 * is
to be referenced
.
37 * On entry
, N specifies the order of the matrix A
.
38 * N must be at least zero
.
41 * ALPHA
- DOUBLE PRECISION.
42 * On entry
, ALPHA specifies the scalar alpha
.
45 * X
- DOUBLE PRECISION array of
dimension at least
46 * ( 1 + ( n
- 1 )*abs
( INCX
) ).
47 * Before entry
, the incremented array X must contain the n
52 * On entry
, INCX specifies the increment
for the elements of
53 * X
. INCX must not be zero
.
56 * Y
- DOUBLE PRECISION array of
dimension at least
57 * ( 1 + ( n
- 1 )*abs
( INCY
) ).
58 * Before entry
, the incremented array Y must contain the n
63 * On entry
, INCY specifies the increment
for the elements of
64 * Y
. INCY must not be zero
.
67 * A
- DOUBLE PRECISION array of
DIMENSION ( LDA
, n
).
68 * Before entry with UPLO
= 'U' or
'u', the leading n by n
69 * upper triangular part of the array A must contain the upper
70 * triangular part of the symmetric matrix and the strictly
71 * lower triangular part of A is not referenced
. On exit
, the
72 * upper triangular part of the array A is overwritten by the
73 * upper triangular part of the updated matrix
.
74 * Before entry with UPLO
= 'L' or
'l', the leading n by n
75 * lower triangular part of the array A must contain the lower
76 * triangular part of the symmetric matrix and the strictly
77 * upper triangular part of A is not referenced
. On exit
, the
78 * lower triangular part of the array A is overwritten by the
79 * lower triangular part of the updated matrix
.
82 * On entry
, LDA specifies the first
dimension of A as declared
83 * in the calling
(sub
) program. LDA must be at least
88 * Level
2 Blas routine
.
90 * -- Written on
22-October
-1986.
91 * Jack Dongarra
, Argonne National Lab
.
92 * Jeremy Du Croz
, Nag Central Office
.
93 * Sven Hammarling
, Nag Central Office
.
94 * Richard Hanson
, Sandia National Labs
.
99 PARAMETER ( ZERO
= 0.0D
+0 )
100 * .. Local Scalars
..
101 DOUBLE PRECISION TEMP1
, TEMP2
102 INTEGER I
, INFO
, IX
, IY
, J
, JX
, JY
, KX
, KY
103 * .. External Functions
..
106 * .. External Subroutines
..
108 * .. Intrinsic Functions
..
111 * .. Executable Statements
..
113 * Test the input parameters
.
116 IF ( .NOT
.LSAME
( UPLO
, 'U' ).AND
.
117 $
.NOT
.LSAME
( UPLO
, 'L' ) )THEN
119 ELSE IF( N
.LT
.0 )THEN
121 ELSE IF( INCX
.EQ
.0 )THEN
123 ELSE IF( INCY
.EQ
.0 )THEN
125 ELSE IF( LDA
.LT
.MAX
( 1, N
) )THEN
129 CALL XERBLA
( 'DSYR2 ', INFO
)
133 * Quick
return if possible
.
135 IF( ( N
.EQ
.0 ).OR
.( ALPHA
.EQ
.ZERO
) )
138 * Set up the start points in X and Y
if the increments are not both
141 IF( ( INCX
.NE
.1 ).OR
.( INCY
.NE
.1 ) )THEN
145 KX
= 1 - ( N
- 1 )*INCX
150 KY
= 1 - ( N
- 1 )*INCY
156 * Start the operations
. In this version the elements of A are
157 * accessed sequentially with one pass through the triangular part
160 IF( LSAME
( UPLO
, 'U' ) )THEN
162 * Form A when A is stored in the upper triangle
.
164 IF( ( INCX
.EQ
.1 ).AND
.( INCY
.EQ
.1 ) )THEN
166 IF( ( X
( J
).NE
.ZERO
).OR
.( Y
( J
).NE
.ZERO
) )THEN
170 A
( I
, J
) = A
( I
, J
) + X
( I
)*TEMP1
+ Y
( I
)*TEMP2
176 IF( ( X
( JX
).NE
.ZERO
).OR
.( Y
( JY
).NE
.ZERO
) )THEN
177 TEMP1
= ALPHA*Y
( JY
)
178 TEMP2
= ALPHA*X
( JX
)
182 A
( I
, J
) = A
( I
, J
) + X
( IX
)*TEMP1
194 * Form A when A is stored in the lower triangle
.
196 IF( ( INCX
.EQ
.1 ).AND
.( INCY
.EQ
.1 ) )THEN
198 IF( ( X
( J
).NE
.ZERO
).OR
.( Y
( J
).NE
.ZERO
) )THEN
202 A
( I
, J
) = A
( I
, J
) + X
( I
)*TEMP1
+ Y
( I
)*TEMP2
208 IF( ( X
( JX
).NE
.ZERO
).OR
.( Y
( JY
).NE
.ZERO
) )THEN
209 TEMP1
= ALPHA*Y
( JY
)
210 TEMP2
= ALPHA*X
( JX
)
214 A
( I
, J
) = A
( I
, J
) + X
( IX
)*TEMP1