Magicloud Magiclouds <magicloud.magiclo...@gmail.com> wrote:

>   Since Maybe is a monad, I could write code like 'maybeA >> maybeB >>
> maybeC' to check if all these are not Nothing. Or 'liftM foo maybeD'
> to avoid ugly 'case of'.

Also check out the somewhat cleaner Functor class with its liftM
equivalent called 'fmap', for which you don't need to import
Control.Monad.  For monads fmap = liftM.


>   But how if here maybe[ABC] are like 'IO (Maybe Int)', or foo is type
> of 'Int -> IO Int'?

Well, this is Haskell, so you can always write your own higher order
functions:

    (~>>=) :: (Monad m) => m (Maybe a) -> (a -> m (Maybe b)) -> m (Maybe b)
    c ~>>= f = c >>= maybe (return Nothing) f

    (~>>) :: (Monad m) => m (Maybe a) -> m (Maybe b) -> m (Maybe b)
    c ~>> d = c >>= maybe (return Nothing) (const d)

    infixl 1 ~>>=
    infixl 1 ~>>

However in the second case of course there is no Maybe, but then notice
that IO itself acts like Maybe through its exceptions.  In fact Maybe is
a transparent exception monad.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.

Attachment: signature.asc
Description: PGP signature

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to