{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# 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 RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Cardano.Ledger.Alonzo.TxBody (
AlonzoTxOut (..),
AlonzoEraTxOut (..),
Addr28Extra,
DataHash32,
TxBody (
MkAlonzoTxBody,
AlonzoTxBody,
atbInputs,
atbCollateral,
atbOutputs,
atbCerts,
atbWithdrawals,
atbTxFee,
atbValidityInterval,
atbUpdate,
atbReqSignerHashes,
atbMint,
atbScriptIntegrityHash,
atbAuxDataHash,
atbTxNetworkId
),
AlonzoTxBodyRaw (..),
AlonzoEraTxBody (..),
ShelleyEraTxBody (..),
AllegraEraTxBody (..),
MaryEraTxBody (..),
Indexable (..),
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.Core
import Cardano.Ledger.Mary.Value (MultiAsset (..), PolicyID (..))
import Cardano.Ledger.MemoBytes (
EqRaw,
Mem,
MemoBytes,
MemoHashIndex,
Memoized (..),
getMemoRawType,
getMemoSafeHash,
lensMemoRawType,
mkMemoizedEra,
)
import Cardano.Ledger.Shelley.PParams (Update (..))
import Cardano.Ledger.Shelley.TxBody (getShelleyGenesisKeyHashCountTxBody)
import Cardano.Ledger.TxIn (TxIn (..))
import Control.DeepSeq (NFData (..), deepseq)
import qualified Data.Map.Strict as Map
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.Word (Word32)
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (InspectHeap (..), NoThunks (..))
type ScriptIntegrityHash = SafeHash EraIndependentScriptIntegrity
class (MaryEraTxBody era, AlonzoEraTxOut era) => AlonzoEraTxBody era where
collateralInputsTxBodyL :: Lens' (TxBody TopTx era) (Set TxIn)
reqSignerHashesTxBodyL :: AtMostEra "Conway" era => Lens' (TxBody l era) (Set (KeyHash Guard))
reqSignerHashesTxBodyG ::
SimpleGetter (TxBody l era) (Set (KeyHash Guard))
default reqSignerHashesTxBodyG ::
AtMostEra "Conway" era => SimpleGetter (TxBody l era) (Set (KeyHash Guard))
reqSignerHashesTxBodyG = (Set (KeyHash Guard) -> Const r (Set (KeyHash Guard)))
-> TxBody l era -> Const r (TxBody l era)
forall era (l :: TxLevel).
(AlonzoEraTxBody era, AtMostEra "Conway" era) =>
Lens' (TxBody l era) (Set (KeyHash Guard))
forall (l :: TxLevel).
AtMostEra "Conway" era =>
Lens' (TxBody l era) (Set (KeyHash Guard))
Lens' (TxBody l era) (Set (KeyHash Guard))
reqSignerHashesTxBodyL
scriptIntegrityHashTxBodyL ::
Lens' (TxBody l era) (StrictMaybe ScriptIntegrityHash)
networkIdTxBodyL :: Lens' (TxBody l era) (StrictMaybe Network)
redeemerPointer ::
TxBody l era ->
PlutusPurpose AsItem era ->
StrictMaybe (PlutusPurpose AsIx era)
redeemerPointerInverse ::
TxBody l era ->
PlutusPurpose AsIx era ->
StrictMaybe (PlutusPurpose AsIxItem era)
data AlonzoTxBodyRaw l era where
AlonzoTxBodyRaw ::
{ forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrInputs :: !(Set TxIn)
, forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrCollateral :: !(Set TxIn)
, forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxOut era)
atbrOutputs :: !(StrictSeq (TxOut era))
, forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxCert era)
atbrCerts :: !(StrictSeq (TxCert era))
, forall era. AlonzoTxBodyRaw TopTx era -> Withdrawals
atbrWithdrawals :: !Withdrawals
, forall era. AlonzoTxBodyRaw TopTx era -> Coin
atbrTxFee :: !Coin
, forall era. AlonzoTxBodyRaw TopTx era -> ValidityInterval
atbrValidityInterval :: !ValidityInterval
, forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe (Update era)
atbrUpdate :: !(StrictMaybe (Update era))
, forall era. AlonzoTxBodyRaw TopTx era -> Set (KeyHash Guard)
atbrReqSignerHashes :: Set (KeyHash Guard)
, forall era. AlonzoTxBodyRaw TopTx era -> MultiAsset
atbrMint :: !MultiAsset
, forall era.
AlonzoTxBodyRaw TopTx era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: !(StrictMaybe ScriptIntegrityHash)
, forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash :: !(StrictMaybe TxAuxDataHash)
, forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe Network
atbrTxNetworkId :: !(StrictMaybe Network)
} ->
AlonzoTxBodyRaw TopTx era
deriving instance Eq (AlonzoTxBodyRaw l AlonzoEra)
deriving via
InspectHeap (AlonzoTxBodyRaw l AlonzoEra)
instance
Typeable l => NoThunks (AlonzoTxBodyRaw l AlonzoEra)
instance
( NFData (TxOut era)
, NFData (TxCert era)
, NFData (PParamsHKD StrictMaybe era)
) =>
NFData (AlonzoTxBodyRaw l era)
where
rnf :: AlonzoTxBodyRaw l era -> ()
rnf AlonzoTxBodyRaw {Set (KeyHash Guard)
Set TxIn
StrictMaybe ScriptIntegrityHash
StrictMaybe TxAuxDataHash
StrictMaybe Network
StrictMaybe (Update era)
ValidityInterval
Withdrawals
Coin
MultiAsset
StrictSeq (TxOut era)
StrictSeq (TxCert era)
atbrInputs :: forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrCollateral :: forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrOutputs :: forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxOut era)
atbrCerts :: forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxCert era)
atbrWithdrawals :: forall era. AlonzoTxBodyRaw TopTx era -> Withdrawals
atbrTxFee :: forall era. AlonzoTxBodyRaw TopTx era -> Coin
atbrValidityInterval :: forall era. AlonzoTxBodyRaw TopTx era -> ValidityInterval
atbrUpdate :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe (Update era)
atbrReqSignerHashes :: forall era. AlonzoTxBodyRaw TopTx era -> Set (KeyHash Guard)
atbrMint :: forall era. AlonzoTxBodyRaw TopTx era -> MultiAsset
atbrScriptIntegrityHash :: forall era.
AlonzoTxBodyRaw TopTx era -> StrictMaybe ScriptIntegrityHash
atbrAuxDataHash :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe TxAuxDataHash
atbrTxNetworkId :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe Network
atbrInputs :: Set TxIn
atbrCollateral :: Set TxIn
atbrOutputs :: StrictSeq (TxOut era)
atbrCerts :: StrictSeq (TxCert era)
atbrWithdrawals :: Withdrawals
atbrTxFee :: Coin
atbrValidityInterval :: ValidityInterval
atbrUpdate :: StrictMaybe (Update era)
atbrReqSignerHashes :: Set (KeyHash Guard)
atbrMint :: MultiAsset
atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrTxNetworkId :: StrictMaybe Network
..} =
Set TxIn
atbrInputs Set TxIn -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
Set TxIn
atbrCollateral Set TxIn -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
StrictSeq (TxOut era)
atbrOutputs StrictSeq (TxOut era) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
StrictSeq (TxCert era)
atbrCerts StrictSeq (TxCert era) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
Withdrawals
atbrWithdrawals Withdrawals -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
Coin
atbrTxFee Coin -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
ValidityInterval
atbrValidityInterval ValidityInterval -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
StrictMaybe (Update era)
atbrUpdate StrictMaybe (Update era) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
Set (KeyHash Guard)
atbrReqSignerHashes Set (KeyHash Guard) -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
MultiAsset
atbrMint MultiAsset -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash StrictMaybe ScriptIntegrityHash -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
StrictMaybe TxAuxDataHash
atbrAuxDataHash StrictMaybe TxAuxDataHash -> () -> ()
forall a b. NFData a => a -> b -> b
`deepseq`
StrictMaybe Network -> ()
forall a. NFData a => a -> ()
rnf StrictMaybe Network
atbrTxNetworkId
deriving instance Show (AlonzoTxBodyRaw l AlonzoEra)
instance Memoized (TxBody l AlonzoEra) where
type RawType (TxBody l AlonzoEra) = AlonzoTxBodyRaw l AlonzoEra
instance HasEraTxLevel AlonzoTxBodyRaw AlonzoEra where
toSTxLevel :: forall (l :: TxLevel).
AlonzoTxBodyRaw l AlonzoEra -> STxLevel l AlonzoEra
toSTxLevel AlonzoTxBodyRaw {} = STxLevel l AlonzoEra
STxTopLevel TopTx AlonzoEra
forall era. STxTopLevel TopTx era
STopTxOnly
instance HasEraTxLevel TxBody AlonzoEra where
toSTxLevel :: forall (l :: TxLevel). TxBody l AlonzoEra -> STxLevel l AlonzoEra
toSTxLevel = AlonzoTxBodyRaw l AlonzoEra -> STxLevel l AlonzoEra
AlonzoTxBodyRaw l AlonzoEra -> STxTopLevel l AlonzoEra
forall (l :: TxLevel).
AlonzoTxBodyRaw l AlonzoEra -> STxLevel l AlonzoEra
forall (t :: TxLevel -> * -> *) era (l :: TxLevel).
HasEraTxLevel t era =>
t l era -> STxLevel l era
toSTxLevel (AlonzoTxBodyRaw l AlonzoEra -> STxTopLevel l AlonzoEra)
-> (TxBody l AlonzoEra -> AlonzoTxBodyRaw l AlonzoEra)
-> TxBody l AlonzoEra
-> STxTopLevel l AlonzoEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxBody l AlonzoEra -> RawType (TxBody l AlonzoEra)
TxBody l AlonzoEra -> AlonzoTxBodyRaw l AlonzoEra
forall t. Memoized t => t -> RawType t
getMemoRawType
instance EraTxBody AlonzoEra where
newtype TxBody l AlonzoEra = MkAlonzoTxBody (MemoBytes (AlonzoTxBodyRaw l AlonzoEra))
deriving (Typeable (TxBody l AlonzoEra)
Typeable (TxBody l AlonzoEra) =>
(TxBody l AlonzoEra -> Encoding)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (TxBody l AlonzoEra) -> Size)
-> ((forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [TxBody l AlonzoEra] -> Size)
-> ToCBOR (TxBody l AlonzoEra)
TxBody l AlonzoEra -> Encoding
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [TxBody l AlonzoEra] -> Size
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (TxBody l AlonzoEra) -> Size
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 (l :: TxLevel). Typeable l => Typeable (TxBody l AlonzoEra)
forall (l :: TxLevel). Typeable l => TxBody l AlonzoEra -> Encoding
forall (l :: TxLevel).
Typeable l =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [TxBody l AlonzoEra] -> Size
forall (l :: TxLevel).
Typeable l =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (TxBody l AlonzoEra) -> Size
$ctoCBOR :: forall (l :: TxLevel). Typeable l => TxBody l AlonzoEra -> Encoding
toCBOR :: TxBody l AlonzoEra -> Encoding
$cencodedSizeExpr :: forall (l :: TxLevel).
Typeable l =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (TxBody l AlonzoEra) -> Size
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (TxBody l AlonzoEra) -> Size
$cencodedListSizeExpr :: forall (l :: TxLevel).
Typeable l =>
(forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [TxBody l AlonzoEra] -> Size
encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy [TxBody l AlonzoEra] -> Size
ToCBOR, (forall x. TxBody l AlonzoEra -> Rep (TxBody l AlonzoEra) x)
-> (forall x. Rep (TxBody l AlonzoEra) x -> TxBody l AlonzoEra)
-> Generic (TxBody l AlonzoEra)
forall x. Rep (TxBody l AlonzoEra) x -> TxBody l AlonzoEra
forall x. TxBody l AlonzoEra -> Rep (TxBody l AlonzoEra) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (l :: TxLevel) x.
Rep (TxBody l AlonzoEra) x -> TxBody l AlonzoEra
forall (l :: TxLevel) x.
TxBody l AlonzoEra -> Rep (TxBody l AlonzoEra) x
$cfrom :: forall (l :: TxLevel) x.
TxBody l AlonzoEra -> Rep (TxBody l AlonzoEra) x
from :: forall x. TxBody l AlonzoEra -> Rep (TxBody l AlonzoEra) x
$cto :: forall (l :: TxLevel) x.
Rep (TxBody l AlonzoEra) x -> TxBody l AlonzoEra
to :: forall x. Rep (TxBody l AlonzoEra) x -> TxBody l AlonzoEra
Generic)
deriving newtype (TxBody l AlonzoEra -> Int
TxBody l AlonzoEra -> ByteString
(TxBody l AlonzoEra -> ByteString)
-> (TxBody l AlonzoEra -> Int)
-> (forall i. Proxy i -> TxBody l AlonzoEra -> SafeHash i)
-> SafeToHash (TxBody l AlonzoEra)
forall i. Proxy i -> TxBody l AlonzoEra -> SafeHash i
forall t.
(t -> ByteString)
-> (t -> Int)
-> (forall i. Proxy i -> t -> SafeHash i)
-> SafeToHash t
forall (l :: TxLevel). TxBody l AlonzoEra -> Int
forall (l :: TxLevel). TxBody l AlonzoEra -> ByteString
forall (l :: TxLevel) i.
Proxy i -> TxBody l AlonzoEra -> SafeHash i
$coriginalBytes :: forall (l :: TxLevel). TxBody l AlonzoEra -> ByteString
originalBytes :: TxBody l AlonzoEra -> ByteString
$coriginalBytesSize :: forall (l :: TxLevel). TxBody l AlonzoEra -> Int
originalBytesSize :: TxBody l AlonzoEra -> Int
$cmakeHashWithExplicitProxys :: forall (l :: TxLevel) i.
Proxy i -> TxBody l AlonzoEra -> SafeHash i
makeHashWithExplicitProxys :: forall i. Proxy i -> TxBody l AlonzoEra -> SafeHash i
SafeToHash)
mkBasicTxBody :: forall (l :: TxLevel). Typeable l => TxBody l AlonzoEra
mkBasicTxBody = TxBody l AlonzoEra
forall (l :: TxLevel). Typeable l => TxBody l AlonzoEra
emptyAlonzoTxBody
inputsTxBodyL :: forall (l :: TxLevel). Lens' (TxBody l AlonzoEra) (Set TxIn)
inputsTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {Set TxIn
atbrInputs :: forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrInputs :: Set TxIn
atbrInputs} -> Set TxIn
atbrInputs) ((RawType (TxBody l AlonzoEra)
-> Set TxIn -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra) (TxBody l AlonzoEra) (Set TxIn) (Set TxIn))
-> (RawType (TxBody l AlonzoEra)
-> Set TxIn -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra) (TxBody l AlonzoEra) (Set TxIn) (Set TxIn)
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw Set TxIn
inputs_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrInputs = inputs_}
{-# INLINEABLE inputsTxBodyL #-}
outputsTxBodyL :: forall (l :: TxLevel).
Lens' (TxBody l AlonzoEra) (StrictSeq (TxOut AlonzoEra))
outputsTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {StrictSeq (TxOut AlonzoEra)
atbrOutputs :: forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxOut era)
atbrOutputs :: StrictSeq (TxOut AlonzoEra)
atbrOutputs} -> StrictSeq (TxOut AlonzoEra)
atbrOutputs) ((RawType (TxBody l AlonzoEra)
-> StrictSeq (TxOut AlonzoEra) -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictSeq (TxOut AlonzoEra))
(StrictSeq (TxOut AlonzoEra)))
-> (RawType (TxBody l AlonzoEra)
-> StrictSeq (TxOut AlonzoEra) -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictSeq (TxOut AlonzoEra))
(StrictSeq (TxOut AlonzoEra))
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw StrictSeq (TxOut AlonzoEra)
outputs_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrOutputs = outputs_}
{-# INLINEABLE outputsTxBodyL #-}
feeTxBodyL :: Lens' (TxBody TopTx AlonzoEra) Coin
feeTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {Coin
atbrTxFee :: forall era. AlonzoTxBodyRaw TopTx era -> Coin
atbrTxFee :: Coin
atbrTxFee} -> Coin
atbrTxFee) ((RawType (TxBody TopTx AlonzoEra)
-> Coin -> RawType (TxBody TopTx AlonzoEra))
-> Lens' (TxBody TopTx AlonzoEra) Coin)
-> (RawType (TxBody TopTx AlonzoEra)
-> Coin -> RawType (TxBody TopTx AlonzoEra))
-> Lens' (TxBody TopTx AlonzoEra) Coin
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody TopTx AlonzoEra)
txBodyRaw Coin
fee_ -> RawType (TxBody TopTx AlonzoEra)
txBodyRaw {atbrTxFee = fee_}
{-# INLINEABLE feeTxBodyL #-}
auxDataHashTxBodyL :: forall (l :: TxLevel).
Lens' (TxBody l AlonzoEra) (StrictMaybe TxAuxDataHash)
auxDataHashTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {StrictMaybe TxAuxDataHash
atbrAuxDataHash :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrAuxDataHash} -> StrictMaybe TxAuxDataHash
atbrAuxDataHash) ((RawType (TxBody l AlonzoEra)
-> StrictMaybe TxAuxDataHash -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictMaybe TxAuxDataHash)
(StrictMaybe TxAuxDataHash))
-> (RawType (TxBody l AlonzoEra)
-> StrictMaybe TxAuxDataHash -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictMaybe TxAuxDataHash)
(StrictMaybe TxAuxDataHash)
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw StrictMaybe TxAuxDataHash
auxDataHash -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrAuxDataHash = auxDataHash}
{-# INLINEABLE auxDataHashTxBodyL #-}
spendableInputsTxBodyF :: forall (l :: TxLevel). SimpleGetter (TxBody l AlonzoEra) (Set TxIn)
spendableInputsTxBodyF = (TxBody l AlonzoEra -> Set TxIn)
-> SimpleGetter (TxBody l AlonzoEra) (Set TxIn)
forall s a. (s -> a) -> SimpleGetter s a
to (TxBody l AlonzoEra
-> (TxBody TopTx AlonzoEra -> Set TxIn) -> Set TxIn
forall (t :: TxLevel -> * -> *) era (l :: TxLevel) a.
(HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) =>
t l era -> (t TopTx era -> a) -> a
`withTopTxLevelOnly` (TxBody TopTx AlonzoEra
-> Getting (Set TxIn) (TxBody TopTx AlonzoEra) (Set TxIn)
-> Set TxIn
forall s a. s -> Getting a s a -> a
^. Getting (Set TxIn) (TxBody TopTx AlonzoEra) (Set TxIn)
forall era.
EraTxBody era =>
SimpleGetter (TxBody TopTx era) (Set TxIn)
SimpleGetter (TxBody TopTx AlonzoEra) (Set TxIn)
allInputsTxBodyF))
{-# INLINE spendableInputsTxBodyF #-}
allInputsTxBodyF :: SimpleGetter (TxBody TopTx AlonzoEra) (Set TxIn)
allInputsTxBodyF =
(TxBody TopTx AlonzoEra -> Set TxIn)
-> SimpleGetter (TxBody TopTx AlonzoEra) (Set TxIn)
forall s a. (s -> a) -> SimpleGetter s a
to ((TxBody TopTx AlonzoEra -> Set TxIn)
-> SimpleGetter (TxBody TopTx AlonzoEra) (Set TxIn))
-> (TxBody TopTx AlonzoEra -> Set TxIn)
-> SimpleGetter (TxBody TopTx AlonzoEra) (Set TxIn)
forall a b. (a -> b) -> a -> b
$ \TxBody TopTx AlonzoEra
txBody -> (TxBody TopTx AlonzoEra
txBody TxBody TopTx AlonzoEra
-> Getting (Set TxIn) (TxBody TopTx AlonzoEra) (Set TxIn)
-> Set TxIn
forall s a. s -> Getting a s a -> a
^. Getting (Set TxIn) (TxBody TopTx AlonzoEra) (Set TxIn)
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) (Set TxIn)
forall (l :: TxLevel). Lens' (TxBody l AlonzoEra) (Set TxIn)
inputsTxBodyL) Set TxIn -> Set TxIn -> Set TxIn
forall a. Ord a => Set a -> Set a -> Set a
`Set.union` (TxBody TopTx AlonzoEra
txBody TxBody TopTx AlonzoEra
-> Getting (Set TxIn) (TxBody TopTx AlonzoEra) (Set TxIn)
-> Set TxIn
forall s a. s -> Getting a s a -> a
^. Getting (Set TxIn) (TxBody TopTx AlonzoEra) (Set TxIn)
forall era.
AlonzoEraTxBody era =>
Lens' (TxBody TopTx era) (Set TxIn)
Lens' (TxBody TopTx AlonzoEra) (Set TxIn)
collateralInputsTxBodyL)
{-# INLINEABLE allInputsTxBodyF #-}
withdrawalsTxBodyL :: forall (l :: TxLevel). Lens' (TxBody l AlonzoEra) Withdrawals
withdrawalsTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {Withdrawals
atbrWithdrawals :: forall era. AlonzoTxBodyRaw TopTx era -> Withdrawals
atbrWithdrawals :: Withdrawals
atbrWithdrawals} -> Withdrawals
atbrWithdrawals) ((RawType (TxBody l AlonzoEra)
-> Withdrawals -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra) (TxBody l AlonzoEra) Withdrawals Withdrawals)
-> (RawType (TxBody l AlonzoEra)
-> Withdrawals -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra) (TxBody l AlonzoEra) Withdrawals Withdrawals
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw Withdrawals
withdrawals_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrWithdrawals = withdrawals_}
{-# INLINEABLE withdrawalsTxBodyL #-}
certsTxBodyL :: forall (l :: TxLevel).
Lens' (TxBody l AlonzoEra) (StrictSeq (TxCert AlonzoEra))
certsTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {StrictSeq (TxCert AlonzoEra)
atbrCerts :: forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxCert era)
atbrCerts :: StrictSeq (TxCert AlonzoEra)
atbrCerts} -> StrictSeq (TxCert AlonzoEra)
atbrCerts) ((RawType (TxBody l AlonzoEra)
-> StrictSeq (TxCert AlonzoEra) -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictSeq (TxCert AlonzoEra))
(StrictSeq (TxCert AlonzoEra)))
-> (RawType (TxBody l AlonzoEra)
-> StrictSeq (TxCert AlonzoEra) -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictSeq (TxCert AlonzoEra))
(StrictSeq (TxCert AlonzoEra))
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw StrictSeq (TxCert AlonzoEra)
certs_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrCerts = certs_}
{-# INLINEABLE certsTxBodyL #-}
getGenesisKeyHashCountTxBody :: TxBody TopTx AlonzoEra -> Int
getGenesisKeyHashCountTxBody = TxBody TopTx AlonzoEra -> Int
forall era. ShelleyEraTxBody era => TxBody TopTx era -> Int
getShelleyGenesisKeyHashCountTxBody
instance ShelleyEraTxBody AlonzoEra where
ttlTxBodyL :: ExactEra ShelleyEra AlonzoEra =>
Lens' (TxBody TopTx AlonzoEra) SlotNo
ttlTxBodyL = (SlotNo -> f SlotNo)
-> TxBody TopTx AlonzoEra -> f (TxBody TopTx AlonzoEra)
forall a b. HasCallStack => Lens' a b
Lens' (TxBody TopTx AlonzoEra) SlotNo
notSupportedInThisEraL
updateTxBodyL :: Lens' (TxBody TopTx AlonzoEra) (StrictMaybe (Update AlonzoEra))
updateTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra RawType (TxBody TopTx AlonzoEra) -> StrictMaybe (Update AlonzoEra)
AlonzoTxBodyRaw TopTx AlonzoEra -> StrictMaybe (Update AlonzoEra)
forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe (Update era)
atbrUpdate ((RawType (TxBody TopTx AlonzoEra)
-> StrictMaybe (Update AlonzoEra)
-> RawType (TxBody TopTx AlonzoEra))
-> Lens' (TxBody TopTx AlonzoEra) (StrictMaybe (Update AlonzoEra)))
-> (RawType (TxBody TopTx AlonzoEra)
-> StrictMaybe (Update AlonzoEra)
-> RawType (TxBody TopTx AlonzoEra))
-> Lens' (TxBody TopTx AlonzoEra) (StrictMaybe (Update AlonzoEra))
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody TopTx AlonzoEra)
txBodyRaw StrictMaybe (Update AlonzoEra)
update_ -> RawType (TxBody TopTx AlonzoEra)
txBodyRaw {atbrUpdate = update_}
{-# INLINEABLE updateTxBodyL #-}
instance AllegraEraTxBody AlonzoEra where
vldtTxBodyL :: forall (l :: TxLevel). Lens' (TxBody l AlonzoEra) ValidityInterval
vldtTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {ValidityInterval
atbrValidityInterval :: forall era. AlonzoTxBodyRaw TopTx era -> ValidityInterval
atbrValidityInterval :: ValidityInterval
atbrValidityInterval} -> ValidityInterval
atbrValidityInterval) ((RawType (TxBody l AlonzoEra)
-> ValidityInterval -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
ValidityInterval
ValidityInterval)
-> (RawType (TxBody l AlonzoEra)
-> ValidityInterval -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
ValidityInterval
ValidityInterval
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw ValidityInterval
vldt_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrValidityInterval = vldt_}
{-# INLINEABLE vldtTxBodyL #-}
instance MaryEraTxBody AlonzoEra where
mintTxBodyL :: forall (l :: TxLevel). Lens' (TxBody l AlonzoEra) MultiAsset
mintTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {MultiAsset
atbrMint :: forall era. AlonzoTxBodyRaw TopTx era -> MultiAsset
atbrMint :: MultiAsset
atbrMint} -> MultiAsset
atbrMint) ((RawType (TxBody l AlonzoEra)
-> MultiAsset -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra) (TxBody l AlonzoEra) MultiAsset MultiAsset)
-> (RawType (TxBody l AlonzoEra)
-> MultiAsset -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra) (TxBody l AlonzoEra) MultiAsset MultiAsset
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw MultiAsset
mint_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrMint = mint_}
{-# INLINEABLE mintTxBodyL #-}
instance AlonzoEraTxBody AlonzoEra where
collateralInputsTxBodyL :: Lens' (TxBody TopTx AlonzoEra) (Set TxIn)
collateralInputsTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {Set TxIn
atbrCollateral :: forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrCollateral :: Set TxIn
atbrCollateral} -> Set TxIn
atbrCollateral) ((RawType (TxBody TopTx AlonzoEra)
-> Set TxIn -> RawType (TxBody TopTx AlonzoEra))
-> Lens' (TxBody TopTx AlonzoEra) (Set TxIn))
-> (RawType (TxBody TopTx AlonzoEra)
-> Set TxIn -> RawType (TxBody TopTx AlonzoEra))
-> Lens' (TxBody TopTx AlonzoEra) (Set TxIn)
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody TopTx AlonzoEra)
txBodyRaw Set TxIn
collateral_ -> RawType (TxBody TopTx AlonzoEra)
txBodyRaw {atbrCollateral = collateral_}
{-# INLINEABLE collateralInputsTxBodyL #-}
reqSignerHashesTxBodyL :: forall (l :: TxLevel).
AtMostEra "Conway" AlonzoEra =>
Lens' (TxBody l AlonzoEra) (Set (KeyHash Guard))
reqSignerHashesTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {Set (KeyHash Guard)
atbrReqSignerHashes :: forall era. AlonzoTxBodyRaw TopTx era -> Set (KeyHash Guard)
atbrReqSignerHashes :: Set (KeyHash Guard)
atbrReqSignerHashes} -> Set (KeyHash Guard)
atbrReqSignerHashes) ((RawType (TxBody l AlonzoEra)
-> Set (KeyHash Guard) -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(Set (KeyHash Guard))
(Set (KeyHash Guard)))
-> (RawType (TxBody l AlonzoEra)
-> Set (KeyHash Guard) -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(Set (KeyHash Guard))
(Set (KeyHash Guard))
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw Set (KeyHash Guard)
reqSignerHashes_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrReqSignerHashes = reqSignerHashes_}
{-# INLINEABLE reqSignerHashesTxBodyL #-}
scriptIntegrityHashTxBodyL :: forall (l :: TxLevel).
Lens' (TxBody l AlonzoEra) (StrictMaybe ScriptIntegrityHash)
scriptIntegrityHashTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: forall era.
AlonzoTxBodyRaw TopTx era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash} -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash) ((RawType (TxBody l AlonzoEra)
-> StrictMaybe ScriptIntegrityHash -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictMaybe ScriptIntegrityHash)
(StrictMaybe ScriptIntegrityHash))
-> (RawType (TxBody l AlonzoEra)
-> StrictMaybe ScriptIntegrityHash -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictMaybe ScriptIntegrityHash)
(StrictMaybe ScriptIntegrityHash)
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw StrictMaybe ScriptIntegrityHash
scriptIntegrityHash_ -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrScriptIntegrityHash = scriptIntegrityHash_}
{-# INLINEABLE scriptIntegrityHashTxBodyL #-}
networkIdTxBodyL :: forall (l :: TxLevel).
Lens' (TxBody l AlonzoEra) (StrictMaybe Network)
networkIdTxBodyL =
forall era t a b.
(Era era, EncCBOR (RawType t), Memoized t) =>
(RawType t -> a) -> (RawType t -> b -> RawType t) -> Lens t t a b
lensMemoRawType @AlonzoEra (\AlonzoTxBodyRaw {StrictMaybe Network
atbrTxNetworkId :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe Network
atbrTxNetworkId :: StrictMaybe Network
atbrTxNetworkId} -> StrictMaybe Network
atbrTxNetworkId) ((RawType (TxBody l AlonzoEra)
-> StrictMaybe Network -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictMaybe Network)
(StrictMaybe Network))
-> (RawType (TxBody l AlonzoEra)
-> StrictMaybe Network -> RawType (TxBody l AlonzoEra))
-> Lens
(TxBody l AlonzoEra)
(TxBody l AlonzoEra)
(StrictMaybe Network)
(StrictMaybe Network)
forall a b. (a -> b) -> a -> b
$
\RawType (TxBody l AlonzoEra)
txBodyRaw StrictMaybe Network
networkId -> RawType (TxBody l AlonzoEra)
txBodyRaw {atbrTxNetworkId = networkId}
{-# INLINEABLE networkIdTxBodyL #-}
redeemerPointer :: forall (l :: TxLevel).
TxBody l AlonzoEra
-> PlutusPurpose AsItem AlonzoEra
-> StrictMaybe (PlutusPurpose AsIx AlonzoEra)
redeemerPointer = TxBody l AlonzoEra
-> AlonzoPlutusPurpose AsItem AlonzoEra
-> StrictMaybe (AlonzoPlutusPurpose AsIx AlonzoEra)
TxBody l AlonzoEra
-> PlutusPurpose AsItem AlonzoEra
-> StrictMaybe (PlutusPurpose AsIx AlonzoEra)
forall era (l :: TxLevel).
MaryEraTxBody era =>
TxBody l era
-> AlonzoPlutusPurpose AsItem era
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
alonzoRedeemerPointer
redeemerPointerInverse :: forall (l :: TxLevel).
TxBody l AlonzoEra
-> PlutusPurpose AsIx AlonzoEra
-> StrictMaybe (PlutusPurpose AsIxItem AlonzoEra)
redeemerPointerInverse = TxBody l AlonzoEra
-> AlonzoPlutusPurpose AsIx AlonzoEra
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem AlonzoEra)
TxBody l AlonzoEra
-> PlutusPurpose AsIx AlonzoEra
-> StrictMaybe (PlutusPurpose AsIxItem AlonzoEra)
forall era (l :: TxLevel).
MaryEraTxBody era =>
TxBody l era
-> AlonzoPlutusPurpose AsIx era
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
alonzoRedeemerPointerInverse
deriving newtype instance Eq (TxBody l AlonzoEra)
deriving instance Typeable l => NoThunks (TxBody l AlonzoEra)
deriving instance NFData (TxBody l AlonzoEra)
deriving instance Show (TxBody l AlonzoEra)
deriving via
Mem (AlonzoTxBodyRaw l AlonzoEra)
instance
Typeable l => DecCBOR (Annotator (TxBody l AlonzoEra))
pattern AlonzoTxBody ::
Set TxIn ->
Set TxIn ->
StrictSeq (TxOut AlonzoEra) ->
StrictSeq (TxCert AlonzoEra) ->
Withdrawals ->
Coin ->
ValidityInterval ->
StrictMaybe (Update AlonzoEra) ->
Set (KeyHash Guard) ->
MultiAsset ->
StrictMaybe ScriptIntegrityHash ->
StrictMaybe TxAuxDataHash ->
StrictMaybe Network ->
TxBody TopTx AlonzoEra
pattern $mAlonzoTxBody :: forall {r}.
TxBody TopTx AlonzoEra
-> (Set TxIn
-> Set TxIn
-> StrictSeq (TxOut AlonzoEra)
-> StrictSeq (TxCert AlonzoEra)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update AlonzoEra)
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> r)
-> ((# #) -> r)
-> r
$bAlonzoTxBody :: Set TxIn
-> Set TxIn
-> StrictSeq (TxOut AlonzoEra)
-> StrictSeq (TxCert AlonzoEra)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update AlonzoEra)
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> TxBody TopTx AlonzoEra
AlonzoTxBody
{ TxBody TopTx AlonzoEra -> Set TxIn
atbInputs
, TxBody TopTx AlonzoEra -> Set TxIn
atbCollateral
, TxBody TopTx AlonzoEra -> StrictSeq (TxOut AlonzoEra)
atbOutputs
, TxBody TopTx AlonzoEra -> StrictSeq (TxCert AlonzoEra)
atbCerts
, TxBody TopTx AlonzoEra -> Withdrawals
atbWithdrawals
, TxBody TopTx AlonzoEra -> Coin
atbTxFee
, TxBody TopTx AlonzoEra -> ValidityInterval
atbValidityInterval
, TxBody TopTx AlonzoEra -> StrictMaybe (Update AlonzoEra)
atbUpdate
, TxBody TopTx AlonzoEra -> Set (KeyHash Guard)
atbReqSignerHashes
, TxBody TopTx AlonzoEra -> MultiAsset
atbMint
, TxBody TopTx AlonzoEra -> StrictMaybe ScriptIntegrityHash
atbScriptIntegrityHash
, TxBody TopTx AlonzoEra -> StrictMaybe TxAuxDataHash
atbAuxDataHash
, TxBody TopTx AlonzoEra -> 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 AlonzoEra)
outputs
StrictSeq (TxCert AlonzoEra)
certs
Withdrawals
withdrawals
Coin
txFee
ValidityInterval
validityInterval
StrictMaybe (Update AlonzoEra)
update
Set (KeyHash Guard)
reqSignerHashes
MultiAsset
mint
StrictMaybe ScriptIntegrityHash
scriptIntegrityHash
StrictMaybe TxAuxDataHash
auxDataHash
StrictMaybe Network
txNetworkId =
forall era t.
(Era era, EncCBOR (RawType t), Memoized t) =>
RawType t -> t
mkMemoizedEra @AlonzoEra (RawType (TxBody TopTx AlonzoEra) -> TxBody TopTx AlonzoEra)
-> RawType (TxBody TopTx AlonzoEra) -> TxBody TopTx AlonzoEra
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 AlonzoEra)
atbrOutputs = StrictSeq (TxOut AlonzoEra)
outputs
, atbrCerts :: StrictSeq (TxCert AlonzoEra)
atbrCerts = StrictSeq (TxCert AlonzoEra)
certs
, atbrWithdrawals :: Withdrawals
atbrWithdrawals = Withdrawals
withdrawals
, atbrTxFee :: Coin
atbrTxFee = Coin
txFee
, atbrValidityInterval :: ValidityInterval
atbrValidityInterval = ValidityInterval
validityInterval
, atbrUpdate :: StrictMaybe (Update AlonzoEra)
atbrUpdate = StrictMaybe (Update AlonzoEra)
update
, atbrReqSignerHashes :: Set (KeyHash Guard)
atbrReqSignerHashes = Set (KeyHash Guard)
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 l era) = EraIndependentTxBody
instance HashAnnotated (TxBody l AlonzoEra) EraIndependentTxBody where
hashAnnotated :: TxBody l AlonzoEra -> SafeHash EraIndependentTxBody
hashAnnotated = TxBody l AlonzoEra -> SafeHash EraIndependentTxBody
TxBody l AlonzoEra
-> SafeHash (MemoHashIndex (RawType (TxBody l AlonzoEra)))
forall t. Memoized t => t -> SafeHash (MemoHashIndex (RawType t))
getMemoSafeHash
instance EqRaw (TxBody l AlonzoEra)
deriving newtype instance EncCBOR (TxBody l AlonzoEra)
instance EncCBOR (AlonzoTxBodyRaw l AlonzoEra) where
encCBOR :: AlonzoTxBodyRaw l AlonzoEra -> Encoding
encCBOR
AlonzoTxBodyRaw
{ Set TxIn
atbrInputs :: forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrInputs :: Set TxIn
atbrInputs
, Set TxIn
atbrCollateral :: forall era. AlonzoTxBodyRaw TopTx era -> Set TxIn
atbrCollateral :: Set TxIn
atbrCollateral
, StrictSeq (TxOut AlonzoEra)
atbrOutputs :: forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxOut era)
atbrOutputs :: StrictSeq (TxOut AlonzoEra)
atbrOutputs
, StrictSeq (TxCert AlonzoEra)
atbrCerts :: forall era. AlonzoTxBodyRaw TopTx era -> StrictSeq (TxCert era)
atbrCerts :: StrictSeq (TxCert AlonzoEra)
atbrCerts
, Withdrawals
atbrWithdrawals :: forall era. AlonzoTxBodyRaw TopTx era -> Withdrawals
atbrWithdrawals :: Withdrawals
atbrWithdrawals
, Coin
atbrTxFee :: forall era. AlonzoTxBodyRaw TopTx era -> Coin
atbrTxFee :: Coin
atbrTxFee
, atbrValidityInterval :: forall era. AlonzoTxBodyRaw TopTx era -> ValidityInterval
atbrValidityInterval = ValidityInterval StrictMaybe SlotNo
bot StrictMaybe SlotNo
top
, StrictMaybe (Update AlonzoEra)
atbrUpdate :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe (Update era)
atbrUpdate :: StrictMaybe (Update AlonzoEra)
atbrUpdate
, Set (KeyHash Guard)
atbrReqSignerHashes :: forall era. AlonzoTxBodyRaw TopTx era -> Set (KeyHash Guard)
atbrReqSignerHashes :: Set (KeyHash Guard)
atbrReqSignerHashes
, MultiAsset
atbrMint :: forall era. AlonzoTxBodyRaw TopTx era -> MultiAsset
atbrMint :: MultiAsset
atbrMint
, StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: forall era.
AlonzoTxBodyRaw TopTx era -> StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash
, StrictMaybe TxAuxDataHash
atbrAuxDataHash :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe TxAuxDataHash
atbrAuxDataHash :: StrictMaybe TxAuxDataHash
atbrAuxDataHash
, StrictMaybe Network
atbrTxNetworkId :: forall era. AlonzoTxBodyRaw TopTx era -> StrictMaybe Network
atbrTxNetworkId :: StrictMaybe Network
atbrTxNetworkId
} =
Encode (Closed Sparse) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode (Closed Sparse) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encoding)
-> Encode (Closed Sparse) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encoding
forall a b. (a -> b) -> a -> b
$
(Set TxIn
-> Set TxIn
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode
(Closed Sparse)
(Set TxIn
-> Set TxIn
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall t. t -> Encode (Closed Sparse) t
Keyed
( \Set TxIn
i Set TxIn
ifee StrictSeq (AlonzoTxOut AlonzoEra)
o Coin
f StrictMaybe SlotNo
t StrictSeq (ShelleyTxCert AlonzoEra)
c Withdrawals
w StrictMaybe (Update AlonzoEra)
u StrictMaybe SlotNo
b Set (KeyHash Guard)
rsh MultiAsset
mi StrictMaybe ScriptIntegrityHash
sh StrictMaybe TxAuxDataHash
ah StrictMaybe Network
ni ->
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut AlonzoEra)
-> StrictSeq (TxCert AlonzoEra)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update AlonzoEra)
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra
forall era.
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx era
AlonzoTxBodyRaw Set TxIn
i Set TxIn
ifee StrictSeq (TxOut AlonzoEra)
StrictSeq (AlonzoTxOut AlonzoEra)
o StrictSeq (TxCert AlonzoEra)
StrictSeq (ShelleyTxCert AlonzoEra)
c Withdrawals
w Coin
f (StrictMaybe SlotNo -> StrictMaybe SlotNo -> ValidityInterval
ValidityInterval StrictMaybe SlotNo
b StrictMaybe SlotNo
t) StrictMaybe (Update AlonzoEra)
u Set (KeyHash Guard)
rsh MultiAsset
mi StrictMaybe ScriptIntegrityHash
sh StrictMaybe TxAuxDataHash
ah StrictMaybe Network
ni
)
Encode
(Closed Sparse)
(Set TxIn
-> Set TxIn
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (Set TxIn)
-> Encode
(Closed Sparse)
(Set TxIn
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> Encode (Closed Dense) (Set TxIn)
-> Encode (Closed Sparse) (Set TxIn)
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
0 (Set TxIn -> Encode (Closed Dense) (Set TxIn)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To Set TxIn
atbrInputs)
Encode
(Closed Sparse)
(Set TxIn
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (Set TxIn)
-> Encode
(Closed Sparse)
(StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> (Set TxIn -> Bool)
-> Encode (Closed Sparse) (Set TxIn)
-> Encode (Closed Sparse) (Set TxIn)
forall t.
(t -> Bool) -> Encode (Closed Sparse) t -> Encode (Closed Sparse) t
Omit Set TxIn -> Bool
forall a. Set a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Word
-> Encode (Closed Dense) (Set TxIn)
-> Encode (Closed Sparse) (Set TxIn)
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
13 (Set TxIn -> Encode (Closed Dense) (Set TxIn)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To Set TxIn
atbrCollateral))
Encode
(Closed Sparse)
(StrictSeq (AlonzoTxOut AlonzoEra)
-> Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictSeq (AlonzoTxOut AlonzoEra))
-> Encode
(Closed Sparse)
(Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> Encode (Closed Dense) (StrictSeq (AlonzoTxOut AlonzoEra))
-> Encode (Closed Sparse) (StrictSeq (AlonzoTxOut AlonzoEra))
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
1 (StrictSeq (AlonzoTxOut AlonzoEra)
-> Encode (Closed Dense) (StrictSeq (AlonzoTxOut AlonzoEra))
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To StrictSeq (TxOut AlonzoEra)
StrictSeq (AlonzoTxOut AlonzoEra)
atbrOutputs)
Encode
(Closed Sparse)
(Coin
-> StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) Coin
-> Encode
(Closed Sparse)
(StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word -> Encode (Closed Dense) Coin -> Encode (Closed Sparse) Coin
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
2 (Coin -> Encode (Closed Dense) Coin
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To Coin
atbrTxFee)
Encode
(Closed Sparse)
(StrictMaybe SlotNo
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe SlotNo)
-> Encode
(Closed Sparse)
(StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> StrictMaybe SlotNo
-> Encode (Closed Sparse) (StrictMaybe SlotNo)
forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode (Closed Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
3 StrictMaybe SlotNo
top
Encode
(Closed Sparse)
(StrictSeq (ShelleyTxCert AlonzoEra)
-> Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictSeq (ShelleyTxCert AlonzoEra))
-> Encode
(Closed Sparse)
(Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> (StrictSeq (ShelleyTxCert AlonzoEra) -> Bool)
-> Encode (Closed Sparse) (StrictSeq (ShelleyTxCert AlonzoEra))
-> Encode (Closed Sparse) (StrictSeq (ShelleyTxCert AlonzoEra))
forall t.
(t -> Bool) -> Encode (Closed Sparse) t -> Encode (Closed Sparse) t
Omit StrictSeq (ShelleyTxCert AlonzoEra) -> Bool
forall a. StrictSeq a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Word
-> Encode (Closed Dense) (StrictSeq (ShelleyTxCert AlonzoEra))
-> Encode (Closed Sparse) (StrictSeq (ShelleyTxCert AlonzoEra))
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
4 (StrictSeq (ShelleyTxCert AlonzoEra)
-> Encode (Closed Dense) (StrictSeq (ShelleyTxCert AlonzoEra))
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To StrictSeq (TxCert AlonzoEra)
StrictSeq (ShelleyTxCert AlonzoEra)
atbrCerts))
Encode
(Closed Sparse)
(Withdrawals
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) Withdrawals
-> Encode
(Closed Sparse)
(StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> (Withdrawals -> Bool)
-> Encode (Closed Sparse) Withdrawals
-> Encode (Closed Sparse) Withdrawals
forall t.
(t -> Bool) -> Encode (Closed Sparse) t -> Encode (Closed Sparse) t
Omit (Map RewardAccount Coin -> Bool
forall a. Map RewardAccount a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Map RewardAccount Coin -> Bool)
-> (Withdrawals -> Map RewardAccount Coin) -> Withdrawals -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Withdrawals -> Map RewardAccount Coin
unWithdrawals) (Word
-> Encode (Closed Dense) Withdrawals
-> Encode (Closed Sparse) Withdrawals
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
5 (Withdrawals -> Encode (Closed Dense) Withdrawals
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To Withdrawals
atbrWithdrawals))
Encode
(Closed Sparse)
(StrictMaybe (Update AlonzoEra)
-> StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe (Update AlonzoEra))
-> Encode
(Closed Sparse)
(StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> StrictMaybe (Update AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe (Update AlonzoEra))
forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode (Closed Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
6 StrictMaybe (Update AlonzoEra)
atbrUpdate
Encode
(Closed Sparse)
(StrictMaybe SlotNo
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe SlotNo)
-> Encode
(Closed Sparse)
(Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> StrictMaybe SlotNo
-> Encode (Closed Sparse) (StrictMaybe SlotNo)
forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode (Closed Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
8 StrictMaybe SlotNo
bot
Encode
(Closed Sparse)
(Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (Set (KeyHash Guard))
-> Encode
(Closed Sparse)
(MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> (Set (KeyHash Guard) -> Bool)
-> Encode (Closed Sparse) (Set (KeyHash Guard))
-> Encode (Closed Sparse) (Set (KeyHash Guard))
forall t.
(t -> Bool) -> Encode (Closed Sparse) t -> Encode (Closed Sparse) t
Omit Set (KeyHash Guard) -> Bool
forall a. Set a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (Word
-> Encode (Closed Dense) (Set (KeyHash Guard))
-> Encode (Closed Sparse) (Set (KeyHash Guard))
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
14 (Set (KeyHash Guard) -> Encode (Closed Dense) (Set (KeyHash Guard))
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To Set (KeyHash Guard)
atbrReqSignerHashes))
Encode
(Closed Sparse)
(MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) MultiAsset
-> Encode
(Closed Sparse)
(StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> (MultiAsset -> Bool)
-> Encode (Closed Sparse) MultiAsset
-> Encode (Closed Sparse) MultiAsset
forall t.
(t -> Bool) -> Encode (Closed Sparse) t -> Encode (Closed Sparse) t
Omit (MultiAsset -> MultiAsset -> Bool
forall a. Eq a => a -> a -> Bool
== MultiAsset
forall a. Monoid a => a
mempty) (Word
-> Encode (Closed Dense) MultiAsset
-> Encode (Closed Sparse) MultiAsset
forall t.
Word -> Encode (Closed Dense) t -> Encode (Closed Sparse) t
Key Word
9 (MultiAsset -> Encode (Closed Dense) MultiAsset
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To MultiAsset
atbrMint))
Encode
(Closed Sparse)
(StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe ScriptIntegrityHash)
-> Encode
(Closed Sparse)
(StrictMaybe TxAuxDataHash
-> StrictMaybe Network -> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> StrictMaybe ScriptIntegrityHash
-> Encode (Closed Sparse) (StrictMaybe ScriptIntegrityHash)
forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode (Closed Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
11 StrictMaybe ScriptIntegrityHash
atbrScriptIntegrityHash
Encode
(Closed Sparse)
(StrictMaybe TxAuxDataHash
-> StrictMaybe Network -> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe TxAuxDataHash)
-> Encode
(Closed Sparse)
(StrictMaybe Network -> AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> StrictMaybe TxAuxDataHash
-> Encode (Closed Sparse) (StrictMaybe TxAuxDataHash)
forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode (Closed Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
7 StrictMaybe TxAuxDataHash
atbrAuxDataHash
Encode
(Closed Sparse)
(StrictMaybe Network -> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Encode (Closed Sparse) (StrictMaybe Network)
-> Encode (Closed Sparse) (AlonzoTxBodyRaw TopTx AlonzoEra)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Word
-> StrictMaybe Network
-> Encode (Closed Sparse) (StrictMaybe Network)
forall a.
EncCBOR a =>
Word -> StrictMaybe a -> Encode (Closed Sparse) (StrictMaybe a)
encodeKeyedStrictMaybe Word
15 StrictMaybe Network
atbrTxNetworkId
instance
Typeable l =>
DecCBOR (AlonzoTxBodyRaw l AlonzoEra)
where
decCBOR :: forall s. Decoder s (AlonzoTxBodyRaw l AlonzoEra)
decCBOR =
(AlonzoTxBodyRaw TopTx AlonzoEra -> AlonzoTxBodyRaw l AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw l AlonzoEra)
forall a b. (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AlonzoTxBodyRaw TopTx AlonzoEra -> AlonzoTxBodyRaw l AlonzoEra
forall (l :: TxLevel) (t :: TxLevel -> * -> *) era.
(Typeable l, HasEraTxLevel t era,
STxLevel l era ~ STxTopLevel l era) =>
t TopTx era -> t l era
asSTxTopLevel (Decoder s (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw l AlonzoEra))
-> (Decode (Closed Dense) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw TopTx AlonzoEra))
-> Decode (Closed Dense) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw l AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Decode (Closed Dense) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw TopTx AlonzoEra)
forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t
decode (Decode (Closed Dense) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw l AlonzoEra))
-> Decode (Closed Dense) (AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decoder s (AlonzoTxBodyRaw l AlonzoEra)
forall a b. (a -> b) -> a -> b
$
String
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> (Word -> Field (AlonzoTxBodyRaw TopTx AlonzoEra))
-> [(Word, String)]
-> Decode (Closed Dense) (AlonzoTxBodyRaw TopTx AlonzoEra)
forall t.
Typeable t =>
String
-> t
-> (Word -> Field t)
-> [(Word, String)]
-> Decode (Closed Dense) t
SparseKeyed
String
"AlonzoTxBodyRaw"
(AlonzoTxBodyRaw TopTx AlonzoEra -> AlonzoTxBodyRaw TopTx AlonzoEra
forall (l :: TxLevel) (t :: TxLevel -> * -> *) era.
(Typeable l, HasEraTxLevel t era,
STxLevel l era ~ STxTopLevel l era) =>
t TopTx era -> t l era
asSTxTopLevel AlonzoTxBodyRaw TopTx AlonzoEra
forall era. AlonzoTxBodyRaw TopTx era
emptyAlonzoTxBodyRaw)
Word -> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
bodyFields
[(Word, String)]
requiredFields
where
bodyFields :: Word -> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
bodyFields :: Word -> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
bodyFields Word
0 = (Set TxIn
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 0)) (Set TxIn)
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\Set TxIn
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrInputs = x}) Decode (Closed (ZonkAny 0)) (Set TxIn)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
1 = (StrictSeq (AlonzoTxOut AlonzoEra)
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 1)) (StrictSeq (AlonzoTxOut AlonzoEra))
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\StrictSeq (AlonzoTxOut AlonzoEra)
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrOutputs = x}) Decode (Closed (ZonkAny 1)) (StrictSeq (AlonzoTxOut AlonzoEra))
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
2 = (Coin
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 2)) Coin
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\Coin
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrTxFee = x}) Decode (Closed (ZonkAny 2)) Coin
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
3 =
(StrictMaybe SlotNo
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 3)) SlotNo
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(StrictMaybe x -> t -> t) -> Decode (Closed d) x -> Field t
ofield
(\StrictMaybe SlotNo
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrValidityInterval = (atbrValidityInterval tx) {invalidHereafter = x}})
Decode (Closed (ZonkAny 3)) SlotNo
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
4 = (StrictSeq (ShelleyTxCert AlonzoEra)
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode
(Closed (ZonkAny 4)) (StrictSeq (ShelleyTxCert AlonzoEra))
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\StrictSeq (ShelleyTxCert AlonzoEra)
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrCerts = x}) Decode (Closed (ZonkAny 4)) (StrictSeq (ShelleyTxCert AlonzoEra))
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
5 = (Withdrawals
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 5)) Withdrawals
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\Withdrawals
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrWithdrawals = x}) Decode (Closed (ZonkAny 5)) Withdrawals
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
6 = (StrictMaybe (Update AlonzoEra)
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 6)) (Update AlonzoEra)
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(StrictMaybe x -> t -> t) -> Decode (Closed d) x -> Field t
ofield (\StrictMaybe (Update AlonzoEra)
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrUpdate = x}) Decode (Closed (ZonkAny 6)) (Update AlonzoEra)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
7 = (StrictMaybe TxAuxDataHash
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 7)) TxAuxDataHash
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(StrictMaybe x -> t -> t) -> Decode (Closed d) x -> Field t
ofield (\StrictMaybe TxAuxDataHash
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrAuxDataHash = x}) Decode (Closed (ZonkAny 7)) TxAuxDataHash
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
8 =
(StrictMaybe SlotNo
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 8)) SlotNo
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(StrictMaybe x -> t -> t) -> Decode (Closed d) x -> Field t
ofield
(\StrictMaybe SlotNo
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrValidityInterval = (atbrValidityInterval tx) {invalidBefore = x}})
Decode (Closed (ZonkAny 8)) SlotNo
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
9 = (MultiAsset
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 9)) MultiAsset
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\MultiAsset
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrMint = x}) Decode (Closed (ZonkAny 9)) MultiAsset
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
11 = (StrictMaybe ScriptIntegrityHash
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 10)) ScriptIntegrityHash
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(StrictMaybe x -> t -> t) -> Decode (Closed d) x -> Field t
ofield (\StrictMaybe ScriptIntegrityHash
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrScriptIntegrityHash = x}) Decode (Closed (ZonkAny 10)) ScriptIntegrityHash
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
13 = (Set TxIn
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 11)) (Set TxIn)
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\Set TxIn
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrCollateral = x}) Decode (Closed (ZonkAny 11)) (Set TxIn)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
14 = (Set (KeyHash Guard)
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 12)) (Set (KeyHash Guard))
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(x -> t -> t) -> Decode (Closed d) x -> Field t
field (\Set (KeyHash Guard)
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrReqSignerHashes = x}) Decode (Closed (ZonkAny 12)) (Set (KeyHash Guard))
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
15 = (StrictMaybe Network
-> AlonzoTxBodyRaw TopTx AlonzoEra
-> AlonzoTxBodyRaw TopTx AlonzoEra)
-> Decode (Closed (ZonkAny 13)) Network
-> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall x t (d :: Density).
Typeable x =>
(StrictMaybe x -> t -> t) -> Decode (Closed d) x -> Field t
ofield (\StrictMaybe Network
x AlonzoTxBodyRaw TopTx AlonzoEra
tx -> AlonzoTxBodyRaw TopTx AlonzoEra
tx {atbrTxNetworkId = x}) Decode (Closed (ZonkAny 13)) Network
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
bodyFields Word
n = Word -> Field (AlonzoTxBodyRaw TopTx AlonzoEra)
forall t. Word -> Field t
invalidField Word
n
requiredFields :: [(Word, String)]
requiredFields =
[ (Word
0, String
"inputs")
, (Word
1, String
"outputs")
, (Word
2, String
"fee")
]
instance Typeable l => DecCBOR (Annotator (AlonzoTxBodyRaw l AlonzoEra)) where
decCBOR :: forall s. Decoder s (Annotator (AlonzoTxBodyRaw l AlonzoEra))
decCBOR = AlonzoTxBodyRaw l AlonzoEra
-> Annotator (AlonzoTxBodyRaw l AlonzoEra)
forall a. a -> Annotator a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AlonzoTxBodyRaw l AlonzoEra
-> Annotator (AlonzoTxBodyRaw l AlonzoEra))
-> Decoder s (AlonzoTxBodyRaw l AlonzoEra)
-> Decoder s (Annotator (AlonzoTxBodyRaw l AlonzoEra))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (AlonzoTxBodyRaw l AlonzoEra)
forall s. Decoder s (AlonzoTxBodyRaw l AlonzoEra)
forall a s. DecCBOR a => Decoder s a
decCBOR
emptyAlonzoTxBodyRaw :: AlonzoTxBodyRaw TopTx era
emptyAlonzoTxBodyRaw :: forall era. AlonzoTxBodyRaw TopTx era
emptyAlonzoTxBodyRaw =
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx era
forall era.
Set TxIn
-> Set TxIn
-> StrictSeq (TxOut era)
-> StrictSeq (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> StrictMaybe (Update era)
-> Set (KeyHash Guard)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> AlonzoTxBodyRaw TopTx era
AlonzoTxBodyRaw
Set TxIn
forall a. Monoid a => a
mempty
Set TxIn
forall a. Monoid a => a
mempty
StrictSeq (TxOut era)
forall a. StrictSeq a
StrictSeq.empty
StrictSeq (TxCert era)
forall a. StrictSeq a
StrictSeq.empty
(Map RewardAccount Coin -> Withdrawals
Withdrawals Map RewardAccount Coin
forall a. Monoid a => a
mempty)
Coin
forall a. Monoid a => a
mempty
(StrictMaybe SlotNo -> StrictMaybe SlotNo -> ValidityInterval
ValidityInterval StrictMaybe SlotNo
forall a. StrictMaybe a
SNothing StrictMaybe SlotNo
forall a. StrictMaybe a
SNothing)
StrictMaybe (Update era)
forall a. StrictMaybe a
SNothing
Set (KeyHash Guard)
forall a. Monoid a => a
mempty
MultiAsset
forall a. Monoid a => a
mempty
StrictMaybe ScriptIntegrityHash
forall a. StrictMaybe a
SNothing
StrictMaybe TxAuxDataHash
forall a. StrictMaybe a
SNothing
StrictMaybe Network
forall a. StrictMaybe a
SNothing
emptyAlonzoTxBody :: Typeable l => TxBody l AlonzoEra
emptyAlonzoTxBody :: forall (l :: TxLevel). Typeable l => TxBody l AlonzoEra
emptyAlonzoTxBody = TxBody TopTx AlonzoEra -> TxBody l AlonzoEra
forall (l :: TxLevel) (t :: TxLevel -> * -> *) era.
(Typeable l, HasEraTxLevel t era,
STxLevel l era ~ STxTopLevel l era) =>
t TopTx era -> t l era
asSTxTopLevel (TxBody TopTx AlonzoEra -> TxBody l AlonzoEra)
-> TxBody TopTx AlonzoEra -> TxBody l AlonzoEra
forall a b. (a -> b) -> a -> b
$ forall era t.
(Era era, EncCBOR (RawType t), Memoized t) =>
RawType t -> t
mkMemoizedEra @AlonzoEra RawType (TxBody TopTx AlonzoEra)
AlonzoTxBodyRaw TopTx AlonzoEra
forall era. AlonzoTxBodyRaw TopTx era
emptyAlonzoTxBodyRaw
alonzoRedeemerPointer ::
forall era l.
MaryEraTxBody era =>
TxBody l era ->
AlonzoPlutusPurpose AsItem era ->
StrictMaybe (AlonzoPlutusPurpose AsIx era)
alonzoRedeemerPointer :: forall era (l :: TxLevel).
MaryEraTxBody era =>
TxBody l era
-> AlonzoPlutusPurpose AsItem era
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
alonzoRedeemerPointer TxBody l era
txBody = \case
AlonzoSpending AsItem Word32 TxIn
txIn ->
AsIx Word32 TxIn -> AlonzoPlutusPurpose AsIx era
forall (f :: * -> * -> *) era.
f Word32 TxIn -> AlonzoPlutusPurpose f era
AlonzoSpending (AsIx Word32 TxIn -> AlonzoPlutusPurpose AsIx era)
-> StrictMaybe (AsIx Word32 TxIn)
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsItem Word32 TxIn -> Set TxIn -> StrictMaybe (AsIx Word32 TxIn)
forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 TxIn
txIn (TxBody l era
txBody TxBody l era
-> Getting (Set TxIn) (TxBody l era) (Set TxIn) -> Set TxIn
forall s a. s -> Getting a s a -> a
^. Getting (Set TxIn) (TxBody l era) (Set TxIn)
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) (Set TxIn)
forall (l :: TxLevel). Lens' (TxBody l era) (Set TxIn)
inputsTxBodyL)
AlonzoMinting AsItem Word32 PolicyID
policyID ->
AsIx Word32 PolicyID -> AlonzoPlutusPurpose AsIx era
forall (f :: * -> * -> *) era.
f Word32 PolicyID -> AlonzoPlutusPurpose f era
AlonzoMinting (AsIx Word32 PolicyID -> AlonzoPlutusPurpose AsIx era)
-> StrictMaybe (AsIx Word32 PolicyID)
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsItem Word32 PolicyID
-> Set PolicyID -> StrictMaybe (AsIx Word32 PolicyID)
forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 PolicyID
policyID (TxBody l era
txBody TxBody l era
-> Getting (Set PolicyID) (TxBody l era) (Set PolicyID)
-> Set PolicyID
forall s a. s -> Getting a s a -> a
^. Getting (Set PolicyID) (TxBody l era) (Set PolicyID)
forall era (l :: TxLevel).
MaryEraTxBody era =>
SimpleGetter (TxBody l era) (Set PolicyID)
forall (l :: TxLevel). SimpleGetter (TxBody l era) (Set PolicyID)
mintedTxBodyF :: Set PolicyID)
AlonzoCertifying AsItem Word32 (TxCert era)
txCert ->
AsIx Word32 (TxCert era) -> AlonzoPlutusPurpose AsIx era
forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> AlonzoPlutusPurpose f era
AlonzoCertifying (AsIx Word32 (TxCert era) -> AlonzoPlutusPurpose AsIx era)
-> StrictMaybe (AsIx Word32 (TxCert era))
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsItem Word32 (TxCert era)
-> StrictSeq (TxCert era) -> StrictMaybe (AsIx Word32 (TxCert era))
forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 (TxCert era)
txCert (TxBody l era
txBody TxBody l era
-> Getting
(StrictSeq (TxCert era)) (TxBody l era) (StrictSeq (TxCert era))
-> StrictSeq (TxCert era)
forall s a. s -> Getting a s a -> a
^. Getting
(StrictSeq (TxCert era)) (TxBody l era) (StrictSeq (TxCert era))
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) (StrictSeq (TxCert era))
forall (l :: TxLevel).
Lens' (TxBody l era) (StrictSeq (TxCert era))
certsTxBodyL)
AlonzoRewarding AsItem Word32 RewardAccount
rewardAccount ->
AsIx Word32 RewardAccount -> AlonzoPlutusPurpose AsIx era
forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> AlonzoPlutusPurpose f era
AlonzoRewarding (AsIx Word32 RewardAccount -> AlonzoPlutusPurpose AsIx era)
-> StrictMaybe (AsIx Word32 RewardAccount)
-> StrictMaybe (AlonzoPlutusPurpose AsIx era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsItem Word32 RewardAccount
-> Map RewardAccount Coin
-> StrictMaybe (AsIx Word32 RewardAccount)
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 l era
txBody TxBody l era
-> Getting Withdrawals (TxBody l era) Withdrawals -> Withdrawals
forall s a. s -> Getting a s a -> a
^. Getting Withdrawals (TxBody l era) Withdrawals
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) Withdrawals
forall (l :: TxLevel). Lens' (TxBody l era) Withdrawals
withdrawalsTxBodyL))
alonzoRedeemerPointerInverse ::
MaryEraTxBody era =>
TxBody l era ->
AlonzoPlutusPurpose AsIx era ->
StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
alonzoRedeemerPointerInverse :: forall era (l :: TxLevel).
MaryEraTxBody era =>
TxBody l era
-> AlonzoPlutusPurpose AsIx era
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
alonzoRedeemerPointerInverse TxBody l era
txBody = \case
AlonzoSpending AsIx Word32 TxIn
idx ->
AsIxItem Word32 TxIn -> AlonzoPlutusPurpose AsIxItem era
forall (f :: * -> * -> *) era.
f Word32 TxIn -> AlonzoPlutusPurpose f era
AlonzoSpending (AsIxItem Word32 TxIn -> AlonzoPlutusPurpose AsIxItem era)
-> StrictMaybe (AsIxItem Word32 TxIn)
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsIx Word32 TxIn -> Set TxIn -> StrictMaybe (AsIxItem Word32 TxIn)
forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 TxIn
idx (TxBody l era
txBody TxBody l era
-> Getting (Set TxIn) (TxBody l era) (Set TxIn) -> Set TxIn
forall s a. s -> Getting a s a -> a
^. Getting (Set TxIn) (TxBody l era) (Set TxIn)
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) (Set TxIn)
forall (l :: TxLevel). Lens' (TxBody l era) (Set TxIn)
inputsTxBodyL)
AlonzoMinting AsIx Word32 PolicyID
idx ->
AsIxItem Word32 PolicyID -> AlonzoPlutusPurpose AsIxItem era
forall (f :: * -> * -> *) era.
f Word32 PolicyID -> AlonzoPlutusPurpose f era
AlonzoMinting (AsIxItem Word32 PolicyID -> AlonzoPlutusPurpose AsIxItem era)
-> StrictMaybe (AsIxItem Word32 PolicyID)
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsIx Word32 PolicyID
-> Set PolicyID -> StrictMaybe (AsIxItem Word32 PolicyID)
forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 PolicyID
idx (TxBody l era
txBody TxBody l era
-> Getting (Set PolicyID) (TxBody l era) (Set PolicyID)
-> Set PolicyID
forall s a. s -> Getting a s a -> a
^. Getting (Set PolicyID) (TxBody l era) (Set PolicyID)
forall era (l :: TxLevel).
MaryEraTxBody era =>
SimpleGetter (TxBody l era) (Set PolicyID)
forall (l :: TxLevel). SimpleGetter (TxBody l era) (Set PolicyID)
mintedTxBodyF)
AlonzoCertifying AsIx Word32 (TxCert era)
idx ->
AsIxItem Word32 (TxCert era) -> AlonzoPlutusPurpose AsIxItem era
forall (f :: * -> * -> *) era.
f Word32 (TxCert era) -> AlonzoPlutusPurpose f era
AlonzoCertifying (AsIxItem Word32 (TxCert era) -> AlonzoPlutusPurpose AsIxItem era)
-> StrictMaybe (AsIxItem Word32 (TxCert era))
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsIx Word32 (TxCert era)
-> StrictSeq (TxCert era)
-> StrictMaybe (AsIxItem Word32 (TxCert era))
forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 (TxCert era)
idx (TxBody l era
txBody TxBody l era
-> Getting
(StrictSeq (TxCert era)) (TxBody l era) (StrictSeq (TxCert era))
-> StrictSeq (TxCert era)
forall s a. s -> Getting a s a -> a
^. Getting
(StrictSeq (TxCert era)) (TxBody l era) (StrictSeq (TxCert era))
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) (StrictSeq (TxCert era))
forall (l :: TxLevel).
Lens' (TxBody l era) (StrictSeq (TxCert era))
certsTxBodyL)
AlonzoRewarding AsIx Word32 RewardAccount
idx ->
AsIxItem Word32 RewardAccount -> AlonzoPlutusPurpose AsIxItem era
forall (f :: * -> * -> *) era.
f Word32 RewardAccount -> AlonzoPlutusPurpose f era
AlonzoRewarding (AsIxItem Word32 RewardAccount -> AlonzoPlutusPurpose AsIxItem era)
-> StrictMaybe (AsIxItem Word32 RewardAccount)
-> StrictMaybe (AlonzoPlutusPurpose AsIxItem era)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AsIx Word32 RewardAccount
-> Map RewardAccount Coin
-> StrictMaybe (AsIxItem Word32 RewardAccount)
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 l era
txBody TxBody l era
-> Getting Withdrawals (TxBody l era) Withdrawals -> Withdrawals
forall s a. s -> Getting a s a -> a
^. Getting Withdrawals (TxBody l era) Withdrawals
forall era (l :: TxLevel).
EraTxBody era =>
Lens' (TxBody l era) Withdrawals
forall (l :: TxLevel). Lens' (TxBody l 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 k -> Set k -> Maybe Int
forall a. Ord a => a -> Set a -> Maybe Int
Set.lookupIndex k
n Set k
s of
Just Int
x -> AsIx Word32 k -> StrictMaybe (AsIx Word32 k)
forall a. a -> StrictMaybe a
SJust (Word32 -> AsIx Word32 k
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 -> StrictMaybe (AsIx Word32 k)
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Set k -> Int
forall a. Set a -> Int
Set.size Set k
s
then AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k)
forall a. a -> StrictMaybe a
SJust (AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k))
-> AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k)
forall a b. (a -> b) -> a -> b
$ Word32 -> k -> AsIxItem Word32 k
forall ix it. ix -> it -> AsIxItem ix it
AsIxItem Word32
w32 (Int -> Set k -> k
forall a. Int -> Set a -> a
Set.elemAt Int
i Set k
s)
else StrictMaybe (AsIxItem Word32 k)
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 (k -> Bool) -> StrictSeq k -> Maybe Int
forall a. (a -> Bool) -> StrictSeq a -> Maybe Int
StrictSeq.findIndexL (k -> k -> Bool
forall a. Eq a => a -> a -> Bool
== k
n) StrictSeq k
seqx of
Just Int
m -> AsIx Word32 k -> StrictMaybe (AsIx Word32 k)
forall a. a -> StrictMaybe a
SJust (Word32 -> AsIx Word32 k
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 -> StrictMaybe (AsIx Word32 k)
forall a. StrictMaybe a
SNothing
fromIndex :: AsIx Word32 k -> StrictSeq k -> StrictMaybe (AsIxItem Word32 k)
fromIndex (AsIx Word32
w32) StrictSeq k
seqx =
case Int -> StrictSeq k -> Maybe k
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 -> StrictMaybe (AsIxItem Word32 k)
forall a. StrictMaybe a
SNothing
Just k
x -> AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k)
forall a. a -> StrictMaybe a
SJust (AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k))
-> AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k)
forall a b. (a -> b) -> a -> b
$ Word32 -> k -> AsIxItem Word32 k
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 k -> Map k v -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe Int
Map.lookupIndex k
n Map k v
mp of
Just Int
x -> AsIx Word32 k -> StrictMaybe (AsIx Word32 k)
forall a. a -> StrictMaybe a
SJust (Word32 -> AsIx Word32 k
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 -> StrictMaybe (AsIx Word32 k)
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Map k v -> Int
forall k a. Map k a -> Int
Map.size Map k v
mp)
then AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k)
forall a. a -> StrictMaybe a
SJust (AsIxItem Word32 k -> StrictMaybe (AsIxItem Word32 k))
-> ((k, v) -> AsIxItem Word32 k)
-> (k, v)
-> StrictMaybe (AsIxItem Word32 k)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> k -> AsIxItem Word32 k
forall ix it. ix -> it -> AsIxItem ix it
AsIxItem Word32
w32 (k -> AsIxItem Word32 k)
-> ((k, v) -> k) -> (k, v) -> AsIxItem Word32 k
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k, v) -> k
forall a b. (a, b) -> a
fst ((k, v) -> StrictMaybe (AsIxItem Word32 k))
-> (k, v) -> StrictMaybe (AsIxItem Word32 k)
forall a b. (a -> b) -> a -> b
$ Int -> Map k v -> (k, v)
forall k a. Int -> Map k a -> (k, a)
Map.elemAt Int
i Map k v
mp
else StrictMaybe (AsIxItem Word32 k)
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 = AsItem Word32 k -> StrictSeq k -> StrictMaybe (AsIx Word32 k)
forall elem container.
Indexable elem container =>
AsItem Word32 elem -> container -> StrictMaybe (AsIx Word32 elem)
indexOf AsItem Word32 k
asItem (StrictSeq k -> StrictMaybe (AsIx Word32 k))
-> (OSet k -> StrictSeq k) -> OSet k -> StrictMaybe (AsIx Word32 k)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OSet k -> StrictSeq k
forall a. OSet a -> StrictSeq a
OSet.toStrictSeq
fromIndex :: AsIx Word32 k -> OSet k -> StrictMaybe (AsIxItem Word32 k)
fromIndex AsIx Word32 k
asIndex = AsIx Word32 k -> StrictSeq k -> StrictMaybe (AsIxItem Word32 k)
forall elem container.
Indexable elem container =>
AsIx Word32 elem -> container -> StrictMaybe (AsIxItem Word32 elem)
fromIndex AsIx Word32 k
asIndex (StrictSeq k -> StrictMaybe (AsIxItem Word32 k))
-> (OSet k -> StrictSeq k)
-> OSet k
-> StrictMaybe (AsIxItem Word32 k)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OSet k -> StrictSeq k
forall a. OSet a -> StrictSeq a
OSet.toStrictSeq