Skip to content

Commit

Permalink
Add tx metadata API integration tests
Browse files Browse the repository at this point in the history
  • Loading branch information
rvl committed Sep 1, 2020
1 parent 257ace1 commit 57297c4
Show file tree
Hide file tree
Showing 4 changed files with 131 additions and 2 deletions.
1 change: 1 addition & 0 deletions lib/core-integration/cardano-wallet-core-integration.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,7 @@ library
, retry
, say
, scrypt
, shelley-spec-ledger
, stm
, template-haskell
, temporary
Expand Down
13 changes: 13 additions & 0 deletions lib/core-integration/src/Test/Integration/Framework/DSL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module Test.Integration.Framework.DSL
, (.>=)
, (.<=)
, (.>)
, (.<)
, verify
, Headers(..)
, Payload(..)
Expand Down Expand Up @@ -571,6 +572,18 @@ x .> bound
, ")"
]

(.<) :: (Ord a, Show a) => a -> a -> Expectation
x .< bound
| x < bound
= return ()
| otherwise
= fail $ mconcat
[ show x
, " does not satisfy (< "
, show bound
, ")"
]

(.>=) :: (Ord a, Show a) => a -> a -> Expectation
a .>= b
| a >= b
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -39,9 +39,17 @@ import Cardano.Wallet.Primitive.AddressDerivation
import Cardano.Wallet.Primitive.AddressDerivation.Icarus
( IcarusKey )
import Cardano.Wallet.Primitive.Types
( Direction (..), Hash (..), SortOrder (..), TxStatus (..), WalletId )
( Direction (..)
, Hash (..)
, SortOrder (..)
, TxMetadata (..)
, TxStatus (..)
, WalletId
)
import Control.Monad
( forM_ )
import Data.Aeson
( (.=) )
import Data.Generics.Internal.VL.Lens
( view, (^.) )
import Data.Generics.Product.Typed
Expand Down Expand Up @@ -102,6 +110,7 @@ import Test.Integration.Framework.DSL
, utcIso8601ToText
, verify
, walletId
, (.<)
, (.>)
, (.>=)
)
Expand All @@ -125,9 +134,12 @@ import Web.HttpApiData
( ToHttpApiData (..) )

import qualified Cardano.Wallet.Api.Link as Link
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BS
import qualified Data.Map as Map
import qualified Data.Text as T
import qualified Network.HTTP.Types.Status as HTTP
import qualified Shelley.Spec.Ledger.MetaData as MD

data TestCase a = TestCase
{ query :: T.Text
Expand Down Expand Up @@ -229,6 +241,7 @@ spec = do
between (feeMin + amt, feeMax + amt)
, expectField (#direction . #getApiT) (`shouldBe` Outgoing)
, expectField (#status . #getApiT) (`shouldBe` Pending)
, expectField (#metadata . #getApiTxMetadata) (`shouldBe` Nothing)
]

ra <- request @ApiWallet ctx (Link.getWallet @'Shelley wa) Default Empty
Expand Down Expand Up @@ -533,6 +546,102 @@ spec = do
(#balance . #available)
(`shouldBe` Quantity (faucetAmt - feeEstMax - amt)) ra2

it "TRANS_CREATE_10 - Transaction with metadata" $ \ctx -> do
(wa, wb) <- (,) <$> fixtureWallet ctx <*> fixtureWallet ctx
let amt = (1 :: Natural)

basePayload <- mkTxPayload ctx wb amt fixturePassphrase

let txMeta = [json|{
"1": "hello"
}|]
let expected = TxMetadata (MD.MetaData (Map.singleton 1 (MD.S "hello")))
let payload = addTxMetadata txMeta basePayload

ra <- request @(ApiTransaction n) ctx
(Link.createTransaction @'Shelley wa) Default payload

verify ra
[ expectSuccess
, expectResponseCode HTTP.status202
, expectField (#status . #getApiT) (`shouldBe` Pending)
, expectField
(#metadata . #getApiTxMetadata)
(`shouldBe` Just (ApiT expected))
]

eventually "metadata is confirmed in transaction list" $ do
let link = Link.listTransactions @'Shelley wa
rb <- request @([ApiTransaction n]) ctx link Default Empty
verify rb
[ expectResponseCode HTTP.status200
, expectListField 0 (#status . #getApiT) (`shouldBe` InLedger)
, expectListField 0
(#metadata . #getApiTxMetadata)
(`shouldBe` Just (ApiT expected))
]

it "TRANS_CREATE_11 - Transaction with invalid metadata" $ \ctx -> do
(wa, wb) <- (,) <$> fixtureWallet ctx <*> fixtureWallet ctx
let amt = (1 :: Natural)

basePayload <- mkTxPayload ctx wb amt fixturePassphrase

let txMeta = Aeson.object ["1" .= T.replicate 65 "a"]
let payload = addTxMetadata txMeta basePayload

r <- request @(ApiTransaction n) ctx
(Link.createTransaction @'Shelley wa) Default payload

expectResponseCode @IO HTTP.status400 r
expectErrorMessage "fixme: api validation error message" r

it "TRANS_CREATE_12 - Transaction with too much metadata" $ \ctx -> do
(wa, wb) <- (,) <$> fixtureWallet ctx <*> fixtureWallet ctx
let amt = (1 :: Natural)

basePayload <- mkTxPayload ctx wb amt fixturePassphrase

-- This will encode to at least 64k of CBOR.
let txMeta = Aeson.object
[ (toText @Int i, Aeson.String (T.replicate 64 "a"))
| i <- [0..1023] ]
let payload = addTxMetadata txMeta basePayload

r <- request @(ApiTransaction n) ctx
(Link.createTransaction @'Shelley wa) Default payload

expectResponseCode @IO HTTP.status400 r
expectErrorMessage "fixme: transaction rejected message" r

it "TRANS_ESTIMATE_xxx - fee estimation includes metadata" $ \ctx -> do
(wa, wb) <- (,) <$> fixtureWallet ctx <*> fixtureWallet ctx
let amt = (1 :: Natural)

payload <- mkTxPayload ctx wb amt fixturePassphrase

let txMeta = [json|{ "1": "hello" }|]
let payloadWithMetadata = addTxMetadata txMeta payload

ra <- request @ApiFee ctx
(Link.getTransactionFee @'Shelley wa) Default payloadWithMetadata
verify ra
[ expectSuccess
, expectResponseCode HTTP.status202
]
let (Quantity feeEstMin) = getFromResponse #estimatedMin ra
let (Quantity feeEstMax) = getFromResponse #estimatedMax ra

-- check that it's estimated to have less fees for transactions without
-- metadata.
rb <- request @ApiFee ctx
(Link.getTransactionFee @'Shelley wa) Default payload
verify rb
[ expectResponseCode HTTP.status202
, expectField (#estimatedMin . #getQuantity) (.< feeEstMin)
, expectField (#estimatedMax . #getQuantity) (.< feeEstMax)
]

describe "TRANS_ESTIMATE_08 - Bad payload" $ do
let matrix =
[ ( "empty payload", NonJson "" )
Expand All @@ -552,7 +661,7 @@ spec = do
w <- emptyWallet ctx
let payload = nonJson
r <- request @ApiFee ctx
(Link.getTransactionFee @'Shelley w) Default payload
(Link.getTransactionFee @'Shelley w) Default payload
expectResponseCode @IO HTTP.status400 r

it "TRANS_ESTIMATE_03 - we see result when we can't cover fee" $ \ctx -> do
Expand Down Expand Up @@ -1641,6 +1750,11 @@ spec = do
"passphrase": #{passphrase}
}|]

addTxMetadata :: Aeson.Value -> Payload -> Payload
addTxMetadata md (Json (Aeson.Object o)) =
Json (Aeson.Object (o <> ("metadata" .= md)))
addTxMetadata _ _ = error "can't do that"

unsafeGetTransactionTime
:: [ApiTransaction n]
-> UTCTime
Expand Down
1 change: 1 addition & 0 deletions nix/.stack.nix/cardano-wallet-core-integration.nix

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

0 comments on commit 57297c4

Please sign in to comment.