tgsja Interface

public interface tgsja

TGSJA computes the generalized singular value decomposition (GSVD) of two complex upper triangular (or trapezoidal) matrices A and B. On entry, it is assumed that matrices A and B have the following forms, which may be obtained by the preprocessing subroutine CGGSVP from a general M-by-N matrix A and P-by-N matrix B: N-K-L K L A = K ( 0 A12 A13 ) if M-K-L >= 0; L ( 0 0 A23 ) M-K-L ( 0 0 0 ) N-K-L K L A = K ( 0 A12 A13 ) if M-K-L < 0; M-K ( 0 0 A23 ) N-K-L K L B = L ( 0 0 B13 ) P-L ( 0 0 0 ) where the K-by-K matrix A12 and L-by-L matrix B13 are nonsingular upper triangular; A23 is L-by-L upper triangular if M-K-L >= 0, otherwise A23 is (M-K)-by-L upper trapezoidal. On exit, UH AQ = D1*( 0 R ), VH BQ = D2( 0 R ), where U, V and Q are unitary matrices. R is a nonsingular upper triangular matrix, and D1 and D2 are ``diagonal'' matrices, which are of the following structures: If M-K-L >= 0, K L D1 = K ( I 0 ) L ( 0 C ) M-K-L ( 0 0 ) K L D2 = L ( 0 S ) P-L ( 0 0 ) N-K-L K L ( 0 R ) = K ( 0 R11 R12 ) K L ( 0 0 R22 ) L where C = diag( ALPHA(K+1), ... , ALPHA(K+L) ), S = diag( BETA(K+1), ... , BETA(K+L) ), C2 + S2 = I. R is stored in A(1:K+L,N-K-L+1:N) on exit. If M-K-L < 0, K M-K K+L-M D1 = K ( I 0 0 ) M-K ( 0 C 0 ) K M-K K+L-M D2 = M-K ( 0 S 0 ) K+L-M ( 0 0 I ) P-L ( 0 0 0 ) N-K-L K M-K K+L-M ( 0 R ) = K ( 0 R11 R12 R13 ) M-K ( 0 0 R22 R23 ) K+L-M ( 0 0 0 R33 ) where C = diag( ALPHA(K+1), ... , ALPHA(M) ), S = diag( BETA(K+1), ... , BETA(M) ), C2 + S*2 = I. R = ( R11 R12 R13 ) is stored in A(1:M, N-K-L+1:N) and R33 is stored ( 0 R22 R23 ) in B(M-K+1:L,N+M-K-L+1:N) on exit. The computation of the unitary transformation matrices U, V or Q is optional. These matrices may either be formed explicitly, or they may be postmultiplied into input matrices U1, V1, or Q1.


Subroutines

public pure subroutine ctgsja(jobu, jobv, jobq, m, p, n, k, l, a, lda, b, ldb, tola, tolb, alpha, beta, u, ldu, v, ldv, q, ldq, work, ncycle, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobu
character(len=1), intent(in) :: jobv
character(len=1), intent(in) :: jobq
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: p
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: k
integer(kind=ilp), intent(in) :: l
complex(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=sp), intent(inout) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=sp), intent(in) :: tola
real(kind=sp), intent(in) :: tolb
real(kind=sp), intent(out) :: alpha(*)
real(kind=sp), intent(out) :: beta(*)
complex(kind=sp), intent(inout) :: u(ldu,*)
integer(kind=ilp), intent(in) :: ldu
complex(kind=sp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
complex(kind=sp), intent(inout) :: q(ldq,*)
integer(kind=ilp), intent(in) :: ldq
complex(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(out) :: ncycle
integer(kind=ilp), intent(out) :: info

public pure subroutine dtgsja(jobu, jobv, jobq, m, p, n, k, l, a, lda, b, ldb, tola, tolb, alpha, beta, u, ldu, v, ldv, q, ldq, work, ncycle, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobu
character(len=1), intent(in) :: jobv
character(len=1), intent(in) :: jobq
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: p
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: k
integer(kind=ilp), intent(in) :: l
real(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=dp), intent(inout) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=dp), intent(in) :: tola
real(kind=dp), intent(in) :: tolb
real(kind=dp), intent(out) :: alpha(*)
real(kind=dp), intent(out) :: beta(*)
real(kind=dp), intent(inout) :: u(ldu,*)
integer(kind=ilp), intent(in) :: ldu
real(kind=dp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
real(kind=dp), intent(inout) :: q(ldq,*)
integer(kind=ilp), intent(in) :: ldq
real(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(out) :: ncycle
integer(kind=ilp), intent(out) :: info

public pure subroutine stgsja(jobu, jobv, jobq, m, p, n, k, l, a, lda, b, ldb, tola, tolb, alpha, beta, u, ldu, v, ldv, q, ldq, work, ncycle, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobu
character(len=1), intent(in) :: jobv
character(len=1), intent(in) :: jobq
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: p
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: k
integer(kind=ilp), intent(in) :: l
real(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=sp), intent(inout) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=sp), intent(in) :: tola
real(kind=sp), intent(in) :: tolb
real(kind=sp), intent(out) :: alpha(*)
real(kind=sp), intent(out) :: beta(*)
real(kind=sp), intent(inout) :: u(ldu,*)
integer(kind=ilp), intent(in) :: ldu
real(kind=sp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
real(kind=sp), intent(inout) :: q(ldq,*)
integer(kind=ilp), intent(in) :: ldq
real(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(out) :: ncycle
integer(kind=ilp), intent(out) :: info

public pure subroutine ztgsja(jobu, jobv, jobq, m, p, n, k, l, a, lda, b, ldb, tola, tolb, alpha, beta, u, ldu, v, ldv, q, ldq, work, ncycle, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobu
character(len=1), intent(in) :: jobv
character(len=1), intent(in) :: jobq
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: p
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: k
integer(kind=ilp), intent(in) :: l
complex(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=dp), intent(inout) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=dp), intent(in) :: tola
real(kind=dp), intent(in) :: tolb
real(kind=dp), intent(out) :: alpha(*)
real(kind=dp), intent(out) :: beta(*)
complex(kind=dp), intent(inout) :: u(ldu,*)
integer(kind=ilp), intent(in) :: ldu
complex(kind=dp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
complex(kind=dp), intent(inout) :: q(ldq,*)
integer(kind=ilp), intent(in) :: ldq
complex(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(out) :: ncycle
integer(kind=ilp), intent(out) :: info

Module Procedures

public interface stdlib_ctgsja()

Arguments

None

public interface stdlib_dtgsja()

Arguments

None

public interface stdlib_stgsja()

Arguments

None

public interface stdlib_ztgsja()

Arguments

None