Copyright | (c) Dong Han 2017-2018 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Various combinators works on Text
s.
Synopsis
- cons :: Char -> Text -> Text
- snoc :: Text -> Char -> Text
- uncons :: Text -> Maybe (Char, Text)
- unsnoc :: Text -> Maybe (Text, Char)
- headMaybe :: Text -> Maybe Char
- tailMayEmpty :: Text -> Text
- lastMaybe :: Text -> Maybe Char
- initMayEmpty :: Text -> Text
- head :: Text -> Char
- tail :: Text -> Text
- last :: Text -> Char
- init :: Text -> Text
- inits :: Text -> [Text]
- tails :: Text -> [Text]
- take :: Int -> Text -> Text
- drop :: Int -> Text -> Text
- takeR :: Int -> Text -> Text
- dropR :: Int -> Text -> Text
- slice :: Int -> Int -> Text -> Text
- splitAt :: Int -> Text -> (Text, Text)
- takeWhile :: (Char -> Bool) -> Text -> Text
- takeWhileR :: (Char -> Bool) -> Text -> Text
- dropWhile :: (Char -> Bool) -> Text -> Text
- dropWhileR :: (Char -> Bool) -> Text -> Text
- dropAround :: (Char -> Bool) -> Text -> Text
- break :: (Char -> Bool) -> Text -> (Text, Text)
- span :: (Char -> Bool) -> Text -> (Text, Text)
- breakR :: (Char -> Bool) -> Text -> (Text, Text)
- spanR :: (Char -> Bool) -> Text -> (Text, Text)
- breakOn :: Text -> Text -> (Text, Text)
- breakOnAll :: Text -> Text -> [(Text, Text)]
- group :: Text -> [Text]
- groupBy :: (Char -> Char -> Bool) -> Text -> [Text]
- stripPrefix :: Text -> Text -> Maybe Text
- stripSuffix :: Text -> Text -> Maybe Text
- split :: Char -> Text -> [Text]
- splitWith :: (Char -> Bool) -> Text -> [Text]
- splitOn :: Text -> Text -> [Text]
- isPrefixOf :: Text -> Text -> Bool
- isSuffixOf :: Text -> Text -> Bool
- isInfixOf :: Text -> Text -> Bool
- commonPrefix :: Text -> Text -> (Text, Text, Text)
- words :: Text -> [Text]
- lines :: Text -> [Text]
- unwords :: [Text] -> Text
- unlines :: [Text] -> Text
- padLeft :: Int -> Char -> Text -> Text
- padRight :: Int -> Char -> Text -> Text
- reverse :: Text -> Text
- intersperse :: Char -> Text -> Text
- intercalate :: Text -> [Text] -> Text
- intercalateElem :: Char -> [Text] -> Text
- transpose :: [Text] -> [Text]
Slice manipulation
cons :: Char -> Text -> Text Source #
O(n) cons
is analogous to (:) for lists, but of different
complexity, as it requires making a copy.
uncons :: Text -> Maybe (Char, Text) Source #
O(1) Extract the head and tail of a text, return Nothing
if it is empty.
unsnoc :: Text -> Maybe (Text, Char) Source #
O(1) Extract the init and last of a text, return Nothing
if text is empty.
tailMayEmpty :: Text -> Text Source #
O(1) Extract the chars after the head of a text.
NOTE: tailMayEmpty
return empty text in the case of an empty text.
initMayEmpty :: Text -> Text Source #
O(1) Extract the chars before of the last one.
NOTE: initMayEmpty
return empty text in the case of an empty text.
O(1) Extract the first char of a text.
Throw EmptyText
if text is empty.
O(1) Extract the chars after the head of a text.
Throw EmptyText
if text is empty.
O(1) Extract the chars before of the last one.
Throw EmptyText
if text is empty.
slice :: Int -> Int -> Text -> Text Source #
O(1) Extract a sub-range text with give start index and length.
This function is a total function just like 'take/drop', index/length exceeds range will be ingored, e.g.
slice 1 3 "hello" == "ell" slice -1 -1 "hello" == "" slice -2 2 "hello" == "" slice 2 10 "hello" == "llo"
This holds for all x y: slice x y vs == drop x . take (x+y) vs
takeWhile :: (Char -> Bool) -> Text -> Text Source #
O(n) Applied to a predicate p
and a text t
,
returns the longest prefix (possibly empty) of t
of elements that
satisfy p
.
takeWhileR :: (Char -> Bool) -> Text -> Text Source #
O(n) Applied to a predicate p
and a text t
,
returns the longest suffix (possibly empty) of t
of elements that
satisfy p
.
dropWhile :: (Char -> Bool) -> Text -> Text Source #
O(n) Applied to a predicate p
and a text vs
,
returns the suffix (possibly empty) remaining after takeWhile
p vs
.
dropWhileR :: (Char -> Bool) -> Text -> Text Source #
O(n) Applied to a predicate p
and a text vs
,
returns the prefix (possibly empty) remaining before takeWhileR
p vs
.
break :: (Char -> Bool) -> Text -> (Text, Text) Source #
O(n) Split the text into the longest prefix of elements that do not satisfy the predicate and the rest without copying.
span :: (Char -> Bool) -> Text -> (Text, Text) Source #
O(n) Split the text into the longest prefix of elements that satisfy the predicate and the rest without copying.
breakOn :: Text -> Text -> (Text, Text) Source #
Break a text on a subtext, returning a pair of the part of the text prior to the match, and the rest of the text, e.g.
break "wor" "hello, world" = ("hello, ", "world")
O(n+m) Find all non-overlapping instances of needle in haystack. Each element of the returned list consists of a pair:
- The entire string prior to the kth match (i.e. the prefix)
- The kth match, followed by the remainder of the string
Examples:
breakOnAll "::" "" ==> [] breakOnAll "" "abc" ==> [("a", "bc"), ("ab", "c"), ("abc", "/")]
The result list is lazy, search is performed when you force the list.
group :: Text -> [Text] Source #
The group function takes a text and returns a list of texts such that the concatenation of the result is equal to the argument. Moreover, each sublist in the result contains only equal elements. For example,
group Mississippi = [M,"i","ss","i","ss","i","pp","i"]
It is a special case of groupBy
, which allows the programmer to supply their own equality test.
stripPrefix :: Text -> Text -> Maybe Text Source #
O(n) The stripPrefix
function takes two texts and returns Just
the remainder of the second iff the first is its prefix, and otherwise
Nothing
.
stripSuffix :: Text -> Text -> Maybe Text Source #
O(n) The stripSuffix
function takes two texts and returns Just the remainder of the second iff the first is its suffix, and otherwise Nothing.
split :: Char -> Text -> [Text] Source #
O(n) Break a text into pieces separated by the delimiter element consuming the delimiter. I.e.
split '\n' "a\nb\nd\ne" == ["a","b","d","e"] split 'a' "aXaXaXa" == ["","X","X","X",""] split 'x' "x" == ["",""]
and
intercalate [c] . split c == id split == splitWith . (==)
NOTE, this function behavior different with bytestring's. see #56.
splitWith :: (Char -> Bool) -> Text -> [Text] Source #
O(n) Splits a text into components delimited by separators, where the predicate returns True for a separator char. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg.
splitWith (=='a') "aabbaca" == ["","","bb","c",""] splitWith (=='a') [] == [""]
splitOn :: Text -> Text -> [Text] Source #
O(m+n) Break haystack into pieces separated by needle.
Note: An empty needle will essentially split haystack element by element.
Examples:
>>>
splitOn "\r\n" "a\r\nb\r\nd\r\ne"
["a","b","d","e"]
>>>
splitOn "aaa" "aaaXaaaXaaaXaaa"
["","X","X","X",""]
>>>
splitOn "x" "x"
["",""]
and
intercalate s . splitOn s == id splitOn (singleton c) == split (==c)
isPrefixOf :: Text -> Text -> Bool Source #
The isPrefix
function returns True
if the first argument is a prefix of the second.
isSuffixOf :: Text -> Text -> Bool Source #
O(n) The isSuffixOf
function takes two text and returns True
if the first is a suffix of the second.
isInfixOf :: Text -> Text -> Bool Source #
Check whether one text is a subtext of another.
needle
.isInfixOf
haystack === null haystack || indices needle haystake /= []
commonPrefix :: Text -> Text -> (Text, Text, Text) Source #
O(n) Find the longest non-empty common prefix of two strings and return it, along with the suffixes of each string at which they no longer match. e.g.
>>>
commonPrefix "foobar" "fooquux"
("foo","bar","quux")
>>>
commonPrefix "veeble" "fetzer"
("","veeble","fetzer")
words :: Text -> [Text] Source #
O(n) Breaks a Bytes
up into a list of words, delimited by unicode space.
unlines :: [Text] -> Text Source #
O(n) Joins lines with ascii n
.
NOTE: This functions is different from unlines
, it DOES NOT add a trailing n
.
padLeft :: Int -> Char -> Text -> Text Source #
Add padding to the left so that the whole text's length is at least n.
padRight :: Int -> Char -> Text -> Text Source #
Add padding to the right so that the whole text's length is at least n.
Transform
intersperse :: Char -> Text -> Text Source #
O(n) The intersperse
function takes a character and places it
between the characters of a Text
. Performs replacement on invalid scalar values.
intercalate :: Text -> [Text] -> Text Source #
O(n) The intercalate
function takes a Text
and a list of
Text
s and concatenates the list after interspersing the first
argument between each element of the list.