[commit: ghc] master: Make listArray fuse (bc68ed0)
git at git.haskell.org
git at git.haskell.org
Tue Nov 18 01:20:05 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/bc68ed02e52d8e1c201aff16c4464fd0ca53d0bc/ghc
>---------------------------------------------------------------
commit bc68ed02e52d8e1c201aff16c4464fd0ca53d0bc
Author: David Feuer <David.Feuer at gmail.com>
Date: Mon Nov 17 19:16:16 2014 -0600
Make listArray fuse
Summary: Make listArray fuse with a list producer. Note: if code size increases too much, we can fix that with some `RULES`.
Reviewers: nomeata, hvr, austin, ekmett, simonmar, bgamari
Reviewed By: bgamari
Subscribers: bgamari, thomie, carter
Differential Revision: https://phabricator.haskell.org/D474
GHC Trac Issues: #9801
>---------------------------------------------------------------
bc68ed02e52d8e1c201aff16c4464fd0ca53d0bc
libraries/base/GHC/Arr.hs | 24 +++++++++++-------------
1 file changed, 11 insertions(+), 13 deletions(-)
diff --git a/libraries/base/GHC/Arr.hs b/libraries/base/GHC/Arr.hs
index 02bf7d8..e68c70f 100644
--- a/libraries/base/GHC/Arr.hs
+++ b/libraries/base/GHC/Arr.hs
@@ -468,12 +468,6 @@ done l u n@(I# _) marr#
= \s1# -> case unsafeFreezeArray# marr# s1# of
(# s2#, arr# #) -> (# s2#, Array l u n arr# #)
--- This is inefficient and I'm not sure why:
--- listArray (l,u) es = unsafeArray (l,u) (zip [0 .. rangeSize (l,u) - 1] es)
--- The code below is better. It still doesn't enable foldr/build
--- transformation on the list of elements; I guess it's impossible
--- using mechanisms currently available.
-
-- | Construct an array from a pair of bounds and a list of values in
-- index order.
{-# INLINE listArray #-}
@@ -481,13 +475,17 @@ listArray :: Ix i => (i,i) -> [e] -> Array i e
listArray (l,u) es = runST (ST $ \s1# ->
case safeRangeSize (l,u) of { n@(I# n#) ->
case newArray# n# arrEleBottom s1# of { (# s2#, marr# #) ->
- let fillFromList i# xs s3# | isTrue# (i# ==# n#) = s3#
- | otherwise = case xs of
- [] -> s3#
- y:ys -> case writeArray# marr# i# y s3# of { s4# ->
- fillFromList (i# +# 1#) ys s4# } in
- case fillFromList 0# es s2# of { s3# ->
- done l u n marr# s3# }}})
+ let
+ go y r = \ i# s3# ->
+ case writeArray# marr# i# y s3# of
+ s4# -> if (isTrue# (i# ==# n# -# 1#))
+ then s4#
+ else r (i# +# 1#) s4#
+ in
+ done l u n marr# (
+ if n == 0
+ then s2#
+ else foldr go (\_ s# -> s#) es 0# s2#)}})
-- | The value at the given index in an array.
{-# INLINE (!) #-}
More information about the ghc-commits
mailing list