raaz-0.3.6: Fast and type safe cryptography.
Copyright(c) Piyush P Kurur 2015
LicenseApache-2.0 OR BSD-3-Clause
MaintainerPiyush P Kurur <ppk@iitpkd.ac.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Encode

Description

 
Synopsis

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 and IsString 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, LE Word64, 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 Format. 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, LE Word64 etc, are instances of Encodable. Note that the corresponding plain type is not an instance of Encodable because encoding of say Word32 without specifying whether the endianness is meaningless.

Laws for encoding

Note that not all byte strings can be valid encodings and fromByteString might fail and return Nothing on certain inputs. However, we require the minimum guarantee that fromByteString for actual encodings of elements, i.e. we require the instances to satisfy the law.

fromByteString . toByteString = Just

TODO: Write test cases for encoding laws.

Minimal complete definition

Nothing

Methods

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

Instances

Instances details
Encodable Word8 Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable () Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable ByteString Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

Encodable Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

Encodable WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

Encodable S Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Encodable R Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Encodable Poly1305 Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Encodable a => Encodable (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (BE Word32) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (BE Word64) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (LE Word32) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (LE Word64) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Encodable prim => Encodable (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

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.

Methods

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.

Instances

Instances details
Format ByteString Source #

Bytestring itself is an encoding format (namely binary format).

Instance details

Defined in Raaz.Core.Encode.Internal

Format Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

Format Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

encode :: (Encodable a, Format fmt) => a -> fmt Source #

Encode in a given format.

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.

unsafeDecode :: (Format fmt, Encodable a) => fmt -> a Source #

The unsafe version of decode.

The base 16 encoding format

data Base16 Source #

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.

Instances

Instances details
Eq Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

Methods

(==) :: Base16 -> Base16 -> Bool #

(/=) :: Base16 -> Base16 -> Bool #

Show Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

IsString Base16 Source #

Ignores spaces and : (colon).

Instance details

Defined in Raaz.Core.Encode.Base16

Methods

fromString :: String -> Base16 #

Semigroup Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

Monoid Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

Format Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

Encodable Base16 Source # 
Instance details

Defined in Raaz.Core.Encode.Base16

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.

showBase16 :: Encodable a => a -> String Source #

Base16 variant of show.

Other binary formats.

data Base64 Source #

The type corresponding to the standard padded base-64 binary encoding.

Instances

Instances details
Eq Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

Methods

(==) :: Base64 -> Base64 -> Bool #

(/=) :: Base64 -> Base64 -> Bool #

Show Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

IsString Base64 Source #

Ignores spaces and newlines.

Instance details

Defined in Raaz.Core.Encode.Base64

Methods

fromString :: String -> Base64 #

Semigroup Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

Monoid Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

Format Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64

Encodable Base64 Source # 
Instance details

Defined in Raaz.Core.Encode.Base64