[Haskell-cafe] Adding Ord constraint to instance Monad Set?
Tomasz Zielonka
t.zielonka at students.mimuw.edu.pl
Wed Mar 31 09:32:39 EST 2004
On Wed, Mar 31, 2004 at 08:48:35AM +0200, Wolfgang Jeltsch wrote:
> > Now, as i think a little more about it, i believe what you want to do makes
> > no sense. The monad operation '>>=' works on monads over *different*
> > 'element' (i.e. argument) types (look at the type of '>>='). Your
> > implementation only works if argument types are the same. I can't see how
> > this can be generalized to different argument types even if both are
> > instances of class Ord.
>
> I disagree. AFAICS, his implementation also works with different element
> types. Am I overlooking something?
I think the real issue is that you can't restrict the types on which
monad operates without modifying the Monad class.
Think about this code:
f :: Monad m => a -> m a
f x = do
return id
return putStrLn
return x
It shouldn't be used in a Set monad, because it internally operates on
uncomparable values, but the type signature doesn't reflect this fact.
You can try to define a different version of Monad using multiparameter
type classes, something like:
class M m a b where
(>>>=) :: m a -> (a -> m b) -> m b
...
but it would complicate type signature contexts a lot, for example you
would have
(\a b c d -> a >>>= b >>>= c >>>= d)
:: forall m a b b1 b2.
(M m b1 b2, M m b b1, M m a b) =>
m a -> (a -> m b) -> (b -> m b1) -> (b1 -> m b2) -> m b2
instead of
(\a b c d -> a >>= b >>= c >>= d)
:: forall m a b b1 b2.
(Monad m) =>
m a -> (a -> m b) -> (b -> m b1) -> (b1 -> m b2) -> m b2
Best regards,
Tom
--
.signature: Too many levels of symbolic links
More information about the Haskell-Cafe
mailing list