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] }

singleton :: a -> Set a
singleton x = Set [x]

unions :: [Set a] -> Set a
unions ss = Set $ concatMap unSet ss

member :: (Eq a) => a -> Set a -> Bool
member x s = x `elem` unSet s

instance Monad Set where
    return = singleton
    x >>= f = unions (map f (unSet x))


On Sat, Jan 8, 2011 at 9:28 PM, Peter Padawitz <peter.padawitz@udo.edu> wrote:
Hi,

is there any way to instantiate m in Monad m with a set datatype in order to implement the usual powerset monad?

My straightforward attempt failed because the bind operator of this instance requires the Eq constraint on the argument types of m.

Peter



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe