binary-typed-0.1.0.1: Type-safe binary serialization

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Binary.Typed

Contents

Description

Defines a type-safe Binary instance to ensure data is decoded with the type it was serialized from.

For usage information, see the Data.Binary.Typed.Tutorial module.

Synopsis

Core functions

data Typed a Source

A value suitable to be typechecked using the contained extra type information.

Instances

Show a => Show (Typed a)

"typed <format> <value>"

(Binary a, Typeable * a) => Binary (Typed a)

Ensures data is decoded as the appropriate type with high or total confidence (depending on with what TypeFormat the Typed was constructed).

typed :: Typeable a => TypeFormat -> a -> Typed a Source

Construct a Typed value using the chosen type format.

Example:

value = typed Full ("hello", 1 :: Int, 2.34 :: Double)
encded = encode value

The decode site can now verify whether decoding happens with the right type.

data TypeFormat Source

Different ways of including/verifying type information of serialized messages.

Constructors

Untyped

Include no type information.

  • Requires one byte more than using Binary directly (namely to tag the data as untyped, required for the decoding step).
Hashed

Compare types by their hash values (using the MurmurHash2 algorithm).

  • Requires only 8 additional bytes for the type information.
  • Subject to false positive due to hash collisions, although in practice this should almost never happen.
  • Type errors cannot tell the provided type ("Expected X, received type with hash H")
Shown

Compare String representation of types, obtained by calling show on the TypeRep, and also include a hash value (like Hashed). The former is mostly for readable error messages, the latter provides collision resistance.

  • Data size larger than Hashed, but usually smaller than Full.
  • Both the hash and the shown type must match to satisfy the typechecker.
  • Useful type errors ("expected X, received Y"). All types are shown unqualified though, making Foo.X and Bar.X look identical in error messages.
Full

Compare the full representation of a data type.

  • More verbose than Hashed and Shown. As a rule of thumb, transmitted data is roughly the same as Shown, but all names are fully qualified (package, module, type name).
  • Correct comparison (no false positives). An semi-exception here is when types change between package versions: package-1.0 Foo.X and package-1.1 Foo.X count as the same type.
  • Useful type errors ("expected X, received Y"). All types are shown unqualified though, making Foo.X and Bar.X look identical in error messages.

erase :: Typed a -> a Source

Extract the value of a Typed, i.e. strip off the explicit type information.

This function is safe to use for all Typed values created by the public API, since all construction sites ensure the actual type matches the contained type description.

erase (typed format x) == x

Useful general helpers

mapTyped :: Typeable b => (a -> b) -> Typed a -> Typed b Source

Modify the value contained in a Typed, keeping the same sort of type representation. In other words, calling mapTyped on something that is typed using Hashed will yield a Hashed value again.

Note: this destroys precached information, so that values have to be precached again if desired. As a consequence, mapTyped id can be used to un-precache values.

reValue :: (a -> a) -> Typed a -> Typed a Source

Change the value contained in a Typed, leaving the type representation unchanged. This can be useful to avoid recomputation of the included type information, and can improve performance significantly if many individual messages are serialized.

Can be seen as a more efficient mapTyped in case f is an endomorphism (i.e. has type a -> a).

reType :: Typeable a => TypeFormat -> Typed a -> Typed a Source

Change the way a type is represented inside a Typed value.

reType format x = typed format (erase x)

precache :: Typed a -> Typed a Source

Calculate the serialization of a TypeInformation and store it in a Typed value so it does not have to be recalculated on every call to encode.

This is typically applied to a dummy value created using typed and the desired TypeFormat; the actual data is then inserted using reValue, which is how encodeTyped works.

Typed serialization

Encoding

encodeTyped :: (Typeable a, Binary a) => TypeFormat -> a -> ByteString Source

Encode a Typeable value to ByteString that includes type information. If at all possible, prefer the more efficient encodeTypedLike though.

encodeTyped format value = encode (typed format value)

encodeTypedLike :: (Typeable a, Binary a) => Typed a -> a -> ByteString Source

Version of encodeTyped that avoids recomputing the type representation of the input by using the one already contained in the first parameter. This is usually much more efficient than using encode, having a computational cost similar to using Binary directly.

encodeTypedLike ty x
-- is observationally identical to
encode (reValue (const x) ty)

This function is intended to generate new encoding functions like so:

encodeInt :: Int -> ByteString
encodeInt = encodeTypedLike (typed Full 0)

Decoding

decodeTyped :: (Typeable a, Binary a) => ByteString -> Either String a Source

Safely decode data, yielding Either an error String or the value. Equivalent to decodeTypedOrFail stripped of the non-essential data.

encoded = encodeTyped Full ("hello", 1 :: Int, 2.34 :: Double)

-- Right <value>:
decodeTyped encoded :: Either String (String, Int, Double)

-- Left "Type error: expected (Char, Int, Double), got (String, Int, Double)"
decodeTyped encoded :: Either String (Char, Int, Double)

decodeTypedOrFail :: (Typeable a, Binary a) => ByteString -> Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a) Source

Safely decode data, yielding Either an error String or the value, along with meta-information of the consumed binary data.

unsafeDecodeTyped :: (Typeable a, Binary a) => ByteString -> a Source

Decode a typed value, throwing an error at runtime on failure. Typed cousin of decode.

encoded = encodeTyped Full ("hello", 1 :: Int, 2.34 :: Double)

-- <value>
unsafeDecodeTyped encoded :: (String, Int, Double)

-- (Descriptive) runtime error
unsafeDecodeTyped encoded :: (Char, Int, Double)