foundation-0.0.12: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Primitive

Contents

Description

Different collections (list, vector, string, ..) unified under 1 API. an API to rules them all, and in the darkness bind them.

Synopsis

Documentation

class Eq ty => PrimType ty where Source #

Represent the accessor for types that can be stored in the UArray and MUArray.

Types need to be a instance of storable and have fixed sized.

Methods

primSizeInBytes :: Proxy ty -> Size8 Source #

get the size in bytes of a ty element

primBaUIndex :: ByteArray# -> Offset ty -> ty Source #

return the element stored at a specific index

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty Source #

Read an element at an index in a mutable array

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () Source #

Write an element to a specific cell in a mutable array.

primAddrIndex :: Addr# -> Offset ty -> ty Source #

Read from Address, without a state. the value read should be considered a constant for all pratical purpose, otherwise bad thing will happens.

primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty Source #

Read a value from Addr in a specific primitive monad

primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim () Source #

Write a value to Addr in a specific primitive monad

Instances

PrimType Char Source # 
PrimType Double Source # 
PrimType Float Source # 
PrimType Int Source # 
PrimType Int8 Source # 
PrimType Int16 Source # 
PrimType Int32 Source # 
PrimType Int64 Source # 
PrimType Word Source # 
PrimType Word8 Source # 
PrimType Word16 Source # 
PrimType Word32 Source # 
PrimType Word64 Source # 
PrimType CChar Source # 
PrimType CUChar Source # 
PrimType Seconds Source # 
PrimType NanoSeconds Source # 
PrimType a => PrimType (BE a) Source # 

Methods

primSizeInBytes :: Proxy * (BE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

PrimType a => PrimType (LE a) Source # 

Methods

primSizeInBytes :: Proxy * (LE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

class (Functor m, Applicative m, Monad m) => PrimMonad m where Source #

Primitive monad that can handle mutation.

For example: IO and ST.

Associated Types

type PrimState m Source #

type of state token associated with the PrimMonad m

type PrimVar m :: * -> * Source #

type of variable associated with the PrimMonad m

Methods

primitive :: (State# (PrimState m) -> (#State# (PrimState m), a#)) -> m a Source #

Unwrap the State# token to pass to a function a primitive function that returns an unboxed state and a value.

primThrow :: Exception e => e -> m a Source #

Throw Exception in the primitive monad

unPrimMonad :: m a -> State# (PrimState m) -> (#State# (PrimState m), a#) Source #

Run a Prim monad from a dedicated state#

primVarNew :: a -> m (PrimVar m a) Source #

Build a new variable in the Prim Monad

primVarRead :: PrimVar m a -> m a Source #

Read the variable in the Prim Monad

primVarWrite :: PrimVar m a -> a -> m () Source #

Write the variable in the Prim Monad

Instances

PrimMonad IO Source # 

Associated Types

type PrimState (IO :: * -> *) :: * Source #

type PrimVar (IO :: * -> *) :: * -> * Source #

PrimMonad (ST s) Source # 

Associated Types

type PrimState (ST s :: * -> *) :: * Source #

type PrimVar (ST s :: * -> *) :: * -> * Source #

Methods

primitive :: (State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#)) -> ST s a Source #

primThrow :: Exception e => e -> ST s a Source #

unPrimMonad :: ST s a -> State# (PrimState (ST s)) -> (#VoidRep, PtrRepLifted, State# (PrimState (ST s)), a#) Source #

primVarNew :: a -> ST s (PrimVar (ST s) a) Source #

primVarRead :: PrimVar (ST s) a -> ST s a Source #

primVarWrite :: PrimVar (ST s) a -> a -> ST s () Source #

endianess

class ByteSwap a Source #

Class of types that can be byte-swapped.

e.g. Word16, Word32, Word64

Minimal complete definition

byteSwap

newtype LE a Source #

Little Endian value

Constructors

LE 

Fields

Instances

Eq a => Eq (LE a) Source # 

Methods

(==) :: LE a -> LE a -> Bool #

(/=) :: LE a -> LE a -> Bool #

(ByteSwap a, Ord a) => Ord (LE a) Source # 

Methods

compare :: LE a -> LE a -> Ordering #

(<) :: LE a -> LE a -> Bool #

(<=) :: LE a -> LE a -> Bool #

(>) :: LE a -> LE a -> Bool #

(>=) :: LE a -> LE a -> Bool #

max :: LE a -> LE a -> LE a #

min :: LE a -> LE a -> LE a #

Show a => Show (LE a) Source # 

Methods

showsPrec :: Int -> LE a -> ShowS #

show :: LE a -> String #

showList :: [LE a] -> ShowS #

PrimType a => PrimType (LE a) Source # 

Methods

primSizeInBytes :: Proxy * (LE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

StorableFixed (LE Word16) Source # 

Methods

size :: proxy (LE Word16) -> CountOf Word8 Source #

alignment :: proxy (LE Word16) -> CountOf Word8 Source #

StorableFixed (LE Word32) Source # 

Methods

size :: proxy (LE Word32) -> CountOf Word8 Source #

alignment :: proxy (LE Word32) -> CountOf Word8 Source #

StorableFixed (LE Word64) Source # 

Methods

size :: proxy (LE Word64) -> CountOf Word8 Source #

alignment :: proxy (LE Word64) -> CountOf Word8 Source #

Storable (LE Word16) Source # 

Methods

peek :: Ptr (LE Word16) -> IO (LE Word16) Source #

poke :: Ptr (LE Word16) -> LE Word16 -> IO () Source #

Storable (LE Word32) Source # 

Methods

peek :: Ptr (LE Word32) -> IO (LE Word32) Source #

poke :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

Storable (LE Word64) Source # 

Methods

peek :: Ptr (LE Word64) -> IO (LE Word64) Source #

poke :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

toLE :: ByteSwap a => a -> LE a Source #

Convert a value in cpu endianess to little endian

fromLE :: ByteSwap a => LE a -> a Source #

Convert from a little endian value to the cpu endianness

newtype BE a Source #

Big Endian value

Constructors

BE 

Fields

Instances

Eq a => Eq (BE a) Source # 

Methods

(==) :: BE a -> BE a -> Bool #

(/=) :: BE a -> BE a -> Bool #

(ByteSwap a, Ord a) => Ord (BE a) Source # 

Methods

compare :: BE a -> BE a -> Ordering #

(<) :: BE a -> BE a -> Bool #

(<=) :: BE a -> BE a -> Bool #

(>) :: BE a -> BE a -> Bool #

(>=) :: BE a -> BE a -> Bool #

max :: BE a -> BE a -> BE a #

min :: BE a -> BE a -> BE a #

Show a => Show (BE a) Source # 

Methods

showsPrec :: Int -> BE a -> ShowS #

show :: BE a -> String #

showList :: [BE a] -> ShowS #

PrimType a => PrimType (BE a) Source # 

Methods

primSizeInBytes :: Proxy * (BE a) -> Size8 Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

StorableFixed (BE Word16) Source # 

Methods

size :: proxy (BE Word16) -> CountOf Word8 Source #

alignment :: proxy (BE Word16) -> CountOf Word8 Source #

StorableFixed (BE Word32) Source # 

Methods

size :: proxy (BE Word32) -> CountOf Word8 Source #

alignment :: proxy (BE Word32) -> CountOf Word8 Source #

StorableFixed (BE Word64) Source # 

Methods

size :: proxy (BE Word64) -> CountOf Word8 Source #

alignment :: proxy (BE Word64) -> CountOf Word8 Source #

Storable (BE Word16) Source # 

Methods

peek :: Ptr (BE Word16) -> IO (BE Word16) Source #

poke :: Ptr (BE Word16) -> BE Word16 -> IO () Source #

Storable (BE Word32) Source # 

Methods

peek :: Ptr (BE Word32) -> IO (BE Word32) Source #

poke :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

Storable (BE Word64) Source # 

Methods

peek :: Ptr (BE Word64) -> IO (BE Word64) Source #

poke :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

toBE :: ByteSwap a => a -> BE a Source #

Convert a value in cpu endianess to big endian

fromBE :: ByteSwap a => BE a -> a Source #

Convert from a big endian value to the cpu endianness

Integral convertion

class IntegralUpsize a b where Source #

Upsize an integral value

The destination type b size need to be greater or equal than the size type of a

Minimal complete definition

integralUpsize

Methods

integralUpsize :: a -> b Source #

Instances

IntegralUpsize Int Int64 Source # 
IntegralUpsize Int Integer Source # 
IntegralUpsize Int8 Int Source # 
IntegralUpsize Int8 Int16 Source # 
IntegralUpsize Int8 Int32 Source # 
IntegralUpsize Int8 Int64 Source # 
IntegralUpsize Int8 Integer Source # 
IntegralUpsize Int16 Int Source # 
IntegralUpsize Int16 Int32 Source # 
IntegralUpsize Int16 Int64 Source # 
IntegralUpsize Int16 Integer Source # 
IntegralUpsize Int32 Int Source # 
IntegralUpsize Int32 Int64 Source # 
IntegralUpsize Int32 Integer Source # 
IntegralUpsize Int64 Integer Source # 
IntegralUpsize Word Integer Source # 
IntegralUpsize Word Word64 Source # 
IntegralUpsize Word Natural Source # 
IntegralUpsize Word8 Int Source # 
IntegralUpsize Word8 Int16 Source # 
IntegralUpsize Word8 Int32 Source # 
IntegralUpsize Word8 Int64 Source # 
IntegralUpsize Word8 Integer Source # 
IntegralUpsize Word8 Word Source # 
IntegralUpsize Word8 Word16 Source # 
IntegralUpsize Word8 Word32 Source # 
IntegralUpsize Word8 Word64 Source # 
IntegralUpsize Word8 Natural Source # 
IntegralUpsize Word16 Integer Source # 
IntegralUpsize Word16 Word Source # 
IntegralUpsize Word16 Word32 Source # 
IntegralUpsize Word16 Word64 Source # 
IntegralUpsize Word16 Natural Source # 
IntegralUpsize Word32 Integer Source # 
IntegralUpsize Word32 Word Source # 
IntegralUpsize Word32 Word64 Source # 
IntegralUpsize Word32 Natural Source # 
IntegralUpsize Word64 Integer Source # 
IntegralUpsize Word64 Natural Source # 
IntegralUpsize Natural Integer Source # 

class IntegralDownsize a b where Source #

Downsize an integral value

Minimal complete definition

integralDownsizeCheck

Methods

integralDownsize :: a -> b Source #

integralDownsize :: a ~ b => a -> b Source #

integralDownsizeCheck :: a -> Maybe b Source #

Instances

IntegralDownsize Int Int8 Source # 
IntegralDownsize Int Int16 Source # 
IntegralDownsize Int Int32 Source # 
IntegralDownsize Int64 Int Source # 
IntegralDownsize Int64 Int8 Source # 
IntegralDownsize Int64 Int16 Source # 
IntegralDownsize Int64 Int32 Source # 
IntegralDownsize Integer Int8 Source # 
IntegralDownsize Integer Int16 Source # 
IntegralDownsize Integer Int32 Source # 
IntegralDownsize Integer Int64 Source # 
IntegralDownsize Integer Word8 Source # 
IntegralDownsize Integer Word16 Source # 
IntegralDownsize Integer Word32 Source # 
IntegralDownsize Integer Word64 Source # 
IntegralDownsize Integer Natural Source # 
IntegralDownsize Word16 Word8 Source # 
IntegralDownsize Word32 Word8 Source # 
IntegralDownsize Word32 Word16 Source # 
IntegralDownsize Word64 Word8 Source # 
IntegralDownsize Word64 Word16 Source # 
IntegralDownsize Word64 Word32 Source # 
IntegralDownsize Natural Word8 Source # 
IntegralDownsize Natural Word16 Source # 
IntegralDownsize Natural Word32 Source # 
IntegralDownsize Natural Word64 Source # 

class IntegralCast a b where Source #

Cast an integral value to another value that have the same representional size

Methods

integralCast :: a -> b Source #

integralCast :: a ~ b => a -> b Source #

Evaluation

class NormalForm a where Source #

Data that can be fully evaluated in Normal Form

Minimal complete definition

toNormalForm

Methods

toNormalForm :: a -> () Source #

Instances

NormalForm Bool Source # 

Methods

toNormalForm :: Bool -> () Source #

NormalForm Char Source # 

Methods

toNormalForm :: Char -> () Source #

NormalForm Double Source # 

Methods

toNormalForm :: Double -> () Source #

NormalForm Float Source # 

Methods

toNormalForm :: Float -> () Source #

NormalForm Int Source # 

Methods

toNormalForm :: Int -> () Source #

NormalForm Int8 Source # 

Methods

toNormalForm :: Int8 -> () Source #

NormalForm Int16 Source # 

Methods

toNormalForm :: Int16 -> () Source #

NormalForm Int32 Source # 

Methods

toNormalForm :: Int32 -> () Source #

NormalForm Int64 Source # 

Methods

toNormalForm :: Int64 -> () Source #

NormalForm Integer Source # 

Methods

toNormalForm :: Integer -> () Source #

NormalForm Word Source # 

Methods

toNormalForm :: Word -> () Source #

NormalForm Word8 Source # 

Methods

toNormalForm :: Word8 -> () Source #

NormalForm Word16 Source # 

Methods

toNormalForm :: Word16 -> () Source #

NormalForm Word32 Source # 

Methods

toNormalForm :: Word32 -> () Source #

NormalForm Word64 Source # 

Methods

toNormalForm :: Word64 -> () Source #

NormalForm () Source # 

Methods

toNormalForm :: () -> () Source #

NormalForm Natural Source # 

Methods

toNormalForm :: Natural -> () Source #

NormalForm CChar Source # 

Methods

toNormalForm :: CChar -> () Source #

NormalForm CSChar Source # 

Methods

toNormalForm :: CSChar -> () Source #

NormalForm CUChar Source # 

Methods

toNormalForm :: CUChar -> () Source #

NormalForm CShort Source # 

Methods

toNormalForm :: CShort -> () Source #

NormalForm CUShort Source # 

Methods

toNormalForm :: CUShort -> () Source #

NormalForm CInt Source # 

Methods

toNormalForm :: CInt -> () Source #

NormalForm CUInt Source # 

Methods

toNormalForm :: CUInt -> () Source #

NormalForm CLong Source # 

Methods

toNormalForm :: CLong -> () Source #

NormalForm CULong Source # 

Methods

toNormalForm :: CULong -> () Source #

NormalForm CLLong Source # 

Methods

toNormalForm :: CLLong -> () Source #

NormalForm CULLong Source # 

Methods

toNormalForm :: CULLong -> () Source #

NormalForm CFloat Source # 

Methods

toNormalForm :: CFloat -> () Source #

NormalForm CDouble Source # 

Methods

toNormalForm :: CDouble -> () Source #

NormalForm String Source # 

Methods

toNormalForm :: String -> () Source #

NormalForm IPv4 Source # 

Methods

toNormalForm :: IPv4 -> () Source #

NormalForm IPv6 Source # 

Methods

toNormalForm :: IPv6 -> () Source #

NormalForm UUID Source # 

Methods

toNormalForm :: UUID -> () Source #

NormalForm a => NormalForm [a] Source # 

Methods

toNormalForm :: [a] -> () Source #

NormalForm a => NormalForm (Maybe a) Source # 

Methods

toNormalForm :: Maybe a -> () Source #

NormalForm (Ptr a) Source # 

Methods

toNormalForm :: Ptr a -> () Source #

NormalForm (CountOf a) Source # 

Methods

toNormalForm :: CountOf a -> () Source #

NormalForm (Offset a) Source # 

Methods

toNormalForm :: Offset a -> () Source #

NormalForm (Block ty) Source # 

Methods

toNormalForm :: Block ty -> () Source #

NormalForm (UArray ty) Source # 

Methods

toNormalForm :: UArray ty -> () Source #

NormalForm a => NormalForm (Array a) Source # 

Methods

toNormalForm :: Array a -> () Source #

NormalForm (ChunkedUArray ty) Source # 

Methods

toNormalForm :: ChunkedUArray ty -> () Source #

(NormalForm l, NormalForm r) => NormalForm (Either l r) Source # 

Methods

toNormalForm :: Either l r -> () Source #

(NormalForm a, NormalForm b) => NormalForm (a, b) Source # 

Methods

toNormalForm :: (a, b) -> () Source #

NormalForm (BlockN n a) Source # 

Methods

toNormalForm :: BlockN n a -> () Source #

(NormalForm a, NormalForm b) => NormalForm (These a b) Source # 

Methods

toNormalForm :: These a b -> () Source #

(NormalForm a, NormalForm b) => NormalForm (Tuple2 a b) Source # 

Methods

toNormalForm :: Tuple2 a b -> () Source #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (a, b, c) Source # 

Methods

toNormalForm :: (a, b, c) -> () Source #

(NormalForm a, NormalForm b, NormalForm c) => NormalForm (Tuple3 a b c) Source # 

Methods

toNormalForm :: Tuple3 a b c -> () Source #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (a, b, c, d) Source # 

Methods

toNormalForm :: (a, b, c, d) -> () Source #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (Tuple4 a b c d) Source # 

Methods

toNormalForm :: Tuple4 a b c d -> () Source #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e) => NormalForm (a, b, c, d, e) Source # 

Methods

toNormalForm :: (a, b, c, d, e) -> () Source #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f) => NormalForm (a, b, c, d, e, f) Source # 

Methods

toNormalForm :: (a, b, c, d, e, f) -> () Source #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g) => NormalForm (a, b, c, d, e, f, g) Source # 

Methods

toNormalForm :: (a, b, c, d, e, f, g) -> () Source #

(NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g, NormalForm h) => NormalForm (a, b, c, d, e, f, g, h) Source # 

Methods

toNormalForm :: (a, b, c, d, e, f, g, h) -> () Source #

force :: NormalForm a => a -> a Source #

deepseq :: NormalForm a => a -> b -> b Source #

These

data These a b Source #

Either a or b or both.

Constructors

This a 
That b 
These a b 

Instances

Bifunctor These Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> These a c -> These b d #

first :: (a -> b) -> These a c -> These b c #

second :: (b -> c) -> These a b -> These a c #

Functor (These a) Source # 

Methods

fmap :: (a -> b) -> These a a -> These a b #

(<$) :: a -> These a b -> These a a #

(Eq b, Eq a) => Eq (These a b) Source # 

Methods

(==) :: These a b -> These a b -> Bool #

(/=) :: These a b -> These a b -> Bool #

(Ord b, Ord a) => Ord (These a b) Source # 

Methods

compare :: These a b -> These a b -> Ordering #

(<) :: These a b -> These a b -> Bool #

(<=) :: These a b -> These a b -> Bool #

(>) :: These a b -> These a b -> Bool #

(>=) :: These a b -> These a b -> Bool #

max :: These a b -> These a b -> These a b #

min :: These a b -> These a b -> These a b #

(Show b, Show a) => Show (These a b) Source # 

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(NormalForm a, NormalForm b) => NormalForm (These a b) Source # 

Methods

toNormalForm :: These a b -> () Source #

Block of memory

data Block ty Source #

A block of memory containing unpacked bytes representing values of type ty

Instances

PrimType ty => IsList (Block ty) Source # 

Associated Types

type Item (Block ty) :: * #

Methods

fromList :: [Item (Block ty)] -> Block ty #

fromListN :: Int -> [Item (Block ty)] -> Block ty #

toList :: Block ty -> [Item (Block ty)] #

(PrimType ty, Eq ty) => Eq (Block ty) Source # 

Methods

(==) :: Block ty -> Block ty -> Bool #

(/=) :: Block ty -> Block ty -> Bool #

Data ty => Data (Block ty) Source # 

Methods

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

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

toConstr :: Block ty -> Constr #

dataTypeOf :: Block ty -> DataType #

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

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

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

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

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

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

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

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

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

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

(PrimType ty, Ord ty) => Ord (Block ty) Source # 

Methods

compare :: Block ty -> Block ty -> Ordering #

(<) :: Block ty -> Block ty -> Bool #

(<=) :: Block ty -> Block ty -> Bool #

(>) :: Block ty -> Block ty -> Bool #

(>=) :: Block ty -> Block ty -> Bool #

max :: Block ty -> Block ty -> Block ty #

min :: Block ty -> Block ty -> Block ty #

(PrimType ty, Show ty) => Show (Block ty) Source # 

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

PrimType ty => Monoid (Block ty) Source # 

Methods

mempty :: Block ty #

mappend :: Block ty -> Block ty -> Block ty #

mconcat :: [Block ty] -> Block ty #

NormalForm (Block ty) Source # 

Methods

toNormalForm :: Block ty -> () Source #

PrimType ty => Copy (Block ty) Source # 

Methods

copy :: Block ty -> Block ty Source #

PrimType ty => Collection (Block ty) Source # 

Methods

null :: Block ty -> Bool Source #

length :: Block ty -> CountOf (Element (Block ty)) Source #

elem :: (Eq a, (* ~ a) (Element (Block ty))) => Element (Block ty) -> Block ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (Block ty))) => Element (Block ty) -> Block ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (Block ty))) => NonEmpty (Block ty) -> Element (Block ty) Source #

minimum :: (Ord a, (* ~ a) (Element (Block ty))) => NonEmpty (Block ty) -> Element (Block ty) Source #

any :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source #

all :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source #

PrimType ty => Foldable (Block ty) Source # 

Methods

foldl' :: (a -> Element (Block ty) -> a) -> a -> Block ty -> a Source #

foldr :: (Element (Block ty) -> a -> a) -> a -> Block ty -> a Source #

foldr' :: (Element (Block ty) -> a -> a) -> a -> Block ty -> a Source #

PrimType ty => IndexedCollection (Block ty) Source # 

Methods

(!) :: Block ty -> Offset (Element (Block ty)) -> Maybe (Element (Block ty)) Source #

findIndex :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Offset (Element (Block ty))) Source #

PrimType ty => Sequential (Block ty) Source # 

Methods

take :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

revTake :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

drop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

revDrop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

splitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source #

revSplitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source #

splitOn :: (Element (Block ty) -> Bool) -> Block ty -> [Block ty] Source #

break :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

breakElem :: Element (Block ty) -> Block ty -> (Block ty, Block ty) Source #

takeWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

dropWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

intersperse :: Element (Block ty) -> Block ty -> Block ty Source #

intercalate :: Element (Block ty) -> Block ty -> Element (Block ty) Source #

span :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

filter :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

partition :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

reverse :: Block ty -> Block ty Source #

uncons :: Block ty -> Maybe (Element (Block ty), Block ty) Source #

unsnoc :: Block ty -> Maybe (Block ty, Element (Block ty)) Source #

snoc :: Block ty -> Element (Block ty) -> Block ty Source #

cons :: Element (Block ty) -> Block ty -> Block ty Source #

find :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Element (Block ty)) Source #

sortBy :: (Element (Block ty) -> Element (Block ty) -> Ordering) -> Block ty -> Block ty Source #

singleton :: Element (Block ty) -> Block ty Source #

head :: NonEmpty (Block ty) -> Element (Block ty) Source #

last :: NonEmpty (Block ty) -> Element (Block ty) Source #

tail :: NonEmpty (Block ty) -> Block ty Source #

init :: NonEmpty (Block ty) -> Block ty Source #

replicate :: CountOf (Element (Block ty)) -> Element (Block ty) -> Block ty Source #

isPrefixOf :: Block ty -> Block ty -> Bool Source #

isSuffixOf :: Block ty -> Block ty -> Bool Source #

isInfixOf :: Block ty -> Block ty -> Bool Source #

type Item (Block ty) Source # 
type Item (Block ty) = ty
type Element (Block ty) Source # 
type Element (Block ty) = ty

data MutableBlock ty st Source #

A Mutable block of memory containing unpacked bytes representing values of type ty

Instances

PrimType ty => MutableCollection (MutableBlock ty) Source # 
type MutableFreezed (MutableBlock ty) Source # 
type MutableKey (MutableBlock ty) Source # 
type MutableValue (MutableBlock ty) Source # 
type MutableValue (MutableBlock ty) = ty