Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgebak (3p)

Name

zgebak - form the right or left eigenvectors of a complex general matrix by backward transformation on the computed eigenvectors of the balanced matrix output by ZGEBAL

Synopsis

SUBROUTINE ZGEBAK(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV, INFO)

CHARACTER*1 JOB, SIDE
DOUBLE COMPLEX V(LDV,*)
INTEGER N, ILO, IHI, M, LDV, INFO
DOUBLE PRECISION SCALE(*)

SUBROUTINE ZGEBAK_64(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV, INFO)

CHARACTER*1 JOB, SIDE
DOUBLE COMPLEX V(LDV,*)
INTEGER*8 N, ILO, IHI, M, LDV, INFO
DOUBLE PRECISION SCALE(*)




F95 INTERFACE
SUBROUTINE GEBAK(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
INFO)

CHARACTER(LEN=1) :: JOB, SIDE
COMPLEX(8), DIMENSION(:,:) :: V
INTEGER :: N, ILO, IHI, M, LDV, INFO
REAL(8), DIMENSION(:) :: SCALE

SUBROUTINE GEBAK_64(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
INFO)

CHARACTER(LEN=1) :: JOB, SIDE
COMPLEX(8), DIMENSION(:,:) :: V
INTEGER(8) :: N, ILO, IHI, M, LDV, INFO
REAL(8), DIMENSION(:) :: SCALE




C INTERFACE
#include <sunperf.h>

void  zgebak(char  job,  char  side,  int  n,  int ilo, int ihi, double
*scale, int m, doublecomplex *v, int ldv, int *info);

void zgebak_64(char job, char side, long n, long ilo, long ihi,  double
*scale, long m, doublecomplex *v, long ldv, long *info);

Description

Oracle Solaris Studio Performance Library                           zgebak(3P)



NAME
       zgebak  -  form  the  right  or  left eigenvectors of a complex general
       matrix by backward transformation on the computed eigenvectors  of  the
       balanced matrix output by ZGEBAL


SYNOPSIS
       SUBROUTINE ZGEBAK(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV, INFO)

       CHARACTER*1 JOB, SIDE
       DOUBLE COMPLEX V(LDV,*)
       INTEGER N, ILO, IHI, M, LDV, INFO
       DOUBLE PRECISION SCALE(*)

       SUBROUTINE ZGEBAK_64(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV, INFO)

       CHARACTER*1 JOB, SIDE
       DOUBLE COMPLEX V(LDV,*)
       INTEGER*8 N, ILO, IHI, M, LDV, INFO
       DOUBLE PRECISION SCALE(*)




   F95 INTERFACE
       SUBROUTINE GEBAK(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
              INFO)

       CHARACTER(LEN=1) :: JOB, SIDE
       COMPLEX(8), DIMENSION(:,:) :: V
       INTEGER :: N, ILO, IHI, M, LDV, INFO
       REAL(8), DIMENSION(:) :: SCALE

       SUBROUTINE GEBAK_64(JOB, SIDE, N, ILO, IHI, SCALE, M, V, LDV,
              INFO)

       CHARACTER(LEN=1) :: JOB, SIDE
       COMPLEX(8), DIMENSION(:,:) :: V
       INTEGER(8) :: N, ILO, IHI, M, LDV, INFO
       REAL(8), DIMENSION(:) :: SCALE




   C INTERFACE
       #include <sunperf.h>

       void  zgebak(char  job,  char  side,  int  n,  int ilo, int ihi, double
                 *scale, int m, doublecomplex *v, int ldv, int *info);

       void zgebak_64(char job, char side, long n, long ilo, long ihi,  double
                 *scale, long m, doublecomplex *v, long ldv, long *info);



PURPOSE
       zgebak forms the right or left eigenvectors of a complex general matrix
       by backward transformation on the computed eigenvectors of the balanced
       matrix output by ZGEBAL.


ARGUMENTS
       JOB (input)
                 Specifies  the  type  of  backward transformation required: =
                 'N', do nothing,  return  immediately;  =  'P',  do  backward
                 transformation  for  permutation  only;  =  'S',  do backward
                 transformation for scaling only; = 'B', do backward transfor-
                 mations  for  both  permutation and scaling.  JOB must be the
                 same as the argument JOB supplied to ZGEBAL.


       SIDE (input)
                 = 'R':  V contains right eigenvectors;
                 = 'L':  V contains left eigenvectors.


       N (input) The number of rows of the matrix V.  N >= 0.


       ILO (input)
                 The integer ILO determined by ZGEBAL.  1 <= ILO <= IHI <=  N,
                 if N > 0; ILO=1 and IHI=0, if N=0.


       IHI (input)
                 The  integer IHI determined by ZGEBAL.  1 <= ILO <= IHI <= N,
                 if N > 0; ILO=1 and IHI=0, if N=0.


       SCALE (input)
                 Details of the permutation and scaling factors,  as  returned
                 by ZGEBAL.


       M (input) The number of columns of the matrix V.  M >= 0.


       V (input/output)
                 On  entry,  the  matrix  of  right or left eigenvectors to be
                 transformed, as returned by CHSEIN or CTREVC.  On exit, V  is
                 overwritten by the transformed eigenvectors.


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


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




                                  7 Nov 2015                        zgebak(3P)