Diff for /rpl/lapack/lapack/dgetc2.f between versions 1.14 and 1.22

version 1.14, 2014/01/27 09:28:17 version 1.22, 2023/08/07 08:38:50
Line 2 Line 2
 *  *
 *  =========== DOCUMENTATION ===========  *  =========== DOCUMENTATION ===========
 *  *
 * Online html documentation available at   * Online html documentation available at
 *            http://www.netlib.org/lapack/explore-html/   *            http://www.netlib.org/lapack/explore-html/
 *  *
 *> \htmlonly  *> \htmlonly
 *> Download DGETC2 + dependencies   *> Download DGETC2 + dependencies
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgetc2.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgetc2.f">
 *> [TGZ]</a>   *> [TGZ]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgetc2.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgetc2.f">
 *> [ZIP]</a>   *> [ZIP]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgetc2.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgetc2.f">
 *> [TXT]</a>  *> [TXT]</a>
 *> \endhtmlonly   *> \endhtmlonly
 *  *
 *  Definition:  *  Definition:
 *  ===========  *  ===========
 *  *
 *       SUBROUTINE DGETC2( N, A, LDA, IPIV, JPIV, INFO )  *       SUBROUTINE DGETC2( N, A, LDA, IPIV, JPIV, INFO )
 *   *
 *       .. Scalar Arguments ..  *       .. Scalar Arguments ..
 *       INTEGER            INFO, LDA, N  *       INTEGER            INFO, LDA, N
 *       ..  *       ..
Line 27 Line 27
 *       INTEGER            IPIV( * ), JPIV( * )  *       INTEGER            IPIV( * ), JPIV( * )
 *       DOUBLE PRECISION   A( LDA, * )  *       DOUBLE PRECISION   A( LDA, * )
 *       ..  *       ..
 *    *
 *  *
 *> \par Purpose:  *> \par Purpose:
 *  =============  *  =============
Line 85 Line 85
 *> \verbatim  *> \verbatim
 *>          INFO is INTEGER  *>          INFO is INTEGER
 *>           = 0: successful exit  *>           = 0: successful exit
 *>           > 0: if INFO = k, U(k, k) is likely to produce owerflow if  *>           > 0: if INFO = k, U(k, k) is likely to produce overflow if
 *>                we try to solve for x in Ax = b. So U is perturbed to  *>                we try to solve for x in Ax = b. So U is perturbed to
 *>                avoid the overflow.  *>                avoid the overflow.
 *> \endverbatim  *> \endverbatim
Line 93 Line 93
 *  Authors:  *  Authors:
 *  ========  *  ========
 *  *
 *> \author Univ. of Tennessee   *> \author Univ. of Tennessee
 *> \author Univ. of California Berkeley   *> \author Univ. of California Berkeley
 *> \author Univ. of Colorado Denver   *> \author Univ. of Colorado Denver
 *> \author NAG Ltd.   *> \author NAG Ltd.
 *  
 *> \date November 2013  
 *  *
 *> \ingroup doubleGEauxiliary  *> \ingroup doubleGEauxiliary
 *  *
Line 111 Line 109
 *  =====================================================================  *  =====================================================================
       SUBROUTINE DGETC2( N, A, LDA, IPIV, JPIV, INFO )        SUBROUTINE DGETC2( N, A, LDA, IPIV, JPIV, INFO )
 *  *
 *  -- LAPACK auxiliary routine (version 3.5.0) --  *  -- LAPACK auxiliary routine --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     November 2013  
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            INFO, LDA, N        INTEGER            INFO, LDA, N
Line 135 Line 132
       DOUBLE PRECISION   BIGNUM, EPS, SMIN, SMLNUM, XMAX        DOUBLE PRECISION   BIGNUM, EPS, SMIN, SMLNUM, XMAX
 *     ..  *     ..
 *     .. External Subroutines ..  *     .. External Subroutines ..
       EXTERNAL           DGER, DSWAP        EXTERNAL           DGER, DSWAP, DLABAD
 *     ..  *     ..
 *     .. External Functions ..  *     .. External Functions ..
       DOUBLE PRECISION   DLAMCH        DOUBLE PRECISION   DLAMCH
Line 146 Line 143
 *     ..  *     ..
 *     .. Executable Statements ..  *     .. Executable Statements ..
 *  *
         INFO = 0
   *
   *     Quick return if possible
   *
         IF( N.EQ.0 )
        $   RETURN
   *
 *     Set constants to control overflow  *     Set constants to control overflow
 *  *
       INFO = 0  
       EPS = DLAMCH( 'P' )        EPS = DLAMCH( 'P' )
       SMLNUM = DLAMCH( 'S' ) / EPS        SMLNUM = DLAMCH( 'S' ) / EPS
       BIGNUM = ONE / SMLNUM        BIGNUM = ONE / SMLNUM
       CALL DLABAD( SMLNUM, BIGNUM )        CALL DLABAD( SMLNUM, BIGNUM )
 *  *
   *     Handle the case N=1 by itself
   *
         IF( N.EQ.1 ) THEN
            IPIV( 1 ) = 1
            JPIV( 1 ) = 1
            IF( ABS( A( 1, 1 ) ).LT.SMLNUM ) THEN
               INFO = 1
               A( 1, 1 ) = SMLNUM
            END IF
            RETURN
         END IF
   *
 *     Factorize A using complete pivoting.  *     Factorize A using complete pivoting.
 *     Set pivots less than SMIN to SMIN.  *     Set pivots less than SMIN to SMIN.
 *  *

Removed from v.1.14  
changed lines
  Added in v.1.22


CVSweb interface <joel.bertrand@systella.fr>