SEARCH
NEW RPMS
DIRECTORIES
ABOUT
FAQ
VARIOUS
BLOG
DONATE


YUM REPOSITORY

 
 

MAN page from openSUSE Leap 42 blas-man-3.5.0-9.1.noarch.rpm

ctbmv.f

Section: LAPACK (3)
Updated: Fri Nov 4 2016
Index 

NAME

ctbmv.f -  

SYNOPSIS


 

Functions/Subroutines


subroutine CTBMV (UPLO, TRANS, DIAG, N, K, A, LDA, X, INCX)
CTBMV  

Function/Subroutine Documentation

 

subroutine CTBMV (character UPLO, character TRANS, character DIAG, integer N, integer K, complex, dimension(lda,*) A, integer LDA, complex, dimension(*) X, integer INCX)

CTBMV

Purpose:

 CTBMV  performs one of the matrix-vector operations    x := A*x,   or   x := A**T*x,   or   x := A**H*x, where x is an n element vector and  A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.


 

Parameters:

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.


TRANS

          TRANS is CHARACTER*1           On entry, TRANS specifies the operation to be performed as           follows:              TRANS = 'N' or 'n'   x := A*x.              TRANS = 'T' or 't'   x := A**T*x.              TRANS = 'C' or 'c'   x := A**H*x.


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.


N

          N is INTEGER           On entry, N specifies the order of the matrix A.           N must be at least zero.


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.


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.


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 ).


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 vector x. On exit, X is overwritten with the           tranformed vector x.


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.  The vector and matrix arguments are not referenced when N = 0, or M = 0  -- 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 188 of file ctbmv.f.

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 2011193 *194 *     .. Scalar Arguments ..195       INTEGER incx,k,lda,n196       CHARACTER diag,trans,uplo197 *     ..198 *     .. Array Arguments ..199       COMPLEX a(lda,*),x(*)200 *     ..201 *202 *  =====================================================================203 *204 *     .. Parameters ..205       COMPLEX zero206       parameter(zero= (0.0e+0,0.0e+0))207 *     ..208 *     .. Local Scalars ..209       COMPLEX temp210       INTEGER i,info,ix,j,jx,kplus1,kx,l211       LOGICAL noconj,nounit212 *     ..213 *     .. External Functions ..214       LOGICAL lsame215       EXTERNAL lsame216 *     ..217 *     .. External Subroutines ..218       EXTERNAL xerbla219 *     ..220 *     .. Intrinsic Functions ..221       INTRINSIC conjg,max,min222 *     ..223 *224 *     Test the input parameters.225 *226       info = 0227       IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN228           info = 1229       ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.230      +         .NOT.lsame(trans,'C')) THEN231           info = 2232       ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN233           info = 3234       ELSE IF (n.LT.0) THEN235           info = 4236       ELSE IF (k.LT.0) THEN237           info = 5238       ELSE IF (lda.LT. (k+1)) THEN239           info = 7240       ELSE IF (incx.EQ.0) THEN241           info = 9242       END IF243       IF (info.NE.0) THEN244           CALL xerbla('CTBMV ',info)245           RETURN246       END IF247 *248 *     Quick return if possible.249 *250       IF (n.EQ.0) RETURN251 *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. This256 *     will be  ( N - 1 )*INCX   too small for descending loops.257 *258       IF (incx.LE.0) THEN259           kx = 1 - (n-1)*incx260       ELSE IF (incx.NE.1) THEN261           kx = 1262       END IF263 *264 *     Start the operations. In this version the elements of A are265 *     accessed sequentially with one pass through A.266 *267       IF (lsame(trans,'N')) THEN268 *269 *         Form  x := A*x.270 *271           IF (lsame(uplo,'U')) THEN272               kplus1 = k + 1273               IF (incx.EQ.1) THEN274                   DO 20 j = 1,n275                       IF (x(j).NE.zero) THEN276                           temp = x(j)277                           l = kplus1 - j278                           DO 10 i = max(1,j-k),j - 1279                               x(i) = x(i) + temp*a(l+i,j)280    10                     CONTINUE281                           IF (nounit) x(j) = x(j)*a(kplus1,j)282                       END IF283    20             CONTINUE284               ELSE285                   jx = kx286                   DO 40 j = 1,n287                       IF (x(jx).NE.zero) THEN288                           temp = x(jx)289                           ix = kx290                           l = kplus1 - j291                           DO 30 i = max(1,j-k),j - 1292                               x(ix) = x(ix) + temp*a(l+i,j)293                               ix = ix + incx294    30                     CONTINUE295                           IF (nounit) x(jx) = x(jx)*a(kplus1,j)296                       END IF297                       jx = jx + incx298                       IF (j.GT.k) kx = kx + incx299    40             CONTINUE300               END IF301           ELSE302               IF (incx.EQ.1) THEN303                   DO 60 j = n,1,-1304                       IF (x(j).NE.zero) THEN305                           temp = x(j)306                           l = 1 - j307                           DO 50 i = min(n,j+k),j + 1,-1308                               x(i) = x(i) + temp*a(l+i,j)309    50                     CONTINUE310                           IF (nounit) x(j) = x(j)*a(1,j)311                       END IF312    60             CONTINUE313               ELSE314                   kx = kx + (n-1)*incx315                   jx = kx316                   DO 80 j = n,1,-1317                       IF (x(jx).NE.zero) THEN318                           temp = x(jx)319                           ix = kx320                           l = 1 - j321                           DO 70 i = min(n,j+k),j + 1,-1322                               x(ix) = x(ix) + temp*a(l+i,j)323                               ix = ix - incx324    70                     CONTINUE325                           IF (nounit) x(jx) = x(jx)*a(1,j)326                       END IF327                       jx = jx - incx328                       IF ((n-j).GE.k) kx = kx - incx329    80             CONTINUE330               END IF331           END IF332       ELSE333 *334 *        Form  x := A**T*x  or  x := A**H*x.335 *336           IF (lsame(uplo,'U')) THEN337               kplus1 = k + 1338               IF (incx.EQ.1) THEN339                   DO 110 j = n,1,-1340                       temp = x(j)341                       l = kplus1 - j342                       IF (noconj) THEN343                           IF (nounit) temp = temp*a(kplus1,j)344                           DO 90 i = j - 1,max(1,j-k),-1345                               temp = temp + a(l+i,j)*x(i)346    90                     CONTINUE347                       ELSE348                           IF (nounit) temp = temp*conjg(a(kplus1,j))349                           DO 100 i = j - 1,max(1,j-k),-1350                               temp = temp + conjg(a(l+i,j))*x(i)351   100                     CONTINUE352                       END IF353                       x(j) = temp354   110             CONTINUE355               ELSE356                   kx = kx + (n-1)*incx357                   jx = kx358                   DO 140 j = n,1,-1359                       temp = x(jx)360                       kx = kx - incx361                       ix = kx362                       l = kplus1 - j363                       IF (noconj) THEN364                           IF (nounit) temp = temp*a(kplus1,j)365                           DO 120 i = j - 1,max(1,j-k),-1366                               temp = temp + a(l+i,j)*x(ix)367                               ix = ix - incx368   120                     CONTINUE369                       ELSE370                           IF (nounit) temp = temp*conjg(a(kplus1,j))371                           DO 130 i = j - 1,max(1,j-k),-1372                               temp = temp + conjg(a(l+i,j))*x(ix)373                               ix = ix - incx374   130                     CONTINUE375                       END IF376                       x(jx) = temp377                       jx = jx - incx378   140             CONTINUE379               END IF380           ELSE381               IF (incx.EQ.1) THEN382                   DO 170 j = 1,n383                       temp = x(j)384                       l = 1 - j385                       IF (noconj) THEN386                           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                     CONTINUE390                       ELSE391                           IF (nounit) temp = temp*conjg(a(1,j))392                           DO 160 i = j + 1,min(n,j+k)393                               temp = temp + conjg(a(l+i,j))*x(i)394   160                     CONTINUE395                       END IF396                       x(j) = temp397   170             CONTINUE398               ELSE399                   jx = kx400                   DO 200 j = 1,n401                       temp = x(jx)402                       kx = kx + incx403                       ix = kx404                       l = 1 - j405                       IF (noconj) THEN406                           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 + incx410   180                     CONTINUE411                       ELSE412                           IF (nounit) temp = temp*conjg(a(1,j))413                           DO 190 i = j + 1,min(n,j+k)414                               temp = temp + conjg(a(l+i,j))*x(ix)415                               ix = ix + incx416   190                     CONTINUE417                       END IF418                       x(jx) = temp419                       jx = jx + incx420   200             CONTINUE421               END IF422           END IF423       END IF424 *425       RETURN426 *427 *     End of CTBMV .428 *
 

Author

Generated automatically by Doxygen for LAPACK from the source code.


 

Index

NAME
SYNOPSIS
Functions/Subroutines
Function/Subroutine Documentation
subroutine CTBMV (character UPLO, character TRANS, character DIAG, integer N, integer K, complex, dimension(lda,*) A, integer LDA, complex, dimension(*) X, integer INCX)
Author

This document was created byman2html,using the manual pages.