LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
zrotg.f
Go to the documentation of this file.
1 *> \brief \b ZROTG
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE ZROTG(CA,CB,C,S)
12 *
13 * .. Scalar Arguments ..
14 * COMPLEX*16 CA,CB,S
15 * DOUBLE PRECISION C
16 * ..
17 *
18 *
19 *> \par Purpose:
20 * =============
21 *>
22 *> \verbatim
23 *>
24 *> ZROTG determines a double complex Givens rotation.
25 *> \endverbatim
26 *
27 * Arguments:
28 * ==========
29 *
30 *> \param[in] CA
31 *> \verbatim
32 *> CA is COMPLEX*16
33 *> \endverbatim
34 *>
35 *> \param[in] CB
36 *> \verbatim
37 *> CB is COMPLEX*16
38 *> \endverbatim
39 *>
40 *> \param[out] C
41 *> \verbatim
42 *> C is DOUBLE PRECISION
43 *> \endverbatim
44 *>
45 *> \param[out] S
46 *> \verbatim
47 *> S is COMPLEX*16
48 *> \endverbatim
49 *
50 * Authors:
51 * ========
52 *
53 *> \author Univ. of Tennessee
54 *> \author Univ. of California Berkeley
55 *> \author Univ. of Colorado Denver
56 *> \author NAG Ltd.
57 *
58 *> \date November 2017
59 *
60 *> \ingroup complex16_blas_level1
61 *
62 * =====================================================================
63  SUBROUTINE zrotg(CA,CB,C,S)
64 *
65 * -- Reference BLAS level1 routine (version 3.8.0) --
66 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
67 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
68 * November 2017
69 *
70 * .. Scalar Arguments ..
71  COMPLEX*16 CA,CB,S
72  DOUBLE PRECISION C
73 * ..
74 *
75 * =====================================================================
76 *
77 * .. Local Scalars ..
78  COMPLEX*16 ALPHA
79  DOUBLE PRECISION NORM,SCALE
80 * ..
81 * .. Intrinsic Functions ..
82  INTRINSIC cdabs,dcmplx,dconjg,dsqrt
83 * ..
84  IF (cdabs(ca).EQ.0.0d0) THEN
85  c = 0.0d0
86  s = (1.0d0,0.0d0)
87  ca = cb
88  ELSE
89  scale = cdabs(ca) + cdabs(cb)
90  norm = scale*dsqrt((cdabs(ca/dcmplx(scale,0.0d0)))**2+
91  $ (cdabs(cb/dcmplx(scale,0.0d0)))**2)
92  alpha = ca/cdabs(ca)
93  c = cdabs(ca)/norm
94  s = alpha*dconjg(cb)/norm
95  ca = alpha*norm
96  END IF
97  RETURN
98  END
zrotg
subroutine zrotg(CA, CB, C, S)
ZROTG
Definition: zrotg.f:64