Skip to content

Commit 1578346

Browse files
committed
Add spanEnd and breakEnd to Data.Text
1 parent 8d1b6ff commit 1578346

File tree

2 files changed

+33
-2
lines changed

2 files changed

+33
-2
lines changed

src/Data/Text.hs

Lines changed: 21 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,9 @@ module Data.Text
141141
, breakOn
142142
, breakOnEnd
143143
, break
144+
, breakEnd
144145
, span
146+
, spanEnd
145147
, group
146148
, groupBy
147149
, inits
@@ -221,7 +223,7 @@ import qualified Data.Text.Internal.Fusion as S
221223
import qualified Data.Text.Internal.Fusion.Common as S
222224
import Data.Text.Encoding (decodeUtf8', encodeUtf8)
223225
import Data.Text.Internal.Fusion (stream, reverseStream, unstream)
224-
import Data.Text.Internal.Private (span_)
226+
import Data.Text.Internal.Private (span_, spanEnd_)
225227
import Data.Text.Internal (Text(..), empty, firstf, mul, safe, text)
226228
import Data.Text.Show (singleton, unpack, unpackCString#)
227229
import qualified Prelude as P
@@ -1333,6 +1335,15 @@ span p t = case span_ p t of
13331335
(# hd,tl #) -> (hd,tl)
13341336
{-# INLINE span #-}
13351337

1338+
-- | /O(n)/ Similar to 'span', but searches from the end of the
1339+
-- string.
1340+
--
1341+
-- >>> T.spanEnd (=='0') "AB000"
1342+
-- ("AB", "000")
1343+
spanEnd :: (Char -> Bool) -> Text -> (Text, Text)
1344+
spanEnd p t = case spanEnd_ p t of (# hd, tl #) -> (hd, tl)
1345+
{-# inline spanEnd #-}
1346+
13361347
-- | /O(n)/ 'break' is like 'span', but the prefix returned is
13371348
-- over elements that fail the predicate @p@.
13381349
--
@@ -1342,6 +1353,15 @@ break :: (Char -> Bool) -> Text -> (Text, Text)
13421353
break p = span (not . p)
13431354
{-# INLINE break #-}
13441355

1356+
-- | /O(n)/ Similar to 'break', but searches from the end of the
1357+
-- string.
1358+
--
1359+
-- >>> T.breakEnd (=='0') "180cm"
1360+
-- ("180","cm")
1361+
breakEnd :: (Char -> Bool) -> Text -> (Text, Text)
1362+
breakEnd p = spanEnd (not . p)
1363+
{-# inline breakEnd #-}
1364+
13451365
-- | /O(n)/ Group characters in a string according to a predicate.
13461366
groupBy :: (Char -> Char -> Bool) -> Text -> [Text]
13471367
groupBy p = loop

src/Data/Text/Internal/Private.hs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,12 @@ module Data.Text.Internal.Private
1313
(
1414
runText
1515
, span_
16+
, spanEnd_
1617
) where
1718

1819
import Control.Monad.ST (ST, runST)
1920
import Data.Text.Internal (Text(..), text)
20-
import Data.Text.Unsafe (Iter(..), iter)
21+
import Data.Text.Unsafe (Iter(..), iter, reverseIter)
2122
import qualified Data.Text.Array as A
2223

2324
span_ :: (Char -> Bool) -> Text -> (# Text, Text #)
@@ -30,6 +31,16 @@ span_ p t@(Text arr off len) = (# hd,tl #)
3031
where Iter c d = iter t i
3132
{-# INLINE span_ #-}
3233

34+
spanEnd_ :: (Char -> Bool) -> Text -> (# Text, Text #)
35+
spanEnd_ p t@(Text arr off len) = (# hd, tl #)
36+
where hd = text arr off (k+1)
37+
tl = text arr (off+k+1) (len-k-1)
38+
!k = loop (len-1)
39+
loop !i | i >= off && p c = loop (i+d)
40+
| otherwise = i
41+
where (c, d) = reverseIter t i
42+
{-# INLINE spanEnd_ #-}
43+
3344
runText :: (forall s. (A.MArray s -> Int -> ST s Text) -> ST s Text) -> Text
3445
runText act = runST (act $ \ !marr !len -> do
3546
arr <- A.unsafeFreeze marr

0 commit comments

Comments
 (0)