packed-data-0.1.0.1
Safe HaskellNone
LanguageHaskell2010

Data.Packed

Synopsis

Classes

class Packable a where Source #

Methods

write :: forall (r :: [Type]) (t :: [Type]). a -> NeedsWriter a r t Source #

Instances

Instances details
Packable FieldSize Source # 
Instance details

Defined in Data.Packed.FieldSize

Methods

write :: forall (r :: [Type]) (t :: [Type]). FieldSize -> NeedsWriter FieldSize r t Source #

Storable a => Packable a Source # 
Instance details

Defined in Data.Packed.Packable

Methods

write :: forall (r :: [Type]) (t :: [Type]). a -> NeedsWriter a r t Source #

Packable a => Packable (Maybe a) Source # 
Instance details

Defined in Data.Packed.Instances

Methods

write :: forall (r :: [Type]) (t :: [Type]). Maybe a -> NeedsWriter (Maybe a) r t Source #

Packable a => Packable [a] Source # 
Instance details

Defined in Data.Packed.Instances

Methods

write :: forall (r :: [Type]) (t :: [Type]). [a] -> NeedsWriter [a] r t Source #

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

Defined in Data.Packed.Instances

Methods

write :: forall (r :: [Type]) (t :: [Type]). Either a b -> NeedsWriter (Either a b) r t Source #

pack :: Packable a => a -> Packed '[a] Source #

class Unpackable a where Source #

An Unpackable is a value that can be read (i.e. deserialised) from a Packed value

Methods

reader :: forall (r :: [Type]). PackedReader '[a] r a Source #

The PackedReader to unpack a value of that type

Instances

Instances details
Unpackable FieldSize Source # 
Instance details

Defined in Data.Packed.FieldSize

Methods

reader :: forall (r :: [Type]). PackedReader '[FieldSize] r FieldSize Source #

Storable a => Unpackable a Source # 
Instance details

Defined in Data.Packed.Unpackable

Methods

reader :: forall (r :: [Type]). PackedReader '[a] r a Source #

Unpackable a => Unpackable (Maybe a) Source # 
Instance details

Defined in Data.Packed.Instances

Methods

reader :: forall (r :: [Type]). PackedReader '[Maybe a] r (Maybe a) Source #

Unpackable a => Unpackable [a] Source # 
Instance details

Defined in Data.Packed.Instances

Methods

reader :: forall (r :: [Type]). PackedReader '[[a]] r [a] Source #

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

Defined in Data.Packed.Instances

Methods

reader :: forall (r :: [Type]). PackedReader '[Either a b] r (Either a b) Source #

readerWithoutShift :: forall a (r :: [Type]). Unpackable a => PackedReader (a ': r) (a ': r) a Source #

In a PackedReader, reads a value without moving the cursor

unpack :: forall a (r :: [Type]). Unpackable a => Packed (a ': r) -> (a, Packed r) Source #

Deserialise a value from a Packed.

Returns the unconsumed Packed portion

unpack' :: forall a (r :: [Type]). Unpackable a => Packed (a ': r) -> a Source #

Same as unpack, but throws away the unconsumed bytes

Needs

data Needs (p :: [Type]) (t :: [Type]) Source #

A buffer where packed values can be written The order to write these values is defined by the l type list

If p is an empty list, then a value of type t can be extracted from that buffer. (See finish)

withEmptyNeeds :: forall (a :: [Type]) (b :: [Type]) (x :: [Type]) (y :: [Type]). NeedsBuilder a b x y -> Needs x y Source #

writeWithFieldSize :: forall a (r :: [Type]) (t :: [Type]). Packable a => a -> NeedsWriter' '[FieldSize, a] r t Source #

Write a value into a Needs, along with its FieldSize

Note: Universal quantifier is nedded for GHC < 9.10, because of ScopedTypeVariables

finish :: forall (t :: [Type]). Needs ('[] :: [Type]) t -> Packed t Source #

Turns a Needs value (that does not expect to be written to) to a Packed

unsafeCastNeeds :: forall (a :: [Type]) (b :: [Type]) (c :: [Type]) (d :: [Type]). Needs a b -> Needs c d Source #

Packed

data Packed (l :: [Type]) Source #

A buffer that contains one or more packed (i.e. serialised) values. The order of the values in the buffer is defined by the l type list

Instances

Instances details
NFData (Packed a) Source # 
Instance details

Defined in Data.Packed.Packed

Methods

rnf :: Packed a -> () #

skipWithFieldSize :: forall a (r :: [Type]). PackedReader '[FieldSize, a] r () Source #

Allows skipping over a field without having to unpack it

isolate :: forall a (r :: [Type]). PackedReader '[FieldSize, a] r (Packed '[a]) Source #

Splits the Packed value, and isolate the first encoded value.

fromPacked :: forall (a :: [Type]). Packed a -> ByteString Source #

Extracts the raw buffer from a Packed value

unsafeToPacked :: forall (a :: [Type]). ByteString -> Packed a Source #

UNSAFE: Casts a generic ByteString into a Needs

unsafeCastPacked :: forall (a :: [Type]) (b :: [Type]). Packed a -> Packed b Source #

UNSAFE: Casts a typed Packed value into another Packed value of another type

PackedReader

data PackedReader (p :: [Type]) (r :: [Type]) v Source #

Basically a function that reads/desrialises a value from a Packed

p the types of the packed values to read

r the packed type after the encoded values to read

v the type of the value to unpack

Note: It is an indexed monad.

Instances

Instances details
Functor (PackedReader p r) Source # 
Instance details

Defined in Data.Packed.Reader

Methods

fmap :: (a -> b) -> PackedReader p r a -> PackedReader p r b #

(<$) :: a -> PackedReader p r b -> PackedReader p r a #

mkPackedReader :: forall (p :: [Type]) (r :: [Type]) v. (ReaderPtr (p :++: r) -> Int -> IO (v, ReaderPtr r, Int)) -> PackedReader p r v Source #

Builds a PackedReader

runReader :: forall (p :: [Type]) (r :: [Type]) v. PackedReader p r v -> Packed (p :++: r) -> IO (v, Packed r) Source #

Run the reading function using a ByteString.

readerWithFieldSize :: forall a (r :: [Type]). Unpackable a => PackedReader '[FieldSize, a] r a Source #

Produces a reader for a value preceded by its FieldSize

Code generation

mkPacked Source #

Arguments

:: Name

The name of the type to generate the functions for

-> [PackingFlag]

Generation customisation flags

-> Q [Dec] 

Generate the following for the given type

Example:

 $(mkPacked ''Tree [InsertFieldSize])

data PackingFlag Source #

Options for the generation process.

Beware: these options alter the signature and behaviour of the generated functions.

Constructors

InsertFieldSize

When specified, each field in a packed data constructor will be preceded by a FieldSize, which indicates the size of the following packed value.

Example

As a consequence, for the following type, the caseTree function will have the following signature

caseTree ::
    (PackedReader (FieldSize ': a ': r) r b) ->
    (PackedReader (FieldSize ': Tree a ': FieldSize ': Tree a ': r) r b) ->
    PackedReader (Tree a ': r) r b
SkipLastFieldSize

This flag should be used in complement to InsertFieldSize

If set, no FieldSize will be inserted before the last parameter of the data constructor.

Example

If this flag is set (along with InsertFieldSize), for the following type, the caseTree function will have the following signature

caseTree ::
    (PackedReader (a ': r) r b) ->
    (PackedReader (FieldSize ': Tree a ': Tree a ': r) r b) ->
    PackedReader (Tree a ': r) r b

Instances

Instances details
Eq PackingFlag Source # 
Instance details

Defined in Data.Packed.TH.Flag

Utils

data FieldSize Source #

Type representation for the size of a packed data. The size is in bytes.

Note: Take a look at the PackingFlags to understand how to use it

Instances

Instances details
Packable FieldSize Source # 
Instance details

Defined in Data.Packed.FieldSize

Methods

write :: forall (r :: [Type]) (t :: [Type]). FieldSize -> NeedsWriter FieldSize r t Source #

Skippable FieldSize Source # 
Instance details

Defined in Data.Packed.FieldSize

Methods

skip :: forall (r :: [Type]). PackedReader '[FieldSize] r () Source #

Unpackable FieldSize Source # 
Instance details

Defined in Data.Packed.FieldSize

Methods

reader :: forall (r :: [Type]). PackedReader '[FieldSize] r FieldSize Source #

getFieldSizeFromPacked :: Packed '[a] -> FieldSize Source #

Returns the size of the packed value.

Warning: For this to be accurate, there should only be one value packed in the binary strea.

class Skippable a where Source #

Methods

skip :: forall (r :: [Type]). PackedReader '[a] r () Source #

Instances

Instances details
Skippable FieldSize Source # 
Instance details

Defined in Data.Packed.FieldSize

Methods

skip :: forall (r :: [Type]). PackedReader '[FieldSize] r () Source #

Storable a => Skippable a Source # 
Instance details

Defined in Data.Packed.Skippable

Methods

skip :: forall (r :: [Type]). PackedReader '[a] r () Source #

Skippable a => Skippable (Maybe a) Source # 
Instance details

Defined in Data.Packed.Instances

Methods

skip :: forall (r :: [Type]). PackedReader '[Maybe a] r () Source #

Skippable a => Skippable [a] Source # 
Instance details

Defined in Data.Packed.Instances

Methods

skip :: forall (r :: [Type]). PackedReader '[[a]] r () Source #

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

Defined in Data.Packed.Instances

Methods

skip :: forall (r :: [Type]). PackedReader '[Either a b] r () Source #