{-# LANGUAGE Trustworthy, MagicHash, MultiParamTypeClasses, FlexibleInstances #-}
module SDP.ByteString.Lazy
(
module System.IO.Classes,
module SDP.Indexed,
module SDP.Sort,
ByteString, LByteString, B.fromStrict, B.toStrict, B.fromChunks, B.toChunks
)
where
import Prelude ()
import SDP.SafePrelude
import SDP.Templates.AnyChunks
import SDP.ByteList.IOUblist
import SDP.ByteList.STUblist
import SDP.ByteList.ST
import SDP.SortM.Tim
import SDP.Indexed
import SDP.Sort
import Data.ByteString.Lazy.Internal ( ByteString (..) )
import qualified Data.ByteString.Lazy as B
import qualified SDP.ByteString as S
import Data.Foldable as F ( foldrM )
import Data.Maybe
import Control.Exception.SDP
import System.IO.Classes
default ()
type LByteString = ByteString
instance Bordered ByteString Int
where
lower :: ByteString -> Int
lower = Int -> ByteString -> Int
forall a b. a -> b -> a
const Int
0
sizeOf :: ByteString -> Int
sizeOf = Int64 -> Int
forall a. Enum a => a -> Int
fromEnum (Int64 -> Int) -> (ByteString -> Int64) -> ByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int64
B.length
upper :: ByteString -> Int
upper ByteString
bs = ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
bounds :: ByteString -> (Int, Int)
bounds ByteString
bs = (Int
0, ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
indices :: ByteString -> [Int]
indices ByteString
bs = [Int
0 .. ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
bs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
indexIn :: ByteString -> Int -> Bool
indexIn ByteString
bs = \ Int
i -> Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
bs
instance Linear ByteString Word8
where
replicate :: Int -> Word8 -> ByteString
replicate = Int64 -> Word8 -> ByteString
B.replicate (Int64 -> Word8 -> ByteString)
-> (Int -> Int64) -> Int -> Word8 -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum
concat :: f ByteString -> ByteString
concat = [ByteString] -> ByteString
B.concat ([ByteString] -> ByteString)
-> (f ByteString -> [ByteString]) -> f ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f ByteString -> [ByteString]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
fromList :: [Word8] -> ByteString
fromList = [Word8] -> ByteString
B.pack
intersperse :: Word8 -> ByteString -> ByteString
intersperse = Word8 -> ByteString -> ByteString
B.intersperse
filter :: (Word8 -> Bool) -> ByteString -> ByteString
filter = (Word8 -> Bool) -> ByteString -> ByteString
B.filter
listR :: ByteString -> [Word8]
listR = \ ByteString
bs -> let n :: Int
n = ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
bs in (ByteString
bs ByteString -> Int -> Word8
forall map key e. Map map key e => map -> key -> e
.!) (Int -> Word8) -> [Int] -> [Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1, Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2 .. Int
0]
single :: Word8 -> ByteString
single = Word8 -> ByteString
B.singleton
listL :: ByteString -> [Word8]
listL = ByteString -> [Word8]
B.unpack
++ :: ByteString -> ByteString -> ByteString
(++) = ByteString -> ByteString -> ByteString
B.append
!^ :: ByteString -> Int -> Word8
(!^) ByteString
es = ByteString -> Int64 -> Word8
B.index ByteString
es (Int64 -> Word8) -> (Int -> Int64) -> Int -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum
write :: ByteString -> Int -> Word8 -> ByteString
write ByteString
bs = (ByteString
bs ByteString -> [(Int, Word8)] -> ByteString
forall map key e. Map map key e => map -> [(key, e)] -> map
//) ([(Int, Word8)] -> ByteString)
-> ((Int, Word8) -> [(Int, Word8)]) -> (Int, Word8) -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Word8) -> [(Int, Word8)]
forall l e. Linear l e => e -> l
single ((Int, Word8) -> ByteString)
-> (Int -> Word8 -> (Int, Word8)) -> Int -> Word8 -> ByteString
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
... (,)
uncons' :: ByteString -> Maybe (Word8, ByteString)
uncons' = ByteString -> Maybe (Word8, ByteString)
B.uncons
unsnoc' :: ByteString -> Maybe (ByteString, Word8)
unsnoc' = ByteString -> Maybe (ByteString, Word8)
B.unsnoc
uncons :: ByteString -> (Word8, ByteString)
uncons = (Word8, ByteString)
-> Maybe (Word8, ByteString) -> (Word8, ByteString)
forall a. a -> Maybe a -> a
fromMaybe (String -> (Word8, ByteString)
forall a. String -> a
pfailEx String
"uncons") (Maybe (Word8, ByteString) -> (Word8, ByteString))
-> (ByteString -> Maybe (Word8, ByteString))
-> ByteString
-> (Word8, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (Word8, ByteString)
B.uncons
unsnoc :: ByteString -> (ByteString, Word8)
unsnoc = (ByteString, Word8)
-> Maybe (ByteString, Word8) -> (ByteString, Word8)
forall a. a -> Maybe a -> a
fromMaybe (String -> (ByteString, Word8)
forall a. String -> a
pfailEx String
"unsnoc") (Maybe (ByteString, Word8) -> (ByteString, Word8))
-> (ByteString -> Maybe (ByteString, Word8))
-> ByteString
-> (ByteString, Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe (ByteString, Word8)
B.unsnoc
toHead :: Word8 -> ByteString -> ByteString
toHead = Word8 -> ByteString -> ByteString
B.cons
toLast :: ByteString -> Word8 -> ByteString
toLast = ByteString -> Word8 -> ByteString
B.snoc
force :: ByteString -> ByteString
force = ByteString -> ByteString
B.copy
head :: ByteString -> Word8
head = ByteString -> Word8
B.head
tail :: ByteString -> ByteString
tail = ByteString -> ByteString
B.tail
last :: ByteString -> Word8
last = ByteString -> Word8
B.last
init :: ByteString -> ByteString
init = ByteString -> ByteString
B.init
partitions :: f (Word8 -> Bool) -> ByteString -> [ByteString]
partitions f (Word8 -> Bool)
is ByteString
bs = ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map [Word8] -> ByteString
forall l e. Linear l e => [e] -> l
fromList ([[Word8]] -> [ByteString])
-> ([Word8] -> [[Word8]]) -> [Word8] -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f (Word8 -> Bool) -> [Word8] -> [[Word8]]
forall l e (f :: * -> *).
(Linear l e, Foldable f) =>
f (e -> Bool) -> l -> [l]
partitions f (Word8 -> Bool)
is ([Word8] -> [ByteString]) -> [Word8] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ ByteString -> [Word8]
forall l e. Linear l e => l -> [e]
listL ByteString
bs
isSubseqOf :: ByteString -> ByteString -> Bool
isSubseqOf ByteString
xs ByteString
ys = (Word8 -> Bool) -> ByteString -> Bool
B.all (Word8 -> ByteString -> Bool
`B.elem` ByteString
ys) ByteString
xs
nub :: ByteString -> ByteString
nub ByteString
bs = (forall s. ST s ByteString) -> ByteString
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ByteString) -> ByteString)
-> (forall s. ST s ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ do
AnyBorder (STUblist s) Word8 Bool
hs <- Int -> Bool -> ST s (AnyBorder (STUblist s) Word8 Bool)
forall (m :: * -> *) l e. LinearM m l e => Int -> e -> m l
filled Int
256 Bool
False
(Word8 -> ST s () -> ST s ()) -> ST s () -> ByteString -> ST s ()
forall b. (Word8 -> b -> b) -> b -> ByteString -> b
B.foldr (\ Word8
b ST s ()
io -> AnyBorder (STUblist s) Word8 Bool -> Word8 -> Bool -> ST s ()
forall (m :: * -> *) v i e. IndexedM m v i e => v -> i -> e -> m ()
writeM' AnyBorder (STUblist s) Word8 Bool
hs Word8
b Bool
True ST s () -> ST s () -> ST s ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ST s ()
io) (() -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) ByteString
bs
AnyBorder (STUblist s) Word8 Bool -> ST s ByteString
forall s. STByteList s Word8 Bool -> ST s ByteString
done' AnyBorder (STUblist s) Word8 Bool
hs
where
done' :: STByteList s Word8 Bool -> ST s ByteString
done' :: STByteList s Word8 Bool -> ST s ByteString
done' = ([Word8] -> ByteString) -> ST s [Word8] -> ST s ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Word8] -> ByteString
forall l e. Linear l e => [e] -> l
fromList (ST s [Word8] -> ST s ByteString)
-> (STByteList s Word8 Bool -> ST s [Word8])
-> STByteList s Word8 Bool
-> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Bool -> [Word8] -> ST s [Word8])
-> [Word8] -> STByteList s Word8 Bool -> ST s [Word8]
forall (m :: * -> *) map key e acc.
MapM m map key e =>
(key -> e -> acc -> m acc) -> acc -> map -> m acc
kfoldrM (\ Word8
i Bool
b [Word8]
is -> [Word8] -> ST s [Word8]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Word8] -> ST s [Word8]) -> [Word8] -> ST s [Word8]
forall a b. (a -> b) -> a -> b
$ Bool
b Bool -> [Word8] -> [Word8] -> [Word8]
forall a. Bool -> a -> a -> a
? (Word8
i Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: [Word8]
is) ([Word8] -> [Word8]) -> [Word8] -> [Word8]
forall a b. (a -> b) -> a -> b
$ [Word8]
is) []
nubBy :: Equal Word8 -> ByteString -> ByteString
nubBy Equal Word8
f = [Word8] -> ByteString
forall l e. Linear l e => [e] -> l
fromList ([Word8] -> ByteString)
-> (ByteString -> [Word8]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> [Word8] -> [Word8]) -> [Word8] -> ByteString -> [Word8]
forall b. (Word8 -> b -> b) -> b -> ByteString -> b
B.foldr (\ Word8
b [Word8]
es -> (Word8 -> Bool) -> [Word8] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Equal Word8
f Word8
b) [Word8]
es Bool -> [Word8] -> [Word8] -> [Word8]
forall a. Bool -> a -> a -> a
? [Word8]
es ([Word8] -> [Word8]) -> [Word8] -> [Word8]
forall a b. (a -> b) -> a -> b
$ (Word8
b Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: [Word8]
es)) [] (ByteString -> [Word8])
-> (ByteString -> ByteString) -> ByteString -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
forall l e. (Linear l e, Eq e) => l -> l
nub
ofoldr :: (Int -> Word8 -> b -> b) -> b -> ByteString -> b
ofoldr Int -> Word8 -> b -> b
f = \ b
base ByteString
bs ->
let n :: Int
n = ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
bs; go :: Int -> b
go Int
i = Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i Bool -> b -> b -> b
forall a. Bool -> a -> a -> a
? b
base (b -> b) -> b -> b
forall a b. (a -> b) -> a -> b
$ Int -> Word8 -> b -> b
f Int
i (ByteString
bs ByteString -> Int -> Word8
forall l e. Linear l e => l -> Int -> e
!^ Int
i) (Int -> b
go (Int -> b) -> Int -> b
forall a b. (a -> b) -> a -> b
$ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
in Int -> b
go Int
0
ofoldl :: (Int -> b -> Word8 -> b) -> b -> ByteString -> b
ofoldl Int -> b -> Word8 -> b
f = \ b
base ByteString
bs ->
let go :: Int -> b
go Int
i = -Int
1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i Bool -> b -> b -> b
forall a. Bool -> a -> a -> a
? b
base (b -> b) -> b -> b
forall a b. (a -> b) -> a -> b
$ Int -> b -> Word8 -> b
f Int
i (Int -> b
go (Int -> b) -> Int -> b
forall a b. (a -> b) -> a -> b
$ Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (ByteString
bs ByteString -> Int -> Word8
forall l e. Linear l e => l -> Int -> e
!^ Int
i)
in Int -> b
go (ByteString -> Int
forall b i. Bordered b i => b -> i
upper ByteString
bs)
o_foldr :: (Word8 -> b -> b) -> b -> ByteString -> b
o_foldr = (Word8 -> b -> b) -> b -> ByteString -> b
forall b. (Word8 -> b -> b) -> b -> ByteString -> b
B.foldr
o_foldl :: (b -> Word8 -> b) -> b -> ByteString -> b
o_foldl = (b -> Word8 -> b) -> b -> ByteString -> b
forall b. (b -> Word8 -> b) -> b -> ByteString -> b
B.foldl
instance Split ByteString Word8
where
take :: Int -> ByteString -> ByteString
take = Int64 -> ByteString -> ByteString
B.take (Int64 -> ByteString -> ByteString)
-> (Int -> Int64) -> Int -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum
drop :: Int -> ByteString -> ByteString
drop = Int64 -> ByteString -> ByteString
B.drop (Int64 -> ByteString -> ByteString)
-> (Int -> Int64) -> Int -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum
split :: Int -> ByteString -> (ByteString, ByteString)
split = Int64 -> ByteString -> (ByteString, ByteString)
B.splitAt (Int64 -> ByteString -> (ByteString, ByteString))
-> (Int -> Int64) -> Int -> ByteString -> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum
isPrefixOf :: ByteString -> ByteString -> Bool
isPrefixOf = ByteString -> ByteString -> Bool
B.isPrefixOf
isSuffixOf :: ByteString -> ByteString -> Bool
isSuffixOf = ByteString -> ByteString -> Bool
B.isSuffixOf
isInfixOf :: ByteString -> ByteString -> Bool
isInfixOf = ([Word8] -> [Word8] -> Bool)
-> (ByteString -> [Word8]) -> ByteString -> ByteString -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on [Word8] -> [Word8] -> Bool
forall s e. (Split s e, Eq e) => s -> s -> Bool
isInfixOf ByteString -> [Word8]
forall l e. Linear l e => l -> [e]
listL
takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhile = (Word8 -> Bool) -> ByteString -> ByteString
B.takeWhile
dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile = (Word8 -> Bool) -> ByteString -> ByteString
B.dropWhile
spanl :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanl = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
B.span
breakl :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
breakl = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
B.break
prefix :: (Word8 -> Bool) -> ByteString -> Int
prefix Word8 -> Bool
p = (Word8 -> Int -> Int) -> Int -> ByteString -> Int
forall b. (Word8 -> b -> b) -> b -> ByteString -> b
B.foldr (\ Word8
e Int
c -> Word8 -> Bool
p Word8
e Bool -> Int -> Int -> Int
forall a. Bool -> a -> a -> a
? Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
0) Int
0
suffix :: (Word8 -> Bool) -> ByteString -> Int
suffix Word8 -> Bool
p = (Int -> Word8 -> Int) -> Int -> ByteString -> Int
forall b. (b -> Word8 -> b) -> b -> ByteString -> b
B.foldl (\ Int
c Word8
e -> Word8 -> Bool
p Word8
e Bool -> Int -> Int -> Int
forall a. Bool -> a -> a -> a
? Int
c Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
0) Int
0
instance Map ByteString Int Word8
where
toMap :: [(Int, Word8)] -> ByteString
toMap = Word8 -> [(Int, Word8)] -> ByteString
forall map key e. Map map key e => e -> [(key, e)] -> map
toMap' Word8
0
toMap' :: Word8 -> [(Int, Word8)] -> ByteString
toMap' Word8
defvalue [(Int, Word8)]
ascs = [(Int, Word8)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, Word8)]
ascs Bool -> ByteString -> ByteString -> ByteString
forall a. Bool -> a -> a -> a
? ByteString
forall e. Nullable e => e
Z (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Word8 -> [(Int, Word8)] -> ByteString
forall v i e. Indexed v i e => (i, i) -> e -> [(i, e)] -> v
assoc' ([(Int, Word8)] -> (Int, Int)
forall a b. Ord a => [(a, b)] -> (a, a)
ascsBounds [(Int, Word8)]
ascs) Word8
defvalue [(Int, Word8)]
ascs
.! :: ByteString -> Int -> Word8
(.!) ByteString
es = ByteString -> Int64 -> Word8
B.index ByteString
es (Int64 -> Word8) -> (Int -> Int64) -> Int -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int64
forall a. Enum a => Int -> a
toEnum
ByteString
Z // :: ByteString -> [(Int, Word8)] -> ByteString
// [(Int, Word8)]
ascs = [(Int, Word8)] -> ByteString
forall map key e. Map map key e => [(key, e)] -> map
toMap [(Int, Word8)]
ascs
ByteString
es // [(Int, Word8)]
ascs = (Int, Int) -> [(Int, Word8)] -> ByteString
forall v i e. Indexed v i e => (i, i) -> [(i, e)] -> v
assoc (ByteString -> (Int, Int)
forall b i. Bordered b i => b -> (i, i)
bounds ByteString
es) (ByteString -> [(Int, Word8)]
forall map key e. Map map key e => map -> [(key, e)]
assocs ByteString
es [(Int, Word8)] -> [(Int, Word8)] -> [(Int, Word8)]
forall l e. Linear l e => l -> l -> l
++ [(Int, Word8)]
ascs)
.$ :: (Word8 -> Bool) -> ByteString -> Maybe Int
(.$) = (Int64 -> Int) -> Maybe Int64 -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Int
forall a. Enum a => a -> Int
fromEnum (Maybe Int64 -> Maybe Int)
-> ((Word8 -> Bool) -> ByteString -> Maybe Int64)
-> (Word8 -> Bool)
-> ByteString
-> Maybe Int
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
... (Word8 -> Bool) -> ByteString -> Maybe Int64
B.findIndex
*$ :: (Word8 -> Bool) -> ByteString -> [Int]
(*$) = (Int64 -> Int) -> [Int64] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Int
forall a. Enum a => a -> Int
fromEnum ([Int64] -> [Int])
-> ((Word8 -> Bool) -> ByteString -> [Int64])
-> (Word8 -> Bool)
-> ByteString
-> [Int]
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
... (Word8 -> Bool) -> ByteString -> [Int64]
B.findIndices
kfoldr :: (Int -> Word8 -> b -> b) -> b -> ByteString -> b
kfoldr = (Int -> Word8 -> b -> b) -> b -> ByteString -> b
forall l e b. Linear l e => (Int -> e -> b -> b) -> b -> l -> b
ofoldr
kfoldl :: (Int -> b -> Word8 -> b) -> b -> ByteString -> b
kfoldl = (Int -> b -> Word8 -> b) -> b -> ByteString -> b
forall l e b. Linear l e => (Int -> b -> e -> b) -> b -> l -> b
ofoldl
instance Indexed ByteString Int Word8
where
assoc :: (Int, Int) -> [(Int, Word8)] -> ByteString
assoc = ((Int, Int) -> Word8 -> [(Int, Word8)] -> ByteString)
-> Word8 -> (Int, Int) -> [(Int, Word8)] -> ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int, Int) -> Word8 -> [(Int, Word8)] -> ByteString
forall v i e. Indexed v i e => (i, i) -> e -> [(i, e)] -> v
assoc' Word8
0
assoc' :: (Int, Int) -> Word8 -> [(Int, Word8)] -> ByteString
assoc' bnds :: (Int, Int)
bnds@(Int
l, Int
_) Word8
defvalue [(Int, Word8)]
ascs = [ByteString] -> ByteString
B.fromChunks ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$
Int -> [(Int, Word8)] -> [ByteString]
go Int
l [ ((Int, Int) -> Int -> Int
forall i. Index i => (i, i) -> i -> Int
offset (Int, Int)
bnds Int
i, Word8
e) | (Int
i, Word8
e) <- [(Int, Word8)]
ascs, (Int, Int) -> Int -> Bool
forall i. Index i => (i, i) -> i -> Bool
inRange (Int, Int)
bnds Int
i ]
where
go :: Int -> [(Int, Word8)] -> [S.ByteString]
go :: Int -> [(Int, Word8)] -> [ByteString]
go Int
_ [] = []
go Int
cl [(Int, Word8)]
ies' = ByteString
chunk ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: Int -> [(Int, Word8)] -> [ByteString]
go Int
nl [(Int, Word8)]
rest
where
chunk :: ByteString
chunk = [Word8] -> ByteString
forall l e. Linear l e => [e] -> l
fromList ([Word8] -> ByteString) -> [Word8] -> ByteString
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Word8 -> [(Int, Word8)] -> [Word8]
forall v i e. Indexed v i e => (i, i) -> e -> [(i, e)] -> v
assoc' (Int
cl, Int
nl Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Word8
defvalue [(Int, Word8)]
ch
([(Int, Word8)]
ch, [(Int, Word8)]
rest) = ((Int, Word8) -> Bool)
-> [(Int, Word8)] -> ([(Int, Word8)], [(Int, Word8)])
forall l e. Linear l e => (e -> Bool) -> l -> (l, l)
partition (\ (Int
i, Word8
_) -> Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
nl) [(Int, Word8)]
ies'
nl :: Int
nl = Int
cl Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lim
fromIndexed :: m -> ByteString
fromIndexed m
es = (Int, Int) -> [(Int, Word8)] -> ByteString
forall v i e. Indexed v i e => (i, i) -> [(i, e)] -> v
assoc (Int, Int)
bnds' [ ((j, j) -> j -> Int
forall i. Index i => (i, i) -> i -> Int
offset (j, j)
bnds j
i, Word8
e) | (j
i, Word8
e) <- m -> [(j, Word8)]
forall map key e. Map map key e => map -> [(key, e)]
assocs m
es ]
where
bnds' :: (Int, Int)
bnds' = Int -> (Int, Int)
forall i. Index i => Int -> (i, i)
defaultBounds (m -> Int
forall b i. Bordered b i => b -> Int
sizeOf m
es)
bnds :: (j, j)
bnds = m -> (j, j)
forall b i. Bordered b i => b -> (i, i)
bounds m
es
instance Sort ByteString Word8
where
sortBy :: Compare Word8 -> ByteString -> ByteString
sortBy Compare Word8
f ByteString
bs = (forall s. ST s ByteString) -> ByteString
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ByteString) -> ByteString)
-> (forall s. ST s ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ do AnyChunks (STBytes# s) Word8
es' <- ByteString -> ST s (AnyChunks (STBytes# s) Word8)
forall (m :: * -> *) v v'. Thaw m v v' => v -> m v'
thaw ByteString
bs; Compare Word8 -> AnyChunks (STBytes# s) Word8 -> ST s ()
forall (m :: * -> *) v e i.
(LinearM m v e, BorderedM m v i) =>
Compare e -> v -> m ()
timSortBy Compare Word8
f AnyChunks (STBytes# s) Word8
es'; AnyChunks (STBytes# s) Word8 -> ST s ByteString
forall s. STUblist s Word8 -> ST s ByteString
done AnyChunks (STBytes# s) Word8
es'
sortedBy :: Equal Word8 -> ByteString -> Bool
sortedBy Equal Word8
_ ByteString
Empty = Bool
True
sortedBy Equal Word8
f (Chunk ByteString
ch ByteString
Z) = Equal Word8 -> ByteString -> Bool
forall s e. Sort s e => (e -> e -> Bool) -> s -> Bool
sortedBy Equal Word8
f ByteString
ch
sortedBy Equal Word8
f (Chunk ByteString
Z ByteString
chs) = Equal Word8 -> ByteString -> Bool
forall s e. Sort s e => (e -> e -> Bool) -> s -> Bool
sortedBy Equal Word8
f ByteString
chs
sortedBy Equal Word8
f (Chunk ByteString
ch ByteString
chs) = Equal Word8 -> ByteString -> Bool
forall s e. Sort s e => (e -> e -> Bool) -> s -> Bool
sortedBy Equal Word8
f ByteString
ch Bool -> Bool -> Bool
&& ByteString -> Word8
forall l e. Linear l e => l -> e
last ByteString
ch Equal Word8
`f` ByteString -> Word8
forall l e. Linear l e => l -> e
head ByteString
chs Bool -> Bool -> Bool
&& Equal Word8 -> ByteString -> Bool
forall s e. Sort s e => (e -> e -> Bool) -> s -> Bool
sortedBy Equal Word8
f ByteString
chs
instance Thaw (ST s) ByteString (STUblist s Word8)
where
thaw :: ByteString -> ST s (STUblist s Word8)
thaw = [STBytes# s Word8] -> ST s (STUblist s Word8)
forall (m :: * -> *) (rep :: * -> *) e.
BorderedM1 m rep Int e =>
[rep e] -> m (AnyChunks rep e)
fromChunksM ([STBytes# s Word8] -> ST s (STUblist s Word8))
-> (ByteString -> ST s [STBytes# s Word8])
-> ByteString
-> ST s (STUblist s Word8)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (ByteString -> ST s [STBytes# s Word8] -> ST s [STBytes# s Word8])
-> ST s [STBytes# s Word8] -> ByteString -> ST s [STBytes# s Word8]
forall a. (ByteString -> a -> a) -> a -> ByteString -> a
B.foldrChunks ((STBytes# s Word8 -> [STBytes# s Word8] -> [STBytes# s Word8])
-> ST s (STBytes# s Word8)
-> ST s [STBytes# s Word8]
-> ST s [STBytes# s Word8]
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) (ST s (STBytes# s Word8)
-> ST s [STBytes# s Word8] -> ST s [STBytes# s Word8])
-> (ByteString -> ST s (STBytes# s Word8))
-> ByteString
-> ST s [STBytes# s Word8]
-> ST s [STBytes# s Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ST s (STBytes# s Word8)
forall (m :: * -> *) v v'. Thaw m v v' => v -> m v'
thaw) ([STBytes# s Word8] -> ST s [STBytes# s Word8]
forall (m :: * -> *) a. Monad m => a -> m a
return [])
instance Freeze (ST s) (STUblist s Word8) ByteString
where
freeze :: STUblist s Word8 -> ST s ByteString
freeze = (STBytes# s Word8 -> ByteString -> ST s ByteString)
-> ByteString -> [STBytes# s Word8] -> ST s ByteString
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> b -> m b) -> b -> t a -> m b
F.foldrM (\ STBytes# s Word8
e ByteString
rs -> (ByteString -> ByteString -> ByteString
`Chunk` ByteString
rs) (ByteString -> ByteString) -> ST s ByteString -> ST s ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> STBytes# s Word8 -> ST s ByteString
forall (m :: * -> *) v' v. Freeze m v' v => v' -> m v
freeze STBytes# s Word8
e) ByteString
Empty ([STBytes# s Word8] -> ST s ByteString)
-> (STUblist s Word8 -> [STBytes# s Word8])
-> STUblist s Word8
-> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STUblist s Word8 -> [STBytes# s Word8]
forall (rep :: * -> *) e. AnyChunks rep e -> [rep e]
toChunks
instance (MonadIO io) => Thaw io ByteString (MIOUblist io Word8)
where
thaw :: ByteString -> io (MIOUblist io Word8)
thaw = [MIOBytes# io Word8] -> io (MIOUblist io Word8)
forall (m :: * -> *) (rep :: * -> *) e.
BorderedM1 m rep Int e =>
[rep e] -> m (AnyChunks rep e)
fromChunksM ([MIOBytes# io Word8] -> io (MIOUblist io Word8))
-> (ByteString -> io [MIOBytes# io Word8])
-> ByteString
-> io (MIOUblist io Word8)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (ByteString -> io [MIOBytes# io Word8] -> io [MIOBytes# io Word8])
-> io [MIOBytes# io Word8] -> ByteString -> io [MIOBytes# io Word8]
forall a. (ByteString -> a -> a) -> a -> ByteString -> a
B.foldrChunks ((MIOBytes# io Word8
-> [MIOBytes# io Word8] -> [MIOBytes# io Word8])
-> io (MIOBytes# io Word8)
-> io [MIOBytes# io Word8]
-> io [MIOBytes# io Word8]
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:) (io (MIOBytes# io Word8)
-> io [MIOBytes# io Word8] -> io [MIOBytes# io Word8])
-> (ByteString -> io (MIOBytes# io Word8))
-> ByteString
-> io [MIOBytes# io Word8]
-> io [MIOBytes# io Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> io (MIOBytes# io Word8)
forall (m :: * -> *) v v'. Thaw m v v' => v -> m v'
thaw) ([MIOBytes# io Word8] -> io [MIOBytes# io Word8]
forall (m :: * -> *) a. Monad m => a -> m a
return [])
instance (MonadIO io) => Freeze io (MIOUblist io Word8) ByteString
where
freeze :: MIOUblist io Word8 -> io ByteString
freeze = (MIOBytes# io Word8 -> ByteString -> io ByteString)
-> ByteString -> [MIOBytes# io Word8] -> io ByteString
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> b -> m b) -> b -> t a -> m b
F.foldrM (\ MIOBytes# io Word8
e ByteString
rs -> (ByteString -> ByteString -> ByteString
`Chunk` ByteString
rs) (ByteString -> ByteString) -> io ByteString -> io ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MIOBytes# io Word8 -> io ByteString
forall (m :: * -> *) v' v. Freeze m v' v => v' -> m v
freeze MIOBytes# io Word8
e) ByteString
Empty ([MIOBytes# io Word8] -> io ByteString)
-> (MIOUblist io Word8 -> [MIOBytes# io Word8])
-> MIOUblist io Word8
-> io ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MIOUblist io Word8 -> [MIOBytes# io Word8]
forall (rep :: * -> *) e. AnyChunks rep e -> [rep e]
toChunks
instance Nullable ByteString
where
lzero :: ByteString
lzero = ByteString
B.empty
isNull :: ByteString -> Bool
isNull = ByteString -> Bool
B.null
instance Estimate ByteString
where
<==> :: Compare ByteString
(<==>) = Int -> Compare ByteString
go Int
0
where
go :: Int -> Compare ByteString
go Int
o ByteString
Empty ByteString
Empty = Int
o Compare Int
forall o. Ord o => Compare o
<=> Int
0
go Int
o ByteString
xs ByteString
Empty = ByteString
xs ByteString -> Int -> Ordering
forall e. Estimate e => e -> Int -> Ordering
<.=> (-Int
o)
go Int
o ByteString
Empty ByteString
ys = Int
o Int -> ByteString -> Ordering
forall e. Estimate e => Int -> e -> Ordering
<=.> ByteString
ys
go Int
o (Chunk ByteString
ch1 ByteString
chs1) (Chunk ByteString
ch2 ByteString
chs2) =
Int -> Compare ByteString
go (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
ch1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
ch2) ByteString
chs1 ByteString
chs2
ByteString
Empty <.=> :: ByteString -> Int -> Ordering
<.=> Int
n = Int
0 Compare Int
forall o. Ord o => Compare o
<=> Int
n
(Chunk ByteString
ch ByteString
chs) <.=> Int
n = ByteString
ch ByteString -> Int -> Bool
forall e. Estimate e => e -> Int -> Bool
.> Int
n Bool -> Ordering -> Ordering -> Ordering
forall a. Bool -> a -> a -> a
? Ordering
GT (Ordering -> Ordering) -> Ordering -> Ordering
forall a b. (a -> b) -> a -> b
$ ByteString
chs ByteString -> Int -> Ordering
forall e. Estimate e => e -> Int -> Ordering
<.=> (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- ByteString -> Int
forall b i. Bordered b i => b -> Int
sizeOf ByteString
ch)
instance IsFile ByteString
where
hGetContents :: Handle -> io ByteString
hGetContents = IO ByteString -> io ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> io ByteString)
-> (Handle -> IO ByteString) -> Handle -> io ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO ByteString
B.hGetContents
hPutContents :: Handle -> ByteString -> io ()
hPutContents = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (Handle -> ByteString -> IO ()) -> Handle -> ByteString -> io ()
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
... Handle -> ByteString -> IO ()
B.hPut
instance IsTextFile ByteString
where
hPutStrLn :: Handle -> ByteString -> io ()
hPutStrLn Handle
h = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> (ByteString -> IO ()) -> ByteString -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> Char -> IO ()
forall (io :: * -> *). MonadIO io => Handle -> Char -> io ()
hPutChar Handle
h Char
'\n') (IO () -> IO ()) -> (ByteString -> IO ()) -> ByteString -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> ByteString -> IO ()
forall text (io :: * -> *).
(IsTextFile text, MonadIO io) =>
Handle -> text -> io ()
hPutStr Handle
h
hGetLine :: Handle -> io ByteString
hGetLine = IO ByteString -> io ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> io ByteString)
-> (Handle -> IO ByteString) -> Handle -> io ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> ByteString
B.fromStrict (IO ByteString -> IO ByteString)
-> (Handle -> IO ByteString) -> Handle -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO ByteString
forall text (io :: * -> *).
(IsTextFile text, MonadIO io) =>
Handle -> io text
S.hGetLine
hPutStr :: Handle -> ByteString -> io ()
hPutStr = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (Handle -> ByteString -> IO ()) -> Handle -> ByteString -> io ()
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
... Handle -> ByteString -> IO ()
B.hPut
ascsBounds :: (Ord a) => [(a, b)] -> (a, a)
ascsBounds :: [(a, b)] -> (a, a)
ascsBounds = \ ((a
x, b
_) : [(a, b)]
xs) -> ((a, b) -> (a, a) -> (a, a)) -> (a, a) -> [(a, b)] -> (a, a)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\ (a
e, b
_) (a
mn, a
mx) -> (a -> a -> a
forall a. Ord a => a -> a -> a
min a
mn a
e, a -> a -> a
forall a. Ord a => a -> a -> a
max a
mx a
e)) (a
x, a
x) [(a, b)]
xs
done :: STUblist s Word8 -> ST s ByteString
done :: STUblist s Word8 -> ST s ByteString
done = STUblist s Word8 -> ST s ByteString
forall (m :: * -> *) v' v. Freeze m v' v => v' -> m v
freeze
pfailEx :: String -> a
pfailEx :: String -> a
pfailEx = PatternMatchFail -> a
forall a e. Exception e => e -> a
throw (PatternMatchFail -> a)
-> (String -> PatternMatchFail) -> String -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PatternMatchFail
PatternMatchFail (String -> PatternMatchFail)
-> (String -> String) -> String -> PatternMatchFail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
showString String
"in SDP.ByteString.Lazy."
lim :: Int
lim :: Int
lim = Int
1024