stdlib_lapack_solve Module



Interfaces

interface

  • public pure module subroutine stdlib_cgbcon(norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgbequ(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgbrfs(trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, 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) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_cgbsv(n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_cgbsvx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: r(*)
    real(kind=sp), intent(inout) :: c(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cgbtf2(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgbtrf(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgbtrs(trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgecon(norm, n, a, lda, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgeequb(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_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

interface

  • public pure module subroutine stdlib_cgesc2(n, a, lda, rhs, ipiv, jpiv, scale)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: rhs(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)
    real(kind=sp), intent(out) :: scale

interface

  • public pure module subroutine stdlib_cgesv(n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_cgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: r(*)
    real(kind=sp), intent(inout) :: c(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cgetc2(n, a, lda, ipiv, jpiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: jpiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgetf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgetrf(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_cgetrf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgetri(n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, 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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgtcon(norm, n, dl, d, du, du2, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: dl(*)
    complex(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: du(*)
    complex(kind=sp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, 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) :: dl(*)
    complex(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: du(*)
    complex(kind=sp), intent(in) :: dlf(*)
    complex(kind=sp), intent(in) :: df(*)
    complex(kind=sp), intent(in) :: duf(*)
    complex(kind=sp), intent(in) :: du2(*)
    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

interface

  • public pure module subroutine stdlib_cgtsv(n, nrhs, dl, d, du, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: dl(*)
    complex(kind=sp), intent(inout) :: d(*)
    complex(kind=sp), intent(inout) :: du(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: dl(*)
    complex(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: du(*)
    complex(kind=sp), intent(inout) :: dlf(*)
    complex(kind=sp), intent(inout) :: df(*)
    complex(kind=sp), intent(inout) :: duf(*)
    complex(kind=sp), intent(inout) :: du2(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cgttrf(n, dl, d, du, du2, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: dl(*)
    complex(kind=sp), intent(inout) :: d(*)
    complex(kind=sp), intent(inout) :: du(*)
    complex(kind=sp), intent(out) :: du2(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, 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) :: dl(*)
    complex(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: du(*)
    complex(kind=sp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cgtts2(itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: itrans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: dl(*)
    complex(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: du(*)
    complex(kind=sp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_checon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_checon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cheequb(uplo, n, a, lda, s, scond, amax, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cherfs(uplo, 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) :: uplo
    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

interface

  • public pure module subroutine stdlib_chesv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chesv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chesv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chesv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_chesvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    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(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: ferr(*)
    real(kind=sp), intent(out) :: berr(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cheswapr(uplo, n, a, lda, i1, i2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,n)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: i1
    integer(kind=ilp), intent(in) :: i2

interface

  • public pure module subroutine stdlib_chetf2(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetf2_rk(uplo, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetf2_rook(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrf(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetri(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetri_rook(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chetrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chpcon(uplo, n, ap, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_chpsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_chpsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: afp(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_chptrf(uplo, n, ap, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chptri(uplo, n, ap, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_chptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module function stdlib_cla_gbrpvgrw(n, kl, ku, ncols, ab, ldab, afb, ldafb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: ncols
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb

    Return Value real(kind=sp)

interface

  • public module function stdlib_cla_herpvgrw(uplo, n, info, a, lda, af, ldaf, ipiv, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: info
    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(*)
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_cla_lin_berr(n, nz, nrhs, res, ayb, berr)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nz
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: res(n,nrhs)
    real(kind=sp), intent(in) :: ayb(n,nrhs)
    real(kind=sp), intent(out) :: berr(nrhs)

interface

  • public module function stdlib_cla_porpvgrw(uplo, ncols, a, lda, af, ldaf, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: ncols
    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
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_clacn2(n, v, x, est, kase, isave)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(out) :: v(*)
    complex(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase
    integer(kind=ilp), intent(inout) :: isave(3_ilp)

interface

  • public module subroutine stdlib_clacon(n, v, x, est, kase)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(out) :: v(n)
    complex(kind=sp), intent(inout) :: x(n)
    real(kind=sp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase

interface

  • public pure module subroutine stdlib_clahef(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clahef_aa(uplo, j1, m, nb, a, lda, ipiv, h, ldh, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: j1
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: nb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: h(ldh,*)
    integer(kind=ilp), intent(in) :: ldh
    complex(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_clahef_rk(uplo, n, nb, kb, a, lda, e, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clahef_rook(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_claqgb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: r(*)
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: rowcnd
    real(kind=sp), intent(in) :: colcnd
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: r(*)
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: rowcnd
    real(kind=sp), intent(in) :: colcnd
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claqhb(uplo, n, kd, ab, ldab, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claqhe(uplo, n, a, lda, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claqhp(uplo, n, ap, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claqsp(uplo, n, ap, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claqsy(uplo, n, a, lda, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_claswp(n, a, lda, k1, k2, ipiv, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: k1
    integer(kind=ilp), intent(in) :: k2
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_clasyf(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clasyf_aa(uplo, j1, m, nb, a, lda, ipiv, h, ldh, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: j1
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: nb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: h(ldh,*)
    integer(kind=ilp), intent(in) :: ldh
    complex(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_clasyf_rk(uplo, n, nb, kb, a, lda, e, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clasyf_rook(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(out) :: scale
    real(kind=sp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clatdf(ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv, jpiv)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: ijob
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: z(ldz,*)
    integer(kind=ilp), intent(in) :: ldz
    complex(kind=sp), intent(inout) :: rhs(*)
    real(kind=sp), intent(inout) :: rdsum
    real(kind=sp), intent(inout) :: rdscal
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)

interface

  • public pure module subroutine stdlib_clatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(out) :: scale
    real(kind=sp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(out) :: scale
    real(kind=sp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clauu2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_clauum(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_cpbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_cpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: s(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cpbtf2(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpbtrf(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpftrf(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpftri(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpftrs(transr, uplo, n, nrhs, a, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: a(0_ilp:*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpocon(uplo, n, a, lda, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpoequ(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpoequb(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    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

interface

  • public pure module subroutine stdlib_cposv(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_cposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: s(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cpotf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpotrf(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_cpotrf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpotri(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpotrs(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cppcon(uplo, n, ap, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cppequ(uplo, n, ap, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_cppsv(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ap(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_cppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ap(*)
    complex(kind=sp), intent(inout) :: afp(*)
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: s(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cpptrf(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpptri(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpptrs(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpstf2(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=sp), intent(in) :: tol
    real(kind=sp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpstrf(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=sp), intent(in) :: tol
    real(kind=sp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cptcon(n, d, e, anorm, rcond, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cptrfs(uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(in) :: df(*)
    complex(kind=sp), intent(in) :: ef(*)
    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

interface

  • public pure module subroutine stdlib_cptsv(n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: d(*)
    complex(kind=sp), intent(inout) :: e(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(inout) :: df(*)
    complex(kind=sp), intent(inout) :: ef(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_cpttrf(n, d, e, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: d(*)
    complex(kind=sp), intent(inout) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cpttrs(uplo, n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: e(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_cptts2(iuplo, n, nrhs, d, e, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: iuplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: e(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_cspcon(uplo, n, ap, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_cspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_cspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: afp(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_csptrf(uplo, n, ap, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csptri(uplo, n, ap, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csycon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csycon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csyconv(uplo, way, n, a, lda, ipiv, e, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csyconvf(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: e(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csyconvf_rook(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csyequb(uplo, n, a, lda, s, scond, amax, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csyrfs(uplo, 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) :: uplo
    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

interface

  • public pure module subroutine stdlib_csysv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csysv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_csysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    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(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: ferr(*)
    real(kind=sp), intent(out) :: berr(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csyswapr(uplo, n, a, lda, i1, i2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,n)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: i1
    integer(kind=ilp), intent(in) :: i2

interface

  • public pure module subroutine stdlib_csytf2(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytf2_rk(uplo, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytf2_rook(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrf(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytri(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytri_rook(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_csytrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ctbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_ctbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctftri(transr, uplo, diag, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ctpcon(norm, uplo, diag, n, ap, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_ctptri(uplo, diag, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ctrcon(norm, uplo, diag, n, a, lda, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: rcond
    complex(kind=sp), intent(out) :: work(*)
    real(kind=sp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_ctrti2(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctrtri(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgbcon(norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgbequ(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgbrfs(trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, 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) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_dgbsv(n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dgbsvx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: r(*)
    real(kind=dp), intent(inout) :: c(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dgbtf2(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgbtrf(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgbtrs(trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgecon(norm, n, a, lda, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgeequb(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_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

interface

  • public pure module subroutine stdlib_dgesc2(n, a, lda, rhs, ipiv, jpiv, scale)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: rhs(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)
    real(kind=dp), intent(out) :: scale

interface

  • public pure module subroutine stdlib_dgesv(n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: r(*)
    real(kind=dp), intent(inout) :: c(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dgetc2(n, a, lda, ipiv, jpiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: jpiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgetf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgetrf(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_dgetrf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgetri(n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, 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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgtcon(norm, n, dl, d, du, du2, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: dl(*)
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: du(*)
    real(kind=dp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, 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) :: dl(*)
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: du(*)
    real(kind=dp), intent(in) :: dlf(*)
    real(kind=dp), intent(in) :: df(*)
    real(kind=dp), intent(in) :: duf(*)
    real(kind=dp), intent(in) :: du2(*)
    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

interface

  • public pure module subroutine stdlib_dgtsv(n, nrhs, dl, d, du, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: dl(*)
    real(kind=dp), intent(inout) :: d(*)
    real(kind=dp), intent(inout) :: du(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: dl(*)
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: du(*)
    real(kind=dp), intent(inout) :: dlf(*)
    real(kind=dp), intent(inout) :: df(*)
    real(kind=dp), intent(inout) :: duf(*)
    real(kind=dp), intent(inout) :: du2(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dgttrf(n, dl, d, du, du2, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dl(*)
    real(kind=dp), intent(inout) :: d(*)
    real(kind=dp), intent(inout) :: du(*)
    real(kind=dp), intent(out) :: du2(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, 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) :: dl(*)
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: du(*)
    real(kind=dp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dgtts2(itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: itrans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: dl(*)
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: du(*)
    real(kind=dp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public module function stdlib_dla_gbrcond(trans, n, kl, ku, ab, ldab, afb, ldafb, ipiv, cmode, c, info, work, iwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: cmode
    real(kind=dp), intent(in) :: c(*)
    integer(kind=ilp), intent(out) :: info
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_dla_gbrpvgrw(n, kl, ku, ncols, ab, ldab, afb, ldafb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: ncols
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb

    Return Value real(kind=dp)

interface

  • public module function stdlib_dla_gercond(trans, n, a, lda, af, ldaf, ipiv, cmode, c, info, work, iwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    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(*)
    integer(kind=ilp), intent(in) :: cmode
    real(kind=dp), intent(in) :: c(*)
    integer(kind=ilp), intent(out) :: info
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_dla_lin_berr(n, nz, nrhs, res, ayb, berr)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nz
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: res(n,nrhs)
    real(kind=dp), intent(in) :: ayb(n,nrhs)
    real(kind=dp), intent(out) :: berr(nrhs)

interface

  • public module function stdlib_dla_porcond(uplo, n, a, lda, af, ldaf, cmode, c, info, work, iwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    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) :: cmode
    real(kind=dp), intent(in) :: c(*)
    integer(kind=ilp), intent(out) :: info
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_dla_porpvgrw(uplo, ncols, a, lda, af, ldaf, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: ncols
    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
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_dlacn2(n, v, x, isgn, est, kase, isave)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(out) :: v(*)
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(out) :: isgn(*)
    real(kind=dp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase
    integer(kind=ilp), intent(inout) :: isave(3_ilp)

interface

  • public module subroutine stdlib_dlacon(n, v, x, isgn, est, kase)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(out) :: v(*)
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(out) :: isgn(*)
    real(kind=dp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase

interface

  • public pure module subroutine stdlib_dlaqgb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: r(*)
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: rowcnd
    real(kind=dp), intent(in) :: colcnd
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_dlaqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: r(*)
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: rowcnd
    real(kind=dp), intent(in) :: colcnd
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_dlaqsp(uplo, n, ap, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: ap(*)
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_dlaqsy(uplo, n, a, lda, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_dlaswp(n, a, lda, k1, k2, ipiv, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: k1
    integer(kind=ilp), intent(in) :: k2
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_dlasyf(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlasyf_aa(uplo, j1, m, nb, a, lda, ipiv, h, ldh, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: j1
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: nb
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: h(ldh,*)
    integer(kind=ilp), intent(in) :: ldh
    real(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_dlasyf_rk(uplo, n, nb, kb, a, lda, e, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlasyf_rook(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(out) :: scale
    real(kind=dp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlatdf(ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv, jpiv)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: ijob
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: z(ldz,*)
    integer(kind=ilp), intent(in) :: ldz
    real(kind=dp), intent(inout) :: rhs(*)
    real(kind=dp), intent(inout) :: rdsum
    real(kind=dp), intent(inout) :: rdscal
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)

interface

  • public pure module subroutine stdlib_dlatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(out) :: scale
    real(kind=dp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(out) :: scale
    real(kind=dp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlauu2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlauum(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_dpbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: s(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dpbtf2(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpbtrf(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpftrf(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpftri(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpftrs(transr, uplo, n, nrhs, a, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: a(0_ilp:*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpoequ(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpoequb(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    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

interface

  • public pure module subroutine stdlib_dposv(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: s(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dpotf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpotrf(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_dpotrf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpotri(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpotrs(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dppcon(uplo, n, ap, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dppequ(uplo, n, ap, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_dppsv(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ap(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ap(*)
    real(kind=dp), intent(inout) :: afp(*)
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: s(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dpptrf(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpptri(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpptrs(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpstf2(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=dp), intent(in) :: tol
    real(kind=dp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpstrf(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=dp), intent(in) :: tol
    real(kind=dp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dptcon(n, d, e, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dptrfs(n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(in) :: df(*)
    real(kind=dp), intent(in) :: ef(*)
    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) :: info

interface

  • public pure module subroutine stdlib_dptsv(n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: d(*)
    real(kind=dp), intent(inout) :: e(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(inout) :: df(*)
    real(kind=dp), intent(inout) :: ef(*)
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: ferr(*)
    real(kind=dp), intent(out) :: berr(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpttrf(n, d, e, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: d(*)
    real(kind=dp), intent(inout) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dpttrs(n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dptts2(n, nrhs, d, e, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_dspcon(uplo, n, ap, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_dspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: afp(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_dsptrf(uplo, n, ap, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsptri(uplo, n, ap, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsycon(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsycon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsyconv(uplo, way, n, a, lda, ipiv, e, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsyconvf(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: e(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsyconvf_rook(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsyequb(uplo, n, a, lda, s, scond, amax, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsyrfs(uplo, 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) :: uplo
    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

interface

  • public pure module subroutine stdlib_dsysv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsysv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dsysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    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(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: ferr(*)
    real(kind=dp), intent(out) :: berr(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsyswapr(uplo, n, a, lda, i1, i2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,n)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: i1
    integer(kind=ilp), intent(in) :: i2

interface

  • public pure module subroutine stdlib_dsytf2(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytf2_rk(uplo, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytf2_rook(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrf(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytri(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytri_rook(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dsytrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dtbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_dtbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtftri(transr, uplo, diag, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dtpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_dtptri(uplo, diag, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_dtrcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_dtrti2(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtrtri(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgbcon(norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgbequ(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgbrfs(trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, 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) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_sgbsv(n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_sgbsvx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: r(*)
    real(kind=sp), intent(inout) :: c(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_sgbtf2(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgbtrf(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgbtrs(trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgecon(norm, n, a, lda, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgeequb(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: r(*)
    real(kind=sp), intent(out) :: c(*)
    real(kind=sp), intent(out) :: rowcnd
    real(kind=sp), intent(out) :: colcnd
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_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

interface

  • public pure module subroutine stdlib_sgesc2(n, a, lda, rhs, ipiv, jpiv, scale)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: rhs(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)
    real(kind=sp), intent(out) :: scale

interface

  • public pure module subroutine stdlib_sgesv(n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_sgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: r(*)
    real(kind=sp), intent(inout) :: c(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_sgetc2(n, a, lda, ipiv, jpiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: jpiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgetf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgetrf(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_sgetrf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgetri(n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, 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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgtcon(norm, n, dl, d, du, du2, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: dl(*)
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: du(*)
    real(kind=sp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, 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) :: dl(*)
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: du(*)
    real(kind=sp), intent(in) :: dlf(*)
    real(kind=sp), intent(in) :: df(*)
    real(kind=sp), intent(in) :: duf(*)
    real(kind=sp), intent(in) :: du2(*)
    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

interface

  • public pure module subroutine stdlib_sgtsv(n, nrhs, dl, d, du, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: dl(*)
    real(kind=sp), intent(inout) :: d(*)
    real(kind=sp), intent(inout) :: du(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: dl(*)
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: du(*)
    real(kind=sp), intent(inout) :: dlf(*)
    real(kind=sp), intent(inout) :: df(*)
    real(kind=sp), intent(inout) :: duf(*)
    real(kind=sp), intent(inout) :: du2(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_sgttrf(n, dl, d, du, du2, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: dl(*)
    real(kind=sp), intent(inout) :: d(*)
    real(kind=sp), intent(inout) :: du(*)
    real(kind=sp), intent(out) :: du2(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, 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) :: dl(*)
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: du(*)
    real(kind=sp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sgtts2(itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: itrans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: dl(*)
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: du(*)
    real(kind=sp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public module function stdlib_sla_gbrcond(trans, n, kl, ku, ab, ldab, afb, ldafb, ipiv, cmode, c, info, work, iwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: cmode
    real(kind=sp), intent(in) :: c(*)
    integer(kind=ilp), intent(out) :: info
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_sla_gbrpvgrw(n, kl, ku, ncols, ab, ldab, afb, ldafb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: ncols
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb

    Return Value real(kind=sp)

interface

  • public module function stdlib_sla_gercond(trans, n, a, lda, af, ldaf, ipiv, cmode, c, info, work, iwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    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(*)
    integer(kind=ilp), intent(in) :: cmode
    real(kind=sp), intent(in) :: c(*)
    integer(kind=ilp), intent(out) :: info
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_sla_lin_berr(n, nz, nrhs, res, ayb, berr)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nz
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: res(n,nrhs)
    real(kind=sp), intent(in) :: ayb(n,nrhs)
    real(kind=sp), intent(out) :: berr(nrhs)

interface

  • public module function stdlib_sla_porcond(uplo, n, a, lda, af, ldaf, cmode, c, info, work, iwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    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) :: cmode
    real(kind=sp), intent(in) :: c(*)
    integer(kind=ilp), intent(out) :: info
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_sla_porpvgrw(uplo, ncols, a, lda, af, ldaf, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: ncols
    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
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_slacn2(n, v, x, isgn, est, kase, isave)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(out) :: v(*)
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(out) :: isgn(*)
    real(kind=sp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase
    integer(kind=ilp), intent(inout) :: isave(3_ilp)

interface

  • public module subroutine stdlib_slacon(n, v, x, isgn, est, kase)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(out) :: v(*)
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(out) :: isgn(*)
    real(kind=sp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase

interface

  • public pure module subroutine stdlib_slaqgb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: r(*)
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: rowcnd
    real(kind=sp), intent(in) :: colcnd
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_slaqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: r(*)
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: rowcnd
    real(kind=sp), intent(in) :: colcnd
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_slaqsp(uplo, n, ap, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: ap(*)
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_slaqsy(uplo, n, a, lda, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(in) :: scond
    real(kind=sp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_slaswp(n, a, lda, k1, k2, ipiv, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: k1
    integer(kind=ilp), intent(in) :: k2
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_slasyf(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slasyf_aa(uplo, j1, m, nb, a, lda, ipiv, h, ldh, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: j1
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: nb
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: h(ldh,*)
    integer(kind=ilp), intent(in) :: ldh
    real(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_slasyf_rk(uplo, n, nb, kb, a, lda, e, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slasyf_rook(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(out) :: scale
    real(kind=sp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slatdf(ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv, jpiv)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: ijob
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: z(ldz,*)
    integer(kind=ilp), intent(in) :: ldz
    real(kind=sp), intent(inout) :: rhs(*)
    real(kind=sp), intent(inout) :: rdsum
    real(kind=sp), intent(inout) :: rdscal
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)

interface

  • public pure module subroutine stdlib_slatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(out) :: scale
    real(kind=sp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(out) :: scale
    real(kind=sp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slauu2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_slauum(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_spbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_spbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: s(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_spbtf2(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spbtrf(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spftrf(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spftri(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spftrs(transr, uplo, n, nrhs, a, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: a(0_ilp:*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spocon(uplo, n, a, lda, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spoequ(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spoequb(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    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

interface

  • public pure module subroutine stdlib_sposv(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_sposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: s(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_spotf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spotrf(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_spotrf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spotri(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spotrs(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sppcon(uplo, n, ap, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sppequ(uplo, n, ap, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_sppsv(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ap(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_sppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ap(*)
    real(kind=sp), intent(inout) :: afp(*)
    character(len=1), intent(inout) :: equed
    real(kind=sp), intent(inout) :: s(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_spptrf(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spptri(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spptrs(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spstf2(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=sp), intent(in) :: tol
    real(kind=sp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spstrf(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=sp), intent(in) :: tol
    real(kind=sp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sptcon(n, d, e, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sptrfs(n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(in) :: df(*)
    real(kind=sp), intent(in) :: ef(*)
    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) :: info

interface

  • public pure module subroutine stdlib_sptsv(n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: d(*)
    real(kind=sp), intent(inout) :: e(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(inout) :: df(*)
    real(kind=sp), intent(inout) :: ef(*)
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: ferr(*)
    real(kind=sp), intent(out) :: berr(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spttrf(n, d, e, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: d(*)
    real(kind=sp), intent(inout) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_spttrs(n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_sptts2(n, nrhs, d, e, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: e(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_sspcon(uplo, n, ap, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_sspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_sspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: afp(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_ssptrf(uplo, n, ap, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssptri(uplo, n, ap, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssycon(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssycon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(in) :: anorm
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssyconv(uplo, way, n, a, lda, ipiv, e, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssyconvf(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: e(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssyconvf_rook(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssyequb(uplo, n, a, lda, s, scond, amax, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: s(*)
    real(kind=sp), intent(out) :: scond
    real(kind=sp), intent(out) :: amax
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssyrfs(uplo, 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) :: uplo
    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

interface

  • public pure module subroutine stdlib_ssysv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssysv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ssysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    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(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: ferr(*)
    real(kind=sp), intent(out) :: berr(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssyswapr(uplo, n, a, lda, i1, i2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,n)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: i1
    integer(kind=ilp), intent(in) :: i2

interface

  • public pure module subroutine stdlib_ssytf2(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytf2_rk(uplo, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytf2_rook(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrf(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytri(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytri_rook(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ssytrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_stbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_stbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stftri(transr, uplo, diag, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_stpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_stptri(uplo, diag, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_strcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: rcond
    real(kind=sp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: iwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_strrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, iwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_strti2(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_strtri(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_strtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgbcon(norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgbequ(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgbrfs(trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, 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) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_zgbsv(n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zgbsvx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: r(*)
    real(kind=dp), intent(inout) :: c(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zgbtf2(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgbtrf(m, n, kl, ku, ab, ldab, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgbtrs(trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgecon(norm, n, a, lda, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgeequb(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: r(*)
    real(kind=dp), intent(out) :: c(*)
    real(kind=dp), intent(out) :: rowcnd
    real(kind=dp), intent(out) :: colcnd
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_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

interface

  • public pure module subroutine stdlib_zgesc2(n, a, lda, rhs, ipiv, jpiv, scale)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: rhs(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)
    real(kind=dp), intent(out) :: scale

interface

  • public pure module subroutine stdlib_zgesv(n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: r(*)
    real(kind=dp), intent(inout) :: c(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zgetc2(n, a, lda, ipiv, jpiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: jpiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgetf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgetrf(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_zgetrf2(m, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgetri(n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, 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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgtcon(norm, n, dl, d, du, du2, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: dl(*)
    complex(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: du(*)
    complex(kind=dp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, 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) :: dl(*)
    complex(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: du(*)
    complex(kind=dp), intent(in) :: dlf(*)
    complex(kind=dp), intent(in) :: df(*)
    complex(kind=dp), intent(in) :: duf(*)
    complex(kind=dp), intent(in) :: du2(*)
    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

interface

  • public pure module subroutine stdlib_zgtsv(n, nrhs, dl, d, du, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: dl(*)
    complex(kind=dp), intent(inout) :: d(*)
    complex(kind=dp), intent(inout) :: du(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: dl(*)
    complex(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: du(*)
    complex(kind=dp), intent(inout) :: dlf(*)
    complex(kind=dp), intent(inout) :: df(*)
    complex(kind=dp), intent(inout) :: duf(*)
    complex(kind=dp), intent(inout) :: du2(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zgttrf(n, dl, d, du, du2, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: dl(*)
    complex(kind=dp), intent(inout) :: d(*)
    complex(kind=dp), intent(inout) :: du(*)
    complex(kind=dp), intent(out) :: du2(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, 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) :: dl(*)
    complex(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: du(*)
    complex(kind=dp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zgtts2(itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: itrans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: dl(*)
    complex(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: du(*)
    complex(kind=dp), intent(in) :: du2(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_zhecon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhecon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zheequb(uplo, n, a, lda, s, scond, amax, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zherfs(uplo, 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) :: uplo
    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

interface

  • public pure module subroutine stdlib_zhesv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhesv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhesv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhesv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zhesvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    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(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: ferr(*)
    real(kind=dp), intent(out) :: berr(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zheswapr(uplo, n, a, lda, i1, i2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,n)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: i1
    integer(kind=ilp), intent(in) :: i2

interface

  • public pure module subroutine stdlib_zhetf2(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetf2_rk(uplo, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetf2_rook(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrf(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetri(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetri_rook(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhetrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhpcon(uplo, n, ap, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_zhpsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zhpsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: afp(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zhptrf(uplo, n, ap, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhptri(uplo, n, ap, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zhptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module function stdlib_zla_gbrpvgrw(n, kl, ku, ncols, ab, ldab, afb, ldafb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    integer(kind=ilp), intent(in) :: ncols
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb

    Return Value real(kind=dp)

interface

  • public module function stdlib_zla_herpvgrw(uplo, n, info, a, lda, af, ldaf, ipiv, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: info
    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(*)
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_zla_lin_berr(n, nz, nrhs, res, ayb, berr)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nz
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: res(n,nrhs)
    real(kind=dp), intent(in) :: ayb(n,nrhs)
    real(kind=dp), intent(out) :: berr(nrhs)

interface

  • public module function stdlib_zla_porpvgrw(uplo, ncols, a, lda, af, ldaf, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: ncols
    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
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_zlacn2(n, v, x, est, kase, isave)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(out) :: v(*)
    complex(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase
    integer(kind=ilp), intent(inout) :: isave(3_ilp)

interface

  • public module subroutine stdlib_zlacon(n, v, x, est, kase)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(out) :: v(n)
    complex(kind=dp), intent(inout) :: x(n)
    real(kind=dp), intent(inout) :: est
    integer(kind=ilp), intent(inout) :: kase

interface

  • public pure module subroutine stdlib_zlahef(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlahef_aa(uplo, j1, m, nb, a, lda, ipiv, h, ldh, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: j1
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: nb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: h(ldh,*)
    integer(kind=ilp), intent(in) :: ldh
    complex(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_zlahef_rk(uplo, n, nb, kb, a, lda, e, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlahef_rook(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlaqgb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: r(*)
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: rowcnd
    real(kind=dp), intent(in) :: colcnd
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaqge(m, n, a, lda, r, c, rowcnd, colcnd, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: r(*)
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: rowcnd
    real(kind=dp), intent(in) :: colcnd
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaqhb(uplo, n, kd, ab, ldab, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaqhe(uplo, n, a, lda, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaqhp(uplo, n, ap, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaqsp(uplo, n, ap, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaqsy(uplo, n, a, lda, s, scond, amax, equed)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(in) :: scond
    real(kind=dp), intent(in) :: amax
    character(len=1), intent(out) :: equed

interface

  • public pure module subroutine stdlib_zlaswp(n, a, lda, k1, k2, ipiv, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: k1
    integer(kind=ilp), intent(in) :: k2
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_zlasyf(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlasyf_aa(uplo, j1, m, nb, a, lda, ipiv, h, ldh, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: j1
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: nb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: h(ldh,*)
    integer(kind=ilp), intent(in) :: ldh
    complex(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_zlasyf_rk(uplo, n, nb, kb, a, lda, e, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlasyf_rook(uplo, n, nb, kb, a, lda, ipiv, w, ldw, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nb
    integer(kind=ilp), intent(out) :: kb
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: w(ldw,*)
    integer(kind=ilp), intent(in) :: ldw
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(out) :: scale
    real(kind=dp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlatdf(ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv, jpiv)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: ijob
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: z(ldz,*)
    integer(kind=ilp), intent(in) :: ldz
    complex(kind=dp), intent(inout) :: rhs(*)
    real(kind=dp), intent(inout) :: rdsum
    real(kind=dp), intent(inout) :: rdscal
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(in) :: jpiv(*)

interface

  • public pure module subroutine stdlib_zlatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(out) :: scale
    real(kind=dp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    character(len=1), intent(in) :: normin
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(out) :: scale
    real(kind=dp), intent(inout) :: cnorm(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlauu2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zlauum(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(in) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    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

interface

  • public pure module subroutine stdlib_zpbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(inout) :: afb(ldafb,*)
    integer(kind=ilp), intent(in) :: ldafb
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: s(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zpbtf2(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpbtrf(uplo, n, kd, ab, ldab, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpftrf(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpftri(transr, uplo, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpftrs(transr, uplo, n, nrhs, a, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: a(0_ilp:*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpocon(uplo, n, a, lda, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpoequ(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpoequb(n, a, lda, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    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

interface

  • public pure module subroutine stdlib_zposv(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: s(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zpotf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpotrf(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure recursive module subroutine stdlib_zpotrf2(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpotri(uplo, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpotrs(uplo, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zppcon(uplo, n, ap, anorm, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zppequ(uplo, n, ap, s, scond, amax, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_zppsv(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ap(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ap(*)
    complex(kind=dp), intent(inout) :: afp(*)
    character(len=1), intent(inout) :: equed
    real(kind=dp), intent(inout) :: s(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zpptrf(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpptri(uplo, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpptrs(uplo, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpstf2(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=dp), intent(in) :: tol
    real(kind=dp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpstrf(uplo, n, a, lda, piv, rank, tol, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: piv(n)
    integer(kind=ilp), intent(out) :: rank
    real(kind=dp), intent(in) :: tol
    real(kind=dp), intent(out) :: work(2_ilp*n)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zptcon(n, d, e, anorm, rcond, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zptrfs(uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(in) :: df(*)
    complex(kind=dp), intent(in) :: ef(*)
    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

interface

  • public pure module subroutine stdlib_zptsv(n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(inout) :: d(*)
    complex(kind=dp), intent(inout) :: e(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: e(*)
    real(kind=dp), intent(inout) :: df(*)
    complex(kind=dp), intent(inout) :: ef(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zpttrf(n, d, e, info)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: d(*)
    complex(kind=dp), intent(inout) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zpttrs(uplo, n, nrhs, d, e, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: e(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zptts2(iuplo, n, nrhs, d, e, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: iuplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    real(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: e(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_zspcon(uplo, n, ap, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsprfs(uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(in) :: afp(*)
    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

interface

  • public pure module subroutine stdlib_zspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: afp(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    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

interface

  • public pure module subroutine stdlib_zsptrf(uplo, n, ap, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsptri(uplo, n, ap, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsptrs(uplo, n, nrhs, ap, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsycon(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsycon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    real(kind=dp), intent(in) :: anorm
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsyconv(uplo, way, n, a, lda, ipiv, e, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsyconvf(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: e(*)
    integer(kind=ilp), intent(inout) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsyconvf_rook(uplo, way, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: way
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsyequb(uplo, n, a, lda, s, scond, amax, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: s(*)
    real(kind=dp), intent(out) :: scond
    real(kind=dp), intent(out) :: amax
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsyrfs(uplo, 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) :: uplo
    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

interface

  • public pure module subroutine stdlib_zsysv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsysv_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsysv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_zsysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: fact
    character(len=1), intent(in) :: uplo
    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(inout) :: af(ldaf,*)
    integer(kind=ilp), intent(in) :: ldaf
    integer(kind=ilp), intent(inout) :: ipiv(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(out) :: rcond
    real(kind=dp), intent(out) :: ferr(*)
    real(kind=dp), intent(out) :: berr(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsyswapr(uplo, n, a, lda, i1, i2)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,n)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: i1
    integer(kind=ilp), intent(in) :: i2

interface

  • public pure module subroutine stdlib_zsytf2(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytf2_rk(uplo, n, a, lda, e, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytf2_rook(uplo, n, a, lda, ipiv, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrf(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrf_aa(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrf_rk(uplo, n, a, lda, e, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: e(*)
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrf_rook(uplo, n, a, lda, ipiv, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytri(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytri_rook(uplo, n, a, lda, ipiv, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrs2(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrs_3(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: e(*)
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrs_aa(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: work(*)
    integer(kind=ilp), intent(in) :: lwork
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zsytrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
    integer(kind=ilp), intent(in) :: ipiv(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ztbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_ztbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: kd
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztftri(transr, uplo, diag, n, a, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ztpcon(norm, uplo, diag, n, ap, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_ztptri(uplo, diag, n, ap, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: nrhs
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info

interface

  • public module subroutine stdlib_ztrcon(norm, uplo, diag, n, a, lda, rcond, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: rcond
    complex(kind=dp), intent(out) :: work(*)
    real(kind=dp), intent(out) :: rwork(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, rwork, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: 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

interface

  • public pure module subroutine stdlib_ztrti2(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztrtri(uplo, diag, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    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(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    integer(kind=ilp), intent(out) :: info