grenade-0.1.0: Practical Deep Learning in Haskell

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

Grenade.Core.Layer

Description

This module defines what a Layer is in a Grenade neural network.

There are two classes of interest: UpdateLayer and Layer.

UpdateLayer is required for all types which are used as a layer in a network. Having no shape information, this class is agnotostic to the input and output data of the layer.

An instance of Layer on the other hand is required for usage in a neural network, but also specifies the shapes of data that the network can transform. Multiple instance of Layer are permitted for a single type, to transform different shapes. The Reshape layer for example can act as a flattening layer, and its inverse, projecting a 1D shape up to 2 or 3 dimensions.

Instances of Layer should be as strict as possible, and not emit runtime errors.

Synopsis

Documentation

class UpdateLayer x => Layer x i o where Source #

Class for a layer. All layers implement this, however, they don't need to implement it for all shapes, only ones which are appropriate.

Minimal complete definition

runForwards, runBackwards

Associated Types

type Tape x i o :: * Source #

The Wengert tape for this layer. Includes all that is required to generate the back propagated gradients efficiently. As a default, `S i` is fine.

Methods

runForwards :: x -> S i -> (Tape x i o, S o) Source #

Used in training and scoring. Take the input from the previous layer, and give the output from this layer.

runBackwards :: x -> Tape x i o -> S o -> (Gradient x, S i) Source #

Back propagate a step. Takes the current layer, the input that the layer gave from the input and the back propagated derivatives from the layer above.

Returns the gradient layer and the derivatives to push back further.

Instances

((~) Shape a b, SingI Shape a) => Layer Logit a b Source # 

Associated Types

type Tape Logit (a :: Shape) (b :: Shape) :: * Source #

Methods

runForwards :: Logit -> S a -> (Tape Logit a b, S b) Source #

runBackwards :: Logit -> Tape Logit a b -> S b -> (Gradient Logit, S a) Source #

((~) Shape a b, SingI Shape a) => Layer Tanh a b Source # 

Associated Types

type Tape Tanh (a :: Shape) (b :: Shape) :: * Source #

Methods

runForwards :: Tanh -> S a -> (Tape Tanh a b, S b) Source #

runBackwards :: Tanh -> Tape Tanh a b -> S b -> (Gradient Tanh, S a) Source #

(~) Shape a b => Layer Trivial a b Source # 

Associated Types

type Tape Trivial (a :: Shape) (b :: Shape) :: * Source #

Methods

runForwards :: Trivial -> S a -> (Tape Trivial a b, S b) Source #

runBackwards :: Trivial -> Tape Trivial a b -> S b -> (Gradient Trivial, S a) Source #

KnownNat i => Layer Dropout (D1 i) (D1 i) Source # 

Associated Types

type Tape Dropout (D1 i :: Shape) (D1 i :: Shape) :: * Source #

Methods

runForwards :: Dropout -> S (D1 i) -> (Tape Dropout (D1 i) (D1 i), S (D1 i)) Source #

runBackwards :: Dropout -> Tape Dropout (D1 i) (D1 i) -> S (D1 i) -> (Gradient Dropout, S (D1 i)) Source #

KnownNat i => Layer Elu (D1 i) (D1 i) Source # 

Associated Types

type Tape Elu (D1 i :: Shape) (D1 i :: Shape) :: * Source #

Methods

runForwards :: Elu -> S (D1 i) -> (Tape Elu (D1 i) (D1 i), S (D1 i)) Source #

runBackwards :: Elu -> Tape Elu (D1 i) (D1 i) -> S (D1 i) -> (Gradient Elu, S (D1 i)) Source #

KnownNat i => Layer Relu (D1 i) (D1 i) Source # 

Associated Types

type Tape Relu (D1 i :: Shape) (D1 i :: Shape) :: * Source #

Methods

runForwards :: Relu -> S (D1 i) -> (Tape Relu (D1 i) (D1 i), S (D1 i)) Source #

runBackwards :: Relu -> Tape Relu (D1 i) (D1 i) -> S (D1 i) -> (Gradient Relu, S (D1 i)) Source #

KnownNat i => Layer Softmax (D1 i) (D1 i) Source # 

Associated Types

type Tape Softmax (D1 i :: Shape) (D1 i :: Shape) :: * Source #

Methods

runForwards :: Softmax -> S (D1 i) -> (Tape Softmax (D1 i) (D1 i), S (D1 i)) Source #

runBackwards :: Softmax -> Tape Softmax (D1 i) (D1 i) -> S (D1 i) -> (Gradient Softmax, S (D1 i)) Source #

(KnownNat a, KnownNat x, KnownNat y, (~) Nat a (* x y)) => Layer Reshape (D1 a) (D2 x y) Source # 

Associated Types

type Tape Reshape (D1 a :: Shape) (D2 x y :: Shape) :: * Source #

Methods

runForwards :: Reshape -> S (D1 a) -> (Tape Reshape (D1 a) (D2 x y), S (D2 x y)) Source #

runBackwards :: Reshape -> Tape Reshape (D1 a) (D2 x y) -> S (D2 x y) -> (Gradient Reshape, S (D1 a)) Source #

(KnownNat a, KnownNat x, KnownNat y, KnownNat (* x z), KnownNat z, (~) Nat a (* (* x y) z)) => Layer Reshape (D1 a) (D3 x y z) Source # 

Associated Types

type Tape Reshape (D1 a :: Shape) (D3 x y z :: Shape) :: * Source #

Methods

runForwards :: Reshape -> S (D1 a) -> (Tape Reshape (D1 a) (D3 x y z), S (D3 x y z)) Source #

runBackwards :: Reshape -> Tape Reshape (D1 a) (D3 x y z) -> S (D3 x y z) -> (Gradient Reshape, S (D1 a)) Source #

(KnownNat a, KnownNat x, KnownNat y, (~) Nat a (* x y)) => Layer Reshape (D2 x y) (D1 a) Source # 

Associated Types

type Tape Reshape (D2 x y :: Shape) (D1 a :: Shape) :: * Source #

Methods

runForwards :: Reshape -> S (D2 x y) -> (Tape Reshape (D2 x y) (D1 a), S (D1 a)) Source #

runBackwards :: Reshape -> Tape Reshape (D2 x y) (D1 a) -> S (D1 a) -> (Gradient Reshape, S (D2 x y)) Source #

(KnownNat i, KnownNat j) => Layer Elu (D2 i j) (D2 i j) Source # 

Associated Types

type Tape Elu (D2 i j :: Shape) (D2 i j :: Shape) :: * Source #

Methods

runForwards :: Elu -> S (D2 i j) -> (Tape Elu (D2 i j) (D2 i j), S (D2 i j)) Source #

runBackwards :: Elu -> Tape Elu (D2 i j) (D2 i j) -> S (D2 i j) -> (Gradient Elu, S (D2 i j)) Source #

(KnownNat i, KnownNat j) => Layer Relu (D2 i j) (D2 i j) Source # 

Associated Types

type Tape Relu (D2 i j :: Shape) (D2 i j :: Shape) :: * Source #

Methods

runForwards :: Relu -> S (D2 i j) -> (Tape Relu (D2 i j) (D2 i j), S (D2 i j)) Source #

runBackwards :: Relu -> Tape Relu (D2 i j) (D2 i j) -> S (D2 i j) -> (Gradient Relu, S (D2 i j)) Source #

(KnownNat y, KnownNat x, KnownNat z, (~) Nat z 1) => Layer Reshape (D2 x y) (D3 x y z) Source # 

Associated Types

type Tape Reshape (D2 x y :: Shape) (D3 x y z :: Shape) :: * Source #

Methods

runForwards :: Reshape -> S (D2 x y) -> (Tape Reshape (D2 x y) (D3 x y z), S (D3 x y z)) Source #

runBackwards :: Reshape -> Tape Reshape (D2 x y) (D3 x y z) -> S (D3 x y z) -> (Gradient Reshape, S (D2 x y)) Source #

(KnownNat a, KnownNat x, KnownNat y, KnownNat (* x z), KnownNat z, (~) Nat a (* (* x y) z)) => Layer Reshape (D3 x y z) (D1 a) Source # 

Associated Types

type Tape Reshape (D3 x y z :: Shape) (D1 a :: Shape) :: * Source #

Methods

runForwards :: Reshape -> S (D3 x y z) -> (Tape Reshape (D3 x y z) (D1 a), S (D1 a)) Source #

runBackwards :: Reshape -> Tape Reshape (D3 x y z) (D1 a) -> S (D1 a) -> (Gradient Reshape, S (D3 x y z)) Source #

(KnownNat y, KnownNat x, KnownNat z, (~) Nat z 1) => Layer Reshape (D3 x y z) (D2 x y) Source # 

Associated Types

type Tape Reshape (D3 x y z :: Shape) (D2 x y :: Shape) :: * Source #

Methods

runForwards :: Reshape -> S (D3 x y z) -> (Tape Reshape (D3 x y z) (D2 x y), S (D2 x y)) Source #

runBackwards :: Reshape -> Tape Reshape (D3 x y z) (D2 x y) -> S (D2 x y) -> (Gradient Reshape, S (D3 x y z)) Source #

(KnownNat i, KnownNat j, KnownNat k) => Layer Elu (D3 i j k) (D3 i j k) Source # 

Associated Types

type Tape Elu (D3 i j k :: Shape) (D3 i j k :: Shape) :: * Source #

Methods

runForwards :: Elu -> S (D3 i j k) -> (Tape Elu (D3 i j k) (D3 i j k), S (D3 i j k)) Source #

runBackwards :: Elu -> Tape Elu (D3 i j k) (D3 i j k) -> S (D3 i j k) -> (Gradient Elu, S (D3 i j k)) Source #

(KnownNat i, KnownNat j, KnownNat k) => Layer Relu (D3 i j k) (D3 i j k) Source # 

Associated Types

type Tape Relu (D3 i j k :: Shape) (D3 i j k :: Shape) :: * Source #

Methods

runForwards :: Relu -> S (D3 i j k) -> (Tape Relu (D3 i j k) (D3 i j k), S (D3 i j k)) Source #

runBackwards :: Relu -> Tape Relu (D3 i j k) (D3 i j k) -> S (D3 i j k) -> (Gradient Relu, S (D3 i j k)) 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 #

(SingI Shape i, SingI Shape o, Layer x i o, Layer y i o) => Layer (Merge x y) i o Source #

Combine the outputs and the inputs, summing the output shape

Associated Types

type Tape (Merge x y) (i :: Shape) (o :: Shape) :: * Source #

Methods

runForwards :: Merge x y -> S i -> (Tape (Merge x y) i o, S o) Source #

runBackwards :: Merge x y -> Tape (Merge x y) i o -> S o -> (Gradient (Merge x y), S i) Source #

(KnownNat i, KnownNat o) => Layer (FullyConnected i o) (D1 i) (D1 o) Source # 

Associated Types

type Tape (FullyConnected i o) (D1 i :: Shape) (D1 o :: Shape) :: * Source #

Methods

runForwards :: FullyConnected i o -> S (D1 i) -> (Tape (FullyConnected i o) (D1 i) (D1 o), S (D1 o)) Source #

runBackwards :: FullyConnected i o -> Tape (FullyConnected i o) (D1 i) (D1 o) -> S (D1 o) -> (Gradient (FullyConnected i o), S (D1 i)) Source #

(SingI Shape i, Layer x i (D1 m), Layer y i (D1 n), KnownNat o, KnownNat m, KnownNat n, (~) Nat o ((+) m n), (~) Nat n ((-) o m), (~) Bool ((<=?) m o) True) => Layer (Concat (D1 m) x (D1 n) y) i (D1 o) Source # 

Associated Types

type Tape (Concat (D1 m) x (D1 n) y) (i :: Shape) (D1 o :: Shape) :: * Source #

Methods

runForwards :: Concat (D1 m) x (D1 n) y -> S i -> (Tape (Concat (D1 m) x (D1 n) y) i (D1 o), S (D1 o)) Source #

runBackwards :: Concat (D1 m) x (D1 n) y -> Tape (Concat (D1 m) x (D1 n) y) i (D1 o) -> S (D1 o) -> (Gradient (Concat (D1 m) x (D1 n) y), S i) Source #

(SingI Shape i, Layer x i (D1 o), Layer y i (D1 o)) => Layer (Concat (D1 o) x (D1 o) y) i (D2 2 o) Source # 

Associated Types

type Tape (Concat (D1 o) x (D1 o) y) (i :: Shape) (D2 2 o :: Shape) :: * Source #

Methods

runForwards :: Concat (D1 o) x (D1 o) y -> S i -> (Tape (Concat (D1 o) x (D1 o) y) i (D2 2 o), S (D2 2 o)) Source #

runBackwards :: Concat (D1 o) x (D1 o) y -> Tape (Concat (D1 o) x (D1 o) y) i (D2 2 o) -> S (D2 2 o) -> (Gradient (Concat (D1 o) x (D1 o) y), S i) Source #

(SingI Shape i, Layer x i (D3 rows cols m), Layer y i (D3 rows cols n), KnownNat (* rows n), KnownNat (* rows m), KnownNat (* rows o), KnownNat o, KnownNat m, KnownNat n, (~) Nat ((+) (* rows m) (* rows n)) (* rows o), (~) Nat ((-) (* rows o) (* rows m)) (* rows n), (~) Bool ((<=?) (* rows m) (* rows o)) True) => Layer (Concat (D3 rows cols m) x (D3 rows cols n) y) i (D3 rows cols o) Source #

Concat 3D shapes, increasing the number of channels.

Associated Types

type Tape (Concat (D3 rows cols m) x (D3 rows cols n) y) (i :: Shape) (D3 rows cols o :: Shape) :: * Source #

Methods

runForwards :: Concat (D3 rows cols m) x (D3 rows cols n) y -> S i -> (Tape (Concat (D3 rows cols m) x (D3 rows cols n) y) i (D3 rows cols o), S (D3 rows cols o)) Source #

runBackwards :: Concat (D3 rows cols m) x (D3 rows cols n) y -> Tape (Concat (D3 rows cols m) x (D3 rows cols n) y) i (D3 rows cols o) -> S (D3 rows cols o) -> (Gradient (Concat (D3 rows cols m) x (D3 rows cols n) y), S i) Source #

(KnownNat cropLeft, KnownNat cropTop, KnownNat cropRight, KnownNat cropBottom, KnownNat inputRows, KnownNat inputColumns, KnownNat outputRows, KnownNat outputColumns, (~) Nat ((-) ((-) inputRows cropTop) cropBottom) outputRows, (~) Nat ((-) ((-) inputColumns cropLeft) cropRight) outputColumns) => Layer (Crop cropLeft cropTop cropRight cropBottom) (D2 inputRows inputColumns) (D2 outputRows outputColumns) Source #

A two dimentional image can be cropped.

Associated Types

type Tape (Crop cropLeft cropTop cropRight cropBottom) (D2 inputRows inputColumns :: Shape) (D2 outputRows outputColumns :: Shape) :: * Source #

Methods

runForwards :: Crop cropLeft cropTop cropRight cropBottom -> S (D2 inputRows inputColumns) -> (Tape (Crop cropLeft cropTop cropRight cropBottom) (D2 inputRows inputColumns) (D2 outputRows outputColumns), S (D2 outputRows outputColumns)) Source #

runBackwards :: Crop cropLeft cropTop cropRight cropBottom -> Tape (Crop cropLeft cropTop cropRight cropBottom) (D2 inputRows inputColumns) (D2 outputRows outputColumns) -> S (D2 outputRows outputColumns) -> (Gradient (Crop cropLeft cropTop cropRight cropBottom), S (D2 inputRows inputColumns)) Source #

(KnownNat padLeft, KnownNat padTop, KnownNat padRight, KnownNat padBottom, KnownNat inputRows, KnownNat inputColumns, KnownNat outputRows, KnownNat outputColumns, (~) Nat ((+) ((+) inputRows padTop) padBottom) outputRows, (~) Nat ((+) ((+) inputColumns padLeft) padRight) outputColumns) => Layer (Pad padLeft padTop padRight padBottom) (D2 inputRows inputColumns) (D2 outputRows outputColumns) Source #

A two dimentional image can be padped.

Associated Types

type Tape (Pad padLeft padTop padRight padBottom) (D2 inputRows inputColumns :: Shape) (D2 outputRows outputColumns :: Shape) :: * Source #

Methods

runForwards :: Pad padLeft padTop padRight padBottom -> S (D2 inputRows inputColumns) -> (Tape (Pad padLeft padTop padRight padBottom) (D2 inputRows inputColumns) (D2 outputRows outputColumns), S (D2 outputRows outputColumns)) Source #

runBackwards :: Pad padLeft padTop padRight padBottom -> Tape (Pad padLeft padTop padRight padBottom) (D2 inputRows inputColumns) (D2 outputRows outputColumns) -> S (D2 outputRows outputColumns) -> (Gradient (Pad padLeft padTop padRight padBottom), S (D2 inputRows inputColumns)) Source #

(KnownNat kernelRows, KnownNat kernelColumns, KnownNat strideRows, KnownNat strideColumns, KnownNat inputRows, KnownNat inputColumns, KnownNat outputRows, KnownNat outputColumns, (~) Nat (* ((-) outputRows 1) strideRows) ((-) inputRows kernelRows), (~) Nat (* ((-) outputColumns 1) strideColumns) ((-) inputColumns kernelColumns)) => Layer (Pooling kernelRows kernelColumns strideRows strideColumns) (D2 inputRows inputColumns) (D2 outputRows outputColumns) Source #

A two dimentional image can be pooled.

Associated Types

type Tape (Pooling kernelRows kernelColumns strideRows strideColumns) (D2 inputRows inputColumns :: Shape) (D2 outputRows outputColumns :: Shape) :: * Source #

Methods

runForwards :: Pooling kernelRows kernelColumns strideRows strideColumns -> S (D2 inputRows inputColumns) -> (Tape (Pooling kernelRows kernelColumns strideRows strideColumns) (D2 inputRows inputColumns) (D2 outputRows outputColumns), S (D2 outputRows outputColumns)) Source #

runBackwards :: Pooling kernelRows kernelColumns strideRows strideColumns -> Tape (Pooling kernelRows kernelColumns strideRows strideColumns) (D2 inputRows inputColumns) (D2 outputRows outputColumns) -> S (D2 outputRows outputColumns) -> (Gradient (Pooling kernelRows kernelColumns strideRows strideColumns), S (D2 inputRows inputColumns)) Source #

(KnownNat cropLeft, KnownNat cropTop, KnownNat cropRight, KnownNat cropBottom, KnownNat inputRows, KnownNat inputColumns, KnownNat outputRows, KnownNat outputColumns, KnownNat channels, KnownNat (* inputRows channels), KnownNat (* outputRows channels), (~) Nat ((+) ((+) outputRows cropTop) cropBottom) inputRows, (~) Nat ((+) ((+) outputColumns cropLeft) cropRight) inputColumns) => Layer (Crop cropLeft cropTop cropRight cropBottom) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels) Source #

A two dimentional image can be cropped.

Associated Types

type Tape (Crop cropLeft cropTop cropRight cropBottom) (D3 inputRows inputColumns channels :: Shape) (D3 outputRows outputColumns channels :: Shape) :: * Source #

Methods

runForwards :: Crop cropLeft cropTop cropRight cropBottom -> S (D3 inputRows inputColumns channels) -> (Tape (Crop cropLeft cropTop cropRight cropBottom) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels), S (D3 outputRows outputColumns channels)) Source #

runBackwards :: Crop cropLeft cropTop cropRight cropBottom -> Tape (Crop cropLeft cropTop cropRight cropBottom) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels) -> S (D3 outputRows outputColumns channels) -> (Gradient (Crop cropLeft cropTop cropRight cropBottom), S (D3 inputRows inputColumns channels)) Source #

(KnownNat padLeft, KnownNat padTop, KnownNat padRight, KnownNat padBottom, KnownNat inputRows, KnownNat inputColumns, KnownNat outputRows, KnownNat outputColumns, KnownNat channels, KnownNat (* inputRows channels), KnownNat (* outputRows channels), (~) Nat ((+) ((+) inputRows padTop) padBottom) outputRows, (~) Nat ((+) ((+) inputColumns padLeft) padRight) outputColumns) => Layer (Pad padLeft padTop padRight padBottom) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels) Source #

A two dimentional image can be padped.

Associated Types

type Tape (Pad padLeft padTop padRight padBottom) (D3 inputRows inputColumns channels :: Shape) (D3 outputRows outputColumns channels :: Shape) :: * Source #

Methods

runForwards :: Pad padLeft padTop padRight padBottom -> S (D3 inputRows inputColumns channels) -> (Tape (Pad padLeft padTop padRight padBottom) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels), S (D3 outputRows outputColumns channels)) Source #

runBackwards :: Pad padLeft padTop padRight padBottom -> Tape (Pad padLeft padTop padRight padBottom) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels) -> S (D3 outputRows outputColumns channels) -> (Gradient (Pad padLeft padTop padRight padBottom), S (D3 inputRows inputColumns channels)) Source #

(KnownNat kernelRows, KnownNat kernelColumns, KnownNat strideRows, KnownNat strideColumns, KnownNat inputRows, KnownNat inputColumns, KnownNat outputRows, KnownNat outputColumns, KnownNat channels, KnownNat (* outputRows channels), (~) Nat (* ((-) outputRows 1) strideRows) ((-) inputRows kernelRows), (~) Nat (* ((-) outputColumns 1) strideColumns) ((-) inputColumns kernelColumns)) => Layer (Pooling kernelRows kernelColumns strideRows strideColumns) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels) Source #

A three dimensional image can be pooled on each layer.

Associated Types

type Tape (Pooling kernelRows kernelColumns strideRows strideColumns) (D3 inputRows inputColumns channels :: Shape) (D3 outputRows outputColumns channels :: Shape) :: * Source #

Methods

runForwards :: Pooling kernelRows kernelColumns strideRows strideColumns -> S (D3 inputRows inputColumns channels) -> (Tape (Pooling kernelRows kernelColumns strideRows strideColumns) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels), S (D3 outputRows outputColumns channels)) Source #

runBackwards :: Pooling kernelRows kernelColumns strideRows strideColumns -> Tape (Pooling kernelRows kernelColumns strideRows strideColumns) (D3 inputRows inputColumns channels) (D3 outputRows outputColumns channels) -> S (D3 outputRows outputColumns channels) -> (Gradient (Pooling kernelRows kernelColumns strideRows strideColumns), S (D3 inputRows inputColumns channels)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, (~) Nat (* ((-) outputRows 1) strideRows) ((-) inputRows kernelRows), (~) Nat (* ((-) outputCols 1) strideCols) ((-) inputCols kernelCols), KnownNat (* (* kernelRows kernelCols) 1), KnownNat (* outputRows 1)) => Layer (Convolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D2 outputRows outputCols) Source #

A two dimensional image may have a convolution filter applied to it producing a two dimensional image if both channels and filters is 1.

Associated Types

type Tape (Convolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols :: Shape) (D2 outputRows outputCols :: Shape) :: * Source #

Methods

runForwards :: Convolution 1 1 kernelRows kernelCols strideRows strideCols -> S (D2 inputRows inputCols) -> (Tape (Convolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D2 outputRows outputCols), S (D2 outputRows outputCols)) Source #

runBackwards :: Convolution 1 1 kernelRows kernelCols strideRows strideCols -> Tape (Convolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D2 outputRows outputCols) -> S (D2 outputRows outputCols) -> (Gradient (Convolution 1 1 kernelRows kernelCols strideRows strideCols), S (D2 inputRows inputCols)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, (~) Nat (* ((-) inputRows 1) strideRows) ((-) outputRows kernelRows), (~) Nat (* ((-) inputCols 1) strideCols) ((-) outputCols kernelCols), KnownNat (* (* kernelRows kernelCols) 1), KnownNat (* outputRows 1)) => Layer (Deconvolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D2 outputRows outputCols) Source #

A two dimentional image may have a Deconvolution filter applied to it

Associated Types

type Tape (Deconvolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols :: Shape) (D2 outputRows outputCols :: Shape) :: * Source #

Methods

runForwards :: Deconvolution 1 1 kernelRows kernelCols strideRows strideCols -> S (D2 inputRows inputCols) -> (Tape (Deconvolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D2 outputRows outputCols), S (D2 outputRows outputCols)) Source #

runBackwards :: Deconvolution 1 1 kernelRows kernelCols strideRows strideCols -> Tape (Deconvolution 1 1 kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D2 outputRows outputCols) -> S (D2 outputRows outputCols) -> (Gradient (Deconvolution 1 1 kernelRows kernelCols strideRows strideCols), S (D2 inputRows inputCols)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat filters, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, (~) Nat (* ((-) outputRows 1) strideRows) ((-) inputRows kernelRows), (~) Nat (* ((-) outputCols 1) strideCols) ((-) inputCols kernelCols), KnownNat (* (* kernelRows kernelCols) 1), KnownNat (* outputRows filters)) => Layer (Convolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D3 outputRows outputCols filters) Source #

A two dimentional image may have a convolution filter applied to it

Associated Types

type Tape (Convolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols :: Shape) (D3 outputRows outputCols filters :: Shape) :: * Source #

Methods

runForwards :: Convolution 1 filters kernelRows kernelCols strideRows strideCols -> S (D2 inputRows inputCols) -> (Tape (Convolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D3 outputRows outputCols filters), S (D3 outputRows outputCols filters)) Source #

runBackwards :: Convolution 1 filters kernelRows kernelCols strideRows strideCols -> Tape (Convolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D3 outputRows outputCols filters) -> S (D3 outputRows outputCols filters) -> (Gradient (Convolution 1 filters kernelRows kernelCols strideRows strideCols), S (D2 inputRows inputCols)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat filters, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, (~) Nat (* ((-) inputRows 1) strideRows) ((-) outputRows kernelRows), (~) Nat (* ((-) inputCols 1) strideCols) ((-) outputCols kernelCols), KnownNat (* (* kernelRows kernelCols) filters), KnownNat (* outputRows filters)) => Layer (Deconvolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D3 outputRows outputCols filters) Source #

A two dimentional image may have a Deconvolution filter applied to it

Associated Types

type Tape (Deconvolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols :: Shape) (D3 outputRows outputCols filters :: Shape) :: * Source #

Methods

runForwards :: Deconvolution 1 filters kernelRows kernelCols strideRows strideCols -> S (D2 inputRows inputCols) -> (Tape (Deconvolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D3 outputRows outputCols filters), S (D3 outputRows outputCols filters)) Source #

runBackwards :: Deconvolution 1 filters kernelRows kernelCols strideRows strideCols -> Tape (Deconvolution 1 filters kernelRows kernelCols strideRows strideCols) (D2 inputRows inputCols) (D3 outputRows outputCols filters) -> S (D3 outputRows outputCols filters) -> (Gradient (Deconvolution 1 filters kernelRows kernelCols strideRows strideCols), S (D2 inputRows inputCols)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, KnownNat channels, (~) Nat (* ((-) outputRows 1) strideRows) ((-) inputRows kernelRows), (~) Nat (* ((-) outputCols 1) strideCols) ((-) inputCols kernelCols), KnownNat (* (* kernelRows kernelCols) channels), KnownNat (* outputRows 1)) => Layer (Convolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D2 outputRows outputCols) Source #

A three dimensional image can produce a 2D image from a convolution with 1 filter

Associated Types

type Tape (Convolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels :: Shape) (D2 outputRows outputCols :: Shape) :: * Source #

Methods

runForwards :: Convolution channels 1 kernelRows kernelCols strideRows strideCols -> S (D3 inputRows inputCols channels) -> (Tape (Convolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D2 outputRows outputCols), S (D2 outputRows outputCols)) Source #

runBackwards :: Convolution channels 1 kernelRows kernelCols strideRows strideCols -> Tape (Convolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D2 outputRows outputCols) -> S (D2 outputRows outputCols) -> (Gradient (Convolution channels 1 kernelRows kernelCols strideRows strideCols), S (D3 inputRows inputCols channels)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, (~) Nat (* ((-) inputRows 1) strideRows) ((-) outputRows kernelRows), (~) Nat (* ((-) inputCols 1) strideCols) ((-) outputCols kernelCols), KnownNat (* (* kernelRows kernelCols) 1), KnownNat (* outputRows 1), KnownNat channels) => Layer (Deconvolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D2 outputRows outputCols) Source #

A two dimentional image may have a Deconvolution filter applied to it

Associated Types

type Tape (Deconvolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels :: Shape) (D2 outputRows outputCols :: Shape) :: * Source #

Methods

runForwards :: Deconvolution channels 1 kernelRows kernelCols strideRows strideCols -> S (D3 inputRows inputCols channels) -> (Tape (Deconvolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D2 outputRows outputCols), S (D2 outputRows outputCols)) Source #

runBackwards :: Deconvolution channels 1 kernelRows kernelCols strideRows strideCols -> Tape (Deconvolution channels 1 kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D2 outputRows outputCols) -> S (D2 outputRows outputCols) -> (Gradient (Deconvolution channels 1 kernelRows kernelCols strideRows strideCols), S (D3 inputRows inputCols channels)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat filters, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, KnownNat channels, (~) Nat (* ((-) outputRows 1) strideRows) ((-) inputRows kernelRows), (~) Nat (* ((-) outputCols 1) strideCols) ((-) inputCols kernelCols), KnownNat (* (* kernelRows kernelCols) channels), KnownNat (* outputRows filters)) => Layer (Convolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D3 outputRows outputCols filters) Source #

A three dimensional image (or 2d with many channels) can have an appropriately sized convolution filter run across it.

Associated Types

type Tape (Convolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels :: Shape) (D3 outputRows outputCols filters :: Shape) :: * Source #

Methods

runForwards :: Convolution channels filters kernelRows kernelCols strideRows strideCols -> S (D3 inputRows inputCols channels) -> (Tape (Convolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D3 outputRows outputCols filters), S (D3 outputRows outputCols filters)) Source #

runBackwards :: Convolution channels filters kernelRows kernelCols strideRows strideCols -> Tape (Convolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D3 outputRows outputCols filters) -> S (D3 outputRows outputCols filters) -> (Gradient (Convolution channels filters kernelRows kernelCols strideRows strideCols), S (D3 inputRows inputCols channels)) Source #

(KnownNat kernelRows, KnownNat kernelCols, KnownNat filters, KnownNat strideRows, KnownNat strideCols, KnownNat inputRows, KnownNat inputCols, KnownNat outputRows, KnownNat outputCols, KnownNat channels, (~) Nat (* ((-) inputRows 1) strideRows) ((-) outputRows kernelRows), (~) Nat (* ((-) inputCols 1) strideCols) ((-) outputCols kernelCols), KnownNat (* (* kernelRows kernelCols) filters), KnownNat (* outputRows filters)) => Layer (Deconvolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D3 outputRows outputCols filters) Source #

A three dimensional image (or 2d with many channels) can have an appropriately sized Deconvolution filter run across it.

Associated Types

type Tape (Deconvolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels :: Shape) (D3 outputRows outputCols filters :: Shape) :: * Source #

Methods

runForwards :: Deconvolution channels filters kernelRows kernelCols strideRows strideCols -> S (D3 inputRows inputCols channels) -> (Tape (Deconvolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D3 outputRows outputCols filters), S (D3 outputRows outputCols filters)) Source #

runBackwards :: Deconvolution channels filters kernelRows kernelCols strideRows strideCols -> Tape (Deconvolution channels filters kernelRows kernelCols strideRows strideCols) (D3 inputRows inputCols channels) (D3 outputRows outputCols filters) -> S (D3 outputRows outputCols filters) -> (Gradient (Deconvolution channels filters kernelRows kernelCols strideRows strideCols), S (D3 inputRows inputCols channels)) Source #

class UpdateLayer x where Source #

Class for updating a layer. All layers implement this, as it describes how to create and update the layer.

Minimal complete definition

runUpdate, createRandom

Associated Types

type Gradient x :: * Source #

The type for the gradient for this layer. Unit if there isn't a gradient to pass back.

Methods

runUpdate :: LearningParameters -> x -> Gradient x -> x Source #

Update a layer with its gradient and learning parameters

createRandom :: MonadRandom m => m x Source #

Create a random layer, many layers will use pure

runUpdates :: LearningParameters -> x -> [Gradient x] -> x Source #

Update a layer with many Gradients

Instances

UpdateLayer Dropout Source # 
UpdateLayer Elu Source # 
UpdateLayer Logit Source # 
UpdateLayer Relu Source # 
UpdateLayer Reshape Source # 
UpdateLayer Softmax Source # 
UpdateLayer Tanh Source # 
UpdateLayer Trivial Source # 
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 #

(KnownNat i, KnownNat o) => UpdateLayer (FullyConnected i o) Source # 
(UpdateLayer x, UpdateLayer y) => UpdateLayer (Merge x y) Source #

Run two layers in parallel, combining their outputs. This just kind of "smooshes" the weights together.

Associated Types

type Gradient (Merge x y) :: * Source #

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

Associated Types

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

(UpdateLayer x, UpdateLayer y) => UpdateLayer (Concat m x n y) Source #

Run two layers in parallel, combining their outputs.

Associated Types

type Gradient (Concat m x n y) :: * Source #

Methods

runUpdate :: LearningParameters -> Concat m x n y -> Gradient (Concat m x n y) -> Concat m x n y Source #

createRandom :: MonadRandom m => m (Concat m x n y) Source #

runUpdates :: LearningParameters -> Concat m x n y -> [Gradient (Concat m x n y)] -> Concat m x n y Source #

UpdateLayer (Crop l t r b) Source # 

Associated Types

type Gradient (Crop l t r b) :: * Source #

Methods

runUpdate :: LearningParameters -> Crop l t r b -> Gradient (Crop l t r b) -> Crop l t r b Source #

createRandom :: MonadRandom m => m (Crop l t r b) Source #

runUpdates :: LearningParameters -> Crop l t r b -> [Gradient (Crop l t r b)] -> Crop l t r b Source #

UpdateLayer (Pad l t r b) Source # 

Associated Types

type Gradient (Pad l t r b) :: * Source #

Methods

runUpdate :: LearningParameters -> Pad l t r b -> Gradient (Pad l t r b) -> Pad l t r b Source #

createRandom :: MonadRandom m => m (Pad l t r b) Source #

runUpdates :: LearningParameters -> Pad l t r b -> [Gradient (Pad l t r b)] -> Pad l t r b Source #

UpdateLayer (Pooling kernelRows kernelColumns strideRows strideColumns) Source # 

Associated Types

type Gradient (Pooling kernelRows kernelColumns strideRows strideColumns) :: * Source #

Methods

runUpdate :: LearningParameters -> Pooling kernelRows kernelColumns strideRows strideColumns -> Gradient (Pooling kernelRows kernelColumns strideRows strideColumns) -> Pooling kernelRows kernelColumns strideRows strideColumns Source #

createRandom :: MonadRandom m => m (Pooling kernelRows kernelColumns strideRows strideColumns) Source #

runUpdates :: LearningParameters -> Pooling kernelRows kernelColumns strideRows strideColumns -> [Gradient (Pooling kernelRows kernelColumns strideRows strideColumns)] -> Pooling kernelRows kernelColumns strideRows strideColumns Source #

(KnownNat channels, KnownNat filters, KnownNat kernelRows, KnownNat kernelColumns, KnownNat strideRows, KnownNat strideColumns, KnownNat (* (* kernelRows kernelColumns) channels)) => UpdateLayer (Convolution channels filters kernelRows kernelColumns strideRows strideColumns) Source # 

Associated Types

type Gradient (Convolution channels filters kernelRows kernelColumns strideRows strideColumns) :: * Source #

Methods

runUpdate :: LearningParameters -> Convolution channels filters kernelRows kernelColumns strideRows strideColumns -> Gradient (Convolution channels filters kernelRows kernelColumns strideRows strideColumns) -> Convolution channels filters kernelRows kernelColumns strideRows strideColumns Source #

createRandom :: MonadRandom m => m (Convolution channels filters kernelRows kernelColumns strideRows strideColumns) Source #

runUpdates :: LearningParameters -> Convolution channels filters kernelRows kernelColumns strideRows strideColumns -> [Gradient (Convolution channels filters kernelRows kernelColumns strideRows strideColumns)] -> Convolution channels filters kernelRows kernelColumns strideRows strideColumns Source #

(KnownNat channels, KnownNat filters, KnownNat kernelRows, KnownNat kernelColumns, KnownNat strideRows, KnownNat strideColumns, KnownNat (* (* kernelRows kernelColumns) filters)) => UpdateLayer (Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns) Source # 

Associated Types

type Gradient (Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns) :: * Source #

Methods

runUpdate :: LearningParameters -> Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns -> Gradient (Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns) -> Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns Source #

createRandom :: MonadRandom m => m (Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns) Source #

runUpdates :: LearningParameters -> Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns -> [Gradient (Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns)] -> Deconvolution channels filters kernelRows kernelColumns strideRows strideColumns Source #