LAPACK 3.3.0

stpmv.f

Go to the documentation of this file.
00001       SUBROUTINE STPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
00002 *     .. Scalar Arguments ..
00003       INTEGER INCX,N
00004       CHARACTER DIAG,TRANS,UPLO
00005 *     ..
00006 *     .. Array Arguments ..
00007       REAL AP(*),X(*)
00008 *     ..
00009 *
00010 *  Purpose
00011 *  =======
00012 *
00013 *  STPMV  performs one of the matrix-vector operations
00014 *
00015 *     x := A*x,   or   x := A'*x,
00016 *
00017 *  where x is an n element vector and  A is an n by n unit, or non-unit,
00018 *  upper or lower triangular matrix, supplied in packed form.
00019 *
00020 *  Arguments
00021 *  ==========
00022 *
00023 *  UPLO   - CHARACTER*1.
00024 *           On entry, UPLO specifies whether the matrix is an upper or
00025 *           lower triangular matrix as follows:
00026 *
00027 *              UPLO = 'U' or 'u'   A is an upper triangular matrix.
00028 *
00029 *              UPLO = 'L' or 'l'   A is a lower triangular matrix.
00030 *
00031 *           Unchanged on exit.
00032 *
00033 *  TRANS  - CHARACTER*1.
00034 *           On entry, TRANS specifies the operation to be performed as
00035 *           follows:
00036 *
00037 *              TRANS = 'N' or 'n'   x := A*x.
00038 *
00039 *              TRANS = 'T' or 't'   x := A'*x.
00040 *
00041 *              TRANS = 'C' or 'c'   x := A'*x.
00042 *
00043 *           Unchanged on exit.
00044 *
00045 *  DIAG   - CHARACTER*1.
00046 *           On entry, DIAG specifies whether or not A is unit
00047 *           triangular as follows:
00048 *
00049 *              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
00050 *
00051 *              DIAG = 'N' or 'n'   A is not assumed to be unit
00052 *                                  triangular.
00053 *
00054 *           Unchanged on exit.
00055 *
00056 *  N      - INTEGER.
00057 *           On entry, N specifies the order of the matrix A.
00058 *           N must be at least zero.
00059 *           Unchanged on exit.
00060 *
00061 *  AP     - REAL             array of DIMENSION at least
00062 *           ( ( n*( n + 1 ) )/2 ).
00063 *           Before entry with  UPLO = 'U' or 'u', the array AP must
00064 *           contain the upper triangular matrix packed sequentially,
00065 *           column by column, so that AP( 1 ) contains a( 1, 1 ),
00066 *           AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
00067 *           respectively, and so on.
00068 *           Before entry with UPLO = 'L' or 'l', the array AP must
00069 *           contain the lower triangular matrix packed sequentially,
00070 *           column by column, so that AP( 1 ) contains a( 1, 1 ),
00071 *           AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
00072 *           respectively, and so on.
00073 *           Note that when  DIAG = 'U' or 'u', the diagonal elements of
00074 *           A are not referenced, but are assumed to be unity.
00075 *           Unchanged on exit.
00076 *
00077 *  X      - REAL             array of dimension at least
00078 *           ( 1 + ( n - 1 )*abs( INCX ) ).
00079 *           Before entry, the incremented array X must contain the n
00080 *           element vector x. On exit, X is overwritten with the
00081 *           tranformed vector x.
00082 *
00083 *  INCX   - INTEGER.
00084 *           On entry, INCX specifies the increment for the elements of
00085 *           X. INCX must not be zero.
00086 *           Unchanged on exit.
00087 *
00088 *  Further Details
00089 *  ===============
00090 *
00091 *  Level 2 Blas routine.
00092 *
00093 *  -- Written on 22-October-1986.
00094 *     Jack Dongarra, Argonne National Lab.
00095 *     Jeremy Du Croz, Nag Central Office.
00096 *     Sven Hammarling, Nag Central Office.
00097 *     Richard Hanson, Sandia National Labs.
00098 *
00099 *  =====================================================================
00100 *
00101 *     .. Parameters ..
00102       REAL ZERO
00103       PARAMETER (ZERO=0.0E+0)
00104 *     ..
00105 *     .. Local Scalars ..
00106       REAL TEMP
00107       INTEGER I,INFO,IX,J,JX,K,KK,KX
00108       LOGICAL NOUNIT
00109 *     ..
00110 *     .. External Functions ..
00111       LOGICAL LSAME
00112       EXTERNAL LSAME
00113 *     ..
00114 *     .. External Subroutines ..
00115       EXTERNAL XERBLA
00116 *     ..
00117 *
00118 *     Test the input parameters.
00119 *
00120       INFO = 0
00121       IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
00122           INFO = 1
00123       ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
00124      +         .NOT.LSAME(TRANS,'C')) THEN
00125           INFO = 2
00126       ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
00127           INFO = 3
00128       ELSE IF (N.LT.0) THEN
00129           INFO = 4
00130       ELSE IF (INCX.EQ.0) THEN
00131           INFO = 7
00132       END IF
00133       IF (INFO.NE.0) THEN
00134           CALL XERBLA('STPMV ',INFO)
00135           RETURN
00136       END IF
00137 *
00138 *     Quick return if possible.
00139 *
00140       IF (N.EQ.0) RETURN
00141 *
00142       NOUNIT = LSAME(DIAG,'N')
00143 *
00144 *     Set up the start point in X if the increment is not unity. This
00145 *     will be  ( N - 1 )*INCX  too small for descending loops.
00146 *
00147       IF (INCX.LE.0) THEN
00148           KX = 1 - (N-1)*INCX
00149       ELSE IF (INCX.NE.1) THEN
00150           KX = 1
00151       END IF
00152 *
00153 *     Start the operations. In this version the elements of AP are
00154 *     accessed sequentially with one pass through AP.
00155 *
00156       IF (LSAME(TRANS,'N')) THEN
00157 *
00158 *        Form  x:= A*x.
00159 *
00160           IF (LSAME(UPLO,'U')) THEN
00161               KK = 1
00162               IF (INCX.EQ.1) THEN
00163                   DO 20 J = 1,N
00164                       IF (X(J).NE.ZERO) THEN
00165                           TEMP = X(J)
00166                           K = KK
00167                           DO 10 I = 1,J - 1
00168                               X(I) = X(I) + TEMP*AP(K)
00169                               K = K + 1
00170    10                     CONTINUE
00171                           IF (NOUNIT) X(J) = X(J)*AP(KK+J-1)
00172                       END IF
00173                       KK = KK + J
00174    20             CONTINUE
00175               ELSE
00176                   JX = KX
00177                   DO 40 J = 1,N
00178                       IF (X(JX).NE.ZERO) THEN
00179                           TEMP = X(JX)
00180                           IX = KX
00181                           DO 30 K = KK,KK + J - 2
00182                               X(IX) = X(IX) + TEMP*AP(K)
00183                               IX = IX + INCX
00184    30                     CONTINUE
00185                           IF (NOUNIT) X(JX) = X(JX)*AP(KK+J-1)
00186                       END IF
00187                       JX = JX + INCX
00188                       KK = KK + J
00189    40             CONTINUE
00190               END IF
00191           ELSE
00192               KK = (N* (N+1))/2
00193               IF (INCX.EQ.1) THEN
00194                   DO 60 J = N,1,-1
00195                       IF (X(J).NE.ZERO) THEN
00196                           TEMP = X(J)
00197                           K = KK
00198                           DO 50 I = N,J + 1,-1
00199                               X(I) = X(I) + TEMP*AP(K)
00200                               K = K - 1
00201    50                     CONTINUE
00202                           IF (NOUNIT) X(J) = X(J)*AP(KK-N+J)
00203                       END IF
00204                       KK = KK - (N-J+1)
00205    60             CONTINUE
00206               ELSE
00207                   KX = KX + (N-1)*INCX
00208                   JX = KX
00209                   DO 80 J = N,1,-1
00210                       IF (X(JX).NE.ZERO) THEN
00211                           TEMP = X(JX)
00212                           IX = KX
00213                           DO 70 K = KK,KK - (N- (J+1)),-1
00214                               X(IX) = X(IX) + TEMP*AP(K)
00215                               IX = IX - INCX
00216    70                     CONTINUE
00217                           IF (NOUNIT) X(JX) = X(JX)*AP(KK-N+J)
00218                       END IF
00219                       JX = JX - INCX
00220                       KK = KK - (N-J+1)
00221    80             CONTINUE
00222               END IF
00223           END IF
00224       ELSE
00225 *
00226 *        Form  x := A'*x.
00227 *
00228           IF (LSAME(UPLO,'U')) THEN
00229               KK = (N* (N+1))/2
00230               IF (INCX.EQ.1) THEN
00231                   DO 100 J = N,1,-1
00232                       TEMP = X(J)
00233                       IF (NOUNIT) TEMP = TEMP*AP(KK)
00234                       K = KK - 1
00235                       DO 90 I = J - 1,1,-1
00236                           TEMP = TEMP + AP(K)*X(I)
00237                           K = K - 1
00238    90                 CONTINUE
00239                       X(J) = TEMP
00240                       KK = KK - J
00241   100             CONTINUE
00242               ELSE
00243                   JX = KX + (N-1)*INCX
00244                   DO 120 J = N,1,-1
00245                       TEMP = X(JX)
00246                       IX = JX
00247                       IF (NOUNIT) TEMP = TEMP*AP(KK)
00248                       DO 110 K = KK - 1,KK - J + 1,-1
00249                           IX = IX - INCX
00250                           TEMP = TEMP + AP(K)*X(IX)
00251   110                 CONTINUE
00252                       X(JX) = TEMP
00253                       JX = JX - INCX
00254                       KK = KK - J
00255   120             CONTINUE
00256               END IF
00257           ELSE
00258               KK = 1
00259               IF (INCX.EQ.1) THEN
00260                   DO 140 J = 1,N
00261                       TEMP = X(J)
00262                       IF (NOUNIT) TEMP = TEMP*AP(KK)
00263                       K = KK + 1
00264                       DO 130 I = J + 1,N
00265                           TEMP = TEMP + AP(K)*X(I)
00266                           K = K + 1
00267   130                 CONTINUE
00268                       X(J) = TEMP
00269                       KK = KK + (N-J+1)
00270   140             CONTINUE
00271               ELSE
00272                   JX = KX
00273                   DO 160 J = 1,N
00274                       TEMP = X(JX)
00275                       IX = JX
00276                       IF (NOUNIT) TEMP = TEMP*AP(KK)
00277                       DO 150 K = KK + 1,KK + N - J
00278                           IX = IX + INCX
00279                           TEMP = TEMP + AP(K)*X(IX)
00280   150                 CONTINUE
00281                       X(JX) = TEMP
00282                       JX = JX + INCX
00283                       KK = KK + (N-J+1)
00284   160             CONTINUE
00285               END IF
00286           END IF
00287       END IF
00288 *
00289       RETURN
00290 *
00291 *     End of STPMV .
00292 *
00293       END
 All Files Functions