Skip to content

Commit 2cac9eb

Browse files
committed
Remove capacity field from MutArray
1 parent 01fa8dd commit 2cac9eb

File tree

5 files changed

+57
-44
lines changed

5 files changed

+57
-44
lines changed

core/src/Streamly/Internal/Data/Array/Mut/Type.hs

Lines changed: 51 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -239,6 +239,7 @@ import Streamly.Internal.Data.Unboxed
239239
, pokeWith
240240
, sizeOf
241241
, touch
242+
, sizeOfMutableByteArray
242243
)
243244
import GHC.Base
244245
( IO(..)
@@ -269,6 +270,8 @@ import qualified Prelude
269270
import Prelude hiding
270271
(length, foldr, read, unlines, splitAt, reverse, truncate)
271272

273+
import System.IO.Unsafe
274+
272275
#include "DocTestDataMutArray.hs"
273276

274277
-------------------------------------------------------------------------------
@@ -343,7 +346,6 @@ data MutArray a =
343346
, arrEnd :: {-# UNPACK #-} !Int -- ^ index into arrContents
344347
-- Represents the first invalid index of
345348
-- the array.
346-
, arrBound :: {-# UNPACK #-} !Int -- ^ first invalid index of arrContents.
347349
}
348350

349351
-------------------------------------------------------------------------------
@@ -398,15 +400,14 @@ newArrayWith alloc alignSize count = do
398400
{ arrContents = contents
399401
, arrStart = 0
400402
, arrEnd = 0
401-
, arrBound = size
402403
}
403404

404405
nil ::
405406
#ifdef DEVBUILD
406407
Unbox a =>
407408
#endif
408409
MutArray a
409-
nil = MutArray Unboxed.nil 0 0 0
410+
nil = MutArray Unboxed.nil 0 0
410411

411412

412413
-- | Allocates a pinned empty array that can hold 'count' items. The memory of
@@ -426,7 +427,6 @@ newPinnedBytes bytes = do
426427
{ arrContents = contents
427428
, arrStart = 0
428429
, arrEnd = 0
429-
, arrBound = bytes
430430
}
431431

432432
-- | Like 'newArrayWith' but using an allocator is a pinned memory allocator and
@@ -725,6 +725,7 @@ roundDownTo elemSize size = size - (size `mod` elemSize)
725725
{-# NOINLINE reallocExplicit #-}
726726
reallocExplicit :: Int -> Int -> MutArray a -> IO (MutArray a)
727727
reallocExplicit elemSize newCapacityInBytes MutArray{..} = do
728+
arrBound <- sizeOfMutableByteArray arrContents
728729
assertM(arrEnd <= arrBound)
729730

730731
-- Allocate new array
@@ -749,7 +750,6 @@ reallocExplicit elemSize newCapacityInBytes MutArray{..} = do
749750
{ arrStart = 0
750751
, arrContents = contents
751752
, arrEnd = newLenInBytes
752-
, arrBound = newCapInBytes
753753
}
754754

755755
-- | @realloc newCapacity array@ reallocates the array to the specified
@@ -839,6 +839,7 @@ resizeExp nElems arr@MutArray{..} = do
839839
{-# INLINE rightSize #-}
840840
rightSize :: forall m a. (MonadIO m, Unbox a) => MutArray a -> m (MutArray a)
841841
rightSize arr@MutArray{..} = do
842+
arrBound <- liftIO $ sizeOfMutableByteArray arrContents
842843
assert (arrEnd <= arrBound) (return ())
843844
let start = arrStart
844845
len = arrEnd - start
@@ -871,6 +872,7 @@ rightSize arr@MutArray{..} = do
871872
{-# INLINE snocNewEnd #-}
872873
snocNewEnd :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m (MutArray a)
873874
snocNewEnd newEnd arr@MutArray{..} x = liftIO $ do
875+
arrBound <- liftIO $ sizeOfMutableByteArray arrContents
874876
assert (newEnd <= arrBound) (return ())
875877
pokeWith arrContents arrEnd x
876878
return $ arr {arrEnd = newEnd}
@@ -894,6 +896,7 @@ snocMay :: forall m a. (MonadIO m, Unbox a) =>
894896
MutArray a -> a -> m (Maybe (MutArray a))
895897
snocMay arr@MutArray{..} x = liftIO $ do
896898
let newEnd = INDEX_NEXT(arrEnd,a)
899+
arrBound <- sizeOfMutableByteArray arrContents
897900
if newEnd <= arrBound
898901
then Just <$> snocNewEnd newEnd arr x
899902
else return Nothing
@@ -930,7 +933,8 @@ snocWith :: forall m a. (MonadIO m, Unbox a) =>
930933
-> m (MutArray a)
931934
snocWith allocSize arr x = liftIO $ do
932935
let newEnd = INDEX_NEXT(arrEnd arr,a)
933-
if newEnd <= arrBound arr
936+
arrBound <- sizeOfMutableByteArray (arrContents arr)
937+
if newEnd <= arrBound
934938
then snocNewEnd newEnd arr x
935939
else snocWithRealloc allocSize arr x
936940

@@ -1026,15 +1030,15 @@ getIndicesD liftio (D.Stream stepi sti) = Unfold step inject
10261030

10271031
where
10281032

1029-
inject (MutArray contents start end _) =
1033+
inject (MutArray contents start end) =
10301034
return $ GetIndicesState contents start end sti
10311035

10321036
{-# INLINE_LATE step #-}
10331037
step (GetIndicesState contents start end st) = do
10341038
r <- stepi defState st
10351039
case r of
10361040
D.Yield i s -> do
1037-
x <- liftio $ getIndex i (MutArray contents start end undefined)
1041+
x <- liftio $ getIndex i (MutArray contents start end)
10381042
return $ D.Yield x (GetIndicesState contents start end s)
10391043
D.Skip s -> return $ D.Skip (GetIndicesState contents start end s)
10401044
D.Stop -> return D.Stop
@@ -1062,14 +1066,14 @@ getSliceUnsafe :: forall a. Unbox a
10621066
-> Int -- ^ length of the slice
10631067
-> MutArray a
10641068
-> MutArray a
1065-
getSliceUnsafe index len (MutArray contents start e _) =
1069+
getSliceUnsafe index len (MutArray contents start e) =
10661070
let fp1 = INDEX_OF(start,index,a)
10671071
end = fp1 + (len * SIZE_OF(a))
10681072
in assert
10691073
(index >= 0 && len >= 0 && end <= e)
10701074
-- Note: In a slice we always use bound = end so that the slice
10711075
-- user cannot overwrite elements beyond the end of the slice.
1072-
(MutArray contents fp1 end end)
1076+
(MutArray contents fp1 end)
10731077

10741078
-- | /O(1)/ Slice an array in constant time. Throws an error if the slice
10751079
-- extends out of the array bounds.
@@ -1081,13 +1085,13 @@ getSlice :: forall a. Unbox a =>
10811085
-> Int -- ^ length of the slice
10821086
-> MutArray a
10831087
-> MutArray a
1084-
getSlice index len (MutArray contents start e _) =
1088+
getSlice index len (MutArray contents start e) =
10851089
let fp1 = INDEX_OF(start,index,a)
10861090
end = fp1 + (len * SIZE_OF(a))
10871091
in if index >= 0 && len >= 0 && end <= e
10881092
-- Note: In a slice we always use bound = end so that the slice user
10891093
-- cannot overwrite elements beyond the end of the slice.
1090-
then MutArray contents fp1 end end
1094+
then MutArray contents fp1 end
10911095
else error
10921096
$ "getSlice: invalid slice, index "
10931097
++ show index ++ " length " ++ show len
@@ -1138,8 +1142,8 @@ partitionBy f arr@MutArray{..} = liftIO $ do
11381142
then return (arr, arr)
11391143
else do
11401144
ptr <- go arrStart (INDEX_PREV(arrEnd,a))
1141-
let pl = MutArray arrContents arrStart ptr ptr
1142-
pr = MutArray arrContents ptr arrEnd arrEnd
1145+
let pl = MutArray arrContents arrStart ptr
1146+
pr = MutArray arrContents ptr arrEnd
11431147
return (pl, pr)
11441148

11451149
where
@@ -1259,14 +1263,19 @@ length arr =
12591263
blen = byteLength arr
12601264
in assert (blen `mod` elemSize == 0) (blen `div` elemSize)
12611265

1266+
{-# INLINE getArrSizeUnsafe #-}
1267+
getArrSizeUnsafe :: MutableByteArray -> Int
1268+
getArrSizeUnsafe = unsafePerformIO . sizeOfMutableByteArray
1269+
12621270
-- | Get the total capacity of an array. An array may have space reserved
12631271
-- beyond the current used length of the array.
12641272
--
12651273
-- /Pre-release/
12661274
{-# INLINE byteCapacity #-}
12671275
byteCapacity :: MutArray a -> Int
12681276
byteCapacity MutArray{..} =
1269-
let len = arrBound - arrStart
1277+
let arrBound = getArrSizeUnsafe arrContents
1278+
len = arrBound - arrStart
12701279
in assert (len >= 0) len
12711280

12721281
-- | The remaining capacity in the array for appending more elements without
@@ -1276,7 +1285,8 @@ byteCapacity MutArray{..} =
12761285
{-# INLINE bytesFree #-}
12771286
bytesFree :: MutArray a -> Int
12781287
bytesFree MutArray{..} =
1279-
let n = arrBound - arrEnd
1288+
let arrBound = getArrSizeUnsafe arrContents
1289+
n = arrBound - arrEnd
12801290
in assert (n >= 0) n
12811291

12821292
-------------------------------------------------------------------------------
@@ -1315,7 +1325,8 @@ chunksOf n (D.Stream step state) =
13151325
error $ "Streamly.Internal.Data.MutArray.Mut.Type.chunksOf: "
13161326
++ "the size of arrays [" ++ show n
13171327
++ "] must be a natural number"
1318-
(MutArray contents start end bound :: MutArray a) <- liftIO $ newPinned n
1328+
(MutArray contents start end :: MutArray a) <- liftIO $ newPinned n
1329+
bound <- liftIO $ sizeOfMutableByteArray contents
13191330
return $ D.Skip (GroupBuffer st contents start end bound)
13201331

13211332
step' gst (GroupBuffer st contents start end bound) = do
@@ -1329,15 +1340,15 @@ chunksOf n (D.Stream step state) =
13291340
then D.Skip
13301341
(GroupYield
13311342
contents start end1 bound (GroupStart s))
1332-
else D.Skip (GroupBuffer s contents start end1 bound)
1343+
else D.Skip (GroupBuffer s contents start end1 bound)
13331344
D.Skip s ->
13341345
return $ D.Skip (GroupBuffer s contents start end bound)
13351346
D.Stop ->
13361347
return
13371348
$ D.Skip (GroupYield contents start end bound GroupFinish)
13381349

1339-
step' _ (GroupYield contents start end bound next) =
1340-
return $ D.Yield (MutArray contents start end bound) next
1350+
step' _ (GroupYield contents start end _bound next) =
1351+
return $ D.Yield (MutArray contents start end) next
13411352

13421353
step' _ GroupFinish = return D.Stop
13431354

@@ -1428,15 +1439,15 @@ data ArrayUnsafe a = ArrayUnsafe
14281439
{-# UNPACK #-} !Int -- index 2
14291440

14301441
toArrayUnsafe :: MutArray a -> ArrayUnsafe a
1431-
toArrayUnsafe (MutArray contents start end _) = ArrayUnsafe contents start end
1442+
toArrayUnsafe (MutArray contents start end) = ArrayUnsafe contents start end
14321443

14331444
fromArrayUnsafe ::
14341445
#ifdef DEVBUILD
14351446
Unbox a =>
14361447
#endif
14371448
ArrayUnsafe a -> MutArray a
14381449
fromArrayUnsafe (ArrayUnsafe contents start end) =
1439-
MutArray contents start end end
1450+
MutArray contents start end
14401451

14411452
{-# INLINE_NORMAL producerWith #-}
14421453
producerWith ::
@@ -1477,7 +1488,7 @@ readerRevWith ::
14771488
readerRevWith liftio = Unfold step inject
14781489
where
14791490

1480-
inject (MutArray contents start end _) =
1491+
inject (MutArray contents start end) =
14811492
let p = INDEX_PREV(end,a)
14821493
in return $ ArrayUnsafe contents start p
14831494

@@ -1668,7 +1679,8 @@ writeAppendNUnsafe n action =
16681679

16691680
initial = do
16701681
assert (n >= 0) (return ())
1671-
arr@(MutArray _ _ end bound) <- action
1682+
arr@(MutArray _ _ end) <- action
1683+
bound <- liftIO $ sizeOfMutableByteArray (arrContents arr)
16721684
let free = bound - end
16731685
needed = n * SIZE_OF(a)
16741686
-- XXX We can also reallocate if the array has too much free space,
@@ -1789,8 +1801,9 @@ writeRevNWithUnsafe alloc n = fromArrayUnsafe <$> FL.foldlM' step initial
17891801

17901802
where
17911803

1792-
toArrayUnsafeRev (MutArray contents _ _ bound) =
1793-
ArrayUnsafe contents bound bound
1804+
toArrayUnsafeRev arr@(MutArray contents _ _) =
1805+
let bound = getArrSizeUnsafe (arrContents arr)
1806+
in ArrayUnsafe contents bound bound
17941807

17951808
initial = toArrayUnsafeRev <$> alloc (max n 0)
17961809

@@ -1887,8 +1900,8 @@ writeWith elemCount =
18871900
when (elemCount < 0) $ error "writeWith: elemCount is negative"
18881901
liftIO $ newPinned elemCount
18891902

1890-
step arr@(MutArray _ start end bound) x
1891-
| INDEX_NEXT(end,a) > bound = do
1903+
step arr@(MutArray _ start end) x
1904+
| INDEX_NEXT(end,a) > getArrSizeUnsafe (arrContents arr) = do
18921905
let oldSize = end - start
18931906
newSize = max (oldSize * 2) 1
18941907
arr1 <- liftIO $ reallocExplicit (SIZE_OF(a)) newSize arr
@@ -2004,7 +2017,8 @@ fromListRev xs = fromListRevN (Prelude.length xs) xs
20042017
{-# INLINE putSliceUnsafe #-}
20052018
putSliceUnsafe :: MonadIO m => MutArray a -> Int -> MutArray a -> Int -> Int -> m ()
20062019
putSliceUnsafe src srcStartBytes dst dstStartBytes lenBytes = liftIO $ do
2007-
assertM(lenBytes <= arrBound dst - dstStartBytes)
2020+
arrBound <- sizeOfMutableByteArray (arrContents dst)
2021+
assertM(lenBytes <= arrBound - dstStartBytes)
20082022
assertM(lenBytes <= arrEnd src - srcStartBytes)
20092023
let !(I# srcStartBytes#) = srcStartBytes
20102024
!(I# dstStartBytes#) = dstStartBytes
@@ -2029,7 +2043,7 @@ spliceCopy arr1 arr2 = liftIO $ do
20292043
len2 = arrEnd arr2 - start2
20302044
newArrContents <- liftIO $ Unboxed.newPinnedBytes (len1 + len2)
20312045
let len = len1 + len2
2032-
newArr = MutArray newArrContents 0 len len
2046+
newArr = MutArray newArrContents 0 len
20332047
putSliceUnsafe arr1 start1 newArr 0 len1
20342048
putSliceUnsafe arr2 start2 newArr len1 len2
20352049
return newArr
@@ -2045,7 +2059,8 @@ spliceUnsafe dst src =
20452059
let startSrc = arrStart src
20462060
srcLen = arrEnd src - startSrc
20472061
endDst = arrEnd dst
2048-
assertM(endDst + srcLen <= arrBound dst)
2062+
arrBound <- sizeOfMutableByteArray (arrContents dst)
2063+
assertM(endDst + srcLen <= arrBound)
20492064
putSliceUnsafe src startSrc dst endDst srcLen
20502065
return $ dst {arrEnd = endDst + srcLen}
20512066

@@ -2060,11 +2075,12 @@ spliceUnsafe dst src =
20602075
{-# INLINE spliceWith #-}
20612076
spliceWith :: forall m a. (MonadIO m, Unbox a) =>
20622077
(Int -> Int -> Int) -> MutArray a -> MutArray a -> m (MutArray a)
2063-
spliceWith sizer dst@(MutArray _ start end bound) src = do
2078+
spliceWith sizer dst@(MutArray _ start end) src = do
20642079
{-
20652080
let f = writeAppendWith (`sizer` byteLength src) (return dst)
20662081
in D.fold f (toStreamD src)
20672082
-}
2083+
bound <- liftIO $ sizeOfMutableByteArray (arrContents dst)
20682084
assert (end <= bound) (return ())
20692085
let srcBytes = arrEnd src - arrStart src
20702086

@@ -2131,13 +2147,11 @@ breakOn sep arr@MutArray{..} = asPtrUnsafe arr $ \p -> liftIO $ do
21312147
{ arrContents = arrContents
21322148
, arrStart = arrStart
21332149
, arrEnd = arrStart + sepIndex -- exclude the separator
2134-
, arrBound = arrStart + sepIndex
21352150
}
21362151
, Just $ MutArray
21372152
{ arrContents = arrContents
21382153
, arrStart = arrStart + (sepIndex + 1)
21392154
, arrEnd = arrEnd
2140-
, arrBound = arrBound
21412155
}
21422156
)
21432157

@@ -2158,13 +2172,11 @@ splitAt i arr@MutArray{..} =
21582172
{ arrContents = arrContents
21592173
, arrStart = arrStart
21602174
, arrEnd = p
2161-
, arrBound = p
21622175
}
21632176
, MutArray
21642177
{ arrContents = arrContents
21652178
, arrStart = p
21662179
, arrEnd = arrEnd
2167-
, arrBound = arrBound
21682180
}
21692181
)
21702182

@@ -2184,8 +2196,8 @@ castUnsafe ::
21842196
Unbox b =>
21852197
#endif
21862198
MutArray a -> MutArray b
2187-
castUnsafe (MutArray contents start end bound) =
2188-
MutArray contents start end bound
2199+
castUnsafe (MutArray contents start end) =
2200+
MutArray contents start end
21892201

21902202
-- | Cast an @MutArray a@ into an @MutArray Word8@.
21912203
--
@@ -2295,7 +2307,7 @@ strip :: forall a m. (Unbox a, MonadIO m) =>
22952307
strip eq arr@MutArray{..} = liftIO $ do
22962308
st <- getStart arrStart
22972309
end <- getLast arrEnd st
2298-
return arr {arrStart = st, arrEnd = end, arrBound = end}
2310+
return arr {arrStart = st, arrEnd = end}
22992311

23002312
where
23012313

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -166,14 +166,14 @@ asPtrUnsafe arr = MA.asPtrUnsafe (unsafeThaw arr)
166166
-- /Pre-release/
167167
{-# INLINE unsafeFreeze #-}
168168
unsafeFreeze :: MutArray a -> Array a
169-
unsafeFreeze (MutArray ac as ae _) = Array ac as ae
169+
unsafeFreeze (MutArray ac as ae) = Array ac as ae
170170

171171
-- | Similar to 'unsafeFreeze' but uses 'MA.rightSize' on the mutable array
172172
-- first.
173173
{-# INLINE unsafeFreezeWithShrink #-}
174174
unsafeFreezeWithShrink :: Unbox a => MutArray a -> Array a
175175
unsafeFreezeWithShrink arr = unsafePerformIO $ do
176-
MutArray ac as ae _ <- MA.rightSize arr
176+
MutArray ac as ae <- MA.rightSize arr
177177
return $ Array ac as ae
178178

179179
-- | Makes a mutable array using the underlying memory of the immutable array.
@@ -186,7 +186,7 @@ unsafeFreezeWithShrink arr = unsafePerformIO $ do
186186
-- /Pre-release/
187187
{-# INLINE unsafeThaw #-}
188188
unsafeThaw :: Array a -> MutArray a
189-
unsafeThaw (Array ac as ae) = MutArray ac as ae ae
189+
unsafeThaw (Array ac as ae) = MutArray ac as ae
190190

191191
-------------------------------------------------------------------------------
192192
-- Pinning & Unpinning

0 commit comments

Comments
 (0)