sdp-0.2: Simple Data Processing
Copyright(c) Andrey Mulik 2019
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilitynon-portable (GHC extensions)
Safe HaskellTrustworthy
LanguageHaskell2010

SDP.Prim.SBytes

Description

SDP.Prim.SBytes provides strict unboxed array pseudo-primitive types SBytes#, STBytes# and IOBytes#.

Synopsis

Exports

module SDP.SortM

module SDP.Sort

Preudo-primitive types

newtype MIOBytes# (io :: Type -> Type) e Source #

MIOBytes# is mutable pseudo-primitive Int-indexed strict unboxed array.

Constructors

MIOBytes# (STBytes# RealWorld e) 

Instances

Instances details
(MonadIO io, Unboxed e) => Thaw io (SBytes# e) (MIOBytes# io e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> io (MIOBytes# io e) Source #

unsafeThaw :: SBytes# e -> io (MIOBytes# io e) Source #

(MonadIO io, Unboxed e) => SortM io (MIOBytes# io e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

sortedMBy :: (e -> e -> Bool) -> MIOBytes# io e -> io Bool Source #

sortMBy :: Compare e -> MIOBytes# io e -> io () Source #

(MonadIO io, Unboxed e) => SplitM io (MIOBytes# io e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

takeM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

dropM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

keepM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

sansM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

splitM :: Int -> MIOBytes# io e -> io (MIOBytes# io e, MIOBytes# io e) Source #

divideM :: Int -> MIOBytes# io e -> io (MIOBytes# io e, MIOBytes# io e) Source #

splitsM :: Foldable f => f Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

dividesM :: Foldable f => f Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

partsM :: Foldable f => f Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

chunksM :: Int -> MIOBytes# io e -> io [MIOBytes# io e] Source #

eachM :: Int -> MIOBytes# io e -> io (MIOBytes# io e) Source #

prefixM :: (e -> Bool) -> MIOBytes# io e -> io Int Source #

suffixM :: (e -> Bool) -> MIOBytes# io e -> io Int Source #

mprefix :: (e -> io Bool) -> MIOBytes# io e -> io Int Source #

msuffix :: (e -> io Bool) -> MIOBytes# io e -> io Int Source #

(MonadIO io, Unboxed e) => LinearM io (MIOBytes# io e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

newNull :: io (MIOBytes# io e) Source #

nowNull :: MIOBytes# io e -> io Bool Source #

singleM :: e -> io (MIOBytes# io e) Source #

getHead :: MIOBytes# io e -> io e Source #

getLast :: MIOBytes# io e -> io e Source #

prepend :: e -> MIOBytes# io e -> io (MIOBytes# io e) Source #

append :: MIOBytes# io e -> e -> io (MIOBytes# io e) Source #

newLinear :: [e] -> io (MIOBytes# io e) Source #

newLinearN :: Int -> [e] -> io (MIOBytes# io e) Source #

fromFoldableM :: Foldable f => f e -> io (MIOBytes# io e) Source #

getLeft :: MIOBytes# io e -> io [e] Source #

getRight :: MIOBytes# io e -> io [e] Source #

(!#>) :: MIOBytes# io e -> Int -> io e Source #

writeM :: MIOBytes# io e -> Int -> e -> io () Source #

copied :: MIOBytes# io e -> io (MIOBytes# io e) Source #

copied' :: MIOBytes# io e -> Int -> Int -> io (MIOBytes# io e) Source #

reversed :: MIOBytes# io e -> io (MIOBytes# io e) Source #

merged :: Foldable f => f (MIOBytes# io e) -> io (MIOBytes# io e) Source #

filled :: Int -> e -> io (MIOBytes# io e) Source #

copyTo :: MIOBytes# io e -> Int -> MIOBytes# io e -> Int -> Int -> io () Source #

ofoldrM :: (Int -> e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

ofoldlM :: (Int -> r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

ofoldrM' :: (Int -> e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

ofoldlM' :: (Int -> r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

foldrM :: (e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

foldlM :: (r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

foldrM' :: (e -> r -> io r) -> r -> MIOBytes# io e -> io r Source #

foldlM' :: (r -> e -> io r) -> r -> MIOBytes# io e -> io r Source #

swapM :: MIOBytes# io e -> Int -> Int -> io () Source #

MonadIO io => BorderedM io (MIOBytes# io e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

getBounds :: MIOBytes# io e -> io (Int, Int) Source #

getLower :: MIOBytes# io e -> io Int Source #

getUpper :: MIOBytes# io e -> io Int Source #

getSizeOf :: MIOBytes# io e -> io Int Source #

getSizesOf :: MIOBytes# io e -> io [Int] Source #

nowIndexIn :: MIOBytes# io e -> Int -> io Bool Source #

getOffsetOf :: MIOBytes# io e -> Int -> io Int Source #

getIndexOf :: MIOBytes# io e -> Int -> io Int Source #

getIndices :: MIOBytes# io e -> io [Int] Source #

(MonadIO io, Unboxed e) => MapM io (MIOBytes# io e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

newMap :: [(Int, e)] -> io (MIOBytes# io e) Source #

newMap' :: e -> [(Int, e)] -> io (MIOBytes# io e) Source #

getAssocs :: MIOBytes# io e -> io [(Int, e)] Source #

(>!) :: MIOBytes# io e -> Int -> io e Source #

(!>) :: MIOBytes# io e -> Int -> io e Source #

(!?>) :: MIOBytes# io e -> Int -> io (Maybe e) Source #

updateM :: MIOBytes# io e -> (Int -> e -> e) -> io (MIOBytes# io e) Source #

overwrite :: MIOBytes# io e -> [(Int, e)] -> io (MIOBytes# io e) Source #

memberM' :: MIOBytes# io e -> Int -> io Bool Source #

getKeys :: MIOBytes# io e -> io [Int] Source #

(.?) :: (e -> Bool) -> MIOBytes# io e -> io (Maybe Int) Source #

(*?) :: (e -> Bool) -> MIOBytes# io e -> io [Int] Source #

kfoldrM :: (Int -> e -> acc -> io acc) -> acc -> MIOBytes# io e -> io acc Source #

kfoldlM :: (Int -> acc -> e -> io acc) -> acc -> MIOBytes# io e -> io acc Source #

kfoldrM' :: (Int -> e -> acc -> io acc) -> acc -> MIOBytes# io e -> io acc Source #

kfoldlM' :: (Int -> acc -> e -> io acc) -> acc -> MIOBytes# io e -> io acc Source #

(MonadIO io, Unboxed e) => IndexedM io (MIOBytes# io e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> io (MIOBytes# io e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> io (MIOBytes# io e) Source #

writeM' :: MIOBytes# io e -> Int -> e -> io () Source #

swapM' :: MIOBytes# io e -> Int -> Int -> io () Source #

fromIndexed' :: Indexed v' j e => v' -> io (MIOBytes# io e) Source #

fromIndexedM :: IndexedM io v' j e => v' -> io (MIOBytes# io e) Source #

reshaped :: IndexedM io v' j e => (Int, Int) -> v' -> (Int -> j) -> io (MIOBytes# io e) Source #

fromAccum :: (e -> e' -> e) -> MIOBytes# io e -> [(Int, e')] -> io (MIOBytes# io e) Source #

updateM' :: MIOBytes# io e -> (e -> e) -> Int -> io () Source #

(MonadIO io, Unboxed e) => Freeze io (MIOBytes# io e) (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

freeze :: MIOBytes# io e -> io (SBytes# e) Source #

unsafeFreeze :: MIOBytes# io e -> io (SBytes# e) Source #

Eq (MIOBytes# io e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(==) :: MIOBytes# io e -> MIOBytes# io e -> Bool #

(/=) :: MIOBytes# io e -> MIOBytes# io e -> Bool #

Estimate (MIOBytes# io e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(<.=>) :: MIOBytes# io e -> Int -> Ordering Source #

(<==>) :: Compare (MIOBytes# io e) Source #

(.==) :: MIOBytes# io e -> Int -> Bool Source #

(./=) :: MIOBytes# io e -> Int -> Bool Source #

(.<=) :: MIOBytes# io e -> Int -> Bool Source #

(.>=) :: MIOBytes# io e -> Int -> Bool Source #

(.<) :: MIOBytes# io e -> Int -> Bool Source #

(.>) :: MIOBytes# io e -> Int -> Bool Source #

(.<.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.>.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.<=.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.>=.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(.==.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

(./=.) :: MIOBytes# io e -> MIOBytes# io e -> Bool Source #

Bordered (MIOBytes# io e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

bounds :: MIOBytes# io e -> (Int, Int) Source #

lower :: MIOBytes# io e -> Int Source #

upper :: MIOBytes# io e -> Int Source #

sizeOf :: MIOBytes# io e -> Int Source #

sizesOf :: MIOBytes# io e -> [Int] Source #

indexIn :: MIOBytes# io e -> Int -> Bool Source #

indices :: MIOBytes# io e -> [Int] Source #

indexOf :: MIOBytes# io e -> Int -> Int Source #

offsetOf :: MIOBytes# io e -> Int -> Int Source #

type IOBytes# = MIOBytes# IO Source #

IOBytes# is mutable pseudo-primitive Int-indexed strict unboxed array.

data STBytes# s e Source #

STBytes# is mutable pseudo-primitive Int-indexed strict unboxed array type.

Instances

Instances details
Unboxed e => Thaw (ST s) (SBytes# e) (STBytes# s e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> ST s (STBytes# s e) Source #

unsafeThaw :: SBytes# e -> ST s (STBytes# s e) Source #

Unboxed e => SortM (ST s) (STBytes# s e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

sortedMBy :: (e -> e -> Bool) -> STBytes# s e -> ST s Bool Source #

sortMBy :: Compare e -> STBytes# s e -> ST s () Source #

Unboxed e => SplitM (ST s) (STBytes# s e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

takeM :: Int -> STBytes# s e -> ST s (STBytes# s e) Source #

dropM :: Int -> STBytes# s e -> ST s (STBytes# s e) Source #

keepM :: Int -> STBytes# s e -> ST s (STBytes# s e) Source #

sansM :: Int -> STBytes# s e -> ST s (STBytes# s e) Source #

splitM :: Int -> STBytes# s e -> ST s (STBytes# s e, STBytes# s e) Source #

divideM :: Int -> STBytes# s e -> ST s (STBytes# s e, STBytes# s e) Source #

splitsM :: Foldable f => f Int -> STBytes# s e -> ST s [STBytes# s e] Source #

dividesM :: Foldable f => f Int -> STBytes# s e -> ST s [STBytes# s e] Source #

partsM :: Foldable f => f Int -> STBytes# s e -> ST s [STBytes# s e] Source #

chunksM :: Int -> STBytes# s e -> ST s [STBytes# s e] Source #

eachM :: Int -> STBytes# s e -> ST s (STBytes# s e) Source #

prefixM :: (e -> Bool) -> STBytes# s e -> ST s Int Source #

suffixM :: (e -> Bool) -> STBytes# s e -> ST s Int Source #

mprefix :: (e -> ST s Bool) -> STBytes# s e -> ST s Int Source #

msuffix :: (e -> ST s Bool) -> STBytes# s e -> ST s Int Source #

Unboxed e => LinearM (ST s) (STBytes# s e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

newNull :: ST s (STBytes# s e) Source #

nowNull :: STBytes# s e -> ST s Bool Source #

singleM :: e -> ST s (STBytes# s e) Source #

getHead :: STBytes# s e -> ST s e Source #

getLast :: STBytes# s e -> ST s e Source #

prepend :: e -> STBytes# s e -> ST s (STBytes# s e) Source #

append :: STBytes# s e -> e -> ST s (STBytes# s e) Source #

newLinear :: [e] -> ST s (STBytes# s e) Source #

newLinearN :: Int -> [e] -> ST s (STBytes# s e) Source #

fromFoldableM :: Foldable f => f e -> ST s (STBytes# s e) Source #

getLeft :: STBytes# s e -> ST s [e] Source #

getRight :: STBytes# s e -> ST s [e] Source #

(!#>) :: STBytes# s e -> Int -> ST s e Source #

writeM :: STBytes# s e -> Int -> e -> ST s () Source #

copied :: STBytes# s e -> ST s (STBytes# s e) Source #

copied' :: STBytes# s e -> Int -> Int -> ST s (STBytes# s e) Source #

reversed :: STBytes# s e -> ST s (STBytes# s e) Source #

merged :: Foldable f => f (STBytes# s e) -> ST s (STBytes# s e) Source #

filled :: Int -> e -> ST s (STBytes# s e) Source #

copyTo :: STBytes# s e -> Int -> STBytes# s e -> Int -> Int -> ST s () Source #

ofoldrM :: (Int -> e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

ofoldlM :: (Int -> r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

ofoldrM' :: (Int -> e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

ofoldlM' :: (Int -> r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldrM :: (e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldlM :: (r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldrM' :: (e -> r -> ST s r) -> r -> STBytes# s e -> ST s r Source #

foldlM' :: (r -> e -> ST s r) -> r -> STBytes# s e -> ST s r Source #

swapM :: STBytes# s e -> Int -> Int -> ST s () Source #

BorderedM (ST s) (STBytes# s e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

Unboxed e => MapM (ST s) (STBytes# s e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

newMap :: [(Int, e)] -> ST s (STBytes# s e) Source #

newMap' :: e -> [(Int, e)] -> ST s (STBytes# s e) Source #

getAssocs :: STBytes# s e -> ST s [(Int, e)] Source #

(>!) :: STBytes# s e -> Int -> ST s e Source #

(!>) :: STBytes# s e -> Int -> ST s e Source #

(!?>) :: STBytes# s e -> Int -> ST s (Maybe e) Source #

updateM :: STBytes# s e -> (Int -> e -> e) -> ST s (STBytes# s e) Source #

overwrite :: STBytes# s e -> [(Int, e)] -> ST s (STBytes# s e) Source #

memberM' :: STBytes# s e -> Int -> ST s Bool Source #

getKeys :: STBytes# s e -> ST s [Int] Source #

(.?) :: (e -> Bool) -> STBytes# s e -> ST s (Maybe Int) Source #

(*?) :: (e -> Bool) -> STBytes# s e -> ST s [Int] Source #

kfoldrM :: (Int -> e -> acc -> ST s acc) -> acc -> STBytes# s e -> ST s acc Source #

kfoldlM :: (Int -> acc -> e -> ST s acc) -> acc -> STBytes# s e -> ST s acc Source #

kfoldrM' :: (Int -> e -> acc -> ST s acc) -> acc -> STBytes# s e -> ST s acc Source #

kfoldlM' :: (Int -> acc -> e -> ST s acc) -> acc -> STBytes# s e -> ST s acc Source #

Unboxed e => IndexedM (ST s) (STBytes# s e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

fromAssocs :: (Int, Int) -> [(Int, e)] -> ST s (STBytes# s e) Source #

fromAssocs' :: (Int, Int) -> e -> [(Int, e)] -> ST s (STBytes# s e) Source #

writeM' :: STBytes# s e -> Int -> e -> ST s () Source #

swapM' :: STBytes# s e -> Int -> Int -> ST s () Source #

fromIndexed' :: Indexed v' j e => v' -> ST s (STBytes# s e) Source #

fromIndexedM :: IndexedM (ST s) v' j e => v' -> ST s (STBytes# s e) Source #

reshaped :: IndexedM (ST s) v' j e => (Int, Int) -> v' -> (Int -> j) -> ST s (STBytes# s e) Source #

fromAccum :: (e -> e' -> e) -> STBytes# s e -> [(Int, e')] -> ST s (STBytes# s e) Source #

updateM' :: STBytes# s e -> (e -> e) -> Int -> ST s () Source #

Unboxed e => Freeze (ST s) (STBytes# s e) (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

freeze :: STBytes# s e -> ST s (SBytes# e) Source #

unsafeFreeze :: STBytes# s e -> ST s (SBytes# e) Source #

Eq (STBytes# s e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(==) :: STBytes# s e -> STBytes# s e -> Bool #

(/=) :: STBytes# s e -> STBytes# s e -> Bool #

Estimate (STBytes# s e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(<.=>) :: STBytes# s e -> Int -> Ordering Source #

(<==>) :: Compare (STBytes# s e) Source #

(.==) :: STBytes# s e -> Int -> Bool Source #

(./=) :: STBytes# s e -> Int -> Bool Source #

(.<=) :: STBytes# s e -> Int -> Bool Source #

(.>=) :: STBytes# s e -> Int -> Bool Source #

(.<) :: STBytes# s e -> Int -> Bool Source #

(.>) :: STBytes# s e -> Int -> Bool Source #

(.<.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.>.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.<=.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.>=.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(.==.) :: STBytes# s e -> STBytes# s e -> Bool Source #

(./=.) :: STBytes# s e -> STBytes# s e -> Bool Source #

Bordered (STBytes# s e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

data SBytes# e Source #

SBytes# is immutable pseudo-primitive Int-indexed strict unboxed array type.

SBytes# isn't real Haskell primitive (like GHC.Exts types) but for reliability and stability, I made it inaccessible to direct work.

Instances

Instances details
(Storable e, Unboxed e) => Thaw IO (SBytes# e) (Int, Ptr e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> IO (Int, Ptr e) Source #

unsafeThaw :: SBytes# e -> IO (Int, Ptr e) Source #

(MonadIO io, Unboxed e) => Thaw io (SBytes# e) (MIOBytes# io e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> io (MIOBytes# io e) Source #

unsafeThaw :: SBytes# e -> io (MIOBytes# io e) Source #

(Storable e, Unboxed e) => Freeze IO (Int, Ptr e) (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

freeze :: (Int, Ptr e) -> IO (SBytes# e) Source #

unsafeFreeze :: (Int, Ptr e) -> IO (SBytes# e) Source #

(MonadIO io, Unboxed e) => Freeze io (MIOBytes# io e) (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

freeze :: MIOBytes# io e -> io (SBytes# e) Source #

unsafeFreeze :: MIOBytes# io e -> io (SBytes# e) Source #

Unboxed e => IsList (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Associated Types

type Item (SBytes# e) #

Methods

fromList :: [Item (SBytes# e)] -> SBytes# e #

fromListN :: Int -> [Item (SBytes# e)] -> SBytes# e #

toList :: SBytes# e -> [Item (SBytes# e)] #

Unboxed e => Eq (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(==) :: SBytes# e -> SBytes# e -> Bool #

(/=) :: SBytes# e -> SBytes# e -> Bool #

(Unboxed e, Ord e) => Ord (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

compare :: SBytes# e -> SBytes# e -> Ordering #

(<) :: SBytes# e -> SBytes# e -> Bool #

(<=) :: SBytes# e -> SBytes# e -> Bool #

(>) :: SBytes# e -> SBytes# e -> Bool #

(>=) :: SBytes# e -> SBytes# e -> Bool #

max :: SBytes# e -> SBytes# e -> SBytes# e #

min :: SBytes# e -> SBytes# e -> SBytes# e #

(Unboxed e, Read e) => Read (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

(Unboxed e, Show e) => Show (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

showsPrec :: Int -> SBytes# e -> ShowS #

show :: SBytes# e -> String #

showList :: [SBytes# e] -> ShowS #

IsString (SBytes# Char) Source # 
Instance details

Defined in SDP.Prim.SBytes

Unboxed e => Semigroup (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

(<>) :: SBytes# e -> SBytes# e -> SBytes# e #

sconcat :: NonEmpty (SBytes# e) -> SBytes# e #

stimes :: Integral b => b -> SBytes# e -> SBytes# e #

Unboxed e => Monoid (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

mempty :: SBytes# e #

mappend :: SBytes# e -> SBytes# e -> SBytes# e #

mconcat :: [SBytes# e] -> SBytes# e #

Default (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

def :: SBytes# e #

Estimate (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Nullable (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Unboxed e => Sort (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

sortedBy :: (e -> e -> Bool) -> SBytes# e -> Bool Source #

sortBy :: Compare e -> SBytes# e -> SBytes# e Source #

Unboxed e => Sort (Ublist e) e Source # 
Instance details

Defined in SDP.ByteList.Ublist

Methods

sortedBy :: (e -> e -> Bool) -> Ublist e -> Bool Source #

sortBy :: Compare e -> Ublist e -> Ublist e Source #

Unboxed e => Split (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

take :: Int -> SBytes# e -> SBytes# e Source #

drop :: Int -> SBytes# e -> SBytes# e Source #

keep :: Int -> SBytes# e -> SBytes# e Source #

sans :: Int -> SBytes# e -> SBytes# e Source #

save :: Int -> SBytes# e -> SBytes# e Source #

skip :: Int -> SBytes# e -> SBytes# e Source #

split :: Int -> SBytes# e -> (SBytes# e, SBytes# e) Source #

divide :: Int -> SBytes# e -> (SBytes# e, SBytes# e) Source #

splits :: Foldable f => f Int -> SBytes# e -> [SBytes# e] Source #

divides :: Foldable f => f Int -> SBytes# e -> [SBytes# e] Source #

parts :: Foldable f => f Int -> SBytes# e -> [SBytes# e] Source #

chunks :: Int -> SBytes# e -> [SBytes# e] Source #

splitBy :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

divideBy :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

splitsBy :: (e -> Bool) -> SBytes# e -> [SBytes# e] Source #

splitsOn :: SBytes# e -> SBytes# e -> [SBytes# e] Source #

replaceBy :: SBytes# e -> SBytes# e -> SBytes# e -> SBytes# e Source #

removeAll :: SBytes# e -> SBytes# e -> SBytes# e Source #

combo :: Equal e -> SBytes# e -> Int Source #

justifyL :: Int -> e -> SBytes# e -> SBytes# e Source #

justifyR :: Int -> e -> SBytes# e -> SBytes# e Source #

each :: Int -> SBytes# e -> SBytes# e Source #

eachFrom :: Int -> Int -> SBytes# e -> SBytes# e Source #

isPrefixOf :: SBytes# e -> SBytes# e -> Bool Source #

isSuffixOf :: SBytes# e -> SBytes# e -> Bool Source #

isInfixOf :: SBytes# e -> SBytes# e -> Bool Source #

prefix :: (e -> Bool) -> SBytes# e -> Int Source #

suffix :: (e -> Bool) -> SBytes# e -> Int Source #

infixes :: SBytes# e -> SBytes# e -> [Int] Source #

dropSide :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

takeWhile :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

dropWhile :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

takeEnd :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

dropEnd :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

spanl :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

breakl :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

spanr :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

breakr :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

selectWhile :: (e -> Maybe a) -> SBytes# e -> [a] Source #

selectEnd :: (e -> Maybe a) -> SBytes# e -> [a] Source #

extractWhile :: (e -> Maybe a) -> SBytes# e -> ([a], SBytes# e) Source #

extractEnd :: (e -> Maybe a) -> SBytes# e -> (SBytes# e, [a]) Source #

selectWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> t a Source #

selectEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> t a Source #

extractWhile' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> (t a, SBytes# e) Source #

extractEnd' :: (t e ~ l, Split1 t a) => (e -> Maybe a) -> SBytes# e -> (SBytes# e, t a) Source #

Unboxed e => Linear (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

uncons :: SBytes# e -> (e, SBytes# e) Source #

uncons' :: SBytes# e -> Maybe (e, SBytes# e) Source #

toHead :: e -> SBytes# e -> SBytes# e Source #

head :: SBytes# e -> e Source #

tail :: SBytes# e -> SBytes# e Source #

unsnoc :: SBytes# e -> (SBytes# e, e) Source #

unsnoc' :: SBytes# e -> Maybe (SBytes# e, e) Source #

toLast :: SBytes# e -> e -> SBytes# e Source #

init :: SBytes# e -> SBytes# e Source #

last :: SBytes# e -> e Source #

single :: e -> SBytes# e Source #

(++) :: SBytes# e -> SBytes# e -> SBytes# e Source #

replicate :: Int -> e -> SBytes# e Source #

fromList :: [e] -> SBytes# e Source #

fromListN :: Int -> [e] -> SBytes# e Source #

listR :: SBytes# e -> [e] Source #

listL :: SBytes# e -> [e] Source #

fromFoldable :: Foldable f => f e -> SBytes# e Source #

(!^) :: SBytes# e -> Int -> e Source #

write :: SBytes# e -> Int -> e -> SBytes# e Source #

concat :: Foldable f => f (SBytes# e) -> SBytes# e Source #

concatMap :: Foldable f => (a -> SBytes# e) -> f a -> SBytes# e Source #

intersperse :: e -> SBytes# e -> SBytes# e Source #

filter :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

except :: (e -> Bool) -> SBytes# e -> SBytes# e Source #

partition :: (e -> Bool) -> SBytes# e -> (SBytes# e, SBytes# e) Source #

partitions :: Foldable f => f (e -> Bool) -> SBytes# e -> [SBytes# e] Source #

select :: (e -> Maybe a) -> SBytes# e -> [a] Source #

select' :: (t e ~ SBytes# e, Linear1 t a) => (e -> Maybe a) -> SBytes# e -> t a Source #

extract :: (e -> Maybe a) -> SBytes# e -> ([a], SBytes# e) Source #

extract' :: (t e ~ SBytes# e, Linear1 t a) => (e -> Maybe a) -> SBytes# e -> (t a, SBytes# e) Source #

selects :: Foldable f => f (e -> Maybe a) -> SBytes# e -> ([[a]], SBytes# e) Source #

selects' :: (Foldable f, t e ~ SBytes# e, Linear1 t a) => f (e -> Maybe a) -> SBytes# e -> ([t a], SBytes# e) Source #

isSubseqOf :: SBytes# e -> SBytes# e -> Bool Source #

reverse :: SBytes# e -> SBytes# e Source #

force :: SBytes# e -> SBytes# e Source #

subsequences :: SBytes# e -> [SBytes# e] Source #

iterate :: Int -> (e -> e) -> e -> SBytes# e Source #

nub :: SBytes# e -> SBytes# e Source #

nubBy :: Equal e -> SBytes# e -> SBytes# e Source #

ofoldr :: (Int -> e -> b -> b) -> b -> SBytes# e -> b Source #

ofoldl :: (Int -> b -> e -> b) -> b -> SBytes# e -> b Source #

ofoldr' :: (Int -> e -> b -> b) -> b -> SBytes# e -> b Source #

ofoldl' :: (Int -> b -> e -> b) -> b -> SBytes# e -> b Source #

o_foldr :: (e -> b -> b) -> b -> SBytes# e -> b Source #

o_foldl :: (b -> e -> b) -> b -> SBytes# e -> b Source #

o_foldr' :: (e -> b -> b) -> b -> SBytes# e -> b Source #

o_foldl' :: (b -> e -> b) -> b -> SBytes# e -> b Source #

Bordered (SBytes# e) Int Source # 
Instance details

Defined in SDP.Prim.SBytes

(Unboxed e, Ord e) => Set (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Unboxed e => SetWith (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Unboxed e => Scan (SBytes# e) e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

scanl :: (b -> e -> b) -> b -> SBytes# e -> [b] Source #

scanl' :: (b -> e -> b) -> b -> SBytes# e -> [b] Source #

scanr :: (e -> b -> b) -> b -> SBytes# e -> [b] Source #

scanr' :: (e -> b -> b) -> b -> SBytes# e -> [b] Source #

scanl1 :: (e -> e -> e) -> SBytes# e -> [e] Source #

scanr1 :: (e -> e -> e) -> SBytes# e -> [e] Source #

Unboxed e => Map (SBytes# e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

assocs :: SBytes# e -> [(Int, e)] Source #

toMap :: [(Int, e)] -> SBytes# e Source #

toMap' :: e -> [(Int, e)] -> SBytes# e Source #

insert' :: Int -> e -> SBytes# e -> SBytes# e Source #

delete' :: Int -> SBytes# e -> SBytes# e Source #

member' :: Int -> SBytes# e -> Bool Source #

(//) :: SBytes# e -> [(Int, e)] -> SBytes# e Source #

(.!) :: SBytes# e -> Int -> e Source #

(!) :: SBytes# e -> Int -> e Source #

(!?) :: SBytes# e -> Int -> Maybe e Source #

filter' :: (Int -> e -> Bool) -> SBytes# e -> SBytes# e Source #

union' :: (e -> e -> e) -> SBytes# e -> SBytes# e -> SBytes# e Source #

difference' :: (e -> e -> Maybe e) -> SBytes# e -> SBytes# e -> SBytes# e Source #

intersection' :: (e -> e -> e) -> SBytes# e -> SBytes# e -> SBytes# e Source #

update :: SBytes# e -> (Int -> e -> e) -> SBytes# e Source #

lookupLT' :: Int -> SBytes# e -> Maybe (Int, e) Source #

lookupGT' :: Int -> SBytes# e -> Maybe (Int, e) Source #

lookupLE' :: Int -> SBytes# e -> Maybe (Int, e) Source #

lookupGE' :: Int -> SBytes# e -> Maybe (Int, e) Source #

keys :: SBytes# e -> [Int] Source #

(.$) :: (e -> Bool) -> SBytes# e -> Maybe Int Source #

(*$) :: (e -> Bool) -> SBytes# e -> [Int] Source #

kfoldr :: (Int -> e -> b -> b) -> b -> SBytes# e -> b Source #

kfoldl :: (Int -> b -> e -> b) -> b -> SBytes# e -> b Source #

kfoldr' :: (Int -> e -> b -> b) -> b -> SBytes# e -> b Source #

kfoldl' :: (Int -> b -> e -> b) -> b -> SBytes# e -> b Source #

Unboxed e => Indexed (SBytes# e) Int e Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

assoc :: (Int, Int) -> [(Int, e)] -> SBytes# e Source #

assoc' :: (Int, Int) -> e -> [(Int, e)] -> SBytes# e Source #

fromIndexed :: Indexed m j e => m -> SBytes# e Source #

write' :: SBytes# e -> Int -> e -> SBytes# e Source #

accum :: (e -> e' -> e) -> SBytes# e -> [(Int, e')] -> SBytes# e Source #

imap :: Map m j e => (Int, Int) -> m -> (Int -> j) -> SBytes# e Source #

update' :: SBytes# e -> (e -> e) -> Int -> SBytes# e Source #

updates' :: SBytes# e -> (Int -> e -> e) -> SBytes# e Source #

Unboxed e => Thaw (ST s) (SBytes# e) (STBytes# s e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

thaw :: SBytes# e -> ST s (STBytes# s e) Source #

unsafeThaw :: SBytes# e -> ST s (STBytes# s e) Source #

Unboxed e => Freeze (ST s) (STBytes# s e) (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

Methods

freeze :: STBytes# s e -> ST s (SBytes# e) Source #

unsafeFreeze :: STBytes# s e -> ST s (SBytes# e) Source #

type Item (SBytes# e) Source # 
Instance details

Defined in SDP.Prim.SBytes

type Item (SBytes# e) = e

Unpack unboxed arrays

offsetSBytes# :: Unboxed e => SBytes# e -> Int Source #

offsetSBytes# returns SBytes# offset in elements.

offsetSTBytes# :: Unboxed e => STBytes# s e -> Int# Source #

offsetSTBytes# returns STBytes# offset in bytes.

Coerce unboxed arrays

unsafeCoerceSBytes# :: (Unboxed a, Unboxed b) => SBytes# a -> SBytes# b Source #

unsafeCoerceSBytes# is unsafe low-lowel coerce of an array with recounting the number of elements and offset (with possible rounding).

unsafeCoerceSTBytes# :: (Unboxed a, Unboxed b) => STBytes# s a -> STBytes# s b Source #

unsafeCoerceSTBytes# is unsafe low-lowel coerce of an mutable array with recounting the number of elements and offset (with possible rounding).

Unsafe pointer conversions

unsafeSBytesToPtr# :: Unboxed e => SBytes# e -> IO (Int, Ptr e) Source #

unsafeSBytesToPtr# es byte-wise stores SBytes# content to Ptr. Returns the number of overwritten elements and a pointer to psizeof es (sizeOf es) bytes of allocated memory.

unsafePtrToSBytes# :: Unboxed e => (Int, Ptr e) -> IO (SBytes# e) Source #

unsafePtrToSBytes# n ptr byte-wise stores n elements of Ptr ptr to SBytes#.

Hash

hashSBytesWith# :: Unboxed e => Int -> SBytes# e -> Int Source #

Calculate hash SBytes# using hashUnboxedWith.