DeepDarkFantasy-0.2017.4.1: 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 Monoid repr w => WithDiff repr w where Source #

Minimal complete definition

withDiff

Methods

withDiff :: repr h ((w -> x) -> w -> Diff x w) Source #

class DBI repr => ConvDiff repr w where Source #

Minimal complete definition

toDiffBy, fromDiffBy

Methods

toDiff :: forall h x. Monoid repr x => Proxy x -> repr h (w -> Diff x w) Source #

toDiffBy :: forall h x. repr h (x -> w -> Diff x w) Source #

fromDiff :: forall h x. Monoid repr x => Proxy x -> repr h (Diff x w -> w) Source #

fromDiffBy :: repr h (x -> Diff x w -> w) Source #

withDiff1 :: (WithDiff * repr w, DBI repr) => repr h (w -> x) -> repr h (w -> Diff x w) Source #

toDiffBy1 :: forall repr w x h. ConvDiff repr w => repr h x -> repr h (w -> Diff x w) Source #

fromDiffBy1 :: forall repr w x h. ConvDiff repr w => repr h x -> repr h (Diff x w -> w) Source #

selfWithDiff :: (DBI repr, WithDiff repr w) => repr h (w -> Diff w w) 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 #

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 repr => DBI (GWDiff repr) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

let_ :: GWDiff repr 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 repr => DBI (WDiff repr v) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

let_ :: WDiff repr v 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 #

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 #

type family Diff (v :: *) (x :: *) Source #

Instances

type Diff v () Source # 
type Diff v () = ()
type Diff v Bool Source # 
type Diff v Bool = Bool
type Diff v Float Source # 
type Diff v Float = (Float, v)
type Diff v Double Source # 
type Diff v Double = (Double, v)
type Diff v Void Source # 
type Diff v Void = Void
type Diff v [l] Source # 
type Diff v [l] = [Diff v l]
type Diff v (Maybe l) Source # 
type Diff v (Maybe l) = Maybe (Diff v l)
type Diff v (IO l) Source # 
type Diff v (IO l) = IO (Diff v l)
type Diff v (l -> r) Source # 
type Diff v (l -> r) = Diff v l -> Diff v r
type Diff v (l, r) Source # 
type Diff v (l, r) = (Diff v l, Diff v r)
type Diff v (State l r) Source # 
type Diff v (State l r) = State (Diff v l) (Diff v r)
type Diff v (Either l r) Source # 
type Diff v (Either l r) = Either (Diff v l) (Diff v r)
type Diff v (Writer l r) Source # 
type Diff v (Writer l r) = Writer (Diff v l) (Diff v r)

newtype WDiff repr v h x Source #

Constructors

WDiff 

Fields

Instances

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

(Vector repr v, Lang repr) => Lang (WDiff repr v) Source # 

Methods

mkProd :: WDiff repr v h (a -> b -> (a, b)) Source #

zro :: WDiff repr v h ((a, b) -> a) Source #

fst :: WDiff repr v h ((a, b) -> b) Source #

double :: Double -> WDiff repr v h Double Source #

doubleZero :: WDiff repr v h Double Source #

doubleOne :: WDiff repr v h Double Source #

doublePlus :: WDiff repr v h (Double -> Double -> Double) Source #

doubleMinus :: WDiff repr v h (Double -> Double -> Double) Source #

doubleMult :: WDiff repr v h (Double -> Double -> Double) Source #

doubleDivide :: WDiff repr v h (Double -> Double -> Double) Source #

doubleExp :: WDiff repr v h (Double -> Double) Source #

float :: Float -> WDiff repr v h Float Source #

floatZero :: WDiff repr v h Float Source #

floatOne :: WDiff repr v h Float Source #

floatPlus :: WDiff repr v h (Float -> Float -> Float) Source #

floatMinus :: WDiff repr v h (Float -> Float -> Float) Source #

floatMult :: WDiff repr v h (Float -> Float -> Float) Source #

floatDivide :: WDiff repr v h (Float -> Float -> Float) Source #

floatExp :: WDiff repr v h (Float -> Float) Source #

fix :: WDiff repr v h ((a -> a) -> a) Source #

left :: WDiff repr v h (a -> Either a b) Source #

right :: WDiff repr v h (b -> Either a b) Source #

sumMatch :: WDiff repr v h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: WDiff repr v h () Source #

exfalso :: WDiff repr v h (Void -> a) Source #

nothing :: WDiff repr v h (Maybe a) Source #

just :: WDiff repr v h (a -> Maybe a) Source #

optionMatch :: WDiff repr v h (b -> (a -> b) -> Maybe a -> b) Source #

ioRet :: WDiff repr v h (a -> IO a) Source #

ioBind :: WDiff repr v h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: WDiff repr v h ((a -> b) -> IO a -> IO b) Source #

nil :: WDiff repr v h [a] Source #

cons :: WDiff repr v h (a -> [a] -> [a]) Source #

listMatch :: WDiff repr v h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: WDiff repr v h ([a] -> [a] -> [a]) Source #

writer :: WDiff repr v h ((a, w) -> Writer w a) Source #

runWriter :: WDiff repr v h (Writer w a -> (a, w)) Source #

swap :: WDiff repr v h ((l, r) -> (r, l)) Source #

curry :: WDiff repr v h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: WDiff repr v h ((a -> b -> c) -> (a, b) -> c) Source #

float2Double :: WDiff repr v h (Float -> Double) Source #

double2Float :: WDiff repr v h (Double -> Float) Source #

undefined :: WDiff repr v h a Source #

state :: WDiff repr v h ((l -> (r, l)) -> State l r) Source #

runState :: WDiff repr v h (State l r -> l -> (r, l)) 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 (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 #

data RunImpW repr h x Source #

Constructors

Weight w => RunImpW (repr h (w -> x)) 

data ImpW repr h x Source #

Constructors

NoImpW (repr h x) 
Weight w => ImpW (repr h (w -> x)) 

Instances

Lang repr => Lang (ImpW * repr) Source # 

Methods

mkProd :: ImpW * repr h (a -> b -> (a, b)) Source #

zro :: ImpW * repr h ((a, b) -> a) Source #

fst :: ImpW * repr h ((a, b) -> b) Source #

double :: Double -> ImpW * repr h Double Source #

doubleZero :: ImpW * repr h Double Source #

doubleOne :: ImpW * repr h Double Source #

doublePlus :: ImpW * repr h (Double -> Double -> Double) Source #

doubleMinus :: ImpW * repr h (Double -> Double -> Double) Source #

doubleMult :: ImpW * repr h (Double -> Double -> Double) Source #

doubleDivide :: ImpW * repr h (Double -> Double -> Double) Source #

doubleExp :: ImpW * repr h (Double -> Double) Source #

float :: Float -> ImpW * repr h Float Source #

floatZero :: ImpW * repr h Float Source #

floatOne :: ImpW * repr h Float Source #

floatPlus :: ImpW * repr h (Float -> Float -> Float) Source #

floatMinus :: ImpW * repr h (Float -> Float -> Float) Source #

floatMult :: ImpW * repr h (Float -> Float -> Float) Source #

floatDivide :: ImpW * repr h (Float -> Float -> Float) Source #

floatExp :: ImpW * repr h (Float -> Float) Source #

fix :: ImpW * repr h ((a -> a) -> a) Source #

left :: ImpW * repr h (a -> Either a b) Source #

right :: ImpW * repr h (b -> Either a b) Source #

sumMatch :: ImpW * repr h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: ImpW * repr h () Source #

exfalso :: ImpW * repr h (Void -> a) Source #

nothing :: ImpW * repr h (Maybe a) Source #

just :: ImpW * repr h (a -> Maybe a) Source #

optionMatch :: ImpW * repr h (b -> (a -> b) -> Maybe a -> b) Source #

ioRet :: ImpW * repr h (a -> IO a) Source #

ioBind :: ImpW * repr h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: ImpW * repr h ((a -> b) -> IO a -> IO b) Source #

nil :: ImpW * repr h [a] Source #

cons :: ImpW * repr h (a -> [a] -> [a]) Source #

listMatch :: ImpW * repr h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: ImpW * repr h ([a] -> [a] -> [a]) Source #

writer :: ImpW * repr h ((a, w) -> Writer w a) Source #

runWriter :: ImpW * repr h (Writer w a -> (a, w)) Source #

swap :: ImpW * repr h ((l, r) -> (r, l)) Source #

curry :: ImpW * repr h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: ImpW * repr h ((a -> b -> c) -> (a, b) -> c) Source #

float2Double :: ImpW * repr h (Float -> Double) Source #

double2Float :: ImpW * repr h (Double -> Float) Source #

undefined :: ImpW * repr h a Source #

state :: ImpW * repr h ((l -> (r, l)) -> State l r) Source #

runState :: ImpW * repr h (State l r -> l -> (r, l)) Source #

type RunImpWR repr h x = forall r. (forall w. Weight w => repr h (w -> x) -> r) -> r Source #

runImpW2RunImpWR :: RunImpW repr h x -> RunImpWR repr h x Source #

runImpWR2RunImpW :: RunImpWR repr h x -> RunImpW repr h x Source #