DeepDarkFantasy-0.2017.4.19: 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) => 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 #

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 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 #

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 #

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 UInt Source # 

Methods

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

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

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

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

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

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

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

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

nil :: UInt h [a] Source #

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

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

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

undefined :: UInt h a Source #

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

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

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

Lang r => Lang (UnLiftEnv r) Source # 

Methods

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

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

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

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

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

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

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

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

nil :: UnLiftEnv r h [a] Source #

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

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

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

undefined :: UnLiftEnv r h a Source #

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

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

putStrLn :: UnLiftEnv r 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 :: 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 #

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

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

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

fix2 :: Lang r => r h ((a -> b) -> a -> b) -> r h a -> r h b 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 #

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

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

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

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

sumMatch2 :: Lang r => r h (a -> c) -> r h (b -> c) -> r h (Either a b -> c) 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 #

module DDF.Bool

module DDF.Char

module DDF.Double

module DDF.Float

module DDF.Bimap

module DDF.Dual

module DDF.Unit

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 #

Lang r => Vector r Float Source # 

Methods

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

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

Lang r => Vector r () Source # 

Methods

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

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

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 #

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 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 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 #

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

Methods

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

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

Methods

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