diff options
author | Herbert Valerio Riedel <hvr@gnu.org> | 2015-12-07 17:32:23 +0100 |
---|---|---|
committer | Herbert Valerio Riedel <hvr@gnu.org> | 2015-12-07 17:33:34 +0100 |
commit | 09333313f32be975faf9158fcd3648489d78ad82 (patch) | |
tree | f7c044e07058a7aa6bdcd9f07d6323ffeb624716 /compiler/utils/Maybes.hs | |
parent | 04e1c27943503f2e12b009b91f7bef195766f6d0 (diff) | |
download | haskell-09333313f32be975faf9158fcd3648489d78ad82.tar.gz |
Re-use `transformers`'s `MaybeT` rather than our own
The now removed `MaybeT` type was originally added back in 2008
via bc845b714132a897032502536fea8cd018ce325b
Reviewed By: bgamari
Differential Revision: https://phabricator.haskell.org/D1583
Diffstat (limited to 'compiler/utils/Maybes.hs')
-rw-r--r-- | compiler/utils/Maybes.hs | 60 |
1 files changed, 4 insertions, 56 deletions
diff --git a/compiler/utils/Maybes.hs b/compiler/utils/Maybes.hs index 656f40a372..ac5107029b 100644 --- a/compiler/utils/Maybes.hs +++ b/compiler/utils/Maybes.hs @@ -3,7 +3,6 @@ (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -} -{-# LANGUAGE CPP #-} module Maybes ( module Data.Maybe, @@ -18,11 +17,9 @@ module Maybes ( MaybeT(..), liftMaybeT ) where -import Control.Applicative +import Control.Applicative as A import Control.Monad -#if __GLASGOW_HASKELL__ > 710 -import Control.Monad.Fail -#endif +import Control.Monad.Trans.Maybe import Data.Maybe infixr 4 `orElse` @@ -64,56 +61,7 @@ orElse = flip fromMaybe ************************************************************************ -} -newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)} - -instance Functor m => Functor (MaybeT m) where - fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => Applicative (MaybeT m) where -#else -instance (Monad m) => Applicative (MaybeT m) where -#endif - pure = MaybeT . pure . Just - (<*>) = ap - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => Monad (MaybeT m) where -#else -instance (Monad m) => Monad (MaybeT m) where -#endif - return = pure - x >>= f = MaybeT $ runMaybeT x >>= maybe (pure Nothing) (runMaybeT . f) - fail _ = MaybeT $ pure Nothing - - -#if __GLASGOW_HASKELL__ > 710 -instance Monad m => MonadFail (MaybeT m) where - fail _ = MaybeT $ return Nothing -#endif - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => Alternative (MaybeT m) where -#else -instance (Monad m) => Alternative (MaybeT m) where -#endif - empty = mzero - (<|>) = mplus - -#if __GLASGOW_HASKELL__ < 710 --- Pre-AMP change -instance (Monad m, Applicative m) => MonadPlus (MaybeT m) where -#else -instance Monad m => MonadPlus (MaybeT m) where -#endif - mzero = MaybeT $ pure Nothing - p `mplus` q = MaybeT $ do ma <- runMaybeT p - case ma of - Just a -> pure (Just a) - Nothing -> runMaybeT q +-- We had our own MaybeT in the past. Now we reuse transformer's MaybeT liftMaybeT :: Monad m => m a -> MaybeT m a liftMaybeT act = MaybeT $ Just `liftM` act @@ -136,7 +84,7 @@ instance Applicative (MaybeErr err) where (<*>) = ap instance Monad (MaybeErr err) where - return = pure + return = A.pure Succeeded v >>= k = k v Failed e >>= _ = Failed e |