binary-typed-0.1.0.1: Type-safe binary serialization

Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Binary.Typed.Internal

Contents

Description

Internals, exposed mostly for potential use by testsuites and benchmarks.

Not recommended to be used from within other independent libraries.

Synopsis

Typed

data Typed a Source

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

Constructors

Typed TypeInformation a

Using this data constructor directly is unsafe, as it allows construction of ill-typed Typed data. Use the typed smart constructor unless you really need Typed.

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).

data TypeInformation Source

Type information stored alongside a value to be serialized, so that the recipient can do consistency checks. See TypeFormat for more detailed information on the fields.

newtype Hash Source

A hash value of a TypeRep. Currently a 64-bit value created using the MurmurHash2 algorithm.

Constructors

Hash Word64 

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.

getFormat :: TypeInformation -> TypeFormat Source

Extract which TypeFormat was used to create a certain TypeInformation.

typecheck :: Typeable a => Typed a -> Either String (Typed a) Source

Typecheck a Typed. Returns the (well-typed) input, or an error message if the types don't work out.

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

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.

TypeRep

data TypeRep Source

TypeRep without the (internal) fingerprint.

Constructors

TypeRep TyCon [TypeRep] 

stripTypeRep :: TypeRep -> TypeRep Source

Strip a TypeRep off the fingerprint. Inverse of unStripTypeRep.

unStripTypeRep :: TypeRep -> TypeRep Source

Add a fingerprint to a TypeRep. Inverse of stripTypeRep.

TyCon

data TyCon Source

TyCon without the (internal) fingerprint.

Constructors

TyCon String String String

Package, module, constructor name

stripTyCon :: TyCon -> TyCon Source

Strip a TyCon off the fingerprint. Inverse of unStripTyCon.

unStripTyCon :: TyCon -> TyCon Source

Add a fingerprint to a TyCon. Inverse of stripTyCon.