Skip to content

Commit a240be5

Browse files
committed
Change the representation of Generic.(Mut)Array to match (Mut)Array
1 parent 1addabb commit a240be5

File tree

5 files changed

+75
-69
lines changed

5 files changed

+75
-69
lines changed

core/src/Streamly/Internal/Data/Array/Generic.hs

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -91,15 +91,15 @@ data Array a =
9191
, arrStart :: {-# UNPACK #-}!Int
9292
-- ^ The starting index of this slice.
9393

94-
, arrLen :: {-# UNPACK #-}!Int
95-
-- ^ The length of this slice.
94+
, arrEnd :: {-# UNPACK #-}!Int
95+
-- ^ First invalid index of the array.
9696
}
9797

9898
unsafeFreeze :: MArray.MutArray a -> Array a
99-
unsafeFreeze (MArray.MutArray cont# arrS arrL _) = Array cont# arrS arrL
99+
unsafeFreeze (MArray.MutArray cont# arrS arrE _) = Array cont# arrS arrE
100100

101101
unsafeThaw :: Array a -> MArray.MutArray a
102-
unsafeThaw (Array cont# arrS arrL) = MArray.MutArray cont# arrS arrL arrL
102+
unsafeThaw (Array cont# arrS arrE) = MArray.MutArray cont# arrS arrE arrE
103103

104104
{-# NOINLINE nil #-}
105105
nil :: Array a
@@ -185,7 +185,7 @@ fromList xs = unsafePerformIO $ fromStream $ D.fromList xs
185185

186186
{-# INLINE length #-}
187187
length :: Array a -> Int
188-
length = arrLen
188+
length arr = arrEnd arr - arrStart arr
189189

190190
{-# INLINE_NORMAL reader #-}
191191
reader :: Monad m => Unfold m (Array a) a
@@ -210,14 +210,16 @@ toList arr = loop 0
210210

211211
{-# INLINE_NORMAL read #-}
212212
read :: Monad m => Array a -> Stream m a
213-
read arr@Array{..} =
214-
D.map (`getIndexUnsafe` arr) $ D.enumerateFromToIntegral 0 (arrLen - 1)
213+
read arr =
214+
D.map (`getIndexUnsafe` arr) $ D.enumerateFromToIntegral 0 (length arr - 1)
215215

216216
{-# INLINE_NORMAL readRev #-}
217217
readRev :: Monad m => Array a -> Stream m a
218-
readRev arr@Array{..} =
218+
readRev arr =
219219
D.map (`getIndexUnsafe` arr)
220220
$ D.enumerateFromThenToIntegral (arrLen - 1) (arrLen - 2) 0
221+
where
222+
arrLen = length arr
221223

222224
-------------------------------------------------------------------------------
223225
-- Elimination - using Folds
@@ -256,8 +258,8 @@ getIndexUnsafe i arr =
256258
--
257259
{-# INLINE getIndex #-}
258260
getIndex :: Int -> Array a -> Maybe a
259-
getIndex i arr@Array {..} =
260-
if i >= 0 && i < arrLen
261+
getIndex i arr =
262+
if i >= 0 && i < length arr
261263
then Just $ getIndexUnsafe i arr
262264
else Nothing
263265

@@ -284,7 +286,8 @@ createOfLast n = FL.rmapM f (RB.createOf n)
284286

285287
{-# INLINE getSliceUnsafe #-}
286288
getSliceUnsafe :: Int -> Int -> Array a -> Array a
287-
getSliceUnsafe offset len (Array cont off1 _) = Array cont (off1 + offset) len
289+
getSliceUnsafe offset len =
290+
unsafeFreeze . MArray.unsafeGetSlice offset len . unsafeThaw
288291

289292
-- XXX This is not efficient as it copies the array. We should support array
290293
-- slicing so that we can just refer to the underlying array memory instead of

core/src/Streamly/Internal/Data/MutArray/Generic.hs

Lines changed: 56 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -223,15 +223,11 @@ data MutArray a =
223223
, arrStart :: {-# UNPACK #-}!Int
224224
-- ^ The starting index of this slice.
225225

226-
, arrLen :: {-# UNPACK #-}!Int
227-
-- ^ The length of this slice.
228-
229-
, arrTrueLen :: {-# UNPACK #-}!Int
230-
-- ^ This is the true length of the array. Coincidentally, this also
231-
-- represents the first index beyond the maximum acceptable index of
232-
-- the array. This is specific to the array contents itself and not
233-
-- dependent on the slice. This value should not change and is shared
234-
-- across all the slices.
226+
, arrEnd :: {-# UNPACK #-}!Int
227+
-- ^ The index after the last initialized index.
228+
229+
, arrBound :: {-# UNPACK #-}!Int
230+
-- ^ The first invalid index.
235231
}
236232

237233
{-# INLINE bottomElement #-}
@@ -289,9 +285,9 @@ nil = new 0
289285
-- check if the index is out of bounds of the array.
290286
--
291287
-- /Pre-release/
292-
{-# INLINE putIndexUnsafeWith #-}
293-
putIndexUnsafeWith :: MonadIO m => Int -> MutableArray# RealWorld a -> a -> m ()
294-
putIndexUnsafeWith n _arrContents# x =
288+
{-# INLINE putIndexUnderlying #-}
289+
putIndexUnderlying :: MonadIO m => Int -> MutableArray# RealWorld a -> a -> m ()
290+
putIndexUnderlying n _arrContents# x =
295291
liftIO
296292
$ IO
297293
$ \s# ->
@@ -306,9 +302,9 @@ putIndexUnsafeWith n _arrContents# x =
306302
-- /Pre-release/
307303
{-# INLINE unsafePutIndex #-}
308304
unsafePutIndex, putIndexUnsafe :: forall m a. MonadIO m => Int -> MutArray a -> a -> m ()
309-
unsafePutIndex i MutArray {..} x =
310-
assert (i >= 0 && i < arrLen)
311-
(putIndexUnsafeWith (i + arrStart) arrContents# x)
305+
unsafePutIndex i arr@(MutArray {..}) x =
306+
assert (i >= 0 && i < length arr)
307+
(putIndexUnderlying (i + arrStart) arrContents# x)
312308

313309
invalidIndex :: String -> Int -> a
314310
invalidIndex label i =
@@ -322,8 +318,8 @@ invalidIndex label i =
322318
-- /Pre-release/
323319
{-# INLINE putIndex #-}
324320
putIndex :: MonadIO m => Int -> MutArray a -> a -> m ()
325-
putIndex i arr@MutArray {..} x =
326-
if i >= 0 && i < arrLen
321+
putIndex i arr x =
322+
if i >= 0 && i < length arr
327323
then unsafePutIndex i arr x
328324
else invalidIndex "putIndex" i
329325

@@ -363,8 +359,8 @@ unsafeModifyIndex i MutArray {..} f = do
363359
--
364360
-- /Pre-release/
365361
modifyIndex :: MonadIO m => Int -> MutArray a -> (a -> (a, b)) -> m b
366-
modifyIndex i arr@MutArray {..} f = do
367-
if i >= 0 && i < arrLen
362+
modifyIndex i arr f = do
363+
if i >= 0 && i < length arr
368364
then unsafeModifyIndex i arr f
369365
else invalidIndex "modifyIndex" i
370366

@@ -380,21 +376,23 @@ modifyIndex i arr@MutArray {..} f = do
380376
realloc :: MonadIO m => Int -> MutArray a -> m (MutArray a)
381377
realloc n arr = do
382378
arr1 <- new n
383-
let !newLen@(I# newLen#) = min n (arrLen arr)
379+
let !newLen@(I# newLen#) = min n (length arr)
384380
!(I# arrS#) = arrStart arr
385381
!(I# arr1S#) = arrStart arr1
386382
arrC# = arrContents# arr
387383
arr1C# = arrContents# arr1
384+
!newEnd = arrStart arr1 + newLen
385+
!newBound = arrStart arr1 + n
388386
liftIO
389387
$ IO
390388
$ \s# ->
391389
let s1# = copyMutableArray# arrC# arrS# arr1C# arr1S# newLen# s#
392-
in (# s1#, arr1 {arrLen = newLen, arrTrueLen = n} #)
390+
in (# s1#, arr1 {arrEnd = newEnd, arrBound = newBound} #)
393391

394392
reallocWith ::
395393
MonadIO m => String -> (Int -> Int) -> Int -> MutArray a -> m (MutArray a)
396394
reallocWith label sizer reqSize arr = do
397-
let oldSize = arrLen arr
395+
let oldSize = length arr
398396
newSize = sizer oldSize
399397
safeSize = max newSize (oldSize + reqSize)
400398
assert (newSize >= oldSize + reqSize || error badSize) (return ())
@@ -421,12 +419,11 @@ reallocWith label sizer reqSize arr = do
421419
--
422420
-- /Internal/
423421
{-# INLINE unsafeSnoc #-}
424-
unsafeSnoc, snocUnsafe :: MonadIO m => MutArray a -> a -> m (MutArray a)
425-
unsafeSnoc arr@MutArray {..} a = do
426-
assert (arrStart + arrLen < arrTrueLen) (return ())
427-
let arr1 = arr {arrLen = arrLen + 1}
428-
unsafePutIndex arrLen arr1 a
429-
return arr1
422+
snocUnsafe, unsafeSnoc :: MonadIO m => MutArray a -> a -> m (MutArray a)
423+
unsafeSnoc arr@(MutArray{..}) x = do
424+
let newEnd = arrEnd + 1
425+
putIndexUnderlying arrEnd arrContents# x
426+
return $ arr {arrEnd = newEnd}
430427

431428
-- NOINLINE to move it out of the way and not pollute the instruction cache.
432429
{-# NOINLINE snocWithRealloc #-}
@@ -448,7 +445,7 @@ snocWithRealloc sizer arr x = do
448445
{-# INLINE snocWith #-}
449446
snocWith :: MonadIO m => (Int -> Int) -> MutArray a -> a -> m (MutArray a)
450447
snocWith sizer arr@MutArray {..} x = do
451-
if arrStart + arrLen < arrTrueLen
448+
if arrEnd < arrBound
452449
then unsafeSnoc arr x
453450
else snocWithRealloc sizer arr x
454451

@@ -479,9 +476,9 @@ snoc = snocWith (* 2)
479476
{-# INLINE uninit #-}
480477
uninit :: MonadIO m => MutArray a -> Int -> m (MutArray a)
481478
uninit arr@MutArray{..} len =
482-
if arrStart + arrLen + len <= arrTrueLen
483-
then return $ arr {arrLen = arrLen + len}
484-
else realloc (arrLen + len) arr
479+
if arrEnd + len <= arrBound
480+
then return $ arr {arrEnd = arrEnd + len}
481+
else realloc (length arr + len) arr
485482

486483
-------------------------------------------------------------------------------
487484
-- Random reads
@@ -511,8 +508,8 @@ unsafeGetIndex n MutArray {..} = unsafeGetIndexWith arrContents# (n + arrStart)
511508
--
512509
{-# INLINE getIndex #-}
513510
getIndex :: MonadIO m => Int -> MutArray a -> m (Maybe a)
514-
getIndex i arr@MutArray {..} =
515-
if i >= 0 && i < arrLen
511+
getIndex i arr =
512+
if i >= 0 && i < length arr
516513
then Just <$> unsafeGetIndex i arr
517514
else return Nothing
518515

@@ -536,8 +533,11 @@ unsafeGetSlice, getSliceUnsafe
536533
-> MutArray a
537534
-> MutArray a
538535
unsafeGetSlice index len arr@MutArray {..} =
539-
assert (index >= 0 && len >= 0 && index + len <= arrLen)
540-
$ arr {arrStart = arrStart + index, arrLen = len}
536+
assert (index >= 0 && len >= 0 && index + len <= length arr)
537+
$ arr {arrStart = newStart, arrEnd = newEnd}
538+
where
539+
newStart = arrStart + index
540+
newEnd = newStart + len
541541

542542
-- | /O(1)/ Slice an array in constant time. Throws an error if the slice
543543
-- extends out of the array bounds.
@@ -550,11 +550,14 @@ getSlice
550550
-> MutArray a
551551
-> MutArray a
552552
getSlice index len arr@MutArray{..} =
553-
if index >= 0 && len >= 0 && index + len <= arrLen
554-
then arr {arrStart = arrStart + index, arrLen = len}
553+
if index >= 0 && len >= 0 && index + len <= length arr
554+
then arr {arrStart = newStart, arrEnd = newEnd}
555555
else error
556556
$ "getSlice: invalid slice, index "
557557
++ show index ++ " length " ++ show len
558+
where
559+
newStart = arrStart + index
560+
newEnd = newStart + len
558561

559562
-------------------------------------------------------------------------------
560563
-- to Lists and streams
@@ -568,24 +571,25 @@ getSlice index len arr@MutArray{..} =
568571
-- /Pre-release/
569572
{-# INLINE toList #-}
570573
toList :: MonadIO m => MutArray a -> m [a]
571-
toList arr@MutArray{..} = mapM (`unsafeGetIndex` arr) [0 .. (arrLen - 1)]
574+
toList arr = mapM (`unsafeGetIndex` arr) [0 .. (length arr - 1)]
572575

573576
-- | Generates a stream from the elements of a @MutArray@.
574577
--
575578
-- >>> read = Stream.unfold MutArray.reader
576579
--
577580
{-# INLINE_NORMAL read #-}
578581
read :: MonadIO m => MutArray a -> D.Stream m a
579-
read arr@MutArray{..} =
580-
D.mapM (`unsafeGetIndex` arr) $ D.enumerateFromToIntegral 0 (arrLen - 1)
582+
read arr =
583+
D.mapM (`unsafeGetIndex` arr) $ D.enumerateFromToIntegral 0 (length arr - 1)
581584

582585
-- Check equivalence with StreamK.fromStream . toStreamD and remove
583586
{-# INLINE toStreamK #-}
584587
toStreamK :: MonadIO m => MutArray a -> K.StreamK m a
585-
toStreamK arr@MutArray{..} = K.unfoldrM step 0
588+
toStreamK arr = K.unfoldrM step 0
586589

587590
where
588591

592+
arrLen = length arr
589593
step i
590594
| i == arrLen = return Nothing
591595
| otherwise = do
@@ -594,9 +598,11 @@ toStreamK arr@MutArray{..} = K.unfoldrM step 0
594598

595599
{-# INLINE_NORMAL readRev #-}
596600
readRev :: MonadIO m => MutArray a -> D.Stream m a
597-
readRev arr@MutArray{..} =
601+
readRev arr =
598602
D.mapM (`unsafeGetIndex` arr)
599603
$ D.enumerateFromThenToIntegral (arrLen - 1) (arrLen - 2) 0
604+
where
605+
arrLen = length arr
600606

601607
-------------------------------------------------------------------------------
602608
-- Folds
@@ -775,7 +781,7 @@ chunksOf n (D.Stream step state) =
775781
r <- step (adaptState gst) st
776782
case r of
777783
D.Yield x s -> do
778-
putIndexUnsafeWith end contents x
784+
putIndexUnderlying end contents x
779785
let end1 = end + 1
780786
return $
781787
if end1 >= bound
@@ -811,11 +817,11 @@ producerWith liftio = Producer step inject extract
811817

812818
{-# INLINE extract #-}
813819
extract (arr, i) =
814-
return $ arr {arrStart = arrStart arr + i, arrLen = arrLen arr - i}
820+
return $ arr {arrStart = arrStart arr + i}
815821

816822
{-# INLINE_LATE step #-}
817823
step (arr, i)
818-
| assert (arrLen arr >= 0) (i == arrLen arr) = return D.Stop
824+
| i == length arr = return D.Stop
819825
step (arr, i) = do
820826
x <- liftio $ unsafeGetIndex i arr
821827
return $ D.Yield x (arr, i + 1)
@@ -842,8 +848,8 @@ reader = Producer.simplify producer
842848
unsafePutSlice, putSliceUnsafe :: MonadIO m =>
843849
MutArray a -> Int -> MutArray a -> Int -> Int -> m ()
844850
unsafePutSlice src srcStart dst dstStart len = liftIO $ do
845-
assertM(len <= arrLen dst)
846-
assertM(len <= arrLen src)
851+
assertM(len <= length dst)
852+
assertM(len <= length src)
847853
let !(I# srcStart#) = srcStart + arrStart src
848854
!(I# dstStart#) = dstStart + arrStart dst
849855
!(I# len#) = len
@@ -856,7 +862,7 @@ unsafePutSlice src srcStart dst dstStart len = liftIO $ do
856862
{-# INLINE clone #-}
857863
clone :: MonadIO m => MutArray a -> m (MutArray a)
858864
clone src = do
859-
let len = arrLen src
865+
let len = length src
860866
dst <- new len
861867
unsafePutSlice src 0 dst 0 len
862868
return dst
@@ -867,7 +873,7 @@ clone src = do
867873

868874
{-# INLINE length #-}
869875
length :: MutArray a -> Int
870-
length = arrLen
876+
length arr = arrEnd arr - arrStart arr
871877

872878
-------------------------------------------------------------------------------
873879
-- Equality

core/src/Streamly/Internal/Data/MutArray/Type.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -471,11 +471,11 @@ data MutArray a =
471471
MutArray
472472
{ arrContents :: {-# UNPACK #-} !MutByteArray
473473
, arrStart :: {-# UNPACK #-} !Int -- ^ index into arrContents
474-
, arrEnd :: {-# UNPACK #-} !Int -- ^ index into arrContents
474+
, arrEnd :: {-# UNPACK #-} !Int -- ^ index into arrContents
475475
-- Represents the first invalid index of
476476
-- the array.
477477
-- XXX rename to arrCapacity to be consistent with ring.
478-
, arrBound :: {-# UNPACK #-} !Int -- ^ first invalid index of arrContents.
478+
, arrBound :: {-# UNPACK #-} !Int -- ^ first invalid index of arrContents.
479479
}
480480

481481
-------------------------------------------------------------------------------

core/src/Streamly/Internal/Data/ParserK/Type.hs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -647,16 +647,13 @@ adaptCGWith pstep initial extract cont !offset0 !usedCount !input = do
647647
where
648648

649649
{-# NOINLINE parseContChunk #-}
650-
parseContChunk !count !offset !state arr@(GenArr.Array contents start len) = do
650+
parseContChunk !count !offset !state arr@(GenArr.Array contents start end) = do
651651
if offset >= 0
652652
then go SPEC (start + offset) state
653653
else return $ Continue offset (parseCont count state)
654654

655655
where
656656

657-
{-# INLINE end #-}
658-
end = start + len
659-
660657
{-# INLINE onDone #-}
661658
onDone n b =
662659
assert (n <= GenArr.length arr)
@@ -685,7 +682,7 @@ adaptCGWith pstep initial extract cont !offset0 !usedCount !input = do
685682
else constr pos pst
686683

687684
go !_ !cur !pst | cur >= end =
688-
onContinue len pst
685+
onContinue (end - start) pst
689686
go !_ !cur !pst = do
690687
let !x = unsafeInlineIO $ GenArr.unsafeGetIndexWith contents cur
691688
pRes <- pstep pst x

core/src/Streamly/Internal/Data/RingArray/Generic.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ toMutArray adj n RingArray{..} =
143143
end = idx + len
144144
if end <= ringMax
145145
then
146-
return $ ringArr { arrStart = idx, arrLen = len }
146+
return $ ringArr { arrStart = idx, arrEnd = end }
147147
else do
148148
-- XXX Just swap the elements in the existing ring and return the
149149
-- same array without reallocation.

0 commit comments

Comments
 (0)