Skip to content

Commit

Permalink
Merge #1618
Browse files Browse the repository at this point in the history
1618: Simplify the en/decoder for PBFtChainState r=mrBliss a=mrBliss

Fixes #1609.

Since we're breaking backwards compatibility of the `ExtLedgerState` serialisation format, we can get rid of the code dealing with backwards compatibility in `PBFtChainState`.

Nevertheless, start using `Versioned` for `PBFtChainState` so that it will be easier in the future to handle changes to the format.

Co-authored-by: Thomas Winant <[email protected]>
  • Loading branch information
iohk-bors[bot] and mrBliss authored Feb 11, 2020
2 parents 34ff528 + d1cac31 commit c0f1e1c
Show file tree
Hide file tree
Showing 9 changed files with 271 additions and 80 deletions.
2 changes: 2 additions & 0 deletions ouroboros-consensus/ouroboros-consensus.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -137,6 +137,7 @@ library
Ouroboros.Consensus.Util.Singletons
Ouroboros.Consensus.Util.STM
Ouroboros.Consensus.Util.TraceSize
Ouroboros.Consensus.Util.Versioned

-- Storing things on disk
Ouroboros.Storage.Common
Expand Down Expand Up @@ -303,6 +304,7 @@ test-suite test-consensus
Test.Consensus.Node
Test.Consensus.Protocol.PBFT
Test.Consensus.ResourceRegistry
Test.Consensus.Util.Versioned
Test.ThreadNet.BFT
Test.ThreadNet.DualPBFT
Test.ThreadNet.General
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
Expand Down Expand Up @@ -40,7 +41,6 @@ module Ouroboros.Consensus.Protocol.PBFT.ChainState (

import Codec.Serialise (Serialise (..))
import Codec.Serialise.Decoding (Decoder)
import qualified Codec.Serialise.Decoding as Serialise
import Codec.Serialise.Encoding (Encoding)
import qualified Codec.Serialise.Encoding as Serialise
import qualified Control.Exception as Exn
Expand All @@ -54,6 +54,7 @@ import Data.Word
import GHC.Generics (Generic)
import GHC.Stack

import Cardano.Binary (enforceSize)
import Cardano.Prelude (NoUnexpectedThunks)

import Ouroboros.Network.Block (SlotNo (..))
Expand All @@ -64,6 +65,7 @@ import Ouroboros.Consensus.Protocol.Abstract
import Ouroboros.Consensus.Protocol.PBFT.ChainState.HeaderHashBytes
import Ouroboros.Consensus.Protocol.PBFT.Crypto
import Ouroboros.Consensus.Util (repeatedly)
import Ouroboros.Consensus.Util.Versioned

{-------------------------------------------------------------------------------
Types
Expand Down Expand Up @@ -565,58 +567,35 @@ fromList k n (anchor, signers, ebbs) =
Serialization
-------------------------------------------------------------------------------}

serializationFormatVersion1 :: Word8
serializationFormatVersion1 = 1

serializationFormatVersion2 :: Word8
serializationFormatVersion2 = 2
-- CHANGELOG
--
-- Version 0 is 2 fields, the anchor and the window. Note that it does not
-- have the version marker.
--
-- Version 1 has 4 fields, the version marker, anchor, window, and @~(Map
-- SlotNo (WithOrigin SlotNo))@.
--
-- Version 2 has 4 fields, the version marker, anchor, window, and @~(Maybe EbbInfo)@.

encodePBftChainState :: (PBftCrypto c, Serialise (PBftVerKeyHash c))
=> PBftChainState c -> Encoding
encodePBftChainState st@PBftChainState{..} = mconcat [
Serialise.encodeListLen 4
, encode serializationFormatVersion2
, encode (withOriginToMaybe anchor)
, encode signers
, encode ebbs'
]
serializationFormatVersion0 :: VersionNumber
serializationFormatVersion0 = 0

encodePBftChainState
:: (PBftCrypto c, Serialise (PBftVerKeyHash c))
=> PBftChainState c -> Encoding
encodePBftChainState st@PBftChainState{..} =
encodeVersion serializationFormatVersion0 $ mconcat [
Serialise.encodeListLen 3
, encode (withOriginToMaybe anchor)
, encode signers
, encode ebbs'
]
where
(anchor, signers, ebbs') = toList st

decodePBftChainState :: (PBftCrypto c, Serialise (PBftVerKeyHash c), HasCallStack)
=> SecurityParam
-> WindowSize
-> Decoder s (PBftChainState c)
decodePBftChainState k n = Serialise.decodeListLen >>= \case
2 -> do -- Version is 0
decodePBftChainState k n = decodeVersion
[(serializationFormatVersion0, Decode decodePBftChainState0)]
where
decodePBftChainState0 = do
enforceSize "PBftChainState" 3
anchor <- withOriginFromMaybe <$> decode
signers <- decode
return $ fromList k n (anchor, signers, ebbsEmpty)
4 -> decode >>= \v -> if
| v == serializationFormatVersion1 -> do
anchor <- withOriginFromMaybe <$> decode
signers <- decode
ebbs' <- decode
let _ = ebbs' :: Map SlotNo (WithOrigin SlotNo)
-- NB we discard ebbs'
return $ fromList k n (anchor, signers, ebbsEmpty)
| v == serializationFormatVersion2 -> do
anchor <- withOriginFromMaybe <$> decode
signers <- decode
ebbs' <- decode
return $ fromList k n (anchor, signers, ebbs')
| otherwise ->
error $ "unexpected serialisation format version: " <> show v
o -> error $ "unexpected list length: " <> show o
ebbs' <- decode
return $ fromList k n (anchor, signers, ebbs')

instance Serialise (PBftVerKeyHash c) => Serialise (PBftSigner c) where
encode = encode . toPair
Expand Down
124 changes: 124 additions & 0 deletions ouroboros-consensus/src/Ouroboros/Consensus/Util/Versioned.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,124 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Ouroboros.Consensus.Util.Versioned
( Versioned (..)
, VersionNumber -- opaque
, VersionError (..)
, VersionDecoder (..)
, encodeVersioned
, encodeVersion
, decodeVersioned
, decodeVersion
) where

import Codec.Serialise (Serialise (..))
import Codec.Serialise.Decoding (Decoder, decodeWord8)
import Codec.Serialise.Encoding (Encoding, encodeListLen, encodeWord8)
import Control.Exception (Exception)
import Data.Word (Word8)

import Cardano.Binary (enforceSize)


newtype VersionNumber = VersionNumber Word8
deriving newtype (Eq, Ord, Num, Show)

instance Serialise VersionNumber where
encode (VersionNumber w) = encodeWord8 w
decode = VersionNumber <$> decodeWord8

data Versioned a = Versioned
{ versionNumber :: !VersionNumber
, versioned :: !a
} deriving (Eq, Show)

data VersionError
= IncompatibleVersion VersionNumber String
-- ^ We cannot deserialise the version of the data with the given
-- 'VersionNumber' because its data format is incompatible.
--
-- For example, the given format lacks data that was added in later
-- version that cannot be reconstructed from scratch.
| UnknownVersion VersionNumber
-- ^ The given 'VersionNumber' is unknown and thus not supported.
| MigrationFailed VersionNumber String
-- ^ A migration from the given 'VersionNumber' failed. See 'Migrate'.
deriving stock (Show)
deriving anyclass (Exception)

-- | How to decode a version of a format.
data VersionDecoder a where
-- | This version is incompatible, fail with 'IncompatibleVersion' and the
-- given message.
Incompatible :: String
-> VersionDecoder a

-- | Decode the version using the given 'Decoder'.
Decode :: (forall s. Decoder s a)
-> VersionDecoder a

-- | Decode an other format (@from@) and migrate from that. When migration
-- fails, the version decoder will fail with @MigrationFailed@.
Migrate :: VersionDecoder from
-> (from -> Either String to)
-> VersionDecoder to

-- | Return a 'Decoder' for the given 'VersionDecoder'.
getVersionDecoder
:: VersionNumber
-> VersionDecoder a
-> forall s. Decoder s a
getVersionDecoder vn = \case
Incompatible msg -> fail $ show $ IncompatibleVersion vn msg
Decode dec -> dec
Migrate vDec migrate -> do
from <- getVersionDecoder vn vDec
case migrate from of
Left msg -> fail $ show $ MigrationFailed vn msg
Right to -> return to

-- | Given a 'VersionNumber' and the encoding of an @a@, encode the
-- corresponding @'Versioned' a@. Use 'decodeVersion' to decode it.
encodeVersion
:: VersionNumber
-> Encoding
-> Encoding
encodeVersion vn encodedA = mconcat
[ encodeListLen 2
, encode vn
, encodedA
]

-- | Decode a /versioned/ @a@ (encoded using 'encodeVersion' or
-- 'encodeVersioned').
--
-- The corresponding 'VersionDecoder' for the deserialised 'VersionNumber' is
-- looked up in the given list. The first match is used (using the semantics
-- of 'lookup'). When no match is found, a decoder that fails with
-- 'UnknownVersion' is returned.
decodeVersion
:: [(VersionNumber, VersionDecoder a)]
-> forall s. Decoder s a
decodeVersion versionDecoders =
versioned <$> decodeVersioned versionDecoders

encodeVersioned
:: ( a -> Encoding)
-> (Versioned a -> Encoding)
encodeVersioned enc (Versioned vn a) =
encodeVersion vn (enc a)

decodeVersioned
:: [(VersionNumber, VersionDecoder a)]
-> forall s. Decoder s (Versioned a)
decodeVersioned versionDecoders = do
enforceSize "Versioned" 2
vn <- decode
case lookup vn versionDecoders of
Nothing -> fail $ show $ UnknownVersion vn
Just vDec -> Versioned vn <$> getVersionDecoder vn vDec
2 changes: 2 additions & 0 deletions ouroboros-consensus/test-consensus/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import qualified Test.Consensus.Mempool (tests)
import qualified Test.Consensus.Node (tests)
import qualified Test.Consensus.Protocol.PBFT (tests)
import qualified Test.Consensus.ResourceRegistry (tests)
import qualified Test.Consensus.Util.Versioned (tests)
import qualified Test.ThreadNet.BFT (tests)
import qualified Test.ThreadNet.DualPBFT (tests)
import qualified Test.ThreadNet.LeaderSchedule (tests)
Expand All @@ -38,6 +39,7 @@ tests =
, Test.Consensus.Node.tests
, Test.Consensus.Protocol.PBFT.tests
, Test.Consensus.ResourceRegistry.tests
, Test.Consensus.Util.Versioned.tests
, Test.ThreadNet.Util.Tests.tests
, Test.ThreadNet.BFT.tests
, Test.ThreadNet.LeaderSchedule.tests
Expand Down
37 changes: 6 additions & 31 deletions ouroboros-consensus/test-consensus/Test/Consensus/Ledger/Byron.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,9 +98,6 @@ tests = testGroup "Byron"
-- Note that for most Byron types, we simply wrap the en/decoders from
-- cardano-ledger, which already has golden tests for them.
[ test_golden_ChainState
, test_golden_ChainState_backwardsCompat_version0
, test_golden_ChainState_backwardsCompat_version1
, test_golden_ChainState_backwardsCompat_version2
, test_golden_LedgerState
, test_golden_GenTxId
, test_golden_UPIState
Expand Down Expand Up @@ -257,9 +254,8 @@ secParam = SecurityParam 2
windowSize :: CS.WindowSize
windowSize = CS.WindowSize 2

exampleChainStateWithoutEBB, exampleChainStateWithEBB :: ChainState (BlockProtocol ByronBlock)
(exampleChainStateWithoutEBB, exampleChainStateWithEBB) =
(withoutEBB, withEBB)
exampleChainState :: ChainState (BlockProtocol ByronBlock)
exampleChainState = withEBB
where
signers = map (`CS.PBftSigner` CC.exampleKeyHash) [1..4]

Expand All @@ -283,29 +279,8 @@ test_golden_ChainState :: TestTree
test_golden_ChainState = goldenTestCBOR
"ChainState"
encodeByronChainState
exampleChainStateWithEBB
"test-consensus/golden/cbor/byron/ChainState2"

test_golden_ChainState_backwardsCompat_version0 :: TestTree
test_golden_ChainState_backwardsCompat_version0 =
testCase "ChainState version 0" $ goldenTestCBORBackwardsCompat
(decodeByronChainState secParam)
exampleChainStateWithoutEBB
"test-consensus/golden/cbor/byron/ChainState0"

test_golden_ChainState_backwardsCompat_version1 :: TestTree
test_golden_ChainState_backwardsCompat_version1 =
testCase "ChainState version 1" $ goldenTestCBORBackwardsCompat
(decodeByronChainState secParam)
exampleChainStateWithoutEBB
"test-consensus/golden/cbor/byron/ChainState1"

test_golden_ChainState_backwardsCompat_version2 :: TestTree
test_golden_ChainState_backwardsCompat_version2 =
testCase "ChainState version 2" $ goldenTestCBORBackwardsCompat
(decodeByronChainState secParam)
exampleChainStateWithEBB
"test-consensus/golden/cbor/byron/ChainState2"
exampleChainState
"test-consensus/golden/cbor/byron/ChainState0"

test_golden_LedgerState :: TestTree
test_golden_LedgerState = goldenTestCBOR
Expand Down Expand Up @@ -350,13 +325,13 @@ goldenTestCBOR name enc a path =

-- | Check whether we can successfully decode the contents of the given file.
-- This file will typically contain an older serialisation format.
goldenTestCBORBackwardsCompat
_goldenTestCBORBackwardsCompat
:: (Eq a, Show a)
=> (forall s. Decoder s a)
-> a
-> FilePath
-> Assertion
goldenTestCBORBackwardsCompat dec a path = do
_goldenTestCBORBackwardsCompat dec a path = do
bytes <- Lazy.readFile path
case deserialiseFromBytes dec bytes of
Left failure
Expand Down
Loading

0 comments on commit c0f1e1c

Please sign in to comment.