Diff for /rpl/lapack/lapack/zlartg.f between versions 1.10 and 1.17

version 1.10, 2012/08/22 09:48:37 version 1.17, 2017/06/17 11:06:56
Line 1 Line 1
 *> \brief \b ZLARTG  *> \brief \b ZLARTG generates a plane rotation with real cosine and complex sine.
 *  *
 *  =========== 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 ZLARTG + dependencies   *> Download ZLARTG + dependencies
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlartg.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlartg.f">
 *> [TGZ]</a>   *> [TGZ]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlartg.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlartg.f">
 *> [ZIP]</a>   *> [ZIP]</a>
 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlartg.f">   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlartg.f">
 *> [TXT]</a>  *> [TXT]</a>
 *> \endhtmlonly   *> \endhtmlonly
 *  *
 *  Definition:  *  Definition:
 *  ===========  *  ===========
 *  *
 *       SUBROUTINE ZLARTG( F, G, CS, SN, R )  *       SUBROUTINE ZLARTG( F, G, CS, SN, R )
 *   *
 *       .. Scalar Arguments ..  *       .. Scalar Arguments ..
 *       DOUBLE PRECISION   CS  *       DOUBLE PRECISION   CS
 *       COMPLEX*16         F, G, R, SN  *       COMPLEX*16         F, G, R, SN
 *       ..  *       ..
 *    *
 *  *
 *> \par Purpose:  *> \par Purpose:
 *  =============  *  =============
Line 80 Line 80
 *  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 2011  *> \date December 2016
 *  *
 *> \ingroup complex16OTHERauxiliary  *> \ingroup complex16OTHERauxiliary
 *  *
Line 103 Line 103
 *  =====================================================================  *  =====================================================================
       SUBROUTINE ZLARTG( F, G, CS, SN, R )        SUBROUTINE ZLARTG( F, G, CS, SN, R )
 *  *
 *  -- LAPACK auxiliary routine (version 3.4.0) --  *  -- LAPACK auxiliary routine (version 3.7.0) --
 *  -- 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 2011  *     December 2016
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       DOUBLE PRECISION   CS        DOUBLE PRECISION   CS
Line 130 Line 130
 *     ..  *     ..
 *     .. External Functions ..  *     .. External Functions ..
       DOUBLE PRECISION   DLAMCH, DLAPY2        DOUBLE PRECISION   DLAMCH, DLAPY2
       EXTERNAL           DLAMCH, DLAPY2        LOGICAL            DISNAN
         EXTERNAL           DLAMCH, DLAPY2, DISNAN
 *     ..  *     ..
 *     .. Intrinsic Functions ..  *     .. Intrinsic Functions ..
       INTRINSIC          ABS, DBLE, DCMPLX, DCONJG, DIMAG, INT, LOG,        INTRINSIC          ABS, DBLE, DCMPLX, DCONJG, DIMAG, INT, LOG,
Line 139 Line 140
 *     .. Statement Functions ..  *     .. Statement Functions ..
       DOUBLE PRECISION   ABS1, ABSSQ        DOUBLE PRECISION   ABS1, ABSSQ
 *     ..  *     ..
 *     .. Save statement ..  
 *     SAVE               FIRST, SAFMX2, SAFMIN, SAFMN2  
 *     ..  
 *     .. Data statements ..  
 *     DATA               FIRST / .TRUE. /  
 *     ..  
 *     .. Statement Function definitions ..  *     .. Statement Function definitions ..
       ABS1( FF ) = MAX( ABS( DBLE( FF ) ), ABS( DIMAG( FF ) ) )        ABS1( FF ) = MAX( ABS( DBLE( FF ) ), ABS( DIMAG( FF ) ) )
       ABSSQ( FF ) = DBLE( FF )**2 + DIMAG( FF )**2        ABSSQ( FF ) = DBLE( FF )**2 + DIMAG( FF )**2
 *     ..  *     ..
 *     .. Executable Statements ..  *     .. Executable Statements ..
 *  *
 *     IF( FIRST ) THEN        SAFMIN = DLAMCH( 'S' )
          SAFMIN = DLAMCH( 'S' )        EPS = DLAMCH( 'E' )
          EPS = DLAMCH( 'E' )        SAFMN2 = DLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) /
          SAFMN2 = DLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) /       $         LOG( DLAMCH( 'B' ) ) / TWO )
      $            LOG( DLAMCH( 'B' ) ) / TWO )        SAFMX2 = ONE / SAFMN2
          SAFMX2 = ONE / SAFMN2  
 *        FIRST = .FALSE.  
 *     END IF  
       SCALE = MAX( ABS1( F ), ABS1( G ) )        SCALE = MAX( ABS1( F ), ABS1( G ) )
       FS = F        FS = F
       GS = G        GS = G
Line 172 Line 164
          IF( SCALE.GE.SAFMX2 )           IF( SCALE.GE.SAFMX2 )
      $      GO TO 10       $      GO TO 10
       ELSE IF( SCALE.LE.SAFMN2 ) THEN        ELSE IF( SCALE.LE.SAFMN2 ) THEN
          IF( G.EQ.CZERO ) THEN           IF( G.EQ.CZERO.OR.DISNAN( ABS( G ) ) ) THEN
             CS = ONE              CS = ONE
             SN = CZERO              SN = CZERO
             R = F              R = F

Removed from v.1.10  
changed lines
  Added in v.1.17


CVSweb interface <joel.bertrand@systella.fr>