File:  [local] / rpl / lapack / lapack / zla_hercond_c.f
Revision 1.15: download - view: text, annotated - select for diffs - revision graph
Sat Jun 17 11:06:51 2017 UTC (6 years, 10 months ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_27, rpl-4_1_26, HEAD
Cohérence.

    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[in] WORK
  115: *> \verbatim
  116: *>          WORK is COMPLEX*16 array, dimension (2*N).
  117: *>     Workspace.
  118: *> \endverbatim
  119: *>
  120: *> \param[in] 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: *> \date December 2016
  135: *
  136: *> \ingroup complex16HEcomputational
  137: *
  138: *  =====================================================================
  139:       DOUBLE PRECISION FUNCTION ZLA_HERCOND_C( UPLO, N, A, LDA, AF,
  140:      $                                         LDAF, IPIV, C, CAPPLY,
  141:      $                                         INFO, WORK, RWORK )
  142: *
  143: *  -- LAPACK computational routine (version 3.7.0) --
  144: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  145: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  146: *     December 2016
  147: *
  148: *     .. Scalar Arguments ..
  149:       CHARACTER          UPLO
  150:       LOGICAL            CAPPLY
  151:       INTEGER            N, LDA, LDAF, INFO
  152: *     ..
  153: *     .. Array Arguments ..
  154:       INTEGER            IPIV( * )
  155:       COMPLEX*16         A( LDA, * ), AF( LDAF, * ), WORK( * )
  156:       DOUBLE PRECISION   C ( * ), RWORK( * )
  157: *     ..
  158: *
  159: *  =====================================================================
  160: *
  161: *     .. Local Scalars ..
  162:       INTEGER            KASE, I, J
  163:       DOUBLE PRECISION   AINVNM, ANORM, TMP
  164:       LOGICAL            UP, UPPER
  165:       COMPLEX*16         ZDUM
  166: *     ..
  167: *     .. Local Arrays ..
  168:       INTEGER            ISAVE( 3 )
  169: *     ..
  170: *     .. External Functions ..
  171:       LOGICAL            LSAME
  172:       EXTERNAL           LSAME
  173: *     ..
  174: *     .. External Subroutines ..
  175:       EXTERNAL           ZLACN2, ZHETRS, XERBLA
  176: *     ..
  177: *     .. Intrinsic Functions ..
  178:       INTRINSIC          ABS, MAX
  179: *     ..
  180: *     .. Statement Functions ..
  181:       DOUBLE PRECISION   CABS1
  182: *     ..
  183: *     .. Statement Function Definitions ..
  184:       CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
  185: *     ..
  186: *     .. Executable Statements ..
  187: *
  188:       ZLA_HERCOND_C = 0.0D+0
  189: *
  190:       INFO = 0
  191:       UPPER = LSAME( UPLO, 'U' )
  192:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  193:          INFO = -1
  194:       ELSE IF( N.LT.0 ) THEN
  195:          INFO = -2
  196:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  197:          INFO = -4
  198:       ELSE IF( LDAF.LT.MAX( 1, N ) ) THEN
  199:          INFO = -6
  200:       END IF
  201:       IF( INFO.NE.0 ) THEN
  202:          CALL XERBLA( 'ZLA_HERCOND_C', -INFO )
  203:          RETURN
  204:       END IF
  205:       UP = .FALSE.
  206:       IF ( LSAME( UPLO, 'U' ) ) UP = .TRUE.
  207: *
  208: *     Compute norm of op(A)*op2(C).
  209: *
  210:       ANORM = 0.0D+0
  211:       IF ( UP ) THEN
  212:          DO I = 1, N
  213:             TMP = 0.0D+0
  214:             IF ( CAPPLY ) THEN
  215:                DO J = 1, I
  216:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  217:                END DO
  218:                DO J = I+1, N
  219:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  220:                END DO
  221:             ELSE
  222:                DO J = 1, I
  223:                   TMP = TMP + CABS1( A( J, I ) )
  224:                END DO
  225:                DO J = I+1, N
  226:                   TMP = TMP + CABS1( A( I, J ) )
  227:                END DO
  228:             END IF
  229:             RWORK( I ) = TMP
  230:             ANORM = MAX( ANORM, TMP )
  231:          END DO
  232:       ELSE
  233:          DO I = 1, N
  234:             TMP = 0.0D+0
  235:             IF ( CAPPLY ) THEN
  236:                DO J = 1, I
  237:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  238:                END DO
  239:                DO J = I+1, N
  240:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  241:                END DO
  242:             ELSE
  243:                DO J = 1, I
  244:                   TMP = TMP + CABS1( A( I, J ) )
  245:                END DO
  246:                DO J = I+1, N
  247:                   TMP = TMP + CABS1( A( J, I ) )
  248:                END DO
  249:             END IF
  250:             RWORK( I ) = TMP
  251:             ANORM = MAX( ANORM, TMP )
  252:          END DO
  253:       END IF
  254: *
  255: *     Quick return if possible.
  256: *
  257:       IF( N.EQ.0 ) THEN
  258:          ZLA_HERCOND_C = 1.0D+0
  259:          RETURN
  260:       ELSE IF( ANORM .EQ. 0.0D+0 ) THEN
  261:          RETURN
  262:       END IF
  263: *
  264: *     Estimate the norm of inv(op(A)).
  265: *
  266:       AINVNM = 0.0D+0
  267: *
  268:       KASE = 0
  269:    10 CONTINUE
  270:       CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
  271:       IF( KASE.NE.0 ) THEN
  272:          IF( KASE.EQ.2 ) THEN
  273: *
  274: *           Multiply by R.
  275: *
  276:             DO I = 1, N
  277:                WORK( I ) = WORK( I ) * RWORK( I )
  278:             END DO
  279: *
  280:             IF ( UP ) THEN
  281:                CALL ZHETRS( 'U', N, 1, AF, LDAF, IPIV,
  282:      $            WORK, N, INFO )
  283:             ELSE
  284:                CALL ZHETRS( 'L', N, 1, AF, LDAF, IPIV,
  285:      $            WORK, N, INFO )
  286:             ENDIF
  287: *
  288: *           Multiply by inv(C).
  289: *
  290:             IF ( CAPPLY ) THEN
  291:                DO I = 1, N
  292:                   WORK( I ) = WORK( I ) * C( I )
  293:                END DO
  294:             END IF
  295:          ELSE
  296: *
  297: *           Multiply by inv(C**H).
  298: *
  299:             IF ( CAPPLY ) THEN
  300:                DO I = 1, N
  301:                   WORK( I ) = WORK( I ) * C( I )
  302:                END DO
  303:             END IF
  304: *
  305:             IF ( UP ) THEN
  306:                CALL ZHETRS( 'U', N, 1, AF, LDAF, IPIV,
  307:      $            WORK, N, INFO )
  308:             ELSE
  309:                CALL ZHETRS( 'L', N, 1, AF, LDAF, IPIV,
  310:      $            WORK, N, INFO )
  311:             END IF
  312: *
  313: *           Multiply by R.
  314: *
  315:             DO I = 1, N
  316:                WORK( I ) = WORK( I ) * RWORK( I )
  317:             END DO
  318:          END IF
  319:          GO TO 10
  320:       END IF
  321: *
  322: *     Compute the estimate of the reciprocal condition number.
  323: *
  324:       IF( AINVNM .NE. 0.0D+0 )
  325:      $   ZLA_HERCOND_C = 1.0D+0 / AINVNM
  326: *
  327:       RETURN
  328: *
  329:       END

CVSweb interface <joel.bertrand@systella.fr>