neural-0.1.1.0: Neural Networks in native Haskell

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

Numeric.Neural.Model

Description

This module defines parameterized functions, components and models. The parameterized functions and components are instances of the Arrow typeclass and can therefore 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 t a b Source

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

Constructors

ParamFun 

Fields

runPF :: a -> t Analytic -> b
 

data Component a b Source

A Component a b is a parameterized function from a to b, combined with some collection of analytic parameters, In contrast to ParamFun, when components are composed, parameters are not shared. Each component carries its own collection of parameters instead.

Constructors

forall t . (Traversable t, Applicative t) => Component 

Fields

weights :: t Double

the specific parameter values

compute :: ParamFun t a b

the encapsulated parameterized function

initR :: forall m. MonadRandom m => m (t Double)

randomly sets the parameters

_weights :: Lens' (Component a b) [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 a b -> a -> b Source

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

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

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

Constructors

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

Instances

Profunctor (Model f g a) Source 

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

A Lens for accessing the component embedded in a model.

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 Analytic) (g Analytic) -> (c -> g Analytic -> Analytic) -> (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.