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

Synapse.Autograd

Description

This module implements reverse-mode automatic differentiation.

Machine learning and training of models are based on calculating gradients of operations. This can be done symbolically by dynamically creating a graph of all operations, which is then traversed to obtain the gradient.

Synapse provides several operations that support automatic differentiation, but you could easily extend list of those: you just need to define function that returns Symbol with correct local gradients. You can check out implementations in the source to give yourself a reference and read more about it in Symbol datatype docs.

Synopsis

Symbolic and Symbol

class (Eq a, Num a) => Symbolic a where Source #

Symbolic typeclass describes types with few properties that are needed for autogradient.

Members of this typeclass could have default implementation due to Num, but such implementation is not always correct. Vecs and Mats do not have only one zero or identity element, and so numerical literal is not enough. symbolicZero and symbolicOne function additionally take reference value to consider dimensions. Absence of default implementations forces to manually ensure correctness of those functions.

Synapse provides implementations for primitive types (Int, Float, Double), and for containers types (Vec, Vec).

Detailed laws of Symbolic properties are in the docs for associated functions.

Minimal complete definition

symbolicZero, symbolicOne

Methods

symbolicZero :: a -> a Source #

Returns additive and multiplicative (elementwise) zero element. Argument is passed for the reference of the dimension.

symbolicOne :: a -> a Source #

Returns multiplicative (elementwise) identity element. Argument is passed for the reference of the dimension.

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

Returns what could be considered N constant (sum of N symbolicOnes). Argument is passed for the reference of the dimension.

Instances

Instances details
Symbolic Double Source # 
Instance details

Defined in Synapse.Autograd

Symbolic Float Source # 
Instance details

Defined in Synapse.Autograd

Symbolic Int Source # 
Instance details

Defined in Synapse.Autograd

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

Defined in Synapse.Autograd

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 => Symbolic (Vec a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

symbolicZero :: Vec a -> Vec a Source #

symbolicOne :: Vec a -> Vec a Source #

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

data Symbol a Source #

Datatype that represents symbol variable (variable which operations are recorded to symbolically obtain derivatives).

Any operation returning Symbol a where a is Symbolic could be autogradiented - returned Symbol has symbolGradients list, which allows Synapse to build a graph of computation and obtain needed gradients. symbolGradients list contains pairs: first element in that pair is symbol wrt which you can take gradient and the second element is closure that represents chain rule - it takes incoming local gradient of said symbol and multiplies it by local derivative. You can check out implementations of those operations in the source to give yourself a reference.

Constructors

Symbol 

Fields

Instances

Instances details
(Symbolic a, Floating a) => Floating (Symbol a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

pi :: Symbol a #

exp :: Symbol a -> Symbol a #

log :: Symbol a -> Symbol a #

sqrt :: Symbol a -> Symbol a #

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

logBase :: Symbol a -> Symbol a -> Symbol a #

sin :: Symbol a -> Symbol a #

cos :: Symbol a -> Symbol a #

tan :: Symbol a -> Symbol a #

asin :: Symbol a -> Symbol a #

acos :: Symbol a -> Symbol a #

atan :: Symbol a -> Symbol a #

sinh :: Symbol a -> Symbol a #

cosh :: Symbol a -> Symbol a #

tanh :: Symbol a -> Symbol a #

asinh :: Symbol a -> Symbol a #

acosh :: Symbol a -> Symbol a #

atanh :: Symbol a -> Symbol a #

log1p :: Symbol a -> Symbol a #

expm1 :: Symbol a -> Symbol a #

log1pexp :: Symbol a -> Symbol a #

log1mexp :: Symbol a -> Symbol a #

Symbolic a => Num (Symbol a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

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

(-) :: Symbol a -> Symbol a -> Symbol a #

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

negate :: Symbol a -> Symbol a #

abs :: Symbol a -> Symbol a #

signum :: Symbol a -> Symbol a #

fromInteger :: Integer -> Symbol a #

(Symbolic a, Fractional a) => Fractional (Symbol a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

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

recip :: Symbol a -> Symbol a #

fromRational :: Rational -> Symbol a #

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

Defined in Synapse.Autograd

Methods

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

show :: Symbol a -> String #

showList :: [Symbol a] -> ShowS #

Eq (Symbol a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

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

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

Hashable (Symbol a) Source # 
Instance details

Defined in Synapse.Autograd

Methods

hashWithSalt :: Int -> Symbol a -> Int #

hash :: Symbol a -> Int #

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

Defined in Synapse.Autograd

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

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

Defined in Synapse.Autograd

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

Defined in Synapse.Autograd

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

Defined in Synapse.Autograd

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

Defined in Synapse.Autograd

Methods

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

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 SymbolVec a = Symbol (Vec a) Source #

SymbolVec a type alias stands for Symbol (Vec a).

type SymbolMat a = Symbol (Mat a) Source #

SymbolMat a type alias stands for Symbol (Mat a).

symbol :: SymbolIdentifier -> a -> Symbol a Source #

Creates new symbol that refers to a variable (so it must have a name to be able to be differentiated wrt).

constSymbol :: a -> Symbol a Source #

Creates new symbol that refers to constant (so it does not have name and thus its gradients are not saved).

renameSymbol :: SymbolIdentifier -> Symbol a -> Symbol a Source #

Renames symbol which allows differentiating wrt it. Note: renaming practically creates new symbol for the gradient calculation.

symbolicUnaryOp :: (a -> a) -> Symbol a -> [(Symbol a, Symbol a -> Symbol a)] -> Symbol a Source #

Converts unary operation into symbolic one.

symbolicBinaryOp :: (a -> a -> a) -> Symbol a -> Symbol a -> [(Symbol a, Symbol a -> Symbol a)] -> Symbol a Source #

Converts binary operation into symbolic one.

Gradients calculation

data Gradients a Source #

Gradients datatype holds all gradients of one symbol with respect to other symbols.

Instances

Instances details
Show a => Show (Gradients a) Source # 
Instance details

Defined in Synapse.Autograd

allGradients :: Gradients a -> [(Symbol a, Symbol a)] Source #

Returns key-value pairs of all gradients of symbol.

getGradientsOf :: Symbolic a => Symbol a -> Gradients a Source #

Generates Gradients for given symbol.

wrt :: Symbolic a => Gradients a -> Symbol a -> Symbol a Source #

Chooses gradient with respect to given symbol.

nthPartialGradient :: Symbolic a => Symbol a -> [Symbol a] -> Symbol a Source #

Takes partial gradients wrt to all symbols in a list sequentially, returning last result.

nthGradient :: Symbolic a => Int -> Symbol a -> Symbol a -> Symbol a Source #

Takes nth order gradient of one symbol wrt other symbol. If n is negative number, an error is returned.