sdp4bytestring-0.2: SDP wrapper for ByteString.
Copyright(c) Andrey Mulik 2019
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilitynon-portable (GHC Extensions)
Safe HaskellTrustworthy
LanguageHaskell2010

SDP.ByteString.Lazy

Description

SDP.ByteString.Lazy provides sdp instances for lazy ByteString.

Synopsis

Exports

module SDP.Sort

ByteString

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A lazy ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Lazy.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Eq ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

NFData ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

rnf :: ByteString -> () #

Nullable ByteString Source # 
Instance details

Defined in SDP.ByteString.Lazy

Estimate ByteString Source # 
Instance details

Defined in SDP.ByteString.Lazy

IsFile ByteString Source # 
Instance details

Defined in SDP.ByteString.Lazy

Methods

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

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

IsTextFile ByteString Source # 
Instance details

Defined in SDP.ByteString.Lazy

Methods

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

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

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

Bordered ByteString Int Source # 
Instance details

Defined in SDP.ByteString.Lazy

Linear ByteString Word8 Source # 
Instance details

Defined in SDP.ByteString.Lazy

Methods

uncons :: ByteString -> (Word8, ByteString) #

uncons' :: ByteString -> Maybe (Word8, ByteString) #

toHead :: Word8 -> ByteString -> ByteString #

head :: ByteString -> Word8 #

tail :: ByteString -> ByteString #

unsnoc :: ByteString -> (ByteString, Word8) #

unsnoc' :: ByteString -> Maybe (ByteString, Word8) #

toLast :: ByteString -> Word8 -> ByteString #

init :: ByteString -> ByteString #

last :: ByteString -> Word8 #

single :: Word8 -> ByteString #

(++) :: ByteString -> ByteString -> ByteString #

replicate :: Int -> Word8 -> ByteString #

fromList :: [Word8] -> ByteString #

fromListN :: Int -> [Word8] -> ByteString #

listR :: ByteString -> [Word8] #

listL :: ByteString -> [Word8] #

fromFoldable :: Foldable f => f Word8 -> ByteString #

(!^) :: ByteString -> Int -> Word8 #

write :: ByteString -> Int -> Word8 -> ByteString #

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

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

intersperse :: Word8 -> ByteString -> ByteString #

filter :: (Word8 -> Bool) -> ByteString -> ByteString #

except :: (Word8 -> Bool) -> ByteString -> ByteString #

partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

partitions :: Foldable f => f (Word8 -> Bool) -> ByteString -> [ByteString] #

select :: (Word8 -> Maybe a) -> ByteString -> [a] #

select' :: (t Word8 ~ ByteString, Linear1 t a) => (Word8 -> Maybe a) -> ByteString -> t a #

extract :: (Word8 -> Maybe a) -> ByteString -> ([a], ByteString) #

extract' :: (t Word8 ~ ByteString, Linear1 t a) => (Word8 -> Maybe a) -> ByteString -> (t a, ByteString) #

selects :: Foldable f => f (Word8 -> Maybe a) -> ByteString -> ([[a]], ByteString) #

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

isSubseqOf :: ByteString -> ByteString -> Bool #

reverse :: ByteString -> ByteString #

force :: ByteString -> ByteString #

subsequences :: ByteString -> [ByteString] #

iterate :: Int -> (Word8 -> Word8) -> Word8 -> ByteString #

nub :: ByteString -> ByteString #

nubBy :: Equal Word8 -> ByteString -> ByteString #

ofoldr :: (Int -> Word8 -> b -> b) -> b -> ByteString -> b #

ofoldl :: (Int -> b -> Word8 -> b) -> b -> ByteString -> b #

ofoldr' :: (Int -> Word8 -> b -> b) -> b -> ByteString -> b #

ofoldl' :: (Int -> b -> Word8 -> b) -> b -> ByteString -> b #

o_foldr :: (Word8 -> b -> b) -> b -> ByteString -> b #

o_foldl :: (b -> Word8 -> b) -> b -> ByteString -> b #

o_foldr' :: (Word8 -> b -> b) -> b -> ByteString -> b #

o_foldl' :: (b -> Word8 -> b) -> b -> ByteString -> b #

Split ByteString Word8 Source # 
Instance details

Defined in SDP.ByteString.Lazy

Methods

take :: Int -> ByteString -> ByteString #

drop :: Int -> ByteString -> ByteString #

keep :: Int -> ByteString -> ByteString #

sans :: Int -> ByteString -> ByteString #

save :: Int -> ByteString -> ByteString #

skip :: Int -> ByteString -> ByteString #

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

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

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

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

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

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

splitBy :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

divideBy :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

splitsBy :: (Word8 -> Bool) -> ByteString -> [ByteString] #

splitsOn :: ByteString -> ByteString -> [ByteString] #

replaceBy :: ByteString -> ByteString -> ByteString -> ByteString #

removeAll :: ByteString -> ByteString -> ByteString #

combo :: Equal Word8 -> ByteString -> Int #

justifyL :: Int -> Word8 -> ByteString -> ByteString #

justifyR :: Int -> Word8 -> ByteString -> ByteString #

each :: Int -> ByteString -> ByteString #

eachFrom :: Int -> Int -> ByteString -> ByteString #

isPrefixOf :: ByteString -> ByteString -> Bool #

isSuffixOf :: ByteString -> ByteString -> Bool #

isInfixOf :: ByteString -> ByteString -> Bool #

prefix :: (Word8 -> Bool) -> ByteString -> Int #

suffix :: (Word8 -> Bool) -> ByteString -> Int #

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

dropSide :: (Word8 -> Bool) -> ByteString -> ByteString #

takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString #

dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString #

takeEnd :: (Word8 -> Bool) -> ByteString -> ByteString #

dropEnd :: (Word8 -> Bool) -> ByteString -> ByteString #

spanl :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

breakl :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

spanr :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

breakr :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

selectWhile :: (Word8 -> Maybe a) -> ByteString -> [a] #

selectEnd :: (Word8 -> Maybe a) -> ByteString -> [a] #

extractWhile :: (Word8 -> Maybe a) -> ByteString -> ([a], ByteString) #

extractEnd :: (Word8 -> Maybe a) -> ByteString -> (ByteString, [a]) #

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

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

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

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

Sort ByteString Word8 Source # 
Instance details

Defined in SDP.ByteString.Lazy

Indexed ByteString Int Word8 Source # 
Instance details

Defined in SDP.ByteString.Lazy

Methods

assoc :: (Int, Int) -> [(Int, Word8)] -> ByteString #

assoc' :: (Int, Int) -> Word8 -> [(Int, Word8)] -> ByteString #

fromIndexed :: Indexed m j Word8 => m -> ByteString #

write' :: ByteString -> Int -> Word8 -> ByteString #

accum :: (Word8 -> e' -> Word8) -> ByteString -> [(Int, e')] -> ByteString #

imap :: Map m j Word8 => (Int, Int) -> m -> (Int -> j) -> ByteString #

update' :: ByteString -> (Word8 -> Word8) -> Int -> ByteString #

updates' :: ByteString -> (Int -> Word8 -> Word8) -> ByteString #

Map ByteString Int Word8 Source # 
Instance details

Defined in SDP.ByteString.Lazy

MonadIO io => Thaw io ByteString (MIOUblist io Word8) Source # 
Instance details

Defined in SDP.ByteString.Lazy

Methods

thaw :: ByteString -> io (MIOUblist io Word8) #

unsafeThaw :: ByteString -> io (MIOUblist io Word8) #

MonadIO io => Freeze io (MIOUblist io Word8) ByteString Source # 
Instance details

Defined in SDP.ByteString.Lazy

Thaw (ST s) ByteString (STUblist s Word8) Source # 
Instance details

Defined in SDP.ByteString.Lazy

Freeze (ST s) (STUblist s Word8) ByteString Source # 
Instance details

Defined in SDP.ByteString.Lazy

type LByteString = ByteString Source #

Type synonym to avoid ambiguity.

fromStrict :: ByteString -> ByteString #

O(1) Convert a strict ByteString into a lazy ByteString.

toStrict :: ByteString -> ByteString #

O(n) Convert a lazy ByteString into a strict ByteString.

Note that this is an expensive operation that forces the whole lazy ByteString into memory and then copies all the data. If possible, try to avoid converting back and forth between strict and lazy bytestrings.

fromChunks :: [ByteString] -> ByteString #

O(c) Convert a list of strict ByteString into a lazy ByteString

toChunks :: ByteString -> [ByteString] #

O(c) Convert a lazy ByteString into a list of strict ByteString

Orphan instances

Nullable ByteString Source # 
Instance details

Estimate ByteString Source # 
Instance details

IsFile ByteString Source # 
Instance details

Methods

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

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

IsTextFile ByteString Source # 
Instance details

Methods

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

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

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

Bordered ByteString Int Source # 
Instance details

Linear ByteString Word8 Source # 
Instance details

Methods

uncons :: ByteString -> (Word8, ByteString) #

uncons' :: ByteString -> Maybe (Word8, ByteString) #

toHead :: Word8 -> ByteString -> ByteString #

head :: ByteString -> Word8 #

tail :: ByteString -> ByteString #

unsnoc :: ByteString -> (ByteString, Word8) #

unsnoc' :: ByteString -> Maybe (ByteString, Word8) #

toLast :: ByteString -> Word8 -> ByteString #

init :: ByteString -> ByteString #

last :: ByteString -> Word8 #

single :: Word8 -> ByteString #

(++) :: ByteString -> ByteString -> ByteString #

replicate :: Int -> Word8 -> ByteString #

fromList :: [Word8] -> ByteString #

fromListN :: Int -> [Word8] -> ByteString #

listR :: ByteString -> [Word8] #

listL :: ByteString -> [Word8] #

fromFoldable :: Foldable f => f Word8 -> ByteString #

(!^) :: ByteString -> Int -> Word8 #

write :: ByteString -> Int -> Word8 -> ByteString #

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

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

intersperse :: Word8 -> ByteString -> ByteString #

filter :: (Word8 -> Bool) -> ByteString -> ByteString #

except :: (Word8 -> Bool) -> ByteString -> ByteString #

partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

partitions :: Foldable f => f (Word8 -> Bool) -> ByteString -> [ByteString] #

select :: (Word8 -> Maybe a) -> ByteString -> [a] #

select' :: (t Word8 ~ ByteString, Linear1 t a) => (Word8 -> Maybe a) -> ByteString -> t a #

extract :: (Word8 -> Maybe a) -> ByteString -> ([a], ByteString) #

extract' :: (t Word8 ~ ByteString, Linear1 t a) => (Word8 -> Maybe a) -> ByteString -> (t a, ByteString) #

selects :: Foldable f => f (Word8 -> Maybe a) -> ByteString -> ([[a]], ByteString) #

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

isSubseqOf :: ByteString -> ByteString -> Bool #

reverse :: ByteString -> ByteString #

force :: ByteString -> ByteString #

subsequences :: ByteString -> [ByteString] #

iterate :: Int -> (Word8 -> Word8) -> Word8 -> ByteString #

nub :: ByteString -> ByteString #

nubBy :: Equal Word8 -> ByteString -> ByteString #

ofoldr :: (Int -> Word8 -> b -> b) -> b -> ByteString -> b #

ofoldl :: (Int -> b -> Word8 -> b) -> b -> ByteString -> b #

ofoldr' :: (Int -> Word8 -> b -> b) -> b -> ByteString -> b #

ofoldl' :: (Int -> b -> Word8 -> b) -> b -> ByteString -> b #

o_foldr :: (Word8 -> b -> b) -> b -> ByteString -> b #

o_foldl :: (b -> Word8 -> b) -> b -> ByteString -> b #

o_foldr' :: (Word8 -> b -> b) -> b -> ByteString -> b #

o_foldl' :: (b -> Word8 -> b) -> b -> ByteString -> b #

Split ByteString Word8 Source # 
Instance details

Methods

take :: Int -> ByteString -> ByteString #

drop :: Int -> ByteString -> ByteString #

keep :: Int -> ByteString -> ByteString #

sans :: Int -> ByteString -> ByteString #

save :: Int -> ByteString -> ByteString #

skip :: Int -> ByteString -> ByteString #

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

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

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

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

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

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

splitBy :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

divideBy :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

splitsBy :: (Word8 -> Bool) -> ByteString -> [ByteString] #

splitsOn :: ByteString -> ByteString -> [ByteString] #

replaceBy :: ByteString -> ByteString -> ByteString -> ByteString #

removeAll :: ByteString -> ByteString -> ByteString #

combo :: Equal Word8 -> ByteString -> Int #

justifyL :: Int -> Word8 -> ByteString -> ByteString #

justifyR :: Int -> Word8 -> ByteString -> ByteString #

each :: Int -> ByteString -> ByteString #

eachFrom :: Int -> Int -> ByteString -> ByteString #

isPrefixOf :: ByteString -> ByteString -> Bool #

isSuffixOf :: ByteString -> ByteString -> Bool #

isInfixOf :: ByteString -> ByteString -> Bool #

prefix :: (Word8 -> Bool) -> ByteString -> Int #

suffix :: (Word8 -> Bool) -> ByteString -> Int #

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

dropSide :: (Word8 -> Bool) -> ByteString -> ByteString #

takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString #

dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString #

takeEnd :: (Word8 -> Bool) -> ByteString -> ByteString #

dropEnd :: (Word8 -> Bool) -> ByteString -> ByteString #

spanl :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

breakl :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

spanr :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

breakr :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) #

selectWhile :: (Word8 -> Maybe a) -> ByteString -> [a] #

selectEnd :: (Word8 -> Maybe a) -> ByteString -> [a] #

extractWhile :: (Word8 -> Maybe a) -> ByteString -> ([a], ByteString) #

extractEnd :: (Word8 -> Maybe a) -> ByteString -> (ByteString, [a]) #

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

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

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

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

Sort ByteString Word8 Source # 
Instance details

Indexed ByteString Int Word8 Source # 
Instance details

Methods

assoc :: (Int, Int) -> [(Int, Word8)] -> ByteString #

assoc' :: (Int, Int) -> Word8 -> [(Int, Word8)] -> ByteString #

fromIndexed :: Indexed m j Word8 => m -> ByteString #

write' :: ByteString -> Int -> Word8 -> ByteString #

accum :: (Word8 -> e' -> Word8) -> ByteString -> [(Int, e')] -> ByteString #

imap :: Map m j Word8 => (Int, Int) -> m -> (Int -> j) -> ByteString #

update' :: ByteString -> (Word8 -> Word8) -> Int -> ByteString #

updates' :: ByteString -> (Int -> Word8 -> Word8) -> ByteString #

Map ByteString Int Word8 Source # 
Instance details

MonadIO io => Thaw io ByteString (MIOUblist io Word8) Source # 
Instance details

Methods

thaw :: ByteString -> io (MIOUblist io Word8) #

unsafeThaw :: ByteString -> io (MIOUblist io Word8) #

MonadIO io => Freeze io (MIOUblist io Word8) ByteString Source # 
Instance details

Thaw (ST s) ByteString (STUblist s Word8) Source # 
Instance details

Freeze (ST s) (STUblist s Word8) ByteString Source # 
Instance details