Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

ctrexc (3p)

Name

ctrexc - reorder the Schur factorization of a complex matrix A = Q*T*Q**H, so that the diagonal element of T with row index IFST is moved to row ILST

Synopsis

SUBROUTINE CTREXC(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

CHARACTER*1 COMPQ
COMPLEX T(LDT,*), Q(LDQ,*)
INTEGER N, LDT, LDQ, IFST, ILST, INFO

SUBROUTINE CTREXC_64(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

CHARACTER*1 COMPQ
COMPLEX T(LDT,*), Q(LDQ,*)
INTEGER*8 N, LDT, LDQ, IFST, ILST, INFO




F95 INTERFACE
SUBROUTINE TREXC(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

CHARACTER(LEN=1) :: COMPQ
COMPLEX, DIMENSION(:,:) :: T, Q
INTEGER :: N, LDT, LDQ, IFST, ILST, INFO

SUBROUTINE TREXC_64(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

CHARACTER(LEN=1) :: COMPQ
COMPLEX, DIMENSION(:,:) :: T, Q
INTEGER(8) :: N, LDT, LDQ, IFST, ILST, INFO




C INTERFACE
#include <sunperf.h>

void  ctrexc(char  compq,  int  n, complex *t, int ldt, complex *q, int
ldq, int ifst, int ilst, int *info);

void ctrexc_64(char compq, long n, complex *t, long  ldt,  complex  *q,
long ldq, long ifst, long ilst, long *info);

Description

Oracle Solaris Studio Performance Library                           ctrexc(3P)



NAME
       ctrexc  -  reorder  the  Schur  factorization  of  a complex matrix A =
       Q*T*Q**H, so that the diagonal element of T  with  row  index  IFST  is
       moved to row ILST


SYNOPSIS
       SUBROUTINE CTREXC(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

       CHARACTER*1 COMPQ
       COMPLEX T(LDT,*), Q(LDQ,*)
       INTEGER N, LDT, LDQ, IFST, ILST, INFO

       SUBROUTINE CTREXC_64(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

       CHARACTER*1 COMPQ
       COMPLEX T(LDT,*), Q(LDQ,*)
       INTEGER*8 N, LDT, LDQ, IFST, ILST, INFO




   F95 INTERFACE
       SUBROUTINE TREXC(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

       CHARACTER(LEN=1) :: COMPQ
       COMPLEX, DIMENSION(:,:) :: T, Q
       INTEGER :: N, LDT, LDQ, IFST, ILST, INFO

       SUBROUTINE TREXC_64(COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO)

       CHARACTER(LEN=1) :: COMPQ
       COMPLEX, DIMENSION(:,:) :: T, Q
       INTEGER(8) :: N, LDT, LDQ, IFST, ILST, INFO




   C INTERFACE
       #include <sunperf.h>

       void  ctrexc(char  compq,  int  n, complex *t, int ldt, complex *q, int
                 ldq, int ifst, int ilst, int *info);

       void ctrexc_64(char compq, long n, complex *t, long  ldt,  complex  *q,
                 long ldq, long ifst, long ilst, long *info);



PURPOSE
       ctrexc  reorders  the  Schur  factorization  of  a  complex  matrix A =
       Q*T*Q**H, so that the diagonal element of T  with  row  index  IFST  is
       moved to row ILST.

       The  Schur  form  T is reordered by a unitary similarity transformation
       Z**H*T*Z, and optionally the matrix Q of Schur vectors  is  updated  by
       postmultplying it with Z.


ARGUMENTS
       COMPQ (input)
                 = 'V':  update the matrix Q of Schur vectors;
                 = 'N':  do not update Q.


       N (input) The order of the matrix T. N >= 0.


       T (input/output)
                 On  entry,  the  upper  triangular  matrix  T.   On exit, the
                 reordered upper triangular matrix.


       LDT (input)
                 The leading dimension of the array T. LDT >= max(1,N).


       Q (input) On entry, if COMPQ = 'V', the matrix Q of Schur vectors.   On
                 exit,  if  COMPQ = 'V', Q has been postmultiplied by the uni-
                 tary transformation matrix Z which reorders T.   If  COMPQ  =
                 'N', Q is not referenced.


       LDQ (input)
                 The leading dimension of the array Q.  LDQ >= max(1,N).


       IFST (input)
                 Specify  the  reordering  of  the diagonal elements of T: The
                 element with row index  IFST  is  moved  to  row  ILST  by  a
                 sequence  of  transpositions between adjacent elements.  1 <=
                 IFST <= N; 1 <= ILST <= N.


       ILST (input)
                 See the description of IFST.


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




                                  7 Nov 2015                        ctrexc(3P)