Skip to content

Commit

Permalink
Merge pull request #261 from cole-miller/feature/bytestring
Browse files Browse the repository at this point in the history
Add non-throwing indexMaybe function (continues #146)
  • Loading branch information
Bodigrim authored Aug 23, 2020
2 parents cb85f82 + 9453694 commit f35e9e5
Show file tree
Hide file tree
Showing 8 changed files with 155 additions and 4 deletions.
5 changes: 5 additions & 0 deletions Changelog.md
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
[0.11.0.0]
* [Add `indexMaybe` and synonym `(!?)` for indexing that returns `Maybe`](https://github.com/haskell/bytestring/pull/261)

[0.11.0.0]: https://github.com/haskell/bytestring/compare/0.10.12.0...0.11.0.0

[0.10.12.0] – August 2020

* **Note:** There are several breaking changes planned to be included in v0.11.
Expand Down
23 changes: 23 additions & 0 deletions Data/ByteString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -152,6 +152,8 @@ module Data.ByteString (

-- * Indexing ByteStrings
index, -- :: ByteString -> Int -> Word8
indexMaybe, -- :: ByteString -> Int -> Maybe Word8
(!?), -- :: ByteString -> Int -> Maybe Word8
elemIndex, -- :: Word8 -> ByteString -> Maybe Int
elemIndices, -- :: Word8 -> ByteString -> [Int]
elemIndexEnd, -- :: Word8 -> ByteString -> Maybe Int
Expand Down Expand Up @@ -1096,6 +1098,27 @@ index ps n
| otherwise = ps `unsafeIndex` n
{-# INLINE index #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ByteString -> Int -> Maybe Word8
indexMaybe ps n
| n < 0 = Nothing
| n >= length ps = Nothing
| otherwise = Just $! ps `unsafeIndex` n
{-# INLINE indexMaybe #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ByteString -> Int -> Maybe Word8
(!?) = indexMaybe
{-# INLINE (!?) #-}

-- | /O(n)/ The 'elemIndex' function returns the index of the first
-- element in the given 'ByteString' which is equal to the query
-- element, or 'Nothing' if there is no such element.
Expand Down
20 changes: 20 additions & 0 deletions Data/ByteString/Char8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -162,6 +162,8 @@ module Data.ByteString.Char8 (

-- * Indexing ByteStrings
index, -- :: ByteString -> Int -> Char
indexMaybe, -- :: ByteString -> Int -> Maybe Char
(!?), -- :: ByteString -> Int -> Maybe Char
elemIndex, -- :: Char -> ByteString -> Maybe Int
elemIndices, -- :: Char -> ByteString -> [Int]
elemIndexEnd, -- :: Char -> ByteString -> Maybe Int
Expand Down Expand Up @@ -644,6 +646,24 @@ index :: ByteString -> Int -> Char
index = (w2c .) . B.index
{-# INLINE index #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ByteString -> Int -> Maybe Char
indexMaybe = (fmap w2c .) . B.indexMaybe
{-# INLINE indexMaybe #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ByteString -> Int -> Maybe Char
(!?) = indexMaybe
{-# INLINE (!?) #-}

-- | /O(n)/ The 'elemIndex' function returns the index of the first
-- element in the given 'ByteString' which is equal (by memchr) to the
-- query element, or 'Nothing' if there is no such element.
Expand Down
25 changes: 25 additions & 0 deletions Data/ByteString/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,6 +165,8 @@ module Data.ByteString.Lazy (

-- * Indexing ByteStrings
index, -- :: ByteString -> Int64 -> Word8
indexMaybe, -- :: ByteString -> Int64 -> Maybe Word8
(!?), -- :: ByteString -> Int64 -> Maybe Word8
elemIndex, -- :: Word8 -> ByteString -> Maybe Int64
elemIndexEnd, -- :: Word8 -> ByteString -> Maybe Int64
elemIndices, -- :: Word8 -> ByteString -> [Int64]
Expand Down Expand Up @@ -894,6 +896,29 @@ index cs0 i = index' cs0 i
index' cs (n - fromIntegral (S.length c))
| otherwise = S.unsafeIndex c (fromIntegral n)

-- | /O(c)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ByteString -> Int64 -> Maybe Word8
indexMaybe _ i | i < 0 = Nothing
indexMaybe cs0 i = index' cs0 i
where index' Empty _ = Nothing
index' (Chunk c cs) n
| n >= fromIntegral (S.length c) =
index' cs (n - fromIntegral (S.length c))
| otherwise = Just $! S.unsafeIndex c (fromIntegral n)

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ByteString -> Int64 -> Maybe Word8
(!?) = indexMaybe
{-# INLINE (!?) #-}

-- | /O(n)/ The 'elemIndex' function returns the index of the first
-- element in the given 'ByteString' which is equal to the query
-- element, or 'Nothing' if there is no such element.
Expand Down
20 changes: 20 additions & 0 deletions Data/ByteString/Lazy/Char8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,8 @@ module Data.ByteString.Lazy.Char8 (

-- * Indexing ByteStrings
index, -- :: ByteString -> Int64 -> Char
indexMaybe, -- :: ByteString -> Int64 -> Maybe Char
(!?), -- :: ByteString -> Int64 -> Maybe Char
elemIndex, -- :: Char -> ByteString -> Maybe Int64
elemIndices, -- :: Char -> ByteString -> [Int64]
findIndex, -- :: (Char -> Bool) -> ByteString -> Maybe Int64
Expand Down Expand Up @@ -529,6 +531,24 @@ index :: ByteString -> Int64 -> Char
index = (w2c .) . L.index
{-# INLINE index #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ByteString -> Int64 -> Maybe Char
indexMaybe = (fmap w2c .) . L.indexMaybe
{-# INLINE indexMaybe #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ByteString -> Int64 -> Maybe Char
(!?) = indexMaybe
{-# INLINE (!?) #-}

-- | /O(n)/ The 'elemIndex' function returns the index of the first
-- element in the given 'ByteString' which is equal (by memchr) to the
-- query element, or 'Nothing' if there is no such element.
Expand Down
2 changes: 1 addition & 1 deletion Data/ByteString/Short.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,7 @@ module Data.ByteString.Short (
unpack,

-- * Other operations
empty, null, length, index,
empty, null, length, index, indexMaybe, (!?),

-- * Low level conversions
-- ** Packing 'Foreign.C.String.CString's and pointers
Expand Down
27 changes: 24 additions & 3 deletions Data/ByteString/Short/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ module Data.ByteString.Short.Internal (
unpack,

-- * Other operations
empty, null, length, index, unsafeIndex,
empty, null, length, index, indexMaybe, (!?), unsafeIndex,

-- * Low level operations
createFromPtr, copyToPtr,
Expand Down Expand Up @@ -102,11 +102,12 @@ import GHC.ST (ST(ST), runST)
import GHC.Word

import Prelude ( Eq(..), Ord(..), Ordering(..), Read(..), Show(..)
, ($), error, (++), (.)
, ($), ($!), error, (++), (.)
, String, userError
, Bool(..), (&&), otherwise
, (+), (-), fromIntegral
, return )
, return
, Maybe(..) )


-- | A compact representation of a 'Word8' vector.
Expand Down Expand Up @@ -214,6 +215,26 @@ index sbs i
| i >= 0 && i < length sbs = unsafeIndex sbs i
| otherwise = indexError sbs i

-- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe sbs i
| i >= 0 && i < length sbs = Just $! unsafeIndex sbs i
| otherwise = Nothing
{-# INLINE indexMaybe #-}

-- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ShortByteString -> Int -> Maybe Word8
(!?) = indexMaybe
{-# INLINE (!?) #-}

unsafeIndex :: ShortByteString -> Int -> Word8
unsafeIndex sbs = indexWord8Array (asBA sbs)

Expand Down
37 changes: 37 additions & 0 deletions tests/Properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -796,6 +796,39 @@ prop_index_C (String8 xs) =
forAll indices $ \i -> (xs !! i) == C.pack xs `C.index` (fromIntegral i)
where indices = choose (0, length xs -1)

-- | Test 'indexMaybe' for Lazy and Strict 'ByteString's.
-- If we are testing within the bounds it should return a 'Just' value.
-- If we are testing outside of the bounds it should return a 'Nothing' value.
prop_indexMaybe_Just_L xs =
not (null xs) ==>
forAll indices $ \i -> isJust (ys `L.indexMaybe` (fromIntegral i))
where
ys = L.pack xs
indices = choose (0, length xs -1)

prop_indexMaybe_Just_P xs =
not (null xs) ==>
forAll indices $ \i -> isJust (ys `P.indexMaybe` (fromIntegral i))
where
ys = P.pack xs
indices = choose (0, length xs -1)

prop_indexMaybe_Nothing_L xs =
not (null xs) ==>
forAll indices $ \i -> isNothing (ys `L.indexMaybe` (fromIntegral i))
where
ys = L.pack xs
outOfBounds = choose (-100, length xs + 100)
indices = suchThat outOfBounds (\n -> n < 0 || n >= length xs)

prop_indexMaybe_Nothing_P xs =
not (null xs) ==>
forAll indices $ \i -> isNothing (ys `P.indexMaybe` (fromIntegral i))
where
ys = P.pack xs
outOfBounds = choose (-100, length xs + 100)
indices = suchThat outOfBounds (\n -> n < 0 || n >= length xs)

prop_elemIndex xs c = (elemIndex c xs) == fmap fromIntegral (L.elemIndex c (pack xs))

prop_elemIndexCL :: String8 -> Char8 -> Bool
Expand Down Expand Up @@ -2406,6 +2439,10 @@ ll_tests =
, testProperty "index" prop_index
, testProperty "index" prop_index_D
, testProperty "index" prop_index_C
, testProperty "indexMaybe" prop_indexMaybe_Just_P
, testProperty "indexMaybe" prop_indexMaybe_Just_L
, testProperty "indexMaybe" prop_indexMaybe_Nothing_P
, testProperty "indexMaybe" prop_indexMaybe_Nothing_L
, testProperty "elemIndex" prop_elemIndex
, testProperty "elemIndices" prop_elemIndices
, testProperty "count/elemIndices" prop_count
Expand Down

0 comments on commit f35e9e5

Please sign in to comment.