3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLAGS2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clags2.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clags2.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clags2.f">
21 * SUBROUTINE CLAGS2( UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV,
24 * .. Scalar Arguments ..
26 * REAL A1, A3, B1, B3, CSQ, CSU, CSV
27 * COMPLEX A2, B2, SNQ, SNU, SNV
36 *> CLAGS2 computes 2-by-2 unitary matrices U, V and Q, such
37 *> that if ( UPPER ) then
39 *> U**H *A*Q = U**H *( A1 A2 )*Q = ( x 0 )
42 *> V**H*B*Q = V**H *( B1 B2 )*Q = ( x 0 )
45 *> or if ( .NOT.UPPER ) then
47 *> U**H *A*Q = U**H *( A1 0 )*Q = ( x x )
50 *> V**H *B*Q = V**H *( B1 0 )*Q = ( x x )
54 *> U = ( CSU SNU ), V = ( CSV SNV ),
55 *> ( -SNU**H CSU ) ( -SNV**H CSV )
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
74 *> = .TRUE.: the input matrices A and B are upper triangular.
75 *> = .FALSE.: the input matrices A and B are lower triangular.
91 *> On entry, A1, A2 and A3 are elements of the input 2-by-2
92 *> upper (lower) triangular matrix A.
108 *> On entry, B1, B2 and B3 are elements of the input 2-by-2
109 *> upper (lower) triangular matrix B.
120 *> The desired unitary matrix U.
131 *> The desired unitary matrix V.
142 *> The desired unitary matrix Q.
148 *> \author Univ. of Tennessee
149 *> \author Univ. of California Berkeley
150 *> \author Univ. of Colorado Denver
153 *> \date November 2011
155 *> \ingroup complexOTHERauxiliary
157 * =====================================================================
158 SUBROUTINE CLAGS2( UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV,
161 * -- LAPACK auxiliary routine (version 3.4.0) --
162 * -- LAPACK is a software package provided by Univ. of Tennessee, --
163 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
166 * .. Scalar Arguments ..
168 REAL A1, A3, B1, B3, CSQ, CSU, CSV
169 COMPLEX A2, B2, SNQ, SNU, SNV
172 * =====================================================================
176 PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
178 * .. Local Scalars ..
179 REAL A, AUA11, AUA12, AUA21, AUA22, AVB11, AVB12,
180 $ AVB21, AVB22, CSL, CSR, D, FB, FC, S1, S2, SNL,
181 $ SNR, UA11R, UA22R, VB11R, VB22R
182 COMPLEX B, C, D1, R, T, UA11, UA12, UA21, UA22, VB11,
185 * .. External Subroutines ..
186 EXTERNAL CLARTG, SLASV2
188 * .. Intrinsic Functions ..
189 INTRINSIC ABS, AIMAG, CMPLX, CONJG, REAL
191 * .. Statement Functions ..
194 * .. Statement Function definitions ..
195 ABS1( T ) = ABS( REAL( T ) ) + ABS( AIMAG( T ) )
197 * .. Executable Statements ..
201 * Input matrices A and B are upper triangular matrices
203 * Form matrix C = A*adj(B) = ( a b )
211 * Transform complex 2-by-2 matrix C to real matrix by unitary
212 * diagonal matrix diag(1,D1).
218 * The SVD of real 2 by 2 triangular C
220 * ( CSL -SNL )*( A B )*( CSR SNR ) = ( R 0 )
221 * ( SNL CSL ) ( 0 D ) ( -SNR CSR ) ( 0 T )
223 CALL SLASV2( A, FB, D, S1, S2, SNR, CSR, SNL, CSL )
225 IF( ABS( CSL ).GE.ABS( SNL ) .OR. ABS( CSR ).GE.ABS( SNR ) )
228 * Compute the (1,1) and (1,2) elements of U**H *A and V**H *B,
229 * and (1,2) element of |U|**H *|A| and |V|**H *|B|.
232 UA12 = CSL*A2 + D1*SNL*A3
235 VB12 = CSR*B2 + D1*SNR*B3
237 AUA12 = ABS( CSL )*ABS1( A2 ) + ABS( SNL )*ABS( A3 )
238 AVB12 = ABS( CSR )*ABS1( B2 ) + ABS( SNR )*ABS( B3 )
240 * zero (1,2) elements of U**H *A and V**H *B
242 IF( ( ABS( UA11R )+ABS1( UA12 ) ).EQ.ZERO ) THEN
243 CALL CLARTG( -CMPLX( VB11R ), CONJG( VB12 ), CSQ, SNQ,
245 ELSE IF( ( ABS( VB11R )+ABS1( VB12 ) ).EQ.ZERO ) THEN
246 CALL CLARTG( -CMPLX( UA11R ), CONJG( UA12 ), CSQ, SNQ,
248 ELSE IF( AUA12 / ( ABS( UA11R )+ABS1( UA12 ) ).LE.AVB12 /
249 $ ( ABS( VB11R )+ABS1( VB12 ) ) ) THEN
250 CALL CLARTG( -CMPLX( UA11R ), CONJG( UA12 ), CSQ, SNQ,
253 CALL CLARTG( -CMPLX( VB11R ), CONJG( VB12 ), CSQ, SNQ,
264 * Compute the (2,1) and (2,2) elements of U**H *A and V**H *B,
265 * and (2,2) element of |U|**H *|A| and |V|**H *|B|.
267 UA21 = -CONJG( D1 )*SNL*A1
268 UA22 = -CONJG( D1 )*SNL*A2 + CSL*A3
270 VB21 = -CONJG( D1 )*SNR*B1
271 VB22 = -CONJG( D1 )*SNR*B2 + CSR*B3
273 AUA22 = ABS( SNL )*ABS1( A2 ) + ABS( CSL )*ABS( A3 )
274 AVB22 = ABS( SNR )*ABS1( B2 ) + ABS( CSR )*ABS( B3 )
276 * zero (2,2) elements of U**H *A and V**H *B, and then swap.
278 IF( ( ABS1( UA21 )+ABS1( UA22 ) ).EQ.ZERO ) THEN
279 CALL CLARTG( -CONJG( VB21 ), CONJG( VB22 ), CSQ, SNQ, R )
280 ELSE IF( ( ABS1( VB21 )+ABS( VB22 ) ).EQ.ZERO ) THEN
281 CALL CLARTG( -CONJG( UA21 ), CONJG( UA22 ), CSQ, SNQ, R )
282 ELSE IF( AUA22 / ( ABS1( UA21 )+ABS1( UA22 ) ).LE.AVB22 /
283 $ ( ABS1( VB21 )+ABS1( VB22 ) ) ) THEN
284 CALL CLARTG( -CONJG( UA21 ), CONJG( UA22 ), CSQ, SNQ, R )
286 CALL CLARTG( -CONJG( VB21 ), CONJG( VB22 ), CSQ, SNQ, R )
298 * Input matrices A and B are lower triangular matrices
300 * Form matrix C = A*adj(B) = ( a 0 )
308 * Transform complex 2-by-2 matrix C to real matrix by unitary
309 * diagonal matrix diag(d1,1).
315 * The SVD of real 2 by 2 triangular C
317 * ( CSL -SNL )*( A 0 )*( CSR SNR ) = ( R 0 )
318 * ( SNL CSL ) ( C D ) ( -SNR CSR ) ( 0 T )
320 CALL SLASV2( A, FC, D, S1, S2, SNR, CSR, SNL, CSL )
322 IF( ABS( CSR ).GE.ABS( SNR ) .OR. ABS( CSL ).GE.ABS( SNL ) )
325 * Compute the (2,1) and (2,2) elements of U**H *A and V**H *B,
326 * and (2,1) element of |U|**H *|A| and |V|**H *|B|.
328 UA21 = -D1*SNR*A1 + CSR*A2
331 VB21 = -D1*SNL*B1 + CSL*B2
334 AUA21 = ABS( SNR )*ABS( A1 ) + ABS( CSR )*ABS1( A2 )
335 AVB21 = ABS( SNL )*ABS( B1 ) + ABS( CSL )*ABS1( B2 )
337 * zero (2,1) elements of U**H *A and V**H *B.
339 IF( ( ABS1( UA21 )+ABS( UA22R ) ).EQ.ZERO ) THEN
340 CALL CLARTG( CMPLX( VB22R ), VB21, CSQ, SNQ, R )
341 ELSE IF( ( ABS1( VB21 )+ABS( VB22R ) ).EQ.ZERO ) THEN
342 CALL CLARTG( CMPLX( UA22R ), UA21, CSQ, SNQ, R )
343 ELSE IF( AUA21 / ( ABS1( UA21 )+ABS( UA22R ) ).LE.AVB21 /
344 $ ( ABS1( VB21 )+ABS( VB22R ) ) ) THEN
345 CALL CLARTG( CMPLX( UA22R ), UA21, CSQ, SNQ, R )
347 CALL CLARTG( CMPLX( VB22R ), VB21, CSQ, SNQ, R )
351 SNU = -CONJG( D1 )*SNR
353 SNV = -CONJG( D1 )*SNL
357 * Compute the (1,1) and (1,2) elements of U**H *A and V**H *B,
358 * and (1,1) element of |U|**H *|A| and |V|**H *|B|.
360 UA11 = CSR*A1 + CONJG( D1 )*SNR*A2
361 UA12 = CONJG( D1 )*SNR*A3
363 VB11 = CSL*B1 + CONJG( D1 )*SNL*B2
364 VB12 = CONJG( D1 )*SNL*B3
366 AUA11 = ABS( CSR )*ABS( A1 ) + ABS( SNR )*ABS1( A2 )
367 AVB11 = ABS( CSL )*ABS( B1 ) + ABS( SNL )*ABS1( B2 )
369 * zero (1,1) elements of U**H *A and V**H *B, and then swap.
371 IF( ( ABS1( UA11 )+ABS1( UA12 ) ).EQ.ZERO ) THEN
372 CALL CLARTG( VB12, VB11, CSQ, SNQ, R )
373 ELSE IF( ( ABS1( VB11 )+ABS1( VB12 ) ).EQ.ZERO ) THEN
374 CALL CLARTG( UA12, UA11, CSQ, SNQ, R )
375 ELSE IF( AUA11 / ( ABS1( UA11 )+ABS1( UA12 ) ).LE.AVB11 /
376 $ ( ABS1( VB11 )+ABS1( VB12 ) ) ) THEN
377 CALL CLARTG( UA12, UA11, CSQ, SNQ, R )
379 CALL CLARTG( VB12, VB11, CSQ, SNQ, R )
383 SNU = CONJG( D1 )*CSR
385 SNV = CONJG( D1 )*CSL