File:
[local] /
rpl /
lapack /
blas /
ztbmv.f
Revision
1.11:
download - view:
text,
annotated -
select for diffs -
revision graph
Mon Jan 27 09:28:14 2014 UTC (11 years, 3 months ago) by
bertrand
Branches:
MAIN
CVS tags:
rpl-4_1_24,
rpl-4_1_23,
rpl-4_1_22,
rpl-4_1_21,
rpl-4_1_20,
rpl-4_1_19,
rpl-4_1_18,
rpl-4_1_17,
HEAD
Cohérence.
1: *> \brief \b ZTBMV
2: *
3: * =========== DOCUMENTATION ===========
4: *
5: * Online html documentation available at
6: * http://www.netlib.org/lapack/explore-html/
7: *
8: * Definition:
9: * ===========
10: *
11: * SUBROUTINE ZTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
12: *
13: * .. Scalar Arguments ..
14: * INTEGER INCX,K,LDA,N
15: * CHARACTER DIAG,TRANS,UPLO
16: * ..
17: * .. Array Arguments ..
18: * COMPLEX*16 A(LDA,*),X(*)
19: * ..
20: *
21: *
22: *> \par Purpose:
23: * =============
24: *>
25: *> \verbatim
26: *>
27: *> ZTBMV performs one of the matrix-vector operations
28: *>
29: *> x := A*x, or x := A**T*x, or x := A**H*x,
30: *>
31: *> where x is an n element vector and A is an n by n unit, or non-unit,
32: *> upper or lower triangular band matrix, with ( k + 1 ) diagonals.
33: *> \endverbatim
34: *
35: * Arguments:
36: * ==========
37: *
38: *> \param[in] UPLO
39: *> \verbatim
40: *> UPLO is CHARACTER*1
41: *> On entry, UPLO specifies whether the matrix is an upper or
42: *> lower triangular matrix as follows:
43: *>
44: *> UPLO = 'U' or 'u' A is an upper triangular matrix.
45: *>
46: *> UPLO = 'L' or 'l' A is a lower triangular matrix.
47: *> \endverbatim
48: *>
49: *> \param[in] TRANS
50: *> \verbatim
51: *> TRANS is CHARACTER*1
52: *> On entry, TRANS specifies the operation to be performed as
53: *> follows:
54: *>
55: *> TRANS = 'N' or 'n' x := A*x.
56: *>
57: *> TRANS = 'T' or 't' x := A**T*x.
58: *>
59: *> TRANS = 'C' or 'c' x := A**H*x.
60: *> \endverbatim
61: *>
62: *> \param[in] DIAG
63: *> \verbatim
64: *> DIAG is CHARACTER*1
65: *> On entry, DIAG specifies whether or not A is unit
66: *> triangular as follows:
67: *>
68: *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
69: *>
70: *> DIAG = 'N' or 'n' A is not assumed to be unit
71: *> triangular.
72: *> \endverbatim
73: *>
74: *> \param[in] N
75: *> \verbatim
76: *> N is INTEGER
77: *> On entry, N specifies the order of the matrix A.
78: *> N must be at least zero.
79: *> \endverbatim
80: *>
81: *> \param[in] K
82: *> \verbatim
83: *> K is INTEGER
84: *> On entry with UPLO = 'U' or 'u', K specifies the number of
85: *> super-diagonals of the matrix A.
86: *> On entry with UPLO = 'L' or 'l', K specifies the number of
87: *> sub-diagonals of the matrix A.
88: *> K must satisfy 0 .le. K.
89: *> \endverbatim
90: *>
91: *> \param[in] A
92: *> \verbatim
93: *> A is COMPLEX*16 array of DIMENSION ( LDA, n ).
94: *> Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
95: *> by n part of the array A must contain the upper triangular
96: *> band part of the matrix of coefficients, supplied column by
97: *> column, with the leading diagonal of the matrix in row
98: *> ( k + 1 ) of the array, the first super-diagonal starting at
99: *> position 2 in row k, and so on. The top left k by k triangle
100: *> of the array A is not referenced.
101: *> The following program segment will transfer an upper
102: *> triangular band matrix from conventional full matrix storage
103: *> to band storage:
104: *>
105: *> DO 20, J = 1, N
106: *> M = K + 1 - J
107: *> DO 10, I = MAX( 1, J - K ), J
108: *> A( M + I, J ) = matrix( I, J )
109: *> 10 CONTINUE
110: *> 20 CONTINUE
111: *>
112: *> Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
113: *> by n part of the array A must contain the lower triangular
114: *> band part of the matrix of coefficients, supplied column by
115: *> column, with the leading diagonal of the matrix in row 1 of
116: *> the array, the first sub-diagonal starting at position 1 in
117: *> row 2, and so on. The bottom right k by k triangle of the
118: *> array A is not referenced.
119: *> The following program segment will transfer a lower
120: *> triangular band matrix from conventional full matrix storage
121: *> to band storage:
122: *>
123: *> DO 20, J = 1, N
124: *> M = 1 - J
125: *> DO 10, I = J, MIN( N, J + K )
126: *> A( M + I, J ) = matrix( I, J )
127: *> 10 CONTINUE
128: *> 20 CONTINUE
129: *>
130: *> Note that when DIAG = 'U' or 'u' the elements of the array A
131: *> corresponding to the diagonal elements of the matrix are not
132: *> referenced, but are assumed to be unity.
133: *> \endverbatim
134: *>
135: *> \param[in] LDA
136: *> \verbatim
137: *> LDA is INTEGER
138: *> On entry, LDA specifies the first dimension of A as declared
139: *> in the calling (sub) program. LDA must be at least
140: *> ( k + 1 ).
141: *> \endverbatim
142: *>
143: *> \param[in] X
144: *> \verbatim
145: *> X is (input/output) COMPLEX*16 array of dimension at least
146: *> ( 1 + ( n - 1 )*abs( INCX ) ).
147: *> Before entry, the incremented array X must contain the n
148: *> element vector x. On exit, X is overwritten with the
149: *> tranformed vector x.
150: *> \endverbatim
151: *>
152: *> \param[in] INCX
153: *> \verbatim
154: *> INCX is INTEGER
155: *> On entry, INCX specifies the increment for the elements of
156: *> X. INCX must not be zero.
157: *> \endverbatim
158: *
159: * Authors:
160: * ========
161: *
162: *> \author Univ. of Tennessee
163: *> \author Univ. of California Berkeley
164: *> \author Univ. of Colorado Denver
165: *> \author NAG Ltd.
166: *
167: *> \date November 2011
168: *
169: *> \ingroup complex16_blas_level2
170: *
171: *> \par Further Details:
172: * =====================
173: *>
174: *> \verbatim
175: *>
176: *> Level 2 Blas routine.
177: *> The vector and matrix arguments are not referenced when N = 0, or M = 0
178: *>
179: *> -- Written on 22-October-1986.
180: *> Jack Dongarra, Argonne National Lab.
181: *> Jeremy Du Croz, Nag Central Office.
182: *> Sven Hammarling, Nag Central Office.
183: *> Richard Hanson, Sandia National Labs.
184: *> \endverbatim
185: *>
186: * =====================================================================
187: SUBROUTINE ZTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
188: *
189: * -- Reference BLAS level2 routine (version 3.4.0) --
190: * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
191: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
192: * November 2011
193: *
194: * .. Scalar Arguments ..
195: INTEGER INCX,K,LDA,N
196: CHARACTER DIAG,TRANS,UPLO
197: * ..
198: * .. Array Arguments ..
199: COMPLEX*16 A(LDA,*),X(*)
200: * ..
201: *
202: * =====================================================================
203: *
204: * .. Parameters ..
205: COMPLEX*16 ZERO
206: PARAMETER (ZERO= (0.0D+0,0.0D+0))
207: * ..
208: * .. Local Scalars ..
209: COMPLEX*16 TEMP
210: INTEGER I,INFO,IX,J,JX,KPLUS1,KX,L
211: LOGICAL NOCONJ,NOUNIT
212: * ..
213: * .. External Functions ..
214: LOGICAL LSAME
215: EXTERNAL LSAME
216: * ..
217: * .. External Subroutines ..
218: EXTERNAL XERBLA
219: * ..
220: * .. Intrinsic Functions ..
221: INTRINSIC DCONJG,MAX,MIN
222: * ..
223: *
224: * Test the input parameters.
225: *
226: INFO = 0
227: IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
228: INFO = 1
229: ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
230: + .NOT.LSAME(TRANS,'C')) THEN
231: INFO = 2
232: ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
233: INFO = 3
234: ELSE IF (N.LT.0) THEN
235: INFO = 4
236: ELSE IF (K.LT.0) THEN
237: INFO = 5
238: ELSE IF (LDA.LT. (K+1)) THEN
239: INFO = 7
240: ELSE IF (INCX.EQ.0) THEN
241: INFO = 9
242: END IF
243: IF (INFO.NE.0) THEN
244: CALL XERBLA('ZTBMV ',INFO)
245: RETURN
246: END IF
247: *
248: * Quick return if possible.
249: *
250: IF (N.EQ.0) RETURN
251: *
252: NOCONJ = LSAME(TRANS,'T')
253: NOUNIT = LSAME(DIAG,'N')
254: *
255: * Set up the start point in X if the increment is not unity. This
256: * will be ( N - 1 )*INCX too small for descending loops.
257: *
258: IF (INCX.LE.0) THEN
259: KX = 1 - (N-1)*INCX
260: ELSE IF (INCX.NE.1) THEN
261: KX = 1
262: END IF
263: *
264: * Start the operations. In this version the elements of A are
265: * accessed sequentially with one pass through A.
266: *
267: IF (LSAME(TRANS,'N')) THEN
268: *
269: * Form x := A*x.
270: *
271: IF (LSAME(UPLO,'U')) THEN
272: KPLUS1 = K + 1
273: IF (INCX.EQ.1) THEN
274: DO 20 J = 1,N
275: IF (X(J).NE.ZERO) THEN
276: TEMP = X(J)
277: L = KPLUS1 - J
278: DO 10 I = MAX(1,J-K),J - 1
279: X(I) = X(I) + TEMP*A(L+I,J)
280: 10 CONTINUE
281: IF (NOUNIT) X(J) = X(J)*A(KPLUS1,J)
282: END IF
283: 20 CONTINUE
284: ELSE
285: JX = KX
286: DO 40 J = 1,N
287: IF (X(JX).NE.ZERO) THEN
288: TEMP = X(JX)
289: IX = KX
290: L = KPLUS1 - J
291: DO 30 I = MAX(1,J-K),J - 1
292: X(IX) = X(IX) + TEMP*A(L+I,J)
293: IX = IX + INCX
294: 30 CONTINUE
295: IF (NOUNIT) X(JX) = X(JX)*A(KPLUS1,J)
296: END IF
297: JX = JX + INCX
298: IF (J.GT.K) KX = KX + INCX
299: 40 CONTINUE
300: END IF
301: ELSE
302: IF (INCX.EQ.1) THEN
303: DO 60 J = N,1,-1
304: IF (X(J).NE.ZERO) THEN
305: TEMP = X(J)
306: L = 1 - J
307: DO 50 I = MIN(N,J+K),J + 1,-1
308: X(I) = X(I) + TEMP*A(L+I,J)
309: 50 CONTINUE
310: IF (NOUNIT) X(J) = X(J)*A(1,J)
311: END IF
312: 60 CONTINUE
313: ELSE
314: KX = KX + (N-1)*INCX
315: JX = KX
316: DO 80 J = N,1,-1
317: IF (X(JX).NE.ZERO) THEN
318: TEMP = X(JX)
319: IX = KX
320: L = 1 - J
321: DO 70 I = MIN(N,J+K),J + 1,-1
322: X(IX) = X(IX) + TEMP*A(L+I,J)
323: IX = IX - INCX
324: 70 CONTINUE
325: IF (NOUNIT) X(JX) = X(JX)*A(1,J)
326: END IF
327: JX = JX - INCX
328: IF ((N-J).GE.K) KX = KX - INCX
329: 80 CONTINUE
330: END IF
331: END IF
332: ELSE
333: *
334: * Form x := A**T*x or x := A**H*x.
335: *
336: IF (LSAME(UPLO,'U')) THEN
337: KPLUS1 = K + 1
338: IF (INCX.EQ.1) THEN
339: DO 110 J = N,1,-1
340: TEMP = X(J)
341: L = KPLUS1 - J
342: IF (NOCONJ) THEN
343: IF (NOUNIT) TEMP = TEMP*A(KPLUS1,J)
344: DO 90 I = J - 1,MAX(1,J-K),-1
345: TEMP = TEMP + A(L+I,J)*X(I)
346: 90 CONTINUE
347: ELSE
348: IF (NOUNIT) TEMP = TEMP*DCONJG(A(KPLUS1,J))
349: DO 100 I = J - 1,MAX(1,J-K),-1
350: TEMP = TEMP + DCONJG(A(L+I,J))*X(I)
351: 100 CONTINUE
352: END IF
353: X(J) = TEMP
354: 110 CONTINUE
355: ELSE
356: KX = KX + (N-1)*INCX
357: JX = KX
358: DO 140 J = N,1,-1
359: TEMP = X(JX)
360: KX = KX - INCX
361: IX = KX
362: L = KPLUS1 - J
363: IF (NOCONJ) THEN
364: IF (NOUNIT) TEMP = TEMP*A(KPLUS1,J)
365: DO 120 I = J - 1,MAX(1,J-K),-1
366: TEMP = TEMP + A(L+I,J)*X(IX)
367: IX = IX - INCX
368: 120 CONTINUE
369: ELSE
370: IF (NOUNIT) TEMP = TEMP*DCONJG(A(KPLUS1,J))
371: DO 130 I = J - 1,MAX(1,J-K),-1
372: TEMP = TEMP + DCONJG(A(L+I,J))*X(IX)
373: IX = IX - INCX
374: 130 CONTINUE
375: END IF
376: X(JX) = TEMP
377: JX = JX - INCX
378: 140 CONTINUE
379: END IF
380: ELSE
381: IF (INCX.EQ.1) THEN
382: DO 170 J = 1,N
383: TEMP = X(J)
384: L = 1 - J
385: IF (NOCONJ) THEN
386: IF (NOUNIT) TEMP = TEMP*A(1,J)
387: DO 150 I = J + 1,MIN(N,J+K)
388: TEMP = TEMP + A(L+I,J)*X(I)
389: 150 CONTINUE
390: ELSE
391: IF (NOUNIT) TEMP = TEMP*DCONJG(A(1,J))
392: DO 160 I = J + 1,MIN(N,J+K)
393: TEMP = TEMP + DCONJG(A(L+I,J))*X(I)
394: 160 CONTINUE
395: END IF
396: X(J) = TEMP
397: 170 CONTINUE
398: ELSE
399: JX = KX
400: DO 200 J = 1,N
401: TEMP = X(JX)
402: KX = KX + INCX
403: IX = KX
404: L = 1 - J
405: IF (NOCONJ) THEN
406: IF (NOUNIT) TEMP = TEMP*A(1,J)
407: DO 180 I = J + 1,MIN(N,J+K)
408: TEMP = TEMP + A(L+I,J)*X(IX)
409: IX = IX + INCX
410: 180 CONTINUE
411: ELSE
412: IF (NOUNIT) TEMP = TEMP*DCONJG(A(1,J))
413: DO 190 I = J + 1,MIN(N,J+K)
414: TEMP = TEMP + DCONJG(A(L+I,J))*X(IX)
415: IX = IX + INCX
416: 190 CONTINUE
417: END IF
418: X(JX) = TEMP
419: JX = JX + INCX
420: 200 CONTINUE
421: END IF
422: END IF
423: END IF
424: *
425: RETURN
426: *
427: * End of ZTBMV .
428: *
429: END
CVSweb interface <joel.bertrand@systella.fr>