Stability | Experimental |
---|---|
Safe Haskell | None |
Language | Haskell98 |
Generic interface to Blas using unsafe foreign calls. Refer to the GHC documentation for more information regarding appropriate use of safe and unsafe foreign calls.
The functions here are named in a similar fashion to the original Blas interface, with
the type-dependent letter(s) removed. Some functions have been merged with
others to allow the interface to work on both real and complex numbers. If you can't a
particular function, try looking for its corresponding complex equivalent (e.g.
symv
is a special case of hemv
applied to real numbers).
Note: although complex versions of rot
and rotg
exist in many implementations,
they are not part of the official Blas standard and therefore not included here. If
you really need them, submit a ticket so we can try to come up with a solution.
The documentation here is still incomplete. Consult the official documentation for more information.
Notation:
⋅
denotes dot product (without any conjugation).*
denotes complex conjugation.⊤
denotes transpose.†
denotes conjugate transpose (Hermitian conjugate).
Conventions:
- All scalars are denoted with lowercase Greek letters
- All vectors are denoted with lowercase Latin letters and are assumed to be column vectors (unless transposed).
- All matrices are denoted with uppercase Latin letters.
Since: 0.1.1
- swap :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- scal :: Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- copy :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- axpy :: Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- dotu :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO (Complex Double)
- dotc :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO (Complex Double)
- nrm2 :: Int -> Ptr (Complex Double) -> Int -> IO Double
- asum :: Int -> Ptr (Complex Double) -> Int -> IO Double
- iamax :: Int -> Ptr (Complex Double) -> Int -> IO Int
- gemv :: Order -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- gbmv :: Order -> Transpose -> Int -> Int -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- hemv :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- hbmv :: Order -> Uplo -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- hpmv :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- trmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- tbmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- tpmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Ptr (Complex Double) -> Int -> IO ()
- trsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- tbsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- tpsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Ptr (Complex Double) -> Int -> IO ()
- geru :: Order -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- gerc :: Order -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- her :: Order -> Uplo -> Int -> Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- hpr :: Order -> Uplo -> Int -> Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> IO ()
- her2 :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- hpr2 :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> IO ()
- gemm :: Order -> Transpose -> Transpose -> Int -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- symm :: Order -> Side -> Uplo -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- hemm :: Order -> Side -> Uplo -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- syrk :: Order -> Uplo -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- herk :: Order -> Uplo -> Transpose -> Int -> Int -> Double -> Ptr (Complex Double) -> Int -> Double -> Ptr (Complex Double) -> Int -> IO ()
- syr2k :: Order -> Uplo -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO ()
- her2k :: Order -> Uplo -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Double -> Ptr (Complex Double) -> Int -> IO ()
- trmm :: Order -> Side -> Uplo -> Transpose -> Diag -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
- trsm :: Order -> Side -> Uplo -> Transpose -> Diag -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO ()
Level 1: vector-vector operations
Basic operations
swap :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Swap two vectors:
(x, y) ← (y, x)
scal :: Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Multiply a vector by a scalar.
x ← α x
copy :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Copy a vector into another vector:
y ← x
axpy :: Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Add a scalar-vector product to a vector.
y ← α x + y
dotu :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO (Complex Double) Source
Calculate the bilinear dot product of two vectors:
x ⋅ y ≡ ∑[i] x[i] y[i]
dotc :: Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO (Complex Double) Source
Calculate the sesquilinear dot product of two vectors.
x* ⋅ y ≡ ∑[i] x[i]* y[i]
Norm operations
nrm2 :: Int -> Ptr (Complex Double) -> Int -> IO Double Source
Calculate the Euclidean (L²) norm of a vector:
‖x‖₂ ≡ √(∑[i] x[i]²)
asum :: Int -> Ptr (Complex Double) -> Int -> IO Double Source
Calculate the Manhattan (L¹) norm, equal to the sum of the magnitudes of the elements:
‖x‖₁ = ∑[i] |x[i]|
iamax :: Int -> Ptr (Complex Double) -> Int -> IO Int Source
Calculate the index of the element with the maximum magnitude (absolute value).
Level 2: matrix-vector operations
Multiplication
gemv :: Order -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a general matrix-vector update.
y ← α T(A) x + β y
gbmv :: Order -> Transpose -> Int -> Int -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a general banded matrix-vector update.
y ← α T(A) x + β y
hemv :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a hermitian matrix-vector update.
y ← α A x + β y
hbmv :: Order -> Uplo -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a hermitian banded matrix-vector update.
y ← α A x + β y
hpmv :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a hermitian packed matrix-vector update.
y ← α A x + β y
Triangular operations
trmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Multiply a triangular matrix by a vector.
x ← T(A) x
tbmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Multiply a triangular banded matrix by a vector.
x ← T(A) x
tpmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Ptr (Complex Double) -> Int -> IO () Source
Multiply a triangular packed matrix by a vector.
x ← T(A) x
trsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Multiply an inverse triangular matrix by a vector.
x ← T(A⁻¹) x
tbsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Multiply an inverse triangular banded matrix by a vector.
x ← T(A⁻¹) x
tpsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr (Complex Double) -> Ptr (Complex Double) -> Int -> IO () Source
Multiply an inverse triangular packed matrix by a vector.
x ← T(A⁻¹) x
Rank updates
geru :: Order -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Perform an unconjugated rank-1 update of a general matrix.
A ← α x y⊤ + A
gerc :: Order -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Perform a conjugated rank-1 update of a general matrix.
A ← α x y† + A
her :: Order -> Uplo -> Int -> Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Perform a rank-1 update of a Hermitian matrix.
A ← α x y† + A
hpr :: Order -> Uplo -> Int -> Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> IO () Source
Perform a rank-1 update of a Hermitian packed matrix.
A ← α x y† + A
her2 :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> IO () Source
Perform a rank-2 update of a Hermitian matrix.
A ← α x y† + y (α x)† + A
hpr2 :: Order -> Uplo -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> IO () Source
Perform a rank-2 update of a Hermitian packed matrix.
A ← α x y† + y (α x)† + A
Level 3: matrix-matrix operations
Multiplication
:: Order | Layout of all the matrices. |
-> Transpose | The operation |
-> Transpose | The operation |
-> Int | Number of rows of |
-> Int | Number of columns of |
-> Int | Number of columns of |
-> Complex Double | Scaling factor |
-> Ptr (Complex Double) | Pointer to a matrix |
-> Int | Stride of the major dimension of |
-> Ptr (Complex Double) | Pointer to a matrix |
-> Int | Stride of the major dimension of |
-> Complex Double | Scaling factor |
-> Ptr (Complex Double) | Pointer to a mutable matrix |
-> Int | Stride of the major dimension of |
-> IO () |
Perform a general matrix-matrix update.
C ← α T(A) U(B) + β C
:: Order | Layout of all the matrices. |
-> Side | Side that |
-> Uplo | The part of |
-> Int | Number of rows of |
-> Int | Number of columns of |
-> Complex Double | Scaling factor |
-> Ptr (Complex Double) | Pointer to a symmetric matrix |
-> Int | Stride of the major dimension of |
-> Ptr (Complex Double) | Pointer to a matrix |
-> Int | Stride of the major dimension of |
-> Complex Double | Scaling factor |
-> Ptr (Complex Double) | Pointer to a mutable matrix |
-> Int | Stride of the major dimension of |
-> IO () |
Perform a symmetric matrix-matrix update.
C ← α A B + β C or C ← α B A + β C
where A
is symmetric. The matrix A
must be in an unpacked format, although the
routine will only access half of it as specified by the
argument.Uplo
:: Order | Layout of all the matrices. |
-> Side | Side that |
-> Uplo | The part of |
-> Int | Number of rows of |
-> Int | Number of columns of |
-> Complex Double | Scaling factor |
-> Ptr (Complex Double) | Pointer to a Hermitian matrix |
-> Int | Stride of the major dimension of |
-> Ptr (Complex Double) | Pointer to a matrix |
-> Int | Stride of the major dimension of |
-> Complex Double | Scaling factor |
-> Ptr (Complex Double) | Pointer to a mutable matrix |
-> Int | Stride of the major dimension of |
-> IO () |
Perform a Hermitian matrix-matrix update.
C ← α A B + β C or C ← α B A + β C
where A
is Hermitian. The matrix A
must be in an unpacked format, although the
routine will only access half of it as specified by the
argument.Uplo
Rank updates
syrk :: Order -> Uplo -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a symmetric rank-k update.
C ← α A A⊤ + β C or C ← α A⊤ A + β C
herk :: Order -> Uplo -> Transpose -> Int -> Int -> Double -> Ptr (Complex Double) -> Int -> Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a Hermitian rank-k update.
C ← α A A† + β C or C ← α A† A + β C
syr2k :: Order -> Uplo -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a symmetric rank-2k update.
C ← α A B⊤ + α* B A⊤ + β C or C ← α A⊤ B + α* B⊤ A + β C
her2k :: Order -> Uplo -> Transpose -> Int -> Int -> Complex Double -> Ptr (Complex Double) -> Int -> Ptr (Complex Double) -> Int -> Double -> Ptr (Complex Double) -> Int -> IO () Source
Perform a Hermitian rank-2k update.
C ← α A B† + α* B A† + β C or C ← α A† B + α* B† A + β C