zgttrf - compute an LU factorization of a complex tridiagonal matrix A using elimination with partial pivoting and row interchanges
SUBROUTINE ZGTTRF(N, LOW, D, UP1, UP2, IPIVOT, INFO) DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*) INTEGER N, INFO INTEGER IPIVOT(*) SUBROUTINE ZGTTRF_64(N, LOW, D, UP1, UP2, IPIVOT, INFO) DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*) INTEGER*8 N, INFO INTEGER*8 IPIVOT(*) F95 INTERFACE SUBROUTINE GTTRF(N, LOW, D, UP1, UP2, IPIVOT, INFO) COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2 INTEGER :: N, INFO INTEGER, DIMENSION(:) :: IPIVOT SUBROUTINE GTTRF_64(N, LOW, D, UP1, UP2, IPIVOT, INFO) COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2 INTEGER(8) :: N, INFO INTEGER(8), DIMENSION(:) :: IPIVOT C INTERFACE #include <sunperf.h> void zgttrf(int n, doublecomplex *low, doublecomplex *d, doublecomplex *up1, doublecomplex *up2, int *ipivot, int *info); void zgttrf_64(long n, doublecomplex *low, doublecomplex *d, doublecom- plex *up1, doublecomplex *up2, long *ipivot, long *info);
Oracle Solaris Studio Performance Library zgttrf(3P)
NAME
zgttrf - compute an LU factorization of a complex tridiagonal matrix A
using elimination with partial pivoting and row interchanges
SYNOPSIS
SUBROUTINE ZGTTRF(N, LOW, D, UP1, UP2, IPIVOT, INFO)
DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*)
INTEGER N, INFO
INTEGER IPIVOT(*)
SUBROUTINE ZGTTRF_64(N, LOW, D, UP1, UP2, IPIVOT, INFO)
DOUBLE COMPLEX LOW(*), D(*), UP1(*), UP2(*)
INTEGER*8 N, INFO
INTEGER*8 IPIVOT(*)
F95 INTERFACE
SUBROUTINE GTTRF(N, LOW, D, UP1, UP2, IPIVOT, INFO)
COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2
INTEGER :: N, INFO
INTEGER, DIMENSION(:) :: IPIVOT
SUBROUTINE GTTRF_64(N, LOW, D, UP1, UP2, IPIVOT, INFO)
COMPLEX(8), DIMENSION(:) :: LOW, D, UP1, UP2
INTEGER(8) :: N, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
C INTERFACE
#include <sunperf.h>
void zgttrf(int n, doublecomplex *low, doublecomplex *d, doublecomplex
*up1, doublecomplex *up2, int *ipivot, int *info);
void zgttrf_64(long n, doublecomplex *low, doublecomplex *d, doublecom-
plex *up1, doublecomplex *up2, long *ipivot, long *info);
PURPOSE
zgttrf computes an LU factorization of a complex tridiagonal matrix A
using elimination with partial pivoting and row interchanges.
The factorization has the form
A = L * U
where L is a product of permutation and unit lower bidiagonal matrices
and U is upper triangular with nonzeros in only the main diagonal and
first two superdiagonals.
ARGUMENTS
N (input) The order of the matrix A.
LOW (input/output)
On entry, LOW must contain the (n-1) sub-diagonal elements of
A.
On exit, LOW is overwritten by the (n-1) multipliers that
define the matrix L from the LU factorization of A.
D (input/output)
On entry, D must contain the diagonal elements of A.
On exit, D is overwritten by the n diagonal elements of the
upper triangular matrix U from the LU factorization of A.
UP1 (input/output)
On entry, UP1 must contain the (n-1) super-diagonal elements
of A.
On exit, UP1 is overwritten by the (n-1) elements of the
first super-diagonal of U.
UP2 (output)
On exit, UP2 is overwritten by the (n-2) elements of the sec-
ond super-diagonal of U.
IPIVOT (output)
The pivot indices; for 1 <= i <= n, row i of the matrix was
interchanged with row IPIVOT(i). IPIVOT(i) will always be
either i or i+1; IPIVOT(i) = i indicates a row interchange
was not required.
INFO (output)
= 0: successful exit
< 0: if INFO = -k, the k-th argument had an illegal value
> 0: if INFO = k, U(k,k) is exactly zero. The factorization
has been completed, but the factor U is exactly singular, and
division by zero will occur if it is used to solve a system
of equations.
7 Nov 2015 zgttrf(3P)