Skip to content

Commit

Permalink
Get rid of the elem function.
Browse files Browse the repository at this point in the history
--HG--
extra : convert_revision : 74db040a17a6b7623b2a23c9a4ac0cdf8133ddde
  • Loading branch information
bos committed Oct 9, 2009
1 parent 8c1753f commit a2a4524
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 21 deletions.
21 changes: 10 additions & 11 deletions Data/Text.hs
Expand Up @@ -140,7 +140,6 @@ module Data.Text
, isInfixOf

-- * Searching
, elem
, filter
, find
, findBy
Expand Down Expand Up @@ -966,14 +965,6 @@ chunksOf k = go
-- ----------------------------------------------------------------------------
-- * Searching

-------------------------------------------------------------------------------
-- ** Searching by equality

-- | /O(n)/ 'elem' is the 'Text' membership predicate.
elem :: Char -> Text -> Bool
elem c t = S.elem c (stream t)
{-# INLINE elem #-}

-------------------------------------------------------------------------------
-- ** Searching with a predicate

Expand Down Expand Up @@ -1222,8 +1213,16 @@ isSuffixOf a@(Text _aarr _aoff alen) b@(Text barr boff blen) =
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
isInfixOf :: Text -> Text -> Bool
isInfixOf pat src = null pat || (not . L.null $ indices pat src)
{-# INLINE isInfixOf #-}
isInfixOf needle haystack
| null needle = True
| isSingleton needle = S.elem (unsafeHead needle) . S.stream $ haystack
| otherwise = not . L.null . indices needle $ haystack
{-# INLINE [1] isInfixOf #-}

{-# RULES
"TEXT isInfixOf/singleton -> S.elem/S.stream" [~1] forall n h.
isInfixOf (singleton n) h = S.elem n (S.stream h)
#-}

emptyError :: String -> a
emptyError fun = P.error ("Data.Text." ++ fun ++ ": empty input")
6 changes: 0 additions & 6 deletions Data/Text/Lazy.hs
Expand Up @@ -144,7 +144,6 @@ module Data.Text.Lazy
, isInfixOf

-- * Searching
, elem
, filter
, findBy
, partitionBy
Expand Down Expand Up @@ -1043,11 +1042,6 @@ isInfixOf needle haystack = L.any (isPrefixOf needle) (tails haystack)
{-# INLINE isInfixOf #-}
-- TODO: a better implementation

-- | /O(n)/ 'elem' is the 'Text' membership predicate.
elem :: Char -> Text -> Bool
elem c t = S.elem c (stream t)
{-# INLINE elem #-}

-- | /O(n)/ 'filter', applied to a predicate and a 'Text',
-- returns a 'Text' containing those characters that satisfy the
-- predicate.
Expand Down
4 changes: 0 additions & 4 deletions tests/Properties.hs
Expand Up @@ -466,8 +466,6 @@ t_isInfixOf s = L.isInfixOf s `eqP` T.isInfixOf (packS s)
tl_isInfixOf s = L.isInfixOf s `eqP` TL.isInfixOf (packS s)

sf_elem p c = (L.elem c . L.filter p) `eqP` (S.elem c . S.filter p)
t_elem c = L.elem c `eqP` T.elem c
tl_elem c = L.elem c `eqP` TL.elem c
sf_filter q p = (L.filter p . L.filter q) `eqP` (unpackS . S.filter p . S.filter q)
t_filter p = L.filter p `eqP` (unpackS . T.filter p)
tl_filter p = L.filter p `eqP` (unpackS . TL.filter p)
Expand Down Expand Up @@ -832,8 +830,6 @@ tests = [

testGroup "searching" [
testProperty "sf_elem" sf_elem,
testProperty "t_elem" t_elem,
testProperty "tl_elem" tl_elem,
testProperty "sf_filter" sf_filter,
testProperty "t_filter" t_filter,
testProperty "tl_filter" tl_filter,
Expand Down

0 comments on commit a2a4524

Please sign in to comment.