Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/7c1dff56f8071e62c708679d79299b062806ff91

>---------------------------------------------------------------

commit 7c1dff56f8071e62c708679d79299b062806ff91
Author: Bas van Dijk <[email protected]>
Date:   Wed Dec 7 15:37:31 2011 +0100

    Moved the instances from Control.Monad.Instances to GHC.Base and Data.Either

>---------------------------------------------------------------

 Control/Applicative.hs     |    1 -
 Control/Monad/Fix.hs       |    6 ------
 Control/Monad/Instances.hs |   22 ++--------------------
 Data/Either.hs             |    9 +++++++++
 GHC/Base.lhs               |   10 ++++++++++
 5 files changed, 21 insertions(+), 27 deletions(-)

diff --git a/Control/Applicative.hs b/Control/Applicative.hs
index 248bbac..bf58bea 100644
--- a/Control/Applicative.hs
+++ b/Control/Applicative.hs
@@ -50,7 +50,6 @@ import Prelude hiding (id,(.))
 import Control.Category
 import Control.Arrow (Arrow(arr, (&&&)), ArrowZero(zeroArrow), 
ArrowPlus((<+>)))
 import Control.Monad (liftM, ap, MonadPlus(..))
-import Control.Monad.Instances ()
 #ifndef __NHC__
 import Control.Monad.ST.Safe (ST)
 import qualified Control.Monad.ST.Lazy.Safe as Lazy (ST)
diff --git a/Control/Monad/Fix.hs b/Control/Monad/Fix.hs
index b1fe43d..a3d2c89 100644
--- a/Control/Monad/Fix.hs
+++ b/Control/Monad/Fix.hs
@@ -27,7 +27,6 @@ module Control.Monad.Fix (
 
 import Prelude
 import System.IO
-import Control.Monad.Instances ()
 import Data.Function (fix)
 #ifdef __HUGS__
 import Hugs.Prelude (MonadFix(mfix))
@@ -65,24 +64,19 @@ class (Monad m) => MonadFix m where
 
 -- Instances of MonadFix for Prelude monads
 
--- Maybe:
 instance MonadFix Maybe where
     mfix f = let a = f (unJust a) in a
              where unJust (Just x) = x
                    unJust Nothing  = error "mfix Maybe: Nothing"
 
--- List:
 instance MonadFix [] where
     mfix f = case fix (f . head) of
                []    -> []
                (x:_) -> x : mfix (tail . f)
 
--- IO:
 instance MonadFix IO where
     mfix = fixIO 
 
--- Prelude types with Monad instances in Control.Monad.Instances
-
 instance MonadFix ((->) r) where
     mfix f = \ r -> let a = f a r in a
 
diff --git a/Control/Monad/Instances.hs b/Control/Monad/Instances.hs
index 3849e3b..f30f7a4 100644
--- a/Control/Monad/Instances.hs
+++ b/Control/Monad/Instances.hs
@@ -13,29 +13,11 @@
 -- Stability   :  provisional
 -- Portability :  portable
 --
+-- /This module is DEPRECATED and will be removed in the future!/
+--
 -- 'Functor' and 'Monad' instances for @(->) r@ and
 -- 'Functor' instances for @(,) a@ and @'Either' a@.
 
 module Control.Monad.Instances (Functor(..),Monad(..)) where
 
 import Prelude
-
-instance Functor ((->) r) where
-        fmap = (.)
-
-instance Monad ((->) r) where
-        return = const
-        f >>= k = \ r -> k (f r) r
-
-instance Functor ((,) a) where
-        fmap f (x,y) = (x, f y)
-
-instance Functor (Either a) where
-        fmap _ (Left x) = Left x
-        fmap f (Right y) = Right (f y)
-
-instance Monad (Either e) where
-        return = Right
-        Left  l >>= _ = Left l
-        Right r >>= k = k r
-
diff --git a/Data/Either.hs b/Data/Either.hs
index cdfa761..46d5c40 100644
--- a/Data/Either.hs
+++ b/Data/Either.hs
@@ -56,6 +56,15 @@ hold a correct value (mnemonic: \"right\" also means 
\"correct\").
 data  Either a b  =  Left a | Right b
   deriving (Eq, Ord, Read, Show, Generic)
 
+instance Functor (Either a) where
+    fmap _ (Left x) = Left x
+    fmap f (Right y) = Right (f y)
+
+instance Monad (Either e) where
+    return = Right
+    Left  l >>= _ = Left l
+    Right r >>= k = k r
+
 -- | Case analysis for the 'Either' type.
 -- If the value is @'Left' a@, apply the first function to @a@;
 -- if it is @'Right' b@, apply the second function to @b@.
diff --git a/GHC/Base.lhs b/GHC/Base.lhs
index e062a36..4b10767 100644
--- a/GHC/Base.lhs
+++ b/GHC/Base.lhs
@@ -229,6 +229,16 @@ class  Monad m  where
     {-# INLINE (>>) #-}
     m >> k      = m >>= \_ -> k
     fail s      = error s
+
+instance Functor ((->) r) where
+    fmap = (.)
+
+instance Monad ((->) r) where
+    return = const
+    f >>= k = \ r -> k (f r) r
+
+instance Functor ((,) a) where
+    fmap f (x,y) = (x, f y)
 \end{code}
 
 



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to