synapse-0.1.0.0: Synapse is a machine learning library written in pure Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

data Mat a Source #

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

Instances details
Foldable Mat Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

fold :: Monoid m => Mat m -> m #

foldMap :: Monoid m => (a -> m) -> Mat a -> m #

foldMap' :: Monoid m => (a -> m) -> Mat a -> m #

foldr :: (a -> b -> b) -> b -> Mat a -> b #

foldr' :: (a -> b -> b) -> b -> Mat a -> b #

foldl :: (b -> a -> b) -> b -> Mat a -> b #

foldl' :: (b -> a -> b) -> b -> Mat a -> b #

foldr1 :: (a -> a -> a) -> Mat a -> a #

foldl1 :: (a -> a -> a) -> Mat a -> a #

toList :: Mat a -> [a] #

null :: Mat a -> Bool #

length :: Mat a -> Int #

elem :: Eq a => a -> Mat a -> Bool #

maximum :: Ord a => Mat a -> a #

minimum :: Ord a => Mat a -> a #

sum :: Num a => Mat a -> a #

product :: Num a => Mat a -> a #

Traversable Mat Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

traverse :: Applicative f => (a -> f b) -> Mat a -> f (Mat b) #

sequenceA :: Applicative f => Mat (f a) -> f (Mat a) #

mapM :: Monad m => (a -> m b) -> Mat a -> m (Mat b) #

sequence :: Monad m => Mat (m a) -> m (Mat a) #

Applicative Mat Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

pure :: a -> Mat a #

(<*>) :: Mat (a -> b) -> Mat a -> Mat b #

liftA2 :: (a -> b -> c) -> Mat a -> Mat b -> Mat c #

(*>) :: Mat a -> Mat b -> Mat b #

(<*) :: Mat a -> Mat b -> Mat a #

Functor Mat Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

fmap :: (a -> b) -> Mat a -> Mat b #

(<$) :: a -> Mat b -> Mat a #

Floating a => Floating (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

pi :: Mat a #

exp :: Mat a -> Mat a #

log :: Mat a -> Mat a #

sqrt :: Mat a -> Mat a #

(**) :: Mat a -> Mat a -> Mat a #

logBase :: Mat a -> Mat a -> Mat a #

sin :: Mat a -> Mat a #

cos :: Mat a -> Mat a #

tan :: Mat a -> Mat a #

asin :: Mat a -> Mat a #

acos :: Mat a -> Mat a #

atan :: Mat a -> Mat a #

sinh :: Mat a -> Mat a #

cosh :: Mat a -> Mat a #

tanh :: Mat a -> Mat a #

asinh :: Mat a -> Mat a #

acosh :: Mat a -> Mat a #

atanh :: Mat a -> Mat a #

log1p :: Mat a -> Mat a #

expm1 :: Mat a -> Mat a #

log1pexp :: Mat a -> Mat a #

log1mexp :: Mat a -> Mat a #

Num a => Num (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

(+) :: Mat a -> Mat a -> Mat a #

(-) :: Mat a -> Mat a -> Mat a #

(*) :: Mat a -> Mat a -> Mat a #

negate :: Mat a -> Mat a #

abs :: Mat a -> Mat a #

signum :: Mat a -> Mat a #

fromInteger :: Integer -> Mat a #

Fractional a => Fractional (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

(/) :: Mat a -> Mat a -> Mat a #

recip :: Mat a -> Mat a #

fromRational :: Rational -> Mat a #

Show a => Show (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

showsPrec :: Int -> Mat a -> ShowS #

show :: Mat a -> String #

showList :: [Mat a] -> ShowS #

Eq a => Eq (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

(==) :: Mat a -> Mat a -> Bool #

(/=) :: Mat a -> Mat a -> Bool #

Symbolic a => Symbolic (Mat a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

symbolicZero :: Mat a -> Mat a Source #

symbolicOne :: Mat a -> Mat a Source #

symbolicN :: Int -> Mat a -> Mat a Source #

Symbolic a => ElementwiseScalarOps (SymbolMat a) Source # 
Instance details

Defined in Synapse.Autograd

ElementwiseScalarOps (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

(+.) :: Mat a -> DType (Mat a) -> Mat a Source #

(-.) :: Mat a -> DType (Mat a) -> Mat a Source #

(*.) :: Mat a -> DType (Mat a) -> Mat a Source #

(/.) :: Mat a -> DType (Mat a) -> Mat a Source #

(**.) :: Mat a -> DType (Mat a) -> Mat a Source #

elementsMin :: Mat a -> DType (Mat a) -> Mat a Source #

elementsMax :: Mat a -> DType (Mat a) -> Mat a Source #

Indexable (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Associated Types

type Index (Mat a) Source #

Methods

unsafeIndex :: Mat a -> Index (Mat a) -> DType (Mat a) Source #

(!) :: Mat a -> Index (Mat a) -> DType (Mat a) Source #

(!?) :: Mat a -> Index (Mat a) -> Maybe (DType (Mat a)) Source #

Symbolic a => MatOps (SymbolMat a) Source # 
Instance details

Defined in Synapse.Autograd

Num a => MatOps (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

Methods

transpose :: Mat a -> Mat a Source #

addMatRow :: Mat a -> Mat a -> Mat a Source #

matMul :: Mat a -> Mat a -> Mat a Source #

Symbolic a => SingletonOps (SymbolMat a) Source # 
Instance details

Defined in Synapse.Autograd

SingletonOps (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

type DType (SymbolMat a) Source # 
Instance details

Defined in Synapse.Autograd

type DType (SymbolMat a) = a
type DType (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

type DType (Mat a) = a
type Index (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

type Index (Mat a) = (Int, Int)

nElements :: Mat a -> Int Source #

Number of elements in a matrix.

size :: Mat a -> (Int, Int) Source #

Size of matrix.

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.

toLists :: Mat a -> [[a]] Source #

Converts matrix to list of lists.

Constructors

empty :: Mat a Source #

Creates empty Mat.

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.

replicate :: (Int, Int) -> a -> Mat a Source #

Creates Mat of given size filled with given element.

Vec operations

rowVec :: Vec a -> Mat a Source #

Converts Vec to a one row Mat.

colVec :: Vec a -> Mat a Source #

Converts Vec to a one column Mat.

fromVec :: (Int, Int) -> Vec a -> Mat a Source #

Initializes Mat from given Vec.

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.

safeIndexRow :: Mat a -> Int -> Maybe (Vec a) Source #

Extracts row from Mat.

safeIndexCol :: Mat a -> Int -> Maybe (Vec a) Source #

Extracts column from Mat.

diagonal :: Mat a -> Vec a Source #

Extracts diagonal from Mat.

flatten :: Mat a -> Vec a Source #

Flattens Mat to a Vec.

Combining

map :: (a -> b) -> Mat a -> Mat b Source #

Applies function to every element of Mat.

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.

for :: Mat a -> (a -> b) -> Mat b Source #

Flipped map.

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 Mats 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.

swapRows :: Mat a -> Int -> Int -> Mat a Source #

Swaps two rows.

swapCols :: Mat a -> Int -> Int -> Mat a Source #

Swaps two columns.

transpose :: MatOps f => f -> f Source #

Transposes matrix.

Submatrices

minor :: Mat a -> (Int, Int) -> Mat a Source #

Extacts minor matrix, skipping given row and column.

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.

join :: (Mat a, Mat a, Mat a, Mat a) -> Mat a Source #

Joins 4 blocks of matrices.

(<|>) :: Mat a -> Mat a -> Mat a infixl 9 Source #

Joins two matrices horizontally.

(<->) :: Mat a -> Mat a -> Mat a infixl 9 Source #

Joins two matrices vertically.

Mathematics

zeroes :: Num a => (Int, Int) -> Mat a Source #

Creates Mat that is filled with zeroes.

ones :: Num a => (Int, Int) -> Mat a Source #

Creates Mat that is filled with ones.

identity :: Num a => Int -> Mat a Source #

Creates identity matrix.

adamarMul :: Num a => Mat a -> Mat a -> Mat a Source #

Adamar multiplication (elementwise multiplication).

matMul :: (MatOps f, Num (DType f)) => f -> f -> f Source #

Mutiplies two matrices.

det :: Num a => Mat a -> a Source #

Determinant of a square matrix. If matrix is empty, zero is returned.

rref :: (Eq a, Fractional a) => Mat a -> Mat a Source #

Row reduced echelon form of matrix.

inverse :: (Eq a, Fractional a) => Mat a -> Maybe (Mat a) Source #

Inverse of a square matrix. If given matrix is empty, empty matrix is returned.

orthogonalized :: Floating a => Mat a -> Mat a Source #

Orthogonalizes matrix by rows using Gram-Schmidt algorithm.