{-# LANGUAGE DataKinds #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} module Test.Cardano.Ledger.Allegra.Binary.Annotator ( module Test.Cardano.Ledger.Shelley.Binary.Annotator, ) where import Cardano.Ledger.Allegra.Scripts import Cardano.Ledger.Allegra.TxAuxData import Cardano.Ledger.Allegra.TxBody import Cardano.Ledger.Binary import Cardano.Ledger.Binary.Coders import Cardano.Ledger.Core import qualified Data.Sequence.Strict as StrictSeq import Test.Cardano.Ledger.Allegra.Arbitrary () import Test.Cardano.Ledger.Core.Binary.Annotator import Test.Cardano.Ledger.Shelley.Binary.Annotator instance Era era => DecCBOR (Annotator (AllegraTxAuxDataRaw era)) where decCBOR :: forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decCBOR = forall s. Decoder s TokenType peekTokenType forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case TokenType TypeMapLen -> forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromMap TokenType TypeMapLen64 -> forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromMap TokenType TypeMapLenIndef -> forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromMap TokenType TypeListLen -> forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromList TokenType TypeListLen64 -> forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromList TokenType TypeListLenIndef -> forall s. Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromList TokenType _ -> forall (m :: * -> *) a. MonadFail m => String -> m a fail String "Failed to decode AuxiliaryDataRaw" where decodeFromMap :: Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromMap = forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t decode ( forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t (w :: Wrapped). t -> Decode w t Emit forall era. Map Word64 Metadatum -> StrictSeq (Timelock era) -> AllegraTxAuxDataRaw era AllegraTxAuxDataRaw) forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann forall t (w :: Wrapped). DecCBOR t => Decode w t From forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t (w :: Wrapped). t -> Decode w t Emit forall a. StrictSeq a StrictSeq.empty) ) decodeFromList :: Decoder s (Annotator (AllegraTxAuxDataRaw era)) decodeFromList = forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t decode ( forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode ('Closed 'Dense) t RecD forall era. Map Word64 Metadatum -> StrictSeq (Timelock era) -> AllegraTxAuxDataRaw era AllegraTxAuxDataRaw) forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann forall t (w :: Wrapped). DecCBOR t => Decode w t From forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t D (forall (t :: * -> *) (m :: * -> *) a. (Traversable t, Monad m) => t (m a) -> m (t a) sequence forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a s. DecCBOR a => Decoder s a decCBOR) ) deriving via (Mem (AllegraTxAuxDataRaw era)) instance Era era => DecCBOR (Annotator (AllegraTxAuxData era)) instance Era era => DecCBOR (Annotator (TimelockRaw era)) where decCBOR :: forall s. Decoder s (Annotator (TimelockRaw era)) decCBOR = forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t decode (forall t. Text -> (Word -> Decode 'Open t) -> Decode ('Closed 'Dense) t Summands Text "TimelockRaw" Word -> Decode 'Open (Annotator (TimelockRaw era)) decRaw) where decRaw :: Word -> Decode 'Open (Annotator (TimelockRaw era)) decRaw :: Word -> Decode 'Open (Annotator (TimelockRaw era)) decRaw Word 0 = forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode 'Open t SumD forall {k} (era :: k). KeyHash 'Witness -> TimelockRaw era TimelockSignature forall a (w1 :: Wrapped) t (w :: Density). Typeable a => Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t <! forall t (w :: Wrapped). DecCBOR t => Decode w t From) decRaw Word 1 = forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode 'Open t SumD forall {k} (era :: k). StrictSeq (Timelock era) -> TimelockRaw era TimelockAllOf) forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t D (forall (t :: * -> *) (m :: * -> *) a. (Traversable t, Monad m) => t (m a) -> m (t a) sequence forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a s. DecCBOR a => Decoder s a decCBOR) decRaw Word 2 = forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode 'Open t SumD forall {k} (era :: k). StrictSeq (Timelock era) -> TimelockRaw era TimelockAnyOf) forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t D (forall (t :: * -> *) (m :: * -> *) a. (Traversable t, Monad m) => t (m a) -> m (t a) sequence forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a s. DecCBOR a => Decoder s a decCBOR) decRaw Word 3 = forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode 'Open t SumD forall {k} (era :: k). Int -> StrictSeq (Timelock era) -> TimelockRaw era TimelockMOf) forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann forall t (w :: Wrapped). DecCBOR t => Decode w t From forall a t (w1 :: Wrapped) (d :: Density). (Typeable a, Typeable t) => Decode w1 (Annotator (a -> t)) -> Decode ('Closed d) (Annotator a) -> Decode w1 (Annotator t) <*! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t D (forall (t :: * -> *) (m :: * -> *) a. (Traversable t, Monad m) => t (m a) -> m (t a) sequence forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a s. DecCBOR a => Decoder s a decCBOR) decRaw Word 4 = forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode 'Open t SumD forall {k} (era :: k). SlotNo -> TimelockRaw era TimelockTimeStart forall a (w1 :: Wrapped) t (w :: Density). Typeable a => Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t <! forall t (w :: Wrapped). DecCBOR t => Decode w t From) decRaw Word 5 = forall t1 (w :: Wrapped). Typeable t1 => Decode w t1 -> Decode w (Annotator t1) Ann (forall t. t -> Decode 'Open t SumD forall {k} (era :: k). SlotNo -> TimelockRaw era TimelockTimeExpire forall a (w1 :: Wrapped) t (w :: Density). Typeable a => Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t <! forall t (w :: Wrapped). DecCBOR t => Decode w t From) decRaw Word n = forall (w :: Wrapped) t. Word -> Decode w t Invalid Word n instance Era era => DecCBOR (Annotator (Timelock era)) where decCBOR :: forall s. Decoder s (Annotator (Timelock era)) decCBOR = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall {k} (era :: k). MemoBytes (TimelockRaw era) -> Timelock era MkTimelock forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a s. DecCBOR a => Decoder s a decCBOR instance (DecCBOR m, Monoid m, AllegraEraTxBody era) => DecCBOR (Annotator (AllegraTxBodyRaw m era)) where decCBOR :: forall s. Decoder s (Annotator (AllegraTxBodyRaw m era)) decCBOR = forall (f :: * -> *) a. Applicative f => a -> f a pure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall a s. DecCBOR a => Decoder s a decCBOR deriving via Mem (AllegraTxBodyRaw () era) instance AllegraEraTxBody era => DecCBOR (Annotator (AllegraTxBody era))