Copyright | (c) Lars Brünjes, 2016 |
---|---|
License | MIT |
Maintainer | brunjlar@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
This module defines parameterized functions, components and models.
The parameterized functions are instances of the Arrow
and ArrowChoice
typeclasses, whereas
Component
s behave like Arrow
s 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.
- newtype ParamFun s t a b = ParamFun {
- runPF :: a -> t s -> b
- data Component f g = (Traversable t, Applicative t, NFData (t Double)) => Component {}
- _weights :: Lens' (Component f g) [Double]
- activate :: Component f g -> f Double -> g Double
- _component :: Lens' (Model f g a b c) (Component f g)
- data Pair s t a = Pair (s a) (t a)
- data FEither f g a
- data Convolve f g a = Convolve (f (g a))
- cArr :: Diff f g -> Component f g
- cFirst :: Component f g -> Component (Pair f h) (Pair g h)
- cLeft :: Component f g -> Component (FEither f h) (FEither g h)
- cConvolve :: Functor h => Component f g -> Component (Convolve h f) (Convolve h g)
- data Model :: (* -> *) -> (* -> *) -> * -> * -> * -> * where
- model :: Model f g a b c -> b -> c
- modelR :: MonadRandom m => Model f g a b c -> m (Model f g a b c)
- modelError :: Foldable h => Model f g a b c -> h a -> Double
- descent :: Foldable h => Model f g a b c -> Double -> h a -> (Double, Model f g a b c)
- type StdModel f g b c = Model f g (b, c) b c
- mkStdModel :: (Functor f, Functor g) => Component f g -> (c -> Diff g Identity) -> (b -> f Double) -> (g Double -> c) -> StdModel f g b c
Documentation
newtype ParamFun s t a b Source #
The type
describes parameterized functions from ParamFun
t a ba
to b
, where the
parameters are of type t s
.
When such components are composed, they all share the same parameters.
A
is a parameterized differentiable function Component
f gf Double -> g Double
.
In contrast to ParamFun
, when components are composed, parameters are not shared.
Each component carries its own collection of parameters instead.
(Traversable t, Applicative t, NFData (t Double)) => Component | |
_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.
The analogue for pairs in the category of functors.
Pair (s a) (t a) |
(Functor s, Functor t) => Functor (Pair s t) Source # | |
(Applicative s, Applicative t) => Applicative (Pair s t) Source # | |
(Foldable s, Foldable t) => Foldable (Pair s t) Source # | |
(Traversable s, Traversable t) => Traversable (Pair s t) Source # | |
(Eq (s a), Eq (t a)) => Eq (Pair s t a) Source # | |
(Ord (s a), Ord (t a)) => Ord (Pair s t a) Source # | |
(Read (s a), Read (t a)) => Read (Pair s t a) Source # | |
(Show (s a), Show (t a)) => Show (Pair s t a) Source # | |
(NFData (s a), NFData (t a)) => NFData (Pair s t a) Source # | |
The analogue for Either
in the category of functors.
(Functor f, Functor g) => Functor (FEither f g) Source # | |
(Foldable f, Foldable g) => Foldable (FEither f g) Source # | |
(Traversable f, Traversable g) => Traversable (FEither f g) Source # | |
(Eq (f a), Eq (g a)) => Eq (FEither f g a) Source # | |
(Ord (f a), Ord (g a)) => Ord (FEither f g a) Source # | |
(Read (f a), Read (g a)) => Read (FEither f g a) Source # | |
(Show (f a), Show (g a)) => Show (FEither f g a) Source # | |
Composition of functors.
Convolve (f (g a)) |
(Functor f, Functor g) => Functor (Convolve f g) Source # | |
(Foldable f, Foldable g) => Foldable (Convolve f g) Source # | |
(Traversable f, Traversable g) => Traversable (Convolve f g) Source # | |
Eq (f (g a)) => Eq (Convolve f g a) Source # | |
Ord (f (g a)) => Ord (Convolve f g a) Source # | |
Read (f (g a)) => Read (Convolve f g a) Source # | |
Show (f (g a)) => Show (Convolve f g a) Source # | |
data Model :: (* -> *) -> (* -> *) -> * -> * -> * -> * where Source #
A
wraps a Model
f g a b c
and models functions Component
f gb -> c
with "samples" (for model error determination)
of type a
.
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.
:: 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,