Skip to content

Commit

Permalink
Add roundtrip tests for serialization of SendFaucetAssets
Browse files Browse the repository at this point in the history
  • Loading branch information
paolino committed May 3, 2024
1 parent 03cb42d commit 5738324
Show file tree
Hide file tree
Showing 4 changed files with 194 additions and 18 deletions.
94 changes: 94 additions & 0 deletions lib/local-cluster/lib/Cardano/Wallet/Faucet/Gen/Address.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,94 @@
{-# LANGUAGE ScopedTypeVariables #-}

module Cardano.Wallet.Faucet.Gen.Address
( genAddress
, NetworkTag (..)
, allTags
)
where

import Prelude

import Cardano.Address
( Address
, unsafeMkAddress
)
import Data.Bits
( Bits (shiftL, (.|.))
)
import Data.ByteString
( ByteString
)
import Data.Word
( Word8
)
import Test.QuickCheck
( Arbitrary (arbitrary)
, Gen
, elements
, vectorOf
)

import qualified Data.ByteString as BS

{-
ADDRESS = %b0000 | NETWORK-TAG | KEY-HASH | KEY-HASH ; type 00, Base Shelley address
\ %b0001 | NETWORK-TAG | SCRIPT-HASH | KEY-HASH ; type 01, Base Shelley address
\ %b0010 | NETWORK-TAG | KEY-HASH | SCRIPT-HASH ; type 02, Base Shelley address
\ %b0011 | NETWORK-TAG | SCRIPT-HASH | SCRIPT-HASH ; type 03, Base Shelley address
\ %b0100 | NETWORK-TAG | KEY-HASH | POINTER ; type 04, Pointer Shelley address
\ %b0101 | NETWORK-TAG | SCRIPT-HASH | POINTER ; type 05, Pointer Shelley address
\ %b0110 | NETWORK-TAG | KEY-HASH ; type 06, Payment Shelley address
\ %b0111 | NETWORK-TAG | SCRIPT-HASH ; type 07, Payment Shelley address
\ %b1000 | BYRON-PAYLOAD ; type 08, Byron / Bootstrap address
\ %b1110 | NETWORK-TAG | KEY-HASH ; type 14, Stake Shelley address
\ %b1111 | NETWORK-TAG | SCRIPT-HASH ; type 15, Stake Shelley address
NETWORK-TAG = %b0000 ; Testnet
\ %b0001 ; Mainnet
POINTER = VARIABLE-LENGTH-UINT ; slot number
| VARIABLE-LENGTH-UINT ; transaction index
| VARIABLE-LENGTH-UINT ; certificate index
VARIABLE-LENGTH-UINT = (%b1 | UINT7 | VARIABLE-LENGTH-UINT)
/ (%b0 | UINT7)
UINT7 = 7BIT
KEY-HASH = 28OCTET
SCRIPT-HASH= 28OCTET
BYRON-PAYLOAD = *OCTET ; see 'Byron Addresses' section or cddl specification.
-}

data NetworkTag = TestnetTag | MainnetTag

tag :: NetworkTag -> Word8
tag TestnetTag = 0
tag MainnetTag = 1

allTags :: [NetworkTag]
allTags = [TestnetTag, MainnetTag]

genPrefix :: [NetworkTag] -> [Word8] -> Gen Word8
genPrefix ts xs = do
network <- elements ts
prefix <- elements xs
pure $ prefix `shiftL` 4 .|. tag network

genHash :: Gen ByteString
genHash = BS.pack <$> vectorOf 28 arbitrary

-- | Generate a random address for the given networks excluding the Byron addresses.
genAddress :: [NetworkTag] -> Gen Address
genAddress tags = fmap unsafeMkAddress $ do
hash1 <- genHash
hash2 <- genHash
prefixONE <- genPrefix tags [6, 7]
prefixTWO <- genPrefix tags [0, 1, 2, 3]
elements
[ prefixONE `BS.cons` hash1
, prefixTWO `BS.cons` hash1 <> hash2
]
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand All @@ -8,6 +9,7 @@
module Cardano.Wallet.Launch.Cluster.Monitoring.Http.SendFaucetAssets
( SendFaucetAssets (..)
, WithNetwork (..)
, genSendFaucetAssets
)
where

Expand All @@ -17,13 +19,17 @@ import Cardano.Wallet.Address.Encoding
( decodeAddress
, encodeAddress
)
import Cardano.Wallet.Faucet.Gen.Address
( NetworkTag (..)
, genAddress
)
import Cardano.Wallet.Primitive.NetworkId
( HasSNetworkId (sNetworkId)
, NetworkDiscriminant
, SNetworkId
, NetworkDiscriminant (..)
, SNetworkId (..)
)
import Cardano.Wallet.Primitive.Types.Address
( Address
( Address (..)
)
import Cardano.Wallet.Primitive.Types.AssetId
( AssetId (..)
Expand All @@ -36,6 +42,9 @@ import Cardano.Wallet.Primitive.Types.TokenBundle
, fromFlatList
, toFlatList
)
import Cardano.Wallet.Primitive.Types.TokenBundle.Gen
( genTokenBundleSmallRange
)
import Cardano.Wallet.Primitive.Types.TokenQuantity
( TokenQuantity
)
Expand All @@ -60,14 +69,22 @@ import Data.Aeson.Types
import Data.Bifunctor
( first
)
import Test.QuickCheck
( Arbitrary (..)
, Gen
, listOf
)

-- | SendFaucetAssets represents the request to send assets to a list of addresses
import qualified Cardano.Address as Addr

-- | Payload to send assets to a list of addresses
data SendFaucetAssets = SendFaucetAssets
{ batchSize :: Int
-- ^ batch size
, assets :: [(Address, (TokenBundle, [(String, String)]))]
-- ^ List of addresses and the assets to send to each address
}
deriving stock (Eq, Show)

-- | WithNetwork carries network discriminant around a value
newtype WithNetwork a (n :: NetworkDiscriminant) = WithNetwork a
Expand Down Expand Up @@ -166,19 +183,41 @@ renderBundle :: TokenBundle -> Value
renderBundle = toJSON . renderBundle' . toFlatList

renderBundle' :: (Coin, [(AssetId, TokenQuantity)]) -> Value
renderBundle' (c, xs) = object
[ "coin" .= renderCoin c
, "assets" .= map renderAssetQuantity xs
]
renderBundle' (c, xs) =
object
[ "coin" .= renderCoin c
, "assets" .= map renderAssetQuantity xs
]

renderAssetQuantity :: (AssetId, TokenQuantity) -> Value
renderAssetQuantity (AssetId tp n, tq) = object
[ "asset" .= object
[ "policy" .= tp
, "name" .= n
renderAssetQuantity (AssetId tp n, tq) =
object
[ "asset"
.= object
[ "policy" .= tp
, "name" .= n
]
, "quantity" .= tq
]
, "quantity" .= tq
]

renderCoin :: Coin -> Value
renderCoin (Coin c) = toJSON c

--- generators -----------------------------------------------------------------

-- | Generate a 'SendFaucetAssets' payload
genSendFaucetAssets :: forall n. HasSNetworkId n
=> Gen (WithNetwork SendFaucetAssets n)
genSendFaucetAssets = do
batchSize <- arbitrary
assets <- listOf $ genAsset $ case sNetworkId @n of
SMainnet -> MainnetTag
STestnet _ -> TestnetTag
pure $ WithNetwork SendFaucetAssets{batchSize, assets}

genAsset :: NetworkTag -> Gen (Address, (TokenBundle, [(String, String)]))
genAsset tag = do
addr <- Address . Addr.unAddress <$> genAddress [tag]
bundle <- genTokenBundleSmallRange
metadata <- listOf ((,) <$> arbitrary <*> arbitrary)
pure (addr, (bundle, metadata))
9 changes: 5 additions & 4 deletions lib/local-cluster/local-cluster.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@ library
Cardano.Node.Cli.Launcher
Cardano.Wallet.Cli.Launcher
Cardano.Wallet.Faucet
Cardano.Wallet.Faucet.Gen.Address
Cardano.Wallet.Launch.Cluster
Cardano.Wallet.Launch.Cluster.Aeson
Cardano.Wallet.Launch.Cluster.CardanoCLI
Expand All @@ -71,6 +72,7 @@ library
Cardano.Wallet.Launch.Cluster.Monitoring.Http.Client
Cardano.Wallet.Launch.Cluster.Monitoring.Http.Logging
Cardano.Wallet.Launch.Cluster.Monitoring.Http.OpenApi
Cardano.Wallet.Launch.Cluster.Monitoring.Http.SendFaucetAssets
Cardano.Wallet.Launch.Cluster.Monitoring.Http.Server
Cardano.Wallet.Launch.Cluster.Monitoring.Monitor
Cardano.Wallet.Launch.Cluster.Monitoring.Phase
Expand Down Expand Up @@ -146,6 +148,7 @@ library
, ouroboros-network-api
, pathtype
, profunctors
, QuickCheck
, retry
, servant
, servant-client
Expand All @@ -166,10 +169,6 @@ executable local-cluster
main-is: local-cluster.hs
hs-source-dirs: exe
ghc-options: -threaded -rtsopts

if flag(release)
ghc-options: -O2 -Werror

build-depends:
, base
, cardano-addresses
Expand Down Expand Up @@ -197,6 +196,7 @@ test-suite test
, aeson
, base
, bytestring
, cardano-wallet-primitive
, cardano-wallet-test-utils
, contra-tracer
, foldl
Expand All @@ -214,6 +214,7 @@ test-suite test
other-modules:
Cardano.Wallet.Launch.Cluster.Monitoring.Http.APISpec
Cardano.Wallet.Launch.Cluster.Monitoring.Http.OpenAPISpec
Cardano.Wallet.Launch.Cluster.Monitoring.Http.SendFaucetAssetsSpec
Cardano.Wallet.Launch.Cluster.Monitoring.MonitorSpec
Control.Monitoring.MonitorSpec
Control.Monitoring.TracingSpec
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.Launch.Cluster.Monitoring.Http.SendFaucetAssetsSpec
( spec
) where

import Prelude

import Cardano.Wallet.Launch.Cluster.Monitoring.Http.SendFaucetAssets
( genSendFaucetAssets
)
import Cardano.Wallet.Primitive.NetworkId
( NetworkDiscriminant (..)
)
import Data.Aeson
( FromJSON
, Result (..)
, ToJSON
, fromJSON
, toJSON
)
import Test.Hspec
( Spec
, describe
, it
, shouldBe
)
import Test.QuickCheck
( forAll
)

jsonRoundtrip :: (ToJSON a, FromJSON a, Eq a, Show a) => a -> IO ()
jsonRoundtrip a = fromJSON (toJSON a) `shouldBe` Success a

spec :: Spec
spec = do
describe "SendFaucetAssets" $ do
it "json instances roundtrips for Mainnet" $ do
forAll (genSendFaucetAssets @Mainnet) jsonRoundtrip
it "json instances roundtrips for Testnet" $ do
forAll (genSendFaucetAssets @(Testnet 42)) jsonRoundtrip

0 comments on commit 5738324

Please sign in to comment.