
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

On 9 January 2011 07:28, Peter Padawitz
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.
See Ganesh Sittampalam's rmonad [1] package. [1]: http://hackage.haskell.org/package/rmonad -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Hello Peter, This is a classic problem with the normal monad type class. You can achieve this with "restricted monads", but there is a bit of tomfoolery you have to do to get do-notation support for them. Here is some relevant reading: - http://okmij.org/ftp/Haskell/types.html#restricted-datatypes - http://hackage.haskell.org/package/rmonad-0.4.1 Cheers, Edward

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

On Sat, Jan 8, 2011 at 4:53 PM, Lennart Augustsson
It so happens that you can make a set data type that is a Monad, but it's not exactly the best possible sets.
There's also the infinite search monad, which allows you to search
infinite sets in finite time, provided your queries meet some
termination criteria.
http://math.andrej.com/2008/11/21/a-haskell-monad-for-infinite-search-in-fin...
http://hackage.haskell.org/package/infinite-search
--
Dave Menendez

On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson
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/

On Sun, Jan 9, 2011 at 7:45 AM, Sebastian Fischer
[...] Only conversion to the underlying Set type requires an Ord constraint. getSet :: Ord a => Set a -> S.Set a getSet a = a >>- S.singleton
this unfortunately also means that duplicated elements only get filtered out at the points where you use getSet, so in "getSet ((return 1 `mplus` return 1) >>= k)" k gets still called twice

That looks like it looses the efficiency of the underlying representation.
On Sun, Jan 9, 2011 at 6:45 AM, Sebastian Fischer
On Sun, Jan 9, 2011 at 6:53 AM, Lennart Augustsson
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

On Sun, Jan 9, 2011 at 10:11 PM, Lennart Augustsson
That looks like it looses the efficiency of the underlying representation.
Yes, I don't think one can retain that cleanly without using restricted monads to exclude things like liftM ($42) (mplus (return pred) (return succ)) or just liftM ($42) (return pred) Maybe one can hack something to achieve mplus :: Ord a => Set a -> Set a -> Set a mplus a b = Set (\k -> S.union (a >>- ret) (b >>- ret) `bind` k) where ret = S.singleton bind = flip Data.Foldable.foldMap mplus :: not (Ord a) => Set a -> Set a -> Set a mplus a b = Set (\k -> S.union (a >>- k) (b >>- k)) using overloading with undecidable instances (?) (and defining a Monoid instance for the Set monad in terms of the MonadPlus instance) Reminds me of instance chains.. [1] Sebastian [1]: http://portal.acm.org/citation.cfm?id=1863596
participants (7)
-
Andrea Vezzosi
-
David Menendez
-
Edward Z. Yang
-
Ivan Lazar Miljenovic
-
Lennart Augustsson
-
Peter Padawitz
-
Sebastian Fischer