[Haskell-cafe] Question on a common pattern

Ertugrul Soeylemez es at ertes.de
Tue Mar 15 16:21:37 CET 2011


Hello tsuraan,

Most often, when we multi-pattern-match on the return value of a monadic
computation, we talk about Maybe or Either or [], and I often find
myself doing this:

    someIO1 :: IO (Maybe A)
    someIO2 :: IO (Either A B)

    result1 <- someIO1 >>= maybe ...
    result2 <- someIO2 >>= either ...

There are many ways of encoding this more nicely.  My personal way is to
use the proper monad transformers for the purpose.  For many of these
situations I have written convenient combinators in the 'contstuff'
package.  I found especially the 'liftF' function very useful in these
cases:

    liftF :: (LiftFunctor t, Monad m) => m (InnerFunctor t a) -> t m a

Example instances:

    liftF :: Monad m => m [a] -> ChoiceT r i m a
    liftF :: Monad m => m (Either e a) -> EitherT r e m a
    liftF :: Monad m => m (Maybe a) -> MaybeT r m a

That way instead of checking each return value individually you would
just write:

    result <- evalMaybeT $ do
        x <- liftF someMaybeIO
        y <- liftF (someOtherMaybeIO x x)
        return (Result x y)


Greets,
Ertugrul


tsuraan <tsuraan at gmail.com> wrote:

> In my code, I'm doing this quite a lot:
> 
> x <- someIO
> case x of
>   Opt1 -> ...
> 
> Having a line for extracting the value from the IO (or STM) and then
> acting on the value seems unnatural.  Is there a more concise way to
> do this?  This code:
> 
> case someIO of
>   Opt1 -> ...
> 
> Doesn't work, but is there something like that, that is valid?



-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/





More information about the Haskell-Cafe mailing list