store-core-0.4.4.1: Fast and lightweight binary serialization

Safe HaskellNone
LanguageHaskell2010

Data.Store.Core

Contents

Synopsis

Core Types

newtype Poke a Source #

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.

Constructors

Poke 

Fields

  • runPoke :: PokeState -> Offset -> IO (Offset, a)

    Run the Poke action, with the Ptr to the buffer where data is poked, and the current Offset. The result is the new offset, along with a return value.

    May throw a PokeException, though this should be avoided when possible. They usually indicate a programming error.

Instances
Monad Poke Source # 
Instance details

Defined in Data.Store.Core

Methods

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

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

return :: a -> Poke a #

fail :: String -> Poke a #

Functor Poke Source # 
Instance details

Defined in Data.Store.Core

Methods

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

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

MonadFail Poke Source # 
Instance details

Defined in Data.Store.Core

Methods

fail :: String -> Poke a #

Applicative Poke Source # 
Instance details

Defined in Data.Store.Core

Methods

pure :: a -> Poke a #

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

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

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

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

MonadIO Poke Source # 
Instance details

Defined in Data.Store.Core

Methods

liftIO :: IO a -> Poke a #

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.

pokeException :: Text -> Poke a Source #

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

newtype Peek a Source #

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.

Constructors

Peek 

Fields

Instances
Monad Peek Source # 
Instance details

Defined in Data.Store.Core

Methods

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

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

return :: a -> Peek a #

fail :: String -> Peek a #

Functor Peek Source # 
Instance details

Defined in Data.Store.Core

Methods

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

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

MonadFail Peek Source # 
Instance details

Defined in Data.Store.Core

Methods

fail :: String -> Peek a #

Applicative Peek Source # 
Instance details

Defined in Data.Store.Core

Methods

pure :: a -> Peek a #

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

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

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

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

MonadIO Peek Source # 
Instance details

Defined in Data.Store.Core

Methods

liftIO :: IO a -> Peek a #

PrimMonad Peek Source # 
Instance details

Defined in Data.Store.Core

Associated Types

type PrimState Peek :: Type #

Methods

primitive :: (State# (PrimState Peek) -> (#State# (PrimState Peek), a#)) -> Peek a #

type PrimState Peek Source # 
Instance details

Defined in Data.Store.Core

data PeekResult a Source #

A result of a Peek action containing the current Ptr and a return value.

Constructors

PeekResult !(Ptr Word8) !a 
Instances
Functor PeekResult Source # 
Instance details

Defined in Data.Store.Core

Methods

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

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

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.

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

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

data PokeState Source #

Holds a pokeStatePtr, which is passed in to each Poke action. If the package is built with the 'force-alignment' flag, this also has a hidden Ptr field, which is used as scratch space during unaligned writes.

data PeekState Source #

Holds a peekStatePtr, which is passed in to each Peek action. If the package is built with the 'force-alignment' flag, this also has a hidden Ptr field, which is used as scratch space during unaligned reads.

type Offset = Int Source #

How far into the given Ptr to look

Encode ByteString

unsafeEncodeWith :: Poke () -> Int -> ByteString Source #

Given a Poke and its length, uses it to fill a ByteString

This function is unsafe because the provided length must exactly match the number of bytes used by the Poke. It will throw PokeException errors when the buffer is under or overshot. However, in the case of overshooting the buffer, memory corruption and segfaults may occur.

Decode ByteString

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.

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.

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.

decodeIOWithFromPtr :: Peek a -> Ptr Word8 -> Int -> IO a Source #

Like decodeIOWith, but using Ptr and length instead of a ByteString.

decodeIOPortionWithFromPtr :: Peek a -> Ptr Word8 -> Int -> IO (Offset, a) Source #

Like decodeIOPortionWith, but using Ptr and length instead of a ByteString.

Storable

pokeStorable :: Storable a => a -> Poke () Source #

A poke implementation based on an instance of Storable.

peekStorable :: forall a. (Storable a, Typeable a) => Peek a Source #

A peek implementation based on an instance of Storable and Typeable.

peekStorableTy :: forall a. Storable a => String -> Peek a Source #

A peek implementation based on an instance of Storable. Use this if the type is not Typeable.

ForeignPtr

pokeFromForeignPtr :: ForeignPtr a -> Int -> Int -> Poke () Source #

Copy a section of memory, based on a ForeignPtr, to the output. Note that this operation is unsafe, the offset and length parameters are not checked.

peekToPlainForeignPtr :: String -> Int -> Peek (ForeignPtr a) Source #

Allocate a plain ForeignPtr (no finalizers), of the specified length and fill it with bytes from the input.

pokeFromPtr :: Ptr a -> Int -> Int -> Poke () Source #

Copy a section of memory, based on a Ptr, to the output. Note that this operation is unsafe, because the offset and length parameters are not checked.

ByteArray

pokeFromByteArray :: ByteArray# -> Int -> Int -> Poke () Source #

Copy a section of memory, based on a ByteArray#, to the output. Note that this operation is unsafe, because the offset and length parameters are not checked.

peekToByteArray :: String -> Int -> Peek ByteArray Source #

Allocate a ByteArray of the specified length and fill it with bytes from the input.

Creation of PokeState / PeekState

unsafeMakePokeState Source #

Arguments

:: Ptr Word8

pokeStatePtr

-> IO (Ptr Word8)

action to produce pokeStateAlignPtr

-> IO PokeState 

Make a PokeState from a buffer pointer.

The first argument is a pointer to the memory to write to. The second argument is an IO action which is invoked if the store-core package was built with the force-alignment flag. The action should yield a pointer to scratch memory as large as maybeAlignmentBufferSize.

Since 0.4.2

unsafeMakePeekState Source #

Arguments

:: Ptr Word8

peekStateEndPtr

-> IO (Ptr Word8)

action to produce peekStateAlignPtr

-> IO PeekState 

Make a PeekState from a buffer pointer.

The first argument is a pointer to the memory to write to. The second argument is an IO action which is invoked if the store-core package was built with the force-alignment flag. The action should yield a pointer to scratch memory as large as maybeAlignmentBufferSize.

Since 0.4.2

maybeAlignmentBufferSize :: Maybe Int Source #

If store-core is built with the force-alignment flag, then this will be a Just value indicating the amount of memory that is expected in the alignment buffer used by PeekState and PokeState. Currently this will either be Just 32 or Nothing.