Skip to content

Commit

Permalink
Merge #3340
Browse files Browse the repository at this point in the history
3340: Update to cardano-node 1.35-rc3 r=Anviking a=sevanspowell

I have:

- Bumped the following dependencies to the `1.35.0-rc3` tag:
  - cardano-node
  - cardano-base
  - cardano-ledger
  - ouroboros-network
- Updated cardano-wallet code to build with `1.35.0-rc3` tag:
  - `evaluateTransactionExecutionUnits` has a new error type, updated
  `ErrAssignRedeemers` accordingly.
  - `SimpleScriptWitness` now takes a `SimpleScriptOrReferenceInput` instead of a
  `SimpleScript`, updated generators accordingly.
 
TODO:
- [x] Consider whether the `prop_balanceTransactionUnresolvedInputs` test makes sense anymore.
- [ ] Test the API output of `ErrAssignRedeemersTranslationError`.
- [x] Update readme compatibility matrix

### Issue Number

ADP-1907

Co-authored-by: Samuel Evans-Powell <[email protected]>
Co-authored-by: Johannes Lund <[email protected]>
  • Loading branch information
3 people authored Jun 20, 2022
2 parents 69ce334 + 700bf4b commit 7bb3ec2
Show file tree
Hide file tree
Showing 7 changed files with 121 additions and 70 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ See **Installation Instructions** for each available [release](https://github.co
>
> | cardano-wallet | cardano-node (compatible versions) | SMASH (compatible versions)
> | --- | --- | ---
> | `master` branch | [1.35.0-rc2](https://github.com/input-output-hk/cardano-node/releases/tag/1.35.0-rc2) | [1.6.1](https://github.com/input-output-hk/smash/releases/tag/1.6.1)
> | `master` branch | [1.35.0-rc3](https://github.com/input-output-hk/cardano-node/releases/tag/1.35.0-rc3) | [1.6.1](https://github.com/input-output-hk/smash/releases/tag/1.6.1)
> | [v2022-05-27](https://github.com/input-output-hk/cardano-wallet/releases/tag/v2022-05-27) | [1.34.1](https://github.com/input-output-hk/cardano-node/releases/tag/1.34.1) | [1.6.1](https://github.com/input-output-hk/smash/releases/tag/1.6.1)
> | [v2022-04-27](https://github.com/input-output-hk/cardano-wallet/releases/tag/v2022-04-27) | [1.34.1](https://github.com/input-output-hk/cardano-node/releases/tag/1.34.1) | [1.6.1](https://github.com/input-output-hk/smash/releases/tag/1.6.1)
> | [v2022-01-18](https://github.com/input-output-hk/cardano-wallet/releases/tag/v2022-01-18) | [1.33.0](https://github.com/input-output-hk/cardano-node/releases/tag/1.33.0) | [1.6.1](https://github.com/input-output-hk/smash/releases/tag/1.6.1)
Expand Down
16 changes: 8 additions & 8 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -105,8 +105,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-base
tag: 631cb6cf1fa01ab346233b610a38b3b4cba6e6ab
--sha256: 0944wg2nqazmhlmsynwgdwxxj6ay0hb9qig9l128isb2cjia0hlp
tag: 0f3a867493059e650cda69e20a5cbf1ace289a57
--sha256: 0p0az3sbkhb7njji8xxdrfb0yx2gc8fmrh872ffm8sfip1w29gg1
subdir:
base-deriving-via
binary
Expand Down Expand Up @@ -154,8 +154,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-ledger
tag: e290bf8d0ea272a51e9acd10adc96b4e12e00d37
--sha256: 1pmdg80a8irrqgdhbp46a9jx628mjbrj0k89xv5nb5dy37z5ig5f
tag: 52da70e5a0472cd4433876289f1aebaa0c6e5c85
--sha256: 0aiislbwx5yqdidwd66zqqpskvay84iwkgsgi5l96rbfcsf0n8lq
subdir:
eras/alonzo/impl
eras/alonzo/test-suite
Expand Down Expand Up @@ -184,8 +184,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/cardano-node
tag: 95c3692cfbd4cdb82071495d771b23e51840fb0e
--sha256: 1s4jjksz185dg4lp36ldha7vccxh0rk8zlvqms00zhg8kla21kr5
tag: 6471c31f8b61798df57a9f3345548703295cac9e
--sha256: 1xq2m40wgl6aw9zygzkvzcxxakcwd3p62q9j671r99i4c4x36z8g
subdir:
cardano-api
cardano-git-rev
Expand Down Expand Up @@ -239,8 +239,8 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/input-output-hk/ouroboros-network
tag: 04245dbd69387da98d3a37de9f400965e922bb0e
--sha256: 0bgfclc7h441dwq9z69697nqfir6shj4358zxmwjiaifp93zkc2p
tag: a65c29b6a85e90d430c7f58d362b7eb097fd4949
--sha256: 1fmab5hmi1y8lss97xh6hhikmyhsx9x31yhvg6zpr2kcq7kc6qkf
subdir:
monoidal-synchronisation
network-mux
Expand Down
18 changes: 15 additions & 3 deletions lib/core/src/Cardano/Api/Gen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,6 +116,7 @@ import Cardano.Api.Shelley
, PoolId
, ProtocolParameters (..)
, ReferenceScript (..)
, SimpleScriptOrReferenceInput (..)
, StakeCredential (..)
, StakePoolMetadata (..)
, StakePoolMetadataReference (..)
Expand Down Expand Up @@ -453,6 +454,17 @@ genSimpleScript lang =
(Positive m) <- arbitrary
genTerm (n `div` (m + 3))

genReferenceInput :: Gen TxIn
genReferenceInput = genTxIn

genSimpleScriptOrReferenceInput
:: SimpleScriptVersion lang
-> Gen (SimpleScriptOrReferenceInput lang)
genSimpleScriptOrReferenceInput lang =
oneof [ SScript <$> genSimpleScript lang
, SReferenceScript <$> genReferenceInput
]

genScript :: ScriptLanguage lang -> Gen (Script lang)
genScript (SimpleScriptLanguage lang) =
SimpleScript lang <$> genSimpleScript lang
Expand Down Expand Up @@ -690,7 +702,7 @@ genScriptWitnessMint
genScriptWitnessMint langEra =
case languageOfScriptLanguageInEra langEra of
(SimpleScriptLanguage ver) ->
SimpleScriptWitness langEra ver <$> genSimpleScript ver
SimpleScriptWitness langEra ver <$> genSimpleScriptOrReferenceInput ver
(PlutusScriptLanguage ver) ->
PlutusScriptWitness langEra ver
<$> genPlutusScriptOrReferenceInput ver
Expand All @@ -704,7 +716,7 @@ genScriptWitnessStake
genScriptWitnessStake langEra =
case languageOfScriptLanguageInEra langEra of
(SimpleScriptLanguage ver) ->
SimpleScriptWitness langEra ver <$> genSimpleScript ver
SimpleScriptWitness langEra ver <$> genSimpleScriptOrReferenceInput ver
(PlutusScriptLanguage ver) ->
PlutusScriptWitness langEra ver
<$> genPlutusScriptOrReferenceInput ver
Expand All @@ -718,7 +730,7 @@ genScriptWitnessSpend
genScriptWitnessSpend langEra =
case languageOfScriptLanguageInEra langEra of
(SimpleScriptLanguage ver) ->
SimpleScriptWitness langEra ver <$> genSimpleScript ver
SimpleScriptWitness langEra ver <$> genSimpleScriptOrReferenceInput ver
(PlutusScriptLanguage ver) ->
PlutusScriptWitness langEra ver
<$> genPlutusScriptOrReferenceInput ver
Expand Down
30 changes: 16 additions & 14 deletions lib/core/src/Cardano/Wallet/Api/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -137,7 +137,8 @@ import Cardano.Api.Extra
import Cardano.BM.Tracing
( HasPrivacyAnnotation (..), HasSeverityAnnotation (..) )
import Cardano.Ledger.Alonzo.TxInfo
( TranslationError (TimeTranslationPastHorizon) )
( TranslationError (TimeTranslationPastHorizon, TranslationLogicMissingInput)
)
import Cardano.Mnemonic
( SomeMnemonic )
import Cardano.Wallet
Expand Down Expand Up @@ -5043,26 +5044,27 @@ instance IsServerError ErrAssignRedeemers where
, "for one of your redeemers since I am unable to decode it"
, "into a valid Plutus data:", pretty r <> "."
]
ErrAssignRedeemersUnresolvedTxIns ins ->
-- Note that although this error is thrown from
-- '_assignScriptRedeemers', it's more related to balanceTransaction
-- in general than to assigning redeemers. Hence we don't mention
-- redeemers in the message.
apiError err400 UnresolvedInputs $ T.unwords
[ "The transaction I was given contains inputs I don't know"
, "about. Please ensure all foreign inputs are specified as "
, "part of the API request. The unknown inputs are:\n\n"
, pretty ins
]
ErrAssignRedeemersTranslationError TimeTranslationPastHorizon ->
ErrAssignRedeemersTranslationError (TranslationLogicMissingInput inp) ->
-- Note that although this error is thrown from
-- '_assignScriptRedeemers', it's more related to balanceTransaction
-- in general than to assigning redeemers. Hence we don't mention
-- redeemers in the message.
apiError err400 UnresolvedInputs $ T.unwords
[ "The transaction I was given contains inputs I don't know"
, "about. Please ensure all foreign inputs are specified as "
, "part of the API request. The unknown input is:\n\n"
, T.pack $ show inp
]
ErrAssignRedeemersTranslationError (TimeTranslationPastHorizon t) ->
-- We differentiate this from @TranslationError@ for partial API
-- backwards compatibility.
apiError err400 PastHorizon $ T.unwords
[ "The transaction's validity interval is past the horizon"
, "of safe slot-to-time conversions."
, "This may happen when I know about a future era"
, "which has not yet been confirmed on-chain. Try setting the"
, "bounds of the validity interval to be earlier."
, "bounds of the validity interval to be earlier.\n\n"
, "Here are the full details: " <> t
]
ErrAssignRedeemersTranslationError e ->
apiError err400 TranslationError $ T.unwords
Expand Down
6 changes: 3 additions & 3 deletions lib/core/src/Cardano/Wallet/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,8 @@ import Cardano.Api
( AnyCardanoEra )
import Cardano.Ledger.Alonzo.TxInfo
( TranslationError )
import Cardano.Ledger.Crypto
( StandardCrypto )
import Cardano.Wallet.CoinSelection
( SelectionCollateralRequirement (..)
, SelectionLimit
Expand Down Expand Up @@ -508,9 +510,7 @@ data ErrAssignRedeemers
-- ^ The given redeemer target couldn't be located in the transaction.
| ErrAssignRedeemersInvalidData Redeemer String
-- ^ Redeemer's data isn't a valid Plutus' data.
| ErrAssignRedeemersUnresolvedTxIns [TxIn]
-- ^ The transaction contains inputs which couldn't be resolved.
| ErrAssignRedeemersTranslationError TranslationError
| ErrAssignRedeemersTranslationError (TranslationError StandardCrypto)
-- ^ Mistranslating of hashes, credentials, certificates etc.
deriving (Generic, Eq, Show)

Expand Down
20 changes: 7 additions & 13 deletions lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,9 +84,7 @@ import Cardano.Binary
import Cardano.Crypto.Wallet
( XPub )
import Cardano.Ledger.Alonzo.Tools
( BasicFailure (BadTranslation, UnknownTxIns)
, evaluateTransactionExecutionUnits
)
( evaluateTransactionExecutionUnits )
import Cardano.Ledger.Crypto
( DSIGN )
import Cardano.Ledger.Era
Expand Down Expand Up @@ -1312,10 +1310,7 @@ _assignScriptRedeemers pparams ti resolveInput redeemers tx =
systemStart
costs
case res of
Left (UnknownTxIns ins) ->
Left $ ErrAssignRedeemersUnresolvedTxIns $
map fromShelleyTxIn (F.toList ins)
Left (BadTranslation translationError) ->
Left translationError ->
Left $ ErrAssignRedeemersTranslationError translationError
Right report ->
Right $ hoistScriptFailure indexedRedeemers report
Expand All @@ -1340,10 +1335,7 @@ _assignScriptRedeemers pparams ti resolveInput redeemers tx =
systemStart
costs
case res of
Left (UnknownTxIns ins) ->
Left $ ErrAssignRedeemersUnresolvedTxIns $
map fromShelleyTxIn (F.toList ins)
Left (BadTranslation translationError) -> do
Left translationError ->
Left $ ErrAssignRedeemersTranslationError translationError
Right report ->
Right $ hoistScriptFailure indexedRedeemers report
Expand Down Expand Up @@ -2340,8 +2332,10 @@ mkUnsignedTx era ttl cs md wdrls certs fees mintData burnData allScripts =
Cardano.negateValue $
toCardanoValue (TokenBundle (Coin 0) burnData)
toScriptWitness script =
Cardano.SimpleScriptWitness scriptWitsSupported
Cardano.SimpleScriptV2 (toCardanoSimpleScript script)
Cardano.SimpleScriptWitness
scriptWitsSupported
Cardano.SimpleScriptV2
(Cardano.SScript $ toCardanoSimpleScript script)
witMap =
Map.map toScriptWitness $
Map.mapKeys (toCardanoPolicyId . TokenMap.tokenPolicyId)
Expand Down
99 changes: 71 additions & 28 deletions lib/shelley/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,8 @@ import Cardano.BM.Data.Tracer
( nullTracer )
import Cardano.BM.Tracer
( Tracer )
import Cardano.Ledger.Alonzo.TxInfo
( TranslationError (TranslationLogicMissingInput) )
import Cardano.Ledger.Shelley.API
( StrictMaybe (SJust, SNothing), Wdrl (..) )
import Cardano.Ledger.ShelleyMA.Timelocks
Expand Down Expand Up @@ -329,6 +331,7 @@ import Test.Hspec
, shouldBe
, shouldSatisfy
, xdescribe
, xit
)
import Test.Hspec.Core.Spec
( SpecM )
Expand Down Expand Up @@ -2254,7 +2257,7 @@ balanceTransactionSpec = do
tx `shouldBe` Left ErrBalanceTxMaxSizeLimitExceeded

describe "when passed unresolved inputs" $ do
it "may fail"
xit "may fail"
$ property prop_balanceTransactionUnresolvedInputs

describe "sizeOfCoin" $ do
Expand Down Expand Up @@ -2988,48 +2991,88 @@ balanceTransaction' (Wallet' utxo wal pending) seed tx =
(utxo, wal, pending)
tx

-- | Tests that 'ErrAssignRedeemersUnresolvedTxIns' can in fact be returned by
-- | Tests that 'TranslationLogicMissingInput' can in fact be returned by
-- 'balanceTransaction'.
--
-- FIXME: Coverage is too poor. It might be best to replace with one or two
-- simple unit tests instead. (one where dropping input resulted in an error
-- like 'TranslationLogicMissingInput' and one where it succeeded anyway because
-- of the wallet utxo)
prop_balanceTransactionUnresolvedInputs
:: Wallet'
-> ShowBuildable (PartialTx Cardano.AlonzoEra)
:: (ShowBuildable (PartialTx Cardano.AlonzoEra))
-> StdGenSeed
-> Property
prop_balanceTransactionUnresolvedInputs wallet (ShowBuildable partialTx') seed =
checkCoverage
$ forAll (dropResolvedInputs partialTx') $ \(partialTx, dropped) -> do
let res = balanceTransaction' wallet seed partialTx
cover 1 (isUnresolvedTxInsErr res) "unknown txins" $
case res of
Right _
| null dropped
-> label "nothing dropped"
$ property True
| otherwise
-> label "succeeded despite unresolved input"
$ property True
-- Balancing can succeed if the dropped inputs
-- happen to be a part of the wallet UTxO.
Left (ErrBalanceTxAssignRedeemers
(ErrAssignRedeemersUnresolvedTxIns _))
-> property True
Left _
-> label "other error" $ property True
prop_balanceTransactionUnresolvedInputs (ShowBuildable partialTx') seed =
-- checkCoverage
forAll (dropResolvedInputs partialTx') $ \(partialTx, dropped) -> do
let wallet = smallWallet
let res = balanceTransaction' wallet seed partialTx

let userSpecifiedInputs = Set.fromList $
map (\(i,_,_) -> i) $ view #inputs partialTx
let walletUTxOInputs =
let
Wallet' _ w _ = wallet
in
Set.fromList $ map fst $ UTxO.toList $ view #utxo w

let requiredInputs =
userSpecifiedInputs `Set.difference` walletUTxOInputs

cover 1 (isUnresolvedTxInsErr res) "unknown txins" $
case res of
Right _
| null dropped
-> label "nothing dropped"
$ property True
| otherwise
-> label "succeeded despite unresolved input" $ do
let droppedSet =
Set.fromList $ map (\(i,_,_) -> i) dropped
property $
(requiredInputs `Set.intersection` droppedSet)
=== mempty
-- Balancing can succeed if the dropped inputs
-- happen to be a part of the wallet UTxO.
Left (ErrBalanceTxAssignRedeemers
(ErrAssignRedeemersTranslationError
(TranslationLogicMissingInput _)))
-> property True
Left e
-> counterexample (show e) $ property False
where
isUnresolvedTxInsErr
(Left (ErrBalanceTxAssignRedeemers
(ErrAssignRedeemersUnresolvedTxIns _))) = True
(Left
(ErrBalanceTxAssignRedeemers
(ErrAssignRedeemersTranslationError
(TranslationLogicMissingInput _)))) = True
isUnresolvedTxInsErr _ = False

dropResolvedInputs (PartialTx tx inputs redeemers) = do
shouldKeep <- vectorOf (length inputs) $ frequency
[ (8, pure False)
, (2, pure True)
[ (9, pure False)
, (1, pure True)
]
let inputs' = map snd $ filter fst $ zip shouldKeep inputs
let dropped = map snd $ filter (not . fst) $ zip shouldKeep inputs
pure (PartialTx tx inputs' redeemers, dropped)

-- A wallet with a single utxo for minimal overlap with user-specified
-- resolution, and lots of ada to make balancing succeed.
smallWallet = mkTestWallet rootK $ utxo [Coin 20_000_000_000_000]
where
utxo coins = UTxO $ Map.fromList $ zip ins outs
where
ins = map (TxIn dummyHash) [0..]
outs = map (TxOut addr . TokenBundle.fromCoin) coins
dummyHash = Hash $ B8.replicate 32 '0'

mw = SomeMnemonic $ either (error . show) id
(entropyToMnemonic @12 <$> mkEntropy "0000000000000000")
rootK = Shelley.unsafeGenerateKeyFromSeed (mw, Nothing) mempty
addr = Address $ unsafeFromHex
"60b1e5e0fb74c86c801f646841e07cdb42df8b82ef3ce4e57cb5412e77"

prop_posAndNegFromCardanoValueRoundtrip :: Property
prop_posAndNegFromCardanoValueRoundtrip = forAll genSignedValue $ \v ->
let
Expand Down

0 comments on commit 7bb3ec2

Please sign in to comment.