sdp4text-0.2: SDP wrapper for Text.
Copyright(c) Andrey Mulik 2020
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilitynon-portable (GHC only)
Safe HaskellTrustworthy
LanguageHaskell2010

SDP.Text

Description

SDP.Text provides sdp instances for strict Text.

Synopsis

Exports

Strict text

type SText = Text Source #

Text alias, may reduce ambiguity.

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
Nullable Text Source # 
Instance details

Defined in SDP.Text

Methods

lzero :: Text #

isNull :: Text -> Bool #

Estimate Text Source # 
Instance details

Defined in SDP.Text

Methods

(<.=>) :: Text -> Int -> Ordering #

(<==>) :: Compare Text #

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

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

(.<=) :: Text -> Int -> Bool #

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

(.<) :: Text -> Int -> Bool #

(.>) :: Text -> Int -> Bool #

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

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

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

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

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

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

IsFile Text Source # 
Instance details

Defined in SDP.Text

Methods

hGetContents :: MonadIO io => Handle -> io Text #

hPutContents :: MonadIO io => Handle -> Text -> io () #

IsTextFile Text Source # 
Instance details

Defined in SDP.Text

Methods

hGetLine :: MonadIO io => Handle -> io Text #

hPutStr :: MonadIO io => Handle -> Text -> io () #

hPutStrLn :: MonadIO io => Handle -> Text -> io () #

Bordered Text Int Source # 
Instance details

Defined in SDP.Text

Methods

bounds :: Text -> (Int, Int) #

lower :: Text -> Int #

upper :: Text -> Int #

sizeOf :: Text -> Int #

sizesOf :: Text -> [Int] #

indexIn :: Text -> Int -> Bool #

indices :: Text -> [Int] #

indexOf :: Text -> Int -> Int #

offsetOf :: Text -> Int -> Int #

Linear Text Char Source # 
Instance details

Defined in SDP.Text

Methods

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

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

toHead :: Char -> Text -> Text #

head :: Text -> Char #

tail :: Text -> Text #

unsnoc :: Text -> (Text, Char) #

unsnoc' :: Text -> Maybe (Text, Char) #

toLast :: Text -> Char -> Text #

init :: Text -> Text #

last :: Text -> Char #

single :: Char -> Text #

(++) :: Text -> Text -> Text #

replicate :: Int -> Char -> Text #

fromList :: [Char] -> Text #

fromListN :: Int -> [Char] -> Text #

listR :: Text -> [Char] #

listL :: Text -> [Char] #

fromFoldable :: Foldable f => f Char -> Text #

(!^) :: Text -> Int -> Char #

write :: Text -> Int -> Char -> Text #

concat :: Foldable f => f Text -> Text #

concatMap :: Foldable f => (a -> Text) -> f a -> Text #

intersperse :: Char -> Text -> Text #

filter :: (Char -> Bool) -> Text -> Text #

except :: (Char -> Bool) -> Text -> Text #

partition :: (Char -> Bool) -> Text -> (Text, Text) #

partitions :: Foldable f => f (Char -> Bool) -> Text -> [Text] #

select :: (Char -> Maybe a) -> Text -> [a] #

select' :: (t Char ~ Text, Linear1 t a) => (Char -> Maybe a) -> Text -> t a #

extract :: (Char -> Maybe a) -> Text -> ([a], Text) #

extract' :: (t Char ~ Text, Linear1 t a) => (Char -> Maybe a) -> Text -> (t a, Text) #

selects :: Foldable f => f (Char -> Maybe a) -> Text -> ([[a]], Text) #

selects' :: (Foldable f, t Char ~ Text, Linear1 t a) => f (Char -> Maybe a) -> Text -> ([t a], Text) #

isSubseqOf :: Text -> Text -> Bool #

reverse :: Text -> Text #

force :: Text -> Text #

subsequences :: Text -> [Text] #

iterate :: Int -> (Char -> Char) -> Char -> Text #

nub :: Text -> Text #

nubBy :: Equal Char -> Text -> Text #

ofoldr :: (Int -> Char -> b -> b) -> b -> Text -> b #

ofoldl :: (Int -> b -> Char -> b) -> b -> Text -> b #

ofoldr' :: (Int -> Char -> b -> b) -> b -> Text -> b #

ofoldl' :: (Int -> b -> Char -> b) -> b -> Text -> b #

o_foldr :: (Char -> b -> b) -> b -> Text -> b #

o_foldl :: (b -> Char -> b) -> b -> Text -> b #

o_foldr' :: (Char -> b -> b) -> b -> Text -> b #

o_foldl' :: (b -> Char -> b) -> b -> Text -> b #

Split Text Char Source # 
Instance details

Defined in SDP.Text

Methods

take :: Int -> Text -> Text #

drop :: Int -> Text -> Text #

keep :: Int -> Text -> Text #

sans :: Int -> Text -> Text #

save :: Int -> Text -> Text #

skip :: Int -> Text -> Text #

split :: Int -> Text -> (Text, Text) #

divide :: Int -> Text -> (Text, Text) #

splits :: Foldable f => f Int -> Text -> [Text] #

divides :: Foldable f => f Int -> Text -> [Text] #

parts :: Foldable f => f Int -> Text -> [Text] #

chunks :: Int -> Text -> [Text] #

splitBy :: (Char -> Bool) -> Text -> (Text, Text) #

divideBy :: (Char -> Bool) -> Text -> (Text, Text) #

splitsBy :: (Char -> Bool) -> Text -> [Text] #

splitsOn :: Text -> Text -> [Text] #

replaceBy :: Text -> Text -> Text -> Text #

removeAll :: Text -> Text -> Text #

combo :: Equal Char -> Text -> Int #

justifyL :: Int -> Char -> Text -> Text #

justifyR :: Int -> Char -> Text -> Text #

each :: Int -> Text -> Text #

eachFrom :: Int -> Int -> Text -> Text #

isPrefixOf :: Text -> Text -> Bool #

isSuffixOf :: Text -> Text -> Bool #

isInfixOf :: Text -> Text -> Bool #

prefix :: (Char -> Bool) -> Text -> Int #

suffix :: (Char -> Bool) -> Text -> Int #

infixes :: Text -> Text -> [Int] #

dropSide :: (Char -> Bool) -> Text -> Text #

takeWhile :: (Char -> Bool) -> Text -> Text #

dropWhile :: (Char -> Bool) -> Text -> Text #

takeEnd :: (Char -> Bool) -> Text -> Text #

dropEnd :: (Char -> Bool) -> Text -> Text #

spanl :: (Char -> Bool) -> Text -> (Text, Text) #

breakl :: (Char -> Bool) -> Text -> (Text, Text) #

spanr :: (Char -> Bool) -> Text -> (Text, Text) #

breakr :: (Char -> Bool) -> Text -> (Text, Text) #

selectWhile :: (Char -> Maybe a) -> Text -> [a] #

selectEnd :: (Char -> Maybe a) -> Text -> [a] #

extractWhile :: (Char -> Maybe a) -> Text -> ([a], Text) #

extractEnd :: (Char -> Maybe a) -> Text -> (Text, [a]) #

selectWhile' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> t a #

selectEnd' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> t a #

extractWhile' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> (t a, Text) #

extractEnd' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> (Text, t a) #

Indexed Text Int Char Source # 
Instance details

Defined in SDP.Text

Methods

assoc :: (Int, Int) -> [(Int, Char)] -> Text #

assoc' :: (Int, Int) -> Char -> [(Int, Char)] -> Text #

fromIndexed :: Indexed m j Char => m -> Text #

write' :: Text -> Int -> Char -> Text #

accum :: (Char -> e' -> Char) -> Text -> [(Int, e')] -> Text #

imap :: Map m j Char => (Int, Int) -> m -> (Int -> j) -> Text #

update' :: Text -> (Char -> Char) -> Int -> Text #

updates' :: Text -> (Int -> Char -> Char) -> Text #

Map Text Int Char Source # 
Instance details

Defined in SDP.Text

Methods

assocs :: Text -> [(Int, Char)] #

toMap :: [(Int, Char)] -> Text #

toMap' :: Char -> [(Int, Char)] -> Text #

insert' :: Int -> Char -> Text -> Text #

delete' :: Int -> Text -> Text #

member' :: Int -> Text -> Bool #

(//) :: Text -> [(Int, Char)] -> Text #

(.!) :: Text -> Int -> Char #

(!) :: Text -> Int -> Char #

(!?) :: Text -> Int -> Maybe Char #

filter' :: (Int -> Char -> Bool) -> Text -> Text #

union' :: (Char -> Char -> Char) -> Text -> Text -> Text #

difference' :: (Char -> Char -> Maybe Char) -> Text -> Text -> Text #

intersection' :: (Char -> Char -> Char) -> Text -> Text -> Text #

update :: Text -> (Int -> Char -> Char) -> Text #

lookupLT' :: Int -> Text -> Maybe (Int, Char) #

lookupGT' :: Int -> Text -> Maybe (Int, Char) #

lookupLE' :: Int -> Text -> Maybe (Int, Char) #

lookupGE' :: Int -> Text -> Maybe (Int, Char) #

keys :: Text -> [Int] #

(.$) :: (Char -> Bool) -> Text -> Maybe Int #

(*$) :: (Char -> Bool) -> Text -> [Int] #

kfoldr :: (Int -> Char -> b -> b) -> b -> Text -> b #

kfoldl :: (Int -> b -> Char -> b) -> b -> Text -> b #

kfoldr' :: (Int -> Char -> b -> b) -> b -> Text -> b #

kfoldl' :: (Int -> b -> Char -> b) -> b -> Text -> b #

MonadIO io => Thaw io Text (MIOBytes# io Char) Source # 
Instance details

Defined in SDP.Text

Methods

thaw :: Text -> io (MIOBytes# io Char) #

unsafeThaw :: Text -> io (MIOBytes# io Char) #

MonadIO io => Freeze io (MIOBytes# io Char) Text Source # 
Instance details

Defined in SDP.Text

Methods

freeze :: MIOBytes# io Char -> io Text #

unsafeFreeze :: MIOBytes# io Char -> io Text #

Thaw (ST s) Text (STBytes# s Char) Source # 
Instance details

Defined in SDP.Text

Methods

thaw :: Text -> ST s (STBytes# s Char) #

unsafeThaw :: Text -> ST s (STBytes# s Char) #

Freeze (ST s) (STBytes# s Char) Text Source # 
Instance details

Defined in SDP.Text

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char

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

toLower :: 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).

toUpper :: 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".

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

Orphan instances

Nullable Text Source # 
Instance details

Methods

lzero :: Text #

isNull :: Text -> Bool #

Estimate Text Source # 
Instance details

Methods

(<.=>) :: Text -> Int -> Ordering #

(<==>) :: Compare Text #

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

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

(.<=) :: Text -> Int -> Bool #

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

(.<) :: Text -> Int -> Bool #

(.>) :: Text -> Int -> Bool #

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

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

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

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

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

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

IsFile Text Source # 
Instance details

Methods

hGetContents :: MonadIO io => Handle -> io Text #

hPutContents :: MonadIO io => Handle -> Text -> io () #

IsTextFile Text Source # 
Instance details

Methods

hGetLine :: MonadIO io => Handle -> io Text #

hPutStr :: MonadIO io => Handle -> Text -> io () #

hPutStrLn :: MonadIO io => Handle -> Text -> io () #

Bordered Text Int Source # 
Instance details

Methods

bounds :: Text -> (Int, Int) #

lower :: Text -> Int #

upper :: Text -> Int #

sizeOf :: Text -> Int #

sizesOf :: Text -> [Int] #

indexIn :: Text -> Int -> Bool #

indices :: Text -> [Int] #

indexOf :: Text -> Int -> Int #

offsetOf :: Text -> Int -> Int #

Linear Text Char Source # 
Instance details

Methods

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

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

toHead :: Char -> Text -> Text #

head :: Text -> Char #

tail :: Text -> Text #

unsnoc :: Text -> (Text, Char) #

unsnoc' :: Text -> Maybe (Text, Char) #

toLast :: Text -> Char -> Text #

init :: Text -> Text #

last :: Text -> Char #

single :: Char -> Text #

(++) :: Text -> Text -> Text #

replicate :: Int -> Char -> Text #

fromList :: [Char] -> Text #

fromListN :: Int -> [Char] -> Text #

listR :: Text -> [Char] #

listL :: Text -> [Char] #

fromFoldable :: Foldable f => f Char -> Text #

(!^) :: Text -> Int -> Char #

write :: Text -> Int -> Char -> Text #

concat :: Foldable f => f Text -> Text #

concatMap :: Foldable f => (a -> Text) -> f a -> Text #

intersperse :: Char -> Text -> Text #

filter :: (Char -> Bool) -> Text -> Text #

except :: (Char -> Bool) -> Text -> Text #

partition :: (Char -> Bool) -> Text -> (Text, Text) #

partitions :: Foldable f => f (Char -> Bool) -> Text -> [Text] #

select :: (Char -> Maybe a) -> Text -> [a] #

select' :: (t Char ~ Text, Linear1 t a) => (Char -> Maybe a) -> Text -> t a #

extract :: (Char -> Maybe a) -> Text -> ([a], Text) #

extract' :: (t Char ~ Text, Linear1 t a) => (Char -> Maybe a) -> Text -> (t a, Text) #

selects :: Foldable f => f (Char -> Maybe a) -> Text -> ([[a]], Text) #

selects' :: (Foldable f, t Char ~ Text, Linear1 t a) => f (Char -> Maybe a) -> Text -> ([t a], Text) #

isSubseqOf :: Text -> Text -> Bool #

reverse :: Text -> Text #

force :: Text -> Text #

subsequences :: Text -> [Text] #

iterate :: Int -> (Char -> Char) -> Char -> Text #

nub :: Text -> Text #

nubBy :: Equal Char -> Text -> Text #

ofoldr :: (Int -> Char -> b -> b) -> b -> Text -> b #

ofoldl :: (Int -> b -> Char -> b) -> b -> Text -> b #

ofoldr' :: (Int -> Char -> b -> b) -> b -> Text -> b #

ofoldl' :: (Int -> b -> Char -> b) -> b -> Text -> b #

o_foldr :: (Char -> b -> b) -> b -> Text -> b #

o_foldl :: (b -> Char -> b) -> b -> Text -> b #

o_foldr' :: (Char -> b -> b) -> b -> Text -> b #

o_foldl' :: (b -> Char -> b) -> b -> Text -> b #

Split Text Char Source # 
Instance details

Methods

take :: Int -> Text -> Text #

drop :: Int -> Text -> Text #

keep :: Int -> Text -> Text #

sans :: Int -> Text -> Text #

save :: Int -> Text -> Text #

skip :: Int -> Text -> Text #

split :: Int -> Text -> (Text, Text) #

divide :: Int -> Text -> (Text, Text) #

splits :: Foldable f => f Int -> Text -> [Text] #

divides :: Foldable f => f Int -> Text -> [Text] #

parts :: Foldable f => f Int -> Text -> [Text] #

chunks :: Int -> Text -> [Text] #

splitBy :: (Char -> Bool) -> Text -> (Text, Text) #

divideBy :: (Char -> Bool) -> Text -> (Text, Text) #

splitsBy :: (Char -> Bool) -> Text -> [Text] #

splitsOn :: Text -> Text -> [Text] #

replaceBy :: Text -> Text -> Text -> Text #

removeAll :: Text -> Text -> Text #

combo :: Equal Char -> Text -> Int #

justifyL :: Int -> Char -> Text -> Text #

justifyR :: Int -> Char -> Text -> Text #

each :: Int -> Text -> Text #

eachFrom :: Int -> Int -> Text -> Text #

isPrefixOf :: Text -> Text -> Bool #

isSuffixOf :: Text -> Text -> Bool #

isInfixOf :: Text -> Text -> Bool #

prefix :: (Char -> Bool) -> Text -> Int #

suffix :: (Char -> Bool) -> Text -> Int #

infixes :: Text -> Text -> [Int] #

dropSide :: (Char -> Bool) -> Text -> Text #

takeWhile :: (Char -> Bool) -> Text -> Text #

dropWhile :: (Char -> Bool) -> Text -> Text #

takeEnd :: (Char -> Bool) -> Text -> Text #

dropEnd :: (Char -> Bool) -> Text -> Text #

spanl :: (Char -> Bool) -> Text -> (Text, Text) #

breakl :: (Char -> Bool) -> Text -> (Text, Text) #

spanr :: (Char -> Bool) -> Text -> (Text, Text) #

breakr :: (Char -> Bool) -> Text -> (Text, Text) #

selectWhile :: (Char -> Maybe a) -> Text -> [a] #

selectEnd :: (Char -> Maybe a) -> Text -> [a] #

extractWhile :: (Char -> Maybe a) -> Text -> ([a], Text) #

extractEnd :: (Char -> Maybe a) -> Text -> (Text, [a]) #

selectWhile' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> t a #

selectEnd' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> t a #

extractWhile' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> (t a, Text) #

extractEnd' :: (t Char ~ l, Split1 t a) => (Char -> Maybe a) -> Text -> (Text, t a) #

Indexed Text Int Char Source # 
Instance details

Methods

assoc :: (Int, Int) -> [(Int, Char)] -> Text #

assoc' :: (Int, Int) -> Char -> [(Int, Char)] -> Text #

fromIndexed :: Indexed m j Char => m -> Text #

write' :: Text -> Int -> Char -> Text #

accum :: (Char -> e' -> Char) -> Text -> [(Int, e')] -> Text #

imap :: Map m j Char => (Int, Int) -> m -> (Int -> j) -> Text #

update' :: Text -> (Char -> Char) -> Int -> Text #

updates' :: Text -> (Int -> Char -> Char) -> Text #

Map Text Int Char Source # 
Instance details

Methods

assocs :: Text -> [(Int, Char)] #

toMap :: [(Int, Char)] -> Text #

toMap' :: Char -> [(Int, Char)] -> Text #

insert' :: Int -> Char -> Text -> Text #

delete' :: Int -> Text -> Text #

member' :: Int -> Text -> Bool #

(//) :: Text -> [(Int, Char)] -> Text #

(.!) :: Text -> Int -> Char #

(!) :: Text -> Int -> Char #

(!?) :: Text -> Int -> Maybe Char #

filter' :: (Int -> Char -> Bool) -> Text -> Text #

union' :: (Char -> Char -> Char) -> Text -> Text -> Text #

difference' :: (Char -> Char -> Maybe Char) -> Text -> Text -> Text #

intersection' :: (Char -> Char -> Char) -> Text -> Text -> Text #

update :: Text -> (Int -> Char -> Char) -> Text #

lookupLT' :: Int -> Text -> Maybe (Int, Char) #

lookupGT' :: Int -> Text -> Maybe (Int, Char) #

lookupLE' :: Int -> Text -> Maybe (Int, Char) #

lookupGE' :: Int -> Text -> Maybe (Int, Char) #

keys :: Text -> [Int] #

(.$) :: (Char -> Bool) -> Text -> Maybe Int #

(*$) :: (Char -> Bool) -> Text -> [Int] #

kfoldr :: (Int -> Char -> b -> b) -> b -> Text -> b #

kfoldl :: (Int -> b -> Char -> b) -> b -> Text -> b #

kfoldr' :: (Int -> Char -> b -> b) -> b -> Text -> b #

kfoldl' :: (Int -> b -> Char -> b) -> b -> Text -> b #

MonadIO io => Thaw io Text (MIOBytes# io Char) Source # 
Instance details

Methods

thaw :: Text -> io (MIOBytes# io Char) #

unsafeThaw :: Text -> io (MIOBytes# io Char) #

MonadIO io => Freeze io (MIOBytes# io Char) Text Source # 
Instance details

Methods

freeze :: MIOBytes# io Char -> io Text #

unsafeFreeze :: MIOBytes# io Char -> io Text #

Thaw (ST s) Text (STBytes# s Char) Source # 
Instance details

Methods

thaw :: Text -> ST s (STBytes# s Char) #

unsafeThaw :: Text -> ST s (STBytes# s Char) #

Freeze (ST s) (STBytes# s Char) Text Source # 
Instance details