BLAS/SRC/zrotg.f90(3)      Library Functions Manual      BLAS/SRC/zrotg.f90(3)

NAME
       BLAS/SRC/zrotg.f90

SYNOPSIS
   Functions/Subroutines
       subroutine zrotg (a, b, c, s)
           ZROTG generates a Givens rotation with real cosine and complex
           sine.

Function/Subroutine Documentation
   subroutine zrotg (complex(wp) a, complex(wp) b, real(wp) c, complex(wp) s)
       ZROTG generates a Givens rotation with real cosine and complex sine.

       Purpose:


           !>
           !> ZROTG constructs a plane rotation
           !>    [  c         s ] [ a ] = [ r ]
           !>    [ -conjg(s)  c ] [ b ]   [ 0 ]
           !> where c is real, s is complex, and c**2 + conjg(s)*s = 1.
           !>
           !> The computation uses the formulas
           !>    |x| = sqrt( Re(x)**2 + Im(x)**2 )
           !>    sgn(x) = x / |x|  if x /= 0
           !>           = 1        if x  = 0
           !>    c = |a| / sqrt(|a|**2 + |b|**2)
           !>    s = sgn(a) * conjg(b) / sqrt(|a|**2 + |b|**2)
           !>    r = sgn(a)*sqrt(|a|**2 + |b|**2)
           !> When a and b are real and r /= 0, the formulas simplify to
           !>    c = a / r
           !>    s = b / r
           !> the same as in DROTG when |a| > |b|.  When |b| >= |a|, the
           !> sign of c and s will be different from those computed by DROTG
           !> if the signs of a and b are not the same.
           !>
           !>

       See also
           lartg:          generate plane rotation, more accurate than BLAS
           rot,


           lartgp:         generate plane rotation, more accurate than BLAS
           rot

       Parameters
           A

           !>          A is DOUBLE COMPLEX
           !>          On entry, the scalar a.
           !>          On exit, the scalar r.
           !>

           B

           !>          B is DOUBLE COMPLEX
           !>          The scalar b.
           !>

           C

           !>          C is DOUBLE PRECISION
           !>          The scalar c.
           !>

           S

           !>          S is DOUBLE COMPLEX
           !>          The scalar s.
           !>

       Author
           Weslley Pereira, University of Colorado Denver, USA

       Date
           December 2021

       Further Details:


           !>
           !> Based on the algorithm from
           !>
           !>  Anderson E. (2017)
           !>  Algorithm 978: Safe Scaling in the Level 1 BLAS
           !>  ACM Trans Math Softw 44:1--28
           !>  https://doi.org/10.1145/3061665
           !>
           !>

       Definition at line 88 of file zrotg.f90.

Author
       Generated automatically by Doxygen for LAPACK from the source code.

LAPACK                          Version 3.12.0           BLAS/SRC/zrotg.f90(3)