@@ -28,39 +28,27 @@ module Test.Util.Serialisation.Roundtrip (
2828 , roundtrip_SerialiseNodeToNode
2929 , roundtrip_all
3030 , roundtrip_envelopes
31- -- * Roundtrip tests for 'Example's
32- , examplesRoundtrip
3331 ) where
3432
3533import Codec.CBOR.Decoding (Decoder )
3634import Codec.CBOR.Encoding (Encoding )
37- import Codec.CBOR.FlatTerm (toFlatTerm , validFlatTerm )
38- import Codec.CBOR.Read (DeserialiseFailure , deserialiseFromBytes )
35+ import Codec.CBOR.Read (deserialiseFromBytes )
3936import Codec.CBOR.Write (toLazyByteString )
40- import Codec.Serialise (decode , encode )
41- import Control.Arrow (left )
42- import Control.Monad (unless )
4337import qualified Data.ByteString.Base16.Lazy as Base16
4438import qualified Data.ByteString.Lazy as Lazy
4539import qualified Data.ByteString.Lazy.Char8 as Char8
4640import qualified Data.ByteString.Short as Short
4741import Data.Function (on )
48- import Data.Maybe (fromMaybe )
49- import qualified Data.Text.Lazy as T
5042import Data.Typeable
5143import GHC.Generics (Generic )
5244import Ouroboros.Consensus.Block
5345import Ouroboros.Consensus.HeaderValidation (AnnTip )
5446import Ouroboros.Consensus.Ledger.Abstract (LedgerState )
55- import Ouroboros.Consensus.Ledger.Extended (ExtLedgerState ,
56- decodeExtLedgerState , encodeExtLedgerState )
5747import Ouroboros.Consensus.Ledger.Query (BlockQuery , Query (.. ),
5848 QueryVersion )
5949import qualified Ouroboros.Consensus.Ledger.Query as Query
6050import Ouroboros.Consensus.Ledger.SupportsMempool (ApplyTxErr , GenTx ,
6151 GenTxId )
62- import Ouroboros.Consensus.Ledger.SupportsProtocol
63- (LedgerSupportsProtocol )
6452import Ouroboros.Consensus.Node.NetworkProtocolVersion
6553import Ouroboros.Consensus.Node.Run (SerialiseNodeToClientConstraints ,
6654 SerialiseNodeToNodeConstraints (.. ))
@@ -73,12 +61,9 @@ import Ouroboros.Network.Block (Serialised (..), fromSerialised,
7361 mkSerialised )
7462import Quiet (Quiet (.. ))
7563import Test.Tasty
76- import Test.Tasty.ExpectedFailure (expectFailBecause )
7764import Test.Tasty.QuickCheck
7865import Test.Util.Orphans.Arbitrary ()
79- import Test.Util.Serialisation.Examples (Examples (.. ), Labelled )
8066import Test.Util.Serialisation.SomeResult (SomeResult (.. ))
81- import Text.Pretty.Simple (pShow )
8267
8368{- -----------------------------------------------------------------------------
8469 Basic test helpers
@@ -93,75 +78,31 @@ roundtrip enc dec = roundtrip' enc (const <$> dec)
9378
9479-- | Roundtrip property for values annotated with their serialized form
9580--
96- -- In addition, we check that the encoded CBOR is valid using 'validFlatTerm'.
97- --
98- -- We check the roundtrip property both by decoding from a 'FlatTerm' directly, and from a bytestring.
99- --
100- -- Decoding from a 'FlatTerm' has the advantage that it allows to
101- -- catch bugs more
102- -- [easily](https://hackage.haskell.org/package/cborg-0.2.9.0/docs/Codec-CBOR-FlatTerm.html):
103- --
104- -- The FlatTerm form is very simple and internally mirrors the
105- -- original Encoding type very carefully. The intention here
106- -- is that once you have Encoding and Decoding values for your
107- -- types, you can round-trip values through FlatTerm to catch
108- -- bugs more easily and with a smaller amount of code to look
109- -- through.
110- --
111- -- We also check 'ByteString' decoding for extra assurance.
112- --
11381-- NOTE: Suppose @a@ consists of a pair of the unannotated value @a'@ and some
11482-- 'Lazy.ByteString'. The roundtrip property will fail if that
11583-- 'Lazy.ByteString' encoding is not equal to @enc a'@. One way in which this
11684-- might happen is if the annotation is not canonical CBOR, but @enc@ does
11785-- produce canonical CBOR.
118- roundtrip' :: forall a .
119- (Eq a , Show a )
86+ roundtrip' :: (Eq a , Show a )
12087 => (a -> Encoding ) -- ^ @enc@
12188 -> (forall s . Decoder s (Lazy. ByteString -> a ))
12289 -> a
12390 -> Property
124- roundtrip' enc dec a = checkRoundtripResult $ do
125- let enc_a = enc a
126- bs = toLazyByteString enc_a
127- flatTerm_a = toFlatTerm enc_a
128-
129- validFlatTerm flatTerm_a ?! " Encoded flat term is not valid: " <> show enc_a
130- -- TODO: the decode test via FlatTerm will currently fail because https://github.com/input-output-hk/cardano-ledger/issues/3741
131- --
132- -- a' <- fromFlatTerm dec flatTerm_a
133- -- a == a' bs ?! pShowNeq a (a' bs)
134- (bsRem, a'' ) <- deserialiseFromBytes dec bs `onError` showByteString bs
135- Lazy. null bsRem ?! " Left-over bytes: " <> toBase16 bsRem
136- a == a'' bs ?! pShowNeq a (a'' bs)
91+ roundtrip' enc dec a = case deserialiseFromBytes dec bs of
92+ Right (bs', a')
93+ | Lazy. null bs'
94+ -> a === a' bs
95+ | otherwise
96+ -> counterexample (" left-over bytes: " <> toBase16 bs') False
97+ Left e
98+ -> counterexample (show e) $
99+ counterexample (toBase16 bs) False
137100 where
138- (?!) :: Bool -> String -> Either String ()
139- cond ?! msg = unless cond $ Left msg
140- infix 1 ?!
141-
142- pShowNeq x y = T. unpack (pShow x) <> " \n \t /= \n " <> T. unpack (pShow y)
143-
144- onError ::
145- Either DeserialiseFailure (Char8. ByteString , Char8. ByteString -> a )
146- -> (DeserialiseFailure -> String )
147- -> Either String (Char8. ByteString , Char8. ByteString -> a )
148- onError result showDeserialiseFailure =
149- left showDeserialiseFailure result
150-
151- showByteString ::
152- Char8. ByteString
153- -> DeserialiseFailure
154- -> String
155- showByteString bs deserialiseFailure =
156- show deserialiseFailure <> " \n " <> " When deserialising " <> toBase16 bs
101+ bs = toLazyByteString (enc a)
157102
158103 toBase16 :: Lazy. ByteString -> String
159104 toBase16 = Char8. unpack . Base16. encode
160105
161- checkRoundtripResult :: Either String () -> Property
162- checkRoundtripResult (Left str) = counterexample str False
163- checkRoundtripResult (Right () ) = property ()
164-
165106{- -----------------------------------------------------------------------------
166107 Test skeleton
167108------------------------------------------------------------------------------}
@@ -651,57 +592,3 @@ decodeThroughSerialised
651592decodeThroughSerialised dec decSerialised = do
652593 serialised <- decSerialised
653594 fromSerialised dec serialised
654-
655- {- -----------------------------------------------------------------------------
656- Roundtrip tests for examples
657- ------------------------------------------------------------------------------}
658-
659- examplesRoundtrip ::
660- forall blk . (SerialiseDiskConstraints blk , Eq blk , Show blk , LedgerSupportsProtocol blk )
661- => CodecConfig blk
662- -> Examples blk
663- -> [TestTree ]
664- examplesRoundtrip codecConfig examples =
665- [ testRoundtripFor " Block" (encodeDisk codecConfig) (decodeDisk codecConfig) exampleBlock
666- , testRoundtripFor " Header hash" encode (const <$> decode) exampleHeaderHash
667- , testRoundtripFor " Ledger state" (encodeDisk codecConfig) (const <$> decodeDisk codecConfig) exampleLedgerState
668- , testRoundtripFor " Annotated tip" (encodeDisk codecConfig) (const <$> decodeDisk codecConfig) exampleAnnTip
669- , testRoundtripFor " Chain dependent state" (encodeDisk codecConfig) (const <$> decodeDisk codecConfig) exampleChainDepState
670- , testRoundtripFor " Extended ledger state" encodeExt (const <$> decodeExt) exampleExtLedgerState
671- ]
672- where
673- testRoundtripFor ::
674- forall a . (Eq a , Show a )
675- => String
676- -> (a -> Encoding )
677- -> (forall s . Decoder s (Char8. ByteString -> a ))
678- -> (Examples blk -> Labelled a )
679- -> TestTree
680- testRoundtripFor testLabel enc dec field =
681- testGroup testLabel
682- [ mkTest exampleName example
683- | (exampleName, example) <- field examples
684- ]
685- where
686- mkTest exampleName example =
687- let
688- runTest = testProperty (fromMaybe " " exampleName) $ once $ roundtrip' enc dec example
689- _3740 = " https://github.com/input-output-hk/cardano-ledger/issues/3740"
690- in
691- case (testLabel, exampleName) of
692- (" Ledger state" , Just " Conway" ) -> expectFailBecause _3740 $ runTest
693- (" Extended ledger state" , Just " Conway" ) -> expectFailBecause _3740 $ runTest
694- _ -> runTest
695-
696- encodeExt =
697- encodeExtLedgerState
698- (encodeDisk codecConfig)
699- (encodeDisk codecConfig)
700- (encodeDisk codecConfig)
701-
702- decodeExt :: forall s . Decoder s (ExtLedgerState blk )
703- decodeExt =
704- decodeExtLedgerState
705- (decodeDisk codecConfig)
706- (decodeDisk codecConfig)
707- (decodeDisk codecConfig)
0 commit comments