{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_HADDOCK not-home #-}
module Cardano.Ledger.Alonzo.TxBody.Internal (
AlonzoTxOut (..),
AlonzoEraTxOut (..),
Addr28Extra,
DataHash32,
AlonzoTxBody (
..,
AlonzoTxBody,
atbInputs,
atbCollateral,
atbOutputs,
atbCerts,
atbWithdrawals,
atbTxFee,
atbValidityInterval,
atbUpdate,
atbReqSignerHashes,
atbMint,
atbScriptIntegrityHash,
atbAuxDataHash,
atbTxNetworkId
),
AlonzoTxBodyRaw (..),
AlonzoTxBodyUpgradeError (..),
AlonzoEraTxBody (..),
ShelleyEraTxBody (..),
AllegraEraTxBody (..),
MaryEraTxBody (..),
Indexable (..),
inputs',
collateral',
outputs',
certs',
withdrawals',
txfee',
vldt',
update',
reqSignerHashes',
mint',
scriptIntegrityHash',
adHash',
txnetworkid',
getAdaOnly,
decodeDataHash32,
encodeDataHash32,
encodeAddress28,
decodeAddress28,
viewCompactTxOut,
viewTxOut,
EraIndependentScriptIntegrity,
ScriptIntegrityHash,
getAlonzoTxOutEitherAddr,
utxoEntrySize,
alonzoRedeemerPointer,
alonzoRedeemerPointerInverse,
)
where
import Cardano.Ledger.Alonzo.Era
import Cardano.Ledger.Alonzo.PParams ()
import Cardano.Ledger.Alonzo.Scripts (
AlonzoPlutusPurpose (..),
AsItem (..),
AsIx (..),
AsIxItem (..),
PlutusPurpose,
)
import Cardano.Ledger.Alonzo.TxAuxData ()
import Cardano.Ledger.Alonzo.TxCert ()
import Cardano.Ledger.Alonzo.TxOut
import Cardano.Ledger.BaseTypes (
Network (..),
StrictMaybe (..),
)
import Cardano.Ledger.Binary (
Annotator,
DecCBOR (..),
EncCBOR (..),
ToCBOR (..),
)
import Cardano.Ledger.Binary.Coders
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Mary.Core
import Cardano.Ledger.Mary.TxBody (MaryTxBody (..))
import Cardano.Ledger.Mary.Value (
MaryValue (MaryValue),
MultiAsset (..),
PolicyID (..),
policies,
)
import Cardano.Ledger.MemoBytes (
EqRaw,
Mem,
MemoBytes,
MemoHashIndex,
Memoized (..),
getMemoRawType,
getMemoSafeHash,
lensMemoRawType,
mkMemoized,
)
import Cardano.Ledger.Shelley.PParams (ProposedPPUpdates (..), Update (..))
import Cardano.Ledger.Shelley.TxBody (getShelleyGenesisKeyHashCountTxBody)
import Cardano.Ledger.TxIn (TxIn (..))
import Control.Arrow (left)
import Control.DeepSeq (NFData (..))
import Control.Monad (when)
import Data.Default (def)
import qualified Data.Map.Strict as Map
import Data.Maybe.Strict (isSJust)
import Data.OSet.Strict (OSet)
import qualified Data.OSet.Strict as OSet
import Data.Sequence.Strict (StrictSeq)
import qualified Data.Sequence.Strict as StrictSeq
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Typeable (Typeable)
import Data.Void (absurd)
import Data.Word (Word32)
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (NoThunks)
type ScriptIntegrityHash = SafeHash EraIndependentScriptIntegrity
class (MaryEraTxBody era, AlonzoEraTxOut era) => AlonzoEraTxBody era where
collateralInputsTxBodyL :: Lens' (TxBody era) (Set TxIn)
reqSignerHashesTxBodyL :: Lens' (TxBody era) (Set (KeyHash 'Witness))
scriptIntegrityHashTxBodyL ::
Lens' (TxBody era) (StrictMaybe ScriptIntegrityHash)
networkIdTxBodyL :: Lens' (TxBody era) (StrictMaybe Network)
redeemerPointer ::
TxBody era ->
PlutusPurpose AsItem era ->
StrictMaybe (PlutusPurpose AsIx era)
redeemerPointerInverse ::
TxBody era ->
PlutusPurpose AsIx era ->
StrictMaybe (PlutusPurpose AsIxItem era)
data AlonzoTxBodyRaw era = AlonzoTxBodyRaw
{ forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrInputs :: !(Set TxIn)
, forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrCollateral :: !(Set TxIn)
, forall era. AlonzoTxBodyRaw era -> StrictSeq (TxOut era)
atbrOutputs :: !(StrictSeq (TxOut era))
, forall era. AlonzoTxBodyRaw era -> StrictSeq (TxCert era)
atbrCerts :: !(StrictSeq (TxCert era))
, forall era. AlonzoTxBodyRaw era -> Withdrawals
atbrWithdrawals :: !Withdrawals
, forall era. AlonzoTxBodyRaw era -> Coin
atbrTxFee :: !Coin
, forall era. AlonzoTxBodyRaw era -> ValidityInterval
atbrValidityInterval :: !ValidityInterval
, forall era. AlonzoTxBodyRaw era -> StrictMaybe (Update era)
atbrUpdate :: !(StrictMaybe (Update era))
, forall era. AlonzoTxBodyRaw era -> Set (KeyHash 'Witness)
atbrReqSignerHashes :: Set (KeyHash 'Witness)
, forall era. AlonzoTxBodyRaw era -> MultiAsset
atbrMint :: !MultiAsset
, forall era. AlonzoTxBodyRaw era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: !(StrictMaybe ScriptIntegrityHash)
, forall era. AlonzoTxBodyRaw era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash :: !(StrictMaybe TxAuxDataHash)
, forall era. AlonzoTxBodyRaw era -> StrictMaybe Network
atbrTxNetworkId :: !(StrictMaybe Network)
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (AlonzoTxBodyRaw era) x -> AlonzoTxBodyRaw era
forall era x. AlonzoTxBodyRaw era -> Rep (AlonzoTxBodyRaw era) x
$cto :: forall era x. Rep (AlonzoTxBodyRaw era) x -> AlonzoTxBodyRaw era
$cfrom :: forall era x. AlonzoTxBodyRaw era -> Rep (AlonzoTxBodyRaw era) x
Generic, Typeable)
deriving instance
(Era era, Eq (TxOut era), Eq (TxCert era), Eq (PParamsUpdate era)) =>
Eq (AlonzoTxBodyRaw era)
instance
(Era era, NoThunks (TxOut era), NoThunks (TxCert era), NoThunks (PParamsUpdate era)) =>
NoThunks (AlonzoTxBodyRaw era)
instance
(Era era, NFData (TxOut era), NFData (TxCert era), NFData (PParamsUpdate era)) =>
NFData (AlonzoTxBodyRaw era)
deriving instance
(Era era, Show (TxOut era), Show (TxCert era), Show (PParamsUpdate era)) =>
Show (AlonzoTxBodyRaw era)
newtype AlonzoTxBody era = TxBodyConstr (MemoBytes AlonzoTxBodyRaw era)
deriving (AlonzoTxBody era -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [AlonzoTxBody era] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (AlonzoTxBody era) -> Size
forall {era}. Typeable era => Typeable (AlonzoTxBody era)
forall era. Typeable era => AlonzoTxBody era -> Encoding
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> ToCBOR a
forall era.
Typeable era =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [AlonzoTxBody era] -> Size
forall era.
Typeable era =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (AlonzoTxBody era) -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [AlonzoTxBody era] -> Size
$cencodedListSizeExpr :: forall era.
Typeable era =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [AlonzoTxBody era] -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (AlonzoTxBody era) -> Size
$cencodedSizeExpr :: forall era.
Typeable era =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (AlonzoTxBody era) -> Size
toCBOR :: AlonzoTxBody era -> Encoding
$ctoCBOR :: forall era. Typeable era => AlonzoTxBody era -> Encoding
ToCBOR, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (AlonzoTxBody era) x -> AlonzoTxBody era
forall era x. AlonzoTxBody era -> Rep (AlonzoTxBody era) x
$cto :: forall era x. Rep (AlonzoTxBody era) x -> AlonzoTxBody era
$cfrom :: forall era x. AlonzoTxBody era -> Rep (AlonzoTxBody era) x
Generic)
deriving newtype (AlonzoTxBody era -> Int
AlonzoTxBody era -> ByteString
forall i. Proxy i -> AlonzoTxBody era -> SafeHash i
forall era. AlonzoTxBody era -> Int
forall era. AlonzoTxBody era -> ByteString
forall t.
(t -> ByteString)
-> (t -> Int)
-> (forall i. Proxy i -> t -> SafeHash i)
-> SafeToHash t
forall era i. Proxy i -> AlonzoTxBody era -> SafeHash i
makeHashWithExplicitProxys :: forall i. Proxy i -> AlonzoTxBody era -> SafeHash i
$cmakeHashWithExplicitProxys :: forall era i. Proxy i -> AlonzoTxBody era -> SafeHash i
originalBytesSize :: AlonzoTxBody era -> Int
$coriginalBytesSize :: forall era. AlonzoTxBody era -> Int
originalBytes :: AlonzoTxBody era -> ByteString
$coriginalBytes :: forall era. AlonzoTxBody era -> ByteString
SafeToHash)
instance Memoized AlonzoTxBody where
type RawType AlonzoTxBody = AlonzoTxBodyRaw
data AlonzoTxBodyUpgradeError
=
ATBUEMinUTxOUpdated
deriving (Int -> AlonzoTxBodyUpgradeError -> ShowS
[AlonzoTxBodyUpgradeError] -> ShowS
AlonzoTxBodyUpgradeError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AlonzoTxBodyUpgradeError] -> ShowS
$cshowList :: [AlonzoTxBodyUpgradeError] -> ShowS
show :: AlonzoTxBodyUpgradeError -> String
$cshow :: AlonzoTxBodyUpgradeError -> String
showsPrec :: Int -> AlonzoTxBodyUpgradeError -> ShowS
$cshowsPrec :: Int -> AlonzoTxBodyUpgradeError -> ShowS
Show)
instance EraTxBody AlonzoEra where
type TxBody AlonzoEra = AlonzoTxBody AlonzoEra
type TxBodyUpgradeError AlonzoEra = AlonzoTxBodyUpgradeError
mkBasicTxBody :: TxBody AlonzoEra
mkBasicTxBody = forall era (t :: * -> *).
(Era era, EncCBOR (RawType t era), Memoized t) =>
RawType t era -> t era
mkMemoized forall era. AlonzoTxBodyRaw era
emptyAlonzoTxBodyRaw
inputsTxBodyL :: Lens' (TxBody AlonzoEra) (Set TxIn)
inputsTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrInputs (\RawType AlonzoTxBody AlonzoEra
txBodyRaw Set TxIn
inputs_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrInputs :: Set TxIn
atbrInputs = Set TxIn
inputs_})
{-# INLINEABLE inputsTxBodyL #-}
outputsTxBodyL :: Lens' (TxBody AlonzoEra) (StrictSeq (TxOut AlonzoEra))
outputsTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> StrictSeq (TxOut era)
atbrOutputs (\RawType AlonzoTxBody AlonzoEra
txBodyRaw StrictSeq (AlonzoTxOut AlonzoEra)
outputs_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrOutputs :: StrictSeq (TxOut AlonzoEra)
atbrOutputs = StrictSeq (AlonzoTxOut AlonzoEra)
outputs_})
{-# INLINEABLE outputsTxBodyL #-}
feeTxBodyL :: Lens' (TxBody AlonzoEra) Coin
feeTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> Coin
atbrTxFee (\RawType AlonzoTxBody AlonzoEra
txBodyRaw Coin
fee_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrTxFee :: Coin
atbrTxFee = Coin
fee_})
{-# INLINEABLE feeTxBodyL #-}
auxDataHashTxBodyL :: Lens' (TxBody AlonzoEra) (StrictMaybe TxAuxDataHash)
auxDataHashTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType
forall era. AlonzoTxBodyRaw era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash
(\RawType AlonzoTxBody AlonzoEra
txBodyRaw StrictMaybe TxAuxDataHash
auxDataHash -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrAuxDataHash = StrictMaybe TxAuxDataHash
auxDataHash})
{-# INLINEABLE auxDataHashTxBodyL #-}
spendableInputsTxBodyF :: SimpleGetter (TxBody AlonzoEra) (Set TxIn)
spendableInputsTxBodyF = forall era. EraTxBody era => SimpleGetter (TxBody era) (Set TxIn)
allInputsTxBodyF
{-# INLINE spendableInputsTxBodyF #-}
allInputsTxBodyF :: SimpleGetter (TxBody AlonzoEra) (Set TxIn)
allInputsTxBodyF =
forall s a. (s -> a) -> SimpleGetter s a
to forall a b. (a -> b) -> a -> b
$ \TxBody AlonzoEra
txBody -> (TxBody AlonzoEra
txBody forall s a. s -> Getting a s a -> a
^. forall era. EraTxBody era => Lens' (TxBody era) (Set TxIn)
inputsTxBodyL) forall a. Ord a => Set a -> Set a -> Set a
`Set.union` (TxBody AlonzoEra
txBody forall s a. s -> Getting a s a -> a
^. forall era. AlonzoEraTxBody era => Lens' (TxBody era) (Set TxIn)
collateralInputsTxBodyL)
{-# INLINEABLE allInputsTxBodyF #-}
withdrawalsTxBodyL :: Lens' (TxBody AlonzoEra) Withdrawals
withdrawalsTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType
forall era. AlonzoTxBodyRaw era -> Withdrawals
atbrWithdrawals
(\RawType AlonzoTxBody AlonzoEra
txBodyRaw Withdrawals
withdrawals_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrWithdrawals :: Withdrawals
atbrWithdrawals = Withdrawals
withdrawals_})
{-# INLINEABLE withdrawalsTxBodyL #-}
certsTxBodyL :: Lens' (TxBody AlonzoEra) (StrictSeq (TxCert AlonzoEra))
certsTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> StrictSeq (TxCert era)
atbrCerts (\RawType AlonzoTxBody AlonzoEra
txBodyRaw StrictSeq (ShelleyTxCert AlonzoEra)
certs_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrCerts :: StrictSeq (TxCert AlonzoEra)
atbrCerts = StrictSeq (ShelleyTxCert AlonzoEra)
certs_})
{-# INLINEABLE certsTxBodyL #-}
getGenesisKeyHashCountTxBody :: TxBody AlonzoEra -> Int
getGenesisKeyHashCountTxBody = forall era. ShelleyEraTxBody era => TxBody era -> Int
getShelleyGenesisKeyHashCountTxBody
upgradeTxBody :: EraTxBody (PreviousEra AlonzoEra) =>
TxBody (PreviousEra AlonzoEra)
-> Either (TxBodyUpgradeError AlonzoEra) (TxBody AlonzoEra)
upgradeTxBody
MaryTxBody
{ Set TxIn
mtbInputs :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> Set TxIn
mtbInputs :: Set TxIn
mtbInputs
, StrictSeq (TxOut MaryEra)
mtbOutputs :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> StrictSeq (TxOut era)
mtbOutputs :: StrictSeq (TxOut MaryEra)
mtbOutputs
, StrictSeq (TxCert MaryEra)
mtbCerts :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> StrictSeq (TxCert era)
mtbCerts :: StrictSeq (TxCert MaryEra)
mtbCerts
, Withdrawals
mtbWithdrawals :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> Withdrawals
mtbWithdrawals :: Withdrawals
mtbWithdrawals
, Coin
mtbTxFee :: forall era. (EraTxOut era, EraTxCert era) => MaryTxBody era -> Coin
mtbTxFee :: Coin
mtbTxFee
, ValidityInterval
mtbValidityInterval :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> ValidityInterval
mtbValidityInterval :: ValidityInterval
mtbValidityInterval
, StrictMaybe (Update MaryEra)
mtbUpdate :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> StrictMaybe (Update era)
mtbUpdate :: StrictMaybe (Update MaryEra)
mtbUpdate
, StrictMaybe TxAuxDataHash
mtbAuxDataHash :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> StrictMaybe TxAuxDataHash
mtbAuxDataHash :: StrictMaybe TxAuxDataHash
mtbAuxDataHash
, MultiAsset
mtbMint :: forall era.
(EraTxOut era, EraTxCert era) =>
MaryTxBody era -> MultiAsset
mtbMint :: MultiAsset
mtbMint
} = do
StrictSeq (TxCert AlonzoEra)
certs <-
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
(forall (a :: * -> * -> *) b c d.
ArrowChoice a =>
a b c -> a (Either b d) (Either c d)
left forall a. Void -> a
absurd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
(EraTxCert era, EraTxCert (PreviousEra era)) =>
TxCert (PreviousEra era)
-> Either (TxCertUpgradeError era) (TxCert era)
upgradeTxCert)
StrictSeq (TxCert MaryEra)
mtbCerts
StrictMaybe (Update AlonzoEra)
updates <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Update MaryEra
-> Either AlonzoTxBodyUpgradeError (Update AlonzoEra)
upgradeUpdate StrictMaybe (Update MaryEra)
mtbUpdate
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
AlonzoTxBody
{ atbInputs :: Set TxIn
atbInputs = Set TxIn
mtbInputs
, atbOutputs :: StrictSeq (TxOut AlonzoEra)
atbOutputs = forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
upgradeTxOut forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictSeq (TxOut MaryEra)
mtbOutputs
, atbCerts :: StrictSeq (TxCert AlonzoEra)
atbCerts = StrictSeq (TxCert AlonzoEra)
certs
, atbWithdrawals :: Withdrawals
atbWithdrawals = Withdrawals
mtbWithdrawals
, atbTxFee :: Coin
atbTxFee = Coin
mtbTxFee
, atbValidityInterval :: ValidityInterval
atbValidityInterval = ValidityInterval
mtbValidityInterval
, atbUpdate :: StrictMaybe (Update AlonzoEra)
atbUpdate = StrictMaybe (Update AlonzoEra)
updates
, atbAuxDataHash :: StrictMaybe TxAuxDataHash
atbAuxDataHash = StrictMaybe TxAuxDataHash
mtbAuxDataHash
, atbMint :: MultiAsset
atbMint = MultiAsset
mtbMint
, atbCollateral :: Set TxIn
atbCollateral = forall a. Monoid a => a
mempty
, atbReqSignerHashes :: Set (KeyHash 'Witness)
atbReqSignerHashes = forall a. Monoid a => a
mempty
, atbScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbScriptIntegrityHash = forall a. StrictMaybe a
SNothing
, atbTxNetworkId :: StrictMaybe Network
atbTxNetworkId = forall a. StrictMaybe a
SNothing
}
where
upgradeUpdate ::
Update MaryEra ->
Either AlonzoTxBodyUpgradeError (Update AlonzoEra)
upgradeUpdate :: Update MaryEra
-> Either AlonzoTxBodyUpgradeError (Update AlonzoEra)
upgradeUpdate (Update ProposedPPUpdates MaryEra
pp EpochNo
epoch) =
forall era. ProposedPPUpdates era -> EpochNo -> Update era
Update forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProposedPPUpdates MaryEra
-> Either AlonzoTxBodyUpgradeError (ProposedPPUpdates AlonzoEra)
upgradeProposedPPUpdates ProposedPPUpdates MaryEra
pp forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure EpochNo
epoch
upgradeProposedPPUpdates ::
ProposedPPUpdates MaryEra ->
Either AlonzoTxBodyUpgradeError (ProposedPPUpdates AlonzoEra)
upgradeProposedPPUpdates :: ProposedPPUpdates MaryEra
-> Either AlonzoTxBodyUpgradeError (ProposedPPUpdates AlonzoEra)
upgradeProposedPPUpdates (ProposedPPUpdates Map (KeyHash 'Genesis) (PParamsUpdate MaryEra)
m) =
forall era.
Map (KeyHash 'Genesis) (PParamsUpdate era) -> ProposedPPUpdates era
ProposedPPUpdates
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
( \PParamsUpdate MaryEra
ppu -> do
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall a. StrictMaybe a -> Bool
isSJust forall a b. (a -> b) -> a -> b
$ PParamsUpdate MaryEra
ppu forall s a. s -> Getting a s a -> a
^. forall era.
(EraPParams era, ProtVerAtMost era 4) =>
Lens' (PParamsUpdate era) (StrictMaybe Coin)
ppuMinUTxOValueL) forall a b. (a -> b) -> a -> b
$
forall a b. a -> Either a b
Left AlonzoTxBodyUpgradeError
ATBUEMinUTxOUpdated
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall era.
(EraPParams era, EraPParams (PreviousEra era)) =>
UpgradePParams StrictMaybe era
-> PParamsUpdate (PreviousEra era) -> PParamsUpdate era
upgradePParamsUpdate forall a. Default a => a
def PParamsUpdate MaryEra
ppu
)
Map (KeyHash 'Genesis) (PParamsUpdate MaryEra)
m
instance ShelleyEraTxBody AlonzoEra where
ttlTxBodyL :: ExactEra ShelleyEra AlonzoEra => Lens' (TxBody AlonzoEra) SlotNo
ttlTxBodyL = forall a b. HasCallStack => Lens' a b
notSupportedInThisEraL
updateTxBodyL :: Lens' (TxBody AlonzoEra) (StrictMaybe (Update AlonzoEra))
updateTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> StrictMaybe (Update era)
atbrUpdate (\RawType AlonzoTxBody AlonzoEra
txBodyRaw StrictMaybe (Update AlonzoEra)
update_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrUpdate :: StrictMaybe (Update AlonzoEra)
atbrUpdate = StrictMaybe (Update AlonzoEra)
update_})
{-# INLINEABLE updateTxBodyL #-}
instance AllegraEraTxBody AlonzoEra where
vldtTxBodyL :: Lens' (TxBody AlonzoEra) ValidityInterval
vldtTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> ValidityInterval
atbrValidityInterval (\RawType AlonzoTxBody AlonzoEra
txBodyRaw ValidityInterval
vldt_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrValidityInterval :: ValidityInterval
atbrValidityInterval = ValidityInterval
vldt_})
{-# INLINEABLE vldtTxBodyL #-}
instance MaryEraTxBody AlonzoEra where
mintTxBodyL :: Lens' (TxBody AlonzoEra) MultiAsset
mintTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> MultiAsset
atbrMint (\RawType AlonzoTxBody AlonzoEra
txBodyRaw MultiAsset
mint_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrMint :: MultiAsset
atbrMint = MultiAsset
mint_})
{-# INLINEABLE mintTxBodyL #-}
mintValueTxBodyF :: SimpleGetter (TxBody AlonzoEra) (Value AlonzoEra)
mintValueTxBodyF = forall era. MaryEraTxBody era => Lens' (TxBody era) MultiAsset
mintTxBodyL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. (s -> a) -> SimpleGetter s a
to (Coin -> MultiAsset -> MaryValue
MaryValue forall a. Monoid a => a
mempty)
{-# INLINEABLE mintValueTxBodyF #-}
mintedTxBodyF :: SimpleGetter (TxBody AlonzoEra) (Set PolicyID)
mintedTxBodyF = forall s a. (s -> a) -> SimpleGetter s a
to (MultiAsset -> Set PolicyID
policies forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. AlonzoTxBodyRaw era -> MultiAsset
atbrMint forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType)
{-# INLINEABLE mintedTxBodyF #-}
instance AlonzoEraTxBody AlonzoEra where
collateralInputsTxBodyL :: Lens' (TxBody AlonzoEra) (Set TxIn)
collateralInputsTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrCollateral (\RawType AlonzoTxBody AlonzoEra
txBodyRaw Set TxIn
collateral_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrCollateral :: Set TxIn
atbrCollateral = Set TxIn
collateral_})
{-# INLINEABLE collateralInputsTxBodyL #-}
reqSignerHashesTxBodyL :: Lens' (TxBody AlonzoEra) (Set (KeyHash 'Witness))
reqSignerHashesTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType
forall era. AlonzoTxBodyRaw era -> Set (KeyHash 'Witness)
atbrReqSignerHashes
(\RawType AlonzoTxBody AlonzoEra
txBodyRaw Set (KeyHash 'Witness)
reqSignerHashes_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrReqSignerHashes :: Set (KeyHash 'Witness)
atbrReqSignerHashes = Set (KeyHash 'Witness)
reqSignerHashes_})
{-# INLINEABLE reqSignerHashesTxBodyL #-}
scriptIntegrityHashTxBodyL :: Lens' (TxBody AlonzoEra) (StrictMaybe ScriptIntegrityHash)
scriptIntegrityHashTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType
forall era. AlonzoTxBodyRaw era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash
(\RawType AlonzoTxBody AlonzoEra
txBodyRaw StrictMaybe ScriptIntegrityHash
scriptIntegrityHash_ -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash = StrictMaybe ScriptIntegrityHash
scriptIntegrityHash_})
{-# INLINEABLE scriptIntegrityHashTxBodyL #-}
networkIdTxBodyL :: Lens' (TxBody AlonzoEra) (StrictMaybe Network)
networkIdTxBodyL =
forall era (t :: * -> *) a b.
(Era era, EncCBOR (RawType t era), Memoized t) =>
(RawType t era -> a)
-> (RawType t era -> b -> RawType t era)
-> Lens (t era) (t era) a b
lensMemoRawType forall era. AlonzoTxBodyRaw era -> StrictMaybe Network
atbrTxNetworkId (\RawType AlonzoTxBody AlonzoEra
txBodyRaw StrictMaybe Network
networkId -> RawType AlonzoTxBody AlonzoEra
txBodyRaw {atbrTxNetworkId :: StrictMaybe Network
atbrTxNetworkId = StrictMaybe Network
networkId})
{-# INLINEABLE networkIdTxBodyL #-}
redeemerPointer :: TxBody AlonzoEra
-> PlutusPurpose AsItem AlonzoEra
-> StrictMaybe (PlutusPurpose AsIx AlonzoEra)
redeemerPointer = forall era.
MaryEraTxBody era =>
TxBody era
-> AlonzoPlutusPurpose AsItem era
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
alonzoRedeemerPointer
redeemerPointerInverse :: TxBody AlonzoEra
-> PlutusPurpose AsIx AlonzoEra
-> StrictMaybe (PlutusPurpose AsIxItem AlonzoEra)
redeemerPointerInverse = forall era.
MaryEraTxBody era =>
TxBody era
-> AlonzoPlutusPurpose AsIx era
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
alonzoRedeemerPointerInverse
deriving newtype instance
(Era era, Eq (TxOut era), Eq (TxCert era), Eq (PParamsUpdate era)) =>
Eq (AlonzoTxBody era)
deriving instance
(Era era, NoThunks (TxOut era), NoThunks (TxCert era), NoThunks (PParamsUpdate era)) =>
NoThunks (AlonzoTxBody era)
deriving instance
(Era era, NFData (TxOut era), NFData (TxCert era), NFData (PParamsUpdate era)) =>
NFData (AlonzoTxBody era)
deriving instance
(Era era, Show (TxOut era), Show (TxCert era), Show (PParamsUpdate era)) =>
Show (AlonzoTxBody era)
deriving via
(Mem AlonzoTxBodyRaw era)
instance
(Era era, DecCBOR (TxOut era), DecCBOR (TxCert era), DecCBOR (PParamsUpdate era)) =>
DecCBOR (Annotator (AlonzoTxBody era))
pattern AlonzoTxBody ::
(EraTxOut era, EraTxCert era) =>
Set TxIn ->
Set TxIn ->
StrictSeq (TxOut era) ->
StrictSeq (TxCert era) ->
Withdrawals ->
Coin ->
ValidityInterval ->
StrictMaybe (Update era) ->
Set (KeyHash 'Witness) ->
MultiAsset ->
StrictMaybe ScriptIntegrityHash ->
StrictMaybe TxAuxDataHash ->
StrictMaybe Network ->
AlonzoTxBody era
pattern $bAlonzoTxBody :: forall era.
(EraTxOut era, EraTxCert era) =>
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBody era
$mAlonzoTxBody :: forall {r} {era}.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era
-> (Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> r)
-> ((# #) -> r)
-> r
AlonzoTxBody
{ forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> Set TxIn
atbInputs
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> Set TxIn
atbCollateral
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> StrictSeq (TxOut era)
atbOutputs
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> StrictSeq (TxCert era)
atbCerts
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> Withdrawals
atbWithdrawals
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> Coin
atbTxFee
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> ValidityInterval
atbValidityInterval
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> StrictMaybe (Update era)
atbUpdate
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> Set (KeyHash 'Witness)
atbReqSignerHashes
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> MultiAsset
atbMint
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> StrictMaybe ScriptIntegrityHash
atbScriptIntegrityHash
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> StrictMaybe TxAuxDataHash
atbAuxDataHash
, forall era.
(EraTxOut era, EraTxCert era) =>
AlonzoTxBody era -> StrictMaybe Network
atbTxNetworkId
} <-
( getMemoRawType ->
AlonzoTxBodyRaw
{ atbrInputs = atbInputs
, atbrCollateral = atbCollateral
, atbrOutputs = atbOutputs
, atbrCerts = atbCerts
, atbrWithdrawals = atbWithdrawals
, atbrTxFee = atbTxFee
, atbrValidityInterval = atbValidityInterval
, atbrUpdate = atbUpdate
, atbrReqSignerHashes = atbReqSignerHashes
, atbrMint = atbMint
, atbrScriptIntegrityHash = atbScriptIntegrityHash
, atbrAuxDataHash = atbAuxDataHash
, atbrTxNetworkId = atbTxNetworkId
}
)
where
AlonzoTxBody
Set TxIn
inputs
Set TxIn
collateral
StrictSeq (TxOut era)
outputs
StrictSeq (TxCert era)
certs
Withdrawals
withdrawals
Coin
txFee
ValidityInterval
validityInterval
StrictMaybe (Update era)
update
Set (KeyHash 'Witness)
reqSignerHashes
MultiAsset
mint
StrictMaybe ScriptIntegrityHash
scriptIntegrityHash
StrictMaybe TxAuxDataHash
auxDataHash
StrictMaybe Network
txNetworkId =
forall era (t :: * -> *).
(Era era, EncCBOR (RawType t era), Memoized t) =>
RawType t era -> t era
mkMemoized forall a b. (a -> b) -> a -> b
$
AlonzoTxBodyRaw
{ atbrInputs :: Set TxIn
atbrInputs = Set TxIn
inputs
, atbrCollateral :: Set TxIn
atbrCollateral = Set TxIn
collateral
, atbrOutputs :: StrictSeq (TxOut era)
atbrOutputs = StrictSeq (TxOut era)
outputs
, atbrCerts :: StrictSeq (TxCert era)
atbrCerts = StrictSeq (TxCert era)
certs
, atbrWithdrawals :: Withdrawals
atbrWithdrawals = Withdrawals
withdrawals
, atbrTxFee :: Coin
atbrTxFee = Coin
txFee
, atbrValidityInterval :: ValidityInterval
atbrValidityInterval = ValidityInterval
validityInterval
, atbrUpdate :: StrictMaybe (Update era)
atbrUpdate = StrictMaybe (Update era)
update
, atbrReqSignerHashes :: Set (KeyHash 'Witness)
atbrReqSignerHashes = Set (KeyHash 'Witness)
reqSignerHashes
, atbrMint :: MultiAsset
atbrMint = MultiAsset
mint
, atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash = StrictMaybe ScriptIntegrityHash
scriptIntegrityHash
, atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrAuxDataHash = StrictMaybe TxAuxDataHash
auxDataHash
, atbrTxNetworkId :: StrictMaybe Network
atbrTxNetworkId = StrictMaybe Network
txNetworkId
}
{-# COMPLETE AlonzoTxBody #-}
type instance MemoHashIndex AlonzoTxBodyRaw = EraIndependentTxBody
instance HashAnnotated (AlonzoTxBody era) EraIndependentTxBody where
hashAnnotated :: AlonzoTxBody era -> SafeHash EraIndependentTxBody
hashAnnotated = forall (t :: * -> *) era.
Memoized t =>
t era -> SafeHash (MemoHashIndex (RawType t))
getMemoSafeHash
inputs' :: AlonzoTxBody era -> Set TxIn
collateral' :: AlonzoTxBody era -> Set TxIn
outputs' :: AlonzoTxBody era -> StrictSeq (TxOut era)
certs' :: AlonzoTxBody era -> StrictSeq (TxCert era)
txfee' :: AlonzoTxBody era -> Coin
withdrawals' :: AlonzoTxBody era -> Withdrawals
vldt' :: AlonzoTxBody era -> ValidityInterval
update' :: AlonzoTxBody era -> StrictMaybe (Update era)
reqSignerHashes' :: AlonzoTxBody era -> Set (KeyHash 'Witness)
adHash' :: AlonzoTxBody era -> StrictMaybe TxAuxDataHash
mint' :: AlonzoTxBody era -> MultiAsset
scriptIntegrityHash' :: AlonzoTxBody era -> StrictMaybe ScriptIntegrityHash
txnetworkid' :: AlonzoTxBody era -> StrictMaybe Network
inputs' :: forall era. AlonzoTxBody era -> Set TxIn
inputs' = forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrInputs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
collateral' :: forall era. AlonzoTxBody era -> Set TxIn
collateral' = forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrCollateral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
outputs' :: forall era. AlonzoTxBody era -> StrictSeq (TxOut era)
outputs' = forall era. AlonzoTxBodyRaw era -> StrictSeq (TxOut era)
atbrOutputs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
certs' :: forall era. AlonzoTxBody era -> StrictSeq (TxCert era)
certs' = forall era. AlonzoTxBodyRaw era -> StrictSeq (TxCert era)
atbrCerts forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
withdrawals' :: forall era. AlonzoTxBody era -> Withdrawals
withdrawals' = forall era. AlonzoTxBodyRaw era -> Withdrawals
atbrWithdrawals forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
txfee' :: forall era. AlonzoTxBody era -> Coin
txfee' = forall era. AlonzoTxBodyRaw era -> Coin
atbrTxFee forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
vldt' :: forall era. AlonzoTxBody era -> ValidityInterval
vldt' = forall era. AlonzoTxBodyRaw era -> ValidityInterval
atbrValidityInterval forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
update' :: forall era. AlonzoTxBody era -> StrictMaybe (Update era)
update' = forall era. AlonzoTxBodyRaw era -> StrictMaybe (Update era)
atbrUpdate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
reqSignerHashes' :: forall era. AlonzoTxBody era -> Set (KeyHash 'Witness)
reqSignerHashes' = forall era. AlonzoTxBodyRaw era -> Set (KeyHash 'Witness)
atbrReqSignerHashes forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
adHash' :: forall era. AlonzoTxBody era -> StrictMaybe TxAuxDataHash
adHash' = forall era. AlonzoTxBodyRaw era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
mint' :: forall era. AlonzoTxBody era -> MultiAsset
mint' = forall era. AlonzoTxBodyRaw era -> MultiAsset
atbrMint forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
scriptIntegrityHash' :: forall era. AlonzoTxBody era -> StrictMaybe ScriptIntegrityHash
scriptIntegrityHash' = forall era. AlonzoTxBodyRaw era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
txnetworkid' :: forall era. AlonzoTxBody era -> StrictMaybe Network
txnetworkid' = forall era. AlonzoTxBodyRaw era -> StrictMaybe Network
atbrTxNetworkId forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) era. Memoized t => t era -> RawType t era
getMemoRawType
instance
(Era era, Eq (PParamsUpdate era), Eq (TxOut era), Eq (TxCert era)) =>
EqRaw (AlonzoTxBody era)
instance Era era => EncCBOR (AlonzoTxBody era)
instance
(Era era, EncCBOR (TxOut era), EncCBOR (TxCert era), EncCBOR (PParamsUpdate era)) =>
EncCBOR (AlonzoTxBodyRaw era)
where
encCBOR :: AlonzoTxBodyRaw era -> Encoding
encCBOR
AlonzoTxBodyRaw
{ Set TxIn
atbrInputs :: Set TxIn
atbrInputs :: forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrInputs
, Set TxIn
atbrCollateral :: Set TxIn
atbrCollateral :: forall era. AlonzoTxBodyRaw era -> Set TxIn
atbrCollateral
, StrictSeq (TxOut era)
atbrOutputs :: StrictSeq (TxOut era)
atbrOutputs :: forall era. AlonzoTxBodyRaw era -> StrictSeq (TxOut era)
atbrOutputs
, StrictSeq (TxCert era)
atbrCerts :: StrictSeq (TxCert era)
atbrCerts :: forall era. AlonzoTxBodyRaw era -> StrictSeq (TxCert era)
atbrCerts
, Withdrawals
atbrWithdrawals :: Withdrawals
atbrWithdrawals :: forall era. AlonzoTxBodyRaw era -> Withdrawals
atbrWithdrawals
, Coin
atbrTxFee :: Coin
atbrTxFee :: forall era. AlonzoTxBodyRaw era -> Coin
atbrTxFee
, atbrValidityInterval :: forall era. AlonzoTxBodyRaw era -> ValidityInterval
atbrValidityInterval = ValidityInterval StrictMaybe SlotNo
bot StrictMaybe SlotNo
top
, StrictMaybe (Update era)
atbrUpdate :: StrictMaybe (Update era)
atbrUpdate :: forall era. AlonzoTxBodyRaw era -> StrictMaybe (Update era)
atbrUpdate
, Set (KeyHash 'Witness)
atbrReqSignerHashes :: Set (KeyHash 'Witness)
atbrReqSignerHashes :: forall era. AlonzoTxBodyRaw era -> Set (KeyHash 'Witness)
atbrReqSignerHashes
, MultiAsset
atbrMint :: MultiAsset
atbrMint :: forall era. AlonzoTxBodyRaw era -> MultiAsset
atbrMint
, StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: forall era. AlonzoTxBodyRaw era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash
, StrictMaybe TxAuxDataHash
atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrAuxDataHash :: forall era. AlonzoTxBodyRaw era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash
, StrictMaybe Network
atbrTxNetworkId :: StrictMaybe Network
atbrTxNetworkId :: forall era. AlonzoTxBodyRaw era -> StrictMaybe Network
atbrTxNetworkId
} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Sparse) t
Keyed
( \Set TxIn
i Set TxIn
ifee StrictSeq (TxOut era)
o Coin
f StrictMaybe SlotNo
t StrictSeq (TxCert era)
c Withdrawals
w StrictMaybe (Update era)
u StrictMaybe SlotNo
b Set (KeyHash 'Witness)
rsh MultiAsset
mi StrictMaybe ScriptIntegrityHash
sh StrictMaybe TxAuxDataHash
ah StrictMaybe Network
ni ->
forall era.
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw era
AlonzoTxBodyRaw Set TxIn
i Set TxIn
ifee StrictSeq (TxOut era)
o StrictSeq (TxCert era)
c Withdrawals
w Coin
f (StrictMaybe SlotNo -> StrictMaybe SlotNo -> ValidityInterval
ValidityInterval StrictMaybe SlotNo
b StrictMaybe SlotNo
t) StrictMaybe (Update era)
u Set (KeyHash 'Witness)
rsh MultiAsset
mi StrictMaybe ScriptIntegrityHash
sh StrictMaybe TxAuxDataHash
ah StrictMaybe Network
ni
)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
0 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set TxIn
atbrInputs)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
(t -> Bool)
-> Encode ('Closed 'Sparse) t -> Encode ('Closed 'Sparse) t
Omit forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
13 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set TxIn
atbrCollateral))
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
1 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To StrictSeq (TxOut era)
atbrOutputs)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
2 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
atbrTxFee)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode ('Closed 'Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
3 StrictMaybe SlotNo
top
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
(t -> Bool)
-> Encode ('Closed 'Sparse) t -> Encode ('Closed 'Sparse) t
Omit forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
4 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To StrictSeq (TxCert era)
atbrCerts))
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
(t -> Bool)
-> Encode ('Closed 'Sparse) t -> Encode ('Closed 'Sparse) t
Omit (forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. Withdrawals -> Map RewardAccount Coin
unWithdrawals) (forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
5 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Withdrawals
atbrWithdrawals))
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode ('Closed 'Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
6 StrictMaybe (Update era)
atbrUpdate
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode ('Closed 'Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
8 StrictMaybe SlotNo
bot
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
(t -> Bool)
-> Encode ('Closed 'Sparse) t -> Encode ('Closed 'Sparse) t
Omit forall (t :: * -> *) a. Foldable t => t a -> Bool
null (forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
14 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set (KeyHash 'Witness)
atbrReqSignerHashes))
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t.
(t -> Bool)
-> Encode ('Closed 'Sparse) t -> Encode ('Closed 'Sparse) t
Omit (forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty) (forall t.
Word -> Encode ('Closed 'Dense) t -> Encode ('Closed 'Sparse) t
Key Word
9 (forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To MultiAsset
atbrMint))
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode ('Closed 'Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
11 StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode ('Closed 'Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
7 StrictMaybe TxAuxDataHash
atbrAuxDataHash
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode ('Closed 'Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
15 StrictMaybe Network
atbrTxNetworkId
instance
(Era era, DecCBOR (TxOut era), DecCBOR (TxCert era), DecCBOR (PParamsUpdate era)) =>
DecCBOR (AlonzoTxBodyRaw era)
where
decCBOR :: forall s. Decoder s (AlonzoTxBodyRaw era)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t.
Typeable t =>
String
-> t
-> (Word -> Field t)
-> [(Word, String)]
-> Decode ('Closed 'Dense) t
SparseKeyed
String
"AlonzoTxBodyRaw"
forall era. AlonzoTxBodyRaw era
emptyAlonzoTxBodyRaw
Word -> Field (AlonzoTxBodyRaw era)
bodyFields
[(Word, String)]
requiredFields
where
bodyFields :: Word -> Field (AlonzoTxBodyRaw era)
bodyFields :: Word -> Field (AlonzoTxBodyRaw era)
bodyFields Word
0 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Set TxIn
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrInputs :: Set TxIn
atbrInputs = Set TxIn
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
13 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Set TxIn
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrCollateral :: Set TxIn
atbrCollateral = Set TxIn
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
1 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\StrictSeq (TxOut era)
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrOutputs :: StrictSeq (TxOut era)
atbrOutputs = StrictSeq (TxOut era)
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
2 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Coin
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrTxFee :: Coin
atbrTxFee = Coin
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
3 =
forall x t (d :: Density).
(StrictMaybe x -> t -> t) -> Decode ('Closed d) x -> Field t
ofield
(\StrictMaybe SlotNo
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrValidityInterval :: ValidityInterval
atbrValidityInterval = (forall era. AlonzoTxBodyRaw era -> ValidityInterval
atbrValidityInterval AlonzoTxBodyRaw era
tx) {invalidHereafter :: StrictMaybe SlotNo
invalidHereafter = StrictMaybe SlotNo
x}})
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
4 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\StrictSeq (TxCert era)
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrCerts :: StrictSeq (TxCert era)
atbrCerts = StrictSeq (TxCert era)
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
5 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Withdrawals
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrWithdrawals :: Withdrawals
atbrWithdrawals = Withdrawals
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
6 = forall x t (d :: Density).
(StrictMaybe x -> t -> t) -> Decode ('Closed d) x -> Field t
ofield (\StrictMaybe (Update era)
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrUpdate :: StrictMaybe (Update era)
atbrUpdate = StrictMaybe (Update era)
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
7 = forall x t (d :: Density).
(StrictMaybe x -> t -> t) -> Decode ('Closed d) x -> Field t
ofield (\StrictMaybe TxAuxDataHash
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrAuxDataHash = StrictMaybe TxAuxDataHash
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
8 =
forall x t (d :: Density).
(StrictMaybe x -> t -> t) -> Decode ('Closed d) x -> Field t
ofield
(\StrictMaybe SlotNo
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrValidityInterval :: ValidityInterval
atbrValidityInterval = (forall era. AlonzoTxBodyRaw era -> ValidityInterval
atbrValidityInterval AlonzoTxBodyRaw era
tx) {invalidBefore :: StrictMaybe SlotNo
invalidBefore = StrictMaybe SlotNo
x}})
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
9 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\MultiAsset
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrMint :: MultiAsset
atbrMint = MultiAsset
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
11 = forall x t (d :: Density).
(StrictMaybe x -> t -> t) -> Decode ('Closed d) x -> Field t
ofield (\StrictMaybe ScriptIntegrityHash
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash = StrictMaybe ScriptIntegrityHash
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
14 = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Set (KeyHash 'Witness)
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrReqSignerHashes :: Set (KeyHash 'Witness)
atbrReqSignerHashes = Set (KeyHash 'Witness)
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
15 = forall x t (d :: Density).
(StrictMaybe x -> t -> t) -> Decode ('Closed d) x -> Field t
ofield (\StrictMaybe Network
x AlonzoTxBodyRaw era
tx -> AlonzoTxBodyRaw era
tx {atbrTxNetworkId :: StrictMaybe Network
atbrTxNetworkId = StrictMaybe Network
x}) forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
n = forall x t (d :: Density).
(x -> t -> t) -> Decode ('Closed d) x -> Field t
field (\Any
_ AlonzoTxBodyRaw era
t -> AlonzoTxBodyRaw era
t) (forall (w :: Wrapped) t. Word -> Decode w t
Invalid Word
n)
requiredFields :: [(Word, String)]
requiredFields =
[ (Word
0, String
"inputs")
, (Word
1, String
"outputs")
, (Word
2, String
"fee")
]
emptyAlonzoTxBodyRaw :: AlonzoTxBodyRaw era
emptyAlonzoTxBodyRaw :: forall era. AlonzoTxBodyRaw era
emptyAlonzoTxBodyRaw =
forall era.
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw era
AlonzoTxBodyRaw
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
forall a. StrictSeq a
StrictSeq.empty
forall a. StrictSeq a
StrictSeq.empty
(Map RewardAccount Coin -> Withdrawals
Withdrawals forall a. Monoid a => a
mempty)
forall a. Monoid a => a
mempty
(StrictMaybe SlotNo -> StrictMaybe SlotNo -> ValidityInterval
ValidityInterval forall a. StrictMaybe a
SNothing forall a. StrictMaybe a
SNothing)
forall a. StrictMaybe a
SNothing
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
forall a. StrictMaybe a
SNothing
forall a. StrictMaybe a
SNothing
forall a. StrictMaybe a
SNothing
instance
(Era era, DecCBOR (TxOut era), DecCBOR (TxCert era), DecCBOR (PParamsUpdate era)) =>
DecCBOR (Annotator (AlonzoTxBodyRaw era))
where
decCBOR :: forall s. Decoder s (Annotator (AlonzoTxBodyRaw era))
decCBOR = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
alonzoRedeemerPointer ::
forall era.
MaryEraTxBody era =>
TxBody era ->
AlonzoPlutusPurpose AsItem era ->
StrictMaybe (AlonzoPlutusPurpose AsIx era)
alonzoRedeemerPointer :: forall era.
MaryEraTxBody era =>
TxBody era
-> AlonzoPlutusPurpose AsItem era
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
alonzoRedeemerPointer TxBody era
txBody = \case
AlonzoSpending AsItem Word32 TxIn
txIn ->
forall (f :: * -> * -> *) era.
f Word32 TxIn -> AlonzoPlutusPurpose f era
AlonzoSpending forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 TxIn
txIn (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era. EraTxBody era => Lens' (TxBody era) (Set TxIn)
inputsTxBodyL)
AlonzoMinting AsItem Word32 PolicyID
policyID ->
forall (f :: * -> * -> *) era.
f Word32 PolicyID -> AlonzoPlutusPurpose f era
AlonzoMinting forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 PolicyID
policyID (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era.
MaryEraTxBody era =>
SimpleGetter (TxBody era) (Set PolicyID)
mintedTxBodyF :: Set PolicyID)
AlonzoCertifying AsItem Word32 (TxCert era)
txCert ->
forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> AlonzoPlutusPurpose f era
AlonzoCertifying forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 (TxCert era)
txCert (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era.
EraTxBody era =>
Lens' (TxBody era) (StrictSeq (TxCert era))
certsTxBodyL)
AlonzoRewarding AsItem Word32 RewardAccount
rewardAccount ->
forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> AlonzoPlutusPurpose f era
AlonzoRewarding forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 RewardAccount
rewardAccount (Withdrawals -> Map RewardAccount Coin
unWithdrawals (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era. EraTxBody era => Lens' (TxBody era) Withdrawals
withdrawalsTxBodyL))
alonzoRedeemerPointerInverse ::
MaryEraTxBody era =>
TxBody era ->
AlonzoPlutusPurpose AsIx era ->
StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
alonzoRedeemerPointerInverse :: forall era.
MaryEraTxBody era =>
TxBody era
-> AlonzoPlutusPurpose AsIx era
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
alonzoRedeemerPointerInverse TxBody era
txBody = \case
AlonzoSpending AsIx Word32 TxIn
idx ->
forall (f :: * -> * -> *) era.
f Word32 TxIn -> AlonzoPlutusPurpose f era
AlonzoSpending forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 TxIn
idx (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era. EraTxBody era => Lens' (TxBody era) (Set TxIn)
inputsTxBodyL)
AlonzoMinting AsIx Word32 PolicyID
idx ->
forall (f :: * -> * -> *) era.
f Word32 PolicyID -> AlonzoPlutusPurpose f era
AlonzoMinting forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 PolicyID
idx (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era.
MaryEraTxBody era =>
SimpleGetter (TxBody era) (Set PolicyID)
mintedTxBodyF)
AlonzoCertifying AsIx Word32 (TxCert era)
idx ->
forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> AlonzoPlutusPurpose f era
AlonzoCertifying forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 (TxCert era)
idx (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era.
EraTxBody era =>
Lens' (TxBody era) (StrictSeq (TxCert era))
certsTxBodyL)
AlonzoRewarding AsIx Word32 RewardAccount
idx ->
forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> AlonzoPlutusPurpose f era
AlonzoRewarding forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 RewardAccount
idx (Withdrawals -> Map RewardAccount Coin
unWithdrawals (TxBody era
txBody forall s a. s -> Getting a s a -> a
^. forall era. EraTxBody era => Lens' (TxBody era) Withdrawals
withdrawalsTxBodyL))
class Indexable elem container where
indexOf :: AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
fromIndex :: AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
instance Ord k => Indexable k (Set k) where
indexOf :: AsItem Word32 k -> Set k -> StrictMaybe (AsIx Word32 k)
indexOf (AsItem k
n) Set k
s = case forall a. Ord a => a -> Set a -> Maybe Int
Set.lookupIndex k
n Set k
s of
Just Int
x -> forall a. a -> StrictMaybe a
SJust (forall ix it. ix -> AsIx ix it
AsIx (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Word32 Int
x))
Maybe Int
Nothing -> forall a. StrictMaybe a
SNothing
fromIndex :: AsIx Word32 k -> Set k -> StrictMaybe (AsIxItem Word32 k)
fromIndex (AsIx Word32
w32) Set k
s =
let i :: Int
i = forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word32 @Int Word32
w32
in if Int
i forall a. Ord a => a -> a -> Bool
< forall a. Set a -> Int
Set.size Set k
s
then forall a. a -> StrictMaybe a
SJust forall a b. (a -> b) -> a -> b
$ forall ix it. ix -> it -> AsIxItem ix it
AsIxItem Word32
w32 (forall a. Int -> Set a -> a
Set.elemAt Int
i Set k
s)
else forall a. StrictMaybe a
SNothing
instance Eq k => Indexable k (StrictSeq k) where
indexOf :: AsItem Word32 k -> StrictSeq k -> StrictMaybe (AsIx Word32 k)
indexOf (AsItem k
n) StrictSeq k
seqx = case forall a. (a -> Bool) -> StrictSeq a -> Maybe Int
StrictSeq.findIndexL (forall a. Eq a => a -> a -> Bool
== k
n) StrictSeq k
seqx of
Just Int
m -> forall a. a -> StrictMaybe a
SJust (forall ix it. ix -> AsIx ix it
AsIx (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Word32 Int
m))
Maybe Int
Nothing -> forall a. StrictMaybe a
SNothing
fromIndex :: AsIx Word32 k -> StrictSeq k -> StrictMaybe (AsIxItem Word32 k)
fromIndex (AsIx Word32
w32) StrictSeq k
seqx =
case forall a. Int -> StrictSeq a -> Maybe a
StrictSeq.lookup (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word32 @Int Word32
w32) StrictSeq k
seqx of
Maybe k
Nothing -> forall a. StrictMaybe a
SNothing
Just k
x -> forall a. a -> StrictMaybe a
SJust forall a b. (a -> b) -> a -> b
$ forall ix it. ix -> it -> AsIxItem ix it
AsIxItem Word32
w32 k
x
instance Ord k => Indexable k (Map.Map k v) where
indexOf :: AsItem Word32 k -> Map k v -> StrictMaybe (AsIx Word32 k)
indexOf (AsItem k
n) Map k v
mp = case forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex k
n Map k v
mp of
Just Int
x -> forall a. a -> StrictMaybe a
SJust (forall ix it. ix -> AsIx ix it
AsIx (forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Word32 Int
x))
Maybe Int
Nothing -> forall a. StrictMaybe a
SNothing
fromIndex :: AsIx Word32 k -> Map k v -> StrictMaybe (AsIxItem Word32 k)
fromIndex (AsIx Word32
w32) Map k v
mp =
let i :: Int
i = forall a b. (Integral a, Num b) => a -> b
fromIntegral @Word32 @Int Word32
w32
in if Int
i forall a. Ord a => a -> a -> Bool
< forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall k a. Map k a -> Int
Map.size Map k v
mp)
then forall a. a -> StrictMaybe a
SJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ix it. ix -> it -> AsIxItem ix it
AsIxItem Word32
w32 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ forall k a. Int -> Map k a -> (k, a)
Map.elemAt Int
i Map k v
mp
else forall a. StrictMaybe a
SNothing
instance Ord k => Indexable k (OSet k) where
indexOf :: AsItem Word32 k -> OSet k -> StrictMaybe (AsIx Word32 k)
indexOf AsItem Word32 k
asItem = forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 k
asItem forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. OSet a -> StrictSeq a
OSet.toStrictSeq
fromIndex :: AsIx Word32 k -> OSet k -> StrictMaybe (AsIxItem Word32 k)
fromIndex AsIx Word32 k
asIndex = forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 k
asIndex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. OSet a -> StrictSeq a
OSet.toStrictSeq