File:
[local] /
rpl /
lapack /
blas /
zhpmv.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 ZHPMV
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 ZHPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
12: *
13: * .. Scalar Arguments ..
14: * COMPLEX*16 ALPHA,BETA
15: * INTEGER INCX,INCY,N
16: * CHARACTER UPLO
17: * ..
18: * .. Array Arguments ..
19: * COMPLEX*16 AP(*),X(*),Y(*)
20: * ..
21: *
22: *
23: *> \par Purpose:
24: * =============
25: *>
26: *> \verbatim
27: *>
28: *> ZHPMV performs the matrix-vector operation
29: *>
30: *> y := alpha*A*x + beta*y,
31: *>
32: *> where alpha and beta are scalars, x and y are n element vectors and
33: *> A is an n by n hermitian matrix, supplied in packed form.
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 matrix A is supplied in the packed
44: *> array AP as follows:
45: *>
46: *> UPLO = 'U' or 'u' The upper triangular part of A is
47: *> supplied in AP.
48: *>
49: *> UPLO = 'L' or 'l' The lower triangular part of A is
50: *> supplied in AP.
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] AP
67: *> \verbatim
68: *> AP is COMPLEX*16 array of DIMENSION at least
69: *> ( ( n*( n + 1 ) )/2 ).
70: *> Before entry with UPLO = 'U' or 'u', the array AP must
71: *> contain the upper triangular part of the hermitian matrix
72: *> packed sequentially, column by column, so that AP( 1 )
73: *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
74: *> and a( 2, 2 ) respectively, and so on.
75: *> Before entry with UPLO = 'L' or 'l', the array AP must
76: *> contain the lower triangular part of the hermitian matrix
77: *> packed sequentially, column by column, so that AP( 1 )
78: *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
79: *> and a( 3, 1 ) respectively, and so on.
80: *> Note that the imaginary parts of the diagonal elements need
81: *> not be set and are assumed to be zero.
82: *> \endverbatim
83: *>
84: *> \param[in] X
85: *> \verbatim
86: *> X is COMPLEX*16 array of dimension at least
87: *> ( 1 + ( n - 1 )*abs( INCX ) ).
88: *> Before entry, the incremented array X must contain the n
89: *> element vector x.
90: *> \endverbatim
91: *>
92: *> \param[in] INCX
93: *> \verbatim
94: *> INCX is INTEGER
95: *> On entry, INCX specifies the increment for the elements of
96: *> X. INCX must not be zero.
97: *> \endverbatim
98: *>
99: *> \param[in] BETA
100: *> \verbatim
101: *> BETA is COMPLEX*16
102: *> On entry, BETA specifies the scalar beta. When BETA is
103: *> supplied as zero then Y need not be set on input.
104: *> \endverbatim
105: *>
106: *> \param[in,out] Y
107: *> \verbatim
108: *> Y is COMPLEX*16 array of dimension at least
109: *> ( 1 + ( n - 1 )*abs( INCY ) ).
110: *> Before entry, the incremented array Y must contain the n
111: *> element vector y. On exit, Y is overwritten by the updated
112: *> vector y.
113: *> \endverbatim
114: *>
115: *> \param[in] INCY
116: *> \verbatim
117: *> INCY is INTEGER
118: *> On entry, INCY specifies the increment for the elements of
119: *> Y. INCY must not be zero.
120: *> \endverbatim
121: *
122: * Authors:
123: * ========
124: *
125: *> \author Univ. of Tennessee
126: *> \author Univ. of California Berkeley
127: *> \author Univ. of Colorado Denver
128: *> \author NAG Ltd.
129: *
130: *> \date November 2011
131: *
132: *> \ingroup complex16_blas_level2
133: *
134: *> \par Further Details:
135: * =====================
136: *>
137: *> \verbatim
138: *>
139: *> Level 2 Blas routine.
140: *> The vector and matrix arguments are not referenced when N = 0, or M = 0
141: *>
142: *> -- Written on 22-October-1986.
143: *> Jack Dongarra, Argonne National Lab.
144: *> Jeremy Du Croz, Nag Central Office.
145: *> Sven Hammarling, Nag Central Office.
146: *> Richard Hanson, Sandia National Labs.
147: *> \endverbatim
148: *>
149: * =====================================================================
150: SUBROUTINE ZHPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
151: *
152: * -- Reference BLAS level2 routine (version 3.4.0) --
153: * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
154: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155: * November 2011
156: *
157: * .. Scalar Arguments ..
158: COMPLEX*16 ALPHA,BETA
159: INTEGER INCX,INCY,N
160: CHARACTER UPLO
161: * ..
162: * .. Array Arguments ..
163: COMPLEX*16 AP(*),X(*),Y(*)
164: * ..
165: *
166: * =====================================================================
167: *
168: * .. Parameters ..
169: COMPLEX*16 ONE
170: PARAMETER (ONE= (1.0D+0,0.0D+0))
171: COMPLEX*16 ZERO
172: PARAMETER (ZERO= (0.0D+0,0.0D+0))
173: * ..
174: * .. Local Scalars ..
175: COMPLEX*16 TEMP1,TEMP2
176: INTEGER I,INFO,IX,IY,J,JX,JY,K,KK,KX,KY
177: * ..
178: * .. External Functions ..
179: LOGICAL LSAME
180: EXTERNAL LSAME
181: * ..
182: * .. External Subroutines ..
183: EXTERNAL XERBLA
184: * ..
185: * .. Intrinsic Functions ..
186: INTRINSIC DBLE,DCONJG
187: * ..
188: *
189: * Test the input parameters.
190: *
191: INFO = 0
192: IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
193: INFO = 1
194: ELSE IF (N.LT.0) THEN
195: INFO = 2
196: ELSE IF (INCX.EQ.0) THEN
197: INFO = 6
198: ELSE IF (INCY.EQ.0) THEN
199: INFO = 9
200: END IF
201: IF (INFO.NE.0) THEN
202: CALL XERBLA('ZHPMV ',INFO)
203: RETURN
204: END IF
205: *
206: * Quick return if possible.
207: *
208: IF ((N.EQ.0) .OR. ((ALPHA.EQ.ZERO).AND. (BETA.EQ.ONE))) RETURN
209: *
210: * Set up the start points in X and Y.
211: *
212: IF (INCX.GT.0) THEN
213: KX = 1
214: ELSE
215: KX = 1 - (N-1)*INCX
216: END IF
217: IF (INCY.GT.0) THEN
218: KY = 1
219: ELSE
220: KY = 1 - (N-1)*INCY
221: END IF
222: *
223: * Start the operations. In this version the elements of the array AP
224: * are accessed sequentially with one pass through AP.
225: *
226: * First form y := beta*y.
227: *
228: IF (BETA.NE.ONE) THEN
229: IF (INCY.EQ.1) THEN
230: IF (BETA.EQ.ZERO) THEN
231: DO 10 I = 1,N
232: Y(I) = ZERO
233: 10 CONTINUE
234: ELSE
235: DO 20 I = 1,N
236: Y(I) = BETA*Y(I)
237: 20 CONTINUE
238: END IF
239: ELSE
240: IY = KY
241: IF (BETA.EQ.ZERO) THEN
242: DO 30 I = 1,N
243: Y(IY) = ZERO
244: IY = IY + INCY
245: 30 CONTINUE
246: ELSE
247: DO 40 I = 1,N
248: Y(IY) = BETA*Y(IY)
249: IY = IY + INCY
250: 40 CONTINUE
251: END IF
252: END IF
253: END IF
254: IF (ALPHA.EQ.ZERO) RETURN
255: KK = 1
256: IF (LSAME(UPLO,'U')) THEN
257: *
258: * Form y when AP contains the upper triangle.
259: *
260: IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
261: DO 60 J = 1,N
262: TEMP1 = ALPHA*X(J)
263: TEMP2 = ZERO
264: K = KK
265: DO 50 I = 1,J - 1
266: Y(I) = Y(I) + TEMP1*AP(K)
267: TEMP2 = TEMP2 + DCONJG(AP(K))*X(I)
268: K = K + 1
269: 50 CONTINUE
270: Y(J) = Y(J) + TEMP1*DBLE(AP(KK+J-1)) + ALPHA*TEMP2
271: KK = KK + J
272: 60 CONTINUE
273: ELSE
274: JX = KX
275: JY = KY
276: DO 80 J = 1,N
277: TEMP1 = ALPHA*X(JX)
278: TEMP2 = ZERO
279: IX = KX
280: IY = KY
281: DO 70 K = KK,KK + J - 2
282: Y(IY) = Y(IY) + TEMP1*AP(K)
283: TEMP2 = TEMP2 + DCONJG(AP(K))*X(IX)
284: IX = IX + INCX
285: IY = IY + INCY
286: 70 CONTINUE
287: Y(JY) = Y(JY) + TEMP1*DBLE(AP(KK+J-1)) + ALPHA*TEMP2
288: JX = JX + INCX
289: JY = JY + INCY
290: KK = KK + J
291: 80 CONTINUE
292: END IF
293: ELSE
294: *
295: * Form y when AP contains the lower triangle.
296: *
297: IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
298: DO 100 J = 1,N
299: TEMP1 = ALPHA*X(J)
300: TEMP2 = ZERO
301: Y(J) = Y(J) + TEMP1*DBLE(AP(KK))
302: K = KK + 1
303: DO 90 I = J + 1,N
304: Y(I) = Y(I) + TEMP1*AP(K)
305: TEMP2 = TEMP2 + DCONJG(AP(K))*X(I)
306: K = K + 1
307: 90 CONTINUE
308: Y(J) = Y(J) + ALPHA*TEMP2
309: KK = KK + (N-J+1)
310: 100 CONTINUE
311: ELSE
312: JX = KX
313: JY = KY
314: DO 120 J = 1,N
315: TEMP1 = ALPHA*X(JX)
316: TEMP2 = ZERO
317: Y(JY) = Y(JY) + TEMP1*DBLE(AP(KK))
318: IX = JX
319: IY = JY
320: DO 110 K = KK + 1,KK + N - J
321: IX = IX + INCX
322: IY = IY + INCY
323: Y(IY) = Y(IY) + TEMP1*AP(K)
324: TEMP2 = TEMP2 + DCONJG(AP(K))*X(IX)
325: 110 CONTINUE
326: Y(JY) = Y(JY) + ALPHA*TEMP2
327: JX = JX + INCX
328: JY = JY + INCY
329: KK = KK + (N-J+1)
330: 120 CONTINUE
331: END IF
332: END IF
333: *
334: RETURN
335: *
336: * End of ZHPMV .
337: *
338: END
CVSweb interface <joel.bertrand@systella.fr>