store-0.4.3: Fast binary serialization

Safe HaskellNone
LanguageHaskell2010

Data.Store

Contents

Description

This is the main public API of the store package. The functions exported here are more likely to be stable between versions.

Usually you won't need to write your own Store instances, and instead can rely on either using the Generic deriving approach or Data.Store.TH for defining Store instances for your datatypes. There are some tradeoffs here - the generics instances do not require -XTemplateHaskell, but they do not optimize as well for sum types that only require a constant number of bytes.

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 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 #

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 

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

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)

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.