Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions |
|
This module has the same interface as Data.Binary.Typed, but emits
debugging messages via Debug.Trace whenever a TypeInformation
is
calculated. This is useful to determine whether caching works properly,
i.e. if a single serialization point emity a lot of caching messages
it's worth having a look at.
A simple example to check sharing is to evaluate
map
(encodeTyped
Hashed5
) "hello world!"
This should print only one debug message "TypeRep/Hashed5 calculated", since the encoding function is shared between all invocations.
- data Typed a
- typed :: Typeable a => TypeFormat -> a -> Typed a
- data TypeFormat
- erase :: Typed a -> a
- mapTyped :: Typeable b => (a -> b) -> Typed a -> Typed b
- reValue :: (a -> a) -> Typed a -> Typed a
- reType :: Typeable a => TypeFormat -> Typed a -> Typed a
- preserialize :: TypeInformation -> TypeInformation
- encodeTyped :: forall a. (Typeable a, Binary a) => TypeFormat -> a -> ByteString
- decodeTyped :: (Typeable a, Binary a) => ByteString -> Either String a
- decodeTypedOrFail :: forall a. (Typeable a, Binary a) => ByteString -> Either (ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
- unsafeDecodeTyped :: (Typeable a, Binary a) => ByteString -> a
Core functions
A value suitable to be typechecked using the contained extra type information.
typed :: Typeable a => TypeFormat -> a -> Typed a Source
data TypeFormat Source
Different ways of including/verifying type information of serialized messages.
Untyped | Include no type information. |
Hashed5 | Like
|
Hashed32 | Compare types by their hash values (using the MurmurHash2 algorithm).
|
Hashed64 | Like |
Shown | Compare
|
Full | Compare the full representation of a data type.
|
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 precache
d information, so that values have to be
precache
d again if desired. As a consequence,
can be used to un-mapTyped
id
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
).
preserialize :: TypeInformation -> TypeInformation Source
Sometimes it can be beneficial to serialize the type information in
advance, so that the maybe costly serialization step does not have to be
repeated on every invocation of encode
. Preserialization comes at a price
though, as the directly contained ByteString
requires its length to
be included in the final serialization, yielding a 8-byte overhead for the
required Int64
, and one for the tag of what was serialized
("shown or full?").
This function calculates the serialized version of TypeInformation
in
cases where the required 9 bytes are negligible (determined by an
arbitrary threshold, currently 10*9 bytes).
Used to make encodeTyped
more efficient; the source
there also makes a good usage example.
Typed serialization
Encoding
encodeTyped :: forall a. (Typeable a, Binary a) => TypeFormat -> a -> ByteString Source
Encode a Typeable
value to ByteString
that includes type
information. This function is useful to create specialized typed encoding
functions, because the type information is cached and does not need to be
recalculated on every serialization.
Observationally,
is equivalent to
encodeTyped
format value
. However, encode
(typed
format value)encodeTyped
does the type
information related calculations in advance and shares the results between
future invocations of it, making it much more efficient to serialize many
values of the same type.
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.
Based on decodeTypedOrFail
.
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 :: forall a. (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.
- Typed cousin of
decodeOrFail
. - Like
decodeTyped
, but with additional data. - Automatically caches
Hashed5
,Hashed32
andHashed64
representations, so that typechecking does not need to recalculate them on every decoding.
unsafeDecodeTyped :: (Typeable a, Binary a) => ByteString -> a Source
Decode a typed value, throwing a descriptive error
at runtime on failure.
Typed cousin of decode
. Based on decodeTypedOrFail
.
encoded =encodeTyped
Full
("hello", 1 ::Int
, 2.34 ::Double
) -- <value>unsafeDecodeTyped
encoded :: (String
,Int
,Double
) -- (Descriptive) runtimeerror
unsafeDecodeTyped
encoded :: (Char
,Int
,Double
)