@@ -423,19 +423,19 @@ head (BS x l)
423
423
--
424
424
-- This is a partial function, consider using 'uncons' instead.
425
425
tail :: HasCallStack => ByteString -> ByteString
426
- tail ( BS p l)
427
- | l <= 0 = errorEmptyList " tail"
428
- | otherwise = BS (plusForeignPtr p 1 ) (l - 1 )
426
+ tail ps
427
+ | length ps <= 0 = errorEmptyList " tail"
428
+ | otherwise = unsafeDrop 1 ps
429
429
{-# INLINE tail #-}
430
430
431
431
-- | /O(1)/ Extract the 'head' and 'tail' of a ByteString, returning 'Nothing'
432
432
-- if it is empty.
433
433
uncons :: ByteString -> Maybe (Word8 , ByteString )
434
- uncons (BS x l)
434
+ uncons ps @ (BS x l)
435
435
| l <= 0 = Nothing
436
436
| otherwise = Just (accursedUnutterablePerformIO $ unsafeWithForeignPtr x
437
437
$ \ p -> peek p,
438
- BS (plusForeignPtr x 1 ) (l - 1 ) )
438
+ unsafeDrop 1 ps )
439
439
{-# INLINE uncons #-}
440
440
441
441
-- | /O(1)/ Extract the last element of a ByteString, which must be finite and non-empty.
@@ -454,17 +454,17 @@ last ps@(BS x l)
454
454
--
455
455
-- This is a partial function, consider using 'unsnoc' instead.
456
456
init :: HasCallStack => ByteString -> ByteString
457
- init ps@ ( BS p l)
457
+ init ps
458
458
| null ps = errorEmptyList " init"
459
- | otherwise = BS p (l - 1 )
459
+ | otherwise = unsafeDropEnd 1 ps
460
460
{-# INLINE init #-}
461
461
462
462
-- | /O(1)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing'
463
463
-- if it is empty.
464
464
unsnoc :: ByteString -> Maybe (ByteString , Word8 )
465
- unsnoc (BS x l)
465
+ unsnoc ps @ (BS x l)
466
466
| l <= 0 = Nothing
467
- | otherwise = Just (BS x (l - 1 ) ,
467
+ | otherwise = Just (unsafeDropEnd 1 ps ,
468
468
accursedUnutterablePerformIO $
469
469
unsafeWithForeignPtr x $ \ p -> peekByteOff p (l- 1 ))
470
470
{-# INLINE unsnoc #-}
@@ -921,10 +921,10 @@ unfoldrN i f x0
921
921
-- | /O(1)/ 'take' @n@, applied to a ByteString @xs@, returns the prefix
922
922
-- of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@.
923
923
take :: Int -> ByteString -> ByteString
924
- take n ps@ (BS x l)
924
+ take n ps@ (BS _ l)
925
925
| n <= 0 = empty
926
926
| n >= l = ps
927
- | otherwise = BS x n
927
+ | otherwise = unsafeTake n ps
928
928
{-# INLINE take #-}
929
929
930
930
-- | /O(1)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@.
@@ -939,19 +939,19 @@ take n ps@(BS x l)
939
939
--
940
940
-- @since 0.11.1.0
941
941
takeEnd :: Int -> ByteString -> ByteString
942
- takeEnd n ps@ (BS x len)
942
+ takeEnd n ps@ (BS _ len)
943
943
| n >= len = ps
944
944
| n <= 0 = empty
945
- | otherwise = BS (plusForeignPtr x (len - n)) n
945
+ | otherwise = unsafeTakeEnd n ps
946
946
{-# INLINE takeEnd #-}
947
947
948
948
-- | /O(1)/ 'drop' @n xs@ returns the suffix of @xs@ after the first @n@
949
949
-- elements, or 'empty' if @n > 'length' xs@.
950
950
drop :: Int -> ByteString -> ByteString
951
- drop n ps@ (BS x l)
951
+ drop n ps@ (BS _ l)
952
952
| n <= 0 = ps
953
953
| n >= l = empty
954
- | otherwise = BS (plusForeignPtr x n) (l - n)
954
+ | otherwise = unsafeDrop n ps
955
955
{-# INLINE drop #-}
956
956
957
957
-- | /O(1)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@.
@@ -966,18 +966,18 @@ drop n ps@(BS x l)
966
966
--
967
967
-- @since 0.11.1.0
968
968
dropEnd :: Int -> ByteString -> ByteString
969
- dropEnd n ps@ (BS x len)
969
+ dropEnd n ps@ (BS _ len)
970
970
| n <= 0 = ps
971
971
| n >= len = empty
972
- | otherwise = BS x (len - n)
972
+ | otherwise = unsafeDropEnd n ps
973
973
{-# INLINE dropEnd #-}
974
974
975
975
-- | /O(1)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.
976
976
splitAt :: Int -> ByteString -> (ByteString , ByteString )
977
- splitAt n ps@ (BS x l)
977
+ splitAt n ps@ (BS _ l)
978
978
| n <= 0 = (empty, ps)
979
979
| n >= l = (ps, empty)
980
- | otherwise = (BS x n, BS (plusForeignPtr x n) (l - n) )
980
+ | otherwise = (unsafeTake n ps, unsafeDrop n ps )
981
981
{-# INLINE splitAt #-}
982
982
983
983
-- | Similar to 'Prelude.takeWhile',
@@ -1151,18 +1151,17 @@ splitWith _ (BS _ 0) = []
1151
1151
splitWith predicate (BS fp len) = splitWith0 0 len fp
1152
1152
where splitWith0 ! off' ! len' ! fp' =
1153
1153
accursedUnutterablePerformIO $
1154
- splitLoop fp 0 off' len' fp'
1154
+ splitLoop 0 off' len' fp'
1155
1155
1156
- splitLoop :: ForeignPtr Word8
1157
- -> Int -> Int -> Int
1156
+ splitLoop :: Int -> Int -> Int
1158
1157
-> ForeignPtr Word8
1159
1158
-> IO [ByteString ]
1160
- splitLoop p idx2 off' len' fp' = go idx2
1159
+ splitLoop idx2 off' len' fp' = go idx2
1161
1160
where
1162
1161
go idx'
1163
1162
| idx' >= len' = return [BS (plusForeignPtr fp' off') idx']
1164
1163
| otherwise = do
1165
- w <- peekFpByteOff p (off'+ idx')
1164
+ w <- peekFpByteOff fp (off'+ idx')
1166
1165
if predicate w
1167
1166
then return (BS (plusForeignPtr fp' off') idx' :
1168
1167
splitWith0 (off'+ idx'+ 1 ) (len'- idx'- 1 ) fp')
@@ -1188,19 +1187,22 @@ splitWith predicate (BS fp len) = splitWith0 0 len fp
1188
1187
--
1189
1188
split :: Word8 -> ByteString -> [ByteString ]
1190
1189
split _ (BS _ 0 ) = []
1191
- split w (BS x l) = loop 0
1190
+ split w ps @ (BS x l) = loop 0
1192
1191
where
1193
1192
loop ! n =
1194
1193
let q = accursedUnutterablePerformIO $ unsafeWithForeignPtr x $ \ p ->
1195
1194
memchr (p `plusPtr` n)
1196
1195
w (fromIntegral (l- n))
1197
1196
in if q == nullPtr
1198
- then [BS (plusForeignPtr x n) (l - n) ]
1197
+ then [unsafeDrop n ps ]
1199
1198
else let i = q `minusPtr` unsafeForeignPtrToPtr x
1200
- in BS (plusForeignPtr x n) (i - n) : loop (i+ 1 )
1199
+ in unsafeSlice n i ps : loop (i+ 1 )
1201
1200
1202
1201
{-# INLINE split #-}
1203
1202
1203
+ unsafeSlice :: Int -> Int -> ByteString -> ByteString
1204
+ unsafeSlice a b (BS x _) = BS (plusForeignPtr x a) (b - a)
1205
+ {-# INLINE unsafeSlice #-}
1204
1206
1205
1207
-- | The 'group' function takes a ByteString and returns a list of
1206
1208
-- ByteStrings such that the concatenation of the result is equal to the
@@ -1716,7 +1718,7 @@ inits bs = NE.toList $! initsNE bs
1716
1718
-- @since 0.11.4.0
1717
1719
initsNE :: ByteString -> NonEmpty ByteString
1718
1720
-- see Note [Avoid NonEmpty combinators]
1719
- initsNE ( BS x len) = empty :| [BS x n | n <- [1 .. len ]]
1721
+ initsNE ps = empty :| [unsafeTake n ps | n <- [1 .. length ps ]]
1720
1722
1721
1723
-- | /O(n)/ Returns all final segments of the given 'ByteString', longest first.
1722
1724
tails :: ByteString -> [ByteString ]
0 commit comments