1*> \brief \b CLAGS2
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CLAGS2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clags2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clags2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clags2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE CLAGS2( UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV,
22*                          SNV, CSQ, SNQ )
23*
24*       .. Scalar Arguments ..
25*       LOGICAL            UPPER
26*       REAL               A1, A3, B1, B3, CSQ, CSU, CSV
27*       COMPLEX            A2, B2, SNQ, SNU, SNV
28*       ..
29*
30*
31*> \par Purpose:
32*  =============
33*>
34*> \verbatim
35*>
36*> CLAGS2 computes 2-by-2 unitary matrices U, V and Q, such
37*> that if ( UPPER ) then
38*>
39*>           U**H *A*Q = U**H *( A1 A2 )*Q = ( x  0  )
40*>                             ( 0  A3 )     ( x  x  )
41*> and
42*>           V**H*B*Q = V**H *( B1 B2 )*Q = ( x  0  )
43*>                            ( 0  B3 )     ( x  x  )
44*>
45*> or if ( .NOT.UPPER ) then
46*>
47*>           U**H *A*Q = U**H *( A1 0  )*Q = ( x  x  )
48*>                             ( A2 A3 )     ( 0  x  )
49*> and
50*>           V**H *B*Q = V**H *( B1 0  )*Q = ( x  x  )
51*>                             ( B2 B3 )     ( 0  x  )
52*> where
53*>
54*>   U = (   CSU    SNU ), V = (  CSV    SNV ),
55*>       ( -SNU**H  CSU )      ( -SNV**H CSV )
56*>
57*>   Q = (   CSQ    SNQ )
58*>       ( -SNQ**H  CSQ )
59*>
60*> The rows of the transformed A and B are parallel. Moreover, if the
61*> input 2-by-2 matrix A is not zero, then the transformed (1,1) entry
62*> of A is not zero. If the input matrices A and B are both not zero,
63*> then the transformed (2,2) element of B is not zero, except when the
64*> first rows of input A and B are parallel and the second rows are
65*> zero.
66*> \endverbatim
67*
68*  Arguments:
69*  ==========
70*
71*> \param[in] UPPER
72*> \verbatim
73*>          UPPER is LOGICAL
74*>          = .TRUE.: the input matrices A and B are upper triangular.
75*>          = .FALSE.: the input matrices A and B are lower triangular.
76*> \endverbatim
77*>
78*> \param[in] A1
79*> \verbatim
80*>          A1 is REAL
81*> \endverbatim
82*>
83*> \param[in] A2
84*> \verbatim
85*>          A2 is COMPLEX
86*> \endverbatim
87*>
88*> \param[in] A3
89*> \verbatim
90*>          A3 is REAL
91*>          On entry, A1, A2 and A3 are elements of the input 2-by-2
92*>          upper (lower) triangular matrix A.
93*> \endverbatim
94*>
95*> \param[in] B1
96*> \verbatim
97*>          B1 is REAL
98*> \endverbatim
99*>
100*> \param[in] B2
101*> \verbatim
102*>          B2 is COMPLEX
103*> \endverbatim
104*>
105*> \param[in] B3
106*> \verbatim
107*>          B3 is REAL
108*>          On entry, B1, B2 and B3 are elements of the input 2-by-2
109*>          upper (lower) triangular matrix B.
110*> \endverbatim
111*>
112*> \param[out] CSU
113*> \verbatim
114*>          CSU is REAL
115*> \endverbatim
116*>
117*> \param[out] SNU
118*> \verbatim
119*>          SNU is COMPLEX
120*>          The desired unitary matrix U.
121*> \endverbatim
122*>
123*> \param[out] CSV
124*> \verbatim
125*>          CSV is REAL
126*> \endverbatim
127*>
128*> \param[out] SNV
129*> \verbatim
130*>          SNV is COMPLEX
131*>          The desired unitary matrix V.
132*> \endverbatim
133*>
134*> \param[out] CSQ
135*> \verbatim
136*>          CSQ is REAL
137*> \endverbatim
138*>
139*> \param[out] SNQ
140*> \verbatim
141*>          SNQ is COMPLEX
142*>          The desired unitary matrix Q.
143*> \endverbatim
144*
145*  Authors:
146*  ========
147*
148*> \author Univ. of Tennessee
149*> \author Univ. of California Berkeley
150*> \author Univ. of Colorado Denver
151*> \author NAG Ltd.
152*
153*> \ingroup complexOTHERauxiliary
154*
155*  =====================================================================
156      SUBROUTINE CLAGS2( UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV,
157     $                   SNV, CSQ, SNQ )
158*
159*  -- LAPACK auxiliary routine --
160*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
161*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162*
163*     .. Scalar Arguments ..
164      LOGICAL            UPPER
165      REAL               A1, A3, B1, B3, CSQ, CSU, CSV
166      COMPLEX            A2, B2, SNQ, SNU, SNV
167*     ..
168*
169*  =====================================================================
170*
171*     .. Parameters ..
172      REAL               ZERO, ONE
173      PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
174*     ..
175*     .. Local Scalars ..
176      REAL               A, AUA11, AUA12, AUA21, AUA22, AVB11, AVB12,
177     $                   AVB21, AVB22, CSL, CSR, D, FB, FC, S1, S2, SNL,
178     $                   SNR, UA11R, UA22R, VB11R, VB22R
179      COMPLEX            B, C, D1, R, T, UA11, UA12, UA21, UA22, VB11,
180     $                   VB12, VB21, VB22
181*     ..
182*     .. External Subroutines ..
183      EXTERNAL           CLARTG, SLASV2
184*     ..
185*     .. Intrinsic Functions ..
186      INTRINSIC          ABS, AIMAG, CMPLX, CONJG, REAL
187*     ..
188*     .. Statement Functions ..
189      REAL               ABS1
190*     ..
191*     .. Statement Function definitions ..
192      ABS1( T ) = ABS( REAL( T ) ) + ABS( AIMAG( T ) )
193*     ..
194*     .. Executable Statements ..
195*
196      IF( UPPER ) THEN
197*
198*        Input matrices A and B are upper triangular matrices
199*
200*        Form matrix C = A*adj(B) = ( a b )
201*                                   ( 0 d )
202*
203         A = A1*B3
204         D = A3*B1
205         B = A2*B1 - A1*B2
206         FB = ABS( B )
207*
208*        Transform complex 2-by-2 matrix C to real matrix by unitary
209*        diagonal matrix diag(1,D1).
210*
211         D1 = ONE
212         IF( FB.NE.ZERO )
213     $      D1 = B / FB
214*
215*        The SVD of real 2 by 2 triangular C
216*
217*         ( CSL -SNL )*( A B )*(  CSR  SNR ) = ( R 0 )
218*         ( SNL  CSL ) ( 0 D ) ( -SNR  CSR )   ( 0 T )
219*
220         CALL SLASV2( A, FB, D, S1, S2, SNR, CSR, SNL, CSL )
221*
222         IF( ABS( CSL ).GE.ABS( SNL ) .OR. ABS( CSR ).GE.ABS( SNR ) )
223     $        THEN
224*
225*           Compute the (1,1) and (1,2) elements of U**H *A and V**H *B,
226*           and (1,2) element of |U|**H *|A| and |V|**H *|B|.
227*
228            UA11R = CSL*A1
229            UA12 = CSL*A2 + D1*SNL*A3
230*
231            VB11R = CSR*B1
232            VB12 = CSR*B2 + D1*SNR*B3
233*
234            AUA12 = ABS( CSL )*ABS1( A2 ) + ABS( SNL )*ABS( A3 )
235            AVB12 = ABS( CSR )*ABS1( B2 ) + ABS( SNR )*ABS( B3 )
236*
237*           zero (1,2) elements of U**H *A and V**H *B
238*
239            IF( ( ABS( UA11R )+ABS1( UA12 ) ).EQ.ZERO ) THEN
240               CALL CLARTG( -CMPLX( VB11R ), CONJG( VB12 ), CSQ, SNQ,
241     $                      R )
242            ELSE IF( ( ABS( VB11R )+ABS1( VB12 ) ).EQ.ZERO ) THEN
243               CALL CLARTG( -CMPLX( UA11R ), CONJG( UA12 ), CSQ, SNQ,
244     $                      R )
245            ELSE IF( AUA12 / ( ABS( UA11R )+ABS1( UA12 ) ).LE.AVB12 /
246     $               ( ABS( VB11R )+ABS1( VB12 ) ) ) THEN
247               CALL CLARTG( -CMPLX( UA11R ), CONJG( UA12 ), CSQ, SNQ,
248     $                      R )
249            ELSE
250               CALL CLARTG( -CMPLX( VB11R ), CONJG( VB12 ), CSQ, SNQ,
251     $                      R )
252            END IF
253*
254            CSU = CSL
255            SNU = -D1*SNL
256            CSV = CSR
257            SNV = -D1*SNR
258*
259         ELSE
260*
261*           Compute the (2,1) and (2,2) elements of U**H *A and V**H *B,
262*           and (2,2) element of |U|**H *|A| and |V|**H *|B|.
263*
264            UA21 = -CONJG( D1 )*SNL*A1
265            UA22 = -CONJG( D1 )*SNL*A2 + CSL*A3
266*
267            VB21 = -CONJG( D1 )*SNR*B1
268            VB22 = -CONJG( D1 )*SNR*B2 + CSR*B3
269*
270            AUA22 = ABS( SNL )*ABS1( A2 ) + ABS( CSL )*ABS( A3 )
271            AVB22 = ABS( SNR )*ABS1( B2 ) + ABS( CSR )*ABS( B3 )
272*
273*           zero (2,2) elements of U**H *A and V**H *B, and then swap.
274*
275            IF( ( ABS1( UA21 )+ABS1( UA22 ) ).EQ.ZERO ) THEN
276               CALL CLARTG( -CONJG( VB21 ), CONJG( VB22 ), CSQ, SNQ, R )
277            ELSE IF( ( ABS1( VB21 )+ABS( VB22 ) ).EQ.ZERO ) THEN
278               CALL CLARTG( -CONJG( UA21 ), CONJG( UA22 ), CSQ, SNQ, R )
279            ELSE IF( AUA22 / ( ABS1( UA21 )+ABS1( UA22 ) ).LE.AVB22 /
280     $               ( ABS1( VB21 )+ABS1( VB22 ) ) ) THEN
281               CALL CLARTG( -CONJG( UA21 ), CONJG( UA22 ), CSQ, SNQ, R )
282            ELSE
283               CALL CLARTG( -CONJG( VB21 ), CONJG( VB22 ), CSQ, SNQ, R )
284            END IF
285*
286            CSU = SNL
287            SNU = D1*CSL
288            CSV = SNR
289            SNV = D1*CSR
290*
291         END IF
292*
293      ELSE
294*
295*        Input matrices A and B are lower triangular matrices
296*
297*        Form matrix C = A*adj(B) = ( a 0 )
298*                                   ( c d )
299*
300         A = A1*B3
301         D = A3*B1
302         C = A2*B3 - A3*B2
303         FC = ABS( C )
304*
305*        Transform complex 2-by-2 matrix C to real matrix by unitary
306*        diagonal matrix diag(d1,1).
307*
308         D1 = ONE
309         IF( FC.NE.ZERO )
310     $      D1 = C / FC
311*
312*        The SVD of real 2 by 2 triangular C
313*
314*         ( CSL -SNL )*( A 0 )*(  CSR  SNR ) = ( R 0 )
315*         ( SNL  CSL ) ( C D ) ( -SNR  CSR )   ( 0 T )
316*
317         CALL SLASV2( A, FC, D, S1, S2, SNR, CSR, SNL, CSL )
318*
319         IF( ABS( CSR ).GE.ABS( SNR ) .OR. ABS( CSL ).GE.ABS( SNL ) )
320     $        THEN
321*
322*           Compute the (2,1) and (2,2) elements of U**H *A and V**H *B,
323*           and (2,1) element of |U|**H *|A| and |V|**H *|B|.
324*
325            UA21 = -D1*SNR*A1 + CSR*A2
326            UA22R = CSR*A3
327*
328            VB21 = -D1*SNL*B1 + CSL*B2
329            VB22R = CSL*B3
330*
331            AUA21 = ABS( SNR )*ABS( A1 ) + ABS( CSR )*ABS1( A2 )
332            AVB21 = ABS( SNL )*ABS( B1 ) + ABS( CSL )*ABS1( B2 )
333*
334*           zero (2,1) elements of U**H *A and V**H *B.
335*
336            IF( ( ABS1( UA21 )+ABS( UA22R ) ).EQ.ZERO ) THEN
337               CALL CLARTG( CMPLX( VB22R ), VB21, CSQ, SNQ, R )
338            ELSE IF( ( ABS1( VB21 )+ABS( VB22R ) ).EQ.ZERO ) THEN
339               CALL CLARTG( CMPLX( UA22R ), UA21, CSQ, SNQ, R )
340            ELSE IF( AUA21 / ( ABS1( UA21 )+ABS( UA22R ) ).LE.AVB21 /
341     $               ( ABS1( VB21 )+ABS( VB22R ) ) ) THEN
342               CALL CLARTG( CMPLX( UA22R ), UA21, CSQ, SNQ, R )
343            ELSE
344               CALL CLARTG( CMPLX( VB22R ), VB21, CSQ, SNQ, R )
345            END IF
346*
347            CSU = CSR
348            SNU = -CONJG( D1 )*SNR
349            CSV = CSL
350            SNV = -CONJG( D1 )*SNL
351*
352         ELSE
353*
354*           Compute the (1,1) and (1,2) elements of U**H *A and V**H *B,
355*           and (1,1) element of |U|**H *|A| and |V|**H *|B|.
356*
357            UA11 = CSR*A1 + CONJG( D1 )*SNR*A2
358            UA12 = CONJG( D1 )*SNR*A3
359*
360            VB11 = CSL*B1 + CONJG( D1 )*SNL*B2
361            VB12 = CONJG( D1 )*SNL*B3
362*
363            AUA11 = ABS( CSR )*ABS( A1 ) + ABS( SNR )*ABS1( A2 )
364            AVB11 = ABS( CSL )*ABS( B1 ) + ABS( SNL )*ABS1( B2 )
365*
366*           zero (1,1) elements of U**H *A and V**H *B, and then swap.
367*
368            IF( ( ABS1( UA11 )+ABS1( UA12 ) ).EQ.ZERO ) THEN
369               CALL CLARTG( VB12, VB11, CSQ, SNQ, R )
370            ELSE IF( ( ABS1( VB11 )+ABS1( VB12 ) ).EQ.ZERO ) THEN
371               CALL CLARTG( UA12, UA11, CSQ, SNQ, R )
372            ELSE IF( AUA11 / ( ABS1( UA11 )+ABS1( UA12 ) ).LE.AVB11 /
373     $               ( ABS1( VB11 )+ABS1( VB12 ) ) ) THEN
374               CALL CLARTG( UA12, UA11, CSQ, SNQ, R )
375            ELSE
376               CALL CLARTG( VB12, VB11, CSQ, SNQ, R )
377            END IF
378*
379            CSU = SNR
380            SNU = CONJG( D1 )*CSR
381            CSV = SNL
382            SNV = CONJG( D1 )*CSL
383*
384         END IF
385*
386      END IF
387*
388      RETURN
389*
390*     End of CLAGS2
391*
392      END
393