{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
module Control.Category where
import qualified GHC.Base (id,(.))
import Data.Type.Coercion
import Data.Type.Equality
import GHC.Prim (coerce)
infixr 9 .
infixr 1 >>>, <<<
class Category cat where
    
    id :: cat a a
    
    (.) :: 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 = GHC.Base.id
    (.) = (GHC.Base..)
instance Category (:~:) where
  id          = Refl
  Refl . Refl = Refl
instance Category Coercion where
  id = Coercion
  (.) Coercion = coerce
(<<<) :: Category cat => cat b c -> cat a b -> cat a c
(<<<) = (.)
(>>>) :: Category cat => cat a b -> cat b c -> cat a c
f >>> g = g . f