ResultT.hs revision e9458b1a7a19a63aa4c179f9ab20f4d50681c168
4751N/A{- |
4751N/AModule : ./Common/ResultT.hs
4751N/ADescription : ResultT type and a monadic transformer instance
4751N/ACopyright : (c) T. Mossakowski, C. Maeder, Uni Bremen 2006
4751N/ALicense : GPLv2 or higher, see LICENSE.txt
4751N/A
4751N/AMaintainer : Christian.Maeder@dfki.de
4751N/AStability : provisional
4751N/APortability : portable
4751N/A
4751N/A'ResultT' type and a monadic transformer instance
4751N/A-}
4751N/A
4751N/Amodule Common.ResultT where
4751N/A
4751N/Aimport Common.Result
4751N/Aimport Control.Applicative
4751N/Aimport Control.Monad
4751N/Aimport Control.Monad.Trans
4751N/A
4751N/Anewtype ResultT m a = ResultT { runResultT :: m (Result a) }
4751N/A
4751N/Ainstance Monad m => Functor (ResultT m) where
4751N/A fmap f m = ResultT $ do
4751N/A r <- runResultT m
5061N/A return $ fmap f r
6184N/A
4751N/Ainstance Monad m => Applicative (ResultT m) where
4751N/A pure = return
4751N/A (<*>) = ap
4751N/A
4751N/Ainstance Monad m => Monad (ResultT m) where
4751N/A return = ResultT . return . return
4751N/A m >>= k = ResultT $ do
4751N/A r@(Result e v) <- runResultT m
4751N/A case v of
4751N/A Nothing -> return $ Result e Nothing
4751N/A Just a -> do
4751N/A s <- runResultT $ k a
4751N/A return $ joinResult r s
4751N/A fail = ResultT . return . fail
4751N/A
4751N/Ainstance MonadTrans ResultT where
4751N/A lift m = ResultT $ do
4751N/A a <- m
4751N/A return $ return a
4751N/A
4751N/A-- | Inspired by the MonadIO-class
4751N/Aclass Monad m => MonadResult m where
4751N/A liftR :: Result a -> m a
4751N/A
4751N/A
4751N/Ainstance Monad m => MonadResult (ResultT m) where
4751N/A liftR = ResultT . return
4751N/A
4751N/Ainstance MonadIO m => MonadIO (ResultT m) where
4751N/A liftIO = ResultT . liftM return . liftIO
4751N/A