[commit: ghc] master: Remove redundant contexts from Foldable methods (0a8e899)
git at git.haskell.org
git at git.haskell.org
Wed Nov 5 08:09:53 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/0a8e8995fd31dd46fa9bdbc7f65984b51c8c13dc/ghc
>---------------------------------------------------------------
commit 0a8e8995fd31dd46fa9bdbc7f65984b51c8c13dc
Author: David Feuer <David.Feuer at gmail.com>
Date: Wed Nov 5 08:42:59 2014 +0100
Remove redundant contexts from Foldable methods
New `Foldable` methods accidentally had `Foldable` contexts, which led
to type roles being assigned incorrectly and preventing GND from
deriving `Foldable` instances. Removing those fixes #9761.
Moreover, this patch takes advantage of this fix by deriving
`Foldable` (and `Eq`) for `UniqFM`.
Differential Revision: https://phabricator.haskell.org/D425
>---------------------------------------------------------------
0a8e8995fd31dd46fa9bdbc7f65984b51c8c13dc
compiler/utils/UniqFM.lhs | 20 +++-----------------
libraries/base/Data/Foldable.hs | 14 +++++++-------
testsuite/tests/ghci/scripts/ghci025.stdout | 3 +--
3 files changed, 11 insertions(+), 26 deletions(-)
diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs
index 3ea97e4..f0f9035 100644
--- a/compiler/utils/UniqFM.lhs
+++ b/compiler/utils/UniqFM.lhs
@@ -72,7 +72,6 @@ import Outputable
import Compiler.Hoopl hiding (Unique)
-import Data.Function (on)
import qualified Data.IntMap as M
import qualified Data.IntSet as S
import qualified Data.Foldable as Foldable
@@ -212,22 +211,9 @@ instance Monoid (UniqFM a) where
%************************************************************************
\begin{code}
-newtype UniqFM ele = UFM { unUFM :: M.IntMap ele }
- deriving (Typeable,Data, Traversable.Traversable, Functor)
-
-instance Eq ele => Eq (UniqFM ele) where
- (==) = (==) `on` unUFM
-
-{-
-instance Functor UniqFM where
- fmap f = fmap f . unUFM
-
-instance Traversable.Traversable UniqFM where
- traverse f = Traversable.traverse f . unUFM
--}
-
-instance Foldable.Foldable UniqFM where
- foldMap f = Foldable.foldMap f . unUFM
+newtype UniqFM ele = UFM (M.IntMap ele)
+ deriving (Data, Eq, Foldable.Foldable, Functor, Traversable.Traversable,
+ Typeable)
emptyUFM = UFM M.empty
isNullUFM (UFM m) = M.null m
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 9d26f86..4167b92 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -145,28 +145,28 @@ class Foldable t where
Just x -> f x y)
-- | List of elements of a structure.
- toList :: Foldable t => t a -> [a]
+ toList :: t a -> [a]
{-# INLINE toList #-}
toList t = build (\ c n -> foldr c n t)
-- | Test whether the structure is empty.
- null :: Foldable t => t a -> Bool
+ null :: t a -> Bool
null = foldr (\_ _ -> False) True
-- | Returns the size/length of a finite structure as an 'Int'.
- length :: Foldable t => t a -> Int
+ length :: t a -> Int
length = foldl' (\c _ -> c+1) 0
-- | Does the element occur in the structure?
- elem :: (Foldable t, Eq a) => a -> t a -> Bool
+ elem :: Eq a => a -> t a -> Bool
elem = any . (==)
-- | The largest element of a non-empty structure.
- maximum :: (Foldable t, Ord a) => t a -> a
+ maximum :: Ord a => t a -> a
maximum = foldr1 max
-- | The least element of a non-empty structure.
- minimum :: (Foldable t, Ord a) => t a -> a
+ minimum :: Ord a => t a -> a
minimum = foldr1 min
-- | The 'sum' function computes the sum of the numbers of a structure.
@@ -175,7 +175,7 @@ class Foldable t where
-- | The 'product' function computes the product of the numbers of a
-- structure.
- product :: (Foldable t, Num a) => t a -> a
+ product :: Num a => t a -> a
product = getProduct . foldMap Product
-- instances for Prelude types
diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout
index 4d21c5f..e5654b3 100644
--- a/testsuite/tests/ghci/scripts/ghci025.stdout
+++ b/testsuite/tests/ghci/scripts/ghci025.stdout
@@ -53,8 +53,7 @@ class Eq a where
(GHC.Classes./=) :: a -> a -> GHC.Types.Bool
-- imported via Prelude, T
Prelude.length ::
- Data.Foldable.Foldable t =>
- forall a. Data.Foldable.Foldable t => t a -> GHC.Types.Int
+ Data.Foldable.Foldable t => forall a. t a -> GHC.Types.Int
-- imported via T
data T.Integer
= integer-gmp-0.5.1.0:GHC.Integer.Type.S# GHC.Prim.Int#
More information about the ghc-commits
mailing list