Skip to content
This repository has been archived by the owner on Dec 2, 2024. It is now read-only.

PLT-738: Include plutus language versions with scripts #681

Merged
merged 3 commits into from
Aug 31, 2022
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 2 additions & 1 deletion playground-common/src/PSGenerator/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ import Ledger.Interval (Extended, Interval, LowerBound, UpperBound)
import Ledger.Scripts (ScriptError)
import Ledger.Slot (Slot)
import Ledger.TimeSlot (SlotConfig, SlotConversionError)
import Ledger.Tx qualified as Tx (Language)
import Ledger.Tx qualified as Tx (Language, Versioned)
import Ledger.Tx.CardanoAPI (FromCardanoError, ToCardanoError)
import Ledger.Value (AssetClass, CurrencySymbol, TokenName, Value)
import Playground.Types (ContractCall, FunctionSchema, KnownCurrency)
Expand Down Expand Up @@ -336,6 +336,7 @@ scriptAnyLangType = SumType (
ledgerTypes :: [SumType 'Haskell]
ledgerTypes =
[ order . genericShow . argonaut $ mkSumType @Tx.Language
, order . genericShow . argonaut $ mkSumType @(Tx.Versioned A)
, equal . genericShow . argonaut $ mkSumType @Slot
, equal . genericShow . argonaut $ mkSumType @Ada
, equal . genericShow . argonaut $ mkSumType @SlotConfig
Expand Down
8 changes: 4 additions & 4 deletions plutus-chain-index-core/src/Plutus/ChainIndex/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ import Data.Proxy (Proxy (..))
import GHC.Generics (Generic)
import Ledger (AssetClass, TxId)
import Ledger.Credential (Credential)
import Ledger.Tx (ChainIndexTxOut, TxOutRef)
import Ledger.Tx (ChainIndexTxOut, TxOutRef, Versioned)
import Plutus.ChainIndex.Tx (ChainIndexTx)
import Plutus.ChainIndex.Types (Diagnostics, Tip)
import Plutus.V1.Ledger.Api (Datum, DatumHash, MintingPolicy, MintingPolicyHash, Redeemer, RedeemerHash, StakeValidator,
Expand Down Expand Up @@ -186,9 +186,9 @@ type API

type FromHashAPI =
"datum" :> Description "Get a datum from its hash." :> ReqBody '[JSON] DatumHash :> Post '[JSON] Datum
:<|> "validator" :> Description "Get a validator script from its hash." :> ReqBody '[JSON] ValidatorHash :> Post '[JSON] Validator
:<|> "minting-policy" :> Description "Get a minting policy from its hash." :> ReqBody '[JSON] MintingPolicyHash :> Post '[JSON] MintingPolicy
:<|> "stake-validator" :> Description "Get a stake validator from its hash." :> ReqBody '[JSON] StakeValidatorHash :> Post '[JSON] StakeValidator
:<|> "validator" :> Description "Get a validator script from its hash." :> ReqBody '[JSON] ValidatorHash :> Post '[JSON] (Versioned Validator)
:<|> "minting-policy" :> Description "Get a minting policy from its hash." :> ReqBody '[JSON] MintingPolicyHash :> Post '[JSON] (Versioned MintingPolicy)
:<|> "stake-validator" :> Description "Get a stake validator from its hash." :> ReqBody '[JSON] StakeValidatorHash :> Post '[JSON] (Versioned StakeValidator)
:<|> "redeemer" :> Description "Get a redeemer from its hash." :> ReqBody '[JSON] RedeemerHash :> Post '[JSON] Redeemer

type SwaggerAPI = "swagger" :> SwaggerSchemaUI "swagger-ui" "swagger.json"
Expand Down
8 changes: 4 additions & 4 deletions plutus-chain-index-core/src/Plutus/ChainIndex/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ import Control.Monad.Freer.Reader (Reader, ask)
import Control.Monad.IO.Class (MonadIO (..))
import Data.Proxy (Proxy (..))
import Ledger (TxId)
import Ledger.Tx (ChainIndexTxOut, TxOutRef)
import Ledger.Tx (ChainIndexTxOut, TxOutRef, Versioned)
import Network.HTTP.Types.Status (Status (..))
import Plutus.ChainIndex.Api (API, IsUtxoResponse, QueryAtAddressRequest (QueryAtAddressRequest), QueryResponse,
TxoAtAddressRequest (TxoAtAddressRequest), TxosResponse,
Expand All @@ -52,9 +52,9 @@ collectGarbage :: ClientM NoContent

-- TODO: Catch 404 error
getDatum :: DatumHash -> ClientM Datum
getValidator :: ValidatorHash -> ClientM Validator
getMintingPolicy :: MintingPolicyHash -> ClientM MintingPolicy
getStakeValidator :: StakeValidatorHash -> ClientM StakeValidator
getValidator :: ValidatorHash -> ClientM (Versioned Validator)
getMintingPolicy :: MintingPolicyHash -> ClientM (Versioned MintingPolicy)
getStakeValidator :: StakeValidatorHash -> ClientM (Versioned StakeValidator)
getRedeemer :: RedeemerHash -> ClientM Redeemer

getTxOut :: TxOutRef -> ClientM ChainIndexTxOut
Expand Down
14 changes: 7 additions & 7 deletions plutus-chain-index-core/src/Plutus/ChainIndex/DbSchema.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Database.Beam (Beamable, Columnar, Database, DatabaseSettings, FromBacken
import Database.Beam.Migrate (CheckedDatabaseSettings, defaultMigratableDbSettings, renameCheckedEntity,
unCheckDatabase)
import Database.Beam.Sqlite (Sqlite)
import Ledger (BlockId (..), ChainIndexTxOut (..), Slot)
import Ledger (BlockId (..), ChainIndexTxOut (..), Slot, Versioned)
import Plutus.ChainIndex.Tx (ChainIndexTx)
import Plutus.ChainIndex.Tx qualified as CI
import Plutus.ChainIndex.Types (BlockNumber (..), Tip (..))
Expand Down Expand Up @@ -257,17 +257,17 @@ instance Serialise a => HasDbType (Serialisable a) where
toDbValue = BSL.toStrict . serialise . getSerialisable

deriving via Serialisable Datum instance HasDbType Datum
deriving via Serialisable MintingPolicy instance HasDbType MintingPolicy
deriving via Serialisable Redeemer instance HasDbType Redeemer
deriving via Serialisable StakeValidator instance HasDbType StakeValidator
deriving via Serialisable Validator instance HasDbType Validator
deriving via Serialisable (Versioned MintingPolicy) instance HasDbType (Versioned MintingPolicy)
deriving via Serialisable (Versioned StakeValidator) instance HasDbType (Versioned StakeValidator)
deriving via Serialisable (Versioned Validator) instance HasDbType (Versioned Validator)
deriving via Serialisable (Versioned Script) instance HasDbType (Versioned Script)
deriving via Serialisable ChainIndexTx instance HasDbType ChainIndexTx
deriving via Serialisable ChainIndexTxOut instance HasDbType ChainIndexTxOut
deriving via Serialisable TxOutRef instance HasDbType TxOutRef
deriving via Serialisable CI.ChainIndexTxOut instance HasDbType CI.ChainIndexTxOut
deriving via Serialisable Credential instance HasDbType Credential
deriving via Serialisable AssetClass instance HasDbType AssetClass
deriving via Serialisable Script instance HasDbType Script

instance HasDbType Slot where
type DbType Slot = Word64 -- In Plutus Slot is Integer, but in the Cardano API it is Word64, so this is safe
Expand All @@ -291,8 +291,8 @@ instance HasDbType (DatumHash, Datum) where
toDbValue (hash, datum) = DatumRow (toDbValue hash) (toDbValue datum)
fromDbValue (DatumRow hash datum) = (fromDbValue hash, fromDbValue datum)

instance HasDbType (ScriptHash, Script) where
type DbType (ScriptHash, Script) = ScriptRow
instance HasDbType (ScriptHash, Versioned Script) where
type DbType (ScriptHash, Versioned Script) = ScriptRow
toDbValue (hash, script) = ScriptRow (toDbValue hash) (toDbValue script)
fromDbValue (ScriptRow hash script) = (fromDbValue hash, fromDbValue script)

Expand Down
8 changes: 4 additions & 4 deletions plutus-chain-index-core/src/Plutus/ChainIndex/Effects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import Control.Monad.Freer.Extras.Pagination (PageQuery)
import Control.Monad.Freer.TH (makeEffect)
import Ledger (AssetClass, TxId)
import Ledger.Credential (Credential)
import Ledger.Tx (ChainIndexTxOut, TxOutRef)
import Ledger.Tx (ChainIndexTxOut, TxOutRef, Versioned)
import Plutus.ChainIndex.Api (IsUtxoResponse, QueryResponse, TxosResponse, UtxosResponse)
import Plutus.ChainIndex.Tx (ChainIndexTx)
import Plutus.ChainIndex.Types (ChainSyncBlock, Diagnostics, Point, Tip)
Expand All @@ -47,16 +47,16 @@ data ChainIndexQueryEffect r where
DatumFromHash :: DatumHash -> ChainIndexQueryEffect (Maybe Datum)

-- | Get the validator from a validator hash (if available)
ValidatorFromHash :: ValidatorHash -> ChainIndexQueryEffect (Maybe Validator)
ValidatorFromHash :: ValidatorHash -> ChainIndexQueryEffect (Maybe (Versioned Validator))

-- | Get the monetary policy from an MPS hash (if available)
MintingPolicyFromHash :: MintingPolicyHash -> ChainIndexQueryEffect (Maybe MintingPolicy)
MintingPolicyFromHash :: MintingPolicyHash -> ChainIndexQueryEffect (Maybe (Versioned MintingPolicy))

-- | Get the redeemer from a redeemer hash (if available)
RedeemerFromHash :: RedeemerHash -> ChainIndexQueryEffect (Maybe Redeemer)

-- | Get the stake validator from a stake validator hash (if available)
StakeValidatorFromHash :: StakeValidatorHash -> ChainIndexQueryEffect (Maybe StakeValidator)
StakeValidatorFromHash :: StakeValidatorHash -> ChainIndexQueryEffect (Maybe (Versioned StakeValidator))

-- | Get the TxOut from a TxOutRef (if available)
UnspentTxOutFromRef :: TxOutRef -> ChainIndexQueryEffect (Maybe ChainIndexTxOut)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ import Data.Set qualified as Set
import GHC.Generics (Generic)
import Ledger.Ada qualified as Ada
import Ledger.Credential (Credential)
import Ledger.Tx (Versioned)
import Plutus.ChainIndex.Tx (ChainIndexTx, ChainIndexTxOut (..), citxData, citxScripts, citxTxId, txOutsWithRef,
txRedeemersWithHash)
import Plutus.ChainIndex.Types (Diagnostics (..))
Expand Down Expand Up @@ -122,7 +123,7 @@ txAssetClassMap =
data DiskState =
DiskState
{ _DataMap :: Map DatumHash Datum
, _ScriptMap :: Map ScriptHash Script
, _ScriptMap :: Map ScriptHash (Versioned Script)
, _RedeemerMap :: Map RedeemerHash Redeemer
, _TxMap :: Map TxId ChainIndexTx
, _AddressMap :: CredentialMap
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ import Data.Set qualified as Set
import GHC.Generics (Generic)
import Ledger.Address (Address (addressCredential))
import Ledger.Scripts (ScriptHash (ScriptHash))
import Ledger.Tx (TxId, TxOutRef (..))
import Ledger.Tx (TxId, TxOutRef (..), Versioned)
import Ledger.Tx qualified as L (ChainIndexTxOut (PublicKeyChainIndexTxOut, ScriptChainIndexTxOut))
import Plutus.ChainIndex.Api (IsUtxoResponse (IsUtxoResponse), QueryResponse (QueryResponse),
TxosResponse (TxosResponse), UtxosResponse (UtxosResponse))
Expand Down Expand Up @@ -83,7 +83,7 @@ getScriptFromHash ::
( Member (State ChainIndexEmulatorState) effs
)
=> ScriptHash
-> Eff effs (Maybe Script)
-> Eff effs (Maybe (Versioned Script))
getScriptFromHash h = gets (view $ diskState . scriptMap . at h)

-- | Get the 'ChainIndexTx' for a transaction ID
Expand Down Expand Up @@ -147,7 +147,7 @@ makeChainIndexTxOut txout@(ChainIndexTxOut address value datum refScript) = do
case datumWithHash of
Just d -> do
v <- getScriptFromHash (ScriptHash h)
pure $ Just $ L.ScriptChainIndexTxOut address value d script (ValidatorHash h, Validator <$> v)
pure $ Just $ L.ScriptChainIndexTxOut address value d script (ValidatorHash h, fmap Validator <$> v)
Nothing -> do
-- If the txout comes from a script address, the Datum should not be Nothing
logWarn $ NoDatumScriptAddr txout
Expand Down Expand Up @@ -196,11 +196,11 @@ handleQuery ::
handleQuery = \case
DatumFromHash h -> getDatumFromHash h
ValidatorFromHash (ValidatorHash h) -> do
fmap (fmap Validator) $ getScriptFromHash (ScriptHash h)
fmap (fmap Validator) <$> getScriptFromHash (ScriptHash h)
MintingPolicyFromHash (MintingPolicyHash h) ->
fmap (fmap MintingPolicy) $ getScriptFromHash (ScriptHash h)
fmap (fmap MintingPolicy) <$> getScriptFromHash (ScriptHash h)
StakeValidatorFromHash (StakeValidatorHash h) ->
fmap (fmap StakeValidator) $ getScriptFromHash (ScriptHash h)
fmap (fmap StakeValidator) <$> getScriptFromHash (ScriptHash h)
UnspentTxOutFromRef ref -> getTxOutFromRef ref
TxOutFromRef ref -> getTxOutFromRef ref
RedeemerFromHash h -> gets (view $ diskState . redeemerMap . at h)
Expand Down
23 changes: 11 additions & 12 deletions plutus-chain-index-core/src/Plutus/ChainIndex/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
{-| The chain index' version of a transaction
-}
module Plutus.ChainIndex.Tx(
Expand Down Expand Up @@ -48,10 +49,9 @@ import Ledger (OnChainTx (..), SomeCardanoApiTx (SomeTx), Tx (..), TxIn (..), Tx
import Ledger.Tx.CardanoAPI (toCardanoTxOut, toCardanoTxOutDatumHash)
import Plutus.ChainIndex.Types
import Plutus.Contract.CardanoAPI (fromCardanoTx, fromCardanoTxOut, setValidity)
import Plutus.Script.Utils.Scripts (datumHash, redeemerHash)
import Plutus.Script.Utils.V1.Scripts (validatorHash)
import Plutus.Script.Utils.Scripts (Versioned, datumHash, redeemerHash, scriptHash)
import Plutus.V1.Ledger.Api (Datum, DatumHash, MintingPolicy (getMintingPolicy), MintingPolicyHash (MintingPolicyHash),
Redeemer, RedeemerHash, Script, Validator (getValidator), ValidatorHash (ValidatorHash))
Redeemer, RedeemerHash, Script, Validator (getValidator))
import Plutus.V1.Ledger.Scripts (ScriptHash (ScriptHash))
import Plutus.V1.Ledger.Tx (RedeemerPtr (RedeemerPtr), Redeemers, ScriptTag (Spend))
import Plutus.V2.Ledger.Api (Address (..), OutputDatum (..), Value (..))
Expand Down Expand Up @@ -123,24 +123,23 @@ fromOnChainCardanoTx :: Bool -> SomeCardanoApiTx -> ChainIndexTx
fromOnChainCardanoTx validity (SomeTx tx era) =
either (error . ("Plutus.ChainIndex.Tx.fromOnChainCardanoTx: " ++) . show) id $ fromCardanoTx era $ setValidity validity tx

mintingPolicies :: Map MintingPolicyHash MintingPolicy -> Map ScriptHash Script
mintingPolicies :: Map MintingPolicyHash (Versioned MintingPolicy) -> Map ScriptHash (Versioned Script)
mintingPolicies = Map.fromList . fmap toScript . Map.toList
where
toScript (MintingPolicyHash mph, mp) = (ScriptHash mph, getMintingPolicy mp)
toScript (MintingPolicyHash mph, mp) = (ScriptHash mph, fmap getMintingPolicy mp)

validators :: [TxIn] -> (Map ScriptHash Script, Map DatumHash Datum, Redeemers)
validators :: [TxIn] -> (Map ScriptHash (Versioned Script), Map DatumHash Datum, Redeemers)
validators = foldMap (\(ix, txIn) -> maybe mempty (withHash ix) $ txInType txIn) . zip [0..] . sort
-- we sort the inputs to make sure that the indices match with redeemer pointers
where
-- TODO: the index of the txin is probably incorrect as we take it from the set.
-- To determine the proper index we have to convert the plutus's `TxIn` to cardano-api `TxIn` and
-- sort them by using the standard `Ord` instance.
withHash ix (ConsumeScriptAddress _lang val red dat) =
let (ValidatorHash vh) = validatorHash val
in ( Map.singleton (ScriptHash vh) (getValidator val)
, Map.singleton (datumHash dat) dat
, Map.singleton (RedeemerPtr Spend ix) red
)
withHash ix (ConsumeScriptAddress (fmap getValidator -> val) red dat) =
( Map.singleton (scriptHash val) val
, Map.singleton (datumHash dat) dat
, Map.singleton (RedeemerPtr Spend ix) red
)
withHash _ _ = mempty

txRedeemersWithHash :: ChainIndexTx -> Map RedeemerHash Redeemer
Expand Down
8 changes: 4 additions & 4 deletions plutus-chain-index-core/src/Plutus/ChainIndex/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ import Data.Set (Set)
import Data.Set qualified as Set
import Data.Word (Word64)
import GHC.Generics (Generic)
import Ledger (Address, SlotRange, SomeCardanoApiTx, TxIn (..), TxOutRef (..))
import Ledger (Address, SlotRange, SomeCardanoApiTx, TxIn (..), TxOutRef (..), Versioned)
import Ledger.Blockchain (BlockId (..))
import Ledger.Blockchain qualified as Ledger
import Ledger.Slot (Slot)
Expand Down Expand Up @@ -142,9 +142,9 @@ instance Serialise C.ScriptInAnyLang where
instance OpenApi.ToSchema C.ScriptInAnyLang where
declareNamedSchema _ = pure $ OpenApi.NamedSchema (Just "ScriptInAnyLang") mempty

fromReferenceScript :: ReferenceScript -> Maybe Script
fromReferenceScript :: ReferenceScript -> Maybe (Versioned Script)
fromReferenceScript ReferenceScriptNone = Nothing
fromReferenceScript (ReferenceScriptInAnyLang sial) = fst <$> fromCardanoScriptInAnyLang sial
fromReferenceScript (ReferenceScriptInAnyLang sial) = fromCardanoScriptInAnyLang sial

data ChainIndexTxOut = ChainIndexTxOut
{ citoAddress :: Address -- ^ We can't use AddressInAnyEra here because of missing FromJson instance for Byron era
Expand Down Expand Up @@ -196,7 +196,7 @@ data ChainIndexTx = ChainIndexTx {
-- ^ Datum objects recorded on this transaction.
_citxRedeemers :: Redeemers,
-- ^ Redeemers of the minting scripts.
_citxScripts :: Map ScriptHash Script,
_citxScripts :: Map ScriptHash (Versioned Script),
-- ^ The scripts (validator, stake validator or minting) part of cardano tx.
_citxCardanoTx :: Maybe SomeCardanoApiTx
-- ^ The full Cardano API tx which was used to populate the rest of the
Expand Down
8 changes: 4 additions & 4 deletions plutus-contract/src/Plutus/Contract/Effects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ import Ledger.Scripts (Validator)
import Ledger.Slot (Slot, SlotRange)
import Ledger.Time (POSIXTime, POSIXTimeRange)
import Ledger.TimeSlot (SlotConversionError)
import Ledger.Tx (CardanoTx, ChainIndexTxOut, getCardanoTxId, onCardanoTx)
import Ledger.Tx (CardanoTx, ChainIndexTxOut, Versioned, getCardanoTxId, onCardanoTx)
import Plutus.ChainIndex (Page (pageItems), PageQuery)
import Plutus.ChainIndex.Api (IsUtxoResponse (IsUtxoResponse), QueryResponse (QueryResponse),
TxosResponse (TxosResponse), UtxosResponse (UtxosResponse))
Expand Down Expand Up @@ -288,9 +288,9 @@ instance Pretty ChainIndexQuery where
-- responses come from the data type 'Plutus.ChainIndex.Effects.ChainIndexQueryEffect'.
data ChainIndexResponse =
DatumHashResponse (Maybe Datum)
| ValidatorHashResponse (Maybe Validator)
| MintingPolicyHashResponse (Maybe MintingPolicy)
| StakeValidatorHashResponse (Maybe StakeValidator)
| ValidatorHashResponse (Maybe (Versioned Validator))
| MintingPolicyHashResponse (Maybe (Versioned MintingPolicy))
| StakeValidatorHashResponse (Maybe (Versioned StakeValidator))
| TxOutRefResponse (Maybe ChainIndexTxOut)
| UnspentTxOutResponse (Maybe ChainIndexTxOut)
| RedeemerHashResponse (Maybe Redeemer)
Expand Down
8 changes: 4 additions & 4 deletions plutus-contract/src/Plutus/Contract/Request.hs
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ import Ledger (AssetClass, DiffMilliSeconds, POSIXTime, PaymentPubKeyHash (Payme
import Ledger.Constraints (TxConstraints)
import Ledger.Constraints.OffChain (ScriptLookups, UnbalancedTx)
import Ledger.Constraints.OffChain qualified as Constraints
import Ledger.Tx (CardanoTx, ChainIndexTxOut, ciTxOutValue, getCardanoTxId)
import Ledger.Tx (CardanoTx, ChainIndexTxOut, Versioned, ciTxOutValue, getCardanoTxId)
import Ledger.Typed.Scripts (Any, TypedValidator, ValidatorTypes (DatumType, RedeemerType))
import Ledger.Value qualified as V
import Plutus.Contract.Util (loopM)
Expand Down Expand Up @@ -315,7 +315,7 @@ validatorFromHash ::
( AsContractError e
)
=> ValidatorHash
-> Contract w s e (Maybe Validator)
-> Contract w s e (Maybe (Versioned Validator))
validatorFromHash h = do
cir <- pabReq (ChainIndexQueryReq $ E.ValidatorFromHash h) E._ChainIndexQueryResp
case cir of
Expand All @@ -327,7 +327,7 @@ mintingPolicyFromHash ::
( AsContractError e
)
=> MintingPolicyHash
-> Contract w s e (Maybe MintingPolicy)
-> Contract w s e (Maybe (Versioned MintingPolicy))
mintingPolicyFromHash h = do
cir <- pabReq (ChainIndexQueryReq $ E.MintingPolicyFromHash h) E._ChainIndexQueryResp
case cir of
Expand All @@ -339,7 +339,7 @@ stakeValidatorFromHash ::
( AsContractError e
)
=> StakeValidatorHash
-> Contract w s e (Maybe StakeValidator)
-> Contract w s e (Maybe (Versioned StakeValidator))
stakeValidatorFromHash h = do
cir <- pabReq (ChainIndexQueryReq $ E.StakeValidatorFromHash h) E._ChainIndexQueryResp
case cir of
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -314,8 +314,8 @@ isVulnerable (DoubleSatisfactionCounterexample orig pre post _ _ _) =
-- a specific datum attached. Even though this doesn't technically matter.
--
-- This is not super important, but we want to leave no room for misunderstanding...
alwaysOkValidator :: Validator
alwaysOkValidator = mkValidatorScript $$(PlutusTx.compile [|| (\_ _ _ -> ()) ||])
alwaysOkValidator :: Versioned Validator
alwaysOkValidator = Versioned (mkValidatorScript $$(PlutusTx.compile [|| (\_ _ _ -> ()) ||])) PlutusV1

doubleSatisfactionCounterexamples :: WrappedTx -> [DoubleSatisfactionCounterexample]
doubleSatisfactionCounterexamples dsc =
Expand Down Expand Up @@ -357,8 +357,7 @@ doubleSatisfactionCounterexamples dsc =
, txOutRefIdx = 1
}
newFakeTxIn = TxIn { txInRef = newFakeTxOutRef
, txInType = Just $ ConsumeScriptAddress PlutusV1
alwaysOkValidator
, txInType = Just $ ConsumeScriptAddress alwaysOkValidator
redeemerEmpty
datumEmpty
}
Expand Down
Loading