Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dgetf2 (3p)

Name

dgetf2 - n matrix A using partial pivoting with row interchanges

Synopsis

SUBROUTINE DGETF2(M, N, A, LDA, IPIV, INFO)

INTEGER M, N, LDA, INFO
INTEGER IPIV(*)
DOUBLE PRECISION A(LDA,*)

SUBROUTINE DGETF2_64(M, N, A, LDA, IPIV, INFO)

INTEGER*8 M, N, LDA, INFO
INTEGER*8 IPIV(*)
DOUBLE PRECISION A(LDA,*)




F95 INTERFACE
SUBROUTINE GETF2(M, N, A, LDA, IPIV, INFO)

INTEGER :: M, N, LDA, INFO
INTEGER, DIMENSION(:) :: IPIV
REAL(8), DIMENSION(:,:) :: A

SUBROUTINE GETF2_64(M, N, A, LDA, IPIV, INFO)

INTEGER(8) :: M, N, LDA, INFO
INTEGER(8), DIMENSION(:) :: IPIV
REAL(8), DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void dgetf2(int m, int n, double *a, int lda, int *ipiv, int *info);

void dgetf2_64(long m, long n, double *a, long lda,  long  *ipiv,  long
*info);

Description

Oracle Solaris Studio Performance Library                           dgetf2(3P)



NAME
       dgetf2 - compute an LU factorization of a general m-by-n matrix A using
       partial pivoting with row interchanges


SYNOPSIS
       SUBROUTINE DGETF2(M, N, A, LDA, IPIV, INFO)

       INTEGER M, N, LDA, INFO
       INTEGER IPIV(*)
       DOUBLE PRECISION A(LDA,*)

       SUBROUTINE DGETF2_64(M, N, A, LDA, IPIV, INFO)

       INTEGER*8 M, N, LDA, INFO
       INTEGER*8 IPIV(*)
       DOUBLE PRECISION A(LDA,*)




   F95 INTERFACE
       SUBROUTINE GETF2(M, N, A, LDA, IPIV, INFO)

       INTEGER :: M, N, LDA, INFO
       INTEGER, DIMENSION(:) :: IPIV
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE GETF2_64(M, N, A, LDA, IPIV, INFO)

       INTEGER(8) :: M, N, LDA, INFO
       INTEGER(8), DIMENSION(:) :: IPIV
       REAL(8), DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void dgetf2(int m, int n, double *a, int lda, int *ipiv, int *info);

       void dgetf2_64(long m, long n, double *a, long lda,  long  *ipiv,  long
                 *info);



PURPOSE
       dgetf2  computes an LU factorization of a general m-by-n matrix A using
       partial pivoting with row interchanges.

       The factorization has the form
          A = P * L * U
       where P is a permutation matrix, L is lower triangular with unit diago-
       nal  elements  (lower  trapezoidal if m > n), and U is upper triangular
       (upper trapezoidal if m < n).

       This is the right-looking Level 2 BLAS version of the algorithm.


ARGUMENTS
       M (input) The number of rows of the matrix A.  M >= 0.


       N (input) The number of columns of the matrix A.  N >= 0.


       A (input/output)
                 On entry, the m by n matrix to be  factored.   On  exit,  the
                 factors  L  and  U from the factorization A = P*L*U; the unit
                 diagonal elements of L are not stored.


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


       IPIV (output)
                 The pivot indices; for 1 <= i  <=  min(M,N),  row  i  of  the
                 matrix was interchanged with row IPIV(i).


       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                        dgetf2(3P)