[commit: ghc] ghc-7.10: {Data, Generic(1), MonadZip} instances for Identity (873c398)

git at git.haskell.org git at git.haskell.org
Mon Feb 23 10:42:14 UTC 2015


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

On branch  : ghc-7.10
Link       : http://ghc.haskell.org/trac/ghc/changeset/873c3981794e0823f3bfb5383068382445007837/ghc

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

commit 873c3981794e0823f3bfb5383068382445007837
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sun Feb 22 15:21:18 2015 +0100

    {Data,Generic(1),MonadZip} instances for Identity
    
    These instances were missed when the identity functor was added to
    the `base` package (re #9664).
    
    (cherry picked from commit 1f60d635cee1ff3db72e0129f9035b147f52c9c4)


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

873c3981794e0823f3bfb5383068382445007837
 libraries/base/Data/Functor/Identity.hs | 11 +++++++++--
 1 file changed, 9 insertions(+), 2 deletions(-)

diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs
index 2465a1e..ac47922 100644
--- a/libraries/base/Data/Functor/Identity.hs
+++ b/libraries/base/Data/Functor/Identity.hs
@@ -1,6 +1,7 @@
-{-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE AutoDeriveTypeable #-}
+{-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE Trustworthy #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -33,14 +34,17 @@ module Data.Functor.Identity (
   ) where
 
 import Control.Monad.Fix
+import Control.Monad.Zip
 import Data.Coerce
+import Data.Data (Data)
 import Data.Foldable
+import GHC.Generics (Generic, Generic1)
 
 -- | Identity functor and monad. (a non-strict monad)
 --
 -- @since 4.8.0.0
 newtype Identity a = Identity { runIdentity :: a }
-    deriving (Eq, Ord, Traversable)
+    deriving (Eq, Ord, Data, Traversable, Generic, Generic1)
 
 -- | This instance would be equivalent to the derived instances of the
 -- 'Identity' newtype if the 'runIdentity' field were removed
@@ -89,6 +93,9 @@ instance Monad Identity where
 instance MonadFix Identity where
     mfix f   = Identity (fix (runIdentity . f))
 
+instance MonadZip Identity where
+    mzipWith = coerce
+    munzip   = coerce
 
 -- | Internal (non-exported) 'Coercible' helper for 'elem'
 --



More information about the ghc-commits mailing list