Statistiques
| Révision :

root / src / blas / ztrsm.f @ 4

Historique | Voir | Annoter | Télécharger (13,5 ko)

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