File:  [local] / rpl / lapack / lapack / dla_gbrcond.f
Revision 1.17: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:38:52 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 DLA_GBRCOND estimates the Skeel condition number for a general banded matrix.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download DLA_GBRCOND + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dla_gbrcond.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dla_gbrcond.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dla_gbrcond.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       DOUBLE PRECISION FUNCTION DLA_GBRCOND( TRANS, N, KL, KU, AB, LDAB,
   22: *                                              AFB, LDAFB, IPIV, CMODE, C,
   23: *                                              INFO, WORK, IWORK )
   24: *
   25: *       .. Scalar Arguments ..
   26: *       CHARACTER          TRANS
   27: *       INTEGER            N, LDAB, LDAFB, INFO, KL, KU, CMODE
   28: *       ..
   29: *       .. Array Arguments ..
   30: *       INTEGER            IWORK( * ), IPIV( * )
   31: *       DOUBLE PRECISION   AB( LDAB, * ), AFB( LDAFB, * ), WORK( * ),
   32: *      $                   C( * )
   33: *       ..
   34: *
   35: *
   36: *> \par Purpose:
   37: *  =============
   38: *>
   39: *> \verbatim
   40: *>
   41: *>    DLA_GBRCOND Estimates the Skeel condition number of  op(A) * op2(C)
   42: *>    where op2 is determined by CMODE as follows
   43: *>    CMODE =  1    op2(C) = C
   44: *>    CMODE =  0    op2(C) = I
   45: *>    CMODE = -1    op2(C) = inv(C)
   46: *>    The Skeel condition number  cond(A) = norminf( |inv(A)||A| )
   47: *>    is computed by computing scaling factors R such that
   48: *>    diag(R)*A*op2(C) is row equilibrated and computing the standard
   49: *>    infinity-norm condition number.
   50: *> \endverbatim
   51: *
   52: *  Arguments:
   53: *  ==========
   54: *
   55: *> \param[in] TRANS
   56: *> \verbatim
   57: *>          TRANS is CHARACTER*1
   58: *>     Specifies the form of the system of equations:
   59: *>       = 'N':  A * X = B     (No transpose)
   60: *>       = 'T':  A**T * X = B  (Transpose)
   61: *>       = 'C':  A**H * X = B  (Conjugate Transpose = Transpose)
   62: *> \endverbatim
   63: *>
   64: *> \param[in] N
   65: *> \verbatim
   66: *>          N is INTEGER
   67: *>     The number of linear equations, i.e., the order of the
   68: *>     matrix A.  N >= 0.
   69: *> \endverbatim
   70: *>
   71: *> \param[in] KL
   72: *> \verbatim
   73: *>          KL is INTEGER
   74: *>     The number of subdiagonals within the band of A.  KL >= 0.
   75: *> \endverbatim
   76: *>
   77: *> \param[in] KU
   78: *> \verbatim
   79: *>          KU is INTEGER
   80: *>     The number of superdiagonals within the band of A.  KU >= 0.
   81: *> \endverbatim
   82: *>
   83: *> \param[in] AB
   84: *> \verbatim
   85: *>          AB is DOUBLE PRECISION array, dimension (LDAB,N)
   86: *>     On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
   87: *>     The j-th column of A is stored in the j-th column of the
   88: *>     array AB as follows:
   89: *>     AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
   90: *> \endverbatim
   91: *>
   92: *> \param[in] LDAB
   93: *> \verbatim
   94: *>          LDAB is INTEGER
   95: *>     The leading dimension of the array AB.  LDAB >= KL+KU+1.
   96: *> \endverbatim
   97: *>
   98: *> \param[in] AFB
   99: *> \verbatim
  100: *>          AFB is DOUBLE PRECISION array, dimension (LDAFB,N)
  101: *>     Details of the LU factorization of the band matrix A, as
  102: *>     computed by DGBTRF.  U is stored as an upper triangular
  103: *>     band matrix with KL+KU superdiagonals in rows 1 to KL+KU+1,
  104: *>     and the multipliers used during the factorization are stored
  105: *>     in rows KL+KU+2 to 2*KL+KU+1.
  106: *> \endverbatim
  107: *>
  108: *> \param[in] LDAFB
  109: *> \verbatim
  110: *>          LDAFB is INTEGER
  111: *>     The leading dimension of the array AFB.  LDAFB >= 2*KL+KU+1.
  112: *> \endverbatim
  113: *>
  114: *> \param[in] IPIV
  115: *> \verbatim
  116: *>          IPIV is INTEGER array, dimension (N)
  117: *>     The pivot indices from the factorization A = P*L*U
  118: *>     as computed by DGBTRF; row i of the matrix was interchanged
  119: *>     with row IPIV(i).
  120: *> \endverbatim
  121: *>
  122: *> \param[in] CMODE
  123: *> \verbatim
  124: *>          CMODE is INTEGER
  125: *>     Determines op2(C) in the formula op(A) * op2(C) as follows:
  126: *>     CMODE =  1    op2(C) = C
  127: *>     CMODE =  0    op2(C) = I
  128: *>     CMODE = -1    op2(C) = inv(C)
  129: *> \endverbatim
  130: *>
  131: *> \param[in] C
  132: *> \verbatim
  133: *>          C is DOUBLE PRECISION array, dimension (N)
  134: *>     The vector C in the formula op(A) * op2(C).
  135: *> \endverbatim
  136: *>
  137: *> \param[out] INFO
  138: *> \verbatim
  139: *>          INFO is INTEGER
  140: *>       = 0:  Successful exit.
  141: *>     i > 0:  The ith argument is invalid.
  142: *> \endverbatim
  143: *>
  144: *> \param[out] WORK
  145: *> \verbatim
  146: *>          WORK is DOUBLE PRECISION array, dimension (5*N).
  147: *>     Workspace.
  148: *> \endverbatim
  149: *>
  150: *> \param[out] IWORK
  151: *> \verbatim
  152: *>          IWORK is INTEGER array, dimension (N).
  153: *>     Workspace.
  154: *> \endverbatim
  155: *
  156: *  Authors:
  157: *  ========
  158: *
  159: *> \author Univ. of Tennessee
  160: *> \author Univ. of California Berkeley
  161: *> \author Univ. of Colorado Denver
  162: *> \author NAG Ltd.
  163: *
  164: *> \ingroup doubleGBcomputational
  165: *
  166: *  =====================================================================
  167:       DOUBLE PRECISION FUNCTION DLA_GBRCOND( TRANS, N, KL, KU, AB, LDAB,
  168:      $                                       AFB, LDAFB, IPIV, CMODE, C,
  169:      $                                       INFO, WORK, IWORK )
  170: *
  171: *  -- LAPACK computational routine --
  172: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  173: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  174: *
  175: *     .. Scalar Arguments ..
  176:       CHARACTER          TRANS
  177:       INTEGER            N, LDAB, LDAFB, INFO, KL, KU, CMODE
  178: *     ..
  179: *     .. Array Arguments ..
  180:       INTEGER            IWORK( * ), IPIV( * )
  181:       DOUBLE PRECISION   AB( LDAB, * ), AFB( LDAFB, * ), WORK( * ),
  182:      $                   C( * )
  183: *     ..
  184: *
  185: *  =====================================================================
  186: *
  187: *     .. Local Scalars ..
  188:       LOGICAL            NOTRANS
  189:       INTEGER            KASE, I, J, KD, KE
  190:       DOUBLE PRECISION   AINVNM, TMP
  191: *     ..
  192: *     .. Local Arrays ..
  193:       INTEGER            ISAVE( 3 )
  194: *     ..
  195: *     .. External Functions ..
  196:       LOGICAL            LSAME
  197:       EXTERNAL           LSAME
  198: *     ..
  199: *     .. External Subroutines ..
  200:       EXTERNAL           DLACN2, DGBTRS, XERBLA
  201: *     ..
  202: *     .. Intrinsic Functions ..
  203:       INTRINSIC          ABS, MAX
  204: *     ..
  205: *     .. Executable Statements ..
  206: *
  207:       DLA_GBRCOND = 0.0D+0
  208: *
  209:       INFO = 0
  210:       NOTRANS = LSAME( TRANS, 'N' )
  211:       IF ( .NOT. NOTRANS .AND. .NOT. LSAME(TRANS, 'T')
  212:      $     .AND. .NOT. LSAME(TRANS, 'C') ) THEN
  213:          INFO = -1
  214:       ELSE IF( N.LT.0 ) THEN
  215:          INFO = -2
  216:       ELSE IF( KL.LT.0 .OR. KL.GT.N-1 ) THEN
  217:          INFO = -3
  218:       ELSE IF( KU.LT.0 .OR. KU.GT.N-1 ) THEN
  219:          INFO = -4
  220:       ELSE IF( LDAB.LT.KL+KU+1 ) THEN
  221:          INFO = -6
  222:       ELSE IF( LDAFB.LT.2*KL+KU+1 ) THEN
  223:          INFO = -8
  224:       END IF
  225:       IF( INFO.NE.0 ) THEN
  226:          CALL XERBLA( 'DLA_GBRCOND', -INFO )
  227:          RETURN
  228:       END IF
  229:       IF( N.EQ.0 ) THEN
  230:          DLA_GBRCOND = 1.0D+0
  231:          RETURN
  232:       END IF
  233: *
  234: *     Compute the equilibration matrix R such that
  235: *     inv(R)*A*C has unit 1-norm.
  236: *
  237:       KD = KU + 1
  238:       KE = KL + 1
  239:       IF ( NOTRANS ) THEN
  240:          DO I = 1, N
  241:             TMP = 0.0D+0
  242:                IF ( CMODE .EQ. 1 ) THEN
  243:                   DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
  244:                      TMP = TMP + ABS( AB( KD+I-J, J ) * C( J ) )
  245:                   END DO
  246:                ELSE IF ( CMODE .EQ. 0 ) THEN
  247:                   DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
  248:                      TMP = TMP + ABS( AB( KD+I-J, J ) )
  249:                   END DO
  250:                ELSE
  251:                   DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
  252:                      TMP = TMP + ABS( AB( KD+I-J, J ) / C( J ) )
  253:                   END DO
  254:                END IF
  255:             WORK( 2*N+I ) = TMP
  256:          END DO
  257:       ELSE
  258:          DO I = 1, N
  259:             TMP = 0.0D+0
  260:             IF ( CMODE .EQ. 1 ) THEN
  261:                DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
  262:                   TMP = TMP + ABS( AB( KE-I+J, I ) * C( J ) )
  263:                END DO
  264:             ELSE IF ( CMODE .EQ. 0 ) THEN
  265:                DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
  266:                   TMP = TMP + ABS( AB( KE-I+J, I ) )
  267:                END DO
  268:             ELSE
  269:                DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
  270:                   TMP = TMP + ABS( AB( KE-I+J, I ) / C( J ) )
  271:                END DO
  272:             END IF
  273:             WORK( 2*N+I ) = TMP
  274:          END DO
  275:       END IF
  276: *
  277: *     Estimate the norm of inv(op(A)).
  278: *
  279:       AINVNM = 0.0D+0
  280: 
  281:       KASE = 0
  282:    10 CONTINUE
  283:       CALL DLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
  284:       IF( KASE.NE.0 ) THEN
  285:          IF( KASE.EQ.2 ) THEN
  286: *
  287: *           Multiply by R.
  288: *
  289:             DO I = 1, N
  290:                WORK( I ) = WORK( I ) * WORK( 2*N+I )
  291:             END DO
  292: 
  293:             IF ( NOTRANS ) THEN
  294:                CALL DGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
  295:      $              IPIV, WORK, N, INFO )
  296:             ELSE
  297:                CALL DGBTRS( 'Transpose', N, KL, KU, 1, AFB, LDAFB, IPIV,
  298:      $              WORK, N, INFO )
  299:             END IF
  300: *
  301: *           Multiply by inv(C).
  302: *
  303:             IF ( CMODE .EQ. 1 ) THEN
  304:                DO I = 1, N
  305:                   WORK( I ) = WORK( I ) / C( I )
  306:                END DO
  307:             ELSE IF ( CMODE .EQ. -1 ) THEN
  308:                DO I = 1, N
  309:                   WORK( I ) = WORK( I ) * C( I )
  310:                END DO
  311:             END IF
  312:          ELSE
  313: *
  314: *           Multiply by inv(C**T).
  315: *
  316:             IF ( CMODE .EQ. 1 ) THEN
  317:                DO I = 1, N
  318:                   WORK( I ) = WORK( I ) / C( I )
  319:                END DO
  320:             ELSE IF ( CMODE .EQ. -1 ) THEN
  321:                DO I = 1, N
  322:                   WORK( I ) = WORK( I ) * C( I )
  323:                END DO
  324:             END IF
  325: 
  326:             IF ( NOTRANS ) THEN
  327:                CALL DGBTRS( 'Transpose', N, KL, KU, 1, AFB, LDAFB, IPIV,
  328:      $              WORK, N, INFO )
  329:             ELSE
  330:                CALL DGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
  331:      $              IPIV, WORK, N, INFO )
  332:             END IF
  333: *
  334: *           Multiply by R.
  335: *
  336:             DO I = 1, N
  337:                WORK( I ) = WORK( I ) * WORK( 2*N+I )
  338:             END DO
  339:          END IF
  340:          GO TO 10
  341:       END IF
  342: *
  343: *     Compute the estimate of the reciprocal condition number.
  344: *
  345:       IF( AINVNM .NE. 0.0D+0 )
  346:      $   DLA_GBRCOND = ( 1.0D+0 / AINVNM )
  347: *
  348:       RETURN
  349: *
  350: *     End of DLA_GBRCOND
  351: *
  352:       END

CVSweb interface <joel.bertrand@systella.fr>