
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

On Tue, Feb 22, 2011 at 2:03 PM, 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)
These are isomorphic to: foo :: a -> MaybeT m a And so on (from the MaybeT package on hackage). So to compose these three, lift them into MaybeT and then use Kleisli composition: MaybeT . foo >=> MaybeT . bar >=> MaybeT . baz Luke
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Feb 22, 2011 at 3:03 PM, 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?.
The MaybeT monad transformer should work pretty well for this. I would use a custom lifting operator:
liftMaybe :: m (Maybe a) -> MaybeT m a liftMaybe = MaybeT
and then:
resultMaybe <- runMaybeT $ do b <- liftMaybe $ foo a c <- liftMaybe $ bar b liftMaybe $ baz c
Here, 'resultMaybe' will be of type 'Maybe d'. Antoine
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

You need the MaybeT and EitherT monad transformers:
http://hackage.haskell.org/packages/archive/MaybeT/0.1.2/doc/html/Control-Mo...
http://hackage.haskell.org/packages/archive/MaybeT/0.1.2/doc/html/Control-Mo...
http://hackage.haskell.org/packages/archive/EitherT/0.0.1/doc/html/Control-M...
http://hackage.haskell.org/packages/archive/EitherT/0.0.1/doc/html/Control-M...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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

From: Alberto G. Corona
Sent: Tue, February 22, 2011 3:03:56 PM 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. ... 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?.
Control.Monad.Trans.Maybe.MaybeT from mtl is defined as newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) } with (among others), instance Monad m => Monad (MaybeT m)
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)
The standard construction uses a distributive law - if you have an operation distribute :: n (m a) -> m (n a), then you can make m around n into a monad by m (n (m (n a))) == by fmap distribute => m (m (n (n a))) == by join (for m) => m (n (n a)) == by fmap join (n's join) => m (n a) Here, that's a function Maybe (m a) -> m (Maybe a), which can be distribute (Just ma) = fmap Just ma distribute Nothing = return Nothing Brandon

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)

I have a function 'justm' for this specific case: -- | This is sort of like a monad transformer, but the Maybe is on the inside -- instead of the outside. -- -- What I really want here is MaybeT, but it requres explicit lifting... justm :: (Monad m) => m (Maybe a) -> (a -> m (Maybe b)) -> m (Maybe b) justm op1 op2 = maybe (return Nothing) op2 =<< op1 Used like: lookup_selnum :: (Cmd.M m) => Types.SelNum -> m (Maybe (ViewId, Types.Selection)) lookup_selnum selnum = justm Cmd.lookup_focused_view $ \view_id -> justm (State.get_selection view_id selnum) $ \sel -> return $ Just (view_id, sel) As implied by the comment, I wanted to use MaybeT but thought all the explicit lifting and wrapping in runMaybeT was too complicated. However losing 'do' notation is not that great either, so maybe I should give it another go.
participants (7)
-
Alberto G. Corona
-
Antoine Latter
-
Brandon Moore
-
Evan Laforge
-
Holger Siegel
-
Job Vranish
-
Luke Palmer