uniform-strings-0.1.5.1: Manipulate and convert strings of characters uniformly and consistently
Safe HaskellSafe-Inferred
LanguageHaskell2010

Uniform.Strings.Utilities

Description

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

Documentation

class Zeros z where #

a minimal algebraic type with nothing than an identity useful to identify a specific value in a type

Minimal complete definition

Nothing

Methods

zero :: z #

isZero :: z -> Bool #

notZero :: z -> Bool #

Instances

Instances details
Zeros ByteString Source # 
Instance details

Defined in Uniform.Strings.Conversion

Zeros Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

zero :: Text #

isZero :: Text -> Bool #

notZero :: Text -> Bool #

Zeros BSUTF Source # 
Instance details

Defined in Uniform.Strings.Conversion

Methods

zero :: BSUTF #

isZero :: BSUTF -> Bool #

notZero :: BSUTF -> Bool #

Zeros LazyByteString Source # 
Instance details

Defined in Uniform.Strings.Conversion

Zeros URL Source # 
Instance details

Defined in Uniform.Strings.Conversion

Methods

zero :: URL #

isZero :: URL -> Bool #

notZero :: URL -> Bool #

Zeros () 
Instance details

Defined in Uniform.Zero

Methods

zero :: () #

isZero :: () -> Bool #

notZero :: () -> Bool #

Zeros Bool 
Instance details

Defined in Uniform.Zero

Methods

zero :: Bool #

isZero :: Bool -> Bool #

notZero :: Bool -> Bool #

Zeros Char 
Instance details

Defined in Uniform.Zero

Methods

zero :: Char #

isZero :: Char -> Bool #

notZero :: Char -> Bool #

Zeros Int 
Instance details

Defined in Uniform.Zero

Methods

zero :: Int #

isZero :: Int -> Bool #

notZero :: Int -> Bool #

Zeros (Maybe a) 
Instance details

Defined in Uniform.Zero

Methods

zero :: Maybe a #

isZero :: Maybe a -> Bool #

notZero :: Maybe a -> Bool #

Zeros [a] 
Instance details

Defined in Uniform.Zero

Methods

zero :: [a] #

isZero :: [a] -> Bool #

notZero :: [a] -> Bool #

(Zeros a, Zeros b) => Zeros (a, b) 
Instance details

Defined in Uniform.Zero

Methods

zero :: (a, b) #

isZero :: (a, b) -> Bool #

notZero :: (a, b) -> Bool #

(Zeros a, Zeros b, Zeros c) => Zeros (a, b, c) 
Instance details

Defined in Uniform.Zero

Methods

zero :: (a, b, c) #

isZero :: (a, b, c) -> Bool #

notZero :: (a, b, c) -> Bool #

(Zeros a, Zeros b, Zeros c, Zeros d) => Zeros (a, b, c, d) 
Instance details

Defined in Uniform.Zero

Methods

zero :: (a, b, c, d) #

isZero :: (a, b, c, d) -> Bool #

notZero :: (a, b, c, d) -> Bool #

(Zeros a, Zeros b, Zeros c, Zeros d, Zeros e) => Zeros (a, b, c, d, e) 
Instance details

Defined in Uniform.Zero

Methods

zero :: (a, b, c, d, e) #

isZero :: (a, b, c, d, e) -> Bool #

notZero :: (a, b, c, d, e) -> Bool #

type family LF l #

Instances

Instances details
type LF Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

type LF Text = Char
type LF BSUTF Source # 
Instance details

Defined in Uniform.Strings.Utilities

type LF BSUTF = Char
type LF LazyByteString Source # 
Instance details

Defined in Uniform.Strings.Utilities

type LF String Source # 
Instance details

Defined in Uniform.Strings.Utilities

type LF String = Char

class (Monoid l, Zeros (LF l)) => ListForms l where #

Minimal complete definition

mkOne

Associated Types

type LF l #

Methods

prependOne :: LF l -> l -> l #

appendOne :: l -> LF l -> l #

mkOne :: LF l -> l #

appendTwo :: l -> l -> l #

Instances

Instances details
ListForms Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Associated Types

type LF Text #

Methods

prependOne :: LF Text -> Text -> Text #

appendOne :: Text -> LF Text -> Text #

mkOne :: LF Text -> Text #

appendTwo :: Text -> Text -> Text #

ListForms BSUTF Source # 
Instance details

Defined in Uniform.Strings.Utilities

Associated Types

type LF BSUTF #

ListForms LazyByteString Source # 
Instance details

Defined in Uniform.Strings.Utilities

Associated Types

type LF LazyByteString #

ListForms String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Associated Types

type LF String #

class (Zeros a, ListForms a, Eq a) => CharChains a where Source #

Methods

toString :: a -> String Source #

toText :: Show a => a -> Text Source #

conversion

unwords' :: [a] -> a Source #

words' :: a -> [a] Source #

unlines' :: [a] -> a Source #

lines' :: a -> [a] Source #

append' :: a -> a -> a Source #

append :: a -> a -> a Source #

null' :: a -> Bool Source #

mknull :: a Source #

toLower' :: a -> a Source #

convert the string to lowercase, idempotent is not inverse of toUpper

toUpper' :: a -> a Source #

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 #

concat' :: [a] -> a Source #

trim' :: a -> a Source #

removes all spaces front and back, idempotent

reverseString :: a -> a Source #

reverse' :: 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 #

nubChar :: a -> a 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

Instances details
CharChains Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

CharChains BSUTF Source # 
Instance details

Defined in Uniform.Strings.Utilities

CharChains LazyByteString Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

toString :: LazyByteString -> String Source #

toText :: LazyByteString -> Text Source #

unwords' :: [LazyByteString] -> LazyByteString Source #

words' :: LazyByteString -> [LazyByteString] Source #

unlines' :: [LazyByteString] -> LazyByteString Source #

lines' :: LazyByteString -> [LazyByteString] Source #

append' :: LazyByteString -> LazyByteString -> LazyByteString Source #

append :: LazyByteString -> LazyByteString -> LazyByteString Source #

null' :: LazyByteString -> Bool Source #

mknull :: LazyByteString Source #

toLower' :: LazyByteString -> LazyByteString Source #

toUpper' :: LazyByteString -> LazyByteString Source #

isPrefixOf' :: LazyByteString -> LazyByteString -> Bool Source #

isInfixOf' :: LazyByteString -> LazyByteString -> Bool Source #

isPostfixOf' :: LazyByteString -> LazyByteString -> Bool Source #

stripPrefix' :: LazyByteString -> LazyByteString -> Maybe LazyByteString Source #

stripSuffix' :: LazyByteString -> LazyByteString -> Maybe LazyByteString Source #

concat' :: [LazyByteString] -> LazyByteString Source #

trim' :: LazyByteString -> LazyByteString Source #

reverseString :: LazyByteString -> LazyByteString Source #

reverse' :: LazyByteString -> LazyByteString Source #

removeLast :: LazyByteString -> LazyByteString Source #

removeChar :: Char -> LazyByteString -> LazyByteString Source #

filterChar :: (Char -> Bool) -> LazyByteString -> LazyByteString Source #

lengthChar :: LazyByteString -> Int Source #

nubChar :: LazyByteString -> LazyByteString Source #

drop' :: Int -> LazyByteString -> LazyByteString Source #

take' :: Int -> LazyByteString -> LazyByteString Source #

intercalate' :: LazyByteString -> [LazyByteString] -> Maybe LazyByteString Source #

splitOn' :: LazyByteString -> LazyByteString -> Maybe [LazyByteString] Source #

printf' :: PrintfArg r => String -> r -> LazyByteString Source #

replace' :: LazyByteString -> LazyByteString -> LazyByteString -> LazyByteString Source #

readMaybe' :: Read b => LazyByteString -> Maybe b Source #

prop_filterChar :: LazyByteString -> Bool Source #

CharChains String Source # 
Instance details

Defined in Uniform.Strings.Utilities

class CharChains2 x a where Source #

Methods

show' :: x -> a Source #

Instances

Instances details
CharChains2 Text Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Text -> Text Source #

CharChains2 Text String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Text -> String Source #

CharChains2 String Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: String -> Text Source #

CharChains2 String String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: String -> String Source #

CharChains2 () Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: () -> Text Source #

CharChains2 () String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: () -> String Source #

CharChains2 Bool Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Bool -> Text Source #

CharChains2 Bool String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Bool -> String Source #

CharChains2 Double Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Double -> Text Source #

CharChains2 Double String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Double -> String Source #

CharChains2 Float Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Float -> Text Source #

CharChains2 Float String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Float -> String Source #

CharChains2 Int Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Int -> Text Source #

CharChains2 Int String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: Int -> String Source #

Show a => CharChains2 [a] Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: [a] -> Text Source #

Show a => CharChains2 [a] String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: [a] -> String Source #

(Show a, Show b) => CharChains2 (a, b) Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: (a, b) -> Text Source #

(Show a, Show b) => CharChains2 (a, b) String Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

show' :: (a, b) -> String Source #

class Show a => NiceStrings a where Source #

Minimal complete definition

showNice

Methods

shownice :: a -> Text Source #

showNice :: a -> Text Source #

showlong :: a -> Text Source #

Instances

Instances details
NiceStrings Text Source # 
Instance details

Defined in Uniform.Strings.Utilities

NiceStrings Double Source # 
Instance details

Defined in Uniform.Strings.Utilities

NiceStrings Float Source # 
Instance details

Defined in Uniform.Strings.Utilities

NiceStrings Int Source # 
Instance details

Defined in Uniform.Strings.Utilities

NiceStrings a => NiceStrings (Maybe a) Source # 
Instance details

Defined in Uniform.Strings.Utilities

(Show a, NiceStrings a) => NiceStrings [a] Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

shownice :: [a] -> Text Source #

showNice :: [a] -> Text Source #

showlong :: [a] -> Text Source #

(NiceStrings a, NiceStrings b) => NiceStrings (a, b) Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

shownice :: (a, b) -> Text Source #

showNice :: (a, b) -> Text Source #

showlong :: (a, b) -> Text Source #

(Show a, Show b, Show c) => NiceStrings (a, b, c) Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

shownice :: (a, b, c) -> Text Source #

showNice :: (a, b, c) -> Text Source #

showlong :: (a, b, c) -> Text Source #

unwordsT :: [Text] -> Text Source #

to fix types for overloaded strings

showT :: Show a => a -> Text Source #

readNoteT :: Read a => Text -> Text -> a Source #

read a Text into a specific format

readNoteTs :: (Show a, Read a) => [Text] -> Text -> a Source #

read a Text into a specific format

sortCaseInsensitive :: (Ord a, CharChains a) => [a] -> [a] Source #

showList' :: Show a => [a] -> Text Source #

show a collection of lines

putIOwords :: MonadIO m => [Text] -> m () Source #

debugPrint :: MonadIO m => Bool -> [Text] -> m () Source #

print the texts when the bool is true (flag debug)

toTitle :: 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.

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

isSpace :: Char -> Bool #

Returns True for any Unicode space character, and the control characters \t, \n, \r, \f, \v.

isLower :: Char -> Bool #

Selects lower-case alphabetic Unicode characters (letters).

class Show a => PrettyStrings a where Source #

Methods

showPretty :: a -> Text Source #

Instances

Instances details
Show a => PrettyStrings a Source # 
Instance details

Defined in Uniform.Strings.Utilities

Methods

showPretty :: a -> Text Source #

dropWhile :: (a -> Bool) -> [a] -> [a] #

dropWhile p xs returns the suffix remaining after takeWhile p xs.

>>> dropWhile (< 3) [1,2,3,4,5,1,2,3]
[3,4,5,1,2,3]
>>> dropWhile (< 9) [1,2,3]
[]
>>> dropWhile (< 0) [1,2,3]
[1,2,3]

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])

span p xs is equivalent to (takeWhile p xs, dropWhile p xs)

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],[])

break p is equivalent to span (not . p).

showAsLines :: Show a => [a] -> Text Source #

show on a line, does not propagate, inside is shown normally

Orphan instances

ListForms Text Source # 
Instance details

Associated Types

type LF Text #

Methods

prependOne :: LF Text -> Text -> Text #

appendOne :: Text -> LF Text -> Text #

mkOne :: LF Text -> Text #

appendTwo :: Text -> Text -> Text #

ListForms BSUTF Source # 
Instance details

Associated Types

type LF BSUTF #

ListForms LazyByteString Source # 
Instance details

Associated Types

type LF LazyByteString #

ListForms String Source # 
Instance details

Associated Types

type LF String #

Zeros Text Source # 
Instance details

Methods

zero :: Text #

isZero :: Text -> Bool #

notZero :: Text -> Bool #