Skip to content

Commit

Permalink
Fix bounds check, add tests
Browse files Browse the repository at this point in the history
  • Loading branch information
TheMatten committed May 13, 2021
1 parent f2a3080 commit 01a2ec0
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 6 deletions.
8 changes: 4 additions & 4 deletions src/Data/Text/Internal/Private.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,11 +34,11 @@ span_ p t@(Text arr off len) = (# hd,tl #)
spanEnd_ :: (Char -> Bool) -> Text -> (# Text, Text #)
spanEnd_ p t@(Text arr off len) = (# hd,tl #)
where hd = text arr off (k+1)
tl = text arr (off+k+1) (len-k-1)
tl = text arr (off+k+1) (len-(k+1))
!k = loop (len-1)
loop !i | i >= off && p c = loop (i+d)
| otherwise = i
where (c,d) = reverseIter t i
loop !i | i >= 0 && p c = loop (i+d)
| otherwise = i
where (c,d) = reverseIter t i
{-# INLINE spanEnd_ #-}

runText :: (forall s. (A.MArray s -> Int -> ST s Text) -> ST s Text) -> Text
Expand Down
21 changes: 19 additions & 2 deletions tests/Tests/Properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -618,8 +618,14 @@ t_strip = T.dropAround isSpace `eq` T.strip
tl_strip = TL.dropAround isSpace `eq` TL.strip
t_splitAt n = L.splitAt n `eqP` (unpack2 . T.splitAt n)
tl_splitAt n = L.splitAt n `eqP` (unpack2 . TL.splitAt (fromIntegral n))
t_span p = L.span p `eqP` (unpack2 . T.span p)
tl_span p = L.span p `eqP` (unpack2 . TL.span p)
t_span p = L.span p `eqP` (unpack2 . T.span p)
tl_span p = L.span p `eqP` (unpack2 . TL.span p)
t_spanEnd p = spanEnd p `eqP` (unpack2 . T.spanEnd p)
tl_spanEnd p = spanEnd p `eqP` (unpack2 . TL.spanEnd p)

spanEnd :: (a -> Bool) -> [a] -> ([a], [a])
spanEnd p l = case span p $ reverse l of
(s, e) -> (reverse e, reverse s)

t_breakOn_id s = squid `eq` (uncurry T.append . T.breakOn s)
where squid t | T.null s = error "empty"
Expand All @@ -641,6 +647,13 @@ tl_breakOnEnd_end (NotEmpty s) t =
in k `TL.isSuffixOf` t && (TL.null m || s `TL.isSuffixOf` m)
t_break p = L.break p `eqP` (unpack2 . T.break p)
tl_break p = L.break p `eqP` (unpack2 . TL.break p)
t_breakEnd p = breakEnd p `eqP` (unpack2 . T.breakEnd p)
tl_breakEnd p = breakEnd p `eqP` (unpack2 . TL.breakEnd p)

breakEnd :: (a -> Bool) -> [a] -> ([a], [a])
breakEnd p l = case break p $ reverse l of
(s, e) -> (reverse e, reverse s)

t_group = L.group `eqP` (map unpackS . T.group)
tl_group = L.group `eqP` (map unpackS . TL.group)
t_groupBy p = L.groupBy p `eqP` (map unpackS . T.groupBy p)
Expand Down Expand Up @@ -1264,6 +1277,8 @@ tests =
testProperty "tl_splitAt" tl_splitAt,
testProperty "t_span" t_span,
testProperty "tl_span" tl_span,
testProperty "t_spanEnd" t_spanEnd,
testProperty "tl_spanEnd" tl_spanEnd,
testProperty "t_breakOn_id" t_breakOn_id,
testProperty "tl_breakOn_id" tl_breakOn_id,
testProperty "t_breakOn_start" t_breakOn_start,
Expand All @@ -1272,6 +1287,8 @@ tests =
testProperty "tl_breakOnEnd_end" tl_breakOnEnd_end,
testProperty "t_break" t_break,
testProperty "tl_break" tl_break,
testProperty "t_breakEnd" t_breakEnd,
testProperty "tl_breakEnd" tl_breakEnd,
testProperty "t_group" t_group,
testProperty "tl_group" tl_group,
testProperty "t_groupBy" t_groupBy,
Expand Down

0 comments on commit 01a2ec0

Please sign in to comment.