Skip to content

Commit

Permalink
Added 2 arg scripts, and associated helper functions.
Browse files Browse the repository at this point in the history
(pay,stake) script pairs now may have plutus in both parts.
Added the use of plutus scripts in minting as well.
Discards are now traced to avoid silence.
Now we use valueFromList rather than Map.singleton to make Values,
this avoids the introduction of non-canonical values.
Added an example of how to profile a property test.
  • Loading branch information
TimSheard committed Jul 29, 2021
1 parent bc901cc commit ea8f281
Show file tree
Hide file tree
Showing 25 changed files with 550 additions and 192 deletions.
3 changes: 3 additions & 0 deletions alonzo/impl/cardano-ledger-alonzo.cabal
Expand Up @@ -68,6 +68,9 @@ library
mtl,
nothunks,
plutus-ledger-api,
plutus-tx,
plutus-core,
prettyprinter,
serialise,
shelley-spec-ledger,
small-steps,
Expand Down
4 changes: 3 additions & 1 deletion alonzo/impl/src/Cardano/Ledger/Alonzo/Scripts.hs
Expand Up @@ -54,6 +54,7 @@ import Cardano.Ledger.Pretty
ppMap,
ppRational,
ppRecord,
ppScriptHash,
ppSexp,
ppString,
ppWord64,
Expand All @@ -80,6 +81,7 @@ import NoThunks.Class (InspectHeapNamed (..), NoThunks)
import Numeric.Natural (Natural)
import Plutus.V1.Ledger.Api (defaultCostModelParams, validateCostModelParams)
import qualified Plutus.V1.Ledger.Examples as Plutus (alwaysFailingNAryFunction, alwaysSucceedingNAryFunction)
import qualified Prettyprinter as PP

-- | Marker indicating the part of a transaction for which this script is acting
-- as a validator.
Expand Down Expand Up @@ -279,7 +281,7 @@ ppTag x = ppString (show x)
instance PrettyA Tag where prettyA = ppTag

ppScript :: forall era. (ValidateScript era, Core.Script era ~ Script era) => Script era -> PDoc
ppScript (s@(PlutusScript _)) = ppString ("PlutusScript " ++ show (hashScript @era s))
ppScript (s@(PlutusScript _)) = ppString "PlutusScript " PP.<+> ppScriptHash (hashScript @era s)
ppScript (TimelockScript x) = ppTimelock x

instance (ValidateScript era, Core.Script era ~ Script era) => PrettyA (Script era) where prettyA = ppScript
Expand Down
3 changes: 2 additions & 1 deletion alonzo/impl/src/Cardano/Ledger/Alonzo/TxInfo.hs
Expand Up @@ -50,6 +50,7 @@ import qualified Data.Set as Set
import Data.Time.Clock (nominalDiffTimeToSeconds)
import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
import Data.Typeable (Typeable)
import Debug.Trace (trace)
import GHC.Records (HasField (..))
import qualified Plutus.V1.Ledger.Api as P
( Address (..),
Expand Down Expand Up @@ -368,7 +369,7 @@ runPLCScript (CostModel cost) scriptbytestring units ds =
(transExUnits units)
scriptbytestring
ds of
(_, Left _e) -> False -- trace ("\nrunPLC fails "++show _e++"\nData = "++show ds) False
(_, Left _e) -> trace ("\nrunPLC fails " ++ show _e ++ "\nData = " ++ show ds) False
(_, Right ()) -> True

validPlutusdata :: P.Data -> Bool
Expand Down
1 change: 1 addition & 0 deletions alonzo/test/cardano-ledger-alonzo-test.cabal
Expand Up @@ -79,6 +79,7 @@ test-suite cardano-ledger-alonzo-test
Test.Cardano.Ledger.Alonzo.Examples
Test.Cardano.Ledger.Alonzo.Translation
Test.Cardano.Ledger.Alonzo.Serialisation.CDDL
Test.Cardano.Ledger.Alonzo.Trials
build-depends:
base16-bytestring,
bytestring,
Expand Down
110 changes: 72 additions & 38 deletions alonzo/test/lib/Test/Cardano/Ledger/Alonzo/AlonzoEraGen.hs
Expand Up @@ -51,13 +51,14 @@ import Cardano.Ledger.Era (Crypto, Era (..), ValidateScript (..))
import Cardano.Ledger.Hashes (ScriptHash)
import Cardano.Ledger.Keys (KeyHash, KeyRole (Witness))
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Mary.Value (policies)
import Cardano.Ledger.Mary.Value (AssetName (..), PolicyID (..), Value, policies, valueFromList)
import Cardano.Ledger.ShelleyMA.AuxiliaryData as Mary (pattern AuxiliaryData)
import Cardano.Ledger.ShelleyMA.Timelocks (Timelock (..))
import Cardano.Ledger.Val (adaOnly, (<+>), (<×>))
import Cardano.Slotting.Slot (SlotNo (..))
import Control.Iterate.SetAlgebra (eval, (◁))
import Control.Monad (replicateM)
import qualified Data.ByteString.Char8 as BS
import Data.Hashable (Hashable (..))
import qualified Data.List as List
import Data.Map as Map
Expand All @@ -76,15 +77,24 @@ import Shelley.Spec.Ledger.PParams (Update)
import Shelley.Spec.Ledger.TxBody (DCert, TxIn, Wdrl)
import Shelley.Spec.Ledger.UTxO (UTxO (..))
import Test.Cardano.Ledger.AllegraEraGen (genValidityInterval)
import Test.Cardano.Ledger.Alonzo.PlutusScripts (evendata3, guessTheNumber3, odddata3)
import Test.Cardano.Ledger.Alonzo.PlutusScripts
( evenRedeemer2,
evendata3,
guessTheNumber3,
oddRedeemer2,
odddata3,
redeemerIs102,
sumsTo103,
)
import Test.Cardano.Ledger.MaryEraGen (addTokens, genMint, maryGenesisValue, policyIndex)
import Test.QuickCheck hiding ((><))
import Test.Shelley.Spec.Ledger.ConcreteCryptoTypes (Mock)
import Test.Shelley.Spec.Ledger.Generator.Constants (Constants (..))
import Test.Shelley.Spec.Ledger.Generator.Core
( GenEnv (..),
ScriptInfo,
TwoPhaseInfo (..),
TwoPhase2ArgInfo (..),
TwoPhase3ArgInfo (..),
findPlutus,
genNatural,
hashData,
Expand All @@ -93,7 +103,7 @@ import Test.Shelley.Spec.Ledger.Generator.EraGen (EraGen (..), MinGenTxout (..))
import Test.Shelley.Spec.Ledger.Generator.ScriptClass (Quantifier (..), ScriptClass (..))
import Test.Shelley.Spec.Ledger.Generator.Update (genM, genShelleyPParamsDelta)
import qualified Test.Shelley.Spec.Ledger.Generator.Update as Shelley (genPParams)
import Test.Shelley.Spec.Ledger.Generator.Utxo (encodedLen)
import Test.Shelley.Spec.Ledger.Generator.Utxo (encodedLen, myDiscard)
import Test.Shelley.Spec.Ledger.Utils (unsafeBoundRational)

-- ============================================================
Expand All @@ -109,17 +119,37 @@ vKeyLocked txout =
isKeyHashAddr (getField @"address" txout)
&& adaOnly (getField @"value" txout)

phase2scripts :: forall c. Mock c => [TwoPhaseInfo (AlonzoEra c)]
phase2scripts =
[ TwoPhaseInfo (alwaysSucceeds 3) (hashScript @(AlonzoEra c) (alwaysSucceeds 3)) (P.I 1) (P.I 1, bigMem, bigStep),
TwoPhaseInfo (alwaysSucceeds 3) (hashScript @(AlonzoEra c) (alwaysSucceeds 3)) (P.I 1) (P.I 1, bigMem, bigStep),
TwoPhaseInfo (alwaysSucceeds 3) (hashScript @(AlonzoEra c) (alwaysSucceeds 3)) (P.I 1) (P.I 1, bigMem, bigStep),
TwoPhaseInfo (alwaysSucceeds 3) (hashScript @(AlonzoEra c) (alwaysSucceeds 3)) (P.I 1) (P.I 1, bigMem, bigStep),
TwoPhaseInfo guessTheNumber3 (hashScript @(AlonzoEra c) guessTheNumber3) (P.I 9) (P.I 9, bigMem, bigStep),
TwoPhaseInfo evendata3 (hashScript @(AlonzoEra c) evendata3) (P.I 8) (P.I 8, bigMem, bigStep),
TwoPhaseInfo odddata3 (hashScript @(AlonzoEra c) odddata3) (P.I 9) (P.I 9, bigMem, bigStep)
phase2scripts3Arg :: forall c. Mock c => [TwoPhase3ArgInfo (AlonzoEra c)]
phase2scripts3Arg =
[ TwoPhase3ArgInfo (alwaysSucceeds 3) (hashScript @(AlonzoEra c) (alwaysSucceeds 3)) (P.I 1) (P.I 1, bigMem, bigStep),
TwoPhase3ArgInfo guessTheNumber3 (hashScript @(AlonzoEra c) guessTheNumber3) (P.I 9) (P.I 9, bigMem, bigStep),
TwoPhase3ArgInfo evendata3 (hashScript @(AlonzoEra c) evendata3) (P.I 8) (P.I 8, bigMem, bigStep),
TwoPhase3ArgInfo odddata3 (hashScript @(AlonzoEra c) odddata3) (P.I 9) (P.I 9, bigMem, bigStep),
TwoPhase3ArgInfo sumsTo103 (hashScript @(AlonzoEra c) sumsTo103) (P.I 1) (P.I 9, bigMem, bigStep)
]

phase2scripts2Arg :: forall c. Mock c => [TwoPhase2ArgInfo (AlonzoEra c)]
phase2scripts2Arg =
[ TwoPhase2ArgInfo (alwaysSucceeds 2) (hashScript @(AlonzoEra c) (alwaysSucceeds 2)) (P.I 1, bigMem, bigStep),
TwoPhase2ArgInfo oddRedeemer2 (hashScript @(AlonzoEra c) oddRedeemer2) (P.I 13, bigMem, bigStep),
TwoPhase2ArgInfo evenRedeemer2 (hashScript @(AlonzoEra c) evenRedeemer2) (P.I 14, bigMem, bigStep),
TwoPhase2ArgInfo redeemerIs102 (hashScript @(AlonzoEra c) redeemerIs102) (P.I 10, bigMem, bigStep)
]

genPlutus2Arg :: Mock c => Gen (Maybe (TwoPhase2ArgInfo (AlonzoEra c)))
genPlutus2Arg = frequency [(10, Just <$> elements phase2scripts2Arg), (90, pure Nothing)]

-- | Gen a Mint value in the Alonzo Era, with a 10% chance that it includes an AlonzoScript
genAlonzoMint :: Mock c => Value c -> Gen (Value c, [Alonzo.Script (AlonzoEra c)])
genAlonzoMint startvalue = do
ans <- genPlutus2Arg
case ans of
Nothing -> pure (startvalue, [])
Just (TwoPhase2ArgInfo script shash _) -> do
count <- chooseEnum (1, 10)
let assetname = AssetName . BS.pack $ "purple"
pure (((valueFromList 0 [(PolicyID shash, assetname, count)]) <> startvalue), [script])

-- ================================================================

-- | A cost model that sets everything as being free
Expand Down Expand Up @@ -206,11 +236,12 @@ genAlonzoTxBody _genenv utxo pparams currentslot input txOuts certs wdrls fee up
_low <- genM (genSlotAfter currentslot)
_high <- genM (genSlotAfter (currentslot + 50))
netid <- genM $ pure Testnet -- frequency [(2, pure Mainnet), (1, pure Testnet)]
minted <- genMint
startvalue <- genMint
(minted, plutusScripts) <- genAlonzoMint startvalue
let (minted2, txouts2) = case addTokens (Proxy @(AlonzoEra c)) mempty pparams minted txOuts of
Nothing -> (mempty, txOuts)
Just os -> (minted, os)
scriptsFromPolicies = List.map (\p -> (Map.!) policyIndex p) (Set.toList $ policies minted)
scriptsFromPolicies = List.map (\p -> (Map.!) policyIndex p) (Set.toList $ policies startvalue)
txouts3 = fmap addMaybeDataHashToTxOut txouts2
validityInterval <- genValidityInterval currentslot
return
Expand All @@ -230,7 +261,7 @@ genAlonzoTxBody _genenv utxo pparams currentslot input txOuts certs wdrls fee up
(hashWitnessPPData pparams (langsUsed @(AlonzoEra c) Map.empty) (Redeemers Map.empty) (TxDats Map.empty))
auxDHash
netid,
List.map TimelockScript scriptsFromPolicies
(List.map TimelockScript scriptsFromPolicies <> plutusScripts)
)

genSlotAfter :: SlotNo -> Gen SlotNo
Expand Down Expand Up @@ -280,13 +311,14 @@ instance HasField "_minUTxOValue" (Alonzo.PParams (AlonzoEra c)) Coin where
getField _ = Coin 4000

bigStep, bigMem :: Word64
bigStep = 999 -- 9999999990
bigMem = 500 -- 50000000
bigStep = 99999 -- 999 -- 9999999990
bigMem = 50000 -- 500 -- 50000000

instance Mock c => EraGen (AlonzoEra c) where
genEraAuxiliaryData = genAux
genGenesisValue = maryGenesisValue
genEraTwoPhaseScripts = phase2scripts
genEraTwoPhase3Arg = phase2scripts3Arg
genEraTwoPhase2Arg = phase2scripts2Arg

genEraTxBody = genAlonzoTxBody
updateEraTxBody utxo pp witnesses txb coinx txin txout = new
Expand Down Expand Up @@ -331,18 +363,20 @@ instance Mock c => EraGen (AlonzoEra c) where
Just script ->
if isNativeScript @(AlonzoEra c) script
then ans -- Native scripts don't have redeemers
else case Map.lookup hash1 scriptinfo of -- It should be one of the known Plutus Scripts
Nothing -> ans
Just info -> addRedeemMap txbody info purpose ans -- Add it to the redeemer map
else case Map.lookup hash1 (fst scriptinfo) of -- It could be one of the known 3-Arg Plutus Scripts
Just info -> addRedeemMap txbody (getRedeemer3 info) purpose ans -- Add it to the redeemer map
Nothing -> case Map.lookup hash1 (snd scriptinfo) of -- It could be one of the known 2-Arg Plutus Scripts
Just info -> addRedeemMap txbody (getRedeemer2 info) purpose ans -- Add it to the redeemer map
Nothing -> ans

constructTx bod wit auxdata = ValidatedTx bod wit (IsValidating True) auxdata

genEraGoodTxOut = vKeyLocked

genEraScriptCost pp script =
if isPlutusScript script
then case List.find (\info -> (getScript @(AlonzoEra c) info) == script) genEraTwoPhaseScripts of
Just (TwoPhaseInfo _script _hash inputdata (rdmr, mems, steps)) ->
then case List.find (\info -> (getScript3 @(AlonzoEra c) info) == script) genEraTwoPhase3Arg of
Just (TwoPhase3ArgInfo _script _hash inputdata (rdmr, mems, steps)) ->
txscriptfee (getField @"_prices" pp) (ExUnits mems steps)
<+> storageCost 10 pp (rdmr, ExUnits mems steps) -- Extra 10 for the RdmrPtr
<+> storageCost 32 pp inputdata -- Extra 32 for the hash
Expand All @@ -355,28 +389,28 @@ instance Mock c => EraGen (AlonzoEra c) where
theFee = getField @"txfee" txb -- Coin supplied to pay fees
minimumFee = minfee @(AlonzoEra c) pp tx
in if (minimumFee <= theFee)
then pure tx
else discard
then (pure tx)
else myDiscard "MinFeee violation: genEraDne: AlonzoEraGem.hs"

genEraTweakBlock pp txns =
let txTotal, ppMax :: ExUnits
txTotal = Prelude.foldr (<>) mempty (fmap totExUnits txns)
ppMax = getField @"_maxBlockExUnits" pp
in if pointWiseExUnits (<=) txTotal ppMax
then pure txns
else discard
else myDiscard "TotExUnits violation: genEraTweakBlock: AlonzoEraGem.hs"

storageCost :: ToCBOR t => Integer -> (Alonzo.PParams era) -> t -> Coin
storageCost extra pp x = (extra + encodedLen x) <×> Coin (fromIntegral (getField @"_minfeeA" pp))

addRedeemMap ::
forall c.
TxBody (AlonzoEra c) ->
TwoPhaseInfo (AlonzoEra c) ->
(Plutus.Data, Word64, Word64) ->
ScriptPurpose c ->
Map RdmrPtr (Data (AlonzoEra c), ExUnits) ->
Map RdmrPtr (Data (AlonzoEra c), ExUnits)
addRedeemMap body1 (TwoPhaseInfo _ _ _ (dat, space, steps)) purpose ans =
addRedeemMap body1 (dat, space, steps) purpose ans =
case (purpose, rdptr @(AlonzoEra c) body1 purpose) of
(Spending _, SJust ptr) -> Map.insert ptr (Data dat, ExUnits space steps) ans
(Minting _, SJust ptr) -> Map.insert ptr (Data dat, ExUnits space steps) ans
Expand All @@ -385,12 +419,12 @@ addRedeemMap body1 (TwoPhaseInfo _ _ _ (dat, space, steps)) purpose ans =
_ -> ans

getDataMap :: forall era. Era era => ScriptInfo era -> Map (ScriptHash (Crypto era)) (Core.Script era) -> Map (DataHash (Crypto era)) (Data era)
getDataMap scriptinfo scrips = Map.foldlWithKey' accum Map.empty scrips
getDataMap (scriptinfo3, _) scrips = Map.foldlWithKey' accum Map.empty scrips
where
accum ans hsh _script =
case Map.lookup hsh scriptinfo of
case Map.lookup hsh scriptinfo3 of
Nothing -> ans
Just (TwoPhaseInfo _script _hash dat _redeem) -> Map.insert (hashData @era dat) (Data dat) ans
Just (TwoPhase3ArgInfo _script _hash dat _redeem) -> Map.insert (hashData @era dat) (Data dat) ans

instance Mock c => MinGenTxout (AlonzoEra c) where
calcEraMinUTxO tout pp = (utxoEntrySize tout <×> getField @"_coinsPerUTxOWord" pp)
Expand All @@ -404,24 +438,24 @@ instance Mock c => MinGenTxout (AlonzoEra c) where
pure (zipWith makeTxOut addrs values)

-- | If an Address is script address, we can find a potential data hash for it from
-- genEraTwoPhaseScripts, which contains all known plutus scripts in the tests set.
-- genEraTwoPhase3Arg, which contains all known 3 arg plutus scripts in the tests set.
-- If the script has is not in that map, then its data hash is SNothing.
dataFromAddr :: forall c. Mock c => Addr c -> StrictMaybe (DataHash c)
dataFromAddr (Addr _network (ScriptHashObj shash) _stakeref) =
case List.find (\info -> shash == hashScript @(AlonzoEra c) (getScript @(AlonzoEra c) info)) genEraTwoPhaseScripts of
Just info -> SJust (hashData @(AlonzoEra c) (getData info))
case List.find (\info -> shash == hashScript @(AlonzoEra c) (getScript3 @(AlonzoEra c) info)) genEraTwoPhase3Arg of
Just info -> SJust (hashData @(AlonzoEra c) (getData3 info))
Nothing -> SNothing
dataFromAddr _ = SNothing

-- | We can find the data associated with the data hashes in the TxOuts, since
-- genEraTwoPhaseScripts, which contains all known plutus scripts stores the data.
-- genEraTwoPhase3Arg, which contains all known 3 arg plutus scripts stores the data.
dataMapFromTxOut :: forall c. Mock c => [TxOut (AlonzoEra c)] -> TxDats (AlonzoEra c) -> TxDats (AlonzoEra c)
dataMapFromTxOut txouts datahashmap = Prelude.foldl accum datahashmap txouts
where
accum !ans (TxOut _ _ SNothing) = ans
accum !ans (TxOut _ _ (SJust dhash)) =
case List.find (\info -> hashData @(AlonzoEra c) (getData info) == dhash) (genEraTwoPhaseScripts @(AlonzoEra c)) of
Just info -> let TxDats' m = ans in TxDats (Map.insert dhash (Data (getData info)) m)
case List.find (\info -> hashData @(AlonzoEra c) (getData3 info) == dhash) (genEraTwoPhase3Arg @(AlonzoEra c)) of
Just info -> let TxDats' m = ans in TxDats (Map.insert dhash (Data (getData3 info)) m)
Nothing -> ans

addMaybeDataHashToTxOut :: Mock c => TxOut (AlonzoEra c) -> TxOut (AlonzoEra c)
Expand Down
70 changes: 66 additions & 4 deletions alonzo/test/lib/Test/Cardano/Ledger/Alonzo/PlutusScripts.hs
Expand Up @@ -135,9 +135,9 @@ oddRedeemer3 =
sumsTo10'_0 :: PlutusTx.Builtins.Internal.BuiltinData ->
PlutusTx.Builtins.Internal.BuiltinData ->
PlutusTx.Builtins.Internal.BuiltinData -> ()
sumsTo10'_0 d1_1 d2_2 _d3_3 = let {m_4 = PlutusTx.Builtins.unsafeDataAsI d1_1;
n_5 = PlutusTx.Builtins.unsafeDataAsI d2_2}
in if (m_4 PlutusTx.Numeric.+ n_5) PlutusTx.Eq.== 10
sumsTo10'_0 d1_1 d2_2 _d3_3 = let {n_4 = PlutusTx.Builtins.unsafeDataAsI d1_1;
m_5 = PlutusTx.Builtins.unsafeDataAsI d2_2}
in if (m_5 PlutusTx.Numeric.+ n_4) PlutusTx.Eq.== 10
then GHC.Tuple.()
else PlutusTx.Builtins.error GHC.Tuple.()
-}
Expand All @@ -147,9 +147,71 @@ sumsTo103 =
(PlutusScript . pack . concat)
[ [88, 102, 1, 0, 0, 50, 51, 50, 34, 50, 50, 50, 50, 51, 34],
[50, 50, 50, 0, 18, 34, 51, 53, 48, 12, 51, 53, 0, 144, 11],
[51, 53, 0, 160, 15, 48, 4, 0, 51, 0, 64, 2, 72, 5, 8],
[51, 53, 0, 160, 15, 48, 4, 0, 35, 0, 64, 3, 72, 5, 8],
[2, 8, 212, 1, 128, 32, 1, 200, 221, 96, 0, 137, 26, 128, 33],
[169, 128, 16, 0, 164, 194, 64, 2, 64, 2, 36, 194, 64, 2, 36],
[0, 36, 70, 102, 174, 84, 205, 196, 128, 16, 0, 128, 40, 2, 9],
[16, 1, 9, 16, 0, 144, 0, 145, 25, 184, 0, 2, 0, 17]
]

{- Preproceesed Plutus Script
oddRedeemer2'_0 :: PlutusTx.Builtins.Internal.BuiltinData ->
PlutusTx.Builtins.Internal.BuiltinData -> ()
oddRedeemer2'_0 d1_1 _d3_2 = let n_3 = PlutusTx.Builtins.unsafeDataAsI d1_1
in if PlutusTx.Prelude.modulo n_3 2 PlutusTx.Eq.== 1
then GHC.Tuple.()
else PlutusTx.Builtins.error GHC.Tuple.()
-}

oddRedeemer2 :: Script era
oddRedeemer2 =
(PlutusScript . pack . concat)
[ [88, 94, 1, 0, 0, 51, 50, 34, 50, 50, 50, 51, 34, 50, 50],
[50, 50, 0, 18, 35, 51, 83, 0, 179, 51, 80, 9, 0, 163, 48],
[4, 48, 3, 0, 36, 128, 17, 32, 2, 32, 8, 35, 80, 6, 0],
[128, 7, 35, 117, 128, 2, 68, 102, 228, 128, 8, 0, 68, 141, 64],
[16, 212, 192, 8, 0, 82, 97, 32, 1, 32, 1, 18, 97, 32, 1],
[34, 51, 53, 114, 166, 110, 36, 0, 128, 4, 1, 64, 16, 72, 128],
[8, 72, 128, 4, 128, 5]
]

{- Preproceesed Plutus Script
evenRedeemer2'_0 :: PlutusTx.Builtins.Internal.BuiltinData ->
PlutusTx.Builtins.Internal.BuiltinData -> ()
evenRedeemer2'_0 d1_1 _d3_2 = let n_3 = PlutusTx.Builtins.unsafeDataAsI d1_1
in if PlutusTx.Prelude.modulo n_3 2 PlutusTx.Eq.== 0
then GHC.Tuple.()
else PlutusTx.Builtins.error GHC.Tuple.()
-}

evenRedeemer2 :: Script era
evenRedeemer2 =
(PlutusScript . pack . concat)
[ [88, 94, 1, 0, 0, 51, 50, 34, 50, 50, 50, 51, 34, 50, 50],
[50, 50, 0, 18, 35, 51, 83, 0, 179, 51, 80, 9, 0, 163, 48],
[4, 48, 3, 0, 36, 128, 17, 32, 0, 32, 8, 35, 80, 6, 0],
[128, 7, 35, 117, 128, 2, 68, 102, 228, 128, 8, 0, 68, 141, 64],
[16, 212, 192, 8, 0, 82, 97, 32, 1, 32, 1, 18, 97, 32, 1],
[34, 51, 53, 114, 166, 110, 36, 0, 128, 4, 1, 64, 16, 72, 128],
[8, 72, 128, 4, 128, 5]
]

{- Preproceesed Plutus Script
redeemerIs102'_0 :: PlutusTx.Builtins.Internal.BuiltinData ->
PlutusTx.Builtins.Internal.BuiltinData -> ()
redeemerIs102'_0 d1_1 _d3_2 = let n_3 = PlutusTx.Builtins.unsafeDataAsI d1_1
in if n_3 PlutusTx.Eq.== 10
then GHC.Tuple.()
else PlutusTx.Builtins.error GHC.Tuple.()
-}

redeemerIs102 :: Script era
redeemerIs102 =
(PlutusScript . pack . concat)
[ [88, 82, 1, 0, 0, 51, 50, 34, 50, 50, 50, 51, 34, 50, 50],
[50, 0, 18, 35, 51, 83, 0, 163, 51, 80, 8, 0, 147, 0, 48],
[2, 72, 5, 8, 1, 200, 212, 1, 64, 28, 1, 136, 221, 96, 0],
[137, 26, 128, 33, 169, 128, 16, 0, 164, 194, 64, 2, 64, 2, 36],
[194, 64, 2, 68, 102, 106, 229, 76, 220, 72, 1, 0, 8, 2, 128],
[32, 145, 0, 16, 145, 0, 9, 0, 9]
]

0 comments on commit ea8f281

Please sign in to comment.