root / src / blas / chpr2.f @ 5
Historique | Voir | Annoter | Télécharger (8,02 ko)
1 | 1 | pfleura2 | SUBROUTINE CHPR2(UPLO,N,ALPHA,X,INCX,Y,INCY,AP) |
---|---|---|---|
2 | 1 | pfleura2 | * .. Scalar Arguments .. |
3 | 1 | pfleura2 | COMPLEX ALPHA |
4 | 1 | pfleura2 | INTEGER INCX,INCY,N |
5 | 1 | pfleura2 | CHARACTER UPLO |
6 | 1 | pfleura2 | * .. |
7 | 1 | pfleura2 | * .. Array Arguments .. |
8 | 1 | pfleura2 | COMPLEX AP(*),X(*),Y(*) |
9 | 1 | pfleura2 | * .. |
10 | 1 | pfleura2 | * |
11 | 1 | pfleura2 | * Purpose |
12 | 1 | pfleura2 | * ======= |
13 | 1 | pfleura2 | * |
14 | 1 | pfleura2 | * CHPR2 performs the hermitian rank 2 operation |
15 | 1 | pfleura2 | * |
16 | 1 | pfleura2 | * A := alpha*x*conjg( y' ) + conjg( alpha )*y*conjg( x' ) + A, |
17 | 1 | pfleura2 | * |
18 | 1 | pfleura2 | * where alpha is a scalar, x and y are n element vectors and A is an |
19 | 1 | pfleura2 | * n by n hermitian matrix, supplied in packed form. |
20 | 1 | pfleura2 | * |
21 | 1 | pfleura2 | * Arguments |
22 | 1 | pfleura2 | * ========== |
23 | 1 | pfleura2 | * |
24 | 1 | pfleura2 | * UPLO - CHARACTER*1. |
25 | 1 | pfleura2 | * On entry, UPLO specifies whether the upper or lower |
26 | 1 | pfleura2 | * triangular part of the matrix A is supplied in the packed |
27 | 1 | pfleura2 | * array AP as follows: |
28 | 1 | pfleura2 | * |
29 | 1 | pfleura2 | * UPLO = 'U' or 'u' The upper triangular part of A is |
30 | 1 | pfleura2 | * supplied in AP. |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * UPLO = 'L' or 'l' The lower triangular part of A is |
33 | 1 | pfleura2 | * supplied in AP. |
34 | 1 | pfleura2 | * |
35 | 1 | pfleura2 | * Unchanged on exit. |
36 | 1 | pfleura2 | * |
37 | 1 | pfleura2 | * N - INTEGER. |
38 | 1 | pfleura2 | * On entry, N specifies the order of the matrix A. |
39 | 1 | pfleura2 | * N must be at least zero. |
40 | 1 | pfleura2 | * Unchanged on exit. |
41 | 1 | pfleura2 | * |
42 | 1 | pfleura2 | * ALPHA - COMPLEX . |
43 | 1 | pfleura2 | * On entry, ALPHA specifies the scalar alpha. |
44 | 1 | pfleura2 | * Unchanged on exit. |
45 | 1 | pfleura2 | * |
46 | 1 | pfleura2 | * X - COMPLEX array of dimension at least |
47 | 1 | pfleura2 | * ( 1 + ( n - 1 )*abs( INCX ) ). |
48 | 1 | pfleura2 | * Before entry, the incremented array X must contain the n |
49 | 1 | pfleura2 | * element vector x. |
50 | 1 | pfleura2 | * Unchanged on exit. |
51 | 1 | pfleura2 | * |
52 | 1 | pfleura2 | * INCX - INTEGER. |
53 | 1 | pfleura2 | * On entry, INCX specifies the increment for the elements of |
54 | 1 | pfleura2 | * X. INCX must not be zero. |
55 | 1 | pfleura2 | * Unchanged on exit. |
56 | 1 | pfleura2 | * |
57 | 1 | pfleura2 | * Y - COMPLEX array of dimension at least |
58 | 1 | pfleura2 | * ( 1 + ( n - 1 )*abs( INCY ) ). |
59 | 1 | pfleura2 | * Before entry, the incremented array Y must contain the n |
60 | 1 | pfleura2 | * element vector y. |
61 | 1 | pfleura2 | * Unchanged on exit. |
62 | 1 | pfleura2 | * |
63 | 1 | pfleura2 | * INCY - INTEGER. |
64 | 1 | pfleura2 | * On entry, INCY specifies the increment for the elements of |
65 | 1 | pfleura2 | * Y. INCY must not be zero. |
66 | 1 | pfleura2 | * Unchanged on exit. |
67 | 1 | pfleura2 | * |
68 | 1 | pfleura2 | * AP - COMPLEX array of DIMENSION at least |
69 | 1 | pfleura2 | * ( ( n*( n + 1 ) )/2 ). |
70 | 1 | pfleura2 | * Before entry with UPLO = 'U' or 'u', the array AP must |
71 | 1 | pfleura2 | * contain the upper triangular part of the hermitian matrix |
72 | 1 | pfleura2 | * packed sequentially, column by column, so that AP( 1 ) |
73 | 1 | pfleura2 | * contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 ) |
74 | 1 | pfleura2 | * and a( 2, 2 ) respectively, and so on. On exit, the array |
75 | 1 | pfleura2 | * AP is overwritten by the upper triangular part of the |
76 | 1 | pfleura2 | * updated matrix. |
77 | 1 | pfleura2 | * Before entry with UPLO = 'L' or 'l', the array AP must |
78 | 1 | pfleura2 | * contain the lower triangular part of the hermitian matrix |
79 | 1 | pfleura2 | * packed sequentially, column by column, so that AP( 1 ) |
80 | 1 | pfleura2 | * contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 ) |
81 | 1 | pfleura2 | * and a( 3, 1 ) respectively, and so on. On exit, the array |
82 | 1 | pfleura2 | * AP is overwritten by the lower triangular part of the |
83 | 1 | pfleura2 | * updated matrix. |
84 | 1 | pfleura2 | * Note that the imaginary parts of the diagonal elements need |
85 | 1 | pfleura2 | * not be set, they are assumed to be zero, and on exit they |
86 | 1 | pfleura2 | * are set to zero. |
87 | 1 | pfleura2 | * |
88 | 1 | pfleura2 | * |
89 | 1 | pfleura2 | * Level 2 Blas routine. |
90 | 1 | pfleura2 | * |
91 | 1 | pfleura2 | * -- Written on 22-October-1986. |
92 | 1 | pfleura2 | * Jack Dongarra, Argonne National Lab. |
93 | 1 | pfleura2 | * Jeremy Du Croz, Nag Central Office. |
94 | 1 | pfleura2 | * Sven Hammarling, Nag Central Office. |
95 | 1 | pfleura2 | * Richard Hanson, Sandia National Labs. |
96 | 1 | pfleura2 | * |
97 | 1 | pfleura2 | * |
98 | 1 | pfleura2 | * .. Parameters .. |
99 | 1 | pfleura2 | COMPLEX ZERO |
100 | 1 | pfleura2 | PARAMETER (ZERO= (0.0E+0,0.0E+0)) |
101 | 1 | pfleura2 | * .. |
102 | 1 | pfleura2 | * .. Local Scalars .. |
103 | 1 | pfleura2 | COMPLEX TEMP1,TEMP2 |
104 | 1 | pfleura2 | INTEGER I,INFO,IX,IY,J,JX,JY,K,KK,KX,KY |
105 | 1 | pfleura2 | * .. |
106 | 1 | pfleura2 | * .. External Functions .. |
107 | 1 | pfleura2 | LOGICAL LSAME |
108 | 1 | pfleura2 | EXTERNAL LSAME |
109 | 1 | pfleura2 | * .. |
110 | 1 | pfleura2 | * .. External Subroutines .. |
111 | 1 | pfleura2 | EXTERNAL XERBLA |
112 | 1 | pfleura2 | * .. |
113 | 1 | pfleura2 | * .. Intrinsic Functions .. |
114 | 1 | pfleura2 | INTRINSIC CONJG,REAL |
115 | 1 | pfleura2 | * .. |
116 | 1 | pfleura2 | * |
117 | 1 | pfleura2 | * Test the input parameters. |
118 | 1 | pfleura2 | * |
119 | 1 | pfleura2 | INFO = 0 |
120 | 1 | pfleura2 | IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN |
121 | 1 | pfleura2 | INFO = 1 |
122 | 1 | pfleura2 | ELSE IF (N.LT.0) THEN |
123 | 1 | pfleura2 | INFO = 2 |
124 | 1 | pfleura2 | ELSE IF (INCX.EQ.0) THEN |
125 | 1 | pfleura2 | INFO = 5 |
126 | 1 | pfleura2 | ELSE IF (INCY.EQ.0) THEN |
127 | 1 | pfleura2 | INFO = 7 |
128 | 1 | pfleura2 | END IF |
129 | 1 | pfleura2 | IF (INFO.NE.0) THEN |
130 | 1 | pfleura2 | CALL XERBLA('CHPR2 ',INFO) |
131 | 1 | pfleura2 | RETURN |
132 | 1 | pfleura2 | END IF |
133 | 1 | pfleura2 | * |
134 | 1 | pfleura2 | * Quick return if possible. |
135 | 1 | pfleura2 | * |
136 | 1 | pfleura2 | IF ((N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN |
137 | 1 | pfleura2 | * |
138 | 1 | pfleura2 | * Set up the start points in X and Y if the increments are not both |
139 | 1 | pfleura2 | * unity. |
140 | 1 | pfleura2 | * |
141 | 1 | pfleura2 | IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN |
142 | 1 | pfleura2 | IF (INCX.GT.0) THEN |
143 | 1 | pfleura2 | KX = 1 |
144 | 1 | pfleura2 | ELSE |
145 | 1 | pfleura2 | KX = 1 - (N-1)*INCX |
146 | 1 | pfleura2 | END IF |
147 | 1 | pfleura2 | IF (INCY.GT.0) THEN |
148 | 1 | pfleura2 | KY = 1 |
149 | 1 | pfleura2 | ELSE |
150 | 1 | pfleura2 | KY = 1 - (N-1)*INCY |
151 | 1 | pfleura2 | END IF |
152 | 1 | pfleura2 | JX = KX |
153 | 1 | pfleura2 | JY = KY |
154 | 1 | pfleura2 | END IF |
155 | 1 | pfleura2 | * |
156 | 1 | pfleura2 | * Start the operations. In this version the elements of the array AP |
157 | 1 | pfleura2 | * are accessed sequentially with one pass through AP. |
158 | 1 | pfleura2 | * |
159 | 1 | pfleura2 | KK = 1 |
160 | 1 | pfleura2 | IF (LSAME(UPLO,'U')) THEN |
161 | 1 | pfleura2 | * |
162 | 1 | pfleura2 | * Form A when upper triangle is stored in AP. |
163 | 1 | pfleura2 | * |
164 | 1 | pfleura2 | IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN |
165 | 1 | pfleura2 | DO 20 J = 1,N |
166 | 1 | pfleura2 | IF ((X(J).NE.ZERO) .OR. (Y(J).NE.ZERO)) THEN |
167 | 1 | pfleura2 | TEMP1 = ALPHA*CONJG(Y(J)) |
168 | 1 | pfleura2 | TEMP2 = CONJG(ALPHA*X(J)) |
169 | 1 | pfleura2 | K = KK |
170 | 1 | pfleura2 | DO 10 I = 1,J - 1 |
171 | 1 | pfleura2 | AP(K) = AP(K) + X(I)*TEMP1 + Y(I)*TEMP2 |
172 | 1 | pfleura2 | K = K + 1 |
173 | 1 | pfleura2 | 10 CONTINUE |
174 | 1 | pfleura2 | AP(KK+J-1) = REAL(AP(KK+J-1)) + |
175 | 1 | pfleura2 | + REAL(X(J)*TEMP1+Y(J)*TEMP2) |
176 | 1 | pfleura2 | ELSE |
177 | 1 | pfleura2 | AP(KK+J-1) = REAL(AP(KK+J-1)) |
178 | 1 | pfleura2 | END IF |
179 | 1 | pfleura2 | KK = KK + J |
180 | 1 | pfleura2 | 20 CONTINUE |
181 | 1 | pfleura2 | ELSE |
182 | 1 | pfleura2 | DO 40 J = 1,N |
183 | 1 | pfleura2 | IF ((X(JX).NE.ZERO) .OR. (Y(JY).NE.ZERO)) THEN |
184 | 1 | pfleura2 | TEMP1 = ALPHA*CONJG(Y(JY)) |
185 | 1 | pfleura2 | TEMP2 = CONJG(ALPHA*X(JX)) |
186 | 1 | pfleura2 | IX = KX |
187 | 1 | pfleura2 | IY = KY |
188 | 1 | pfleura2 | DO 30 K = KK,KK + J - 2 |
189 | 1 | pfleura2 | AP(K) = AP(K) + X(IX)*TEMP1 + Y(IY)*TEMP2 |
190 | 1 | pfleura2 | IX = IX + INCX |
191 | 1 | pfleura2 | IY = IY + INCY |
192 | 1 | pfleura2 | 30 CONTINUE |
193 | 1 | pfleura2 | AP(KK+J-1) = REAL(AP(KK+J-1)) + |
194 | 1 | pfleura2 | + REAL(X(JX)*TEMP1+Y(JY)*TEMP2) |
195 | 1 | pfleura2 | ELSE |
196 | 1 | pfleura2 | AP(KK+J-1) = REAL(AP(KK+J-1)) |
197 | 1 | pfleura2 | END IF |
198 | 1 | pfleura2 | JX = JX + INCX |
199 | 1 | pfleura2 | JY = JY + INCY |
200 | 1 | pfleura2 | KK = KK + J |
201 | 1 | pfleura2 | 40 CONTINUE |
202 | 1 | pfleura2 | END IF |
203 | 1 | pfleura2 | ELSE |
204 | 1 | pfleura2 | * |
205 | 1 | pfleura2 | * Form A when lower triangle is stored in AP. |
206 | 1 | pfleura2 | * |
207 | 1 | pfleura2 | IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN |
208 | 1 | pfleura2 | DO 60 J = 1,N |
209 | 1 | pfleura2 | IF ((X(J).NE.ZERO) .OR. (Y(J).NE.ZERO)) THEN |
210 | 1 | pfleura2 | TEMP1 = ALPHA*CONJG(Y(J)) |
211 | 1 | pfleura2 | TEMP2 = CONJG(ALPHA*X(J)) |
212 | 1 | pfleura2 | AP(KK) = REAL(AP(KK)) + |
213 | 1 | pfleura2 | + REAL(X(J)*TEMP1+Y(J)*TEMP2) |
214 | 1 | pfleura2 | K = KK + 1 |
215 | 1 | pfleura2 | DO 50 I = J + 1,N |
216 | 1 | pfleura2 | AP(K) = AP(K) + X(I)*TEMP1 + Y(I)*TEMP2 |
217 | 1 | pfleura2 | K = K + 1 |
218 | 1 | pfleura2 | 50 CONTINUE |
219 | 1 | pfleura2 | ELSE |
220 | 1 | pfleura2 | AP(KK) = REAL(AP(KK)) |
221 | 1 | pfleura2 | END IF |
222 | 1 | pfleura2 | KK = KK + N - J + 1 |
223 | 1 | pfleura2 | 60 CONTINUE |
224 | 1 | pfleura2 | ELSE |
225 | 1 | pfleura2 | DO 80 J = 1,N |
226 | 1 | pfleura2 | IF ((X(JX).NE.ZERO) .OR. (Y(JY).NE.ZERO)) THEN |
227 | 1 | pfleura2 | TEMP1 = ALPHA*CONJG(Y(JY)) |
228 | 1 | pfleura2 | TEMP2 = CONJG(ALPHA*X(JX)) |
229 | 1 | pfleura2 | AP(KK) = REAL(AP(KK)) + |
230 | 1 | pfleura2 | + REAL(X(JX)*TEMP1+Y(JY)*TEMP2) |
231 | 1 | pfleura2 | IX = JX |
232 | 1 | pfleura2 | IY = JY |
233 | 1 | pfleura2 | DO 70 K = KK + 1,KK + N - J |
234 | 1 | pfleura2 | IX = IX + INCX |
235 | 1 | pfleura2 | IY = IY + INCY |
236 | 1 | pfleura2 | AP(K) = AP(K) + X(IX)*TEMP1 + Y(IY)*TEMP2 |
237 | 1 | pfleura2 | 70 CONTINUE |
238 | 1 | pfleura2 | ELSE |
239 | 1 | pfleura2 | AP(KK) = REAL(AP(KK)) |
240 | 1 | pfleura2 | END IF |
241 | 1 | pfleura2 | JX = JX + INCX |
242 | 1 | pfleura2 | JY = JY + INCY |
243 | 1 | pfleura2 | KK = KK + N - J + 1 |
244 | 1 | pfleura2 | 80 CONTINUE |
245 | 1 | pfleura2 | END IF |
246 | 1 | pfleura2 | END IF |
247 | 1 | pfleura2 | * |
248 | 1 | pfleura2 | RETURN |
249 | 1 | pfleura2 | * |
250 | 1 | pfleura2 | * End of CHPR2 . |
251 | 1 | pfleura2 | * |
252 | 1 | pfleura2 | END |