fay-base-0.21.0.0: The base package for Fay.

Safe HaskellNone
LanguageHaskell98

Data.Text

Contents

Description

Compatible API with the text package.

Synopsis

Documentation

data Text Source #

A space efficient, packed, unboxed Unicode text type.

Instances

Eq Text Source # 

Methods

(==) :: Text -> Text -> Bool #

(/=) :: Text -> Text -> Bool #

Data Text Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text -> c Text #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text #

toConstr :: Text -> Constr #

dataTypeOf :: Text -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Text) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Text) #

gmapT :: (forall b. Data b => b -> b) -> Text -> Text #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Text -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Text -> r #

gmapQ :: (forall d. Data d => d -> u) -> Text -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Text -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Text -> m Text #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Text -> m Text #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Text -> m Text #

IsString Text Source # 

Methods

fromString :: String -> Text #

Ord Text Source # 

Methods

(<) :: Text -> Text -> Bool Source #

(<=) :: Text -> Text -> Bool Source #

(>) :: Text -> Text -> Bool Source #

(>=) :: Text -> Text -> Bool Source #

Creation and elimination

pack :: String -> Text Source #

O(n) Convert a String into a Text. Subject to fusion. Performs replacement on invalid scalar values.

unpack :: Text -> String Source #

O(n) Convert a Text into a String. Subject to fusion.

fromString :: String -> Text Source #

Convert from a string to text.

empty :: Text Source #

O(1) The empty Text.

Conversions

I/O

Breaking into many substrings

splitOn :: Text -> Text -> [Text] Source #

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

stripSuffix Source #

Arguments

:: Text

Suffix.

-> Text

Text.

-> Maybe Text 

O(n) Return the prefix of the second string if its suffix matches the entire first string.

Basic interface

cons :: Char -> Text -> Text Source #

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.

snoc :: Text -> Char -> Text Source #

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.

append :: Text -> Text -> Text Source #

O(n) Appends one Text to the other by copying both of them into a new Text. Subject to fusion.

(<>) :: Text -> Text -> Text Source #

Append two texts.

uncons :: Text -> Maybe (Char, Text) Source #

O(1) Returns the first character and rest of a Text, or Nothing if empty. Subject to fusion.

head :: Text -> Char Source #

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

init :: Text -> Text Source #

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

last :: Text -> Char Source #

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

tail :: Text -> Text Source #

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

null :: Text -> Bool Source #

O(1) Tests whether a Text is empty or not. Subject to fusion.

length :: Text -> Int Source #

O(n) Returns the number of characters in a Text. Subject to fusion.

Special folds

maximum :: Text -> Char Source #

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

all :: (Char -> Bool) -> Text -> Bool Source #

O(n) all p t determines whether all characters in the Text t satisify the predicate p. Subject to fusion.

any :: (Char -> Bool) -> Text -> Bool Source #

O(n) any p t determines whether any character in the Text t satisifes the predicate p. Subject to fusion.

concatMap :: (Char -> Text) -> Text -> Text Source #

O(n) Map a function over a Text that results in a Text, and concatenate the results.

concat :: [Text] -> Text Source #

O(n) Concatenate a list of Texts.

minimum :: Text -> Char Source #

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

Case conversion

toLower :: Text -> Text Source #

O(n) Convert a string to lower case, using simple case conversion. 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).

toUpper :: Text -> Text Source #

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.

Transformations

map :: (Char -> Char) -> Text -> Text Source #

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.

intercalate :: Text -> [Text] -> Text Source #

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.

intersperse :: Char -> Text -> Text Source #

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.

reverse :: Text -> Text Source #

O(n) Reverse the characters of a string. Subject to fusion.

Predicates

isPrefixOf :: Text -> Text -> Bool Source #

O(n) The isPrefixOf function takes two Texts and returns True iff the first is a prefix of the second. Subject to fusion. http://docs.closure-library.googlecode.com/git/closure_goog_string_string.js.source.html

Substrings

drop :: Int -> Text -> Text Source #

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.

take :: Int -> Text -> Text Source #

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.

Breaking into lines and words

unlines :: [Text] -> Text Source #

O(n) Joins lines, after appending a terminating newline to each.

lines :: Text -> [Text] Source #

O(n) Breaks a Text up into a list of Texts at newline Chars. The resulting strings do not contain newlines.