ghc-internal-9.1001.0: Basic libraries
Copyright(c) Ashley Yakeley 2007
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerashley@semantic.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.Internal.Control.Category

Description

 
Synopsis
  • class Category (cat :: k -> k -> Type) where
    • id :: forall (a :: k). cat a a
    • (.) :: forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c
  • (<<<) :: forall {k} cat (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c
  • (>>>) :: forall {k} cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c

Documentation

class Category (cat :: k -> k -> Type) where Source #

A class for categories. Instances should satisfy the laws

Right identity
f . id = f
Left identity
id . f = f
Associativity
f . (g . h) = (f . g) . h

Methods

id :: forall (a :: k). cat a a Source #

the identity morphism

(.) :: forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c infixr 9 Source #

morphism composition

Instances

Instances details
Monad m => Category (Kleisli m :: Type -> Type -> Type) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Arrow

Methods

id :: Kleisli m a a Source #

(.) :: Kleisli m b c -> Kleisli m a b -> Kleisli m a c Source #

Category (Coercion :: k -> k -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: forall (a :: k). Coercion a a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). Coercion b c -> Coercion a b -> Coercion a c Source #

Category ((:~:) :: k -> k -> Type) Source #

@since base-4.7.0.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: forall (a :: k). a :~: a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). (b :~: c) -> (a :~: b) -> a :~: c Source #

Category (->) Source #

@since base-3.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: a -> a Source #

(.) :: (b -> c) -> (a -> b) -> a -> c Source #

Category ((:~~:) :: k -> k -> Type) Source #

@since base-4.10.0.0

Instance details

Defined in GHC.Internal.Control.Category

Methods

id :: forall (a :: k). a :~~: a Source #

(.) :: forall (b :: k) (c :: k) (a :: k). (b :~~: c) -> (a :~~: b) -> a :~~: c Source #

(<<<) :: forall {k} cat (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c infixr 1 Source #

Right-to-left composition

(>>>) :: forall {k} cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c infixr 1 Source #

Left-to-right composition