DeepDarkFantasy-0.2017.8.18: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.PE

Documentation

data P repr h a where Source #

Constructors

Open :: (forall hout. EnvT repr h hout -> P repr hout a) -> P repr h a 
Unk :: repr h a -> P repr h a 
Known :: K repr h a -> repr h a -> (forall hout. EnvT repr h hout -> P repr hout a) -> (forall any. P repr (any, h) a) -> (forall hh ht. (hh, ht) ~ h => P repr ht (hh -> a)) -> P repr h a 

Instances

DBI r => DBI (P r) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

Float r => Float (P r) Source # 
Option repr => Option (P repr) Source # 

Methods

nothing :: P repr h (Maybe a) Source #

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

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

Prod r => Prod (P r) Source # 

Methods

mkProd :: P r h (a -> b -> (a, b)) Source #

zro :: P r h ((a, b) -> a) Source #

fst :: P r h ((a, b) -> b) Source #

swap :: P r h ((x, y) -> (y, x)) Source #

curry :: P r h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: P r h ((a -> b -> c) -> (a, b) -> c) Source #

Dual repr => Dual (P repr) Source # 

Methods

dual :: P repr h ((x, y) -> Dual x y) Source #

runDual :: P repr h (Dual x y -> (x, y)) Source #

mkDual :: P repr h (x -> y -> Dual x y) Source #

dualOrig :: P repr h (Dual x y -> x) Source #

dualDiff :: P repr h (Dual x y -> y) Source #

Sum r => Sum (P r) Source # 

Methods

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

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

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

Unit repr => Unit (P repr) Source # 

Methods

unit :: P repr h () Source #

Y r => Y (P r) Source # 

Methods

y :: P r h ((a -> a) -> a) Source #

undefined :: P r h a Source #

List repr => List (P repr) Source # 

Methods

nil :: P repr h [a] Source #

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

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

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

Char repr => Char (P repr) Source # 

Methods

char :: Char -> P repr h Char Source #

IO repr => IO (P repr) Source # 

Methods

putStrLn :: P repr h (String -> IO ()) Source #

Bool r => Bool (P r) Source # 

Methods

bool :: Bool -> P r h Bool Source #

true :: P r h Bool Source #

false :: P r h Bool Source #

ite :: P r h (a -> a -> Bool -> a) Source #

Double r => Double (P r) Source # 
Int repr => Int (P repr) Source # 

Methods

int :: Int -> P repr h Int Source #

pred :: P repr h (Int -> Int) Source #

isZero :: P repr h (Int -> Bool) Source #

IO repr => Monad (P repr) IO Source # 

Methods

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

join :: P repr h (IO (IO a) -> IO a) Source #

IO repr => Applicative (P repr) IO Source # 

Methods

pure :: P repr h (x -> IO x) Source #

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

IO repr => Functor (P repr) IO Source # 

Methods

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

know :: DBI repr => K repr h a -> repr h a -> (forall hout. EnvT repr h hout -> P repr hout a) -> (forall any. P repr (any, h) a) -> P repr h a Source #

static :: forall repr h a. DBI repr => (forall h'. (K repr h' a, repr h' a)) -> P repr h a Source #

isOpen :: P t2 t1 t -> Bool Source #

type family K (repr :: * -> * -> *) h a Source #

Instances

type K repr h () Source # 
type K repr h () = ()
type K repr h Int Source # 
type K repr h Int = Int
type K repr h Char Source # 
type K repr h Char = Char
type K repr h Float Source # 
type K repr h Float = Float
type K repr h Double Source # 
type K repr h Double = Double
type K repr h Bool Source # 
type K repr h Bool = Bool
type K repr h (IO a) Source # 
type K repr h (IO a) = P repr h a
type K repr h (Maybe a) Source # 
type K repr h (Maybe a) = Maybe (P repr h a)
type K repr h [a] Source # 
type K repr h [a] = Maybe (P repr h a, P repr h [a])
type K repr h (Dual l r) Source # 
type K repr h (Dual l r) = (P repr h l, P repr h r)
type K repr h (Either a b) Source # 
type K repr h (Either a b) = Either (P repr h a) (P repr h b)
type K repr h (a, b) Source # 
type K repr h (a, b) = (P repr h a, P repr h b)
type K repr h (a -> b) Source # 
type K repr h (a -> b) = Fun repr h a b

mkFun :: DBI repr => (forall hout. EnvT repr (a, h) hout -> P repr hout b) -> P repr h (a -> b) Source #

data EnvT repr hin hout where Source #

Constructors

Dyn :: EnvT repr hin hin 
Arg :: P repr hout a -> EnvT repr (a, hout) hout 
Weak :: EnvT repr h (a, h) 
Next :: EnvT repr hin hout -> EnvT repr (a, hin) (a, hout) 

dynamic :: DBI repr => P repr h a -> repr h a Source #

app_open :: DBI repr => P repr hin r -> EnvT repr hin hout -> P repr hout r Source #

newtype Fun repr h a b Source #

Constructors

Fun 

Fields

  • runFun :: forall hout. EnvT repr (a, h) hout -> P repr hout b
     

data MapPE repr h k a :: * where Source #

Constructors

EmptyMap :: MapPE repr h k a 
SingletonMap :: P repr h k -> P repr h a -> MapPE repr h k a 

pe :: DBI repr => P repr () a -> repr () a Source #