Diff for /rpl/lapack/lapack/dgsvj0.f between versions 1.14 and 1.21

version 1.14, 2015/11/26 11:44:17 version 1.21, 2023/08/07 08:38:51
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 DGSVJ0 + dependencies   *> Download DGSVJ0 + dependencies
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgsvj0.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgsvj0.f">
 *> [TGZ]</a>   *> [TGZ]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgsvj0.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgsvj0.f">
 *> [ZIP]</a>   *> [ZIP]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgsvj0.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgsvj0.f">
 *> [TXT]</a>  *> [TXT]</a>
 *> \endhtmlonly   *> \endhtmlonly
 *  *
 *  Definition:  *  Definition:
 *  ===========  *  ===========
 *  *
 *       SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,  *       SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,
 *                          SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )  *                          SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )
 *   *
 *       .. Scalar Arguments ..  *       .. Scalar Arguments ..
 *       INTEGER            INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP  *       INTEGER            INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP
 *       DOUBLE PRECISION   EPS, SFMIN, TOL  *       DOUBLE PRECISION   EPS, SFMIN, TOL
Line 30 Line 30
 *       DOUBLE PRECISION   A( LDA, * ), SVA( N ), D( N ), V( LDV, * ),  *       DOUBLE PRECISION   A( LDA, * ), SVA( N ), D( N ), V( LDV, * ),
 *      $                   WORK( LWORK )  *      $                   WORK( LWORK )
 *       ..  *       ..
 *    *
 *  *
 *> \par Purpose:  *> \par Purpose:
 *  =============  *  =============
Line 117 Line 117
 *> \param[in] MV  *> \param[in] MV
 *> \verbatim  *> \verbatim
 *>          MV is INTEGER  *>          MV is INTEGER
 *>          If JOBV .EQ. 'A', then MV rows of V are post-multipled by a  *>          If JOBV = 'A', then MV rows of V are post-multipled by a
 *>                           sequence of Jacobi rotations.  *>                           sequence of Jacobi rotations.
 *>          If JOBV = 'N',   then MV is not referenced.  *>          If JOBV = 'N',   then MV is not referenced.
 *> \endverbatim  *> \endverbatim
Line 125 Line 125
 *> \param[in,out] V  *> \param[in,out] V
 *> \verbatim  *> \verbatim
 *>          V is DOUBLE PRECISION array, dimension (LDV,N)  *>          V is DOUBLE PRECISION array, dimension (LDV,N)
 *>          If JOBV .EQ. 'V' then N rows of V are post-multipled by a  *>          If JOBV = 'V' then N rows of V are post-multipled by a
 *>                           sequence of Jacobi rotations.  *>                           sequence of Jacobi rotations.
 *>          If JOBV .EQ. 'A' then MV rows of V are post-multipled by a  *>          If JOBV = 'A' then MV rows of V are post-multipled by a
 *>                           sequence of Jacobi rotations.  *>                           sequence of Jacobi rotations.
 *>          If JOBV = 'N',   then V is not referenced.  *>          If JOBV = 'N',   then V is not referenced.
 *> \endverbatim  *> \endverbatim
Line 136 Line 136
 *> \verbatim  *> \verbatim
 *>          LDV is INTEGER  *>          LDV is INTEGER
 *>          The leading dimension of the array V,  LDV >= 1.  *>          The leading dimension of the array V,  LDV >= 1.
 *>          If JOBV = 'V', LDV .GE. N.  *>          If JOBV = 'V', LDV >= N.
 *>          If JOBV = 'A', LDV .GE. MV.  *>          If JOBV = 'A', LDV >= MV.
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[in] EPS  *> \param[in] EPS
Line 157 Line 157
 *>          TOL is DOUBLE PRECISION  *>          TOL is DOUBLE PRECISION
 *>          TOL is the threshold for Jacobi rotations. For a pair  *>          TOL is the threshold for Jacobi rotations. For a pair
 *>          A(:,p), A(:,q) of pivot columns, the Jacobi rotation is  *>          A(:,p), A(:,q) of pivot columns, the Jacobi rotation is
 *>          applied only if DABS(COS(angle(A(:,p),A(:,q)))) .GT. TOL.  *>          applied only if DABS(COS(angle(A(:,p),A(:,q)))) > TOL.
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[in] NSWEEP  *> \param[in] NSWEEP
Line 175 Line 175
 *> \param[in] LWORK  *> \param[in] LWORK
 *> \verbatim  *> \verbatim
 *>          LWORK is INTEGER  *>          LWORK is INTEGER
 *>          LWORK is the dimension of WORK. LWORK .GE. M.  *>          LWORK is the dimension of WORK. LWORK >= M.
 *> \endverbatim  *> \endverbatim
 *>  *>
 *> \param[out] INFO  *> \param[out] INFO
 *> \verbatim  *> \verbatim
 *>          INFO is INTEGER  *>          INFO is INTEGER
 *>          = 0 : successful exit.  *>          = 0:  successful exit.
 *>          < 0 : if INFO = -i, then the i-th argument had an illegal value  *>          < 0:  if INFO = -i, then the i-th argument had an illegal value
 *> \endverbatim  *> \endverbatim
 *  *
 *  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 2015  
 *  *
 *> \ingroup doubleOTHERcomputational  *> \ingroup doubleOTHERcomputational
 *  *
Line 218 Line 216
       SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,        SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,
      $                   SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )       $                   SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )
 *  *
 *  -- LAPACK computational routine (version 3.6.0) --  *  -- LAPACK computational 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 2015  
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP        INTEGER            INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP
Line 262 Line 259
       EXTERNAL           IDAMAX, LSAME, DDOT, DNRM2        EXTERNAL           IDAMAX, LSAME, DDOT, DNRM2
 *     ..  *     ..
 *     .. External Subroutines ..  *     .. External Subroutines ..
       EXTERNAL           DAXPY, DCOPY, DLASCL, DLASSQ, DROTM, DSWAP        EXTERNAL           DAXPY, DCOPY, DLASCL, DLASSQ, DROTM, DSWAP,
        $                   XERBLA
 *     ..  *     ..
 *     .. Executable Statements ..  *     .. Executable Statements ..
 *  *
Line 280 Line 278
          INFO = -5           INFO = -5
       ELSE IF( ( RSVEC.OR.APPLV ) .AND. ( MV.LT.0 ) ) THEN        ELSE IF( ( RSVEC.OR.APPLV ) .AND. ( MV.LT.0 ) ) THEN
          INFO = -8           INFO = -8
       ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR.         ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR.
      $         ( APPLV.AND.( LDV.LT.MV ) ) ) THEN       $         ( APPLV.AND.( LDV.LT.MV ) ) ) THEN
          INFO = -10           INFO = -10
       ELSE IF( TOL.LE.EPS ) THEN        ELSE IF( TOL.LE.EPS ) THEN
Line 391 Line 389
 *        Some BLAS implementations compute DNRM2(M,A(1,p),1)  *        Some BLAS implementations compute DNRM2(M,A(1,p),1)
 *        as DSQRT(DDOT(M,A(1,p),1,A(1,p),1)), which may result in  *        as DSQRT(DDOT(M,A(1,p),1,A(1,p),1)), which may result in
 *        overflow for ||A(:,p)||_2 > DSQRT(overflow_threshold), and  *        overflow for ||A(:,p)||_2 > DSQRT(overflow_threshold), and
 *        undeflow for ||A(:,p)||_2 < DSQRT(underflow_threshold).  *        underflow for ||A(:,p)||_2 < DSQRT(underflow_threshold).
 *        Hence, DNRM2 cannot be trusted, not even in the case when  *        Hence, DNRM2 cannot be trusted, not even in the case when
 *        the true norm is far from the under(over)flow boundaries.  *        the true norm is far from the under(over)flow boundaries.
 *        If properly implemented DNRM2 is available, the IF-THEN-ELSE  *        If properly implemented DNRM2 is available, the IF-THEN-ELSE
Line 485 Line 483
      $                                              FASTR )       $                                              FASTR )
                                     SVA( q ) = AAQQ*DSQRT( MAX( ZERO,                                      SVA( q ) = AAQQ*DSQRT( MAX( ZERO,
      $                                         ONE+T*APOAQ*AAPQ ) )       $                                         ONE+T*APOAQ*AAPQ ) )
                                     AAPP = AAPP*DSQRT( MAX( ZERO,                                       AAPP = AAPP*DSQRT( MAX( ZERO,
      $                                     ONE-T*AQOAP*AAPQ ) )       $                                     ONE-T*AQOAP*AAPQ ) )
                                     MXSINJ = MAX( MXSINJ, DABS( T ) )                                      MXSINJ = MAX( MXSINJ, DABS( T ) )
 *  *
Line 800 Line 798
                                     MXSINJ = MAX( MXSINJ, DABS( SN ) )                                      MXSINJ = MAX( MXSINJ, DABS( SN ) )
                                     SVA( q ) = AAQQ*DSQRT( MAX( ZERO,                                      SVA( q ) = AAQQ*DSQRT( MAX( ZERO,
      $                                         ONE+T*APOAQ*AAPQ ) )       $                                         ONE+T*APOAQ*AAPQ ) )
                                     AAPP = AAPP*DSQRT( MAX( ZERO,                                       AAPP = AAPP*DSQRT( MAX( ZERO,
      $                                     ONE-T*AQOAP*AAPQ ) )       $                                     ONE-T*AQOAP*AAPQ ) )
 *  *
                                     APOAQ = D( p ) / D( q )                                      APOAQ = D( p ) / D( q )
Line 1044 Line 1042
   
  1993 CONTINUE   1993 CONTINUE
 *     end i=1:NSWEEP loop  *     end i=1:NSWEEP loop
 * #:) Reaching this point means that the procedure has comleted the given  * #:) Reaching this point means that the procedure has completed the given
 *     number of iterations.  *     number of iterations.
       INFO = NSWEEP - 1        INFO = NSWEEP - 1
       GO TO 1995        GO TO 1995

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


CVSweb interface <joel.bertrand@systella.fr>