grenade-0.1.0: Practical Deep Learning in Haskell

Safe HaskellNone
LanguageHaskell98

Grenade.Recurrent.Core.Network

Synopsis

Documentation

data Recurrent :: * -> * Source #

Witness type to say indicate we're building up with a recurrent layer.

Instances

(SingI Shape (RecurrentShape x), RecurrentUpdateLayer x, Num (RecurrentInputs ys)) => Num (RecurrentInputs ((:) * (Recurrent x) ys)) Source # 

Methods

(+) :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

(-) :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

(*) :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

negate :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

abs :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

signum :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

fromInteger :: Integer -> RecurrentInputs ((* ': Recurrent x) ys) #

(SingI Shape (RecurrentShape x), RecurrentUpdateLayer x, Serialize (RecurrentInputs ys)) => Serialize (RecurrentInputs ((:) * (Recurrent x) ys)) Source # 

Methods

put :: Putter (RecurrentInputs ((* ': Recurrent x) ys)) #

get :: Get (RecurrentInputs ((* ': Recurrent x) ys)) #

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

Methods

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

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

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

(SingI Shape i, RecurrentLayer x i o, Serialize x, Serialize (RecurrentNetwork xs ((:) Shape o rs))) => Serialize (RecurrentNetwork ((:) * (Recurrent x) xs) ((:) Shape i ((:) Shape o rs))) Source # 

Methods

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

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

data FeedForward :: * -> * Source #

Witness type to say indicate we're building up with a normal feed forward layer.

Instances

(UpdateLayer x, Num (RecurrentInputs ys)) => Num (RecurrentInputs ((:) * (FeedForward x) ys)) Source # 
(UpdateLayer x, Serialize (RecurrentInputs ys)) => Serialize (RecurrentInputs ((:) * (FeedForward x) ys)) Source # 

Methods

put :: Putter (RecurrentInputs ((* ': FeedForward x) ys)) #

get :: Get (RecurrentInputs ((* ': FeedForward x) ys)) #

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

Methods

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

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

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

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

Methods

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

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

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

Type of a recurrent neural network.

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

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

The definition is similar to a Network, but every layer in the type is tagged by whether it's a FeedForward Layer of a Recurrent layer.

Often, to make the definitions more concise, one will use a type alias for these empty data types.

Constructors

RNil :: SingI i => RecurrentNetwork '[] '[i] 
(:~~>) :: (SingI i, Layer x i h) => !x -> !(RecurrentNetwork xs (h ': hs)) -> RecurrentNetwork (FeedForward x ': xs) (i ': (h ': hs)) infixr 5 
(:~@>) :: (SingI i, RecurrentLayer x i h) => !x -> !(RecurrentNetwork xs (h ': hs)) -> RecurrentNetwork (Recurrent x ': xs) (i ': (h ': hs)) infixr 5 

Instances

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

Methods

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

(SingI Shape i, RecurrentLayer x i o, Serialize x, Serialize (RecurrentNetwork xs ((:) Shape o rs))) => Serialize (RecurrentNetwork ((:) * (Recurrent x) xs) ((:) Shape i ((:) Shape o rs))) Source # 

Methods

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

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

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

Methods

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

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

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

Add very simple serialisation to the recurrent network

Methods

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

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

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

Recurrent inputs (sideways shapes on an imaginary unrolled graph) Parameterised on the layers of a Network.

Instances

(SingI Shape (RecurrentShape x), RecurrentUpdateLayer x, Num (RecurrentInputs ys)) => Num (RecurrentInputs ((:) * (Recurrent x) ys)) Source # 

Methods

(+) :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

(-) :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

(*) :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

negate :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

abs :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

signum :: RecurrentInputs ((* ': Recurrent x) ys) -> RecurrentInputs ((* ': Recurrent x) ys) #

fromInteger :: Integer -> RecurrentInputs ((* ': Recurrent x) ys) #

(UpdateLayer x, Num (RecurrentInputs ys)) => Num (RecurrentInputs ((:) * (FeedForward x) ys)) Source # 
Num (RecurrentInputs ([] *)) Source # 
(SingI Shape (RecurrentShape x), RecurrentUpdateLayer x, Serialize (RecurrentInputs ys)) => Serialize (RecurrentInputs ((:) * (Recurrent x) ys)) Source # 

Methods

put :: Putter (RecurrentInputs ((* ': Recurrent x) ys)) #

get :: Get (RecurrentInputs ((* ': Recurrent x) ys)) #

(UpdateLayer x, Serialize (RecurrentInputs ys)) => Serialize (RecurrentInputs ((:) * (FeedForward x) ys)) Source # 

Methods

put :: Putter (RecurrentInputs ((* ': FeedForward x) ys)) #

get :: Get (RecurrentInputs ((* ': FeedForward x) ys)) #

Serialize (RecurrentInputs ([] *)) Source # 

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

All the information required to backpropogate through time safely.

We index on the time step length as well, to ensure that that all Tape lengths are the same.

Constructors

TRNil :: SingI i => RecurrentTapes '[] '[i] 
(:\~>) :: [Tape x i h] -> !(RecurrentTapes xs (h ': hs)) -> RecurrentTapes (FeedForward x ': xs) (i ': (h ': hs)) 
(:\@>) :: [RecTape x i h] -> !(RecurrentTapes xs (h ': hs)) -> RecurrentTapes (Recurrent x ': xs) (i ': (h ': hs)) 

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

Gradient of a network.

Parameterised on the layers of the network.

Constructors

RGNil :: RecurrentGradients '[] 
(://>) :: UpdateLayer x => [Gradient x] -> RecurrentGradients xs -> RecurrentGradients (phantom x ': xs) 

randomRecurrent :: (CreatableRecurrent xs ss, MonadRandom m) => m (RecurrentNetwork xs ss, RecurrentInputs xs) Source #

Create a network of the types requested

runRecurrentNetwork :: forall shapes layers. RecurrentNetwork layers shapes -> RecurrentInputs layers -> [S (Head shapes)] -> (RecurrentTapes layers shapes, RecurrentInputs layers, [S (Last shapes)]) Source #

runRecurrentGradient :: forall layers shapes. RecurrentNetwork layers shapes -> RecurrentTapes layers shapes -> RecurrentInputs layers -> [S (Last shapes)] -> (RecurrentGradients layers, RecurrentInputs layers, [S (Head shapes)]) Source #

applyRecurrentUpdate :: LearningParameters -> RecurrentNetwork layers shapes -> RecurrentGradients layers -> RecurrentNetwork layers shapes Source #

Apply a batch of gradients to the network Uses runUpdates which can be specialised for a layer.