DeepDarkFantasy-0.2017.8.8: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.ImpW

Documentation

class ProdCon con l r where Source #

Minimal complete definition

prodCon

Methods

prodCon :: (con l, con r) :- con (l, r) Source #

Instances

ProdCon Show l r Source # 

Methods

prodCon :: (Show l, Show r) :- Show (l, r) Source #

ProdCon Random l r Source # 

Methods

prodCon :: (Random l, Random r) :- Random (l, r) Source #

ProdCon RandRange l r Source # 

Methods

prodCon :: (RandRange l, RandRange r) :- RandRange (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 (Reify repr) l r Source # 

Methods

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

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

Methods

prodCon :: (WithDiff repr l, WithDiff repr r) :- WithDiff 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 #

class Weight w where Source #

Minimal complete definition

weightCon

Methods

weightCon :: (con (), con Float, con Double, ForallV (ProdCon con)) :- con w Source #

Instances

Weight Double Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con Double Source #

Weight Float Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con Float Source #

Weight () Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con () Source #

(Weight l, Weight r) => Weight (l, r) Source # 

Methods

weightCon :: (con (), con Float, con Double, ForallV (* -> * -> Constraint) (ProdCon con)) :- con (l, r) Source #

runImpW :: forall r h x. Unit r => ImpW r h x -> RunImpW r h x Source #

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, Fix r) => Fix (ImpW r) Source # 

Methods

fix :: ImpW r h (f (Fix f) -> Fix f) Source #

runFix :: ImpW r h (Fix f -> f (Fix f)) Source #

(Prod r, Float r) => Float (ImpW r) Source # 
(Prod r, FreeVector r) => FreeVector (ImpW r) Source # 

Methods

freeVector :: ImpW r h ((b -> d) -> FreeVector b d) Source #

runFreeVector :: ImpW r h (FreeVector b d -> b -> d) 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 #

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

Methods

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 #

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

Methods

unit :: ImpW r h () Source #

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

Methods

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

undefined :: ImpW r h a Source #

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

Methods

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 #

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

Methods

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

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

Methods

putStrLn :: ImpW r h (String -> IO ()) 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 #

(Prod r, Double r) => Double (ImpW r) 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 (Map k a -> k -> 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 #

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

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

(Prod r, DiffWrapper r) => DiffWrapper (ImpW r) Source # 
(Prod r, VectorTF r) => VectorTF (ImpW r) Source # 

Methods

zero :: ImpW r h (VectorTF t f) Source #

basis :: ImpW r h (t -> VectorTF t f) Source #

plus :: ImpW r h (f -> f -> VectorTF t f) Source #

mult :: ImpW r h (Double -> f -> VectorTF t f) Source #

vtfMatch :: ImpW r h (a -> (t -> a) -> (f -> f -> a) -> (Double -> f -> a) -> VectorTF t f -> a) Source #

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

Methods

int :: Int -> ImpW r h Int Source #

pred :: ImpW r h (Int -> Int) Source #

isZero :: ImpW r h (Int -> Bool) Source #

Bimap r => Bimap (ImpW r) Source # 

Methods

size :: ImpW r h (Bimap a b -> Int) Source #

lookupL :: (Ord a, Ord b) => ImpW r h (Bimap a b -> a -> Maybe b) Source #

lookupR :: (Ord a, Ord b) => ImpW r h (Bimap a b -> b -> Maybe a) Source #

empty :: ImpW r h (Bimap a b) Source #

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

toMapL :: ImpW r h (Bimap a b -> Map a b) Source #

toMapR :: ImpW r h (Bimap a b -> Map b a) Source #

insert :: (Ord a, Ord b) => ImpW r h ((a, b) -> Bimap a b -> Bimap a b) Source #

updateL :: (Ord a, Ord b) => ImpW r h ((b -> Maybe b) -> a -> Bimap a b -> Bimap a b) Source #

updateR :: (Ord a, Ord b) => ImpW r h ((a -> Maybe a) -> b -> Bimap a b -> Bimap 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 #

(Prod r, Monad r x) => Monad (ImpW r) x Source # 

Methods

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

join :: ImpW r h (x (x a) -> x a) Source #

(Prod r, Applicative r x) => Applicative (ImpW r) x Source # 

Methods

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

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

(Prod r, Functor r x) => Functor (ImpW r) x Source # 

Methods

map :: ImpW r h ((a -> b) -> x a -> x b) 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 #