stdlib_linalg_blas Module



Interfaces

public interface axpy

AXPY constant times a vector plus a vector.

  • public pure subroutine caxpy(n, ca, cx, incx, cy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ca
    complex(kind=sp), intent(in) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(inout) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine daxpy(n, da, dx, incx, dy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: da
    real(kind=dp), intent(in) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine saxpy(n, sa, sx, incx, sy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sa
    real(kind=sp), intent(in) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine zaxpy(n, za, zx, incx, zy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: za
    complex(kind=dp), intent(in) :: zx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: zy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_caxpy(n, ca, cx, incx, cy, incy)

    CAXPY constant times a vector plus a vector.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ca
    complex(kind=sp), intent(in) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(inout) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_daxpy(n, da, dx, incx, dy, incy)

    DAXPY constant times a vector plus a vector. uses unrolled loops for increments equal to one.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: da
    real(kind=dp), intent(in) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_saxpy(n, sa, sx, incx, sy, incy)

    SAXPY constant times a vector plus a vector. uses unrolled loops for increments equal to one.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sa
    real(kind=sp), intent(in) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_zaxpy(n, za, zx, incx, zy, incy)

    ZAXPY constant times a vector plus a vector.

    Arguments

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

public interface copy

COPY copies a vector x to a vector y.

  • public pure subroutine ccopy(n, cx, incx, cy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(out) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine dcopy(n, dx, incx, dy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(out) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine scopy(n, sx, incx, sy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(out) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine zcopy(n, zx, incx, zy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: zx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(out) :: zy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_ccopy(n, cx, incx, cy, incy)

    CCOPY copies a vector x to a vector y.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=sp), intent(out) :: cy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_dcopy(n, dx, incx, dy, incy)

    DCOPY copies a vector, x, to a vector, y. uses unrolled loops for increments equal to 1.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(out) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_scopy(n, sx, incx, sy, incy)

    SCOPY copies a vector, x, to a vector, y. uses unrolled loops for increments equal to 1.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(out) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_zcopy(n, zx, incx, zy, incy)

    ZCOPY copies a vector, x, to a vector, y.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: zx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(out) :: zy(*)
    integer(kind=ilp), intent(in) :: incy

public interface dot

DOT forms the dot product of two vectors. uses unrolled loops for increments equal to one.

  • public pure function ddot(n, dx, incx, dy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: dy(*)
    integer(kind=ilp), intent(in) :: incy

    Return Value real(kind=dp)

  • public pure function sdot(n, sx, incx, sy, incy)

    Arguments

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

    Return Value real(kind=sp)

  • public pure function stdlib_ddot(n, dx, incx, dy, incy)

    DDOT forms the dot product of two vectors. uses unrolled loops for increments equal to one.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: dy(*)
    integer(kind=ilp), intent(in) :: incy

    Return Value real(kind=dp)

  • public pure function stdlib_sdot(n, sx, incx, sy, incy)

    SDOT forms the dot product of two vectors. uses unrolled loops for increments equal to one.

    Arguments

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

    Return Value real(kind=sp)

public interface dotc

DOTC forms the dot product of two complex vectors DOTC = X^H * Y

  • public pure function cdotc(n, cx, incx, cy, incy)

    Arguments

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

    Return Value complex(kind=sp)

  • public pure function zdotc(n, zx, incx, zy, incy)

    Arguments

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

    Return Value complex(kind=dp)

  • public pure function stdlib_cdotc(n, cx, incx, cy, incy)

    CDOTC forms the dot product of two complex vectors CDOTC = X^H * Y

    Arguments

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

    Return Value complex(kind=sp)

  • public pure function stdlib_zdotc(n, zx, incx, zy, incy)

    ZDOTC forms the dot product of two complex vectors ZDOTC = X^H * Y

    Arguments

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

    Return Value complex(kind=dp)

public interface dotu

DOTU forms the dot product of two complex vectors DOTU = X^T * Y

  • public pure function cdotu(n, cx, incx, cy, incy)

    Arguments

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

    Return Value complex(kind=sp)

  • public pure function zdotu(n, zx, incx, zy, incy)

    Arguments

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

    Return Value complex(kind=dp)

  • public pure function stdlib_cdotu(n, cx, incx, cy, incy)

    CDOTU forms the dot product of two complex vectors CDOTU = X^T * Y

    Arguments

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

    Return Value complex(kind=sp)

  • public pure function stdlib_zdotu(n, zx, incx, zy, incy)

    ZDOTU forms the dot product of two complex vectors ZDOTU = X^T * Y

    Arguments

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

    Return Value complex(kind=dp)

public interface gbmv

GBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals.

  • public pure subroutine cgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
    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
  • public pure subroutine dgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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) :: 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
  • public pure subroutine sgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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) :: 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
  • public pure subroutine zgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
    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
  • public pure subroutine stdlib_cgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    CGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
    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
  • public pure subroutine stdlib_dgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    DGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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) :: 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
  • public pure subroutine stdlib_sgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    SGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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) :: 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
  • public pure subroutine stdlib_zgbmv(trans, m, n, kl, ku, alpha, a, lda, x, incx, beta, y, incy)

    ZGBMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n band matrix, with kl sub-diagonals and ku super-diagonals.

    Arguments

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

public interface gemm

GEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.

  • public pure subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    CGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    DGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = X*T, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    SGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = X*T, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    ZGEMM performs one of the matrix-matrix operations C := alphaop( A )op( B ) + betaC, where op( X ) is one of op( X ) = X or op( X ) = XT or op( X ) = X*H, alpha and beta are scalars, and A, B and C are matrices, with op( A ) an m by k matrix, op( B ) a k by n matrix and C an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: transa
    character(len=1), intent(in) :: transb
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc

public interface gemv

GEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.

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

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    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
  • public pure subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
  • public pure subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
  • public pure subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    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
  • public pure subroutine stdlib_cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    CGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: m
    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
  • public pure subroutine stdlib_dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    DGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
  • public pure subroutine stdlib_sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    SGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), 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
  • public pure subroutine stdlib_zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)

    ZGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, or y := alpha*AHx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.

    Arguments

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

public interface ger

GER performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

  • public pure subroutine dger(m, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine sger(m, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_dger(m, n, alpha, x, incx, y, incy, a, lda)

    DGER performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_sger(m, n, alpha, x, incx, y, incy, a, lda)

    SGER performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

    Arguments

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

public interface gerc

GERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

  • public pure subroutine cgerc(m, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine zgerc(m, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_cgerc(m, n, alpha, x, incx, y, incy, a, lda)

    CGERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_zgerc(m, n, alpha, x, incx, y, incy, a, lda)

    ZGERC performs the rank 1 operation A := alphaxy**H + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

public interface geru

GERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

  • public pure subroutine cgeru(m, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine zgeru(m, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_cgeru(m, n, alpha, x, incx, y, incy, a, lda)

    CGERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_zgeru(m, n, alpha, x, incx, y, incy, a, lda)

    ZGERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: m
    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

public interface hbmv

HBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals.

  • public pure subroutine chbmv(uplo, n, k, 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
    integer(kind=ilp), intent(in) :: k
    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
  • public pure subroutine zhbmv(uplo, n, k, 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
    integer(kind=ilp), intent(in) :: k
    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
  • public pure subroutine stdlib_chbmv(uplo, n, k, alpha, a, lda, x, incx, beta, y, incy)

    CHBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    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
  • public pure subroutine stdlib_zhbmv(uplo, n, k, alpha, a, lda, x, incx, beta, y, incy)

    ZHBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian band matrix, with k super-diagonals.

    Arguments

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

public interface hemm

HEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices.

  • public pure subroutine chemm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zhemm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_chemm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    CHEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zhemm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    ZHEMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is an hermitian matrix and B and C are m by n matrices.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc

public interface hemv

HEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix.

  • public pure subroutine chemv(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
  • public pure subroutine zhemv(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
  • public pure subroutine stdlib_chemv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    CHEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix.

    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
  • public pure subroutine stdlib_zhemv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    ZHEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix.

    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

public interface her

HER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix.

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

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(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
  • public pure subroutine zher(uplo, n, alpha, x, incx, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(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
  • public pure subroutine stdlib_cher(uplo, n, alpha, x, incx, a, lda)

    CHER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(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
  • public pure subroutine stdlib_zher(uplo, n, alpha, x, incx, a, lda)

    ZHER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix.

    Arguments

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

public interface her2

HER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix.

  • public pure subroutine cher2(uplo, n, alpha, x, incx, y, incy, 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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine zher2(uplo, n, alpha, x, incx, y, incy, 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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_cher2(uplo, n, alpha, x, incx, y, incy, a, lda)

    CHER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix.

    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_zher2(uplo, n, alpha, x, incx, y, incy, a, lda)

    ZHER2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix.

    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda

public interface her2k

HER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

  • public pure subroutine cher2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zher2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_cher2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    CHER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zher2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    ZHER2K performs one of the hermitian rank 2k operations C := alphaABH + conjg( alpha )BAH + betaC, or C := alphaAHB + conjg( alpha )BHA + betaC, where alpha and beta are scalars with beta real, C is an n by n hermitian matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

    Arguments

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

public interface herk

HERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

  • public pure subroutine cherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_cherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    CHERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    ZHERK performs one of the hermitian rank k operations C := alphaAAH + betaC, or C := alphaAHA + betaC, where alpha and beta are real scalars, C is an n by n hermitian matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc

public interface hpmv

HPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.

  • public pure subroutine chpmv(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
  • public pure subroutine zhpmv(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
  • public pure subroutine stdlib_chpmv(uplo, n, alpha, ap, x, incx, beta, y, incy)

    CHPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.

    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
  • public pure subroutine stdlib_zhpmv(uplo, n, alpha, ap, x, incx, beta, y, incy)

    ZHPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.

    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

public interface hpr

HPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form.

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

    Arguments

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

    Arguments

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

    CHPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form.

    Arguments

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

    ZHPR performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector and A is an n by n hermitian matrix, supplied in packed form.

    Arguments

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

public interface hpr2

HPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.

  • public pure subroutine chpr2(uplo, n, alpha, x, incx, y, incy, 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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: ap(*)
  • public pure subroutine zhpr2(uplo, n, alpha, x, incx, y, incy, 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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: ap(*)
  • public pure subroutine stdlib_chpr2(uplo, n, alpha, x, incx, y, incy, ap)

    CHPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.

    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=sp), intent(inout) :: ap(*)
  • public pure subroutine stdlib_zhpr2(uplo, n, alpha, x, incx, y, incy, ap)

    ZHPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.

    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(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    complex(kind=dp), intent(inout) :: ap(*)

public interface nrm2

NRM2 returns the euclidean norm of a vector via the function name, so that NRM2 := sqrt( x'*x )

  • public pure function dnrm2(n, x, incx)

    Arguments

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

    Return Value real(kind=dp)

  • public pure function snrm2(n, x, incx)

    Arguments

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

    Return Value real(kind=sp)

  • public pure function stdlib_dnrm2(n, x, incx)

    DNRM2 returns the euclidean norm of a vector via the function name, so that DNRM2 := sqrt( x'*x )

    Arguments

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

    Return Value real(kind=dp)

  • public pure function stdlib_snrm2(n, x, incx)

    SNRM2 returns the euclidean norm of a vector via the function name, so that SNRM2 := sqrt( x'*x ).

    Arguments

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

    Return Value real(kind=sp)

public interface rot

ROT applies a plane rotation.

  • public pure subroutine drot(n, dx, incx, dy, incy, c, s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: c
    real(kind=dp), intent(in) :: s
  • public pure subroutine srot(n, sx, incx, sy, incy, c, s)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(in) :: c
    real(kind=sp), intent(in) :: s
  • public pure subroutine stdlib_drot(n, dx, incx, dy, incy, c, s)

    DROT applies a plane rotation.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: c
    real(kind=dp), intent(in) :: s
  • public pure subroutine stdlib_srot(n, sx, incx, sy, incy, c, s)

    applies a plane rotation.

    Arguments

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

public interface rotg

The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in SROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by SROTG if the signs of a and b are not the same.

  • public pure subroutine crotg(a, b, c, s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout) :: a
    complex(kind=sp), intent(in) :: b
    real(kind=sp), intent(out) :: c
    complex(kind=sp), intent(out) :: s
  • public pure subroutine drotg(a, b, c, s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: a
    real(kind=dp), intent(inout) :: b
    real(kind=dp), intent(out) :: c
    real(kind=dp), intent(out) :: s
  • public pure subroutine srotg(a, b, c, s)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: a
    real(kind=sp), intent(inout) :: b
    real(kind=sp), intent(out) :: c
    real(kind=sp), intent(out) :: s
  • public pure subroutine zrotg(a, b, c, s)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout) :: a
    complex(kind=dp), intent(in) :: b
    real(kind=dp), intent(out) :: c
    complex(kind=dp), intent(out) :: s
  • public pure subroutine stdlib_crotg(a, b, c, s)

    The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in SROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by SROTG if the signs of a and b are not the same.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout) :: a
    complex(kind=sp), intent(in) :: b
    real(kind=sp), intent(out) :: c
    complex(kind=sp), intent(out) :: s
  • public pure subroutine stdlib_drotg(a, b, c, s)

    The computation uses the formulas sigma = sgn(a) if |a| > |b| = sgn(b) if |b| >= |a| r = sigmasqrt( a2 + b2 ) c = 1; s = 0 if r = 0 c = a/r; s = b/r if r != 0 The subroutine also computes z = s if |a| > |b|, = 1/c if |b| >= |a| and c != 0 = 1 if c = 0 This allows c and s to be reconstructed from z as follows: If z = 1, set c = 0, s = 1. If |z| < 1, set c = sqrt(1 - z2) and s = z. If |z| > 1, set c = 1/z and s = sqrt( 1 - c*2).

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: a
    real(kind=dp), intent(inout) :: b
    real(kind=dp), intent(out) :: c
    real(kind=dp), intent(out) :: s
  • public pure subroutine stdlib_srotg(a, b, c, s)

    The computation uses the formulas sigma = sgn(a) if |a| > |b| = sgn(b) if |b| >= |a| r = sigmasqrt( a2 + b2 ) c = 1; s = 0 if r = 0 c = a/r; s = b/r if r != 0 The subroutine also computes z = s if |a| > |b|, = 1/c if |b| >= |a| and c != 0 = 1 if c = 0 This allows c and s to be reconstructed from z as follows: If z = 1, set c = 0, s = 1. If |z| < 1, set c = sqrt(1 - z2) and s = z. If |z| > 1, set c = 1/z and s = sqrt( 1 - c*2).

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: a
    real(kind=sp), intent(inout) :: b
    real(kind=sp), intent(out) :: c
    real(kind=sp), intent(out) :: s
  • public pure subroutine stdlib_zrotg(a, b, c, s)

    The computation uses the formulas |x| = sqrt( Re(x)2 + Im(x)2 ) sgn(x) = x / |x| if x /= 0 = 1 if x = 0 c = |a| / sqrt(|a|2 + |b|2) s = sgn(a) * conjg(b) / sqrt(|a|2 + |b|2) When a and b are real and r /= 0, the formulas simplify to r = sgn(a)sqrt(|a|2 + |b|*2) c = a / r s = b / r the same as in DROTG when |a| > |b|. When |b| >= |a|, the sign of c and s will be different from those computed by DROTG if the signs of a and b are not the same.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout) :: a
    complex(kind=dp), intent(in) :: b
    real(kind=dp), intent(out) :: c
    complex(kind=dp), intent(out) :: s

public interface rotm

ROTM applies the modified Givens transformation, , to the 2-by-N matrix where indicates transpose. The elements of are in DX(LX+IINCX), I = 0:N-1, where LX = 1 if INCX >= 0, else LX = (-INCX)N, and similarly for DY using LY and INCY. With DPARAM(1)=DFLAG, has one of the following forms:
See ROTMG for a description of data storage in DPARAM.

  • public pure subroutine drotm(n, dx, incx, dy, incy, dparam)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: dparam(5)
  • public pure subroutine srotm(n, sx, incx, sy, incy, sparam)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(in) :: sparam(5)
  • public pure subroutine stdlib_drotm(n, dx, incx, dy, incy, dparam)

    DROTM applies the modified Givens transformation, , to the 2-by-N matrix where indicates transpose. The elements of are in DX(LX+IINCX), I = 0:N-1, where LX = 1 if INCX >= 0, else LX = (-INCX)N, and similarly for DY using LY and INCY. With DPARAM(1)=DFLAG, has one of the following forms:
    See DROTMG for a description of data storage in DPARAM.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(in) :: dparam(5)
  • public pure subroutine stdlib_srotm(n, sx, incx, sy, incy, sparam)

    SROTM applies the modified Givens transformation, , to the 2-by-N matrix where indicates transpose. The elements of are in SX(LX+IINCX), I = 0:N-1, where LX = 1 if INCX >= 0, else LX = (-INCX)N, and similarly for SY using LY and INCY. With SPARAM(1)=SFLAG, has one of the following forms:
    See SROTMG for a description of data storage in SPARAM.

    Arguments

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

public interface rotmg

ROTMG Constructs the modified Givens transformation matrix which zeros the second component of the 2-vector With DPARAM(1)=DFLAG, has one of the following forms:
Locations 2-4 of DPARAM contain DH11, DH21, DH12 and DH22 respectively. (Values of 1.0, -1.0, or 0.0 implied by the value of DPARAM(1) are not stored in DPARAM.) The values of parameters GAMSQ and RGAMSQ may be inexact. This is OK as they are only used for testing the size of DD1 and DD2. All actual scaling of data is done using GAM.

  • public pure subroutine drotmg(dd1, dd2, dx1, dy1, dparam)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: dd1
    real(kind=dp), intent(inout) :: dd2
    real(kind=dp), intent(inout) :: dx1
    real(kind=dp), intent(in) :: dy1
    real(kind=dp), intent(out) :: dparam(5)
  • public pure subroutine srotmg(sd1, sd2, sx1, sy1, sparam)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: sd1
    real(kind=sp), intent(inout) :: sd2
    real(kind=sp), intent(inout) :: sx1
    real(kind=sp), intent(in) :: sy1
    real(kind=sp), intent(out) :: sparam(5)
  • public pure subroutine stdlib_drotmg(dd1, dd2, dx1, dy1, dparam)

    DROTMG Constructs the modified Givens transformation matrix which zeros the second component of the 2-vector With DPARAM(1)=DFLAG, has one of the following forms:
    Locations 2-4 of DPARAM contain DH11, DH21, DH12 and DH22 respectively. (Values of 1.0, -1.0, or 0.0 implied by the value of DPARAM(1) are not stored in DPARAM.) The values of parameters GAMSQ and RGAMSQ may be inexact. This is OK as they are only used for testing the size of DD1 and DD2. All actual scaling of data is done using GAM.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: dd1
    real(kind=dp), intent(inout) :: dd2
    real(kind=dp), intent(inout) :: dx1
    real(kind=dp), intent(in) :: dy1
    real(kind=dp), intent(out) :: dparam(5)
  • public pure subroutine stdlib_srotmg(sd1, sd2, sx1, sy1, sparam)

    SROTMG Constructs the modified Givens transformation matrix which zeros the second component of the 2-vector With SPARAM(1)=SFLAG, has one of the following forms:
    Locations 2-4 of SPARAM contain SH11, SH21, SH12 and SH22 respectively. (Values of 1.0, -1.0, or 0.0 implied by the value of SPARAM(1) are not stored in SPARAM.) The values of parameters GAMSQ and RGAMSQ may be inexact. This is OK as they are only used for testing the size of DD1 and DD2. All actual scaling of data is done using GAM.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: sd1
    real(kind=sp), intent(inout) :: sd2
    real(kind=sp), intent(inout) :: sx1
    real(kind=sp), intent(in) :: sy1
    real(kind=sp), intent(out) :: sparam(5)

public interface sbmv

SBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric band matrix, with k super-diagonals.

  • public pure subroutine dsbmv(uplo, n, k, 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
    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) :: 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
  • public pure subroutine ssbmv(uplo, n, k, 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
    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) :: 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
  • public pure subroutine stdlib_dsbmv(uplo, n, k, alpha, a, lda, x, incx, beta, y, incy)

    DSBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric band matrix, with k super-diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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) :: 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
  • public pure subroutine stdlib_ssbmv(uplo, n, k, alpha, a, lda, x, incx, beta, y, incy)

    SSBMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric band matrix, with k super-diagonals.

    Arguments

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

public interface scal

SCAL scales a vector by a constant.

  • public pure subroutine cscal(n, ca, cx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ca
    complex(kind=sp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dscal(n, da, dx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: da
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine sscal(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
  • public pure subroutine zscal(n, za, zx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: za
    complex(kind=dp), intent(inout) :: zx(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_cscal(n, ca, cx, incx)

    CSCAL scales a vector by a constant.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ca
    complex(kind=sp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dscal(n, da, dx, incx)

    DSCAL scales a vector by a constant. uses unrolled loops for increment equal to 1.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: da
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_sscal(n, sa, sx, incx)

    SSCAL scales a vector by a constant. uses unrolled loops for increment equal to 1.

    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
  • public pure subroutine stdlib_zscal(n, za, zx, incx)

    ZSCAL scales a vector by a constant.

    Arguments

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

public interface sdot

Compute the inner product of two vectors with extended precision accumulation and result. Returns D.P. dot product accumulated in D.P., for S.P. SX and SY SDOT = sum for I = 0 to N-1 of SX(LX+IINCX) * SY(LY+IINCY), where LX = 1 if INCX >= 0, else LX = 1+(1-N)*INCX, and LY is defined in a similar way using INCY.

  • public pure function dsdot(n, sx, incx, sy, incy)

    Arguments

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

    Return Value real(kind=dp)

  • public pure function stdlib_dsdot(n, sx, incx, sy, incy)

    Compute the inner product of two vectors with extended precision accumulation and result. Returns D.P. dot product accumulated in D.P., for S.P. SX and SY DSDOT = sum for I = 0 to N-1 of SX(LX+IINCX) * SY(LY+IINCY), where LX = 1 if INCX >= 0, else LX = 1+(1-N)*INCX, and LY is defined in a similar way using INCY.

    Arguments

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

    Return Value real(kind=dp)

public interface spmv

SPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form.

  • public pure subroutine dspmv(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
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: ap(*)
    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
  • public pure subroutine sspmv(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
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: ap(*)
    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
  • public pure subroutine stdlib_dspmv(uplo, n, alpha, ap, x, incx, beta, y, incy)

    DSPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: ap(*)
    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
  • public pure subroutine stdlib_sspmv(uplo, n, alpha, ap, x, incx, beta, y, incy)

    SSPMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form.

    Arguments

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

public interface spr

SPR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix, supplied in packed form.

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

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: ap(*)
  • public pure subroutine sspr(uplo, n, alpha, x, incx, ap)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: ap(*)
  • public pure subroutine stdlib_dspr(uplo, n, alpha, x, incx, ap)

    DSPR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix, supplied in packed form.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: ap(*)
  • public pure subroutine stdlib_sspr(uplo, n, alpha, x, incx, ap)

    SSPR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix, supplied in packed form.

    Arguments

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

public interface spr2

SPR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form.

  • public pure subroutine dspr2(uplo, n, alpha, x, incx, y, incy, ap)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(inout) :: ap(*)
  • public pure subroutine sspr2(uplo, n, alpha, x, incx, y, incy, ap)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(inout) :: ap(*)
  • public pure subroutine stdlib_dspr2(uplo, n, alpha, x, incx, y, incy, ap)

    DSPR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(inout) :: ap(*)
  • public pure subroutine stdlib_sspr2(uplo, n, alpha, x, incx, y, incy, ap)

    SSPR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix, supplied in packed form.

    Arguments

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

public interface srot

SROT applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78.

  • public pure subroutine csrot(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
    real(kind=sp), intent(in) :: s
  • public pure subroutine stdlib_csrot(n, cx, incx, cy, incy, c, s)

    CSROT applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78.

    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
    real(kind=sp), intent(in) :: s

public interface sscal

SSCAL scales a complex vector by a real constant.

  • public pure subroutine csscal(n, sa, cx, incx)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: sa
    complex(kind=sp), intent(inout) :: cx(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_csscal(n, sa, cx, incx)

    CSSCAL scales a complex vector by a real constant.

    Arguments

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

public interface swap

SWAP interchanges two vectors.

  • public pure subroutine cswap(n, cx, incx, cy, incy)

    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
  • public pure subroutine dswap(n, dx, incx, dy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine sswap(n, sx, incx, sy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine zswap(n, zx, incx, zy, incy)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(inout) :: zx(*)
    integer(kind=ilp), intent(in) :: incx
    complex(kind=dp), intent(inout) :: zy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_cswap(n, cx, incx, cy, incy)

    CSWAP interchanges two vectors.

    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
  • public pure subroutine stdlib_dswap(n, dx, incx, dy, incy)

    DSWAP interchanges two vectors. uses unrolled loops for increments equal to 1.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(inout) :: dx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: dy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_sswap(n, sx, incx, sy, incy)

    SSWAP interchanges two vectors. uses unrolled loops for increments equal to 1.

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(inout) :: sx(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: sy(*)
    integer(kind=ilp), intent(in) :: incy
  • public pure subroutine stdlib_zswap(n, zx, incx, zy, incy)

    ZSWAP interchanges two vectors.

    Arguments

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

public interface symm

SYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices.

  • public pure subroutine csymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine dsymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine ssymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zsymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_csymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    CSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_dsymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    DSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_ssymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    SSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zsymm(side, uplo, m, n, alpha, a, lda, b, ldb, beta, c, ldc)

    ZSYMM performs one of the matrix-matrix operations C := alphaAB + betaC, or C := alphaBA + betaC, where alpha and beta are scalars, A is a symmetric matrix and B and C are m by n matrices.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    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) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc

public interface symv

SYMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix.

  • public pure subroutine dsymv(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
    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
  • public pure subroutine ssymv(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
    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
  • public pure subroutine stdlib_dsymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    DSYMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    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
  • public pure subroutine stdlib_ssymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)

    SSYMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n symmetric matrix.

    Arguments

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

public interface syr

SYR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix.

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

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine ssyr(uplo, n, alpha, x, incx, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_dsyr(uplo, n, alpha, x, incx, a, lda)

    DSYR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_ssyr(uplo, n, alpha, x, incx, a, lda)

    SSYR performs the symmetric rank 1 operation A := alphaxx**T + A, where alpha is a real scalar, x is an n element vector and A is an n by n symmetric matrix.

    Arguments

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

public interface syr2

SYR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix.

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

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine ssyr2(uplo, n, alpha, x, incx, y, incy, a, lda)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: alpha
    real(kind=sp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=sp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=sp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_dsyr2(uplo, n, alpha, x, incx, y, incy, a, lda)

    DSYR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: alpha
    real(kind=dp), intent(in) :: x(*)
    integer(kind=ilp), intent(in) :: incx
    real(kind=dp), intent(in) :: y(*)
    integer(kind=ilp), intent(in) :: incy
    real(kind=dp), intent(inout) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
  • public pure subroutine stdlib_ssyr2(uplo, n, alpha, x, incx, y, incy, a, lda)

    SSYR2 performs the symmetric rank 2 operation A := alphaxyT + alphayxT + A, where alpha is a scalar, x and y are n element vectors and A is an n by n symmetric matrix.

    Arguments

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

public interface syr2k

SYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

  • public pure subroutine csyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine dsyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine ssyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zsyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_csyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    CSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_dsyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    DSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

    Arguments

    Type IntentOptional Attributes Name
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=dp), intent(in) :: beta
    real(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_ssyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    SSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

    Arguments

    Type IntentOptional Attributes Name
    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) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
    real(kind=sp), intent(in) :: beta
    real(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zsyr2k(uplo, trans, n, k, alpha, a, lda, b, ldb, beta, c, ldc)

    ZSYR2K performs one of the symmetric rank 2k operations C := alphaABT + alphaBAT + betaC, or C := alphaATB + alphaBTA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A and B are n by k matrices in the first case and k by n matrices in the second case.

    Arguments

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

public interface syrk

SYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

  • public pure subroutine csyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine dsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine ssyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine zsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(in) :: beta
    complex(kind=dp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_csyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    CSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(in) :: beta
    complex(kind=sp), intent(inout) :: c(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_dsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    DSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_ssyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    SSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

    Arguments

    Type IntentOptional Attributes Name
    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(ldc,*)
    integer(kind=ilp), intent(in) :: ldc
  • public pure subroutine stdlib_zsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)

    ZSYRK performs one of the symmetric rank k operations C := alphaAAT + betaC, or C := alphaATA + betaC, where alpha and beta are scalars, C is an n by n symmetric matrix and A is an n by k matrix in the first case and a k by n matrix in the second case.

    Arguments

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

public interface tbmv

TBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.

  • public pure subroutine ctbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dtbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine ztbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ctbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    CTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dtbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    DTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_stbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    STBMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ztbmv(uplo, trans, diag, n, k, a, lda, x, incx)

    ZTBMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals.

    Arguments

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

public interface tbsv

TBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

  • public pure subroutine ctbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dtbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine ztbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ctbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    CTBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dtbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    DTBSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_stbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    STBSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    integer(kind=ilp), intent(in) :: k
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ztbsv(uplo, trans, diag, n, k, a, lda, x, incx)

    ZTBSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular band matrix, with ( k + 1 ) diagonals. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

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

public interface tpmv

TPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form.

  • public pure subroutine ctpmv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dtpmv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stpmv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine ztpmv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ctpmv(uplo, trans, diag, n, ap, x, incx)

    CTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dtpmv(uplo, trans, diag, n, ap, x, incx)

    DTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_stpmv(uplo, trans, diag, n, ap, x, incx)

    STPMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ztpmv(uplo, trans, diag, n, ap, x, incx)

    ZTPMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form.

    Arguments

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

public interface tpsv

TPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

  • public pure subroutine ctpsv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dtpsv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stpsv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine ztpsv(uplo, trans, diag, n, ap, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: ap(*)
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ctpsv(uplo, trans, diag, n, ap, x, incx)

    CTPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: ap(*)
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dtpsv(uplo, trans, diag, n, ap, x, incx)

    DTPSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: ap(*)
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_stpsv(uplo, trans, diag, n, ap, x, incx)

    STPSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: ap(*)
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ztpsv(uplo, trans, diag, n, ap, x, incx)

    ZTPSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix, supplied in packed form. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

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

public interface trmm

TRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH.

  • public pure subroutine ctrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine dtrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine strmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine ztrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_ctrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    CTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_dtrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    DTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ), where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_strmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    STRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ), where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_ztrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    ZTRMM performs one of the matrix-matrix operations B := alphaop( A )B, or B := alphaBop( A ) where alpha is a scalar, B is an m by n matrix, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH.

    Arguments

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

public interface trmv

TRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix.

  • public pure subroutine ctrmv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dtrmv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine strmv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine ztrmv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ctrmv(uplo, trans, diag, n, a, lda, x, incx)

    CTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dtrmv(uplo, trans, diag, n, a, lda, x, incx)

    DTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_strmv(uplo, trans, diag, n, a, lda, x, incx)

    STRMV performs one of the matrix-vector operations x := Ax, or x := ATx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ztrmv(uplo, trans, diag, n, a, lda, x, incx)

    ZTRMV performs one of the matrix-vector operations x := Ax, or x := ATx, or x := A*Hx, where x is an n element vector and A is an n by n unit, or non-unit, upper or lower triangular matrix.

    Arguments

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

public interface trsm

TRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B.

  • public pure subroutine ctrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine strsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine ztrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_ctrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    CTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    DTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T. The matrix X is overwritten on B.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_strsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    STRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = A**T. The matrix X is overwritten on B.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: side
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: transa
    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(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: b(ldb,*)
    integer(kind=ilp), intent(in) :: ldb
  • public pure subroutine stdlib_ztrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)

    ZTRSM solves one of the matrix equations op( A )X = alphaB, or Xop( A ) = alphaB, where alpha is a scalar, X and B are m by n matrices, A is a unit, or non-unit, upper or lower triangular matrix and op( A ) is one of op( A ) = A or op( A ) = AT or op( A ) = AH. The matrix X is overwritten on B.

    Arguments

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

public interface trsv

TRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

  • public pure subroutine ctrsv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine dtrsv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine strsv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine ztrsv(uplo, trans, diag, n, a, lda, x, incx)

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ctrsv(uplo, trans, diag, n, a, lda, x, incx)

    CTRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    complex(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    complex(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_dtrsv(uplo, trans, diag, n, a, lda, x, incx)

    DTRSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=dp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=dp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_strsv(uplo, trans, diag, n, a, lda, x, incx)

    STRSV solves one of the systems of equations Ax = b, or ATx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

    Type IntentOptional Attributes Name
    character(len=1), intent(in) :: uplo
    character(len=1), intent(in) :: trans
    character(len=1), intent(in) :: diag
    integer(kind=ilp), intent(in) :: n
    real(kind=sp), intent(in) :: a(lda,*)
    integer(kind=ilp), intent(in) :: lda
    real(kind=sp), intent(inout) :: x(*)
    integer(kind=ilp), intent(in) :: incx
  • public pure subroutine stdlib_ztrsv(uplo, trans, diag, n, a, lda, x, incx)

    ZTRSV solves one of the systems of equations Ax = b, or ATx = b, or A*Hx = b, where b and x are n element vectors and A is an n by n unit, or non-unit, upper or lower triangular matrix. No test for singularity or near-singularity is included in this routine. Such tests must be performed before calling this routine.

    Arguments

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