[commit: ghc] master: Fix AMP warnings for MaybeT/MaybeErr (10d36f3)
git at git.haskell.org
git at git.haskell.org
Tue Jan 14 09:47:20 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/10d36f3cb20a85a5cf7f11ba1d6a0ac1bb6b1a7f/ghc
>---------------------------------------------------------------
commit 10d36f3cb20a85a5cf7f11ba1d6a0ac1bb6b1a7f
Author: Austin Seipp <austin at well-typed.com>
Date: Mon Jan 13 18:39:10 2014 -0600
Fix AMP warnings for MaybeT/MaybeErr
Signed-off-by: Austin Seipp <austin at well-typed.com>
>---------------------------------------------------------------
10d36f3cb20a85a5cf7f11ba1d6a0ac1bb6b1a7f
compiler/utils/Maybes.lhs | 14 +++++++++++++-
1 file changed, 13 insertions(+), 1 deletion(-)
diff --git a/compiler/utils/Maybes.lhs b/compiler/utils/Maybes.lhs
index 859908e..3c943bd 100644
--- a/compiler/utils/Maybes.lhs
+++ b/compiler/utils/Maybes.lhs
@@ -20,7 +20,8 @@ module Maybes (
MaybeT(..)
) where
-
+import Control.Applicative
+import Control.Monad
import Data.Maybe
infixr 4 `orElse`
@@ -95,6 +96,10 @@ 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
+instance (Monad m, Functor m) => Applicative (MaybeT m) where
+ pure = return
+ (<*>) = ap
+
instance Monad m => Monad (MaybeT m) where
return = MaybeT . return . Just
x >>= f = MaybeT $ runMaybeT x >>= maybe (return Nothing) (runMaybeT . f)
@@ -112,6 +117,13 @@ instance Monad m => Monad (MaybeT m) where
\begin{code}
data MaybeErr err val = Succeeded val | Failed err
+instance Functor (MaybeErr err) where
+ fmap = liftM
+
+instance Applicative (MaybeErr err) where
+ pure = return
+ (<*>) = ap
+
instance Monad (MaybeErr err) where
return v = Succeeded v
Succeeded v >>= k = k v
More information about the ghc-commits
mailing list