gerfs Interface

public interface gerfs

GERFS improves the computed solution to a system of linear equations and provides error bounds and backward error estimates for the solution.


Subroutines

public pure subroutine cgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: nrhs
complex(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=sp), intent(in) :: af(ldaf,*)
integer(kind=ilp), intent(in) :: ldaf
integer(kind=ilp), intent(in) :: ipiv(*)
complex(kind=sp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
complex(kind=sp), intent(inout) :: x(ldx,*)
integer(kind=ilp), intent(in) :: ldx
real(kind=sp), intent(out) :: ferr(*)
real(kind=sp), intent(out) :: berr(*)
complex(kind=sp), intent(out) :: work(*)
real(kind=sp), intent(out) :: rwork(*)
integer(kind=ilp), intent(out) :: info

public pure subroutine dgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: nrhs
real(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=dp), intent(in) :: af(ldaf,*)
integer(kind=ilp), intent(in) :: ldaf
integer(kind=ilp), intent(in) :: ipiv(*)
real(kind=dp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=dp), intent(inout) :: x(ldx,*)
integer(kind=ilp), intent(in) :: ldx
real(kind=dp), intent(out) :: ferr(*)
real(kind=dp), intent(out) :: berr(*)
real(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(out) :: iwork(*)
integer(kind=ilp), intent(out) :: info

public pure subroutine sgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: nrhs
real(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=sp), intent(in) :: af(ldaf,*)
integer(kind=ilp), intent(in) :: ldaf
integer(kind=ilp), intent(in) :: ipiv(*)
real(kind=sp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=sp), intent(inout) :: x(ldx,*)
integer(kind=ilp), intent(in) :: ldx
real(kind=sp), intent(out) :: ferr(*)
real(kind=sp), intent(out) :: berr(*)
real(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(out) :: iwork(*)
integer(kind=ilp), intent(out) :: info

public pure subroutine zgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: nrhs
complex(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=dp), intent(in) :: af(ldaf,*)
integer(kind=ilp), intent(in) :: ldaf
integer(kind=ilp), intent(in) :: ipiv(*)
complex(kind=dp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
complex(kind=dp), intent(inout) :: x(ldx,*)
integer(kind=ilp), intent(in) :: ldx
real(kind=dp), intent(out) :: ferr(*)
real(kind=dp), intent(out) :: berr(*)
complex(kind=dp), intent(out) :: work(*)
real(kind=dp), intent(out) :: rwork(*)
integer(kind=ilp), intent(out) :: info

Module Procedures

public interface stdlib_cgerfs()

Arguments

None

public interface stdlib_dgerfs()

Arguments

None

public interface stdlib_sgerfs()

Arguments

None

public interface stdlib_zgerfs()

Arguments

None