grenade-0.1.0: Practical Deep Learning in Haskell

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

Grenade.Core.Shape

Description

 

Synopsis

Documentation

data Shape Source #

The current shapes we accept. at the moment this is just one, two, and three dimensional Vectors/Matricies.

These are only used with DataKinds, as Kind Shape, with Types 'D1, 'D2, 'D3.

Constructors

D1 Nat

One dimensional vector

D2 Nat Nat

Two dimensional matrix. Row, Column.

D3 Nat Nat Nat

Three dimensional matrix. Row, Column, Channels.

Instances

KnownNat a => SingI Shape (D1 a) Source # 

Methods

sing :: Sing (D1 a) a #

(KnownNat a, KnownNat b) => SingI Shape (D2 a b) Source # 

Methods

sing :: Sing (D2 a b) a #

(KnownNat a, KnownNat b, KnownNat c, KnownNat (* a c)) => SingI Shape (D3 a b c) Source # 

Methods

sing :: Sing (D3 a b c) a #

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

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

Methods

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

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

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

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

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

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

Methods

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

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

showList :: [RecurrentNetwork [*] ((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))) # 

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

Add very simple serialisation to the network

Methods

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

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

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

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

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

Add very simple serialisation to the recurrent network

Methods

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

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

data Sing Shape Source # 
data Sing Shape where

data S n where Source #

Concrete data structures for a Shape.

All shapes are held in contiguous memory. 3D is held in a matrix (usually row oriented) which has height depth * rows.

Constructors

S1D :: KnownNat len => R len -> S (D1 len) 
S2D :: (KnownNat rows, KnownNat columns) => L rows columns -> S (D2 rows columns) 
S3D :: (KnownNat rows, KnownNat columns, KnownNat depth, KnownNat (rows * depth)) => L (rows * depth) columns -> S (D3 rows columns depth) 

Instances

SingI Shape x => Floating (S x) Source # 

Methods

pi :: S x #

exp :: S x -> S x #

log :: S x -> S x #

sqrt :: S x -> S x #

(**) :: S x -> S x -> S x #

logBase :: S x -> S x -> S x #

sin :: S x -> S x #

cos :: S x -> S x #

tan :: S x -> S x #

asin :: S x -> S x #

acos :: S x -> S x #

atan :: S x -> S x #

sinh :: S x -> S x #

cosh :: S x -> S x #

tanh :: S x -> S x #

asinh :: S x -> S x #

acosh :: S x -> S x #

atanh :: S x -> S x #

log1p :: S x -> S x #

expm1 :: S x -> S x #

log1pexp :: S x -> S x #

log1mexp :: S x -> S x #

SingI Shape x => Fractional (S x) Source # 

Methods

(/) :: S x -> S x -> S x #

recip :: S x -> S x #

fromRational :: Rational -> S x #

SingI Shape x => Num (S x) Source # 

Methods

(+) :: S x -> S x -> S x #

(-) :: S x -> S x -> S x #

(*) :: S x -> S x -> S x #

negate :: S x -> S x #

abs :: S x -> S x #

signum :: S x -> S x #

fromInteger :: Integer -> S x #

Show (S n) Source # 

Methods

showsPrec :: Int -> S n -> ShowS #

show :: S n -> String #

showList :: [S n] -> ShowS #

NFData (S x) Source # 

Methods

rnf :: S x -> () #

data family Sing k (a :: k) :: * #

The singleton kind-indexed data family.

Instances

data Sing Bool 
data Sing Bool where
data Sing Ordering 
data Sing Nat 
data Sing Nat where
data Sing Symbol 
data Sing Symbol where
data Sing () 
data Sing () where
data Sing Shape # 
data Sing Shape where
data Sing [a0] 
data Sing [a0] where
data Sing (Maybe a0) 
data Sing (Maybe a0) where
data Sing (NonEmpty a0) 
data Sing (NonEmpty a0) where
data Sing (Either a0 b0) 
data Sing (Either a0 b0) where
data Sing (a0, b0) 
data Sing (a0, b0) where
data Sing ((~>) k1 k2) 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a0, b0, c0) 
data Sing (a0, b0, c0) where
data Sing (a0, b0, c0, d0) 
data Sing (a0, b0, c0, d0) where
data Sing (a0, b0, c0, d0, e0) 
data Sing (a0, b0, c0, d0, e0) where
data Sing (a0, b0, c0, d0, e0, f0) 
data Sing (a0, b0, c0, d0, e0, f0) where
data Sing (a0, b0, c0, d0, e0, f0, g0) 
data Sing (a0, b0, c0, d0, e0, f0, g0) where

randomOfShape :: forall x m. (MonadRandom m, SingI x) => m (S x) Source #

Generate random data of the desired shape

fromStorable :: forall x. SingI x => Vector Double -> Maybe (S x) Source #

Generate a shape from a Storable Vector.

Returns Nothing if the vector is of the wrong size.