store-0.1.0.1: 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.

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 Source

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 Source

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) Source

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 Source

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) Source

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 .

Minimal complete definition

Nothing

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.

runPeek :: Peek a -> forall byte. Ptr byte -> Ptr byte -> IO (Ptr byte, a) Source

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.

Exceptions thrown by Poke

data PokeException Source

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.

Constructors

PokeException 

Fields

pokeExByteIndex :: Offset
 
pokeExMessage :: Text
 

Exceptions thrown by Peek

data PeekException Source

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.

Constructors

PeekException 

Fields

peekExBytesFromEnd :: Offset
 
peekExMessage :: Text
 

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

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 

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

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

contramapSize :: (a -> b) -> Size b -> Size a Source

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

combineSize' :: forall a b c. (c -> a) -> (c -> b) -> Size a -> Size b -> Size c Source

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

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.

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.

Static Size type

class KnownNat n => IsStaticSize n a where Source

Methods

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

newtype StaticSize n a Source

Constructors

StaticSize 

Fields

unStaticSize :: a
 

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