[commit: ghc] master: Move Data.Functor.Identity from transformers to base (8710136)

git at git.haskell.org git at git.haskell.org
Mon Nov 10 20:51:26 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/87101364e0c2db5e472c6331ad35503028b2ec3c/ghc

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

commit 87101364e0c2db5e472c6331ad35503028b2ec3c
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Oct 5 15:18:49 2014 +0200

    Move Data.Functor.Identity from transformers to base
    
    This also updates the `transformers` submodule to the just
    released `transformers-0.4.2.0` package version.
    
    See #9664 for more details
    
    Reviewed By: austin, ekmett
    
    Differential Revision: https://phabricator.haskell.org/D313


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

87101364e0c2db5e472c6331ad35503028b2ec3c
 libraries/base/Data/Functor/Identity.hs   | 75 +++++++++++++++++++++++++++++++
 libraries/base/base.cabal                 |  1 +
 libraries/base/changelog.md               |  3 ++
 libraries/transformers                    |  2 +-
 testsuite/tests/ghci/scripts/T5979.stderr |  6 +--
 5 files changed, 83 insertions(+), 4 deletions(-)

diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs
new file mode 100644
index 0000000..4058df8
--- /dev/null
+++ b/libraries/base/Data/Functor/Identity.hs
@@ -0,0 +1,75 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE AutoDeriveTypeable #-}
+-----------------------------------------------------------------------------
+-- |
+-- Module      :  Data.Functor.Identity
+-- Copyright   :  (c) Andy Gill 2001,
+--                (c) Oregon Graduate Institute of Science and Technology 2001
+-- License     :  BSD-style (see the file LICENSE)
+--
+-- Maintainer  :  ross at soi.city.ac.uk
+-- Stability   :  experimental
+-- Portability :  portable
+--
+-- The identity functor and monad.
+--
+-- This trivial type constructor serves two purposes:
+--
+-- * It can be used with functions parameterized by functor or monad classes.
+--
+-- * It can be used as a base monad to which a series of monad
+--   transformers may be applied to construct a composite monad.
+--   Most monad transformer modules include the special case of
+--   applying the transformer to 'Identity'.  For example, @State s@
+--   is an abbreviation for @StateT s 'Identity'@.
+--
+-- /Since: 4.8.0.0/
+-----------------------------------------------------------------------------
+
+module Data.Functor.Identity (
+    Identity(..),
+  ) where
+
+import Control.Monad.Fix
+import Data.Functor
+
+-- | Identity functor and monad. (a non-strict monad)
+--
+-- /Since: 4.8.0.0/
+newtype Identity a = Identity { runIdentity :: a }
+    deriving (Eq, Ord)
+
+-- | This instance would be equivalent to the derived instances of the
+-- 'Identity' newtype if the 'runIdentity' field were removed
+instance (Read a) => Read (Identity a) where
+    readsPrec d = readParen (d > 10) $ \ r ->
+        [(Identity x,t) | ("Identity",s) <- lex r, (x,t) <- readsPrec 11 s]
+
+-- | This instance would be equivalent to the derived instances of the
+-- 'Identity' newtype if the 'runIdentity' field were removed
+instance (Show a) => Show (Identity a) where
+    showsPrec d (Identity x) = showParen (d > 10) $
+        showString "Identity " . showsPrec 11 x
+
+-- ---------------------------------------------------------------------------
+-- Identity instances for Functor and Monad
+
+instance Functor Identity where
+    fmap f m = Identity (f (runIdentity m))
+
+instance Foldable Identity where
+    foldMap f (Identity x) = f x
+
+instance Traversable Identity where
+    traverse f (Identity x) = Identity <$> f x
+
+instance Applicative Identity where
+    pure a = Identity a
+    Identity f <*> Identity x = Identity (f x)
+
+instance Monad Identity where
+    return a = Identity a
+    m >>= k  = k (runIdentity m)
+
+instance MonadFix Identity where
+    mfix f = Identity (fix (runIdentity . f))
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 6277d89..7e5ca15 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -130,6 +130,7 @@ Library
         Data.Foldable
         Data.Function
         Data.Functor
+        Data.Functor.Identity
         Data.IORef
         Data.Int
         Data.Ix
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 2fa25ae..c5047ce 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -97,6 +97,9 @@
     are swapped, such that `Data.List.nubBy (<) [1,2]` now returns `[1]`
     instead of `[1,2]` (#2528, #3280, #7913)
 
+  * New module `Data.Functor.Identity` (previously provided by `transformers`
+    package). (#9664)
+
 ## 4.7.0.1  *Jul 2014*
 
   * Bundled with GHC 7.8.3
diff --git a/libraries/transformers b/libraries/transformers
index 87d9892..c55953c 160000
--- a/libraries/transformers
+++ b/libraries/transformers
@@ -1 +1 @@
-Subproject commit 87d9892a604b56d687ce70f1d1abc7848f78c6e4
+Subproject commit c55953c1298a5b63e250dfcd402154f6d187825e
diff --git a/testsuite/tests/ghci/scripts/T5979.stderr b/testsuite/tests/ghci/scripts/T5979.stderr
index c8fc7c2..9be8573 100644
--- a/testsuite/tests/ghci/scripts/T5979.stderr
+++ b/testsuite/tests/ghci/scripts/T5979.stderr
@@ -2,6 +2,6 @@
 <no location info>:
     Could not find module ‘Control.Monad.Trans.State’
     Perhaps you meant
-      Control.Monad.Trans.State (from transformers-0.4.1.0 at trans_<HASH>)
-      Control.Monad.Trans.Class (from transformers-0.4.1.0 at trans_<HASH>)
-      Control.Monad.Trans.Cont (from transformers-0.4.1.0 at trans_<HASH>)
+      Control.Monad.Trans.State (from transformers-0.4.2.0 at trans_<HASH>)
+      Control.Monad.Trans.Class (from transformers-0.4.2.0 at trans_<HASH>)
+      Control.Monad.Trans.Cont (from transformers-0.4.2.0 at trans_<HASH>)



More information about the ghc-commits mailing list