Stability | experimental |
---|---|
Maintainer | Patrick Perry <patperry@stanford.edu> |
Immutable dense matrices.
- data Matrix np e
- class (HasVectorView a, Elem e, MatrixShaped a, BaseVector (VectorView a) e) => BaseMatrix a e where
- ldaMatrix :: a (n, p) e -> Int
- transEnumMatrix :: a (n, p) e -> TransEnum
- isHermMatrix :: a (n, p) e -> Bool
- coerceMatrix :: a np e -> a np' e
- module Data.Matrix.Class
- module Data.Matrix.Class.IMatrix
- matrix :: BLAS3 e => (Int, Int) -> [((Int, Int), e)] -> Matrix (n, p) e
- listMatrix :: BLAS3 e => (Int, Int) -> [e] -> Matrix (n, p) e
- rowsMatrix :: BLAS3 e => (Int, Int) -> [Vector p e] -> Matrix (n, p) e
- colsMatrix :: BLAS3 e => (Int, Int) -> [Vector n e] -> Matrix (n, p) e
- zeroMatrix :: BLAS3 e => (Int, Int) -> Matrix (n, p) e
- constantMatrix :: BLAS3 e => (Int, Int) -> e -> Matrix (n, p) e
- identityMatrix :: BLAS3 e => (Int, Int) -> Matrix (n, p) e
- matrixFromRow :: BLAS3 e => Vector p e -> Matrix (one, p) e
- matrixFromCol :: BLAS3 e => Vector n e -> Matrix (n, one) e
- matrixFromVector :: BLAS3 e => (Int, Int) -> Vector np e -> Matrix (n, p) e
- vectorFromMatrix :: BLAS3 e => Matrix (n, p) e -> Vector np e
- submatrix :: Elem e => Matrix (n, p) e -> (Int, Int) -> (Int, Int) -> Matrix (n', p') e
- splitRowsAt :: BaseMatrix a e => Int -> a (n, p) e -> (a (n1, p) e, a (n2, p) e)
- splitColsAt :: BaseMatrix a e => Int -> a (n, p) e -> (a (n, p1) e, a (n, p2) e)
- diag :: Elem e => Matrix (n, p) e -> Int -> Vector k e
- module Data.Tensor.Class
- module Data.Tensor.Class.ITensor
Dense matrix type
Immutable dense matrices. The type arguments are as follows:
-
np
: a phantom type for the shape of the matrix. Most functions will demand that this be specified as a pair. When writing a function signature, you should always preferMatrix (n,p) e
toMatrix np e
. -
e
: the element type of the matrix. Only certain element types are supported.
MatrixShaped Matrix | |
HasVectorView Matrix | |
Elem e => BaseMatrix Matrix e | |
BLAS3 e => IMatrix Matrix e | |
BLAS3 e => MMatrix Matrix e IO | |
BLAS3 e => ReadMatrix Matrix e IO | |
BLAS3 e => MMatrix Matrix e (ST s) | |
BLAS3 e => ReadMatrix Matrix e (ST s) | |
Shaped Matrix (Int, Int) | |
BLAS3 e => ITensor Matrix (Int, Int) e | |
(BLAS3 e, Monad m) => ReadTensor Matrix (Int, Int) e m | |
BLAS3 e => IMatrix (Herm Matrix) e | |
BLAS3 e => IMatrix (Tri Matrix) e | |
BLAS3 e => ISolve (Tri Matrix) e | |
BLAS3 e => MSolve (Tri Matrix) e IO | |
BLAS3 e => MMatrix (Herm Matrix) e IO | |
BLAS3 e => MMatrix (Tri Matrix) e IO | |
BLAS3 e => MSolve (Tri Matrix) e (ST s) | |
BLAS3 e => MMatrix (Herm Matrix) e (ST s) | |
BLAS3 e => MMatrix (Tri Matrix) e (ST s) | |
(BLAS3 e, Eq e) => Eq (Matrix (n, p) e) | |
(BLAS3 e, Floating e) => Floating (Matrix (m, n) e) | |
BLAS3 e => Fractional (Matrix (n, p) e) | |
BLAS3 e => Num (Matrix (n, p) e) | |
(BLAS3 e, Show e) => Show (Matrix (n, p) e) | |
(BLAS3 e, AEq e) => AEq (Matrix (n, p) e) |
Overloaded interface for dense matrices
class (HasVectorView a, Elem e, MatrixShaped a, BaseVector (VectorView a) e) => BaseMatrix a e whereSource
Common functionality for all dense matrix types.
ldaMatrix :: a (n, p) e -> IntSource
Get the leading dimension of the storage of the matrix.
transEnumMatrix :: a (n, p) e -> TransEnumSource
Get the storage type of the matrix.
isHermMatrix :: a (n, p) e -> BoolSource
Indicate whether or not the underlying matrix storage is transposed and conjugated.
coerceMatrix :: a np e -> a np' eSource
Cast the shape type of the matrix.
Elem e => BaseMatrix IOMatrix e | |
Elem e => BaseMatrix Matrix e | |
Elem e => BaseMatrix (STMatrix s) e |
Overloaded interface for matrices
module Data.Matrix.Class
module Data.Matrix.Class.IMatrix
Creating matrices
matrix :: BLAS3 e => (Int, Int) -> [((Int, Int), e)] -> Matrix (n, p) eSource
Create a new matrix of the given size and initialize the given elements to the given values. All other elements get set to zero.
listMatrix :: BLAS3 e => (Int, Int) -> [e] -> Matrix (n, p) eSource
Create a new matrix with the given elements in row-major order.
rowsMatrix :: BLAS3 e => (Int, Int) -> [Vector p e] -> Matrix (n, p) eSource
Create a matrix of the given shape from a list of rows
colsMatrix :: BLAS3 e => (Int, Int) -> [Vector n e] -> Matrix (n, p) eSource
Create a matrix of the given shape from a list of columns
Special matrices
constantMatrix :: BLAS3 e => (Int, Int) -> e -> Matrix (n, p) eSource
Get a new constant of the given shape.
identityMatrix :: BLAS3 e => (Int, Int) -> Matrix (n, p) eSource
Get a new matrix of the given shape with ones along the diagonal and zeroes everywhere else.
Conversions between vectors and matrices
matrixFromRow :: BLAS3 e => Vector p e -> Matrix (one, p) eSource
Get a matrix from a row vector.
matrixFromCol :: BLAS3 e => Vector n e -> Matrix (n, one) eSource
Get a matrix from a column vector.
matrixFromVector :: BLAS3 e => (Int, Int) -> Vector np e -> Matrix (n, p) eSource
Get a matrix from the elements stored in columnwise order in the vector.
vectorFromMatrix :: BLAS3 e => Matrix (n, p) e -> Vector np eSource
Get a vector by concatenating the columns of the matrix.
Matrix views
submatrix :: Elem e => Matrix (n, p) e -> (Int, Int) -> (Int, Int) -> Matrix (n', p') eSource
submatrix a ij mn
returns the submatrix of a
with element (0,0)
being element ij
in a
, and having shape mn
.
splitRowsAt :: BaseMatrix a e => Int -> a (n, p) e -> (a (n1, p) e, a (n2, p) e)Source
Divide the rows of a matrix into two blocks and return views into the blocks. The integer argument indicates how many rows should be in the first block.
splitColsAt :: BaseMatrix a e => Int -> a (n, p) e -> (a (n, p1) e, a (n, p2) e)Source
Divide the columns of a matrix into two blocks and return views into the blocks. The integer argument indicates how many columns should be in the first block.
Vector views
diag :: Elem e => Matrix (n, p) e -> Int -> Vector k eSource
Get a the given diagonal in a matrix. Negative indices correspond to sub-diagonals.
Overloaded interface for reading matrix elements
module Data.Tensor.Class
module Data.Tensor.Class.ITensor