Skip to content

Commit

Permalink
Add SMASH integration test
Browse files Browse the repository at this point in the history
  • Loading branch information
Julian Ospald committed Nov 16, 2020
1 parent 0fb5139 commit 3e7e73a
Show file tree
Hide file tree
Showing 5 changed files with 124 additions and 51 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,8 @@ import Prelude

import Cardano.Wallet.Api.Types
( ApiCertificate (JoinPool, QuitPool, RegisterRewardAccount)
, ApiStakePool
, ApiStakePool (flags)
, ApiStakePoolFlag (..)
, ApiT (..)
, ApiTransaction
, ApiWallet
Expand Down Expand Up @@ -76,6 +77,8 @@ import Data.Text.Class
( showT, toText )
import Numeric.Natural
( Natural )
import System.Environment
( getEnv )
import Test.Hspec
( SpecWith, describe, pendingWith )
import Test.Hspec.Expectations.Lifted
Expand Down Expand Up @@ -137,6 +140,7 @@ import Test.Integration.Framework.TestData
import qualified Cardano.Wallet.Api.Link as Link
import qualified Data.ByteString as BS
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Network.HTTP.Types.Status as HTTP

spec :: forall n t.
Expand Down Expand Up @@ -966,33 +970,6 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do
updateMetadataSource ctx "direct"
eventually "metadata is fetched" $ do
r <- listPools ctx arbitraryStake
let metadataPossible = Set.fromList
[ StakePoolMetadata
{ ticker = (StakePoolTicker "GPA")
, name = "Genesis Pool A"
, description = Nothing
, homepage = "https://iohk.io"
}
, StakePoolMetadata
{ ticker = (StakePoolTicker "GPB")
, name = "Genesis Pool B"
, description = Nothing
, homepage = "https://iohk.io"
}
, StakePoolMetadata
{ ticker = (StakePoolTicker "GPC")
, name = "Genesis Pool C"
, description = Just "Lorem Ipsum Dolor Sit Amet."
, homepage = "https://iohk.io"
}
, StakePoolMetadata
{ ticker = (StakePoolTicker "GPD")
, name = "Genesis Pool D"
, description = Just "Lorem Ipsum Dolor Sit Amet."
, homepage = "https://iohk.io"
}
]

verify r
[ expectListSize 3
, expectField Prelude.id $ \pools' -> do
Expand Down Expand Up @@ -1120,7 +1097,56 @@ spec = describe "SHELLEY_STAKE_POOLS" $ do
let epochs = poolGarbageCollectionEpochNo <$> events
(reverse epochs `zip` [1 ..]) `shouldSatisfy` all (uncurry (==))

it "STAKE_POOLS_SMASH_01 - fetching metadata from SMASH works with delisted pools" $
\ctx -> runResourceT $ do
smashUrl <- liftIO $ getEnv "CARDANO_WALLET_SMASH_URL"
updateMetadataSource ctx (T.pack smashUrl)
eventually "metadata is fetched" $ do
r <- listPools ctx arbitraryStake
verify r
[ expectListSize 3
, expectField Prelude.id $ \pools' -> do
let metadataActual = Set.fromList $
mapMaybe (fmap getApiT . view #metadata) pools'
delistedPools = filter (\pool -> Delisted `elem` flags pool)
pools'
metadataActual
`shouldSatisfy` (`Set.isSubsetOf` metadataPossible)
metadataActual
`shouldSatisfy` (not . Set.null)
(fmap (getApiT . view #id) delistedPools)
`shouldBe` [PoolId . unsafeFromHex $
"b45768c1a2da4bd13ebcaa1ea51408eda31dcc21765ccbd407cda9f2"]
]

where
metadataPossible = Set.fromList
[ StakePoolMetadata
{ ticker = (StakePoolTicker "GPA")
, name = "Genesis Pool A"
, description = Nothing
, homepage = "https://iohk.io"
}
, StakePoolMetadata
{ ticker = (StakePoolTicker "GPB")
, name = "Genesis Pool B"
, description = Nothing
, homepage = "https://iohk.io"
}
, StakePoolMetadata
{ ticker = (StakePoolTicker "GPC")
, name = "Genesis Pool C"
, description = Just "Lorem Ipsum Dolor Sit Amet."
, homepage = "https://iohk.io"
}
, StakePoolMetadata
{ ticker = (StakePoolTicker "GPD")
, name = "Genesis Pool D"
, description = Just "Lorem Ipsum Dolor Sit Amet."
, homepage = "https://iohk.io"
}
]

arbitraryStake :: Maybe Coin
arbitraryStake = Just $ ada 10_000_000_000
where ada = Coin . (1000*1000*)
Expand Down
3 changes: 3 additions & 0 deletions lib/core/src/Cardano/Pool/Metadata.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,9 @@ module Cardano.Pool.Metadata
-- * re-exports
, newManager
, defaultManagerSettings

-- * Types
, SMASHPoolId (..)
) where

import Prelude
Expand Down
48 changes: 44 additions & 4 deletions lib/shelley/src/Cardano/Wallet/Shelley/Launch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Cardano.Wallet.Shelley.Launch
withCluster
, withBFTNode
, withStakePool
, withSMASH
, NodeParams (..)
, singleNodeParams
, PoolConfig (..)
Expand All @@ -53,6 +54,9 @@ module Cardano.Wallet.Shelley.Launch
, testLogDirFromEnv
, walletListenFromEnv

-- * global vars
, operators

-- * Logging
, ClusterLog (..)
) where
Expand Down Expand Up @@ -85,6 +89,8 @@ import Cardano.Launcher.Node
, NodePort (..)
, withCardanoNode
)
import Cardano.Pool.Metadata
( SMASHPoolId (..) )
import Cardano.Wallet.Api.Server
( Listen (..) )
import Cardano.Wallet.Logging
Expand Down Expand Up @@ -120,7 +126,7 @@ import Control.Concurrent.Async
import Control.Concurrent.Chan
( newChan, readChan, writeChan )
import Control.Concurrent.MVar
( MVar, modifyMVar, newMVar, putMVar, takeMVar )
( MVar, modifyMVar, newMVar, putMVar, readMVar, takeMVar )
import Control.Exception
( SomeException, finally, handle, throwIO )
import Control.Monad
Expand Down Expand Up @@ -819,6 +825,40 @@ withStakePool tr baseDir idx params pledgeAmt poolConfig action =
dir = baseDir </> name
name = "pool-" ++ show idx

-- | Run a SMASH stub server, serving some delisted pool IDs.
withSMASH
:: Tracer IO ClusterLog
-> IO a
-> IO a
withSMASH tr action =
withSystemTempDir tr "smash" $ \fp -> do
let baseDir = fp </> "api/v1"

-- write pool metadatas
pools <- readMVar operators
forM_ pools $ \(poolId, _, _, _, metadata) -> do
let bytes = Aeson.encode metadata

let metadataDir = baseDir </> "metadata"
poolDir = metadataDir </> T.unpack (toText poolId)
hash = blake2b256S (BL.toStrict bytes)
hashFile = poolDir </> hash

createDirectoryIfMissing True poolDir
BL8.writeFile (poolDir </> hashFile) bytes

-- write delisted pools
let delisted = [SMASHPoolId (T.pack
"b45768c1a2da4bd13ebcaa1ea51408eda31dcc21765ccbd407cda9f2")]
bytes = Aeson.encode delisted
BL8.writeFile (baseDir </> "delisted") bytes

withStaticServer fp $ \baseUrl -> do
setEnv envVar baseUrl
action
where
envVar :: String
envVar = "CARDANO_WALLET_SMASH_URL"

updateVersion :: Tracer IO ClusterLog -> FilePath -> IO ()
updateVersion tr tmpDir = do
Expand Down Expand Up @@ -1402,7 +1442,7 @@ faucetIndex = unsafePerformIO $ newMVar 1
operators :: MVar [(PoolId, Aeson.Value, Aeson.Value, Aeson.Value, Aeson.Value)]
operators = unsafePerformIO $ newMVar
[ ( PoolId $ unsafeFromHex
"c7258ccc42a43b653aaf2f80dde3120df124ebc3a79353eed782267f78d04739"
"ec28f33dcbe6d6400a1e5e339bd0647c0973ca6c0cf9c2bbe6838dc6"
, Aeson.object
[ "type" .= Aeson.String "StakePoolVerificationKey_ed25519"
, "description" .= Aeson.String "Stake pool operator key"
Expand All @@ -1429,7 +1469,7 @@ operators = unsafePerformIO $ newMVar
]
)
, ( PoolId $ unsafeFromHex
"775af3b22eff9ff53a0bdd3ac6f8e1c5013ab68445768c476ccfc1e1c6b629b4"
"1b3dc19c6ab89eaffc8501f375bb03c11bf8ed5d183736b1d80413d6"
, Aeson.object
[ "type" .= Aeson.String "StakePoolVerificationKey_ed25519"
, "description" .= Aeson.String "Stake pool operator key"
Expand All @@ -1456,7 +1496,7 @@ operators = unsafePerformIO $ newMVar
]
)
, ( PoolId $ unsafeFromHex
"5a7b67c7dcfa8c4c25796bea05bcdfca01590c8c7612cc537c97012bed0dec35"
"b45768c1a2da4bd13ebcaa1ea51408eda31dcc21765ccbd407cda9f2"
, Aeson.object
[ "type" .= Aeson.String "StakePoolVerificationKey_ed25519"
, "description" .= Aeson.String "Stake pool operator key"
Expand Down
38 changes: 21 additions & 17 deletions lib/shelley/test/integration/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,7 @@ import Cardano.Wallet.Shelley.Launch
, testMinSeverityFromEnv
, walletMinSeverityFromEnv
, withCluster
, withSMASH
, withSystemTempDir
, withTempDir
)
Expand Down Expand Up @@ -149,22 +150,25 @@ main = withUtf8Encoding $ withTracers $ \tracers -> do
parallelIf (not nix) $ describe "Miscellaneous CLI tests" $
MiscellaneousCLI.spec @t
specWithServer tracers $ do
parallel $ describe "API Specifications" $ do
Addresses.spec @n
CoinSelections.spec @n
ByronAddresses.spec @n
ByronCoinSelections.spec @n
Wallets.spec @n
ByronWallets.spec @n
HWWallets.spec @n
Migrations.spec @n
ByronMigrations.spec @n
Transactions.spec @n
Network.spec
Network_.spec
StakePools.spec @n
ByronTransactions.spec @n
ByronHWWallets.spec @n
describe "API Specifications" $ do
parallel $ do
Addresses.spec @n
CoinSelections.spec @n
ByronAddresses.spec @n
ByronCoinSelections.spec @n
Wallets.spec @n
ByronWallets.spec @n
HWWallets.spec @n
Migrations.spec @n
ByronMigrations.spec @n
Transactions.spec @n
Network.spec
Network_.spec
StakePools.spec @n
ByronTransactions.spec @n
ByronHWWallets.spec @n

-- possible conflict with StakePools
Settings.spec @n

-- Hydra runs tests with code coverage enabled. CLI tests run
Expand Down Expand Up @@ -243,7 +247,7 @@ specWithServer (tr, tracers) = aroundAll withContext
atomicModifyIORef' eventsRef ((, ()) . (event :))
pure certificates

withServer dbDecorator action = bracketTracer' tr "withServer" $ do
withServer dbDecorator action = bracketTracer' tr "withServer" $ withSMASH tr' $ do
minSev <- nodeMinSeverityFromEnv
testPoolConfigs <- poolConfigsFromEnv
withSystemTempDir tr' "test" $ \dir -> do
Expand Down
4 changes: 2 additions & 2 deletions lib/test-utils/src/Test/Utils/StaticServer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module Test.Utils.StaticServer
import Prelude

import Network.Wai.Application.Static
( defaultWebAppSettings, staticApp )
( defaultFileServerSettings, staticApp )
import Network.Wai.Handler.Warp
( withApplication )

Expand All @@ -27,5 +27,5 @@ withStaticServer
withStaticServer root action =
withApplication (pure app) $ \port -> action (baseUrl port)
where
app = staticApp $ defaultWebAppSettings root
app = staticApp $ defaultFileServerSettings root
baseUrl port = "http://localhost:" <> show port <> "/"

0 comments on commit 3e7e73a

Please sign in to comment.