| Copyright | Gautier DI FOLCO | 
|---|---|
| License | BSD2 | 
| Maintainer | Gautier DI FOLCO <gautier.difolco@gmail.com> | 
| Stability | Unstable | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Text.Sized
Description
Synopsis
- type SizedText s = SizedStrictText s
 - type SizedStrictText s = Sized s Text
 - pack :: Sized s String -> SizedStrictText s
 - unpack :: HasCallStack => SizedStrictText s -> Sized s String
 - singleton :: SizedSingleton a => Proxy a -> SizedSingletonElement a -> Sized (Exactly 1) a
 - cons :: Char -> SizedStrictText s -> SizedStrictText (Exactly 1 <+> s)
 - snoc :: SizedStrictText s -> Char -> SizedStrictText (s <+> Exactly 1)
 - uncons :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedStrictText s -> (Char, SizedStrictText s')
 - unsnoc :: (IsNotEmpty s, (s <+> Exactly 1) ~ s') => SizedStrictText s -> (SizedStrictText s', Char)
 - head :: IsNotEmpty s => SizedStrictText s -> Char
 - last :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedStrictText s -> Char
 - tail :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedStrictText s -> SizedStrictText s'
 - init :: (IsNotEmpty s, (s <+> Exactly 1) ~ s') => SizedStrictText s -> SizedStrictText s'
 - length :: SizedStrictText s -> Int
 - compareLength :: (KnownNat n, Includes s n) => SizedStrictText s -> Proxy n -> Ordering
 - map :: (Char -> Char) -> SizedStrictText s -> SizedStrictText s
 - intercalate :: Text -> Sized s [SizedStrictText s'] -> SizedStrictText (s <*> s')
 - intersperse :: Char -> SizedStrictText s -> SizedStrictText ((s <*> Exactly 2) <-> Exactly 1)
 - transpose :: Sized s [SizedStrictText s'] -> Sized s' [SizedStrictText s]
 - reverse :: HasCallStack => SizedStrictText s -> SizedStrictText s
 - replace :: SizedStrictText s0 -> SizedStrictText s1 -> SizedStrictText s2 -> SizedStrictText Unknown
 - toCaseFold :: SizedStrictText s -> SizedStrictText s
 - toLower :: SizedStrictText s -> SizedStrictText s
 - toUpper :: SizedStrictText s -> SizedStrictText s
 - toTitle :: SizedStrictText s -> SizedStrictText s
 - justifyLeft :: KnownNat n => Proxy n -> Char -> SizedStrictText s -> SizedStrictText (AtLeast n)
 - justifyRight :: KnownNat n => Proxy n -> Char -> SizedStrictText s -> SizedStrictText (AtLeast n)
 - center :: KnownNat n => Proxy n -> Char -> SizedStrictText s -> SizedStrictText (AtLeast n)
 - foldl :: (a -> Char -> a) -> a -> SizedStrictText s -> a
 - foldl' :: (a -> Char -> a) -> a -> SizedStrictText s -> a
 - foldl1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> Char
 - foldl1' :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> Char
 - foldr :: (Char -> a -> a) -> a -> SizedStrictText s -> a
 - foldr1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> Char
 - concat :: Sized s [SizedStrictText s'] -> SizedStrictText (s <*> s')
 - concatMap :: (Char -> SizedStrictText s') -> SizedStrictText s -> SizedStrictText (s <*> s')
 - any :: (Char -> Bool) -> SizedStrictText s -> Bool
 - all :: (Char -> Bool) -> SizedStrictText s -> Bool
 - maximum :: IsNotEmpty s => SizedStrictText s -> Char
 - minimum :: IsNotEmpty s => SizedStrictText s -> Char
 - scanl :: (Char -> Char -> Char) -> Char -> SizedStrictText s -> SizedStrictText s
 - scanl1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> SizedStrictText s
 - scanr :: (Char -> Char -> Char) -> Char -> SizedStrictText s -> SizedStrictText s
 - scanr1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> SizedStrictText s
 - mapAccumL :: forall a s. (a -> Char -> (a, Char)) -> a -> SizedStrictText s -> (a, SizedStrictText s)
 - mapAccumR :: forall a s. (a -> Char -> (a, Char)) -> a -> SizedStrictText s -> (a, SizedStrictText s)
 - replicate :: KnownNat n => Proxy n -> SizedStrictText s -> SizedStrictText (s <*> Exactly n)
 - take :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (AtMost n)
 - takeEnd :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (AtMost n)
 - drop :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (s <-> Exactly n)
 - dropEnd :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (s <-> Exactly n)
 - takeWhile :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - takeWhileEnd :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - dropWhile :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - dropWhileEnd :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - dropAround :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - strip :: SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - stripStart :: SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - stripEnd :: SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - splitAt :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))
 - breakOn :: SizedStrictText s -> SizedStrictText s' -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))
 - breakOnEnd :: SizedStrictText s -> SizedStrictText s' -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))
 - break :: (Char -> Bool) -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))
 - span :: (Char -> Bool) -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))
 - group :: SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
 - groupBy :: (Char -> Char -> Bool) -> SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
 - inits :: SizedStrictText s -> Sized (s <+> Exactly 1) [SizedStrictText (RestrictAtMost s)]
 - tails :: SizedStrictText s -> Sized (s <+> Exactly 1) [SizedStrictText (RestrictAtMost s)]
 - splitOn :: SizedStrictText s -> SizedStrictText s' -> Sized (RestrictAtMost s') [SizedStrictText (RestrictAtMost s')]
 - split :: (Char -> Bool) -> SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
 - chunksOf :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> Sized (AtMost d) [SizedStrictText (RestrictAtMost s)]
 - lines :: SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
 - words :: SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
 - unlines :: Sized s [SizedStrictText s'] -> SizedStrictText (s <*> (s' <+> Exactly 1))
 - unwords :: Sized s [SizedStrictText s'] -> SizedStrictText (s <*> (s' <+> Exactly 1))
 - isPrefixOf :: IsMoreGeneral s' s => SizedStrictText s -> SizedStrictText s' -> Bool
 - isSuffixOf :: IsMoreGeneral s' s => SizedStrictText s -> SizedStrictText s' -> Bool
 - isInfixOf :: (IsMoreGeneral s' s, HasCallStack) => SizedStrictText s -> SizedStrictText s' -> Bool
 - stripPrefix :: SizedStrictText s -> SizedStrictText s' -> Maybe (SizedStrictText (s <-> s'))
 - stripSuffix :: SizedStrictText s -> SizedStrictText s' -> Maybe (SizedStrictText (s <-> s'))
 - commonPrefixes :: SizedStrictText s -> SizedStrictText s' -> Maybe (Text, Text, Text)
 - filter :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s)
 - breakOnAll :: SizedStrictText s -> SizedStrictText s' -> Sized (RestrictAtMost s) [(SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))]
 - find :: (Char -> Bool) -> SizedStrictText s -> Maybe Char
 - partition :: (Char -> Bool) -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))
 - index :: (KnownNat n, Includes s n, HasCallStack) => SizedStrictText s -> Proxy n -> Char
 - findIndex :: (Char -> Bool) -> SizedStrictText s -> Maybe Int
 - count :: SizedStrictText s -> SizedStrictText s' -> Int
 - zip :: SizedStrictText s -> SizedStrictText s -> Sized s [(Char, Char)]
 - zipWith :: (Char -> Char -> Char) -> SizedStrictText s -> SizedStrictText s -> SizedStrictText s
 
Types
type SizedText s = SizedStrictText s Source #
type SizedStrictText s = Sized s Text Source #
Creation and elimination
pack :: Sized s String -> SizedStrictText s Source #
O(n) Convert a 'Sized s String' into a 'SizedStrictText s'. Performs replacement on invalid scalar values.
unpack :: HasCallStack => SizedStrictText s -> Sized s String Source #
O(n) Convert a 'SizedStrictText s' into a 'Sized s String'.
singleton :: SizedSingleton a => Proxy a -> SizedSingletonElement a -> Sized (Exactly 1) a #
Build a Sized value from a singleton value
Basic interface
cons :: Char -> SizedStrictText s -> SizedStrictText (Exactly 1 <+> s) infixr 5 Source #
O(n) Adds a character to the front of a SizedStrictText.  This function
 is more costly than its List counterpart because it requires
 copying a new array.  Performs replacement on
 invalid scalar values.
snoc :: SizedStrictText s -> Char -> SizedStrictText (s <+> Exactly 1) Source #
O(n) Adds a character to the end of a SizedStrictText.  This copies the
 entire array in the process.
 Performs replacement on invalid scalar values.
uncons :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedStrictText s -> (Char, SizedStrictText s') Source #
O(1) Returns the first character and rest of a SizedStrictText.
unsnoc :: (IsNotEmpty s, (s <+> Exactly 1) ~ s') => SizedStrictText s -> (SizedStrictText s', Char) Source #
O(1) Returns all but the last character and the last character of a
 SizedStrictText.
head :: IsNotEmpty s => SizedStrictText s -> Char Source #
O(1) Returns the first character of a SizedStrictText.
last :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedStrictText s -> Char Source #
O(1) Returns the last character of a SizedStrictText.
tail :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedStrictText s -> SizedStrictText s' Source #
O(1) Returns all characters after the head of a SizedStrictText.
init :: (IsNotEmpty s, (s <+> Exactly 1) ~ s') => SizedStrictText s -> SizedStrictText s' Source #
O(1) Returns all but the last character of a SizedStrictText.
length :: SizedStrictText s -> Int Source #
O(n) Returns the number of characters in a SizedStrictText.
compareLength :: (KnownNat n, Includes s n) => SizedStrictText s -> Proxy n -> Ordering Source #
O(min(n,c)) Compare the count of characters in a SizedStrictText to a number.
compareLengtht c =compare(lengtht) c
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.
Transformations
map :: (Char -> Char) -> SizedStrictText s -> SizedStrictText s Source #
O(n) map f t is the SizedStrictText obtained by applying f to
 each element of t.
Example:
>>>let message = pack "I am not angry. Not at all.">>>T.map (\c -> if c == '.' then '!' else c) message"I am not angry! Not at all!"
Performs replacement on invalid scalar values.
intercalate :: Text -> Sized s [SizedStrictText s'] -> SizedStrictText (s <*> s') Source #
O(n) The intercalate function takes a SizedStrictText and a list of
 SizedStrictTexts and concatenates the list after interspersing the first
 argument between each element of the list.
Example:
>>>T.intercalate "NI!" ["We", "seek", "the", "Holy", "Grail"]"WeNI!seekNI!theNI!HolyNI!Grail"
intersperse :: Char -> SizedStrictText s -> SizedStrictText ((s <*> Exactly 2) <-> Exactly 1) Source #
O(n) The intersperse function takes a character and places it
 between the characters of a SizedStrictText.
Example:
>>>T.intersperse '.' "SHIELD""S.H.I.E.L.D"
Performs replacement on invalid scalar values.
transpose :: Sized s [SizedStrictText s'] -> Sized s' [SizedStrictText s] Source #
O(n) The transpose function transposes the rows and columns
 of its SizedStrictText argument.  Note that this function uses pack,
 unpack, and the list version of transpose, and is thus not very
 efficient.
Examples:
>>>transpose ["green","orange"]["go","rr","ea","en","ng","e"]
>>>transpose ["blue","red"]["br","le","ud","e"]
reverse :: HasCallStack => SizedStrictText s -> SizedStrictText s Source #
O(n) Reverse the characters of a string.
Example:
>>>T.reverse "desrever""reversed"
Arguments
| :: SizedStrictText s0 | 
  | 
| -> SizedStrictText s1 | 
  | 
| -> SizedStrictText s2 | 
  | 
| -> SizedStrictText Unknown | 
O(m+n) Replace every non-trustedChangeOverlapping occurrence of needle in
 haystack with replacement.
This function behaves as though it was defined as follows:
replace needle replacement haystack =intercalatereplacement (splitOnneedle 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).
Case conversion
When case converting SizedStrictText values, do not use combinators like
 map toUpper to case convert each character of a string
 individually, as this gives incorrect results according to the
 rules of some writing systems.  The whole-string case conversion
 functions from this module, such as toUpper, obey the correct
 case conversion rules.  As a result, these functions may map one
 input character to two or three output characters. For examples,
 see the documentation of each function.
Note: In some languages, case conversion is a locale- and context-dependent operation. The case conversion functions in this module are not locale sensitive. Programs that require locale sensitivity should use appropriate versions of the case mapping functions from the text-icu package.
toCaseFold :: SizedStrictText s -> SizedStrictText s Source #
O(n) Convert a string to folded case.
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.
toLower :: SizedStrictText s -> SizedStrictText s 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 :: SizedStrictText s -> SizedStrictText s 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".
toTitle :: SizedStrictText s -> SizedStrictText s Source #
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.
Justification
justifyLeft :: KnownNat n => Proxy n -> Char -> SizedStrictText s -> SizedStrictText (AtLeast n) Source #
O(n) Left-justify a string to the given length, using the specified fill character on the right. Performs replacement on invalid scalar values.
Examples:
>>>justifyLeft 7 'x' "foo""fooxxxx"
>>>justifyLeft 3 'x' "foobar""foobar"
justifyRight :: KnownNat n => Proxy n -> Char -> SizedStrictText s -> SizedStrictText (AtLeast n) Source #
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"
center :: KnownNat n => Proxy n -> Char -> SizedStrictText s -> SizedStrictText (AtLeast n) Source #
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"
Folds
foldl :: (a -> Char -> a) -> a -> SizedStrictText s -> a Source #
O(n) foldl, applied to a binary operator, a starting value
 (typically the left-identity of the operator), and a SizedStrictText,
 reduces the SizedStrictText using the binary operator, from left to right.
foldl1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> Char Source #
O(n) A variant of foldl that has no starting value argument.
foldl1' :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> Char Source #
O(n) A strict version of foldl1.
foldr :: (Char -> a -> a) -> a -> SizedStrictText s -> a Source #
O(n) foldr, applied to a binary operator, a starting value
 (typically the right-identity of the operator), and a SizedStrictText,
 reduces the SizedStrictText using the binary operator, from right to left.
If the binary operator is strict in its second argument, use foldr'
 instead.
foldr is lazy like foldr for lists: evaluation actually
 traverses the SizedStrictText from left to right, only as far as it needs to.
 @
Searches from left to right with short-circuiting behavior can
 also be defined using foldr (e.g., any, all, find, elem).
foldr1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> Char Source #
O(n) A variant of foldr that has no starting value argument.
Special folds
concat :: Sized s [SizedStrictText s'] -> SizedStrictText (s <*> s') Source #
O(n) Concatenate a list of SizedStrictTexts.
concatMap :: (Char -> SizedStrictText s') -> SizedStrictText s -> SizedStrictText (s <*> s') Source #
O(n) Map a function over a SizedStrictText that results in a SizedStrictText, and
 concatenate the results.
any :: (Char -> Bool) -> SizedStrictText s -> Bool Source #
O(n) any p t determines whether any character in the
 SizedStrictText t satisfies the predicate p.
all :: (Char -> Bool) -> SizedStrictText s -> Bool Source #
O(n) all p t determines whether all characters in the
 SizedStrictText t satisfy the predicate p.
maximum :: IsNotEmpty s => SizedStrictText s -> Char Source #
O(n) maximum returns the maximum value from a SizedStrictText.
minimum :: IsNotEmpty s => SizedStrictText s -> Char Source #
O(n) minimum returns the minimum value from a SizedStrictText.
Construction
Scans
scanl :: (Char -> Char -> Char) -> Char -> SizedStrictText s -> SizedStrictText s Source #
scanl1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> SizedStrictText s Source #
scanr :: (Char -> Char -> Char) -> Char -> SizedStrictText s -> SizedStrictText s Source #
scanr1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedStrictText s -> SizedStrictText s Source #
Accumulating maps
mapAccumL :: forall a s. (a -> Char -> (a, Char)) -> a -> SizedStrictText s -> (a, SizedStrictText s) Source #
O(n) Like a combination of map and foldl'. Applies a
 function to each element of a SizedStrictText, passing an accumulating
 parameter from left to right, and returns a final SizedStrictText.  Performs
 replacement on invalid scalar values.
mapAccumR :: forall a s. (a -> Char -> (a, Char)) -> a -> SizedStrictText s -> (a, SizedStrictText s) Source #
The mapAccumR function behaves like a combination of map and
 a strict foldr; it applies a function to each element of a
 SizedStrictText, passing an accumulating parameter from right to left, and
 returning a final value of this accumulator together with the new
 SizedStrictText.
 Performs replacement on invalid scalar values.
Generation and unfolding
replicate :: KnownNat n => Proxy n -> SizedStrictText s -> SizedStrictText (s <*> Exactly n) Source #
O(n*m) replicate n t is a SizedStrictText consisting of the input
 t repeated n times, n should be strictly positive.
Substrings
Breaking strings
take :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (AtMost n) Source #
O(n) take n, applied to a SizedStrictText, returns the prefix of the
 Text of length n, or the Text itself if n is greater than
 the length of the SizedStrictText.
takeEnd :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (AtMost n) Source #
O(n) takeEnd n t returns the suffix remaining after
 taking n characters from the end of t.
Examples:
>>>takeEnd 3 "foobar""bar"
drop :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (s <-> Exactly n) Source #
O(n) drop n, applied to a SizedStrictText, returns the suffix of the
 Text after the first n characters, or the empty Text if n
 is greater than the length of the SizedStrictText.
dropEnd :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> SizedStrictText (s <-> Exactly n) Source #
O(n) dropEnd n t returns the prefix remaining after
 dropping n characters from the end of t.
Examples:
>>>dropEnd 3 "foobar""foo"
takeWhile :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
O(n) takeWhile, applied to a predicate p and a SizedStrictText,
 returns the longest prefix (possibly empty) of elements that
 satisfy p.
takeWhileEnd :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
O(n) takeWhileEnd, applied to a predicate p and a SizedStrictText,
 returns the longest suffix (possibly empty) of elements that
 satisfy p.
 Examples:
>>>takeWhileEnd (=='o') "foo""oo"
dropWhile :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
dropWhileEnd :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
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"
dropAround :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
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.
strip :: SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
O(n) Remove leading and trailing white space from a string. Equivalent to:
dropAround isSpace
stripStart :: SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
O(n) Remove leading white space from a string. Equivalent to:
dropWhile isSpace
stripEnd :: SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
O(n) Remove trailing white space from a string. Equivalent to:
dropWhileEnd isSpace
splitAt :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s)) Source #
breakOn :: SizedStrictText s -> SizedStrictText s' -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s)) Source #
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).
breakOnEnd :: SizedStrictText s -> SizedStrictText s' -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s)) Source #
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")
break :: (Char -> Bool) -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s)) Source #
span :: (Char -> Bool) -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s)) Source #
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 text.
>>>T.span (=='0') "000AB"("000","AB")
group :: SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Group characters in a string by equality.
groupBy :: (Char -> Char -> Bool) -> SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Group characters in a string according to a predicate.
inits :: SizedStrictText s -> Sized (s <+> Exactly 1) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Return all initial segments of the given SizedStrictText, shortest
 first.
tails :: SizedStrictText s -> Sized (s <+> Exactly 1) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Return all final segments of the given SizedStrictText, longest
 first.
Breaking into many substrings
Splitting functions in this library do not perform character-wise
 copies to create substrings; they just construct new Texts that
 are slices of the original.
Arguments
| :: SizedStrictText s | String to split on. If this string is empty, an error will occur.  | 
| -> SizedStrictText s' | Input text.  | 
| -> Sized (RestrictAtMost s') [SizedStrictText (RestrictAtMost s')] | 
O(m+n) Break a SizedStrictText 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).
split :: (Char -> Bool) -> SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Splits a SizedStrictText 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') ""[""]
chunksOf :: (KnownNat n, Includes s n) => Proxy n -> SizedStrictText s -> Sized (AtMost d) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Splits a SizedStrictText 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"]
Breaking into lines and words
lines :: SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Breaks a SizedStrictText up into a list of SizedStrictTexts at newline characters
 '\n' (LF, line feed). The resulting strings do not contain newlines.
lines does not treat '\r' (CR, carriage return) as a newline character.
words :: SizedStrictText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)] Source #
O(n) Breaks a SizedStrictText up into a list of words, delimited by Chars
 representing white space.
unlines :: Sized s [SizedStrictText s'] -> SizedStrictText (s <*> (s' <+> Exactly 1)) Source #
O(n) Joins lines, after appending a terminating newline to each.
unwords :: Sized s [SizedStrictText s'] -> SizedStrictText (s <*> (s' <+> Exactly 1)) Source #
O(n) Joins words using single space characters.
Predicates
isPrefixOf :: IsMoreGeneral s' s => SizedStrictText s -> SizedStrictText s' -> Bool Source #
O(n) The isPrefixOf function takes two SizedStrictTexts and returns
 True if and only if the first is a prefix of the second.
isSuffixOf :: IsMoreGeneral s' s => SizedStrictText s -> SizedStrictText s' -> Bool Source #
O(n) The isSuffixOf function takes two SizedStrictTexts and returns
 True if and only if the first is a suffix of the second.
isInfixOf :: (IsMoreGeneral s' s, HasCallStack) => SizedStrictText s -> SizedStrictText s' -> Bool Source #
O(n+m) The isInfixOf function takes two SizedStrictTexts and returns
 True if and only if 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).
View patterns
stripPrefix :: SizedStrictText s -> SizedStrictText s' -> Maybe (SizedStrictText (s <-> s')) Source #
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.Sized as T
fnordLength :: SizedStrictText -> Int
fnordLength (stripPrefix "fnord" -> Just suf) = T.length suf
fnordLength _                                 = -1stripSuffix :: SizedStrictText s -> SizedStrictText s' -> Maybe (SizedStrictText (s <-> s')) Source #
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.Sized as T
quuxLength :: SizedStrictText -> Int
quuxLength (stripSuffix "quux" -> Just pre) = T.length pre
quuxLength _                                = -1commonPrefixes :: SizedStrictText s -> SizedStrictText s' -> Maybe (Text, Text, Text) Source #
O(n) Find the longest non-empty common prefix of two strings and return it, along with the suffixes of each string at which they no longer match.
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
Searching
filter :: (Char -> Bool) -> SizedStrictText s -> SizedStrictText (RestrictAtMost s) Source #
O(n) filter, applied to a predicate and a SizedStrictText,
 returns a Text containing those characters that satisfy the
 predicate.
Arguments
| :: SizedStrictText s | 
  | 
| -> SizedStrictText s' | 
  | 
| -> Sized (RestrictAtMost s) [(SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s))] | 
O(n+m) Find all non-overlapping instances of needle in
 haystack.  Each element of the returned list consists of a pair:
- The entire string prior to the kth match (i.e. the prefix)
 - The kth match, followed by the remainder of the string
 
Examples:
>>>breakOnAll "::" ""[]
>>>breakOnAll "/" "a/b/c/"[("a","/b/c/"),("a/b","/c/"),("a/b/c","/")]
In (unlikely) bad cases, this function's time complexity degrades towards O(n*m).
The needle parameter may not be empty.
find :: (Char -> Bool) -> SizedStrictText s -> Maybe Char Source #
O(n) The elem function takes a character and a SizedStrictText, and
 returns True if the element is found in the given SizedStrictText, or
 False otherwise.
O(n) The find function takes a predicate and a SizedStrictText, and
 returns the first element matching the predicate, or Nothing if
 there is no such element.
partition :: (Char -> Bool) -> SizedStrictText s -> (SizedStrictText (RestrictAtMost s), SizedStrictText (RestrictAtMost s)) Source #
O(n) The partition function takes a predicate and a SizedStrictText,
 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)
Indexing
index :: (KnownNat n, Includes s n, HasCallStack) => SizedStrictText s -> Proxy n -> Char Source #
O(n) SizedStrictText index (subscript) operator, starting from 0.
findIndex :: (Char -> Bool) -> SizedStrictText s -> Maybe Int Source #
O(n) The findIndex function takes a predicate and a SizedStrictText
 and returns the index of the first element in the SizedStrictText satisfying
 the predicate.
count :: SizedStrictText s -> SizedStrictText s' -> Int Source #
O(n+m) The count function returns the number of times the
 query string appears in the given SizedStrictText. 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).
Zipping
zip :: SizedStrictText s -> SizedStrictText s -> Sized s [(Char, Char)] Source #
O(n) zip takes two SizedStrictTexts and returns a list of
 corresponding pairs of bytes. If one input SizedStrictText is short,
 excess elements of the longer SizedStrictText are discarded. This is
 equivalent to a pair of unpack operations.
zipWith :: (Char -> Char -> Char) -> SizedStrictText s -> SizedStrictText s -> SizedStrictText s Source #
Orphan instances
| SizedSingleton Text Source # | |
Associated Types type SizedSingletonElement Text # Methods sizedSingleton :: Proxy Text -> SizedSingletonElement Text -> Text #  | |
| SizedFromContainer Text Source # | |