License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This is an attempt at the Kleisli category, and the construction of an adjunction for each monad.
Documentation
newtype KleisliFree m Source #
KleisliFree (Monad m) |
Instances
(Functor m, Dom m ~ k, Cod m ~ k) => Functor (KleisliFree m) Source # | |
Defined in Data.Category.Kleisli type Dom (KleisliFree m) :: Type -> Type -> Type Source # type Cod (KleisliFree m) :: Type -> Type -> Type Source # type (KleisliFree m) :% a :: Type Source # (%) :: KleisliFree m -> Dom (KleisliFree m) a b -> Cod (KleisliFree m) (KleisliFree m :% a) (KleisliFree m :% b) Source # | |
type Dom (KleisliFree m) Source # | |
Defined in Data.Category.Kleisli | |
type Cod (KleisliFree m) Source # | |
Defined in Data.Category.Kleisli | |
type (KleisliFree m) :% a Source # | |
Defined in Data.Category.Kleisli |
data KleisliForget m Source #
Instances
(Functor m, Dom m ~ k, Cod m ~ k) => Functor (KleisliForget m) Source # | |
Defined in Data.Category.Kleisli type Dom (KleisliForget m) :: Type -> Type -> Type Source # type Cod (KleisliForget m) :: Type -> Type -> Type Source # type (KleisliForget m) :% a :: Type Source # (%) :: KleisliForget m -> Dom (KleisliForget m) a b -> Cod (KleisliForget m) (KleisliForget m :% a) (KleisliForget m :% b) Source # | |
type Dom (KleisliForget m) Source # | |
Defined in Data.Category.Kleisli | |
type Cod (KleisliForget m) Source # | |
Defined in Data.Category.Kleisli | |
type (KleisliForget m) :% a Source # | |
Defined in Data.Category.Kleisli |
kleisliAdj :: (Functor m, Dom m ~ k, Cod m ~ k) => Monad m -> Adjunction (Kleisli m) k (KleisliFree m) (KleisliForget m) Source #