Skip to content

Commit 8eaea6c

Browse files
committed
Remove duplicated code
Use `unsafeDrop` and friends instead of pattern matching on `Data.ByteString.Internal.BS`. - All those primitives are marked with `INLINE`. - This does not change the generated core.
1 parent 2e2e5ca commit 8eaea6c

File tree

7 files changed

+64
-47
lines changed

7 files changed

+64
-47
lines changed

Data/ByteString.hs

+30-28
Original file line numberDiff line numberDiff line change
@@ -423,19 +423,19 @@ head (BS x l)
423423
--
424424
-- This is a partial function, consider using 'uncons' instead.
425425
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
429429
{-# INLINE tail #-}
430430

431431
-- | /O(1)/ Extract the 'head' and 'tail' of a ByteString, returning 'Nothing'
432432
-- if it is empty.
433433
uncons :: ByteString -> Maybe (Word8, ByteString)
434-
uncons (BS x l)
434+
uncons ps@(BS x l)
435435
| l <= 0 = Nothing
436436
| otherwise = Just (accursedUnutterablePerformIO $ unsafeWithForeignPtr x
437437
$ \p -> peek p,
438-
BS (plusForeignPtr x 1) (l-1))
438+
unsafeDrop 1 ps)
439439
{-# INLINE uncons #-}
440440

441441
-- | /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)
454454
--
455455
-- This is a partial function, consider using 'unsnoc' instead.
456456
init :: HasCallStack => ByteString -> ByteString
457-
init ps@(BS p l)
457+
init ps
458458
| null ps = errorEmptyList "init"
459-
| otherwise = BS p (l-1)
459+
| otherwise = unsafeDropEnd 1 ps
460460
{-# INLINE init #-}
461461

462462
-- | /O(1)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing'
463463
-- if it is empty.
464464
unsnoc :: ByteString -> Maybe (ByteString, Word8)
465-
unsnoc (BS x l)
465+
unsnoc ps@(BS x l)
466466
| l <= 0 = Nothing
467-
| otherwise = Just (BS x (l-1),
467+
| otherwise = Just (unsafeDropEnd 1 ps,
468468
accursedUnutterablePerformIO $
469469
unsafeWithForeignPtr x $ \p -> peekByteOff p (l-1))
470470
{-# INLINE unsnoc #-}
@@ -921,10 +921,10 @@ unfoldrN i f x0
921921
-- | /O(1)/ 'take' @n@, applied to a ByteString @xs@, returns the prefix
922922
-- of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@.
923923
take :: Int -> ByteString -> ByteString
924-
take n ps@(BS x l)
924+
take n ps@(BS _ l)
925925
| n <= 0 = empty
926926
| n >= l = ps
927-
| otherwise = BS x n
927+
| otherwise = unsafeTake n ps
928928
{-# INLINE take #-}
929929

930930
-- | /O(1)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@.
@@ -939,19 +939,19 @@ take n ps@(BS x l)
939939
--
940940
-- @since 0.11.1.0
941941
takeEnd :: Int -> ByteString -> ByteString
942-
takeEnd n ps@(BS x len)
942+
takeEnd n ps@(BS _ len)
943943
| n >= len = ps
944944
| n <= 0 = empty
945-
| otherwise = BS (plusForeignPtr x (len - n)) n
945+
| otherwise = unsafeTakeEnd n ps
946946
{-# INLINE takeEnd #-}
947947

948948
-- | /O(1)/ 'drop' @n xs@ returns the suffix of @xs@ after the first @n@
949949
-- elements, or 'empty' if @n > 'length' xs@.
950950
drop :: Int -> ByteString -> ByteString
951-
drop n ps@(BS x l)
951+
drop n ps@(BS _ l)
952952
| n <= 0 = ps
953953
| n >= l = empty
954-
| otherwise = BS (plusForeignPtr x n) (l-n)
954+
| otherwise = unsafeDrop n ps
955955
{-# INLINE drop #-}
956956

957957
-- | /O(1)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@.
@@ -966,18 +966,18 @@ drop n ps@(BS x l)
966966
--
967967
-- @since 0.11.1.0
968968
dropEnd :: Int -> ByteString -> ByteString
969-
dropEnd n ps@(BS x len)
969+
dropEnd n ps@(BS _ len)
970970
| n <= 0 = ps
971971
| n >= len = empty
972-
| otherwise = BS x (len - n)
972+
| otherwise = unsafeDropEnd n ps
973973
{-# INLINE dropEnd #-}
974974

975975
-- | /O(1)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.
976976
splitAt :: Int -> ByteString -> (ByteString, ByteString)
977-
splitAt n ps@(BS x l)
977+
splitAt n ps@(BS _ l)
978978
| n <= 0 = (empty, ps)
979979
| n >= l = (ps, empty)
980-
| otherwise = (BS x n, BS (plusForeignPtr x n) (l-n))
980+
| otherwise = (unsafeTake n ps, unsafeDrop n ps)
981981
{-# INLINE splitAt #-}
982982

983983
-- | Similar to 'Prelude.takeWhile',
@@ -1151,18 +1151,17 @@ splitWith _ (BS _ 0) = []
11511151
splitWith predicate (BS fp len) = splitWith0 0 len fp
11521152
where splitWith0 !off' !len' !fp' =
11531153
accursedUnutterablePerformIO $
1154-
splitLoop fp 0 off' len' fp'
1154+
splitLoop 0 off' len' fp'
11551155

1156-
splitLoop :: ForeignPtr Word8
1157-
-> Int -> Int -> Int
1156+
splitLoop :: Int -> Int -> Int
11581157
-> ForeignPtr Word8
11591158
-> IO [ByteString]
1160-
splitLoop p idx2 off' len' fp' = go idx2
1159+
splitLoop idx2 off' len' fp' = go idx2
11611160
where
11621161
go idx'
11631162
| idx' >= len' = return [BS (plusForeignPtr fp' off') idx']
11641163
| otherwise = do
1165-
w <- peekFpByteOff p (off'+idx')
1164+
w <- peekFpByteOff fp (off'+idx')
11661165
if predicate w
11671166
then return (BS (plusForeignPtr fp' off') idx' :
11681167
splitWith0 (off'+idx'+1) (len'-idx'-1) fp')
@@ -1188,19 +1187,22 @@ splitWith predicate (BS fp len) = splitWith0 0 len fp
11881187
--
11891188
split :: Word8 -> ByteString -> [ByteString]
11901189
split _ (BS _ 0) = []
1191-
split w (BS x l) = loop 0
1190+
split w ps@(BS x l) = loop 0
11921191
where
11931192
loop !n =
11941193
let q = accursedUnutterablePerformIO $ unsafeWithForeignPtr x $ \p ->
11951194
memchr (p `plusPtr` n)
11961195
w (fromIntegral (l-n))
11971196
in if q == nullPtr
1198-
then [BS (plusForeignPtr x n) (l-n)]
1197+
then [unsafeDrop n ps]
11991198
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)
12011200

12021201
{-# INLINE split #-}
12031202

1203+
unsafeSlice :: Int -> Int -> ByteString -> ByteString
1204+
unsafeSlice a b (BS x _) = BS (plusForeignPtr x a) (b - a)
1205+
{-# INLINE unsafeSlice #-}
12041206

12051207
-- | The 'group' function takes a ByteString and returns a list of
12061208
-- ByteStrings such that the concatenation of the result is equal to the
@@ -1716,7 +1718,7 @@ inits bs = NE.toList $! initsNE bs
17161718
-- @since 0.11.4.0
17171719
initsNE :: ByteString -> NonEmpty ByteString
17181720
-- 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]]
17201722

17211723
-- | /O(n)/ Returns all final segments of the given 'ByteString', longest first.
17221724
tails :: ByteString -> [ByteString]

Data/ByteString/Char8.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -874,12 +874,12 @@ unzip ls = (pack (P.map fst ls), pack (P.map snd ls))
874874
-- > break isSpace == breakSpace
875875
--
876876
breakSpace :: ByteString -> (ByteString,ByteString)
877-
breakSpace (BS x l) = accursedUnutterablePerformIO $ unsafeWithForeignPtr x $ \p -> do
877+
breakSpace ps@(BS x l) = accursedUnutterablePerformIO $ unsafeWithForeignPtr x $ \p -> do
878878
i <- firstspace p 0 l
879879
return $! case () of {_
880-
| i == 0 -> (empty, BS x l)
881-
| i == l -> (BS x l, empty)
882-
| otherwise -> (BS x i, BS (plusForeignPtr x i) (l-i))
880+
| i == 0 -> (empty, ps)
881+
| i == l -> (ps, empty)
882+
| otherwise -> B.splitAt i ps
883883
}
884884
{-# INLINE breakSpace #-}
885885

@@ -897,9 +897,9 @@ firstspace !ptr !n !m
897897
--
898898
-- @since 0.10.12.0
899899
dropSpace :: ByteString -> ByteString
900-
dropSpace (BS x l) = accursedUnutterablePerformIO $ unsafeWithForeignPtr x $ \p -> do
900+
dropSpace ps@(BS x l) = accursedUnutterablePerformIO $ unsafeWithForeignPtr x $ \p -> do
901901
i <- firstnonspace p 0 l
902-
return $! if i == l then empty else BS (plusForeignPtr x i) (l-i)
902+
return $! if i == l then empty else B.unsafeDrop i ps
903903
{-# INLINE dropSpace #-}
904904

905905
firstnonspace :: Ptr Word8 -> Int -> Int -> IO Int

Data/ByteString/Lazy.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -1462,8 +1462,8 @@ initsNE = (Empty :|) . inits' id
14621462
inits' :: (ByteString -> ByteString) -> ByteString -> [ByteString]
14631463
-- inits' f bs === map f (tail (inits bs))
14641464
inits' _ Empty = []
1465-
inits' f (Chunk c@(S.BS x len) cs)
1466-
= [f (S.BS x n `Chunk` Empty) | n <- [1..len]]
1465+
inits' f (Chunk c cs)
1466+
= [f (S.unsafeTake n c `Chunk` Empty) | n <- [1..S.length c]]
14671467
++ inits' (f . Chunk c) cs
14681468

14691469
-- | /O(n)/ Returns all final segments of the given 'ByteString', longest first.

Data/ByteString/Lazy/Internal.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -331,7 +331,7 @@ toStrict = \cs -> goLen0 cs cs
331331
-- closures which would result in unnecessary closure allocation.
332332
where
333333
-- It's still possible that the result is empty
334-
goLen0 _ Empty = S.BS S.nullForeignPtr 0
334+
goLen0 _ Empty = S.empty
335335
goLen0 cs0 (Chunk c cs) = goLen1 cs0 c cs
336336

337337
-- It's still possible that the result is a single chunk

Data/ByteString/Lazy/ReadInt.hs

+6-5
Original file line numberDiff line numberDiff line change
@@ -27,14 +27,15 @@ module Data.ByteString.Lazy.ReadInt
2727
) where
2828

2929
import qualified Data.ByteString.Internal as BI
30+
import Data.ByteString.Unsafe
3031
#ifdef BYTESTRING_STRICT
3132
import Data.ByteString
3233
#else
3334
import Data.ByteString.Lazy
3435
import Data.ByteString.Lazy.Internal
3536
#endif
3637
import Data.Bits (FiniteBits, isSigned)
37-
import Data.ByteString.Internal (pattern BS, plusForeignPtr)
38+
import Data.ByteString.Internal (pattern BS)
3839
import Data.Int
3940
import Data.Word
4041
import Foreign.ForeignPtr (ForeignPtr)
@@ -177,18 +178,18 @@ _readDecimal !r = consume
177178
where
178179
consume :: ByteString -> Word64 -> Maybe (a, ByteString)
179180
#ifdef BYTESTRING_STRICT
180-
consume (BS fp len) a = case _digits q r fp len a of
181+
consume ps@(BS fp len) a = case _digits q r fp len a of
181182
Result used acc
182183
| used == len
183184
-> convert acc empty
184185
| otherwise
185-
-> convert acc $ BS (fp `plusForeignPtr` used) (len - used)
186+
-> convert acc $ unsafeDrop used ps
186187
_ -> Nothing
187188
#else
188189
-- All done
189190
consume Empty acc = convert acc Empty
190191
-- Process next chunk
191-
consume (Chunk (BS fp len) cs) acc
192+
consume (Chunk ps@(BS fp len) cs) acc
192193
= case _digits q r fp len acc of
193194
Result used acc'
194195
| used == len
@@ -197,7 +198,7 @@ _readDecimal !r = consume
197198
| otherwise
198199
-- ran into a non-digit
199200
-> convert acc' $
200-
Chunk (BS (fp `plusForeignPtr` used) (len - used)) cs
201+
Chunk (unsafeDrop used ps) cs
201202
_ -> Nothing
202203
#endif
203204
convert :: Word64 -> ByteString -> Maybe (a, ByteString)

Data/ByteString/Lazy/ReadNat.hs

+6-5
Original file line numberDiff line numberDiff line change
@@ -21,14 +21,15 @@ module Data.ByteString.Lazy.ReadNat
2121
) where
2222

2323
import qualified Data.ByteString.Internal as BI
24+
import Data.ByteString.Unsafe
2425
#ifdef BYTESTRING_STRICT
2526
import Data.ByteString
2627
#else
2728
import Data.ByteString.Lazy
2829
import Data.ByteString.Lazy.Internal
2930
#endif
3031
import Data.Bits (finiteBitSize)
31-
import Data.ByteString.Internal (pattern BS, plusForeignPtr)
32+
import Data.ByteString.Internal (pattern BS)
3233
import Data.Word
3334
import Foreign.ForeignPtr (ForeignPtr)
3435
import Foreign.Ptr (Ptr, minusPtr, plusPtr)
@@ -127,7 +128,7 @@ _readDecimal =
127128
consume :: [Natural] -> Int -> Word -> ByteString
128129
-> (Natural, ByteString)
129130
#ifdef BYTESTRING_STRICT
130-
consume ns cnt acc (BS fp len) =
131+
consume ns cnt acc ps@(BS fp len) =
131132
-- Having read one digit, we're about to read the 2nd
132133
-- So the digit count up to 'safeLog' starts at 2.
133134
case natdigits fp len acc cnt ns of
@@ -136,18 +137,18 @@ _readDecimal =
136137
-> convert acc' cnt' ns' $ empty
137138
| otherwise
138139
-> convert acc' cnt' ns' $
139-
BS (fp `plusForeignPtr` used) (len - used)
140+
unsafeDrop used ps
140141
#else
141142
-- All done
142143
consume ns cnt acc Empty = convert acc cnt ns Empty
143144
-- Process next chunk
144-
consume ns cnt acc (Chunk (BS fp len) cs)
145+
consume ns cnt acc (Chunk ps@(BS fp len) cs)
145146
= case natdigits fp len acc cnt ns of
146147
Result used acc' cnt' ns'
147148
| used == len -- process more chunks
148149
-> consume ns' cnt' acc' cs
149150
| otherwise -- ran into a non-digit
150-
-> let c = Chunk (BS (fp `plusForeignPtr` used) (len - used)) cs
151+
-> let c = Chunk (unsafeDrop used ps) cs
151152
in convert acc' cnt' ns' c
152153
#endif
153154
convert !acc !cnt !ns rest =

Data/ByteString/Unsafe.hs

+13
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,9 @@ module Data.ByteString.Unsafe (
2525
unsafeLast,
2626
unsafeIndex,
2727
unsafeTake,
28+
unsafeTakeEnd,
2829
unsafeDrop,
30+
unsafeDropEnd,
2931

3032
-- * Low level interaction with CStrings
3133
-- ** Using ByteStrings with functions for CStrings
@@ -113,12 +115,23 @@ unsafeTake :: Int -> ByteString -> ByteString
113115
unsafeTake n (BS x l) = assert (0 <= n && n <= l) $ BS x n
114116
{-# INLINE unsafeTake #-}
115117

118+
-- | A variety of 'takeEnd' which omits the checks on @n@ so there is an
119+
-- obligation on the programmer to provide a proof that @0 <= n <= 'length' xs@.
120+
unsafeTakeEnd :: Int -> ByteString -> ByteString
121+
unsafeTakeEnd n (BS x l) = assert (0 <= n && n <= l) $ BS (plusForeignPtr x (l-n)) n
122+
{-# INLINE unsafeTakeEnd #-}
123+
116124
-- | A variety of 'drop' which omits the checks on @n@ so there is an
117125
-- obligation on the programmer to provide a proof that @0 <= n <= 'length' xs@.
118126
unsafeDrop :: Int -> ByteString -> ByteString
119127
unsafeDrop n (BS x l) = assert (0 <= n && n <= l) $ BS (plusForeignPtr x n) (l-n)
120128
{-# INLINE unsafeDrop #-}
121129

130+
-- | A variety of 'dropEnd' which omits the checks on @n@ so there is an
131+
-- obligation on the programmer to provide a proof that @0 <= n <= 'length' xs@.
132+
unsafeDropEnd :: Int -> ByteString -> ByteString
133+
unsafeDropEnd n (BS x l) = assert (0 <= n && n <= l) $ BS x (l-n)
134+
{-# INLINE unsafeDropEnd #-}
122135

123136
-- | /O(1)/ 'unsafePackAddressLen' provides constant-time construction of
124137
-- 'ByteString's, which is ideal for string literals. It packs a sequence

0 commit comments

Comments
 (0)