Skip to content

Commit

Permalink
Add pending test that wallet with existing stake key can delegate
Browse files Browse the repository at this point in the history
STAKE_POOLS_JOIN_05

This is a pending regression test for "Cannot join pool with ITN rewards wallet on shelley testnet"
  • Loading branch information
Anviking committed Jul 2, 2020
1 parent f70d7e9 commit 8c9bee4
Show file tree
Hide file tree
Showing 7 changed files with 119 additions and 17 deletions.
Expand Up @@ -3,6 +3,7 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down Expand Up @@ -48,6 +49,8 @@ import Data.Quantity
( Quantity (..) )
import Data.Set
( Set )
import Data.Text
( Text )
import Data.Text.Class
( toText )
import Test.Hspec
Expand All @@ -71,6 +74,7 @@ import Test.Integration.Framework.DSL
, fixtureWalletWith
, getSlotParams
, joinStakePool
, json
, mkEpochInfo
, notDelegating
, quitStakePool
Expand Down Expand Up @@ -334,6 +338,28 @@ spec = do
-- (`shouldBe` reward)
-- ]

it "STAKE_POOLS_JOIN_05 - Can join when stake key already exists" $ \ctx -> do
pendingWith "tracking stake key registrations"
let (walletWithPreRegKey:: [Text]) =
[ "over", "decorate", "flock", "badge", "beauty"
, "stamp" , "chest", "owner", "excess", "omit"
, "bid", "raccoon", "spin" , "reduce", "rival"
]
let payload = Json [json| {
"name": "Wallet with pre-registered stake key",
"mnemonic_sentence": #{walletWithPreRegKey},
"passphrase": "Secure Passphrase"
} |]
(_, w) <- unsafeRequest @ApiWallet ctx (Link.postWallet @'Shelley) payload
pool:_ <- map (view #id) . snd
<$> unsafeRequest @[ApiStakePool] ctx (Link.listStakePools arbitraryStake) Empty

joinStakePool @n ctx pool (w, passwd)>>= flip verify
[ expectResponseCode HTTP.status202
, expectField (#status . #getApiT) (`shouldBe` Pending)
, expectField (#direction . #getApiT) (`shouldBe` Outgoing)
]

describe "STAKE_POOLS_JOIN_01x - Fee boundary values" $ do
it "STAKE_POOLS_JOIN_01x - \
\I can join if I have just the right amount" $ \ctx -> do
Expand Down
2 changes: 2 additions & 0 deletions lib/shelley/cardano-wallet-shelley.cabal
Expand Up @@ -187,6 +187,8 @@ test-suite integration
, async
, bytestring
, cardano-wallet-cli
, cardano-addresses
, cardano-slotting
, cardano-wallet-core
, cardano-wallet-core-integration
, cardano-wallet-launcher
Expand Down
12 changes: 12 additions & 0 deletions lib/shelley/src/Cardano/Wallet/Shelley/Compatibility.hs
Expand Up @@ -38,6 +38,7 @@ module Cardano.Wallet.Shelley.Compatibility
-- * Genesis
, emptyGenesis
, genesisTip
, initialFundsPseudoTxIn

-- * Conversions
, toShelleyHash
Expand Down Expand Up @@ -618,6 +619,14 @@ fromShelleyTxIn (SL.TxIn txid ix) =
unsafeCast :: Natural -> Word32
unsafeCast = fromIntegral

-- | Create a TxIn pointing to the initial funds in the genesis file.
initialFundsPseudoTxIn :: W.Address -> W.TxIn
initialFundsPseudoTxIn =
fromShelleyTxIn
. SL.initialFundsPseudoTxIn @TPraosStandardCrypto
. fromMaybe (error "initialFundsPseudoTxIn: invalid addr")
. toShelleyAddress

fromShelleyTxOut :: SL.TxOut crypto -> W.TxOut
fromShelleyTxOut (SL.TxOut addr amount) =
W.TxOut (fromShelleyAddress addr) (fromShelleyCoin amount)
Expand All @@ -626,6 +635,9 @@ fromShelleyAddress :: SL.Addr crypto -> W.Address
fromShelleyAddress = W.Address
. SL.serialiseAddr

toShelleyAddress :: O.Crypto crypto => W.Address -> Maybe (SL.Addr crypto)
toShelleyAddress = SL.deserialiseAddr . W.unAddress

fromShelleyCoin :: SL.Coin -> W.Coin
fromShelleyCoin (SL.Coin c) = W.Coin $ unsafeCast c
where
Expand Down
2 changes: 2 additions & 0 deletions lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs
Expand Up @@ -31,6 +31,8 @@ module Cardano.Wallet.Shelley.Transaction
, mkWitness
, realFee
, mkTx
, TxPayload (..)
, emptyTxPayload
) where

import Prelude
Expand Down
5 changes: 5 additions & 0 deletions lib/shelley/test/data/cardano-node-shelley/genesis.yaml
Expand Up @@ -1427,3 +1427,8 @@ initialFunds:
- 610cdec48bb2168dbaa18f5a7e67ede598449e3783891f926d99c7ace8: 1
- 61d1e87828a2ff41f11e575e7827d0c38f48f2bf6778b359042c7a2e3e: 1
- 610130f3030867e827cb09eb1bf50401b0d9f413b2ca872b57a8d2fae4: 1

# Special wallet ["over", "decorate", "flock", "badge", "beauty", "stamp", "chest", "owner", "excess", "omit", "bid", "raccoon", "spin", "reduce", "rival"]
# for STAKE_POOLS_JOIN_05.
- 6199a7c32aaa55a628d936b539f01d5415318dec8bcb5e59ec71af695b: 10000000000
- 60386c7a86d8844f4085a50241556043c9842d72c315c897a42a8a0510: 10000000000
87 changes: 70 additions & 17 deletions lib/shelley/test/integration/Main.hs
Expand Up @@ -13,6 +13,8 @@ module Main where

import Prelude

import Cardano.Address.Derivation
( XPrv, xprvFromBytes, xpubFromBytes )
import Cardano.BM.Data.Severity
( Severity (..) )
import Cardano.BM.Data.Tracer
Expand All @@ -23,6 +25,8 @@ import Cardano.CLI
( Port (..), parseLoggingSeverity, withLogging )
import Cardano.Launcher
( ProcessHasExited (..) )
import Cardano.Slotting.Slot
( SlotNo (..) )
import Cardano.Startup
( withUtf8Encoding )
import Cardano.Wallet.Api.Server
Expand All @@ -31,10 +35,14 @@ import Cardano.Wallet.Api.Types
( ApiByronWallet, ApiWallet, WalletStyle (..) )
import Cardano.Wallet.Logging
( BracketLog (..), bracketTracer, trMessageText )
import Cardano.Wallet.Network
( NetworkLayer (..) )
import Cardano.Wallet.Network.Ports
( unsafePortNumber )
import Cardano.Wallet.Primitive.AddressDerivation
( NetworkDiscriminant (..) )
( Depth (..), NetworkDiscriminant (..), paymentAddress, publicKey )
import Cardano.Wallet.Primitive.AddressDerivation.Shelley
( ShelleyKey (..) )
import Cardano.Wallet.Primitive.CoinSelection
( CoinSelection (..) )
import Cardano.Wallet.Primitive.Fee
Expand All @@ -59,15 +67,19 @@ import Cardano.Wallet.Shelley
, tracerSeverities
)
import Cardano.Wallet.Shelley.Compatibility
( Shelley )
( Shelley, initialFundsPseudoTxIn, toStakeKeyRegCert )
import Cardano.Wallet.Shelley.Faucet
( initFaucet )
import Cardano.Wallet.Shelley.Launch
( ClusterLog, withCluster, withSystemTempDir, withTempDir )
import Cardano.Wallet.Shelley.Network
( withNetworkLayer )
import Cardano.Wallet.Shelley.Transaction
( _minimumFee )
( TxPayload (..), mkTx, _minimumFee )
import Cardano.Wallet.Transaction
( Certificate (..) )
import Cardano.Wallet.Unsafe
( unsafeFromHex, unsafeRunExceptT )
import Control.Concurrent.Async
( race )
import Control.Concurrent.MVar
Expand All @@ -77,7 +89,9 @@ import Control.Exception
import Control.Monad
( forM_, void )
import Control.Tracer
( Tracer (..), contramap, traceWith )
( Tracer (..), contramap, nullTracer, traceWith )
import Data.Maybe
( fromJust )
import Data.Proxy
( Proxy (..) )
import Data.Text
Expand Down Expand Up @@ -209,19 +223,21 @@ specWithServer (tr, tracers) = aroundAll withContext . after tearDown
let tr' = contramap MsgCluster tr
withSystemTempDir tr' "test" $ \dir ->
withCluster tr' minSev 3 dir $ \socketPath block0 (gp, vData) ->
withTempDir tr' dir "wallets" $ \db ->
serveWallet @(IO Shelley)
(SomeNetworkDiscriminant $ Proxy @'Mainnet)
tracers
(SyncTolerance 10)
(Just db)
"127.0.0.1"
ListenOnRandomPort
Nothing
socketPath
block0
(gp, vData)
(onStart gp)
withTempDir tr' dir "wallets" $ \db -> do
withNetworkLayer nullTracer gp socketPath vData $ \nl -> do
preregisterStakingKeysForTests nl
serveWallet @(IO Shelley)
(SomeNetworkDiscriminant $ Proxy @'Mainnet)
tracers
(SyncTolerance 10)
(Just db)
"127.0.0.1"
ListenOnRandomPort
Nothing
socketPath
block0
(gp, vData)
(onStart gp)

-- | teardown after each test (currently only deleting all wallets)
tearDown :: Context t -> IO ()
Expand Down Expand Up @@ -324,3 +340,40 @@ minSeverityFromEnv def var = lookupEnv var >>= \case
Nothing -> pure def
Just "" -> pure def
Just arg -> either die pure (parseLoggingSeverity arg)

-- | Pre-register a staking key for the STAKE_POOLS_JOIN_05 test.
preregisterStakingKeysForTests :: NetworkLayer IO t b -> IO ()
preregisterStakingKeysForTests nl = do
let payload = TxPayload
[toStakeKeyRegCert rewardPub]
(const mempty)
(Fee 9999999900)
let keystore = const (Just (xprv, mempty))
let txIn = initialFundsPseudoTxIn addr

let dummyOut = TxOut addr (Coin 0)

let Right (_, tx) = mkTx
@ShelleyKey
payload
keystore
(SlotNo 5000)
[(txIn, dummyOut)]
[]
unsafeRunExceptT $ postTx nl tx
where

addr :: Address
addr = paymentAddress @'Mainnet (publicKey xprv)

-- The wallet's reward key
Just rewardPub = xpubFromBytes $ unsafeFromHex
"949fc9e6b7e1e12e933ac35de5a565c9264b0ac5b631b4f5a21548bc6d65616f30\
\42af27ce48e0fce0f88696b6ed3476f8c3412cce2f984931fb7658dee1872e"

xprv :: ShelleyKey 'AddressK XPrv
xprv = ShelleyKey $ fromJust $ xprvFromBytes $ unsafeFromHex
"90b23d7d7d2d77e943bf81b89af4f4b263049b4c2c7f52b9ae\
\2093bff8ff8c4e845d4583dcbf226613bc1b823811fe682483\
\c71bf0de92dc7f8f05bacdaba79994f3d3f3cc1793d8afe804\
\53ab06a875d21ed1adcfad913617796c8662d375fc"
2 changes: 2 additions & 0 deletions nix/.stack.nix/cardano-wallet-shelley.nix

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 8c9bee4

Please sign in to comment.