{-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeApplications #-} module Test.Cardano.Ledger.BinarySpec (spec) where import Cardano.Ledger.BaseTypes import Cardano.Ledger.Binary import Cardano.Ledger.Coin import Cardano.Ledger.Compactible import Cardano.Ledger.DRep (DRep (..), DRepState (..)) import Cardano.Ledger.Hashes (EraIndependentData, SafeHash, ScriptHash) import Cardano.Ledger.Keys import Cardano.Ledger.TxIn import Cardano.Ledger.UMap (RDPair) import qualified PlutusLedgerApi.V1 as PV1 import Test.Cardano.Ledger.Binary (decoderEquivalenceSpec) import Test.Cardano.Ledger.Binary.RoundTrip import Test.Cardano.Ledger.Common import Test.Cardano.Ledger.Core.Arbitrary () import Test.Cardano.Ledger.Core.Binary.Annotator () spec :: Spec spec :: Spec spec = do String -> Spec -> Spec forall a. HasCallStack => String -> SpecWith a -> SpecWith a describe String "RoundTrip" (Spec -> Spec) -> Spec -> Spec forall a b. (a -> b) -> a -> b $ do forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @Coin forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @(CompactForm Coin) String -> (Coin -> Expectation) -> Spec forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "Encode CompactCoin - Decode Coin" ((Coin -> Expectation) -> Spec) -> (Coin -> Expectation) -> Spec forall a b. (a -> b) -> a -> b $ forall t. (Show t, Eq t, Typeable t, HasCallStack) => Trip t t -> t -> Expectation roundTripExpectation @Coin ((Coin -> Encoding) -> (forall s. Decoder s Coin) -> Trip Coin Coin forall a b. (a -> Encoding) -> (forall s. Decoder s b) -> Trip a b mkTrip (CompactForm Coin -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR (CompactForm Coin -> Encoding) -> (Coin -> CompactForm Coin) -> Coin -> Encoding forall b c a. (b -> c) -> (a -> b) -> a -> c . HasCallStack => Coin -> CompactForm Coin Coin -> CompactForm Coin compactCoinOrError) Decoder s Coin forall s. Decoder s Coin forall a s. DecCBOR a => Decoder s a decCBOR) String -> (Coin -> Expectation) -> Spec forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "Encode Coin - Decode CompactCoin" ((Coin -> Expectation) -> Spec) -> (Coin -> Expectation) -> Spec forall a b. (a -> b) -> a -> b $ forall t. (Show t, Eq t, Typeable t, HasCallStack) => Trip t t -> t -> Expectation roundTripExpectation @Coin ((Coin -> Encoding) -> (forall s. Decoder s Coin) -> Trip Coin Coin forall a b. (a -> Encoding) -> (forall s. Decoder s b) -> Trip a b mkTrip Coin -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR (CompactForm Coin -> Coin forall a. Compactible a => CompactForm a -> a fromCompact (CompactForm Coin -> Coin) -> Decoder s (CompactForm Coin) -> Decoder s Coin forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (CompactForm Coin) forall s. Decoder s (CompactForm Coin) forall a s. DecCBOR a => Decoder s a decCBOR)) forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @ProtVer forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @Nonce forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @Url forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @DnsName forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @Port forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @ActiveSlotCoeff forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @Network forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @BlocksMade forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @TxIx forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @CertIx forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @Anchor forall t. (Show t, Eq t, Arbitrary t, ToCBOR t, DecCBOR (Annotator t)) => Spec roundTripAnnCborSpec @BootstrapWitness forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @BootstrapWitness forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @TxId forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @GenDelegPair forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @GenDelegs forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @DRepState forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @DRep forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @RDPair forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @ScriptHash forall t. (Show t, Eq t, Arbitrary t, EncCBOR t, DecCBOR t) => Spec roundTripCborSpec @(SafeHash EraIndependentData) String -> Spec -> Spec forall a. HasCallStack => String -> SpecWith a -> SpecWith a describe String "DecCBOR instances equivalence" (Spec -> Spec) -> Spec -> Spec forall a b. (a -> b) -> a -> b $ do forall t. (Eq t, ToCBOR t, DecCBOR (Annotator t), Arbitrary t, Show t) => Version -> Version -> Spec decoderEquivalenceSpec @BootstrapWitness Version forall a. Bounded a => a minBound Version forall a. Bounded a => a maxBound forall t. (Eq t, ToCBOR t, DecCBOR (Annotator t), Arbitrary t, Show t) => Version -> Version -> Spec decoderEquivalenceSpec @(WitVKey 'Witness) Version forall a. Bounded a => a minBound Version forall a. Bounded a => a maxBound forall t. (Eq t, ToCBOR t, DecCBOR (Annotator t), Arbitrary t, Show t) => Version -> Version -> Spec decoderEquivalenceSpec @PV1.Data Version forall a. Bounded a => a minBound Version forall a. Bounded a => a maxBound