File:  [local] / rpl / lapack / lapack / zla_syrcond_c.f
Revision 1.16: download - view: text, annotated - select for diffs - revision graph
Tue May 29 07:18:24 2018 UTC (5 years, 11 months ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_31, rpl-4_1_30, rpl-4_1_29, rpl-4_1_28, HEAD
Mise à jour de Lapack.

    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[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 complex16SYcomputational
  137: *
  138: *  =====================================================================
  139:       DOUBLE PRECISION FUNCTION ZLA_SYRCOND_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
  163:       DOUBLE PRECISION   AINVNM, ANORM, TMP
  164:       INTEGER            I, J
  165:       LOGICAL            UP, UPPER
  166:       COMPLEX*16         ZDUM
  167: *     ..
  168: *     .. Local Arrays ..
  169:       INTEGER            ISAVE( 3 )
  170: *     ..
  171: *     .. External Functions ..
  172:       LOGICAL            LSAME
  173:       EXTERNAL           LSAME
  174: *     ..
  175: *     .. External Subroutines ..
  176:       EXTERNAL           ZLACN2, ZSYTRS, XERBLA
  177: *     ..
  178: *     .. Intrinsic Functions ..
  179:       INTRINSIC          ABS, MAX
  180: *     ..
  181: *     .. Statement Functions ..
  182:       DOUBLE PRECISION CABS1
  183: *     ..
  184: *     .. Statement Function Definitions ..
  185:       CABS1( ZDUM ) = ABS( DBLE( ZDUM ) ) + ABS( DIMAG( ZDUM ) )
  186: *     ..
  187: *     .. Executable Statements ..
  188: *
  189:       ZLA_SYRCOND_C = 0.0D+0
  190: *
  191:       INFO = 0
  192:       UPPER = LSAME( UPLO, 'U' )
  193:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
  194:          INFO = -1
  195:       ELSE IF( N.LT.0 ) THEN
  196:          INFO = -2
  197:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  198:          INFO = -4
  199:       ELSE IF( LDAF.LT.MAX( 1, N ) ) THEN
  200:          INFO = -6
  201:       END IF
  202:       IF( INFO.NE.0 ) THEN
  203:          CALL XERBLA( 'ZLA_SYRCOND_C', -INFO )
  204:          RETURN
  205:       END IF
  206:       UP = .FALSE.
  207:       IF ( LSAME( UPLO, 'U' ) ) UP = .TRUE.
  208: *
  209: *     Compute norm of op(A)*op2(C).
  210: *
  211:       ANORM = 0.0D+0
  212:       IF ( UP ) THEN
  213:          DO I = 1, N
  214:             TMP = 0.0D+0
  215:             IF ( CAPPLY ) THEN
  216:                DO J = 1, I
  217:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  218:                END DO
  219:                DO J = I+1, N
  220:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  221:                END DO
  222:             ELSE
  223:                DO J = 1, I
  224:                   TMP = TMP + CABS1( A( J, I ) )
  225:                END DO
  226:                DO J = I+1, N
  227:                   TMP = TMP + CABS1( A( I, J ) )
  228:                END DO
  229:             END IF
  230:             RWORK( I ) = TMP
  231:             ANORM = MAX( ANORM, TMP )
  232:          END DO
  233:       ELSE
  234:          DO I = 1, N
  235:             TMP = 0.0D+0
  236:             IF ( CAPPLY ) THEN
  237:                DO J = 1, I
  238:                   TMP = TMP + CABS1( A( I, J ) ) / C( J )
  239:                END DO
  240:                DO J = I+1, N
  241:                   TMP = TMP + CABS1( A( J, I ) ) / C( J )
  242:                END DO
  243:             ELSE
  244:                DO J = 1, I
  245:                   TMP = TMP + CABS1( A( I, J ) )
  246:                END DO
  247:                DO J = I+1, N
  248:                   TMP = TMP + CABS1( A( J, I ) )
  249:                END DO
  250:             END IF
  251:             RWORK( I ) = TMP
  252:             ANORM = MAX( ANORM, TMP )
  253:          END DO
  254:       END IF
  255: *
  256: *     Quick return if possible.
  257: *
  258:       IF( N.EQ.0 ) THEN
  259:          ZLA_SYRCOND_C = 1.0D+0
  260:          RETURN
  261:       ELSE IF( ANORM .EQ. 0.0D+0 ) THEN
  262:          RETURN
  263:       END IF
  264: *
  265: *     Estimate the norm of inv(op(A)).
  266: *
  267:       AINVNM = 0.0D+0
  268: *
  269:       KASE = 0
  270:    10 CONTINUE
  271:       CALL ZLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
  272:       IF( KASE.NE.0 ) THEN
  273:          IF( KASE.EQ.2 ) THEN
  274: *
  275: *           Multiply by R.
  276: *
  277:             DO I = 1, N
  278:                WORK( I ) = WORK( I ) * RWORK( I )
  279:             END DO
  280: *
  281:             IF ( UP ) THEN
  282:                CALL ZSYTRS( 'U', N, 1, AF, LDAF, IPIV,
  283:      $            WORK, N, INFO )
  284:             ELSE
  285:                CALL ZSYTRS( 'L', N, 1, AF, LDAF, IPIV,
  286:      $            WORK, N, INFO )
  287:             ENDIF
  288: *
  289: *           Multiply by inv(C).
  290: *
  291:             IF ( CAPPLY ) THEN
  292:                DO I = 1, N
  293:                   WORK( I ) = WORK( I ) * C( I )
  294:                END DO
  295:             END IF
  296:          ELSE
  297: *
  298: *           Multiply by inv(C**T).
  299: *
  300:             IF ( CAPPLY ) THEN
  301:                DO I = 1, N
  302:                   WORK( I ) = WORK( I ) * C( I )
  303:                END DO
  304:             END IF
  305: *
  306:             IF ( UP ) THEN
  307:                CALL ZSYTRS( 'U', N, 1, AF, LDAF, IPIV,
  308:      $            WORK, N, INFO )
  309:             ELSE
  310:                CALL ZSYTRS( 'L', N, 1, AF, LDAF, IPIV,
  311:      $            WORK, N, INFO )
  312:             END IF
  313: *
  314: *           Multiply by R.
  315: *
  316:             DO I = 1, N
  317:                WORK( I ) = WORK( I ) * RWORK( I )
  318:             END DO
  319:          END IF
  320:          GO TO 10
  321:       END IF
  322: *
  323: *     Compute the estimate of the reciprocal condition number.
  324: *
  325:       IF( AINVNM .NE. 0.0D+0 )
  326:      $   ZLA_SYRCOND_C = 1.0D+0 / AINVNM
  327: *
  328:       RETURN
  329: *
  330:       END

CVSweb interface <joel.bertrand@systella.fr>