| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Streamly.Internal.Data.Unboxed
Description
Synopsis
- class Unbox a where- sizeOf :: Proxy a -> Int
- peekByteIndex :: Int -> MutableByteArray -> IO a
- pokeByteIndex :: Int -> MutableByteArray -> a -> IO ()
 
- peekWith :: Unbox a => MutableByteArray -> Int -> IO a
- pokeWith :: Unbox a => MutableByteArray -> Int -> a -> IO ()
- data MutableByteArray = MutableByteArray (MutableByteArray# RealWorld)
- touch :: MutableByteArray -> IO ()
- getMutableByteArray# :: MutableByteArray -> MutableByteArray# RealWorld
- pin :: MutableByteArray -> IO MutableByteArray
- unpin :: MutableByteArray -> IO MutableByteArray
- newUnpinnedBytes :: Int -> IO MutableByteArray
- newPinnedBytes :: Int -> IO MutableByteArray
- newAlignedPinnedBytes :: Int -> Int -> IO MutableByteArray
- nil :: MutableByteArray
- data BoundedPtr = BoundedPtr MutableByteArray Int Int
- newtype Peeker a = Peeker (Builder BoundedPtr IO a)
- read :: Unbox a => Peeker a
- readUnsafe :: Unbox a => Peeker a
- skipByte :: Peeker ()
- runPeeker :: Peeker a -> BoundedPtr -> IO a
- pokeBoundedPtrUnsafe :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
- pokeBoundedPtr :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr
- genericSizeOf :: forall a. SizeOfRep (Rep a) => Proxy a -> Int
- genericPeekByteIndex :: (Generic a, PeekRep (Rep a)) => MutableByteArray -> Int -> IO a
- genericPokeByteIndex :: (Generic a, PokeRep (Rep a)) => MutableByteArray -> Int -> a -> IO ()
- class PeekRep (f :: Type -> Type) where
- class PokeRep (f :: Type -> Type) where- pokeRep :: f a -> BoundedPtr -> IO BoundedPtr
 
- class SizeOfRep (f :: Type -> Type) where
Documentation
A type implementing the Unbox interface supplies operations for reading
 and writing the type from and to a mutable byte array (an unboxed
 representation of the type) in memory. The read operation peekByteIndex
 deserializes the boxed type from the mutable byte array. The write operation
 pokeByteIndex serializes the boxed type to the mutable byte array.
Instances can be derived via Generic. Note that the data type must be
 non-recursive. Here is an example, for deriving an instance of this type
 class.
>>>import GHC.Generics (Generic)>>>:{data Object = Object { _int0 :: Int , _int1 :: Int } deriving Generic :}
WARNING! Generic deriving hangs for recursive data types.
>>>import Streamly.Data.Array (Unbox(..))>>>instance Unbox Object
If you want to write the instance manually:
>>>:{instance Unbox Object where sizeOf _ = 16 peekByteIndex i arr = do x0 <- peekByteIndex i arr x1 <- peekByteIndex (i + 8) arr return $ Object x0 x1 pokeByteIndex i arr (Object x0 x1) = do pokeByteIndex i arr x0 pokeByteIndex (i + 8) arr x1 :}
Minimal complete definition
Nothing
Methods
sizeOf :: Proxy a -> Int Source #
Get the size. Size cannot be zero.
peekByteIndex :: Int -> MutableByteArray -> IO a Source #
Read an element of type "a" from a MutableByteArray given the byte index.
IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.
default peekByteIndex :: (Generic a, PeekRep (Rep a)) => Int -> MutableByteArray -> IO a Source #
pokeByteIndex :: Int -> MutableByteArray -> a -> IO () Source #
Write an element of type "a" to a MutableByteArray given the byte index.
IMPORTANT: The implementation of this interface may not check the bounds of the array, the caller must not assume that.
default pokeByteIndex :: (Generic a, PokeRep (Rep a)) => Int -> MutableByteArray -> a -> IO () Source #
Instances
data MutableByteArray Source #
Constructors
| MutableByteArray (MutableByteArray# RealWorld) | 
touch :: MutableByteArray -> IO () Source #
pin :: MutableByteArray -> IO MutableByteArray Source #
newUnpinnedBytes :: Int -> IO MutableByteArray Source #
newPinnedBytes :: Int -> IO MutableByteArray Source #
newAlignedPinnedBytes :: Int -> Int -> IO MutableByteArray Source #
Type Parser and Builder
data BoundedPtr Source #
A location inside a mutable byte array with the bound of the array. Is it cheaper to just get the bound using the size of the array whenever needed?
Constructors
| BoundedPtr MutableByteArray Int Int | 
Chains peek functions that pass the current position to the next function
Constructors
| Peeker (Builder BoundedPtr IO a) | 
readUnsafe :: Unbox a => Peeker a Source #
pokeBoundedPtrUnsafe :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr Source #
pokeBoundedPtr :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr Source #
Generic Unbox instances
genericPeekByteIndex :: (Generic a, PeekRep (Rep a)) => MutableByteArray -> Int -> IO a Source #
genericPokeByteIndex :: (Generic a, PokeRep (Rep a)) => MutableByteArray -> Int -> a -> IO () Source #
class PeekRep (f :: Type -> Type) where Source #
Instances
| PeekRep (V1 :: Type -> Type) Source # | |
| PeekRep (U1 :: Type -> Type) Source # | |
| Unbox a => PeekRep (K1 i a :: Type -> Type) Source # | |
| (MaxArity256 (SumArity (f :+: g)), PeekRepSum 0 (f :+: g)) => PeekRep (f :+: g) Source # | |
| (PeekRep f, PeekRep g) => PeekRep (f :*: g) Source # | |
| PeekRep f => PeekRep (M1 i c f) Source # | |
class PokeRep (f :: Type -> Type) where Source #
Methods
pokeRep :: f a -> BoundedPtr -> IO BoundedPtr Source #
Instances
| PokeRep (V1 :: Type -> Type) Source # | |
| Defined in Streamly.Internal.Data.Unboxed Methods pokeRep :: V1 a -> BoundedPtr -> IO BoundedPtr Source # | |
| PokeRep (U1 :: Type -> Type) Source # | |
| Defined in Streamly.Internal.Data.Unboxed Methods pokeRep :: U1 a -> BoundedPtr -> IO BoundedPtr Source # | |
| Unbox a => PokeRep (K1 i a :: Type -> Type) Source # | |
| Defined in Streamly.Internal.Data.Unboxed Methods pokeRep :: K1 i a a0 -> BoundedPtr -> IO BoundedPtr Source # | |
| (MaxArity256 (SumArity (f :+: g)), PokeRepSum 0 (f :+: g)) => PokeRep (f :+: g) Source # | |
| Defined in Streamly.Internal.Data.Unboxed Methods pokeRep :: (f :+: g) a -> BoundedPtr -> IO BoundedPtr Source # | |
| (PokeRep f, PokeRep g) => PokeRep (f :*: g) Source # | |
| Defined in Streamly.Internal.Data.Unboxed Methods pokeRep :: (f :*: g) a -> BoundedPtr -> IO BoundedPtr Source # | |
| PokeRep f => PokeRep (M1 i c f) Source # | |
| Defined in Streamly.Internal.Data.Unboxed Methods pokeRep :: M1 i c f a -> BoundedPtr -> IO BoundedPtr Source # | |
class SizeOfRep (f :: Type -> Type) where Source #
Implementation of sizeOf that works on the generic representation of an ADT.
Instances
| SizeOfRep (V1 :: Type -> Type) Source # | |
| SizeOfRep (U1 :: Type -> Type) Source # | |
| Unbox a => SizeOfRep (K1 i a :: Type -> Type) Source # | |
| (MaxArity256 (SumArity (f :+: g)), SizeOfRepSum f, SizeOfRepSum g) => SizeOfRep (f :+: g) Source # | |
| (SizeOfRep f, SizeOfRep g) => SizeOfRep (f :*: g) Source # | |
| SizeOfRep f => SizeOfRep (M1 i c f) Source # | |