[commit: packages/bytestring] master: Added Data.ByteString.Lazy.elemIndexEnd implementation (8312989)

git at git.haskell.org git at git.haskell.org
Fri Jan 23 22:41:59 UTC 2015


Repository : ssh://git@git.haskell.org/bytestring

On branch  : master
Link       : http://git.haskell.org/packages/bytestring.git/commitdiff/831298906342f9d8cd0f5ae6f2ed0e9dd474a281

>---------------------------------------------------------------

commit 831298906342f9d8cd0f5ae6f2ed0e9dd474a281
Author: David Turner <dave.c.turner at gmail.com>
Date:   Thu Feb 27 11:24:09 2014 +0000

    Added Data.ByteString.Lazy.elemIndexEnd implementation


>---------------------------------------------------------------

831298906342f9d8cd0f5ae6f2ed0e9dd474a281
 Data/ByteString/Lazy.hs | 23 +++++++++++------------
 tests/Properties.hs     | 10 ++++++++++
 2 files changed, 21 insertions(+), 12 deletions(-)

diff --git a/Data/ByteString/Lazy.hs b/Data/ByteString/Lazy.hs
index 22ba1ee..d4fe0d2 100644
--- a/Data/ByteString/Lazy.hs
+++ b/Data/ByteString/Lazy.hs
@@ -166,6 +166,7 @@ module Data.ByteString.Lazy (
         -- * Indexing ByteStrings
         index,                  -- :: ByteString -> Int64 -> Word8
         elemIndex,              -- :: Word8 -> ByteString -> Maybe Int64
+        elemIndexEnd,           -- :: Word8 -> ByteString -> Maybe Int64
         elemIndices,            -- :: Word8 -> ByteString -> [Int64]
         findIndex,              -- :: (Word8 -> Bool) -> ByteString -> Maybe Int64
         findIndices,            -- :: (Word8 -> Bool) -> ByteString -> [Int64]
@@ -222,6 +223,7 @@ import qualified Data.ByteString.Unsafe as S
 import Data.ByteString.Lazy.Internal
 
 import Data.Monoid              (Monoid(..))
+import Control.Monad            (mplus)
 
 import Data.Word                (Word8)
 import Data.Int                 (Int64)
@@ -904,7 +906,6 @@ elemIndex w cs0 = elemIndex' 0 cs0
             Nothing -> elemIndex' (n + fromIntegral (S.length c)) cs
             Just i  -> Just (n + fromIntegral i)
 
-{-
 -- | /O(n)/ The 'elemIndexEnd' function returns the last index of the
 -- element in the given 'ByteString' which is equal to the query
 -- element, or 'Nothing' if there is no such element. The following
@@ -912,18 +913,16 @@ elemIndex w cs0 = elemIndex' 0 cs0
 --
 -- > elemIndexEnd c xs == 
 -- > (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
---
-elemIndexEnd :: Word8 -> ByteString -> Maybe Int
-elemIndexEnd ch (PS x s l) = accursedUnutterablePerformIO $ withForeignPtr x $ \p ->
-    go (p `plusPtr` s) (l-1)
+
+elemIndexEnd :: Word8 -> ByteString -> Maybe Int64
+elemIndexEnd w = elemIndexEnd' 0
   where
-    STRICT2(go)
-    go p i | i < 0     = return Nothing
-           | otherwise = do ch' <- peekByteOff p i
-                            if ch == ch'
-                                then return $ Just i
-                                else go p (i-1)
--}
+    elemIndexEnd' _ Empty = Nothing
+    elemIndexEnd' n (Chunk c cs) = let
+      n' = n + S.length c
+      i = fmap (fromIntegral . (n +)) $ S.elemIndexEnd w c
+      in n' `seq` i `seq` elemIndexEnd' n' cs `mplus` i
+
 -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning
 -- the indices of all elements equal to the query element, in ascending order.
 -- This implementation uses memchr(3).
diff --git a/tests/Properties.hs b/tests/Properties.hs
index 9f60552..729e649 100644
--- a/tests/Properties.hs
+++ b/tests/Properties.hs
@@ -1090,6 +1090,14 @@ prop_elemIndexEnd1CC c xs = (C.elemIndexEnd c (C.pack xs)) ==
 prop_elemIndexEnd2BB c xs = (P.elemIndexEnd c (P.pack xs)) ==
                            ((-) (length xs - 1) `fmap` P.elemIndex c (P.pack $ reverse xs))
 
+prop_elemIndexEnd1LL c xs = (L.elemIndexEnd c (L.pack xs)) ==
+                           (case L.elemIndex c (L.pack (reverse xs)) of
+                                Nothing -> Nothing
+                                Just i  -> Just (fromIntegral (length xs) -1 -i))
+
+prop_elemIndexEnd2LL c xs = (L.elemIndexEnd c (L.pack xs)) ==
+                           ((-) (fromIntegral (length xs) - 1) `fmap` L.elemIndex c (L.pack $ reverse xs))
+
 prop_elemIndicesBB xs c = elemIndices c xs == P.elemIndices c (P.pack xs)
 
 prop_findIndexBB xs a = (findIndex (==a) xs) == (P.findIndex (==a) (P.pack xs))
@@ -2333,6 +2341,8 @@ bb_tests =
     , testProperty "elemIndexEnd 1" prop_elemIndexEnd1BB
     , testProperty "elemIndexEnd 1" prop_elemIndexEnd1CC
     , testProperty "elemIndexEnd 2" prop_elemIndexEnd2BB
+    , testProperty "elemIndexEnd 1" prop_elemIndexEnd1LL
+    , testProperty "elemIndexEnd 2" prop_elemIndexEnd2LL
 --  , testProperty "words'"         prop_wordsBB'
 --  , testProperty "lines'"         prop_linesBB'
 --  , testProperty "dropSpaceEnd"   prop_dropSpaceEndBB



More information about the ghc-commits mailing list