-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | An efficient packed Unicode text type. -- -- An efficient packed, immutable Unicode text type (both strict and -- lazy), with a powerful loop fusion optimization framework. -- -- The Text type represents Unicode character strings, in a time -- and space-efficient manner. This package provides text processing -- capabilities that are optimized for performance critical use, both in -- terms of large data quantities and high speed. -- -- The Text type provides character-encoding, type-safe case -- conversion via whole-string case conversion functions. It also -- provides a range of functions for converting Text values to and -- from ByteStrings, using several standard encodings. -- -- Efficient locale-sensitive support for text IO is also supported. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
-- import qualified Data.Text as T ---- -- To use an extended and very rich family of functions for working with -- Unicode text (including normalization, regular expressions, -- non-standard encodings, text breaking, and locales), see the -- text-icu package: -- http://hackage.haskell.org/package/text-icu @package text @version 1.2.2.2 -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Fast, unchecked bit shifting functions. module Data.Text.Internal.Unsafe.Shift -- | This is a workaround for poor optimisation in GHC 6.8.2. It fails to -- notice constant-width shifts, and adds a test and branch to every -- shift. This imposes about a 10% performance hit. -- -- These functions are undefined when the amount being shifted by is -- greater than the size in bits of a machine Int#. class UnsafeShift a shiftL :: UnsafeShift a => a -> Int -> a shiftR :: UnsafeShift a => a -> Int -> a instance Data.Text.Internal.Unsafe.Shift.UnsafeShift GHC.Word.Word16 instance Data.Text.Internal.Unsafe.Shift.UnsafeShift GHC.Word.Word32 instance Data.Text.Internal.Unsafe.Shift.UnsafeShift GHC.Word.Word64 instance Data.Text.Internal.Unsafe.Shift.UnsafeShift GHC.Types.Int -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- A module containing unsafe operations, for very very -- careful use in heavily tested code. module Data.Text.Internal.Unsafe -- | Allow an ST computation to be deferred lazily. When passed an -- action of type ST s a, the action will only -- be performed when the value of a is demanded. -- -- This function is identical to the normal unsafeInterleaveST, but is -- inlined and hence faster. -- -- Note: This operation is highly unsafe, as it can introduce -- externally visible non-determinism into an ST action. inlineInterleaveST :: ST s a -> ST s a -- | Just like unsafePerformIO, but we inline it. Big performance gains as -- it exposes lots of things to further inlining. Very unsafe. In -- particular, you should do no memory allocation inside an -- inlinePerformIO block. On Hugs this is just -- unsafePerformIO. inlinePerformIO :: IO a -> a -- | Common internal functions for reading textual data. module Data.Text.Internal.Read type IReader t a = t -> Either String (a, t) newtype IParser t a P :: IReader t a -> IParser t a [runP] :: IParser t a -> IReader t a data T T :: !Integer -> !Int -> T digitToInt :: Char -> Int hexDigitToInt :: Char -> Int perhaps :: a -> IParser t a -> IParser t a instance GHC.Base.Functor (Data.Text.Internal.Read.IParser t) instance GHC.Base.Applicative (Data.Text.Internal.Read.IParser t) instance GHC.Base.Monad (Data.Text.Internal.Read.IParser t) -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Useful functions. module Data.Text.Internal.Functions -- | A lazier version of Data.List.intersperse. The other version causes -- space leaks! intersperse :: a -> [a] -> [a] -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Basic UTF-32 validation. module Data.Text.Internal.Encoding.Utf32 validate :: Word32 -> Bool -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Basic UTF-16 validation and character manipulation. module Data.Text.Internal.Encoding.Utf16 chr2 :: Word16 -> Word16 -> Char validate1 :: Word16 -> Bool validate2 :: Word16 -> Word16 -> Bool -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! module Data.Text.Internal.Builder.RealFloat.Functions roundTo :: Int -> [Int] -> (Int, [Int]) module Data.Text.Internal.Builder.Int.Digits digits :: ByteString -- | Types and functions for dealing with encoding and decoding errors in -- Unicode text. -- -- The standard functions for encoding and decoding text are strict, -- which is to say that they throw exceptions on invalid input. This is -- often unhelpful on real world input, so alternative functions exist -- that accept custom handlers for dealing with invalid inputs. These -- OnError handlers are normal Haskell functions. You can use one -- of the presupplied functions in this module, or you can write a custom -- handler of your own. module Data.Text.Encoding.Error -- | An exception type for representing Unicode encoding errors. data UnicodeException -- | Could not decode a byte sequence because it was invalid under the -- given encoding, or ran out of input in mid-decode. DecodeError :: String -> (Maybe Word8) -> UnicodeException -- | Tried to encode a character that could not be represented under the -- given encoding, or ran out of input in mid-encode. -- | Deprecated: This constructor is never used, and will be -- removed. EncodeError :: String -> (Maybe Char) -> UnicodeException -- | Function type for handling a coding error. It is supplied with two -- inputs: -- --
-- import qualified Data.Text.Array as A ---- -- The names in this module resemble those in the Array family of -- modules, but are shorter due to the assumption of qualified naming. module Data.Text.Array -- | Immutable array type. data Array Array :: ByteArray# -> Array [aBA] :: Array -> ByteArray# -- | Mutable array type, for use in the ST monad. data MArray s MArray :: MutableByteArray# s -> MArray s [maBA] :: MArray s -> MutableByteArray# s -- | Copy some elements of a mutable array. copyM :: MArray s -> Int -> MArray s -> Int -> Int -> ST s () -- | Copy some elements of an immutable array. copyI :: MArray s -> Int -> Array -> Int -> Int -> ST s () -- | An empty immutable array. empty :: Array -- | Compare portions of two arrays for equality. No bounds checking is -- performed. equal :: Array -> Int -> Array -> Int -> Int -> Bool -- | Run an action in the ST monad and return an immutable array of its -- result. run :: (forall s. ST s (MArray s)) -> Array -- | Run an action in the ST monad and return an immutable array of its -- result paired with whatever else the action returns. run2 :: (forall s. ST s (MArray s, a)) -> (Array, a) -- | Convert an immutable array to a list. toList :: Array -> Int -> Int -> [Word16] -- | Freeze a mutable array. Do not mutate the MArray afterwards! unsafeFreeze :: MArray s -> ST s Array -- | Unchecked read of an immutable array. May return garbage or crash on -- an out-of-bounds access. unsafeIndex :: Array -> Int -> Word16 -- | Create an uninitialized mutable array. new :: forall s. Int -> ST s (MArray s) -- | Unchecked write of a mutable array. May return garbage or crash on an -- out-of-bounds access. unsafeWrite :: MArray s -> Int -> Word16 -> ST s () -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Fast character manipulation functions. module Data.Text.Internal.Unsafe.Char ord :: Char -> Int unsafeChr :: Word16 -> Char unsafeChr8 :: Word8 -> Char unsafeChr32 :: Word32 -> Char -- | Write a character into the array at the given offset. Returns the -- number of Word16s written. unsafeWrite :: MArray s -> Int -> Char -> ST s Int -- | A module containing private Text internals. This exposes the -- Text representation and low level construction functions. -- Modules which extend the Text system may need to use this -- module. -- -- You should not use this module unless you are determined to monkey -- with the internals, as the functions here do just about nothing to -- preserve data invariants. You have been warned! module Data.Text.Internal -- | A space efficient, packed, unboxed Unicode text type. data Text Text :: {-# UNPACK #-} !Array -> {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> Text -- | Construct a Text without invisibly pinning its byte array in -- memory if its length has dwindled to zero. text :: Array -> Int -> Int -> Text -- | Deprecated: Use text instead textP :: Array -> Int -> Int -> Text -- | Map a Char to a Text-safe value. -- -- UTF-16 surrogate code points are not included in the set of Unicode -- scalar values, but are unfortunately admitted as valid Char -- values by Haskell. They cannot be represented in a Text. This -- function remaps those code points to the Unicode replacement character -- (U+FFFD, '�'), and leaves other code points unchanged. safe :: Char -> Char -- | O(1) The empty Text. empty :: Text -- | A non-inlined version of empty. empty_ :: Text -- | Apply a function to the first element of an optional pair. firstf :: (a -> c) -> Maybe (a, b) -> Maybe (c, b) -- | Checked multiplication. Calls error if the result would -- overflow. mul :: Int -> Int -> Int infixl 7 `mul` -- | Checked multiplication. Calls error if the result would -- overflow. mul32 :: Int32 -> Int32 -> Int32 infixl 7 `mul32` -- | Checked multiplication. Calls error if the result would -- overflow. mul64 :: Int64 -> Int64 -> Int64 infixl 7 `mul64` -- | A useful show-like function for debugging purposes. showText :: Text -> String -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Size hints. module Data.Text.Internal.Fusion.Size data Size exactly :: Size -> Maybe Int exactSize :: Int -> Size maxSize :: Int -> Size betweenSize :: Int -> Int -> Size unknownSize :: Size -- | Minimum of two size hints. smaller :: Size -> Size -> Size -- | Maximum of two size hints. larger :: Size -> Size -> Size -- | Compute the maximum size from a size hint, if possible. upperBound :: Int -> Size -> Int -- | Compute the maximum size from a size hint, if possible. lowerBound :: Int -> Size -> Int compareSize :: Size -> Int -> Maybe Ordering isEmpty :: Size -> Bool instance GHC.Show.Show Data.Text.Internal.Fusion.Size.Size instance GHC.Classes.Eq Data.Text.Internal.Fusion.Size.Size instance GHC.Num.Num Data.Text.Internal.Fusion.Size.Size -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Core stream fusion functionality for text. module Data.Text.Internal.Fusion.Types -- | Specialised tuple for case conversion. data CC s CC :: !s -> {-# UNPACK #-} !Char -> {-# UNPACK #-} !Char -> CC s -- | Strict pair. data PairS a b (:*:) :: !a -> !b -> PairS a b -- | An intermediate result in a scan. data Scan s Scan1 :: {-# UNPACK #-} !Char -> !s -> Scan s Scan2 :: {-# UNPACK #-} !Char -> !s -> Scan s -- | Restreaming state. data RS s RS0 :: !s -> RS s RS1 :: !s -> {-# UNPACK #-} !Word8 -> RS s RS2 :: !s -> {-# UNPACK #-} !Word8 -> {-# UNPACK #-} !Word8 -> RS s RS3 :: !s -> {-# UNPACK #-} !Word8 -> {-# UNPACK #-} !Word8 -> {-# UNPACK #-} !Word8 -> RS s -- | Intermediate result in a processing pipeline. data Step s a Done :: Step s a Skip :: !s -> Step s a Yield :: !a -> !s -> Step s a data Stream a Stream :: (s -> Step s a) -> !s -> !Size -> Stream a -- | The empty stream. empty :: Stream a instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Text.Internal.Fusion.Types.Stream a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Text.Internal.Fusion.Types.Stream a) module Data.Text.Internal.Fusion.CaseMapping upperMapping :: forall s. Char -> s -> Step (CC s) Char lowerMapping :: forall s. Char -> s -> Step (CC s) Char titleMapping :: forall s. Char -> s -> Step (CC s) Char foldMapping :: forall s. Char -> s -> Step (CC s) Char -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Common stream fusion functionality for text. module Data.Text.Internal.Fusion.Common singleton :: Char -> Stream Char streamList :: [a] -> Stream a unstreamList :: Stream a -> [a] -- | Stream the UTF-8-like packed encoding used by GHC to represent -- constant strings in generated code. -- -- This encoding uses the byte sequence "xc0x80" to represent NUL, and -- the string is NUL-terminated. streamCString# :: Addr# -> Stream Char -- | O(n) Adds a character to the front of a Stream Char. cons :: Char -> Stream Char -> Stream Char -- | O(n) Adds a character to the end of a stream. snoc :: Stream Char -> Char -> Stream Char -- | O(n) Appends one Stream to the other. append :: Stream Char -> Stream Char -> Stream Char -- | O(1) Returns the first character of a Text, which must be -- non-empty. Subject to array fusion. head :: Stream Char -> Char -- | O(1) Returns the first character and remainder of a 'Stream -- Char', or Nothing if empty. Subject to array fusion. uncons :: Stream Char -> Maybe (Char, Stream Char) -- | O(n) Returns the last character of a 'Stream Char', which must -- be non-empty. last :: Stream Char -> Char -- | O(1) Returns all characters after the head of a Stream Char, -- which must be non-empty. tail :: Stream Char -> Stream Char -- | O(1) Returns all but the last character of a Stream Char, which -- must be non-empty. init :: Stream Char -> Stream Char -- | O(1) Tests whether a Stream Char is empty or not. null :: Stream Char -> Bool -- | O(n) Returns the number of characters in a string. lengthI :: Integral a => Stream Char -> a -- | O(n) Compares the count of characters in a string to a number. -- Subject to fusion. -- -- This function gives the same answer as comparing against the result of -- lengthI, but can short circuit if the count of characters is -- greater than the number or if the stream can't possibly be as long as -- the number supplied, and hence be more efficient. compareLengthI :: Integral a => Stream Char -> a -> Ordering -- | O(n) Indicate whether a string contains exactly one element. isSingleton :: Stream Char -> Bool -- | O(n) map f xs is the Stream Char obtained by -- applying f to each element of xs. map :: (Char -> Char) -> Stream Char -> Stream Char intercalate :: Stream Char -> [Stream Char] -> Stream Char -- | O(n) Take a character and place it between each of the -- characters of a 'Stream Char'. intersperse :: Char -> Stream Char -> Stream Char -- | O(n) Convert a string to folded case. This function is mainly -- useful for performing caseless (or case insensitive) string -- comparisons. -- -- A string x is a caseless match for a string y if and -- only if: -- --
-- toCaseFold x == toCaseFold y ---- -- The result string may be longer than the input string, and may differ -- from applying toLower to the input string. For instance, the -- Armenian small ligature men now (U+FB13) is case folded to the bigram -- men now (U+0574 U+0576), while the micro sign (U+00B5) is case folded -- to the Greek small letter letter mu (U+03BC) instead of itself. toCaseFold :: Stream Char -> Stream Char -- | O(n) Convert a string to lower case, using simple case -- conversion. The result string may be longer than the input string. For -- instance, the Latin capital letter I with dot above (U+0130) maps to -- the sequence Latin small letter i (U+0069) followed by combining dot -- above (U+0307). toLower :: Stream Char -> Stream Char -- | O(n) Convert a string to title case, using simple case -- conversion. -- -- The first letter of the input is converted to title case, as is every -- subsequent letter that immediately follows a non-letter. Every letter -- that immediately follows another letter is converted to lower case. -- -- The result string may be longer than the input string. For example, -- the Latin small ligature fl (U+FB02) is converted to the sequence Latin -- capital letter F (U+0046) followed by Latin small letter l (U+006C). -- -- Note: this function does not take language or culture specific -- rules into account. For instance, in English, different style guides -- disagree on whether the book name "The Hill of the Red Fox" is -- correctly title cased—but this function will capitalize every -- word. toTitle :: Stream Char -> Stream Char -- | O(n) Convert a string to upper case, using simple case -- conversion. The result string may be longer than the input string. For -- instance, the German eszett (U+00DF) maps to the two-letter sequence -- SS. toUpper :: Stream Char -> Stream Char justifyLeftI :: Integral a => a -> Char -> Stream Char -> Stream Char -- | foldl, applied to a binary operator, a starting value (typically the -- left-identity of the operator), and a Stream, reduces the Stream using -- the binary operator, from left to right. foldl :: (b -> Char -> b) -> b -> Stream Char -> b -- | A strict version of foldl. foldl' :: (b -> Char -> b) -> b -> Stream Char -> b -- | foldl1 is a variant of foldl that has no starting value argument, and -- thus must be applied to non-empty Streams. foldl1 :: (Char -> Char -> Char) -> Stream Char -> Char -- | A strict version of foldl1. foldl1' :: (Char -> Char -> Char) -> Stream Char -> Char -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a stream, reduces -- the stream using the binary operator, from right to left. foldr :: (Char -> b -> b) -> b -> Stream Char -> b -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty streams. Subject to -- array fusion. foldr1 :: (Char -> Char -> Char) -> Stream Char -> Char -- | O(n) Concatenate a list of streams. Subject to array fusion. concat :: [Stream Char] -> Stream Char -- | Map a function over a stream that results in a stream and concatenate -- the results. concatMap :: (Char -> Stream Char) -> Stream Char -> Stream Char -- | O(n) any p xs determines if any character in the -- stream xs satisfies the predicate p. any :: (Char -> Bool) -> Stream Char -> Bool -- | O(n) all p xs determines if all characters in the -- Text xs satisfy the predicate p. all :: (Char -> Bool) -> Stream Char -> Bool -- | O(n) maximum returns the maximum value from a stream, which -- must be non-empty. maximum :: Stream Char -> Char -- | O(n) minimum returns the minimum value from a Text, -- which must be non-empty. minimum :: Stream Char -> Char scanl :: (Char -> Char -> Char) -> Char -> Stream Char -> Stream Char replicateCharI :: Integral a => a -> Char -> Stream Char replicateI :: Int64 -> Stream Char -> Stream Char -- | O(n), where n is the length of the result. The unfoldr -- function is analogous to the List unfoldr. unfoldr builds a -- stream from a seed value. The function takes the element and returns -- Nothing if it is done producing the stream or returns Just (a,b), in -- which case, a is the next Char in the string, and b is the seed value -- for further production. unfoldr :: (a -> Maybe (Char, a)) -> a -> Stream Char -- | O(n) Like unfoldr, unfoldrNI builds a stream from -- a seed value. However, the length of the result is limited by the -- first argument to unfoldrNI. This function is more efficient -- than unfoldr when the length of the result is known. unfoldrNI :: Integral a => a -> (b -> Maybe (Char, b)) -> b -> Stream Char -- | O(n) take n, applied to a stream, returns the prefix of the -- stream of length n, or the stream itself if n is -- greater than the length of the stream. take :: Integral a => a -> Stream Char -> Stream Char -- | O(n) drop n, applied to a stream, returns the suffix of the -- stream after the first n characters, or the empty stream if -- n is greater than the length of the stream. drop :: Integral a => a -> Stream Char -> Stream Char -- | takeWhile, applied to a predicate p and a stream, returns the -- longest prefix (possibly empty) of elements that satisfy p. takeWhile :: (Char -> Bool) -> Stream Char -> Stream Char -- | dropWhile p xs returns the suffix remaining after takeWhile -- p xs. dropWhile :: (Char -> Bool) -> Stream Char -> Stream Char -- | O(n) The isPrefixOf function takes two Streams -- and returns True iff the first is a prefix of the second. isPrefixOf :: (Eq a) => Stream a -> Stream a -> Bool -- | O(n) elem is the stream membership predicate. elem :: Char -> Stream Char -> Bool -- | O(n) filter, applied to a predicate and a stream, -- returns a stream containing those characters that satisfy the -- predicate. filter :: (Char -> Bool) -> Stream Char -> Stream Char -- | O(n) The findBy function takes a predicate and a stream, -- and returns the first element in matching the predicate, or -- Nothing if there is no such element. findBy :: (Char -> Bool) -> Stream Char -> Maybe Char -- | O(n) Stream index (subscript) operator, starting from 0. indexI :: Integral a => Stream Char -> a -> Char -- | The findIndexI function takes a predicate and a stream and -- returns the index of the first element in the stream satisfying the -- predicate. findIndexI :: Integral a => (Char -> Bool) -> Stream Char -> Maybe a -- | O(n) The countCharI function returns the number of times -- the query element appears in the given stream. countCharI :: Integral a => Char -> Stream Char -> a -- | zipWith generalises zip by zipping with the function given as -- the first argument, instead of a tupling function. zipWith :: (a -> a -> b) -> Stream a -> Stream a -> Stream b -- | Fast substring search for Text, based on work by Boyer, Moore, -- Horspool, Sunday, and Lundh. -- -- References: -- --
-- import qualified Data.Text as T ---- -- To use an extended and very rich family of functions for working with -- Unicode text (including normalization, regular expressions, -- non-standard encodings, text breaking, and locales), see the -- text-icu package. module Data.Text -- | A space efficient, packed, unboxed Unicode text type. data Text -- | O(n) Convert a String into a Text. Subject to -- fusion. Performs replacement on invalid scalar values. pack :: String -> Text -- | O(n) Convert a Text into a String. Subject to -- fusion. unpack :: Text -> String -- | O(1) Convert a character into a Text. Subject to fusion. -- Performs replacement on invalid scalar values. singleton :: Char -> Text -- | O(1) The empty Text. empty :: Text -- | O(n) Adds a character to the front of a Text. This -- function is more costly than its List counterpart because it -- requires copying a new array. Subject to fusion. Performs replacement -- on invalid scalar values. cons :: Char -> Text -> Text infixr 5 `cons` -- | O(n) Adds a character to the end of a Text. This copies -- the entire array in the process, unless fused. Subject to fusion. -- Performs replacement on invalid scalar values. snoc :: Text -> Char -> Text -- | O(n) Appends one Text to the other by copying both of -- them into a new Text. Subject to fusion. append :: Text -> Text -> Text -- | O(1) Returns the first character and rest of a Text, or -- Nothing if empty. Subject to fusion. uncons :: Text -> Maybe (Char, Text) -- | O(1) Returns the first character of a Text, which must -- be non-empty. Subject to fusion. head :: Text -> Char -- | O(1) Returns the last character of a Text, which must be -- non-empty. Subject to fusion. last :: Text -> Char -- | O(1) Returns all characters after the head of a Text, -- which must be non-empty. Subject to fusion. tail :: Text -> Text -- | O(1) Returns all but the last character of a Text, which -- must be non-empty. Subject to fusion. init :: Text -> Text -- | O(1) Tests whether a Text is empty or not. Subject to -- fusion. null :: Text -> Bool -- | O(n) Returns the number of characters in a Text. Subject -- to fusion. length :: Text -> Int -- | O(n) Compare the count of characters in a Text to a -- number. Subject to fusion. -- -- This function gives the same answer as comparing against the result of -- length, but can short circuit if the count of characters is -- greater than the number, and hence be more efficient. compareLength :: Text -> Int -> Ordering -- | O(n) map f t is the Text -- obtained by applying f to each element of t. Subject -- to fusion. Performs replacement on invalid scalar values. map :: (Char -> Char) -> Text -> Text -- | O(n) The intercalate function takes a Text and a -- list of Texts and concatenates the list after interspersing the -- first argument between each element of the list. intercalate :: Text -> [Text] -> Text -- | O(n) The intersperse function takes a character and -- places it between the characters of a Text. Subject to fusion. -- Performs replacement on invalid scalar values. intersperse :: Char -> Text -> Text -- | O(n) The transpose function transposes the rows and -- columns of its Text argument. Note that this function uses -- pack, unpack, and the list version of transpose, and is -- thus not very efficient. transpose :: [Text] -> [Text] -- | O(n) Reverse the characters of a string. Subject to fusion. reverse :: Text -> 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). replace :: Text -> Text -> Text -> Text -- | O(n) Convert a string to folded case. Subject to fusion. -- -- This function is mainly useful for performing caseless (also known as -- case insensitive) string comparisons. -- -- A string x is a caseless match for a string y if and -- only if: -- --
-- toCaseFold x == toCaseFold y ---- -- The result string may be longer than the input string, and may differ -- from applying toLower to the input string. For instance, the -- Armenian small ligature "ﬓ" (men now, U+FB13) is case folded to the -- sequence "մ" (men, U+0574) followed by "ն" (now, U+0576), while the -- Greek "µ" (micro sign, U+00B5) is case folded to "μ" (small letter mu, -- U+03BC) instead of itself. toCaseFold :: Text -> Text -- | O(n) Convert a string to lower case, using simple case -- conversion. Subject to fusion. -- -- The result string may be longer than the input string. For instance, -- "İ" (Latin capital letter I with dot above, U+0130) maps to the -- sequence "i" (Latin small letter i, U+0069) followed by " ̇" -- (combining dot above, U+0307). toLower :: Text -> Text -- | O(n) Convert a string to upper case, using simple case -- conversion. Subject to fusion. -- -- The result string may be longer than the input string. For instance, -- the German "ß" (eszett, U+00DF) maps to the two-letter sequence "SS". toUpper :: Text -> Text -- | O(n) Convert a string to title case, using simple case -- conversion. Subject to fusion. -- -- The first letter of the input is converted to title case, as is every -- subsequent letter that immediately follows a non-letter. Every letter -- that immediately follows another letter is converted to lower case. -- -- The result string may be longer than the input string. For example, -- the Latin small ligature fl (U+FB02) is converted to the sequence Latin -- capital letter F (U+0046) followed by Latin small letter l (U+006C). -- -- Note: this function does not take language or culture specific -- rules into account. For instance, in English, different style guides -- disagree on whether the book name "The Hill of the Red Fox" is -- correctly title cased—but this function will capitalize every -- word. toTitle :: Text -> Text -- | O(n) Left-justify a string to the given length, using the -- specified fill character on the right. Subject to fusion. Performs -- replacement on invalid scalar values. -- -- Examples: -- --
-- justifyLeft 7 'x' "foo" == "fooxxxx" -- justifyLeft 3 'x' "foobar" == "foobar" --justifyLeft :: Int -> Char -> Text -> Text -- | O(n) Right-justify a string to the given length, using the -- specified fill character on the left. Performs replacement on invalid -- scalar values. -- -- Examples: -- --
-- justifyRight 7 'x' "bar" == "xxxxbar" -- justifyRight 3 'x' "foobar" == "foobar" --justifyRight :: Int -> Char -> Text -> Text -- | O(n) Center a string to the given length, using the specified -- fill character on either side. Performs replacement on invalid scalar -- values. -- -- Examples: -- --
-- center 8 'x' "HS" = "xxxHSxxx" --center :: Int -> Char -> Text -> Text -- | O(n) foldl, applied to a binary operator, a starting -- value (typically the left-identity of the operator), and a -- Text, reduces the Text using the binary operator, from -- left to right. Subject to fusion. foldl :: (a -> Char -> a) -> a -> Text -> a -- | O(n) A strict version of foldl. Subject to fusion. foldl' :: (a -> Char -> a) -> a -> Text -> a -- | 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. foldl1' :: (Char -> Char -> Char) -> Text -> Char -- | O(n) foldr, applied to a binary operator, a starting -- value (typically the right-identity of the operator), and a -- Text, reduces the Text using the binary operator, from -- right to left. Subject to fusion. foldr :: (Char -> a -> a) -> a -> Text -> a -- | 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. foldr1 :: (Char -> Char -> Char) -> Text -> Char -- | O(n) Concatenate a list of Texts. concat :: [Text] -> Text -- | O(n) Map a function over a Text that results in a -- Text, and concatenate the results. concatMap :: (Char -> Text) -> Text -> Text -- | O(n) any p t determines whether any -- character in the Text t satisfies the predicate -- p. Subject to fusion. any :: (Char -> Bool) -> Text -> Bool -- | O(n) all p t determines whether all -- characters in the Text t satisfy the predicate -- p. Subject to fusion. all :: (Char -> Bool) -> Text -> Bool -- | O(n) maximum returns the maximum value from a -- Text, which must be non-empty. Subject to fusion. maximum :: Text -> Char -- | O(n) minimum returns the minimum value from a -- Text, which must be non-empty. Subject to fusion. minimum :: Text -> Char -- | O(n) scanl is similar to foldl, but returns a -- list of successive reduced values from the left. Subject to fusion. -- Performs replacement on invalid scalar values. -- --
-- scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] ---- -- Note that -- --
-- last (scanl f z xs) == foldl f z xs. --scanl :: (Char -> Char -> Char) -> Char -> Text -> Text -- | O(n) scanl1 is a variant of scanl that has no -- starting value argument. Subject to fusion. Performs replacement on -- invalid scalar values. -- --
-- scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] --scanl1 :: (Char -> Char -> Char) -> Text -> Text -- | O(n) scanr is the right-to-left dual of scanl. -- Performs replacement on invalid scalar values. -- --
-- scanr f v == reverse . scanl (flip f) v . reverse --scanr :: (Char -> Char -> Char) -> Char -> Text -> Text -- | O(n) scanr1 is a variant of scanr that has no -- starting value argument. Subject to fusion. Performs replacement on -- invalid scalar values. scanr1 :: (Char -> Char -> Char) -> Text -> Text -- | O(n) Like a combination of map and foldl'. -- Applies a function to each element of a Text, passing an -- accumulating parameter from left to right, and returns a final -- Text. Performs replacement on invalid scalar values. mapAccumL :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) -- | The mapAccumR function behaves like a combination of map -- and a strict foldr; it applies a function to each element of a -- Text, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- Text. Performs replacement on invalid scalar values. mapAccumR :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) -- | O(n*m) replicate n t is a Text -- consisting of the input t repeated n times. replicate :: Int -> Text -> Text -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List unfoldr. -- unfoldr builds a Text from a seed value. The function -- takes the element and returns Nothing if it is done producing -- the Text, otherwise Just (a,b). In this case, -- a is the next Char in the string, and b is -- the seed value for further production. Subject to fusion. Performs -- replacement on invalid scalar values. unfoldr :: (a -> Maybe (Char, a)) -> a -> Text -- | O(n) Like unfoldr, unfoldrN builds a Text -- from a seed value. However, the length of the result should be limited -- by the first argument to unfoldrN. This function is more -- efficient than unfoldr when the maximum length of the result is -- known and correct, otherwise its performance is similar to -- unfoldr. Subject to fusion. Performs replacement on invalid -- scalar values. unfoldrN :: Int -> (a -> Maybe (Char, a)) -> a -> Text -- | O(n) take n, applied to a Text, returns -- the prefix of the Text of length n, or the Text -- itself if n is greater than the length of the Text. Subject -- to fusion. take :: Int -> Text -> Text -- | O(n) takeEnd n t returns the suffix -- remaining after taking n characters from the end of -- t. -- -- Examples: -- --
-- takeEnd 3 "foobar" == "bar" --takeEnd :: Int -> Text -> Text -- | O(n) drop n, applied to a Text, returns -- the suffix of the Text after the first n characters, -- or the empty Text if n is greater than the length of -- the Text. Subject to fusion. drop :: Int -> Text -> Text -- | O(n) dropEnd n t returns the prefix -- remaining after dropping n characters from the end of -- t. -- -- Examples: -- --
-- dropEnd 3 "foobar" == "foo" --dropEnd :: Int -> Text -> Text -- | O(n) takeWhile, applied to a predicate p and a -- Text, returns the longest prefix (possibly empty) of elements -- that satisfy p. Subject to fusion. takeWhile :: (Char -> Bool) -> Text -> Text -- | O(n) takeWhileEnd, applied to a predicate p and -- a Text, returns the longest suffix (possibly empty) of elements -- that satisfy p. Subject to fusion. Examples: -- --
-- takeWhileEnd (=='o') "foo" == "oo" --takeWhileEnd :: (Char -> Bool) -> Text -> Text -- | O(n) dropWhile p t returns the suffix -- remaining after takeWhile p t. Subject to -- fusion. dropWhile :: (Char -> Bool) -> Text -> Text -- | O(n) dropWhileEnd p t returns the -- prefix remaining after dropping characters that satisfy the predicate -- p from the end of t. Subject to fusion. -- -- Examples: -- --
-- dropWhileEnd (=='.') "foo..." == "foo" --dropWhileEnd :: (Char -> Bool) -> Text -> Text -- | O(n) dropAround p t returns the -- substring remaining after dropping characters that satisfy the -- predicate p from both the beginning and end of t. -- Subject to fusion. dropAround :: (Char -> Bool) -> Text -> Text -- | O(n) Remove leading and trailing white space from a string. -- Equivalent to: -- --
-- dropAround isSpace --strip :: Text -> Text -- | O(n) Remove leading white space from a string. Equivalent to: -- --
-- dropWhile isSpace --stripStart :: Text -> Text -- | O(n) Remove trailing white space from a string. Equivalent to: -- --
-- dropWhileEnd isSpace --stripEnd :: Text -> Text -- | O(n) splitAt n t returns a pair whose first -- element is a prefix of t of length n, and whose -- second is the remainder of the string. It is equivalent to -- (take n t, drop n t). splitAt :: Int -> 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. -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). breakOn :: 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")
--
breakOnEnd :: Text -> Text -> (Text, Text)
-- | O(n) break is like span, but the prefix returned
-- is over elements that fail the predicate p.
break :: (Char -> Bool) -> Text -> (Text, Text)
-- | O(n) span, applied to a predicate p and text
-- t, returns 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.
span :: (Char -> Bool) -> Text -> (Text, Text)
-- | O(n) Group characters in a string by equality.
group :: Text -> [Text]
-- | O(n) Group characters in a string according to a predicate.
groupBy :: (Char -> Char -> Bool) -> Text -> [Text]
-- | O(n) Return all initial segments of the given Text,
-- shortest first.
inits :: Text -> [Text]
-- | O(n) Return all final segments of the given Text,
-- longest first.
tails :: Text -> [Text]
-- | O(m+n) Break a Text into pieces separated by the first
-- Text argument (which cannot be empty), 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.) -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). splitOn :: Text -> Text -> [Text] -- | O(n) Splits a Text into components delimited by -- separators, where the predicate returns True for a separator element. -- The resulting components do not contain the separators. Two adjacent -- separators result in an empty component in the output. eg. -- --
-- split (=='a') "aabbaca" == ["","","bb","c",""] -- split (=='a') "" == [""] --split :: (Char -> Bool) -> Text -> [Text] -- | O(n) Splits a Text into components of length k. -- The last element may be shorter than the other chunks, depending on -- the length of the input. Examples: -- --
-- chunksOf 3 "foobarbaz" == ["foo","bar","baz"] -- chunksOf 4 "haskell.org" == ["hask","ell.","org"] --chunksOf :: Int -> Text -> [Text] -- | O(n) Breaks a Text up into a list of Texts at -- newline Chars. The resulting strings do not contain newlines. lines :: Text -> [Text] -- | O(n) Breaks a Text up into a list of words, delimited by -- Chars representing white space. words :: Text -> [Text] -- | O(n) Joins lines, after appending a terminating newline to -- each. unlines :: [Text] -> Text -- | O(n) Joins words using single space characters. unwords :: [Text] -> Text -- | O(n) The isPrefixOf function takes two Texts and -- returns True iff the first is a prefix of the second. Subject -- to fusion. isPrefixOf :: Text -> Text -> Bool -- | O(n) The isSuffixOf function takes two Texts and -- returns True iff the first is a suffix of the second. isSuffixOf :: Text -> Text -> Bool -- | O(n+m) The isInfixOf function takes two Texts and -- returns True iff the first is contained, wholly and intact, -- anywhere within the second. -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). isInfixOf :: Text -> Text -> Bool -- | O(n) Return the suffix of the second string if its prefix -- matches the entire first string. -- -- Examples: -- --
-- stripPrefix "foo" "foobar" == Just "bar" -- stripPrefix "" "baz" == Just "baz" -- stripPrefix "foo" "quux" == Nothing ---- -- This is particularly useful with the ViewPatterns extension -- to GHC, as follows: -- --
-- {-# LANGUAGE ViewPatterns #-}
-- import Data.Text as T
--
-- fnordLength :: Text -> Int
-- fnordLength (stripPrefix "fnord" -> Just suf) = T.length suf
-- fnordLength _ = -1
--
stripPrefix :: Text -> Text -> Maybe Text
-- | O(n) Return the prefix of the second string if its suffix
-- matches the entire first string.
--
-- Examples:
--
-- -- stripSuffix "bar" "foobar" == Just "foo" -- stripSuffix "" "baz" == Just "baz" -- stripSuffix "foo" "quux" == Nothing ---- -- This is particularly useful with the ViewPatterns extension -- to GHC, as follows: -- --
-- {-# LANGUAGE ViewPatterns #-}
-- import Data.Text as T
--
-- quuxLength :: Text -> Int
-- quuxLength (stripSuffix "quux" -> Just pre) = T.length pre
-- quuxLength _ = -1
--
stripSuffix :: Text -> Text -> Maybe Text
-- | 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.
--
-- If the strings do not have a common prefix or either one is empty,
-- this function returns Nothing.
--
-- Examples:
--
--
-- commonPrefixes "foobar" "fooquux" == Just ("foo","bar","quux")
-- commonPrefixes "veeble" "fetzer" == Nothing
-- commonPrefixes "" "baz" == Nothing
--
commonPrefixes :: Text -> Text -> Maybe (Text, Text, Text)
-- | O(n) filter, applied to a predicate and a Text,
-- returns a Text containing those characters that satisfy the
-- predicate.
filter :: (Char -> Bool) -> Text -> Text
-- | O(n+m) Find all non-overlapping instances of needle in
-- haystack. Each element of the returned list consists of a
-- pair:
--
--
-- breakOnAll "::" ""
-- ==> []
-- breakOnAll "/" "a/b/c/"
-- ==> [("a", "/b/c/"), ("a/b", "/c/"), ("a/b/c", "/")]
--
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards O(n*m).
--
-- The needle parameter may not be empty.
breakOnAll :: Text -> Text -> [(Text, Text)]
-- | O(n) The find function takes a predicate and a
-- Text, and returns the first element matching the predicate, or
-- Nothing if there is no such element.
find :: (Char -> Bool) -> Text -> Maybe Char
-- | O(n) The partition function takes a predicate and a
-- Text, and returns the pair of Texts with elements which
-- do and do not satisfy the predicate, respectively; i.e.
--
-- -- partition p t == (filter p t, filter (not . p) t) --partition :: (Char -> Bool) -> Text -> (Text, Text) -- | O(n) Text index (subscript) operator, starting from 0. index :: Text -> Int -> Char -- | O(n) The findIndex function takes a predicate and a -- Text and returns the index of the first element in the -- Text satisfying the predicate. Subject to fusion. findIndex :: (Char -> Bool) -> Text -> Maybe Int -- | O(n+m) The count function returns the number of times -- the query string appears in the given Text. An empty query -- string is invalid, and will cause an error to be raised. -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). count :: Text -> Text -> Int -- | O(n) zip takes two Texts and returns a list of -- corresponding pairs of bytes. If one input Text is short, -- excess elements of the longer Text are discarded. This is -- equivalent to a pair of unpack operations. zip :: Text -> Text -> [(Char, Char)] -- | O(n) zipWith generalises zip by zipping with the -- function given as the first argument, instead of a tupling function. -- Performs replacement on invalid scalar values. zipWith :: (Char -> Char -> Char) -> Text -> Text -> Text -- | O(n) Make a distinct copy of the given string, sharing no -- storage with the original string. -- -- As an example, suppose you read a large string, of which you need only -- a small portion. If you do not use copy, the entire original -- array will be kept alive in memory by the smaller string. Making a -- copy "breaks the link" to the original array, allowing it to be -- garbage collected if there are no other live references to it. copy :: Text -> Text -- | O(n) Convert a literal string into a Text. Subject to -- fusion. -- -- This is exposed solely for people writing GHC rewrite rules. unpackCString# :: Addr# -> Text instance GHC.Classes.Eq Data.Text.Internal.Text instance GHC.Classes.Ord Data.Text.Internal.Text instance GHC.Read.Read Data.Text.Internal.Text instance Data.Semigroup.Semigroup Data.Text.Internal.Text instance GHC.Base.Monoid Data.Text.Internal.Text instance Data.String.IsString Data.Text.Internal.Text instance GHC.Exts.IsList Data.Text.Internal.Text instance Control.DeepSeq.NFData Data.Text.Internal.Text instance Data.Binary.Class.Binary Data.Text.Internal.Text instance Data.Data.Data Data.Text.Internal.Text instance Text.Printf.PrintfArg Data.Text.Internal.Text -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Low-level support for text I/O. module Data.Text.Internal.IO -- | Read a single line of input from a handle, constructing a list of -- decoded chunks as we go. When we're done, transform them into the -- destination type. hGetLineWith :: ([Text] -> t) -> Handle -> IO t -- | Read a single chunk of strict text from a buffer. Used by both the -- strict and lazy implementations of hGetContents. readChunk :: Handle__ -> CharBuffer -> IO Text -- | Efficient locale-sensitive support for text I/O. -- -- Skip past the synopsis for some important notes on performance and -- portability across different versions of GHC. module Data.Text.IO -- | The readFile function reads a file and returns the contents of -- the file as a string. The entire file is read strictly, as with -- getContents. readFile :: FilePath -> IO Text -- | Write a string to a file. The file is truncated to zero length before -- writing begins. writeFile :: FilePath -> Text -> IO () -- | Write a string the end of a file. appendFile :: FilePath -> Text -> IO () -- | Read the remaining contents of a Handle as a string. The -- Handle is closed once the contents have been read, or if an -- exception is thrown. -- -- Internally, this function reads a chunk at a time from the lower-level -- buffering abstraction, and concatenates the chunks into a single -- string once the entire file has been read. -- -- As a result, it requires approximately twice as much memory as its -- result to construct its result. For files more than a half of -- available RAM in size, this may result in memory exhaustion. hGetContents :: Handle -> IO Text -- | Experimental. Read a single chunk of strict text from a -- Handle. The size of the chunk depends on the amount of input -- currently buffered. -- -- This function blocks only if there is no data available, and EOF has -- not yet been reached. Once EOF is reached, this function returns an -- empty string instead of throwing an exception. hGetChunk :: Handle -> IO Text -- | Read a single line from a handle. hGetLine :: Handle -> IO Text -- | Write a string to a handle. hPutStr :: Handle -> Text -> IO () -- | Write a string to a handle, followed by a newline. hPutStrLn :: Handle -> Text -> IO () -- | The interact function takes a function of type Text -> -- Text as its argument. The entire input from the standard input -- device is passed to this function as its argument, and the resulting -- string is output on the standard output device. interact :: (Text -> Text) -> IO () -- | Read all user input on stdin as a single string. getContents :: IO Text -- | Read a single line of user input from stdin. getLine :: IO Text -- | Write a string to stdout. putStr :: Text -> IO () -- | Write a string to stdout, followed by a newline. putStrLn :: Text -> IO () -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- A module containing private Text internals. This exposes the -- Text representation and low level construction functions. -- Modules which extend the Text system may need to use this -- module. module Data.Text.Internal.Lazy data Text Empty :: Text Chunk :: {-# UNPACK #-} !Text -> Text -> Text -- | Smart constructor for Chunk. Guarantees the data type -- invariant. chunk :: Text -> Text -> Text -- | Smart constructor for Empty. empty :: Text -- | Consume the chunks of a lazy Text with a natural right fold. foldrChunks :: (Text -> a -> a) -> a -> Text -> a -- | Consume the chunks of a lazy Text with a strict, -- tail-recursive, accumulating left fold. foldlChunks :: (a -> Text -> a) -> a -> Text -> a -- | Check the invariant strictly. strictInvariant :: Text -> Bool -- | Check the invariant lazily. lazyInvariant :: Text -> Text -- | Display the internal structure of a lazy Text. showStructure :: Text -> String -- | Currently set to 16 KiB, less the memory management overhead. defaultChunkSize :: Int -- | Currently set to 128 bytes, less the memory management overhead. smallChunkSize :: Int -- | The memory management overhead. Currently this is tuned for GHC only. chunkOverhead :: Int -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Core stream fusion functionality for text. module Data.Text.Internal.Lazy.Fusion -- | O(n) Convert a Text into a 'Stream Char'. stream :: Text -> Stream Char -- | O(n) Convert a 'Stream Char' into a Text, using -- defaultChunkSize. unstream :: Stream Char -> Text -- | O(n) Convert a 'Stream Char' into a Text, using the -- given chunk size. unstreamChunks :: Int -> Stream Char -> Text -- | O(n) Returns the number of characters in a text. length :: Stream Char -> Int64 -- | O(n) Like unfoldr, unfoldrN builds a stream -- from a seed value. However, the length of the result is limited by the -- first argument to unfoldrN. This function is more efficient -- than unfoldr when the length of the result is known. unfoldrN :: Int64 -> (a -> Maybe (Char, a)) -> a -> Stream Char -- | O(n) stream index (subscript) operator, starting from 0. index :: Stream Char -> Int64 -> Char -- | O(n) The count function returns the number of times -- the query element appears in the given stream. countChar :: Char -> Stream Char -> Int64 -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Fast substring search for lazy Text, based on work by Boyer, -- Moore, Horspool, Sunday, and Lundh. Adapted from the strict -- implementation. module Data.Text.Internal.Lazy.Search -- | O(n+m) Find the offsets of all non-overlapping indices of -- needle within haystack. -- -- This function is strict in needle, and lazy (as far as -- possible) in the chunks of haystack. -- -- In (unlikely) bad cases, this algorithm's complexity degrades towards -- O(n*m). indices :: Text -> Text -> [Int64] -- | This module has been renamed to Lazy. This name for the module -- will be removed in the next major release. -- | Deprecated: Use Data.Text.Internal.Lazy instead module Data.Text.Lazy.Internal -- | Functions for converting lazy Text values to and from lazy -- ByteString, using several standard encodings. -- -- To gain access to a much larger variety of encodings, use the -- text-icu package: -- http://hackage.haskell.org/package/text-icu module Data.Text.Lazy.Encoding -- | Deprecated. Decode a ByteString containing 7-bit ASCII -- encoded text. -- | Deprecated: Use decodeUtf8 instead decodeASCII :: ByteString -> Text -- | Decode a ByteString containing Latin-1 (aka ISO-8859-1) -- encoded text. decodeLatin1 :: ByteString -> Text -- | Decode a ByteString containing UTF-8 encoded text that is -- known to be valid. -- -- If the input contains any invalid UTF-8 data, an exception will be -- thrown that cannot be caught in pure code. For more control over the -- handling of invalid data, use decodeUtf8' or -- decodeUtf8With. decodeUtf8 :: ByteString -> Text -- | Decode text from little endian UTF-16 encoding. -- -- If the input contains any invalid little endian UTF-16 data, an -- exception will be thrown. For more control over the handling of -- invalid data, use decodeUtf16LEWith. decodeUtf16LE :: ByteString -> Text -- | Decode text from big endian UTF-16 encoding. -- -- If the input contains any invalid big endian UTF-16 data, an exception -- will be thrown. For more control over the handling of invalid data, -- use decodeUtf16BEWith. decodeUtf16BE :: ByteString -> Text -- | Decode text from little endian UTF-32 encoding. -- -- If the input contains any invalid little endian UTF-32 data, an -- exception will be thrown. For more control over the handling of -- invalid data, use decodeUtf32LEWith. decodeUtf32LE :: ByteString -> Text -- | Decode text from big endian UTF-32 encoding. -- -- If the input contains any invalid big endian UTF-32 data, an exception -- will be thrown. For more control over the handling of invalid data, -- use decodeUtf32BEWith. decodeUtf32BE :: ByteString -> Text -- | Decode a ByteString containing UTF-8 encoded text.. -- -- If the input contains any invalid UTF-8 data, the relevant exception -- will be returned, otherwise the decoded text. -- -- Note: this function is not lazy, as it must decode its -- entire input before it can return a result. If you need lazy -- (streaming) decoding, use decodeUtf8With in lenient mode. decodeUtf8' :: ByteString -> Either UnicodeException Text -- | Decode a ByteString containing UTF-8 encoded text. decodeUtf8With :: OnDecodeError -> ByteString -> Text -- | Decode text from little endian UTF-16 encoding. decodeUtf16LEWith :: OnDecodeError -> ByteString -> Text -- | Decode text from big endian UTF-16 encoding. decodeUtf16BEWith :: OnDecodeError -> ByteString -> Text -- | Decode text from little endian UTF-32 encoding. decodeUtf32LEWith :: OnDecodeError -> ByteString -> Text -- | Decode text from big endian UTF-32 encoding. decodeUtf32BEWith :: OnDecodeError -> ByteString -> Text encodeUtf8 :: Text -> ByteString -- | Encode text using little endian UTF-16 encoding. encodeUtf16LE :: Text -> ByteString -- | Encode text using big endian UTF-16 encoding. encodeUtf16BE :: Text -> ByteString -- | Encode text using little endian UTF-32 encoding. encodeUtf32LE :: Text -> ByteString -- | Encode text using big endian UTF-32 encoding. encodeUtf32BE :: Text -> ByteString encodeUtf8Builder :: Text -> Builder encodeUtf8BuilderEscaped :: BoundedPrim Word8 -> Text -> Builder -- | A time and space-efficient implementation of Unicode text using lists -- of packed arrays. -- -- Note: Read below the synopsis for important notes on the use of -- this module. -- -- The representation used by this module is suitable for high -- performance use and for streaming large quantities of data. It -- provides a means to manipulate a large body of text without requiring -- that the entire content be resident in memory. -- -- Some operations, such as concat, append, reverse -- and cons, have better time complexity than their -- Data.Text equivalents, due to the underlying representation -- being a list of chunks. For other operations, lazy Texts are -- usually within a few percent of strict ones, but often with better -- heap usage if used in a streaming fashion. For data larger than -- available memory, or if you have tight memory constraints, this module -- will be the only option. -- -- This module is intended to be imported qualified, to avoid -- name clashes with Prelude functions. eg. -- --
-- import qualified Data.Text.Lazy as L --module Data.Text.Lazy data Text -- | O(n) Convert a String into a Text. -- -- Subject to fusion. Performs replacement on invalid scalar values. pack :: String -> Text -- | O(n) Convert a Text into a String. Subject to -- fusion. unpack :: Text -> String -- | O(1) Convert a character into a Text. Subject to fusion. -- Performs replacement on invalid scalar values. singleton :: Char -> Text -- | Smart constructor for Empty. empty :: Text -- | O(c) Convert a list of strict Texts into a lazy -- Text. fromChunks :: [Text] -> Text -- | O(n) Convert a lazy Text into a list of strict -- Texts. toChunks :: Text -> [Text] -- | O(n) Convert a lazy Text into a strict Text. toStrict :: Text -> Text -- | O(c) Convert a strict Text into a lazy Text. fromStrict :: Text -> Text -- | Consume the chunks of a lazy Text with a natural right fold. foldrChunks :: (Text -> a -> a) -> a -> Text -> a -- | Consume the chunks of a lazy Text with a strict, -- tail-recursive, accumulating left fold. foldlChunks :: (a -> Text -> a) -> a -> Text -> a -- | O(n) Adds a character to the front of a Text. This -- function is more costly than its List counterpart because it -- requires copying a new array. Subject to fusion. cons :: Char -> Text -> Text infixr 5 `cons` -- | O(n) Adds a character to the end of a Text. This copies -- the entire array in the process, unless fused. Subject to fusion. snoc :: Text -> Char -> Text -- | O(n/c) Appends one Text to another. Subject to fusion. append :: Text -> Text -> Text -- | O(1) Returns the first character and rest of a Text, or -- Nothing if empty. Subject to fusion. uncons :: Text -> Maybe (Char, Text) -- | O(1) Returns the first character of a Text, which must -- be non-empty. Subject to fusion. head :: Text -> Char -- | O(n/c) Returns the last character of a Text, which must -- be non-empty. Subject to fusion. last :: Text -> Char -- | O(1) Returns all characters after the head of a Text, -- which must be non-empty. Subject to fusion. tail :: Text -> Text -- | O(n/c) Returns all but the last character of a Text, -- which must be non-empty. Subject to fusion. init :: Text -> Text -- | O(1) Tests whether a Text is empty or not. Subject to -- fusion. null :: Text -> Bool -- | O(n) Returns the number of characters in a Text. Subject -- to fusion. length :: Text -> Int64 -- | O(n) Compare the count of characters in a Text to a -- number. Subject to fusion. -- -- This function gives the same answer as comparing against the result of -- length, but can short circuit if the count of characters is -- greater than the number, and hence be more efficient. compareLength :: Text -> Int64 -> Ordering -- | O(n) map f t is the Text -- obtained by applying f to each element of t. Subject -- to fusion. Performs replacement on invalid scalar values. map :: (Char -> Char) -> Text -> Text -- | O(n) The intercalate function takes a Text and a -- list of Texts and concatenates the list after interspersing the -- first argument between each element of the list. intercalate :: Text -> [Text] -> Text -- | O(n) The intersperse function takes a character and -- places it between the characters of a Text. Subject to fusion. -- Performs replacement on invalid scalar values. intersperse :: Char -> Text -> Text -- | O(n) The transpose function transposes the rows and -- columns of its Text argument. Note that this function uses -- pack, unpack, and the list version of transpose, and is -- thus not very efficient. transpose :: [Text] -> [Text] -- | O(n) reverse t returns the elements of -- t in reverse order. reverse :: Text -> 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). replace :: Text -> Text -> Text -> Text -- | O(n) Convert a string to folded case. Subject to fusion. -- -- This function is mainly useful for performing caseless (or case -- insensitive) string comparisons. -- -- A string x is a caseless match for a string y if and -- only if: -- --
-- toCaseFold x == toCaseFold y ---- -- The result string may be longer than the input string, and may differ -- from applying toLower to the input string. For instance, the -- Armenian small ligature men now (U+FB13) is case folded to the bigram -- men now (U+0574 U+0576), while the micro sign (U+00B5) is case folded -- to the Greek small letter letter mu (U+03BC) instead of itself. toCaseFold :: Text -> Text -- | O(n) Convert a string to lower case, using simple case -- conversion. Subject to fusion. -- -- The result string may be longer than the input string. For instance, -- the Latin capital letter I with dot above (U+0130) maps to the -- sequence Latin small letter i (U+0069) followed by combining dot above -- (U+0307). toLower :: Text -> Text -- | O(n) Convert a string to upper case, using simple case -- conversion. Subject to fusion. -- -- The result string may be longer than the input string. For instance, -- the German eszett (U+00DF) maps to the two-letter sequence SS. toUpper :: Text -> Text -- | O(n) Convert a string to title case, using simple case -- conversion. Subject to fusion. -- -- The first letter of the input is converted to title case, as is every -- subsequent letter that immediately follows a non-letter. Every letter -- that immediately follows another letter is converted to lower case. -- -- The result string may be longer than the input string. For example, -- the Latin small ligature fl (U+FB02) is converted to the sequence Latin -- capital letter F (U+0046) followed by Latin small letter l (U+006C). -- -- Note: this function does not take language or culture specific -- rules into account. For instance, in English, different style guides -- disagree on whether the book name "The Hill of the Red Fox" is -- correctly title cased—but this function will capitalize every -- word. toTitle :: Text -> Text -- | O(n) Left-justify a string to the given length, using the -- specified fill character on the right. Subject to fusion. Performs -- replacement on invalid scalar values. -- -- Examples: -- --
-- justifyLeft 7 'x' "foo" == "fooxxxx" -- justifyLeft 3 'x' "foobar" == "foobar" --justifyLeft :: Int64 -> Char -> Text -> Text -- | O(n) Right-justify a string to the given length, using the -- specified fill character on the left. Performs replacement on invalid -- scalar values. -- -- Examples: -- --
-- justifyRight 7 'x' "bar" == "xxxxbar" -- justifyRight 3 'x' "foobar" == "foobar" --justifyRight :: Int64 -> Char -> Text -> Text -- | O(n) Center a string to the given length, using the specified -- fill character on either side. Performs replacement on invalid scalar -- values. -- -- Examples: -- --
-- center 8 'x' "HS" = "xxxHSxxx" --center :: Int64 -> Char -> Text -> Text -- | O(n) foldl, applied to a binary operator, a starting -- value (typically the left-identity of the operator), and a -- Text, reduces the Text using the binary operator, from -- left to right. Subject to fusion. foldl :: (a -> Char -> a) -> a -> Text -> a -- | O(n) A strict version of foldl. Subject to fusion. foldl' :: (a -> Char -> a) -> a -> Text -> a -- | 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. foldl1' :: (Char -> Char -> Char) -> Text -> Char -- | O(n) foldr, applied to a binary operator, a starting -- value (typically the right-identity of the operator), and a -- Text, reduces the Text using the binary operator, from -- right to left. Subject to fusion. foldr :: (Char -> a -> a) -> a -> Text -> a -- | 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. foldr1 :: (Char -> Char -> Char) -> Text -> Char -- | O(n) Concatenate a list of Texts. concat :: [Text] -> Text -- | O(n) Map a function over a Text that results in a -- Text, and concatenate the results. concatMap :: (Char -> Text) -> Text -> Text -- | O(n) any p t determines whether any -- character in the Text t satisfies the predicate -- p. Subject to fusion. any :: (Char -> Bool) -> Text -> Bool -- | O(n) all p t determines whether all -- characters in the Text t satisfy the predicate -- p. Subject to fusion. all :: (Char -> Bool) -> Text -> Bool -- | O(n) maximum returns the maximum value from a -- Text, which must be non-empty. Subject to fusion. maximum :: Text -> Char -- | O(n) minimum returns the minimum value from a -- Text, which must be non-empty. Subject to fusion. minimum :: Text -> Char -- | O(n) scanl is similar to foldl, but returns a -- list of successive reduced values from the left. Subject to fusion. -- Performs replacement on invalid scalar values. -- --
-- scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...] ---- -- Note that -- --
-- last (scanl f z xs) == foldl f z xs. --scanl :: (Char -> Char -> Char) -> Char -> Text -> Text -- | O(n) scanl1 is a variant of scanl that has no -- starting value argument. Subject to fusion. Performs replacement on -- invalid scalar values. -- --
-- scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...] --scanl1 :: (Char -> Char -> Char) -> Text -> Text -- | O(n) scanr is the right-to-left dual of scanl. -- Performs replacement on invalid scalar values. -- --
-- scanr f v == reverse . scanl (flip f) v . reverse --scanr :: (Char -> Char -> Char) -> Char -> Text -> Text -- | O(n) scanr1 is a variant of scanr that has no -- starting value argument. Performs replacement on invalid scalar -- values. scanr1 :: (Char -> Char -> Char) -> Text -> Text -- | O(n) Like a combination of map and foldl'. -- Applies a function to each element of a Text, passing an -- accumulating parameter from left to right, and returns a final -- Text. Performs replacement on invalid scalar values. mapAccumL :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) -- | The mapAccumR function behaves like a combination of map -- and a strict foldr; it applies a function to each element of a -- Text, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- Text. Performs replacement on invalid scalar values. mapAccumR :: (a -> Char -> (a, Char)) -> a -> Text -> (a, Text) -- | repeat x is an infinite Text, with x -- the value of every element. repeat :: Char -> Text -- | O(n*m) replicate n t is a Text -- consisting of the input t repeated n times. replicate :: Int64 -> Text -> Text -- | cycle ties a finite, non-empty Text into a circular one, -- or equivalently, the infinite repetition of the original Text. cycle :: Text -> Text -- | iterate f x returns an infinite Text of -- repeated applications of f to x: -- --
-- iterate f x == [x, f x, f (f x), ...] --iterate :: (Char -> Char) -> Char -> Text -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List unfoldr. -- unfoldr builds a Text from a seed value. The function -- takes the element and returns Nothing if it is done producing -- the Text, otherwise Just (a,b). In this case, -- a is the next Char in the string, and b is -- the seed value for further production. Performs replacement on invalid -- scalar values. unfoldr :: (a -> Maybe (Char, a)) -> a -> Text -- | O(n) Like unfoldr, unfoldrN builds a Text -- from a seed value. However, the length of the result should be limited -- by the first argument to unfoldrN. This function is more -- efficient than unfoldr when the maximum length of the result is -- known and correct, otherwise its performance is similar to -- unfoldr. Performs replacement on invalid scalar values. unfoldrN :: Int64 -> (a -> Maybe (Char, a)) -> a -> Text -- | O(n) take n, applied to a Text, returns -- the prefix of the Text of length n, or the Text -- itself if n is greater than the length of the Text. Subject -- to fusion. take :: Int64 -> Text -> Text -- | O(n) takeEnd n t returns the suffix -- remaining after taking n characters from the end of -- t. -- -- Examples: -- --
-- takeEnd 3 "foobar" == "bar" --takeEnd :: Int64 -> Text -> Text -- | O(n) drop n, applied to a Text, returns -- the suffix of the Text after the first n characters, -- or the empty Text if n is greater than the length of -- the Text. Subject to fusion. drop :: Int64 -> Text -> Text -- | O(n) dropEnd n t returns the prefix -- remaining after dropping n characters from the end of -- t. -- -- Examples: -- --
-- dropEnd 3 "foobar" == "foo" --dropEnd :: Int64 -> Text -> Text -- | O(n) takeWhile, applied to a predicate p and a -- Text, returns the longest prefix (possibly empty) of elements -- that satisfy p. Subject to fusion. takeWhile :: (Char -> Bool) -> Text -> Text -- | O(n) takeWhileEnd, applied to a predicate p and -- a Text, returns the longest suffix (possibly empty) of elements -- that satisfy p. Examples: -- --
-- takeWhileEnd (=='o') "foo" == "oo" --takeWhileEnd :: (Char -> Bool) -> Text -> Text -- | O(n) dropWhile p t returns the suffix -- remaining after takeWhile p t. Subject to -- fusion. dropWhile :: (Char -> Bool) -> Text -> Text -- | O(n) dropWhileEnd p t returns the -- prefix remaining after dropping characters that satisfy the predicate -- p from the end of t. -- -- Examples: -- --
-- dropWhileEnd (=='.') "foo..." == "foo" --dropWhileEnd :: (Char -> Bool) -> Text -> Text -- | O(n) dropAround p t returns the -- substring remaining after dropping characters that satisfy the -- predicate p from both the beginning and end of t. -- Subject to fusion. dropAround :: (Char -> Bool) -> Text -> Text -- | O(n) Remove leading and trailing white space from a string. -- Equivalent to: -- --
-- dropAround isSpace --strip :: Text -> Text -- | O(n) Remove leading white space from a string. Equivalent to: -- --
-- dropWhile isSpace --stripStart :: Text -> Text -- | O(n) Remove trailing white space from a string. Equivalent to: -- --
-- dropWhileEnd isSpace --stripEnd :: Text -> Text -- | O(n) splitAt n t returns a pair whose first -- element is a prefix of t of length n, and whose -- second is the remainder of the string. It is equivalent to -- (take n t, drop n t). splitAt :: Int64 -> Text -> (Text, Text) -- | O(n) span, applied to a predicate p and text -- t, returns 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. span :: (Char -> Bool) -> 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). breakOn :: 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")
--
breakOnEnd :: Text -> Text -> (Text, Text)
-- | O(n) break is like span, but the prefix returned
-- is over elements that fail the predicate p.
break :: (Char -> Bool) -> Text -> (Text, Text)
-- | 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. group :: Text -> [Text] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Char -> Char -> Bool) -> Text -> [Text] -- | O(n) Return all initial segments of the given Text, -- shortest first. inits :: Text -> [Text] -- | O(n) Return all final segments of the given Text, -- longest first. tails :: 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). splitOn :: Text -> Text -> [Text] -- | O(n) Splits a Text into components delimited by -- separators, where the predicate returns True for a separator element. -- The resulting components do not contain the separators. Two adjacent -- separators result in an empty component in the output. eg. -- --
-- split (=='a') "aabbaca" == ["","","bb","c",""] -- split (=='a') [] == [""] --split :: (Char -> Bool) -> Text -> [Text] -- | O(n) Splits a Text into components of length k. -- The last element may be shorter than the other chunks, depending on -- the length of the input. Examples: -- --
-- chunksOf 3 "foobarbaz" == ["foo","bar","baz"] -- chunksOf 4 "haskell.org" == ["hask","ell.","org"] --chunksOf :: Int64 -> Text -> [Text] -- | O(n) Breaks a Text up into a list of Texts at -- newline Chars. The resulting strings do not contain newlines. lines :: Text -> [Text] -- | O(n) Breaks a Text up into a list of words, delimited by -- Chars representing white space. words :: Text -> [Text] -- | O(n) Joins lines, after appending a terminating newline to -- each. unlines :: [Text] -> Text -- | O(n) Joins words using single space characters. unwords :: [Text] -> Text -- | O(n) The isPrefixOf function takes two Texts and -- returns True iff the first is a prefix of the second. Subject -- to fusion. isPrefixOf :: Text -> Text -> Bool -- | O(n) The isSuffixOf function takes two Texts and -- returns True iff the first is a suffix of the second. isSuffixOf :: Text -> Text -> Bool -- | O(n+m) The isInfixOf function takes two Texts and -- returns True iff the first is contained, wholly and intact, -- anywhere within the second. -- -- 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). isInfixOf :: Text -> Text -> Bool -- | O(n) Return the suffix of the second string if its prefix -- matches the entire first string. -- -- Examples: -- --
-- stripPrefix "foo" "foobar" == Just "bar" -- stripPrefix "" "baz" == Just "baz" -- stripPrefix "foo" "quux" == Nothing ---- -- This is particularly useful with the ViewPatterns extension -- to GHC, as follows: -- --
-- {-# LANGUAGE ViewPatterns #-}
-- import Data.Text.Lazy as T
--
-- fnordLength :: Text -> Int
-- fnordLength (stripPrefix "fnord" -> Just suf) = T.length suf
-- fnordLength _ = -1
--
stripPrefix :: Text -> Text -> Maybe Text
-- | O(n) Return the prefix of the second string if its suffix
-- matches the entire first string.
--
-- Examples:
--
-- -- stripSuffix "bar" "foobar" == Just "foo" -- stripSuffix "" "baz" == Just "baz" -- stripSuffix "foo" "quux" == Nothing ---- -- This is particularly useful with the ViewPatterns extension -- to GHC, as follows: -- --
-- {-# LANGUAGE ViewPatterns #-}
-- import Data.Text.Lazy as T
--
-- quuxLength :: Text -> Int
-- quuxLength (stripSuffix "quux" -> Just pre) = T.length pre
-- quuxLength _ = -1
--
stripSuffix :: Text -> Text -> Maybe Text
-- | 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.
--
-- If the strings do not have a common prefix or either one is empty,
-- this function returns Nothing.
--
-- Examples:
--
--
-- commonPrefixes "foobar" "fooquux" == Just ("foo","bar","quux")
-- commonPrefixes "veeble" "fetzer" == Nothing
-- commonPrefixes "" "baz" == Nothing
--
commonPrefixes :: Text -> Text -> Maybe (Text, Text, Text)
-- | O(n) filter, applied to a predicate and a Text,
-- returns a Text containing those characters that satisfy the
-- predicate.
filter :: (Char -> Bool) -> Text -> Text
-- | O(n) The find function takes a predicate and a
-- Text, and returns the first element in matching the predicate,
-- or Nothing if there is no such element.
find :: (Char -> Bool) -> Text -> Maybe Char
-- | O(n+m) Find all non-overlapping instances of needle in
-- haystack. Each element of the returned list consists of a
-- pair:
--
--
-- 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.
breakOnAll :: Text -> Text -> [(Text, Text)]
-- | O(n) The partition function takes a predicate and a
-- Text, and returns the pair of Texts with elements which
-- do and do not satisfy the predicate, respectively; i.e.
--
-- -- partition p t == (filter p t, filter (not . p) t) --partition :: (Char -> Bool) -> Text -> (Text, Text) -- | O(n) Text index (subscript) operator, starting from 0. index :: Text -> Int64 -> Char -- | O(n+m) The count function returns the number of times -- the query string appears in the given Text. An empty query -- string is invalid, and will cause an error to be raised. -- -- In (unlikely) bad cases, this function's time complexity degrades -- towards O(n*m). count :: Text -> Text -> Int64 -- | O(n) zip takes two Texts and returns a list of -- corresponding pairs of bytes. If one input Text is short, -- excess elements of the longer Text are discarded. This is -- equivalent to a pair of unpack operations. zip :: Text -> Text -> [(Char, Char)] -- | O(n) zipWith generalises zip by zipping with the -- function given as the first argument, instead of a tupling function. -- Performs replacement on invalid scalar values. zipWith :: (Char -> Char -> Char) -> Text -> Text -> Text instance GHC.Classes.Eq Data.Text.Internal.Lazy.Text instance GHC.Classes.Ord Data.Text.Internal.Lazy.Text instance GHC.Show.Show Data.Text.Internal.Lazy.Text instance GHC.Read.Read Data.Text.Internal.Lazy.Text instance Data.Semigroup.Semigroup Data.Text.Internal.Lazy.Text instance GHC.Base.Monoid Data.Text.Internal.Lazy.Text instance Data.String.IsString Data.Text.Internal.Lazy.Text instance GHC.Exts.IsList Data.Text.Internal.Lazy.Text instance Control.DeepSeq.NFData Data.Text.Internal.Lazy.Text instance Data.Binary.Class.Binary Data.Text.Internal.Lazy.Text instance Data.Data.Data Data.Text.Internal.Lazy.Text instance Text.Printf.PrintfArg Data.Text.Internal.Lazy.Text -- | Warning: this is an internal module, and does not have a stable -- API or name. Functions in this module may not check or enforce -- preconditions expected by public modules. Use at your own risk! -- -- Efficient construction of lazy Text values. The principal -- operations on a Builder are singleton, -- fromText, and fromLazyText, which construct new -- builders, and mappend, which concatenates two builders. -- -- To get maximum performance when building lazy Text values -- using a builder, associate mappend calls to the right. For -- example, prefer -- --
-- singleton 'a' `mappend` (singleton 'b' `mappend` singleton 'c') ---- -- to -- --
-- singleton 'a' `mappend` singleton 'b' `mappend` singleton 'c' ---- -- as the latter associates mappend to the left. module Data.Text.Internal.Builder -- | A Builder is an efficient way to build lazy Text -- values. There are several functions for constructing builders, but -- only one to inspect them: to extract any data, you have to turn them -- into lazy Text values using toLazyText. -- -- Internally, a builder constructs a lazy Text by filling -- arrays piece by piece. As each buffer is filled, it is 'popped' off, -- to become a new chunk of the resulting lazy Text. All this is -- hidden from the user of the Builder. data Builder -- | O(n). Extract a lazy Text from a Builder with -- a default buffer size. The construction work takes place if and when -- the relevant part of the lazy Text is demanded. toLazyText :: Builder -> Text -- | O(n). Extract a lazy Text from a Builder, -- using the given size for the initial buffer. The construction work -- takes place if and when the relevant part of the lazy Text is -- demanded. -- -- If the initial buffer is too small to hold all data, subsequent -- buffers will be the default buffer size. toLazyTextWith :: Int -> Builder -> Text -- | O(1). A Builder taking a single character, satisfying -- --
toLazyText (singleton c) = singleton -- c
toLazyText (fromText t) = fromChunks -- [t]
toLazyText (fromLazyText t) = t
toLazyText (fromString s) = fromChunks -- [S.pack s]
-- singleton 'a' `mappend` (singleton 'b' `mappend` singleton 'c') ---- -- to -- --
-- singleton 'a' `mappend` singleton 'b' `mappend` singleton 'c' ---- -- as the latter associates mappend to the left. Or, -- equivalently, prefer -- --
-- singleton 'a' <> singleton 'b' <> singleton 'c' ---- -- since the <> from recent versions of Monoid -- associates to the right. module Data.Text.Lazy.Builder -- | A Builder is an efficient way to build lazy Text -- values. There are several functions for constructing builders, but -- only one to inspect them: to extract any data, you have to turn them -- into lazy Text values using toLazyText. -- -- Internally, a builder constructs a lazy Text by filling -- arrays piece by piece. As each buffer is filled, it is 'popped' off, -- to become a new chunk of the resulting lazy Text. All this is -- hidden from the user of the Builder. data Builder -- | O(n). Extract a lazy Text from a Builder with -- a default buffer size. The construction work takes place if and when -- the relevant part of the lazy Text is demanded. toLazyText :: Builder -> Text -- | O(n). Extract a lazy Text from a Builder, -- using the given size for the initial buffer. The construction work -- takes place if and when the relevant part of the lazy Text is -- demanded. -- -- If the initial buffer is too small to hold all data, subsequent -- buffers will be the default buffer size. toLazyTextWith :: Int -> Builder -> Text -- | O(1). A Builder taking a single character, satisfying -- --
toLazyText (singleton c) = singleton -- c
toLazyText (fromText t) = fromChunks -- [t]
toLazyText (fromLazyText t) = t
toLazyText (fromString s) = fromChunks -- [S.pack s]
-- rational "3" == Right (3.0, "") -- rational "3.1" == Right (3.1, "") -- rational "3e4" == Right (30000.0, "") -- rational "3.1e4" == Right (31000.0, "") -- rational ".3" == Left "input does not start with a digit" -- rational "e3" == Left "input does not start with a digit" ---- -- Examples of differences from read: -- --
-- rational "3.foo" == Right (3.0, ".foo") -- rational "3e" == Right (3.0, "e") --rational :: Fractional a => Reader a -- | Read a rational number. -- -- The syntax accepted by this function is the same as for -- rational. -- -- Note: This function is almost ten times faster than -- rational, but is slightly less accurate. -- -- The Double type supports about 16 decimal places of accuracy. -- For 94.2% of numbers, this function and rational give identical -- results, but for the remaining 5.8%, this function loses precision -- around the 15th decimal place. For 0.001% of numbers, this function -- will lose precision at the 13th or 14th decimal place. double :: Reader Double -- | Functions used frequently when reading textual data. module Data.Text.Read -- | Read some text. If the read succeeds, return its value and the -- remaining text, otherwise an error message. type Reader a = IReader Text a -- | Read a decimal integer. The input must begin with at least one decimal -- digit, and is consumed until a non-digit or end of string is reached. -- -- This function does not handle leading sign characters. If you need to -- handle signed input, use signed decimal. -- -- Note: For fixed-width integer types, this function does not -- attempt to detect overflow, so a sufficiently long input may give -- incorrect results. If you are worried about overflow, use -- Integer for your result type. decimal :: Integral a => Reader a -- | Read a hexadecimal integer, consisting of an optional leading -- "0x" followed by at least one hexadecimal digit. Input is -- consumed until a non-hex-digit or end of string is reached. This -- function is case insensitive. -- -- This function does not handle leading sign characters. If you need to -- handle signed input, use signed hexadecimal. -- -- Note: For fixed-width integer types, this function does not -- attempt to detect overflow, so a sufficiently long input may give -- incorrect results. If you are worried about overflow, use -- Integer for your result type. hexadecimal :: Integral a => Reader a -- | Read an optional leading sign character ('-' or '+') -- and apply it to the result of applying the given reader. signed :: Num a => Reader a -> Reader a -- | Read a rational number. -- -- This function accepts an optional leading sign character, followed by -- at least one decimal digit. The syntax similar to that accepted by the -- read function, with the exception that a trailing '.' -- or 'e' not followed by a number is not consumed. -- -- Examples (with behaviour identical to read): -- --
-- rational "3" == Right (3.0, "") -- rational "3.1" == Right (3.1, "") -- rational "3e4" == Right (30000.0, "") -- rational "3.1e4" == Right (31000.0, "") -- rational ".3" == Left "input does not start with a digit" -- rational "e3" == Left "input does not start with a digit" ---- -- Examples of differences from read: -- --
-- rational "3.foo" == Right (3.0, ".foo") -- rational "3e" == Right (3.0, "e") --rational :: Fractional a => Reader a -- | Read a rational number. -- -- The syntax accepted by this function is the same as for -- rational. -- -- Note: This function is almost ten times faster than -- rational, but is slightly less accurate. -- -- The Double type supports about 16 decimal places of accuracy. -- For 94.2% of numbers, this function and rational give identical -- results, but for the remaining 5.8%, this function loses precision -- around the 15th decimal place. For 0.001% of numbers, this function -- will lose precision at the 13th or 14th decimal place. double :: Reader Double