grenade-0.1.0: Practical Deep Learning in Haskell

Safe HaskellNone
LanguageHaskell98

Grenade.Recurrent.Layers.LSTM

Synopsis

Documentation

data LSTM :: Nat -> Nat -> * where Source #

Long Short Term Memory Recurrent unit

This is a Peephole formulation, so the recurrent shape is just the cell state, the previous output is not held or used at all.

Constructors

LSTM :: (KnownNat input, KnownNat output) => !(LSTMWeights input output) -> !(LSTMWeights input output) -> LSTM input output 

Instances

Show (LSTM i o) Source # 

Methods

showsPrec :: Int -> LSTM i o -> ShowS #

show :: LSTM i o -> String #

showList :: [LSTM i o] -> ShowS #

(KnownNat i, KnownNat o) => Serialize (LSTM i o) Source # 

Methods

put :: Putter (LSTM i o) #

get :: Get (LSTM i o) #

(KnownNat i, KnownNat o) => UpdateLayer (LSTM i o) Source # 

Associated Types

type Gradient (LSTM i o) :: * Source #

(KnownNat i, KnownNat o) => RecurrentUpdateLayer (LSTM i o) Source # 

Associated Types

type RecurrentShape (LSTM i o) :: Shape Source #

(KnownNat i, KnownNat o) => RecurrentLayer (LSTM i o) (D1 i) (D1 o) Source # 

Associated Types

type RecTape (LSTM i o) (D1 i :: Shape) (D1 o :: Shape) :: * Source #

Methods

runRecurrentForwards :: LSTM i o -> S (RecurrentShape (LSTM i o)) -> S (D1 i) -> (RecTape (LSTM i o) (D1 i) (D1 o), S (RecurrentShape (LSTM i o)), S (D1 o)) Source #

runRecurrentBackwards :: LSTM i o -> RecTape (LSTM i o) (D1 i) (D1 o) -> S (RecurrentShape (LSTM i o)) -> S (D1 o) -> (Gradient (LSTM i o), S (RecurrentShape (LSTM i o)), S (D1 i)) Source #

type Gradient (LSTM i o) Source # 
type Gradient (LSTM i o) = LSTMWeights i o
type RecurrentShape (LSTM i o) Source # 
type RecurrentShape (LSTM i o) = D1 o
type RecTape (LSTM i o) (D1 i) (D1 o) Source # 
type RecTape (LSTM i o) (D1 i) (D1 o) = (S (D1 o), S (D1 i))

data LSTMWeights :: Nat -> Nat -> * where Source #

Constructors

LSTMWeights :: (KnownNat input, KnownNat output) => {..} -> LSTMWeights input output 

Fields

randomLSTM :: forall m i o. (MonadRandom m, KnownNat i, KnownNat o) => m (LSTM i o) Source #

Generate an LSTM layer with random Weights one can also just call createRandom from UpdateLayer

Has forget gate biases set to 1 to encourage early learning.

https://github.com/karpathy/char-rnn/commit/0dfeaa454e687dd0278f036552ea1e48a0a408c9