Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
a module with a class for strings, such that the normal functions are all polymorphic for string and text (and total) the string (i.e. [Char]) functions are the semantic definitions, the other implementation are tested against these. except intercalate, which returns Maybe (the corresponding restrictions for the unlines and unwords functions are not enforced)
performance can be improved by using the "native" functions could be expanded
Synopsis
- class Zeros z where
- type family LF l
- class (Monoid l, Zeros (LF l)) => ListForms l where
- class (Zeros a, ListForms a, Eq a) => CharChains a where
- toString :: a -> String
- toText :: Show a => a -> Text
- unwords' :: [a] -> a
- words' :: a -> [a]
- unlines' :: [a] -> a
- lines' :: a -> [a]
- append', append :: a -> a -> a
- null' :: a -> Bool
- mknull :: a
- toLower' :: a -> a
- toUpper' :: a -> a
- isPrefixOf', isInfixOf', isPostfixOf' :: a -> a -> Bool
- stripPrefix' :: a -> a -> Maybe a
- stripSuffix' :: a -> a -> Maybe a
- concat' :: [a] -> a
- trim' :: a -> a
- reverseString, reverse' :: a -> a
- removeLast :: a -> a
- removeChar :: Char -> a -> a
- filterChar :: (Char -> Bool) -> a -> a
- lengthChar :: a -> Int
- nubChar :: a -> a
- drop' :: Int -> a -> a
- take' :: Int -> a -> a
- intercalate' :: a -> [a] -> Maybe a
- splitOn' :: a -> a -> Maybe [a]
- printf' :: PrintfArg r => String -> r -> a
- replace' :: a -> a -> a -> a
- readMaybe' :: Read b => a -> Maybe b
- prop_filterChar :: a -> Bool
- class CharChains2 x a where
- show' :: x -> a
- class Show a => NiceStrings a where
- unlinesT :: [Text] -> Text
- unwordsT :: [Text] -> Text
- wordsT :: Text -> [Text]
- concatT :: [Text] -> Text
- showT :: Show a => a -> Text
- readNoteT :: Read a => Text -> Text -> a
- readNoteTs :: (Show a, Read a) => [Text] -> Text -> a
- sortCaseInsensitive :: (Ord a, CharChains a) => [a] -> [a]
- cmpCaseInsensitive :: (Ord a, CharChains a) => a -> a -> Ordering
- maybe2string :: IsString s => Maybe s -> s
- showList' :: Show a => [a] -> Text
- putIOwords :: MonadIO m => [Text] -> m ()
- debugPrint :: MonadIO m => Bool -> [Text] -> m ()
- toTitle :: Text -> Text
- toLowerStart :: Text -> Text
- toUpperStart :: Text -> Text
- prop_filterChar :: CharChains a => a -> Bool
- isSpace :: Char -> Bool
- isLower :: Char -> Bool
- class Show a => PrettyStrings a where
- showPretty :: a -> Text
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- formatInt :: Int -> Int -> Text
- showAsLines :: Show a => [a] -> Text
Documentation
a minimal algebraic type with nothing than an identity useful to identify a specific value in a type
Nothing
Instances
Zeros ByteString Source # | |
Defined in Uniform.Strings.Conversion | |
Zeros Text Source # | |
Zeros BSUTF Source # | |
Zeros LazyByteString Source # | |
Defined in Uniform.Strings.Conversion | |
Zeros URL Source # | |
Zeros () | |
Zeros Bool | |
Zeros Char | |
Zeros Int | |
Zeros (Maybe a) | |
Zeros [a] | |
(Zeros a, Zeros b) => Zeros (a, b) | |
(Zeros a, Zeros b, Zeros c) => Zeros (a, b, c) | |
(Zeros a, Zeros b, Zeros c, Zeros d) => Zeros (a, b, c, d) | |
(Zeros a, Zeros b, Zeros c, Zeros d, Zeros e) => Zeros (a, b, c, d, e) | |
Instances
type LF Text Source # | |
Defined in Uniform.Strings.Utilities | |
type LF BSUTF Source # | |
Defined in Uniform.Strings.Utilities | |
type LF LazyByteString Source # | |
Defined in Uniform.Strings.Utilities | |
type LF String Source # | |
Defined in Uniform.Strings.Utilities |
class (Monoid l, Zeros (LF l)) => ListForms l where #
prependOne :: LF l -> l -> l #
Instances
ListForms Text Source # | |
ListForms BSUTF Source # | |
ListForms LazyByteString Source # | |
Defined in Uniform.Strings.Utilities type LF LazyByteString # prependOne :: LF LazyByteString -> LazyByteString -> LazyByteString # appendOne :: LazyByteString -> LF LazyByteString -> LazyByteString # mkOne :: LF LazyByteString -> LazyByteString # appendTwo :: LazyByteString -> LazyByteString -> LazyByteString # | |
ListForms String Source # | |
class (Zeros a, ListForms a, Eq a) => CharChains a where Source #
toString, unwords', words', unlines', lines', mknull, toLower', toUpper', isPrefixOf', isInfixOf', stripPrefix', stripSuffix', concat', trim', reverseString, removeLast, removeChar, filterChar, lengthChar, nubChar, drop', take', intercalate', splitOn', printf', replace', readMaybe', prop_filterChar
toString :: a -> String Source #
toText :: Show a => a -> Text Source #
conversion
append' :: a -> a -> a Source #
append :: a -> a -> a Source #
convert the string to lowercase, idempotent is not inverse of toUpper
is not idempotent and gives different results for string and text (sz and similar ligatures)
isPrefixOf' :: a -> a -> Bool Source #
isInfixOf' :: a -> a -> Bool Source #
isPostfixOf' :: a -> a -> Bool Source #
stripPrefix' :: a -> a -> Maybe a Source #
takes the prefix away, if present (and return rest). nothing if no prefix
stripSuffix' :: a -> a -> Maybe a Source #
removes all spaces front and back, idempotent
reverseString :: a -> a Source #
removeLast :: a -> a Source #
remove last char
removeChar :: Char -> a -> a Source #
remove a character from a string
filterChar :: (Char -> Bool) -> a -> a Source #
lengthChar :: a -> Int Source #
drop' :: Int -> a -> a Source #
take' :: Int -> a -> a Source #
add a splitAt or dropN function
intercalate' :: a -> [a] -> Maybe a Source #
splitOn' and intercalate' are inverses (see Data.SplitList) returns Nothing if second is empty and intercalate "x" "" gives Just "" return Nothing if first is empty or contained in second to achievee inverse with splitOn
splitOn' :: a -> a -> Maybe [a] Source #
splits the first by all occurences of the second the second is removed from results returns Nothing if second is empty
printf' :: PrintfArg r => String -> r -> a Source #
formats a string accoding to a pattern - restricted to a single string (perhaps) requires type of argument fixed!
replace' :: a -> a -> a -> a Source #
readMaybe' :: Read b => a -> Maybe b Source #
prop_filterChar :: a -> Bool Source #
Instances
class CharChains2 x a where Source #
Instances
CharChains2 Text Text Source # | |
CharChains2 Text String Source # | |
CharChains2 String Text Source # | |
CharChains2 String String Source # | |
CharChains2 () Text Source # | |
Defined in Uniform.Strings.Utilities | |
CharChains2 () String Source # | |
Defined in Uniform.Strings.Utilities | |
CharChains2 Bool Text Source # | |
CharChains2 Bool String Source # | |
CharChains2 Double Text Source # | |
CharChains2 Double String Source # | |
CharChains2 Float Text Source # | |
CharChains2 Float String Source # | |
CharChains2 Int Text Source # | |
CharChains2 Int String Source # | |
Show a => CharChains2 [a] Text Source # | |
Defined in Uniform.Strings.Utilities | |
Show a => CharChains2 [a] String Source # | |
Defined in Uniform.Strings.Utilities | |
(Show a, Show b) => CharChains2 (a, b) Text Source # | |
Defined in Uniform.Strings.Utilities | |
(Show a, Show b) => CharChains2 (a, b) String Source # | |
Defined in Uniform.Strings.Utilities |
class Show a => NiceStrings a where Source #
Instances
NiceStrings Text Source # | |
NiceStrings Double Source # | |
NiceStrings Float Source # | |
NiceStrings Int Source # | |
NiceStrings a => NiceStrings (Maybe a) Source # | |
(Show a, NiceStrings a) => NiceStrings [a] Source # | |
(NiceStrings a, NiceStrings b) => NiceStrings (a, b) Source # | |
(Show a, Show b, Show c) => NiceStrings (a, b, c) Source # | |
sortCaseInsensitive :: (Ord a, CharChains a) => [a] -> [a] Source #
cmpCaseInsensitive :: (Ord a, CharChains a) => a -> a -> Ordering Source #
maybe2string :: IsString s => Maybe s -> s Source #
putIOwords :: MonadIO m => [Text] -> m () Source #
debugPrint :: MonadIO m => Bool -> [Text] -> m () Source #
print the texts when the bool is true (flag debug)
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.
Since: text-1.0.0.0
toLowerStart :: Text -> Text Source #
convert the first character to lowercase - for Properties in RDF
toUpperStart :: Text -> Text Source #
convert the first character to Uppercase - for PosTags in Spanish
prop_filterChar :: CharChains a => a -> Bool Source #
Returns True
for any Unicode space character, and the control
characters \t
, \n
, \r
, \f
, \v
.
class Show a => PrettyStrings a where Source #
showPretty :: a -> Text Source #
Instances
Show a => PrettyStrings a Source # | |
Defined in Uniform.Strings.Utilities showPretty :: a -> Text Source # |
takeWhile :: (a -> Bool) -> [a] -> [a] #
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
.
>>>
takeWhile (< 3) [1,2,3,4,1,2,3,4]
[1,2]>>>
takeWhile (< 9) [1,2,3]
[1,2,3]>>>
takeWhile (< 0) [1,2,3]
[]
span :: (a -> Bool) -> [a] -> ([a], [a]) #
span
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
satisfy p
and second element is the remainder of the list:
>>>
span (< 3) [1,2,3,4,1,2,3,4]
([1,2],[3,4,1,2,3,4])>>>
span (< 9) [1,2,3]
([1,2,3],[])>>>
span (< 0) [1,2,3]
([],[1,2,3])
break :: (a -> Bool) -> [a] -> ([a], [a]) #
break
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and second element is the remainder of the list:
>>>
break (> 3) [1,2,3,4,1,2,3,4]
([1,2,3],[4,1,2,3,4])>>>
break (< 9) [1,2,3]
([],[1,2,3])>>>
break (> 9) [1,2,3]
([1,2,3],[])
showAsLines :: Show a => [a] -> Text Source #
show on a line, does not propagate, inside is shown normally