Skip to content

Commit

Permalink
Add dropWhileEnd, takeWhileEnd, strip
Browse files Browse the repository at this point in the history
  • Loading branch information
nmattia committed Jul 1, 2020
1 parent 1efc9c0 commit 3688b4b
Show file tree
Hide file tree
Showing 4 changed files with 46 additions and 0 deletions.
4 changes: 4 additions & 0 deletions Changelog.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
0.10.10.2 –

* Add `takeWhileEnd`, `dropWhileEnd` and `strip` for strict bytestrings

0.10.10.1 – June 2020

* Fix off-by-one infinite loop in primMapByteStringBounded ([#203])
Expand Down
14 changes: 14 additions & 0 deletions Data/ByteString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,9 @@ module Data.ByteString (
drop, -- :: Int -> ByteString -> ByteString
splitAt, -- :: Int -> ByteString -> (ByteString, ByteString)
takeWhile, -- :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhileEnd, -- :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile, -- :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhileEnd, -- :: (Word8 -> Bool) -> ByteString -> ByteString
span, -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd, -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break, -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
Expand Down Expand Up @@ -835,11 +837,23 @@ takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhile f ps = unsafeTake (findIndexOrEnd (not . f) ps) ps
{-# INLINE takeWhile #-}

-- | 'takeWhileEnd', applied to a predicate @p@ and a ByteString @xs@, returns
-- the longest suffix (possibly empty) of @xs@ of elements that satisfy @p@.
takeWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhileEnd f ps = unsafeDrop (findFromEndUntil (not . f) ps) ps
{-# INLINE takeWhileEnd #-}

-- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@.
dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile f ps = unsafeDrop (findIndexOrEnd (not . f) ps) ps
{-# INLINE dropWhile #-}

-- | 'dropWhileEnd' @p xs@ returns the prefix remaining after 'takeWhileEnd' @p
-- xs@.
dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhileEnd f ps = unsafeTake (findFromEndUntil (not . f) ps) ps
{-# INLINE dropWhileEnd #-}

-- instead of findIndexOrEnd, we could use memchr here.

-- | 'break' @p@ is equivalent to @'span' ('not' . p)@.
Expand Down
21 changes: 21 additions & 0 deletions Data/ByteString/Char8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,10 @@ module Data.ByteString.Char8 (
drop, -- :: Int -> ByteString -> ByteString
splitAt, -- :: Int -> ByteString -> (ByteString, ByteString)
takeWhile, -- :: (Char -> Bool) -> ByteString -> ByteString
takeWhileEnd, -- :: (Char -> Bool) -> ByteString -> ByteString
dropWhile, -- :: (Char -> Bool) -> ByteString -> ByteString
dropWhileEnd, -- :: (Char -> Bool) -> ByteString -> ByteString
dropSpace, -- :: ByteString -> ByteString
span, -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd, -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
break, -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
Expand All @@ -124,6 +127,7 @@ module Data.ByteString.Char8 (
groupBy, -- :: (Char -> Char -> Bool) -> ByteString -> [ByteString]
inits, -- :: ByteString -> [ByteString]
tails, -- :: ByteString -> [ByteString]
strip, -- :: ByteString -> ByteString
stripPrefix, -- :: ByteString -> ByteString -> Maybe ByteString
stripSuffix, -- :: ByteString -> ByteString -> Maybe ByteString

Expand Down Expand Up @@ -497,6 +501,13 @@ takeWhile :: (Char -> Bool) -> ByteString -> ByteString
takeWhile f = B.takeWhile (f . w2c)
{-# INLINE takeWhile #-}

-- | 'takeWhileEnd', applied to a predicate @p@ and a ByteString @xs@,
-- returns the longest suffix (possibly empty) of @xs@ of elements that
-- satisfy @p@.
takeWhileEnd :: (Char -> Bool) -> ByteString -> ByteString
takeWhileEnd f = B.takeWhileEnd (f . w2c)
{-# INLINE takeWhileEnd #-}

-- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@.
dropWhile :: (Char -> Bool) -> ByteString -> ByteString
dropWhile f = B.dropWhile (f . w2c)
Expand All @@ -507,6 +518,12 @@ dropWhile f = B.dropWhile (f . w2c)
dropWhile isSpace = dropSpace
#-}

-- | 'dropWhile' @p xs@ returns the prefix remaining after 'takeWhileEnd' @p
-- xs@.
dropWhileEnd :: (Char -> Bool) -> ByteString -> ByteString
dropWhileEnd f = B.dropWhileEnd (f . w2c)
{-# INLINE dropWhileEnd #-}

-- | 'break' @p@ is equivalent to @'span' ('not' . p)@.
break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
break f = B.break (f . w2c)
Expand Down Expand Up @@ -824,6 +841,10 @@ firstnonspace !ptr !n !m
| otherwise = do w <- peekElemOff ptr n
if isSpaceWord8 w then firstnonspace ptr (n+1) m else return n

-- | Remove leading and trailing white space from a 'ByteString'.
strip :: ByteString -> ByteString
strip = dropWhile isSpace . dropWhileEnd isSpace

{-
-- | 'dropSpaceEnd' efficiently returns the 'ByteString' argument with
-- white space removed from the end. I.e.
Expand Down
7 changes: 7 additions & 0 deletions tests/Properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -719,6 +719,8 @@ prop_splitAt i xs = --collect (i >= 0 && i < length xs) $

prop_takeWhile f xs = L.takeWhile f (pack xs) == pack (takeWhile f xs)
prop_dropWhile f xs = L.dropWhile f (pack xs) == pack (dropWhile f xs)
prop_takeWhileEnd f = P.takeWhileEnd f `eq1` (P.reverse . P.takeWhile f . P.reverse)
prop_dropWhileEnd f = P.dropWhileEnd f `eq1` (P.reverse . P.dropWhile f . P.reverse)

prop_break f xs = L.break f (pack xs) ==
let (a,b) = break f xs in (pack a, pack b)
Expand Down Expand Up @@ -1183,6 +1185,8 @@ prop_intersperseBB c xs = (intersperse c xs) == (P.unpack $ P.intersperse c (P.p
prop_maximumBB xs = (not (null xs)) ==> (maximum xs) == (P.maximum ( P.pack xs ))
prop_minimumBB xs = (not (null xs)) ==> (minimum xs) == (P.minimum ( P.pack xs ))

prop_strip = C.strip `eq1` (C.dropSpace . C.reverse . C.dropSpace . C.reverse)

-- prop_dropSpaceBB xs = dropWhile isSpace xs == C.unpack (C.dropSpace (C.pack xs))
-- prop_dropSpaceEndBB xs = (C.reverse . (C.dropWhile isSpace) . C.reverse) (C.pack xs) ==
-- (C.dropSpaceEnd (C.pack xs))
Expand Down Expand Up @@ -2229,6 +2233,7 @@ bb_tests =
, testProperty "intersperse" prop_intersperseBB
, testProperty "maximum" prop_maximumBB
, testProperty "minimum" prop_minimumBB
, testProperty "strip" prop_strip
-- , testProperty "breakChar" prop_breakCharBB
-- , testProperty "spanChar 1" prop_spanCharBB
-- , testProperty "spanChar 2" prop_spanChar_1BB
Expand Down Expand Up @@ -2400,6 +2405,8 @@ ll_tests =
, testProperty "splitAt" prop_drop1
, testProperty "takeWhile" prop_takeWhile
, testProperty "dropWhile" prop_dropWhile
, testProperty "takeWhileEnd" prop_takeWhileEnd
, testProperty "dropWhileEnd" prop_dropWhileEnd
, testProperty "break" prop_break
, testProperty "span" prop_span
, testProperty "splitAt" prop_splitAt
Expand Down

0 comments on commit 3688b4b

Please sign in to comment.