@@ -36,7 +36,6 @@ module Data.HashMap.Array
36
36
, unsafeThaw
37
37
, unsafeSameArray
38
38
, run
39
- , run2
40
39
, copy
41
40
, copyM
42
41
@@ -59,6 +58,11 @@ import Control.Applicative (Applicative (..), (<$>))
59
58
import Control.Applicative (liftA2 )
60
59
import Control.DeepSeq
61
60
import GHC.Exts (Int (.. ), Int #, reallyUnsafePtrEquality #, tagToEnum #, unsafeCoerce #, State #)
61
+ #if MIN_VERSION_base(4,10,0)
62
+ import GHC.Exts (runRW #)
63
+ #elif MIN_VERSION_base(4,9,0)
64
+ import GHC.Base (runRW #)
65
+ #endif
62
66
import GHC.ST (ST (.. ))
63
67
import Control.Monad.ST (stToIO )
64
68
@@ -256,13 +260,17 @@ new_ :: Int -> ST s (MArray s a)
256
260
new_ n = new n undefinedElem
257
261
258
262
singleton :: a -> Array a
259
- singleton x = runST (singletonM x)
263
+ singleton x = run (singletonMut x)
260
264
{-# INLINE singleton #-}
261
265
262
266
singletonM :: a -> ST s (Array a )
263
267
singletonM x = new 1 x >>= unsafeFreeze
264
268
{-# INLINE singletonM #-}
265
269
270
+ singletonMut :: a -> ST s (MArray s a )
271
+ singletonMut x = new 1 x
272
+ {-# INLINE singletonMut #-}
273
+
266
274
pair :: a -> a -> Array a
267
275
pair x y = run $ do
268
276
ary <- new 2 x
@@ -314,15 +322,19 @@ unsafeThaw ary
314
322
{-# INLINE unsafeThaw #-}
315
323
316
324
run :: (forall s . ST s (MArray s e )) -> Array e
317
- run act = runST $ act >>= unsafeFreeze
325
+ #if MIN_VERSION_base(4,9,0)
326
+ -- GHC can't unbox across the runRW# boundary, so we apply the Array constructor
327
+ -- on the outside.
328
+ run (ST act) =
329
+ case runRW# $ \ s ->
330
+ case act s of { (# s', MArray mary # ) ->
331
+ unsafeFreezeArray# mary s' } of
332
+ (# _, ary # ) -> Array ary
333
+ #else
334
+ run act = runST (act >>= unsafeFreeze)
335
+ #endif
318
336
{-# INLINE run #-}
319
337
320
- run2 :: (forall s . ST s (MArray s e , a )) -> (Array e , a )
321
- run2 k = runST (do
322
- (marr,b) <- k
323
- arr <- unsafeFreeze marr
324
- return (arr,b))
325
-
326
338
-- | Unsafely copy the elements of an array. Array bounds are not checked.
327
339
copy :: Array e -> Int -> MArray s e -> Int -> Int -> ST s ()
328
340
copy ! src ! _sidx@ (I # sidx# ) ! dst ! _didx@ (I # didx# ) _n@ (I # n# ) =
@@ -357,34 +369,38 @@ trim mary n = cloneM mary 0 n >>= unsafeFreeze
357
369
-- | /O(n)/ Insert an element at the given position in this array,
358
370
-- increasing its size by one.
359
371
insert :: Array e -> Int -> e -> Array e
360
- insert ary idx b = runST (insertM ary idx b)
372
+ insert ary idx b = run (insertMut ary idx b)
361
373
{-# INLINE insert #-}
362
374
363
375
-- | /O(n)/ Insert an element at the given position in this array,
364
376
-- increasing its size by one.
365
377
insertM :: Array e -> Int -> e -> ST s (Array e )
366
- insertM ary idx b =
378
+ insertM ary idx b = insertMut ary idx b >>= unsafeFreeze
379
+ {-# INLINE insertM #-}
380
+
381
+ insertMut :: Array e -> Int -> e -> ST s (MArray s e )
382
+ insertMut ary idx b =
367
383
CHECK_BOUNDS (" insertM" , count + 1 , idx)
368
384
do mary <- new_ (count+ 1 )
369
385
copy ary 0 mary 0 idx
370
386
write mary idx b
371
387
copy ary idx mary (idx+ 1 ) (count- idx)
372
- unsafeFreeze mary
388
+ return mary
373
389
where ! count = length ary
374
- {-# INLINE insertM #-}
390
+ {-# INLINE insertMut #-}
375
391
376
392
-- | /O(n)/ Update the element at the given position in this array.
377
393
update :: Array e -> Int -> e -> Array e
378
- update ary idx b = runST (updateM ary idx b)
394
+ update ary idx b = run (updateM ary idx b)
379
395
{-# INLINE update #-}
380
396
381
397
-- | /O(n)/ Update the element at the given position in this array.
382
- updateM :: Array e -> Int -> e -> ST s (Array e )
398
+ updateM :: Array e -> Int -> e -> ST s (MArray s e )
383
399
updateM ary idx b =
384
400
CHECK_BOUNDS (" updateM" , count, idx)
385
401
do mary <- thaw ary 0 count
386
402
write mary idx b
387
- unsafeFreeze mary
403
+ return mary
388
404
where ! count = length ary
389
405
{-# INLINE updateM #-}
390
406
@@ -442,18 +458,18 @@ thaw !ary !_o@(I# o#) !n@(I# n#) =
442
458
-- | /O(n)/ Delete an element at the given position in this array,
443
459
-- decreasing its size by one.
444
460
delete :: Array e -> Int -> Array e
445
- delete ary idx = runST (deleteM ary idx)
461
+ delete ary idx = run (deleteM ary idx)
446
462
{-# INLINE delete #-}
447
463
448
464
-- | /O(n)/ Delete an element at the given position in this array,
449
465
-- decreasing its size by one.
450
- deleteM :: Array e -> Int -> ST s (Array e )
466
+ deleteM :: Array e -> Int -> ST s (MArray s e )
451
467
deleteM ary idx = do
452
468
CHECK_BOUNDS (" deleteM" , count, idx)
453
469
do mary <- new_ (count- 1 )
454
470
copy ary 0 mary 0 idx
455
471
copy ary (idx+ 1 ) mary idx (count- (idx+ 1 ))
456
- unsafeFreeze mary
472
+ return mary
457
473
where ! count = length ary
458
474
{-# INLINE deleteM #-}
459
475
@@ -463,9 +479,10 @@ map f = \ ary ->
463
479
in run $ do
464
480
mary <- new_ n
465
481
go ary mary 0 n
482
+ return mary
466
483
where
467
484
go ary mary i n
468
- | i >= n = return mary
485
+ | i >= n = return ()
469
486
| otherwise = do
470
487
x <- indexM ary i
471
488
write mary i $ f x
@@ -479,9 +496,10 @@ map' f = \ ary ->
479
496
in run $ do
480
497
mary <- new_ n
481
498
go ary mary 0 n
499
+ return mary
482
500
where
483
501
go ary mary i n
484
- | i >= n = return mary
502
+ | i >= n = return ()
485
503
| otherwise = do
486
504
x <- indexM ary i
487
505
write mary i $! f x
@@ -494,8 +512,9 @@ fromList n xs0 =
494
512
run $ do
495
513
mary <- new_ n
496
514
go xs0 mary 0
515
+ return mary
497
516
where
498
- go [] ! mary ! _ = return mary
517
+ go [] ! _ ! _ = return ()
499
518
go (x: xs) mary i = do write mary i x
500
519
go xs mary (i+ 1 )
501
520
0 commit comments