sgetrs - solve a system of linear equations A * X = B or A' * X = B with a general N-by-N matrix A using the LU factorization computed by SGETRF
SUBROUTINE SGETRS(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER*1 TRANSA INTEGER N, NRHS, LDA, LDB, INFO INTEGER IPIVOT(*) REAL A(LDA,*), B(LDB,*) SUBROUTINE SGETRS_64(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER*1 TRANSA INTEGER*8 N, NRHS, LDA, LDB, INFO INTEGER*8 IPIVOT(*) REAL A(LDA,*), B(LDB,*) F95 INTERFACE SUBROUTINE GETRS(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER(LEN=1) :: TRANSA INTEGER :: N, NRHS, LDA, LDB, INFO INTEGER, DIMENSION(:) :: IPIVOT REAL, DIMENSION(:,:) :: A, B SUBROUTINE GETRS_64(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB, INFO) CHARACTER(LEN=1) :: TRANSA INTEGER(8) :: N, NRHS, LDA, LDB, INFO INTEGER(8), DIMENSION(:) :: IPIVOT REAL, DIMENSION(:,:) :: A, B C INTERFACE #include <sunperf.h> void sgetrs(char transa, int n, int nrhs, float *a, int lda, int *ipivot, float *b, int ldb, int *info); void sgetrs_64(char transa, long n, long nrhs, float *a, long lda, long *ipivot, float *b, long ldb, long *info);
Oracle Solaris Studio Performance Library sgetrs(3P)
NAME
sgetrs - solve a system of linear equations A * X = B or A' * X = B
with a general N-by-N matrix A using the LU factorization computed by
SGETRF
SYNOPSIS
SUBROUTINE SGETRS(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)
CHARACTER*1 TRANSA
INTEGER N, NRHS, LDA, LDB, INFO
INTEGER IPIVOT(*)
REAL A(LDA,*), B(LDB,*)
SUBROUTINE SGETRS_64(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB, INFO)
CHARACTER*1 TRANSA
INTEGER*8 N, NRHS, LDA, LDB, INFO
INTEGER*8 IPIVOT(*)
REAL A(LDA,*), B(LDB,*)
F95 INTERFACE
SUBROUTINE GETRS(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB,
INFO)
CHARACTER(LEN=1) :: TRANSA
INTEGER :: N, NRHS, LDA, LDB, INFO
INTEGER, DIMENSION(:) :: IPIVOT
REAL, DIMENSION(:,:) :: A, B
SUBROUTINE GETRS_64(TRANSA, N, NRHS, A, LDA, IPIVOT, B, LDB,
INFO)
CHARACTER(LEN=1) :: TRANSA
INTEGER(8) :: N, NRHS, LDA, LDB, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
REAL, DIMENSION(:,:) :: A, B
C INTERFACE
#include <sunperf.h>
void sgetrs(char transa, int n, int nrhs, float *a, int lda, int
*ipivot, float *b, int ldb, int *info);
void sgetrs_64(char transa, long n, long nrhs, float *a, long lda, long
*ipivot, float *b, long ldb, long *info);
PURPOSE
sgetrs solves a system of linear equations
A * X = B or A' * X = B with a general N-by-N matrix A using the
LU factorization computed by SGETRF.
ARGUMENTS
TRANSA (input)
Specifies the form of the system of equations:
= 'N': A * X = B (No transpose)
= 'T': A'* X = B (Transpose)
= 'C': A'* X = B (Conjugate transpose = Transpose)
N (input) 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) The factors L and U from the factorization A = P*L*U as com-
puted by SGETRF.
LDA (input)
The leading dimension of the array A. LDA >= max(1,N).
IPIVOT (input)
The pivot indices from SGETRF; for 1<=i<=N, row i of the
matrix was interchanged with row IPIVOT(i).
B (input/output)
On entry, the right hand side matrix B. On exit, the solu-
tion 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
7 Nov 2015 sgetrs(3P)