On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson
<lenn...@augustsson.net>wrote:

> It so happens that you can make a set data type that is a Monad, but it's
> not exactly the best possible sets.
>
> module SetMonad where
>
> newtype Set a = Set { unSet :: [a] }
>

Here is a version that also does not require restricted monads but works
with an arbitrary underlying Set data type (e.g. from Data.Set). It uses
continuations with a Rank2Type.

    import qualified Data.Set as S

    newtype Set a = Set { (>>-) :: forall b . Ord b => (a -> S.Set b) ->
S.Set b }

    instance Monad Set where
      return x = Set ($x)
      a >>= f  = Set (\k -> a >>- \x -> f x >>- k)

Only conversion to the underlying Set type requires an Ord constraint.

    getSet :: Ord a => Set a -> S.Set a
    getSet a = a >>- S.singleton

A `MonadPlus` instance can lift `empty` and `union`.

    instance MonadPlus Set where
      mzero     = Set (const S.empty)
      mplus a b = Set (\k -> S.union (a >>- k) (b >>- k))

Maybe, Heinrich Apfelmus's operational package [1] can be used to do the
same without continuations.

[1]: http://projects.haskell.org/operational/
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to