neural-0.3.0.0: Neural Networks in native Haskell

Copyright(c) Lars Brünjes, 2016
LicenseMIT
Maintainerbrunjlar@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • MonoLocalBinds
  • Arrows
  • ScopedTypeVariables
  • GADTs
  • GADTSyntax
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • FlexibleContexts
  • ExistentialQuantification
  • KindSignatures
  • RankNTypes
  • ExplicitForAll

Numeric.Neural.Model

Description

This module defines parameterized functions, components and models. The parameterized functions are instances of the Arrow and ArrowChoice typeclasses, whereas Components behave like Arrows with choice over a different base category (the category Diff of differentiable functions). Both parameterized functions and components can be combined easily and flexibly.

Models contain a component, can measure their error with regard to samples and can be trained by gradient descent/ backpropagation.

Synopsis

Documentation

newtype ParamFun s t a b Source #

The type ParamFun t a b describes parameterized functions from a to b, where the parameters are of type t s. When such components are composed, they all share the same parameters.

Constructors

ParamFun 

Fields

Instances

Category * (ParamFun s t) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Arrow (ParamFun s t) Source # 

Methods

arr :: (b -> c) -> ParamFun s t b c #

first :: ParamFun s t b c -> ParamFun s t (b, d) (c, d) #

second :: ParamFun s t b c -> ParamFun s t (d, b) (d, c) #

(***) :: ParamFun s t b c -> ParamFun s t b' c' -> ParamFun s t (b, b') (c, c') #

(&&&) :: ParamFun s t b c -> ParamFun s t b c' -> ParamFun s t b (c, c') #

ArrowChoice (ParamFun s t) Source # 

Methods

left :: ParamFun s t b c -> ParamFun s t (Either b d) (Either c d) #

right :: ParamFun s t b c -> ParamFun s t (Either d b) (Either d c) #

(+++) :: ParamFun s t b c -> ParamFun s t b' c' -> ParamFun s t (Either b b') (Either c c') #

(|||) :: ParamFun s t b d -> ParamFun s t c d -> ParamFun s t (Either b c) d #

Profunctor (ParamFun s t) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> ParamFun s t b c -> ParamFun s t a d #

lmap :: (a -> b) -> ParamFun s t b c -> ParamFun s t a c #

rmap :: (b -> c) -> ParamFun s t a b -> ParamFun s t a c #

(#.) :: Coercible * c b => (b -> c) -> ParamFun s t a b -> ParamFun s t a c #

(.#) :: Coercible * b a => ParamFun s t b c -> (a -> b) -> ParamFun s t a c #

ArrowConvolve (ParamFun s t) Source # 

Methods

convolve :: Functor f => ParamFun s t b c -> ParamFun s t (f b) (f c) Source #

Functor (ParamFun s t a) Source # 

Methods

fmap :: (a -> b) -> ParamFun s t a a -> ParamFun s t a b #

(<$) :: a -> ParamFun s t a b -> ParamFun s t a a #

Applicative (ParamFun s t a) Source # 

Methods

pure :: a -> ParamFun s t a a #

(<*>) :: ParamFun s t a (a -> b) -> ParamFun s t a a -> ParamFun s t a b #

(*>) :: ParamFun s t a a -> ParamFun s t a b -> ParamFun s t a b #

(<*) :: ParamFun s t a a -> ParamFun s t a b -> ParamFun s t a a #

data Component f g Source #

A Component f g is a parameterized differentiable function f Double -> g Double. In contrast to ParamFun, when components are composed, parameters are not shared. Each component carries its own collection of parameters instead.

Constructors

(Traversable t, Applicative t, NFData (t Double)) => Component 

Fields

Instances

NFData (Component f g) Source # 

Methods

rnf :: Component f g -> () #

Category (* -> *) Component Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

_weights :: Lens' (Component f g) [Double] Source #

A Lens' to get or set the weights of a component. The shape of the parameter collection is hidden by existential quantification, so this lens has to use simple generic lists.

activate :: Component f g -> f Double -> g Double Source #

Activates a component, i.e. applies it to the specified input, using the current parameter values.

_component :: Lens' (Model f g a b c) (Component f g) Source #

A Lens for accessing the component embedded in a model.

data Pair s t a Source #

The analogue for pairs in the category of functors.

Constructors

Pair (s a) (t a) 

Instances

(Functor s, Functor t) => Functor (Pair s t) Source # 

Methods

fmap :: (a -> b) -> Pair s t a -> Pair s t b #

(<$) :: a -> Pair s t b -> Pair s t a #

(Applicative s, Applicative t) => Applicative (Pair s t) Source # 

Methods

pure :: a -> Pair s t a #

(<*>) :: Pair s t (a -> b) -> Pair s t a -> Pair s t b #

(*>) :: Pair s t a -> Pair s t b -> Pair s t b #

(<*) :: Pair s t a -> Pair s t b -> Pair s t a #

(Foldable s, Foldable t) => Foldable (Pair s t) Source # 

Methods

fold :: Monoid m => Pair s t m -> m #

foldMap :: Monoid m => (a -> m) -> Pair s t a -> m #

foldr :: (a -> b -> b) -> b -> Pair s t a -> b #

foldr' :: (a -> b -> b) -> b -> Pair s t a -> b #

foldl :: (b -> a -> b) -> b -> Pair s t a -> b #

foldl' :: (b -> a -> b) -> b -> Pair s t a -> b #

foldr1 :: (a -> a -> a) -> Pair s t a -> a #

foldl1 :: (a -> a -> a) -> Pair s t a -> a #

toList :: Pair s t a -> [a] #

null :: Pair s t a -> Bool #

length :: Pair s t a -> Int #

elem :: Eq a => a -> Pair s t a -> Bool #

maximum :: Ord a => Pair s t a -> a #

minimum :: Ord a => Pair s t a -> a #

sum :: Num a => Pair s t a -> a #

product :: Num a => Pair s t a -> a #

(Traversable s, Traversable t) => Traversable (Pair s t) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Pair s t a -> f (Pair s t b) #

sequenceA :: Applicative f => Pair s t (f a) -> f (Pair s t a) #

mapM :: Monad m => (a -> m b) -> Pair s t a -> m (Pair s t b) #

sequence :: Monad m => Pair s t (m a) -> m (Pair s t a) #

(Eq (s a), Eq (t a)) => Eq (Pair s t a) Source # 

Methods

(==) :: Pair s t a -> Pair s t a -> Bool #

(/=) :: Pair s t a -> Pair s t a -> Bool #

(Ord (s a), Ord (t a)) => Ord (Pair s t a) Source # 

Methods

compare :: Pair s t a -> Pair s t a -> Ordering #

(<) :: Pair s t a -> Pair s t a -> Bool #

(<=) :: Pair s t a -> Pair s t a -> Bool #

(>) :: Pair s t a -> Pair s t a -> Bool #

(>=) :: Pair s t a -> Pair s t a -> Bool #

max :: Pair s t a -> Pair s t a -> Pair s t a #

min :: Pair s t a -> Pair s t a -> Pair s t a #

(Read (s a), Read (t a)) => Read (Pair s t a) Source # 

Methods

readsPrec :: Int -> ReadS (Pair s t a) #

readList :: ReadS [Pair s t a] #

readPrec :: ReadPrec (Pair s t a) #

readListPrec :: ReadPrec [Pair s t a] #

(Show (s a), Show (t a)) => Show (Pair s t a) Source # 

Methods

showsPrec :: Int -> Pair s t a -> ShowS #

show :: Pair s t a -> String #

showList :: [Pair s t a] -> ShowS #

(NFData (s a), NFData (t a)) => NFData (Pair s t a) Source # 

Methods

rnf :: Pair s t a -> () #

data FEither f g a Source #

The analogue for Either in the category of functors.

Constructors

FLeft (f a) 
FRight (g a) 

Instances

(Functor f, Functor g) => Functor (FEither f g) Source # 

Methods

fmap :: (a -> b) -> FEither f g a -> FEither f g b #

(<$) :: a -> FEither f g b -> FEither f g a #

(Foldable f, Foldable g) => Foldable (FEither f g) Source # 

Methods

fold :: Monoid m => FEither f g m -> m #

foldMap :: Monoid m => (a -> m) -> FEither f g a -> m #

foldr :: (a -> b -> b) -> b -> FEither f g a -> b #

foldr' :: (a -> b -> b) -> b -> FEither f g a -> b #

foldl :: (b -> a -> b) -> b -> FEither f g a -> b #

foldl' :: (b -> a -> b) -> b -> FEither f g a -> b #

foldr1 :: (a -> a -> a) -> FEither f g a -> a #

foldl1 :: (a -> a -> a) -> FEither f g a -> a #

toList :: FEither f g a -> [a] #

null :: FEither f g a -> Bool #

length :: FEither f g a -> Int #

elem :: Eq a => a -> FEither f g a -> Bool #

maximum :: Ord a => FEither f g a -> a #

minimum :: Ord a => FEither f g a -> a #

sum :: Num a => FEither f g a -> a #

product :: Num a => FEither f g a -> a #

(Traversable f, Traversable g) => Traversable (FEither f g) Source # 

Methods

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

sequenceA :: Applicative f => FEither f g (f a) -> f (FEither f g a) #

mapM :: Monad m => (a -> m b) -> FEither f g a -> m (FEither f g b) #

sequence :: Monad m => FEither f g (m a) -> m (FEither f g a) #

(Eq (f a), Eq (g a)) => Eq (FEither f g a) Source # 

Methods

(==) :: FEither f g a -> FEither f g a -> Bool #

(/=) :: FEither f g a -> FEither f g a -> Bool #

(Ord (f a), Ord (g a)) => Ord (FEither f g a) Source # 

Methods

compare :: FEither f g a -> FEither f g a -> Ordering #

(<) :: FEither f g a -> FEither f g a -> Bool #

(<=) :: FEither f g a -> FEither f g a -> Bool #

(>) :: FEither f g a -> FEither f g a -> Bool #

(>=) :: FEither f g a -> FEither f g a -> Bool #

max :: FEither f g a -> FEither f g a -> FEither f g a #

min :: FEither f g a -> FEither f g a -> FEither f g a #

(Read (f a), Read (g a)) => Read (FEither f g a) Source # 

Methods

readsPrec :: Int -> ReadS (FEither f g a) #

readList :: ReadS [FEither f g a] #

readPrec :: ReadPrec (FEither f g a) #

readListPrec :: ReadPrec [FEither f g a] #

(Show (f a), Show (g a)) => Show (FEither f g a) Source # 

Methods

showsPrec :: Int -> FEither f g a -> ShowS #

show :: FEither f g a -> String #

showList :: [FEither f g a] -> ShowS #

data Convolve f g a Source #

Composition of functors.

Constructors

Convolve (f (g a)) 

Instances

(Functor f, Functor g) => Functor (Convolve f g) Source # 

Methods

fmap :: (a -> b) -> Convolve f g a -> Convolve f g b #

(<$) :: a -> Convolve f g b -> Convolve f g a #

(Foldable f, Foldable g) => Foldable (Convolve f g) Source # 

Methods

fold :: Monoid m => Convolve f g m -> m #

foldMap :: Monoid m => (a -> m) -> Convolve f g a -> m #

foldr :: (a -> b -> b) -> b -> Convolve f g a -> b #

foldr' :: (a -> b -> b) -> b -> Convolve f g a -> b #

foldl :: (b -> a -> b) -> b -> Convolve f g a -> b #

foldl' :: (b -> a -> b) -> b -> Convolve f g a -> b #

foldr1 :: (a -> a -> a) -> Convolve f g a -> a #

foldl1 :: (a -> a -> a) -> Convolve f g a -> a #

toList :: Convolve f g a -> [a] #

null :: Convolve f g a -> Bool #

length :: Convolve f g a -> Int #

elem :: Eq a => a -> Convolve f g a -> Bool #

maximum :: Ord a => Convolve f g a -> a #

minimum :: Ord a => Convolve f g a -> a #

sum :: Num a => Convolve f g a -> a #

product :: Num a => Convolve f g a -> a #

(Traversable f, Traversable g) => Traversable (Convolve f g) Source # 

Methods

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

sequenceA :: Applicative f => Convolve f g (f a) -> f (Convolve f g a) #

mapM :: Monad m => (a -> m b) -> Convolve f g a -> m (Convolve f g b) #

sequence :: Monad m => Convolve f g (m a) -> m (Convolve f g a) #

Eq (f (g a)) => Eq (Convolve f g a) Source # 

Methods

(==) :: Convolve f g a -> Convolve f g a -> Bool #

(/=) :: Convolve f g a -> Convolve f g a -> Bool #

Ord (f (g a)) => Ord (Convolve f g a) Source # 

Methods

compare :: Convolve f g a -> Convolve f g a -> Ordering #

(<) :: Convolve f g a -> Convolve f g a -> Bool #

(<=) :: Convolve f g a -> Convolve f g a -> Bool #

(>) :: Convolve f g a -> Convolve f g a -> Bool #

(>=) :: Convolve f g a -> Convolve f g a -> Bool #

max :: Convolve f g a -> Convolve f g a -> Convolve f g a #

min :: Convolve f g a -> Convolve f g a -> Convolve f g a #

Read (f (g a)) => Read (Convolve f g a) Source # 
Show (f (g a)) => Show (Convolve f g a) Source # 

Methods

showsPrec :: Int -> Convolve f g a -> ShowS #

show :: Convolve f g a -> String #

showList :: [Convolve f g a] -> ShowS #

cArr :: Diff f g -> Component f g Source #

The analogue of arr for Components.

cFirst :: Component f g -> Component (Pair f h) (Pair g h) Source #

The analogue of first for Components.

cLeft :: Component f g -> Component (FEither f h) (FEither g h) Source #

The analogue of left for Components.

cConvolve :: Functor h => Component f g -> Component (Convolve h f) (Convolve h g) Source #

The analogue of convolve for Components.

data Model :: (* -> *) -> (* -> *) -> * -> * -> * -> * where Source #

A Model f g a b c wraps a Component f g and models functions b -> c with "samples" (for model error determination) of type a.

Constructors

Model :: (Functor f, Functor g) => Component f g -> (a -> (f Double, Diff g Identity)) -> (b -> f Double) -> (g Double -> c) -> Model f g a b c 

Instances

Profunctor (Model f g a) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Model f g a b c -> Model f g a a d #

lmap :: (a -> b) -> Model f g a b c -> Model f g a a c #

rmap :: (b -> c) -> Model f g a a b -> Model f g a a c #

(#.) :: Coercible * c b => (b -> c) -> Model f g a a b -> Model f g a a c #

(.#) :: Coercible * b a => Model f g a b c -> (a -> b) -> Model f g a a c #

NFData (Model f g a b c) Source # 

Methods

rnf :: Model f g a b c -> () #

model :: Model f g a b c -> b -> c Source #

Computes the modelled function.

modelR :: MonadRandom m => Model f g a b c -> m (Model f g a b c) Source #

Generates a model with randomly initialized weights. All other properties are copied from the provided model.

modelError :: Foldable h => Model f g a b c -> h a -> Double Source #

Calculates the avarage model error for a "mini-batch" of samples.

descent Source #

Arguments

:: Foldable h 
=> Model f g a b c

the model whose error should be decreased

-> Double

the learning rate

-> h a

a mini-batch of samples

-> (Double, Model f g a b c)

returns the average sample error and the improved model

Performs one step of gradient descent/ backpropagation on the model,

type StdModel f g b c = Model f g (b, c) b c Source #

A type abbreviation for the most common type of models, where samples are just input-output tuples.

mkStdModel :: (Functor f, Functor g) => Component f g -> (c -> Diff g Identity) -> (b -> f Double) -> (g Double -> c) -> StdModel f g b c Source #

Creates a StdModel, using the simplifying assumtion that the error can be computed from the expected output allone.