Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zuncsd (3p)

Name

zuncsd - M partitioned unitary matrix

Synopsis

RECURSIVE SUBROUTINE ZUNCSD(JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS, SIGNS,
M,  P,  Q,  X11,  LDX11,  X12, LDX12, X21, LDX21, X22, LDX22,
THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,  WORK,
LWORK, RWORK, LRWORK, IWORK, INFO)


CHARACTER*1 JOBU1, JOBU2, JOBV1T, JOBV2T, SIGNS, TRANS

INTEGER  INFO,  LDU1,  LDU2,  LDV1T, LDV2T, LDX11, LDX12, LDX21, LDX22,
LRWORK, LWORK, M, P, Q

INTEGER IWORK(*)

DOUBLE PRECISION THETA(*), RWORK(*)

DOUBLE  COMPLEX  U1(LDU1,*),  U2(LDU2,*),  V1T(LDV1T,*),  V2T(LDV2T,*),
WORK(*),     X11(LDX11,*),     X12(LDX12,*),    X21(LDX21,*),
X22(LDX22,*)


RECURSIVE SUBROUTINE ZUNCSD_64(JOBU1,  JOBU2,  JOBV1T,  JOBV2T,  TRANS,
SIGNS,  M,  P,  Q,  X11,  LDX11, X12, LDX12, X21, LDX21, X22,
LDX22, THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,
WORK, LWORK, RWORK, LRWORK, IWORK, INFO)


CHARACTER*1 JOBU1, JOBU2, JOBV1T, JOBV2T, SIGNS, TRANS

INTEGER*8  INFO,  LDU1, LDU2, LDV1T, LDV2T, LDX11, LDX12, LDX21, LDX22,
LRWORK, LWORK, M, P, Q

INTEGER*8 IWORK(*)

DOUBLE PRECISION THETA(*), RWORK(*)

DOUBLE  COMPLEX  U1(LDU1,*),  U2(LDU2,*),  V1T(LDV1T,*),  V2T(LDV2T,*),
WORK(*), X11(LDX11,*), X12(LDX12,*), X21(LDX21,*), X22(LDX22,
*)


F95 INTERFACE
RECURSIVE SUBROUTINE UNCSD(JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS,  SIGNS,
M,  P,  Q,  X11,  LDX11,  X12, LDX12, X21, LDX21, X22, LDX22,
THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,  WORK,
LWORK, RWORK, LRWORK, IWORK, INFO)


INTEGER  ::  M,  P,  Q,  LDX11, LDX12, LDX21, LDX22, LDU1, LDU2, LDV1T,
LDV2T, LWORK, LRWORK, INFO

CHARACTER(LEN=1) :: JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS, SIGNS

INTEGER, DIMENSION(:) :: IWORK

COMPLEX(8), DIMENSION(:) :: WORK

REAL(8), DIMENSION(:) :: THETA, RWORK

COMPLEX(8), DIMENSION(:,:) :: X11, X12, X21, X22, U1, U2, V1T, V2T


RECURSIVE SUBROUTINE  UNCSD_64(JOBU1,  JOBU2,  JOBV1T,  JOBV2T,  TRANS,
SIGNS,  M,  P,  Q,  X11,  LDX11, X12, LDX12, X21, LDX21, X22,
LDX22, THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,
WORK, LWORK, RWORK, LRWORK, IWORK, INFO)


INTEGER(8)  ::  M, P, Q, LDX11, LDX12, LDX21, LDX22, LDU1, LDU2, LDV1T,
LDV2T, LWORK, LRWORK, INFO

CHARACTER(LEN=1) :: JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS, SIGNS

INTEGER(8), DIMENSION(:) :: IWORK

COMPLEX(8), DIMENSION(:) :: WORK

REAL(8), DIMENSION(:) :: THETA, RWORK

COMPLEX(8), DIMENSION(:,:) :: X11, X12, X21, X22, U1, U2, V1T, V2T


C INTERFACE
#include <sunperf.h>

void zuncsd (char jobu1, char jobu2, char  jobv1t,  char  jobv2t,  char
trans,  char  signs, int m, int p, int q, doublecomplex *x11,
int ldx11, doublecomplex *x12, int ldx12, doublecomplex *x21,
int ldx21, doublecomplex *x22, int ldx22, double *theta, dou-
blecomplex *u1, int ldu1, doublecomplex *u2, int  ldu2,  dou-
blecomplex  *v1t,  int  ldv1t, doublecomplex *v2t, int ldv2t,
double *rwork, int lrwork, int *iwork, int *info);


void zuncsd_64 (char jobu1, char jobu2, char jobv1t, char jobv2t,  char
trans,  char  signs,  long  m,  long p, long q, doublecomplex
*x11, long ldx11, doublecomplex *x12, long ldx12,  doublecom-
plex *x21, long ldx21, doublecomplex *x22, long ldx22, double
*theta, doublecomplex *u1, long ldu1, doublecomplex *u2, long
ldu2,  doublecomplex  *v1t,  long  ldv1t, doublecomplex *v2t,
long ldv2t, double *rwork, long  lrwork,  long  *iwork,  long
*info);

Description

Oracle Solaris Studio Performance Library                           zuncsd(3P)



NAME
       zuncsd  - compute the CS decomposition of an M-by-M partitioned unitary
       matrix

SYNOPSIS
       RECURSIVE SUBROUTINE ZUNCSD(JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS, SIGNS,
                 M,  P,  Q,  X11,  LDX11,  X12, LDX12, X21, LDX21, X22, LDX22,
                 THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,  WORK,
                 LWORK, RWORK, LRWORK, IWORK, INFO)


       CHARACTER*1 JOBU1, JOBU2, JOBV1T, JOBV2T, SIGNS, TRANS

       INTEGER  INFO,  LDU1,  LDU2,  LDV1T, LDV2T, LDX11, LDX12, LDX21, LDX22,
                 LRWORK, LWORK, M, P, Q

       INTEGER IWORK(*)

       DOUBLE PRECISION THETA(*), RWORK(*)

       DOUBLE  COMPLEX  U1(LDU1,*),  U2(LDU2,*),  V1T(LDV1T,*),  V2T(LDV2T,*),
                 WORK(*),     X11(LDX11,*),     X12(LDX12,*),    X21(LDX21,*),
                 X22(LDX22,*)


       RECURSIVE SUBROUTINE ZUNCSD_64(JOBU1,  JOBU2,  JOBV1T,  JOBV2T,  TRANS,
                 SIGNS,  M,  P,  Q,  X11,  LDX11, X12, LDX12, X21, LDX21, X22,
                 LDX22, THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,
                 WORK, LWORK, RWORK, LRWORK, IWORK, INFO)


       CHARACTER*1 JOBU1, JOBU2, JOBV1T, JOBV2T, SIGNS, TRANS

       INTEGER*8  INFO,  LDU1, LDU2, LDV1T, LDV2T, LDX11, LDX12, LDX21, LDX22,
                 LRWORK, LWORK, M, P, Q

       INTEGER*8 IWORK(*)

       DOUBLE PRECISION THETA(*), RWORK(*)

       DOUBLE  COMPLEX  U1(LDU1,*),  U2(LDU2,*),  V1T(LDV1T,*),  V2T(LDV2T,*),
                 WORK(*), X11(LDX11,*), X12(LDX12,*), X21(LDX21,*), X22(LDX22,
                 *)


   F95 INTERFACE
       RECURSIVE SUBROUTINE UNCSD(JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS,  SIGNS,
                 M,  P,  Q,  X11,  LDX11,  X12, LDX12, X21, LDX21, X22, LDX22,
                 THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,  WORK,
                 LWORK, RWORK, LRWORK, IWORK, INFO)


       INTEGER  ::  M,  P,  Q,  LDX11, LDX12, LDX21, LDX22, LDU1, LDU2, LDV1T,
                 LDV2T, LWORK, LRWORK, INFO

       CHARACTER(LEN=1) :: JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS, SIGNS

       INTEGER, DIMENSION(:) :: IWORK

       COMPLEX(8), DIMENSION(:) :: WORK

       REAL(8), DIMENSION(:) :: THETA, RWORK

       COMPLEX(8), DIMENSION(:,:) :: X11, X12, X21, X22, U1, U2, V1T, V2T


       RECURSIVE SUBROUTINE  UNCSD_64(JOBU1,  JOBU2,  JOBV1T,  JOBV2T,  TRANS,
                 SIGNS,  M,  P,  Q,  X11,  LDX11, X12, LDX12, X21, LDX21, X22,
                 LDX22, THETA, U1, LDU1, U2, LDU2,  V1T,  LDV1T,  V2T,  LDV2T,
                 WORK, LWORK, RWORK, LRWORK, IWORK, INFO)


       INTEGER(8)  ::  M, P, Q, LDX11, LDX12, LDX21, LDX22, LDU1, LDU2, LDV1T,
                 LDV2T, LWORK, LRWORK, INFO

       CHARACTER(LEN=1) :: JOBU1, JOBU2, JOBV1T, JOBV2T, TRANS, SIGNS

       INTEGER(8), DIMENSION(:) :: IWORK

       COMPLEX(8), DIMENSION(:) :: WORK

       REAL(8), DIMENSION(:) :: THETA, RWORK

       COMPLEX(8), DIMENSION(:,:) :: X11, X12, X21, X22, U1, U2, V1T, V2T


   C INTERFACE
       #include <sunperf.h>

       void zuncsd (char jobu1, char jobu2, char  jobv1t,  char  jobv2t,  char
                 trans,  char  signs, int m, int p, int q, doublecomplex *x11,
                 int ldx11, doublecomplex *x12, int ldx12, doublecomplex *x21,
                 int ldx21, doublecomplex *x22, int ldx22, double *theta, dou-
                 blecomplex *u1, int ldu1, doublecomplex *u2, int  ldu2,  dou-
                 blecomplex  *v1t,  int  ldv1t, doublecomplex *v2t, int ldv2t,
                 double *rwork, int lrwork, int *iwork, int *info);


       void zuncsd_64 (char jobu1, char jobu2, char jobv1t, char jobv2t,  char
                 trans,  char  signs,  long  m,  long p, long q, doublecomplex
                 *x11, long ldx11, doublecomplex *x12, long ldx12,  doublecom-
                 plex *x21, long ldx21, doublecomplex *x22, long ldx22, double
                 *theta, doublecomplex *u1, long ldu1, doublecomplex *u2, long
                 ldu2,  doublecomplex  *v1t,  long  ldv1t, doublecomplex *v2t,
                 long ldv2t, double *rwork, long  lrwork,  long  *iwork,  long
                 *info);


PURPOSE
       zuncsd  computes  the CS decomposition of an M-by-M partitioned unitary
       matrix X:

                                       [  I  0  0 |  0  0  0 ]
                                       [  0  C  0 |  0 -S  0 ]
           [ X11 | X12 ]   [ U1 |    ] [  0  0  0 |  0  0 -I ] [ V1 |    ]**H
       X = [-----------] = [---------] [---------------------] [---------]   .
           [ X21 | X22 ]   [    | U2 ] [  0  0  0 |  I  0  0 ] [    | V2 ]
                                       [  0  S  0 |  0  C  0 ]
                                       [  0  0  I |  0  0  0 ]


   X11 is P-by-Q. The unitary matrices U1, U2, V1, and V2 are P-by-P,
       (M-P)-by-(M-P), Q-by-Q, and (M-Q)-by-(M-Q), respectively. C and  S  are
       R-by-R nonnegative diagonal matrices satisfying C^2 + S^2 = I, in which
       R = MIN(P,M-P,Q,M-Q).


ARGUMENTS
       JOBU1 (input)
                 JOBU1 is CHARACTER
                 = 'Y':      U1 is computed;
                 otherwise:  U1 is not computed.


       JOBU2 (input)
                 JOBU2 is CHARACTER
                 = 'Y':      U2 is computed;
                 otherwise:  U2 is not computed.


       JOBV1T (input)
                 JOBV1T is CHARACTER
                 = 'Y':      V1T is computed;
                 otherwise:  V1T is not computed.


       JOBV2T (input)
                 JOBV2T is CHARACTER
                 = 'Y':      V2T is computed;
                 otherwise:  V2T is not computed.


       TRANS (input)
                 TRANS is CHARACTER
                 = 'T': X, U1, U2, V1T, and V2T are stored in row-major order;
                 otherwise:  X,  U1,  U2,  V1T,  and V2T are stored in column-
                 major order.


       SIGNS (input)
                 SIGNS is CHARACTER
                 = 'O': The lower-left block is made nonpositive (the  "other"
                 convention);
                 otherwise:  The  upper-right  block  is made nonpositive (the
                 "default" convention).


       M (input)
                 M is INTEGER
                 The number of rows and columns in X.


       P (input)
                 P is INTEGER
                 The number of rows in X11 and X12. 0 <= P <= M.


       Q (input)
                 Q is INTEGER
                 The number of columns in X11 and X21. 0 <= Q <= M.


       X11 (input/output)
                 X11 is COMPLEX*16 array, dimension (LDX11,Q)
                 On entry, part of the unitary matrix whose CSD is desired.


       LDX11 (input)
                 LDX11 is INTEGER
                 The leading dimension of X11. LDX11 >= MAX(1,P).


       X12 (input/output)
                 X12 is COMPLEX*16 array, dimension (LDX12,M-Q)
                 On entry, part of the unitary matrix whose CSD is desired.


       LDX12 (input)
                 LDX12 is INTEGER
                 The leading dimension of X12. LDX12 >= MAX(1,P).


       X21 (input/output)
                 X21 is COMPLEX*16 array, dimension (LDX21,Q)
                 On entry, part of the unitary matrix whose CSD is desired.


       LDX21 (input)
                 LDX21 is INTEGER
                 The leading dimension of X11. LDX21 >= MAX(1,M-P).


       X22 (input/output)
                 X22 is COMPLEX*16 array, dimension (LDX22,M-Q)
                 On entry, part of the unitary matrix whose CSD is desired.


       LDX22 (input)
                 LDX22 is INTEGER
                 The leading dimension of X11. LDX22 >= MAX(1,M-P).


       THETA (output)
                 THETA is DOUBLE PRECISION array, dimension (R), in which R  =
                 MIN(P,M-P,Q,M-Q).
                 C = DIAG( COS(THETA(1)), ... , COS(THETA(R)) ) and
                 S = DIAG( SIN(THETA(1)), ... , SIN(THETA(R)) ).


       U1 (output)
                 U1 is COMPLEX*16 array, dimension (P)
                 If JOBU1 = 'Y', U1 contains the P-by-P unitary matrix U1.


       LDU1 (input)
                 LDU1 is INTEGER
                 The  leading  dimension  of  U1.  If  JOBU1  =  'Y',  LDU1 >=
                 MAX(1,P).


       U2 (output)
                 U2 is COMPLEX*16 array, dimension (M-P)
                 If JOBU2 = 'Y', U2 contains the (M-P)-by-(M-P) unitary matrix
                 U2.


       LDU2 (input)
                 LDU2 is INTEGER
                 The leading dimension of U2. If JOBU2 = 'Y', LDU2 >= MAX(1,M-
                 P).


       V1T (output)
                 V1T is COMPLEX*16 array, dimension (Q)
                 If JOBV1T = 'Y',  V1T  contains  the  Q-by-Q  matrix  unitary
                 matrix V1**H.


       LDV1T (input)
                 LDV1T is INTEGER
                 The  leading  dimension  of  V1T.  If  JOBV1T = 'Y', LDV1T >=
                 MAX(1,Q).


       V2T (output)
                 V2T is COMPLEX*16 array, dimension (M-Q)
                 If JOBV2T = 'Y',  V2T  contains  the  (M-Q)-by-(M-Q)  unitary
                 matrix V2**H.


       LDV2T (input)
                 LDV2T is INTEGER
                 The leading dimension of V2T. If JOBV2T = 'Y', LDV2T >=
                 MAX(1,M-Q).


       WORK (output)
                 WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
                 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.


       LWORK (input)
                 LWORK is INTEGER
                 The dimension of the array WORK.
                 If LWORK = -1, then a workspace query is assumed; the routine
                 only calculates the optimal size of the WORK  array,  returns
                 this value as the first entry of the work array, and no error
                 message related to LWORK is issued by XERBLA.


       RWORK (output)
                 RWORK is DOUBLE PRECISION array, dimension MAX(1,LRWORK)
                 On exit, if INFO = 0, RWORK(1) returns  the  optimal  LRWORK.
                 If  INFO  > 0 on exit, RWORK(2:R) contains the values PHI(1),
                 define  the  matrix  in  intermediate  bidiagonal-block  form
                 remaining  after nonconvergence. INFO specifies the number of
                 nonzero PHI's.


       LRWORK (input)
                 LRWORK is INTEGER
                 The dimension of the array RWORK.
                 If LRWORK = -1, then a workspace query is assumed;  the  rou-
                 tine  only  calculates  the  optimal size of the RWORK array,
                 returns this value as the first entry of the work array,  and
                 no error message related to LRWORK is issued by XERBLA.


       IWORK (output)
                 IWORK is INTEGER array, dimension (M-MIN(P,M-P,Q,M-Q))


       INFO (output)
                 INFO is INTEGER
                 = 0:  successful exit;
                 < 0:  if INFO = -i, the i-th argument had an illegal value;
                 >  0:   ZBBCSD did not converge. See the description of RWORK
                 above for details.



                                  7 Nov 2015                        zuncsd(3P)