root / src / blas / ctrmm.f @ 10
Historique | Voir | Annoter | Télécharger (12,61 ko)
1 | 1 | pfleura2 | SUBROUTINE CTRMM(SIDE,UPLO,TRANSA,DIAG,M,N,ALPHA,A,LDA,B,LDB) |
---|---|---|---|
2 | 1 | pfleura2 | * .. Scalar Arguments .. |
3 | 1 | pfleura2 | COMPLEX ALPHA |
4 | 1 | pfleura2 | INTEGER LDA,LDB,M,N |
5 | 1 | pfleura2 | CHARACTER DIAG,SIDE,TRANSA,UPLO |
6 | 1 | pfleura2 | * .. |
7 | 1 | pfleura2 | * .. Array Arguments .. |
8 | 1 | pfleura2 | COMPLEX A(LDA,*),B(LDB,*) |
9 | 1 | pfleura2 | * .. |
10 | 1 | pfleura2 | * |
11 | 1 | pfleura2 | * Purpose |
12 | 1 | pfleura2 | * ======= |
13 | 1 | pfleura2 | * |
14 | 1 | pfleura2 | * CTRMM performs one of the matrix-matrix operations |
15 | 1 | pfleura2 | * |
16 | 1 | pfleura2 | * B := alpha*op( A )*B, or B := alpha*B*op( A ) |
17 | 1 | pfleura2 | * |
18 | 1 | pfleura2 | * where alpha is a scalar, B is an m by n matrix, A is a unit, or |
19 | 1 | pfleura2 | * non-unit, upper or lower triangular matrix and op( A ) is one of |
20 | 1 | pfleura2 | * |
21 | 1 | pfleura2 | * op( A ) = A or op( A ) = A' or op( A ) = conjg( A' ). |
22 | 1 | pfleura2 | * |
23 | 1 | pfleura2 | * Arguments |
24 | 1 | pfleura2 | * ========== |
25 | 1 | pfleura2 | * |
26 | 1 | pfleura2 | * SIDE - CHARACTER*1. |
27 | 1 | pfleura2 | * On entry, SIDE specifies whether op( A ) multiplies B from |
28 | 1 | pfleura2 | * the left or right as follows: |
29 | 1 | pfleura2 | * |
30 | 1 | pfleura2 | * SIDE = 'L' or 'l' B := alpha*op( A )*B. |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * SIDE = 'R' or 'r' B := alpha*B*op( A ). |
33 | 1 | pfleura2 | * |
34 | 1 | pfleura2 | * Unchanged on exit. |
35 | 1 | pfleura2 | * |
36 | 1 | pfleura2 | * UPLO - CHARACTER*1. |
37 | 1 | pfleura2 | * On entry, UPLO specifies whether the matrix A is an upper or |
38 | 1 | pfleura2 | * lower triangular matrix as follows: |
39 | 1 | pfleura2 | * |
40 | 1 | pfleura2 | * UPLO = 'U' or 'u' A is an upper triangular matrix. |
41 | 1 | pfleura2 | * |
42 | 1 | pfleura2 | * UPLO = 'L' or 'l' A is a lower triangular matrix. |
43 | 1 | pfleura2 | * |
44 | 1 | pfleura2 | * Unchanged on exit. |
45 | 1 | pfleura2 | * |
46 | 1 | pfleura2 | * TRANSA - CHARACTER*1. |
47 | 1 | pfleura2 | * On entry, TRANSA specifies the form of op( A ) to be used in |
48 | 1 | pfleura2 | * the matrix multiplication as follows: |
49 | 1 | pfleura2 | * |
50 | 1 | pfleura2 | * TRANSA = 'N' or 'n' op( A ) = A. |
51 | 1 | pfleura2 | * |
52 | 1 | pfleura2 | * TRANSA = 'T' or 't' op( A ) = A'. |
53 | 1 | pfleura2 | * |
54 | 1 | pfleura2 | * TRANSA = 'C' or 'c' op( A ) = conjg( A' ). |
55 | 1 | pfleura2 | * |
56 | 1 | pfleura2 | * Unchanged on exit. |
57 | 1 | pfleura2 | * |
58 | 1 | pfleura2 | * DIAG - CHARACTER*1. |
59 | 1 | pfleura2 | * On entry, DIAG specifies whether or not A is unit triangular |
60 | 1 | pfleura2 | * as follows: |
61 | 1 | pfleura2 | * |
62 | 1 | pfleura2 | * DIAG = 'U' or 'u' A is assumed to be unit triangular. |
63 | 1 | pfleura2 | * |
64 | 1 | pfleura2 | * DIAG = 'N' or 'n' A is not assumed to be unit |
65 | 1 | pfleura2 | * triangular. |
66 | 1 | pfleura2 | * |
67 | 1 | pfleura2 | * Unchanged on exit. |
68 | 1 | pfleura2 | * |
69 | 1 | pfleura2 | * M - INTEGER. |
70 | 1 | pfleura2 | * On entry, M specifies the number of rows of B. M must be at |
71 | 1 | pfleura2 | * least zero. |
72 | 1 | pfleura2 | * Unchanged on exit. |
73 | 1 | pfleura2 | * |
74 | 1 | pfleura2 | * N - INTEGER. |
75 | 1 | pfleura2 | * On entry, N specifies the number of columns of B. N must be |
76 | 1 | pfleura2 | * at least zero. |
77 | 1 | pfleura2 | * Unchanged on exit. |
78 | 1 | pfleura2 | * |
79 | 1 | pfleura2 | * ALPHA - COMPLEX . |
80 | 1 | pfleura2 | * On entry, ALPHA specifies the scalar alpha. When alpha is |
81 | 1 | pfleura2 | * zero then A is not referenced and B need not be set before |
82 | 1 | pfleura2 | * entry. |
83 | 1 | pfleura2 | * Unchanged on exit. |
84 | 1 | pfleura2 | * |
85 | 1 | pfleura2 | * A - COMPLEX array of DIMENSION ( LDA, k ), where k is m |
86 | 1 | pfleura2 | * when SIDE = 'L' or 'l' and is n when SIDE = 'R' or 'r'. |
87 | 1 | pfleura2 | * Before entry with UPLO = 'U' or 'u', the leading k by k |
88 | 1 | pfleura2 | * upper triangular part of the array A must contain the upper |
89 | 1 | pfleura2 | * triangular matrix and the strictly lower triangular part of |
90 | 1 | pfleura2 | * A is not referenced. |
91 | 1 | pfleura2 | * Before entry with UPLO = 'L' or 'l', the leading k by k |
92 | 1 | pfleura2 | * lower triangular part of the array A must contain the lower |
93 | 1 | pfleura2 | * triangular matrix and the strictly upper triangular part of |
94 | 1 | pfleura2 | * A is not referenced. |
95 | 1 | pfleura2 | * Note that when DIAG = 'U' or 'u', the diagonal elements of |
96 | 1 | pfleura2 | * A are not referenced either, but are assumed to be unity. |
97 | 1 | pfleura2 | * Unchanged on exit. |
98 | 1 | pfleura2 | * |
99 | 1 | pfleura2 | * LDA - INTEGER. |
100 | 1 | pfleura2 | * On entry, LDA specifies the first dimension of A as declared |
101 | 1 | pfleura2 | * in the calling (sub) program. When SIDE = 'L' or 'l' then |
102 | 1 | pfleura2 | * LDA must be at least max( 1, m ), when SIDE = 'R' or 'r' |
103 | 1 | pfleura2 | * then LDA must be at least max( 1, n ). |
104 | 1 | pfleura2 | * Unchanged on exit. |
105 | 1 | pfleura2 | * |
106 | 1 | pfleura2 | * B - COMPLEX array of DIMENSION ( LDB, n ). |
107 | 1 | pfleura2 | * Before entry, the leading m by n part of the array B must |
108 | 1 | pfleura2 | * contain the matrix B, and on exit is overwritten by the |
109 | 1 | pfleura2 | * transformed matrix. |
110 | 1 | pfleura2 | * |
111 | 1 | pfleura2 | * LDB - INTEGER. |
112 | 1 | pfleura2 | * On entry, LDB specifies the first dimension of B as declared |
113 | 1 | pfleura2 | * in the calling (sub) program. LDB must be at least |
114 | 1 | pfleura2 | * max( 1, m ). |
115 | 1 | pfleura2 | * Unchanged on exit. |
116 | 1 | pfleura2 | * |
117 | 1 | pfleura2 | * |
118 | 1 | pfleura2 | * Level 3 Blas routine. |
119 | 1 | pfleura2 | * |
120 | 1 | pfleura2 | * -- Written on 8-February-1989. |
121 | 1 | pfleura2 | * Jack Dongarra, Argonne National Laboratory. |
122 | 1 | pfleura2 | * Iain Duff, AERE Harwell. |
123 | 1 | pfleura2 | * Jeremy Du Croz, Numerical Algorithms Group Ltd. |
124 | 1 | pfleura2 | * Sven Hammarling, Numerical Algorithms Group Ltd. |
125 | 1 | pfleura2 | * |
126 | 1 | pfleura2 | * |
127 | 1 | pfleura2 | * .. External Functions .. |
128 | 1 | pfleura2 | LOGICAL LSAME |
129 | 1 | pfleura2 | EXTERNAL LSAME |
130 | 1 | pfleura2 | * .. |
131 | 1 | pfleura2 | * .. External Subroutines .. |
132 | 1 | pfleura2 | EXTERNAL XERBLA |
133 | 1 | pfleura2 | * .. |
134 | 1 | pfleura2 | * .. Intrinsic Functions .. |
135 | 1 | pfleura2 | INTRINSIC CONJG,MAX |
136 | 1 | pfleura2 | * .. |
137 | 1 | pfleura2 | * .. Local Scalars .. |
138 | 1 | pfleura2 | COMPLEX TEMP |
139 | 1 | pfleura2 | INTEGER I,INFO,J,K,NROWA |
140 | 1 | pfleura2 | LOGICAL LSIDE,NOCONJ,NOUNIT,UPPER |
141 | 1 | pfleura2 | * .. |
142 | 1 | pfleura2 | * .. Parameters .. |
143 | 1 | pfleura2 | COMPLEX ONE |
144 | 1 | pfleura2 | PARAMETER (ONE= (1.0E+0,0.0E+0)) |
145 | 1 | pfleura2 | COMPLEX ZERO |
146 | 1 | pfleura2 | PARAMETER (ZERO= (0.0E+0,0.0E+0)) |
147 | 1 | pfleura2 | * .. |
148 | 1 | pfleura2 | * |
149 | 1 | pfleura2 | * Test the input parameters. |
150 | 1 | pfleura2 | * |
151 | 1 | pfleura2 | LSIDE = LSAME(SIDE,'L') |
152 | 1 | pfleura2 | IF (LSIDE) THEN |
153 | 1 | pfleura2 | NROWA = M |
154 | 1 | pfleura2 | ELSE |
155 | 1 | pfleura2 | NROWA = N |
156 | 1 | pfleura2 | END IF |
157 | 1 | pfleura2 | NOCONJ = LSAME(TRANSA,'T') |
158 | 1 | pfleura2 | NOUNIT = LSAME(DIAG,'N') |
159 | 1 | pfleura2 | UPPER = LSAME(UPLO,'U') |
160 | 1 | pfleura2 | * |
161 | 1 | pfleura2 | INFO = 0 |
162 | 1 | pfleura2 | IF ((.NOT.LSIDE) .AND. (.NOT.LSAME(SIDE,'R'))) THEN |
163 | 1 | pfleura2 | INFO = 1 |
164 | 1 | pfleura2 | ELSE IF ((.NOT.UPPER) .AND. (.NOT.LSAME(UPLO,'L'))) THEN |
165 | 1 | pfleura2 | INFO = 2 |
166 | 1 | pfleura2 | ELSE IF ((.NOT.LSAME(TRANSA,'N')) .AND. |
167 | 1 | pfleura2 | + (.NOT.LSAME(TRANSA,'T')) .AND. |
168 | 1 | pfleura2 | + (.NOT.LSAME(TRANSA,'C'))) THEN |
169 | 1 | pfleura2 | INFO = 3 |
170 | 1 | pfleura2 | ELSE IF ((.NOT.LSAME(DIAG,'U')) .AND. (.NOT.LSAME(DIAG,'N'))) THEN |
171 | 1 | pfleura2 | INFO = 4 |
172 | 1 | pfleura2 | ELSE IF (M.LT.0) THEN |
173 | 1 | pfleura2 | INFO = 5 |
174 | 1 | pfleura2 | ELSE IF (N.LT.0) THEN |
175 | 1 | pfleura2 | INFO = 6 |
176 | 1 | pfleura2 | ELSE IF (LDA.LT.MAX(1,NROWA)) THEN |
177 | 1 | pfleura2 | INFO = 9 |
178 | 1 | pfleura2 | ELSE IF (LDB.LT.MAX(1,M)) THEN |
179 | 1 | pfleura2 | INFO = 11 |
180 | 1 | pfleura2 | END IF |
181 | 1 | pfleura2 | IF (INFO.NE.0) THEN |
182 | 1 | pfleura2 | CALL XERBLA('CTRMM ',INFO) |
183 | 1 | pfleura2 | RETURN |
184 | 1 | pfleura2 | END IF |
185 | 1 | pfleura2 | * |
186 | 1 | pfleura2 | * Quick return if possible. |
187 | 1 | pfleura2 | * |
188 | 1 | pfleura2 | IF (M.EQ.0 .OR. N.EQ.0) RETURN |
189 | 1 | pfleura2 | * |
190 | 1 | pfleura2 | * And when alpha.eq.zero. |
191 | 1 | pfleura2 | * |
192 | 1 | pfleura2 | IF (ALPHA.EQ.ZERO) THEN |
193 | 1 | pfleura2 | DO 20 J = 1,N |
194 | 1 | pfleura2 | DO 10 I = 1,M |
195 | 1 | pfleura2 | B(I,J) = ZERO |
196 | 1 | pfleura2 | 10 CONTINUE |
197 | 1 | pfleura2 | 20 CONTINUE |
198 | 1 | pfleura2 | RETURN |
199 | 1 | pfleura2 | END IF |
200 | 1 | pfleura2 | * |
201 | 1 | pfleura2 | * Start the operations. |
202 | 1 | pfleura2 | * |
203 | 1 | pfleura2 | IF (LSIDE) THEN |
204 | 1 | pfleura2 | IF (LSAME(TRANSA,'N')) THEN |
205 | 1 | pfleura2 | * |
206 | 1 | pfleura2 | * Form B := alpha*A*B. |
207 | 1 | pfleura2 | * |
208 | 1 | pfleura2 | IF (UPPER) THEN |
209 | 1 | pfleura2 | DO 50 J = 1,N |
210 | 1 | pfleura2 | DO 40 K = 1,M |
211 | 1 | pfleura2 | IF (B(K,J).NE.ZERO) THEN |
212 | 1 | pfleura2 | TEMP = ALPHA*B(K,J) |
213 | 1 | pfleura2 | DO 30 I = 1,K - 1 |
214 | 1 | pfleura2 | B(I,J) = B(I,J) + TEMP*A(I,K) |
215 | 1 | pfleura2 | 30 CONTINUE |
216 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*A(K,K) |
217 | 1 | pfleura2 | B(K,J) = TEMP |
218 | 1 | pfleura2 | END IF |
219 | 1 | pfleura2 | 40 CONTINUE |
220 | 1 | pfleura2 | 50 CONTINUE |
221 | 1 | pfleura2 | ELSE |
222 | 1 | pfleura2 | DO 80 J = 1,N |
223 | 1 | pfleura2 | DO 70 K = M,1,-1 |
224 | 1 | pfleura2 | IF (B(K,J).NE.ZERO) THEN |
225 | 1 | pfleura2 | TEMP = ALPHA*B(K,J) |
226 | 1 | pfleura2 | B(K,J) = TEMP |
227 | 1 | pfleura2 | IF (NOUNIT) B(K,J) = B(K,J)*A(K,K) |
228 | 1 | pfleura2 | DO 60 I = K + 1,M |
229 | 1 | pfleura2 | B(I,J) = B(I,J) + TEMP*A(I,K) |
230 | 1 | pfleura2 | 60 CONTINUE |
231 | 1 | pfleura2 | END IF |
232 | 1 | pfleura2 | 70 CONTINUE |
233 | 1 | pfleura2 | 80 CONTINUE |
234 | 1 | pfleura2 | END IF |
235 | 1 | pfleura2 | ELSE |
236 | 1 | pfleura2 | * |
237 | 1 | pfleura2 | * Form B := alpha*A'*B or B := alpha*conjg( A' )*B. |
238 | 1 | pfleura2 | * |
239 | 1 | pfleura2 | IF (UPPER) THEN |
240 | 1 | pfleura2 | DO 120 J = 1,N |
241 | 1 | pfleura2 | DO 110 I = M,1,-1 |
242 | 1 | pfleura2 | TEMP = B(I,J) |
243 | 1 | pfleura2 | IF (NOCONJ) THEN |
244 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*A(I,I) |
245 | 1 | pfleura2 | DO 90 K = 1,I - 1 |
246 | 1 | pfleura2 | TEMP = TEMP + A(K,I)*B(K,J) |
247 | 1 | pfleura2 | 90 CONTINUE |
248 | 1 | pfleura2 | ELSE |
249 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*CONJG(A(I,I)) |
250 | 1 | pfleura2 | DO 100 K = 1,I - 1 |
251 | 1 | pfleura2 | TEMP = TEMP + CONJG(A(K,I))*B(K,J) |
252 | 1 | pfleura2 | 100 CONTINUE |
253 | 1 | pfleura2 | END IF |
254 | 1 | pfleura2 | B(I,J) = ALPHA*TEMP |
255 | 1 | pfleura2 | 110 CONTINUE |
256 | 1 | pfleura2 | 120 CONTINUE |
257 | 1 | pfleura2 | ELSE |
258 | 1 | pfleura2 | DO 160 J = 1,N |
259 | 1 | pfleura2 | DO 150 I = 1,M |
260 | 1 | pfleura2 | TEMP = B(I,J) |
261 | 1 | pfleura2 | IF (NOCONJ) THEN |
262 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*A(I,I) |
263 | 1 | pfleura2 | DO 130 K = I + 1,M |
264 | 1 | pfleura2 | TEMP = TEMP + A(K,I)*B(K,J) |
265 | 1 | pfleura2 | 130 CONTINUE |
266 | 1 | pfleura2 | ELSE |
267 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*CONJG(A(I,I)) |
268 | 1 | pfleura2 | DO 140 K = I + 1,M |
269 | 1 | pfleura2 | TEMP = TEMP + CONJG(A(K,I))*B(K,J) |
270 | 1 | pfleura2 | 140 CONTINUE |
271 | 1 | pfleura2 | END IF |
272 | 1 | pfleura2 | B(I,J) = ALPHA*TEMP |
273 | 1 | pfleura2 | 150 CONTINUE |
274 | 1 | pfleura2 | 160 CONTINUE |
275 | 1 | pfleura2 | END IF |
276 | 1 | pfleura2 | END IF |
277 | 1 | pfleura2 | ELSE |
278 | 1 | pfleura2 | IF (LSAME(TRANSA,'N')) THEN |
279 | 1 | pfleura2 | * |
280 | 1 | pfleura2 | * Form B := alpha*B*A. |
281 | 1 | pfleura2 | * |
282 | 1 | pfleura2 | IF (UPPER) THEN |
283 | 1 | pfleura2 | DO 200 J = N,1,-1 |
284 | 1 | pfleura2 | TEMP = ALPHA |
285 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*A(J,J) |
286 | 1 | pfleura2 | DO 170 I = 1,M |
287 | 1 | pfleura2 | B(I,J) = TEMP*B(I,J) |
288 | 1 | pfleura2 | 170 CONTINUE |
289 | 1 | pfleura2 | DO 190 K = 1,J - 1 |
290 | 1 | pfleura2 | IF (A(K,J).NE.ZERO) THEN |
291 | 1 | pfleura2 | TEMP = ALPHA*A(K,J) |
292 | 1 | pfleura2 | DO 180 I = 1,M |
293 | 1 | pfleura2 | B(I,J) = B(I,J) + TEMP*B(I,K) |
294 | 1 | pfleura2 | 180 CONTINUE |
295 | 1 | pfleura2 | END IF |
296 | 1 | pfleura2 | 190 CONTINUE |
297 | 1 | pfleura2 | 200 CONTINUE |
298 | 1 | pfleura2 | ELSE |
299 | 1 | pfleura2 | DO 240 J = 1,N |
300 | 1 | pfleura2 | TEMP = ALPHA |
301 | 1 | pfleura2 | IF (NOUNIT) TEMP = TEMP*A(J,J) |
302 | 1 | pfleura2 | DO 210 I = 1,M |
303 | 1 | pfleura2 | B(I,J) = TEMP*B(I,J) |
304 | 1 | pfleura2 | 210 CONTINUE |
305 | 1 | pfleura2 | DO 230 K = J + 1,N |
306 | 1 | pfleura2 | IF (A(K,J).NE.ZERO) THEN |
307 | 1 | pfleura2 | TEMP = ALPHA*A(K,J) |
308 | 1 | pfleura2 | DO 220 I = 1,M |
309 | 1 | pfleura2 | B(I,J) = B(I,J) + TEMP*B(I,K) |
310 | 1 | pfleura2 | 220 CONTINUE |
311 | 1 | pfleura2 | END IF |
312 | 1 | pfleura2 | 230 CONTINUE |
313 | 1 | pfleura2 | 240 CONTINUE |
314 | 1 | pfleura2 | END IF |
315 | 1 | pfleura2 | ELSE |
316 | 1 | pfleura2 | * |
317 | 1 | pfleura2 | * Form B := alpha*B*A' or B := alpha*B*conjg( A' ). |
318 | 1 | pfleura2 | * |
319 | 1 | pfleura2 | IF (UPPER) THEN |
320 | 1 | pfleura2 | DO 280 K = 1,N |
321 | 1 | pfleura2 | DO 260 J = 1,K - 1 |
322 | 1 | pfleura2 | IF (A(J,K).NE.ZERO) THEN |
323 | 1 | pfleura2 | IF (NOCONJ) THEN |
324 | 1 | pfleura2 | TEMP = ALPHA*A(J,K) |
325 | 1 | pfleura2 | ELSE |
326 | 1 | pfleura2 | TEMP = ALPHA*CONJG(A(J,K)) |
327 | 1 | pfleura2 | END IF |
328 | 1 | pfleura2 | DO 250 I = 1,M |
329 | 1 | pfleura2 | B(I,J) = B(I,J) + TEMP*B(I,K) |
330 | 1 | pfleura2 | 250 CONTINUE |
331 | 1 | pfleura2 | END IF |
332 | 1 | pfleura2 | 260 CONTINUE |
333 | 1 | pfleura2 | TEMP = ALPHA |
334 | 1 | pfleura2 | IF (NOUNIT) THEN |
335 | 1 | pfleura2 | IF (NOCONJ) THEN |
336 | 1 | pfleura2 | TEMP = TEMP*A(K,K) |
337 | 1 | pfleura2 | ELSE |
338 | 1 | pfleura2 | TEMP = TEMP*CONJG(A(K,K)) |
339 | 1 | pfleura2 | END IF |
340 | 1 | pfleura2 | END IF |
341 | 1 | pfleura2 | IF (TEMP.NE.ONE) THEN |
342 | 1 | pfleura2 | DO 270 I = 1,M |
343 | 1 | pfleura2 | B(I,K) = TEMP*B(I,K) |
344 | 1 | pfleura2 | 270 CONTINUE |
345 | 1 | pfleura2 | END IF |
346 | 1 | pfleura2 | 280 CONTINUE |
347 | 1 | pfleura2 | ELSE |
348 | 1 | pfleura2 | DO 320 K = N,1,-1 |
349 | 1 | pfleura2 | DO 300 J = K + 1,N |
350 | 1 | pfleura2 | IF (A(J,K).NE.ZERO) THEN |
351 | 1 | pfleura2 | IF (NOCONJ) THEN |
352 | 1 | pfleura2 | TEMP = ALPHA*A(J,K) |
353 | 1 | pfleura2 | ELSE |
354 | 1 | pfleura2 | TEMP = ALPHA*CONJG(A(J,K)) |
355 | 1 | pfleura2 | END IF |
356 | 1 | pfleura2 | DO 290 I = 1,M |
357 | 1 | pfleura2 | B(I,J) = B(I,J) + TEMP*B(I,K) |
358 | 1 | pfleura2 | 290 CONTINUE |
359 | 1 | pfleura2 | END IF |
360 | 1 | pfleura2 | 300 CONTINUE |
361 | 1 | pfleura2 | TEMP = ALPHA |
362 | 1 | pfleura2 | IF (NOUNIT) THEN |
363 | 1 | pfleura2 | IF (NOCONJ) THEN |
364 | 1 | pfleura2 | TEMP = TEMP*A(K,K) |
365 | 1 | pfleura2 | ELSE |
366 | 1 | pfleura2 | TEMP = TEMP*CONJG(A(K,K)) |
367 | 1 | pfleura2 | END IF |
368 | 1 | pfleura2 | END IF |
369 | 1 | pfleura2 | IF (TEMP.NE.ONE) THEN |
370 | 1 | pfleura2 | DO 310 I = 1,M |
371 | 1 | pfleura2 | B(I,K) = TEMP*B(I,K) |
372 | 1 | pfleura2 | 310 CONTINUE |
373 | 1 | pfleura2 | END IF |
374 | 1 | pfleura2 | 320 CONTINUE |
375 | 1 | pfleura2 | END IF |
376 | 1 | pfleura2 | END IF |
377 | 1 | pfleura2 | END IF |
378 | 1 | pfleura2 | * |
379 | 1 | pfleura2 | RETURN |
380 | 1 | pfleura2 | * |
381 | 1 | pfleura2 | * End of CTRMM . |
382 | 1 | pfleura2 | * |
383 | 1 | pfleura2 | END |