packed-data-0.1.0.3
Safe HaskellNone
LanguageHaskell2010

Data.Packed.TH

Description

Module responsible for generating various functions to manipulate packed data.

Note: For each example, consider that the code is generated for the following type:

data Tree a = Leaf a | Node (Tree a) (Tree a)
Synopsis

Entrypoint

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

Generate Case function

genCase Source #

Arguments

:: [PackingFlag] 
-> Name

The name of the type to generate the function for

-> Q [Dec] 

Generates a function to allow pattern matching a packed data type using the data constructors

Example:

For the Tree data type, it generates the following function:

caseTree ::
    (PackedReader '[a] r b) ->
    (PackedReader '[Tree a, Tree a] r b) ->
    PackedReader '[Tree a] r b
caseTree leafCase nodeCase = mkPackedReader $ packed l -> do
   (tag :: Tag, packed1, l1) <- runReader reader packed l
   case tag of
       0 -> runReader leafCase packed1 l1
       1 -> runReader nodeCase packed1 l1
       _ -> fail "Bad Tag"

Generate Packing function

genPackableInstance Source #

Arguments

:: [PackingFlag] 
-> Name

The name of the type to generate the instance for

-> Q [Dec] 

Generates an instance of Packable for the given type

All the parameters of each constructor should be instances of Packable

Note: The pack function simply calls the function generated by genWrite

Example

For the Tree data type, it generates the following instance:

instance (Packable a) => Packable (Tree a) where
    write = writeTree

genConstructorPackers :: [PackingFlag] -> Name -> Q [Dec] Source #

Generates a function that serialises an applied data constructor

The function calls the functions generated by genConWrite

Example:

For the Tree data type, it generates the following functions

packLeaf :: (Packable a) => a -> Packed '[Tree a]
packLeaf n = finish (withEmptyNeeds (writeLeaf n))

packNode :: (Packable a) => Tree a -> Tree a -> Packed '[Tree a]
packNode t1 t2 = finish (withEmptyNeeds (writeNode t1 t2))

genConstructorRepackers :: [PackingFlag] -> Name -> Q [Dec] Source #

Generates a function that builds back data using already serialised fields

Example:

For the Tree data type, it generates the following functions

repackLeaf :: Needs '[] a -> Needs '[] (Tree a)
repackLeaf pval = withEmptyNeeds (startLeaf N.>> concatNeeds pval)

repackNode :: Needs '[] (Tree a) -> Needs '[] (Tree a) -> Needs '[] (Tree a)
repackNode lval rval = withEmptyNeeds (startNode N.>> concatNeeds lval N.>> concatNeeds rval)

genWrite Source #

Arguments

:: [PackingFlag] 
-> Name

The name of the type to generate the function for

-> Q [Dec] 

Generates a function that serialises and writes a value into a Needs

The function simply calls the functions generated by genConWrite

Example:

For the Tree data type, it generates the following function

writeTree :: (Packable a) => Tree a -> NeedsWriter (Tree a) r t
writeTree (Leaf n) = writeConLeaf n
writeTree (Node l r) = writeConNode l r

genConWrite Source #

Arguments

:: [PackingFlag] 
-> Con

The name of the data constructor to generate the function for

-> Tag

A unique (to the data type) Tag to identify the packed data constructor.

For example, for a Tree data type, we would typically use '0' for the Leaf constructor and '1' for the Node constructor

-> Q [Dec] 

Generates a function that serialises and write a value to a Needs. The generated function is specific to a single data constructor.

Example:

For the Tree data type, it generates the following function for the Leaf constructor

writeConLeaf :: (Packable a) => a -> 'NeedsWriter (Tree a) r t'
writeConLeaf n  = startLeaf >> write n

genStart Source #

Arguments

:: [PackingFlag] 
-> Con

Constructor to generate the function for

-> Tag

The Tag (byte) to write for this constructor

-> Q [Dec] 

Generates a function that prepares a Needs to receive values from a data constructor.

Example:

For the Tree data type, it generates the following functions

startLeaf :: NeedsBuilder (Tree a ': r) t (a ': r) t
startLeaf = mkNeedsBuilder (n -> runBuilder (write (0 :: Word8) (unsafeCastNeeds n)))

startNode :: NeedsBuilder (Tree a ': r) t (Tree a ': Tree a ': r) t
startNode = mkNeedsBuilder (n -> runBuilder (write (1 :: Word8) (unsafeCastNeeds n)))

Generate Unpacking function

genUnpackableInstance :: [PackingFlag] -> Name -> Q [Dec] Source #

Generates an instance of Unpackable for the given type

All the parameters of each constructor should be instances of Unpackable

Note: The unpack function simply calls the function generated by genRead

Example

For the Tree data type, it generates the following instance:

instance (Unpackable a) => Unpackable (Tree a) where
   reader = readTree

genRead Source #

Arguments

:: [PackingFlag] 
-> Name 
-> Q [Dec]

The name of the type to generate the function for

Generates an function to read (i.e. deserialise) the given data type.

Example:

For the Tree data type, it generates the following function:

readTree :: (Unpackable a) => PackedReader '[Tree a] r (Tree a)
readTree = caseTree
    (reader >>= \leafContent ->
         return $ Leaf leafContent
    )

    (reader >>= \leftContent ->
     reader >>= \rightContent ->
         return $ Node leftContent rightContent
    )

Note We use bindings (>>=) intead of a do-notation, since Reader is not a monad. It's an indexed monad, meaning that the user would have to enable the QualifiedDo extenstion for it to compile.

Generate Skip function

genSkippableInstance :: [PackingFlag] -> Name -> Q [Dec] Source #

Generates an instance of Skippable for the given type

All the parameters of each constructor should be instances of Skippable

Example

For the Tree data type, it generates the following instance:

instance (Skippable a) => Skippable (Tree a) where
    skip = skipTree

genSkip :: [PackingFlag] -> Name -> Q [Dec] Source #

Generates an function to skip a value of the given type in a Packed

Example:

For the Tree data type, it generates the following function:

skipTree :: (Skippable a) => PackedReader '[Tree a] r ()
skipTree = caseTree
     skip
     (skipTree >> skipTree)

Generate Transform function

Misc

type Tag = Word8 Source #

Byte in a Packed value to identify which data constructor is serialised