{-# 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 Test.Cardano.Ledger.Binary.RoundTrip import Test.Cardano.Ledger.Common import Test.Cardano.Ledger.Core.Arbitrary () spec :: Spec spec :: Spec spec = do forall a. HasCallStack => String -> SpecWith a -> SpecWith a describe String "RoundTrip" 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) forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "Encode CompactCoin - Decode Coin" forall a b. (a -> b) -> a -> b $ forall t. (Show t, Eq t, Typeable t, HasCallStack) => Trip t t -> t -> Expectation roundTripExpectation @Coin (forall a b. (a -> Encoding) -> (forall s. Decoder s b) -> Trip a b mkTrip (forall a. EncCBOR a => a -> Encoding encCBOR forall b c a. (b -> c) -> (a -> b) -> a -> c . HasCallStack => Coin -> CompactForm Coin compactCoinOrError) forall a s. DecCBOR a => Decoder s a decCBOR) forall prop. (HasCallStack, Testable prop) => String -> prop -> Spec prop String "Encode Coin - Decode CompactCoin" forall a b. (a -> b) -> a -> b $ forall t. (Show t, Eq t, Typeable t, HasCallStack) => Trip t t -> t -> Expectation roundTripExpectation @Coin (forall a b. (a -> Encoding) -> (forall s. Decoder s b) -> Trip a b mkTrip forall a. EncCBOR a => a -> Encoding encCBOR (forall a. Compactible a => CompactForm a -> a fromCompact forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> 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 @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)