From 73cb3d2008357064cc9ddf7283802ab00b57f64e Mon Sep 17 00:00:00 2001
From: konsumlamm <konsumlamm@gmail.com>
Date: Fri, 8 Sep 2023 18:00:22 +0200
Subject: [PATCH] Inline `newArray`

---
 Control/Concurrent/STM/TArray.hs | 13 ++++++++-----
 1 file changed, 8 insertions(+), 5 deletions(-)

diff --git a/Control/Concurrent/STM/TArray.hs b/Control/Concurrent/STM/TArray.hs
index 73e9d54..0755dd1 100644
--- a/Control/Concurrent/STM/TArray.hs
+++ b/Control/Concurrent/STM/TArray.hs
@@ -9,7 +9,7 @@
 -- Module      :  Control.Concurrent.STM.TArray
 -- Copyright   :  (c) The University of Glasgow 2005
 -- License     :  BSD-style (see the file libraries/base/LICENSE)
--- 
+--
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
 -- Portability :  non-portable (requires STM)
@@ -27,8 +27,7 @@ import Data.Array.Base (listArray, unsafeAt, MArray(..),
                         IArray(numElements))
 import Data.Ix (rangeSize)
 import Data.Typeable (Typeable)
-import Control.Concurrent.STM.TVar (TVar, newTVar, readTVar, writeTVar
-                                   , newTVarIO, readTVarIO)
+import Control.Concurrent.STM.TVar (TVar, newTVar, newTVarIO, readTVar, readTVarIO, writeTVar)
 #ifdef __GLASGOW_HASKELL__
 import GHC.Conc (STM, atomically)
 #else
@@ -46,22 +45,26 @@ newtype TArray i e = TArray (Array i (TVar e)) deriving (Eq, Typeable)
 
 instance MArray TArray e STM where
     getBounds (TArray a) = return (bounds a)
+    getNumElements (TArray a) = return (numElements a)
     newArray b e = do
         a <- rep (rangeSize b) (newTVar e)
         return $ TArray (listArray b a)
     unsafeRead (TArray a) i = readTVar $ unsafeAt a i
     unsafeWrite (TArray a) i e = writeTVar (unsafeAt a i) e
-    getNumElements (TArray a) = return (numElements a)
+
+    {-# INLINE newArray #-}
 
 -- | Writes are slow in `IO`.
 instance MArray TArray e IO where
     getBounds (TArray a) = return (bounds a)
+    getNumElements (TArray a) = return (numElements a)
     newArray b e = do
         a <- rep (rangeSize b) (newTVarIO e)
         return $ TArray (listArray b a)
     unsafeRead (TArray a) i = readTVarIO $ unsafeAt a i
     unsafeWrite (TArray a) i e = atomically $ writeTVar (unsafeAt a i) e
-    getNumElements (TArray a) = return (numElements a)
+
+    {-# INLINE newArray #-}
 
 -- | Like 'replicateM' but uses an accumulator to prevent stack overflows.
 -- Unlike 'replicateM' the returned list is in reversed order.
-- 
GitLab