LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ctbsv ( character  UPLO,
character  TRANS,
character  DIAG,
integer  N,
integer  K,
complex, dimension(lda,*)  A,
integer  LDA,
complex, dimension(*)  X,
integer  INCX 
)

CTBSV

Purpose:
 CTBSV  solves one of the systems of equations

    A*x = b,   or   A**T*x = b,   or   A**H*x = b,

 where b and x are n element vectors and A is an n by n unit, or
 non-unit, upper or lower triangular band matrix, with ( k + 1 )
 diagonals.

 No test for singularity or near-singularity is included in this
 routine. Such tests must be performed before calling this routine.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the matrix is an upper or
           lower triangular matrix as follows:

              UPLO = 'U' or 'u'   A is an upper triangular matrix.

              UPLO = 'L' or 'l'   A is a lower triangular matrix.
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the equations to be solved as
           follows:

              TRANS = 'N' or 'n'   A*x = b.

              TRANS = 'T' or 't'   A**T*x = b.

              TRANS = 'C' or 'c'   A**H*x = b.
[in]DIAG
          DIAG is CHARACTER*1
           On entry, DIAG specifies whether or not A is unit
           triangular as follows:

              DIAG = 'U' or 'u'   A is assumed to be unit triangular.

              DIAG = 'N' or 'n'   A is not assumed to be unit
                                  triangular.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]K
          K is INTEGER
           On entry with UPLO = 'U' or 'u', K specifies the number of
           super-diagonals of the matrix A.
           On entry with UPLO = 'L' or 'l', K specifies the number of
           sub-diagonals of the matrix A.
           K must satisfy  0 .le. K.
[in]A
          A is COMPLEX array of DIMENSION ( LDA, n ).
           Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
           by n part of the array A must contain the upper triangular
           band part of the matrix of coefficients, supplied column by
           column, with the leading diagonal of the matrix in row
           ( k + 1 ) of the array, the first super-diagonal starting at
           position 2 in row k, and so on. The top left k by k triangle
           of the array A is not referenced.
           The following program segment will transfer an upper
           triangular band matrix from conventional full matrix storage
           to band storage:

                 DO 20, J = 1, N
                    M = K + 1 - J
                    DO 10, I = MAX( 1, J - K ), J
                       A( M + I, J ) = matrix( I, J )
              10    CONTINUE
              20 CONTINUE

           Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
           by n part of the array A must contain the lower triangular
           band part of the matrix of coefficients, supplied column by
           column, with the leading diagonal of the matrix in row 1 of
           the array, the first sub-diagonal starting at position 1 in
           row 2, and so on. The bottom right k by k triangle of the
           array A is not referenced.
           The following program segment will transfer a lower
           triangular band matrix from conventional full matrix storage
           to band storage:

                 DO 20, J = 1, N
                    M = 1 - J
                    DO 10, I = J, MIN( N, J + K )
                       A( M + I, J ) = matrix( I, J )
              10    CONTINUE
              20 CONTINUE

           Note that when DIAG = 'U' or 'u' the elements of the array A
           corresponding to the diagonal elements of the matrix are not
           referenced, but are assumed to be unity.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           ( k + 1 ).
[in,out]X
          X is COMPLEX array of dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the n
           element right-hand side vector b. On exit, X is overwritten
           with the solution vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011
Further Details:
  Level 2 Blas routine.

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.

Definition at line 191 of file ctbsv.f.

191 *
192 * -- Reference BLAS level2 routine (version 3.4.0) --
193 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
194 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
195 * November 2011
196 *
197 * .. Scalar Arguments ..
198  INTEGER incx,k,lda,n
199  CHARACTER diag,trans,uplo
200 * ..
201 * .. Array Arguments ..
202  COMPLEX a(lda,*),x(*)
203 * ..
204 *
205 * =====================================================================
206 *
207 * .. Parameters ..
208  COMPLEX zero
209  parameter(zero= (0.0e+0,0.0e+0))
210 * ..
211 * .. Local Scalars ..
212  COMPLEX temp
213  INTEGER i,info,ix,j,jx,kplus1,kx,l
214  LOGICAL noconj,nounit
215 * ..
216 * .. External Functions ..
217  LOGICAL lsame
218  EXTERNAL lsame
219 * ..
220 * .. External Subroutines ..
221  EXTERNAL xerbla
222 * ..
223 * .. Intrinsic Functions ..
224  INTRINSIC conjg,max,min
225 * ..
226 *
227 * Test the input parameters.
228 *
229  info = 0
230  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
231  info = 1
232  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
233  + .NOT.lsame(trans,'C')) THEN
234  info = 2
235  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
236  info = 3
237  ELSE IF (n.LT.0) THEN
238  info = 4
239  ELSE IF (k.LT.0) THEN
240  info = 5
241  ELSE IF (lda.LT. (k+1)) THEN
242  info = 7
243  ELSE IF (incx.EQ.0) THEN
244  info = 9
245  END IF
246  IF (info.NE.0) THEN
247  CALL xerbla('CTBSV ',info)
248  RETURN
249  END IF
250 *
251 * Quick return if possible.
252 *
253  IF (n.EQ.0) RETURN
254 *
255  noconj = lsame(trans,'T')
256  nounit = lsame(diag,'N')
257 *
258 * Set up the start point in X if the increment is not unity. This
259 * will be ( N - 1 )*INCX too small for descending loops.
260 *
261  IF (incx.LE.0) THEN
262  kx = 1 - (n-1)*incx
263  ELSE IF (incx.NE.1) THEN
264  kx = 1
265  END IF
266 *
267 * Start the operations. In this version the elements of A are
268 * accessed by sequentially with one pass through A.
269 *
270  IF (lsame(trans,'N')) THEN
271 *
272 * Form x := inv( A )*x.
273 *
274  IF (lsame(uplo,'U')) THEN
275  kplus1 = k + 1
276  IF (incx.EQ.1) THEN
277  DO 20 j = n,1,-1
278  IF (x(j).NE.zero) THEN
279  l = kplus1 - j
280  IF (nounit) x(j) = x(j)/a(kplus1,j)
281  temp = x(j)
282  DO 10 i = j - 1,max(1,j-k),-1
283  x(i) = x(i) - temp*a(l+i,j)
284  10 CONTINUE
285  END IF
286  20 CONTINUE
287  ELSE
288  kx = kx + (n-1)*incx
289  jx = kx
290  DO 40 j = n,1,-1
291  kx = kx - incx
292  IF (x(jx).NE.zero) THEN
293  ix = kx
294  l = kplus1 - j
295  IF (nounit) x(jx) = x(jx)/a(kplus1,j)
296  temp = x(jx)
297  DO 30 i = j - 1,max(1,j-k),-1
298  x(ix) = x(ix) - temp*a(l+i,j)
299  ix = ix - incx
300  30 CONTINUE
301  END IF
302  jx = jx - incx
303  40 CONTINUE
304  END IF
305  ELSE
306  IF (incx.EQ.1) THEN
307  DO 60 j = 1,n
308  IF (x(j).NE.zero) THEN
309  l = 1 - j
310  IF (nounit) x(j) = x(j)/a(1,j)
311  temp = x(j)
312  DO 50 i = j + 1,min(n,j+k)
313  x(i) = x(i) - temp*a(l+i,j)
314  50 CONTINUE
315  END IF
316  60 CONTINUE
317  ELSE
318  jx = kx
319  DO 80 j = 1,n
320  kx = kx + incx
321  IF (x(jx).NE.zero) THEN
322  ix = kx
323  l = 1 - j
324  IF (nounit) x(jx) = x(jx)/a(1,j)
325  temp = x(jx)
326  DO 70 i = j + 1,min(n,j+k)
327  x(ix) = x(ix) - temp*a(l+i,j)
328  ix = ix + incx
329  70 CONTINUE
330  END IF
331  jx = jx + incx
332  80 CONTINUE
333  END IF
334  END IF
335  ELSE
336 *
337 * Form x := inv( A**T )*x or x := inv( A**H )*x.
338 *
339  IF (lsame(uplo,'U')) THEN
340  kplus1 = k + 1
341  IF (incx.EQ.1) THEN
342  DO 110 j = 1,n
343  temp = x(j)
344  l = kplus1 - j
345  IF (noconj) THEN
346  DO 90 i = max(1,j-k),j - 1
347  temp = temp - a(l+i,j)*x(i)
348  90 CONTINUE
349  IF (nounit) temp = temp/a(kplus1,j)
350  ELSE
351  DO 100 i = max(1,j-k),j - 1
352  temp = temp - conjg(a(l+i,j))*x(i)
353  100 CONTINUE
354  IF (nounit) temp = temp/conjg(a(kplus1,j))
355  END IF
356  x(j) = temp
357  110 CONTINUE
358  ELSE
359  jx = kx
360  DO 140 j = 1,n
361  temp = x(jx)
362  ix = kx
363  l = kplus1 - j
364  IF (noconj) THEN
365  DO 120 i = max(1,j-k),j - 1
366  temp = temp - a(l+i,j)*x(ix)
367  ix = ix + incx
368  120 CONTINUE
369  IF (nounit) temp = temp/a(kplus1,j)
370  ELSE
371  DO 130 i = max(1,j-k),j - 1
372  temp = temp - conjg(a(l+i,j))*x(ix)
373  ix = ix + incx
374  130 CONTINUE
375  IF (nounit) temp = temp/conjg(a(kplus1,j))
376  END IF
377  x(jx) = temp
378  jx = jx + incx
379  IF (j.GT.k) kx = kx + incx
380  140 CONTINUE
381  END IF
382  ELSE
383  IF (incx.EQ.1) THEN
384  DO 170 j = n,1,-1
385  temp = x(j)
386  l = 1 - j
387  IF (noconj) THEN
388  DO 150 i = min(n,j+k),j + 1,-1
389  temp = temp - a(l+i,j)*x(i)
390  150 CONTINUE
391  IF (nounit) temp = temp/a(1,j)
392  ELSE
393  DO 160 i = min(n,j+k),j + 1,-1
394  temp = temp - conjg(a(l+i,j))*x(i)
395  160 CONTINUE
396  IF (nounit) temp = temp/conjg(a(1,j))
397  END IF
398  x(j) = temp
399  170 CONTINUE
400  ELSE
401  kx = kx + (n-1)*incx
402  jx = kx
403  DO 200 j = n,1,-1
404  temp = x(jx)
405  ix = kx
406  l = 1 - j
407  IF (noconj) THEN
408  DO 180 i = min(n,j+k),j + 1,-1
409  temp = temp - a(l+i,j)*x(ix)
410  ix = ix - incx
411  180 CONTINUE
412  IF (nounit) temp = temp/a(1,j)
413  ELSE
414  DO 190 i = min(n,j+k),j + 1,-1
415  temp = temp - conjg(a(l+i,j))*x(ix)
416  ix = ix - incx
417  190 CONTINUE
418  IF (nounit) temp = temp/conjg(a(1,j))
419  END IF
420  x(jx) = temp
421  jx = jx - incx
422  IF ((n-j).GE.k) kx = kx - incx
423  200 CONTINUE
424  END IF
425  END IF
426  END IF
427 *
428  RETURN
429 *
430 * End of CTBSV .
431 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: