
This is a recurring problem[1] and I'm still looking for a really satisfying solution. The only working and non-verbose solution I found is the one Miguel suggests. Although I'm not too fond of splitting up the monadic functions into separate type classes. A similar solution is described elsewhere[2]. It also desribes how you can use Template Haskell to regain the power of the do-notation with your own restricted monad type class. Kind regards, Thomas [1] http://www.nabble.com/Monad-instance-for-Data.Set%2C-again-td16259448.html [2] http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros Miguel Mitrofanov wrote:
{-# LANGUAGE MultiParamTypeClasses #-} class Returnable m a where ret :: a -> m a class Bindable m a b where bind :: m a -> (a -> m b) -> m b newtype MOAMonad r m a = MOAMonad ((a -> m r) -> m r) instance Monad (MOAMonad r m) where return x = MOAMonad $ ($ x) MOAMonad h >>= f = MOAMonad $ \p -> h $ \x -> let MOAMonad h' = f x in h' p fromMOAMonad :: Returnable m r => MOAMonad r m r -> m r fromMOAMonad (MOAMonad h) = h ret toMOAMonad :: Bindable m a r => m a -> MOAMonad r m a toMOAMonad mx = MOAMonad $ \p -> bind mx p class FMappable f a b where fmp :: (a -> b) -> f a -> f b newtype MOAFunctor r f a = MOAFunctor ((a -> r) -> f r) instance Functor (MOAFunctor r f) where fmap f (MOAFunctor h) = MOAFunctor $ \p -> h $ p . f fromMOAFunctor :: MOAFunctor r f r -> f r fromMOAFunctor (MOAFunctor h) = h id toMOAFunctor :: FMappable f a r => f a -> MOAFunctor r f a toMOAFunctor fx = MOAFunctor $ \p -> fmp p fx
-- MOA stands for "Mother Of All"
On 26 Apr 2009, at 15:21, Neil Brown wrote:
Hi,
I have a Haskell problem that keeps cropping up and I wondered if there was any solution/work-around/dirty-hack that could help. I keep wanting to define class instances for things like Functor or Monad, but with restrictions on the inner type. I'll explain with an example, because I find explaining this in words a bit difficult. Let's say I want to create a Monad instance for Set akin to that for lists:
== import Data.Set import Prelude hiding (map)
instance Monad Set where return = singleton m >>= f = fold union empty (map f m)
-- Error: Could not deduce (Ord a, Ord b) from the context (Monad Set) ==
Everything fits (I think) -- except the type-class constraints. Obviously my Monad instance won't work if you have things inside the set that aren't Ord, but I can't work out how to define a restricted instance that only exists for types that have Ord instances. I can't express the constraint on the instance because the a and b types of return and >>= aren't visible in the class header. Shifting the constraint to be present in the type doesn't seem to help either (e.g. newtype Ord a => MySet a = MySet (Set a)...).
Is there any way to get such instances as the one for Set working? I cannot carry around a compare function myself in a data type that wraps Set, because return cannot create such functions without the original type-class instance. I don't actually need a Monad for Set, but it neatly demonstrates my problem of wanting constraints on the type inside a Monad (or a Functor, or an Applicative, etc).
I worked around a similar problem with Functor by opting for a new Functor-like type-class with the constraints, but doing that with Monad rules out using all the monad helper functions (liftM, mapM, etc), and the do notation, which would be a step too far. All suggestions are welcome, no matter how hacky, or how many GHC extensions are required :-) (provided they don't break all the other monads, e.g. redefining the signature of Monad).
Thanks,
Neil. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe