Free cookie consent management tool by TermsFeed Policy Generator

source: branches/MathNetNumerics-Exploration-2789/HeuristicLab.Algorithms.DataAnalysis.Experimental/sbart/ctbmv.f @ 15457

Last change on this file since 15457 was 15457, checked in by gkronber, 6 years ago

#2789 added Finbarr O'Sullivan smoothing spline code

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