DeepDarkFantasy-0.2017.4.9: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.ImpW

Documentation

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

Prod r => DBI (ImpW r) Source # 

Methods

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

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

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

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

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

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

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

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

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

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

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

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

(Prod r, Double r) => Double (ImpW r) Source # 
(Prod r, Float r) => Float (ImpW r) Source # 
(Prod r, Option r) => Option (ImpW r) Source # 

Methods

nothing :: ImpW r h (Maybe a) Source #

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

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

Prod r => Prod (ImpW r) Source # 

Methods

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

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

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

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

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

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

Dual r => Dual (ImpW r) Source # 

Methods

dual :: ImpW r h ((x, y) -> Dual x y) Source #

runDual :: ImpW r h (Dual x y -> (x, y)) Source #

mkDual :: ImpW r h (x -> y -> Dual x y) Source #

dualOrig :: ImpW r h (Dual x y -> x) Source #

dualDiff :: ImpW r h (Dual x y -> y) Source #

Map r => Map (ImpW r) Source # 

Methods

empty :: ImpW r h (Map k a) Source #

singleton :: ImpW r h (k -> a -> Map k a) Source #

lookup :: Ord k => ImpW r h (k -> Map k a -> Maybe a) Source #

alter :: Ord k => ImpW r h ((Maybe a -> Maybe a) -> k -> Map k a -> Map k a) Source #

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

(Prod r, Char r) => Char (ImpW r) Source # 

Methods

char :: Char -> ImpW r h Char Source #

(Prod r, Bool r) => Bool (ImpW r) Source # 

Methods

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

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

Bimap r => Bimap (ImpW r) 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 #

runImpW :: forall repr h x. Lang repr => ImpW repr h x -> RunImpW repr h x 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 #