DeepDarkFantasy-0.2017.4.1: A DSL for creating neural network.

Safe HaskellSafe
LanguageHaskell2010

DDF.Lang

Contents

Documentation

class Bool repr => Lang repr where Source #

Methods

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

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

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

double :: Double -> repr h Double Source #

doubleZero :: repr h Double Source #

doubleOne :: 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 #

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

float :: Float -> repr h Float Source #

floatZero :: repr h Float Source #

floatOne :: repr h Float Source #

floatPlus :: repr h (Float -> Float -> Float) Source #

floatMinus :: repr h (Float -> Float -> Float) Source #

floatMult :: repr h (Float -> Float -> Float) Source #

floatDivide :: repr h (Float -> Float -> Float) Source #

floatExp :: repr h (Float -> Float) 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 #

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 #

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

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

float2Double :: repr h (Float -> Double) Source #

double2Float :: repr h (Double -> Float) Source #

undefined :: repr h a Source #

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

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

Instances

Lang Eval Source # 

Methods

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

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

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

double :: Double -> Eval h Double Source #

doubleZero :: Eval h Double Source #

doubleOne :: 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 #

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

float :: Float -> Eval h Float Source #

floatZero :: Eval h Float Source #

floatOne :: Eval h Float Source #

floatPlus :: Eval h (Float -> Float -> Float) Source #

floatMinus :: Eval h (Float -> Float -> Float) Source #

floatMult :: Eval h (Float -> Float -> Float) Source #

floatDivide :: Eval h (Float -> Float -> Float) Source #

floatExp :: Eval h (Float -> Float) 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 #

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 #

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

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

float2Double :: Eval h (Float -> Double) Source #

double2Float :: Eval h (Double -> Float) Source #

undefined :: Eval h a Source #

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

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

Lang Show Source # 

Methods

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

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

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

double :: Double -> Show h Double Source #

doubleZero :: Show h Double Source #

doubleOne :: 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 #

doubleExp :: Show h (Double -> Double) Source #

float :: Float -> Show h Float Source #

floatZero :: Show h Float Source #

floatOne :: Show h Float Source #

floatPlus :: Show h (Float -> Float -> Float) Source #

floatMinus :: Show h (Float -> Float -> Float) Source #

floatMult :: Show h (Float -> Float -> Float) Source #

floatDivide :: Show h (Float -> Float -> Float) Source #

floatExp :: Show h (Float -> Float) 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 #

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 #

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

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

float2Double :: Show h (Float -> Double) Source #

double2Float :: Show h (Double -> Float) Source #

undefined :: Show h a Source #

state :: Show h ((l -> (r, l)) -> State l r) Source #

runState :: Show h (State l r -> l -> (r, l)) Source #

Lang repr => Lang (GWDiff repr) Source # 

Methods

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

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

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

double :: Double -> GWDiff repr h Double Source #

doubleZero :: GWDiff repr h Double Source #

doubleOne :: GWDiff repr h Double Source #

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

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

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

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

doubleExp :: GWDiff repr h (Double -> Double) Source #

float :: Float -> GWDiff repr h Float Source #

floatZero :: GWDiff repr h Float Source #

floatOne :: GWDiff repr h Float Source #

floatPlus :: GWDiff repr h (Float -> Float -> Float) Source #

floatMinus :: GWDiff repr h (Float -> Float -> Float) Source #

floatMult :: GWDiff repr h (Float -> Float -> Float) Source #

floatDivide :: GWDiff repr h (Float -> Float -> Float) Source #

floatExp :: GWDiff repr h (Float -> Float) Source #

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

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

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

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

unit :: GWDiff repr h () Source #

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

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

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

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

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

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

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

nil :: GWDiff repr h [a] Source #

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

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

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

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

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

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

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

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

float2Double :: GWDiff repr h (Float -> Double) Source #

double2Float :: GWDiff repr h (Double -> Float) Source #

undefined :: GWDiff repr h a Source #

state :: GWDiff repr h ((l -> (r, l)) -> State l r) Source #

runState :: GWDiff repr h (State l r -> l -> (r, l)) Source #

Lang repr => Lang (UnHOAS repr) Source # 

Methods

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

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

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

double :: Double -> UnHOAS repr h Double Source #

doubleZero :: UnHOAS repr h Double Source #

doubleOne :: UnHOAS repr h Double Source #

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

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

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

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

doubleExp :: UnHOAS repr h (Double -> Double) Source #

float :: Float -> UnHOAS repr h Float Source #

floatZero :: UnHOAS repr h Float Source #

floatOne :: UnHOAS repr h Float Source #

floatPlus :: UnHOAS repr h (Float -> Float -> Float) Source #

floatMinus :: UnHOAS repr h (Float -> Float -> Float) Source #

floatMult :: UnHOAS repr h (Float -> Float -> Float) Source #

floatDivide :: UnHOAS repr h (Float -> Float -> Float) Source #

floatExp :: UnHOAS repr h (Float -> Float) Source #

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

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

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

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

unit :: UnHOAS repr h () Source #

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

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

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

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

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

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

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

nil :: UnHOAS repr h [a] Source #

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

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

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

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

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

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

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

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

float2Double :: UnHOAS repr h (Float -> Double) Source #

double2Float :: UnHOAS repr h (Double -> Float) Source #

undefined :: UnHOAS repr h a Source #

state :: UnHOAS repr h ((l -> (r, l)) -> State l r) Source #

runState :: UnHOAS repr h (State l r -> l -> (r, l)) Source #

Lang repr => Lang (ImpW * repr) Source # 

Methods

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 #

double :: Double -> ImpW * repr h Double Source #

doubleZero :: ImpW * repr h Double Source #

doubleOne :: 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 #

doubleExp :: ImpW * repr h (Double -> Double) Source #

float :: Float -> ImpW * repr h Float Source #

floatZero :: ImpW * repr h Float Source #

floatOne :: ImpW * repr h Float Source #

floatPlus :: ImpW * repr h (Float -> Float -> Float) Source #

floatMinus :: ImpW * repr h (Float -> Float -> Float) Source #

floatMult :: ImpW * repr h (Float -> Float -> Float) Source #

floatDivide :: ImpW * repr h (Float -> Float -> Float) Source #

floatExp :: ImpW * repr h (Float -> Float) 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 #

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 #

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

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

float2Double :: ImpW * repr h (Float -> Double) Source #

double2Float :: ImpW * repr h (Double -> Float) Source #

undefined :: ImpW * repr h a Source #

state :: ImpW * repr h ((l -> (r, l)) -> State l r) Source #

runState :: ImpW * repr h (State l r -> l -> (r, l)) Source #

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

Methods

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 #

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

doubleZero :: WDiff repr v h Double Source #

doubleOne :: 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 #

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

float :: Float -> WDiff repr v h Float Source #

floatZero :: WDiff repr v h Float Source #

floatOne :: WDiff repr v h Float Source #

floatPlus :: WDiff repr v h (Float -> Float -> Float) Source #

floatMinus :: WDiff repr v h (Float -> Float -> Float) Source #

floatMult :: WDiff repr v h (Float -> Float -> Float) Source #

floatDivide :: WDiff repr v h (Float -> Float -> Float) Source #

floatExp :: WDiff repr v h (Float -> Float) 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 #

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 #

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

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

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

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

undefined :: WDiff repr v h a Source #

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

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

(Lang l, Lang r) => Lang (Combine l r) Source # 

Methods

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

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

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

double :: Double -> Combine l r h Double Source #

doubleZero :: Combine l r h Double Source #

doubleOne :: Combine l r h Double Source #

doublePlus :: Combine l r h (Double -> Double -> Double) Source #

doubleMinus :: Combine l r h (Double -> Double -> Double) Source #

doubleMult :: Combine l r h (Double -> Double -> Double) Source #

doubleDivide :: Combine l r h (Double -> Double -> Double) Source #

doubleExp :: Combine l r h (Double -> Double) Source #

float :: Float -> Combine l r h Float Source #

floatZero :: Combine l r h Float Source #

floatOne :: Combine l r h Float Source #

floatPlus :: Combine l r h (Float -> Float -> Float) Source #

floatMinus :: Combine l r h (Float -> Float -> Float) Source #

floatMult :: Combine l r h (Float -> Float -> Float) Source #

floatDivide :: Combine l r h (Float -> Float -> Float) Source #

floatExp :: Combine l r h (Float -> Float) Source #

fix :: Combine l r h ((a -> a) -> a) Source #

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

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

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

unit :: Combine l r h () Source #

exfalso :: Combine l r h (Void -> a) Source #

nothing :: Combine l r h (Maybe a) Source #

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

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

ioRet :: Combine l r h (a -> IO a) Source #

ioBind :: Combine l r h (IO a -> (a -> IO b) -> IO b) Source #

ioMap :: Combine l r h ((a -> b) -> IO a -> IO b) Source #

nil :: Combine l r h [a] Source #

cons :: Combine l r h (a -> [a] -> [a]) Source #

listMatch :: Combine l r h (b -> (a -> [a] -> b) -> [a] -> b) Source #

listAppend :: Combine l r h ([a] -> [a] -> [a]) Source #

writer :: Combine l r h ((a, w) -> Writer w a) Source #

runWriter :: Combine l r h (Writer w a -> (a, w)) Source #

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

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

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

float2Double :: Combine l r h (Float -> Double) Source #

double2Float :: Combine l r h (Double -> Float) Source #

undefined :: Combine l r h a Source #

state :: Combine l r h ((l -> (r, l)) -> State l r) Source #

runState :: Combine l r h (State l r -> l -> (r, l)) Source #

class Reify repr x where Source #

Minimal complete definition

reify

Methods

reify :: x -> repr h x Source #

Instances

Lang repr => Reify * repr Double Source # 

Methods

reify :: x -> Double h x Source #

Lang repr => Reify * repr () Source # 

Methods

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

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

Methods

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

Lang repr => ProdCon (Reify * repr) l r Source # 

Methods

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

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

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

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

Instances

Lang r => Group r Float Source # 

Methods

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

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

Lang r => Group r Double Source # 

Methods

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

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

Lang r => Group r () Source # 

Methods

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

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

(Lang repr, Group repr v) => Group repr (Double -> v) Source # 

Methods

invert :: repr h ((Double -> v) -> Double -> v) Source #

minus :: repr h ((Double -> v) -> (Double -> v) -> Double -> v) Source #

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

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 #

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

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

Instances

Lang r => Vector r Float Source # 

Methods

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

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

Lang r => Vector r Double Source # 

Methods

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

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

Lang r => Vector r () Source # 

Methods

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

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

(Lang repr, Vector repr v) => Vector repr (Double -> v) Source # 

Methods

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

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

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

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

Methods

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

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

cons2 :: Lang repr => repr h a1 -> repr h [a1] -> repr h [a1] Source #

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

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

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

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

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

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

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

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

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

mult2 :: (Vector repr b, DBI repr) => repr h Double -> repr h b -> repr h b Source #

divide2 :: (Vector repr b, DBI repr) => repr h b -> repr h Double -> repr h b Source #

invert1 :: (Group repr b, DBI repr) => repr h b -> repr h b Source #

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

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

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

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

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

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

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

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

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

minus2 :: (Group repr b, DBI repr) => repr h b -> repr h b -> repr h b Source #

float2Double1 :: Lang repr => repr h Float -> repr h Double Source #

doubleExp1 :: Lang repr => repr h Double -> repr h Double Source #

floatExp1 :: Lang repr => repr h Float -> repr h Float Source #

sumMatch2 :: Lang repr => repr h (a -> c) -> repr h (b -> c) -> repr h (Either a b -> c) Source #

state1 :: Lang repr => repr h (l -> (r, l)) -> repr h (State l r) Source #

runState1 :: Lang repr => repr h (State l r) -> repr h (l -> (r, l)) Source #

runState2 :: Lang repr => repr h (State a r) -> repr h a -> repr h (r, a) Source #

module DDF.Bool

Orphan instances

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

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

Lang repr => ConvDiff repr Float Source # 

Methods

toDiff :: Monoid * repr x => Proxy * x -> repr h (Float -> Diff x Float) Source #

toDiffBy :: repr h (x -> Float -> Diff x Float) Source #

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

fromDiffBy :: repr h (x -> Diff x Float -> Float) Source #

Lang repr => ConvDiff repr Double Source # 

Methods

toDiff :: Monoid * repr x => Proxy * x -> repr h (Double -> Diff x Double) Source #

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

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

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

Lang repr => ConvDiff repr () Source # 

Methods

toDiff :: Monoid * repr x => Proxy * x -> repr h (() -> Diff x ()) Source #

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

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

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

Lang r => BiFunctor * r (,) Source # 

Methods

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

Lang r => BiFunctor * r Either Source # 

Methods

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

Lang r => Applicative * r Maybe Source # 

Methods

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

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

Lang r => Applicative * r IO Source # 

Methods

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

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

Lang r => Functor * r Maybe Source # 

Methods

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

Lang r => Functor * r IO Source # 

Methods

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

Lang r => Functor * r [] Source # 

Methods

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

Lang repr => WithDiff * repr Float Source # 

Methods

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

Lang repr => WithDiff * repr Double Source # 

Methods

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

Lang repr => WithDiff * repr () Source # 

Methods

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

Lang r => Monoid * r Float Source # 

Methods

zero :: Float h m Source #

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

Lang r => Monoid * r Double Source # 

Methods

zero :: Double h m Source #

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

Lang r => Monoid * r () Source # 

Methods

zero :: () h m Source #

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

Lang r => Applicative * r (State l) Source # 

Methods

pure :: State l h (x -> a x) Source #

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

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

Lang r => Functor * r (State l) Source # 

Methods

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

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

Methods

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

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

Methods

zero :: [a] h m Source #

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

(Lang repr, WithDiff * repr l, WithDiff * repr r) => WithDiff * repr (l, r) Source # 

Methods

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

(Lang repr, Monoid * repr v) => Monoid * repr (Double -> v) Source # 

Methods

zero :: (Double -> v) h m Source #

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

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

Lang r => Monad r (State l) Source # 

Methods

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

join :: r h (State l (State l a) -> State l a) Source #

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

(Lang repr, ConvDiff repr l) => ConvDiff repr [l] Source # 

Methods

toDiff :: Monoid * repr x => Proxy * x -> repr h ([l] -> Diff x [l]) Source #

toDiffBy :: repr h (x -> [l] -> Diff x [l]) Source #

fromDiff :: Monoid * repr x => Proxy * x -> repr h (Diff x [l] -> [l]) Source #

fromDiffBy :: repr h (x -> Diff x [l] -> [l]) Source #

(Lang repr, ConvDiff repr l, ConvDiff repr r) => ConvDiff repr (l -> r) Source # 

Methods

toDiff :: Monoid * repr x => Proxy * x -> repr h ((l -> r) -> Diff x (l -> r)) Source #

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

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

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

(Lang repr, ConvDiff repr l, ConvDiff repr r) => ConvDiff repr (Either l r) Source # 

Methods

toDiff :: Monoid * repr x => Proxy * x -> repr h (Either l r -> Diff x (Either l r)) Source #

toDiffBy :: repr h (x -> Either l r -> Diff x (Either l r)) Source #

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

fromDiffBy :: repr h (x -> Diff x (Either l r) -> Either l r) Source #

(Lang repr, ConvDiff repr l, ConvDiff repr r) => ConvDiff repr (l, r) Source # 

Methods

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

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

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

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

Lang repr => DBI (ImpW * repr) Source # 

Methods

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

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

abs :: 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 #

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

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

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

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

Lang r => Bool (ImpW * r) Source # 

Methods

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

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

(Bool r, Vector r v) => Bool (WDiff r v) Source # 

Methods

bool :: Bool -> WDiff r v h Bool Source #

ite :: WDiff r v h (a -> a -> Bool -> a) 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 #