[commit: packages/containers] changelog-foldtree, cleaned_bugfix394, develop-0.6, develop-0.6-questionable, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-184-generic, revert-408-bugfix_394, zip-devel: Make Foldable.fold be INLINABLE without an argument. (398e466)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:34:27 UTC 2017


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

On branches: changelog-foldtree,cleaned_bugfix394,develop-0.6,develop-0.6-questionable,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-184-generic,revert-408-bugfix_394,zip-devel
Link       : http://git.haskell.org/packages/containers.git/commitdiff/398e46672e498f83f28733f3a7a188651e9576b8

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

commit 398e46672e498f83f28733f3a7a188651e9576b8
Author: Milan Straka <fox at ucw.cz>
Date:   Sun Oct 19 14:07:13 2014 +0200

    Make Foldable.fold be INLINABLE without an argument.


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

398e46672e498f83f28733f3a7a188651e9576b8
 Data/IntMap/Base.hs | 2 +-
 Data/Map/Base.hs    | 2 +-
 Data/Set/Base.hs    | 2 +-
 3 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 8f2e32f..c1b2f4d 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -313,7 +313,7 @@ instance Monoid (IntMap a) where
     mconcat = unions
 
 instance Foldable.Foldable IntMap where
-  fold t = go t
+  fold = go
     where go Nil = mempty
           go (Tip _ v) = v
           go (Bin _ _ l r) = go l `mappend` go r
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index edcfdb7..781ac3a 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -2647,7 +2647,7 @@ instance Traversable (Map k) where
   {-# INLINE traverse #-}
 
 instance Foldable.Foldable (Map k) where
-  fold t = go t
+  fold = go
     where go Tip = mempty
           go (Bin 1 _ v _ _) = v
           go (Bin _ _ v l r) = go l `mappend` (v `mappend` go r)
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index e676a6f..67ade4e 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -255,7 +255,7 @@ instance Ord a => Monoid (Set a) where
     mconcat = unions
 
 instance Foldable.Foldable Set where
-    fold t = go t
+    fold = go
       where go Tip = mempty
             go (Bin 1 k _ _) = k
             go (Bin _ k l r) = go l `mappend` (k `mappend` go r)



More information about the ghc-commits mailing list