Skip to content

Commit

Permalink
Add a 3rd Plutus end-to-end scenario
Browse files Browse the repository at this point in the history
  This 3rd scenarios exercises two components of the transaction workflow: minting and burning of tokens (automatically detected from the transaction context), as well as, required signatures from a transaction (field #14), that are necessary here to execute the minting / burning policy. The policy itself is a template which requires a verification key hash and validates if the minting/burning transaction is signed by the sk corresponding to that key hash. When executing the scenario, the vk is pulled from the wallet known keys, and added as required signers to the transaction so that the wallet produces a signature for that key regardless of whether it is needed for an input.
  • Loading branch information
KtorZ committed Oct 14, 2021
1 parent d94ad3f commit da99c76
Show file tree
Hide file tree
Showing 5 changed files with 158 additions and 21 deletions.
26 changes: 22 additions & 4 deletions lib/core-integration/src/Test/Integration/Framework/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,6 +84,7 @@ module Test.Integration.Framework.DSL
, getSharedWalletKey
, postAccountKeyShared
, getAccountKeyShared
, getSomeVerificationKey

-- * Wallet helpers
, listFilteredWallets
Expand Down Expand Up @@ -249,6 +250,7 @@ import Cardano.Wallet.Api.Types
, ApiTxId (ApiTxId)
, ApiUtxoStatistics (..)
, ApiVerificationKeyShared
, ApiVerificationKeyShelley (..)
, ApiWallet
, ApiWalletDelegation (..)
, ApiWalletDelegationNext (..)
Expand Down Expand Up @@ -333,6 +335,8 @@ import Control.Retry
( capDelay, constantDelay, retrying )
import Crypto.Hash
( Blake2b_160, Digest, digestFromByteString )
import Crypto.Hash.Utils
( blake2b224 )
import Data.Aeson
( FromJSON, ToJSON, Value, (.=) )
import Data.Aeson.QQ
Expand Down Expand Up @@ -1558,13 +1562,13 @@ getSharedWalletKey
-> DerivationIndex
-> Maybe Bool
-> m (HTTP.Status, Either RequestException ApiVerificationKeyShared)
getSharedWalletKey ctx wal role ix hashed =
getSharedWalletKey ctx wal role ix isHashed =
case wal of
ApiSharedWallet (Left wal') -> r wal'
ApiSharedWallet (Right wal') -> r wal'
where
r :: forall w. HasType (ApiT WalletId) w => w -> m (HTTP.Status, Either RequestException ApiVerificationKeyShared)
r w = request @ApiVerificationKeyShared ctx (Link.getWalletKey @'Shared w role ix hashed) Default Empty
r w = request @ApiVerificationKeyShared ctx (Link.getWalletKey @'Shared w role ix isHashed) Default Empty

postAccountKeyShared
:: forall m.
Expand Down Expand Up @@ -1594,13 +1598,27 @@ getAccountKeyShared
-> ApiSharedWallet
-> Maybe KeyFormat
-> m (HTTP.Status, Either RequestException ApiAccountKeyShared)
getAccountKeyShared ctx wal hashed =
getAccountKeyShared ctx wal isHashed =
case wal of
ApiSharedWallet (Left wal') -> r wal'
ApiSharedWallet (Right wal') -> r wal'
where
r :: forall w. HasType (ApiT WalletId) w => w -> m (HTTP.Status, Either RequestException ApiAccountKeyShared)
r w = request @ApiAccountKeyShared ctx (Link.getAccountKey @'Shared w hashed) Default Empty
r w = request @ApiAccountKeyShared ctx (Link.getAccountKey @'Shared w isHashed) Default Empty

getSomeVerificationKey
:: forall m.
( MonadIO m
, MonadUnliftIO m
)
=> Context
-> ApiWallet
-> m (ApiVerificationKeyShelley, ApiT (Hash "VerificationKey"))
getSomeVerificationKey ctx w = do
let link = Link.getWalletKey @'Shelley w UtxoExternal (DerivationIndex 0) Nothing
(_, vk@(ApiVerificationKeyShelley (bytes, _) _)) <-
unsafeRequest @ApiVerificationKeyShelley ctx link Empty
pure (vk, ApiT $ Hash $ blake2b224 @ByteString bytes)

patchEndpointEnding :: CredentialType -> Text
patchEndpointEnding = \case
Expand Down
87 changes: 86 additions & 1 deletion lib/core-integration/src/Test/Integration/Plutus.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}

Expand All @@ -8,24 +9,38 @@ module Test.Integration.Plutus
, game_1
, game_2
, game_3

, mkMintBurnPolicy
, mintBurn_1
, mintBurn_2
) where

import Prelude

import Cardano.Wallet.Api.Types
( ApiT (..) )
import Cardano.Wallet.Primitive.Types.Hash
( Hash (..) )
import Cardano.Wallet.Unsafe
( unsafeRight )
( unsafeFromHex, unsafeRight )
import Control.Arrow
( left )
import Control.Monad.IO.Unlift
( MonadUnliftIO (..) )
import Crypto.Hash.Utils
( blake2b224 )
import Data.Aeson.QQ
( aesonQQ )
import Data.String.Interpolate
( i )
import Data.Text
( Text )
import Text.Microstache
( compileMustacheText, renderMustache )

import qualified Data.Aeson as Aeson
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Text.Microstache as Mustache

Expand Down Expand Up @@ -149,6 +164,76 @@ game_3 =
]
}|]

--
-- Required Signers
--

-- | Create a policy for which the only validation condition is that the
-- transaction is signed by some key.
--
-- This template has one parameter:
--
-- - vkHash: flat-encoded blake2b-224 hash of some verification key, in base16.
--
mkMintBurnPolicy :: Aeson.Value -> (Text, ApiT (Hash "TokenPolicy"))
mkMintBurnPolicy args =
let policy = TL.toStrict (renderMustache template args)
policyId = ApiT $ Hash $ blake2b224 $ unsafeFromHex $ ("01" <>) $ T.encodeUtf8 policy
in
(policy, policyId)
where
template = unsafeRight $ left show $ compileMustacheText "mkSignerPolicy"
[i|59160e0100003323332223232323233223232323332223332223332223233332222323322323333222232332232332232333222323322323322323233223232323333222232323232323322332233333333333332222222222222323233333333222222223322332233223322323322332233223233223232323232323232323232323233333222223322332223003300200122232325335308601330053333573466e1cd55ce9baa0044800080708d4074d4c06ccd5ce2481035054310001c499263333573466e1cd55cea8012400046601064646464646464646464646666ae68cdc39aab9d500a480008cccccccccc0c8cd40688c8c8cccd5cd19b8735573aa004900011981c18119aba15002301f357426ae8940088d40b4d4c0accd5ce249035054310002c49926135573ca00226ea8004d5d0a80519a80d00d9aba150093335501d75ca0386ae854020ccd54075d7280e1aba1500733501a02335742a00c66a03466aa04c048eb4d5d0a8029919191999ab9a3370e6aae754009200023350553232323333573466e1cd55cea80124000466a0b666a052eb4d5d0a80118151aba135744a00446a0626a605e66ae712401035054310003049926135573ca00226ea8004d5d0a8011919191999ab9a3370e6aae7540092000233507a33502975a6ae854008c0a8d5d09aba2500223503135302f3357389201035054310003049926135573ca00226ea8004d5d09aba2500223502d35302b3357389201035054310002c49926135573ca00226ea8004d5d0a80219a80d3ae35742a00666a03466aa04ceb88004d5d0a80118101aba135744a00446a0526a604e66ae71241035054310002849926135744a00226ae8940044d5d1280089aba25001135744a00226ae8940044d5d1280089aba25001135573ca00226ea8004d5d0a8011919191999ab9a3370ea002900311808980d9aba135573ca00646666ae68cdc3a8012400846020603a6ae84d55cf280211999ab9a3370ea006900111808180c9aba135573ca00a46666ae68cdc3a80224000460266eb8d5d09aab9e50062350243530223357389201035054310002349926499264984d55cea80089baa001357426ae8940088d4074d4c06ccd5ce249035054310001c49926101b13501c35301a3357389201035054350001b4984d55cf280089baa00122235301800233223535501d002222533530890133355305f12001350595058235300a00522330290020030031533530890133355305f12001350595058235300a0052235302a0022222222222353503100d22533530980133355306e12001350625064235303900122330940100200400c109a0113357389201024c3000099010021533530890133355305f12001350595058235300a0052235302a0022222222222353502f00d22533530980133355306e12001350625064235303b00122253353508a01001215335309d0133305f09501003006153353508b01330703530310073374a90001bb149802484cc254040040084278044278044274054cd4d4218054cccd4c06803485422004854220048542200484ccd54c1bc4800541cc8d4c0e8004894cd4c27004cc254040080104d42300400c5422c0403484d4c0e400488d4c0f4004888ccd54c18c4800488d4c108008888d4c11c02088d4c124014894cd4c29c04cccc2500401000c0080044cd41fc024020402141dc0444d40b8d4c0b0cd5ce249024c660002d4984268044cd5ce2481024c310009901001108b011508801150880115088013335501c3322330023042005001505c505d505d505d0012212330010030022001212222300400521222230030052122223002005212222300100520011232230023758002640026aa0fa446666aae7c004941588cd4154c010d5d080118019aba200201123232323333573466e1cd55cea801a400046660406464646666ae68cdc39aab9d5002480008cc098c04cd5d0a80119a8060091aba135744a00446a02e6a602a66ae712401035054310001649926135573ca00226ea8004d5d0a801999aa803bae500635742a00466a010eb8d5d09aba25002235013353011335738921035054310001249926135744a00226aae7940044dd5000899aa800bae75a224464460046eac004c8004d541ec88c8cccd55cf8011282a919a82a19aa82898031aab9d5002300535573ca00460086ae8800c0404d5d080089119191999ab9a3370ea002900011a83518029aba135573ca00646666ae68cdc3a801240044a0d446a0226a601e66ae7124010350543100010499264984d55cea80089baa001232323333573466e1cd55cea801240004660e6600a6ae854008dd69aba135744a00446a01c6a601866ae71241035054310000d49926135573ca00226ea80048c8cccd5cd19b8735573aa002900011bae357426aae7940088d4030d4c028cd5ce249035054310000b499261375400224464646666ae68cdc3a800a40084a0b246666ae68cdc3a8012400446a0b8600c6ae84d55cf280211999ab9a3370ea00690001282e11a8079a980699ab9c4901035054310000e4992649926135573aa00226ea80048c8cccd5cd19b8750014800881d88cccd5cd19b8750024800081d88d402cd4c024cd5ce249035054310000a499264984d55ce9baa001232323232323333573466e1d4005200c202023333573466e1d4009200a202223333573466e1d400d2008233020375c6ae854014dd69aba135744a00a46666ae68cdc3a8022400c4660446eb8d5d0a8039bae357426ae89401c8cccd5cd19b875005480108cc09cc030d5d0a8049bae357426ae8940248cccd5cd19b875006480088c0a4c034d5d09aab9e500b23333573466e1d401d200023028300e357426aae7940308d404cd4c044cd5ce2481035054310001249926499264992649926135573aa00826aae79400c4d55cf280109aab9e5001137540024646464646666ae68cdc3a800a400446660ce6eb4d5d0a8021bad35742a0066eb4d5d09aba2500323333573466e1d40092000230693008357426aae7940188d4030d4c028cd5ce2481035054310000b499264984d55cea80189aba25001135573ca00226ea80048c8c8cccd5cd19b875001480088c19cdd71aba135573ca00646666ae68cdc3a80124000460d26eb8d5d09aab9e500423500935300733573892010350543100008499264984d55cea80089baa0011122232323333573466e1cd55cea80124000466aa090600c6ae854008c014d5d09aba25002235009353007335738921035054310000849926135573ca00226ea80044800480044984488848ccc00401000c00844800448848cc00400c0084800448848cc00400c00848004c8004d54198888cccccccccccd4c0580048d4c01400c88888888894cd4c1c54cd4d417cccd54c11c48005412c94cd4c1c8ccd5cd19b8f00c0010740731350620011506100321074107210731335738921024c340007222353006004222222222253353506053353506033355304812001504c2353550470012253353075333573466e3c00803c1dc1d84d419400c5419000884d418cd4d5411c0048800454184854cd4c1ccccd5cd19baf00100c07507410751506f1506e2353005003222222222253353071333553047120013503b503d2333573466ebc0300041d01cccd54c0f0480048d4d541180048800400841cc4cd5ce249024c3200072222323225335306c333573466e1cd4c0280208888888888c03001c0041b81b441b84cd5ce2481024c390006d3200135506d22335350430014800088d4d54108008894cd4c1c0ccd5cd19b8f00200a07207113007001130060033200135506c22335350420014800088d4d54104008894cd4c1bcccd5cd19b8f002007071070100113006003222353007005222222222253353073333553049120013503d503f2353016001222533535065001215335307833303a070003010153353506635301601422222222223305501b0022153353079333573466e3c0040081ec1e84d4c07401488cccc1a0008004c1c005541a841e841e441e441e002441d44cd5ce249024c6200074225335306833302a02900133355302d12001501750413530060042222222222333553037120012235301600222235301b00322335306d00225335307a333573466e3c0500041f01ec4cd414801401c401c801d412c02441a84cd5ce2481024c6100069253353067333029028001353005003222222222233355304712001501f235301400122200200910691335738921024c360006825335306733355303d1200135031503323300500400100110691335738921024c6400068253353067333029028001353005003222222222233355304712001501f23530120012235301600122200200a106913357389201024c35000682353005003222222222253353505f33355304712001504b235301200122533530743306d00200e1350640031506300a213530120012235301600122253353506500121507510791506e22353006004222222222253353506033355304812001504c235301300122533530753306e00200f1350650031506400a2107513357389201024c380007323530050032222222222353502e00b223535032002223535032008223535036002225335307933333332222222533353069333506000700600315335308001002153353080010051333505d0070010041081011333505d0070010041081011333505d007001004333333335060071225335307b333573466e1c0080041f41f0419c54cd4c1ecccd5cd19b8900200107d07c1065106622333573466e200080041f41f00e888ccd5cd19b8900200107c07d22333573466e200080041f01f4894cd4c1ecccd5cd19b8900200107d07c10011002225335307b333573466e240080041f41f04008400401801401c00800400c41ec4cd5ce249024c330007a222222222212333333333300100b00a0090080070060050040030022001221233001003002200122212333001004003002200122123300100300220012122222223007008221222222233006009008212222222300500812222222004122222220032212222222330020090082212222222330010090082001133502e5001502b1223355301e1200123535502800122335502b002335530211200123535502b00122335502e002333535501f0012330584800000488cc1640080048cc16000520000013301600200121222222222222300c00d2212222222222223300b00e00d21222222222222300a00d22221222222222222333300901000f00e00d222122222222222233300800f00e00d2212222222222223300700e00d21222222222222300600d21222222222222300500d21222222222222300400d21222222222222300300d2212222222222223300200e00d21222222222222300100d200112212330010030021200112212330010030021200122333573466e2400800410c108888ccd54c05c48004d404540408d4d5405800488ccd54c06848004d4051404c8d4d5406400488ccd4d540340048cc0292000001223300b00200123300a00148000004cc01000800488cd54c028480048d4d5405000488cd5405c008ccd4d540200048cd54c038480048d4d5406000488cd5406c008d5403c00400488ccd5540200ec0080048cd54c038480048d4d5406000488cd5406c008d54034004004ccd55400c0d8008004444888ccd54c01048005405ccd54c028480048d4d5405000488cd5405c008d5402c004ccd54c0104800488d4d54054008894cd4c10cccd54c06448004d4035403c8d4d5406000488cc028008014018400c4cd406c01000d4060004cd54c028480048d4d5405000488c8cd5406000cc004014c8004d54114894cd4d406c0044d5402c00c884d4d54068008894cd4c120cc0300080204cd5404001c0044c01800c008c8004d540f888448894cd4d405c0044008884cc014008ccd54c01c480040140100044484888c00c01044884888cc0080140104484888c00401044800448cd404c88ccd4d401800c88008008004d4d401000488004c8004d540e08844894cd4d404000454048884cd404cc010008cd54c018480040100044cd4008894cd4c0d800840e040040d448848cc00400c008480044cd400c894cd4c0cc008400440d00cc48cd403488ccd4d401000c88008008004d4d40080048800448848cc00400c00848004894cd4d4074ccd54c0144800540248d4d54010004894cd4c0c8ccd5cd19baf00100503403313502200315021001213502035355004001220021501e112212330010030021120013200135502d22112225335350060011353500a0032200122133353500c005220023004002333553007120010050040011122002122122330010040031200113350022253353501600221003100150151221233001003002120011222353500400222353500600322533353013333500a00700400215335302a0031001102c102b102c122123300100300212001122232323232533353500800621533353500900621533353500a0082130041613003161533353500a0072130041613003161015101315333535009007213004161300316153335350090062130041613003161014153335350080052101210131011153335350080052153335350090072130051613004161533353500900621300516130041610141012153335350080062130051613004161533353500800521300516130041610132533353500800521533353500900721533353500a00721333500f00a00200113011161301116130101610131533353500800621533353500900621333500e009002001130101613010161300f16101210112533353500700421533353500800621533353500900621333500e009002001130101613010161300f1610121533353500700521533353500800521333500d0080020011300f161300f161300e16101110102533353500600321533353500700521533353500800521333500d0080020011300f161300f161300e1610111533353500600421533353500700421333500c0070020011300e161300e161300d161010100f2533353500500221533353500600421533353500700421333500c0070020011300e161300e161300d1610101533353500500321533353500600321333500b0060020011300d161300d161300c16100f100e121222300300411222002112220011200112353500200122222222007122222222123333333300100900800700600500400300212001261222003122200212220012001222232335300c0052335300d00425335301a333573466e3c00800407006c5400c406c806c8cd4c034010806c94cd4c068ccd5cd19b8f00200101c01b15003101b15335350050032153353500600221335300a0022335300b0022335300f00223353010002233014002001201e23353010002201e23301400200122201e222335300d004201e2225335301f333573466e1c01800c08408054cd4c07cccd5cd19b8700500202102013301700400110201020101915335350050012101910191212230020031122001120012122300200322212233300100500400320012122300200321223001003200122333573466e3c00800403403088ccd5cd19b8700200100c00b2253353009333573466e3cd4c00c00888008d4c00c0048800802c0284ccd5cd19b87353003002220013530030012200100b00a100a221233001003002200113357389201024c630000513357389201024c37000042233700004002266ae71241024c640000212200212200120011123230010012233003300200200148811c{{vkHash}}0001|]

-- | A first transaction template which mints some token aimed for the wallet
-- submitting the transaction (collected as part of balancing). Other than the
-- minted token, the transaction has no inputs and no outputs. So the wallet is
-- expected to balance it out and assign the minted token to a change address.
--
-- The template has three parameters:
--
-- - policyId: A base16 policyId
-- - policy: A base16 corresponding policy (see mkMintBurnPolicy)
-- - vkHash: The verification key hash (base16) which was used to generate the policy.
--
mintBurn_1 :: (MonadUnliftIO m, MonadFail m) => Aeson.Value -> m Aeson.Value
mintBurn_1 =
renderMustacheThrow template
where
template = unsafeRight $ left show $ compileMustacheText "mintBurn_1" [i|{
"transaction": "84a600800d80018002000e81581c{{ vkHash }}09a1581c{{ policyId }}a1496d696e742d6275726e01a20381591611{{ policy }}0480f5f6",
"inputs": [],
"redeemers": [
{
"purpose": "minting",
"policy_id": "{{ policyId }}",
"data": "D87980"
}
]
}|]

-- The second transaction burn the token minted by the previous one. The token
-- isn't explictly listed in the inputs, as we expect the wallet to select the
-- right input during balancing.
--
-- The template has the same three parameters as 'mintBurn_1'
--
mintBurn_2 :: (MonadUnliftIO m, MonadFail m) => Aeson.Value -> m Aeson.Value
mintBurn_2 =
renderMustacheThrow template
where
template = unsafeRight $ left show $ compileMustacheText "mintBurn_2" [i|{
"transaction": "84a600800d80018002000e81581c{{ vkHash }}09a1581c{{ policyId }}a1496d696e742d6275726e20a20381591611{{ policy }}0480f5f6",
"inputs": [],
"redeemers": [
{
"purpose": "minting",
"policy_id": "{{ policyId }}",
"data": "D87980"
}
]
}|]

--
-- Helpers
--
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -112,6 +112,7 @@ import Test.Integration.Framework.DSL
, fixtureWalletWith
, fixtureWalletWithMnemonics
, getFromResponse
, getSomeVerificationKey
, json
, listAddresses
, minUTxOValue
Expand Down Expand Up @@ -1201,23 +1202,45 @@ spec = describe "NEW_SHELLEY_TRANSACTIONS" $ do
describe "Plutus scenarios" $ do
let scenarios =
[ ( "ping-pong"
, PlutusScenario.pingPong_1
, [ PlutusScenario.pingPong_2
]
, \_ _ -> pure
( PlutusScenario.pingPong_1
, [ PlutusScenario.pingPong_2 ]
)
)
, ( "game state-machine"
, PlutusScenario.game_1
, [ PlutusScenario.game_2
, PlutusScenario.game_3
]
, \_ _ -> pure
( PlutusScenario.game_1
, [ PlutusScenario.game_2
, PlutusScenario.game_3
]
)
)
, ( "mint-burn"
, \ctx w -> do
(_vk, vkHash) <- getSomeVerificationKey ctx w
let (policy, policyId) = PlutusScenario.mkMintBurnPolicy [json|{
"vkHash": #{vkHash} }
|]
mint <- PlutusScenario.mintBurn_1 [json|{
"policy": #{policy},
"policyId": #{policyId},
"vkHash": #{vkHash}
}|]
let burn = \_ -> PlutusScenario.mintBurn_2 [json|{
"policy": #{policy},
"policyId": #{policyId},
"vkHash": #{vkHash}
}|]
pure (mint, [burn])
)
]

forM_ scenarios $ \(title, setup, steps) -> it title $ \ctx -> runResourceT $ do
forM_ scenarios $ \(title, setupContract) -> it title $ \ctx -> runResourceT $ do
w <- fixtureWallet ctx
let balanceEndpoint = Link.balanceTransaction @'Shelley w
let signEndpoint = Link.signTransaction @'Shelley w

(setup, steps) <- setupContract ctx w

-- Balance
let toBalance = Json setup
Expand Down
Loading

0 comments on commit da99c76

Please sign in to comment.