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