minimal complete definition (Data.Monoid)

Marc A. Ziegert coeus at gmx.de
Tue Oct 18 11:43:55 EDT 2005


i've just played a bit with monoids, especially with Ross Paterson's nice version of "class (Monoid b)=>Monoid(a->b)" mapped to Arrows, and Implicit Parameters (i tried to simulate dynamic instances).
for me, i came to the conclusion, that it is easier and nicer to generalise some functions, to be able to set the used monoid-functions via parameter. (not implicit parameter!)

minimizing the overhead, i read this in the libraries:

[docu]
class Monoid a where
The monoid class. A minimal complete definition must supply mempty and mappend, and these should satisfy the monoid laws.
[/docu]

is that really the only minimal complete definition, that is implemented?
how about mconcat?

[code]
mempty = mconcat []
mappend a b = mconcat [a,b]
[/code]

the mconcat may be not optimised, if there are only the "minimal complete definition" mempty and mappend; so, it is good, that mconcat is one of the class-functions...
but writing only the optimized mconcat is a "minimal complete definition", too.


by the way: instead of Ross Paterson's "Data.Monoid"(Date: 2005-09-13 15:52:31 GMT), i would prefer another class:

[code]
import Prelude hiding (sequence)
import qualified Control.Monad
import Control.Arrow

class Sequence m where
  sequence :: [m a] -> m [a]

instance Monad m => Sequence m where
  sequence = Control.Monad.sequence

instance (Arrow f) => Sequence (f a) where
  sequence []     = pure (const [])
  sequence [f]    = f >>> pure (:[])
  sequence (f:fr) = (f &&& sequence fr) >>> pure (uncurry (:))

--Ross Paterson's Monoid:
rp_concat :: (Monoid b) => [a->b] -> a->b
rp_concat = mconcat . sequence

rp_concat' :: (Arrow f,Monoid b) => [f a b] -> f a b
rp_concat' fs = sequence fs >>> pure mconcat
[/code]




More information about the Libraries mailing list