DeepDarkFantasy-0.2017.4.9: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.DBI

Documentation

class Monoid r m where Source #

Minimal complete definition

zero, plus

Methods

zero :: r h m Source #

plus :: r h (m -> m -> m) Source #

class DBI repr where Source #

Minimal complete definition

z, s, abs, app

Methods

z :: repr (a, h) a Source #

s :: repr h b -> repr (a, h) b Source #

abs :: repr (a, h) b -> repr h (a -> b) Source #

app :: repr h (a -> b) -> repr h a -> repr h b Source #

hoas :: (repr (a, h) a -> repr (a, h) b) -> repr h (a -> b) Source #

We use a variant of HOAS so it can be compile to DBI, which is more compositional (No Negative Occurence). It require explicit lifting of variables. Use lam to do automatic lifting of variables.

com :: repr h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: repr h ((a -> b -> c) -> b -> a -> c) Source #

id :: repr h (a -> a) Source #

const :: repr h (a -> b -> a) Source #

scomb :: repr h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: repr h ((a -> a -> b) -> a -> b) Source #

let_ :: repr h (a -> (a -> b) -> b) Source #

Instances

DBI Eval Source # 

Methods

z :: Eval (a, h) a Source #

s :: Eval h b -> Eval (a, h) b Source #

abs :: Eval (a, h) b -> Eval h (a -> b) Source #

app :: Eval h (a -> b) -> Eval h a -> Eval h b Source #

hoas :: (Eval (a, h) a -> Eval (a, h) b) -> Eval h (a -> b) Source #

com :: Eval h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: Eval h ((a -> b -> c) -> b -> a -> c) Source #

id :: Eval h (a -> a) Source #

const :: Eval h (a -> b -> a) Source #

scomb :: Eval h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: Eval h ((a -> a -> b) -> a -> b) Source #

let_ :: Eval h (a -> (a -> b) -> b) Source #

DBI Show Source # 

Methods

z :: Show (a, h) a Source #

s :: Show h b -> Show (a, h) b Source #

abs :: Show (a, h) b -> Show h (a -> b) Source #

app :: Show h (a -> b) -> Show h a -> Show h b Source #

hoas :: (Show (a, h) a -> Show (a, h) b) -> Show h (a -> b) Source #

com :: Show h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: Show h ((a -> b -> c) -> b -> a -> c) Source #

id :: Show h (a -> a) Source #

const :: Show h (a -> b -> a) Source #

scomb :: Show h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: Show h ((a -> a -> b) -> a -> b) Source #

let_ :: Show h (a -> (a -> b) -> b) Source #

DBI Size Source # 

Methods

z :: Size (a, h) a Source #

s :: Size h b -> Size (a, h) b Source #

abs :: Size (a, h) b -> Size h (a -> b) Source #

app :: Size h (a -> b) -> Size h a -> Size h b Source #

hoas :: (Size (a, h) a -> Size (a, h) b) -> Size h (a -> b) Source #

com :: Size h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: Size h ((a -> b -> c) -> b -> a -> c) Source #

id :: Size h (a -> a) Source #

const :: Size h (a -> b -> a) Source #

scomb :: Size h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: Size h ((a -> a -> b) -> a -> b) Source #

let_ :: Size h (a -> (a -> b) -> b) Source #

DBI r => DBI (GWDiff r) Source # 

Methods

z :: GWDiff r (a, h) a Source #

s :: GWDiff r h b -> GWDiff r (a, h) b Source #

abs :: GWDiff r (a, h) b -> GWDiff r h (a -> b) Source #

app :: GWDiff r h (a -> b) -> GWDiff r h a -> GWDiff r h b Source #

hoas :: (GWDiff r (a, h) a -> GWDiff r (a, h) b) -> GWDiff r h (a -> b) Source #

com :: GWDiff r h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: GWDiff r h ((a -> b -> c) -> b -> a -> c) Source #

id :: GWDiff r h (a -> a) Source #

const :: GWDiff r h (a -> b -> a) Source #

scomb :: GWDiff r h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: GWDiff r h ((a -> a -> b) -> a -> b) Source #

let_ :: GWDiff r h (a -> (a -> b) -> b) Source #

Prod r => DBI (ImpW r) Source # 

Methods

z :: ImpW r (a, h) a Source #

s :: ImpW r h b -> ImpW r (a, h) b Source #

abs :: ImpW r (a, h) b -> ImpW r h (a -> b) Source #

app :: ImpW r h (a -> b) -> ImpW r h a -> ImpW r h b Source #

hoas :: (ImpW r (a, h) a -> ImpW r (a, h) b) -> ImpW r h (a -> b) Source #

com :: ImpW r h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: ImpW r h ((a -> b -> c) -> b -> a -> c) Source #

id :: ImpW r h (a -> a) Source #

const :: ImpW r h (a -> b -> a) Source #

scomb :: ImpW r h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: ImpW r h ((a -> a -> b) -> a -> b) Source #

let_ :: ImpW r h (a -> (a -> b) -> b) Source #

DBI repr => DBI (UnHOAS repr) Source # 

Methods

z :: UnHOAS repr (a, h) a Source #

s :: UnHOAS repr h b -> UnHOAS repr (a, h) b Source #

abs :: UnHOAS repr (a, h) b -> UnHOAS repr h (a -> b) Source #

app :: UnHOAS repr h (a -> b) -> UnHOAS repr h a -> UnHOAS repr h b Source #

hoas :: (UnHOAS repr (a, h) a -> UnHOAS repr (a, h) b) -> UnHOAS repr h (a -> b) Source #

com :: UnHOAS repr h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: UnHOAS repr h ((a -> b -> c) -> b -> a -> c) Source #

id :: UnHOAS repr h (a -> a) Source #

const :: UnHOAS repr h (a -> b -> a) Source #

scomb :: UnHOAS repr h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: UnHOAS repr h ((a -> a -> b) -> a -> b) Source #

let_ :: UnHOAS repr h (a -> (a -> b) -> b) Source #

(DBI l, DBI r) => DBI (Combine l r) Source # 

Methods

z :: Combine l r (a, h) a Source #

s :: Combine l r h b -> Combine l r (a, h) b Source #

abs :: Combine l r (a, h) b -> Combine l r h (a -> b) Source #

app :: Combine l r h (a -> b) -> Combine l r h a -> Combine l r h b Source #

hoas :: (Combine l r (a, h) a -> Combine l r (a, h) b) -> Combine l r h (a -> b) Source #

com :: Combine l r h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: Combine l r h ((a -> b -> c) -> b -> a -> c) Source #

id :: Combine l r h (a -> a) Source #

const :: Combine l r h (a -> b -> a) Source #

scomb :: Combine l r h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: Combine l r h ((a -> a -> b) -> a -> b) Source #

let_ :: Combine l r h (a -> (a -> b) -> b) Source #

DBI r => DBI (WDiff r v) Source # 

Methods

z :: WDiff r v (a, h) a Source #

s :: WDiff r v h b -> WDiff r v (a, h) b Source #

abs :: WDiff r v (a, h) b -> WDiff r v h (a -> b) Source #

app :: WDiff r v h (a -> b) -> WDiff r v h a -> WDiff r v h b Source #

hoas :: (WDiff r v (a, h) a -> WDiff r v (a, h) b) -> WDiff r v h (a -> b) Source #

com :: WDiff r v h ((b -> c) -> (a -> b) -> a -> c) Source #

flip :: WDiff r v h ((a -> b -> c) -> b -> a -> c) Source #

id :: WDiff r v h (a -> a) Source #

const :: WDiff r v h (a -> b -> a) Source #

scomb :: WDiff r v h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

dup :: WDiff r v h ((a -> a -> b) -> a -> b) Source #

let_ :: WDiff r v h (a -> (a -> b) -> b) Source #

const1 :: DBI repr => repr h a -> repr h (b -> a) Source #

map2 :: (Functor * repr f, DBI repr) => repr h (a -> b) -> repr h (f a) -> repr h (f b) Source #

return :: Applicative k r a => r h (x -> a x) Source #

bind2 :: Monad repr m => repr h (m a) -> repr h (a -> m b) -> repr h (m b) Source #

map1 :: (Functor * repr f, DBI repr) => repr h (a -> b) -> repr h (f a -> f b) Source #

join1 :: Monad repr m => repr h (m (m a)) -> repr h (m a) Source #

bimap2 :: (BiFunctor * repr p, DBI repr) => repr h (a -> b) -> repr h (c -> d) -> repr h (p a c -> p b d) Source #

bimap3 :: (BiFunctor * repr p, DBI repr) => repr h (a -> b) -> repr h (c -> d) -> repr h (p a c) -> repr h (p b d) Source #

flip1 :: DBI repr => repr h (a -> b -> c) -> repr h (b -> a -> c) Source #

flip2 :: DBI repr => repr h (a1 -> a -> c) -> repr h a -> repr h (a1 -> c) Source #

let_2 :: DBI repr => repr h a -> repr h (a -> b) -> repr h b Source #

class Functor r f where Source #

Minimal complete definition

map

Methods

map :: r h ((a -> b) -> f a -> f b) Source #

class Functor r a => Applicative r a where Source #

Minimal complete definition

pure, ap

Methods

pure :: r h (x -> a x) Source #

ap :: r h (a (x -> y) -> a x -> a y) Source #

class (DBI r, Applicative r m) => Monad r m where Source #

Minimal complete definition

join | bind

Methods

bind :: r h (m a -> (a -> m b) -> m b) Source #

join :: r h (m (m a) -> m a) Source #

class BiFunctor r p where Source #

Minimal complete definition

bimap

Methods

bimap :: r h ((a -> b) -> (c -> d) -> p a c -> p b d) Source #

app3 :: DBI repr => repr h (a2 -> a1 -> a -> b) -> repr h a2 -> repr h a1 -> repr h a -> repr h b Source #

com2 :: DBI repr => repr h (b -> c) -> repr h (a -> b) -> repr h (a -> c) Source #

class NT repr l r where Source #

Minimal complete definition

conv

Methods

conv :: repr l t -> repr r t Source #

Instances

NT k k1 repr x x Source # 

Methods

conv :: x l t -> x r t Source #

NTS k k1 repr l r => NT k k1 repr l r Source # 

Methods

conv :: r l t -> r r t Source #

class NTS repr l r where Source #

Minimal complete definition

convS

Methods

convS :: repr l t -> repr r t Source #

Instances

(DBI repr, NT * * repr l r) => NTS * * repr l (a, r) Source # 

Methods

convS :: (a, r) l t -> (a, r) r t Source #

lam :: forall repr a b h. DBI repr => ((forall k. NT repr (a, h) k => repr k a) -> repr (a, h) b) -> repr h (a -> b) Source #

lam2 :: forall repr a b c h. DBI repr => ((forall k. NT repr (a, h) k => repr k a) -> (forall k. NT repr (b, (a, h)) k => repr k b) -> repr (b, (a, h)) c) -> repr h (a -> b -> c) Source #

lam3 :: (NT * * repr (a, (b1, (a1, h))) k, NT * * repr (b1, (a1, h)) k1, NT * * repr (a1, h) k2, DBI repr) => (repr k2 a1 -> repr k1 b1 -> repr k a -> repr (a, (b1, (a1, h))) b) -> repr h (a1 -> b1 -> a -> b) Source #

app2 :: DBI repr => repr h (a1 -> a -> b) -> repr h a1 -> repr h a -> repr h b Source #

plus2 :: (Monoid * repr b, DBI repr) => repr h b -> repr h b -> repr h b Source #

noEnv :: repr () x -> repr () x Source #

class ProdCon con l r where Source #

Minimal complete definition

prodCon

Methods

prodCon :: (con l, con r) :- con (l, r) Source #

Instances

ProdCon Show l r Source # 

Methods

prodCon :: (Show l, Show r) :- Show (l, r) Source #

ProdCon Random l r Source # 

Methods

prodCon :: (Random l, Random r) :- Random (l, r) Source #

ProdCon RandRange l r Source # 

Methods

prodCon :: (RandRange l, RandRange r) :- RandRange (l, r) Source #

Lang repr => ProdCon (Vector repr) l r Source # 

Methods

prodCon :: (Vector repr l, Vector repr r) :- Vector repr (l, r) Source #

Lang repr => ProdCon (WithDiff repr) l r Source # 

Methods

prodCon :: (WithDiff repr l, WithDiff repr r) :- WithDiff repr (l, r) Source #

Lang repr => ProdCon (Reify * repr) l r Source # 

Methods

prodCon :: (Reify * repr l, Reify * repr r) :- Reify * repr (l, r) Source #

class Weight w where Source #

Minimal complete definition

weightCon

Methods

weightCon :: (con (), con Float, con Double, ForallV (ProdCon con)) :- con w Source #

Instances

Weight Double Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con Double Source #

Weight () Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con () Source #

(Weight l, Weight r) => Weight (l, r) Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con (l, r) Source #