grenade-0.1.0: Practical Deep Learning in Haskell

Copyright(c) Huw Campbell 2016-2017
LicenseBSD2
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Grenade.Core.Network

Description

This module defines the core data types and functions for non-recurrent neural networks.

Synopsis

Documentation

data Network :: [*] -> [Shape] -> * where Source #

Type of a network.

The [*] type specifies the types of the layers.

The [Shape] type specifies the shapes of data passed between the layers.

Can be considered to be a heterogeneous list of layers which are able to transform the data shapes of the network.

Constructors

NNil :: SingI i => Network '[] '[i] 
(:~>) :: (SingI i, SingI h, Layer x i h) => !x -> !(Network xs (h ': hs)) -> Network (x ': xs) (i ': (h ': hs)) infixr 5 

Instances

(Show x, Show (Network xs rs)) => Show (Network ((:) * x xs) ((:) Shape i rs)) Source # 

Methods

showsPrec :: Int -> Network ((* ': x) xs) ((Shape ': i) rs) -> ShowS #

show :: Network ((* ': x) xs) ((Shape ': i) rs) -> String #

showList :: [Network ((* ': x) xs) ((Shape ': i) rs)] -> ShowS #

Show (Network ([] *) ((:) Shape i ([] Shape))) Source # 

Methods

showsPrec :: Int -> Network [*] ((Shape ': i) [Shape]) -> ShowS #

show :: Network [*] ((Shape ': i) [Shape]) -> String #

showList :: [Network [*] ((Shape ': i) [Shape])] -> ShowS #

(SingI Shape i, SingI Shape o, Layer x i o, Serialize x, Serialize (Network xs ((:) Shape o rs))) => Serialize (Network ((:) * x xs) ((:) Shape i ((:) Shape o rs))) Source # 

Methods

put :: Putter (Network ((* ': x) xs) ((Shape ': i) ((Shape ': o) rs))) #

get :: Get (Network ((* ': x) xs) ((Shape ': i) ((Shape ': o) rs))) #

SingI Shape i => Serialize (Network ([] *) ((:) Shape i ([] Shape))) Source #

Add very simple serialisation to the network

Methods

put :: Putter (Network [*] ((Shape ': i) [Shape])) #

get :: Get (Network [*] ((Shape ': i) [Shape])) #

CreatableNetwork sublayers subshapes => UpdateLayer (Network sublayers subshapes) Source #

Ultimate composition.

This allows a complete network to be treated as a layer in a larger network.

Associated Types

type Gradient (Network sublayers subshapes) :: * Source #

Methods

runUpdate :: LearningParameters -> Network sublayers subshapes -> Gradient (Network sublayers subshapes) -> Network sublayers subshapes Source #

createRandom :: MonadRandom m => m (Network sublayers subshapes) Source #

runUpdates :: LearningParameters -> Network sublayers subshapes -> [Gradient (Network sublayers subshapes)] -> Network sublayers subshapes Source #

(CreatableNetwork sublayers subshapes, (~) Shape i (Head Shape subshapes), (~) Shape o (Last Shape subshapes)) => Layer (Network sublayers subshapes) i o Source #

Ultimate composition.

This allows a complete network to be treated as a layer in a larger network.

Associated Types

type Tape (Network sublayers subshapes) (i :: Shape) (o :: Shape) :: * Source #

Methods

runForwards :: Network sublayers subshapes -> S i -> (Tape (Network sublayers subshapes) i o, S o) Source #

runBackwards :: Network sublayers subshapes -> Tape (Network sublayers subshapes) i o -> S o -> (Gradient (Network sublayers subshapes), S i) Source #

type Gradient (Network sublayers subshapes) Source # 
type Gradient (Network sublayers subshapes) = Gradients sublayers
type Tape (Network sublayers subshapes) i o Source # 
type Tape (Network sublayers subshapes) i o = Tapes sublayers subshapes

data Gradients :: [*] -> * where Source #

Gradient of a network.

Parameterised on the layers of the network.

Constructors

GNil :: Gradients '[] 
(:/>) :: UpdateLayer x => Gradient x -> Gradients xs -> Gradients (x ': xs) 

data Tapes :: [*] -> [Shape] -> * where Source #

Wegnert Tape of a network.

Parameterised on the layers and shapes of the network.

Constructors

TNil :: SingI i => Tapes '[] '[i] 
(:\>) :: (SingI i, SingI h, Layer x i h) => !(Tape x i h) -> !(Tapes xs (h ': hs)) -> Tapes (x ': xs) (i ': (h ': hs)) 

runNetwork :: forall layers shapes. Network layers shapes -> S (Head shapes) -> (Tapes layers shapes, S (Last shapes)) Source #

Running a network forwards with some input data.

This gives the output, and the Wengert tape required for back propagation.

runGradient :: forall layers shapes. Network layers shapes -> Tapes layers shapes -> S (Last shapes) -> (Gradients layers, S (Head shapes)) Source #

Running a loss gradient back through the network.

This requires a Wengert tape, generated with the appropriate input for the loss.

Gives the gradients for the layer, and the gradient across the input (which may not be required).

applyUpdate :: LearningParameters -> Network layers shapes -> Gradients layers -> Network layers shapes Source #

Apply one step of stochastic gradient decent across the network.

randomNetwork :: (CreatableNetwork xs ss, MonadRandom m) => m (Network xs ss) Source #

Create a network with randomly initialised weights.

Calls to this function will not compile if the type of the neural network is not sound.