DeepDarkFantasy-0.2017.8.8: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.Lang

Contents

Documentation

class (Bool r, Char r, Double r, Float r, Bimap r, Dual r, Unit r, Sum r, Int r, IO r, VectorTF r, DiffWrapper r, Fix r, FreeVector r) => Lang r where Source #

Methods

exfalso :: r h (Void -> a) Source #

writer :: r h ((a, w) -> Writer w a) Source #

runWriter :: r h (Writer w a -> (a, w)) Source #

float2Double :: r h (Float -> Double) Source #

double2Float :: r h (Double -> Float) Source #

state :: r h ((x -> (y, x)) -> State x y) Source #

runState :: r h (State x y -> x -> (y, x)) Source #

iterate :: r h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => r h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => r h (VectorTF b Int -> SVTFBuilder b) Source #

get :: r h (Maybe a -> a) Source #

getVar :: r h (State x x) Source #

update :: r h ((x -> x) -> State x ()) Source #

updateWengert :: r h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: r h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Instances

Lang Eval Source # 

Methods

exfalso :: Eval h (Void -> a) Source #

writer :: Eval h ((a, w) -> Writer w a) Source #

runWriter :: Eval h (Writer w a -> (a, w)) Source #

float2Double :: Eval h (Float -> Double) Source #

double2Float :: Eval h (Double -> Float) Source #

state :: Eval h ((x -> (y, x)) -> State x y) Source #

runState :: Eval h (State x y -> x -> (y, x)) Source #

iterate :: Eval h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => Eval h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => Eval h (VectorTF b Int -> SVTFBuilder b) Source #

get :: Eval h (Maybe a -> a) Source #

getVar :: Eval h (State x x) Source #

update :: Eval h ((x -> x) -> State x ()) Source #

updateWengert :: Eval h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: Eval h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Lang Show Source # 

Methods

exfalso :: Show h (Void -> a) Source #

writer :: Show h ((a, w) -> Writer w a) Source #

runWriter :: Show h (Writer w a -> (a, w)) Source #

float2Double :: Show h (Float -> Double) Source #

double2Float :: Show h (Double -> Float) Source #

state :: Show h ((x -> (y, x)) -> State x y) Source #

runState :: Show h (State x y -> x -> (y, x)) Source #

iterate :: Show h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => Show h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => Show h (VectorTF b Int -> SVTFBuilder b) Source #

get :: Show h (Maybe a -> a) Source #

getVar :: Show h (State x x) Source #

update :: Show h ((x -> x) -> State x ()) Source #

updateWengert :: Show h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: Show h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Lang Size Source # 

Methods

exfalso :: Size h (Void -> a) Source #

writer :: Size h ((a, w) -> Writer w a) Source #

runWriter :: Size h (Writer w a -> (a, w)) Source #

float2Double :: Size h (Float -> Double) Source #

double2Float :: Size h (Double -> Float) Source #

state :: Size h ((x -> (y, x)) -> State x y) Source #

runState :: Size h (State x y -> x -> (y, x)) Source #

iterate :: Size h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => Size h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => Size h (VectorTF b Int -> SVTFBuilder b) Source #

get :: Size h (Maybe a -> a) Source #

getVar :: Size h (State x x) Source #

update :: Size h ((x -> x) -> State x ()) Source #

updateWengert :: Size h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: Size h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Lang UInt Source # 

Methods

exfalso :: UInt h (Void -> a) Source #

writer :: UInt h ((a, w) -> Writer w a) Source #

runWriter :: UInt h (Writer w a -> (a, w)) Source #

float2Double :: UInt h (Float -> Double) Source #

double2Float :: UInt h (Double -> Float) Source #

state :: UInt h ((x -> (y, x)) -> State x y) Source #

runState :: UInt h (State x y -> x -> (y, x)) Source #

iterate :: UInt h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => UInt h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => UInt h (VectorTF b Int -> SVTFBuilder b) Source #

get :: UInt h (Maybe a -> a) Source #

getVar :: UInt h (State x x) Source #

update :: UInt h ((x -> x) -> State x ()) Source #

updateWengert :: UInt h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: UInt h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

SubL c Lang => Lang (Term c) Source # 

Methods

exfalso :: Term c h (Void -> a) Source #

writer :: Term c h ((a, w) -> Writer w a) Source #

runWriter :: Term c h (Writer w a -> (a, w)) Source #

float2Double :: Term c h (Float -> Double) Source #

double2Float :: Term c h (Double -> Float) Source #

state :: Term c h ((x -> (y, x)) -> State x y) Source #

runState :: Term c h (State x y -> x -> (y, x)) Source #

iterate :: Term c h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => Term c h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => Term c h (VectorTF b Int -> SVTFBuilder b) Source #

get :: Term c h (Maybe a -> a) Source #

getVar :: Term c h (State x x) Source #

update :: Term c h ((x -> x) -> State x ()) Source #

updateWengert :: Term c h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: Term c h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Lang r => Lang (UnHOAS r) Source # 

Methods

exfalso :: UnHOAS r h (Void -> a) Source #

writer :: UnHOAS r h ((a, w) -> Writer w a) Source #

runWriter :: UnHOAS r h (Writer w a -> (a, w)) Source #

float2Double :: UnHOAS r h (Float -> Double) Source #

double2Float :: UnHOAS r h (Double -> Float) Source #

state :: UnHOAS r h ((x -> (y, x)) -> State x y) Source #

runState :: UnHOAS r h (State x y -> x -> (y, x)) Source #

iterate :: UnHOAS r h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => UnHOAS r h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => UnHOAS r h (VectorTF b Int -> SVTFBuilder b) Source #

get :: UnHOAS r h (Maybe a -> a) Source #

getVar :: UnHOAS r h (State x x) Source #

update :: UnHOAS r h ((x -> x) -> State x ()) Source #

updateWengert :: UnHOAS r h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: UnHOAS r h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Lang r => Lang (UnLiftEnv r) Source # 

Methods

exfalso :: UnLiftEnv r h (Void -> a) Source #

writer :: UnLiftEnv r h ((a, w) -> Writer w a) Source #

runWriter :: UnLiftEnv r h (Writer w a -> (a, w)) Source #

float2Double :: UnLiftEnv r h (Float -> Double) Source #

double2Float :: UnLiftEnv r h (Double -> Float) Source #

state :: UnLiftEnv r h ((x -> (y, x)) -> State x y) Source #

runState :: UnLiftEnv r h (State x y -> x -> (y, x)) Source #

iterate :: UnLiftEnv r h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => UnLiftEnv r h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => UnLiftEnv r h (VectorTF b Int -> SVTFBuilder b) Source #

get :: UnLiftEnv r h (Maybe a -> a) Source #

getVar :: UnLiftEnv r h (State x x) Source #

update :: UnLiftEnv r h ((x -> x) -> State x ()) Source #

updateWengert :: UnLiftEnv r h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: UnLiftEnv r h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Lang r => Lang (ImpW r) Source # 

Methods

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

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

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

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

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

state :: ImpW r h ((x -> (y, x)) -> State x y) Source #

runState :: ImpW r h (State x y -> x -> (y, x)) Source #

iterate :: ImpW r h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => ImpW r h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => ImpW r h (VectorTF b Int -> SVTFBuilder b) Source #

get :: ImpW r h (Maybe a -> a) Source #

getVar :: ImpW r h (State x x) Source #

update :: ImpW r h ((x -> x) -> State x ()) Source #

updateWengert :: ImpW r h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: ImpW r h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

type SubLC c Lang Source # 

class Reify r x where Source #

Minimal complete definition

reify

Methods

reify :: x -> r h x Source #

Instances

Lang r => Reify r Double Source # 

Methods

reify :: Double -> r h Double Source #

Lang r => Reify r () Source # 

Methods

reify :: () -> r h () Source #

(Lang repr, Reify repr l, Reify repr r) => Reify repr (l, r) Source # 

Methods

reify :: (l, r) -> repr h (l, r) Source #

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

Methods

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

uncurry1 :: Prod r => r h (a -> b -> c) -> r h ((a, b) -> c) Source #

optionMatch2 :: Option r => r h a1 -> r h (a -> a1) -> r h (Maybe a -> a1) Source #

optionMatch3 :: Option r => r h b -> r h (a -> b) -> r h (Maybe a) -> r h b Source #

writer1 :: Lang r => r h (a, w) -> r h (Writer w a) Source #

runWriter1 :: Lang r => r h (Writer w a) -> r h (a, w) Source #

float2Double1 :: Lang r => r h Float -> r h Double Source #

floatExp1 :: Float r => r h Float -> r h Float Source #

state1 :: Lang r => r h (x -> (y, x)) -> r h (State x y) Source #

runState1 :: Lang r => r h (State x y) -> r h (x -> (y, x)) Source #

runState2 :: Lang r => r h (State a y) -> r h a -> r h (y, a) Source #

toSVTFBuilder1 :: (Ord b, Lang r) => r h (VectorTF b Int) -> r h (SVTFBuilder b) Source #

double2Float1 :: Lang r => r h Double -> r h Float Source #

get1 :: Lang r => r h (Maybe b) -> r h b Source #

return1 :: Applicative r a => r h a1 -> r h (a a1) Source #

update1 :: Lang r => r h (x -> x) -> r h (State x ()) Source #

updateWengert2 :: Lang r => r h Int -> r h Double -> r h (Map Int Double -> Map Int Double) Source #

vtfCata1 :: Lang r => r h (VectorTF a b -> b) -> r h (Fix (VectorTF a) -> b) Source #

module DDF.Bool

module DDF.Char

module DDF.Double

module DDF.Float

module DDF.Bimap

module DDF.Dual

module DDF.Unit

module DDF.Sum

module DDF.Int

module DDF.IO

module DDF.Fix

Orphan instances

Ord Int Source # 

Methods

diffOrd :: Proxy * (v, Int) -> Dict (Ord (DiffType v Int)) Source #

Lang r => Monad r Maybe Source # 

Methods

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

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

Lang r => Applicative r Maybe Source # 

Methods

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

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

Lang r => Functor r Maybe Source # 

Methods

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

Lang r => Functor r [] Source # 

Methods

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

Lang r => Vector r Double Source # 

Associated Types

type Basis Double :: * Source #

Lang r => Vector r Float Source # 

Associated Types

type Basis Float :: * Source #

Lang r => Vector r () Source # 

Associated Types

type Basis () :: * Source #

Methods

mult :: r h (Double -> () -> ()) Source #

divide :: r h (() -> Double -> ()) Source #

toFreeVector :: r h (() -> FreeVector (Basis ()) Double) Source #

Double r => Group r Double Source # 

Methods

invert :: r h (Double -> Double) Source #

minus :: r h (Double -> Double -> Double) Source #

Float r => Group r Float Source # 

Methods

invert :: r h (Float -> Float) Source #

minus :: r h (Float -> Float -> Float) Source #

Lang r => Group r () Source # 

Methods

invert :: r h (() -> ()) Source #

minus :: r h (() -> () -> ()) Source #

Dual r => BiFunctor * r Dual Source # 

Methods

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

Prod r => BiFunctor * r (,) Source # 

Methods

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

Lang r => BiFunctor * r Either Source # 

Methods

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

Double r => Monoid * r Double Source # 

Methods

zero :: Double h m Source #

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

Float r => Monoid * r Float Source # 

Methods

zero :: Float h m Source #

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

Lang r => Monoid * r () Source # 

Methods

zero :: () h m Source #

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

(Ord b, Lang r) => Monoid * r (SVTFBuilder b) Source # 

Methods

zero :: SVTFBuilder b h m Source #

plus :: SVTFBuilder b h (m -> m -> m) Source #

Lang r => Monoid * r (Fix (VectorTF b)) Source # 

Methods

zero :: Fix (VectorTF b) h m Source #

plus :: Fix (VectorTF b) h (m -> m -> m) Source #

(Ord b, Lang r) => Monoid * r (FreeVectorBuilder b) Source # 

Methods

zero :: FreeVectorBuilder b h m Source #

plus :: FreeVectorBuilder b h (m -> m -> m) Source #

Lang r => Monoid * r [a] Source # 

Methods

zero :: [a] h m Source #

plus :: [a] h (m -> m -> m) Source #

Lang r => Monoid * r (FreeVector b Double) Source # 

Methods

zero :: FreeVector b Double h m Source #

plus :: FreeVector b Double h (m -> m -> m) Source #

(Double r, Monoid * r v) => Monoid * r (Double -> v) Source # 

Methods

zero :: (Double -> v) h m Source #

plus :: (Double -> v) h (m -> m -> m) Source #

(Prod repr, Monoid * repr l, Monoid * repr r) => Monoid * repr (l, r) Source # 

Methods

zero :: (l, r) h m Source #

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

Lang r => Monad r (State l) Source # 

Methods

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

join :: r h (State l (State l a) -> State l a) Source #

(Lang r, Monoid * r w) => Monad r (Writer w) Source # 

Methods

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

join :: r h (Writer w (Writer w a) -> Writer w a) Source #

Lang r => Applicative r (State l) Source # 

Methods

pure :: r h (x -> State l x) Source #

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

(Lang r, Monoid * r w) => Applicative r (Writer w) Source # 

Methods

pure :: r h (x -> Writer w x) Source #

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

Lang r => Functor r (State l) Source # 

Methods

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

Lang r => Functor r (Map k) Source # 

Methods

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

Lang r => Functor r (Writer w) Source # 

Methods

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

Lang r => Functor r (VectorTF b) Source # 

Methods

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

(Ord b, Lang r) => Vector r (SVTFBuilder b) Source # 

Associated Types

type Basis (SVTFBuilder b) :: * Source #

(Ord b, Lang r) => Vector r (Fix (VectorTF b)) Source # 

Associated Types

type Basis (Fix (VectorTF b)) :: * Source #

Methods

mult :: r h (Double -> Fix (VectorTF b) -> Fix (VectorTF b)) Source #

divide :: r h (Fix (VectorTF b) -> Double -> Fix (VectorTF b)) Source #

toFreeVector :: r h (Fix (VectorTF b) -> FreeVector (Basis (Fix (VectorTF b))) Double) Source #

(Ord b, Lang r) => Vector r (FreeVectorBuilder b) Source # 
(Ord b, Lang r) => Group r (SVTFBuilder b) Source # 
(Ord b, Lang r) => Group r (Fix (VectorTF b)) Source # 

Methods

invert :: r h (Fix (VectorTF b) -> Fix (VectorTF b)) Source #

minus :: r h (Fix (VectorTF b) -> Fix (VectorTF b) -> Fix (VectorTF b)) Source #

(Ord b, Lang r) => Group r (FreeVectorBuilder b) Source # 
Lang r => Vector r (FreeVector b Double) Source # 
(Lang r, Vector r v) => Vector r (Double -> v) Source # 

Associated Types

type Basis (Double -> v) :: * Source #

Methods

mult :: r h (Double -> (Double -> v) -> Double -> v) Source #

divide :: r h ((Double -> v) -> Double -> Double -> v) Source #

toFreeVector :: r h ((Double -> v) -> FreeVector (Basis (Double -> v)) Double) Source #

(Prod repr, Double repr, Sum repr, FreeVector repr, Vector repr l, Vector repr r) => Vector repr (l, r) Source # 

Associated Types

type Basis (l, r) :: * Source #

Methods

mult :: repr h (Double -> (l, r) -> (l, r)) Source #

divide :: repr h ((l, r) -> Double -> (l, r)) Source #

toFreeVector :: repr h ((l, r) -> FreeVector (Basis (l, r)) Double) Source #

Lang r => Group r (FreeVector b Double) Source # 
(Lang r, Group r v) => Group r (Double -> v) Source # 

Methods

invert :: r h ((Double -> v) -> Double -> v) Source #

minus :: r h ((Double -> v) -> (Double -> v) -> Double -> v) Source #

(Prod repr, Group repr l, Group repr r) => Group repr (l, r) Source # 

Methods

invert :: repr h ((l, r) -> (l, r)) Source #

minus :: repr h ((l, r) -> (l, r) -> (l, r)) Source #

(Ord b, Ord f) => Ord (VectorTF b f) Source # 

Methods

diffOrd :: Proxy * (v, VectorTF b f) -> Dict (Ord (DiffType v (VectorTF b f))) Source #