dggsvp man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

dggsvp(3P)		    Sun Performance Library		    dggsvp(3P)

NAME
       dggsvp  -  compute orthogonal matrices U, V and Q such that   N-K-L K L
       U'*A*Q = K ( 0 A12 A13 ) if M-K-L >= 0

SYNOPSIS
       SUBROUTINE DGGSVP(JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB, TOLA,
	     TOLB, K, L, U, LDU, V, LDV, Q, LDQ, IWORK, TAU, WORK, INFO)

       CHARACTER * 1 JOBU, JOBV, JOBQ
       INTEGER M, P, N, LDA, LDB, K, L, LDU, LDV, LDQ, INFO
       INTEGER IWORK(*)
       DOUBLE PRECISION TOLA, TOLB
       DOUBLE PRECISION	 A(LDA,*),  B(LDB,*),  U(LDU,*),  V(LDV,*),  Q(LDQ,*),
       TAU(*), WORK(*)

       SUBROUTINE DGGSVP_64(JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB, TOLA,
	     TOLB, K, L, U, LDU, V, LDV, Q, LDQ, IWORK, TAU, WORK, INFO)

       CHARACTER * 1 JOBU, JOBV, JOBQ
       INTEGER*8 M, P, N, LDA, LDB, K, L, LDU, LDV, LDQ, INFO
       INTEGER*8 IWORK(*)
       DOUBLE PRECISION TOLA, TOLB
       DOUBLE  PRECISION  A(LDA,*),  B(LDB,*),	U(LDU,*),  V(LDV,*), Q(LDQ,*),
       TAU(*), WORK(*)

   F95 INTERFACE
       SUBROUTINE GGSVP(JOBU, JOBV, JOBQ, [M], [P], [N], A, [LDA], B, [LDB],
	      TOLA, TOLB, K, L, U, [LDU], V, [LDV], Q, [LDQ], [IWORK], [TAU],
	      [WORK], [INFO])

       CHARACTER(LEN=1) :: JOBU, JOBV, JOBQ
       INTEGER :: M, P, N, LDA, LDB, K, L, LDU, LDV, LDQ, INFO
       INTEGER, DIMENSION(:) :: IWORK
       REAL(8) :: TOLA, TOLB
       REAL(8), DIMENSION(:) :: TAU, WORK
       REAL(8), DIMENSION(:,:) :: A, B, U, V, Q

       SUBROUTINE GGSVP_64(JOBU, JOBV, JOBQ, [M], [P], [N], A, [LDA], B,
	      [LDB], TOLA, TOLB, K, L, U, [LDU], V, [LDV], Q, [LDQ], [IWORK],
	      [TAU], [WORK], [INFO])

       CHARACTER(LEN=1) :: JOBU, JOBV, JOBQ
       INTEGER(8) :: M, P, N, LDA, LDB, K, L, LDU, LDV, LDQ, INFO
       INTEGER(8), DIMENSION(:) :: IWORK
       REAL(8) :: TOLA, TOLB
       REAL(8), DIMENSION(:) :: TAU, WORK
       REAL(8), DIMENSION(:,:) :: A, B, U, V, Q

   C INTERFACE
       #include <sunperf.h>

       void dggsvp(char jobu, char jobv, char jobq, int m, int p, int n,  dou‐
		 ble  *a,  int	lda,  double  *b, int ldb, double tola, double
		 tolb, int *k, int *l, double *u, int ldu, double *v, int ldv,
		 double *q, int ldq, int *info);

       void dggsvp_64(char jobu, char jobv, char jobq, long m, long p, long n,
		 double *a, long lda, double *b, long ldb, double tola, double
		 tolb,	long *k, long *l, double *u, long ldu, double *v, long
		 ldv, double *q, long ldq, long *info);

PURPOSE
       dggsvp computes orthogonal matrices U, V and Q such that
		     L ( 0     0   A23 )
		 M-K-L ( 0     0    0  )

			N-K-L  K    L
	       =     K ( 0    A12  A13 )  if M-K-L < 0;
		   M-K ( 0     0   A23 )

		      N-K-L  K	  L
	V'*B*Q =   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.	 K+L = the effective numerical rank of
       the (M+P)-by-N matrix (A',B')'.	Z' denotes the transpose of Z.

       This decomposition is the preprocessing step for computing the General‐
       ized Singular Value Decomposition (GSVD), see subroutine DGGSVD.

ARGUMENTS
       JOBU (input)
		 = 'U':	 Orthogonal matrix U is computed;
		 = 'N':	 U is not computed.

       JOBV (input)
		 = 'V':	 Orthogonal matrix V is computed;
		 = 'N':	 V is not computed.

       JOBQ (input)
		 = 'Q':	 Orthogonal matrix Q is computed;
		 = 'N':	 Q is not computed.

       M (input) The number of rows of the matrix A.  M >= 0.

       P (input) The number of rows of the matrix B.  P >= 0.

       N (input) The number of columns of the matrices A and B.	 N >= 0.

       A (input/output)
		 On entry, the M-by-N matrix A.	 On exit, A contains the  tri‐
		 angular (or trapezoidal) matrix described in the Purpose sec‐
		 tion.

       LDA (input)
		 The leading dimension of the array A. LDA >= max(1,M).

       B (input/output)
		 On entry, the P-by-N matrix B.	 On exit, B contains the  tri‐
		 angular matrix described in the Purpose section.

       LDB (input)
		 The leading dimension of the array B. LDB >= max(1,P).

       TOLA (input)
		 TOLA  and  TOLB are the thresholds to determine the effective
		 numerical rank of matrix B and a subblock  of	A.  Generally,
		 they  are  set	 to  TOLA  =  MAX(M,N)*norm(A)*MACHEPS, TOLB =
		 MAX(P,N)*norm(B)*MACHEPS.  The size  of  TOLA	and  TOLB  may
		 affect the size of backward errors of the decomposition.

       TOLB (input)
		 See the description of TOLA.

       K (output)
		 On  exit,  K  and  L  specify	the dimension of the subblocks
		 described in Purpose.	K + L = effective  numerical  rank  of
		 (A',B')'.

       L (output)
		 See the description of K.

       U (output)
		 If JOBU = 'U', U contains the orthogonal matrix U.  If JOBU =
		 'N', U is not referenced.

       LDU (input)
		 The leading dimension of the array U. LDU >= max(1,M) if JOBU
		 = 'U'; LDU >= 1 otherwise.

       V (output)
		 If JOBV = 'V', V contains the orthogonal matrix V.  If JOBV =
		 'N', V is not referenced.

       LDV (input)
		 The leading dimension of the array V. LDV >= max(1,P) if JOBV
		 = 'V'; LDV >= 1 otherwise.

       Q (output)
		 If JOBQ = 'Q', Q contains the orthogonal matrix Q.  If JOBQ =
		 'N', Q is not referenced.

       LDQ (input)
		 The leading dimension of the array Q. LDQ >= max(1,N) if JOBQ
		 = 'Q'; LDQ >= 1 otherwise.

       IWORK (workspace)
		 dimension(N)

       TAU (workspace)
		 dimension(N)

       WORK (workspace)
		 dimension(MAX(3*N,M,P))

       INFO (output)
		 = 0:  successful exit
		 < 0:  if INFO = -i, the i-th argument had an illegal value.

FURTHER DETAILS
       The  subroutine	uses LAPACK subroutine DGEQPF for the QR factorization
       with column pivoting to detect the effective numerical rank  of	the  a
       matrix. It may be replaced by a better rank determination strategy.

				  6 Mar 2009			    dggsvp(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net