@@ -73,7 +73,7 @@ module Data.HashMap.Internal.Array
7373
7474import Control.Applicative (liftA2 )
7575import Control.DeepSeq (NFData (.. ))
76- import GHC.Exts (Int (.. ), Int #, reallyUnsafePtrEquality #, tagToEnum #, unsafeCoerce #, State #)
76+ import GHC.Exts (Int (.. ), reallyUnsafePtrEquality #, tagToEnum #, unsafeCoerce #)
7777import GHC.ST (ST (.. ))
7878import Control.Monad.ST (runST , stToIO )
7979
@@ -94,72 +94,6 @@ import qualified Control.DeepSeq as NF
9494
9595import Control.Monad ((>=>) )
9696
97-
98- type Array # a = SmallArray # a
99- type MutableArray # a = SmallMutableArray # a
100-
101- newArray# :: Int # -> a -> State # d -> (# State # d , SmallMutableArray # d a # )
102- newArray# = newSmallArray#
103-
104- unsafeFreezeArray# :: SmallMutableArray # d a
105- -> State # d -> (# State # d, SmallArray # a # )
106- unsafeFreezeArray# = unsafeFreezeSmallArray#
107-
108- readArray# :: SmallMutableArray # d a
109- -> Int # -> State # d -> (# State # d, a # )
110- readArray# = readSmallArray#
111-
112- writeArray# :: SmallMutableArray # d a
113- -> Int # -> a -> State # d -> State # d
114- writeArray# = writeSmallArray#
115-
116- indexArray# :: SmallArray # a -> Int # -> (# a # )
117- indexArray# = indexSmallArray#
118-
119- unsafeThawArray# :: SmallArray # a
120- -> State # d -> (# State # d, SmallMutableArray # d a # )
121- unsafeThawArray# = unsafeThawSmallArray#
122-
123- sizeofArray# :: SmallArray # a -> Int #
124- sizeofArray# = sizeofSmallArray#
125-
126- copyArray# :: SmallArray # a
127- -> Int #
128- -> SmallMutableArray # d a
129- -> Int #
130- -> Int #
131- -> State # d
132- -> State # d
133- copyArray# = copySmallArray#
134-
135- cloneMutableArray# :: SmallMutableArray # s a
136- -> Int #
137- -> Int #
138- -> State # s
139- -> (# State # s, SmallMutableArray # s a # )
140- cloneMutableArray# = cloneSmallMutableArray#
141-
142- thawArray# :: SmallArray # a
143- -> Int #
144- -> Int #
145- -> State # d
146- -> (# State # d, SmallMutableArray # d a # )
147- thawArray# = thawSmallArray#
148-
149- sizeofMutableArray# :: SmallMutableArray # s a -> Int #
150- sizeofMutableArray# = sizeofSmallMutableArray#
151-
152- copyMutableArray# :: SmallMutableArray # d a
153- -> Int #
154- -> SmallMutableArray # d a
155- -> Int #
156- -> Int #
157- -> State # d
158- -> State # d
159- copyMutableArray# = copySmallMutableArray#
160-
161- ------------------------------------------------------------------------
162-
16397#if defined(ASSERTS)
16498-- This fugly hack is brought by GHC's apparent reluctance to deal
16599-- with MagicHash and UnboxedTuples when inferring types. Eek!
@@ -179,7 +113,7 @@ if not ((_lhs_) _op_ (_rhs_)) then error ("Data.HashMap.Internal.Array." ++ (_fu
179113#endif
180114
181115data Array a = Array {
182- unArray :: ! (Array # a )
116+ unArray :: ! (SmallArray # a )
183117 }
184118
185119instance Show a => Show (Array a ) where
@@ -207,15 +141,15 @@ sameArray1 eq !xs0 !ys0
207141 ! lenys = length ys0
208142
209143length :: Array a -> Int
210- length ary = I # (sizeofArray # (unArray ary))
144+ length ary = I # (sizeofSmallArray # (unArray ary))
211145{-# INLINE length #-}
212146
213147data MArray s a = MArray {
214- unMArray :: ! (MutableArray # s a )
148+ unMArray :: ! (SmallMutableArray # s a )
215149 }
216150
217151lengthM :: MArray s a -> Int
218- lengthM mary = I # (sizeofMutableArray # (unMArray mary))
152+ lengthM mary = I # (sizeofSmallMutableArray # (unMArray mary))
219153{-# INLINE lengthM #-}
220154
221155------------------------------------------------------------------------
@@ -258,7 +192,7 @@ new :: Int -> a -> ST s (MArray s a)
258192new _n@ (I # n# ) b =
259193 CHECK_GT (" new" ,_n,(0 :: Int ))
260194 ST $ \ s ->
261- case newArray # n# b s of
195+ case newSmallArray # n# b s of
262196 (# s', ary # ) -> (# s', MArray ary # )
263197{-# INLINE new #-}
264198
@@ -283,43 +217,43 @@ pair x y = run $ do
283217read :: MArray s a -> Int -> ST s a
284218read ary _i@ (I # i# ) = ST $ \ s ->
285219 CHECK_BOUNDS (" read" , lengthM ary, _i)
286- readArray # (unMArray ary) i# s
220+ readSmallArray # (unMArray ary) i# s
287221{-# INLINE read #-}
288222
289223write :: MArray s a -> Int -> a -> ST s ()
290224write ary _i@ (I # i# ) b = ST $ \ s ->
291225 CHECK_BOUNDS (" write" , lengthM ary, _i)
292- case writeArray # (unMArray ary) i# b s of
226+ case writeSmallArray # (unMArray ary) i# b s of
293227 s' -> (# s' , () # )
294228{-# INLINE write #-}
295229
296230index :: Array a -> Int -> a
297231index ary _i@ (I # i# ) =
298232 CHECK_BOUNDS (" index" , length ary, _i)
299- case indexArray # (unArray ary) i# of (# b # ) -> b
233+ case indexSmallArray # (unArray ary) i# of (# b # ) -> b
300234{-# INLINE index #-}
301235
302236index# :: Array a -> Int -> (# a # )
303237index# ary _i@ (I # i# ) =
304238 CHECK_BOUNDS (" index#" , length ary, _i)
305- indexArray # (unArray ary) i#
239+ indexSmallArray # (unArray ary) i#
306240{-# INLINE index# #-}
307241
308242indexM :: Array a -> Int -> ST s a
309243indexM ary _i@ (I # i# ) =
310244 CHECK_BOUNDS (" indexM" , length ary, _i)
311- case indexArray # (unArray ary) i# of (# b # ) -> return b
245+ case indexSmallArray # (unArray ary) i# of (# b # ) -> return b
312246{-# INLINE indexM #-}
313247
314248unsafeFreeze :: MArray s a -> ST s (Array a )
315249unsafeFreeze mary
316- = ST $ \ s -> case unsafeFreezeArray # (unMArray mary) s of
250+ = ST $ \ s -> case unsafeFreezeSmallArray # (unMArray mary) s of
317251 (# s', ary # ) -> (# s', Array ary # )
318252{-# INLINE unsafeFreeze #-}
319253
320254unsafeThaw :: Array a -> ST s (MArray s a )
321255unsafeThaw ary
322- = ST $ \ s -> case unsafeThawArray # (unArray ary) s of
256+ = ST $ \ s -> case unsafeThawSmallArray # (unArray ary) s of
323257 (# s', mary # ) -> (# s', MArray mary # )
324258{-# INLINE unsafeThaw #-}
325259
@@ -333,7 +267,7 @@ copy !src !_sidx@(I# sidx#) !dst !_didx@(I# didx#) _n@(I# n#) =
333267 CHECK_LE (" copy" , _sidx + _n, length src)
334268 CHECK_LE (" copy" , _didx + _n, lengthM dst)
335269 ST $ \ s# ->
336- case copyArray # (unArray src) sidx# (unMArray dst) didx# n# s# of
270+ case copySmallArray # (unArray src) sidx# (unMArray dst) didx# n# s# of
337271 s2 -> (# s2, () # )
338272
339273-- | Unsafely copy the elements of an array. Array bounds are not checked.
@@ -342,15 +276,15 @@ copyM !src !_sidx@(I# sidx#) !dst !_didx@(I# didx#) _n@(I# n#) =
342276 CHECK_BOUNDS (" copyM: src" , lengthM src, _sidx + _n - 1 )
343277 CHECK_BOUNDS (" copyM: dst" , lengthM dst, _didx + _n - 1 )
344278 ST $ \ s# ->
345- case copyMutableArray # (unMArray src) sidx# (unMArray dst) didx# n# s# of
279+ case copySmallMutableArray # (unMArray src) sidx# (unMArray dst) didx# n# s# of
346280 s2 -> (# s2, () # )
347281
348282cloneM :: MArray s a -> Int -> Int -> ST s (MArray s a )
349283cloneM _mary@ (MArray mary# ) _off@ (I # off# ) _len@ (I # len# ) =
350284 CHECK_BOUNDS (" cloneM_off" , lengthM _mary, _off - 1 )
351285 CHECK_BOUNDS (" cloneM_end" , lengthM _mary, _off + _len - 1 )
352286 ST $ \ s ->
353- case cloneMutableArray # mary# off# len# s of
287+ case cloneSmallMutableArray # mary# off# len# s of
354288 (# s', mary'# # ) -> (# s', MArray mary'# # )
355289
356290-- | Create a new array of the @n@ first elements of @mary@.
@@ -476,7 +410,7 @@ undefinedElem = error "Data.HashMap.Internal.Array: Undefined element"
476410thaw :: Array e -> Int -> Int -> ST s (MArray s e )
477411thaw ! ary ! _o@ (I # o# ) _n@ (I # n# ) =
478412 CHECK_LE (" thaw" , _o + _n, length ary)
479- ST $ \ s -> case thawArray # (unArray ary) o# n# s of
413+ ST $ \ s -> case thawSmallArray # (unArray ary) o# n# s of
480414 (# s2, mary# # ) -> (# s2, MArray mary# # )
481415{-# INLINE thaw #-}
482416
@@ -543,7 +477,7 @@ fromList n xs0 =
543477toList :: Array a -> [a ]
544478toList = foldr (:) []
545479
546- newtype STA a = STA { _runSTA :: forall s . MutableArray # s a -> ST s (Array a )}
480+ newtype STA a = STA { _runSTA :: forall s . SmallMutableArray # s a -> ST s (Array a )}
547481
548482runSTA :: Int -> STA a -> Array a
549483runSTA ! n (STA m) = runST $ new_ n >>= \ (MArray ar) -> m ar
0 commit comments