⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 sgbmv.f

📁 贝尔实验室多年开发的矩阵计算程序库的说明文件
💻 F
字号:
      SUBROUTINE SGBMV(TRANS,M,N,KL,KU,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)*     .. Scalar Arguments ..      REAL ALPHA,BETA      INTEGER INCX,INCY,KL,KU,LDA,M,N      CHARACTER TRANS*     ..*     .. Array Arguments ..      REAL A(LDA,*),X(*),Y(*)*     ..**  Purpose*  =======**  SGBMV  performs one of the matrix-vector operations**     y := alpha*A*x + beta*y,   or   y := alpha*A'*x + beta*y,**  where alpha and beta are scalars, x and y are vectors and A is an*  m by n band matrix, with kl sub-diagonals and ku super-diagonals.**  Arguments*  ==========**  TRANS  - CHARACTER*1.*           On entry, TRANS specifies the operation to be performed as*           follows:**              TRANS = 'N' or 'n'   y := alpha*A*x + beta*y.**              TRANS = 'T' or 't'   y := alpha*A'*x + beta*y.**              TRANS = 'C' or 'c'   y := alpha*A'*x + beta*y.**           Unchanged on exit.**  M      - INTEGER.*           On entry, M specifies the number of rows of the matrix A.*           M must be at least zero.*           Unchanged on exit.**  N      - INTEGER.*           On entry, N specifies the number of columns of the matrix A.*           N must be at least zero.*           Unchanged on exit.**  KL     - INTEGER.*           On entry, KL specifies the number of sub-diagonals of the*           matrix A. KL must satisfy  0 .le. KL.*           Unchanged on exit.**  KU     - INTEGER.*           On entry, KU specifies the number of super-diagonals of the*           matrix A. KU must satisfy  0 .le. KU.*           Unchanged on exit.**  ALPHA  - REAL            .*           On entry, ALPHA specifies the scalar alpha.*           Unchanged on exit.**  A      - REAL             array of DIMENSION ( LDA, n ).*           Before entry, the leading ( kl + ku + 1 ) by n part of the*           array A must contain the matrix of coefficients, supplied*           column by column, with the leading diagonal of the matrix in*           row ( ku + 1 ) of the array, the first super-diagonal*           starting at position 2 in row ku, the first sub-diagonal*           starting at position 1 in row ( ku + 2 ), and so on.*           Elements in the array A that do not correspond to elements*           in the band matrix (such as the top left ku by ku triangle)*           are not referenced.*           The following program segment will transfer a band matrix*           from conventional full matrix storage to band storage:**                 DO 20, J = 1, N*                    K = KU + 1 - J*                    DO 10, I = MAX( 1, J - KU ), MIN( M, J + KL )*                       A( K + I, J ) = matrix( I, J )*              10    CONTINUE*              20 CONTINUE**           Unchanged on exit.**  LDA    - INTEGER.*           On entry, LDA specifies the first dimension of A as declared*           in the calling (sub) program. LDA must be at least*           ( kl + ku + 1 ).*           Unchanged on exit.**  X      - REAL             array of DIMENSION at least*           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'*           and at least*           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.*           Before entry, the incremented array X must contain the*           vector x.*           Unchanged on exit.**  INCX   - INTEGER.*           On entry, INCX specifies the increment for the elements of*           X. INCX must not be zero.*           Unchanged on exit.**  BETA   - REAL            .*           On entry, BETA specifies the scalar beta. When BETA is*           supplied as zero then Y need not be set on input.*           Unchanged on exit.**  Y      - REAL             array of DIMENSION at least*           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'*           and at least*           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.*           Before entry, the incremented array Y must contain the*           vector y. On exit, Y is overwritten by the updated vector y.**  INCY   - INTEGER.*           On entry, INCY specifies the increment for the elements of*           Y. INCY must not be zero.*           Unchanged on exit.***  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.**     .. Parameters ..      REAL ONE,ZERO      PARAMETER (ONE=1.0E+0,ZERO=0.0E+0)*     ..*     .. Local Scalars ..      REAL TEMP      INTEGER I,INFO,IX,IY,J,JX,JY,K,KUP1,KX,KY,LENX,LENY*     ..*     .. External Functions ..      LOGICAL LSAME      EXTERNAL LSAME*     ..*     .. External Subroutines ..      EXTERNAL XERBLA*     ..*     .. Intrinsic Functions ..      INTRINSIC MAX,MIN*     ..**     Test the input parameters.*      INFO = 0      IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.     +    .NOT.LSAME(TRANS,'C')) THEN          INFO = 1      ELSE IF (M.LT.0) THEN          INFO = 2      ELSE IF (N.LT.0) THEN          INFO = 3      ELSE IF (KL.LT.0) THEN          INFO = 4      ELSE IF (KU.LT.0) THEN          INFO = 5      ELSE IF (LDA.LT. (KL+KU+1)) THEN          INFO = 8      ELSE IF (INCX.EQ.0) THEN          INFO = 10      ELSE IF (INCY.EQ.0) THEN          INFO = 13      END IF      IF (INFO.NE.0) THEN          CALL XERBLA('SGBMV ',INFO)          RETURN      END IF**     Quick return if possible.*      IF ((M.EQ.0) .OR. (N.EQ.0) .OR.     +    ((ALPHA.EQ.ZERO).AND. (BETA.EQ.ONE))) RETURN**     Set  LENX  and  LENY, the lengths of the vectors x and y, and set*     up the start points in  X  and  Y.*      IF (LSAME(TRANS,'N')) THEN          LENX = N          LENY = M      ELSE          LENX = M          LENY = N      END IF      IF (INCX.GT.0) THEN          KX = 1      ELSE          KX = 1 - (LENX-1)*INCX      END IF      IF (INCY.GT.0) THEN          KY = 1      ELSE          KY = 1 - (LENY-1)*INCY      END IF**     Start the operations. In this version the elements of A are*     accessed sequentially with one pass through the band part of A.**     First form  y := beta*y.*      IF (BETA.NE.ONE) THEN          IF (INCY.EQ.1) THEN              IF (BETA.EQ.ZERO) THEN                  DO 10 I = 1,LENY                      Y(I) = ZERO   10             CONTINUE              ELSE                  DO 20 I = 1,LENY                      Y(I) = BETA*Y(I)   20             CONTINUE              END IF          ELSE              IY = KY              IF (BETA.EQ.ZERO) THEN                  DO 30 I = 1,LENY                      Y(IY) = ZERO                      IY = IY + INCY   30             CONTINUE              ELSE                  DO 40 I = 1,LENY                      Y(IY) = BETA*Y(IY)                      IY = IY + INCY   40             CONTINUE              END IF          END IF      END IF      IF (ALPHA.EQ.ZERO) RETURN      KUP1 = KU + 1      IF (LSAME(TRANS,'N')) THEN**        Form  y := alpha*A*x + y.*          JX = KX          IF (INCY.EQ.1) THEN              DO 60 J = 1,N                  IF (X(JX).NE.ZERO) THEN                      TEMP = ALPHA*X(JX)                      K = KUP1 - J                      DO 50 I = MAX(1,J-KU),MIN(M,J+KL)                          Y(I) = Y(I) + TEMP*A(K+I,J)   50                 CONTINUE                  END IF                  JX = JX + INCX   60         CONTINUE          ELSE              DO 80 J = 1,N                  IF (X(JX).NE.ZERO) THEN                      TEMP = ALPHA*X(JX)                      IY = KY                      K = KUP1 - J                      DO 70 I = MAX(1,J-KU),MIN(M,J+KL)                          Y(IY) = Y(IY) + TEMP*A(K+I,J)                          IY = IY + INCY   70                 CONTINUE                  END IF                  JX = JX + INCX                  IF (J.GT.KU) KY = KY + INCY   80         CONTINUE          END IF      ELSE**        Form  y := alpha*A'*x + y.*          JY = KY          IF (INCX.EQ.1) THEN              DO 100 J = 1,N                  TEMP = ZERO                  K = KUP1 - J                  DO 90 I = MAX(1,J-KU),MIN(M,J+KL)                      TEMP = TEMP + A(K+I,J)*X(I)   90             CONTINUE                  Y(JY) = Y(JY) + ALPHA*TEMP                  JY = JY + INCY  100         CONTINUE          ELSE              DO 120 J = 1,N                  TEMP = ZERO                  IX = KX                  K = KUP1 - J                  DO 110 I = MAX(1,J-KU),MIN(M,J+KL)                      TEMP = TEMP + A(K+I,J)*X(IX)                      IX = IX + INCX  110             CONTINUE                  Y(JY) = Y(JY) + ALPHA*TEMP                  JY = JY + INCY                  IF (J.GT.KU) KX = KX + INCX  120         CONTINUE          END IF      END IF*      RETURN**     End of SGBMV .*      END

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -