stdlib_lapack_base Module



Interfaces

interface

  • public pure module subroutine stdlib_chfrk(transr, uplo, trans, n, k, alpha, a, lda, beta, c)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(*)

interface

  • public module subroutine stdlib_cla_gbamv(trans, m, n, kl, ku, alpha, ab, ldab, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    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) :: alpha
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public module subroutine stdlib_cla_geamv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public module subroutine stdlib_cla_heamv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_cla_wwaddw(n, x, y, w)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: x(*)
    complex(kind=sp), intent(inout) :: y(*)
    complex(kind=sp), intent(in) :: w(*)

interface

  • public pure module subroutine stdlib_clacgv(n, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_clacp2(uplo, m, n, a, lda, b, ldb)

    Arguments

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

interface

  • public pure module subroutine stdlib_clacpy(uplo, m, n, a, lda, b, ldb)

    Arguments

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

interface

  • public pure module subroutine stdlib_clacrm(m, n, a, lda, b, ldb, c, ldc, rwork)

    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(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=sp), intent(out) :: rwork(*)

interface

  • public pure module subroutine stdlib_clacrt(n, cx, incx, cy, incy, c, s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(inout) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(in) :: c
    complex(kind=sp), intent(in) :: s

interface

  • public pure module function stdlib_cladiv(x, y)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: x
    complex(kind=sp), intent(in) :: y

    Return Value complex(kind=sp)

interface

  • public pure module subroutine stdlib_clagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)

    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) :: alpha
    complex(kind=sp), intent(in) :: dl(*)
    complex(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: du(*)
    complex(kind=sp), intent(in) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public module function stdlib_clangb(norm, n, kl, ku, ab, ldab, work)

    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
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_clange(norm, m, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_clangt(norm, n, dl, d, du)

    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(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_clanhb(norm, uplo, n, k, ab, ldab, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clanhe(norm, uplo, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clanhf(norm, transr, uplo, n, a, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clanhp(norm, uplo, n, ap, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clanhs(norm, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_clanht(norm, n, d, e)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: d(*)
    complex(kind=sp), intent(in) :: e(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_clansb(norm, uplo, n, k, ab, ldab, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clansp(norm, uplo, n, ap, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clansy(norm, uplo, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_clantb(norm, uplo, diag, n, k, ab, ldab, work)

    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) :: k
    complex(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_clantp(norm, uplo, diag, n, ap, work)

    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) :: work(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_clantr(norm, uplo, diag, m, n, a, lda, work)

    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) :: 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) :: work(*)

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_claqsb(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(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_clar2v(n, x, y, z, incx, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: x(*)
    complex(kind=sp), intent(inout) :: y(*)
    complex(kind=sp), intent(inout) :: z(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: c(*)
    complex(kind=sp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_clarcm(m, n, a, lda, b, ldb, c, ldc, rwork)

    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
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(out) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=sp), intent(out) :: rwork(*)

interface

  • public pure module subroutine stdlib_clarf(side, m, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    complex(kind=sp), intent(in) :: tau
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_clarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    complex(kind=sp), intent(in) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=sp), intent(out) :: work(ldwork,*)
    integer(kind=ilp), intent(in) :: ldwork

interface

  • public pure module subroutine stdlib_clarfg(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: alpha
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(out) :: tau

interface

  • public module subroutine stdlib_clarfgp(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: alpha
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(out) :: tau

interface

  • public pure module subroutine stdlib_clarft(direct, storev, n, k, v, ldv, tau, t, ldt)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    complex(kind=sp), intent(in) :: tau(*)
    complex(kind=sp), intent(out) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt

interface

  • public pure module subroutine stdlib_clarfx(side, m, n, v, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: v(*)
    complex(kind=sp), intent(in) :: tau
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_clarfy(uplo, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    complex(kind=sp), intent(in) :: tau
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_clargv(n, x, incx, y, incy, c, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(out) :: c(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_clarnv(idist, iseed, n, x)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: idist
    integer(kind=ilp), intent(inout) :: iseed(4_ilp)
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(out) :: x(*)

interface

  • public pure module subroutine stdlib_clartg(f, g, c, s, r)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: f
    complex(kind=sp), intent(in) :: g
    real(kind=sp), intent(out) :: c
    complex(kind=sp), intent(out) :: s
    complex(kind=sp), intent(out) :: r

interface

  • public pure module subroutine stdlib_clartv(n, x, incx, y, incy, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(in) :: c(*)
    complex(kind=sp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_clascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: type
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(in) :: cfrom
    real(kind=sp), intent(in) :: cto
    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) :: info

interface

  • public pure module subroutine stdlib_claset(uplo, m, n, alpha, beta, a, lda)

    Arguments

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

interface

  • public pure module subroutine stdlib_clasr(side, pivot, direct, m, n, c, s, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: pivot
    character(len=1), intent(in) :: direct
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: s(*)
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

interface

  • public pure module subroutine stdlib_classq(n, x, incx, scl, sumsq)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: scl
    real(kind=sp), intent(inout) :: sumsq

interface

  • public pure module subroutine stdlib_crot(n, cx, incx, cy, incy, c, s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(inout) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(in) :: c
    complex(kind=sp), intent(in) :: s

interface

  • public pure module subroutine stdlib_cspmv(uplo, n, alpha, ap, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_cspr(uplo, n, alpha, x, incx, ap)

    Arguments

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

interface

  • public pure module subroutine stdlib_csrscl(n, sa, sx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sa
    complex(kind=sp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_csymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_csyr(uplo, n, alpha, x, incx, a, lda)

    Arguments

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

interface

  • public pure module subroutine stdlib_ctfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(0_ilp:*)
    complex(kind=sp), intent(inout) :: b(0_ilp:ldb-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_ctfttp(transr, uplo, n, arf, ap, 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(in) :: arf(0_ilp:*)
    complex(kind=sp), intent(out) :: ap(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctfttr(transr, uplo, n, arf, a, lda, 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(in) :: arf(0_ilp:*)
    complex(kind=sp), intent(out) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctpttf(transr, uplo, n, ap, arf, 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(in) :: ap(0_ilp:*)
    complex(kind=sp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

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

    Arguments

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

interface

  • public pure module subroutine stdlib_ctrttf(transr, uplo, n, a, lda, arf, 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(in) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ctrttp(uplo, n, a, lda, ap, 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
    complex(kind=sp), intent(out) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module function stdlib_disnan(din)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: din

    Return Value logical(kind=lk)

interface

  • public module subroutine stdlib_dla_gbamv(trans, m, n, kl, ku, alpha, ab, ldab, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    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) :: alpha
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public module subroutine stdlib_dla_geamv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_dla_wwaddw(n, x, y, w)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(inout) :: y(*)
    real(kind=dp), intent(in) :: w(*)

interface

  • public pure module subroutine stdlib_dlabad(small, large)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: small
    real(kind=dp), intent(inout) :: large

interface

  • public pure module subroutine stdlib_dlacpy(uplo, m, n, a, lda, b, ldb)

    Arguments

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

interface

  • public pure module subroutine stdlib_dladiv(a, b, c, d, p, q)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a
    real(kind=dp), intent(in) :: b
    real(kind=dp), intent(in) :: c
    real(kind=dp), intent(in) :: d
    real(kind=dp), intent(out) :: p
    real(kind=dp), intent(out) :: q

interface

  • public pure module subroutine stdlib_dladiv1(a, b, c, d, p, q)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: a
    real(kind=dp), intent(in) :: b
    real(kind=dp), intent(in) :: c
    real(kind=dp), intent(in) :: d
    real(kind=dp), intent(out) :: p
    real(kind=dp), intent(out) :: q

interface

  • public pure module function stdlib_dladiv2(a, b, c, d, r, t)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a
    real(kind=dp), intent(in) :: b
    real(kind=dp), intent(in) :: c
    real(kind=dp), intent(in) :: d
    real(kind=dp), intent(in) :: r
    real(kind=dp), intent(in) :: t

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_dlag2s(m, n, a, lda, sa, ldsa, 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=sp), intent(out) :: sa(ldsa,*)
    integer(kind=ilp), intent(in) :: ldsa
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dlagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)

    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) :: alpha
    real(kind=dp), intent(in) :: dl(*)
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: du(*)
    real(kind=dp), intent(in) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module function stdlib_dlaisnan(din1, din2)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: din1
    real(kind=dp), intent(in) :: din2

    Return Value logical(kind=lk)

interface

  • public pure module function stdlib_dlamc3(a, b)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a
    real(kind=dp), intent(in) :: b

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_dlamch(cmach)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: cmach

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlangb(norm, n, kl, ku, ab, ldab, work)

    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
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlange(norm, m, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_dlangt(norm, n, dl, d, du)

    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(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlanhs(norm, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlansb(norm, uplo, n, k, ab, ldab, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlansf(norm, transr, uplo, n, a, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlansp(norm, uplo, n, ap, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_dlanst(norm, n, d, e)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: d(*)
    real(kind=dp), intent(in) :: e(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlansy(norm, uplo, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlantb(norm, uplo, diag, n, k, ab, ldab, work)

    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) :: k
    real(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlantp(norm, uplo, diag, n, ap, work)

    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) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_dlantr(norm, uplo, diag, m, n, a, lda, work)

    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) :: 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) :: work(*)

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_dlapy2(x, y)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x
    real(kind=dp), intent(in) :: y

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_dlapy3(x, y, z)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: x
    real(kind=dp), intent(in) :: y
    real(kind=dp), intent(in) :: z

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_dlaqsb(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
    real(kind=dp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    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_dlar2v(n, x, y, z, incx, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: x(*)
    real(kind=dp), intent(inout) :: y(*)
    real(kind=dp), intent(inout) :: z(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_dlarf(side, m, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    real(kind=dp), intent(in) :: tau
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_dlarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    real(kind=dp), intent(in) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=dp), intent(out) :: work(ldwork,*)
    integer(kind=ilp), intent(in) :: ldwork

interface

  • public pure module subroutine stdlib_dlarfg(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: alpha
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(out) :: tau

interface

  • public module subroutine stdlib_dlarfgp(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: alpha
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(out) :: tau

interface

  • public pure module subroutine stdlib_dlarft(direct, storev, n, k, v, ldv, tau, t, ldt)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    real(kind=dp), intent(in) :: tau(*)
    real(kind=dp), intent(out) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt

interface

  • public pure module subroutine stdlib_dlarfx(side, m, n, v, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: v(*)
    real(kind=dp), intent(in) :: tau
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_dlarfy(uplo, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    real(kind=dp), intent(in) :: tau
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_dlargv(n, x, incx, y, incy, c, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(out) :: c(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_dlarnv(idist, iseed, n, x)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: idist
    integer(kind=ilp), intent(inout) :: iseed(4_ilp)
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(out) :: x(*)

interface

  • public pure module subroutine stdlib_dlartg(f, g, c, s, r)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: f
    real(kind=dp), intent(in) :: g
    real(kind=dp), intent(out) :: c
    real(kind=dp), intent(out) :: s
    real(kind=dp), intent(out) :: r

interface

  • public pure module subroutine stdlib_dlartgp(f, g, cs, sn, r)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: f
    real(kind=dp), intent(in) :: g
    real(kind=dp), intent(out) :: cs
    real(kind=dp), intent(out) :: sn
    real(kind=dp), intent(out) :: r

interface

  • public pure module subroutine stdlib_dlartv(n, x, incx, y, incy, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_dlaruv(iseed, n, x)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(inout) :: iseed(4_ilp)
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(out) :: x(n)

interface

  • public pure module subroutine stdlib_dlascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: type
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(in) :: cfrom
    real(kind=dp), intent(in) :: cto
    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) :: info

interface

  • public pure module subroutine stdlib_dlaset(uplo, m, n, alpha, beta, a, lda)

    Arguments

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

interface

  • public pure module subroutine stdlib_dlasr(side, pivot, direct, m, n, c, s, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: pivot
    character(len=1), intent(in) :: direct
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: s(*)
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

interface

  • public pure module subroutine stdlib_dlasrt(id, n, d, info)

    Arguments

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

interface

  • public pure module subroutine stdlib_dlassq(n, x, incx, scl, sumsq)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: scl
    real(kind=dp), intent(inout) :: sumsq

interface

  • public pure module subroutine stdlib_dlat2s(uplo, n, a, lda, sa, ldsa, 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=sp), intent(out) :: sa(ldsa,*)
    integer(kind=ilp), intent(in) :: ldsa
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_drscl(n, sa, sx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: sa
    real(kind=dp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_dsfrk(transr, uplo, trans, n, k, alpha, a, lda, beta, c)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(*)

interface

  • public pure module subroutine stdlib_dtfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: a(0_ilp:*)
    real(kind=dp), intent(inout) :: b(0_ilp:ldb-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_dtfttp(transr, uplo, n, arf, ap, 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(in) :: arf(0_ilp:*)
    real(kind=dp), intent(out) :: ap(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtfttr(transr, uplo, n, arf, a, lda, 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(in) :: arf(0_ilp:*)
    real(kind=dp), intent(out) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtpttf(transr, uplo, n, ap, arf, 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(in) :: ap(0_ilp:*)
    real(kind=dp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtpttr(uplo, n, ap, a, lda, 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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtrttf(transr, uplo, n, a, lda, arf, 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(in) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_dtrttp(uplo, n, a, lda, ap, 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) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module function stdlib_dzsum1(n, cx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: cx(*)
    integer(kind=ilp), intent(in) :: incx

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_scsum1(n, cx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: cx(*)
    integer(kind=ilp), intent(in) :: incx

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_sisnan(sin)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: sin

    Return Value logical(kind=lk)

interface

  • public module subroutine stdlib_sla_gbamv(trans, m, n, kl, ku, alpha, ab, ldab, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    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) :: alpha
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public module subroutine stdlib_sla_geamv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_sla_wwaddw(n, x, y, w)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(inout) :: y(*)
    real(kind=sp), intent(in) :: w(*)

interface

  • public pure module subroutine stdlib_slabad(small, large)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: small
    real(kind=sp), intent(inout) :: large

interface

  • public pure module subroutine stdlib_slacpy(uplo, m, n, a, lda, b, ldb)

    Arguments

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

interface

  • public pure module subroutine stdlib_sladiv(a, b, c, d, p, q)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a
    real(kind=sp), intent(in) :: b
    real(kind=sp), intent(in) :: c
    real(kind=sp), intent(in) :: d
    real(kind=sp), intent(out) :: p
    real(kind=sp), intent(out) :: q

interface

  • public pure module subroutine stdlib_sladiv1(a, b, c, d, p, q)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: a
    real(kind=sp), intent(in) :: b
    real(kind=sp), intent(in) :: c
    real(kind=sp), intent(in) :: d
    real(kind=sp), intent(out) :: p
    real(kind=sp), intent(out) :: q

interface

  • public pure module function stdlib_sladiv2(a, b, c, d, r, t)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a
    real(kind=sp), intent(in) :: b
    real(kind=sp), intent(in) :: c
    real(kind=sp), intent(in) :: d
    real(kind=sp), intent(in) :: r
    real(kind=sp), intent(in) :: t

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_slag2d(m, n, sa, ldsa, a, lda, info)

    Arguments

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

interface

  • public pure module subroutine stdlib_slagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)

    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) :: alpha
    real(kind=sp), intent(in) :: dl(*)
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: du(*)
    real(kind=sp), intent(in) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module function stdlib_slaisnan(sin1, sin2)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: sin1
    real(kind=sp), intent(in) :: sin2

    Return Value logical(kind=lk)

interface

  • public pure module function stdlib_slamc3(a, b)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a
    real(kind=sp), intent(in) :: b

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_slamch(cmach)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: cmach

    Return Value real(kind=sp)

interface

  • public module function stdlib_slangb(norm, n, kl, ku, ab, ldab, work)

    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
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_slange(norm, m, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_slangt(norm, n, dl, d, du)

    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(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_slanhs(norm, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_slansb(norm, uplo, n, k, ab, ldab, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_slansf(norm, transr, uplo, n, a, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_slansp(norm, uplo, n, ap, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_slanst(norm, n, d, e)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: d(*)
    real(kind=sp), intent(in) :: e(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_slansy(norm, uplo, n, a, lda, work)

    Arguments

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

    Return Value real(kind=sp)

interface

  • public module function stdlib_slantb(norm, uplo, diag, n, k, ab, ldab, work)

    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) :: k
    real(kind=sp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=sp), intent(out) :: work(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_slantp(norm, uplo, diag, n, ap, work)

    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) :: work(*)

    Return Value real(kind=sp)

interface

  • public module function stdlib_slantr(norm, uplo, diag, m, n, a, lda, work)

    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) :: 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) :: work(*)

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_slapy2(x, y)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x
    real(kind=sp), intent(in) :: y

    Return Value real(kind=sp)

interface

  • public pure module function stdlib_slapy3(x, y, z)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: x
    real(kind=sp), intent(in) :: y
    real(kind=sp), intent(in) :: z

    Return Value real(kind=sp)

interface

  • public pure module subroutine stdlib_slaqsb(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
    real(kind=sp), intent(inout) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    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_slar2v(n, x, y, z, incx, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: x(*)
    real(kind=sp), intent(inout) :: y(*)
    real(kind=sp), intent(inout) :: z(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_slarf(side, m, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    real(kind=sp), intent(in) :: tau
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_slarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    real(kind=sp), intent(in) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=sp), intent(out) :: work(ldwork,*)
    integer(kind=ilp), intent(in) :: ldwork

interface

  • public pure module subroutine stdlib_slarfg(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: alpha
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(out) :: tau

interface

  • public module subroutine stdlib_slarfgp(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: alpha
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(out) :: tau

interface

  • public pure module subroutine stdlib_slarft(direct, storev, n, k, v, ldv, tau, t, ldt)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    real(kind=sp), intent(in) :: tau(*)
    real(kind=sp), intent(out) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt

interface

  • public pure module subroutine stdlib_slarfx(side, m, n, v, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: v(*)
    real(kind=sp), intent(in) :: tau
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_slarfy(uplo, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    real(kind=sp), intent(in) :: tau
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=sp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_slargv(n, x, incx, y, incy, c, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(out) :: c(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_slarnv(idist, iseed, n, x)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: idist
    integer(kind=ilp), intent(inout) :: iseed(4_ilp)
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(out) :: x(*)

interface

  • public pure module subroutine stdlib_slartg(f, g, c, s, r)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: f
    real(kind=sp), intent(in) :: g
    real(kind=sp), intent(out) :: c
    real(kind=sp), intent(out) :: s
    real(kind=sp), intent(out) :: r

interface

  • public pure module subroutine stdlib_slartgp(f, g, cs, sn, r)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: f
    real(kind=sp), intent(in) :: g
    real(kind=sp), intent(out) :: cs
    real(kind=sp), intent(out) :: sn
    real(kind=sp), intent(out) :: r

interface

  • public pure module subroutine stdlib_slartv(n, x, incx, y, incy, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_slaruv(iseed, n, x)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(inout) :: iseed(4_ilp)
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(out) :: x(n)

interface

  • public pure module subroutine stdlib_slascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: type
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=sp), intent(in) :: cfrom
    real(kind=sp), intent(in) :: cto
    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) :: info

interface

  • public pure module subroutine stdlib_slaset(uplo, m, n, alpha, beta, a, lda)

    Arguments

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

interface

  • public pure module subroutine stdlib_slasr(side, pivot, direct, m, n, c, s, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: pivot
    character(len=1), intent(in) :: direct
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: c(*)
    real(kind=sp), intent(in) :: s(*)
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

interface

  • public pure module subroutine stdlib_slasrt(id, n, d, info)

    Arguments

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

interface

  • public pure module subroutine stdlib_slassq(n, x, incx, scl, sumsq)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: scl
    real(kind=sp), intent(inout) :: sumsq

interface

  • public pure module subroutine stdlib_srscl(n, sa, sx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sa
    real(kind=sp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_ssfrk(transr, uplo, trans, n, k, alpha, a, lda, beta, c)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(*)

interface

  • public pure module subroutine stdlib_stfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: a(0_ilp:*)
    real(kind=sp), intent(inout) :: b(0_ilp:ldb-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_stfttp(transr, uplo, n, arf, ap, 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(in) :: arf(0_ilp:*)
    real(kind=sp), intent(out) :: ap(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stfttr(transr, uplo, n, arf, a, lda, 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(in) :: arf(0_ilp:*)
    real(kind=sp), intent(out) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stpttf(transr, uplo, n, ap, arf, 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(in) :: ap(0_ilp:*)
    real(kind=sp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_stpttr(uplo, n, ap, a, lda, 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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_strttf(transr, uplo, n, a, lda, arf, 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(in) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_strttp(uplo, n, a, lda, ap, 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) :: ap(*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_zdrscl(n, sa, sx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: sa
    complex(kind=dp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_zhfrk(transr, uplo, trans, n, k, alpha, a, lda, beta, c)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(*)

interface

  • public module subroutine stdlib_zla_gbamv(trans, m, n, kl, ku, alpha, ab, ldab, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    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) :: alpha
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public module subroutine stdlib_zla_geamv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public module subroutine stdlib_zla_heamv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_zla_wwaddw(n, x, y, w)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: x(*)
    complex(kind=dp), intent(inout) :: y(*)
    complex(kind=dp), intent(in) :: w(*)

interface

  • public pure module subroutine stdlib_zlacgv(n, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx

interface

  • public pure module subroutine stdlib_zlacp2(uplo, m, n, a, lda, b, ldb)

    Arguments

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

interface

  • public pure module subroutine stdlib_zlacpy(uplo, m, n, a, lda, b, ldb)

    Arguments

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

interface

  • public pure module subroutine stdlib_zlacrm(m, n, a, lda, b, ldb, c, ldc, rwork)

    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(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=dp), intent(out) :: rwork(*)

interface

  • public pure module subroutine stdlib_zlacrt(n, cx, incx, cy, incy, c, s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(in) :: c
    complex(kind=dp), intent(in) :: s

interface

  • public pure module function stdlib_zladiv(x, y)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: x
    complex(kind=dp), intent(in) :: y

    Return Value complex(kind=dp)

interface

  • public pure module subroutine stdlib_zlagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)

    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) :: alpha
    complex(kind=dp), intent(in) :: dl(*)
    complex(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: du(*)
    complex(kind=dp), intent(in) :: x(ldx,*)
    integer(kind=ilp), intent(in) :: ldx
    real(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public module function stdlib_zlangb(norm, n, kl, ku, ab, ldab, work)

    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
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlange(norm, m, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_zlangt(norm, n, dl, d, du)

    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(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlanhb(norm, uplo, n, k, ab, ldab, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlanhe(norm, uplo, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlanhf(norm, transr, uplo, n, a, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlanhp(norm, uplo, n, ap, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlanhs(norm, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public pure module function stdlib_zlanht(norm, n, d, e)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: d(*)
    complex(kind=dp), intent(in) :: e(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlansb(norm, uplo, n, k, ab, ldab, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: norm
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlansp(norm, uplo, n, ap, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlansy(norm, uplo, n, a, lda, work)

    Arguments

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

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlantb(norm, uplo, diag, n, k, ab, ldab, work)

    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) :: k
    complex(kind=dp), intent(in) :: ab(ldab,*)
    integer(kind=ilp), intent(in) :: ldab
    real(kind=dp), intent(out) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlantp(norm, uplo, diag, n, ap, work)

    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) :: work(*)

    Return Value real(kind=dp)

interface

  • public module function stdlib_zlantr(norm, uplo, diag, m, n, a, lda, work)

    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) :: 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) :: work(*)

    Return Value real(kind=dp)

interface

  • public pure module subroutine stdlib_zlaqsb(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(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_zlar2v(n, x, y, z, incx, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: x(*)
    complex(kind=dp), intent(inout) :: y(*)
    complex(kind=dp), intent(inout) :: z(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: c(*)
    complex(kind=dp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_zlarcm(m, n, a, lda, b, ldb, c, ldc, rwork)

    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
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(out) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    real(kind=dp), intent(out) :: rwork(*)

interface

  • public pure module subroutine stdlib_zlarf(side, m, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    complex(kind=dp), intent(in) :: tau
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_zlarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    complex(kind=dp), intent(in) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=dp), intent(out) :: work(ldwork,*)
    integer(kind=ilp), intent(in) :: ldwork

interface

  • public pure module subroutine stdlib_zlarfg(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: alpha
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(out) :: tau

interface

  • public module subroutine stdlib_zlarfgp(n, alpha, x, incx, tau)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: alpha
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(out) :: tau

interface

  • public pure module subroutine stdlib_zlarft(direct, storev, n, k, v, ldv, tau, t, ldt)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: direct
    character(len=1), intent(in) :: storev
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: v(ldv,*)
    integer(kind=ilp), intent(in) :: ldv
    complex(kind=dp), intent(in) :: tau(*)
    complex(kind=dp), intent(out) :: t(ldt,*)
    integer(kind=ilp), intent(in) :: ldt

interface

  • public pure module subroutine stdlib_zlarfx(side, m, n, v, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: v(*)
    complex(kind=dp), intent(in) :: tau
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_zlarfy(uplo, n, v, incv, tau, c, ldc, work)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: v(*)
    integer(kind=ilp), intent(in) :: incv
    complex(kind=dp), intent(in) :: tau
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
    complex(kind=dp), intent(out) :: work(*)

interface

  • public pure module subroutine stdlib_zlargv(n, x, incx, y, incy, c, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(out) :: c(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_zlarnv(idist, iseed, n, x)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: idist
    integer(kind=ilp), intent(inout) :: iseed(4_ilp)
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(out) :: x(*)

interface

  • public pure module subroutine stdlib_zlartg(f, g, c, s, r)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: f
    complex(kind=dp), intent(in) :: g
    real(kind=dp), intent(out) :: c
    complex(kind=dp), intent(out) :: s
    complex(kind=dp), intent(out) :: r

interface

  • public pure module subroutine stdlib_zlartv(n, x, incx, y, incy, c, s, incc)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: c(*)
    complex(kind=dp), intent(in) :: s(*)
    integer(kind=ilp), intent(in) :: incc

interface

  • public pure module subroutine stdlib_zlascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: type
    integer(kind=ilp), intent(in) :: kl
    integer(kind=ilp), intent(in) :: ku
    real(kind=dp), intent(in) :: cfrom
    real(kind=dp), intent(in) :: cto
    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) :: info

interface

  • public pure module subroutine stdlib_zlaset(uplo, m, n, alpha, beta, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(out) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

interface

  • public pure module subroutine stdlib_zlasr(side, pivot, direct, m, n, c, s, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: pivot
    character(len=1), intent(in) :: direct
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: c(*)
    real(kind=dp), intent(in) :: s(*)
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

interface

  • public pure module subroutine stdlib_zlassq(n, x, incx, scl, sumsq)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: scl
    real(kind=dp), intent(inout) :: sumsq

interface

  • public pure module subroutine stdlib_zrot(n, cx, incx, cy, incy, c, s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: c
    complex(kind=dp), intent(in) :: s

interface

  • public pure module subroutine stdlib_zspmv(uplo, n, alpha, ap, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_zspr(uplo, n, alpha, x, incx, ap)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: ap(*)

interface

  • public pure module subroutine stdlib_zsymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: y(*)
    integer(kind=ilp), intent(in) :: incy

interface

  • public pure module subroutine stdlib_zsyr(uplo, n, alpha, x, incx, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

interface

  • public pure module subroutine stdlib_ztfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transr
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(0_ilp:*)
    complex(kind=dp), intent(inout) :: b(0_ilp:ldb-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: ldb

interface

  • public pure module subroutine stdlib_ztfttp(transr, uplo, n, arf, ap, 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(in) :: arf(0_ilp:*)
    complex(kind=dp), intent(out) :: ap(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztfttr(transr, uplo, n, arf, a, lda, 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(in) :: arf(0_ilp:*)
    complex(kind=dp), intent(out) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztpttf(transr, uplo, n, ap, arf, 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(in) :: ap(0_ilp:*)
    complex(kind=dp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

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

    Arguments

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

interface

  • public pure module subroutine stdlib_ztrttf(transr, uplo, n, a, lda, arf, 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(in) :: a(0_ilp:lda-1,0_ilp:*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(out) :: arf(0_ilp:*)
    integer(kind=ilp), intent(out) :: info

interface

  • public pure module subroutine stdlib_ztrttp(uplo, n, a, lda, ap, 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
    complex(kind=dp), intent(out) :: ap(*)
    integer(kind=ilp), intent(out) :: info