RLP-1.1.1: RLP serialization as defined in Ethereum Yellow Paper

LicenseLGPL-3 (see LICENSE)
MaintainerJavier Sagredo <jasataco@gmail.com>
Stabilitystable
Safe HaskellSafe
LanguageHaskell2010

Data.Serialize.RLP

Contents

Description

An implementation of the Recursive Length Prefix method as described in the Yellow Paper https://ethereum.github.io/yellowpaper/paper.pdf.

To actually use this module, the type that is going to be encoded has to be instance of RLPSerialize defining toRLP and fromRLP.

Synopsis

The RLP Type

data RLPT Source #

The RLPT type represents the result of transforming the initial data into its byte-array representation, taking in account the structure of the fields.

Fields that can't be directly transformed into a ByteString (such as a type with several fields) should generate a list with the representations of its fields (using the RLPL constructor).

RLPT represents the T type defined in the Ethereum Yellowpaper for defining the RLP protocol.

Constructors

RLPL [RLPT] 
RLPB ByteString 
Instances
Eq RLPT Source # 
Instance details

Defined in Data.Serialize.RLP.Internal

Methods

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

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

Show RLPT Source # 
Instance details

Defined in Data.Serialize.RLP.Internal

Methods

showsPrec :: Int -> RLPT -> ShowS #

show :: RLPT -> String #

showList :: [RLPT] -> ShowS #

RLPSerialize RLPT Source # 
Instance details

Defined in Data.Serialize.RLP

Subtleties

The idea of transforming a custom type into RLPT is to preserve the original structure as far as possible. For example, suppose we have a data structure:

data Name   = (String, String)   -- represents the first and last name of a Person
data Person = Person Name Int    -- represents the whole name of a Person and its age

Then the desired output of the transformation of a Person value to RLPT should be (pseudocode):

RLPL [ RLPL [ RLPB, RLPB ], RLPB ]

This way the structure is clearly preserved. Eventhough this does not have to be true as the transformation to RLPL is defined by the user and a custom process can be implemented, it is advised to follow this guideline for better understanding of the generated code.

It is important to remark that although it can't be imposed, it doesn't make sense to try to transform to RLP types with more than one constructor that don't difer in structure. The transformation should encode a way to find out which of the constructors belongs to the data so not only data is being encoded in the result, also information about the structure futher than the actual length prefixes. That's why it only makes sense to transform to RLP types with just one constructor. On the other hand, it's perfectly viable to encode types with more than one constructor if the structure of each of them is different as it can be adjusted via pattern matching strategies.

Helper Int functions

Helper String functions

The RLPSerialize class

class RLPSerialize a where Source #

The RLPSerialize class provides functions for transforming values to RLPT structures. For encoding and decoding values with the RLP protocol, toRLP and fromRLP have to be implemented.

Instances of RLPSerialize are expected to satisfy the following property:

fromRLP . toRLP == id

In such case, it can be assured with the default definition that:

rlpDecode . rlpEncode == id

RLPSerialize makes use of the Get and Put classes together with a set of custom serializations for encoding and decoding RLPT data.

Minimal complete definition

toRLP, fromRLP

Methods

toRLP :: a -> RLPT Source #

Transform a value to the RLPT structure that best fits its internal structure

fromRLP :: RLPT -> Maybe a Source #

Transform an RLPT structure back into the value it represents. Its return type is 'Maybe a' because it can fail

rlpEncode :: a -> ByteString Source #

Transform a value to an RLPT structure and then encode it following the RLP standard.

rlpDecode :: ByteString -> Either String a Source #

Transform a ByteString to an RLPT structure following the RLP standard and then transform it to the original type. It returns 'Left s' when failing on the decoding of the transforming from RLPT into the required type, and 'Right v' on success.

Instances
RLPSerialize Bool Source # 
Instance details

Defined in Data.Serialize.RLP

RLPSerialize Char Source # 
Instance details

Defined in Data.Serialize.RLP

RLPSerialize Int Source # 
Instance details

Defined in Data.Serialize.RLP

RLPSerialize String Source # 
Instance details

Defined in Data.Serialize.RLP

RLPSerialize ByteString Source # 
Instance details

Defined in Data.Serialize.RLP

RLPSerialize RLPT Source # 
Instance details

Defined in Data.Serialize.RLP

RLPSerialize a => RLPSerialize [a] Source # 
Instance details

Defined in Data.Serialize.RLP

(RLPSerialize a, RLPSerialize b) => RLPSerialize (a, b) Source # 
Instance details

Defined in Data.Serialize.RLP

Methods

toRLP :: (a, b) -> RLPT Source #

fromRLP :: RLPT -> Maybe (a, b) Source #

rlpEncode :: (a, b) -> ByteString Source #

rlpDecode :: ByteString -> Either String (a, b) Source #

(RLPSerialize a, RLPSerialize b, RLPSerialize c) => RLPSerialize (a, b, c) Source # 
Instance details

Defined in Data.Serialize.RLP

Methods

toRLP :: (a, b, c) -> RLPT Source #

fromRLP :: RLPT -> Maybe (a, b, c) Source #

rlpEncode :: (a, b, c) -> ByteString Source #

rlpDecode :: ByteString -> Either String (a, b, c) Source #

(RLPSerialize a, RLPSerialize b, RLPSerialize c, RLPSerialize d) => RLPSerialize (a, b, c, d) Source # 
Instance details

Defined in Data.Serialize.RLP

Methods

toRLP :: (a, b, c, d) -> RLPT Source #

fromRLP :: RLPT -> Maybe (a, b, c, d) Source #

rlpEncode :: (a, b, c, d) -> ByteString Source #

rlpDecode :: ByteString -> Either String (a, b, c, d) Source #

(RLPSerialize a, RLPSerialize b, RLPSerialize c, RLPSerialize d, RLPSerialize e) => RLPSerialize (a, b, c, d, e) Source # 
Instance details

Defined in Data.Serialize.RLP

Methods

toRLP :: (a, b, c, d, e) -> RLPT Source #

fromRLP :: RLPT -> Maybe (a, b, c, d, e) Source #

rlpEncode :: (a, b, c, d, e) -> ByteString Source #

rlpDecode :: ByteString -> Either String (a, b, c, d, e) Source #

(RLPSerialize a, RLPSerialize b, RLPSerialize c, RLPSerialize d, RLPSerialize e, RLPSerialize f) => RLPSerialize (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Serialize.RLP

Methods

toRLP :: (a, b, c, d, e, f) -> RLPT Source #

fromRLP :: RLPT -> Maybe (a, b, c, d, e, f) Source #

rlpEncode :: (a, b, c, d, e, f) -> ByteString Source #

rlpDecode :: ByteString -> Either String (a, b, c, d, e, f) Source #

Example

For a full example, we reproduce the implementation of the Person type as in the subtleties section.

First of all, we define the type:

type Name = (String, String)
data Person = Person {
                   name :: Name,
                   age  :: Int
               } deriving (Show)

Then we have to make it an instance of RLPSerialize:

instance RLPSerialize Person where
  toRLP p = RLPL [
                RLPL [
                    toRLP . toByteStringS . fst . name $ p,
                    toRLP . toByteStringS . snd . name $ p
                    ],
                toRLP . age $ p]

  fromRLP (RLPL [ RLPL [ RLPB a, RLPB b ], RLPB c ]) =
    case fromBigEndianS c of
      Right v -> Just $ Person (fromByteStringS a, fromByteStringS b) v
      _       -> Nothing
  fromRLP _ = Nothing

This way, if the decoding gives rise to other structure than the expected, a the resulting value would be Nothing. We can now use our decoder and encoder with our custom type:

p = Person ("John", "Snow") 33
e = rlpEncode p
-- "\204\202\132John\132Snow!" ~ [204,202,132,74,111,104,110,132,83,110,111,119,33]
rlpDecode e :: Maybe Person
-- Right (Person {name = ("John","Snow"), age = 33})

Errors and special cases

In case we run into an error situation, depending whether the RLPT structure is not well formed or the generated structure couldn't be transformed into the expected type, an error is returned in the form of a Left value.

Just to see this as an example, if we chop the resulting ByteString, there's no way to generate a correct RLPT structure so an error is thrown:

rlpDecode $ DBSL.take 6 $ rlpEncode $ RLPL [ RLPB $ toByteStringS "John", RLPB $ toByteStringS "Snow" ] :: Either String RLPT
-- Left "not enough bytes"

On the other hand, if we try to transform an incorrect value from the decoded RLPT we generate a new error:

rlpDecode $ rlpEncode $ RLPB $ toByteStringS "\STX" :: Either String Bool
-- Left "RLPT value couldn't ve transformed into the required type"

If a ByteString is the result of the concatenation of more than one serialized RLPT structure, only the first one would be decoded. This isn't quite specified in the Yellow Paper although it is possible that an error should be thrown when finding trailing bytes:

a = rlpEncode $ RLPL [ RLPB $ toByteStringS "John", RLPB $ toByteStringS "Snow" ]
b = DBSL.append a a
-- "\202\132John\132Snow\202\132John\132Snow"
rlpDecode b :: Either String RLPT
-- Right (RLPL [RLPB "John",RLPB "Snow"])