[Haskell-cafe] The container problem

David Menendez dave at zednenem.com
Sun Sep 28 20:59:53 EDT 2008


On Sat, Sep 27, 2008 at 9:24 AM, Andrew Coppin
<andrewcoppin at btinternet.com> wrote:
> David Menendez wrote:
>>
>> I wouldn't say that. It's important to remember that Haskell class
>> Monad does not, and can not, represent *all* monads, only (strong)
>> monads built on a functor from the category of Haskell types and
>> functions to itself.
>>
>> Data.Set is a functor from the category of Haskell types *with
>> decidable ordering* and *order-preserving* functions to itself. That's
>> not the same category, although it is closely related.
>>
>
> I nominate this post for the September 2008 Most Incomprehensible Cafe Post
> award! :-D
>
> Seriously, that sounded like gibberish. (But then, you're talking to
> somebody who can't figure out the difference between a set and a class,
> so...)

Sorry about that. I was rushing out the door at the time.

> All I know is that sometimes I write stuff in the list monad when the result
> really ought to be *sets*, not lists, because
>
> 1. there is no senamically important ordering
>
> 2. there should be no duplicates
>
> But Haskell's type system forbids me. (It also forbids me from making Set
> into a Functor, actually... so no fmap for you!)

I understand your frustration. The point that I was trying to make is
that this isn't just some arbitrary limitation in Haskell's type
system. Data.Set and [] can both be thought of as monads, but they
aren't the same kind of monad.

====

Incidentally, there are other ways to simulate a set monad. Depending
on your usage pattern, you may find this implementation preferable to
using the list monad:

> {-# LANGUAGE PolymorphicComponents #-}
>
> import Control.Monad
> import qualified Data.Set as Set
> type Set = Set.Set
>
> newtype SetM a = SetM { unSetM :: forall b. (Ord b) => (a -> Set b) -> Set b }
>
> toSet :: (Ord a) => SetM a -> Set a
> toSet m = unSetM m Set.singleton
>
> fromSet :: (Ord a) => Set a -> SetM a
> fromSet s = SetM (\k -> Set.unions (map k (Set.toList s)))
>
> instance Monad SetM where
> 	return a = SetM (\k -> k a)
> 	m >>= f  = SetM (\k -> unSetM m (\a -> unSetM (f a) k))
> 	
> instance MonadPlus SetM where
> 	mzero = SetM (\_ -> Set.empty)
> 	mplus m1 m2 = SetM (\k -> Set.union (unSetM m1 k) (unSetM m2 k))

It will still duplicate work. For example, if you write,

    return x `mplus` return x >>= f

then "f x" will get evaluated twice. You can minimize that by
inserting "fromSet . toSet" in strategic places.

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list