Statistiques
| Révision :

root / src / blas / ctpsv.f @ 7

Historique | Voir | Annoter | Télécharger (10,73 ko)

1
      SUBROUTINE CTPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
2
*     .. Scalar Arguments ..
3
      INTEGER INCX,N
4
      CHARACTER DIAG,TRANS,UPLO
5
*     ..
6
*     .. Array Arguments ..
7
      COMPLEX AP(*),X(*)
8
*     ..
9
*
10
*  Purpose
11
*  =======
12
*
13
*  CTPSV  solves one of the systems of equations
14
*
15
*     A*x = b,   or   A'*x = b,   or   conjg( A' )*x = b,
16
*
17
*  where b and x are n element vectors and A is an n by n unit, or
18
*  non-unit, upper or lower triangular matrix, supplied in packed form.
19
*
20
*  No test for singularity or near-singularity is included in this
21
*  routine. Such tests must be performed before calling this routine.
22
*
23
*  Arguments
24
*  ==========
25
*
26
*  UPLO   - CHARACTER*1.
27
*           On entry, UPLO specifies whether the matrix is an upper or
28
*           lower triangular matrix as follows:
29
*
30
*              UPLO = 'U' or 'u'   A is an upper triangular matrix.
31
*
32
*              UPLO = 'L' or 'l'   A is a lower triangular matrix.
33
*
34
*           Unchanged on exit.
35
*
36
*  TRANS  - CHARACTER*1.
37
*           On entry, TRANS specifies the equations to be solved as
38
*           follows:
39
*
40
*              TRANS = 'N' or 'n'   A*x = b.
41
*
42
*              TRANS = 'T' or 't'   A'*x = b.
43
*
44
*              TRANS = 'C' or 'c'   conjg( A' )*x = b.
45
*
46
*           Unchanged on exit.
47
*
48
*  DIAG   - CHARACTER*1.
49
*           On entry, DIAG specifies whether or not A is unit
50
*           triangular as follows:
51
*
52
*              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
53
*
54
*              DIAG = 'N' or 'n'   A is not assumed to be unit
55
*                                  triangular.
56
*
57
*           Unchanged on exit.
58
*
59
*  N      - INTEGER.
60
*           On entry, N specifies the order of the matrix A.
61
*           N must be at least zero.
62
*           Unchanged on exit.
63
*
64
*  AP     - COMPLEX          array of DIMENSION at least
65
*           ( ( n*( n + 1 ) )/2 ).
66
*           Before entry with  UPLO = 'U' or 'u', the array AP must
67
*           contain the upper triangular matrix packed sequentially,
68
*           column by column, so that AP( 1 ) contains a( 1, 1 ),
69
*           AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
70
*           respectively, and so on.
71
*           Before entry with UPLO = 'L' or 'l', the array AP must
72
*           contain the lower triangular matrix packed sequentially,
73
*           column by column, so that AP( 1 ) contains a( 1, 1 ),
74
*           AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
75
*           respectively, and so on.
76
*           Note that when  DIAG = 'U' or 'u', the diagonal elements of
77
*           A are not referenced, but are assumed to be unity.
78
*           Unchanged on exit.
79
*
80
*  X      - COMPLEX          array of dimension at least
81
*           ( 1 + ( n - 1 )*abs( INCX ) ).
82
*           Before entry, the incremented array X must contain the n
83
*           element right-hand side vector b. On exit, X is overwritten
84
*           with the solution vector x.
85
*
86
*  INCX   - INTEGER.
87
*           On entry, INCX specifies the increment for the elements of
88
*           X. INCX must not be zero.
89
*           Unchanged on exit.
90
*
91
*
92
*  Level 2 Blas routine.
93
*
94
*  -- Written on 22-October-1986.
95
*     Jack Dongarra, Argonne National Lab.
96
*     Jeremy Du Croz, Nag Central Office.
97
*     Sven Hammarling, Nag Central Office.
98
*     Richard Hanson, Sandia National Labs.
99
*
100
*
101
*     .. Parameters ..
102
      COMPLEX ZERO
103
      PARAMETER (ZERO= (0.0E+0,0.0E+0))
104
*     ..
105
*     .. Local Scalars ..
106
      COMPLEX TEMP
107
      INTEGER I,INFO,IX,J,JX,K,KK,KX
108
      LOGICAL NOCONJ,NOUNIT
109
*     ..
110
*     .. External Functions ..
111
      LOGICAL LSAME
112
      EXTERNAL LSAME
113
*     ..
114
*     .. External Subroutines ..
115
      EXTERNAL XERBLA
116
*     ..
117
*     .. Intrinsic Functions ..
118
      INTRINSIC CONJG
119
*     ..
120
*
121
*     Test the input parameters.
122
*
123
      INFO = 0
124
      IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
125
          INFO = 1
126
      ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
127
     +         .NOT.LSAME(TRANS,'C')) THEN
128
          INFO = 2
129
      ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
130
          INFO = 3
131
      ELSE IF (N.LT.0) THEN
132
          INFO = 4
133
      ELSE IF (INCX.EQ.0) THEN
134
          INFO = 7
135
      END IF
136
      IF (INFO.NE.0) THEN
137
          CALL XERBLA('CTPSV ',INFO)
138
          RETURN
139
      END IF
140
*
141
*     Quick return if possible.
142
*
143
      IF (N.EQ.0) RETURN
144
*
145
      NOCONJ = LSAME(TRANS,'T')
146
      NOUNIT = LSAME(DIAG,'N')
147
*
148
*     Set up the start point in X if the increment is not unity. This
149
*     will be  ( N - 1 )*INCX  too small for descending loops.
150
*
151
      IF (INCX.LE.0) THEN
152
          KX = 1 - (N-1)*INCX
153
      ELSE IF (INCX.NE.1) THEN
154
          KX = 1
155
      END IF
156
*
157
*     Start the operations. In this version the elements of AP are
158
*     accessed sequentially with one pass through AP.
159
*
160
      IF (LSAME(TRANS,'N')) THEN
161
*
162
*        Form  x := inv( A )*x.
163
*
164
          IF (LSAME(UPLO,'U')) THEN
165
              KK = (N* (N+1))/2
166
              IF (INCX.EQ.1) THEN
167
                  DO 20 J = N,1,-1
168
                      IF (X(J).NE.ZERO) THEN
169
                          IF (NOUNIT) X(J) = X(J)/AP(KK)
170
                          TEMP = X(J)
171
                          K = KK - 1
172
                          DO 10 I = J - 1,1,-1
173
                              X(I) = X(I) - TEMP*AP(K)
174
                              K = K - 1
175
   10                     CONTINUE
176
                      END IF
177
                      KK = KK - J
178
   20             CONTINUE
179
              ELSE
180
                  JX = KX + (N-1)*INCX
181
                  DO 40 J = N,1,-1
182
                      IF (X(JX).NE.ZERO) THEN
183
                          IF (NOUNIT) X(JX) = X(JX)/AP(KK)
184
                          TEMP = X(JX)
185
                          IX = JX
186
                          DO 30 K = KK - 1,KK - J + 1,-1
187
                              IX = IX - INCX
188
                              X(IX) = X(IX) - TEMP*AP(K)
189
   30                     CONTINUE
190
                      END IF
191
                      JX = JX - INCX
192
                      KK = KK - J
193
   40             CONTINUE
194
              END IF
195
          ELSE
196
              KK = 1
197
              IF (INCX.EQ.1) THEN
198
                  DO 60 J = 1,N
199
                      IF (X(J).NE.ZERO) THEN
200
                          IF (NOUNIT) X(J) = X(J)/AP(KK)
201
                          TEMP = X(J)
202
                          K = KK + 1
203
                          DO 50 I = J + 1,N
204
                              X(I) = X(I) - TEMP*AP(K)
205
                              K = K + 1
206
   50                     CONTINUE
207
                      END IF
208
                      KK = KK + (N-J+1)
209
   60             CONTINUE
210
              ELSE
211
                  JX = KX
212
                  DO 80 J = 1,N
213
                      IF (X(JX).NE.ZERO) THEN
214
                          IF (NOUNIT) X(JX) = X(JX)/AP(KK)
215
                          TEMP = X(JX)
216
                          IX = JX
217
                          DO 70 K = KK + 1,KK + N - J
218
                              IX = IX + INCX
219
                              X(IX) = X(IX) - TEMP*AP(K)
220
   70                     CONTINUE
221
                      END IF
222
                      JX = JX + INCX
223
                      KK = KK + (N-J+1)
224
   80             CONTINUE
225
              END IF
226
          END IF
227
      ELSE
228
*
229
*        Form  x := inv( A' )*x  or  x := inv( conjg( A' ) )*x.
230
*
231
          IF (LSAME(UPLO,'U')) THEN
232
              KK = 1
233
              IF (INCX.EQ.1) THEN
234
                  DO 110 J = 1,N
235
                      TEMP = X(J)
236
                      K = KK
237
                      IF (NOCONJ) THEN
238
                          DO 90 I = 1,J - 1
239
                              TEMP = TEMP - AP(K)*X(I)
240
                              K = K + 1
241
   90                     CONTINUE
242
                          IF (NOUNIT) TEMP = TEMP/AP(KK+J-1)
243
                      ELSE
244
                          DO 100 I = 1,J - 1
245
                              TEMP = TEMP - CONJG(AP(K))*X(I)
246
                              K = K + 1
247
  100                     CONTINUE
248
                          IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK+J-1))
249
                      END IF
250
                      X(J) = TEMP
251
                      KK = KK + J
252
  110             CONTINUE
253
              ELSE
254
                  JX = KX
255
                  DO 140 J = 1,N
256
                      TEMP = X(JX)
257
                      IX = KX
258
                      IF (NOCONJ) THEN
259
                          DO 120 K = KK,KK + J - 2
260
                              TEMP = TEMP - AP(K)*X(IX)
261
                              IX = IX + INCX
262
  120                     CONTINUE
263
                          IF (NOUNIT) TEMP = TEMP/AP(KK+J-1)
264
                      ELSE
265
                          DO 130 K = KK,KK + J - 2
266
                              TEMP = TEMP - CONJG(AP(K))*X(IX)
267
                              IX = IX + INCX
268
  130                     CONTINUE
269
                          IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK+J-1))
270
                      END IF
271
                      X(JX) = TEMP
272
                      JX = JX + INCX
273
                      KK = KK + J
274
  140             CONTINUE
275
              END IF
276
          ELSE
277
              KK = (N* (N+1))/2
278
              IF (INCX.EQ.1) THEN
279
                  DO 170 J = N,1,-1
280
                      TEMP = X(J)
281
                      K = KK
282
                      IF (NOCONJ) THEN
283
                          DO 150 I = N,J + 1,-1
284
                              TEMP = TEMP - AP(K)*X(I)
285
                              K = K - 1
286
  150                     CONTINUE
287
                          IF (NOUNIT) TEMP = TEMP/AP(KK-N+J)
288
                      ELSE
289
                          DO 160 I = N,J + 1,-1
290
                              TEMP = TEMP - CONJG(AP(K))*X(I)
291
                              K = K - 1
292
  160                     CONTINUE
293
                          IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK-N+J))
294
                      END IF
295
                      X(J) = TEMP
296
                      KK = KK - (N-J+1)
297
  170             CONTINUE
298
              ELSE
299
                  KX = KX + (N-1)*INCX
300
                  JX = KX
301
                  DO 200 J = N,1,-1
302
                      TEMP = X(JX)
303
                      IX = KX
304
                      IF (NOCONJ) THEN
305
                          DO 180 K = KK,KK - (N- (J+1)),-1
306
                              TEMP = TEMP - AP(K)*X(IX)
307
                              IX = IX - INCX
308
  180                     CONTINUE
309
                          IF (NOUNIT) TEMP = TEMP/AP(KK-N+J)
310
                      ELSE
311
                          DO 190 K = KK,KK - (N- (J+1)),-1
312
                              TEMP = TEMP - CONJG(AP(K))*X(IX)
313
                              IX = IX - INCX
314
  190                     CONTINUE
315
                          IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK-N+J))
316
                      END IF
317
                      X(JX) = TEMP
318
                      JX = JX - INCX
319
                      KK = KK - (N-J+1)
320
  200             CONTINUE
321
              END IF
322
          END IF
323
      END IF
324
*
325
      RETURN
326
*
327
*     End of CTPSV .
328
*
329
      END