[Haskell-cafe] monadic plumbing

Holger Siegel holgersiegel74 at yahoo.de
Tue Feb 22 22:31:12 CET 2011


Am 22.02.2011 um 22:03 schrieb Alberto G. Corona:

> 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?.


import Control.Monad.Trans.Maybe

fooBarBaz = runMaybeT (MaybeT . foo >=> MaybeT . bar >=> MaybeT . baz)

(untested)


> 
> 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


Ignoring the newtype wrappers, this is the same as the actual monad instance of MaybeT:

newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) }

instance (Monad m) => Monad (MaybeT m) where
    fail _ = MaybeT (return Nothing)
    return = lift . return
    x >>= f = MaybeT $ do
        v <- runMaybeT x
        case v of
            Nothing -> return Nothing
            Just y  -> runMaybeT (f y)




More information about the Haskell-Cafe mailing list