File:  [local] / rpl / lapack / lapack / zla_syrcond_c.f
Revision 1.18: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:28 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 ZLA_SYRCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for symmetric indefinite matrices.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZLA_SYRCOND_C + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zla_syrcond_c.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zla_syrcond_c.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zla_syrcond_c.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       DOUBLE PRECISION FUNCTION ZLA_SYRCOND_C( UPLO, N, A, LDA, AF,
   22: *                                                LDAF, IPIV, C, CAPPLY,
   23: *                                                INFO, WORK, RWORK )
   24: *
   25: *       .. Scalar Arguments ..
   26: *       CHARACTER          UPLO
   27: *       LOGICAL            CAPPLY
   28: *       INTEGER            N, LDA, LDAF, INFO
   29: *       ..
   30: *       .. Array Arguments ..
   31: *       INTEGER            IPIV( * )
   32: *       COMPLEX*16         A( LDA, * ), AF( LDAF, * ), WORK( * )
   33: *       DOUBLE PRECISION   C( * ), RWORK( * )
   34: *       ..
   35: *
   36: *
   37: *> \par Purpose:
   38: *  =============
   39: *>
   40: *> \verbatim
   41: *>
   42: *>    ZLA_SYRCOND_C Computes the infinity norm condition number of
   43: *>    op(A) * inv(diag(C)) where C is a DOUBLE PRECISION vector.
   44: *> \endverbatim
   45: *
   46: *  Arguments:
   47: *  ==========
   48: *
   49: *> \param[in] UPLO
   50: *> \verbatim
   51: *>          UPLO is CHARACTER*1
   52: *>       = 'U':  Upper triangle of A is stored;
   53: *>       = 'L':  Lower triangle of A is stored.
   54: *> \endverbatim
   55: *>
   56: *> \param[in] N
   57: *> \verbatim
   58: *>          N is INTEGER
   59: *>     The number of linear equations, i.e., the order of the
   60: *>     matrix A.  N >= 0.
   61: *> \endverbatim
   62: *>
   63: *> \param[in] A
   64: *> \verbatim
   65: *>          A is COMPLEX*16 array, dimension (LDA,N)
   66: *>     On entry, the N-by-N matrix A
   67: *> \endverbatim
   68: *>
   69: *> \param[in] LDA
   70: *> \verbatim
   71: *>          LDA is INTEGER
   72: *>     The leading dimension of the array A.  LDA >= max(1,N).
   73: *> \endverbatim
   74: *>
   75: *> \param[in] AF
   76: *> \verbatim
   77: *>          AF is COMPLEX*16 array, dimension (LDAF,N)
   78: *>     The block diagonal matrix D and the multipliers used to
   79: *>     obtain the factor U or L as computed by ZSYTRF.
   80: *> \endverbatim
   81: *>
   82: *> \param[in] LDAF
   83: *> \verbatim
   84: *>          LDAF is INTEGER
   85: *>     The leading dimension of the array AF.  LDAF >= max(1,N).
   86: *> \endverbatim
   87: *>
   88: *> \param[in] IPIV
   89: *> \verbatim
   90: *>          IPIV is INTEGER array, dimension (N)
   91: *>     Details of the interchanges and the block structure of D
   92: *>     as determined by ZSYTRF.
   93: *> \endverbatim
   94: *>
   95: *> \param[in] C
   96: *> \verbatim
   97: *>          C is DOUBLE PRECISION array, dimension (N)
   98: *>     The vector C in the formula op(A) * inv(diag(C)).
   99: *> \endverbatim
  100: *>
  101: *> \param[in] CAPPLY
  102: *> \verbatim
  103: *>          CAPPLY is LOGICAL
  104: *>     If .TRUE. then access the vector C in the formula above.
  105: *> \endverbatim
  106: *>
  107: *> \param[out] INFO
  108: *> \verbatim
  109: *>          INFO is INTEGER
  110: *>       = 0:  Successful exit.
  111: *>     i > 0:  The ith argument is invalid.
  112: *> \endverbatim
  113: *>
  114: *> \param[out] WORK
  115: *> \verbatim
  116: *>          WORK is COMPLEX*16 array, dimension (2*N).
  117: *>     Workspace.
  118: *> \endverbatim
  119: *>
  120: *> \param[out] RWORK
  121: *> \verbatim
  122: *>          RWORK is DOUBLE PRECISION array, dimension (N).
  123: *>     Workspace.
  124: *> \endverbatim
  125: *
  126: *  Authors:
  127: *  ========
  128: *
  129: *> \author Univ. of Tennessee
  130: *> \author Univ. of California Berkeley
  131: *> \author Univ. of Colorado Denver
  132: *> \author NAG Ltd.
  133: *
  134: *> \ingroup complex16SYcomputational
  135: *
  136: *  =====================================================================
  137:       DOUBLE PRECISION FUNCTION ZLA_SYRCOND_C( UPLO, N, A, LDA, AF,
  138:      $                                         LDAF, IPIV, C, CAPPLY,
  139:      $                                         INFO, WORK, RWORK )
  140: *
  141: *  -- LAPACK computational routine --
  142: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  143: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  144: *
  145: *     .. Scalar Arguments ..
  146:       CHARACTER          UPLO
  147:       LOGICAL            CAPPLY
  148:       INTEGER            N, LDA, LDAF, INFO
  149: *     ..
  150: *     .. Array Arguments ..
  151:       INTEGER            IPIV( * )
  152:       COMPLEX*16         A( LDA, * ), AF( LDAF, * ), WORK( * )
  153:       DOUBLE PRECISION   C( * ), RWORK( * )
  154: *     ..
  155: *
  156: *  =====================================================================
  157: *
  158: *     .. Local Scalars ..
  159:       INTEGER            KASE
  160:       DOUBLE PRECISION   AINVNM, ANORM, TMP
  161:       INTEGER            I, J
  162:       LOGICAL            UP, UPPER
  163:       COMPLEX*16         ZDUM
  164: *     ..
  165: *     .. Local Arrays ..
  166:       INTEGER            ISAVE( 3 )
  167: *     ..
  168: *     .. External Functions ..
  169:       LOGICAL            LSAME
  170:       EXTERNAL           LSAME
  171: *     ..
  172: *     .. External Subroutines ..
  173:       EXTERNAL           ZLACN2, ZSYTRS, XERBLA
  174: *     ..
  175: *     .. Intrinsic Functions ..
  176:       INTRINSIC          ABS, MAX
  177: *     ..
  178: *     .. Statement Functions ..
  179:       DOUBLE PRECISION CABS1
  180: *     ..
  181: *     .. Statement Function Definitions ..
  182:       CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
  183: *     ..
  184: *     .. Executable Statements ..
  185: *
  186:       ZLA_SYRCOND_C = 0.0D+0
  187: *
  188:       INFO = 0
  189:       UPPER = LSAME( UPLO, 'U' )
  190:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  191:          INFO = -1
  192:       ELSE IF( N.LT.0 ) THEN
  193:          INFO = -2
  194:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  195:          INFO = -4
  196:       ELSE IF( LDAF.LT.MAX( 1, N ) ) THEN
  197:          INFO = -6
  198:       END IF
  199:       IF( INFO.NE.0 ) THEN
  200:          CALL XERBLA( 'ZLA_SYRCOND_C', -INFO )
  201:          RETURN
  202:       END IF
  203:       UP = .FALSE.
  204:       IF ( LSAME( UPLO, 'U' ) ) UP = .TRUE.
  205: *
  206: *     Compute norm of op(A)*op2(C).
  207: *
  208:       ANORM = 0.0D+0
  209:       IF ( UP ) THEN
  210:          DO I = 1, N
  211:             TMP = 0.0D+0
  212:             IF ( CAPPLY ) THEN
  213:                DO J = 1, I
  214:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  215:                END DO
  216:                DO J = I+1, N
  217:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  218:                END DO
  219:             ELSE
  220:                DO J = 1, I
  221:                   TMP = TMP + CABS1( A( J, I ) )
  222:                END DO
  223:                DO J = I+1, N
  224:                   TMP = TMP + CABS1( A( I, J ) )
  225:                END DO
  226:             END IF
  227:             RWORK( I ) = TMP
  228:             ANORM = MAX( ANORM, TMP )
  229:          END DO
  230:       ELSE
  231:          DO I = 1, N
  232:             TMP = 0.0D+0
  233:             IF ( CAPPLY ) THEN
  234:                DO J = 1, I
  235:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  236:                END DO
  237:                DO J = I+1, N
  238:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  239:                END DO
  240:             ELSE
  241:                DO J = 1, I
  242:                   TMP = TMP + CABS1( A( I, J ) )
  243:                END DO
  244:                DO J = I+1, N
  245:                   TMP = TMP + CABS1( A( J, I ) )
  246:                END DO
  247:             END IF
  248:             RWORK( I ) = TMP
  249:             ANORM = MAX( ANORM, TMP )
  250:          END DO
  251:       END IF
  252: *
  253: *     Quick return if possible.
  254: *
  255:       IF( N.EQ.0 ) THEN
  256:          ZLA_SYRCOND_C = 1.0D+0
  257:          RETURN
  258:       ELSE IF( ANORM .EQ. 0.0D+0 ) THEN
  259:          RETURN
  260:       END IF
  261: *
  262: *     Estimate the norm of inv(op(A)).
  263: *
  264:       AINVNM = 0.0D+0
  265: *
  266:       KASE = 0
  267:    10 CONTINUE
  268:       CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
  269:       IF( KASE.NE.0 ) THEN
  270:          IF( KASE.EQ.2 ) THEN
  271: *
  272: *           Multiply by R.
  273: *
  274:             DO I = 1, N
  275:                WORK( I ) = WORK( I ) * RWORK( I )
  276:             END DO
  277: *
  278:             IF ( UP ) THEN
  279:                CALL ZSYTRS( 'U', N, 1, AF, LDAF, IPIV,
  280:      $            WORK, N, INFO )
  281:             ELSE
  282:                CALL ZSYTRS( 'L', N, 1, AF, LDAF, IPIV,
  283:      $            WORK, N, INFO )
  284:             ENDIF
  285: *
  286: *           Multiply by inv(C).
  287: *
  288:             IF ( CAPPLY ) THEN
  289:                DO I = 1, N
  290:                   WORK( I ) = WORK( I ) * C( I )
  291:                END DO
  292:             END IF
  293:          ELSE
  294: *
  295: *           Multiply by inv(C**T).
  296: *
  297:             IF ( CAPPLY ) THEN
  298:                DO I = 1, N
  299:                   WORK( I ) = WORK( I ) * C( I )
  300:                END DO
  301:             END IF
  302: *
  303:             IF ( UP ) THEN
  304:                CALL ZSYTRS( 'U', N, 1, AF, LDAF, IPIV,
  305:      $            WORK, N, INFO )
  306:             ELSE
  307:                CALL ZSYTRS( 'L', N, 1, AF, LDAF, IPIV,
  308:      $            WORK, N, INFO )
  309:             END IF
  310: *
  311: *           Multiply by R.
  312: *
  313:             DO I = 1, N
  314:                WORK( I ) = WORK( I ) * RWORK( I )
  315:             END DO
  316:          END IF
  317:          GO TO 10
  318:       END IF
  319: *
  320: *     Compute the estimate of the reciprocal condition number.
  321: *
  322:       IF( AINVNM .NE. 0.0D+0 )
  323:      $   ZLA_SYRCOND_C = 1.0D+0 / AINVNM
  324: *
  325:       RETURN
  326: *
  327: *     End of ZLA_SYRCOND_C
  328: *
  329:       END

CVSweb interface <joel.bertrand@systella.fr>