DeepDarkFantasy-0.2017.8.9: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.UInt

Documentation

data UInt h x Source #

Constructors

UInt 

Instances

DBI UInt Source # 

Methods

z :: UInt (a, h) a Source #

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

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

app :: UInt h (a -> b) -> UInt h a -> UInt h b Source #

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

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

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

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

const :: UInt h (a -> b -> a) Source #

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

dup :: UInt h ((a -> a -> b) -> a -> b) Source #

let_ :: UInt h (a -> (a -> b) -> b) Source #

Fix UInt Source # 

Methods

fix :: UInt h (f (Fix f) -> Fix f) Source #

runFix :: UInt h (Fix f -> f (Fix f)) Source #

Float UInt Source # 
FreeVector UInt Source # 

Methods

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

runFreeVector :: UInt h (FreeVector b d -> b -> d) Source #

Option UInt Source # 

Methods

nothing :: UInt h (Maybe a) Source #

just :: UInt h (a -> Maybe a) Source #

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

Prod UInt Source # 

Methods

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

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

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

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

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

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

Dual UInt Source # 

Methods

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

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

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

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

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

Sum UInt Source # 

Methods

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 #

Unit UInt Source # 

Methods

unit :: UInt h () Source #

Y UInt Source # 

Methods

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

undefined :: UInt h a Source #

List UInt Source # 

Methods

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 #

Char UInt Source # 

Methods

char :: Char -> UInt h Char Source #

IO UInt Source # 

Methods

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

Bool UInt Source # 

Methods

bool :: Bool -> UInt h Bool Source #

ite :: UInt h (a -> a -> Bool -> a) Source #

Double UInt Source # 
Map UInt Source # 

Methods

empty :: UInt h (Map k a) Source #

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

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

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

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

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

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

DiffWrapper UInt Source # 
VectorTF UInt Source # 

Methods

zero :: UInt h (VectorTF t f) Source #

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

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

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

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

Int UInt Source # 

Methods

int :: Int -> UInt h Int Source #

pred :: UInt h (Int -> Int) Source #

isZero :: UInt h (Int -> Bool) Source #

Bimap UInt Source # 

Methods

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

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

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

empty :: UInt h (Bimap a b) Source #

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

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

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

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

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

updateR :: (Ord a, Ord b) => UInt h ((a -> Maybe a) -> b -> Bimap a b -> Bimap a b) Source #

Lang UInt Source # 

Methods

exfalso :: UInt h (Void -> 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 #

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

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

iterate :: UInt h ((x -> x) -> x -> [x]) Source #

buildFreeVector :: Ord b => UInt h (FreeVectorBuilder b -> FreeVector b Double) Source #

toSVTFBuilder :: Ord b => UInt h (VectorTF b Int -> SVTFBuilder b) Source #

get :: UInt h (Maybe a -> a) Source #

getVar :: UInt h (State x x) Source #

update :: UInt h ((x -> x) -> State x ()) Source #

updateWengert :: UInt h (Int -> Double -> Map Int Double -> Map Int Double) Source #

vtfCata :: UInt h ((VectorTF a b -> b) -> Fix (VectorTF a) -> b) Source #

Monad UInt x Source # 

Methods

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

join :: UInt h (x (x a) -> x a) Source #

Applicative UInt x Source # 

Methods

pure :: UInt h (x -> x x) Source #

ap :: UInt h (x (x -> y) -> x x -> x y) Source #

Functor UInt x Source # 

Methods

map :: UInt h ((a -> b) -> x a -> x b) Source #