grenade-0.1.0: Practical Deep Learning in Haskell

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

Grenade.Layers.Concat

Description

This module provides the concatenation layer, which runs two chilld layers in parallel and combines their outputs.

Synopsis

Documentation

data Concat :: Shape -> * -> Shape -> * -> * where Source #

A Concatentating Layer.

This layer shares it's input state between two sublayers, and concatenates their output.

With Networks able to be Layers, this allows for very expressive composition of complex Networks.

The Concat layer has a few instances, which allow one to flexibly "bash" together the outputs.

Two 1D vectors, can go to a 2D shape with 2 rows if their lengths are identical. Any 2 1D vectors can also become a longer 1D Vector.

3D images become 3D images with more channels. The sizes must be the same, one can use Pad and Crop layers to ensure this is the case.

Constructors

Concat :: x -> y -> Concat m x n y 

Instances

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

Methods

showsPrec :: Int -> Concat m x n y -> ShowS #

show :: Concat m x n y -> String #

showList :: [Concat m x n y] -> ShowS #

(Serialize a, Serialize b) => Serialize (Concat sa a sb b) Source # 

Methods

put :: Putter (Concat sa a sb b) #

get :: Get (Concat sa a sb b) #

(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 #

(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 #

type Gradient (Concat m x n y) Source # 
type Gradient (Concat m x n y) = (Gradient x, Gradient y)
type Tape (Concat (D1 m) x (D1 n) y) i (D1 o) Source # 
type Tape (Concat (D1 m) x (D1 n) y) i (D1 o) = (Tape x i (D1 m), Tape y i (D1 n))
type Tape (Concat (D1 o) x (D1 o) y) i (D2 2 o) Source # 
type Tape (Concat (D1 o) x (D1 o) y) i (D2 2 o) = (Tape x i (D1 o), Tape y i (D1 o))
type Tape (Concat (D3 rows cols m) x (D3 rows cols n) y) i (D3 rows cols o) Source # 
type Tape (Concat (D3 rows cols m) x (D3 rows cols n) y) i (D3 rows cols o) = (Tape x i (D3 rows cols m), Tape y i (D3 rows cols n))