[commit: ghc] master: Make sure that `all`, `any`, `and`, and `or` fuse (#9848) (22bbc1c)
git at git.haskell.org
git at git.haskell.org
Wed Aug 5 12:44:23 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/22bbc1cf209d44b8bb8897ae7a35f9ebaf411b10/ghc
>---------------------------------------------------------------
commit 22bbc1cf209d44b8bb8897ae7a35f9ebaf411b10
Author: Takano Akio <aljee at hyper.cx>
Date: Wed Aug 5 14:23:22 2015 +0200
Make sure that `all`, `any`, `and`, and `or` fuse (#9848)
Test Plan: validate
Reviewers: hvr, austin, bgamari, simonpj
Reviewed By: simonpj
Subscribers: simonpj, thomie
Differential Revision: https://phabricator.haskell.org/D1126
GHC Trac Issues: #9848
>---------------------------------------------------------------
22bbc1cf209d44b8bb8897ae7a35f9ebaf411b10
libraries/base/Data/Foldable.hs | 2 ++
libraries/base/tests/T9848.hs | 14 ++++++++++++++
libraries/base/tests/{T2528.stdout => T9848.stdout} | 2 --
libraries/base/tests/all.T | 7 +++++++
4 files changed, 23 insertions(+), 2 deletions(-)
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 1f20261..24b6dd1 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -119,6 +119,8 @@ class Foldable t where
-- | Map each element of the structure to a monoid,
-- and combine the results.
foldMap :: Monoid m => (a -> m) -> t a -> m
+ {-# INLINE foldMap #-}
+ -- This INLINE allows more list functions to fuse. See Trac #9848.
foldMap f = foldr (mappend . f) mempty
-- | Right-associative fold of a structure.
diff --git a/libraries/base/tests/T9848.hs b/libraries/base/tests/T9848.hs
new file mode 100644
index 0000000..d473f93
--- /dev/null
+++ b/libraries/base/tests/T9848.hs
@@ -0,0 +1,14 @@
+import Data.IORef
+
+foo :: Int -> Bool
+foo n = all (<10000000) [1..n]
+
+bar :: Int -> Bool
+bar n = and $ map (<10000000) [1..n]
+
+main :: IO ()
+main = do
+ ref <- newIORef 1000000
+ val <- readIORef ref
+ print $ foo val
+ print $ bar val
diff --git a/libraries/base/tests/T2528.stdout b/libraries/base/tests/T9848.stdout
similarity index 55%
copy from libraries/base/tests/T2528.stdout
copy to libraries/base/tests/T9848.stdout
index 4f90091..dbde422 100644
--- a/libraries/base/tests/T2528.stdout
+++ b/libraries/base/tests/T9848.stdout
@@ -1,4 +1,2 @@
-[A]
-[1]
True
True
diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T
index 34176d0..1b065a3 100644
--- a/libraries/base/tests/all.T
+++ b/libraries/base/tests/all.T
@@ -191,3 +191,10 @@ test('T9681', normal, compile_fail, [''])
test('T8089', [exit_code(99), run_timeout_multiplier(0.01)],
compile_and_run, [''])
test('T9826',normal, compile_and_run,[''])
+test('T9848',
+ [ stats_num_field('bytes allocated',
+ [ (wordsize(64), 51840, 20)
+ , (wordsize(32), 47348, 20) ])
+ , only_ways(['normal'])],
+ compile_and_run,
+ ['-O'])
More information about the ghc-commits
mailing list