OpenRadioss
2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cher2.f
Go to the documentation of this file.
1
*> \brief \b CHER2
2
*
3
* =========== DOCUMENTATION ===========
4
*
5
* Online html documentation available at
6
* http://www.netlib.org/lapack/explore-html/
7
*
8
* Definition:
9
* ===========
10
*
11
* SUBROUTINE CHER2(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
12
*
13
* .. Scalar Arguments ..
14
* COMPLEX ALPHA
15
* INTEGER INCX,INCY,LDA,N
16
* CHARACTER UPLO
17
* ..
18
* .. Array Arguments ..
19
* COMPLEX A(LDA,*),X(*),Y(*)
20
* ..
21
*
22
*
23
*> \par Purpose:
24
* =============
25
*>
26
*> \verbatim
27
*>
28
*> CHER2 performs the hermitian rank 2 operation
29
*>
30
*> A := alpha*x*y**H + conjg( alpha )*y*x**H + A,
31
*>
32
*> where alpha is a scalar, x and y are n element vectors and A is an n
33
*> by n hermitian matrix.
34
*> \endverbatim
35
*
36
* Arguments:
37
* ==========
38
*
39
*> \param[in] UPLO
40
*> \verbatim
41
*> UPLO is CHARACTER*1
42
*> On entry, UPLO specifies whether the upper or lower
43
*> triangular part of the array A is to be referenced as
44
*> follows:
45
*>
46
*> UPLO = 'U' or 'u' Only the upper triangular part of A
47
*> is to be referenced.
48
*>
49
*> UPLO = 'L' or 'l' Only the lower triangular part of A
50
*> is to be referenced.
51
*> \endverbatim
52
*>
53
*> \param[in] N
54
*> \verbatim
55
*> N is INTEGER
56
*> On entry, N specifies the order of the matrix A.
57
*> N must be at least zero.
58
*> \endverbatim
59
*>
60
*> \param[in] ALPHA
61
*> \verbatim
62
*> ALPHA is COMPLEX
63
*> On entry, ALPHA specifies the scalar alpha.
64
*> \endverbatim
65
*>
66
*> \param[in] X
67
*> \verbatim
68
*> X is COMPLEX array, dimension at least
69
*> ( 1 + ( n - 1 )*abs( INCX ) ).
70
*> Before entry, the incremented array X must contain the n
71
*> element vector x.
72
*> \endverbatim
73
*>
74
*> \param[in] INCX
75
*> \verbatim
76
*> INCX is INTEGER
77
*> On entry, INCX specifies the increment for the elements of
78
*> X. INCX must not be zero.
79
*> \endverbatim
80
*>
81
*> \param[in] Y
82
*> \verbatim
83
*> Y is COMPLEX array, dimension at least
84
*> ( 1 + ( n - 1 )*abs( INCY ) ).
85
*> Before entry, the incremented array Y must contain the n
86
*> element vector y.
87
*> \endverbatim
88
*>
89
*> \param[in] INCY
90
*> \verbatim
91
*> INCY is INTEGER
92
*> On entry, INCY specifies the increment for the elements of
93
*> Y. INCY must not be zero.
94
*> \endverbatim
95
*>
96
*> \param[in,out] A
97
*> \verbatim
98
*> A is COMPLEX array, dimension ( LDA, N )
99
*> Before entry with UPLO = 'U' or 'u', the leading n by n
100
*> upper triangular part of the array A must contain the upper
101
*> triangular part of the hermitian matrix and the strictly
102
*> lower triangular part of A is not referenced. On exit, the
103
*> upper triangular part of the array A is overwritten by the
104
*> upper triangular part of the updated matrix.
105
*> Before entry with UPLO = 'L' or 'l', the leading n by n
106
*> lower triangular part of the array A must contain the lower
107
*> triangular part of the hermitian matrix and the strictly
108
*> upper triangular part of A is not referenced. On exit, the
109
*> lower triangular part of the array A is overwritten by the
110
*> lower triangular part of the updated matrix.
111
*> Note that the imaginary parts of the diagonal elements need
112
*> not be set, they are assumed to be zero, and on exit they
113
*> are set to zero.
114
*> \endverbatim
115
*>
116
*> \param[in] LDA
117
*> \verbatim
118
*> LDA is INTEGER
119
*> On entry, LDA specifies the first dimension of A as declared
120
*> in the calling (sub) program. LDA must be at least
121
*> max( 1, n ).
122
*> \endverbatim
123
*
124
* Authors:
125
* ========
126
*
127
*> \author Univ. of Tennessee
128
*> \author Univ. of California Berkeley
129
*> \author Univ. of Colorado Denver
130
*> \author NAG Ltd.
131
*
132
*> \ingroup complex_blas_level2
133
*
134
*> \par Further Details:
135
* =====================
136
*>
137
*> \verbatim
138
*>
139
*> Level 2 Blas routine.
140
*>
141
*> -- Written on 22-October-1986.
142
*> Jack Dongarra, Argonne National Lab.
143
*> Jeremy Du Croz, Nag Central Office.
144
*> Sven Hammarling, Nag Central Office.
145
*> Richard Hanson, Sandia National Labs.
146
*> \endverbatim
147
*>
148
* =====================================================================
149
SUBROUTINE
cher2
(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
150
*
151
* -- Reference BLAS level2 routine --
152
* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
153
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
154
*
155
* .. Scalar Arguments ..
156
COMPLEX
ALPHA
157
INTEGER
INCX,INCY,
LDA
,
N
158
CHARACTER
UPLO
159
* ..
160
* .. Array Arguments ..
161
COMPLEX
A
(
LDA
,*),X(*),Y(*)
162
* ..
163
*
164
* =====================================================================
165
*
166
* .. Parameters ..
167
COMPLEX
ZERO
168
parameter
(zero= (0.0e+0,0.0e+0))
169
* ..
170
* .. Local Scalars ..
171
COMPLEX
TEMP1,TEMP2
172
INTEGER
I,INFO,
IX
,IY,J,JX,JY,KX,KY
173
* ..
174
* .. External Functions ..
175
LOGICAL
LSAME
176
EXTERNAL
lsame
177
* ..
178
* .. External Subroutines ..
179
EXTERNAL
xerbla
180
* ..
181
* .. Intrinsic Functions ..
182
INTRINSIC
conjg,
max
,real
183
* ..
184
*
185
* Test the input parameters.
186
*
187
info = 0
188
IF
(.NOT.lsame(uplo,
'U'
) .AND. .NOT.lsame(uplo,
'L'
))
THEN
189
info = 1
190
ELSE
IF
(n.LT.0)
THEN
191
info = 2
192
ELSE
IF
(incx.EQ.0)
THEN
193
info = 5
194
ELSE
IF
(incy.EQ.0)
THEN
195
info = 7
196
ELSE
IF
(lda.LT.
max
(1,n))
THEN
197
info = 9
198
END IF
199
IF
(info.NE.0)
THEN
200
CALL
xerbla
('
cher2
',INFO)
201
RETURN
202
END IF
203
*
204
* Quick return if possible.
205
*
206
.EQ..OR..EQ.
IF ((N0) (ALPHAZERO)) RETURN
207
*
208
* Set up the start points in X and Y if the increments are not both
209
* unity.
210
*
211
.NE..OR..NE.
IF ((INCX1) (INCY1)) THEN
212
.GT.
IF (INCX0) THEN
213
KX = 1
214
ELSE
215
KX = 1 - (N-1)*INCX
216
END IF
217
.GT.
IF (INCY0) THEN
218
KY = 1
219
ELSE
220
KY = 1 - (N-1)*INCY
221
END IF
222
JX = KX
223
JY = KY
224
END IF
225
*
226
* Start the operations. In this version the elements of A are
227
* accessed sequentially with one pass through the triangular part
228
* of A.
229
*
230
IF (LSAME(UPLO,'
u
')) THEN
231
*
232
* Form A when A is stored in the upper triangle.
233
*
234
.EQ..AND..EQ.
IF ((INCX1) (INCY1)) THEN
235
DO 20 J = 1,N
236
.NE..OR..NE.
IF ((X(J)ZERO) (Y(J)ZERO)) THEN
237
TEMP1 = ALPHA*CONJG(Y(J))
238
TEMP2 = CONJG(ALPHA*X(J))
239
DO 10 I = 1,J - 1
240
A(I,J) = A(I,J) + X(I)*TEMP1 + Y(I)*TEMP2
241
10 CONTINUE
242
A(J,J) = REAL(A(J,J)) +
243
+ REAL(X(J)*TEMP1+Y(J)*TEMP2)
244
ELSE
245
A(J,J) = REAL(A(J,J))
246
END IF
247
20 CONTINUE
248
ELSE
249
DO 40 J = 1,N
250
.NE..OR..NE.
IF ((X(JX)ZERO) (Y(JY)ZERO)) THEN
251
TEMP1 = ALPHA*CONJG(Y(JY))
252
TEMP2 = CONJG(ALPHA*X(JX))
253
IX = KX
254
IY = KY
255
DO 30 I = 1,J - 1
256
A(I,J) = A(I,J) + X(IX)*TEMP1 + Y(IY)*TEMP2
257
IX = IX + INCX
258
IY = IY + INCY
259
30 CONTINUE
260
A(J,J) = REAL(A(J,J)) +
261
+ REAL(X(JX)*TEMP1+Y(JY)*TEMP2)
262
ELSE
263
A(J,J) = REAL(A(J,J))
264
END IF
265
JX = JX + INCX
266
JY = JY + INCY
267
40 CONTINUE
268
END IF
269
ELSE
270
*
271
* Form A when A is stored in the lower triangle.
272
*
273
.EQ..AND..EQ.
IF ((INCX1) (INCY1)) THEN
274
DO 60 J = 1,N
275
.NE..OR..NE.
IF ((X(J)ZERO) (Y(J)ZERO)) THEN
276
TEMP1 = ALPHA*CONJG(Y(J))
277
TEMP2 = CONJG(ALPHA*X(J))
278
A(J,J) = REAL(A(J,J)) +
279
+ REAL(X(J)*TEMP1+Y(J)*TEMP2)
280
DO 50 I = J + 1,N
281
A(I,J) = A(I,J) + X(I)*TEMP1 + Y(I)*TEMP2
282
50 CONTINUE
283
ELSE
284
A(J,J) = REAL(A(J,J))
285
END IF
286
60 CONTINUE
287
ELSE
288
DO 80 J = 1,N
289
.NE..OR..NE.
IF ((X(JX)ZERO) (Y(JY)ZERO)) THEN
290
TEMP1 = ALPHA*CONJG(Y(JY))
291
TEMP2 = CONJG(ALPHA*X(JX))
292
A(J,J) = REAL(A(J,J)) +
293
+ REAL(X(JX)*TEMP1+Y(JY)*TEMP2)
294
IX = JX
295
IY = JY
296
DO 70 I = J + 1,N
297
IX = IX + INCX
298
IY = IY + INCY
299
A(I,J) = A(I,J) + X(IX)*TEMP1 + Y(IY)*TEMP2
300
70 CONTINUE
301
ELSE
302
A(J,J) = REAL(A(J,J))
303
END IF
304
JX = JX + INCX
305
JY = JY + INCY
306
80 CONTINUE
307
END IF
308
END IF
309
*
310
RETURN
311
*
312
* End of CHER2
313
*
314
END
xerbla
subroutine xerbla(srname, info)
XERBLA
Definition
xerbla.f:60
cher2
subroutine cher2(uplo, n, alpha, x, incx, y, incy, a, lda)
CHER2
Definition
cher2.f:150
max
#define max(a, b)
Definition
macros.h:21
engine
extlib
lapack-3.10.1
BLAS
SRC
cher2.f
Generated by
1.15.0