{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Cardano.Ledger.Conway.Rules.Utxo (
allegraToConwayUtxoPredFailure,
babbageToConwayUtxoPredFailure,
alonzoToConwayUtxoPredFailure,
ConwayUtxoPredFailure (..),
) where
import Cardano.Ledger.Address (Addr, RewardAccount)
import Cardano.Ledger.Allegra.Rules (AllegraUtxoPredFailure, shelleyToAllegraUtxoPredFailure)
import qualified Cardano.Ledger.Allegra.Rules as Allegra (AllegraUtxoPredFailure (..))
import Cardano.Ledger.Alonzo.Rules (
AlonzoUtxoEvent,
AlonzoUtxoPredFailure,
AlonzoUtxosPredFailure,
)
import qualified Cardano.Ledger.Alonzo.Rules as Alonzo (
AlonzoUtxoEvent (UtxosEvent),
AlonzoUtxoPredFailure (..),
)
import Cardano.Ledger.Alonzo.Tx (AlonzoTx (..))
import Cardano.Ledger.Babbage.Rules (BabbageUtxoPredFailure)
import qualified Cardano.Ledger.Babbage.Rules as Babbage (
BabbageUtxoPredFailure (..),
utxoTransition,
)
import Cardano.Ledger.BaseTypes (
Mismatch (..),
Network,
Relation (..),
ShelleyBase,
SlotNo,
swapMismatch,
unswapMismatch,
)
import Cardano.Ledger.Binary (DecCBOR (..), EncCBOR (..))
import Cardano.Ledger.Binary.Coders (
Decode (..),
Encode (..),
decode,
encode,
(!>),
(<!),
)
import Cardano.Ledger.Coin (Coin, DeltaCoin)
import Cardano.Ledger.Conway.Core
import Cardano.Ledger.Conway.Era (ConwayEra, ConwayUTXO, ConwayUTXOS)
import Cardano.Ledger.Conway.Rules.Utxos (
ConwayUtxosPredFailure (..),
)
import Cardano.Ledger.Plutus (ExUnits)
import qualified Cardano.Ledger.Shelley.LedgerState as Shelley (UTxOState)
import Cardano.Ledger.Shelley.Rules (ShelleyUtxoPredFailure)
import qualified Cardano.Ledger.Shelley.Rules as Shelley (UtxoEnv)
import Cardano.Ledger.TxIn (TxIn)
import Cardano.Ledger.UTxO (EraUTxO, UTxO (..))
import Control.DeepSeq (NFData)
import Control.State.Transition.Extended (Embed (..), STS (..))
import Data.List.NonEmpty (NonEmpty)
import Data.Set (Set)
import GHC.Generics (Generic)
import GHC.Natural (Natural)
import NoThunks.Class (InspectHeapNamed (..), NoThunks (..))
data ConwayUtxoPredFailure era
=
UtxosFailure (PredicateFailure (EraRule "UTXOS" era))
|
BadInputsUTxO
!(Set TxIn)
| OutsideValidityIntervalUTxO
!ValidityInterval
!SlotNo
| MaxTxSizeUTxO
!(Mismatch 'RelLTEQ Integer)
| InputSetEmptyUTxO
| FeeTooSmallUTxO
!(Mismatch 'RelGTEQ Coin)
| ValueNotConservedUTxO
!(Mismatch 'RelEQ (Value era))
|
WrongNetwork
!Network
!(Set Addr)
| WrongNetworkWithdrawal
!Network
!(Set RewardAccount)
|
OutputTooSmallUTxO
![TxOut era]
|
OutputBootAddrAttrsTooBig
![TxOut era]
|
OutputTooBigUTxO
![(Int, Int, TxOut era)]
| InsufficientCollateral
!DeltaCoin
!Coin
|
ScriptsNotPaidUTxO
!(UTxO era)
| ExUnitsTooBigUTxO
!(Mismatch 'RelLTEQ ExUnits)
|
CollateralContainsNonADA !(Value era)
|
WrongNetworkInTxBody
!(Mismatch 'RelEQ Network)
|
OutsideForecast
!SlotNo
|
TooManyCollateralInputs
!(Mismatch 'RelLTEQ Natural)
| NoCollateralInputs
|
IncorrectTotalCollateralField
!DeltaCoin
!Coin
|
BabbageOutputTooSmallUTxO
![(TxOut era, Coin)]
|
BabbageNonDisjointRefInputs
!(NonEmpty TxIn)
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x.
Rep (ConwayUtxoPredFailure era) x -> ConwayUtxoPredFailure era
forall era x.
ConwayUtxoPredFailure era -> Rep (ConwayUtxoPredFailure era) x
$cto :: forall era x.
Rep (ConwayUtxoPredFailure era) x -> ConwayUtxoPredFailure era
$cfrom :: forall era x.
ConwayUtxoPredFailure era -> Rep (ConwayUtxoPredFailure era) x
Generic)
type instance EraRuleFailure "UTXO" ConwayEra = ConwayUtxoPredFailure ConwayEra
type instance EraRuleEvent "UTXO" ConwayEra = AlonzoUtxoEvent ConwayEra
instance InjectRuleFailure "UTXO" ConwayUtxoPredFailure ConwayEra
instance InjectRuleFailure "UTXO" BabbageUtxoPredFailure ConwayEra where
injectFailure :: BabbageUtxoPredFailure ConwayEra -> EraRuleFailure "UTXO" ConwayEra
injectFailure = forall era. BabbageUtxoPredFailure era -> ConwayUtxoPredFailure era
babbageToConwayUtxoPredFailure
instance InjectRuleFailure "UTXO" AlonzoUtxoPredFailure ConwayEra where
injectFailure :: AlonzoUtxoPredFailure ConwayEra -> EraRuleFailure "UTXO" ConwayEra
injectFailure = forall era. AlonzoUtxoPredFailure era -> ConwayUtxoPredFailure era
alonzoToConwayUtxoPredFailure
instance InjectRuleFailure "UTXO" ShelleyUtxoPredFailure ConwayEra where
injectFailure :: ShelleyUtxoPredFailure ConwayEra -> EraRuleFailure "UTXO" ConwayEra
injectFailure =
forall era.
(EraRuleFailure "PPUP" era ~ VoidEraRule "PPUP" era) =>
AllegraUtxoPredFailure era -> ConwayUtxoPredFailure era
allegraToConwayUtxoPredFailure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ShelleyUtxoPredFailure era -> AllegraUtxoPredFailure era
shelleyToAllegraUtxoPredFailure
instance InjectRuleFailure "UTXO" Allegra.AllegraUtxoPredFailure ConwayEra where
injectFailure :: AllegraUtxoPredFailure ConwayEra -> EraRuleFailure "UTXO" ConwayEra
injectFailure = forall era.
(EraRuleFailure "PPUP" era ~ VoidEraRule "PPUP" era) =>
AllegraUtxoPredFailure era -> ConwayUtxoPredFailure era
allegraToConwayUtxoPredFailure
instance InjectRuleFailure "UTXO" ConwayUtxosPredFailure ConwayEra where
injectFailure :: ConwayUtxosPredFailure ConwayEra -> EraRuleFailure "UTXO" ConwayEra
injectFailure = forall era.
PredicateFailure (EraRule "UTXOS" era) -> ConwayUtxoPredFailure era
UtxosFailure
instance InjectRuleFailure "UTXO" AlonzoUtxosPredFailure ConwayEra where
injectFailure :: AlonzoUtxosPredFailure ConwayEra -> EraRuleFailure "UTXO" ConwayEra
injectFailure =
forall era. AlonzoUtxoPredFailure era -> ConwayUtxoPredFailure era
alonzoToConwayUtxoPredFailure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
PredicateFailure (EraRule "UTXOS" era) -> AlonzoUtxoPredFailure era
Alonzo.UtxosFailure
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (rule :: Symbol) (t :: * -> *) era.
InjectRuleFailure rule t era =>
t era -> EraRuleFailure rule era
injectFailure
deriving instance
( Era era
, Show (Value era)
, Show (PredicateFailure (EraRule "UTXOS" era))
, Show (TxOut era)
, Show (Script era)
, Show TxIn
) =>
Show (ConwayUtxoPredFailure era)
deriving instance
( Era era
, Eq (Value era)
, Eq (PredicateFailure (EraRule "UTXOS" era))
, Eq (TxOut era)
, Eq (Script era)
, Eq TxIn
) =>
Eq (ConwayUtxoPredFailure era)
deriving via
InspectHeapNamed "ConwayUtxoPred" (ConwayUtxoPredFailure era)
instance
NoThunks (ConwayUtxoPredFailure era)
instance
( Era era
, NFData (Value era)
, NFData (TxOut era)
, NFData (PredicateFailure (EraRule "UTXOS" era))
) =>
NFData (ConwayUtxoPredFailure era)
instance
forall era.
( EraTx era
, EraUTxO era
, ConwayEraTxBody era
, AlonzoEraTxWits era
, Tx era ~ AlonzoTx era
, EraRule "UTXO" era ~ ConwayUTXO era
, InjectRuleFailure "UTXO" ShelleyUtxoPredFailure era
, InjectRuleFailure "UTXO" AllegraUtxoPredFailure era
, InjectRuleFailure "UTXO" AlonzoUtxoPredFailure era
, InjectRuleFailure "UTXO" BabbageUtxoPredFailure era
, InjectRuleFailure "UTXO" ConwayUtxoPredFailure era
, Embed (EraRule "UTXOS" era) (ConwayUTXO era)
, Environment (EraRule "UTXOS" era) ~ Shelley.UtxoEnv era
, State (EraRule "UTXOS" era) ~ Shelley.UTxOState era
, Signal (EraRule "UTXOS" era) ~ Tx era
, PredicateFailure (EraRule "UTXO" era) ~ ConwayUtxoPredFailure era
) =>
STS (ConwayUTXO era)
where
type State (ConwayUTXO era) = Shelley.UTxOState era
type Signal (ConwayUTXO era) = AlonzoTx era
type Environment (ConwayUTXO era) = Shelley.UtxoEnv era
type BaseM (ConwayUTXO era) = ShelleyBase
type PredicateFailure (ConwayUTXO era) = ConwayUtxoPredFailure era
type Event (ConwayUTXO era) = AlonzoUtxoEvent era
initialRules :: [InitialRule (ConwayUTXO era)]
initialRules = []
transitionRules :: [TransitionRule (ConwayUTXO era)]
transitionRules = [forall era.
(EraUTxO era, BabbageEraTxBody era, AlonzoEraTxWits era,
Tx era ~ AlonzoTx era,
InjectRuleFailure "UTXO" ShelleyUtxoPredFailure era,
InjectRuleFailure "UTXO" AllegraUtxoPredFailure era,
InjectRuleFailure "UTXO" AlonzoUtxoPredFailure era,
InjectRuleFailure "UTXO" BabbageUtxoPredFailure era,
Environment (EraRule "UTXO" era) ~ UtxoEnv era,
State (EraRule "UTXO" era) ~ UTxOState era,
Signal (EraRule "UTXO" era) ~ AlonzoTx era,
BaseM (EraRule "UTXO" era) ~ ShelleyBase, STS (EraRule "UTXO" era),
Embed (EraRule "UTXOS" era) (EraRule "UTXO" era),
Environment (EraRule "UTXOS" era) ~ UtxoEnv era,
State (EraRule "UTXOS" era) ~ UTxOState era,
Signal (EraRule "UTXOS" era) ~ Tx era) =>
TransitionRule (EraRule "UTXO" era)
Babbage.utxoTransition @era]
instance
( Era era
, STS (ConwayUTXOS era)
, PredicateFailure (EraRule "UTXOS" era) ~ ConwayUtxosPredFailure era
, Event (EraRule "UTXOS" era) ~ Event (ConwayUTXOS era)
) =>
Embed (ConwayUTXOS era) (ConwayUTXO era)
where
wrapFailed :: PredicateFailure (ConwayUTXOS era)
-> PredicateFailure (ConwayUTXO era)
wrapFailed = forall era.
PredicateFailure (EraRule "UTXOS" era) -> ConwayUtxoPredFailure era
UtxosFailure
wrapEvent :: Event (ConwayUTXOS era) -> Event (ConwayUTXO era)
wrapEvent = forall era. Event (EraRule "UTXOS" era) -> AlonzoUtxoEvent era
Alonzo.UtxosEvent
instance
( Era era
, EncCBOR (TxOut era)
, EncCBOR (Value era)
, EncCBOR (PredicateFailure (EraRule "UTXOS" era))
) =>
EncCBOR (ConwayUtxoPredFailure era)
where
encCBOR :: ConwayUtxoPredFailure era -> Encoding
encCBOR =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
UtxosFailure PredicateFailure (EraRule "UTXOS" era)
a -> forall t. t -> Word -> Encode 'Open t
Sum (forall era.
PredicateFailure (EraRule "UTXOS" era) -> ConwayUtxoPredFailure era
UtxosFailure @era) Word
0 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To PredicateFailure (EraRule "UTXOS" era)
a
BadInputsUTxO Set TxIn
ins -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. Set TxIn -> ConwayUtxoPredFailure era
BadInputsUTxO @era) Word
1 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set TxIn
ins
OutsideValidityIntervalUTxO ValidityInterval
a SlotNo
b -> forall t. t -> Word -> Encode 'Open t
Sum forall era. ValidityInterval -> SlotNo -> ConwayUtxoPredFailure era
OutsideValidityIntervalUTxO Word
2 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To ValidityInterval
a forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To SlotNo
b
MaxTxSizeUTxO Mismatch 'RelLTEQ Integer
mm -> forall t. t -> Word -> Encode 'Open t
Sum forall era. Mismatch 'RelLTEQ Integer -> ConwayUtxoPredFailure era
MaxTxSizeUTxO Word
3 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBORGroup t => t -> Encode ('Closed 'Dense) t
ToGroup Mismatch 'RelLTEQ Integer
mm
ConwayUtxoPredFailure era
InputSetEmptyUTxO -> forall t. t -> Word -> Encode 'Open t
Sum forall era. ConwayUtxoPredFailure era
InputSetEmptyUTxO Word
4
FeeTooSmallUTxO Mismatch 'RelGTEQ Coin
mm -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. Mismatch 'RelGTEQ Coin -> ConwayUtxoPredFailure era
FeeTooSmallUTxO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch) Word
5 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBORGroup t => t -> Encode ('Closed 'Dense) t
ToGroup (forall (r :: Relation) a. Mismatch r a -> (a, a)
swapMismatch Mismatch 'RelGTEQ Coin
mm)
ValueNotConservedUTxO Mismatch 'RelEQ (Value era)
mm -> forall t. t -> Word -> Encode 'Open t
Sum (forall era.
Mismatch 'RelEQ (Value era) -> ConwayUtxoPredFailure era
ValueNotConservedUTxO @era) Word
6 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBORGroup t => t -> Encode ('Closed 'Dense) t
ToGroup Mismatch 'RelEQ (Value era)
mm
WrongNetwork Network
right Set Addr
wrongs -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. Network -> Set Addr -> ConwayUtxoPredFailure era
WrongNetwork @era) Word
7 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Network
right forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set Addr
wrongs
WrongNetworkWithdrawal Network
right Set RewardAccount
wrongs -> forall t. t -> Word -> Encode 'Open t
Sum (forall era.
Network -> Set RewardAccount -> ConwayUtxoPredFailure era
WrongNetworkWithdrawal @era) Word
8 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Network
right forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set RewardAccount
wrongs
OutputTooSmallUTxO [TxOut era]
outs -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputTooSmallUTxO @era) Word
9 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To [TxOut era]
outs
OutputBootAddrAttrsTooBig [TxOut era]
outs -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputBootAddrAttrsTooBig @era) Word
10 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To [TxOut era]
outs
OutputTooBigUTxO [(Int, Int, TxOut era)]
outs -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. [(Int, Int, TxOut era)] -> ConwayUtxoPredFailure era
OutputTooBigUTxO @era) Word
11 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To [(Int, Int, TxOut era)]
outs
InsufficientCollateral DeltaCoin
a Coin
b -> forall t. t -> Word -> Encode 'Open t
Sum forall era. DeltaCoin -> Coin -> ConwayUtxoPredFailure era
InsufficientCollateral Word
12 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To DeltaCoin
a forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
b
ScriptsNotPaidUTxO UTxO era
a -> forall t. t -> Word -> Encode 'Open t
Sum forall era. UTxO era -> ConwayUtxoPredFailure era
ScriptsNotPaidUTxO Word
13 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To UTxO era
a
ExUnitsTooBigUTxO Mismatch 'RelLTEQ ExUnits
mm -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. Mismatch 'RelLTEQ ExUnits -> ConwayUtxoPredFailure era
ExUnitsTooBigUTxO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch) Word
14 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBORGroup t => t -> Encode ('Closed 'Dense) t
ToGroup (forall (r :: Relation) a. Mismatch r a -> (a, a)
swapMismatch Mismatch 'RelLTEQ ExUnits
mm)
CollateralContainsNonADA Value era
a -> forall t. t -> Word -> Encode 'Open t
Sum forall era. Value era -> ConwayUtxoPredFailure era
CollateralContainsNonADA Word
15 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Value era
a
WrongNetworkInTxBody Mismatch 'RelEQ Network
mm -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. Mismatch 'RelEQ Network -> ConwayUtxoPredFailure era
WrongNetworkInTxBody forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch) Word
16 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBORGroup t => t -> Encode ('Closed 'Dense) t
ToGroup (forall (r :: Relation) a. Mismatch r a -> (a, a)
swapMismatch Mismatch 'RelEQ Network
mm)
OutsideForecast SlotNo
a -> forall t. t -> Word -> Encode 'Open t
Sum forall era. SlotNo -> ConwayUtxoPredFailure era
OutsideForecast Word
17 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To SlotNo
a
TooManyCollateralInputs Mismatch 'RelLTEQ Natural
mm -> forall t. t -> Word -> Encode 'Open t
Sum (forall era. Mismatch 'RelLTEQ Natural -> ConwayUtxoPredFailure era
TooManyCollateralInputs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch) Word
18 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBORGroup t => t -> Encode ('Closed 'Dense) t
ToGroup (forall (r :: Relation) a. Mismatch r a -> (a, a)
swapMismatch Mismatch 'RelLTEQ Natural
mm)
ConwayUtxoPredFailure era
NoCollateralInputs -> forall t. t -> Word -> Encode 'Open t
Sum forall era. ConwayUtxoPredFailure era
NoCollateralInputs Word
19
IncorrectTotalCollateralField DeltaCoin
c1 Coin
c2 -> forall t. t -> Word -> Encode 'Open t
Sum forall era. DeltaCoin -> Coin -> ConwayUtxoPredFailure era
IncorrectTotalCollateralField Word
20 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To DeltaCoin
c1 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
c2
BabbageOutputTooSmallUTxO [(TxOut era, Coin)]
x -> forall t. t -> Word -> Encode 'Open t
Sum forall era. [(TxOut era, Coin)] -> ConwayUtxoPredFailure era
BabbageOutputTooSmallUTxO Word
21 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To [(TxOut era, Coin)]
x
BabbageNonDisjointRefInputs NonEmpty TxIn
x -> forall t. t -> Word -> Encode 'Open t
Sum forall era. NonEmpty TxIn -> ConwayUtxoPredFailure era
BabbageNonDisjointRefInputs Word
22 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To NonEmpty TxIn
x
instance
( Era era
, DecCBOR (TxOut era)
, EncCBOR (Value era)
, DecCBOR (Value era)
, DecCBOR (PredicateFailure (EraRule "UTXOS" era))
) =>
DecCBOR (ConwayUtxoPredFailure era)
where
decCBOR :: forall s. Decoder s (ConwayUtxoPredFailure era)
decCBOR = forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t.
Text -> (Word -> Decode 'Open t) -> Decode ('Closed 'Dense) t
Summands Text
"ConwayUtxoPredFailure" forall a b. (a -> b) -> a -> b
$ \case
Word
0 -> forall t. t -> Decode 'Open t
SumD forall era.
PredicateFailure (EraRule "UTXOS" era) -> ConwayUtxoPredFailure era
UtxosFailure forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
1 -> forall t. t -> Decode 'Open t
SumD forall era. Set TxIn -> ConwayUtxoPredFailure era
BadInputsUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
2 -> forall t. t -> Decode 'Open t
SumD forall era. ValidityInterval -> SlotNo -> ConwayUtxoPredFailure era
OutsideValidityIntervalUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
3 -> forall t. t -> Decode 'Open t
SumD forall era. Mismatch 'RelLTEQ Integer -> ConwayUtxoPredFailure era
MaxTxSizeUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped).
(EncCBORGroup t, DecCBORGroup t) =>
Decode w t
FromGroup
Word
4 -> forall t. t -> Decode 'Open t
SumD forall era. ConwayUtxoPredFailure era
InputSetEmptyUTxO
Word
5 -> forall t. t -> Decode 'Open t
SumD forall era. Mismatch 'RelGTEQ Coin -> ConwayUtxoPredFailure era
FeeTooSmallUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t (w :: Wrapped).
(EncCBORGroup t, DecCBORGroup t) =>
Decode w t
FromGroup)
Word
6 -> forall t. t -> Decode 'Open t
SumD forall era.
Mismatch 'RelEQ (Value era) -> ConwayUtxoPredFailure era
ValueNotConservedUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped).
(EncCBORGroup t, DecCBORGroup t) =>
Decode w t
FromGroup
Word
7 -> forall t. t -> Decode 'Open t
SumD forall era. Network -> Set Addr -> ConwayUtxoPredFailure era
WrongNetwork forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
8 -> forall t. t -> Decode 'Open t
SumD forall era.
Network -> Set RewardAccount -> ConwayUtxoPredFailure era
WrongNetworkWithdrawal forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
9 -> forall t. t -> Decode 'Open t
SumD forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputTooSmallUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
10 -> forall t. t -> Decode 'Open t
SumD forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputBootAddrAttrsTooBig forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
11 -> forall t. t -> Decode 'Open t
SumD forall era. [(Int, Int, TxOut era)] -> ConwayUtxoPredFailure era
OutputTooBigUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
12 -> forall t. t -> Decode 'Open t
SumD forall era. DeltaCoin -> Coin -> ConwayUtxoPredFailure era
InsufficientCollateral forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
13 -> forall t. t -> Decode 'Open t
SumD forall era. UTxO era -> ConwayUtxoPredFailure era
ScriptsNotPaidUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall era. Map TxIn (TxOut era) -> UTxO era
UTxO forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR)
Word
14 -> forall t. t -> Decode 'Open t
SumD forall era. Mismatch 'RelLTEQ ExUnits -> ConwayUtxoPredFailure era
ExUnitsTooBigUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t (w :: Wrapped).
(EncCBORGroup t, DecCBORGroup t) =>
Decode w t
FromGroup)
Word
15 -> forall t. t -> Decode 'Open t
SumD forall era. Value era -> ConwayUtxoPredFailure era
CollateralContainsNonADA forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
16 -> forall t. t -> Decode 'Open t
SumD forall era. Mismatch 'RelEQ Network -> ConwayUtxoPredFailure era
WrongNetworkInTxBody forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t (w :: Wrapped).
(EncCBORGroup t, DecCBORGroup t) =>
Decode w t
FromGroup)
Word
17 -> forall t. t -> Decode 'Open t
SumD forall era. SlotNo -> ConwayUtxoPredFailure era
OutsideForecast forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
18 -> forall t. t -> Decode 'Open t
SumD forall era. Mismatch 'RelLTEQ Natural -> ConwayUtxoPredFailure era
TooManyCollateralInputs forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall a (r :: Relation). (a, a) -> Mismatch r a
unswapMismatch forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t (w :: Wrapped).
(EncCBORGroup t, DecCBORGroup t) =>
Decode w t
FromGroup)
Word
19 -> forall t. t -> Decode 'Open t
SumD forall era. ConwayUtxoPredFailure era
NoCollateralInputs
Word
20 -> forall t. t -> Decode 'Open t
SumD forall era. DeltaCoin -> Coin -> ConwayUtxoPredFailure era
IncorrectTotalCollateralField forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
21 -> forall t. t -> Decode 'Open t
SumD forall era. [(TxOut era, Coin)] -> ConwayUtxoPredFailure era
BabbageOutputTooSmallUTxO forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
22 -> forall t. t -> Decode 'Open t
SumD forall era. NonEmpty TxIn -> ConwayUtxoPredFailure era
BabbageNonDisjointRefInputs forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
n -> forall (w :: Wrapped) t. Word -> Decode w t
Invalid Word
n
babbageToConwayUtxoPredFailure ::
forall era.
BabbageUtxoPredFailure era ->
ConwayUtxoPredFailure era
babbageToConwayUtxoPredFailure :: forall era. BabbageUtxoPredFailure era -> ConwayUtxoPredFailure era
babbageToConwayUtxoPredFailure = \case
Babbage.AlonzoInBabbageUtxoPredFailure AlonzoUtxoPredFailure era
a -> forall era. AlonzoUtxoPredFailure era -> ConwayUtxoPredFailure era
alonzoToConwayUtxoPredFailure AlonzoUtxoPredFailure era
a
Babbage.IncorrectTotalCollateralField DeltaCoin
c1 Coin
c2 -> forall era. DeltaCoin -> Coin -> ConwayUtxoPredFailure era
IncorrectTotalCollateralField DeltaCoin
c1 Coin
c2
Babbage.BabbageOutputTooSmallUTxO [(TxOut era, Coin)]
ts -> forall era. [(TxOut era, Coin)] -> ConwayUtxoPredFailure era
BabbageOutputTooSmallUTxO [(TxOut era, Coin)]
ts
Babbage.BabbageNonDisjointRefInputs NonEmpty TxIn
ts -> forall era. NonEmpty TxIn -> ConwayUtxoPredFailure era
BabbageNonDisjointRefInputs NonEmpty TxIn
ts
alonzoToConwayUtxoPredFailure ::
forall era.
AlonzoUtxoPredFailure era ->
ConwayUtxoPredFailure era
alonzoToConwayUtxoPredFailure :: forall era. AlonzoUtxoPredFailure era -> ConwayUtxoPredFailure era
alonzoToConwayUtxoPredFailure = \case
Alonzo.BadInputsUTxO Set TxIn
x -> forall era. Set TxIn -> ConwayUtxoPredFailure era
BadInputsUTxO Set TxIn
x
Alonzo.OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo -> forall era. ValidityInterval -> SlotNo -> ConwayUtxoPredFailure era
OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo
Alonzo.MaxTxSizeUTxO Mismatch 'RelLTEQ Integer
m -> forall era. Mismatch 'RelLTEQ Integer -> ConwayUtxoPredFailure era
MaxTxSizeUTxO Mismatch 'RelLTEQ Integer
m
AlonzoUtxoPredFailure era
Alonzo.InputSetEmptyUTxO -> forall era. ConwayUtxoPredFailure era
InputSetEmptyUTxO
Alonzo.FeeTooSmallUTxO Mismatch 'RelGTEQ Coin
m -> forall era. Mismatch 'RelGTEQ Coin -> ConwayUtxoPredFailure era
FeeTooSmallUTxO Mismatch 'RelGTEQ Coin
m
Alonzo.ValueNotConservedUTxO Mismatch 'RelEQ (Value era)
m -> forall era.
Mismatch 'RelEQ (Value era) -> ConwayUtxoPredFailure era
ValueNotConservedUTxO Mismatch 'RelEQ (Value era)
m
Alonzo.WrongNetwork Network
x Set Addr
y -> forall era. Network -> Set Addr -> ConwayUtxoPredFailure era
WrongNetwork Network
x Set Addr
y
Alonzo.WrongNetworkWithdrawal Network
x Set RewardAccount
y -> forall era.
Network -> Set RewardAccount -> ConwayUtxoPredFailure era
WrongNetworkWithdrawal Network
x Set RewardAccount
y
Alonzo.OutputTooSmallUTxO [TxOut era]
x -> forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputTooSmallUTxO [TxOut era]
x
Alonzo.UtxosFailure PredicateFailure (EraRule "UTXOS" era)
x -> forall era.
PredicateFailure (EraRule "UTXOS" era) -> ConwayUtxoPredFailure era
UtxosFailure PredicateFailure (EraRule "UTXOS" era)
x
Alonzo.OutputBootAddrAttrsTooBig [TxOut era]
xs -> forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputBootAddrAttrsTooBig [TxOut era]
xs
AlonzoUtxoPredFailure era
Alonzo.TriesToForgeADA ->
forall a. HasCallStack => String -> a
error
String
"Impossible case, soon to be removed. See: https://github.com/IntersectMBO/cardano-ledger/issues/4085"
Alonzo.OutputTooBigUTxO [(Integer, Integer, TxOut era)]
xs ->
let
toRestricted :: (Integer, Integer, TxOut era) -> (Int, Int, TxOut era)
toRestricted :: (Integer, Integer, TxOut era) -> (Int, Int, TxOut era)
toRestricted (Integer
sz, Integer
mv, TxOut era
out) = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
sz, forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
mv, TxOut era
out)
in
forall era. [(Int, Int, TxOut era)] -> ConwayUtxoPredFailure era
OutputTooBigUTxO forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (Integer, Integer, TxOut era) -> (Int, Int, TxOut era)
toRestricted [(Integer, Integer, TxOut era)]
xs
Alonzo.InsufficientCollateral DeltaCoin
c1 Coin
c2 -> forall era. DeltaCoin -> Coin -> ConwayUtxoPredFailure era
InsufficientCollateral DeltaCoin
c1 Coin
c2
Alonzo.ScriptsNotPaidUTxO UTxO era
u -> forall era. UTxO era -> ConwayUtxoPredFailure era
ScriptsNotPaidUTxO UTxO era
u
Alonzo.ExUnitsTooBigUTxO Mismatch 'RelLTEQ ExUnits
m -> forall era. Mismatch 'RelLTEQ ExUnits -> ConwayUtxoPredFailure era
ExUnitsTooBigUTxO Mismatch 'RelLTEQ ExUnits
m
Alonzo.CollateralContainsNonADA Value era
v -> forall era. Value era -> ConwayUtxoPredFailure era
CollateralContainsNonADA Value era
v
Alonzo.WrongNetworkInTxBody Mismatch 'RelEQ Network
m -> forall era. Mismatch 'RelEQ Network -> ConwayUtxoPredFailure era
WrongNetworkInTxBody Mismatch 'RelEQ Network
m
Alonzo.OutsideForecast SlotNo
sno -> forall era. SlotNo -> ConwayUtxoPredFailure era
OutsideForecast SlotNo
sno
Alonzo.TooManyCollateralInputs Mismatch 'RelLTEQ Natural
m -> forall era. Mismatch 'RelLTEQ Natural -> ConwayUtxoPredFailure era
TooManyCollateralInputs Mismatch 'RelLTEQ Natural
m
AlonzoUtxoPredFailure era
Alonzo.NoCollateralInputs -> forall era. ConwayUtxoPredFailure era
NoCollateralInputs
allegraToConwayUtxoPredFailure ::
forall era.
EraRuleFailure "PPUP" era ~ VoidEraRule "PPUP" era =>
Allegra.AllegraUtxoPredFailure era ->
ConwayUtxoPredFailure era
allegraToConwayUtxoPredFailure :: forall era.
(EraRuleFailure "PPUP" era ~ VoidEraRule "PPUP" era) =>
AllegraUtxoPredFailure era -> ConwayUtxoPredFailure era
allegraToConwayUtxoPredFailure = \case
Allegra.BadInputsUTxO Set TxIn
x -> forall era. Set TxIn -> ConwayUtxoPredFailure era
BadInputsUTxO Set TxIn
x
Allegra.OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo -> forall era. ValidityInterval -> SlotNo -> ConwayUtxoPredFailure era
OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo
Allegra.MaxTxSizeUTxO Mismatch 'RelLTEQ Integer
m -> forall era. Mismatch 'RelLTEQ Integer -> ConwayUtxoPredFailure era
MaxTxSizeUTxO Mismatch 'RelLTEQ Integer
m
AllegraUtxoPredFailure era
Allegra.InputSetEmptyUTxO -> forall era. ConwayUtxoPredFailure era
InputSetEmptyUTxO
Allegra.FeeTooSmallUTxO Mismatch 'RelGTEQ Coin
m -> forall era. Mismatch 'RelGTEQ Coin -> ConwayUtxoPredFailure era
FeeTooSmallUTxO Mismatch 'RelGTEQ Coin
m
Allegra.ValueNotConservedUTxO Mismatch 'RelEQ (Value era)
m -> forall era.
Mismatch 'RelEQ (Value era) -> ConwayUtxoPredFailure era
ValueNotConservedUTxO Mismatch 'RelEQ (Value era)
m
Allegra.WrongNetwork Network
x Set Addr
y -> forall era. Network -> Set Addr -> ConwayUtxoPredFailure era
WrongNetwork Network
x Set Addr
y
Allegra.WrongNetworkWithdrawal Network
x Set RewardAccount
y -> forall era.
Network -> Set RewardAccount -> ConwayUtxoPredFailure era
WrongNetworkWithdrawal Network
x Set RewardAccount
y
Allegra.OutputTooSmallUTxO [TxOut era]
x -> forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputTooSmallUTxO [TxOut era]
x
Allegra.UpdateFailure EraRuleFailure "PPUP" era
x -> forall (rule :: Symbol) era a. VoidEraRule rule era -> a
absurdEraRule @"PPUP" @era EraRuleFailure "PPUP" era
x
Allegra.OutputBootAddrAttrsTooBig [TxOut era]
xs -> forall era. [TxOut era] -> ConwayUtxoPredFailure era
OutputBootAddrAttrsTooBig [TxOut era]
xs
AllegraUtxoPredFailure era
Allegra.TriesToForgeADA ->
forall a. HasCallStack => String -> a
error
String
"Impossible case, soon to be removed. See: https://github.com/IntersectMBO/cardano-ledger/issues/4085"
Allegra.OutputTooBigUTxO [TxOut era]
xs -> forall era. [(Int, Int, TxOut era)] -> ConwayUtxoPredFailure era
OutputTooBigUTxO (forall a b. (a -> b) -> [a] -> [b]
map (Int
0,Int
0,) [TxOut era]
xs)