@@ -80,26 +80,28 @@ module Data.HashMap.Internal.Array
8080 , shrink
8181 ) where
8282
83- import Control.Applicative (liftA2 )
83+ import Control.Applicative (Applicative ( .. ) )
8484import Control.DeepSeq (NFData (.. ), NFData1 (.. ))
8585import Control.Monad ((>=>) )
8686import Control.Monad.ST (runST , stToIO )
8787import GHC.Exts (Int (.. ), SmallArray #, SmallMutableArray #,
8888 cloneSmallMutableArray #, copySmallArray #,
89- copySmallMutableArray #, indexSmallArray #,
90- newSmallArray #, readSmallArray #,
89+ copySmallMutableArray #, getSizeofSmallMutableArray #,
90+ indexSmallArray #, newSmallArray #, readSmallArray #,
9191 reallyUnsafePtrEquality #, sizeofSmallArray #,
92- sizeofSmallMutableArray #, tagToEnum #,
93- thawSmallArray #, unsafeCoerce #,
92+ tagToEnum #, thawSmallArray #, unsafeCoerce #,
9493 unsafeFreezeSmallArray #, unsafeThawSmallArray #,
9594 writeSmallArray #)
9695import GHC.ST (ST (.. ))
97- import Prelude hiding (Foldable (.. ), all , filter ,
96+ import Prelude hiding (Applicative ( .. ), Foldable (.. ), all , filter ,
9897 map , read , traverse )
9998
10099import qualified GHC.Exts as Exts
101100import qualified Language.Haskell.TH.Syntax as TH
101+
102102#if defined(ASSERTS)
103+ import GHC.Exts (sizeofSmallMutableArray #)
104+
103105import qualified Prelude
104106#endif
105107
@@ -158,10 +160,19 @@ data MArray s a = MArray {
158160 unMArray :: ! (SmallMutableArray # s a )
159161 }
160162
161- lengthM :: MArray s a -> Int
162- lengthM mary = I # (sizeofSmallMutableArray# (unMArray mary))
163+ lengthM :: MArray s a -> ST s Int
164+ lengthM (MArray ary) = ST $ \ s ->
165+ case getSizeofSmallMutableArray# ary s of
166+ (# s', n # ) -> (# s', I # n # )
163167{-# INLINE lengthM #-}
164168
169+ #if defined(ASSERTS)
170+ -- | Unsafe. Only for use in the @CHECK_*@ pragmas.
171+ unsafeLengthM :: MArray s a -> Int
172+ unsafeLengthM mary = I # (sizeofSmallMutableArray# (unMArray mary))
173+ {-# INLINE unsafeLengthM #-}
174+ #endif
175+
165176------------------------------------------------------------------------
166177
167178instance NFData a => NFData (Array a ) where
@@ -211,7 +222,7 @@ new_ n = new n undefinedElem
211222shrink :: MArray s a -> Int -> ST s (MArray s a )
212223shrink mary _n@ (I # n# ) =
213224 CHECK_GT (" shrink" , _n, (0 :: Int ))
214- CHECK_LE (" shrink" , _n, (lengthM mary))
225+ CHECK_LE (" shrink" , _n, (unsafeLengthM mary))
215226 ST $ \ s -> case Exts. shrinkSmallMutableArray# (unMArray mary) n# s of
216227 s' -> (# s', mary # )
217228{-# INLINE shrink #-}
@@ -242,13 +253,13 @@ pair x y = run $ do
242253
243254read :: MArray s a -> Int -> ST s a
244255read ary _i@ (I # i# ) = ST $ \ s ->
245- CHECK_BOUNDS (" read" , lengthM ary, _i)
256+ CHECK_BOUNDS (" read" , unsafeLengthM ary, _i)
246257 readSmallArray# (unMArray ary) i# s
247258{-# INLINE read #-}
248259
249260write :: MArray s a -> Int -> a -> ST s ()
250261write ary _i@ (I # i# ) b = ST $ \ s ->
251- CHECK_BOUNDS (" write" , lengthM ary, _i)
262+ CHECK_BOUNDS (" write" , unsafeLengthM ary, _i)
252263 case writeSmallArray# (unMArray ary) i# b s of
253264 s' -> (# s' , () # )
254265{-# INLINE write #-}
@@ -291,24 +302,24 @@ run act = runST $ act >>= unsafeFreeze
291302copy :: Array e -> Int -> MArray s e -> Int -> Int -> ST s ()
292303copy ! src ! _sidx@ (I # sidx# ) ! dst ! _didx@ (I # didx# ) _n@ (I # n# ) =
293304 CHECK_LE (" copy" , _sidx + _n, length src)
294- CHECK_LE (" copy" , _didx + _n, lengthM dst)
305+ CHECK_LE (" copy" , _didx + _n, unsafeLengthM dst)
295306 ST $ \ s# ->
296307 case copySmallArray# (unArray src) sidx# (unMArray dst) didx# n# s# of
297308 s2 -> (# s2, () # )
298309
299310-- | Unsafely copy the elements of an array. Array bounds are not checked.
300311copyM :: MArray s e -> Int -> MArray s e -> Int -> Int -> ST s ()
301312copyM ! src ! _sidx@ (I # sidx# ) ! dst ! _didx@ (I # didx# ) _n@ (I # n# ) =
302- CHECK_BOUNDS (" copyM: src" , lengthM src, _sidx + _n - 1 )
303- CHECK_BOUNDS (" copyM: dst" , lengthM dst, _didx + _n - 1 )
313+ CHECK_BOUNDS (" copyM: src" , unsafeLengthM src, _sidx + _n - 1 )
314+ CHECK_BOUNDS (" copyM: dst" , unsafeLengthM dst, _didx + _n - 1 )
304315 ST $ \ s# ->
305316 case copySmallMutableArray# (unMArray src) sidx# (unMArray dst) didx# n# s# of
306317 s2 -> (# s2, () # )
307318
308319cloneM :: MArray s a -> Int -> Int -> ST s (MArray s a )
309320cloneM _mary@ (MArray mary# ) _off@ (I # off# ) _len@ (I # len# ) =
310- CHECK_BOUNDS (" cloneM_off" , lengthM _mary, _off)
311- CHECK_BOUNDS (" cloneM_end" , lengthM _mary, _off + _len - 1 )
321+ CHECK_BOUNDS (" cloneM_off" , unsafeLengthM _mary, _off)
322+ CHECK_BOUNDS (" cloneM_end" , unsafeLengthM _mary, _off + _len - 1 )
312323 ST $ \ s ->
313324 case cloneSmallMutableArray# mary# off# len# s of
314325 (# s', mary'# # ) -> (# s', MArray mary'# # )
0 commit comments