{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

module Cardano.Ledger.Alonzo.Rules.Utxo where

-- Inject instances
import Cardano.Binary (FromCBOR (..), ToCBOR (..), serialize)
import Cardano.Ledger.Address (Addr (..), RewardAcnt)
-- we need the fields
import Cardano.Ledger.Alonzo.Data (DataHash, dataHashSize)
import Cardano.Ledger.Alonzo.PParams (PParams' (..))
import Cardano.Ledger.Alonzo.Rules.Utxos (ConcreteAlonzo, UTXOS, UtxosPredicateFailure)
import Cardano.Ledger.Alonzo.Scripts (ExUnits (..), Prices, pointWiseExUnits)
import Cardano.Ledger.Alonzo.Tx (ValidatedTx (..), minfee, totExUnits)
import qualified Cardano.Ledger.Alonzo.Tx as Alonzo (ValidatedTx)
import qualified Cardano.Ledger.Alonzo.TxSeq as Alonzo (TxSeq)
import Cardano.Ledger.Alonzo.TxWitness (Redeemers, TxWitness (txrdmrs'), nullRedeemers)
import Cardano.Ledger.BaseTypes
  ( Network,
    ProtVer,
    ShelleyBase,
    StrictMaybe (..),
    epochInfo,
    networkId,
    systemStart,
  )
import Cardano.Ledger.Coin
import Cardano.Ledger.CompactAddress
  ( CompactAddr,
    isBootstrapCompactAddr,
    isPayCredScriptCompactAddr,
  )
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Credential (Credential (..))
import qualified Cardano.Ledger.Crypto as CC
import Cardano.Ledger.Era (Era (..), ValidateScript (..))
import qualified Cardano.Ledger.Era as Era
import Cardano.Ledger.Rules.ValidationMode
  ( Inject (..),
    InjectMaybe (..),
    Test,
    runTest,
    runTestOnSignal,
  )
import Cardano.Ledger.Shelley.HardForks (allowOutsideForecastTTL)
import qualified Cardano.Ledger.Shelley.LedgerState as Shelley
import qualified Cardano.Ledger.Shelley.Rules.Utxo as Shelley
import Cardano.Ledger.Shelley.Tx (TxIn)
import Cardano.Ledger.Shelley.UTxO (UTxO (..), balance, txouts)
import Cardano.Ledger.ShelleyMA.Rules.Utxo ()
import qualified Cardano.Ledger.ShelleyMA.Rules.Utxo as ShelleyMA
import Cardano.Ledger.ShelleyMA.Timelocks (ValidityInterval (..))
import qualified Cardano.Ledger.Val as Val
import Cardano.Slotting.EpochInfo.API (EpochInfo, epochInfoSlotToUTCTime)
import Cardano.Slotting.EpochInfo.Extend (unsafeLinearExtendEpochInfo)
import Cardano.Slotting.Slot (SlotNo)
import Cardano.Slotting.Time (SystemStart)
import Control.Monad (unless)
import Control.Monad.Trans.Reader (asks)
import Control.SetAlgebra (eval, (◁))
import Control.State.Transition.Extended
import qualified Data.ByteString.Lazy as BSL (length)
import Data.Coders
  ( Decode (..),
    Encode (..),
    Wrapped (Open),
    decode,
    decodeList,
    decodeMap,
    decodeSet,
    encode,
    encodeFoldable,
    (!>),
    (<!),
  )
import Data.Coerce (coerce)
import Data.Either (isRight)
import Data.Foldable (foldl', sequenceA_, toList)
import qualified Data.Map.Strict as Map
import Data.Ratio ((%))
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import GHC.Records
import NoThunks.Class (NoThunks)
import Numeric.Natural (Natural)
import Validation

-- | Compute an estimate of the size of storing one UTxO entry.
-- This function implements the UTxO entry size estimate done by scaledMinDeposit in the ShelleyMA era
utxoEntrySize ::
  ( Era era,
    HasField "datahash" (Core.TxOut era) (StrictMaybe (DataHash c))
  ) =>
  Core.TxOut era ->
  Integer
utxoEntrySize :: TxOut era -> Integer
utxoEntrySize TxOut era
txout = Integer
utxoEntrySizeWithoutVal Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Value era -> Integer
forall t. Val t => t -> Integer
Val.size Value era
v Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ StrictMaybe (DataHash c) -> Integer
forall c. StrictMaybe (DataHash c) -> Integer
dataHashSize StrictMaybe (DataHash c)
dh
  where
    v :: Value era
v = TxOut era -> Value era
forall k (x :: k) r a. HasField x r a => r -> a
getField @"value" TxOut era
txout
    dh :: StrictMaybe (DataHash c)
dh = TxOut era -> StrictMaybe (DataHash c)
forall k (x :: k) r a. HasField x r a => r -> a
getField @"datahash" TxOut era
txout
    -- lengths obtained from tracing on HeapWords of inputs and outputs
    -- obtained experimentally, and number used here
    -- units are Word64s

    -- size of UTxO entry excluding the Value part
    utxoEntrySizeWithoutVal :: Integer
    utxoEntrySizeWithoutVal :: Integer
utxoEntrySizeWithoutVal = Integer
27 -- 6 + txoutLenNoVal [14] + txinLen [7]

-- ============================================

-- | The uninhabited type that marks the Alonzo UTxO rule
data AlonzoUTXO era

-- ==========================================================

data UtxoPredicateFailure era
  = -- | The bad transaction inputs
    BadInputsUTxO
      !(Set (TxIn (Crypto era)))
  | OutsideValidityIntervalUTxO
      !ValidityInterval
      -- ^ transaction's validity interval
      !SlotNo
      -- ^ current slot
  | MaxTxSizeUTxO
      !Integer
      -- ^ the actual transaction size
      !Integer
      -- ^ the max transaction size
  | InputSetEmptyUTxO
  | FeeTooSmallUTxO
      !Coin
      -- ^ the minimum fee for this transaction
      !Coin
      -- ^ the fee supplied in this transaction
  | ValueNotConservedUTxO
      !(Core.Value era)
      -- ^ the Coin consumed by this transaction
      !(Core.Value era)
      -- ^ the Coin produced by this transaction
  | -- | the set of addresses with incorrect network IDs
    WrongNetwork
      !Network
      -- ^ the expected network id
      !(Set (Addr (Crypto era)))
      -- ^ the set of addresses with incorrect network IDs
  | WrongNetworkWithdrawal
      !Network
      -- ^ the expected network id
      !(Set (RewardAcnt (Crypto era)))
      -- ^ the set of reward addresses with incorrect network IDs
  | -- | list of supplied transaction outputs that are too small
    OutputTooSmallUTxO
      ![Core.TxOut era]
  | -- | Subtransition Failures
    UtxosFailure (PredicateFailure (Core.EraRule "UTXOS" era))
  | -- | list of supplied bad transaction outputs
    OutputBootAddrAttrsTooBig
      ![Core.TxOut era]
  | TriesToForgeADA
  | -- | list of supplied bad transaction output triples (actualSize,PParameterMaxValue,TxOut)
    OutputTooBigUTxO
      ![(Integer, Integer, Core.TxOut era)]
  | InsufficientCollateral
      !Coin
      -- ^ balance computed
      !Coin
      -- ^ the required collateral for the given fee
  | -- | The UTxO entries which have the wrong kind of script
    ScriptsNotPaidUTxO
      !(UTxO era)
  | ExUnitsTooBigUTxO
      !ExUnits
      -- ^ Max EXUnits from the protocol parameters
      !ExUnits
      -- ^ EXUnits supplied
  | -- | The inputs marked for use as fees contain non-ADA tokens
    CollateralContainsNonADA !(Core.Value era)
  | -- | Wrong Network ID in body
    WrongNetworkInTxBody
      !Network
      -- ^ Actual Network ID
      !Network
      -- ^ Network ID in transaction body
  | -- | slot number outside consensus forecast range
    OutsideForecast
      !SlotNo
  | -- | There are too many collateral inputs
    TooManyCollateralInputs
      !Natural
      -- ^ Max allowed collateral inputs
      !Natural
      -- ^ Number of collateral inputs
  | NoCollateralInputs
  deriving ((forall x.
 UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x)
-> (forall x.
    Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era)
-> Generic (UtxoPredicateFailure era)
forall x.
Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era
forall x.
UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x.
Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era
forall era x.
UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x
$cto :: forall era x.
Rep (UtxoPredicateFailure era) x -> UtxoPredicateFailure era
$cfrom :: forall era x.
UtxoPredicateFailure era -> Rep (UtxoPredicateFailure era) x
Generic)

deriving stock instance
  ( Era era,
    Show (Core.Value era),
    Show (Core.TxOut era),
    Show (Core.TxBody era),
    Show (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  Show (UtxoPredicateFailure era)

deriving stock instance
  ( CC.Crypto (Crypto era),
    Eq (Core.Value era),
    Eq (Core.TxOut era),
    Eq (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  Eq (UtxoPredicateFailure era)

instance
  ( Era era,
    ToCBOR (Core.Value era),
    ToCBOR (Core.TxOut era),
    ToCBOR (Core.TxBody era),
    NoThunks (Core.Value era),
    NoThunks (Core.TxOut era),
    NoThunks (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  NoThunks (UtxoPredicateFailure era)

newtype UtxoEvent era
  = UtxosEvent (Event (Core.EraRule "UTXOS" era))

-- | Returns true for VKey locked addresses, and false for any kind of
-- script-locked address.
isKeyHashAddr :: Addr crypto -> Bool
isKeyHashAddr :: Addr crypto -> Bool
isKeyHashAddr (AddrBootstrap BootstrapAddress crypto
_) = Bool
True
isKeyHashAddr (Addr Network
_ (KeyHashObj KeyHash 'Payment crypto
_) StakeReference crypto
_) = Bool
True
isKeyHashAddr Addr crypto
_ = Bool
False

-- | This is equivalent to `isKeyHashAddr`, but for compacted version of an address.
isKeyHashCompactAddr :: CompactAddr crypto -> Bool
isKeyHashCompactAddr :: CompactAddr crypto -> Bool
isKeyHashCompactAddr CompactAddr crypto
cAddr =
  CompactAddr crypto -> Bool
forall crypto. CompactAddr crypto -> Bool
isBootstrapCompactAddr CompactAddr crypto
cAddr Bool -> Bool -> Bool
|| Bool -> Bool
not (CompactAddr crypto -> Bool
forall crypto. CompactAddr crypto -> Bool
isPayCredScriptCompactAddr CompactAddr crypto
cAddr)

vKeyLocked :: Era era => Core.TxOut era -> Bool
vKeyLocked :: TxOut era -> Bool
vKeyLocked TxOut era
txOut =
  case TxOut era -> Either (Addr (Crypto era)) (CompactAddr (Crypto era))
forall e.
Era e =>
TxOut e -> Either (Addr (Crypto e)) (CompactAddr (Crypto e))
getTxOutEitherAddr TxOut era
txOut of
    Left Addr (Crypto era)
addr -> Addr (Crypto era) -> Bool
forall crypto. Addr crypto -> Bool
isKeyHashAddr Addr (Crypto era)
addr
    Right CompactAddr (Crypto era)
cAddr -> CompactAddr (Crypto era) -> Bool
forall crypto. CompactAddr crypto -> Bool
isKeyHashCompactAddr CompactAddr (Crypto era)
cAddr

-- | feesOK is a predicate with several parts. Some parts only apply in special circumstances.
--   1) The fee paid is >= the minimum fee
--   2) If the total ExUnits are 0 in both Memory and Steps, no further part needs to be checked.
--   3) The collateral consists only of VKey addresses
--   4) The collateral is sufficient to cover the appropriate percentage of the
--      fee marked in the transaction
--   5) The collateral inputs do not contain any non-ADA part
--   6) There is at least one collateral input
--   As a TransitionRule it will return (), and produce a validation failure (rather than
--   return) if any of the required parts are False.
feesOK ::
  forall era.
  ( Era era,
    Core.Tx era ~ Alonzo.ValidatedTx era,
    -- "collateral" to get inputs to pay the fees
    HasField "collateral" (Core.TxBody era) (Set (TxIn (Crypto era))),
    HasField "txrdmrs" (Core.Witnesses era) (Redeemers era),
    HasField "_minfeeA" (Core.PParams era) Natural,
    HasField "_minfeeB" (Core.PParams era) Natural,
    HasField "_prices" (Core.PParams era) Prices,
    HasField "_collateralPercentage" (Core.PParams era) Natural
  ) =>
  Core.PParams era ->
  Core.Tx era ->
  UTxO era ->
  Test (UtxoPredicateFailure era)
feesOK :: PParams era
-> Tx era -> UTxO era -> Test (UtxoPredicateFailure era)
feesOK PParams era
pp Tx era
tx (UTxO Map (TxIn (Crypto era)) (TxOut era)
utxo) =
  let txb :: TxBody era
txb = ValidatedTx era -> TxBody era
forall k (x :: k) r a. HasField x r a => r -> a
getField @"body" Tx era
ValidatedTx era
tx
      collateral :: Set (TxIn (Crypto era))
collateral = TxBody era -> Set (TxIn (Crypto era))
forall k (x :: k) r a. HasField x r a => r -> a
getField @"collateral" TxBody era
txb -- Inputs allocated to pay txfee
      -- restrict Utxo to those inputs we use to pay fees.
      utxoCollateral :: Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral = Exp (Map (TxIn (Crypto era)) (TxOut era))
-> Map (TxIn (Crypto era)) (TxOut era)
forall s t. Embed s t => Exp t -> s
eval (Set (TxIn (Crypto era))
collateral Set (TxIn (Crypto era))
-> Map (TxIn (Crypto era)) (TxOut era)
-> Exp (Map (TxIn (Crypto era)) (TxOut era))
forall k s1 s2 (f :: * -> * -> *) v.
(Ord k, HasExp s1 (Sett k ()), HasExp s2 (f k v)) =>
s1 -> s2 -> Exp (f k v)
 Map (TxIn (Crypto era)) (TxOut era)
utxo)
      bal :: Value era
bal = UTxO era -> Value era
forall era. Era era => UTxO era -> Value era
balance @era (Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
forall era. Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
UTxO Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral)
      theFee :: Coin
theFee = TxBody era -> Coin
forall k (x :: k) r a. HasField x r a => r -> a
getField @"txfee" TxBody era
txb
      minimumFee :: Coin
minimumFee = PParams era -> Tx era -> Coin
forall era.
(HasField "_minfeeA" (PParams era) Natural,
 HasField "_minfeeB" (PParams era) Natural,
 HasField "_prices" (PParams era) Prices,
 HasField "wits" (Tx era) (Witnesses era),
 HasField "txrdmrs" (Witnesses era) (Redeemers era),
 HasField "txsize" (Tx era) Integer) =>
PParams era -> Tx era -> Coin
minfee @era PParams era
pp Tx era
tx
   in [Test (UtxoPredicateFailure era)]
-> Test (UtxoPredicateFailure era)
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Applicative f) =>
t (f a) -> f ()
sequenceA_
        [ -- Part 1: minfee pp tx ≤ txfee txb
          Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless (Coin
minimumFee Coin -> Coin -> Bool
forall a. Ord a => a -> a -> Bool
<= Coin
theFee) (UtxoPredicateFailure era -> UtxoPredicateFailure era
forall t s. Inject t s => t -> s
inject (Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
FeeTooSmallUTxO @era Coin
minimumFee Coin
theFee)),
          -- Part 2: (txrdmrs tx ≠ ∅ ⇒ validateCollateral)
          Bool
-> Test (UtxoPredicateFailure era)
-> Test (UtxoPredicateFailure era)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Redeemers era -> Bool
forall era. Redeemers era -> Bool
nullRedeemers (Redeemers era -> Bool)
-> (ValidatedTx era -> Redeemers era) -> ValidatedTx era -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxWitness era -> Redeemers era
forall era. TxWitness era -> Redeemers era
txrdmrs' (TxWitness era -> Redeemers era)
-> (ValidatedTx era -> TxWitness era)
-> ValidatedTx era
-> Redeemers era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidatedTx era -> TxWitness era
forall era. ValidatedTx era -> TxWitness era
wits (ValidatedTx era -> Bool) -> ValidatedTx era -> Bool
forall a b. (a -> b) -> a -> b
$ Tx era
ValidatedTx era
tx) (Test (UtxoPredicateFailure era)
 -> Test (UtxoPredicateFailure era))
-> Test (UtxoPredicateFailure era)
-> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$
            PParams era
-> TxBody era
-> Map (TxIn (Crypto era)) (TxOut era)
-> Value era
-> Test (UtxoPredicateFailure era)
forall era.
(Era era,
 HasField "_collateralPercentage" (PParams era) Natural) =>
PParams era
-> TxBody era
-> Map (TxIn (Crypto era)) (TxOut era)
-> Value era
-> Test (UtxoPredicateFailure era)
validateCollateral PParams era
pp TxBody era
txb Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral Value era
bal
        ]

validateCollateral ::
  ( Era era,
    HasField "_collateralPercentage" (Core.PParams era) Natural
  ) =>
  Core.PParams era ->
  Core.TxBody era ->
  Map.Map (TxIn (Crypto era)) (Core.TxOut era) ->
  Core.Value era ->
  Test (UtxoPredicateFailure era)
validateCollateral :: PParams era
-> TxBody era
-> Map (TxIn (Crypto era)) (TxOut era)
-> Value era
-> Test (UtxoPredicateFailure era)
validateCollateral PParams era
pp TxBody era
txb Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral Value era
bal =
  [Test (UtxoPredicateFailure era)]
-> Test (UtxoPredicateFailure era)
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Applicative f) =>
t (f a) -> f ()
sequenceA_
    [ -- Part 3: (∀(a,_,_) ∈ range (collateral txb ◁ utxo), a ∈ Addrvkey)
      Map (TxIn (Crypto era)) (TxOut era)
-> Test (UtxoPredicateFailure era)
forall era.
Era era =>
Map (TxIn (Crypto era)) (TxOut era)
-> Test (UtxoPredicateFailure era)
validateScriptsNotPaidUTxO Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral,
      -- Part 4: balance ∗ 100 ≥ txfee txb ∗ (collateralPercent pp)
      PParams era
-> TxBody era -> Value era -> Test (UtxoPredicateFailure era)
forall era.
(HasField "_collateralPercentage" (PParams era) Natural,
 HasField "txfee" (TxBody era) Coin, Val (Value era)) =>
PParams era
-> TxBody era -> Value era -> Test (UtxoPredicateFailure era)
validateInsufficientCollateral PParams era
pp TxBody era
txb Value era
bal,
      -- Part 5: isAdaOnly balance
      Value era -> Test (UtxoPredicateFailure era)
forall era.
Val (Value era) =>
Value era -> Test (UtxoPredicateFailure era)
validateCollateralContainsNonADA Value era
bal,
      -- Part 6: (∀(a,_,_) ∈ range (collateral txb ◁ utxo), a ∈ Addrvkey)
      Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureIf (Map (TxIn (Crypto era)) (TxOut era) -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral) UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
NoCollateralInputs
    ]

-- > (∀(a,_,_) ∈ range (collateral txb ◁ utxo), a ∈ Addrvkey)
validateScriptsNotPaidUTxO ::
  Era era =>
  Map.Map (TxIn (Crypto era)) (Core.TxOut era) ->
  Test (UtxoPredicateFailure era)
validateScriptsNotPaidUTxO :: Map (TxIn (Crypto era)) (TxOut era)
-> Test (UtxoPredicateFailure era)
validateScriptsNotPaidUTxO Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless ((TxOut era -> Bool) -> Map (TxIn (Crypto era)) (TxOut era) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all TxOut era -> Bool
forall era. Era era => TxOut era -> Bool
vKeyLocked Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$
    UTxO era -> UtxoPredicateFailure era
forall era. UTxO era -> UtxoPredicateFailure era
ScriptsNotPaidUTxO (Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
forall era. Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
UTxO ((TxOut era -> Bool)
-> Map (TxIn (Crypto era)) (TxOut era)
-> Map (TxIn (Crypto era)) (TxOut era)
forall a k. (a -> Bool) -> Map k a -> Map k a
Map.filter (Bool -> Bool
not (Bool -> Bool) -> (TxOut era -> Bool) -> TxOut era -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOut era -> Bool
forall era. Era era => TxOut era -> Bool
vKeyLocked) Map (TxIn (Crypto era)) (TxOut era)
utxoCollateral))

-- > balance ∗ 100 ≥ txfee txb ∗ (collateralPercent pp)
validateInsufficientCollateral ::
  ( HasField "_collateralPercentage" (Core.PParams era) Natural,
    HasField "txfee" (Core.TxBody era) Coin,
    Val.Val (Core.Value era)
  ) =>
  Core.PParams era ->
  Core.TxBody era ->
  Core.Value era ->
  Test (UtxoPredicateFailure era)
validateInsufficientCollateral :: PParams era
-> TxBody era -> Value era -> Test (UtxoPredicateFailure era)
validateInsufficientCollateral PParams era
pp TxBody era
txb Value era
bal =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless (Int -> Coin -> Coin
forall t i. (Val t, Integral i) => i -> t -> t
Val.scale (Int
100 :: Int) (Value era -> Coin
forall t. Val t => t -> Coin
Val.coin Value era
bal) Coin -> Coin -> Bool
forall a. Ord a => a -> a -> Bool
>= Natural -> Coin -> Coin
forall t i. (Val t, Integral i) => i -> t -> t
Val.scale Natural
collPerc Coin
txfee) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$
    Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
InsufficientCollateral
      (Value era -> Coin
forall t. Val t => t -> Coin
Val.coin Value era
bal)
      (Rational -> Coin
rationalToCoinViaCeiling (Rational -> Coin) -> Rational -> Coin
forall a b. (a -> b) -> a -> b
$ (Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
collPerc Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Coin -> Integer
unCoin Coin
txfee) Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
100)
  where
    txfee :: Coin
txfee = TxBody era -> Coin
forall k (x :: k) r a. HasField x r a => r -> a
getField @"txfee" TxBody era
txb -- Coin supplied to pay fees
    collPerc :: Natural
collPerc = PParams era -> Natural
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_collateralPercentage" PParams era
pp

-- > isAdaOnly balance
validateCollateralContainsNonADA ::
  Val.Val (Core.Value era) =>
  Core.Value era ->
  Test (UtxoPredicateFailure era)
validateCollateralContainsNonADA :: Value era -> Test (UtxoPredicateFailure era)
validateCollateralContainsNonADA Value era
bal =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless (Value era -> Bool
forall t. Val t => t -> Bool
Val.isAdaOnly Value era
bal) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Value era -> UtxoPredicateFailure era
forall era. Value era -> UtxoPredicateFailure era
CollateralContainsNonADA Value era
bal

-- | If tx has non-native scripts, end of validity interval must translate to time
--
-- > (_,i_f) := txvldt tx
-- > ◇ ∉ { txrdmrs tx, i_f } ⇒ epochInfoSlotToUTCTime epochInfo systemTime i_f ≠ ◇
validateOutsideForecast ::
  ( HasField "vldt" (Core.TxBody era) ValidityInterval,
    HasField "_protocolVersion" (Core.PParams era) ProtVer
  ) =>
  Core.PParams era ->
  EpochInfo (Either a) ->
  -- | Current slot number
  SlotNo ->
  SystemStart ->
  ValidatedTx era ->
  Test (UtxoPredicateFailure era)
validateOutsideForecast :: PParams era
-> EpochInfo (Either a)
-> SlotNo
-> SystemStart
-> ValidatedTx era
-> Test (UtxoPredicateFailure era)
validateOutsideForecast PParams era
pp EpochInfo (Either a)
ei SlotNo
slotNo SystemStart
sysSt ValidatedTx era
tx =
  {-   (_,i_f) := txvldt tx   -}
  case TxBody era -> ValidityInterval
forall k (x :: k) r a. HasField x r a => r -> a
getField @"vldt" (ValidatedTx era -> TxBody era
forall era. ValidatedTx era -> TxBody era
body ValidatedTx era
tx) of
    ValidityInterval StrictMaybe SlotNo
_ (SJust SlotNo
ifj)
      | Bool -> Bool
not (Redeemers era -> Bool
forall era. Redeemers era -> Bool
nullRedeemers (TxWitness era -> Redeemers era
forall era. TxWitness era -> Redeemers era
txrdmrs' (TxWitness era -> Redeemers era) -> TxWitness era -> Redeemers era
forall a b. (a -> b) -> a -> b
$ ValidatedTx era -> TxWitness era
forall era. ValidatedTx era -> TxWitness era
wits ValidatedTx era
tx)) ->
          let ei' :: EpochInfo (Either a)
ei' =
                if PParams era -> Bool
forall pp. HasField "_protocolVersion" pp ProtVer => pp -> Bool
allowOutsideForecastTTL PParams era
pp
                  then SlotNo -> EpochInfo (Either a) -> EpochInfo (Either a)
forall (m :: * -> *).
Monad m =>
SlotNo -> EpochInfo m -> EpochInfo m
unsafeLinearExtendEpochInfo SlotNo
slotNo EpochInfo (Either a)
ei
                  else EpochInfo (Either a)
ei
           in -- ◇ ∉ { txrdmrs tx, i_f } ⇒
              Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless (Either a UTCTime -> Bool
forall a b. Either a b -> Bool
isRight (EpochInfo (Either a) -> SystemStart -> SlotNo -> Either a UTCTime
forall (m :: * -> *).
(HasCallStack, Monad m) =>
EpochInfo m -> SystemStart -> SlotNo -> m UTCTime
epochInfoSlotToUTCTime EpochInfo (Either a)
ei' SystemStart
sysSt SlotNo
ifj)) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ SlotNo -> UtxoPredicateFailure era
forall era. SlotNo -> UtxoPredicateFailure era
OutsideForecast SlotNo
ifj
    ValidityInterval
_ -> () -> Test (UtxoPredicateFailure era)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

-- | Ensure that there are no `Core.TxOut`s that have value less than the sized @coinsPerUTxOWord@
--
-- > ∀ txout ∈ txouts txb, getValue txout ≥ inject (utxoEntrySize txout ∗ coinsPerUTxOWord pp)
validateOutputTooSmallUTxO ::
  ( HasField "_coinsPerUTxOWord" (Core.PParams era) Coin,
    HasField "datahash" (Core.TxOut era) (StrictMaybe (DataHash c)),
    Era era
  ) =>
  Core.PParams era ->
  UTxO era ->
  Test (UtxoPredicateFailure era)
validateOutputTooSmallUTxO :: PParams era -> UTxO era -> Test (UtxoPredicateFailure era)
validateOutputTooSmallUTxO PParams era
pp (UTxO Map (TxIn (Crypto era)) (TxOut era)
outputs) =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless ([TxOut era] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TxOut era]
outputsTooSmall) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ [TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputTooSmallUTxO [TxOut era]
outputsTooSmall
  where
    Coin Integer
coinsPerUTxOWord = PParams era -> Coin
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_coinsPerUTxOWord" PParams era
pp
    outputsTooSmall :: [TxOut era]
outputsTooSmall =
      (TxOut era -> Bool) -> [TxOut era] -> [TxOut era]
forall a. (a -> Bool) -> [a] -> [a]
filter
        ( \TxOut era
out ->
            let v :: Value era
v = TxOut era -> Value era
forall k (x :: k) r a. HasField x r a => r -> a
getField @"value" TxOut era
out
             in -- pointwise is used because non-ada amounts must be >= 0 too
                Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Integer -> Integer -> Bool) -> Value era -> Value era -> Bool
forall t. Val t => (Integer -> Integer -> Bool) -> t -> t -> Bool
Val.pointwise Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
(>=) Value era
v (Coin -> Value era
forall t. Val t => Coin -> t
Val.inject (Coin -> Value era) -> Coin -> Value era
forall a b. (a -> b) -> a -> b
$ Integer -> Coin
Coin (TxOut era -> Integer
forall era c.
(Era era,
 HasField "datahash" (TxOut era) (StrictMaybe (DataHash c))) =>
TxOut era -> Integer
utxoEntrySize TxOut era
out Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
coinsPerUTxOWord))
        )
        (Map (TxIn (Crypto era)) (TxOut era) -> [TxOut era]
forall k a. Map k a -> [a]
Map.elems Map (TxIn (Crypto era)) (TxOut era)
outputs)

-- | Ensure that there are no `Core.TxOut`s that have `Value` of size larger
-- than @MaxValSize@. We use serialized length of `Core.Value` because this Value
-- size is being limited inside a serialized `Core.Tx`.
--
-- > ∀ txout ∈ txouts txb, serSize (getValue txout) ≤ maxValSize pp
validateOutputTooBigUTxO ::
  ( HasField "_maxValSize" (Core.PParams era) Natural,
    HasField "value" (Core.TxOut era) (Core.Value era),
    ToCBOR (Core.Value era)
  ) =>
  Core.PParams era ->
  UTxO era ->
  Test (UtxoPredicateFailure era)
validateOutputTooBigUTxO :: PParams era -> UTxO era -> Test (UtxoPredicateFailure era)
validateOutputTooBigUTxO PParams era
pp (UTxO Map (TxIn (Crypto era)) (TxOut era)
outputs) =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless ([(Integer, Integer, TxOut era)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Integer, Integer, TxOut era)]
outputsTooBig) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ [(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
forall era.
[(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
OutputTooBigUTxO [(Integer, Integer, TxOut era)]
outputsTooBig
  where
    maxValSize :: Natural
maxValSize = PParams era -> Natural
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_maxValSize" PParams era
pp
    outputsTooBig :: [(Integer, Integer, TxOut era)]
outputsTooBig = ([(Integer, Integer, TxOut era)]
 -> TxOut era -> [(Integer, Integer, TxOut era)])
-> [(Integer, Integer, TxOut era)]
-> [TxOut era]
-> [(Integer, Integer, TxOut era)]
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' [(Integer, Integer, TxOut era)]
-> TxOut era -> [(Integer, Integer, TxOut era)]
accum [] ([TxOut era] -> [(Integer, Integer, TxOut era)])
-> [TxOut era] -> [(Integer, Integer, TxOut era)]
forall a b. (a -> b) -> a -> b
$ Map (TxIn (Crypto era)) (TxOut era) -> [TxOut era]
forall k a. Map k a -> [a]
Map.elems Map (TxIn (Crypto era)) (TxOut era)
outputs
    accum :: [(Integer, Integer, TxOut era)]
-> TxOut era -> [(Integer, Integer, TxOut era)]
accum [(Integer, Integer, TxOut era)]
ans TxOut era
out =
      let v :: Value era
v = TxOut era -> Value era
forall k (x :: k) r a. HasField x r a => r -> a
getField @"value" TxOut era
out
          serSize :: Natural
serSize = Int64 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Natural) -> Int64 -> Natural
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
BSL.length (ByteString -> Int64) -> ByteString -> Int64
forall a b. (a -> b) -> a -> b
$ Value era -> ByteString
forall a. ToCBOR a => a -> ByteString
serialize Value era
v
       in if Natural
serSize Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Natural
maxValSize
            then (Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
serSize, Natural -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
maxValSize, TxOut era
out) (Integer, Integer, TxOut era)
-> [(Integer, Integer, TxOut era)]
-> [(Integer, Integer, TxOut era)]
forall a. a -> [a] -> [a]
: [(Integer, Integer, TxOut era)]
ans
            else [(Integer, Integer, TxOut era)]
ans

-- | Ensure if NetworkId is present in the txbody it matches the global NetworkId
--
-- > (txnetworkid txb = NetworkId) ∨ (txnetworkid txb = ◇)
validateWrongNetworkInTxBody ::
  HasField "txnetworkid" (Core.TxBody era) (StrictMaybe Network) =>
  Network ->
  Core.TxBody era ->
  Test (UtxoPredicateFailure era)
validateWrongNetworkInTxBody :: Network -> TxBody era -> Test (UtxoPredicateFailure era)
validateWrongNetworkInTxBody Network
netId TxBody era
txb =
  case TxBody era -> StrictMaybe Network
forall k (x :: k) r a. HasField x r a => r -> a
getField @"txnetworkid" TxBody era
txb of
    StrictMaybe Network
SNothing -> () -> Test (UtxoPredicateFailure era)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
    SJust Network
bid -> Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless (Network
netId Network -> Network -> Bool
forall a. Eq a => a -> a -> Bool
== Network
bid) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Network -> Network -> UtxoPredicateFailure era
forall era. Network -> Network -> UtxoPredicateFailure era
WrongNetworkInTxBody Network
netId Network
bid

-- | Ensure that execution units to not exceed the maximum allowed @maxTxExUnits@ parameter.
--
-- > totExunits tx ≤ maxTxExUnits pp
validateExUnitsTooBigUTxO ::
  ( HasField "_maxTxExUnits" (Core.PParams era) ExUnits,
    HasField "txrdmrs" (Core.Witnesses era) (Redeemers era),
    HasField "wits" (Core.Tx era) (Core.Witnesses era)
  ) =>
  Core.PParams era ->
  Core.Tx era ->
  Test (UtxoPredicateFailure era)
validateExUnitsTooBigUTxO :: PParams era -> Tx era -> Test (UtxoPredicateFailure era)
validateExUnitsTooBigUTxO PParams era
pp Tx era
tx =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless ((Natural -> Natural -> Bool) -> ExUnits -> ExUnits -> Bool
pointWiseExUnits Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
(<=) ExUnits
totalExUnits ExUnits
maxTxExUnits) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$
    ExUnits -> ExUnits -> UtxoPredicateFailure era
forall era. ExUnits -> ExUnits -> UtxoPredicateFailure era
ExUnitsTooBigUTxO ExUnits
maxTxExUnits ExUnits
totalExUnits
  where
    maxTxExUnits :: ExUnits
maxTxExUnits = PParams era -> ExUnits
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_maxTxExUnits" PParams era
pp
    -- This sums up the ExUnits for all embedded Plutus Scripts anywhere in the transaction:
    totalExUnits :: ExUnits
totalExUnits = Tx era -> ExUnits
forall era.
(HasField "wits" (Tx era) (Witnesses era),
 HasField "txrdmrs" (Witnesses era) (Redeemers era)) =>
Tx era -> ExUnits
totExUnits Tx era
tx

-- | Ensure that number of collaterals does not exceed the allowed @maxCollInputs@ parameter.
--
-- > ‖collateral tx‖  ≤  maxCollInputs pp
validateTooManyCollateralInputs ::
  ( HasField "_maxCollateralInputs" (Core.PParams era) Natural,
    HasField "collateral" (Core.TxBody era) (Set a)
  ) =>
  Core.PParams era ->
  Core.TxBody era ->
  Test (UtxoPredicateFailure era)
validateTooManyCollateralInputs :: PParams era -> TxBody era -> Test (UtxoPredicateFailure era)
validateTooManyCollateralInputs PParams era
pp TxBody era
txb =
  Bool -> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall e. Bool -> e -> Validation (NonEmpty e) ()
failureUnless (Natural
numColl Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
<= Natural
maxColl) (UtxoPredicateFailure era -> Test (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Natural -> Natural -> UtxoPredicateFailure era
forall era. Natural -> Natural -> UtxoPredicateFailure era
TooManyCollateralInputs Natural
maxColl Natural
numColl
  where
    maxColl, numColl :: Natural
    maxColl :: Natural
maxColl = PParams era -> Natural
forall k (x :: k) r a. HasField x r a => r -> a
getField @"_maxCollateralInputs" PParams era
pp
    numColl :: Natural
numColl = Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Natural) -> (Set a -> Int) -> Set a -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set a -> Int
forall a. Set a -> Int
Set.size (Set a -> Natural) -> Set a -> Natural
forall a b. (a -> b) -> a -> b
$ TxBody era -> Set a
forall k (x :: k) r a. HasField x r a => r -> a
getField @"collateral" TxBody era
txb

-- ================================================================

-- | The UTxO transition rule for the Alonzo eras.
utxoTransition ::
  forall era.
  ( Era era,
    ValidateScript era,
    ConcreteAlonzo era, -- Unlike the Tests, we are ony going to use this once, so we fix the Core.XX types
    Core.Tx era ~ ValidatedTx era,
    Core.Witnesses era ~ TxWitness era,
    STS (AlonzoUTXO era),
    -- instructions for calling UTXOS from AlonzoUTXO
    Embed (Core.EraRule "UTXOS" era) (AlonzoUTXO era),
    Environment (Core.EraRule "UTXOS" era) ~ Shelley.UtxoEnv era,
    State (Core.EraRule "UTXOS" era) ~ Shelley.UTxOState era,
    Signal (Core.EraRule "UTXOS" era) ~ Core.Tx era,
    Inject (PredicateFailure (Core.EraRule "PPUP" era)) (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  TransitionRule (AlonzoUTXO era)
utxoTransition :: TransitionRule (AlonzoUTXO era)
utxoTransition = do
  TRC (Shelley.UtxoEnv slot pp stakepools _genDelegs, State (AlonzoUTXO era)
u, Signal (AlonzoUTXO era)
tx) <- F (Clause (AlonzoUTXO era) 'Transition) (TRC (AlonzoUTXO era))
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext
  let Shelley.UTxOState UTxO era
utxo Coin
_deposits Coin
_fees State (EraRule "PPUP" era)
_ppup IncrementalStake (Crypto era)
_ = UTxOState era
State (AlonzoUTXO era)
u

  {-   txb := txbody tx   -}
  let txb :: TxBody era
txb = ValidatedTx era -> TxBody era
forall era. ValidatedTx era -> TxBody era
body Signal (AlonzoUTXO era)
ValidatedTx era
tx
      inputsAndCollateral :: Set (TxIn (Crypto era))
inputsAndCollateral =
        Set (TxIn (Crypto era))
-> Set (TxIn (Crypto era)) -> Set (TxIn (Crypto era))
forall a. Ord a => Set a -> Set a -> Set a
Set.union
          (TxBody era -> Set (TxIn (Crypto era))
forall k (x :: k) r a. HasField x r a => r -> a
getField @"inputs" TxBody era
TxBody era
txb)
          (TxBody era -> Set (TxIn (Crypto era))
forall k (x :: k) r a. HasField x r a => r -> a
getField @"collateral" TxBody era
TxBody era
txb)

  {- ininterval slot (txvld txb) -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$
    SlotNo -> TxBody era -> Test (UtxoPredicateFailure era)
forall era.
HasField "vldt" (TxBody era) ValidityInterval =>
SlotNo -> TxBody era -> Test (UtxoPredicateFailure era)
ShelleyMA.validateOutsideValidityIntervalUTxO SlotNo
slot TxBody era
txb

  SystemStart
sysSt <- BaseM (AlonzoUTXO era) SystemStart
-> Rule (AlonzoUTXO era) 'Transition SystemStart
forall sts a (ctx :: RuleType).
STS sts =>
BaseM sts a -> Rule sts ctx a
liftSTS (BaseM (AlonzoUTXO era) SystemStart
 -> Rule (AlonzoUTXO era) 'Transition SystemStart)
-> BaseM (AlonzoUTXO era) SystemStart
-> Rule (AlonzoUTXO era) 'Transition SystemStart
forall a b. (a -> b) -> a -> b
$ (Globals -> SystemStart) -> ReaderT Globals Identity SystemStart
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Globals -> SystemStart
systemStart
  EpochInfo (Either Text)
ei <- BaseM (AlonzoUTXO era) (EpochInfo (Either Text))
-> Rule (AlonzoUTXO era) 'Transition (EpochInfo (Either Text))
forall sts a (ctx :: RuleType).
STS sts =>
BaseM sts a -> Rule sts ctx a
liftSTS (BaseM (AlonzoUTXO era) (EpochInfo (Either Text))
 -> Rule (AlonzoUTXO era) 'Transition (EpochInfo (Either Text)))
-> BaseM (AlonzoUTXO era) (EpochInfo (Either Text))
-> Rule (AlonzoUTXO era) 'Transition (EpochInfo (Either Text))
forall a b. (a -> b) -> a -> b
$ (Globals -> EpochInfo (Either Text))
-> ReaderT Globals Identity (EpochInfo (Either Text))
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Globals -> EpochInfo (Either Text)
epochInfo

  {- epochInfoSlotToUTCTime epochInfo systemTime i_f ≠ ◇ -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era
-> EpochInfo (Either Text)
-> SlotNo
-> SystemStart
-> ValidatedTx era
-> Test (UtxoPredicateFailure era)
forall era a.
(HasField "vldt" (TxBody era) ValidityInterval,
 HasField "_protocolVersion" (PParams era) ProtVer) =>
PParams era
-> EpochInfo (Either a)
-> SlotNo
-> SystemStart
-> ValidatedTx era
-> Test (UtxoPredicateFailure era)
validateOutsideForecast PParams era
pp EpochInfo (Either Text)
ei SlotNo
slot SystemStart
sysSt Signal (AlonzoUTXO era)
ValidatedTx era
tx

  {-   txins txb ≠ ∅   -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ TxBody era -> Test (UtxoPredicateFailure era)
forall era.
HasField "inputs" (TxBody era) (Set (TxIn (Crypto era))) =>
TxBody era -> Test (UtxoPredicateFailure era)
Shelley.validateInputSetEmptyUTxO TxBody era
txb

  {-   feesOK pp tx utxo   -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era
-> Tx era -> UTxO era -> Test (UtxoPredicateFailure era)
forall era.
(Era era, Tx era ~ ValidatedTx era,
 HasField "collateral" (TxBody era) (Set (TxIn (Crypto era))),
 HasField "txrdmrs" (Witnesses era) (Redeemers era),
 HasField "_minfeeA" (PParams era) Natural,
 HasField "_minfeeB" (PParams era) Natural,
 HasField "_prices" (PParams era) Prices,
 HasField "_collateralPercentage" (PParams era) Natural) =>
PParams era
-> Tx era -> UTxO era -> Test (UtxoPredicateFailure era)
feesOK PParams era
pp Tx era
Signal (AlonzoUTXO era)
tx UTxO era
utxo -- Generalizes the fee to small from earlier Era's

  {- inputsAndCollateral = txins txb ∪ collateral txb -}
  {- (txins txb) ∪ (collateral txb) ⊆ dom utxo   -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$
    UTxO era
-> Set (TxIn (Crypto era)) -> Test (UtxoPredicateFailure era)
forall era.
UTxO era
-> Set (TxIn (Crypto era)) -> Test (UtxoPredicateFailure era)
Shelley.validateBadInputsUTxO UTxO era
utxo Set (TxIn (Crypto era))
inputsAndCollateral

  {- consumed pp utxo txb = produced pp poolParams txb -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$
    PParams era
-> UTxO era
-> Map (KeyHash 'StakePool (Crypto era)) (PoolParams (Crypto era))
-> TxBody era
-> Test (UtxoPredicateFailure era)
forall era a.
(Era era, HasField "_keyDeposit" (PParams era) Coin,
 HasField "_poolDeposit" (PParams era) Coin,
 HasField "certs" (TxBody era) (StrictSeq (DCert (Crypto era))),
 HasField "inputs" (TxBody era) (Set (TxIn (Crypto era))),
 HasField "wdrls" (TxBody era) (Wdrl (Crypto era)),
 HasField "mint" (TxBody era) (Value era)) =>
PParams era
-> UTxO era
-> Map (KeyHash 'StakePool (Crypto era)) a
-> TxBody era
-> Test (UtxoPredicateFailure era)
ShelleyMA.validateValueNotConservedUTxO PParams era
pp UTxO era
utxo Map (KeyHash 'StakePool (Crypto era)) (PoolParams (Crypto era))
stakepools TxBody era
txb

  {-   adaID ∉ supp mint tx   -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$
    TxBody era -> Test (UtxoPredicateFailure era)
forall era.
(Val (Value era), HasField "mint" (TxBody era) (Value era)) =>
TxBody era -> Test (UtxoPredicateFailure era)
ShelleyMA.validateTriesToForgeADA TxBody era
txb

  let outputs :: UTxO era
outputs = TxBody era -> UTxO era
forall era. Era era => TxBody era -> UTxO era
txouts TxBody era
txb
  {-   ∀ txout ∈ txouts txb, getValuetxout ≥ inject (uxoEntrySizetxout ∗ coinsPerUTxOWord p) -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era -> UTxO era -> Test (UtxoPredicateFailure era)
forall era c.
(HasField "_coinsPerUTxOWord" (PParams era) Coin,
 HasField "datahash" (TxOut era) (StrictMaybe (DataHash c)),
 Era era) =>
PParams era -> UTxO era -> Test (UtxoPredicateFailure era)
validateOutputTooSmallUTxO PParams era
pp UTxO era
outputs

  {-   ∀ txout ∈ txouts txb, serSize (getValue txout) ≤ maxValSize pp   -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era -> UTxO era -> Test (UtxoPredicateFailure era)
forall era.
(HasField "_maxValSize" (PParams era) Natural,
 HasField "value" (TxOut era) (Value era), ToCBOR (Value era)) =>
PParams era -> UTxO era -> Test (UtxoPredicateFailure era)
validateOutputTooBigUTxO PParams era
pp UTxO era
outputs

  {- ∀ ( _ ↦ (a,_)) ∈ txoutstxb,  a ∈ Addrbootstrap → bootstrapAttrsSize a ≤ 64 -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$
    UTxO era -> Test (UtxoPredicateFailure era)
forall era. Era era => UTxO era -> Test (UtxoPredicateFailure era)
Shelley.validateOutputBootAddrAttrsTooBig UTxO era
outputs

  Network
netId <- BaseM (AlonzoUTXO era) Network
-> Rule (AlonzoUTXO era) 'Transition Network
forall sts a (ctx :: RuleType).
STS sts =>
BaseM sts a -> Rule sts ctx a
liftSTS (BaseM (AlonzoUTXO era) Network
 -> Rule (AlonzoUTXO era) 'Transition Network)
-> BaseM (AlonzoUTXO era) Network
-> Rule (AlonzoUTXO era) 'Transition Network
forall a b. (a -> b) -> a -> b
$ (Globals -> Network) -> ReaderT Globals Identity Network
forall (m :: * -> *) r a. Monad m => (r -> a) -> ReaderT r m a
asks Globals -> Network
networkId

  {- ∀(_ → (a, _)) ∈ txouts txb, netId a = NetworkId -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ Network -> [TxOut era] -> Test (UtxoPredicateFailure era)
forall era.
Era era =>
Network -> [TxOut era] -> Test (UtxoPredicateFailure era)
Shelley.validateWrongNetwork Network
netId ([TxOut era] -> Test (UtxoPredicateFailure era))
-> (StrictSeq (TxOut era) -> [TxOut era])
-> StrictSeq (TxOut era)
-> Test (UtxoPredicateFailure era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (TxOut era) -> [TxOut era]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (StrictSeq (TxOut era) -> Test (UtxoPredicateFailure era))
-> StrictSeq (TxOut era) -> Test (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ TxBody era -> StrictSeq (TxOut era)
forall k (x :: k) r a. HasField x r a => r -> a
getField @"outputs" TxBody era
TxBody era
txb

  {- ∀(a → ) ∈ txwdrls txb, netId a = NetworkId -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ Network -> TxBody era -> Test (UtxoPredicateFailure era)
forall era.
HasField "wdrls" (TxBody era) (Wdrl (Crypto era)) =>
Network -> TxBody era -> Test (UtxoPredicateFailure era)
Shelley.validateWrongNetworkWithdrawal Network
netId TxBody era
txb

  {- (txnetworkid txb = NetworkId) ∨ (txnetworkid txb = ◇) -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ Network -> TxBody era -> Test (UtxoPredicateFailure era)
forall era.
HasField "txnetworkid" (TxBody era) (StrictMaybe Network) =>
Network -> TxBody era -> Test (UtxoPredicateFailure era)
validateWrongNetworkInTxBody Network
netId TxBody era
txb

  {- txsize tx ≤ maxTxSize pp -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTestOnSignal (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era -> Tx era -> Test (UtxoPredicateFailure era)
forall era.
(HasField "_maxTxSize" (PParams era) Natural,
 HasField "txsize" (Tx era) Integer) =>
PParams era -> Tx era -> Test (UtxoPredicateFailure era)
Shelley.validateMaxTxSizeUTxO PParams era
pp Tx era
Signal (AlonzoUTXO era)
tx

  {-   totExunits tx ≤ maxTxExUnits pp    -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era -> Tx era -> Test (UtxoPredicateFailure era)
forall era.
(HasField "_maxTxExUnits" (PParams era) ExUnits,
 HasField "txrdmrs" (Witnesses era) (Redeemers era),
 HasField "wits" (Tx era) (Witnesses era)) =>
PParams era -> Tx era -> Test (UtxoPredicateFailure era)
validateExUnitsTooBigUTxO PParams era
pp Tx era
Signal (AlonzoUTXO era)
tx

  {-   ‖collateral tx‖  ≤  maxCollInputs pp   -}
  Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall t sts (ctx :: RuleType).
Inject t (PredicateFailure sts) =>
Test t -> Rule sts ctx ()
runTest (Test (UtxoPredicateFailure era)
 -> Rule (AlonzoUTXO era) 'Transition ())
-> Test (UtxoPredicateFailure era)
-> Rule (AlonzoUTXO era) 'Transition ()
forall a b. (a -> b) -> a -> b
$ PParams era -> TxBody era -> Test (UtxoPredicateFailure era)
forall era a.
(HasField "_maxCollateralInputs" (PParams era) Natural,
 HasField "collateral" (TxBody era) (Set a)) =>
PParams era -> TxBody era -> Test (UtxoPredicateFailure era)
validateTooManyCollateralInputs PParams era
pp TxBody era
txb

  forall sub super (rtype :: RuleType).
Embed sub super =>
RuleContext rtype sub -> Rule super rtype (State sub)
forall super (rtype :: RuleType).
Embed (EraRule "UTXOS" era) super =>
RuleContext rtype (EraRule "UTXOS" era)
-> Rule super rtype (State (EraRule "UTXOS" era))
trans @(Core.EraRule "UTXOS" era) (TRC (EraRule "UTXOS" era)
 -> F (Clause (AlonzoUTXO era) 'Transition) (UTxOState era))
-> F (Clause (AlonzoUTXO era) 'Transition)
     (TRC (EraRule "UTXOS" era))
-> F (Clause (AlonzoUTXO era) 'Transition) (UTxOState era)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< TRC (AlonzoUTXO era) -> TRC (EraRule "UTXOS" era)
coerce (TRC (AlonzoUTXO era) -> TRC (EraRule "UTXOS" era))
-> F (Clause (AlonzoUTXO era) 'Transition) (TRC (AlonzoUTXO era))
-> F (Clause (AlonzoUTXO era) 'Transition)
     (TRC (EraRule "UTXOS" era))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> F (Clause (AlonzoUTXO era) 'Transition) (TRC (AlonzoUTXO era))
forall sts (rtype :: RuleType).
Rule sts rtype (RuleContext rtype sts)
judgmentContext

--------------------------------------------------------------------------------
-- AlonzoUTXO STS
--------------------------------------------------------------------------------

instance
  forall era.
  ( ValidateScript era,
    ConcreteAlonzo era, -- Unlike the Tests, we are only going to use this once, so we fix the Core.XX types
    Core.Tx era ~ ValidatedTx era,
    Core.Witnesses era ~ TxWitness era,
    Embed (Core.EraRule "UTXOS" era) (AlonzoUTXO era),
    Environment (Core.EraRule "UTXOS" era) ~ Shelley.UtxoEnv era,
    State (Core.EraRule "UTXOS" era) ~ Shelley.UTxOState era,
    Signal (Core.EraRule "UTXOS" era) ~ ValidatedTx era,
    Inject (PredicateFailure (Core.EraRule "PPUP" era)) (PredicateFailure (Core.EraRule "UTXOS" era)),
    Era.TxSeq era ~ Alonzo.TxSeq era
  ) =>
  STS (AlonzoUTXO era)
  where
  type State (AlonzoUTXO era) = Shelley.UTxOState era
  type Signal (AlonzoUTXO era) = ValidatedTx era
  type Environment (AlonzoUTXO era) = Shelley.UtxoEnv era
  type BaseM (AlonzoUTXO era) = ShelleyBase
  type PredicateFailure (AlonzoUTXO era) = UtxoPredicateFailure era
  type Event (AlonzoUTXO era) = UtxoEvent era

  initialRules :: [InitialRule (AlonzoUTXO era)]
initialRules = []
  transitionRules :: [TransitionRule (AlonzoUTXO era)]
transitionRules = [TransitionRule (AlonzoUTXO era)
forall era.
(Era era, ValidateScript era, ConcreteAlonzo era,
 Tx era ~ ValidatedTx era, Witnesses era ~ TxWitness era,
 STS (AlonzoUTXO era), Embed (EraRule "UTXOS" era) (AlonzoUTXO era),
 Environment (EraRule "UTXOS" era) ~ UtxoEnv era,
 State (EraRule "UTXOS" era) ~ UTxOState era,
 Signal (EraRule "UTXOS" era) ~ Tx era,
 Inject
   (PredicateFailure (EraRule "PPUP" era))
   (PredicateFailure (EraRule "UTXOS" era))) =>
TransitionRule (AlonzoUTXO era)
utxoTransition]

instance
  ( Era era,
    STS (UTXOS era),
    PredicateFailure (Core.EraRule "UTXOS" era) ~ UtxosPredicateFailure era,
    Event (Core.EraRule "UTXOS" era) ~ Event (UTXOS era)
  ) =>
  Embed (UTXOS era) (AlonzoUTXO era)
  where
  wrapFailed :: PredicateFailure (UTXOS era) -> PredicateFailure (AlonzoUTXO era)
wrapFailed = PredicateFailure (UTXOS era) -> PredicateFailure (AlonzoUTXO era)
forall era.
PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
UtxosFailure
  wrapEvent :: Event (UTXOS era) -> Event (AlonzoUTXO era)
wrapEvent = Event (UTXOS era) -> Event (AlonzoUTXO era)
forall era. Event (EraRule "UTXOS" era) -> UtxoEvent era
UtxosEvent

--------------------------------------------------------------------------------
-- Serialisation
--------------------------------------------------------------------------------

instance
  ( Typeable era,
    Era era,
    ToCBOR (Core.TxOut era),
    ToCBOR (Core.Value era),
    ToCBOR (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  ToCBOR (UtxoPredicateFailure era)
  where
  toCBOR :: UtxoPredicateFailure era -> Encoding
toCBOR UtxoPredicateFailure era
x = Encode 'Open (UtxoPredicateFailure era) -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (UtxoPredicateFailure era -> Encode 'Open (UtxoPredicateFailure era)
forall era.
(Era era, ToCBOR (TxOut era), ToCBOR (Value era),
 ToCBOR (PredicateFailure (EraRule "UTXOS" era))) =>
UtxoPredicateFailure era -> Encode 'Open (UtxoPredicateFailure era)
encFail UtxoPredicateFailure era
x)

encFail ::
  forall era.
  ( Era era,
    ToCBOR (Core.TxOut era),
    ToCBOR (Core.Value era),
    ToCBOR (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  UtxoPredicateFailure era ->
  Encode 'Open (UtxoPredicateFailure era)
encFail :: UtxoPredicateFailure era -> Encode 'Open (UtxoPredicateFailure era)
encFail (BadInputsUTxO Set (TxIn (Crypto era))
ins) =
  (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
forall era. Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
BadInputsUTxO @era) Word
0 Encode 'Open (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (Set (TxIn (Crypto era)))
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> (Set (TxIn (Crypto era)) -> Encoding)
-> Set (TxIn (Crypto era))
-> Encode ('Closed 'Dense) (Set (TxIn (Crypto era)))
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E Set (TxIn (Crypto era)) -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable Set (TxIn (Crypto era))
ins
encFail (OutsideValidityIntervalUTxO ValidityInterval
a SlotNo
b) =
  (ValidityInterval -> SlotNo -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open (ValidityInterval -> SlotNo -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum ValidityInterval -> SlotNo -> UtxoPredicateFailure era
forall era. ValidityInterval -> SlotNo -> UtxoPredicateFailure era
OutsideValidityIntervalUTxO Word
1 Encode
  'Open (ValidityInterval -> SlotNo -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) ValidityInterval
-> Encode 'Open (SlotNo -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ValidityInterval -> Encode ('Closed 'Dense) ValidityInterval
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To ValidityInterval
a Encode 'Open (SlotNo -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) SlotNo
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> SlotNo -> Encode ('Closed 'Dense) SlotNo
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To SlotNo
b
encFail (MaxTxSizeUTxO Integer
a Integer
b) =
  (Integer -> Integer -> UtxoPredicateFailure era)
-> Word
-> Encode 'Open (Integer -> Integer -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum Integer -> Integer -> UtxoPredicateFailure era
forall era. Integer -> Integer -> UtxoPredicateFailure era
MaxTxSizeUTxO Word
2 Encode 'Open (Integer -> Integer -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Integer
-> Encode 'Open (Integer -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
a Encode 'Open (Integer -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Integer
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
b
encFail UtxoPredicateFailure era
InputSetEmptyUTxO =
  UtxoPredicateFailure era
-> Word -> Encode 'Open (UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
InputSetEmptyUTxO Word
3
encFail (FeeTooSmallUTxO Coin
a Coin
b) =
  (Coin -> Coin -> UtxoPredicateFailure era)
-> Word -> Encode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
FeeTooSmallUTxO Word
4 Encode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Coin
-> Encode 'Open (Coin -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Coin -> Encode ('Closed 'Dense) Coin
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
a Encode 'Open (Coin -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Coin
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Coin -> Encode ('Closed 'Dense) Coin
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
b
encFail (ValueNotConservedUTxO Value era
a Value era
b) =
  (Value era -> Value era -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open (Value era -> Value era -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum (Value era -> Value era -> UtxoPredicateFailure era
forall era. Value era -> Value era -> UtxoPredicateFailure era
ValueNotConservedUTxO @era) Word
5 Encode 'Open (Value era -> Value era -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (Value era)
-> Encode 'Open (Value era -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Value era -> Encode ('Closed 'Dense) (Value era)
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Value era
a Encode 'Open (Value era -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (Value era)
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Value era -> Encode ('Closed 'Dense) (Value era)
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Value era
b
encFail (OutputTooSmallUTxO [TxOut era]
outs) =
  ([TxOut era] -> UtxoPredicateFailure era)
-> Word -> Encode 'Open ([TxOut era] -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum ([TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputTooSmallUTxO @era) Word
6 Encode 'Open ([TxOut era] -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) [TxOut era]
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ([TxOut era] -> Encoding)
-> [TxOut era] -> Encode ('Closed 'Dense) [TxOut era]
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E [TxOut era] -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable [TxOut era]
outs
encFail (UtxosFailure PredicateFailure (EraRule "UTXOS" era)
a) =
  (PredicateFailure (EraRule "UTXOS" era)
 -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open
     (PredicateFailure (EraRule "UTXOS" era)
      -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum (PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
forall era.
PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
UtxosFailure @era) Word
7 Encode
  'Open
  (PredicateFailure (EraRule "UTXOS" era)
   -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (PredicateFailure (EraRule "UTXOS" era))
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> PredicateFailure (EraRule "UTXOS" era)
-> Encode ('Closed 'Dense) (PredicateFailure (EraRule "UTXOS" era))
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To PredicateFailure (EraRule "UTXOS" era)
a
encFail (WrongNetwork Network
right Set (Addr (Crypto era))
wrongs) =
  (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open
     (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
WrongNetwork @era) Word
8 Encode
  'Open
  (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Network
-> Encode
     'Open (Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Network -> Encode ('Closed 'Dense) Network
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Network
right Encode 'Open (Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (Set (Addr (Crypto era)))
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> (Set (Addr (Crypto era)) -> Encoding)
-> Set (Addr (Crypto era))
-> Encode ('Closed 'Dense) (Set (Addr (Crypto era)))
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E Set (Addr (Crypto era)) -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable Set (Addr (Crypto era))
wrongs
encFail (WrongNetworkWithdrawal Network
right Set (RewardAcnt (Crypto era))
wrongs) =
  (Network
 -> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open
     (Network
      -> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum (Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
WrongNetworkWithdrawal @era) Word
9 Encode
  'Open
  (Network
   -> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Network
-> Encode
     'Open (Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Network -> Encode ('Closed 'Dense) Network
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Network
right Encode
  'Open (Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (Set (RewardAcnt (Crypto era)))
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> (Set (RewardAcnt (Crypto era)) -> Encoding)
-> Set (RewardAcnt (Crypto era))
-> Encode ('Closed 'Dense) (Set (RewardAcnt (Crypto era)))
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E Set (RewardAcnt (Crypto era)) -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable Set (RewardAcnt (Crypto era))
wrongs
encFail (OutputBootAddrAttrsTooBig [TxOut era]
outs) =
  ([TxOut era] -> UtxoPredicateFailure era)
-> Word -> Encode 'Open ([TxOut era] -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum ([TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputBootAddrAttrsTooBig @era) Word
10 Encode 'Open ([TxOut era] -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) [TxOut era]
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ([TxOut era] -> Encoding)
-> [TxOut era] -> Encode ('Closed 'Dense) [TxOut era]
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E [TxOut era] -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable [TxOut era]
outs
encFail UtxoPredicateFailure era
TriesToForgeADA =
  UtxoPredicateFailure era
-> Word -> Encode 'Open (UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
TriesToForgeADA Word
11
encFail (OutputTooBigUTxO [(Integer, Integer, TxOut era)]
outs) =
  ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era)
-> Word
-> Encode
     'Open ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
forall era.
[(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
OutputTooBigUTxO @era) Word
12 Encode
  'Open ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) [(Integer, Integer, TxOut era)]
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ([(Integer, Integer, TxOut era)] -> Encoding)
-> [(Integer, Integer, TxOut era)]
-> Encode ('Closed 'Dense) [(Integer, Integer, TxOut era)]
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E [(Integer, Integer, TxOut era)] -> Encoding
forall a (f :: * -> *). (ToCBOR a, Foldable f) => f a -> Encoding
encodeFoldable [(Integer, Integer, TxOut era)]
outs
encFail (InsufficientCollateral Coin
a Coin
b) =
  (Coin -> Coin -> UtxoPredicateFailure era)
-> Word -> Encode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
InsufficientCollateral Word
13 Encode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Coin
-> Encode 'Open (Coin -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Coin -> Encode ('Closed 'Dense) Coin
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
a Encode 'Open (Coin -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Coin
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Coin -> Encode ('Closed 'Dense) Coin
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
b
encFail (ScriptsNotPaidUTxO UTxO era
a) =
  (UTxO era -> UtxoPredicateFailure era)
-> Word -> Encode 'Open (UTxO era -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum UTxO era -> UtxoPredicateFailure era
forall era. UTxO era -> UtxoPredicateFailure era
ScriptsNotPaidUTxO Word
14 Encode 'Open (UTxO era -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (UTxO era)
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> UTxO era -> Encode ('Closed 'Dense) (UTxO era)
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To UTxO era
a
encFail (ExUnitsTooBigUTxO ExUnits
a ExUnits
b) =
  (ExUnits -> ExUnits -> UtxoPredicateFailure era)
-> Word
-> Encode 'Open (ExUnits -> ExUnits -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum ExUnits -> ExUnits -> UtxoPredicateFailure era
forall era. ExUnits -> ExUnits -> UtxoPredicateFailure era
ExUnitsTooBigUTxO Word
15 Encode 'Open (ExUnits -> ExUnits -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) ExUnits
-> Encode 'Open (ExUnits -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ExUnits -> Encode ('Closed 'Dense) ExUnits
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To ExUnits
a Encode 'Open (ExUnits -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) ExUnits
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ExUnits -> Encode ('Closed 'Dense) ExUnits
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To ExUnits
b
encFail (CollateralContainsNonADA Value era
a) =
  (Value era -> UtxoPredicateFailure era)
-> Word -> Encode 'Open (Value era -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum Value era -> UtxoPredicateFailure era
forall era. Value era -> UtxoPredicateFailure era
CollateralContainsNonADA Word
16 Encode 'Open (Value era -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) (Value era)
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Value era -> Encode ('Closed 'Dense) (Value era)
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Value era
a
encFail (WrongNetworkInTxBody Network
a Network
b) =
  (Network -> Network -> UtxoPredicateFailure era)
-> Word
-> Encode 'Open (Network -> Network -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum Network -> Network -> UtxoPredicateFailure era
forall era. Network -> Network -> UtxoPredicateFailure era
WrongNetworkInTxBody Word
17 Encode 'Open (Network -> Network -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Network
-> Encode 'Open (Network -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Network -> Encode ('Closed 'Dense) Network
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Network
a Encode 'Open (Network -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Network
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Network -> Encode ('Closed 'Dense) Network
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Network
b
encFail (OutsideForecast SlotNo
a) =
  (SlotNo -> UtxoPredicateFailure era)
-> Word -> Encode 'Open (SlotNo -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum SlotNo -> UtxoPredicateFailure era
forall era. SlotNo -> UtxoPredicateFailure era
OutsideForecast Word
18 Encode 'Open (SlotNo -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) SlotNo
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> SlotNo -> Encode ('Closed 'Dense) SlotNo
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To SlotNo
a
encFail (TooManyCollateralInputs Natural
a Natural
b) =
  (Natural -> Natural -> UtxoPredicateFailure era)
-> Word
-> Encode 'Open (Natural -> Natural -> UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum Natural -> Natural -> UtxoPredicateFailure era
forall era. Natural -> Natural -> UtxoPredicateFailure era
TooManyCollateralInputs Word
19 Encode 'Open (Natural -> Natural -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Natural
-> Encode 'Open (Natural -> UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Natural -> Encode ('Closed 'Dense) Natural
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Natural
a Encode 'Open (Natural -> UtxoPredicateFailure era)
-> Encode ('Closed 'Dense) Natural
-> Encode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Natural -> Encode ('Closed 'Dense) Natural
forall t. ToCBOR t => t -> Encode ('Closed 'Dense) t
To Natural
b
encFail UtxoPredicateFailure era
NoCollateralInputs =
  UtxoPredicateFailure era
-> Word -> Encode 'Open (UtxoPredicateFailure era)
forall t. t -> Word -> Encode 'Open t
Sum UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
NoCollateralInputs Word
20

decFail ::
  ( Era era,
    FromCBOR (Core.TxOut era),
    FromCBOR (Core.Value era),
    FromCBOR (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  Word ->
  Decode 'Open (UtxoPredicateFailure era)
decFail :: Word -> Decode 'Open (UtxoPredicateFailure era)
decFail Word
0 = (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era)
-> Decode
     'Open (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
forall era. Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
BadInputsUTxO Decode 'Open (Set (TxIn (Crypto era)) -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) (Set (TxIn (Crypto era)))
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s (Set (TxIn (Crypto era))))
-> Decode ('Closed 'Dense) (Set (TxIn (Crypto era)))
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (Decoder s (TxIn (Crypto era))
-> Decoder s (Set (TxIn (Crypto era)))
forall a s. Ord a => Decoder s a -> Decoder s (Set a)
decodeSet Decoder s (TxIn (Crypto era))
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
1 = (ValidityInterval -> SlotNo -> UtxoPredicateFailure era)
-> Decode
     'Open (ValidityInterval -> SlotNo -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD ValidityInterval -> SlotNo -> UtxoPredicateFailure era
forall era. ValidityInterval -> SlotNo -> UtxoPredicateFailure era
OutsideValidityIntervalUTxO Decode
  'Open (ValidityInterval -> SlotNo -> UtxoPredicateFailure era)
-> Decode ('Closed Any) ValidityInterval
-> Decode 'Open (SlotNo -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) ValidityInterval
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (SlotNo -> UtxoPredicateFailure era)
-> Decode ('Closed Any) SlotNo
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) SlotNo
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
2 = (Integer -> Integer -> UtxoPredicateFailure era)
-> Decode 'Open (Integer -> Integer -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Integer -> Integer -> UtxoPredicateFailure era
forall era. Integer -> Integer -> UtxoPredicateFailure era
MaxTxSizeUTxO Decode 'Open (Integer -> Integer -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Integer
-> Decode 'Open (Integer -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Integer -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Integer
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
3 = UtxoPredicateFailure era -> Decode 'Open (UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
InputSetEmptyUTxO
decFail Word
4 = (Coin -> Coin -> UtxoPredicateFailure era)
-> Decode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
FeeTooSmallUTxO Decode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Coin
-> Decode 'Open (Coin -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Coin
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Coin -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Coin
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Coin
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
5 = (Value era -> Value era -> UtxoPredicateFailure era)
-> Decode
     'Open (Value era -> Value era -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Value era -> Value era -> UtxoPredicateFailure era
forall era. Value era -> Value era -> UtxoPredicateFailure era
ValueNotConservedUTxO Decode 'Open (Value era -> Value era -> UtxoPredicateFailure era)
-> Decode ('Closed Any) (Value era)
-> Decode 'Open (Value era -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (Value era)
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Value era -> UtxoPredicateFailure era)
-> Decode ('Closed Any) (Value era)
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (Value era)
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
6 = ([TxOut era] -> UtxoPredicateFailure era)
-> Decode 'Open ([TxOut era] -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD [TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputTooSmallUTxO Decode 'Open ([TxOut era] -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) [TxOut era]
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s [TxOut era])
-> Decode ('Closed 'Dense) [TxOut era]
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (Decoder s (TxOut era) -> Decoder s [TxOut era]
forall s a. Decoder s a -> Decoder s [a]
decodeList Decoder s (TxOut era)
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
7 = (PredicateFailure (EraRule "UTXOS" era)
 -> UtxoPredicateFailure era)
-> Decode
     'Open
     (PredicateFailure (EraRule "UTXOS" era)
      -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
forall era.
PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
UtxosFailure Decode
  'Open
  (PredicateFailure (EraRule "UTXOS" era)
   -> UtxoPredicateFailure era)
-> Decode ('Closed Any) (PredicateFailure (EraRule "UTXOS" era))
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (PredicateFailure (EraRule "UTXOS" era))
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
8 = (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
-> Decode
     'Open
     (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
WrongNetwork Decode
  'Open
  (Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Network
-> Decode
     'Open (Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Network
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Set (Addr (Crypto era)) -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) (Set (Addr (Crypto era)))
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s (Set (Addr (Crypto era))))
-> Decode ('Closed 'Dense) (Set (Addr (Crypto era)))
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (Decoder s (Addr (Crypto era))
-> Decoder s (Set (Addr (Crypto era)))
forall a s. Ord a => Decoder s a -> Decoder s (Set a)
decodeSet Decoder s (Addr (Crypto era))
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
9 = (Network
 -> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
-> Decode
     'Open
     (Network
      -> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
WrongNetworkWithdrawal Decode
  'Open
  (Network
   -> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Network
-> Decode
     'Open (Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Network
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode
  'Open (Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) (Set (RewardAcnt (Crypto era)))
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s (Set (RewardAcnt (Crypto era))))
-> Decode ('Closed 'Dense) (Set (RewardAcnt (Crypto era)))
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (Decoder s (RewardAcnt (Crypto era))
-> Decoder s (Set (RewardAcnt (Crypto era)))
forall a s. Ord a => Decoder s a -> Decoder s (Set a)
decodeSet Decoder s (RewardAcnt (Crypto era))
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
10 = ([TxOut era] -> UtxoPredicateFailure era)
-> Decode 'Open ([TxOut era] -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD [TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputBootAddrAttrsTooBig Decode 'Open ([TxOut era] -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) [TxOut era]
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s [TxOut era])
-> Decode ('Closed 'Dense) [TxOut era]
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (Decoder s (TxOut era) -> Decoder s [TxOut era]
forall s a. Decoder s a -> Decoder s [a]
decodeList Decoder s (TxOut era)
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
11 = UtxoPredicateFailure era -> Decode 'Open (UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
TriesToForgeADA
decFail Word
12 =
  let fromRestricted :: (Int, Int, Core.TxOut era) -> (Integer, Integer, Core.TxOut era)
      fromRestricted :: (Int, Int, TxOut era) -> (Integer, Integer, TxOut era)
fromRestricted (Int
sz, Int
mv, TxOut era
txOut) = (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
sz, Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
mv, TxOut era
txOut)
   in ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era)
-> Decode
     'Open ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD [(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
forall era.
[(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
OutputTooBigUTxO Decode
  'Open ([(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) [(Integer, Integer, TxOut era)]
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s [(Integer, Integer, TxOut era)])
-> Decode ('Closed 'Dense) [(Integer, Integer, TxOut era)]
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (((Int, Int, TxOut era) -> (Integer, Integer, TxOut era))
-> [(Int, Int, TxOut era)] -> [(Integer, Integer, TxOut era)]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Int, TxOut era) -> (Integer, Integer, TxOut era)
forall era. (Int, Int, TxOut era) -> (Integer, Integer, TxOut era)
fromRestricted ([(Int, Int, TxOut era)] -> [(Integer, Integer, TxOut era)])
-> Decoder s [(Int, Int, TxOut era)]
-> Decoder s [(Integer, Integer, TxOut era)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (Int, Int, TxOut era)
-> Decoder s [(Int, Int, TxOut era)]
forall s a. Decoder s a -> Decoder s [a]
decodeList Decoder s (Int, Int, TxOut era)
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
13 = (Coin -> Coin -> UtxoPredicateFailure era)
-> Decode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
InsufficientCollateral Decode 'Open (Coin -> Coin -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Coin
-> Decode 'Open (Coin -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Coin
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Coin -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Coin
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Coin
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
14 =
  (UTxO era -> UtxoPredicateFailure era)
-> Decode 'Open (UTxO era -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD UTxO era -> UtxoPredicateFailure era
forall era. UTxO era -> UtxoPredicateFailure era
ScriptsNotPaidUTxO
    Decode 'Open (UTxO era -> UtxoPredicateFailure era)
-> Decode ('Closed 'Dense) (UTxO era)
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s (UTxO era))
-> Decode ('Closed 'Dense) (UTxO era)
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
forall era. Map (TxIn (Crypto era)) (TxOut era) -> UTxO era
UTxO (Map (TxIn (Crypto era)) (TxOut era) -> UTxO era)
-> Decoder s (Map (TxIn (Crypto era)) (TxOut era))
-> Decoder s (UTxO era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (TxIn (Crypto era))
-> Decoder s (TxOut era)
-> Decoder s (Map (TxIn (Crypto era)) (TxOut era))
forall a s b.
Ord a =>
Decoder s a -> Decoder s b -> Decoder s (Map a b)
decodeMap Decoder s (TxIn (Crypto era))
forall a s. FromCBOR a => Decoder s a
fromCBOR Decoder s (TxOut era)
forall a s. FromCBOR a => Decoder s a
fromCBOR)
decFail Word
15 = (ExUnits -> ExUnits -> UtxoPredicateFailure era)
-> Decode 'Open (ExUnits -> ExUnits -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD ExUnits -> ExUnits -> UtxoPredicateFailure era
forall era. ExUnits -> ExUnits -> UtxoPredicateFailure era
ExUnitsTooBigUTxO Decode 'Open (ExUnits -> ExUnits -> UtxoPredicateFailure era)
-> Decode ('Closed Any) ExUnits
-> Decode 'Open (ExUnits -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) ExUnits
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (ExUnits -> UtxoPredicateFailure era)
-> Decode ('Closed Any) ExUnits
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) ExUnits
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
16 = (Value era -> UtxoPredicateFailure era)
-> Decode 'Open (Value era -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Value era -> UtxoPredicateFailure era
forall era. Value era -> UtxoPredicateFailure era
CollateralContainsNonADA Decode 'Open (Value era -> UtxoPredicateFailure era)
-> Decode ('Closed Any) (Value era)
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (Value era)
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
17 = (Network -> Network -> UtxoPredicateFailure era)
-> Decode 'Open (Network -> Network -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Network -> Network -> UtxoPredicateFailure era
forall era. Network -> Network -> UtxoPredicateFailure era
WrongNetworkInTxBody Decode 'Open (Network -> Network -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Network
-> Decode 'Open (Network -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Network
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Network -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Network
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Network
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
18 = (SlotNo -> UtxoPredicateFailure era)
-> Decode 'Open (SlotNo -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD SlotNo -> UtxoPredicateFailure era
forall era. SlotNo -> UtxoPredicateFailure era
OutsideForecast Decode 'Open (SlotNo -> UtxoPredicateFailure era)
-> Decode ('Closed Any) SlotNo
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) SlotNo
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
19 = (Natural -> Natural -> UtxoPredicateFailure era)
-> Decode 'Open (Natural -> Natural -> UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD Natural -> Natural -> UtxoPredicateFailure era
forall era. Natural -> Natural -> UtxoPredicateFailure era
TooManyCollateralInputs Decode 'Open (Natural -> Natural -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Natural
-> Decode 'Open (Natural -> UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Natural
forall t (w :: Wrapped). FromCBOR t => Decode w t
From Decode 'Open (Natural -> UtxoPredicateFailure era)
-> Decode ('Closed Any) Natural
-> Decode 'Open (UtxoPredicateFailure era)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Natural
forall t (w :: Wrapped). FromCBOR t => Decode w t
From
decFail Word
20 = UtxoPredicateFailure era -> Decode 'Open (UtxoPredicateFailure era)
forall t. t -> Decode 'Open t
SumD UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
NoCollateralInputs
decFail Word
n = Word -> Decode 'Open (UtxoPredicateFailure era)
forall (w :: Wrapped) t. Word -> Decode w t
Invalid Word
n

instance
  ( Era era,
    FromCBOR (Core.TxOut era),
    FromCBOR (Core.Value era),
    FromCBOR (PredicateFailure (Core.EraRule "UTXOS" era))
  ) =>
  FromCBOR (UtxoPredicateFailure era)
  where
  fromCBOR :: Decoder s (UtxoPredicateFailure era)
fromCBOR = Decode ('Closed 'Dense) (UtxoPredicateFailure era)
-> Decoder s (UtxoPredicateFailure era)
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode (String
-> (Word -> Decode 'Open (UtxoPredicateFailure era))
-> Decode ('Closed 'Dense) (UtxoPredicateFailure era)
forall t.
String -> (Word -> Decode 'Open t) -> Decode ('Closed 'Dense) t
Summands String
"UtxoPredicateFailure" Word -> Decode 'Open (UtxoPredicateFailure era)
forall era.
(Era era, FromCBOR (TxOut era), FromCBOR (Value era),
 FromCBOR (PredicateFailure (EraRule "UTXOS" era))) =>
Word -> Decode 'Open (UtxoPredicateFailure era)
decFail)

-- =====================================================
-- Injecting from one PredicateFailure to another

fromShelleyFailure :: Shelley.UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
fromShelleyFailure :: UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
fromShelleyFailure = \case
  Shelley.BadInputsUTxO Set (TxIn (Crypto era))
ins -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
forall era. Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
BadInputsUTxO Set (TxIn (Crypto era))
ins
  Shelley.ExpiredUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Replaced with `OutsideValidityIntervalUTxO` in ShelleyMA
  Shelley.MaxTxSizeUTxO Integer
a Integer
m -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> UtxoPredicateFailure era
forall era. Integer -> Integer -> UtxoPredicateFailure era
MaxTxSizeUTxO Integer
a Integer
m
  UtxoPredicateFailure era
Shelley.InputSetEmptyUTxO -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
InputSetEmptyUTxO
  Shelley.FeeTooSmallUTxO Coin
mf Coin
af -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
FeeTooSmallUTxO Coin
mf Coin
af
  Shelley.ValueNotConservedUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Updated in ShelleyMA
  Shelley.WrongNetwork Network
n Set (Addr (Crypto era))
as -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
WrongNetwork Network
n Set (Addr (Crypto era))
as
  Shelley.WrongNetworkWithdrawal Network
n Set (RewardAcnt (Crypto era))
as -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
WrongNetworkWithdrawal Network
n Set (RewardAcnt (Crypto era))
as
  Shelley.OutputTooSmallUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Updated in ShelleyMA
  Shelley.UpdateFailure {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Removed
  Shelley.OutputBootAddrAttrsTooBig [TxOut era]
outs -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ [TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputBootAddrAttrsTooBig [TxOut era]
outs

fromShelleyMAFailure :: ShelleyMA.UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
fromShelleyMAFailure :: UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
fromShelleyMAFailure = \case
  ShelleyMA.BadInputsUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  ShelleyMA.OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ ValidityInterval -> SlotNo -> UtxoPredicateFailure era
forall era. ValidityInterval -> SlotNo -> UtxoPredicateFailure era
OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo
  ShelleyMA.MaxTxSizeUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  UtxoPredicateFailure era
ShelleyMA.InputSetEmptyUTxO -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  ShelleyMA.FeeTooSmallUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  ShelleyMA.ValueNotConservedUTxO Value era
vc Value era
vp -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just (UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era))
-> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a b. (a -> b) -> a -> b
$ Value era -> Value era -> UtxoPredicateFailure era
forall era. Value era -> Value era -> UtxoPredicateFailure era
ValueNotConservedUTxO Value era
vc Value era
vp
  ShelleyMA.WrongNetwork {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  ShelleyMA.WrongNetworkWithdrawal {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  ShelleyMA.OutputTooSmallUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Updated
  ShelleyMA.UpdateFailure {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Removed
  ShelleyMA.OutputBootAddrAttrsTooBig {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Inherited from Shelley
  UtxoPredicateFailure era
ShelleyMA.TriesToForgeADA -> UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall a. a -> Maybe a
Just UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
TriesToForgeADA
  ShelleyMA.OutputTooBigUTxO {} -> Maybe (UtxoPredicateFailure era)
forall a. Maybe a
Nothing -- Updated error reporting

instance Inject (UtxoPredicateFailure era) (UtxoPredicateFailure era) where
  inject :: UtxoPredicateFailure era -> UtxoPredicateFailure era
inject = UtxoPredicateFailure era -> UtxoPredicateFailure era
forall a. a -> a
id

instance
  PredicateFailure (Core.EraRule "UTXOS" era) ~ UtxosPredicateFailure era =>
  Inject (UtxosPredicateFailure era) (UtxoPredicateFailure era)
  where
  inject :: UtxosPredicateFailure era -> UtxoPredicateFailure era
inject = UtxosPredicateFailure era -> UtxoPredicateFailure era
forall era.
PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
UtxosFailure

instance
  Inject (PredicateFailure (Core.EraRule "PPUP" era)) (PredicateFailure (Core.EraRule "UTXOS" era)) =>
  Inject (ShelleyMA.UtxoPredicateFailure era) (UtxoPredicateFailure era)
  where
  inject :: UtxoPredicateFailure era -> UtxoPredicateFailure era
inject = UtxoPredicateFailure era -> UtxoPredicateFailure era
forall era.
Inject
  (PredicateFailure (EraRule "PPUP" era))
  (PredicateFailure (EraRule "UTXOS" era)) =>
UtxoPredicateFailure era -> UtxoPredicateFailure era
utxoPredFailMaToAlonzo

utxoPredFailMaToAlonzo ::
  Inject (PredicateFailure (Core.EraRule "PPUP" era)) (PredicateFailure (Core.EraRule "UTXOS" era)) =>
  ShelleyMA.UtxoPredicateFailure era ->
  UtxoPredicateFailure era
utxoPredFailMaToAlonzo :: UtxoPredicateFailure era -> UtxoPredicateFailure era
utxoPredFailMaToAlonzo (ShelleyMA.BadInputsUTxO Set (TxIn (Crypto era))
x) = Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
forall era. Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
BadInputsUTxO Set (TxIn (Crypto era))
x
utxoPredFailMaToAlonzo (ShelleyMA.OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo) =
  ValidityInterval -> SlotNo -> UtxoPredicateFailure era
forall era. ValidityInterval -> SlotNo -> UtxoPredicateFailure era
OutsideValidityIntervalUTxO ValidityInterval
vi SlotNo
slotNo
utxoPredFailMaToAlonzo (ShelleyMA.MaxTxSizeUTxO Integer
x Integer
y) = Integer -> Integer -> UtxoPredicateFailure era
forall era. Integer -> Integer -> UtxoPredicateFailure era
MaxTxSizeUTxO Integer
x Integer
y
utxoPredFailMaToAlonzo UtxoPredicateFailure era
ShelleyMA.InputSetEmptyUTxO = UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
InputSetEmptyUTxO
utxoPredFailMaToAlonzo (ShelleyMA.FeeTooSmallUTxO Coin
c1 Coin
c2) = Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
FeeTooSmallUTxO Coin
c1 Coin
c2
utxoPredFailMaToAlonzo (ShelleyMA.ValueNotConservedUTxO Value era
vc Value era
vp) = Value era -> Value era -> UtxoPredicateFailure era
forall era. Value era -> Value era -> UtxoPredicateFailure era
ValueNotConservedUTxO Value era
vc Value era
vp
utxoPredFailMaToAlonzo (ShelleyMA.WrongNetwork Network
x Set (Addr (Crypto era))
y) = Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
WrongNetwork Network
x Set (Addr (Crypto era))
y
utxoPredFailMaToAlonzo (ShelleyMA.WrongNetworkWithdrawal Network
x Set (RewardAcnt (Crypto era))
y) = Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
WrongNetworkWithdrawal Network
x Set (RewardAcnt (Crypto era))
y
utxoPredFailMaToAlonzo (ShelleyMA.OutputTooSmallUTxO [TxOut era]
x) = [TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputTooSmallUTxO [TxOut era]
x
utxoPredFailMaToAlonzo (ShelleyMA.UpdateFailure PredicateFailure (EraRule "PPUP" era)
x) = PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
forall era.
PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
UtxosFailure (PredicateFailure (EraRule "PPUP" era)
-> PredicateFailure (EraRule "UTXOS" era)
forall t s. Inject t s => t -> s
inject PredicateFailure (EraRule "PPUP" era)
x)
utxoPredFailMaToAlonzo (ShelleyMA.OutputBootAddrAttrsTooBig [TxOut era]
xs) =
  [(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
forall era.
[(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
OutputTooBigUTxO ((TxOut era -> (Integer, Integer, TxOut era))
-> [TxOut era] -> [(Integer, Integer, TxOut era)]
forall a b. (a -> b) -> [a] -> [b]
map (\TxOut era
x -> (Integer
0, Integer
0, TxOut era
x)) [TxOut era]
xs)
utxoPredFailMaToAlonzo UtxoPredicateFailure era
ShelleyMA.TriesToForgeADA = UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
TriesToForgeADA
utxoPredFailMaToAlonzo (ShelleyMA.OutputTooBigUTxO [TxOut era]
xs) = [(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
forall era.
[(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
OutputTooBigUTxO ((TxOut era -> (Integer, Integer, TxOut era))
-> [TxOut era] -> [(Integer, Integer, TxOut era)]
forall a b. (a -> b) -> [a] -> [b]
map (\TxOut era
x -> (Integer
0, Integer
0, TxOut era
x)) [TxOut era]
xs)

instance
  Inject (PredicateFailure (Core.EraRule "PPUP" era)) (PredicateFailure (Core.EraRule "UTXOS" era)) =>
  Inject (Shelley.UtxoPredicateFailure era) (UtxoPredicateFailure era)
  where
  inject :: UtxoPredicateFailure era -> UtxoPredicateFailure era
inject = UtxoPredicateFailure era -> UtxoPredicateFailure era
forall era.
Inject
  (PredicateFailure (EraRule "PPUP" era))
  (PredicateFailure (EraRule "UTXOS" era)) =>
UtxoPredicateFailure era -> UtxoPredicateFailure era
utxoPredFailShelleyToAlonzo

utxoPredFailShelleyToAlonzo ::
  Inject (PredicateFailure (Core.EraRule "PPUP" era)) (PredicateFailure (Core.EraRule "UTXOS" era)) =>
  Shelley.UtxoPredicateFailure era ->
  UtxoPredicateFailure era
utxoPredFailShelleyToAlonzo :: UtxoPredicateFailure era -> UtxoPredicateFailure era
utxoPredFailShelleyToAlonzo (Shelley.BadInputsUTxO Set (TxIn (Crypto era))
ins) = Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
forall era. Set (TxIn (Crypto era)) -> UtxoPredicateFailure era
BadInputsUTxO Set (TxIn (Crypto era))
ins
utxoPredFailShelleyToAlonzo (Shelley.ExpiredUTxO SlotNo
ttl SlotNo
current) =
  ValidityInterval -> SlotNo -> UtxoPredicateFailure era
forall era. ValidityInterval -> SlotNo -> UtxoPredicateFailure era
OutsideValidityIntervalUTxO (StrictMaybe SlotNo -> StrictMaybe SlotNo -> ValidityInterval
ValidityInterval StrictMaybe SlotNo
forall a. StrictMaybe a
SNothing (SlotNo -> StrictMaybe SlotNo
forall a. a -> StrictMaybe a
SJust SlotNo
ttl)) SlotNo
current
utxoPredFailShelleyToAlonzo (Shelley.MaxTxSizeUTxO Integer
a Integer
m) = Integer -> Integer -> UtxoPredicateFailure era
forall era. Integer -> Integer -> UtxoPredicateFailure era
MaxTxSizeUTxO Integer
a Integer
m
utxoPredFailShelleyToAlonzo UtxoPredicateFailure era
Shelley.InputSetEmptyUTxO = UtxoPredicateFailure era
forall era. UtxoPredicateFailure era
InputSetEmptyUTxO
utxoPredFailShelleyToAlonzo (Shelley.FeeTooSmallUTxO Coin
mf Coin
af) = Coin -> Coin -> UtxoPredicateFailure era
forall era. Coin -> Coin -> UtxoPredicateFailure era
FeeTooSmallUTxO Coin
mf Coin
af
utxoPredFailShelleyToAlonzo (Shelley.ValueNotConservedUTxO Value era
vc Value era
vp) = Value era -> Value era -> UtxoPredicateFailure era
forall era. Value era -> Value era -> UtxoPredicateFailure era
ValueNotConservedUTxO Value era
vc Value era
vp
utxoPredFailShelleyToAlonzo (Shelley.WrongNetwork Network
n Set (Addr (Crypto era))
as) = Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network -> Set (Addr (Crypto era)) -> UtxoPredicateFailure era
WrongNetwork Network
n Set (Addr (Crypto era))
as
utxoPredFailShelleyToAlonzo (Shelley.WrongNetworkWithdrawal Network
n Set (RewardAcnt (Crypto era))
as) = Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
forall era.
Network
-> Set (RewardAcnt (Crypto era)) -> UtxoPredicateFailure era
WrongNetworkWithdrawal Network
n Set (RewardAcnt (Crypto era))
as
utxoPredFailShelleyToAlonzo (Shelley.OutputTooSmallUTxO [TxOut era]
x) = [TxOut era] -> UtxoPredicateFailure era
forall era. [TxOut era] -> UtxoPredicateFailure era
OutputTooSmallUTxO [TxOut era]
x
utxoPredFailShelleyToAlonzo (Shelley.UpdateFailure PredicateFailure (EraRule "PPUP" era)
x) = PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
forall era.
PredicateFailure (EraRule "UTXOS" era) -> UtxoPredicateFailure era
UtxosFailure (PredicateFailure (EraRule "PPUP" era)
-> PredicateFailure (EraRule "UTXOS" era)
forall t s. Inject t s => t -> s
inject PredicateFailure (EraRule "PPUP" era)
x)
utxoPredFailShelleyToAlonzo (Shelley.OutputBootAddrAttrsTooBig [TxOut era]
outs) =
  [(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
forall era.
[(Integer, Integer, TxOut era)] -> UtxoPredicateFailure era
OutputTooBigUTxO ((TxOut era -> (Integer, Integer, TxOut era))
-> [TxOut era] -> [(Integer, Integer, TxOut era)]
forall a b. (a -> b) -> [a] -> [b]
map (\TxOut era
x -> (Integer
0, Integer
0, TxOut era
x)) [TxOut era]
outs)

instance InjectMaybe (Shelley.UtxoPredicateFailure era) (UtxoPredicateFailure era) where
  injectMaybe :: UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
injectMaybe = UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall era.
UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
fromShelleyFailure

instance InjectMaybe (ShelleyMA.UtxoPredicateFailure era) (UtxoPredicateFailure era) where
  injectMaybe :: UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
injectMaybe = UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
forall era.
UtxoPredicateFailure era -> Maybe (UtxoPredicateFailure era)
fromShelleyMAFailure