streamly-core-0.1.0: Streaming, parsers, arrays and more
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Unboxed

Description

 
Synopsis

Documentation

class Unbox a where Source #

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.

default sizeOf :: SizeOfRep (Rep a) => Proxy a -> Int Source #

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

Instances details
Unbox IntPtr Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox WordPtr Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Fingerprint Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox IoSubSystem Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word16 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word32 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word64 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word8 Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox MicroSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox MilliSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox NanoSecond64 Source # 
Instance details

Defined in Streamly.Internal.Data.Time.Units

Unbox () Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Bool Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Char Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Double Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Float Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Int Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox Word Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Complex a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Identity a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Down a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox (FunPtr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox (Ptr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Ratio a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox (StablePtr a) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Unbox a => Unbox (Const a b) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

pokeWith :: Unbox a => MutableByteArray -> Int -> a -> IO () 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?

newtype Peeker a Source #

Chains peek functions that pass the current position to the next function

Constructors

Peeker (Builder BoundedPtr IO a) 

Instances

Instances details
Applicative Peeker Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

pure :: a -> Peeker a #

(<*>) :: Peeker (a -> b) -> Peeker a -> Peeker b #

liftA2 :: (a -> b -> c) -> Peeker a -> Peeker b -> Peeker c #

(*>) :: Peeker a -> Peeker b -> Peeker b #

(<*) :: Peeker a -> Peeker b -> Peeker a #

Functor Peeker Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

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

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

Monad Peeker Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

(>>=) :: Peeker a -> (a -> Peeker b) -> Peeker b #

(>>) :: Peeker a -> Peeker b -> Peeker b #

return :: a -> Peeker a #

pokeBoundedPtr :: forall a. Unbox a => a -> BoundedPtr -> IO BoundedPtr Source #

Generic Unbox instances

genericSizeOf :: forall a. SizeOfRep (Rep a) => Proxy a -> Int Source #

class PeekRep (f :: Type -> Type) where Source #

Methods

peekRep :: Peeker (f x) Source #

Instances

Instances details
PeekRep (U1 :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

peekRep :: Peeker (U1 x) Source #

PeekRep (V1 :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

peekRep :: Peeker (V1 x) Source #

(PeekRep f, PeekRep g) => PeekRep (f :*: g) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

peekRep :: Peeker ((f :*: g) x) Source #

(MaxArity256 (SumArity (f :+: g)), PeekRepSum 0 (f :+: g)) => PeekRep (f :+: g) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

peekRep :: Peeker ((f :+: g) x) Source #

Unbox a => PeekRep (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

peekRep :: Peeker (K1 i a x) Source #

PeekRep f => PeekRep (M1 i c f) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

peekRep :: Peeker (M1 i c f x) Source #

class PokeRep (f :: Type -> Type) where Source #

Methods

pokeRep :: f a -> BoundedPtr -> IO BoundedPtr Source #

Instances

Instances details
PokeRep (U1 :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

PokeRep (V1 :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

(PokeRep f, PokeRep g) => PokeRep (f :*: g) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

pokeRep :: (f :*: g) a -> BoundedPtr -> IO BoundedPtr Source #

(MaxArity256 (SumArity (f :+: g)), PokeRepSum 0 (f :+: g)) => PokeRep (f :+: g) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

pokeRep :: (f :+: g) a -> BoundedPtr -> IO BoundedPtr Source #

Unbox a => PokeRep (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

pokeRep :: K1 i a a0 -> BoundedPtr -> IO BoundedPtr Source #

PokeRep f => PokeRep (M1 i c f) Source # 
Instance details

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.

Methods

sizeOfRep :: f x -> Int Source #

Instances

Instances details
SizeOfRep (U1 :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

sizeOfRep :: U1 x -> Int Source #

SizeOfRep (V1 :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

sizeOfRep :: V1 x -> Int Source #

(SizeOfRep f, SizeOfRep g) => SizeOfRep (f :*: g) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

sizeOfRep :: (f :*: g) x -> Int Source #

(MaxArity256 (SumArity (f :+: g)), SizeOfRepSum f, SizeOfRepSum g) => SizeOfRep (f :+: g) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

sizeOfRep :: (f :+: g) x -> Int Source #

Unbox a => SizeOfRep (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

sizeOfRep :: K1 i a x -> Int Source #

SizeOfRep f => SizeOfRep (M1 i c f) Source # 
Instance details

Defined in Streamly.Internal.Data.Unboxed

Methods

sizeOfRep :: M1 i c f x -> Int Source #