File:  [local] / rpl / lapack / blas / ztpmv.f
Revision 1.16: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:38:46 2023 UTC (8 months, 3 weeks ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Première mise à jour de lapack et blas.

    1: *> \brief \b ZTPMV
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *  Definition:
    9: *  ===========
   10: *
   11: *       SUBROUTINE ZTPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
   12: *
   13: *       .. Scalar Arguments ..
   14: *       INTEGER INCX,N
   15: *       CHARACTER DIAG,TRANS,UPLO
   16: *       ..
   17: *       .. Array Arguments ..
   18: *       COMPLEX*16 AP(*),X(*)
   19: *       ..
   20: *
   21: *
   22: *> \par Purpose:
   23: *  =============
   24: *>
   25: *> \verbatim
   26: *>
   27: *> ZTPMV  performs one of the matrix-vector operations
   28: *>
   29: *>    x := A*x,   or   x := A**T*x,   or   x := A**H*x,
   30: *>
   31: *> where x is an n element vector and  A is an n by n unit, or non-unit,
   32: *> upper or lower triangular matrix, supplied in packed form.
   33: *> \endverbatim
   34: *
   35: *  Arguments:
   36: *  ==========
   37: *
   38: *> \param[in] UPLO
   39: *> \verbatim
   40: *>          UPLO is CHARACTER*1
   41: *>           On entry, UPLO specifies whether the matrix is an upper or
   42: *>           lower triangular matrix as follows:
   43: *>
   44: *>              UPLO = 'U' or 'u'   A is an upper triangular matrix.
   45: *>
   46: *>              UPLO = 'L' or 'l'   A is a lower triangular matrix.
   47: *> \endverbatim
   48: *>
   49: *> \param[in] TRANS
   50: *> \verbatim
   51: *>          TRANS is CHARACTER*1
   52: *>           On entry, TRANS specifies the operation to be performed as
   53: *>           follows:
   54: *>
   55: *>              TRANS = 'N' or 'n'   x := A*x.
   56: *>
   57: *>              TRANS = 'T' or 't'   x := A**T*x.
   58: *>
   59: *>              TRANS = 'C' or 'c'   x := A**H*x.
   60: *> \endverbatim
   61: *>
   62: *> \param[in] DIAG
   63: *> \verbatim
   64: *>          DIAG is CHARACTER*1
   65: *>           On entry, DIAG specifies whether or not A is unit
   66: *>           triangular as follows:
   67: *>
   68: *>              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
   69: *>
   70: *>              DIAG = 'N' or 'n'   A is not assumed to be unit
   71: *>                                  triangular.
   72: *> \endverbatim
   73: *>
   74: *> \param[in] N
   75: *> \verbatim
   76: *>          N is INTEGER
   77: *>           On entry, N specifies the order of the matrix A.
   78: *>           N must be at least zero.
   79: *> \endverbatim
   80: *>
   81: *> \param[in] AP
   82: *> \verbatim
   83: *>          AP is COMPLEX*16 array, dimension at least
   84: *>           ( ( n*( n + 1 ) )/2 ).
   85: *>           Before entry with  UPLO = 'U' or 'u', the array AP must
   86: *>           contain the upper triangular matrix packed sequentially,
   87: *>           column by column, so that AP( 1 ) contains a( 1, 1 ),
   88: *>           AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
   89: *>           respectively, and so on.
   90: *>           Before entry with UPLO = 'L' or 'l', the array AP must
   91: *>           contain the lower triangular matrix packed sequentially,
   92: *>           column by column, so that AP( 1 ) contains a( 1, 1 ),
   93: *>           AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
   94: *>           respectively, and so on.
   95: *>           Note that when  DIAG = 'U' or 'u', the diagonal elements of
   96: *>           A are not referenced, but are assumed to be unity.
   97: *> \endverbatim
   98: *>
   99: *> \param[in,out] X
  100: *> \verbatim
  101: *>          X is COMPLEX*16 array, dimension at least
  102: *>           ( 1 + ( n - 1 )*abs( INCX ) ).
  103: *>           Before entry, the incremented array X must contain the n
  104: *>           element vector x. On exit, X is overwritten with the
  105: *>           transformed vector x.
  106: *> \endverbatim
  107: *>
  108: *> \param[in] INCX
  109: *> \verbatim
  110: *>          INCX is INTEGER
  111: *>           On entry, INCX specifies the increment for the elements of
  112: *>           X. INCX must not be zero.
  113: *> \endverbatim
  114: *
  115: *  Authors:
  116: *  ========
  117: *
  118: *> \author Univ. of Tennessee
  119: *> \author Univ. of California Berkeley
  120: *> \author Univ. of Colorado Denver
  121: *> \author NAG Ltd.
  122: *
  123: *> \ingroup complex16_blas_level2
  124: *
  125: *> \par Further Details:
  126: *  =====================
  127: *>
  128: *> \verbatim
  129: *>
  130: *>  Level 2 Blas routine.
  131: *>  The vector and matrix arguments are not referenced when N = 0, or M = 0
  132: *>
  133: *>  -- Written on 22-October-1986.
  134: *>     Jack Dongarra, Argonne National Lab.
  135: *>     Jeremy Du Croz, Nag Central Office.
  136: *>     Sven Hammarling, Nag Central Office.
  137: *>     Richard Hanson, Sandia National Labs.
  138: *> \endverbatim
  139: *>
  140: *  =====================================================================
  141:       SUBROUTINE ZTPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
  142: *
  143: *  -- Reference BLAS level2 routine --
  144: *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
  145: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  146: *
  147: *     .. Scalar Arguments ..
  148:       INTEGER INCX,N
  149:       CHARACTER DIAG,TRANS,UPLO
  150: *     ..
  151: *     .. Array Arguments ..
  152:       COMPLEX*16 AP(*),X(*)
  153: *     ..
  154: *
  155: *  =====================================================================
  156: *
  157: *     .. Parameters ..
  158:       COMPLEX*16 ZERO
  159:       PARAMETER (ZERO= (0.0D+0,0.0D+0))
  160: *     ..
  161: *     .. Local Scalars ..
  162:       COMPLEX*16 TEMP
  163:       INTEGER I,INFO,IX,J,JX,K,KK,KX
  164:       LOGICAL NOCONJ,NOUNIT
  165: *     ..
  166: *     .. External Functions ..
  167:       LOGICAL LSAME
  168:       EXTERNAL LSAME
  169: *     ..
  170: *     .. External Subroutines ..
  171:       EXTERNAL XERBLA
  172: *     ..
  173: *     .. Intrinsic Functions ..
  174:       INTRINSIC DCONJG
  175: *     ..
  176: *
  177: *     Test the input parameters.
  178: *
  179:       INFO = 0
  180:       IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
  181:           INFO = 1
  182:       ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
  183:      +         .NOT.LSAME(TRANS,'C')) THEN
  184:           INFO = 2
  185:       ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
  186:           INFO = 3
  187:       ELSE IF (N.LT.0) THEN
  188:           INFO = 4
  189:       ELSE IF (INCX.EQ.0) THEN
  190:           INFO = 7
  191:       END IF
  192:       IF (INFO.NE.0) THEN
  193:           CALL XERBLA('ZTPMV ',INFO)
  194:           RETURN
  195:       END IF
  196: *
  197: *     Quick return if possible.
  198: *
  199:       IF (N.EQ.0) RETURN
  200: *
  201:       NOCONJ = LSAME(TRANS,'T')
  202:       NOUNIT = LSAME(DIAG,'N')
  203: *
  204: *     Set up the start point in X if the increment is not unity. This
  205: *     will be  ( N - 1 )*INCX  too small for descending loops.
  206: *
  207:       IF (INCX.LE.0) THEN
  208:           KX = 1 - (N-1)*INCX
  209:       ELSE IF (INCX.NE.1) THEN
  210:           KX = 1
  211:       END IF
  212: *
  213: *     Start the operations. In this version the elements of AP are
  214: *     accessed sequentially with one pass through AP.
  215: *
  216:       IF (LSAME(TRANS,'N')) THEN
  217: *
  218: *        Form  x:= A*x.
  219: *
  220:           IF (LSAME(UPLO,'U')) THEN
  221:               KK = 1
  222:               IF (INCX.EQ.1) THEN
  223:                   DO 20 J = 1,N
  224:                       IF (X(J).NE.ZERO) THEN
  225:                           TEMP = X(J)
  226:                           K = KK
  227:                           DO 10 I = 1,J - 1
  228:                               X(I) = X(I) + TEMP*AP(K)
  229:                               K = K + 1
  230:    10                     CONTINUE
  231:                           IF (NOUNIT) X(J) = X(J)*AP(KK+J-1)
  232:                       END IF
  233:                       KK = KK + J
  234:    20             CONTINUE
  235:               ELSE
  236:                   JX = KX
  237:                   DO 40 J = 1,N
  238:                       IF (X(JX).NE.ZERO) THEN
  239:                           TEMP = X(JX)
  240:                           IX = KX
  241:                           DO 30 K = KK,KK + J - 2
  242:                               X(IX) = X(IX) + TEMP*AP(K)
  243:                               IX = IX + INCX
  244:    30                     CONTINUE
  245:                           IF (NOUNIT) X(JX) = X(JX)*AP(KK+J-1)
  246:                       END IF
  247:                       JX = JX + INCX
  248:                       KK = KK + J
  249:    40             CONTINUE
  250:               END IF
  251:           ELSE
  252:               KK = (N* (N+1))/2
  253:               IF (INCX.EQ.1) THEN
  254:                   DO 60 J = N,1,-1
  255:                       IF (X(J).NE.ZERO) THEN
  256:                           TEMP = X(J)
  257:                           K = KK
  258:                           DO 50 I = N,J + 1,-1
  259:                               X(I) = X(I) + TEMP*AP(K)
  260:                               K = K - 1
  261:    50                     CONTINUE
  262:                           IF (NOUNIT) X(J) = X(J)*AP(KK-N+J)
  263:                       END IF
  264:                       KK = KK - (N-J+1)
  265:    60             CONTINUE
  266:               ELSE
  267:                   KX = KX + (N-1)*INCX
  268:                   JX = KX
  269:                   DO 80 J = N,1,-1
  270:                       IF (X(JX).NE.ZERO) THEN
  271:                           TEMP = X(JX)
  272:                           IX = KX
  273:                           DO 70 K = KK,KK - (N- (J+1)),-1
  274:                               X(IX) = X(IX) + TEMP*AP(K)
  275:                               IX = IX - INCX
  276:    70                     CONTINUE
  277:                           IF (NOUNIT) X(JX) = X(JX)*AP(KK-N+J)
  278:                       END IF
  279:                       JX = JX - INCX
  280:                       KK = KK - (N-J+1)
  281:    80             CONTINUE
  282:               END IF
  283:           END IF
  284:       ELSE
  285: *
  286: *        Form  x := A**T*x  or  x := A**H*x.
  287: *
  288:           IF (LSAME(UPLO,'U')) THEN
  289:               KK = (N* (N+1))/2
  290:               IF (INCX.EQ.1) THEN
  291:                   DO 110 J = N,1,-1
  292:                       TEMP = X(J)
  293:                       K = KK - 1
  294:                       IF (NOCONJ) THEN
  295:                           IF (NOUNIT) TEMP = TEMP*AP(KK)
  296:                           DO 90 I = J - 1,1,-1
  297:                               TEMP = TEMP + AP(K)*X(I)
  298:                               K = K - 1
  299:    90                     CONTINUE
  300:                       ELSE
  301:                           IF (NOUNIT) TEMP = TEMP*DCONJG(AP(KK))
  302:                           DO 100 I = J - 1,1,-1
  303:                               TEMP = TEMP + DCONJG(AP(K))*X(I)
  304:                               K = K - 1
  305:   100                     CONTINUE
  306:                       END IF
  307:                       X(J) = TEMP
  308:                       KK = KK - J
  309:   110             CONTINUE
  310:               ELSE
  311:                   JX = KX + (N-1)*INCX
  312:                   DO 140 J = N,1,-1
  313:                       TEMP = X(JX)
  314:                       IX = JX
  315:                       IF (NOCONJ) THEN
  316:                           IF (NOUNIT) TEMP = TEMP*AP(KK)
  317:                           DO 120 K = KK - 1,KK - J + 1,-1
  318:                               IX = IX - INCX
  319:                               TEMP = TEMP + AP(K)*X(IX)
  320:   120                     CONTINUE
  321:                       ELSE
  322:                           IF (NOUNIT) TEMP = TEMP*DCONJG(AP(KK))
  323:                           DO 130 K = KK - 1,KK - J + 1,-1
  324:                               IX = IX - INCX
  325:                               TEMP = TEMP + DCONJG(AP(K))*X(IX)
  326:   130                     CONTINUE
  327:                       END IF
  328:                       X(JX) = TEMP
  329:                       JX = JX - INCX
  330:                       KK = KK - J
  331:   140             CONTINUE
  332:               END IF
  333:           ELSE
  334:               KK = 1
  335:               IF (INCX.EQ.1) THEN
  336:                   DO 170 J = 1,N
  337:                       TEMP = X(J)
  338:                       K = KK + 1
  339:                       IF (NOCONJ) THEN
  340:                           IF (NOUNIT) TEMP = TEMP*AP(KK)
  341:                           DO 150 I = J + 1,N
  342:                               TEMP = TEMP + AP(K)*X(I)
  343:                               K = K + 1
  344:   150                     CONTINUE
  345:                       ELSE
  346:                           IF (NOUNIT) TEMP = TEMP*DCONJG(AP(KK))
  347:                           DO 160 I = J + 1,N
  348:                               TEMP = TEMP + DCONJG(AP(K))*X(I)
  349:                               K = K + 1
  350:   160                     CONTINUE
  351:                       END IF
  352:                       X(J) = TEMP
  353:                       KK = KK + (N-J+1)
  354:   170             CONTINUE
  355:               ELSE
  356:                   JX = KX
  357:                   DO 200 J = 1,N
  358:                       TEMP = X(JX)
  359:                       IX = JX
  360:                       IF (NOCONJ) THEN
  361:                           IF (NOUNIT) TEMP = TEMP*AP(KK)
  362:                           DO 180 K = KK + 1,KK + N - J
  363:                               IX = IX + INCX
  364:                               TEMP = TEMP + AP(K)*X(IX)
  365:   180                     CONTINUE
  366:                       ELSE
  367:                           IF (NOUNIT) TEMP = TEMP*DCONJG(AP(KK))
  368:                           DO 190 K = KK + 1,KK + N - J
  369:                               IX = IX + INCX
  370:                               TEMP = TEMP + DCONJG(AP(K))*X(IX)
  371:   190                     CONTINUE
  372:                       END IF
  373:                       X(JX) = TEMP
  374:                       JX = JX + INCX
  375:                       KK = KK + (N-J+1)
  376:   200             CONTINUE
  377:               END IF
  378:           END IF
  379:       END IF
  380: *
  381:       RETURN
  382: *
  383: *     End of ZTPMV
  384: *
  385:       END

CVSweb interface <joel.bertrand@systella.fr>