License | BSD-style (see the file LICENSE) |
---|---|
Maintainer | sjoerd@w3future.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
2 a.k.a. the Boolean category a.k.a. the walking arrow. It contains 2 objects, one for false and one for true. It contains 3 arrows, 2 identity arrows and one from false to true.
Synopsis
- data Fls
- data Tru
- data Boolean a b where
- trueProductMonoid :: MonoidObject (ProductFunctor Boolean) Tru
- falseCoproductComonoid :: ComonoidObject (CoproductFunctor Boolean) Fls
- trueProductComonoid :: ComonoidObject (ProductFunctor Boolean) Tru
- falseCoproductMonoid :: MonoidObject (CoproductFunctor Boolean) Fls
- trueCoproductMonoid :: MonoidObject (CoproductFunctor Boolean) Tru
- falseProductComonoid :: ComonoidObject (ProductFunctor Boolean) Fls
- data Arrow k a b = Arrow (k a b)
- type SrcFunctor = LimitFunctor Boolean
- type TgtFunctor = ColimitFunctor Boolean
- data Terminator (k :: * -> * -> *) = Terminator
- terminatorLimitAdj :: HasTerminalObject k => Adjunction k (Nat Boolean k) (SrcFunctor k) (Terminator k)
- data Initializer (k :: * -> * -> *) = Initializer
- initializerColimitAdj :: HasInitialObject k => Adjunction (Nat Boolean k) k (Initializer k) (TgtFunctor k)
Documentation
Instances
type BinaryCoproduct Boolean Tru Fls Source # | |
Defined in Data.Category.Boolean | |
type BinaryCoproduct Boolean Fls Tru Source # | |
Defined in Data.Category.Boolean | |
type BinaryCoproduct Boolean Fls Fls Source # | |
Defined in Data.Category.Boolean | |
type BinaryProduct Boolean Tru Fls Source # | |
Defined in Data.Category.Boolean | |
type BinaryProduct Boolean Fls Tru Source # | |
Defined in Data.Category.Boolean | |
type BinaryProduct Boolean Fls Fls Source # | |
Defined in Data.Category.Boolean | |
type Exponential Boolean Tru Fls Source # | |
Defined in Data.Category.Boolean | |
type Exponential Boolean Fls Tru Source # | |
Defined in Data.Category.Boolean | |
type Exponential Boolean Fls Fls Source # | |
Defined in Data.Category.Boolean | |
type (Arrow k a b) :% Fls Source # | |
Defined in Data.Category.Boolean |
Instances
type BinaryCoproduct Boolean Tru Tru Source # | |
Defined in Data.Category.Boolean | |
type BinaryCoproduct Boolean Tru Fls Source # | |
Defined in Data.Category.Boolean | |
type BinaryCoproduct Boolean Fls Tru Source # | |
Defined in Data.Category.Boolean | |
type BinaryProduct Boolean Tru Tru Source # | |
Defined in Data.Category.Boolean | |
type BinaryProduct Boolean Tru Fls Source # | |
Defined in Data.Category.Boolean | |
type BinaryProduct Boolean Fls Tru Source # | |
Defined in Data.Category.Boolean | |
type Exponential Boolean Tru Tru Source # | |
Defined in Data.Category.Boolean | |
type Exponential Boolean Tru Fls Source # | |
Defined in Data.Category.Boolean | |
type Exponential Boolean Fls Tru Source # | |
Defined in Data.Category.Boolean | |
type (Arrow k a b) :% Tru Source # | |
Defined in Data.Category.Boolean |
data Boolean a b where Source #
Instances
Arrow (k a b) |
Instances
Category k => Functor (Arrow k a b) Source # | Any functor from the Boolean category points to an arrow in its target category. |
type Dom (Arrow k a b) Source # | |
Defined in Data.Category.Boolean | |
type Cod (Arrow k a b) Source # | |
Defined in Data.Category.Boolean | |
type (Arrow k a b) :% Fls Source # | |
Defined in Data.Category.Boolean | |
type (Arrow k a b) :% Tru Source # | |
Defined in Data.Category.Boolean |
type SrcFunctor = LimitFunctor Boolean Source #
The source functor sends arrows (as functors from the Boolean category) to their source.
type TgtFunctor = ColimitFunctor Boolean Source #
The target functor sends arrows (as functors from the Boolean category) to their target.
data Terminator (k :: * -> * -> *) Source #
Instances
HasTerminalObject k => Functor (Terminator k) Source # |
|
Defined in Data.Category.Boolean type Dom (Terminator k) :: Type -> Type -> Type Source # type Cod (Terminator k) :: Type -> Type -> Type Source # type (Terminator k) :% a :: Type Source # (%) :: Terminator k -> Dom (Terminator k) a b -> Cod (Terminator k) (Terminator k :% a) (Terminator k :% b) Source # | |
type Dom (Terminator k) Source # | |
Defined in Data.Category.Boolean | |
type Cod (Terminator k) Source # | |
Defined in Data.Category.Boolean | |
type (Terminator k) :% a Source # | |
Defined in Data.Category.Boolean |
terminatorLimitAdj :: HasTerminalObject k => Adjunction k (Nat Boolean k) (SrcFunctor k) (Terminator k) Source #
Terminator
is right adjoint to the source functor.
data Initializer (k :: * -> * -> *) Source #
Instances
HasInitialObject k => Functor (Initializer k) Source # |
|
Defined in Data.Category.Boolean type Dom (Initializer k) :: Type -> Type -> Type Source # type Cod (Initializer k) :: Type -> Type -> Type Source # type (Initializer k) :% a :: Type Source # (%) :: Initializer k -> Dom (Initializer k) a b -> Cod (Initializer k) (Initializer k :% a) (Initializer k :% b) Source # | |
type Dom (Initializer k) Source # | |
Defined in Data.Category.Boolean | |
type Cod (Initializer k) Source # | |
Defined in Data.Category.Boolean | |
type (Initializer k) :% a Source # | |
Defined in Data.Category.Boolean |
initializerColimitAdj :: HasInitialObject k => Adjunction (Nat Boolean k) k (Initializer k) (TgtFunctor k) Source #
Initializer
is left adjoint to the target functor.