Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / clags2.f
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 *> \date November 2011
154 *
155 *> \ingroup complexOTHERauxiliary
156 *
157 *  =====================================================================
158       SUBROUTINE CLAGS2( UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV,
159      $                   SNV, CSQ, SNQ )
160 *
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..--
164 *     November 2011
165 *
166 *     .. Scalar Arguments ..
167       LOGICAL            UPPER
168       REAL               A1, A3, B1, B3, CSQ, CSU, CSV
169       COMPLEX            A2, B2, SNQ, SNU, SNV
170 *     ..
171 *
172 *  =====================================================================
173 *
174 *     .. Parameters ..
175       REAL               ZERO, ONE
176       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
177 *     ..
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,
183      $                   VB12, VB21, VB22
184 *     ..
185 *     .. External Subroutines ..
186       EXTERNAL           CLARTG, SLASV2
187 *     ..
188 *     .. Intrinsic Functions ..
189       INTRINSIC          ABS, AIMAG, CMPLX, CONJG, REAL
190 *     ..
191 *     .. Statement Functions ..
192       REAL               ABS1
193 *     ..
194 *     .. Statement Function definitions ..
195       ABS1( T ) = ABS( REAL( T ) ) + ABS( AIMAG( T ) )
196 *     ..
197 *     .. Executable Statements ..
198 *
199       IF( UPPER ) THEN
200 *
201 *        Input matrices A and B are upper triangular matrices
202 *
203 *        Form matrix C = A*adj(B) = ( a b )
204 *                                   ( 0 d )
205 *
206          A = A1*B3
207          D = A3*B1
208          B = A2*B1 - A1*B2
209          FB = ABS( B )
210 *
211 *        Transform complex 2-by-2 matrix C to real matrix by unitary
212 *        diagonal matrix diag(1,D1).
213 *
214          D1 = ONE
215          IF( FB.NE.ZERO )
216      $      D1 = B / FB
217 *
218 *        The SVD of real 2 by 2 triangular C
219 *
220 *         ( CSL -SNL )*( A B )*(  CSR  SNR ) = ( R 0 )
221 *         ( SNL  CSL ) ( 0 D ) ( -SNR  CSR )   ( 0 T )
222 *
223          CALL SLASV2( A, FB, D, S1, S2, SNR, CSR, SNL, CSL )
224 *
225          IF( ABS( CSL ).GE.ABS( SNL ) .OR. ABS( CSR ).GE.ABS( SNR ) )
226      $        THEN
227 *
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|.
230 *
231             UA11R = CSL*A1
232             UA12 = CSL*A2 + D1*SNL*A3
233 *
234             VB11R = CSR*B1
235             VB12 = CSR*B2 + D1*SNR*B3
236 *
237             AUA12 = ABS( CSL )*ABS1( A2 ) + ABS( SNL )*ABS( A3 )
238             AVB12 = ABS( CSR )*ABS1( B2 ) + ABS( SNR )*ABS( B3 )
239 *
240 *           zero (1,2) elements of U**H *A and V**H *B
241 *
242             IF( ( ABS( UA11R )+ABS1( UA12 ) ).EQ.ZERO ) THEN
243                CALL CLARTG( -CMPLX( VB11R ), CONJG( VB12 ), CSQ, SNQ,
244      $                      R )
245             ELSE IF( ( ABS( VB11R )+ABS1( VB12 ) ).EQ.ZERO ) THEN
246                CALL CLARTG( -CMPLX( UA11R ), CONJG( UA12 ), CSQ, SNQ,
247      $                      R )
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,
251      $                      R )
252             ELSE
253                CALL CLARTG( -CMPLX( VB11R ), CONJG( VB12 ), CSQ, SNQ,
254      $                      R )
255             END IF
256 *
257             CSU = CSL
258             SNU = -D1*SNL
259             CSV = CSR
260             SNV = -D1*SNR
261 *
262          ELSE
263 *
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|.
266 *
267             UA21 = -CONJG( D1 )*SNL*A1
268             UA22 = -CONJG( D1 )*SNL*A2 + CSL*A3
269 *
270             VB21 = -CONJG( D1 )*SNR*B1
271             VB22 = -CONJG( D1 )*SNR*B2 + CSR*B3
272 *
273             AUA22 = ABS( SNL )*ABS1( A2 ) + ABS( CSL )*ABS( A3 )
274             AVB22 = ABS( SNR )*ABS1( B2 ) + ABS( CSR )*ABS( B3 )
275 *
276 *           zero (2,2) elements of U**H *A and V**H *B, and then swap.
277 *
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 )
285             ELSE
286                CALL CLARTG( -CONJG( VB21 ), CONJG( VB22 ), CSQ, SNQ, R )
287             END IF
288 *
289             CSU = SNL
290             SNU = D1*CSL
291             CSV = SNR
292             SNV = D1*CSR
293 *
294          END IF
295 *
296       ELSE
297 *
298 *        Input matrices A and B are lower triangular matrices
299 *
300 *        Form matrix C = A*adj(B) = ( a 0 )
301 *                                   ( c d )
302 *
303          A = A1*B3
304          D = A3*B1
305          C = A2*B3 - A3*B2
306          FC = ABS( C )
307 *
308 *        Transform complex 2-by-2 matrix C to real matrix by unitary
309 *        diagonal matrix diag(d1,1).
310 *
311          D1 = ONE
312          IF( FC.NE.ZERO )
313      $      D1 = C / FC
314 *
315 *        The SVD of real 2 by 2 triangular C
316 *
317 *         ( CSL -SNL )*( A 0 )*(  CSR  SNR ) = ( R 0 )
318 *         ( SNL  CSL ) ( C D ) ( -SNR  CSR )   ( 0 T )
319 *
320          CALL SLASV2( A, FC, D, S1, S2, SNR, CSR, SNL, CSL )
321 *
322          IF( ABS( CSR ).GE.ABS( SNR ) .OR. ABS( CSL ).GE.ABS( SNL ) )
323      $        THEN
324 *
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|.
327 *
328             UA21 = -D1*SNR*A1 + CSR*A2
329             UA22R = CSR*A3
330 *
331             VB21 = -D1*SNL*B1 + CSL*B2
332             VB22R = CSL*B3
333 *
334             AUA21 = ABS( SNR )*ABS( A1 ) + ABS( CSR )*ABS1( A2 )
335             AVB21 = ABS( SNL )*ABS( B1 ) + ABS( CSL )*ABS1( B2 )
336 *
337 *           zero (2,1) elements of U**H *A and V**H *B.
338 *
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 )
346             ELSE
347                CALL CLARTG( CMPLX( VB22R ), VB21, CSQ, SNQ, R )
348             END IF
349 *
350             CSU = CSR
351             SNU = -CONJG( D1 )*SNR
352             CSV = CSL
353             SNV = -CONJG( D1 )*SNL
354 *
355          ELSE
356 *
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|.
359 *
360             UA11 = CSR*A1 + CONJG( D1 )*SNR*A2
361             UA12 = CONJG( D1 )*SNR*A3
362 *
363             VB11 = CSL*B1 + CONJG( D1 )*SNL*B2
364             VB12 = CONJG( D1 )*SNL*B3
365 *
366             AUA11 = ABS( CSR )*ABS( A1 ) + ABS( SNR )*ABS1( A2 )
367             AVB11 = ABS( CSL )*ABS( B1 ) + ABS( SNL )*ABS1( B2 )
368 *
369 *           zero (1,1) elements of U**H *A and V**H *B, and then swap.
370 *
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 )
378             ELSE
379                CALL CLARTG( VB12, VB11, CSQ, SNQ, R )
380             END IF
381 *
382             CSU = SNR
383             SNU = CONJG( D1 )*CSR
384             CSV = SNL
385             SNV = CONJG( D1 )*CSL
386 *
387          END IF
388 *
389       END IF
390 *
391       RETURN
392 *
393 *     End of CLAGS2
394 *
395       END