Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | sjoerd@w3future.com |
Documentation
type family Exponential (~>) y z :: *Source
class (HasTerminalObject ~>, HasBinaryProducts ~>) => CartesianClosed (~>) whereSource
apply :: Obj ~> y -> Obj ~> z -> BinaryProduct ~> (Exponential ~> y z) y ~> zSource
tuple :: Obj ~> y -> Obj ~> z -> z ~> Exponential ~> y (BinaryProduct ~> z y)Source
(^^^) :: (z1 ~> z2) -> (y2 ~> y1) -> Exponential ~> y1 z1 ~> Exponential ~> y2 z2Source
data ProductWith (~>) y Source
ProductWith (Obj ~> y) |
HasBinaryProducts ~> => Functor (ProductWith ~> y) |
data ExponentialWith (~>) y Source
ExponentialWith (Obj ~> y) |
CartesianClosed ~> => Functor (ExponentialWith ~> y) |
curryAdj :: CartesianClosed ~> => Obj ~> y -> Adjunction ~> ~> (ProductWith ~> y) (ExponentialWith ~> y)Source
curry :: CartesianClosed ~> => Obj ~> x -> Obj ~> y -> Obj ~> z -> ((ProductWith ~> y :% x) ~> z) -> x ~> (ExponentialWith ~> y :% z)Source
uncurry :: CartesianClosed ~> => Obj ~> x -> Obj ~> y -> Obj ~> z -> (x ~> (ExponentialWith ~> y :% z)) -> (ProductWith ~> y :% x) ~> zSource
type State (~>) s a = ExponentialWith ~> s :% (ProductWith ~> s :% a)Source
stateMonadReturn :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> a ~> State ~> s aSource
stateMonadJoin :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> State ~> s (State ~> s a) ~> State ~> s aSource
type Context (~>) s a = ProductWith ~> s :% (ExponentialWith ~> s :% a)Source
contextComonadExtract :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> Context ~> s a ~> aSource
contextComonadDuplicate :: CartesianClosed ~> => Obj ~> s -> Obj ~> a -> Context ~> s a ~> Context ~> s (Context ~> s a)Source