LAPACK 3.3.1
Linear Algebra PACKage

chpmv.f

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