From 2567549328aebd563c751f555fe3ae6ddf2f8c8b Mon Sep 17 00:00:00 2001
From: meooow25 <soumiksarkar.3120@gmail.com>
Date: Sun, 24 Sep 2023 17:13:45 +0530
Subject: [PATCH] Optimize newGenArray a little

* Use unsafeNewArray_ instead of newAray_. We know we will fill the
  array, and newArray_ wastefully initializes it beforehand.
* Avoid safeIndexing the range when writing the elements. range
  generates the elements in the required order, so we can simply use an
  Int counter.
---
 Data/Array/Base.hs | 15 +++++++++++----
 1 file changed, 11 insertions(+), 4 deletions(-)

diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs
index 60329e46..8a06afd3 100644
--- a/Data/Array/Base.hs
+++ b/Data/Array/Base.hs
@@ -921,10 +921,17 @@ newListArray (l,u) es = do
 -- | Constructs a mutable array using a generator function.
 -- It invokes the generator function in ascending order of the indices.
 newGenArray :: (MArray a e m, Ix i) => (i,i) -> (i -> m e) -> m (a i e)
-newGenArray (l,u) f = do
-    marr <- newArray_ (l,u)
-    let n = safeRangeSize (l,u)
-    sequence_ [ f i >>= unsafeWrite marr (safeIndex (l,u) n i) | i <- range (l,u)]
+newGenArray bnds f = do
+    let n = safeRangeSize bnds
+    marr <- unsafeNewArray_ bnds
+    let g ix k i
+            | i == n    = return ()
+            | otherwise = do
+                x <- f ix
+                unsafeWrite marr i x
+                k (i+1)
+    foldr g (\ !_i -> return ()) (range bnds) 0
+    -- The bang above is important for GHC for unbox the Int.
     return marr
 
 {-# INLINE readArray #-}
-- 
GitLab