*nix Documentation Project
·  Home
 +   man pages
·  Linux HOWTOs
·  FreeBSD Tips
·  *niX Forums

  man pages->IRIX man pages -> complib/clags2 (3)              
Title
Content
Arch
Section
 

Contents


CLAGS2(3F)							    CLAGS2(3F)


NAME    [Toc]    [Back]

     CLAGS2 - compute 2-by-2 unitary matrices U, V and Q, such that if ( UPPER
     ) then   U'*A*Q = U'*( A1 A2 )*Q =	( x 0 )	 ( 0 A3	) ( x x	) and  V'*B*Q
     = V'*( B1 B2 )*Q =	( x 0 )	 ( 0 B3	) ( x x	)  or if ( .NOT.UPPER )	then
     U'*A*Q = U'*( A1 0	)*Q = (	x x )  ( A2 A3 ) ( 0 x ) and  V'*B*Q = V'*( B1
     0 )*Q = ( x x )  (	B2 B3 )	( 0 x )	where	U = ( CSU SNU ), V = ( CSV SNV
     ),

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	CLAGS2(	UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV, SNV,
			CSQ, SNQ )

	 LOGICAL	UPPER

	 REAL		A1, A3,	B1, B3,	CSQ, CSU, CSV

	 COMPLEX	A2, B2,	SNQ, SNU, SNV

PURPOSE    [Toc]    [Back]

     CLAGS2 computes 2-by-2 unitary matrices U,	V and Q, such that if (	UPPER
     ) then
	   ( -CONJG(SNU)  CSU )	     ( -CONJG(SNV) CSV )

       Q = (	 CSQ	  SNQ )
	   ( -CONJG(SNQ)  CSQ )

     Z'	denotes	the conjugate transpose	of Z.

     The rows of the transformed A and B are parallel. Moreover, if the	input
     2-by-2 matrix A is	not zero, then the transformed (1,1) entry of A	is not
     zero. If the input	matrices A and B are both not zero, then the
     transformed (2,2) element of B is not zero, except	when the first rows of
     input A and B are parallel	and the	second rows are	zero.

ARGUMENTS    [Toc]    [Back]

     UPPER   (input) LOGICAL
	     = .TRUE.: the input matrices A and	B are upper triangular.
	     = .FALSE.:	the input matrices A and B are lower triangular.

     A1	     (input) REAL
	     A2	     (input) COMPLEX A3	     (input) REAL On entry, A1,	A2 and
	     A3	are elements of	the input 2-by-2 upper (lower) triangular
	     matrix A.

     B1	     (input) REAL
	     B2	     (input) COMPLEX B3	     (input) REAL On entry, B1,	B2 and
	     B3	are elements of	the input 2-by-2 upper (lower) triangular
	     matrix B.






									Page 1






CLAGS2(3F)							    CLAGS2(3F)



     CSU     (output) REAL
	     SNU     (output) COMPLEX The desired unitary matrix U.

     CSV     (output) REAL
	     SNV     (output) COMPLEX The desired unitary matrix V.

     CSQ     (output) REAL
	     SNQ     (output) COMPLEX The desired unitary matrix Q.
CLAGS2(3F)							    CLAGS2(3F)


NAME    [Toc]    [Back]

     CLAGS2 - compute 2-by-2 unitary matrices U, V and Q, such that if ( UPPER
     ) then   U'*A*Q = U'*( A1 A2 )*Q =	( x 0 )	 ( 0 A3	) ( x x	) and  V'*B*Q
     = V'*( B1 B2 )*Q =	( x 0 )	 ( 0 B3	) ( x x	)  or if ( .NOT.UPPER )	then
     U'*A*Q = U'*( A1 0	)*Q = (	x x )  ( A2 A3 ) ( 0 x ) and  V'*B*Q = V'*( B1
     0 )*Q = ( x x )  (	B2 B3 )	( 0 x )	where	U = ( CSU SNU ), V = ( CSV SNV
     ),

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	CLAGS2(	UPPER, A1, A2, A3, B1, B2, B3, CSU, SNU, CSV, SNV,
			CSQ, SNQ )

	 LOGICAL	UPPER

	 REAL		A1, A3,	B1, B3,	CSQ, CSU, CSV

	 COMPLEX	A2, B2,	SNQ, SNU, SNV

PURPOSE    [Toc]    [Back]

     CLAGS2 computes 2-by-2 unitary matrices U,	V and Q, such that if (	UPPER
     ) then
	   ( -CONJG(SNU)  CSU )	     ( -CONJG(SNV) CSV )

       Q = (	 CSQ	  SNQ )
	   ( -CONJG(SNQ)  CSQ )

     Z'	denotes	the conjugate transpose	of Z.

     The rows of the transformed A and B are parallel. Moreover, if the	input
     2-by-2 matrix A is	not zero, then the transformed (1,1) entry of A	is not
     zero. If the input	matrices A and B are both not zero, then the
     transformed (2,2) element of B is not zero, except	when the first rows of
     input A and B are parallel	and the	second rows are	zero.

ARGUMENTS    [Toc]    [Back]

     UPPER   (input) LOGICAL
	     = .TRUE.: the input matrices A and	B are upper triangular.
	     = .FALSE.:	the input matrices A and B are lower triangular.

     A1	     (input) REAL
	     A2	     (input) COMPLEX A3	     (input) REAL On entry, A1,	A2 and
	     A3	are elements of	the input 2-by-2 upper (lower) triangular
	     matrix A.

     B1	     (input) REAL
	     B2	     (input) COMPLEX B3	     (input) REAL On entry, B1,	B2 and
	     B3	are elements of	the input 2-by-2 upper (lower) triangular
	     matrix B.






									Page 1






CLAGS2(3F)							    CLAGS2(3F)



     CSU     (output) REAL
	     SNU     (output) COMPLEX The desired unitary matrix U.

     CSV     (output) REAL
	     SNV     (output) COMPLEX The desired unitary matrix V.

     CSQ     (output) REAL
	     SNQ     (output) COMPLEX The desired unitary matrix Q.


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
zgghrd IRIX reduce a pair of complex matrices (A,B) to generalized upper Hessenberg form using unitary transformations, wh
cgghrd IRIX reduce a pair of complex matrices (A,B) to generalized upper Hessenberg form using unitary transformations, wh
slags2 IRIX compute 2-by-2 orthogonal matrices U, V and Q, such that if ( UPPER ) then U'*A*Q = U'*( A1 A2 )*Q = ( x 0 ) (
dlags2 IRIX compute 2-by-2 orthogonal matrices U, V and Q, such that if ( UPPER ) then U'*A*Q = U'*( A1 A2 )*Q = ( x 0 ) (
shseqr IRIX compute the eigenvalues of a real upper Hessenberg matrix H and, optionally, the matrices T and Z from the Sch
chseqr IRIX compute the eigenvalues of a complex upper Hessenberg matrix H, and, optionally, the matrices T and Z from the
dhseqr IRIX compute the eigenvalues of a real upper Hessenberg matrix H and, optionally, the matrices T and Z from the Sch
zhseqr IRIX compute the eigenvalues of a complex upper Hessenberg matrix H, and, optionally, the matrices T and Z from the
ctzrqf IRIX reduce the M-by-N ( M<=N ) complex upper trapezoidal matrix A to upper triangular form by means of unitary tra
ztzrqf IRIX reduce the M-by-N ( M<=N ) complex upper trapezoidal matrix A to upper triangular form by means of unitary tra
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service