goal-geometry-0.20: The basic geometric type system of Goal
Safe HaskellNone
LanguageHaskell2010

Goal.Geometry.Map.NeuralNetwork

Description

Multilayer perceptrons which instantiate backpropagation through laziness. Right now the structure is simplier than it could be, but it leads to nice types. If anyone ever wants to use a DNN with super-Affine biases, the code is willing.

Synopsis

Neural Networks

data NeuralNetwork (gys :: [(Type -> Type -> Type, Type)]) (f :: Type -> Type -> Type) z x Source #

A multilayer, artificial neural network.

Instances

Instances details
Map c f z x => Map c (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f) z x Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Methods

(>.>) :: (c # NeuralNetwork '[] f z x) -> (c #* x) -> c # z Source #

(>$>) :: (c # NeuralNetwork '[] f z x) -> [c #* x] -> [c # z] Source #

(Map c f z y, Map c (NeuralNetwork gys g) y x, Transition c (Dual c) y) => Map c (NeuralNetwork ('(g, y) ': gys) f) z x Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Methods

(>.>) :: (c # NeuralNetwork ('(g, y) ': gys) f z x) -> (c #* x) -> c # z Source #

(>$>) :: (c # NeuralNetwork ('(g, y) ': gys) f z x) -> [c #* x] -> [c # z] Source #

(Propagate c f z y, Propagate c (NeuralNetwork gys g) y x, Map c f y z, Transition c (Dual c) y, Legendre y, Riemannian c y, Bilinear f z y) => Propagate c (NeuralNetwork ('(g, y) ': gys) f) z x Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Methods

propagate :: [c #* z] -> [c #* x] -> (c # NeuralNetwork ('(g, y) ': gys) f z x) -> (c #* NeuralNetwork ('(g, y) ': gys) f z x, [c # z]) Source #

Propagate c f z x => Propagate c (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f) z x Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Methods

propagate :: [c #* z] -> [c #* x] -> (c # NeuralNetwork '[] f z x) -> (c #* NeuralNetwork '[] f z x, [c # z]) Source #

(Manifold (Affine f z z y), Manifold (NeuralNetwork gys g y x)) => Product (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Associated Types

type First (NeuralNetwork ('(g, y) ': gys) f z x) Source #

type Second (NeuralNetwork ('(g, y) ': gys) f z x) Source #

Methods

join :: (c # First (NeuralNetwork ('(g, y) ': gys) f z x)) -> (c # Second (NeuralNetwork ('(g, y) ': gys) f z x)) -> c # NeuralNetwork ('(g, y) ': gys) f z x Source #

split :: (c # NeuralNetwork ('(g, y) ': gys) f z x) -> (c # First (NeuralNetwork ('(g, y) ': gys) f z x), c # Second (NeuralNetwork ('(g, y) ': gys) f z x)) Source #

(Manifold (Affine f z z y), Manifold (NeuralNetwork gys g y x)) => Manifold (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Associated Types

type Dimension (NeuralNetwork ('(g, y) ': gys) f z x) :: Nat Source #

Manifold (Affine f z z x) => Manifold (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

Associated Types

type Dimension (NeuralNetwork '[] f z x) :: Nat Source #

type First (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

type First (NeuralNetwork ('(g, y) ': gys) f z x) = Affine f z z y
type Second (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

type Second (NeuralNetwork ('(g, y) ': gys) f z x) = NeuralNetwork gys g y x
type Dimension (NeuralNetwork ('(g, y) ': gys) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

type Dimension (NeuralNetwork ('(g, y) ': gys) f z x) = Dimension (Affine f z z y) + Dimension (NeuralNetwork gys g y x)
type Dimension (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f z x) Source # 
Instance details

Defined in Goal.Geometry.Map.NeuralNetwork

type Dimension (NeuralNetwork ('[] :: [(Type -> Type -> Type, Type)]) f z x) = Dimension (Affine f z z x)