rio-0.1.11.0: A standard library for Haskell

Safe HaskellSafe
LanguageHaskell2010

RIO.Text.Lazy.Partial

Contents

Description

Lazy Text partial functions. Import as:

import qualified RIO.Text.Lazy.Partial as TL'
Synopsis

Creation and elimination

head :: Text -> Char #

O(1) Returns the first character of a Text, which must be non-empty. Subject to fusion.

last :: Text -> Char #

O(n/c) Returns the last character of a Text, which must be non-empty. Subject to fusion.

tail :: Text -> Text #

O(1) Returns all characters after the head of a Text, which must be non-empty. Subject to fusion.

init :: Text -> Text #

O(n/c) Returns all but the last character of a Text, which must be non-empty. Subject to fusion.

Transformations

replace #

Arguments

:: Text

needle to search for. If this string is empty, an error will occur.

-> Text

replacement to replace needle with.

-> Text

haystack in which to search.

-> Text 

O(m+n) Replace every non-overlapping occurrence of needle in haystack with replacement.

This function behaves as though it was defined as follows:

replace needle replacement haystack =
  intercalate replacement (splitOn needle haystack)

As this suggests, each occurrence is replaced exactly once. So if needle occurs in replacement, that occurrence will not itself be replaced recursively:

replace "oo" "foo" "oo" == "foo"

In cases where several instances of needle overlap, only the first one will be replaced:

replace "ofo" "bar" "ofofo" == "barfo"

In (unlikely) bad cases, this function's time complexity degrades towards O(n*m).

Folds

foldl1 :: (Char -> Char -> Char) -> Text -> Char #

O(n) A variant of foldl that has no starting value argument, and thus must be applied to a non-empty Text. Subject to fusion.

foldl1' :: (Char -> Char -> Char) -> Text -> Char #

O(n) A strict version of foldl1. Subject to fusion.

foldr1 :: (Char -> Char -> Char) -> Text -> Char #

O(n) A variant of foldr that has no starting value argument, and thus must be applied to a non-empty Text. Subject to fusion.

Special folds

maximum :: Text -> Char #

O(n) maximum returns the maximum value from a Text, which must be non-empty. Subject to fusion.

minimum :: Text -> Char #

O(n) minimum returns the minimum value from a Text, which must be non-empty. Subject to fusion.

Substrings

Breaking strings

breakOn :: Text -> Text -> (Text, Text) #

O(n+m) Find the first instance of needle (which must be non-null) in haystack. The first element of the returned tuple is the prefix of haystack before needle is matched. The second is the remainder of haystack, starting with the match.

Examples:

breakOn "::" "a::b::c" ==> ("a", "::b::c")
breakOn "/" "foobar"   ==> ("foobar", "")

Laws:

append prefix match == haystack
  where (prefix, match) = breakOn needle haystack

If you need to break a string by a substring repeatedly (e.g. you want to break on every instance of a substring), use breakOnAll instead, as it has lower startup overhead.

This function is strict in its first argument, and lazy in its second.

In (unlikely) bad cases, this function's time complexity degrades towards O(n*m).

breakOnEnd :: Text -> Text -> (Text, Text) #

O(n+m) Similar to breakOn, but searches from the end of the string.

The first element of the returned tuple is the prefix of haystack up to and including the last match of needle. The second is the remainder of haystack, following the match.

breakOnEnd "::" "a::b::c" ==> ("a::b::", "c")

Breaking into many substrings

splitOn #

Arguments

:: Text

String to split on. If this string is empty, an error will occur.

-> Text

Input text.

-> [Text] 

O(m+n) Break a Text into pieces separated by the first Text argument (which cannot be an empty string), consuming the delimiter. An empty delimiter is invalid, and will cause an error to be raised.

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)

(Note: the string s to split on above cannot be empty.)

This function is strict in its first argument, and lazy in its second.

In (unlikely) bad cases, this function's time complexity degrades towards O(n*m).

Searching

breakOnAll #

Arguments

:: Text

needle to search for

-> Text

haystack in which to search

-> [(Text, Text)] 

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 "/" "a/b/c/"
==> [("a", "/b/c/"), ("a/b", "/c/"), ("a/b/c", "/")]

This function is strict in its first argument, and lazy in its second.

In (unlikely) bad cases, this function's time complexity degrades towards O(n*m).

The needle parameter may not be empty.