listArray does not fuse away the input list
I noticed that the input list to listArray
does not fuse away.
This is not the case for array
and accumArray
, the two other ways to create arrays. This is surprising, because I expected listArray
to be the most efficient since it has no extra work to do with indices.
Looking at the code, listArray
gets rewritten to use listArrayST
/listUArrayST
, which consumes the list with fillFromList
.
https://gitlab.haskell.org/ghc/packages/array/-/blob/f487b8de85f2b271a3831c14ab6439b9bc9b8343/Data/Array/Base.hs#L176-272
But listArrayST
/listUArrayST
can be written to use foldr
instead, which can fuse with the list, so I don't think this has to be this way.
Here are some benchmarks:
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.ST
import Criterion.Main
import Data.Array.Base
import Data.Ix
main :: IO ()
main = defaultMain
[ bench "listArray" $ whnf mkListArray n
, bench "array" $ whnf mkArray n
, bench "accumArray" $ whnf mkAccumArray n
, bench "listArrayNew" $ whnf mkListArrayNew n
]
where
n = 1000000
mkListArray :: Int -> UArray Int Int
mkListArray n = listArray (1,n) [1..n]
mkArray :: Int -> UArray Int Int
mkArray n = array (1,n) [(i,i) | i <- [1..n]]
mkAccumArray :: Int -> UArray Int Int
mkAccumArray n = accumArray (const id) 0 (1,n) [(i,i) | i <- [1..n]]
-- Can we do this instead?
listUArraySTNew :: (MArray (STUArray s) e (ST s), Ix i) => (i,i) -> [e] -> ST s (STUArray s i e)
listUArraySTNew (l,u) es = do
marr <- newArray_ (l,u)
let n = safeRangeSize (l,u)
let f x k i
| i == n = pure ()
| otherwise = unsafeWrite marr i x *> k (i + 1)
foldr f (const (pure ())) es 0
return marr
mkListArrayNew :: Int -> UArray Int Int
mkListArrayNew n = runST $ listUArraySTNew (1,n) [1..n] >>= unsafeFreezeSTUArray
On GHC 9.2.5 with -O2:
Running them individually since they seem to interfere with each other.
benchmarking listArray
time 5.835 ms (5.811 ms .. 5.856 ms)
1.000 R² (1.000 R² .. 1.000 R²)
mean 5.869 ms (5.844 ms .. 5.953 ms)
std dev 128.9 μs (24.44 μs .. 266.1 μs)
benchmarking array
time 989.2 μs (984.9 μs .. 992.8 μs)
1.000 R² (1.000 R² .. 1.000 R²)
mean 987.1 μs (985.7 μs .. 989.4 μs)
std dev 6.069 μs (3.730 μs .. 10.02 μs)
benchmarking accumArray
time 985.2 μs (984.1 μs .. 986.4 μs)
1.000 R² (1.000 R² .. 1.000 R²)
mean 987.4 μs (986.1 μs .. 989.0 μs)
std dev 4.958 μs (3.462 μs .. 6.930 μs)
benchmarking listArrayNew
time 995.4 μs (991.0 μs .. 999.8 μs)
1.000 R² (1.000 R² .. 1.000 R²)
mean 994.5 μs (993.5 μs .. 996.3 μs)
std dev 4.452 μs (3.154 μs .. 7.208 μs)