Monad instance for Data.Set, again

The blog article http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros describes a variant of the Monad class which allows to restrict the type of the monadic result, in order to be able to make Data.Set an instance of Monad (requiring Ord constraint for the monadic result). The same problem arises for container data structures with restricted element types, where the element type restriction depends on the implementation of the container structure (such as UArray). It would be cumbersome to have several class parts, even more, type constraints in type signatures may reveal implementation details. E.g. constraint (Container c x y z) might be needed for a 'zipWith' function, whereas (Container c y x z) is needed if you use 'zipWith' with swapped arguments. Here is another approach that looks tempting, but unfortunately does not work, and I wonder whether this can be made working. module RestrictedMonad where import Data.Set(Set) import qualified Data.Set as Set class AssociatedMonad m a where class RestrictedMonad m where return :: AssociatedMonad m a => a -> m a (>>=) :: (AssociatedMonad m a, AssociatedMonad m b) => m a -> (a -> m b) -> m b instance (Ord a) => AssociatedMonad Set a where instance RestrictedMonad Set where return = Set.singleton x >>= f = Set.unions (map f (Set.toList x)) GHC says: RestrictedMonad.hs:21:13: Could not deduce (Ord b) from the context (RestrictedMonad Set, AssociatedMonad Set a, AssociatedMonad Set b) arising from use of `Data.Set.unions' at RestrictedMonad.hs:21:13-22 Probable fix: add (Ord b) to the class or instance method `RestrictedMonad.>>=' In the definition of `>>=': >>= x f = Data.Set.unions (map f (Data.Set.toList x)) In the definition for method `RestrictedMonad.>>=' In the instance declaration for `RestrictedMonad Set'

Am Montag, 24. März 2008 20:47 schrieb Henning Thielemann:
[…]
Here is another approach that looks tempting, but unfortunately does not work, and I wonder whether this can be made working.
module RestrictedMonad where
import Data.Set(Set) import qualified Data.Set as Set
class AssociatedMonad m a where
class RestrictedMonad m where return :: AssociatedMonad m a => a -> m a (>>=) :: (AssociatedMonad m a, AssociatedMonad m b) => m a -> (a -> m b) -> m b
instance (Ord a) => AssociatedMonad Set a where
instance RestrictedMonad Set where return = Set.singleton x >>= f = Set.unions (map f (Set.toList x))
[…]
The problem is that while an expression of type (AssociatedMonad Set a, AssociatedMonad Set b) => Set a -> (a -> Set b) -> Set b has type (Ord a, Ord b) => Set a -> (a -> Set b) -> Set b, the opposite doesn’t hold. Your AssociatedMonad class doesn’t provide you any Ord dictionary which you need in order to use the Set functions. The instance declaration instance (Ord a) => AssociatedMonad Set a says how to construct an AssociatedMonad dictionary from an Ord dictionary but not the other way round. But it is possible to give a construction of an Ord dictionary from an AssociatedMonad dictionary. See the attached code. It works like a charm. :-) Best wishes, Wolfgang {-# LANGUAGE ExistentialQuantification, MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-} import Data.Set (Set) import qualified Data.Set as Set class Suitable monad val where data Constraints monad val :: * constraints :: monad val -> Constraints monad val class NewMonad monad where newReturn :: (Suitable monad val) => val -> monad val newBind :: (Suitable monad val, Suitable monad val') => monad val -> (val -> monad val') -> monad val' instance (Ord val) => Suitable Set val where data Constraints Set val = Ord val => SetConstraints constraints _ = SetConstraints instance NewMonad Set where newReturn = Set.singleton newBind set1 set2Gen = let set2Constraints = constraints result result = case set2Constraints of SetConstraints -> Set.unions $ map set2Gen $ Set.toList set1 in result

On Fri, 28 Mar 2008, Wolfgang Jeltsch wrote:
But it is possible to give a construction of an Ord dictionary from an AssociatedMonad dictionary. See the attached code. It works like a charm. :-)
Yeah, type families! In which GHC release they will be included? Sometimes I wonder how many single type extensions we will see in future or whether there will be one mechanism which subsumes all existing ones in a simple manner. (Full logic programming on type level? Manual determination of the class dictionary to be used?)

On Fri, 28 Mar 2008, Wolfgang Jeltsch wrote:
But it is possible to give a construction of an Ord dictionary from an AssociatedMonad dictionary. See the attached code. It works like a charm. :-)
This is really cool, and with much wider applicability than restricted monads; it gives us a general way to abstract over type class constraints. The NewMonad class is also very straightforward and I think will cause much fewer type-checking headaches and large type signatures than Oleg's solution. Ganesh

I'm having trouble embedding unconstrained monads into the NewMonad:
{-# LANGUAGE ...,UndecidableInstances #-}
instance Monad m => Suitable m v where data Constraints m v = NoConstraints constraints _ = NoConstraints
instance Monad m => NewMonad m where newReturn = return newBind x k = let list2Constraints = constraints result result = case list2Constraints of NoConstraints -> (x >>= k) in result
SetMonad.hs:25:9: Conflicting family instance declarations: data instance Constraints Set val -- Defined at SetMonad.hs:25:9-19 data instance Constraints m v -- Defined at SetMonad.hs:47:9-19 Since Set is not an instance of Monad, there is no actual overlap between (Monad m => m) and Set, but it seems that Haskell has no way of knowing that. Is there some trick (e.g. newtype boxing/unboxing) to get all the unconstrained monads automatically instanced? Then the do notation could be presumably remapped to the new class structure. Dan Wolfgang Jeltsch wrote:
Am Montag, 24. März 2008 20:47 schrieb Henning Thielemann:
[…]
Here is another approach that looks tempting, but unfortunately does not work, and I wonder whether this can be made working.
module RestrictedMonad where
import Data.Set(Set) import qualified Data.Set as Set
class AssociatedMonad m a where
class RestrictedMonad m where return :: AssociatedMonad m a => a -> m a (>>=) :: (AssociatedMonad m a, AssociatedMonad m b) => m a -> (a -> m b) -> m b
instance (Ord a) => AssociatedMonad Set a where
instance RestrictedMonad Set where return = Set.singleton x >>= f = Set.unions (map f (Set.toList x))
[…]
The problem is that while an expression of type
(AssociatedMonad Set a, AssociatedMonad Set b) => Set a -> (a -> Set b) -> Set b
has type
(Ord a, Ord b) => Set a -> (a -> Set b) -> Set b,
the opposite doesn’t hold.
Your AssociatedMonad class doesn’t provide you any Ord dictionary which you need in order to use the Set functions. The instance declaration
instance (Ord a) => AssociatedMonad Set a
says how to construct an AssociatedMonad dictionary from an Ord dictionary but not the other way round.
But it is possible to give a construction of an Ord dictionary from an AssociatedMonad dictionary. See the attached code. It works like a charm. :-)
Best wishes, Wolfgang
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 3/28/08, Dan Weston
I'm having trouble embedding unconstrained monads into the NewMonad:
Is there some trick (e.g. newtype boxing/unboxing) to get all the unconstrained monads automatically instanced? Then the do notation could be presumably remapped to the new class structure.
The usual trick here is to use newtypes. (Yes, it sucks)
newtype OldMonad m = OldMonad m unwrapMonad :: OldMonad m -> m unwrapMonad (OldMonad m) = m
instance Monad m => Suitable (OldMonad m) v where data Constraints (OldMonad m) v = NoConstraints constraints _ = NoConstraints instance Monad m => NewMonad (OldMonad m) where newReturn = OldMonad . return newBind x k = OldMonad $ unwrapMonad x >>= unwrapMonad . k
participants (5)
-
Dan Weston
-
Ganesh Sittampalam
-
Henning Thielemann
-
Ryan Ingram
-
Wolfgang Jeltsch