Safe Haskell | None |
---|---|
Language | Haskell2010 |
Encoding and decoding values to formats.
- class Encodable a where
- class (IsString fmt, Show fmt, Encodable fmt) => Format fmt where
- encode :: (Encodable a, Format fmt) => a -> fmt
- decode :: (Format fmt, Encodable a) => fmt -> Maybe a
- translate :: (Format fmt1, Format fmt2) => fmt1 -> fmt2
- unsafeDecode :: (Format fmt, Encodable a) => fmt -> a
- data Base16
- fromBase16 :: Encodable a => String -> a
- showBase16 :: Encodable a => a -> String
- data Base64
Encoding of binary data.
Often one wants to represent cryptographic hashes, secret keys or just binary data into various enocoding formats like base64, hexadecimal etc. This module gives a generic interface for all such operations. There are two main classes that capture the essence of encoding.
Format
:- The class of all types that are encoding formats to binary
data. They are all instances of
Show
andIsString
for ease of printing and inclusion in source code. Encodable
:- The class of all types that can be encoded into binary.
The combinators encode
and decode
allows encoding any instance of Encodable
to
any of the instances of Format
.
Sample code that makes use of Base16 encoding.
theAnswer :: LE Word64 theAnswer = 42 main = do putStr "The answer to life, universe and everything is:" print answserInBase16 where answerInBase16 :: Base16 answerInBase16 = encode theAnswer checkAnswer :: Base16 -> Bool checkAnswer = maybe False (==theAnswer) . decode checkAnswerBS :: ByteString -> Bool checkAnswerBS = checkAnswer . fromString
In the above example,
, which captures 64-bit unsigned
integers is an instance of Encode (but not Word64). The encode
combinator then converts in into the type Base16 that is an
instance of LE
Word64Format
. The print then uses the Show
instance of
Base16 to print it as a sequence of hexadecimal
characters. Similarly the decode combinator in checkAnswer
decodes a base16 before comparing with the answer.
Liberal IsString
instances
Certain ascii printable formats like Base16 and Base64 have a more
liberal IsString
instance: they typically allow the use of spaces
and newline in the input to the fromString
function . This allows
a more readable representation of these types when using the
OverloadedStrings
extension. See the documentation of the
corresponding instance declarations to see what characters are
ignored. However, all Show
instance of formats are strict in the
sense that they do not produce any such extraneous characters.
class Encodable a where Source #
The type class Encodable
captures all the types that can be
encoded into a stream of bytes. For a user defined type say Foo
,
defining an instance Encodable
is all that is required to make
use of encode
and decode
for any of the supported encoding
formats (i.e. instances of the class Format
).
Minimum complete definition for this class is toByteString
and
fromByteString
. Instances of EndianStore
have default
definitions for both these functions and hence a trivial instance
declaration is sufficient for such types.
newtype Foo = Foo (LE Word64) deriving (Storable, EndianStore) instance EndianStore Foo where ... instance Encodable Foo
In particular, all the endian encoded versions of Haskell's word,
i.e types like
, LE
Word32
etc, are instances of
LE
Word64Encodable
. Note that the corresponding plain type is not an
instance of Encodable
because encoding of say Word32
without
specifying whether the endianness is meaningless.
toByteString :: a -> ByteString Source #
Convert stuff to bytestring
fromByteString :: ByteString -> Maybe a Source #
Try parsing back a value. Returns nothing on failure.
unsafeFromByteString :: ByteString -> a Source #
Unsafe version of fromByteString
toByteString :: EndianStore a => a -> ByteString Source #
Convert stuff to bytestring
fromByteString :: EndianStore a => ByteString -> Maybe a Source #
Try parsing back a value. Returns nothing on failure.
Encodable Word8 Source # | |
Encodable ByteString Source # | |
Encodable Base16 Source # | |
Encodable Base64 Source # | |
Encodable BLAKE2s Source # | |
Encodable BLAKE2b Source # | |
Encodable SHA1 Source # | |
Encodable SHA256 Source # | |
Encodable SHA224 Source # | |
Encodable SHA384 Source # | |
Encodable SHA512 Source # | |
Encodable KEY Source # | |
Encodable IV Source # | |
Encodable IV Source # | |
Encodable KEY256 Source # | |
Encodable KEY192 Source # | |
Encodable KEY128 Source # | |
Encodable a => Encodable (BITS a) Source # | |
Encodable a => Encodable (BYTES a) Source # | |
Encodable (BE Word32) Source # | |
Encodable (BE Word64) Source # | |
Encodable (LE Word32) Source # | |
Encodable (LE Word64) Source # | |
Encodable (WriteM IO) Source # | |
Encodable h => Encodable (HMAC h) Source # | |
class (IsString fmt, Show fmt, Encodable fmt) => Format fmt where Source #
A binary format is a representation of binary data often in
printable form. We distinguish between various binary formats at
the type level and each supported format corresponds to an instance
of the the class Format
. The encodeByteString
and
decodeFormat
are required to satisfy the laws
decodeFormat . encodeByteString = id
For type safety, the formats themselves are opaque types and hence
it is not possible to obtain the underlying binary data directly.
We require binary formats to be instances of the class Encodable
,
with the combinators toByteString
and fromByteString
of the
Encodable
class performing the actual encoding and decoding.
Instances of Format
are required to be instances of Show
and so
that the encoded format can be easily printed. They are also
required to be instances of IsString
so that they can be easily
represented in Haskell source using the OverloadedStrings
extension. However, be careful when using this due to the fact
that invalid encodings can lead to runtime errors.
encodeByteString :: ByteString -> fmt Source #
Encode binary data into the format. The return type gurantees that any binary data can indeed be encoded into a format.
decodeFormat :: fmt -> ByteString Source #
Decode the format to its associated binary
representation. Notice that this function always succeeds: we
assume that elements of the type fmt
are valid encodings and
hence the return type is ByteString
instead of
.Maybe
ByteString
decode :: (Format fmt, Encodable a) => fmt -> Maybe a Source #
Decode from a given format. It results in Nothing if there is a parse error.
translate :: (Format fmt1, Format fmt2) => fmt1 -> fmt2 Source #
Translate from one format to another.
The base 16 encoding format
The type corresponding to base-16 or hexadecimal encoding. The
Base16
encoding has a special place in this library: most
cryptographic types use Base16
encoding for their Show
and
IsString
instance. The combinators fromBase16
and showBase16
are exposed mainly to make these definitions easy.
fromBase16 :: Encodable a => String -> a Source #
Base16 variant of fromString
. Useful in definition of
IsString
instances as well as in cases where the default
IsString
instance does not parse from a base16 encoding.