Skip to content
Snippets Groups Projects
Unverified Commit 1b275ff7 authored by Oleg Grenrus's avatar Oleg Grenrus Committed by GitHub
Browse files

Merge pull request #308 from phadej/pr-306-span-break-doctest

Add examples to 'span' and 'break'
parents dce58c13 c1d610b5
No related branches found
Tags 1.2.4.1
No related merge requests found
......@@ -1359,6 +1359,9 @@ splitAt n t@(Text arr off len)
-- a pair whose first element is the longest prefix (possibly empty)
-- of @t@ of elements that satisfy @p@, and whose second is the
-- remainder of the list.
--
-- >>> T.span (=='0') "000AB"
-- ("000","AB")
span :: (Char -> Bool) -> Text -> (Text, Text)
span p t = case span_ p t of
(# hd,tl #) -> (hd,tl)
......@@ -1366,6 +1369,9 @@ span p t = case span_ p t of
-- | /O(n)/ 'break' is like 'span', but the prefix returned is
-- over elements that fail the predicate @p@.
--
-- >>> T.break (=='c') "180cm"
-- ("180","cm")
break :: (Char -> Bool) -> Text -> (Text, Text)
break p = span (not . p)
{-# INLINE break #-}
......
......@@ -307,6 +307,11 @@ import Text.Printf (PrintfArg, formatArg, formatString)
-- measure. For details, see
-- <http://unicode.org/reports/tr36/#Deletion_of_Noncharacters Unicode Technical Report 36, §3.5 >.)
-- $setup
-- >>> import Data.Text
-- >>> import qualified Data.Text as T
-- >>> :seti -XOverloadedStrings
equal :: Text -> Text -> Bool
equal Empty Empty = True
equal Empty _ = False
......@@ -1385,6 +1390,9 @@ breakOnAll pat src
-- | /O(n)/ 'break' is like 'span', but the prefix returned is over
-- elements that fail the predicate @p@.
--
-- >>> T.break (=='c') "180cm"
-- ("180","cm")
break :: (Char -> Bool) -> Text -> (Text, Text)
break p t0 = break' t0
where break' Empty = (empty, empty)
......@@ -1400,6 +1408,9 @@ break p t0 = break' t0
-- a pair whose first element is the longest prefix (possibly empty)
-- of @t@ of elements that satisfy @p@, and whose second is the
-- remainder of the list.
--
-- >>> T.span (=='0') "000AB"
-- ("000","AB")
span :: (Char -> Bool) -> Text -> (Text, Text)
span p = break (not . p)
{-# INLINE span #-}
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment