| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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.
If you need streaming encode / decode of multiple store encoded
messages, take a look at the store-streaming package.
Gotchas
Store is best used for communication between trusted processes and local caches. It can certainly be used for other purposes, but the builtin set of instances have some gotchas to be aware of:
- Store's builtin instances serialize in a format which depends on machine endianness.
- Store's builtin instances trust the data when deserializing. For
example, the deserialization of
Vectorwill read the vector's link from the first 8 bytes. It will then allocate enough memory to store all the elements. Malicious or malformed input could cause allocation of large amounts of memory. See https://github.com/fpco/store/issues/122
Synopsis
- encode :: Store a => a -> ByteString
- decode :: Store a => ByteString -> Either PeekException a
- decodeWith :: Peek a -> ByteString -> Either PeekException a
- decodeEx :: Store a => ByteString -> a
- decodeExWith :: Peek a -> ByteString -> a
- decodeExPortionWith :: Peek a -> ByteString -> (Offset, a)
- decodeIO :: Store a => ByteString -> IO a
- decodeIOWith :: Peek a -> ByteString -> IO a
- decodeIOPortionWith :: Peek a -> ByteString -> IO (Offset, a)
- class Store a where
- data Size a
- data Poke a
- data Peek a
- class GStoreSize f
- class GStorePoke f
- class GStorePeek f
- data PeekException = PeekException {}
- peekException :: Text -> Peek a
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.
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
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.
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.
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.
Instances
Info about a type's serialized length. Either the length is known independently of the value, or the length depends on the value.
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 | |
| Functor Poke | |
| MonadFail Poke | |
Defined in Data.Store.Core | |
| Applicative Poke | |
| MonadIO Poke | |
Defined in Data.Store.Core | |
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 | |
| Functor Peek | |
| MonadFail Peek | |
Defined in Data.Store.Core | |
| Applicative Peek | |
| MonadIO Peek | |
Defined in Data.Store.Core | |
| PrimMonad Peek | |
| type PrimState Peek | |
Defined in Data.Store.Core | |
class GStoreSize f Source #
Minimal complete definition
gsize
Instances
| GStoreSize (V1 :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| GStoreSize (U1 :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| Store a => GStoreSize (K1 i a :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| (FitsInByte (SumArity (a :+: b)), GStoreSizeSum 0 (a :+: b)) => GStoreSize (a :+: b) Source # | |
Defined in Data.Store.Impl | |
| (GStoreSize a, GStoreSize b) => GStoreSize (a :*: b) Source # | |
Defined in Data.Store.Impl | |
| GStoreSize f => GStoreSize (M1 i c f) Source # | |
Defined in Data.Store.Impl | |
class GStorePoke f Source #
Minimal complete definition
gpoke
Instances
| GStorePoke (V1 :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| GStorePoke (U1 :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| Store a => GStorePoke (K1 i a :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| (FitsInByte (SumArity (a :+: b)), GStorePokeSum 0 (a :+: b)) => GStorePoke (a :+: b) Source # | |
Defined in Data.Store.Impl | |
| (GStorePoke a, GStorePoke b) => GStorePoke (a :*: b) Source # | |
Defined in Data.Store.Impl | |
| GStorePoke f => GStorePoke (M1 i c f) Source # | |
Defined in Data.Store.Impl | |
class GStorePeek f Source #
Minimal complete definition
gpeek
Instances
| GStorePeek (V1 :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| GStorePeek (U1 :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| Store a => GStorePeek (K1 i a :: Type -> Type) Source # | |
Defined in Data.Store.Impl | |
| (FitsInByte (SumArity (a :+: b)), GStorePeekSum 0 (a :+: b)) => GStorePeek (a :+: b) Source # | |
Defined in Data.Store.Impl | |
| (GStorePeek a, GStorePeek b) => GStorePeek (a :*: b) Source # | |
Defined in Data.Store.Impl | |
| GStorePeek f => GStorePeek (M1 i c f) Source # | |
Defined in Data.Store.Impl | |
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.
Constructors
| PeekException | |
Fields | |
Instances
| Eq PeekException | |
Defined in Data.Store.Core Methods (==) :: PeekException -> PeekException -> Bool # (/=) :: PeekException -> PeekException -> Bool # | |
| Show PeekException | |
Defined in Data.Store.Core Methods showsPrec :: Int -> PeekException -> ShowS # show :: PeekException -> String # showList :: [PeekException] -> ShowS # | |
| Exception PeekException | |
Defined in Data.Store.Core Methods toException :: PeekException -> SomeException # fromException :: SomeException -> Maybe PeekException # displayException :: PeekException -> String # | |
peekException :: Text -> Peek a #
Throws a PeekException.