Home | History | Annotate | Download | only in blas
      1       SUBROUTINE CTPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
      2 *     .. Scalar Arguments ..
      3       INTEGER INCX,N
      4       CHARACTER DIAG,TRANS,UPLO
      5 *     ..
      6 *     .. Array Arguments ..
      7       COMPLEX AP(*),X(*)
      8 *     ..
      9 *
     10 *  Purpose
     11 *  =======
     12 *
     13 *  CTPSV  solves one of the systems of equations
     14 *
     15 *     A*x = b,   or   A'*x = b,   or   conjg( A' )*x = b,
     16 *
     17 *  where b and x are n element vectors and A is an n by n unit, or
     18 *  non-unit, upper or lower triangular matrix, supplied in packed form.
     19 *
     20 *  No test for singularity or near-singularity is included in this
     21 *  routine. Such tests must be performed before calling this routine.
     22 *
     23 *  Arguments
     24 *  ==========
     25 *
     26 *  UPLO   - CHARACTER*1.
     27 *           On entry, UPLO specifies whether the matrix is an upper or
     28 *           lower triangular matrix as follows:
     29 *
     30 *              UPLO = 'U' or 'u'   A is an upper triangular matrix.
     31 *
     32 *              UPLO = 'L' or 'l'   A is a lower triangular matrix.
     33 *
     34 *           Unchanged on exit.
     35 *
     36 *  TRANS  - CHARACTER*1.
     37 *           On entry, TRANS specifies the equations to be solved as
     38 *           follows:
     39 *
     40 *              TRANS = 'N' or 'n'   A*x = b.
     41 *
     42 *              TRANS = 'T' or 't'   A'*x = b.
     43 *
     44 *              TRANS = 'C' or 'c'   conjg( A' )*x = b.
     45 *
     46 *           Unchanged on exit.
     47 *
     48 *  DIAG   - CHARACTER*1.
     49 *           On entry, DIAG specifies whether or not A is unit
     50 *           triangular as follows:
     51 *
     52 *              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
     53 *
     54 *              DIAG = 'N' or 'n'   A is not assumed to be unit
     55 *                                  triangular.
     56 *
     57 *           Unchanged on exit.
     58 *
     59 *  N      - INTEGER.
     60 *           On entry, N specifies the order of the matrix A.
     61 *           N must be at least zero.
     62 *           Unchanged on exit.
     63 *
     64 *  AP     - COMPLEX          array of DIMENSION at least
     65 *           ( ( n*( n + 1 ) )/2 ).
     66 *           Before entry with  UPLO = 'U' or 'u', the array AP must
     67 *           contain the upper triangular matrix packed sequentially,
     68 *           column by column, so that AP( 1 ) contains a( 1, 1 ),
     69 *           AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
     70 *           respectively, and so on.
     71 *           Before entry with UPLO = 'L' or 'l', the array AP must
     72 *           contain the lower triangular matrix packed sequentially,
     73 *           column by column, so that AP( 1 ) contains a( 1, 1 ),
     74 *           AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
     75 *           respectively, and so on.
     76 *           Note that when  DIAG = 'U' or 'u', the diagonal elements of
     77 *           A are not referenced, but are assumed to be unity.
     78 *           Unchanged on exit.
     79 *
     80 *  X      - COMPLEX          array of dimension at least
     81 *           ( 1 + ( n - 1 )*abs( INCX ) ).
     82 *           Before entry, the incremented array X must contain the n
     83 *           element right-hand side vector b. On exit, X is overwritten
     84 *           with the solution vector x.
     85 *
     86 *  INCX   - INTEGER.
     87 *           On entry, INCX specifies the increment for the elements of
     88 *           X. INCX must not be zero.
     89 *           Unchanged on exit.
     90 *
     91 *  Further Details
     92 *  ===============
     93 *
     94 *  Level 2 Blas routine.
     95 *
     96 *  -- Written on 22-October-1986.
     97 *     Jack Dongarra, Argonne National Lab.
     98 *     Jeremy Du Croz, Nag Central Office.
     99 *     Sven Hammarling, Nag Central Office.
    100 *     Richard Hanson, Sandia National Labs.
    101 *
    102 *  =====================================================================
    103 *
    104 *     .. Parameters ..
    105       COMPLEX ZERO
    106       PARAMETER (ZERO= (0.0E+0,0.0E+0))
    107 *     ..
    108 *     .. Local Scalars ..
    109       COMPLEX TEMP
    110       INTEGER I,INFO,IX,J,JX,K,KK,KX
    111       LOGICAL NOCONJ,NOUNIT
    112 *     ..
    113 *     .. External Functions ..
    114       LOGICAL LSAME
    115       EXTERNAL LSAME
    116 *     ..
    117 *     .. External Subroutines ..
    118       EXTERNAL XERBLA
    119 *     ..
    120 *     .. Intrinsic Functions ..
    121       INTRINSIC CONJG
    122 *     ..
    123 *
    124 *     Test the input parameters.
    125 *
    126       INFO = 0
    127       IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
    128           INFO = 1
    129       ELSE IF (.NOT.LSAME(TRANS,'N') .AND. .NOT.LSAME(TRANS,'T') .AND.
    130      +         .NOT.LSAME(TRANS,'C')) THEN
    131           INFO = 2
    132       ELSE IF (.NOT.LSAME(DIAG,'U') .AND. .NOT.LSAME(DIAG,'N')) THEN
    133           INFO = 3
    134       ELSE IF (N.LT.0) THEN
    135           INFO = 4
    136       ELSE IF (INCX.EQ.0) THEN
    137           INFO = 7
    138       END IF
    139       IF (INFO.NE.0) THEN
    140           CALL XERBLA('CTPSV ',INFO)
    141           RETURN
    142       END IF
    143 *
    144 *     Quick return if possible.
    145 *
    146       IF (N.EQ.0) RETURN
    147 *
    148       NOCONJ = LSAME(TRANS,'T')
    149       NOUNIT = LSAME(DIAG,'N')
    150 *
    151 *     Set up the start point in X if the increment is not unity. This
    152 *     will be  ( N - 1 )*INCX  too small for descending loops.
    153 *
    154       IF (INCX.LE.0) THEN
    155           KX = 1 - (N-1)*INCX
    156       ELSE IF (INCX.NE.1) THEN
    157           KX = 1
    158       END IF
    159 *
    160 *     Start the operations. In this version the elements of AP are
    161 *     accessed sequentially with one pass through AP.
    162 *
    163       IF (LSAME(TRANS,'N')) THEN
    164 *
    165 *        Form  x := inv( A )*x.
    166 *
    167           IF (LSAME(UPLO,'U')) THEN
    168               KK = (N* (N+1))/2
    169               IF (INCX.EQ.1) THEN
    170                   DO 20 J = N,1,-1
    171                       IF (X(J).NE.ZERO) THEN
    172                           IF (NOUNIT) X(J) = X(J)/AP(KK)
    173                           TEMP = X(J)
    174                           K = KK - 1
    175                           DO 10 I = J - 1,1,-1
    176                               X(I) = X(I) - TEMP*AP(K)
    177                               K = K - 1
    178    10                     CONTINUE
    179                       END IF
    180                       KK = KK - J
    181    20             CONTINUE
    182               ELSE
    183                   JX = KX + (N-1)*INCX
    184                   DO 40 J = N,1,-1
    185                       IF (X(JX).NE.ZERO) THEN
    186                           IF (NOUNIT) X(JX) = X(JX)/AP(KK)
    187                           TEMP = X(JX)
    188                           IX = JX
    189                           DO 30 K = KK - 1,KK - J + 1,-1
    190                               IX = IX - INCX
    191                               X(IX) = X(IX) - TEMP*AP(K)
    192    30                     CONTINUE
    193                       END IF
    194                       JX = JX - INCX
    195                       KK = KK - J
    196    40             CONTINUE
    197               END IF
    198           ELSE
    199               KK = 1
    200               IF (INCX.EQ.1) THEN
    201                   DO 60 J = 1,N
    202                       IF (X(J).NE.ZERO) THEN
    203                           IF (NOUNIT) X(J) = X(J)/AP(KK)
    204                           TEMP = X(J)
    205                           K = KK + 1
    206                           DO 50 I = J + 1,N
    207                               X(I) = X(I) - TEMP*AP(K)
    208                               K = K + 1
    209    50                     CONTINUE
    210                       END IF
    211                       KK = KK + (N-J+1)
    212    60             CONTINUE
    213               ELSE
    214                   JX = KX
    215                   DO 80 J = 1,N
    216                       IF (X(JX).NE.ZERO) THEN
    217                           IF (NOUNIT) X(JX) = X(JX)/AP(KK)
    218                           TEMP = X(JX)
    219                           IX = JX
    220                           DO 70 K = KK + 1,KK + N - J
    221                               IX = IX + INCX
    222                               X(IX) = X(IX) - TEMP*AP(K)
    223    70                     CONTINUE
    224                       END IF
    225                       JX = JX + INCX
    226                       KK = KK + (N-J+1)
    227    80             CONTINUE
    228               END IF
    229           END IF
    230       ELSE
    231 *
    232 *        Form  x := inv( A' )*x  or  x := inv( conjg( A' ) )*x.
    233 *
    234           IF (LSAME(UPLO,'U')) THEN
    235               KK = 1
    236               IF (INCX.EQ.1) THEN
    237                   DO 110 J = 1,N
    238                       TEMP = X(J)
    239                       K = KK
    240                       IF (NOCONJ) THEN
    241                           DO 90 I = 1,J - 1
    242                               TEMP = TEMP - AP(K)*X(I)
    243                               K = K + 1
    244    90                     CONTINUE
    245                           IF (NOUNIT) TEMP = TEMP/AP(KK+J-1)
    246                       ELSE
    247                           DO 100 I = 1,J - 1
    248                               TEMP = TEMP - CONJG(AP(K))*X(I)
    249                               K = K + 1
    250   100                     CONTINUE
    251                           IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK+J-1))
    252                       END IF
    253                       X(J) = TEMP
    254                       KK = KK + J
    255   110             CONTINUE
    256               ELSE
    257                   JX = KX
    258                   DO 140 J = 1,N
    259                       TEMP = X(JX)
    260                       IX = KX
    261                       IF (NOCONJ) THEN
    262                           DO 120 K = KK,KK + J - 2
    263                               TEMP = TEMP - AP(K)*X(IX)
    264                               IX = IX + INCX
    265   120                     CONTINUE
    266                           IF (NOUNIT) TEMP = TEMP/AP(KK+J-1)
    267                       ELSE
    268                           DO 130 K = KK,KK + J - 2
    269                               TEMP = TEMP - CONJG(AP(K))*X(IX)
    270                               IX = IX + INCX
    271   130                     CONTINUE
    272                           IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK+J-1))
    273                       END IF
    274                       X(JX) = TEMP
    275                       JX = JX + INCX
    276                       KK = KK + J
    277   140             CONTINUE
    278               END IF
    279           ELSE
    280               KK = (N* (N+1))/2
    281               IF (INCX.EQ.1) THEN
    282                   DO 170 J = N,1,-1
    283                       TEMP = X(J)
    284                       K = KK
    285                       IF (NOCONJ) THEN
    286                           DO 150 I = N,J + 1,-1
    287                               TEMP = TEMP - AP(K)*X(I)
    288                               K = K - 1
    289   150                     CONTINUE
    290                           IF (NOUNIT) TEMP = TEMP/AP(KK-N+J)
    291                       ELSE
    292                           DO 160 I = N,J + 1,-1
    293                               TEMP = TEMP - CONJG(AP(K))*X(I)
    294                               K = K - 1
    295   160                     CONTINUE
    296                           IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK-N+J))
    297                       END IF
    298                       X(J) = TEMP
    299                       KK = KK - (N-J+1)
    300   170             CONTINUE
    301               ELSE
    302                   KX = KX + (N-1)*INCX
    303                   JX = KX
    304                   DO 200 J = N,1,-1
    305                       TEMP = X(JX)
    306                       IX = KX
    307                       IF (NOCONJ) THEN
    308                           DO 180 K = KK,KK - (N- (J+1)),-1
    309                               TEMP = TEMP - AP(K)*X(IX)
    310                               IX = IX - INCX
    311   180                     CONTINUE
    312                           IF (NOUNIT) TEMP = TEMP/AP(KK-N+J)
    313                       ELSE
    314                           DO 190 K = KK,KK - (N- (J+1)),-1
    315                               TEMP = TEMP - CONJG(AP(K))*X(IX)
    316                               IX = IX - INCX
    317   190                     CONTINUE
    318                           IF (NOUNIT) TEMP = TEMP/CONJG(AP(KK-N+J))
    319                       END IF
    320                       X(JX) = TEMP
    321                       JX = JX - INCX
    322                       KK = KK - (N-J+1)
    323   200             CONTINUE
    324               END IF
    325           END IF
    326       END IF
    327 *
    328       RETURN
    329 *
    330 *     End of CTPSV .
    331 *
    332       END
    333