store-0.4.2: Fast binary serialization

Safe HaskellNone
LanguageHaskell2010

Data.Store.Internal

Contents

Description

Internal API for the store package. The functions here which are not re-exported by Data.Store are less likely to have stable APIs.

This module also defines most of the included Store instances, for types from the base package and other commonly used packages (bytestring, containers, text, time, etc).

Synopsis

Encoding and decoding strict ByteStrings.

encode :: Store a => a -> ByteString Source #

Serializes a value to a ByteString. In order to do this, it first allocates a ByteString of the correct size (based on size), and then uses poke to fill it.

Safety of this function depends on correctness of the Store instance. If size returns a. The good news is that this isn't an issue if you use well-tested manual instances (such as those from this package) combined with auomatic definition of instances.

decode :: Store a => ByteString -> Either PeekException a Source #

Decodes a value from a ByteString. Returns an exception if there's an error while decoding, or if decoding undershoots / overshoots the end of the buffer.

decodeWith :: Peek a -> ByteString -> Either PeekException a #

Decodes a value from a ByteString, potentially throwing exceptions, and taking a Peek to run. It is an exception to not consume all input.

decodeEx :: Store a => ByteString -> a Source #

Decodes a value from a ByteString, potentially throwing exceptions. It is an exception to not consume all input.

decodeExWith :: Peek a -> ByteString -> a #

Decodes a value from a ByteString, potentially throwing exceptions, and taking a Peek to run. It is an exception to not consume all input.

decodeExPortionWith :: Peek a -> ByteString -> (Offset, a) #

Similar to decodeExWith, but it allows there to be more of the buffer remaining. The Offset of the buffer contents immediately after the decoded value is returned.

decodeIO :: Store a => ByteString -> IO a Source #

Decodes a value from a ByteString, potentially throwing exceptions. It is an exception to not consume all input.

decodeIOWith :: Peek a -> ByteString -> IO a #

Decodes a value from a ByteString, potentially throwing exceptions, and taking a Peek to run. It is an exception to not consume all input.

decodeIOPortionWith :: Peek a -> ByteString -> IO (Offset, a) #

Similar to decodeExPortionWith, but runs in the IO monad.

Store class and related types.

class Store a where Source #

The Store typeclass provides efficient serialization and deserialization to raw pointer addresses.

The peek and poke methods should be defined such that decodeEx (encode x) == x .

Methods

size :: Size a Source #

Yields the Size of the buffer, in bytes, required to store the encoded representation of the type.

Note that the correctness of this function is crucial for the safety of poke, as it does not do any bounds checking. It is the responsibility of the invoker of poke (encode and similar functions) to ensure that there's enough space in the output buffer. If poke writes beyond, then arbitrary memory can be overwritten, causing undefined behavior and segmentation faults.

poke :: a -> Poke () Source #

Serializes a value to bytes. It is the responsibility of the caller to ensure that at least the number of bytes required by size are available. These details are handled by encode and similar utilities.

peek :: Peek a Source #

Serialized a value from bytes, throwing exceptions if it encounters invalid data or runs out of input bytes.

size :: (Generic a, GStoreSize (Rep a)) => Size a Source #

Yields the Size of the buffer, in bytes, required to store the encoded representation of the type.

Note that the correctness of this function is crucial for the safety of poke, as it does not do any bounds checking. It is the responsibility of the invoker of poke (encode and similar functions) to ensure that there's enough space in the output buffer. If poke writes beyond, then arbitrary memory can be overwritten, causing undefined behavior and segmentation faults.

poke :: (Generic a, GStorePoke (Rep a)) => a -> Poke () Source #

Serializes a value to bytes. It is the responsibility of the caller to ensure that at least the number of bytes required by size are available. These details are handled by encode and similar utilities.

peek :: (Generic a, GStorePeek (Rep a)) => Peek a Source #

Serialized a value from bytes, throwing exceptions if it encounters invalid data or runs out of input bytes.

data Poke a :: * -> * #

Poke actions are useful for building sequential serializers.

They are actions which write values to bytes into memory specified by a Ptr base. The Applicative and Monad instances make it easy to write serializations, by keeping track of the Offset of the current byte. They allow you to chain Poke action such that subsequent Pokes write into subsequent portions of the output.

Instances

Monad Poke 

Methods

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

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

return :: a -> Poke a #

fail :: String -> Poke a #

Functor Poke 

Methods

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

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

MonadFail Poke 

Methods

fail :: String -> Poke a #

Applicative Poke 

Methods

pure :: a -> Poke a #

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

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

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

MonadIO Poke 

Methods

liftIO :: IO a -> Poke a #

data Peek a :: * -> * #

Peek actions are useful for building sequential deserializers.

They are actions which read from memory and construct values from it. The Applicative and Monad instances make it easy to chain these together to get more complicated deserializers. This machinery keeps track of the current Ptr and end-of-buffer Ptr.

Instances

Monad Peek 

Methods

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

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

return :: a -> Peek a #

fail :: String -> Peek a #

Functor Peek 

Methods

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

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

MonadFail Peek 

Methods

fail :: String -> Peek a #

Applicative Peek 

Methods

pure :: a -> Peek a #

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

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

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

MonadIO Peek 

Methods

liftIO :: IO a -> Peek a #

PrimMonad Peek 

Associated Types

type PrimState (Peek :: * -> *) :: * #

type PrimState Peek 

runPeek :: Peek a -> PeekState -> Ptr Word8 -> IO (PeekResult a) #

Run the Peek action, with a Ptr to the end of the buffer where data is poked, and a Ptr to the current position. The result is the Ptr, along with a return value.

May throw a PeekException if the memory contains invalid values.

Exceptions thrown by Poke

data PokeException :: * #

Exception thrown while running poke. Note that other types of exceptions could also be thrown. Invocations of fail in the Poke monad causes this exception to be thrown.

PokeExceptions are not expected to occur in ordinary circumstances, and usually indicate a programming error.

pokeException :: Text -> Poke a #

Throws a PokeException. These should be avoided when possible, they usually indicate a programming error.

Exceptions thrown by Peek

data PeekException :: * #

Exception thrown while running peek. Note that other types of exceptions can also be thrown. Invocations of fail in the Poke monad causes this exception to be thrown.

PeekException is thrown when the data being decoded is invalid.

tooManyBytes :: Int -> Int -> String -> IO void #

Throws a PeekException about an attempt to read too many bytes.

Size type

data Size a Source #

Info about a type's serialized length. Either the length is known independently of the value, or the length depends on the value.

Constructors

VarSize (a -> Int) 
ConstSize !Int 

Instances

Contravariant Size Source # 

Methods

contramap :: (a -> b) -> Size b -> Size a #

(>$) :: b -> Size b -> Size a #

getSize :: Store a => a -> Int Source #

Get the number of bytes needed to store the given value. See size.

getSizeWith :: Size a -> a -> Int Source #

Given a Size value and a value of the type a, returns its Int size.

combineSize :: forall a b c. (Store a, Store b) => (c -> a) -> (c -> b) -> Size c Source #

Create an aggregate Size by providing functions to split the input into two pieces.

If both of the types are ConstSize, the result is ConstSize and the functions will not be used.

combineSizeWith :: forall a b c. (c -> a) -> (c -> b) -> Size a -> Size b -> Size c Source #

Create an aggregate Size by providing functions to split the input into two pieces, as well as Size values to use to measure the results.

If both of the input Size values are ConstSize, the result is ConstSize and the functions will not be used.

addSize :: Int -> Size a -> Size a Source #

Adds a constant amount to a Size value.

Store instances in terms of IsSequence

sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t Source #

Implement size for an IsSequence of Store instances.

Note that many monomorphic containers have more efficient implementations (for example, via memcpy).

pokeSequence :: (IsSequence t, Store (Element t)) => t -> Poke () Source #

Implement poke for an IsSequence of Store instances.

Note that many monomorphic containers have more efficient implementations (for example, via memcpy).

peekSequence :: (IsSequence t, Store (Element t), Index t ~ Int) => Peek t Source #

Implement peek for an IsSequence of Store instances.

Note that many monomorphic containers have more efficient implementations (for example, via memcpy).

Store instances in terms of IsSet

sizeSet :: forall t. (IsSet t, Store (Element t)) => Size t Source #

Implement size for an IsSet of Store instances.

pokeSet :: (IsSet t, Store (Element t)) => t -> Poke () Source #

Implement poke for an IsSequence of Store instances.

peekSet :: (IsSet t, Store (Element t)) => Peek t Source #

Implement peek for an IsSequence of Store instances.

Store instances in terms of IsMap

sizeMap :: forall t. (Store (ContainerKey t), Store (MapValue t), IsMap t) => Size t Source #

Implement size for an IsMap of where both ContainerKey and MapValue are Store instances.

pokeMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => t -> Poke () Source #

Implement poke for an IsMap of where both ContainerKey and MapValue are Store instances.

peekMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => Peek t Source #

Implement peek for an IsMap of where both ContainerKey and MapValue are Store instances.

Utilities for ordered maps

sizeOrdMap :: forall t. (Store (ContainerKey t), Store (MapValue t), IsMap t) => Size t Source #

Like sizeMap but should only be used for ordered containers where mapToList returns an ascending list.

pokeOrdMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => t -> Poke () Source #

Like pokeMap but should only be used for ordered containers where mapToList returns an ascending list.

peekOrdMapWith Source #

Arguments

:: (Store (ContainerKey t), Store (MapValue t)) 
=> ([(ContainerKey t, MapValue t)] -> t)

A function to construct the map from an ascending list such as fromDistinctAscList.

-> Peek t 

Decode the results of pokeOrdMap using a given function to construct the map.

Store instances in terms of IArray

sizeArray :: (Ix i, IArray a e, Store i, Store e) => Size (a i e) Source #

pokeArray :: (Ix i, IArray a e, Store i, Store e) => a i e -> Poke () Source #

peekArray :: (Ix i, IArray a e, Store i, Store e) => Peek (a i e) Source #

Store instances in terms of Generic

class GStoreSize f Source #

Minimal complete definition

gsize

Instances

GStoreSize V1 Source # 

Methods

gsize :: Size (V1 a)

GStoreSize U1 Source # 

Methods

gsize :: Size (U1 a)

Store a => GStoreSize (K1 i a) Source # 

Methods

gsize :: Size (K1 i a a)

((<=) (SumArity ((:+:) a b)) 255, GStoreSizeSum 0 ((:+:) a b)) => GStoreSize ((:+:) a b) Source # 

Methods

gsize :: Size ((a :+: b) a)

(GStoreSize a, GStoreSize b) => GStoreSize ((:*:) a b) Source # 

Methods

gsize :: Size ((a :*: b) a)

GStoreSize f => GStoreSize (M1 i c f) Source # 

Methods

gsize :: Size (M1 i c f a)

class GStorePoke f Source #

Minimal complete definition

gpoke

Instances

GStorePoke V1 Source # 

Methods

gpoke :: V1 a -> Poke ()

GStorePoke U1 Source # 

Methods

gpoke :: U1 a -> Poke ()

Store a => GStorePoke (K1 i a) Source # 

Methods

gpoke :: K1 i a a -> Poke ()

((<=) (SumArity ((:+:) a b)) 255, GStorePokeSum 0 ((:+:) a b)) => GStorePoke ((:+:) a b) Source # 

Methods

gpoke :: (a :+: b) a -> Poke ()

(GStorePoke a, GStorePoke b) => GStorePoke ((:*:) a b) Source # 

Methods

gpoke :: (a :*: b) a -> Poke ()

GStorePoke f => GStorePoke (M1 i c f) Source # 

Methods

gpoke :: M1 i c f a -> Poke ()

genericPoke :: (Generic a, GStorePoke (Rep a)) => a -> Poke () Source #

class GStorePeek f Source #

Minimal complete definition

gpeek

Instances

GStorePeek V1 Source # 

Methods

gpeek :: Peek (V1 a)

GStorePeek U1 Source # 

Methods

gpeek :: Peek (U1 a)

Store a => GStorePeek (K1 i a) Source # 

Methods

gpeek :: Peek (K1 i a a)

((<=) (SumArity ((:+:) a b)) 255, GStorePeekSum 0 ((:+:) a b)) => GStorePeek ((:+:) a b) Source # 

Methods

gpeek :: Peek ((a :+: b) a)

(GStorePeek a, GStorePeek b) => GStorePeek ((:*:) a b) Source # 

Methods

gpeek :: Peek ((a :*: b) a)

GStorePeek f => GStorePeek (M1 i c f) Source # 

Methods

gpeek :: Peek (M1 i c f a)

Peek utilities

skip :: Int -> Peek () Source #

Skip n bytes forward.

isolate :: Int -> Peek a -> Peek a Source #

Isolate the input to n bytes, skipping n bytes forward. Fails if m advances the offset beyond the isolated region.

peekMagic :: (Eq a, Show a, Store a) => String -> a -> Peek () Source #

Ensure the presence of a given magic value.

Throws a PeekException if the value isn't present.

Static Size type

class KnownNat n => IsStaticSize n a where Source #

Minimal complete definition

toStaticSize

Methods

toStaticSize :: a -> Maybe (StaticSize n a) Source #

newtype StaticSize n a Source #

Constructors

StaticSize 

Fields

Instances

Eq a => Eq (StaticSize n a) Source # 

Methods

(==) :: StaticSize n a -> StaticSize n a -> Bool #

(/=) :: StaticSize n a -> StaticSize n a -> Bool #

(Data a, KnownNat n) => Data (StaticSize n a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StaticSize n a -> c (StaticSize n a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StaticSize n a) #

toConstr :: StaticSize n a -> Constr #

dataTypeOf :: StaticSize n a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (StaticSize n a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StaticSize n a)) #

gmapT :: (forall b. Data b => b -> b) -> StaticSize n a -> StaticSize n a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StaticSize n a -> r #

gmapQ :: (forall d. Data d => d -> u) -> StaticSize n a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StaticSize n a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StaticSize n a -> m (StaticSize n a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticSize n a -> m (StaticSize n a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StaticSize n a -> m (StaticSize n a) #

Ord a => Ord (StaticSize n a) Source # 

Methods

compare :: StaticSize n a -> StaticSize n a -> Ordering #

(<) :: StaticSize n a -> StaticSize n a -> Bool #

(<=) :: StaticSize n a -> StaticSize n a -> Bool #

(>) :: StaticSize n a -> StaticSize n a -> Bool #

(>=) :: StaticSize n a -> StaticSize n a -> Bool #

max :: StaticSize n a -> StaticSize n a -> StaticSize n a #

min :: StaticSize n a -> StaticSize n a -> StaticSize n a #

Show a => Show (StaticSize n a) Source # 

Methods

showsPrec :: Int -> StaticSize n a -> ShowS #

show :: StaticSize n a -> String #

showList :: [StaticSize n a] -> ShowS #

Generic (StaticSize n a) Source # 

Associated Types

type Rep (StaticSize n a) :: * -> * #

Methods

from :: StaticSize n a -> Rep (StaticSize n a) x #

to :: Rep (StaticSize n a) x -> StaticSize n a #

NFData a => NFData (StaticSize n a) Source # 

Methods

rnf :: StaticSize n a -> () #

KnownNat n => Store (StaticSize n ByteString) Source # 
type Rep (StaticSize n a) Source # 
type Rep (StaticSize n a) = D1 (MetaData "StaticSize" "Data.Store.Internal" "store-0.4.2-KsechW2Te9QIGKfijwJIuv" True) (C1 (MetaCons "StaticSize" PrefixI True) (S1 (MetaSel (Just Symbol "unStaticSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

liftStaticSize :: forall n a. (KnownNat n, Lift a) => TypeQ -> StaticSize n a -> ExpQ Source #

Orphan instances

Store Bool Source # 
Store Char Source # 
Store Double Source # 
Store Float Source # 
Store Int Source # 
Store Int8 Source # 
Store Int16 Source # 
Store Int32 Source # 
Store Int64 Source # 
Store Integer Source # 
Store Word Source # 
Store Word8 Source # 
Store Word16 Source # 
Store Word32 Source # 
Store Word64 Source # 
Store Exp Source # 
Store Match Source # 
Store Clause Source # 
Store Pat Source # 
Store Type Source # 
Store Dec Source # 
Store Name Source # 
Store FunDep Source # 
Store TyVarBndr Source # 
Store InjectivityAnn Source # 
Store Overlap Source # 
Store () Source # 

Methods

size :: Size () Source #

poke :: () -> Poke () Source #

peek :: Peek () Source #

Store Void Source # 
Store CDev Source # 
Store CIno Source # 
Store CMode Source # 
Store COff Source # 
Store CPid Source # 
Store CSsize Source # 
Store CGid Source # 
Store CNlink Source # 
Store CUid Source # 
Store CCc Source # 
Store CSpeed Source # 
Store CTcflag Source # 
Store CRLim Source # 
Store Fd Source # 

Methods

size :: Size Fd Source #

poke :: Fd -> Poke () Source #

peek :: Peek Fd Source #

Store WordPtr Source # 
Store IntPtr Source # 
Store CChar Source # 
Store CSChar Source # 
Store CUChar Source # 
Store CShort Source # 
Store CUShort Source # 
Store CInt Source # 
Store CUInt Source # 
Store CLong Source # 
Store CULong Source # 
Store CLLong Source # 
Store CULLong Source # 
Store CFloat Source # 
Store CDouble Source # 
Store CPtrdiff Source # 
Store CSize Source # 
Store CWchar Source # 
Store CSigAtomic Source # 
Store CClock Source # 
Store CTime Source # 
Store CUSeconds Source # 
Store CSUSeconds Source # 
Store CIntPtr Source # 
Store CUIntPtr Source # 
Store CIntMax Source # 
Store CUIntMax Source # 
Store All Source # 
Store Any Source # 
Store Fingerprint Source # 
Store ShortByteString Source # 
Store ByteString Source # 
Store ByteString Source # 
Store Text Source # 
Store IntSet Source # 
Store ModName Source # 
Store PkgName Source # 
Store OccName Source # 
Store NameFlavour Source # 
Store NameSpace Source # 
Store Info Source # 
Store Fixity Source # 
Store FixityDirection Source # 
Store Lit Source # 
Store Body Source # 
Store Guard Source # 
Store Stmt Source # 
Store Range Source # 
Store TypeFamilyHead Source # 
Store TySynEqn Source # 
Store Foreign Source # 
Store Callconv Source # 
Store Safety Source # 
Store Pragma Source # 
Store Inline Source # 
Store RuleMatch Source # 
Store Phases Source # 
Store RuleBndr Source # 
Store AnnTarget Source # 
Store SourceUnpackedness Source # 
Store SourceStrictness Source # 
Store Con Source # 
Store Bang Source # 
Store FamilyResultSig Source # 
Store TyLit Source # 
Store Role Source # 
Store UTCTime Source # 
Store Day Source # 
Store DiffTime Source # 
Store a => Store [a] Source # 

Methods

size :: Size [a] Source #

poke :: [a] -> Poke () Source #

peek :: Peek [a] Source #

Store a => Store (Maybe a) Source # 

Methods

size :: Size (Maybe a) Source #

poke :: Maybe a -> Poke () Source #

peek :: Peek (Maybe a) Source #

Store a => Store (Ratio a) Source # 

Methods

size :: Size (Ratio a) Source #

poke :: Ratio a -> Poke () Source #

peek :: Peek (Ratio a) Source #

Store (StablePtr a0) Source # 
Store (Ptr a0) Source # 

Methods

size :: Size (Ptr a0) Source #

poke :: Ptr a0 -> Poke () Source #

peek :: Peek (Ptr a0) Source #

Store (FunPtr a0) Source # 

Methods

size :: Size (FunPtr a0) Source #

poke :: FunPtr a0 -> Poke () Source #

peek :: Peek (FunPtr a0) Source #

Storable a0 => Store (Identity a0) Source # 

Methods

size :: Size (Identity a0) Source #

poke :: Identity a0 -> Poke () Source #

peek :: Peek (Identity a0) Source #

Store a => Store (NonEmpty a) Source # 
Store (Fixed a) Source # 

Methods

size :: Size (Fixed a) Source #

poke :: Fixed a -> Poke () Source #

peek :: Peek (Fixed a) Source #

Storable a0 => Store (Complex a0) Source # 

Methods

size :: Size (Complex a0) Source #

poke :: Complex a0 -> Poke () Source #

peek :: Peek (Complex a0) Source #

Store a => Store (Dual a) Source # 

Methods

size :: Size (Dual a) Source #

poke :: Dual a -> Poke () Source #

peek :: Peek (Dual a) Source #

Store a => Store (Sum a) Source # 

Methods

size :: Size (Sum a) Source #

poke :: Sum a -> Poke () Source #

peek :: Peek (Sum a) Source #

Store a => Store (Product a) Source # 

Methods

size :: Size (Product a) Source #

poke :: Product a -> Poke () Source #

peek :: Peek (Product a) Source #

Store a => Store (First a) Source # 

Methods

size :: Size (First a) Source #

poke :: First a -> Poke () Source #

peek :: Peek (First a) Source #

Store a => Store (Last a) Source # 

Methods

size :: Size (Last a) Source #

poke :: Last a -> Poke () Source #

peek :: Peek (Last a) Source #

Store a => Store (IntMap a) Source # 

Methods

size :: Size (IntMap a) Source #

poke :: IntMap a -> Poke () Source #

peek :: Peek (IntMap a) Source #

Store a => Store (Seq a) Source # 

Methods

size :: Size (Seq a) Source #

poke :: Seq a -> Poke () Source #

peek :: Peek (Seq a) Source #

(Store a, Ord a) => Store (Set a) Source # 

Methods

size :: Size (Set a) Source #

poke :: Set a -> Poke () Source #

peek :: Peek (Set a) Source #

(Eq a, Hashable a, Store a) => Store (HashSet a) Source # 

Methods

size :: Size (HashSet a) Source #

poke :: HashSet a -> Poke () Source #

peek :: Peek (HashSet a) Source #

Store a => Store (Vector a) Source # 

Methods

size :: Size (Vector a) Source #

poke :: Vector a -> Poke () Source #

peek :: Peek (Vector a) Source #

Storable a => Store (Vector a) Source # 

Methods

size :: Size (Vector a) Source #

poke :: Vector a -> Poke () Source #

peek :: Peek (Vector a) Source #

Store (Vector Bool) Source # 
Store (Vector Char) Source # 
Store (Vector Double) Source # 
Store (Vector Float) Source # 
Store (Vector Int) Source # 
Store (Vector Int8) Source # 
Store (Vector Int16) Source # 
Store (Vector Int32) Source # 
Store (Vector Int64) Source # 
Store (Vector Word) Source # 
Store (Vector Word8) Source # 
Store (Vector Word16) Source # 
Store (Vector Word32) Source # 
Store (Vector Word64) Source # 
Store (Vector ()) Source # 

Methods

size :: Size (Vector ()) Source #

poke :: Vector () -> Poke () Source #

peek :: Peek (Vector ()) Source #

(Store (Vector a), Store (Vector b)) => Store (Vector (a, b)) Source # 

Methods

size :: Size (Vector (a, b)) Source #

poke :: Vector (a, b) -> Poke () Source #

peek :: Peek (Vector (a, b)) Source #

(Store (Vector a), Store (Vector b), Store (Vector c)) => Store (Vector (a, b, c)) Source # 

Methods

size :: Size (Vector (a, b, c)) Source #

poke :: Vector (a, b, c) -> Poke () Source #

peek :: Peek (Vector (a, b, c)) Source #

(Store (Vector a), Store (Vector b), Store (Vector c), Store (Vector d)) => Store (Vector (a, b, c, d)) Source # 

Methods

size :: Size (Vector (a, b, c, d)) Source #

poke :: Vector (a, b, c, d) -> Poke () Source #

peek :: Peek (Vector (a, b, c, d)) Source #

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

Methods

size :: Size (Vector (a, b, c, d, e)) Source #

poke :: Vector (a, b, c, d, e) -> Poke () Source #

peek :: Peek (Vector (a, b, c, d, e)) Source #

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

Methods

size :: Size (Vector (a, b, c, d, e, f)) Source #

poke :: Vector (a, b, c, d, e, f) -> Poke () Source #

peek :: Peek (Vector (a, b, c, d, e, f)) Source #

Store (Vector a) => Store (Vector (Complex a)) Source # 
Store (Vector Char) Source # 
Store (Vector Double) Source # 
Store (Vector Float) Source # 
Store (Vector Int) Source # 
Store (Vector Int8) Source # 
Store (Vector Int16) Source # 
Store (Vector Int32) Source # 
Store (Vector Int64) Source # 
Store (Vector Word) Source # 
Store (Vector Word8) Source # 
Store (Vector Word16) Source # 
Store (Vector Word32) Source # 
Store (Vector Word64) Source # 
Store (Vector (Ptr a0)) Source # 

Methods

size :: Size (Vector (Ptr a0)) Source #

poke :: Vector (Ptr a0) -> Poke () Source #

peek :: Peek (Vector (Ptr a0)) Source #

Store (Vector (FunPtr a0)) Source # 

Methods

size :: Size (Vector (FunPtr a0)) Source #

poke :: Vector (FunPtr a0) -> Poke () Source #

peek :: Peek (Vector (FunPtr a0)) Source #

Store (Vector Addr) Source # 
(Store a, Store b) => Store (Either a b) Source # 

Methods

size :: Size (Either a b) Source #

poke :: Either a b -> Poke () Source #

peek :: Peek (Either a b) Source #

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

Methods

size :: Size (a, b) Source #

poke :: (a, b) -> Poke () Source #

peek :: Peek (a, b) Source #

(Ix i, IArray UArray e, Store i, Store e) => Store (UArray i e) Source # 

Methods

size :: Size (UArray i e) Source #

poke :: UArray i e -> Poke () Source #

peek :: Peek (UArray i e) Source #

(Ix i, Store i, Store e) => Store (Array i e) Source # 

Methods

size :: Size (Array i e) Source #

poke :: Array i e -> Poke () Source #

peek :: Peek (Array i e) Source #

(Ord k, Store k, Store a) => Store (Map k a) Source # 

Methods

size :: Size (Map k a) Source #

poke :: Map k a -> Poke () Source #

peek :: Peek (Map k a) Source #

(Eq k, Hashable k, Store k, Store a) => Store (HashMap k a) Source # 

Methods

size :: Size (HashMap k a) Source #

poke :: HashMap k a -> Poke () Source #

peek :: Peek (HashMap k a) Source #

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

Methods

size :: Size (a, b, c) Source #

poke :: (a, b, c) -> Poke () Source #

peek :: Peek (a, b, c) Source #

Storable a0 => Store (Const * a0 b0) Source # 

Methods

size :: Size (Const * a0 b0) Source #

poke :: Const * a0 b0 -> Poke () Source #

peek :: Peek (Const * a0 b0) Source #

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

Methods

size :: Size (a, b, c, d) Source #

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

peek :: Peek (a, b, c, d) Source #

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

Methods

size :: Size (a, b, c, d, e) Source #

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

peek :: Peek (a, b, c, d, e) Source #

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

Methods

size :: Size (a, b, c, d, e, f) Source #

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

peek :: Peek (a, b, c, d, e, f) Source #

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

Methods

size :: Size (a, b, c, d, e, f, g) Source #

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

peek :: Peek (a, b, c, d, e, f, g) Source #