[commit: ghc] master: Make findIndices fuse (ef2d027)
git at git.haskell.org
git at git.haskell.org
Tue Oct 21 21:50:43 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/ef2d027917ca7e5415ba5e9f3ff439beda89b3ea/ghc
>---------------------------------------------------------------
commit ef2d027917ca7e5415ba5e9f3ff439beda89b3ea
Author: David Feuer <David.Feuer at gmail.com>
Date: Tue Oct 21 15:01:26 2014 -0500
Make findIndices fuse
Summary:
Steal the findIndices implementation from Data.Sequence, that can
participate in fold/build fusion
Reviewers: nomeata, austin
Reviewed By: nomeata, austin
Subscribers: thomie, carter, ezyang, simonmar
Differential Revision: https://phabricator.haskell.org/D345
>---------------------------------------------------------------
ef2d027917ca7e5415ba5e9f3ff439beda89b3ea
libraries/base/Data/OldList.hs | 12 ++++++------
1 file changed, 6 insertions(+), 6 deletions(-)
diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index ff85154..0e6709e 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -277,12 +277,12 @@ findIndices :: (a -> Bool) -> [a] -> [Int]
#ifdef USE_REPORT_PRELUDE
findIndices p xs = [ i | (x,i) <- zip xs [0..], p x]
#else
--- Efficient definition
-findIndices p ls = loop 0# ls
- where
- loop _ [] = []
- loop n (x:xs) | p x = I# n : loop (n +# 1#) xs
- | otherwise = loop (n +# 1#) xs
+-- Efficient definition, adapted from Data.Sequence
+{-# INLINE findIndices #-}
+findIndices p ls = build $ \c n ->
+ let go x r k | p x = I# k `c` r (k +# 1#)
+ | otherwise = r (k +# 1#)
+ in foldr go (\_ -> n) ls 0#
#endif /* USE_REPORT_PRELUDE */
-- | The 'isPrefixOf' function takes two lists and returns 'True'
More information about the ghc-commits
mailing list