[Haskell-cafe] Monoid wants a (++) equivalent

Edward Kmett ekmett at gmail.com
Thu Jul 2 14:11:16 EDT 2009


 Wed, Jul 1, 2009 at 4:17 PM, Raynor Vliegendhart <shinnonoir at gmail.com>wrote:

> We could use (Control.Category..) as an operator, but this would
> require an additional wrapping layer if we wish to use the existing
> Monoid instances:
>
> > import Prelude hiding (id, (.))
> > import Control.Category
> > import Data.Monoid
> >
> > -- Category wrapper for existing Monoid instances
> > newtype MonoidC m a b = MonoidC {unwrapMC :: m} deriving (Show)
> >
> > instance Monoid m => Category (MonoidC m) where
> >     id = MonoidC mempty
> >     MonoidC m . MonoidC n = MonoidC $ m `mappend` n
>
> Furthermore, writing Category instances for monoids require dummy type
> parameters:
>
> > -- Example instance
> > newtype SumC m a b = SumC {getSumC :: m} deriving (Show, Eq)
> >
> > instance Num a => Category (SumC a) where
> >     id = SumC (fromIntegral 0)
> >     SumC x . SumC y = SumC $ x + y
>
I have a monoid-as-category and category-endomorphism as monoid in:
http://comonad.com/haskell/monoids/dist/doc/html/monoids/Data-Monoid-Categorical.html

but there are issues.

1.)  these completely change the typing involved
2.) the monoid as category-with-one-object is pretty scary to someone
without a category theory background.
3.) This doesn't properly represent the category-with-one-object because at
best the two phantom types yield you something like a category like Hask,
which has been fully connected * M where M is the category of your monoid.
Even if you use GADTs to cut down the phantom types to one where the head
and tail of the arrow are the same object and |.| takes a category to its
discrete category (discarding all non-identity arrows) you are looking at a
category like |Hask| * M because of the phantom type.

data CMonoid m n o where
    M :: Monoid m => m -> CMonoid m a a

instance Monoid m => Category (CMonoid m) where
    id = M mempty
    M a . M b = M (a `mappend` b)

 Attempting to go any further and railroad that type to equal m fails when
you go to define id. So the categorical notion of a monoid is pretty much a
non-starter in Haskell.

 -Edward Kmett

On
Another disadvantage of this approach is that we cannot have a default
monoid instance for lists (kind mismatch).
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090702/530f47f5/attachment-0001.html


More information about the Haskell-Cafe mailing list