LAPACK 3.3.1
Linear Algebra PACKage

clartg.f

Go to the documentation of this file.
00001       SUBROUTINE CLARTG( F, G, CS, SN, R )
00002 *
00003 *  -- LAPACK auxiliary routine (version 3.2) --
00004 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00005 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00006 *     November 2006
00007 *
00008 *     .. Scalar Arguments ..
00009       REAL               CS
00010       COMPLEX            F, G, R, SN
00011 *     ..
00012 *
00013 *  Purpose
00014 *  =======
00015 *
00016 *  CLARTG generates a plane rotation so that
00017 *
00018 *     [  CS  SN  ]     [ F ]     [ R ]
00019 *     [  __      ]  .  [   ]  =  [   ]   where CS**2 + |SN|**2 = 1.
00020 *     [ -SN  CS  ]     [ G ]     [ 0 ]
00021 *
00022 *  This is a faster version of the BLAS1 routine CROTG, except for
00023 *  the following differences:
00024 *     F and G are unchanged on return.
00025 *     If G=0, then CS=1 and SN=0.
00026 *     If F=0, then CS=0 and SN is chosen so that R is real.
00027 *
00028 *  Arguments
00029 *  =========
00030 *
00031 *  F       (input) COMPLEX
00032 *          The first component of vector to be rotated.
00033 *
00034 *  G       (input) COMPLEX
00035 *          The second component of vector to be rotated.
00036 *
00037 *  CS      (output) REAL
00038 *          The cosine of the rotation.
00039 *
00040 *  SN      (output) COMPLEX
00041 *          The sine of the rotation.
00042 *
00043 *  R       (output) COMPLEX
00044 *          The nonzero component of the rotated vector.
00045 *
00046 *  Further Details
00047 *  ======= =======
00048 *
00049 *  3-5-96 - Modified with a new algorithm by W. Kahan and J. Demmel
00050 *
00051 *  This version has a few statements commented out for thread safety
00052 *  (machine parameters are computed on each entry). 10 feb 03, SJH.
00053 *
00054 *  =====================================================================
00055 *
00056 *     .. Parameters ..
00057       REAL               TWO, ONE, ZERO
00058       PARAMETER          ( TWO = 2.0E+0, ONE = 1.0E+0, ZERO = 0.0E+0 )
00059       COMPLEX            CZERO
00060       PARAMETER          ( CZERO = ( 0.0E+0, 0.0E+0 ) )
00061 *     ..
00062 *     .. Local Scalars ..
00063 *     LOGICAL            FIRST
00064       INTEGER            COUNT, I
00065       REAL               D, DI, DR, EPS, F2, F2S, G2, G2S, SAFMIN,
00066      $                   SAFMN2, SAFMX2, SCALE
00067       COMPLEX            FF, FS, GS
00068 *     ..
00069 *     .. External Functions ..
00070       REAL               SLAMCH, SLAPY2
00071       EXTERNAL           SLAMCH, SLAPY2
00072 *     ..
00073 *     .. Intrinsic Functions ..
00074       INTRINSIC          ABS, AIMAG, CMPLX, CONJG, INT, LOG, MAX, REAL,
00075      $                   SQRT
00076 *     ..
00077 *     .. Statement Functions ..
00078       REAL               ABS1, ABSSQ
00079 *     ..
00080 *     .. Save statement ..
00081 *     SAVE               FIRST, SAFMX2, SAFMIN, SAFMN2
00082 *     ..
00083 *     .. Data statements ..
00084 *     DATA               FIRST / .TRUE. /
00085 *     ..
00086 *     .. Statement Function definitions ..
00087       ABS1( FF ) = MAX( ABS( REAL( FF ) ), ABS( AIMAG( FF ) ) )
00088       ABSSQ( FF ) = REAL( FF )**2 + AIMAG( FF )**2
00089 *     ..
00090 *     .. Executable Statements ..
00091 *
00092 *     IF( FIRST ) THEN
00093          SAFMIN = SLAMCH( 'S' )
00094          EPS = SLAMCH( 'E' )
00095          SAFMN2 = SLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) /
00096      $            LOG( SLAMCH( 'B' ) ) / TWO )
00097          SAFMX2 = ONE / SAFMN2
00098 *        FIRST = .FALSE.
00099 *     END IF
00100       SCALE = MAX( ABS1( F ), ABS1( G ) )
00101       FS = F
00102       GS = G
00103       COUNT = 0
00104       IF( SCALE.GE.SAFMX2 ) THEN
00105    10    CONTINUE
00106          COUNT = COUNT + 1
00107          FS = FS*SAFMN2
00108          GS = GS*SAFMN2
00109          SCALE = SCALE*SAFMN2
00110          IF( SCALE.GE.SAFMX2 )
00111      $      GO TO 10
00112       ELSE IF( SCALE.LE.SAFMN2 ) THEN
00113          IF( G.EQ.CZERO ) THEN
00114             CS = ONE
00115             SN = CZERO
00116             R = F
00117             RETURN
00118          END IF
00119    20    CONTINUE
00120          COUNT = COUNT - 1
00121          FS = FS*SAFMX2
00122          GS = GS*SAFMX2
00123          SCALE = SCALE*SAFMX2
00124          IF( SCALE.LE.SAFMN2 )
00125      $      GO TO 20
00126       END IF
00127       F2 = ABSSQ( FS )
00128       G2 = ABSSQ( GS )
00129       IF( F2.LE.MAX( G2, ONE )*SAFMIN ) THEN
00130 *
00131 *        This is a rare case: F is very small.
00132 *
00133          IF( F.EQ.CZERO ) THEN
00134             CS = ZERO
00135             R = SLAPY2( REAL( G ), AIMAG( G ) )
00136 *           Do complex/real division explicitly with two real divisions
00137             D = SLAPY2( REAL( GS ), AIMAG( GS ) )
00138             SN = CMPLX( REAL( GS ) / D, -AIMAG( GS ) / D )
00139             RETURN
00140          END IF
00141          F2S = SLAPY2( REAL( FS ), AIMAG( FS ) )
00142 *        G2 and G2S are accurate
00143 *        G2 is at least SAFMIN, and G2S is at least SAFMN2
00144          G2S = SQRT( G2 )
00145 *        Error in CS from underflow in F2S is at most
00146 *        UNFL / SAFMN2 .lt. sqrt(UNFL*EPS) .lt. EPS
00147 *        If MAX(G2,ONE)=G2, then F2 .lt. G2*SAFMIN,
00148 *        and so CS .lt. sqrt(SAFMIN)
00149 *        If MAX(G2,ONE)=ONE, then F2 .lt. SAFMIN
00150 *        and so CS .lt. sqrt(SAFMIN)/SAFMN2 = sqrt(EPS)
00151 *        Therefore, CS = F2S/G2S / sqrt( 1 + (F2S/G2S)**2 ) = F2S/G2S
00152          CS = F2S / G2S
00153 *        Make sure abs(FF) = 1
00154 *        Do complex/real division explicitly with 2 real divisions
00155          IF( ABS1( F ).GT.ONE ) THEN
00156             D = SLAPY2( REAL( F ), AIMAG( F ) )
00157             FF = CMPLX( REAL( F ) / D, AIMAG( F ) / D )
00158          ELSE
00159             DR = SAFMX2*REAL( F )
00160             DI = SAFMX2*AIMAG( F )
00161             D = SLAPY2( DR, DI )
00162             FF = CMPLX( DR / D, DI / D )
00163          END IF
00164          SN = FF*CMPLX( REAL( GS ) / G2S, -AIMAG( GS ) / G2S )
00165          R = CS*F + SN*G
00166       ELSE
00167 *
00168 *        This is the most common case.
00169 *        Neither F2 nor F2/G2 are less than SAFMIN
00170 *        F2S cannot overflow, and it is accurate
00171 *
00172          F2S = SQRT( ONE+G2 / F2 )
00173 *        Do the F2S(real)*FS(complex) multiply with two real multiplies
00174          R = CMPLX( F2S*REAL( FS ), F2S*AIMAG( FS ) )
00175          CS = ONE / F2S
00176          D = F2 + G2
00177 *        Do complex/real division explicitly with two real divisions
00178          SN = CMPLX( REAL( R ) / D, AIMAG( R ) / D )
00179          SN = SN*CONJG( GS )
00180          IF( COUNT.NE.0 ) THEN
00181             IF( COUNT.GT.0 ) THEN
00182                DO 30 I = 1, COUNT
00183                   R = R*SAFMX2
00184    30          CONTINUE
00185             ELSE
00186                DO 40 I = 1, -COUNT
00187                   R = R*SAFMN2
00188    40          CONTINUE
00189             END IF
00190          END IF
00191       END IF
00192       RETURN
00193 *
00194 *     End of CLARTG
00195 *
00196       END
 All Files Functions