{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}
module Cardano.Api.Internal.Experimental.Plutus.IndexedPlutusScriptWitness
(
AnyIndexedPlutusScriptWitness (..)
, IndexedPlutusScriptWitness (..)
, Witnessable (..)
, WitnessableItem (..)
, GetPlutusScriptPurpose (..)
, createIndexedPlutusScriptWitnesses
, getAnyWitnessRedeemerPointerMap
, obtainAlonzoScriptPurposeConstraints
)
where
import Cardano.Api.Internal.Address
import Cardano.Api.Internal.Eon.AlonzoEraOnwards
import Cardano.Api.Internal.Eon.ShelleyBasedEra
import Cardano.Api.Internal.Experimental.Plutus.ScriptWitness
import Cardano.Api.Internal.Experimental.Witness.AnyWitness
import Cardano.Api.Internal.Script (toAlonzoExUnits)
import Cardano.Api.Internal.ScriptData
import Cardano.Api.Internal.TxIn
import Cardano.Api.Internal.Value
import Cardano.Api.Ledger qualified as L
import Cardano.Ledger.Alonzo.TxWits qualified as L
import Cardano.Ledger.Conway.Scripts qualified as L
import Data.Function
import Data.List qualified as List
import Data.Word
import GHC.Exts
data IndexedPlutusScriptWitness witnessable (lang :: L.Language) (purpose :: PlutusScriptPurpose) era where
IndexedPlutusScriptWitness
:: Witnessable witnessable era
-> (L.PlutusPurpose L.AsIx era)
-> (PlutusScriptWitness lang purpose era)
-> IndexedPlutusScriptWitness witnessable lang purpose era
data AnyIndexedPlutusScriptWitness era where
AnyIndexedPlutusScriptWitness
:: GetPlutusScriptPurpose era
=> IndexedPlutusScriptWitness witnessable lang purpose era
-> AnyIndexedPlutusScriptWitness era
data Witnessable (thing :: WitnessableItem) era where
WitTxIn
:: L.AlonzoEraScript era
=> TxIn
-> Witnessable TxInItem era
WitTxCert
:: (L.EraTxCert era, L.AlonzoEraScript era)
=> L.TxCert era
-> StakeCredential
-> Witnessable CertItem era
WitMint
:: L.AlonzoEraScript era
=> PolicyId
-> PolicyAssets
-> Witnessable MintItem era
WitWithdrawal
:: L.AlonzoEraScript era
=> StakeAddress
-> L.Coin
-> Witnessable WithdrawalItem era
WitVote
:: L.ConwayEraScript era
=> L.Voter
-> Witnessable VoterItem era
WitProposal
:: (L.ConwayEraScript era, L.EraPParams era)
=> L.ProposalProcedure era
-> Witnessable ProposalItem era
deriving instance Show (Witnessable thing era)
deriving instance Eq (Witnessable thing era)
compareWitnesses :: Witnessable thing era -> Witnessable thing era -> Ordering
compareWitnesses :: forall (thing :: WitnessableItem) era.
Witnessable thing era -> Witnessable thing era -> Ordering
compareWitnesses Witnessable thing era
a Witnessable thing era
b =
case (Witnessable thing era
a, Witnessable thing era
b) of
(WitTxIn TxIn
txinA, WitTxIn TxIn
txinB) -> TxIn -> TxIn -> Ordering
forall a. Ord a => a -> a -> Ordering
compare TxIn
txinA TxIn
txinB
(WitTxCert{}, WitTxCert{}) -> Ordering
LT
(WitMint PolicyId
polIdA PolicyAssets
_, WitMint PolicyId
polIdB PolicyAssets
_) -> PolicyId -> PolicyId -> Ordering
forall a. Ord a => a -> a -> Ordering
compare PolicyId
polIdA PolicyId
polIdB
(WitWithdrawal StakeAddress
stakeAddrA Coin
_, WitWithdrawal StakeAddress
stakeAddrB Coin
_) -> StakeAddress -> StakeAddress -> Ordering
forall a. Ord a => a -> a -> Ordering
compare StakeAddress
stakeAddrA StakeAddress
stakeAddrB
(WitVote Voter
voterA, WitVote Voter
voterB) -> Voter -> Voter -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Voter
voterA Voter
voterB
(WitProposal ProposalProcedure era
propA, WitProposal ProposalProcedure era
propB) -> ProposalProcedure era -> ProposalProcedure era -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ProposalProcedure era
propA ProposalProcedure era
propB
data WitnessableItem
= TxInItem
| CertItem
| MintItem
| WithdrawalItem
| VoterItem
| ProposalItem
class GetPlutusScriptPurpose era where
toPlutusScriptPurpose
:: Word32
-> Witnessable thing era
-> L.PlutusPurpose L.AsIx era
instance GetPlutusScriptPurpose era where
toPlutusScriptPurpose :: forall (thing :: WitnessableItem).
Word32 -> Witnessable thing era -> PlutusPurpose AsIx era
toPlutusScriptPurpose Word32
index WitTxIn{} = AsIx Word32 TxIn -> PlutusPurpose AsIx era
forall era (f :: * -> * -> *).
AlonzoEraScript era =>
f Word32 TxIn -> PlutusPurpose f era
forall (f :: * -> * -> *). f Word32 TxIn -> PlutusPurpose f era
L.mkSpendingPurpose (Word32 -> AsIx Word32 TxIn
forall ix it. ix -> AsIx ix it
L.AsIx Word32
index)
toPlutusScriptPurpose Word32
index WitWithdrawal{} = AsIx Word32 RewardAccount -> PlutusPurpose AsIx era
forall era (f :: * -> * -> *).
AlonzoEraScript era =>
f Word32 RewardAccount -> PlutusPurpose f era
forall (f :: * -> * -> *).
f Word32 RewardAccount -> PlutusPurpose f era
L.mkRewardingPurpose (Word32 -> AsIx Word32 RewardAccount
forall ix it. ix -> AsIx ix it
L.AsIx Word32
index)
toPlutusScriptPurpose Word32
index WitMint{} = AsIx Word32 PolicyID -> PlutusPurpose AsIx era
forall era (f :: * -> * -> *).
AlonzoEraScript era =>
f Word32 PolicyID -> PlutusPurpose f era
forall (f :: * -> * -> *). f Word32 PolicyID -> PlutusPurpose f era
L.mkMintingPurpose (Word32 -> AsIx Word32 PolicyID
forall ix it. ix -> AsIx ix it
L.AsIx Word32
index)
toPlutusScriptPurpose Word32
index WitTxCert{} = AsIx Word32 (TxCert era) -> PlutusPurpose AsIx era
forall era (f :: * -> * -> *).
AlonzoEraScript era =>
f Word32 (TxCert era) -> PlutusPurpose f era
forall (f :: * -> * -> *).
f Word32 (TxCert era) -> PlutusPurpose f era
L.mkCertifyingPurpose (Word32 -> AsIx Word32 (TxCert era)
forall ix it. ix -> AsIx ix it
L.AsIx Word32
index)
toPlutusScriptPurpose Word32
index WitVote{} = AsIx Word32 Voter -> PlutusPurpose AsIx era
forall era (f :: * -> * -> *).
ConwayEraScript era =>
f Word32 Voter -> PlutusPurpose f era
forall (f :: * -> * -> *). f Word32 Voter -> PlutusPurpose f era
L.mkVotingPurpose (Word32 -> AsIx Word32 Voter
forall ix it. ix -> AsIx ix it
L.AsIx Word32
index)
toPlutusScriptPurpose Word32
index WitProposal{} = AsIx Word32 (ProposalProcedure era) -> PlutusPurpose AsIx era
forall era (f :: * -> * -> *).
ConwayEraScript era =>
f Word32 (ProposalProcedure era) -> PlutusPurpose f era
forall (f :: * -> * -> *).
f Word32 (ProposalProcedure era) -> PlutusPurpose f era
L.mkProposingPurpose (Word32 -> AsIx Word32 (ProposalProcedure era)
forall ix it. ix -> AsIx ix it
L.AsIx Word32
index)
createIndexedPlutusScriptWitness
:: Word32
-> Witnessable witnessable era
-> PlutusScriptWitness lang purpose era
-> IndexedPlutusScriptWitness witnessable lang purpose era
createIndexedPlutusScriptWitness :: forall (witnessable :: WitnessableItem) era (lang :: Language)
(purpose :: PlutusScriptPurpose).
Word32
-> Witnessable witnessable era
-> PlutusScriptWitness lang purpose era
-> IndexedPlutusScriptWitness witnessable lang purpose era
createIndexedPlutusScriptWitness Word32
index Witnessable witnessable era
witnessable =
Witnessable witnessable era
-> PlutusPurpose AsIx era
-> PlutusScriptWitness lang purpose era
-> IndexedPlutusScriptWitness witnessable lang purpose era
forall (witnessable :: WitnessableItem) era (lang :: Language)
(purpose :: PlutusScriptPurpose).
Witnessable witnessable era
-> PlutusPurpose AsIx era
-> PlutusScriptWitness lang purpose era
-> IndexedPlutusScriptWitness witnessable lang purpose era
IndexedPlutusScriptWitness Witnessable witnessable era
witnessable (Word32 -> Witnessable witnessable era -> PlutusPurpose AsIx era
forall era (thing :: WitnessableItem).
GetPlutusScriptPurpose era =>
Word32 -> Witnessable thing era -> PlutusPurpose AsIx era
forall (thing :: WitnessableItem).
Word32 -> Witnessable thing era -> PlutusPurpose AsIx era
toPlutusScriptPurpose Word32
index Witnessable witnessable era
witnessable)
createIndexedPlutusScriptWitnesses
:: [(Witnessable witnessable era, AnyWitness era)]
-> [AnyIndexedPlutusScriptWitness era]
createIndexedPlutusScriptWitnesses :: forall (witnessable :: WitnessableItem) era.
[(Witnessable witnessable era, AnyWitness era)]
-> [AnyIndexedPlutusScriptWitness era]
createIndexedPlutusScriptWitnesses [(Witnessable witnessable era, AnyWitness era)]
witnessableThings =
[ IndexedPlutusScriptWitness witnessable lang purpose era
-> AnyIndexedPlutusScriptWitness era
forall era (witnessable :: WitnessableItem) (lang :: Language)
(purpose :: PlutusScriptPurpose).
GetPlutusScriptPurpose era =>
IndexedPlutusScriptWitness witnessable lang purpose era
-> AnyIndexedPlutusScriptWitness era
AnyIndexedPlutusScriptWitness (IndexedPlutusScriptWitness witnessable lang purpose era
-> AnyIndexedPlutusScriptWitness era)
-> IndexedPlutusScriptWitness witnessable lang purpose era
-> AnyIndexedPlutusScriptWitness era
forall a b. (a -> b) -> a -> b
$ Word32
-> Witnessable witnessable era
-> PlutusScriptWitness lang purpose era
-> IndexedPlutusScriptWitness witnessable lang purpose era
forall (witnessable :: WitnessableItem) era (lang :: Language)
(purpose :: PlutusScriptPurpose).
Word32
-> Witnessable witnessable era
-> PlutusScriptWitness lang purpose era
-> IndexedPlutusScriptWitness witnessable lang purpose era
createIndexedPlutusScriptWitness Word32
index Witnessable witnessable era
thing PlutusScriptWitness lang purpose era
sWit
| (Word32
index, (Witnessable witnessable era
thing, AnyPlutusScriptWitness PlutusScriptWitness lang purpose era
sWit)) <- [Word32]
-> [(Witnessable witnessable era, AnyWitness era)]
-> [(Word32, (Witnessable witnessable era, AnyWitness era))]
forall a b. [a] -> [b] -> [(a, b)]
zip [Word32
0 ..] ([(Witnessable witnessable era, AnyWitness era)]
-> [(Word32, (Witnessable witnessable era, AnyWitness era))])
-> [(Witnessable witnessable era, AnyWitness era)]
-> [(Word32, (Witnessable witnessable era, AnyWitness era))]
forall a b. (a -> b) -> a -> b
$ [(Witnessable witnessable era, AnyWitness era)]
-> [(Witnessable witnessable era, AnyWitness era)]
forall {thing :: WitnessableItem} {era} {b}.
[(Witnessable thing era, b)] -> [(Witnessable thing era, b)]
enforceOrdering [(Witnessable witnessable era, AnyWitness era)]
witnessableThings
]
where
enforceOrdering :: [(Witnessable thing era, b)] -> [(Witnessable thing era, b)]
enforceOrdering = ((Witnessable thing era, b)
-> (Witnessable thing era, b) -> Ordering)
-> [(Witnessable thing era, b)] -> [(Witnessable thing era, b)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy (Witnessable thing era -> Witnessable thing era -> Ordering
forall (thing :: WitnessableItem) era.
Witnessable thing era -> Witnessable thing era -> Ordering
compareWitnesses (Witnessable thing era -> Witnessable thing era -> Ordering)
-> ((Witnessable thing era, b) -> Witnessable thing era)
-> (Witnessable thing era, b)
-> (Witnessable thing era, b)
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (Witnessable thing era, b) -> Witnessable thing era
forall a b. (a, b) -> a
fst)
getAnyWitnessRedeemerPointerMap
:: AlonzoEraOnwards era
-> (Witnessable witnessable (ShelleyLedgerEra era), AnyWitness (ShelleyLedgerEra era))
-> L.Redeemers (ShelleyLedgerEra era)
getAnyWitnessRedeemerPointerMap :: forall era (witnessable :: WitnessableItem).
AlonzoEraOnwards era
-> (Witnessable witnessable (ShelleyLedgerEra era),
AnyWitness (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
getAnyWitnessRedeemerPointerMap AlonzoEraOnwards era
eon (Witnessable witnessable (ShelleyLedgerEra era)
_, AnyWitness (ShelleyLedgerEra era)
AnyKeyWitnessPlaceholder) = AlonzoEraOnwards era
-> (AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
forall era a.
AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
alonzoEraOnwardsConstraints AlonzoEraOnwards era
eon Redeemers (ShelleyLedgerEra era)
AlonzoEraOnwardsConstraints era => Redeemers (ShelleyLedgerEra era)
forall a. Monoid a => a
mempty
getAnyWitnessRedeemerPointerMap AlonzoEraOnwards era
eon (Witnessable witnessable (ShelleyLedgerEra era)
_, AnySimpleScriptWitness{}) = AlonzoEraOnwards era
-> (AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
forall era a.
AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
alonzoEraOnwardsConstraints AlonzoEraOnwards era
eon Redeemers (ShelleyLedgerEra era)
AlonzoEraOnwardsConstraints era => Redeemers (ShelleyLedgerEra era)
forall a. Monoid a => a
mempty
getAnyWitnessRedeemerPointerMap AlonzoEraOnwards era
eon (Witnessable witnessable (ShelleyLedgerEra era),
AnyWitness (ShelleyLedgerEra era))
anyWit =
AlonzoEraOnwards era
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> Redeemers (ShelleyLedgerEra era)
forall era.
AlonzoEraOnwards era
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> Redeemers (ShelleyLedgerEra era)
constructRedeeemerPointerMap AlonzoEraOnwards era
eon ([AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> Redeemers (ShelleyLedgerEra era))
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> Redeemers (ShelleyLedgerEra era)
forall a b. (a -> b) -> a -> b
$
[(Witnessable witnessable (ShelleyLedgerEra era),
AnyWitness (ShelleyLedgerEra era))]
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
forall (witnessable :: WitnessableItem) era.
[(Witnessable witnessable era, AnyWitness era)]
-> [AnyIndexedPlutusScriptWitness era]
createIndexedPlutusScriptWitnesses [(Witnessable witnessable (ShelleyLedgerEra era),
AnyWitness (ShelleyLedgerEra era))
anyWit]
constructRedeemerPointer
:: AlonzoEraOnwards era
-> AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)
-> L.Redeemers (ShelleyLedgerEra era)
constructRedeemerPointer :: forall era.
AlonzoEraOnwards era
-> AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)
-> Redeemers (ShelleyLedgerEra era)
constructRedeemerPointer AlonzoEraOnwards era
eon (AnyIndexedPlutusScriptWitness (IndexedPlutusScriptWitness Witnessable witnessable (ShelleyLedgerEra era)
_ PlutusPurpose AsIx (ShelleyLedgerEra era)
purpose PlutusScriptWitness lang purpose (ShelleyLedgerEra era)
scriptWit)) =
let PlutusScriptWitness SLanguage lang
_ PlutusScriptOrReferenceInput lang (ShelleyLedgerEra era)
_ PlutusScriptDatum lang purpose
_ ScriptRedeemer
redeemer ExecutionUnits
execUnits = PlutusScriptWitness lang purpose (ShelleyLedgerEra era)
scriptWit
in AlonzoEraOnwards era
-> (AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
forall era a.
AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
alonzoEraOnwardsConstraints AlonzoEraOnwards era
eon ((AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era))
-> (AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
forall a b. (a -> b) -> a -> b
$
Map
(PlutusPurpose AsIx (ShelleyLedgerEra era))
(Data (ShelleyLedgerEra era), ExUnits)
-> Redeemers (ShelleyLedgerEra era)
forall era.
AlonzoEraScript era =>
Map (PlutusPurpose AsIx era) (Data era, ExUnits) -> Redeemers era
L.Redeemers (Map
(PlutusPurpose AsIx (ShelleyLedgerEra era))
(Data (ShelleyLedgerEra era), ExUnits)
-> Redeemers (ShelleyLedgerEra era))
-> Map
(PlutusPurpose AsIx (ShelleyLedgerEra era))
(Data (ShelleyLedgerEra era), ExUnits)
-> Redeemers (ShelleyLedgerEra era)
forall a b. (a -> b) -> a -> b
$
[Item
(Map
(PlutusPurpose AsIx (ShelleyLedgerEra era))
(Data (ShelleyLedgerEra era), ExUnits))]
-> Map
(PlutusPurpose AsIx (ShelleyLedgerEra era))
(Data (ShelleyLedgerEra era), ExUnits)
forall l. IsList l => [Item l] -> l
fromList [(PlutusPurpose AsIx (ShelleyLedgerEra era)
purpose, (ScriptRedeemer -> Data (ShelleyLedgerEra era)
forall ledgerera. Era ledgerera => ScriptRedeemer -> Data ledgerera
toAlonzoData ScriptRedeemer
redeemer, ExecutionUnits -> ExUnits
toAlonzoExUnits ExecutionUnits
execUnits))]
constructRedeeemerPointerMap
:: AlonzoEraOnwards era
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> L.Redeemers (ShelleyLedgerEra era)
constructRedeeemerPointerMap :: forall era.
AlonzoEraOnwards era
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> Redeemers (ShelleyLedgerEra era)
constructRedeeemerPointerMap AlonzoEraOnwards era
eon [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
scriptWits =
let redeemerPointers :: [Redeemers (ShelleyLedgerEra era)]
redeemerPointers = (AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)
-> Redeemers (ShelleyLedgerEra era))
-> [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
-> [Redeemers (ShelleyLedgerEra era)]
forall a b. (a -> b) -> [a] -> [b]
map (AlonzoEraOnwards era
-> AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)
-> Redeemers (ShelleyLedgerEra era)
forall era.
AlonzoEraOnwards era
-> AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)
-> Redeemers (ShelleyLedgerEra era)
constructRedeemerPointer AlonzoEraOnwards era
eon) [AnyIndexedPlutusScriptWitness (ShelleyLedgerEra era)]
scriptWits
in AlonzoEraOnwards era
-> (AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
forall era a.
AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
alonzoEraOnwardsConstraints AlonzoEraOnwards era
eon ((AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era))
-> (AlonzoEraOnwardsConstraints era =>
Redeemers (ShelleyLedgerEra era))
-> Redeemers (ShelleyLedgerEra era)
forall a b. (a -> b) -> a -> b
$ [Redeemers (ShelleyLedgerEra era)]
-> Redeemers (ShelleyLedgerEra era)
forall a. Monoid a => [a] -> a
mconcat [Redeemers (ShelleyLedgerEra era)]
redeemerPointers
obtainAlonzoScriptPurposeConstraints
:: AlonzoEraOnwards era
-> ((GetPlutusScriptPurpose era, L.AlonzoEraScript (ShelleyLedgerEra era)) => a)
-> a
obtainAlonzoScriptPurposeConstraints :: forall era a.
AlonzoEraOnwards era
-> ((GetPlutusScriptPurpose era,
AlonzoEraScript (ShelleyLedgerEra era)) =>
a)
-> a
obtainAlonzoScriptPurposeConstraints AlonzoEraOnwards era
v =
case AlonzoEraOnwards era
v of
AlonzoEraOnwards era
AlonzoEraOnwardsAlonzo -> a -> a
((GetPlutusScriptPurpose era,
AlonzoEraScript (ShelleyLedgerEra era)) =>
a)
-> a
forall a. a -> a
id
AlonzoEraOnwards era
AlonzoEraOnwardsBabbage -> a -> a
((GetPlutusScriptPurpose era,
AlonzoEraScript (ShelleyLedgerEra era)) =>
a)
-> a
forall a. a -> a
id
AlonzoEraOnwards era
AlonzoEraOnwardsConway -> a -> a
((GetPlutusScriptPurpose era,
AlonzoEraScript (ShelleyLedgerEra era)) =>
a)
-> a
forall a. a -> a
id