Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Store.Internal
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
- 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 Poke a
- data Peek a
- runPeek :: Peek a -> PeekState -> Ptr Word8 -> IO (PeekResult a)
- data PokeException = PokeException {
- pokeExByteIndex :: Offset
- pokeExMessage :: Text
- pokeException :: Text -> Poke a
- data PeekException = PeekException {
- peekExBytesFromEnd :: Offset
- peekExMessage :: Text
- peekException :: Text -> Peek a
- tooManyBytes :: Int -> Int -> String -> IO void
- data Size a
- getSize :: Store a => a -> Int
- getSizeWith :: Size a -> a -> Int
- combineSize :: forall a b c. (Store a, Store b) => (c -> a) -> (c -> b) -> Size c
- combineSizeWith :: forall a b c. (c -> a) -> (c -> b) -> Size a -> Size b -> Size c
- addSize :: Int -> Size a -> Size a
- sizeSequence :: forall t. (IsSequence t, Store (Element t)) => Size t
- pokeSequence :: (IsSequence t, Store (Element t)) => t -> Poke ()
- peekSequence :: (IsSequence t, Store (Element t), Index t ~ Int) => Peek t
- sizeSet :: forall t. (IsSet t, Store (Element t)) => Size t
- pokeSet :: (IsSet t, Store (Element t)) => t -> Poke ()
- peekSet :: (IsSet t, Store (Element t)) => Peek t
- sizeMap :: forall t. (Store (ContainerKey t), Store (MapValue t), IsMap t) => Size t
- pokeMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => t -> Poke ()
- peekMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => Peek t
- sizeOrdMap :: forall t. (Store (ContainerKey t), Store (MapValue t), IsMap t) => Size t
- pokeOrdMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => t -> Poke ()
- peekOrdMapWith :: (Store (ContainerKey t), Store (MapValue t)) => ([(ContainerKey t, MapValue t)] -> t) -> Peek t
- sizeArray :: (Ix i, IArray a e, Store i, Store e) => Size (a i e)
- pokeArray :: (Ix i, IArray a e, Store i, Store e) => a i e -> Poke ()
- peekArray :: (Ix i, IArray a e, Store i, Store e) => Peek (a i e)
- class GStoreSize f
- genericSize :: (Generic a, GStoreSize (Rep a)) => Size a
- class GStorePoke f
- genericPoke :: (Generic a, GStorePoke (Rep a)) => a -> Poke ()
- class GStorePeek f
- genericPeek :: (Generic a, GStorePeek (Rep a)) => Peek a
- skip :: Int -> Peek ()
- isolate :: Int -> Peek a -> Peek a
- peekMagic :: (Eq a, Show a, Store a) => String -> a -> Peek ()
- class KnownNat n => IsStaticSize n a where
- toStaticSize :: a -> Maybe (StaticSize n a)
- newtype StaticSize (n :: Nat) a = StaticSize {
- unStaticSize :: a
- toStaticSizeEx :: IsStaticSize n a => a -> StaticSize n a
- liftStaticSize :: forall n a. (KnownNat n, Lift a) => TypeQ -> StaticSize n a -> ExpQ
- staticByteStringExp :: ByteString -> ExpQ
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 #
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 #
decodeExPortionWith :: Peek a -> ByteString -> (Offset, a) #
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 #
decodeIOPortionWith :: Peek a -> ByteString -> IO (Offset, a) #
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
Exceptions thrown by Poke
data PokeException #
Constructors
PokeException | |
Fields
|
Instances
Eq PokeException | |
Defined in Data.Store.Core Methods (==) :: PokeException -> PokeException -> Bool Source # (/=) :: PokeException -> PokeException -> Bool Source # | |
Show PokeException | |
Defined in Data.Store.Core | |
Exception PokeException | |
Defined in Data.Store.Core Methods toException :: PokeException -> SomeException Source # fromException :: SomeException -> Maybe PokeException Source # |
pokeException :: Text -> Poke a #
Exceptions thrown by Peek
data PeekException #
Constructors
PeekException | |
Fields
|
Instances
Eq PeekException | |
Defined in Data.Store.Core Methods (==) :: PeekException -> PeekException -> Bool Source # (/=) :: PeekException -> PeekException -> Bool Source # | |
Show PeekException | |
Defined in Data.Store.Core | |
Exception PeekException | |
Defined in Data.Store.Core Methods toException :: PeekException -> SomeException Source # fromException :: SomeException -> Maybe PeekException Source # |
peekException :: Text -> Peek a #
Size type
Info about a type's serialized length. Either the length is known independently of the value, or the length depends on the value.
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 #
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
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 #
pokeOrdMap :: (Store (ContainerKey t), Store (MapValue t), IsMap t) => t -> Poke () 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
|
-> Peek t |
Decode the results of pokeOrdMap
using a given function to construct
the map.
Store instances in terms of IArray
Store instances in terms of Generic
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 |
genericSize :: (Generic a, GStoreSize (Rep a)) => Size a Source #
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 |
genericPoke :: (Generic a, GStorePoke (Rep a)) => a -> Poke () Source #
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 |
genericPeek :: (Generic a, GStorePeek (Rep a)) => Peek a Source #
Peek utilities
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 #
Methods
toStaticSize :: a -> Maybe (StaticSize n a) Source #
Instances
KnownNat n => IsStaticSize n ByteString Source # | |
Defined in Data.Store.Internal Methods toStaticSize :: ByteString -> Maybe (StaticSize n ByteString) Source # |
newtype StaticSize (n :: Nat) a Source #
Constructors
StaticSize | |
Fields
|
Instances
toStaticSizeEx :: IsStaticSize n a => a -> StaticSize n a Source #
liftStaticSize :: forall n a. (KnownNat n, Lift a) => TypeQ -> StaticSize n a -> ExpQ Source #
staticByteStringExp :: ByteString -> ExpQ Source #