persist-state-0.2.0.0: Serialization library with state and leb128 encoding

Safe HaskellNone
LanguageHaskell2010

Data.PersistState

Contents

Synopsis

The Persist class

class Persist s t where Source #

Minimal complete definition

Nothing

Methods

put :: t -> Put s () Source #

Encode a value in the Put monad.

get :: Get s t Source #

Decode a value in the Get monad

put :: (Generic t, GPersistPut s (Rep t)) => t -> Put s () Source #

Encode a value in the Put monad.

get :: (Generic t, GPersistGet s (Rep t)) => Get s t Source #

Decode a value in the Get monad

Instances
Persist s IntSet Source # 
Instance details

Defined in Data.PersistState

Methods

put :: IntSet -> Put s () Source #

get :: Get s IntSet Source #

Persist s ShortByteString Source # 
Instance details

Defined in Data.PersistState

Persist s ByteString Source # 
Instance details

Defined in Data.PersistState

Methods

put :: ByteString -> Put s () Source #

get :: Get s ByteString Source #

Persist s ByteString Source # 
Instance details

Defined in Data.PersistState

Methods

put :: ByteString -> Put s () Source #

get :: Get s ByteString Source #

Persist s Any Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Any -> Put s () Source #

get :: Get s Any Source #

Persist s All Source # 
Instance details

Defined in Data.PersistState

Methods

put :: All -> Put s () Source #

get :: Get s All Source #

Persist s Ordering Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Ordering -> Put s () Source #

get :: Get s Ordering Source #

Persist s Bool Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Bool -> Put s () Source #

get :: Get s Bool Source #

Persist s Text Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Text -> Put s () Source #

get :: Get s Text Source #

Persist s Char Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Char -> Put s () Source #

get :: Get s Char Source #

Persist s Natural Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Natural -> Put s () Source #

get :: Get s Natural Source #

Persist s Integer Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Integer -> Put s () Source #

get :: Get s Integer Source #

Persist s Int Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Int -> Put s () Source #

get :: Get s Int Source #

Persist s Word Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Word -> Put s () Source #

get :: Get s Word Source #

Persist s Float Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Float -> Put s () Source #

get :: Get s Float Source #

Persist s Double Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Double -> Put s () Source #

get :: Get s Double Source #

Persist s Int64 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Int64 -> Put s () Source #

get :: Get s Int64 Source #

Persist s Int32 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Int32 -> Put s () Source #

get :: Get s Int32 Source #

Persist s Int16 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Int16 -> Put s () Source #

get :: Get s Int16 Source #

Persist s Int8 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Int8 -> Put s () Source #

get :: Get s Int8 Source #

Persist s Word64 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Word64 -> Put s () Source #

get :: Get s Word64 Source #

Persist s Word32 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Word32 -> Put s () Source #

get :: Get s Word32 Source #

Persist s Word16 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Word16 -> Put s () Source #

get :: Get s Word16 Source #

Persist s Word8 Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Word8 -> Put s () Source #

get :: Get s Word8 Source #

Persist s () Source # 
Instance details

Defined in Data.PersistState

Methods

put :: () -> Put s () Source #

get :: Get s () Source #

Persist s e => Persist s (Seq e) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Seq e -> Put s () Source #

get :: Get s (Seq e) Source #

Persist s e => Persist s (IntMap e) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: IntMap e -> Put s () Source #

get :: Get s (IntMap e) Source #

Persist s e => Persist s (NonEmpty e) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: NonEmpty e -> Put s () Source #

get :: Get s (NonEmpty e) Source #

(Ord a, Persist s a) => Persist s (Set a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Set a -> Put s () Source #

get :: Get s (Set a) Source #

Persist s a => Persist s [a] Source #

Persist a list in the following format: Word64 (little endian format) element 1 ... element n

Instance details

Defined in Data.PersistState

Methods

put :: [a] -> Put s () Source #

get :: Get s [a] Source #

Persist s a => Persist s (Last a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Last a -> Put s () Source #

get :: Get s (Last a) Source #

Persist s a => Persist s (First a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: First a -> Put s () Source #

get :: Get s (First a) Source #

Persist s a => Persist s (Product a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Product a -> Put s () Source #

get :: Get s (Product a) Source #

Persist s a => Persist s (Sum a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Sum a -> Put s () Source #

get :: Get s (Sum a) Source #

Persist s a => Persist s (Dual a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Dual a -> Put s () Source #

get :: Get s (Dual a) Source #

Persist s e => Persist s (Tree e) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Tree e -> Put s () Source #

get :: Get s (Tree e) Source #

Persist s a => Persist s (Maybe a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Maybe a -> Put s () Source #

get :: Get s (Maybe a) Source #

Persist s a => Persist s (Ratio a) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Ratio a -> Put s () Source #

get :: Get s (Ratio a) Source #

Persist s (BigEndian Int) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: BigEndian Int -> Put s () Source #

get :: Get s (BigEndian Int) Source #

Persist s (LittleEndian Int) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: BigEndian Word -> Put s () Source #

get :: Get s (BigEndian Word) Source #

Persist s (LittleEndian Word) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Float) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Float) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Double) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Double) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Int64) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Int64) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Int32) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Int32) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Int16) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Int16) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word64) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word64) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word32) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word32) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word16) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word16) Source # 
Instance details

Defined in Data.PersistState

(Ord k, Persist s k, Persist s e) => Persist s (Map k e) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Map k e -> Put s () Source #

get :: Get s (Map k e) Source #

(Persist s a, Persist s b) => Persist s (a, b) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: (a, b) -> Put s () Source #

get :: Get s (a, b) Source #

(Persist s a, Persist s b) => Persist s (Either a b) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: Either a b -> Put s () Source #

get :: Get s (Either a b) Source #

(Persist s a, Persist s b, Persist s c) => Persist s (a, b, c) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: (a, b, c) -> Put s () Source #

get :: Get s (a, b, c) Source #

(Persist s a, Persist s b, Persist s c, Persist s d) => Persist s (a, b, c, d) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: (a, b, c, d) -> Put s () Source #

get :: Get s (a, b, c, d) Source #

(Persist s a, Persist s b, Persist s c, Persist s d, Persist s e) => Persist s (a, b, c, d, e) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: (a, b, c, d, e) -> Put s () Source #

get :: Get s (a, b, c, d, e) Source #

(Persist s a, Persist s b, Persist s c, Persist s d, Persist s e, Persist s f) => Persist s (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: (a, b, c, d, e, f) -> Put s () Source #

get :: Get s (a, b, c, d, e, f) Source #

(Persist s a, Persist s b, Persist s c, Persist s d, Persist s e, Persist s f, Persist s h) => Persist s (a, b, c, d, e, f, h) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: (a, b, c, d, e, f, h) -> Put s () Source #

get :: Get s (a, b, c, d, e, f, h) Source #

Endianness

newtype BigEndian a Source #

Constructors

BigEndian 

Fields

Instances
Functor BigEndian Source # 
Instance details

Defined in Data.PersistState

Methods

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

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

Foldable BigEndian Source # 
Instance details

Defined in Data.PersistState

Methods

fold :: Monoid m => BigEndian m -> m #

foldMap :: Monoid m => (a -> m) -> BigEndian a -> m #

foldr :: (a -> b -> b) -> b -> BigEndian a -> b #

foldr' :: (a -> b -> b) -> b -> BigEndian a -> b #

foldl :: (b -> a -> b) -> b -> BigEndian a -> b #

foldl' :: (b -> a -> b) -> b -> BigEndian a -> b #

foldr1 :: (a -> a -> a) -> BigEndian a -> a #

foldl1 :: (a -> a -> a) -> BigEndian a -> a #

toList :: BigEndian a -> [a] #

null :: BigEndian a -> Bool #

length :: BigEndian a -> Int #

elem :: Eq a => a -> BigEndian a -> Bool #

maximum :: Ord a => BigEndian a -> a #

minimum :: Ord a => BigEndian a -> a #

sum :: Num a => BigEndian a -> a #

product :: Num a => BigEndian a -> a #

Traversable BigEndian Source # 
Instance details

Defined in Data.PersistState

Methods

traverse :: Applicative f => (a -> f b) -> BigEndian a -> f (BigEndian b) #

sequenceA :: Applicative f => BigEndian (f a) -> f (BigEndian a) #

mapM :: Monad m => (a -> m b) -> BigEndian a -> m (BigEndian b) #

sequence :: Monad m => BigEndian (m a) -> m (BigEndian a) #

Persist s (BigEndian Int) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: BigEndian Int -> Put s () Source #

get :: Get s (BigEndian Int) Source #

Persist s (BigEndian Word) Source # 
Instance details

Defined in Data.PersistState

Methods

put :: BigEndian Word -> Put s () Source #

get :: Get s (BigEndian Word) Source #

Persist s (BigEndian Float) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Double) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Int64) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Int32) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Int16) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word64) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word32) Source # 
Instance details

Defined in Data.PersistState

Persist s (BigEndian Word16) Source # 
Instance details

Defined in Data.PersistState

Eq a => Eq (BigEndian a) Source # 
Instance details

Defined in Data.PersistState

Methods

(==) :: BigEndian a -> BigEndian a -> Bool #

(/=) :: BigEndian a -> BigEndian a -> Bool #

Ord a => Ord (BigEndian a) Source # 
Instance details

Defined in Data.PersistState

Show a => Show (BigEndian a) Source # 
Instance details

Defined in Data.PersistState

Generic (BigEndian a) Source # 
Instance details

Defined in Data.PersistState

Associated Types

type Rep (BigEndian a) :: Type -> Type #

Methods

from :: BigEndian a -> Rep (BigEndian a) x #

to :: Rep (BigEndian a) x -> BigEndian a #

type Rep (BigEndian a) Source # 
Instance details

Defined in Data.PersistState

type Rep (BigEndian a) = D1 (MetaData "BigEndian" "Data.PersistState" "persist-state-0.2.0.0-KiTZP5jmBZy2GQ7euApMic" True) (C1 (MetaCons "BigEndian" PrefixI True) (S1 (MetaSel (Just "unBE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype LittleEndian a Source #

Constructors

LittleEndian 

Fields

Instances
Functor LittleEndian Source # 
Instance details

Defined in Data.PersistState

Methods

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

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

Foldable LittleEndian Source # 
Instance details

Defined in Data.PersistState

Methods

fold :: Monoid m => LittleEndian m -> m #

foldMap :: Monoid m => (a -> m) -> LittleEndian a -> m #

foldr :: (a -> b -> b) -> b -> LittleEndian a -> b #

foldr' :: (a -> b -> b) -> b -> LittleEndian a -> b #

foldl :: (b -> a -> b) -> b -> LittleEndian a -> b #

foldl' :: (b -> a -> b) -> b -> LittleEndian a -> b #

foldr1 :: (a -> a -> a) -> LittleEndian a -> a #

foldl1 :: (a -> a -> a) -> LittleEndian a -> a #

toList :: LittleEndian a -> [a] #

null :: LittleEndian a -> Bool #

length :: LittleEndian a -> Int #

elem :: Eq a => a -> LittleEndian a -> Bool #

maximum :: Ord a => LittleEndian a -> a #

minimum :: Ord a => LittleEndian a -> a #

sum :: Num a => LittleEndian a -> a #

product :: Num a => LittleEndian a -> a #

Traversable LittleEndian Source # 
Instance details

Defined in Data.PersistState

Methods

traverse :: Applicative f => (a -> f b) -> LittleEndian a -> f (LittleEndian b) #

sequenceA :: Applicative f => LittleEndian (f a) -> f (LittleEndian a) #

mapM :: Monad m => (a -> m b) -> LittleEndian a -> m (LittleEndian b) #

sequence :: Monad m => LittleEndian (m a) -> m (LittleEndian a) #

Persist s (LittleEndian Int) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Float) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Double) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Int64) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Int32) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Int16) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word64) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word32) Source # 
Instance details

Defined in Data.PersistState

Persist s (LittleEndian Word16) Source # 
Instance details

Defined in Data.PersistState

Eq a => Eq (LittleEndian a) Source # 
Instance details

Defined in Data.PersistState

Ord a => Ord (LittleEndian a) Source # 
Instance details

Defined in Data.PersistState

Show a => Show (LittleEndian a) Source # 
Instance details

Defined in Data.PersistState

Generic (LittleEndian a) Source # 
Instance details

Defined in Data.PersistState

Associated Types

type Rep (LittleEndian a) :: Type -> Type #

Methods

from :: LittleEndian a -> Rep (LittleEndian a) x #

to :: Rep (LittleEndian a) x -> LittleEndian a #

type Rep (LittleEndian a) Source # 
Instance details

Defined in Data.PersistState

type Rep (LittleEndian a) = D1 (MetaData "LittleEndian" "Data.PersistState" "persist-state-0.2.0.0-KiTZP5jmBZy2GQ7euApMic" True) (C1 (MetaCons "LittleEndian" PrefixI True) (S1 (MetaSel (Just "unLE") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

Serialization

encode :: forall s a. Persist s a => PutState s -> a -> ByteString Source #

Encode a value using binary serialization to a strict ByteString.

decode :: forall s a. Persist s a => GetState s -> ByteString -> Either String a Source #

Decode a value from a strict ByteString, reconstructing the original structure.

The Get type

data Get s a Source #

Instances
Monad (Get s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

(>>=) :: Get s a -> (a -> Get s b) -> Get s b #

(>>) :: Get s a -> Get s b -> Get s b #

return :: a -> Get s a #

fail :: String -> Get s a #

Functor (Get s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

fmap :: (a -> b) -> Get s a -> Get s b #

(<$) :: a -> Get s b -> Get s a #

MonadFail (Get s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

fail :: String -> Get s a #

Applicative (Get s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

pure :: a -> Get s a #

(<*>) :: Get s (a -> b) -> Get s a -> Get s b #

liftA2 :: (a -> b -> c) -> Get s a -> Get s b -> Get s c #

(*>) :: Get s a -> Get s b -> Get s b #

(<*) :: Get s a -> Get s b -> Get s a #

type family GetState s Source #

runGet :: Get s a -> GetState s -> ByteString -> Either String a Source #

Run the Get monad applies a get-based parser on the input ByteString

ensure :: Int -> Get s () Source #

Ensure that n bytes are available. Fails if fewer than n bytes are available.

skip :: Int -> Get s () Source #

Skip ahead n bytes. Fails if fewer than n bytes are available.

getBytes :: Int -> Get s ByteString Source #

Pull n bytes from the input, as a strict ByteString.

getByteString :: Int -> Get s ByteString Source #

An efficient get method for strict ByteStrings. Fails if fewer than n bytes are left in the input. This function creates a fresh copy of the underlying bytes.

remaining :: Get s Int Source #

Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed.

eof :: Get s () Source #

getBE :: Persist s (BigEndian a) => Get s a Source #

The Put type

data Put s a Source #

Instances
Monad (Put s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

(>>=) :: Put s a -> (a -> Put s b) -> Put s b #

(>>) :: Put s a -> Put s b -> Put s b #

return :: a -> Put s a #

fail :: String -> Put s a #

Functor (Put s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

fmap :: (a -> b) -> Put s a -> Put s b #

(<$) :: a -> Put s b -> Put s a #

Applicative (Put s) Source # 
Instance details

Defined in Data.PersistState.Internal

Methods

pure :: a -> Put s a #

(<*>) :: Put s (a -> b) -> Put s a -> Put s b #

liftA2 :: (a -> b -> c) -> Put s a -> Put s b -> Put s c #

(*>) :: Put s a -> Put s b -> Put s b #

(<*) :: Put s a -> Put s b -> Put s a #

type family PutState s Source #

evalPut :: Put s a -> PutState s -> (a, ByteString) Source #

grow :: Int -> Put s () Source #

Ensure that n bytes can be written.

putHE :: Persist s (HostEndian a) => a -> Put s () Source #

putLE :: Persist s (LittleEndian a) => a -> Put s () Source #

putBE :: Persist s (BigEndian a) => a -> Put s () Source #