Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synapse.Tensors.Mat
Description
Implementation of matrix.
Matrices are a backbone of any machine learning library, since most of the operations are implemented by the matrices combinations (matrix multiplication, elementwise operations).
Mat
datatype provides interface for all of those operations.
Synopsis
- data Mat a
- nElements :: Mat a -> Int
- size :: Mat a -> (Int, Int)
- isTransposed :: Mat a -> Bool
- isSubmatrix :: Mat a -> Bool
- force :: Mat a -> Mat a
- toLists :: Mat a -> [[a]]
- empty :: Mat a
- singleton :: SingletonOps f => DType f -> f
- fromList :: (Int, Int) -> [a] -> Mat a
- fromLists :: (Int, Int) -> [[a]] -> Mat a
- generate :: (Int, Int) -> ((Int, Int) -> a) -> Mat a
- replicate :: (Int, Int) -> a -> Mat a
- rowVec :: Vec a -> Mat a
- colVec :: Vec a -> Mat a
- fromVec :: (Int, Int) -> Vec a -> Mat a
- indexRow :: Mat a -> Int -> Vec a
- indexCol :: Mat a -> Int -> Vec a
- safeIndexRow :: Mat a -> Int -> Maybe (Vec a)
- safeIndexCol :: Mat a -> Int -> Maybe (Vec a)
- diagonal :: Mat a -> Vec a
- flatten :: Mat a -> Vec a
- map :: (a -> b) -> Mat a -> Mat b
- mapRow :: Int -> (Vec a -> Vec a) -> Mat a -> Mat a
- mapCol :: Int -> (Vec a -> Vec a) -> Mat a -> Mat a
- for :: Mat a -> (a -> b) -> Mat b
- imap :: ((Int, Int) -> a -> b) -> Mat a -> Mat b
- elementwise :: (a -> b -> c) -> Mat a -> Mat b -> Mat c
- setSize :: Mat a -> a -> (Int, Int) -> Mat a
- extend :: Mat a -> a -> (Int, Int) -> Mat a
- shrink :: Mat a -> (Int, Int) -> Mat a
- swapRows :: Mat a -> Int -> Int -> Mat a
- swapCols :: Mat a -> Int -> Int -> Mat a
- transpose :: MatOps f => f -> f
- minor :: Mat a -> (Int, Int) -> Mat a
- submatrix :: Mat a -> ((Int, Int), (Int, Int)) -> Mat a
- split :: Mat a -> (Int, Int) -> (Mat a, Mat a, Mat a, Mat a)
- join :: (Mat a, Mat a, Mat a, Mat a) -> Mat a
- (<|>) :: Mat a -> Mat a -> Mat a
- (<->) :: Mat a -> Mat a -> Mat a
- zeroes :: Num a => (Int, Int) -> Mat a
- ones :: Num a => (Int, Int) -> Mat a
- identity :: Num a => Int -> Mat a
- adamarMul :: Num a => Mat a -> Mat a -> Mat a
- matMul :: (MatOps f, Num (DType f)) => f -> f -> f
- det :: Num a => Mat a -> a
- rref :: (Eq a, Fractional a) => Mat a -> Mat a
- inverse :: (Eq a, Fractional a) => Mat a -> Maybe (Mat a)
- orthogonalized :: Floating a => Mat a -> Mat a
Documentation
Mathematical matrix (collection of elements).
This implementation focuses on sharing parts of matrices and clever indexation
to reduce overhead of several essential operations.
Those include splitting matrices into submatrices, transposing - their asymptotical complexity becomes O(1).
However there are few downsides:
the first is that severely splitted matrix is hard to garbage collect and is not cache-friendly
and the second is that mass traversal operations on those sparse matrices might not fuse and combine well.
force
function and some functions that by their nature are forced address those issues,
but most of the time those problems are not significant enough and you are just better using convenient functions instead of workarounds.
Instances
isTransposed :: Mat a -> Bool Source #
Returns whether the matrix is transposed. If the matrix consists of only one element, it is considered never transposed.
isSubmatrix :: Mat a -> Bool Source #
Returns whether the matrix is a submatrix from another matrix.
Utility
force :: Mat a -> Mat a Source #
Copies matrix data dropping any extra memory that may be held if given matrix is a submatrix.
Constructors
singleton :: SingletonOps f => DType f -> f Source #
Initializes singleton container.
fromList :: (Int, Int) -> [a] -> Mat a Source #
Creates Mat
from list (will throw an error, if elements of that list do not form a matrix of given size).
fromLists :: (Int, Int) -> [[a]] -> Mat a Source #
Creates Mat
from list of lists (alias for fromLists (rows, cols) (concat xs)
).
generate :: (Int, Int) -> ((Int, Int) -> a) -> Mat a Source #
Creates Mat
of given size using generating function.
Vec operations
indexRow :: Mat a -> Int -> Vec a Source #
Extracts row from Mat
. If row is not present, an error is thrown.
indexCol :: Mat a -> Int -> Vec a Source #
Extracts column from Mat
. If column is not present, an error is thrown.
Combining
mapRow :: Int -> (Vec a -> Vec a) -> Mat a -> Mat a Source #
Applies function to a given row. If new Vec
is longer then кщц, it is truncated.
mapCol :: Int -> (Vec a -> Vec a) -> Mat a -> Mat a Source #
Applies function to a given column. If new Vec
is longer then column, it is truncated.
imap :: ((Int, Int) -> a -> b) -> Mat a -> Mat b Source #
Applies function to every element and its position of Mat
.
elementwise :: (a -> b -> c) -> Mat a -> Mat b -> Mat c Source #
Zips two Mat
s together using given function.
Operations with matrices
setSize :: Mat a -> a -> (Int, Int) -> Mat a Source #
Sets new size for a matrix relative to top left corner and uses given element for new entries if the matrix is extended.
extend :: Mat a -> a -> (Int, Int) -> Mat a Source #
Extends matrix size relative to top left corner using given element for new entries. The matrix is never reduced in size.
shrink :: Mat a -> (Int, Int) -> Mat a Source #
Shrinks matrix size relative to top left corner. The matrix is never extended in size.
Submatrices
submatrix :: Mat a -> ((Int, Int), (Int, Int)) -> Mat a Source #
Extracts submatrix, that is located between given two positions.
split :: Mat a -> (Int, Int) -> (Mat a, Mat a, Mat a, Mat a) Source #
Splits matrix into 4 parts, given position is a pivot, that corresponds to first element of bottom-right subpart.
Mathematics
adamarMul :: Num a => Mat a -> Mat a -> Mat a Source #
Adamar multiplication (elementwise multiplication).
det :: Num a => Mat a -> a Source #
Determinant of a square matrix. If matrix is empty, zero is returned.