| License | BSD-style (see the file LICENSE) |
|---|---|
| Maintainer | sjoerd@w3future.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Category.Unit
Description
Documentation
Instances
| Category Unit Source # |
|
| CartesianClosed Unit Source # | |
Defined in Data.Category.CartesianClosed Associated Types type Exponential Unit y z :: Kind k Source # Methods apply :: forall (y :: k) (z :: k). Obj Unit y -> Obj Unit z -> Unit (BinaryProduct Unit (Exponential Unit y z) y) z Source # tuple :: forall (y :: k) (z :: k). Obj Unit y -> Obj Unit z -> Unit z (Exponential Unit y (BinaryProduct Unit z y)) Source # (^^^) :: forall (z1 :: k) (z2 :: k) (y2 :: k) (y1 :: k). Unit z1 z2 -> Unit y2 y1 -> Unit (Exponential Unit y1 z1) (Exponential Unit y2 z2) Source # | |
| HasBinaryCoproducts Unit Source # | In the category of one object that object is its own coproduct. |
Defined in Data.Category.Limit Associated Types type BinaryCoproduct Unit x y :: Kind k Source # Methods inj1 :: forall (x :: k) (y :: k). Obj Unit x -> Obj Unit y -> Unit x (BinaryCoproduct Unit x y) Source # inj2 :: forall (x :: k) (y :: k). Obj Unit x -> Obj Unit y -> Unit y (BinaryCoproduct Unit x y) Source # (|||) :: forall (x :: k) (a :: k) (y :: k). Unit x a -> Unit y a -> Unit (BinaryCoproduct Unit x y) a Source # (+++) :: forall (a1 :: k) (b1 :: k) (a2 :: k) (b2 :: k). Unit a1 b1 -> Unit a2 b2 -> Unit (BinaryCoproduct Unit a1 a2) (BinaryCoproduct Unit b1 b2) Source # | |
| HasBinaryProducts Unit Source # | In the category of one object that object is its own product. |
Defined in Data.Category.Limit Associated Types type BinaryProduct Unit x y :: Kind k Source # Methods proj1 :: forall (x :: k) (y :: k). Obj Unit x -> Obj Unit y -> Unit (BinaryProduct Unit x y) x Source # proj2 :: forall (x :: k) (y :: k). Obj Unit x -> Obj Unit y -> Unit (BinaryProduct Unit x y) y Source # (&&&) :: forall (a :: k) (x :: k) (y :: k). Unit a x -> Unit a y -> Unit a (BinaryProduct Unit x y) Source # (***) :: forall (a1 :: k) (b1 :: k) (a2 :: k) (b2 :: k). Unit a1 b1 -> Unit a2 b2 -> Unit (BinaryProduct Unit a1 a2) (BinaryProduct Unit b1 b2) Source # | |
| Category k => HasColimits Unit k Source # | The colimit of a single object is that object. |
Defined in Data.Category.Limit Associated Types type ColimitFam Unit k f Source # | |
| HasInitialObject Unit Source # | The category of one object has that object as initial object. |
Defined in Data.Category.Limit Associated Types type InitialObject Unit :: Kind k Source # Methods initialObject :: Obj Unit (InitialObject Unit) Source # initialize :: forall (a :: k). Obj Unit a -> Unit (InitialObject Unit) a Source # | |
| Category k => HasLimits Unit k Source # | The limit of a single object is that object. |
| HasTerminalObject Unit Source # | The category of one object has that object as terminal object. |
Defined in Data.Category.Limit Associated Types type TerminalObject Unit :: Kind k Source # Methods terminalObject :: Obj Unit (TerminalObject Unit) Source # terminate :: forall (a :: k). Obj Unit a -> Unit a (TerminalObject Unit) Source # | |
| HasColimits j k => HasLeftKan (Const j Unit ()) k Source # | The left Kan extension of |
Defined in Data.Category.KanExtension Methods lan :: Const j Unit () -> Obj (Nat (Dom (Const j Unit ())) k) f -> Nat (Dom (Const j Unit ())) k f (LanFam (Const j Unit ()) k f :.: Const j Unit ()) Source # lanFactorizer :: Nat (Dom (Const j Unit ())) k f (h :.: Const j Unit ()) -> Nat (Cod (Const j Unit ())) k (LanFam (Const j Unit ()) k f) h Source # | |
| HasLimits j k => HasRightKan (Const j Unit ()) k Source # | The right Kan extension of |
Defined in Data.Category.KanExtension Methods ran :: Const j Unit () -> Obj (Nat (Dom (Const j Unit ())) k) f -> Nat (Dom (Const j Unit ())) k (RanFam (Const j Unit ()) k f :.: Const j Unit ()) f Source # ranFactorizer :: Nat (Dom (Const j Unit ())) k (h :.: Const j Unit ()) f -> Nat (Cod (Const j Unit ())) k h (RanFam (Const j Unit ()) k f) Source # | |
| type InitialObject Unit Source # | |
Defined in Data.Category.Limit | |
| type TerminalObject Unit Source # | |
Defined in Data.Category.Limit | |
| type ColimitFam Unit k f Source # | |
Defined in Data.Category.Limit | |
| type LimitFam Unit k f Source # | |
Defined in Data.Category.Limit | |
| type Exponential Unit () () Source # | |
Defined in Data.Category.CartesianClosed | |
| type BinaryCoproduct Unit () () Source # | |
Defined in Data.Category.Limit | |
| type BinaryProduct Unit () () Source # | |
Defined in Data.Category.Limit | |
| type LanFam (Const j Unit ()) k f Source # | |
Defined in Data.Category.KanExtension | |
| type RanFam (Const j Unit ()) k f Source # | |