[commit: ghc] master: base: Mark `findIndices` as INLINABLE instead of INLINE (fixes #15426) (1481762)

git at git.haskell.org git at git.haskell.org
Tue Aug 21 22:57:43 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/14817621aae2d45f8272a36b171b9ccce8763bba/ghc

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

commit 14817621aae2d45f8272a36b171b9ccce8763bba
Author: Kevin Buhr <buhr at asaurus.net>
Date:   Tue Aug 21 16:04:59 2018 -0400

    base: Mark `findIndices` as INLINABLE instead of INLINE (fixes #15426)
    
    If `findIndices` is marked INLINE in `Data.OldList`, then the unfolded
    versions of `elemIndex` and `findIndex` included in the interface file
    are unfusible (even though `findIndices` itself remains fusible).  By
    marking it INLINABLE instead, elemIndex` and `findIndex` will fuse
    properly.
    
    Test Plan: make TEST=T15426
    
    Reviewers: hvr, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, carter
    
    GHC Trac Issues: #15426
    
    Differential Revision: https://phabricator.haskell.org/D5063


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

14817621aae2d45f8272a36b171b9ccce8763bba
 libraries/base/Data/OldList.hs            |  4 +++-
 testsuite/tests/perf/should_run/T15426.hs | 13 +++++++++++++
 testsuite/tests/perf/should_run/all.T     |  9 +++++++++
 3 files changed, 25 insertions(+), 1 deletion(-)

diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index c4c38d4..ee2dfac 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -310,7 +310,9 @@ findIndices      :: (a -> Bool) -> [a] -> [Int]
 findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
 #else
 -- Efficient definition, adapted from Data.Sequence
-{-# INLINE findIndices #-}
+-- (Note that making this INLINABLE instead of INLINE allows
+-- 'findIndex' to fuse, fixing #15426.)
+{-# INLINABLE findIndices #-}
 findIndices p ls = build $ \c n ->
   let go x r k | p x       = I# k `c` r (k +# 1#)
                | otherwise = r (k +# 1#)
diff --git a/testsuite/tests/perf/should_run/T15426.hs b/testsuite/tests/perf/should_run/T15426.hs
new file mode 100644
index 0000000..de88c28
--- /dev/null
+++ b/testsuite/tests/perf/should_run/T15426.hs
@@ -0,0 +1,13 @@
+import Control.Exception (evaluate)
+import Data.List
+
+-- The following will fuse with minimal heap usage provided
+-- `findIndices` is marked `INLINABLE` instead of `INLINE`.
+
+unsafeFindIndex p = head . findIndices p
+
+main = do evaluate $ elemIndex 999999 [(1::Int)..1000000]
+          evaluate $ elemIndices 999999 [(1::Int)..1000000]
+          evaluate $ findIndex (>=999999) [(1::Int)..1000000]
+          evaluate $ findIndices (>=999999) [(1::Int)..1000000]
+          evaluate $ unsafeFindIndex (>=999999) [(1::Int)..1000000]
diff --git a/testsuite/tests/perf/should_run/all.T b/testsuite/tests/perf/should_run/all.T
index 9705a08..6a7bcf0 100644
--- a/testsuite/tests/perf/should_run/all.T
+++ b/testsuite/tests/perf/should_run/all.T
@@ -595,3 +595,12 @@ test('T15226a',
      only_ways(['normal'])],
     compile_and_run,
     ['-O'])
+
+test('T15426',
+    [stats_num_field('bytes allocated',
+                    [ (wordsize(64), 41272, 20) ]),
+		    # 2018-08-10   41272  Change findIndices from INLINE to INLINABLE
+		    # initial  160041176
+     only_ways(['normal'])],
+    compile_and_run,
+    ['-O2'])



More information about the ghc-commits mailing list