Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

strexc (3p)

Name

strexc - reorder the real Schur factorization of a real matrix A = Q*T*Q**T, so that the diagonal block of T with row index IFST is moved to row ILST

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           strexc(3P)



NAME
       strexc  -  reorder  the  real  Schur factorization of a real matrix A =
       Q*T*Q**T, so that the diagonal block of T with row index IFST is  moved
       to row ILST


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       strexc  reorders  the  real  Schur  factorization  of a real matrix A =
       Q*T*Q**T, so that the diagonal block of T with row index IFST is  moved
       to row ILST.

       The  real  Schur form T is reordered by an orthogonal similarity trans-
       formation Z**T*T*Z, and optionally the matrix Q  of  Schur  vectors  is
       updated by postmultiplying it with Z.

       T  must  be  in  Schur canonical form (as returned by SHSEQR), that is,
       block upper triangular with 1-by-1 and  2-by-2  diagonal  blocks;  each
       2-by-2 diagonal block has its diagonal elements equal and its off-diag-
       onal elements of opposite sign.


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 quasi-triangular matrix T, in Schur Schur
                 canonical  form.  On exit, the reordered upper quasi-triangu-
                 lar matrix, again in Schur canonical form.


       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
                 orthogonal 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/output)
                 Specify  the  reordering  of  the  diagonal blocks of T.  The
                 block with row index IFST is moved to row ILST, by a sequence
                 of  transpositions between adjacent blocks.  On exit, if IFST
                 pointed on entry to the second row of a 2-by-2 block,  it  is
                 changed  to point to the first row; ILST always points to the
                 first row of the block in its final position (which may  dif-
                 fer  from its input value by +1 or -1).  1 <= IFST <= N; 1 <=
                 ILST <= N.


       ILST (input/output)
                 See the description of IFST.


       WORK (workspace)
                 dimension(N)

       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 = 1:  two adjacent blocks were too close to swap (the problem
                 is   very   ill-conditioned);   T  may  have  been  partially
                 reordered, and ILST points to the first row  of  the  current
                 position of the block being moved.




                                  7 Nov 2015                        strexc(3P)