Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Packed
Synopsis
- class Packable a where
- write :: forall (r :: [Type]) (t :: [Type]). a -> NeedsWriter a r t
- pack :: Packable a => a -> Packed '[a]
- class Unpackable a where
- reader :: forall (r :: [Type]). PackedReader '[a] r a
- readerWithoutShift :: forall a (r :: [Type]). Unpackable a => PackedReader (a ': r) (a ': r) a
- unpack :: forall a (r :: [Type]). Unpackable a => Packed (a ': r) -> (a, Packed r)
- unpack' :: forall a (r :: [Type]). Unpackable a => Packed (a ': r) -> a
- data Needs (p :: [Type]) (t :: [Type])
- withEmptyNeeds :: forall (a :: [Type]) (b :: [Type]) (x :: [Type]) (y :: [Type]). NeedsBuilder a b x y -> Needs x y
- writeWithFieldSize :: forall a (r :: [Type]) (t :: [Type]). Packable a => a -> NeedsWriter' '[FieldSize, a] r t
- finish :: forall (t :: [Type]). Needs ('[] :: [Type]) t -> Packed t
- unsafeCastNeeds :: forall (a :: [Type]) (b :: [Type]) (c :: [Type]) (d :: [Type]). Needs a b -> Needs c d
- data Packed (l :: [Type])
- skipWithFieldSize :: forall a (r :: [Type]). PackedReader '[FieldSize, a] r ()
- isolate :: forall a (r :: [Type]). PackedReader '[FieldSize, a] r (Packed '[a])
- fromPacked :: forall (a :: [Type]). Packed a -> ByteString
- unsafeToPacked :: forall (a :: [Type]). ByteString -> Packed a
- unsafeCastPacked :: forall (a :: [Type]) (b :: [Type]). Packed a -> Packed b
- data PackedReader (p :: [Type]) (r :: [Type]) v
- mkPackedReader :: forall (p :: [Type]) (r :: [Type]) v. (ReaderPtr (p :++: r) -> Int -> IO (v, ReaderPtr r, Int)) -> PackedReader p r v
- runReader :: forall (p :: [Type]) (r :: [Type]) v. PackedReader p r v -> Packed (p :++: r) -> IO (v, Packed r)
- readerWithFieldSize :: forall a (r :: [Type]). Unpackable a => PackedReader '[FieldSize, a] r a
- mkPacked :: Name -> [PackingFlag] -> Q [Dec]
- data PackingFlag
- data FieldSize
- getFieldSizeFromPacked :: Packed '[a] -> FieldSize
- class Skippable a where
- skip :: forall (r :: [Type]). PackedReader '[a] r ()
Classes
class Packable a where Source #
Instances
Packable FieldSize Source # | |
Defined in Data.Packed.FieldSize | |
Storable a => Packable a Source # | |
Defined in Data.Packed.Packable | |
Packable a => Packable (Maybe a) Source # | |
Defined in Data.Packed.Instances | |
Packable a => Packable [a] Source # | |
Defined in Data.Packed.Instances | |
(Packable a, Packable b) => Packable (Either a b) Source # | |
Defined in Data.Packed.Instances |
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
Unpackable FieldSize Source # | |
Defined in Data.Packed.FieldSize | |
Storable a => Unpackable a Source # | |
Defined in Data.Packed.Unpackable Methods reader :: forall (r :: [Type]). PackedReader '[a] r a Source # | |
Unpackable a => Unpackable (Maybe a) Source # | |
Defined in Data.Packed.Instances | |
Unpackable a => Unpackable [a] Source # | |
Defined in Data.Packed.Instances Methods reader :: forall (r :: [Type]). PackedReader '[[a]] r [a] Source # | |
(Unpackable a, Unpackable b) => Unpackable (Either a b) Source # | |
Defined in Data.Packed.Instances |
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 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 #
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
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
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
Functor (PackedReader p r) Source # | |
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
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
- A 'case' function (see
genCase
) - An instance of
Packable
(seegenPackableInstance
) - An instance of
Unpackable
(seegenUnpackableInstance
) - An instance of
Skippable
(seegenSkippableInstance
)
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 Example As a consequence, for the following type, the caseTree :: ( |
SkipLastFieldSize | This flag should be used in complement to If set, no Example If this flag is set (along with caseTree :: ( |
Instances
Eq PackingFlag Source # | |
Defined in Data.Packed.TH.Flag |
Utils
Type representation for the size of a packed data. The size is in bytes.
Note: Take a look at the PackingFlag
s to understand how to use it
Instances
Packable FieldSize Source # | |
Defined in Data.Packed.FieldSize | |
Skippable FieldSize Source # | |
Defined in Data.Packed.FieldSize | |
Unpackable FieldSize Source # | |
Defined in Data.Packed.FieldSize |
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
Skippable FieldSize Source # | |
Defined in Data.Packed.FieldSize | |
Storable a => Skippable a Source # | |
Defined in Data.Packed.Skippable Methods skip :: forall (r :: [Type]). PackedReader '[a] r () Source # | |
Skippable a => Skippable (Maybe a) Source # | |
Defined in Data.Packed.Instances | |
Skippable a => Skippable [a] Source # | |
Defined in Data.Packed.Instances Methods skip :: forall (r :: [Type]). PackedReader '[[a]] r () Source # | |
(Skippable a, Skippable b) => Skippable (Either a b) Source # | |
Defined in Data.Packed.Instances |