DeepDarkFantasy-0.0.1.1: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DBI

Contents

Documentation

class Reify repr x where Source #

Minimal complete definition

reify

Methods

reify :: x -> repr h x Source #

Instances

DBI repr => Reify * repr Double Source # 

Methods

reify :: x -> Double h x Source #

DBI repr => Reify * repr () Source # 

Methods

reify :: x -> () h x Source #

(DBI repr, Reify * repr l, Reify * repr r) => Reify * repr (l, r) Source # 

Methods

reify :: x -> (l, r) h x Source #

class DBI repr where Source #

Methods

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

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

lam :: repr (a, h) b -> repr h (a -> b) Source #

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

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

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

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

lit :: Double -> repr h Double Source #

litZero :: repr h Double Source #

litOne :: repr h Double Source #

doublePlus :: repr h (Double -> Double -> Double) Source #

doubleMinus :: repr h (Double -> Double -> Double) Source #

doubleMult :: repr h (Double -> Double -> Double) Source #

doubleDivide :: repr h (Double -> Double -> Double) Source #

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

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

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

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

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

unit :: repr h () Source #

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

nothing :: repr h (Maybe a) Source #

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

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

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

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

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

nil :: repr h [a] Source #

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

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

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

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

writer :: repr h ((a, w) -> Writer w a) Source #

runWriter :: repr h (Writer w a -> (a, w)) Source #

swap :: repr h ((l, r) -> (r, l)) Source #

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

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

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

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

exp :: repr h (Double -> Double) Source #

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

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

Instances

DBI Eval Source # 

Methods

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

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

lam :: Eval (a, h) b -> Eval h (a -> b) Source #

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

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

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

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

lit :: Double -> Eval h Double Source #

litZero :: Eval h Double Source #

litOne :: Eval h Double Source #

doublePlus :: Eval h (Double -> Double -> Double) Source #

doubleMinus :: Eval h (Double -> Double -> Double) Source #

doubleMult :: Eval h (Double -> Double -> Double) Source #

doubleDivide :: Eval h (Double -> Double -> Double) Source #

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

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

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

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

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

unit :: Eval h () Source #

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

nothing :: Eval h (Maybe a) Source #

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

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

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

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

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

nil :: Eval h [a] Source #

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

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

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

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

writer :: Eval h ((a, w) -> Writer w a) Source #

runWriter :: Eval h (Writer w a -> (a, w)) Source #

swap :: Eval h ((l, r) -> (r, l)) Source #

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

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

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

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

exp :: Eval h (Double -> Double) Source #

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

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

DBI repr => DBI (ImpW repr) Source # 

Methods

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

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

lam :: ImpW repr (a, h) b -> ImpW repr h (a -> b) Source #

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

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

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

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

lit :: Double -> ImpW repr h Double Source #

litZero :: ImpW repr h Double Source #

litOne :: ImpW repr h Double Source #

doublePlus :: ImpW repr h (Double -> Double -> Double) Source #

doubleMinus :: ImpW repr h (Double -> Double -> Double) Source #

doubleMult :: ImpW repr h (Double -> Double -> Double) Source #

doubleDivide :: ImpW repr h (Double -> Double -> Double) Source #

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

fix :: ImpW repr h ((a -> a) -> a) Source #

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

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

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

unit :: ImpW repr h () Source #

exfalso :: ImpW repr h (Void -> a) Source #

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

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

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

ioRet :: ImpW repr h (a -> IO a) Source #

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

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

nil :: ImpW repr h [a] Source #

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

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

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

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

writer :: ImpW repr h ((a, w) -> Writer w a) Source #

runWriter :: ImpW repr h (Writer w a -> (a, w)) Source #

swap :: ImpW repr h ((l, r) -> (r, l)) Source #

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

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

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

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

exp :: ImpW repr h (Double -> Double) Source #

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

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

(Vector repr v, DBI repr) => DBI (WDiff repr v) Source # 

Methods

z :: WDiff repr v (a, h) a Source #

s :: WDiff repr v h b -> WDiff repr v (a, h) b Source #

lam :: WDiff repr v (a, h) b -> WDiff repr v h (a -> b) Source #

app :: WDiff repr v h (a -> b) -> WDiff repr v h a -> WDiff repr v h b Source #

mkProd :: WDiff repr v h (a -> b -> (a, b)) Source #

zro :: WDiff repr v h ((a, b) -> a) Source #

fst :: WDiff repr v h ((a, b) -> b) Source #

lit :: Double -> WDiff repr v h Double Source #

litZero :: WDiff repr v h Double Source #

litOne :: WDiff repr v h Double Source #

doublePlus :: WDiff repr v h (Double -> Double -> Double) Source #

doubleMinus :: WDiff repr v h (Double -> Double -> Double) Source #

doubleMult :: WDiff repr v h (Double -> Double -> Double) Source #

doubleDivide :: WDiff repr v h (Double -> Double -> Double) Source #

hoas :: (WDiff repr v (a, h) a -> WDiff repr v (a, h) b) -> WDiff repr v h (a -> b) Source #

fix :: WDiff repr v h ((a -> a) -> a) Source #

left :: WDiff repr v h (a -> Either a b) Source #

right :: WDiff repr v h (b -> Either a b) Source #

sumMatch :: WDiff repr v h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: WDiff repr v h () Source #

exfalso :: WDiff repr v h (Void -> a) Source #

nothing :: WDiff repr v h (Maybe a) Source #

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

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

ioRet :: WDiff repr v h (a -> IO a) Source #

ioBind :: WDiff repr v h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: WDiff repr v h ((a -> b) -> IO a -> IO b) Source #

nil :: WDiff repr v h [a] Source #

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

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

com :: WDiff repr v h ((b -> c) -> (a -> b) -> a -> c) Source #

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

writer :: WDiff repr v h ((a, w) -> Writer w a) Source #

runWriter :: WDiff repr v h (Writer w a -> (a, w)) Source #

swap :: WDiff repr v h ((l, r) -> (r, l)) Source #

flip :: WDiff repr v h ((a -> b -> c) -> b -> a -> c) Source #

id :: WDiff repr v h (a -> a) Source #

const :: WDiff repr v h (a -> b -> a) Source #

scomb :: WDiff repr v h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

exp :: WDiff repr v h (Double -> Double) Source #

curry :: WDiff repr v h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: WDiff repr v h ((a -> b -> c) -> (a, b) -> c) Source #

DBI (Show * *) Source # 

Methods

z :: Show * * (a, h) a Source #

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

lam :: Show * * (a, h) b -> Show * * h (a -> b) Source #

app :: Show * * h (a -> b) -> Show * * h a -> Show * * h b Source #

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

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

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

lit :: Double -> Show * * h Double Source #

litZero :: Show * * h Double Source #

litOne :: Show * * h Double Source #

doublePlus :: Show * * h (Double -> Double -> Double) Source #

doubleMinus :: Show * * h (Double -> Double -> Double) Source #

doubleMult :: Show * * h (Double -> Double -> Double) Source #

doubleDivide :: Show * * h (Double -> Double -> Double) Source #

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

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 #

unit :: Show * * h () Source #

exfalso :: Show * * h (Void -> a) Source #

nothing :: Show * * h (Maybe a) Source #

just :: Show * * h (a -> Maybe a) Source #

optionMatch :: Show * * h (b -> (a -> b) -> Maybe a -> b) 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 #

com :: Show * * h ((b -> c) -> (a -> b) -> a -> c) 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 #

swap :: Show * * h ((l, r) -> (r, l)) Source #

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

id :: Show * * h (a -> a) Source #

const :: Show * * h (a -> b -> a) Source #

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

exp :: Show * * h (Double -> Double) Source #

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

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

DBI (Term * * DBI) Source # 

Methods

z :: Term * * DBI (a, h) a Source #

s :: Term * * DBI h b -> Term * * DBI (a, h) b Source #

lam :: Term * * DBI (a, h) b -> Term * * DBI h (a -> b) Source #

app :: Term * * DBI h (a -> b) -> Term * * DBI h a -> Term * * DBI h b Source #

mkProd :: Term * * DBI h (a -> b -> (a, b)) Source #

zro :: Term * * DBI h ((a, b) -> a) Source #

fst :: Term * * DBI h ((a, b) -> b) Source #

lit :: Double -> Term * * DBI h Double Source #

litZero :: Term * * DBI h Double Source #

litOne :: Term * * DBI h Double Source #

doublePlus :: Term * * DBI h (Double -> Double -> Double) Source #

doubleMinus :: Term * * DBI h (Double -> Double -> Double) Source #

doubleMult :: Term * * DBI h (Double -> Double -> Double) Source #

doubleDivide :: Term * * DBI h (Double -> Double -> Double) Source #

hoas :: (Term * * DBI (a, h) a -> Term * * DBI (a, h) b) -> Term * * DBI h (a -> b) Source #

fix :: Term * * DBI h ((a -> a) -> a) Source #

left :: Term * * DBI h (a -> Either a b) Source #

right :: Term * * DBI h (b -> Either a b) Source #

sumMatch :: Term * * DBI h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: Term * * DBI h () Source #

exfalso :: Term * * DBI h (Void -> a) Source #

nothing :: Term * * DBI h (Maybe a) Source #

just :: Term * * DBI h (a -> Maybe a) Source #

optionMatch :: Term * * DBI h (b -> (a -> b) -> Maybe a -> b) Source #

ioRet :: Term * * DBI h (a -> IO a) Source #

ioBind :: Term * * DBI h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: Term * * DBI h ((a -> b) -> IO a -> IO b) Source #

nil :: Term * * DBI h [a] Source #

cons :: Term * * DBI h (a -> [a] -> [a]) Source #

listMatch :: Term * * DBI h (b -> (a -> [a] -> b) -> [a] -> b) Source #

com :: Term * * DBI h ((b -> c) -> (a -> b) -> a -> c) Source #

listAppend :: Term * * DBI h ([a] -> [a] -> [a]) Source #

writer :: Term * * DBI h ((a, w) -> Writer w a) Source #

runWriter :: Term * * DBI h (Writer w a -> (a, w)) Source #

swap :: Term * * DBI h ((l, r) -> (r, l)) Source #

flip :: Term * * DBI h ((a -> b -> c) -> b -> a -> c) Source #

id :: Term * * DBI h (a -> a) Source #

const :: Term * * DBI h (a -> b -> a) Source #

scomb :: Term * * DBI h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

exp :: Term * * DBI h (Double -> Double) Source #

curry :: Term * * DBI h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: Term * * DBI h ((a -> b -> c) -> (a, b) -> c) Source #

const1 :: DBI repr => repr h a -> repr h (b -> a) Source #

cons2 :: DBI repr => repr h a -> repr h [a] -> repr h [a] Source #

listMatch2 :: DBI repr => repr h a1 -> repr h (a -> [a] -> a1) -> repr h ([a] -> a1) Source #

fix1 :: DBI repr => repr h (b -> b) -> repr h b Source #

fix2 :: DBI repr => repr h ((a -> b) -> a -> b) -> repr h a -> repr h b Source #

uncurry1 :: DBI repr => repr h (a -> b -> c) -> repr h ((a, b) -> c) Source #

class Monoid r m where Source #

Minimal complete definition

zero, plus

Methods

zero :: r h m Source #

plus :: r h (m -> m -> m) Source #

Instances

DBI r => Monoid * r Double Source # 

Methods

zero :: Double h m Source #

plus :: Double h (m -> m -> m) Source #

DBI r => Monoid * r () Source # 

Methods

zero :: () h m Source #

plus :: () h (m -> m -> m) Source #

DBI r => Monoid * r [a] Source # 

Methods

zero :: [a] h m Source #

plus :: [a] h (m -> m -> m) Source #

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

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

class (DBI r, Monoid r g) => Group r g where Source #

Minimal complete definition

invert | minus

Methods

invert :: r h (g -> g) Source #

minus :: r h (g -> g -> g) Source #

Instances

DBI r => Group r Double Source # 

Methods

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

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

DBI r => Group r () Source # 

Methods

invert :: r h (() -> ()) Source #

minus :: r h (() -> () -> ()) Source #

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

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

minus1 :: Group repr a => repr h a -> repr h (a -> a) Source #

divide1 :: Vector repr a => repr h a -> repr h (Double -> a) Source #

recip :: DBI repr => repr h (Double -> Double) Source #

recip1 :: DBI repr => repr h Double -> repr h Double Source #

class Group r v => Vector r v where Source #

Minimal complete definition

mult | divide

Methods

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

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

Instances

DBI r => Vector r Double Source # 

Methods

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

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

DBI r => Vector r () Source # 

Methods

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

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

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

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

class Functor r f where Source #

Minimal complete definition

map

Methods

map :: r h ((a -> b) -> f a -> f b) Source #

Instances

DBI r => Functor * r Maybe Source # 

Methods

map :: Maybe h ((a -> b) -> f a -> f b) Source #

DBI r => Functor * r IO Source # 

Methods

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

DBI r => Functor * r [] Source # 

Methods

map :: [h] ((a -> b) -> f a -> f b) Source #

DBI r => Functor * r (Writer w) Source # 

Methods

map :: Writer w h ((a -> b) -> f a -> f b) Source #

map2 :: (Functor * repr f, DBI repr) => repr h (a -> b) -> repr h (f a) -> repr h (f b) Source #

class Functor r a => Applicative r a where Source #

Minimal complete definition

pure, ap

Methods

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

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

Instances

DBI r => Applicative * r Maybe Source # 

Methods

pure :: Maybe h (x -> a x) Source #

ap :: Maybe h (a (x -> y) -> a x -> a y) Source #

DBI r => Applicative * r IO Source # 

Methods

pure :: IO h (x -> a x) Source #

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

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

return :: Applicative k r a => r h (x -> a x) Source #

class (DBI r, Applicative r m) => Monad r m where Source #

Minimal complete definition

join | bind

Methods

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

join :: r h (m (m a) -> m a) Source #

Instances

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

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

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

bind2 :: Monad repr m => repr h (m a) -> repr h (a -> m b) -> repr h (m b) Source #

map1 :: (Functor * repr f, DBI repr) => repr h (a -> b) -> repr h (f a -> f b) Source #

join1 :: Monad repr m => repr h (m (m a)) -> repr h (m a) Source #

bimap2 :: BiFunctor repr p => repr h (a -> b) -> repr h (c -> d) -> repr h (p a c -> p b d) Source #

flip1 :: DBI repr => repr h (a -> b -> c) -> repr h (b -> a -> c) Source #

flip2 :: DBI repr => repr h (a1 -> a -> c) -> repr h a -> repr h (a1 -> c) Source #

class DBI r => BiFunctor r p where Source #

Minimal complete definition

bimap

Methods

bimap :: r h ((a -> b) -> (c -> d) -> p a c -> p b d) Source #

Instances

DBI r => BiFunctor r (,) Source # 

Methods

bimap :: r h ((a -> b) -> (c -> d) -> (a, c) -> (b, d)) Source #

writer1 :: DBI repr => repr h (a, w) -> repr h (Writer w a) Source #

runWriter1 :: DBI repr => repr h (Writer w a) -> repr h (a, w) Source #

ioBind2 :: DBI repr => repr h (IO a) -> repr h (a -> IO b) -> repr h (IO b) Source #

app3 :: DBI repr => repr h (a2 -> a1 -> a -> b) -> repr h a2 -> repr h a1 -> repr h a -> repr h b Source #

optionMatch2 :: DBI repr => repr h a1 -> repr h (a -> a1) -> repr h (Maybe a -> a1) Source #

optionMatch3 :: DBI repr => repr h b -> repr h (a -> b) -> repr h (Maybe a) -> repr h b Source #

com2 :: DBI repr => repr h (b -> c) -> repr h (a -> b) -> repr h (a -> c) Source #

newtype Eval h x Source #

Constructors

Eval 

Fields

Instances

DBI Eval Source # 

Methods

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

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

lam :: Eval (a, h) b -> Eval h (a -> b) Source #

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

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

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

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

lit :: Double -> Eval h Double Source #

litZero :: Eval h Double Source #

litOne :: Eval h Double Source #

doublePlus :: Eval h (Double -> Double -> Double) Source #

doubleMinus :: Eval h (Double -> Double -> Double) Source #

doubleMult :: Eval h (Double -> Double -> Double) Source #

doubleDivide :: Eval h (Double -> Double -> Double) Source #

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

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

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

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

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

unit :: Eval h () Source #

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

nothing :: Eval h (Maybe a) Source #

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

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

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

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

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

nil :: Eval h [a] Source #

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

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

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

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

writer :: Eval h ((a, w) -> Writer w a) Source #

runWriter :: Eval h (Writer w a -> (a, w)) Source #

swap :: Eval h ((l, r) -> (r, l)) Source #

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

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

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

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

exp :: Eval h (Double -> Double) Source #

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

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

comb :: x -> Eval h x Source #

data AST Source #

Constructors

Leaf String 
App String AST [AST] 
Lam String [String] AST 

Instances

Show AST Source # 

Methods

showsPrec :: Int -> AST -> ShowS #

show :: AST -> String #

showList :: [AST] -> ShowS #

newtype Show h a Source #

Constructors

Show 

Fields

Instances

DBI (Show * *) Source # 

Methods

z :: Show * * (a, h) a Source #

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

lam :: Show * * (a, h) b -> Show * * h (a -> b) Source #

app :: Show * * h (a -> b) -> Show * * h a -> Show * * h b Source #

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

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

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

lit :: Double -> Show * * h Double Source #

litZero :: Show * * h Double Source #

litOne :: Show * * h Double Source #

doublePlus :: Show * * h (Double -> Double -> Double) Source #

doubleMinus :: Show * * h (Double -> Double -> Double) Source #

doubleMult :: Show * * h (Double -> Double -> Double) Source #

doubleDivide :: Show * * h (Double -> Double -> Double) Source #

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

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 #

unit :: Show * * h () Source #

exfalso :: Show * * h (Void -> a) Source #

nothing :: Show * * h (Maybe a) Source #

just :: Show * * h (a -> Maybe a) Source #

optionMatch :: Show * * h (b -> (a -> b) -> Maybe a -> b) 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 #

com :: Show * * h ((b -> c) -> (a -> b) -> a -> c) 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 #

swap :: Show * * h ((l, r) -> (r, l)) Source #

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

id :: Show * * h (a -> a) Source #

const :: Show * * h (a -> b -> a) Source #

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

exp :: Show * * h (Double -> Double) Source #

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

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

name :: String -> Show k k1 h a Source #

class NT repr l r where Source #

Minimal complete definition

conv

Methods

conv :: repr l t -> repr r t Source #

Instances

NT k k1 repr x x Source # 

Methods

conv :: x l t -> x r t Source #

(DBI repr, NT * * repr l r) => NT * * repr l (a, r) Source # 

Methods

conv :: (a, r) l t -> (a, r) r t Source #

hlam :: forall repr a b h. DBI repr => ((forall k. NT repr (a, h) k => repr k a) -> repr (a, h) b) -> repr h (a -> b) Source #

hlam2 :: forall repr a b c h. DBI repr => ((forall k. NT repr (a, h) k => repr k a) -> (forall k. NT repr (b, (a, h)) k => repr k b) -> repr (b, (a, h)) c) -> repr h (a -> b -> c) Source #

hlam3 :: (NT * * repr (a, (b1, (a1, h))) k, NT * * repr (b1, (a1, h)) k1, NT * * repr (a1, h) k2, DBI repr) => (repr k2 a1 -> repr k1 b1 -> repr k a -> repr (a, (b1, (a1, h))) b) -> repr h (a1 -> b1 -> a -> b) Source #

type family Diff v x Source #

Instances

type Diff v Void Source # 
type Diff v Void = Void
type Diff v () Source # 
type Diff v () = ()
type Diff v Double Source # 
type Diff v Double = (Double, v)
type Diff v [a] Source # 
type Diff v [a] = [Diff v a]
type Diff v (IO a) Source # 
type Diff v (IO a) = IO (Diff v a)
type Diff v (Maybe a) Source # 
type Diff v (Maybe a) = Maybe (Diff v a)
type Diff v (Writer w a) Source # 
type Diff v (Writer w a) = Writer (Diff v w) (Diff v a)
type Diff v (Either a b) Source # 
type Diff v (Either a b) = Either (Diff v a) (Diff v b)
type Diff v (a -> b) Source # 
type Diff v (a -> b) = Diff v a -> Diff v b
type Diff v (a, b) Source # 
type Diff v (a, b) = (Diff v a, Diff v b)

newtype WDiff repr v h x Source #

Constructors

WDiff 

Fields

Instances

(Vector repr v, DBI repr) => DBI (WDiff repr v) Source # 

Methods

z :: WDiff repr v (a, h) a Source #

s :: WDiff repr v h b -> WDiff repr v (a, h) b Source #

lam :: WDiff repr v (a, h) b -> WDiff repr v h (a -> b) Source #

app :: WDiff repr v h (a -> b) -> WDiff repr v h a -> WDiff repr v h b Source #

mkProd :: WDiff repr v h (a -> b -> (a, b)) Source #

zro :: WDiff repr v h ((a, b) -> a) Source #

fst :: WDiff repr v h ((a, b) -> b) Source #

lit :: Double -> WDiff repr v h Double Source #

litZero :: WDiff repr v h Double Source #

litOne :: WDiff repr v h Double Source #

doublePlus :: WDiff repr v h (Double -> Double -> Double) Source #

doubleMinus :: WDiff repr v h (Double -> Double -> Double) Source #

doubleMult :: WDiff repr v h (Double -> Double -> Double) Source #

doubleDivide :: WDiff repr v h (Double -> Double -> Double) Source #

hoas :: (WDiff repr v (a, h) a -> WDiff repr v (a, h) b) -> WDiff repr v h (a -> b) Source #

fix :: WDiff repr v h ((a -> a) -> a) Source #

left :: WDiff repr v h (a -> Either a b) Source #

right :: WDiff repr v h (b -> Either a b) Source #

sumMatch :: WDiff repr v h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: WDiff repr v h () Source #

exfalso :: WDiff repr v h (Void -> a) Source #

nothing :: WDiff repr v h (Maybe a) Source #

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

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

ioRet :: WDiff repr v h (a -> IO a) Source #

ioBind :: WDiff repr v h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: WDiff repr v h ((a -> b) -> IO a -> IO b) Source #

nil :: WDiff repr v h [a] Source #

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

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

com :: WDiff repr v h ((b -> c) -> (a -> b) -> a -> c) Source #

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

writer :: WDiff repr v h ((a, w) -> Writer w a) Source #

runWriter :: WDiff repr v h (Writer w a -> (a, w)) Source #

swap :: WDiff repr v h ((l, r) -> (r, l)) Source #

flip :: WDiff repr v h ((a -> b -> c) -> b -> a -> c) Source #

id :: WDiff repr v h (a -> a) Source #

const :: WDiff repr v h (a -> b -> a) Source #

scomb :: WDiff repr v h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

exp :: WDiff repr v h (Double -> Double) Source #

curry :: WDiff repr v h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: WDiff repr v h ((a -> b -> c) -> (a, b) -> c) Source #

app2 :: DBI repr => repr h (a1 -> a -> b) -> repr h a1 -> repr h a -> repr h b Source #

mkProd1 :: DBI repr => repr h a -> repr h (b -> (a, b)) Source #

mkProd2 :: DBI repr => repr h a1 -> repr h a -> repr h (a1, a) Source #

plus2 :: (Monoid * repr b, DBI repr) => repr h b -> repr h b -> repr h b Source #

zro1 :: DBI repr => repr h (b1, b) -> repr h b1 Source #

fst1 :: DBI repr => repr h (a, b) -> repr h b Source #

minus2 :: Group repr b => repr h b -> repr h b -> repr h b Source #

mult1 :: Vector repr v => repr h Double -> repr h (v -> v) Source #

mult2 :: Vector repr b => repr h Double -> repr h b -> repr h b Source #

divide2 :: Vector repr b => repr h b -> repr h Double -> repr h b Source #

invert1 :: Group repr b => repr h b -> repr h b Source #

exp1 :: DBI repr => repr h Double -> repr h Double Source #

noEnv :: repr () x -> repr () x Source #

selfWithDiff :: (DBI repr, Weight repr w) => repr h (w -> Diff w w) Source #

withDiff1 :: Weight repr w => repr h (w -> x) -> repr h (w -> Diff x w) Source #

class RandRange w where Source #

Minimal complete definition

randRange

Methods

randRange :: (Double, Double) -> (w, w) Source #

Instances

RandRange Double Source # 
RandRange () Source # 

Methods

randRange :: (Double, Double) -> ((), ()) Source #

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

Methods

randRange :: (Double, Double) -> ((l, r), (l, r)) Source #

class (Random w, RandRange w, Reify repr w, Show w, Vector repr w) => Weight repr w where Source #

Minimal complete definition

withDiff, fromDiff

Methods

withDiff :: repr h ((w -> x) -> w -> Diff x w) Source #

fromDiff :: Proxy x -> repr h (Diff x w -> w) Source #

Instances

DBI repr => Weight repr Double Source # 

Methods

withDiff :: repr h ((Double -> x) -> Double -> Diff x Double) Source #

fromDiff :: Proxy * x -> repr h (Diff x Double -> Double) Source #

DBI repr => Weight repr () Source # 

Methods

withDiff :: repr h ((() -> x) -> () -> Diff x ()) Source #

fromDiff :: Proxy * x -> repr h (Diff x () -> ()) Source #

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

Methods

withDiff :: repr h (((l, r) -> x) -> (l, r) -> Diff x (l, r)) Source #

fromDiff :: Proxy * x -> repr h (Diff x (l, r) -> (l, r)) Source #

data RunImpW repr h x Source #

Constructors

Weight repr w => RunImpW (repr h (w -> x)) 

data ImpW repr h x Source #

Constructors

NoImpW (repr h x) 
Weight repr w => ImpW (repr h (w -> x)) 

Instances

DBI repr => DBI (ImpW repr) Source # 

Methods

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

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

lam :: ImpW repr (a, h) b -> ImpW repr h (a -> b) Source #

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

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

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

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

lit :: Double -> ImpW repr h Double Source #

litZero :: ImpW repr h Double Source #

litOne :: ImpW repr h Double Source #

doublePlus :: ImpW repr h (Double -> Double -> Double) Source #

doubleMinus :: ImpW repr h (Double -> Double -> Double) Source #

doubleMult :: ImpW repr h (Double -> Double -> Double) Source #

doubleDivide :: ImpW repr h (Double -> Double -> Double) Source #

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

fix :: ImpW repr h ((a -> a) -> a) Source #

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

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

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

unit :: ImpW repr h () Source #

exfalso :: ImpW repr h (Void -> a) Source #

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

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

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

ioRet :: ImpW repr h (a -> IO a) Source #

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

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

nil :: ImpW repr h [a] Source #

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

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

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

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

writer :: ImpW repr h ((a, w) -> Writer w a) Source #

runWriter :: ImpW repr h (Writer w a -> (a, w)) Source #

swap :: ImpW repr h ((l, r) -> (r, l)) Source #

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

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

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

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

exp :: ImpW repr h (Double -> Double) Source #

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

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

runImpW :: forall repr h x. DBI repr => ImpW repr h x -> RunImpW repr h x Source #

data Term con h x Source #

Constructors

Term (forall r. con r => r h x) 

Instances

DBI (Term * * DBI) Source # 

Methods

z :: Term * * DBI (a, h) a Source #

s :: Term * * DBI h b -> Term * * DBI (a, h) b Source #

lam :: Term * * DBI (a, h) b -> Term * * DBI h (a -> b) Source #

app :: Term * * DBI h (a -> b) -> Term * * DBI h a -> Term * * DBI h b Source #

mkProd :: Term * * DBI h (a -> b -> (a, b)) Source #

zro :: Term * * DBI h ((a, b) -> a) Source #

fst :: Term * * DBI h ((a, b) -> b) Source #

lit :: Double -> Term * * DBI h Double Source #

litZero :: Term * * DBI h Double Source #

litOne :: Term * * DBI h Double Source #

doublePlus :: Term * * DBI h (Double -> Double -> Double) Source #

doubleMinus :: Term * * DBI h (Double -> Double -> Double) Source #

doubleMult :: Term * * DBI h (Double -> Double -> Double) Source #

doubleDivide :: Term * * DBI h (Double -> Double -> Double) Source #

hoas :: (Term * * DBI (a, h) a -> Term * * DBI (a, h) b) -> Term * * DBI h (a -> b) Source #

fix :: Term * * DBI h ((a -> a) -> a) Source #

left :: Term * * DBI h (a -> Either a b) Source #

right :: Term * * DBI h (b -> Either a b) Source #

sumMatch :: Term * * DBI h ((a -> c) -> (b -> c) -> Either a b -> c) Source #

unit :: Term * * DBI h () Source #

exfalso :: Term * * DBI h (Void -> a) Source #

nothing :: Term * * DBI h (Maybe a) Source #

just :: Term * * DBI h (a -> Maybe a) Source #

optionMatch :: Term * * DBI h (b -> (a -> b) -> Maybe a -> b) Source #

ioRet :: Term * * DBI h (a -> IO a) Source #

ioBind :: Term * * DBI h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: Term * * DBI h ((a -> b) -> IO a -> IO b) Source #

nil :: Term * * DBI h [a] Source #

cons :: Term * * DBI h (a -> [a] -> [a]) Source #

listMatch :: Term * * DBI h (b -> (a -> [a] -> b) -> [a] -> b) Source #

com :: Term * * DBI h ((b -> c) -> (a -> b) -> a -> c) Source #

listAppend :: Term * * DBI h ([a] -> [a] -> [a]) Source #

writer :: Term * * DBI h ((a, w) -> Writer w a) Source #

runWriter :: Term * * DBI h (Writer w a -> (a, w)) Source #

swap :: Term * * DBI h ((l, r) -> (r, l)) Source #

flip :: Term * * DBI h ((a -> b -> c) -> b -> a -> c) Source #

id :: Term * * DBI h (a -> a) Source #

const :: Term * * DBI h (a -> b -> a) Source #

scomb :: Term * * DBI h ((a -> b -> c) -> (a -> b) -> a -> c) Source #

exp :: Term * * DBI h (Double -> Double) Source #

curry :: Term * * DBI h (((a, b) -> c) -> a -> b -> c) Source #

uncurry :: Term * * DBI h ((a -> b -> c) -> (a, b) -> c) Source #

Orphan instances

Random () Source # 

Methods

randomR :: RandomGen g => ((), ()) -> g -> ((), g) #

random :: RandomGen g => g -> ((), g) #

randomRs :: RandomGen g => ((), ()) -> g -> [()] #

randoms :: RandomGen g => g -> [()] #

randomRIO :: ((), ()) -> IO () #

randomIO :: IO () #

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

Methods

randomR :: RandomGen g => ((l, r), (l, r)) -> g -> ((l, r), g) #

random :: RandomGen g => g -> ((l, r), g) #

randomRs :: RandomGen g => ((l, r), (l, r)) -> g -> [(l, r)] #

randoms :: RandomGen g => g -> [(l, r)] #

randomRIO :: ((l, r), (l, r)) -> IO (l, r) #

randomIO :: IO (l, r) #