Proposal: Make GHC.Arr.listArray slightly stricter to allow fusion

David Feuer david.feuer at gmail.com
Thu Nov 13 10:22:36 UTC 2014


Currently, GHC.Arr.listArray is pretty lazy:

listArray (1,3) $ [1,2,3] ++ undefined

will work perfectly fine.

This is actually lazier than the current array:

array (1,3) $ [(1,1), (2,2), (3,3)] ++ undefined = undefined

Unfortunately, I don't think it's possible to make listArray fuse with a
list producer while preserving quite that level of laziness. If we're
willing to be slightly stricter, however, I think everything works.
Specifically, I propose that we allow

listArray (length xs) (xs ++ _|_) = _|_

The resulting listArray code is below.

{-# INLINE mylistArray #-}
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 y r i# s3#
          | isTrue# (i# ==# n#) = s3#
          | otherwise = case writeArray# marr# i# y s3# of
                          s4# -> r (i# +# 1#) s4#
      in
        case foldr fillFromList (\_ s# -> s#) es 0# s2# of
          s5# -> done l u n marr# s5# }})
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20141113/78db77ff/attachment.html>


More information about the Libraries mailing list