Skip to content

Commit 44ae8f4

Browse files
committed
Rename the array slice functions
1 parent 1cb34f7 commit 44ae8f4

File tree

11 files changed

+73
-61
lines changed

11 files changed

+73
-61
lines changed

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ module Streamly.Internal.Data.Array
5353
, asCStringUnsafe
5454

5555
-- * Subarrays
56-
-- , getSlice
56+
-- , sliceOffLen
5757
, indexerFromLen
5858
, splitterFromLen
5959

@@ -301,7 +301,7 @@ getSliceUnsafe ::
301301
-> Int -- ^ length of the slice
302302
-> Array a
303303
-> Array a
304-
RENAME(getSliceUnsafe,unsafeGetSlice)
304+
RENAME(getSliceUnsafe,unsafeSliceOffLen)
305305

306306
sliceEndBy_, splitOn :: (Monad m, Unbox a) =>
307307
(a -> Bool) -> Array a -> Stream m (Array a)

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

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -42,13 +42,14 @@ module Streamly.Internal.Data.Array.Generic
4242
-- * Random Access
4343
, unsafeGetIndex
4444
, getIndex
45-
, unsafeGetSlice
45+
, unsafeSliceOffLen
4646
, dropAround
4747

4848
-- * Deprecated
4949
, strip
5050
, getIndexUnsafe
5151
, getSliceUnsafe
52+
, unsafeGetSlice
5253
, writeN
5354
, write
5455
, fromByteStr#
@@ -288,10 +289,11 @@ createOfLast n = FL.rmapM f (RB.createOf n)
288289
arr <- RB.copyToMutArray 0 n rb
289290
return $ unsafeFreeze arr
290291

291-
{-# INLINE unsafeGetSlice #-}
292-
unsafeGetSlice, getSliceUnsafe :: Int -> Int -> Array a -> Array a
293-
unsafeGetSlice offset len =
294-
unsafeFreeze . MArray.unsafeGetSlice offset len . unsafeThaw
292+
{-# INLINE unsafeSliceOffLen #-}
293+
unsafeSliceOffLen, getSliceUnsafe, unsafeGetSlice
294+
:: Int -> Int -> Array a -> Array a
295+
unsafeSliceOffLen offset len =
296+
unsafeFreeze . MArray.unsafeSliceOffLen offset len . unsafeThaw
295297

296298
-- XXX This is not efficient as it copies the array. We should support array
297299
-- slicing so that we can just refer to the underlying array memory instead of
@@ -357,5 +359,6 @@ instance Read a => Read (Array a) where
357359
-------------------------------------------------------------------------------
358360

359361
RENAME(strip,dropAround)
360-
RENAME(getSliceUnsafe,unsafeGetSlice)
362+
RENAME(getSliceUnsafe,unsafeSliceOffLen)
363+
RENAME(unsafeGetSlice,unsafeSliceOffLen)
361364
RENAME(getIndexUnsafe,unsafeGetIndex)

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

Lines changed: 7 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ module Streamly.Internal.Data.Array.Type
3737
, unsafeAsForeignPtr
3838

3939
-- * Subarrays
40-
, unsafeGetSlice
40+
, unsafeSliceOffLen
4141

4242
-- ** Construction
4343
, empty
@@ -155,6 +155,7 @@ module Streamly.Internal.Data.Array.Type
155155
, compactMin
156156

157157
-- ** Deprecated
158+
, unsafeGetSlice
158159
, strip
159160
, stripStart
160161
, stripEnd
@@ -532,18 +533,19 @@ fromStreamD = fromStream
532533
-- /Unsafe/
533534
--
534535
-- /Pre-release/
535-
{-# INLINE unsafeGetSlice #-}
536-
unsafeGetSlice ::
536+
{-# INLINE unsafeSliceOffLen #-}
537+
unsafeSliceOffLen, unsafeGetSlice ::
537538
forall a. Unbox a
538539
=> Int -- ^ starting index
539540
-> Int -- ^ length of the slice
540541
-> Array a
541542
-> Array a
542-
unsafeGetSlice index len (Array contents start e) =
543+
unsafeSliceOffLen index len (Array contents start e) =
543544
let size = SIZE_OF(a)
544545
start1 = start + (index * size)
545546
end1 = start1 + (len * size)
546547
in assert (end1 <= e) (Array contents start1 end1)
548+
RENAME(unsafeGetSlice,unsafeSliceOffLen)
547549

548550
-------------------------------------------------------------------------------
549551
-- Streams of arrays
@@ -626,7 +628,7 @@ splitEndBy p arr = D.map unsafeFreeze $ MA.splitEndBy p (unsafeThaw arr)
626628
splitEndBy_ :: (Monad m, Unbox a) =>
627629
(a -> Bool) -> Array a -> Stream m (Array a)
628630
splitEndBy_ predicate arr =
629-
fmap (\(i, len) -> unsafeGetSlice i len arr)
631+
fmap (\(i, len) -> unsafeSliceOffLen i len arr)
630632
$ D.indexEndBy_ predicate (read arr)
631633

632634
-- | Convert a stream of arrays into a stream of their elements.

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ splitterFromLen, slicerFromLen :: forall m a. (Monad m, Unbox a)
115115
-> Int -- ^ length of the slice
116116
-> Unfold m (MutArray a) (MutArray a)
117117
splitterFromLen from len =
118-
let mkSlice arr (i, n) = return $ unsafeGetSlice i n arr
118+
let mkSlice arr (i, n) = return $ unsafeSliceOffLen i n arr
119119
in Unfold.mapM2 mkSlice (indexerFromLen from len)
120120
RENAME(slicerFromLen,splitterFromLen)
121121

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

Lines changed: 16 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -144,10 +144,10 @@ module Streamly.Internal.Data.MutArray.Generic
144144

145145
-- ** Construct from arrays
146146
-- get chunks without copying
147-
, unsafeGetSlice
148-
, getSlice
147+
, unsafeSliceOffLen
148+
, sliceOffLen
149149
-- , getSlicesFromLenN
150-
-- , splitAt -- XXX should be able to express using getSlice
150+
-- , splitAt -- XXX should be able to express using sliceOffLen
151151
-- , breakOn
152152

153153
-- ** Appending arrays
@@ -162,6 +162,8 @@ module Streamly.Internal.Data.MutArray.Generic
162162
, clone
163163

164164
-- * Deprecated
165+
, unsafeGetSlice
166+
, getSlice
165167
, strip
166168
, new
167169
, writeNUnsafe
@@ -527,13 +529,13 @@ getIndex i arr =
527529
-- /Unsafe/
528530
--
529531
-- /Pre-release/
530-
{-# INLINE unsafeGetSlice #-}
531-
unsafeGetSlice, getSliceUnsafe
532+
{-# INLINE unsafeSliceOffLen #-}
533+
unsafeSliceOffLen, getSliceUnsafe, unsafeGetSlice
532534
:: Int -- ^ from index
533535
-> Int -- ^ length of the slice
534536
-> MutArray a
535537
-> MutArray a
536-
unsafeGetSlice index len arr@MutArray {..} =
538+
unsafeSliceOffLen index len arr@MutArray {..} =
537539
assert (index >= 0 && len >= 0 && index + len <= length arr)
538540
$ arr {arrStart = newStart, arrEnd = newEnd}
539541
where
@@ -544,17 +546,17 @@ unsafeGetSlice index len arr@MutArray {..} =
544546
-- extends out of the array bounds.
545547
--
546548
-- /Pre-release/
547-
{-# INLINE getSlice #-}
548-
getSlice
549+
{-# INLINE sliceOffLen #-}
550+
sliceOffLen, getSlice
549551
:: Int -- ^ from index
550552
-> Int -- ^ length of the slice
551553
-> MutArray a
552554
-> MutArray a
553-
getSlice index len arr@MutArray{..} =
555+
sliceOffLen index len arr@MutArray{..} =
554556
if index >= 0 && len >= 0 && index + len <= length arr
555557
then arr {arrStart = newStart, arrEnd = newEnd}
556558
else error
557-
$ "getSlice: invalid slice, index "
559+
$ "sliceOffLen: invalid slice, index "
558560
++ show index ++ " length " ++ show len
559561
where
560562
newStart = arrStart + index
@@ -940,7 +942,7 @@ dropAround p arr = liftIO $ do
940942
then return arr
941943
else
942944
let newLen = indexR - indexL + 1
943-
in return $ unsafeGetSlice indexL newLen arr
945+
in return $ unsafeSliceOffLen indexL newLen arr
944946

945947
where
946948

@@ -967,6 +969,8 @@ RENAME(putIndexUnsafe, unsafePutIndex)
967969
RENAME(modifyIndexUnsafe, unsafeModifyIndex)
968970
RENAME(getIndexUnsafe, unsafeGetIndex)
969971
RENAME(getIndexUnsafeWith, unsafeGetIndexWith)
970-
RENAME(getSliceUnsafe, unsafeGetSlice)
972+
RENAME(getSliceUnsafe,unsafeSliceOffLen)
973+
RENAME(unsafeGetSlice,unsafeSliceOffLen)
971974
RENAME(putSliceUnsafe, unsafePutSlice)
975+
RENAME(getSlice,sliceOffLen)
972976
RENAME(snocUnsafe, unsafeSnoc)

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

Lines changed: 22 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -65,8 +65,8 @@ module Streamly.Internal.Data.MutArray.Type
6565

6666
-- *** Slicing
6767
-- | Get a subarray without copying
68-
, unsafeGetSlice -- XXX unsafeSliceAtLen
69-
, getSlice -- XXX sliceAtLen
68+
, unsafeSliceOffLen
69+
, sliceOffLen
7070
, unsafeBreakAt
7171
, breakAt
7272
, breakEndByWord8_
@@ -308,6 +308,8 @@ module Streamly.Internal.Data.MutArray.Type
308308
, roundUpToPower2
309309

310310
-- * Deprecated
311+
, unsafeGetSlice
312+
, getSlice
311313
, sliceEndBy_
312314
, strip
313315
, stripStart
@@ -1431,7 +1433,6 @@ getIndices = indexReader
14311433
-------------------------------------------------------------------------------
14321434

14331435
-- XXX We can also get immutable slices.
1434-
-- XXX Rename getSlice to sliceAtLen indicating argument usage
14351436
-- XXX sliceFromLen for a stream of slices starting from a given index
14361437

14371438
-- | /O(1)/ Slice an array in constant time.
@@ -1441,13 +1442,13 @@ getIndices = indexReader
14411442
-- /Unsafe/
14421443
--
14431444
-- /Pre-release/
1444-
{-# INLINE unsafeGetSlice #-}
1445-
getSliceUnsafe, unsafeGetSlice :: forall a. Unbox a
1445+
{-# INLINE unsafeSliceOffLen #-}
1446+
unsafeSliceOffLen, getSliceUnsafe, unsafeGetSlice :: forall a. Unbox a
14461447
=> Int -- ^ from index
14471448
-> Int -- ^ length of the slice
14481449
-> MutArray a
14491450
-> MutArray a
1450-
unsafeGetSlice index len (MutArray contents start e _) =
1451+
unsafeSliceOffLen index len (MutArray contents start e _) =
14511452
let fp1 = INDEX_OF(start,index,a)
14521453
end = fp1 + (len * SIZE_OF(a))
14531454
in assert
@@ -1460,21 +1461,21 @@ unsafeGetSlice index len (MutArray contents start e _) =
14601461
-- extends out of the array bounds.
14611462
--
14621463
-- /Pre-release/
1463-
{-# INLINE getSlice #-}
1464-
getSlice :: forall a. Unbox a =>
1464+
{-# INLINE sliceOffLen #-}
1465+
sliceOffLen, getSlice :: forall a. Unbox a =>
14651466
Int -- ^ from index
14661467
-> Int -- ^ length of the slice
14671468
-> MutArray a
14681469
-> MutArray a
1469-
getSlice index len (MutArray contents start e _) =
1470+
sliceOffLen index len (MutArray contents start e _) =
14701471
let fp1 = INDEX_OF(start,index,a)
14711472
end = fp1 + (len * SIZE_OF(a))
14721473
in if index >= 0 && len >= 0 && end <= e
14731474
-- Note: In a slice we always use bound = end so that the slice user
14741475
-- cannot overwrite elements beyond the end of the slice.
14751476
then MutArray contents fp1 end end
14761477
else error
1477-
$ "getSlice: invalid slice, index "
1478+
$ "sliceOffLen: invalid slice, index "
14781479
++ show index ++ " length " ++ show len
14791480

14801481
-------------------------------------------------------------------------------
@@ -2823,7 +2824,7 @@ cloneAs ps src =
28232824

28242825
-- | Clones a MutArray.
28252826
--
2826-
-- To clone a slice of "MutArray" you can create a slice with "unsafeGetSlice"
2827+
-- To clone a slice of "MutArray" you can create a slice with "unsafeSliceOffLen"
28272828
-- and then use "clone".
28282829
--
28292830
-- The new "MutArray" is unpinned in nature. Use "clone'" to clone the
@@ -2981,7 +2982,7 @@ splitUsing :: (MonadIO m, Unbox a) =>
29812982
((a -> Bool) -> Stream m a -> Stream m (Int, Int))
29822983
-> (a -> Bool) -> MutArray a -> Stream m (MutArray a)
29832984
splitUsing f predicate arr =
2984-
fmap (\(i, len) -> unsafeGetSlice i len arr)
2985+
fmap (\(i, len) -> unsafeSliceOffLen i len arr)
29852986
$ f predicate (read arr)
29862987

29872988
-- | Generate a stream of array slices using a predicate. The array element
@@ -3025,8 +3026,8 @@ breakUsing adj indexer predicate arr = do
30253026
arr1 =
30263027
if i1 >= arrLen
30273028
then empty
3028-
else unsafeGetSlice i1 (arrLen - i1) arr
3029-
in return (unsafeGetSlice i len arr, arr1)
3029+
else unsafeSliceOffLen i1 (arrLen - i1) arr
3030+
in return (unsafeSliceOffLen i len arr, arr1)
30303031
Nothing -> return (arr, empty)
30313032

30323033
{-# INLINE revBreakUsing #-}
@@ -3046,8 +3047,8 @@ revBreakUsing withSep predicate arr = do
30463047
arr0 =
30473048
if len1 >= arrLen
30483049
then empty
3049-
else unsafeGetSlice 0 (arrLen - len1) arr
3050-
arr1 = unsafeGetSlice (arrLen - len) len arr
3050+
else unsafeSliceOffLen 0 (arrLen - len1) arr
3051+
arr1 = unsafeSliceOffLen (arrLen - len) len arr
30513052
in return (arr0, arr1)
30523053
Nothing -> return (arr, empty)
30533054

@@ -3145,13 +3146,13 @@ RENAME(breakOn,breakEndByWord8_)
31453146

31463147
-- | Like 'breakAt' but does not check whether the index is valid.
31473148
--
3148-
-- >>> unsafeBreakAt i arr = (MutArray.unsafeGetSlice 0 i arr, MutArray.unsafeGetSlice i (MutArray.length arr - i) arr)
3149+
-- >>> unsafeBreakAt i arr = (MutArray.unsafeSliceOffLen 0 i arr, MutArray.unsafeSliceOffLen i (MutArray.length arr - i) arr)
31493150
--
31503151
{-# INLINE unsafeBreakAt #-}
31513152
unsafeBreakAt, unsafeSplitAt :: forall a. Unbox a =>
31523153
Int -> MutArray a -> (MutArray a, MutArray a)
31533154
unsafeBreakAt i MutArray{..} =
3154-
-- (unsafeGetSlice 0 i arr, unsafeGetSlice i (length arr - i) arr)
3155+
-- (unsafeSliceOffLen 0 i arr, unsafeSliceOffLen i (length arr - i) arr)
31553156
let off = i * SIZE_OF(a)
31563157
p = arrStart + off
31573158
in ( MutArray
@@ -3852,7 +3853,9 @@ bubble cmp0 arr =
38523853
RENAME(realloc,reallocBytes)
38533854
RENAME(castUnsafe,unsafeCast)
38543855
RENAME(newArrayWith,emptyWithAligned)
3855-
RENAME(getSliceUnsafe,unsafeGetSlice)
3856+
RENAME(getSliceUnsafe,unsafeSliceOffLen)
3857+
RENAME(unsafeGetSlice,unsafeSliceOffLen)
3858+
RENAME(getSlice,sliceOffLen)
38563859
RENAME(putIndexUnsafe,unsafePutIndex)
38573860
RENAME(modifyIndexUnsafe,unsafeModifyIndex)
38583861
RENAME(getIndexUnsafe,unsafeGetIndex)

core/src/Streamly/Internal/Data/StreamK.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1583,8 +1583,8 @@ backTrackGenericChunks = go
15831583
then go (n - len) xs (cons x stream)
15841584
else if n == len
15851585
then (cons x stream, xs)
1586-
else let arr1 = GenArr.unsafeGetSlice (len - n) n x
1587-
arr2 = GenArr.unsafeGetSlice 0 (len - n) x
1586+
else let arr1 = GenArr.unsafeSliceOffLen (len - n) n x
1587+
arr2 = GenArr.unsafeSliceOffLen 0 (len - n) x
15881588
in (cons arr1 stream, arr2:xs)
15891589

15901590
-- | Similar to 'parseBreak' but works on generic arrays

core/src/Streamly/Internal/FileSystem/Path/Common.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -742,7 +742,7 @@ splitWithFilter
742742
splitWithFilter filt withSep os arr =
743743
f (isSeparatorWord os) (Array.read arr)
744744
& Stream.filter filt
745-
& fmap (\(i, len) -> Array.unsafeGetSlice i len arr)
745+
& fmap (\(i, len) -> Array.unsafeSliceOffLen i len arr)
746746

747747
where
748748

@@ -1091,7 +1091,7 @@ splitFile os arr =
10911091
then
10921092
if baseLen <= 0
10931093
then (Array.empty, arr)
1094-
else (Array.unsafeGetSlice 0 baseLen base, file) -- "/"
1094+
else (Array.unsafeSliceOffLen 0 baseLen base, file) -- "/"
10951095
else (arr, Array.empty)
10961096

10971097
-- | Split a multi-component path into (dir, last component). If the path has a

core/src/Streamly/Internal/Unicode/Stream.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -737,7 +737,7 @@ mkEvenW8Chunks (D.Stream step state) = D.Stream step1 (MECSInit state)
737737
Yield arr st1 ->
738738
let len = Array.length arr
739739
in if (len .&. 1) == 1
740-
then let arr1 = Array.unsafeGetSlice 0 (len - 1) arr
740+
then let arr1 = Array.unsafeSliceOffLen 0 (len - 1) arr
741741
remElem = Array.unsafeGetIndex (len - 1) arr
742742
in Yield arr1 (MECSBuffer remElem st1)
743743
else Yield arr (MECSInit st1)
@@ -756,11 +756,11 @@ mkEvenW8Chunks (D.Stream step state) = D.Stream step1 (MECSInit state)
756756
Yield arr st1 ->
757757
let len = Array.length arr
758758
in if (len .&. 1) == 1
759-
then let arr1 = Array.unsafeGetSlice 1 (len - 1) arr
759+
then let arr1 = Array.unsafeSliceOffLen 1 (len - 1) arr
760760
fstElem = Array.unsafeGetIndex 0 arr
761761
w16 = Array.fromList [remElem, fstElem]
762762
in Yield w16 (MECSYieldAndInit arr1 st1)
763-
else let arr1 = Array.unsafeGetSlice 1 (len - 2) arr
763+
else let arr1 = Array.unsafeSliceOffLen 1 (len - 2) arr
764764
fstElem = Array.unsafeGetIndex 0 arr
765765
lstElem = Array.unsafeGetIndex (len - 1) arr
766766
w16 = Array.fromList [remElem, fstElem]

0 commit comments

Comments
 (0)