cardano-ledger-alonzo-0.1.0.0: Cardano ledger introducing Plutus Core
Safe Haskell None
Language Haskell2010

Cardano.Ledger.Alonzo.Rules.Utxo

Synopsis

Documentation

utxoEntrySize :: ( Era era, HasField "datahash" ( TxOut era) ( StrictMaybe ( DataHash c))) => TxOut era -> Integer Source #

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

data AlonzoUTXO era Source #

The uninhabited type that marks the Alonzo UTxO rule

Instances

Instances details
( ValidateScript era, ConcreteAlonzo era, Tx era ~ ValidatedTx era, Witnesses era ~ TxWitness era, Embed ( EraRule "UTXOS" era) ( AlonzoUTXO era), Environment ( EraRule "UTXOS" era) ~ UtxoEnv era, State ( EraRule "UTXOS" era) ~ UTxOState era, Signal ( EraRule "UTXOS" era) ~ ValidatedTx era, Inject ( PredicateFailure ( EraRule "PPUP" era)) ( PredicateFailure ( EraRule "UTXOS" era)), TxSeq era ~ TxSeq era) => STS ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

( Era era, STS ( UTXOS era), PredicateFailure ( EraRule "UTXOS" era) ~ UtxosPredicateFailure era, Event ( EraRule "UTXOS" era) ~ Event ( UTXOS era)) => Embed ( UTXOS era) ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

( Era era, STS ( AlonzoUTXO era), PredicateFailure ( EraRule "UTXO" era) ~ UtxoPredicateFailure era, Event ( EraRule "UTXO" era) ~ UtxoEvent era, BaseM ( AlonzoUTXOW era) ~ ShelleyBase , PredicateFailure ( AlonzoUTXOW era) ~ UtxowPredicateFail era, Event ( AlonzoUTXOW era) ~ AlonzoEvent era) => Embed ( AlonzoUTXO era) ( AlonzoUTXOW era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxow

type State ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type Event ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type PredicateFailure ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type BaseM ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type Environment ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type Signal ( AlonzoUTXO era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

data UtxoPredicateFailure era Source #

Constructors

BadInputsUTxO !( Set ( TxIn ( Crypto era)))

The bad transaction inputs

OutsideValidityIntervalUTxO

Fields

MaxTxSizeUTxO

Fields

InputSetEmptyUTxO
FeeTooSmallUTxO

Fields

  • ! Coin

    the minimum fee for this transaction

  • ! Coin

    the fee supplied in this transaction

ValueNotConservedUTxO

Fields

  • !( Value era)

    the Coin consumed by this transaction

  • !( Value era)

    the Coin produced by this transaction

WrongNetwork

the set of addresses with incorrect network IDs

Fields

WrongNetworkWithdrawal

Fields

OutputTooSmallUTxO ![ TxOut era]

list of supplied transaction outputs that are too small

UtxosFailure ( PredicateFailure ( EraRule "UTXOS" era))

Subtransition Failures

OutputBootAddrAttrsTooBig ![ TxOut era]

list of supplied bad transaction outputs

TriesToForgeADA
OutputTooBigUTxO ![( Integer , Integer , TxOut era)]

list of supplied bad transaction output triples (actualSize,PParameterMaxValue,TxOut)

InsufficientCollateral

Fields

  • ! Coin

    balance computed

  • ! Coin

    the required collateral for the given fee

ScriptsNotPaidUTxO !( UTxO era)

The UTxO entries which have the wrong kind of script

ExUnitsTooBigUTxO

Fields

CollateralContainsNonADA !( Value era)

The inputs marked for use as fees contain non-ADA tokens

WrongNetworkInTxBody

Wrong Network ID in body

Fields

OutsideForecast ! SlotNo

slot number outside consensus forecast range

TooManyCollateralInputs

There are too many collateral inputs

Fields

NoCollateralInputs

Instances

Instances details
( Crypto ( Crypto era), Eq ( Value era), Eq ( TxOut era), Eq ( PredicateFailure ( EraRule "UTXOS" era))) => Eq ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

( Era era, Show ( Value era), Show ( TxOut era), Show ( TxBody era), Show ( PredicateFailure ( EraRule "UTXOS" era))) => Show ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

Generic ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

( Typeable era, Era era, ToCBOR ( TxOut era), ToCBOR ( Value era), ToCBOR ( PredicateFailure ( EraRule "UTXOS" era))) => ToCBOR ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

( Era era, FromCBOR ( TxOut era), FromCBOR ( Value era), FromCBOR ( PredicateFailure ( EraRule "UTXOS" era))) => FromCBOR ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

( Era era, ToCBOR ( Value era), ToCBOR ( TxOut era), ToCBOR ( TxBody era), NoThunks ( Value era), NoThunks ( TxOut era), NoThunks ( PredicateFailure ( EraRule "UTXOS" era))) => NoThunks ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

Inject ( PredicateFailure ( EraRule "PPUP" era)) ( PredicateFailure ( EraRule "UTXOS" era)) => Inject ( UtxoPredicateFailure era) ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

Inject ( PredicateFailure ( EraRule "PPUP" era)) ( PredicateFailure ( EraRule "UTXOS" era)) => Inject ( UtxoPredicateFailure era) ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

PredicateFailure ( EraRule "UTXOS" era) ~ UtxosPredicateFailure era => Inject ( UtxosPredicateFailure era) ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

Inject ( UtxoPredicateFailure era) ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

InjectMaybe ( UtxoPredicateFailure era) ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

InjectMaybe ( UtxoPredicateFailure era) ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type Rep ( UtxoPredicateFailure era) Source #
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type Rep ( UtxoPredicateFailure era) = D1 (' MetaData "UtxoPredicateFailure" "Cardano.Ledger.Alonzo.Rules.Utxo" "cardano-ledger-alonzo-0.1.0.0-xW3meaGVQP43dxJ76zbGD" ' False ) (((( C1 (' MetaCons "BadInputsUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( Set ( TxIn ( Crypto era))))) :+: C1 (' MetaCons "OutsideValidityIntervalUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ValidityInterval ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 SlotNo ))) :+: ( C1 (' MetaCons "MaxTxSizeUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Integer ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Integer )) :+: ( C1 (' MetaCons "InputSetEmptyUTxO" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "FeeTooSmallUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Coin ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Coin ))))) :+: (( C1 (' MetaCons "ValueNotConservedUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( Value era)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( Value era))) :+: C1 (' MetaCons "WrongNetwork" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Network ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( Set ( Addr ( Crypto era)))))) :+: ( C1 (' MetaCons "WrongNetworkWithdrawal" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Network ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( Set ( RewardAcnt ( Crypto era))))) :+: ( C1 (' MetaCons "OutputTooSmallUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 [ TxOut era])) :+: C1 (' MetaCons "UtxosFailure" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( PredicateFailure ( EraRule "UTXOS" era)))))))) :+: ((( C1 (' MetaCons "OutputBootAddrAttrsTooBig" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 [ TxOut era])) :+: C1 (' MetaCons "TriesToForgeADA" ' PrefixI ' False ) ( U1 :: Type -> Type )) :+: ( C1 (' MetaCons "OutputTooBigUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 [( Integer , Integer , TxOut era)])) :+: ( C1 (' MetaCons "InsufficientCollateral" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Coin ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Coin )) :+: C1 (' MetaCons "ScriptsNotPaidUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( UTxO era)))))) :+: (( C1 (' MetaCons "ExUnitsTooBigUTxO" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ExUnits ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ExUnits )) :+: ( C1 (' MetaCons "CollateralContainsNonADA" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( Value era))) :+: C1 (' MetaCons "WrongNetworkInTxBody" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Network ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Network )))) :+: ( C1 (' MetaCons "OutsideForecast" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 SlotNo )) :+: ( C1 (' MetaCons "TooManyCollateralInputs" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Natural ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Natural )) :+: C1 (' MetaCons "NoCollateralInputs" ' PrefixI ' False ) ( U1 :: Type -> Type ))))))

newtype UtxoEvent era Source #

Constructors

UtxosEvent ( Event ( EraRule "UTXOS" era))

isKeyHashAddr :: Addr crypto -> Bool Source #

Returns true for VKey locked addresses, and false for any kind of script-locked address.

isKeyHashCompactAddr :: CompactAddr crypto -> Bool Source #

This is equivalent to isKeyHashAddr , but for compacted version of an address.

feesOK :: 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) Source #

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.

validateOutsideForecast Source #

Arguments

:: ( HasField "vldt" ( TxBody era) ValidityInterval , HasField "_protocolVersion" ( PParams era) ProtVer )
=> PParams era
-> EpochInfo ( Either a)
-> SlotNo

Current slot number

-> SystemStart
-> ValidatedTx era
-> Test ( UtxoPredicateFailure era)

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 ≠ ◇

validateOutputTooSmallUTxO :: ( HasField "_coinsPerUTxOWord" ( PParams era) Coin , HasField "datahash" ( TxOut era) ( StrictMaybe ( DataHash c)), Era era) => PParams era -> UTxO era -> Test ( UtxoPredicateFailure era) Source #

Ensure that there are no TxOut s that have value less than the sized coinsPerUTxOWord

∀ txout ∈ txouts txb, getValue txout ≥ inject (utxoEntrySize txout ∗ coinsPerUTxOWord pp)

validateOutputTooBigUTxO :: ( HasField "_maxValSize" ( PParams era) Natural , HasField "value" ( TxOut era) ( Value era), ToCBOR ( Value era)) => PParams era -> UTxO era -> Test ( UtxoPredicateFailure era) Source #

Ensure that there are no TxOut s that have Value of size larger than MaxValSize . We use serialized length of Value because this Value size is being limited inside a serialized Tx .

∀ txout ∈ txouts txb, serSize (getValue txout) ≤ maxValSize pp

validateWrongNetworkInTxBody :: HasField "txnetworkid" ( TxBody era) ( StrictMaybe Network ) => Network -> TxBody era -> Test ( UtxoPredicateFailure era) Source #

Ensure if NetworkId is present in the txbody it matches the global NetworkId

(txnetworkid txb = NetworkId) ∨ (txnetworkid txb = ◇)

validateExUnitsTooBigUTxO :: ( HasField "_maxTxExUnits" ( PParams era) ExUnits , HasField "txrdmrs" ( Witnesses era) ( Redeemers era), HasField "wits" ( Tx era) ( Witnesses era)) => PParams era -> Tx era -> Test ( UtxoPredicateFailure era) Source #

Ensure that execution units to not exceed the maximum allowed maxTxExUnits parameter.

totExunits tx ≤ maxTxExUnits pp

validateTooManyCollateralInputs :: ( HasField "_maxCollateralInputs" ( PParams era) Natural , HasField "collateral" ( TxBody era) ( Set a)) => PParams era -> TxBody era -> Test ( UtxoPredicateFailure era) Source #

Ensure that number of collaterals does not exceed the allowed maxCollInputs parameter.

‖collateral tx‖  ≤  maxCollInputs pp

utxoTransition :: 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) Source #

The UTxO transition rule for the Alonzo eras.