Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Documentation
z, s, lam, app, mkProd, zro, fst, lit, plus, minus, mult, divide, fix, left, right, sumMatch, unit, exfalso, nothing, just, optionMatch, ioRet, ioBind, ioMap, nil, cons, listMatch, writer, runWriter
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 #
litZro :: repr h Double Source #
litOne :: repr h Double Source #
plus :: repr h (Double -> Double -> Double) Source #
minus :: repr h (Double -> Double -> Double) Source #
mult :: repr h (Double -> Double -> Double) Source #
divide :: 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 #
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 #
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 #
append :: 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 #
listMatch2 :: DBI repr => repr h a1 -> repr h (a -> [a] -> a1) -> repr h ([a] -> a1) Source #
class Functor r a => Applicative r a where Source #
return :: Applicative r a => r h (x -> a x) Source #
class Applicative r m => Monad r m where Source #
bimap2 :: BiFunctor repr p => repr h (a -> b) -> repr h (c -> d) -> repr h (p a c -> p b d) Source #
runWriter1 :: DBI repr => repr h (Writer w a) -> repr h (a, w) Source #
app3 :: DBI repr => repr h (a2 -> a1 -> a -> b) -> repr h a2 -> repr h a1 -> repr h a -> repr h b Source #
optionMatch3 :: DBI repr => repr h b -> repr h (a -> b) -> repr h (Maybe a) -> repr h b Source #
optionMatch2 :: DBI repr => repr h a1 -> repr h (a -> a1) -> repr h (Maybe a -> a1) 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 #