File:  [local] / rpl / lapack / lapack / zla_hercond_c.f
Revision 1.18: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:39:27 2023 UTC (9 months 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_HERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for Hermitian 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_HERCOND_C + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zla_hercond_c.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zla_hercond_c.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zla_hercond_c.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       DOUBLE PRECISION FUNCTION ZLA_HERCOND_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_HERCOND_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 ZHETRF.
   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 CHETRF.
   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 complex16HEcomputational
  135: *
  136: *  =====================================================================
  137:       DOUBLE PRECISION FUNCTION ZLA_HERCOND_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, I, J
  160:       DOUBLE PRECISION   AINVNM, ANORM, TMP
  161:       LOGICAL            UP, UPPER
  162:       COMPLEX*16         ZDUM
  163: *     ..
  164: *     .. Local Arrays ..
  165:       INTEGER            ISAVE( 3 )
  166: *     ..
  167: *     .. External Functions ..
  168:       LOGICAL            LSAME
  169:       EXTERNAL           LSAME
  170: *     ..
  171: *     .. External Subroutines ..
  172:       EXTERNAL           ZLACN2, ZHETRS, XERBLA
  173: *     ..
  174: *     .. Intrinsic Functions ..
  175:       INTRINSIC          ABS, MAX
  176: *     ..
  177: *     .. Statement Functions ..
  178:       DOUBLE PRECISION   CABS1
  179: *     ..
  180: *     .. Statement Function Definitions ..
  181:       CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
  182: *     ..
  183: *     .. Executable Statements ..
  184: *
  185:       ZLA_HERCOND_C = 0.0D+0
  186: *
  187:       INFO = 0
  188:       UPPER = LSAME( UPLO, 'U' )
  189:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  190:          INFO = -1
  191:       ELSE IF( N.LT.0 ) THEN
  192:          INFO = -2
  193:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  194:          INFO = -4
  195:       ELSE IF( LDAF.LT.MAX( 1, N ) ) THEN
  196:          INFO = -6
  197:       END IF
  198:       IF( INFO.NE.0 ) THEN
  199:          CALL XERBLA( 'ZLA_HERCOND_C', -INFO )
  200:          RETURN
  201:       END IF
  202:       UP = .FALSE.
  203:       IF ( LSAME( UPLO, 'U' ) ) UP = .TRUE.
  204: *
  205: *     Compute norm of op(A)*op2(C).
  206: *
  207:       ANORM = 0.0D+0
  208:       IF ( UP ) THEN
  209:          DO I = 1, N
  210:             TMP = 0.0D+0
  211:             IF ( CAPPLY ) THEN
  212:                DO J = 1, I
  213:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  214:                END DO
  215:                DO J = I+1, N
  216:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  217:                END DO
  218:             ELSE
  219:                DO J = 1, I
  220:                   TMP = TMP + CABS1( A( J, I ) )
  221:                END DO
  222:                DO J = I+1, N
  223:                   TMP = TMP + CABS1( A( I, J ) )
  224:                END DO
  225:             END IF
  226:             RWORK( I ) = TMP
  227:             ANORM = MAX( ANORM, TMP )
  228:          END DO
  229:       ELSE
  230:          DO I = 1, N
  231:             TMP = 0.0D+0
  232:             IF ( CAPPLY ) THEN
  233:                DO J = 1, I
  234:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  235:                END DO
  236:                DO J = I+1, N
  237:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  238:                END DO
  239:             ELSE
  240:                DO J = 1, I
  241:                   TMP = TMP + CABS1( A( I, J ) )
  242:                END DO
  243:                DO J = I+1, N
  244:                   TMP = TMP + CABS1( A( J, I ) )
  245:                END DO
  246:             END IF
  247:             RWORK( I ) = TMP
  248:             ANORM = MAX( ANORM, TMP )
  249:          END DO
  250:       END IF
  251: *
  252: *     Quick return if possible.
  253: *
  254:       IF( N.EQ.0 ) THEN
  255:          ZLA_HERCOND_C = 1.0D+0
  256:          RETURN
  257:       ELSE IF( ANORM .EQ. 0.0D+0 ) THEN
  258:          RETURN
  259:       END IF
  260: *
  261: *     Estimate the norm of inv(op(A)).
  262: *
  263:       AINVNM = 0.0D+0
  264: *
  265:       KASE = 0
  266:    10 CONTINUE
  267:       CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
  268:       IF( KASE.NE.0 ) THEN
  269:          IF( KASE.EQ.2 ) THEN
  270: *
  271: *           Multiply by R.
  272: *
  273:             DO I = 1, N
  274:                WORK( I ) = WORK( I ) * RWORK( I )
  275:             END DO
  276: *
  277:             IF ( UP ) THEN
  278:                CALL ZHETRS( 'U', N, 1, AF, LDAF, IPIV,
  279:      $            WORK, N, INFO )
  280:             ELSE
  281:                CALL ZHETRS( 'L', N, 1, AF, LDAF, IPIV,
  282:      $            WORK, N, INFO )
  283:             ENDIF
  284: *
  285: *           Multiply by inv(C).
  286: *
  287:             IF ( CAPPLY ) THEN
  288:                DO I = 1, N
  289:                   WORK( I ) = WORK( I ) * C( I )
  290:                END DO
  291:             END IF
  292:          ELSE
  293: *
  294: *           Multiply by inv(C**H).
  295: *
  296:             IF ( CAPPLY ) THEN
  297:                DO I = 1, N
  298:                   WORK( I ) = WORK( I ) * C( I )
  299:                END DO
  300:             END IF
  301: *
  302:             IF ( UP ) THEN
  303:                CALL ZHETRS( 'U', N, 1, AF, LDAF, IPIV,
  304:      $            WORK, N, INFO )
  305:             ELSE
  306:                CALL ZHETRS( 'L', N, 1, AF, LDAF, IPIV,
  307:      $            WORK, N, INFO )
  308:             END IF
  309: *
  310: *           Multiply by R.
  311: *
  312:             DO I = 1, N
  313:                WORK( I ) = WORK( I ) * RWORK( I )
  314:             END DO
  315:          END IF
  316:          GO TO 10
  317:       END IF
  318: *
  319: *     Compute the estimate of the reciprocal condition number.
  320: *
  321:       IF( AINVNM .NE. 0.0D+0 )
  322:      $   ZLA_HERCOND_C = 1.0D+0 / AINVNM
  323: *
  324:       RETURN
  325: *
  326: *     End of ZLA_HERCOND_C
  327: *
  328:       END

CVSweb interface <joel.bertrand@systella.fr>