File:
[local] /
rpl /
lapack /
blas /
zher2.f
Revision
1.11:
download - view:
text,
annotated -
select for diffs -
revision graph
Mon Jan 27 09:28:14 2014 UTC (11 years, 3 months ago) by
bertrand
Branches:
MAIN
CVS tags:
rpl-4_1_24,
rpl-4_1_23,
rpl-4_1_22,
rpl-4_1_21,
rpl-4_1_20,
rpl-4_1_19,
rpl-4_1_18,
rpl-4_1_17,
HEAD
Cohérence.
1: *> \brief \b ZHER2
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 ZHER2(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
12: *
13: * .. Scalar Arguments ..
14: * COMPLEX*16 ALPHA
15: * INTEGER INCX,INCY,LDA,N
16: * CHARACTER UPLO
17: * ..
18: * .. Array Arguments ..
19: * COMPLEX*16 A(LDA,*),X(*),Y(*)
20: * ..
21: *
22: *
23: *> \par Purpose:
24: * =============
25: *>
26: *> \verbatim
27: *>
28: *> ZHER2 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*16
63: *> On entry, ALPHA specifies the scalar alpha.
64: *> \endverbatim
65: *>
66: *> \param[in] X
67: *> \verbatim
68: *> X is COMPLEX*16 array of 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*16 array of 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*16 array of 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: *> \date November 2011
133: *
134: *> \ingroup complex16_blas_level2
135: *
136: *> \par Further Details:
137: * =====================
138: *>
139: *> \verbatim
140: *>
141: *> Level 2 Blas routine.
142: *>
143: *> -- Written on 22-October-1986.
144: *> Jack Dongarra, Argonne National Lab.
145: *> Jeremy Du Croz, Nag Central Office.
146: *> Sven Hammarling, Nag Central Office.
147: *> Richard Hanson, Sandia National Labs.
148: *> \endverbatim
149: *>
150: * =====================================================================
151: SUBROUTINE ZHER2(UPLO,N,ALPHA,X,INCX,Y,INCY,A,LDA)
152: *
153: * -- Reference BLAS level2 routine (version 3.4.0) --
154: * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
155: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156: * November 2011
157: *
158: * .. Scalar Arguments ..
159: COMPLEX*16 ALPHA
160: INTEGER INCX,INCY,LDA,N
161: CHARACTER UPLO
162: * ..
163: * .. Array Arguments ..
164: COMPLEX*16 A(LDA,*),X(*),Y(*)
165: * ..
166: *
167: * =====================================================================
168: *
169: * .. Parameters ..
170: COMPLEX*16 ZERO
171: PARAMETER (ZERO= (0.0D+0,0.0D+0))
172: * ..
173: * .. Local Scalars ..
174: COMPLEX*16 TEMP1,TEMP2
175: INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY
176: * ..
177: * .. External Functions ..
178: LOGICAL LSAME
179: EXTERNAL LSAME
180: * ..
181: * .. External Subroutines ..
182: EXTERNAL XERBLA
183: * ..
184: * .. Intrinsic Functions ..
185: INTRINSIC DBLE,DCONJG,MAX
186: * ..
187: *
188: * Test the input parameters.
189: *
190: INFO = 0
191: IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
192: INFO = 1
193: ELSE IF (N.LT.0) THEN
194: INFO = 2
195: ELSE IF (INCX.EQ.0) THEN
196: INFO = 5
197: ELSE IF (INCY.EQ.0) THEN
198: INFO = 7
199: ELSE IF (LDA.LT.MAX(1,N)) THEN
200: INFO = 9
201: END IF
202: IF (INFO.NE.0) THEN
203: CALL XERBLA('ZHER2 ',INFO)
204: RETURN
205: END IF
206: *
207: * Quick return if possible.
208: *
209: IF ((N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN
210: *
211: * Set up the start points in X and Y if the increments are not both
212: * unity.
213: *
214: IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN
215: IF (INCX.GT.0) THEN
216: KX = 1
217: ELSE
218: KX = 1 - (N-1)*INCX
219: END IF
220: IF (INCY.GT.0) THEN
221: KY = 1
222: ELSE
223: KY = 1 - (N-1)*INCY
224: END IF
225: JX = KX
226: JY = KY
227: END IF
228: *
229: * Start the operations. In this version the elements of A are
230: * accessed sequentially with one pass through the triangular part
231: * of A.
232: *
233: IF (LSAME(UPLO,'U')) THEN
234: *
235: * Form A when A is stored in the upper triangle.
236: *
237: IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
238: DO 20 J = 1,N
239: IF ((X(J).NE.ZERO) .OR. (Y(J).NE.ZERO)) THEN
240: TEMP1 = ALPHA*DCONJG(Y(J))
241: TEMP2 = DCONJG(ALPHA*X(J))
242: DO 10 I = 1,J - 1
243: A(I,J) = A(I,J) + X(I)*TEMP1 + Y(I)*TEMP2
244: 10 CONTINUE
245: A(J,J) = DBLE(A(J,J)) +
246: + DBLE(X(J)*TEMP1+Y(J)*TEMP2)
247: ELSE
248: A(J,J) = DBLE(A(J,J))
249: END IF
250: 20 CONTINUE
251: ELSE
252: DO 40 J = 1,N
253: IF ((X(JX).NE.ZERO) .OR. (Y(JY).NE.ZERO)) THEN
254: TEMP1 = ALPHA*DCONJG(Y(JY))
255: TEMP2 = DCONJG(ALPHA*X(JX))
256: IX = KX
257: IY = KY
258: DO 30 I = 1,J - 1
259: A(I,J) = A(I,J) + X(IX)*TEMP1 + Y(IY)*TEMP2
260: IX = IX + INCX
261: IY = IY + INCY
262: 30 CONTINUE
263: A(J,J) = DBLE(A(J,J)) +
264: + DBLE(X(JX)*TEMP1+Y(JY)*TEMP2)
265: ELSE
266: A(J,J) = DBLE(A(J,J))
267: END IF
268: JX = JX + INCX
269: JY = JY + INCY
270: 40 CONTINUE
271: END IF
272: ELSE
273: *
274: * Form A when A is stored in the lower triangle.
275: *
276: IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
277: DO 60 J = 1,N
278: IF ((X(J).NE.ZERO) .OR. (Y(J).NE.ZERO)) THEN
279: TEMP1 = ALPHA*DCONJG(Y(J))
280: TEMP2 = DCONJG(ALPHA*X(J))
281: A(J,J) = DBLE(A(J,J)) +
282: + DBLE(X(J)*TEMP1+Y(J)*TEMP2)
283: DO 50 I = J + 1,N
284: A(I,J) = A(I,J) + X(I)*TEMP1 + Y(I)*TEMP2
285: 50 CONTINUE
286: ELSE
287: A(J,J) = DBLE(A(J,J))
288: END IF
289: 60 CONTINUE
290: ELSE
291: DO 80 J = 1,N
292: IF ((X(JX).NE.ZERO) .OR. (Y(JY).NE.ZERO)) THEN
293: TEMP1 = ALPHA*DCONJG(Y(JY))
294: TEMP2 = DCONJG(ALPHA*X(JX))
295: A(J,J) = DBLE(A(J,J)) +
296: + DBLE(X(JX)*TEMP1+Y(JY)*TEMP2)
297: IX = JX
298: IY = JY
299: DO 70 I = J + 1,N
300: IX = IX + INCX
301: IY = IY + INCY
302: A(I,J) = A(I,J) + X(IX)*TEMP1 + Y(IY)*TEMP2
303: 70 CONTINUE
304: ELSE
305: A(J,J) = DBLE(A(J,J))
306: END IF
307: JX = JX + INCX
308: JY = JY + INCY
309: 80 CONTINUE
310: END IF
311: END IF
312: *
313: RETURN
314: *
315: * End of ZHER2 .
316: *
317: END
CVSweb interface <joel.bertrand@systella.fr>