[Haskell-cafe] monadic plumbing
Job Vranish
job.vranish at gmail.com
Tue Feb 22 22:22:32 CET 2011
You need the MaybeT and EitherT monad transformers:
http://hackage.haskell.org/packages/archive/MaybeT/0.1.2/doc/html/Control-Monad-Maybe.html
<http://hackage.haskell.org/packages/archive/MaybeT/0.1.2/doc/html/Control-Monad-Maybe.html>
http://hackage.haskell.org/packages/archive/EitherT/0.0.1/doc/html/Control-Monad-Either.html
<http://hackage.haskell.org/packages/archive/EitherT/0.0.1/doc/html/Control-Monad-Either.html>With
MaybeT, you can wrap foo, bar, and baz with a MaybeT constructor, which
gives you a new monad that you can compose the usual way.
For example:
result <- runMaybeT (MaybeT foo >>= MaybeT bar >>= MaybeT baz)
case result of
Just x -> ...
Nothing -> ...
- Job
On Tue, Feb 22, 2011 at 4:03 PM, Alberto G. Corona <agocorona at gmail.com>wrote:
> Recently I had to navigatate trough data structures chained with mutable
> referenes in th STM monad. The problem is that their values are enveloped in
> Either or Maybe results.
>
> functional compositions in the Either of Maybe , or list monads are not
> possible when the values are embedded inside effect monads (i.e. STM or IO)
> . I tried to find some trick to handle it.
>
> to summarize, given:
>
> foo, : a -> m (Maybe b)
> bar : b -> m (Maybe c)
> baz : c -> m (Maybe d)
>
> how to compose foo bar and baz? Or, at least, Are something out there to
> handle it in the less painful way?.
>
>
> I solved the generalized problem (chaining any double monadic
> combination) with a sort of monadic connector that acts as a " double
> monadic" operator >>>>== so that
>
> return. return (x :: a) >>>>== foo >>>== bar >>>== baz
>
> can be possible. Although I don't know if it is the best solution. I
> wonder why nobody has written about it before:
>
> class (Monad m, Monad n) => Bimonad m n where
> (>>>=) :: n a -> (a -> m(n b)) -> m(n b)
>
> (>>>>==) :: (Bimonad m n) => m (n a) -> (a -> m(n b)) -> m (n b)
> (>>>>==) x f = x >>= \y -> y >>>= f
>
> x >>>> f = x >>>>== \ _-> f
>
> infixl 1 >>>>==, >>>>
>
> The instance for handling the Maybe monad under any other monad is very
> similar to the definition of the "normal" monad:
>
> instance (Monad m) => Bimonad m Maybe where
> Just x >>>= f = f x
> Nothing >>>= _ = return $ Nothing
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110222/0a1b4f44/attachment.htm>
More information about the Haskell-Cafe
mailing list