DeepDarkFantasy-0.2017.4.5: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.Lang

Contents

Documentation

class (Bool r, Char r, Double r, Float r, Map r, Dual r) => Lang r where Source #

Methods

fix :: r h ((a -> a) -> a) Source #

left :: r h (a -> Either a b) Source #

right :: r h (b -> Either a b) Source #

sumMatch :: r h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: r h () Source #

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

ioRet :: r h (a -> IO a) Source #

ioBind :: r h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: r h ((a -> b) -> IO a -> IO b) Source #

nil :: r h [a] Source #

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

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

listAppend :: r h ([a] -> [a] -> [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 #

undefined :: r h a Source #

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

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

putStrLn :: r h (String -> IO ()) Source #

Instances

Lang Eval Source # 

Methods

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

left :: Eval h (a -> Either a b) Source #

right :: Eval h (b -> Either a b) Source #

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

unit :: Eval h () Source #

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

ioRet :: Eval h (a -> IO a) Source #

ioBind :: Eval h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: Eval h ((a -> b) -> IO a -> IO b) Source #

nil :: Eval h [a] Source #

cons :: Eval h (a -> [a] -> [a]) Source #

listMatch :: Eval h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: Eval h ([a] -> [a] -> [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 #

undefined :: Eval h a Source #

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

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

putStrLn :: Eval h (String -> IO ()) Source #

Lang Show Source # 

Methods

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

left :: Show h (a -> Either a b) Source #

right :: Show h (b -> Either a b) Source #

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

unit :: Show h () Source #

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

ioRet :: Show h (a -> IO a) Source #

ioBind :: Show h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: Show h ((a -> b) -> IO a -> IO b) Source #

nil :: Show h [a] Source #

cons :: Show h (a -> [a] -> [a]) Source #

listMatch :: Show h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: Show h ([a] -> [a] -> [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 #

undefined :: Show h a Source #

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

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

putStrLn :: Show h (String -> IO ()) Source #

Lang Size Source # 

Methods

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

left :: Size h (a -> Either a b) Source #

right :: Size h (b -> Either a b) Source #

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

unit :: Size h () Source #

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

ioRet :: Size h (a -> IO a) Source #

ioBind :: Size h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: Size h ((a -> b) -> IO a -> IO b) Source #

nil :: Size h [a] Source #

cons :: Size h (a -> [a] -> [a]) Source #

listMatch :: Size h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: Size h ([a] -> [a] -> [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 #

undefined :: Size h a Source #

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

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

putStrLn :: Size h (String -> IO ()) Source #

Lang r => Lang (GWDiff r) Source # 

Methods

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

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

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

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

unit :: GWDiff r h () Source #

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

ioRet :: GWDiff r h (a -> IO a) Source #

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

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

nil :: GWDiff r h [a] Source #

cons :: GWDiff r h (a -> [a] -> [a]) Source #

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

listAppend :: GWDiff r h ([a] -> [a] -> [a]) Source #

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

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

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

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

undefined :: GWDiff r h a Source #

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

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

putStrLn :: GWDiff r h (String -> IO ()) Source #

Lang r => Lang (ImpW r) Source # 

Methods

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

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

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

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

unit :: ImpW r h () Source #

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

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

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

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

nil :: ImpW r h [a] Source #

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

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

listAppend :: ImpW r h ([a] -> [a] -> [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 #

undefined :: ImpW r h a Source #

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

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

putStrLn :: ImpW r h (String -> IO ()) Source #

Lang r => Lang (UnHOAS r) Source # 

Methods

fix :: UnHOAS r h ((a -> a) -> a) Source #

left :: UnHOAS r h (a -> Either a b) Source #

right :: UnHOAS r h (b -> Either a b) Source #

sumMatch :: UnHOAS r h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: UnHOAS r h () Source #

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

ioRet :: UnHOAS r h (a -> IO a) Source #

ioBind :: UnHOAS r h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: UnHOAS r h ((a -> b) -> IO a -> IO b) Source #

nil :: UnHOAS r h [a] Source #

cons :: UnHOAS r h (a -> [a] -> [a]) Source #

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

listAppend :: UnHOAS r h ([a] -> [a] -> [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 #

undefined :: UnHOAS r h a Source #

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

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

putStrLn :: UnHOAS r h (String -> IO ()) Source #

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

Methods

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

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

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

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

unit :: Combine l r h () Source #

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

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

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

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

nil :: Combine l r h [a] Source #

cons :: Combine l r h (a -> [a] -> [a]) Source #

listMatch :: Combine l r h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: Combine l r h ([a] -> [a] -> [a]) Source #

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

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

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

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

undefined :: Combine l r h a Source #

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

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

putStrLn :: Combine l r h (String -> IO ()) Source #

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

Methods

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

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

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

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

unit :: WDiff r v h () Source #

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

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

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

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

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

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

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

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

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

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

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

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

undefined :: WDiff r v h a Source #

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

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

putStrLn :: WDiff r v h (String -> IO ()) 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 :: x -> Double h x Source #

Lang r => Reify * r () Source # 

Methods

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

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

Methods

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

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

Methods

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

class Monoid r g => Group r g where Source #

Minimal complete definition

invert | minus

Methods

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

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

invert :: DBI r => r h (g -> g) Source #

minus :: DBI r => r h (g -> g -> g) Source #

Instances

Float r => Group r Float Source # 

Methods

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

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

Double r => Group r Double Source # 

Methods

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

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

Lang r => Group r () Source # 

Methods

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

minus :: r h (() -> () -> ()) 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 #

class Group r v => Vector r v where Source #

Minimal complete definition

mult | divide

Methods

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

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

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

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

Instances

Lang r => Vector r Float Source # 

Methods

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

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

Double r => Vector r Double Source # 

Methods

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

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

Lang r => Vector r () Source # 

Methods

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

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

(Lang r, Vector r v) => Vector r (Double -> v) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

cons2 :: Lang repr => repr h a1 -> repr h [a1] -> repr h [a1] Source #

listMatch2 :: Lang repr => repr h a1 -> repr h (a -> [a] -> a1) -> repr h ([a] -> a1) Source #

fix1 :: Lang repr => repr h (b -> b) -> repr h b Source #

fix2 :: Lang repr => repr h ((a -> b) -> a -> b) -> repr h a -> repr h b Source #

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

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

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

mult1 :: (Vector repr v, DBI repr) => repr h Double -> repr h (v -> v) Source #

mult2 :: (Vector repr b, DBI repr) => repr h Double -> repr h b -> repr h b Source #

divide2 :: (Vector repr b, DBI repr) => repr h b -> repr h Double -> repr h b Source #

invert1 :: (Group repr b, DBI repr) => repr h b -> repr h b Source #

minus1 :: (Group repr a, DBI repr) => repr h a -> repr h (a -> a) Source #

divide1 :: (Vector repr a, DBI repr) => repr h a -> repr h (Double -> a) Source #

recip :: Double repr => repr h (Double -> Double) Source #

recip1 :: Double repr => repr h Double -> repr h Double Source #

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

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

ioBind2 :: Lang repr => repr h (IO a) -> repr h (a -> IO b) -> repr h (IO b) Source #

minus2 :: (Group repr b, DBI repr) => repr h b -> repr h b -> repr h b Source #

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

doubleExp1 :: Double repr => repr h Double -> repr h Double Source #

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

sumMatch2 :: Lang repr => repr h (a -> c) -> repr h (b -> c) -> repr h (Either a b -> c) Source #

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

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

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

module DDF.Bool

module DDF.Char

module DDF.Double

module DDF.Float

module DDF.Map

module DDF.Dual

Orphan instances

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 => Monad r IO Source # 

Methods

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

join :: r h (IO (IO a) -> IO a) 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 #

Lang r => Applicative * r Maybe Source # 

Methods

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

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

Lang r => Applicative * r IO Source # 

Methods

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

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

Lang r => Functor * r Maybe Source # 

Methods

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

Lang r => Functor * r IO Source # 

Methods

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

Lang r => Functor * r [] Source # 

Methods

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

Float r => Monoid * r Float Source # 

Methods

zero :: Float h m Source #

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

Double r => Monoid * r Double Source # 

Methods

zero :: Double h m Source #

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

Lang r => Monoid * r () Source # 

Methods

zero :: () h m Source #

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

zero :: [a] h m Source #

plus :: [a] 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 repr => ProdCon (Monoid * repr) l r Source # 

Methods

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