{-# LANGUAGE GADTs, FlexibleInstances, MultiParamTypeClasses #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Monoid.Categorical -- Copyright : (c) Edward Kmett 2009 -- License : BSD-style -- Maintainer : libraries@haskell.org -- Stability : experimental -- Portability : portable -- ----------------------------------------------------------------------------- module Data.Monoid.Categorical ( module Data.Monoid.Reducer , module Control.Category -- * Generalized Endo , GEndo(GEndo, getGEndo) -- * Monoids as Categories , Mon(Mon) , getMon ) where import Prelude hiding ((.),id) import Data.Monoid.Reducer import Control.Category -- | The 'Monoid' of the endomorphisms over some object in an arbitrary 'Category'. data GEndo k a = GEndo { getGEndo :: k a a } instance Category k => Monoid (GEndo k a) where mempty = GEndo id GEndo f `mappend` GEndo g = GEndo (f . g) -- | A 'Monoid' is just a 'Category' with one object. data Mon m n o where Mon :: Monoid m => m -> Mon m a a -- | Extract the 'Monoid' from its representation as a 'Category' getMon :: Mon m m m -> m getMon (Mon m) = m instance Monoid m => Category (Mon m) where id = Mon mempty Mon a . Mon b = Mon (a `mappend` b) instance Monoid m => Monoid (Mon m m m) where mempty = id mappend = (.) instance (c `Reducer` m) => Reducer c (Mon m m m) where unit = Mon . unit