Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgesv (3p)

Name

cgesv - compute the solution to a complex system of linear equations A*X=B, where A is an N-by-N matrix and X and B are N-by-NRHS matrices

Synopsis

SUBROUTINE CGESV(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

COMPLEX A(LDA,*), B(LDB,*)
INTEGER N, NRHS, LDA, LDB, INFO
INTEGER IPIVOT(*)

SUBROUTINE CGESV_64(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

COMPLEX A(LDA,*), B(LDB,*)
INTEGER*8 N, NRHS, LDA, LDB, INFO
INTEGER*8 IPIVOT(*)




F95 INTERFACE
SUBROUTINE GESV(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

COMPLEX, DIMENSION(:,:) :: A, B
INTEGER :: N, NRHS, LDA, LDB, INFO
INTEGER, DIMENSION(:) :: IPIVOT

SUBROUTINE GESV_64(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

COMPLEX, DIMENSION(:,:) :: A, B
INTEGER(8) :: N, NRHS, LDA, LDB, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT




C INTERFACE
#include <sunperf.h>

void cgesv(int n, int nrhs, complex *a, int lda, int  *ipivot,  complex
*b, int ldb, int *info);

void  cgesv_64(long  n,  long nrhs, complex *a, long lda, long *ipivot,
complex *b, long ldb, long *info);

Description

Oracle Solaris Studio Performance Library                            cgesv(3P)



NAME
       cgesv  -  compute  the solution to a complex system of linear equations
       A*X=B, where A is an N-by-N matrix and X and B are N-by-NRHS matrices


SYNOPSIS
       SUBROUTINE CGESV(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

       COMPLEX A(LDA,*), B(LDB,*)
       INTEGER N, NRHS, LDA, LDB, INFO
       INTEGER IPIVOT(*)

       SUBROUTINE CGESV_64(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

       COMPLEX A(LDA,*), B(LDB,*)
       INTEGER*8 N, NRHS, LDA, LDB, INFO
       INTEGER*8 IPIVOT(*)




   F95 INTERFACE
       SUBROUTINE GESV(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

       COMPLEX, DIMENSION(:,:) :: A, B
       INTEGER :: N, NRHS, LDA, LDB, INFO
       INTEGER, DIMENSION(:) :: IPIVOT

       SUBROUTINE GESV_64(N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)

       COMPLEX, DIMENSION(:,:) :: A, B
       INTEGER(8) :: N, NRHS, LDA, LDB, INFO
       INTEGER(8), DIMENSION(:) :: IPIVOT




   C INTERFACE
       #include <sunperf.h>

       void cgesv(int n, int nrhs, complex *a, int lda, int  *ipivot,  complex
                 *b, int ldb, int *info);

       void  cgesv_64(long  n,  long nrhs, complex *a, long lda, long *ipivot,
                 complex *b, long ldb, long *info);



PURPOSE
       cgesv computes the solution to a complex system of linear equations
          A * X = B, where A is an N-by-N matrix and X  and  B  are  N-by-NRHS
       matrices.

       The LU decomposition with partial pivoting and row interchanges is used
       to factor A as
          A = P * L * U,
       where P is a permutation matrix, L is unit lower triangular, and  U  is
       upper  triangular.   The  factored  form of A is then used to solve the
       system of equations A * X = B.


ARGUMENTS
       N (input) The number of linear equations, i.e., the order of the matrix
                 A.  N >= 0.


       NRHS (input)
                 The  number  of right hand sides, i.e., the number of columns
                 of the matrix B.  NRHS >= 0.


       A (input/output)
                 On entry, the N-by-N coefficient matrix A.  On exit, the fac-
                 tors L and U from the factorization A = P*L*U; the unit diag-
                 onal elements of L are not stored.


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


       IPIVOT (output)
                 The pivot indices that define the permutation matrix P; row i
                 of the matrix was interchanged with row IPIVOT(i).


       B (input/output)
                 On  entry,  the N-by-NRHS matrix of right hand side matrix B.
                 On exit, if INFO = 0, the N-by-NRHS solution matrix X.


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


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  if INFO = i, U(i,i) is exactly zero.  The factorization
                 has  been completed, but the factor U is exactly singular, so
                 the solution could not be computed.



                                  7 Nov 2015                         cgesv(3P)