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

Synapse.Tensors

Description

Module that provides mathematical base for neural networks.

This module implements Vec and Mat datatypes and provides several useful function to work with them.

Most of typeclasses of this module are working with DType type family. That is to permit instances on types that are not exactly containers, but rather wrappers of containers, and it allows imposing additional constraints on inner type. The best example is Symbol from Synapse.Autograd.

Synopsis

DType type family

type family DType f :: Type Source #

DType type family allows to get type of element for any container of that type - even for nested ones!

Instances

Instances details
type DType (SymbolMat a) Source # 
Instance details

Defined in Synapse.Autograd

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

Defined in Synapse.Autograd

type DType (SymbolVec a) = a
type DType (Dataset a) Source # 
Instance details

Defined in Synapse.NN.Batching

type DType (Dataset a) = DType a
type DType (Sample a) Source # 
Instance details

Defined in Synapse.NN.Batching

type DType (Sample a) = DType a
type DType (Dense a) Source # 
Instance details

Defined in Synapse.NN.Layers.Dense

type DType (Dense a) = a
type DType (Layer a) Source # 
Instance details

Defined in Synapse.NN.Layers.Layer

type DType (Layer a) = a
type DType (SequentialModel a) Source # 
Instance details

Defined in Synapse.NN.Models

type DType (SequentialModel a) = a
type DType (SGD a) Source # 
Instance details

Defined in Synapse.NN.Optimizers

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

Defined in Synapse.Tensors.Mat

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

Defined in Synapse.Tensors.Vec

type DType (Vec a) = a

Indexable typeclass

class Indexable f where Source #

Indexable typeclass provides indexing interface for datatypes.

Associated Types

type Index f :: Type Source #

Type of index for Indexable container.

Methods

unsafeIndex :: f -> Index f -> DType f Source #

Unsafe indexing.

(!) :: f -> Index f -> DType f infixl 9 Source #

Indexing with bounds checking.

(!?) :: f -> Index f -> Maybe (DType f) infixl 9 Source #

Safe indexing.

Instances

Instances details
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 #

Indexable (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Associated Types

type Index (Vec a) Source #

Methods

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

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

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

Container-scalar operations

class ElementwiseScalarOps f where Source #

ElementwiseScalarOps typeclass allows containers over numerical values easily work with scalars by using elementwise operations.

This typeclass operates on DType to permit instances on types that are not exactly containers, but rather wrappers of containers. The best example is Symbol from Synapse.Autograd.

Methods

(+.) :: Num (DType f) => f -> DType f -> f infixl 6 Source #

Adds given value to every element of the container.

(-.) :: Num (DType f) => f -> DType f -> f infixl 6 Source #

Subtracts given value from every element of the functor.

(*.) :: Num (DType f) => f -> DType f -> f infixl 7 Source #

Multiplies every element of the functor by given value.

(/.) :: Fractional (DType f) => f -> DType f -> f infixl 7 Source #

Divides every element of the functor by given value.

(**.) :: Floating (DType f) => f -> DType f -> f infixr 8 Source #

Exponentiates every element of the functor by given value.

elementsMin :: Ord (DType f) => f -> DType f -> f Source #

Applies min operation with given value to every element.

elementsMax :: Ord (DType f) => f -> DType f -> f Source #

Applies max operation with given value to every element.

Instances

Instances details
Symbolic a => ElementwiseScalarOps (Symbol (Vec a)) Source # 
Instance details

Defined in Synapse.Autograd

Methods

(+.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(-.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(*.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(/.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

(**.) :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

elementsMin :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec a) Source #

elementsMax :: Symbol (Vec a) -> DType (Symbol (Vec a)) -> Symbol (Vec 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 #

ElementwiseScalarOps (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

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

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

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

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

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

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

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

class SingletonOps f where Source #

SingletonOps typeclass provides operations that relate to singleton containers (scalars that are wrapped in said container).

All functions of that typeclass must return singletons (scalars that are wrapped in container).

This typeclass operates on DType to permit instances on types that are not exactly containers, but rather wrappers of containers. The best example is Symbol from Synapse.Autograd.

Methods

singleton :: DType f -> f Source #

Initializes singleton container.

isSingleton :: f -> Bool Source #

Return true if container represents a singleton.

unSingleton :: f -> DType f Source #

Unwraps singleton container.

extendSingleton :: f -> f -> f Source #

elementsSum :: Num (DType f) => f -> f Source #

Sums all elements of container.

elementsProduct :: Fractional (DType f) => f -> f Source #

Multiplies all elements of container (Fractional constraint is needed for efficient gradient calculation, although it may be overly restrictive in some situations).

mean :: Fractional (DType f) => f -> f Source #

Calculates the mean of all elements of container.

norm :: Floating (DType f) => f -> f Source #

Calculates the Frobenius norm of all elements of container.

Instances

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

Defined in Synapse.Autograd

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

Defined in Synapse.Autograd

SingletonOps (Mat a) Source # 
Instance details

Defined in Synapse.Tensors.Mat

SingletonOps (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Specific container operations

class VecOps f where Source #

VecOps typeclass provides vector-specific operations.

This typeclass operates on DType to permit instances on types that are not exactly containers, but rather wrappers of containers. The best example is Symbol from Synapse.Autograd.

Methods

dot :: Num (DType f) => f -> f -> f Source #

Calculates dot product of two vectors.

Instances

Instances details
Symbolic a => VecOps (SymbolVec a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

dot :: SymbolVec a -> SymbolVec a -> SymbolVec a Source #

Num a => VecOps (Vec a) Source # 
Instance details

Defined in Synapse.Tensors.Vec

Methods

dot :: Vec a -> Vec a -> Vec a Source #

class MatOps f where Source #

MatOps typeclass provides matrix-specific operations.

This typeclass operates on DType to permit instances on types that are not exactly containers, but rather wrappers of containers. The best example is Symbol from Synapse.Autograd.

Methods

transpose :: f -> f Source #

Transposes matrix.

addMatRow :: Num (DType f) => f -> f -> f Source #

Add matrix that represents row to every row of given matrix.

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

Mutiplies two matrices.

Instances

Instances details
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 #