George Russel wrote:
[snip]
> I presume it would not in fact be difficult to synthesise a left identity at
> the cost of making things slower, thus (forgive any syntax errors, I'm not going to
> test this).
>
> data MonadIO a = Action (IO a) | Return a
> instance Monad (MonadIO a) where
> return a = Return a
> (>>=) (Return a) k = k a
> (>>=) (Action act) f =
> Action (act >>= (\ a -> case f a of {Return a -> return a;Action act -> act}))
Or, more general:
data MonadWrap m a = M (m a) | R a
instance Monad m => Monad (MonadWrap m) where
return = R
R x >>= f = f x
M x >>= f = M (x >>= \a->case f a of
R b -> return b
M c -> c)
I don't think this really solves the problem with the left unit
(not in general, and not for IO either),
it merely pushes it to a different place.
I think you need the left-unit law for monad m
to prove the 'associativity' law for monad (MonadWrap m)
The 'associativity' law:
m >>= (\x -> k x >>= h) = (m >>= k) >>= h
The case in which the situation occurs is m=(M x) with (k x)=(R b).
Stefan Kahrs
_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell