----------------------------------------------------------------------------- -- | -- Module : Control.Category -- Copyright : (c) Ashley Yakeley 2007 -- License : BSD-style (see the LICENSE file in the distribution) -- -- Maintainer : ashley@semantic.org -- Stability : experimental -- Portability : portable -- http://hackage.haskell.org/trac/ghc/ticket/1773 module Control.Category where import Prelude hiding (id,(.)) import qualified Prelude infixr 9 . infixr 1 >>>, <<< -- | A class for categories. -- id and (.) must form a monoid. class Category cat where -- | the identity morphism id :: cat a a -- | morphism composition (.) :: cat b c -> cat a b -> cat a c {-# RULES "identity/left" forall p . id . p = p "identity/right" forall p . p . id = p "association" forall p q r . (p . q) . r = p . (q . r) #-} instance Category (->) where id = Prelude.id #ifndef __HADDOCK__ -- Haddock 1.x cannot parse this: (.) = (Prelude..) #endif -- | Right-to-left composition (<<<) :: Category cat => cat b c -> cat a b -> cat a c (<<<) = (.) -- | Left-to-right composition (>>>) :: Category cat => cat a b -> cat b c -> cat a c f >>> g = g . f