Skip to content

Commit 298f91d

Browse files
committed
assign correct network discrimination to withdrawals
This was hard-coded to mainnet, for some reasons.
1 parent 8078cf0 commit 298f91d

File tree

5 files changed

+63
-35
lines changed

5 files changed

+63
-35
lines changed

lib/core/src/Cardano/Wallet/Primitive/AddressDerivation.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -472,7 +472,7 @@ instance MonadRandom ((->) (Passphrase "salt")) where
472472
-------------------------------------------------------------------------------}
473473

474474
-- | Available network options.
475-
data NetworkDiscriminant = Mainnet | Testnet Nat
475+
data NetworkDiscriminant = Mainnet | Testnet Nat deriving Typeable
476476

477477
class NetworkDiscriminantVal (n :: NetworkDiscriminant) where
478478
networkDiscriminantVal :: Text

lib/shelley/src/Cardano/Wallet/Shelley.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -153,6 +153,8 @@ import System.Exit
153153
( ExitCode (..) )
154154
import System.IOManager
155155
( withIOManager )
156+
import Type.Reflection
157+
( Typeable )
156158

157159
import qualified Cardano.Pool.DB.Sqlite as Pool
158160
import qualified Cardano.Wallet.Api.Server as Server
@@ -172,6 +174,7 @@ data SomeNetworkDiscriminant where
172174
, DelegationAddress n ShelleyKey
173175
, DecodeAddress n
174176
, EncodeAddress n
177+
, Typeable n
175178
)
176179
=> Proxy n
177180
-> SomeNetworkDiscriminant

lib/shelley/src/Cardano/Wallet/Shelley/Transaction.hs

Lines changed: 41 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -105,12 +105,16 @@ import Data.Proxy
105105
( Proxy (..) )
106106
import Data.Quantity
107107
( Quantity (..) )
108+
import Data.Type.Equality
109+
( testEquality )
108110
import Data.Word
109111
( Word16, Word64, Word8 )
110112
import Ouroboros.Consensus.Shelley.Protocol.Crypto
111113
( Crypto (..) )
112114
import Ouroboros.Network.Block
113115
( SlotNo )
116+
import Type.Reflection
117+
( Typeable, typeRep )
114118

115119
import qualified Cardano.Api as Cardano
116120
import qualified Cardano.Byron.Codec.Cbor as CBOR
@@ -157,17 +161,19 @@ emptyTxPayload :: Crypto c => TxPayload c
157161
emptyTxPayload = TxPayload mempty mempty
158162

159163
mkTx
160-
:: WalletKey k
161-
=> TxPayload TPraosStandardCrypto
164+
:: forall (n :: NetworkDiscriminant) k. (Typeable n, WalletKey k)
165+
=> Proxy n
166+
-> TxPayload TPraosStandardCrypto
162167
-> SlotNo
163168
-- ^ Time to Live
164169
-> (k 'AddressK XPrv, Passphrase "encryption")
165170
-- ^ Reward account
166171
-> (Address -> Maybe (k 'AddressK XPrv, Passphrase "encryption"))
167172
-> CoinSelection
168173
-> Either ErrMkTx (Tx, SealedTx)
169-
mkTx (TxPayload certs mkExtraWits) timeToLive (rewardAcnt, pwdAcnt) keyFrom cs = do
174+
mkTx proxy (TxPayload certs mkExtraWits) timeToLive (rewardAcnt, pwdAcnt) keyFrom cs = do
170175
let withdrawals = mkWithdrawals
176+
proxy
171177
(toChimericAccountRaw . getRawKey . publicKey $ rewardAcnt)
172178
(withdrawal cs)
173179

@@ -193,24 +199,25 @@ newTransactionLayer
193199
:: forall (n :: NetworkDiscriminant) k t.
194200
( t ~ IO Shelley
195201
, WalletKey k
202+
, Typeable n
196203
)
197204
=> Proxy n
198205
-> ProtocolMagic
199206
-> EpochLength
200207
-> TransactionLayer t k
201-
newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
202-
{ mkStdTx = \acc ks tip -> mkTx emptyTxPayload (defaultTTL epochLength tip) acc ks
208+
newTransactionLayer proxy _protocolMagic epochLength = TransactionLayer
209+
{ mkStdTx = \acc ks tip ->
210+
mkTx proxy emptyTxPayload (defaultTTL epochLength tip) acc ks
203211
, initDelegationSelection = _initDelegationSelection
204212
, mkDelegationJoinTx = _mkDelegationJoinTx
205213
, mkDelegationQuitTx = _mkDelegationQuitTx
206214
, decodeSignedTx = _decodeSignedTx
207-
, minimumFee = _minimumFee
208-
, estimateMaxNumberOfInputs = _estimateMaxNumberOfInputs
215+
, minimumFee = _minimumFee proxy
216+
, estimateMaxNumberOfInputs = _estimateMaxNumberOfInputs proxy
209217
, validateSelection = const $ return ()
210218
, allowUnbalancedTx = True
211219
}
212220
where
213-
214221
_initDelegationSelection
215222
:: FeePolicy
216223
-- Current fee policy
@@ -254,7 +261,7 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
254261

255262
let payload = TxPayload certs mkWits
256263
let ttl = defaultTTL epochLength tip
257-
mkTx payload ttl acc keyFrom cs
264+
mkTx proxy payload ttl acc keyFrom cs
258265

259266
_mkDelegationQuitTx
260267
:: (k 'AddressK XPrv, Passphrase "encryption")
@@ -277,15 +284,17 @@ newTransactionLayer _proxy _protocolMagic epochLength = TransactionLayer
277284

278285
let payload = TxPayload certs mkWits
279286
let ttl = defaultTTL epochLength tip
280-
mkTx payload ttl acc keyFrom cs
287+
mkTx proxy payload ttl acc keyFrom cs
281288

282289
_estimateMaxNumberOfInputs
283-
:: Quantity "byte" Word16
290+
:: forall (n :: NetworkDiscriminant). Typeable n
291+
=> Proxy n
292+
-> Quantity "byte" Word16
284293
-- ^ Transaction max size in bytes
285294
-> Word8
286295
-- ^ Number of outputs in transaction
287296
-> Word8
288-
_estimateMaxNumberOfInputs (Quantity maxSize) nOuts =
297+
_estimateMaxNumberOfInputs proxy (Quantity maxSize) nOuts =
289298
fromIntegral $ bisect (lowerBound, upperBound)
290299
where
291300
bisect (!inf, !sup)
@@ -306,7 +315,7 @@ _estimateMaxNumberOfInputs (Quantity maxSize) nOuts =
306315

307316
isTooBig nInps = size > fromIntegral maxSize
308317
where
309-
size = computeTxSize Nothing sel
318+
size = computeTxSize proxy Nothing sel
310319
sel = dummyCoinSel nInps (fromIntegral nOuts)
311320

312321
dummyCoinSel :: Int -> Int -> CoinSelection
@@ -346,12 +355,14 @@ _decodeSignedTx bytes = do
346355
Left $ ErrDecodeSignedTxWrongPayload (Cardano.renderApiError apiErr)
347356

348357
_minimumFee
349-
:: FeePolicy
358+
:: forall (n :: NetworkDiscriminant). Typeable n
359+
=> Proxy (n :: NetworkDiscriminant)
360+
-> FeePolicy
350361
-> Maybe DelegationAction
351362
-> CoinSelection
352363
-> Fee
353-
_minimumFee policy action cs =
354-
computeFee $ computeTxSize action cs
364+
_minimumFee proxy policy action cs =
365+
computeFee $ computeTxSize proxy action cs
355366
where
356367
computeFee :: Integer -> Fee
357368
computeFee size =
@@ -360,10 +371,12 @@ _minimumFee policy action cs =
360371
LinearFee (Quantity a) (Quantity b) _unused = policy
361372

362373
computeTxSize
363-
:: Maybe DelegationAction
374+
:: forall (n :: NetworkDiscriminant). Typeable n
375+
=> Proxy (n :: NetworkDiscriminant)
376+
-> Maybe DelegationAction
364377
-> CoinSelection
365378
-> Integer
366-
computeTxSize action cs =
379+
computeTxSize proxy action cs =
367380
SL.txsize $ SL.Tx unsigned wits metadata
368381
where
369382
metadata = SL.SNothing
@@ -397,6 +410,7 @@ computeTxSize action cs =
397410
dummyKeyHashRaw = BS.pack (replicate 28 0)
398411

399412
withdrawals = mkWithdrawals
413+
proxy
400414
(ChimericAccount dummyKeyHashRaw)
401415
(withdrawal cs)
402416

@@ -459,19 +473,24 @@ mkUnsignedTx ttl cs withdrawals certs =
459473
unsigned
460474

461475
mkWithdrawals
462-
:: ChimericAccount
476+
:: forall (n :: NetworkDiscriminant). (Typeable n)
477+
=> Proxy n
478+
-> ChimericAccount
463479
-> Word64
464480
-> Map (SL.RewardAcnt TPraosStandardCrypto) SL.Coin
465-
mkWithdrawals (ChimericAccount keyHash) amount
481+
mkWithdrawals _ (ChimericAccount keyHash) amount
466482
| amount == 0 = mempty
467483
| otherwise = Map.fromList
468-
[ ( SL.RewardAcnt SL.Mainnet keyHashObj
484+
[ ( SL.RewardAcnt network keyHashObj
469485
, SL.Coin $ fromIntegral amount
470486
)
471487
]
472488
where
473489
keyHashObj = SL.KeyHashObj $ SL.KeyHash $ Hash.UnsafeHash keyHash
474-
490+
network =
491+
case testEquality (typeRep @n) (typeRep @'Mainnet) of
492+
Just{} -> SL.Mainnet
493+
Nothing -> SL.Testnet
475494

476495
-- TODO: The SlotId-SlotNo conversion based on epoch length would not
477496
-- work if the epoch length changed in a hard fork.

lib/shelley/test/integration/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -266,7 +266,7 @@ mkFeeEstimator policy = \case
266266
mempty { inputs = inps, change = outs }
267267

268268
computeFee selection action =
269-
fromIntegral $ getFee $ _minimumFee policy action selection
269+
fromIntegral $ getFee $ _minimumFee (Proxy @'Mainnet) policy action selection
270270

271271
{-------------------------------------------------------------------------------
272272
Logging

lib/shelley/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs

Lines changed: 17 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -113,14 +113,15 @@ spec = do
113113
prop "roundtrip" prop_decodeSignedTxRoundtrip
114114

115115
describe "estimateMaxNumberOfInputs" $ do
116+
let proxy = Proxy @'Mainnet
116117
it "order of magnitude, nOuts = 1" $
117-
_estimateMaxNumberOfInputs (Quantity 4096) 1 `shouldBe` 27
118+
_estimateMaxNumberOfInputs proxy (Quantity 4096) 1 `shouldBe` 27
118119
it "order of magnitude, nOuts = 10" $
119-
_estimateMaxNumberOfInputs (Quantity 4096) 10 `shouldBe` 19
120+
_estimateMaxNumberOfInputs proxy (Quantity 4096) 10 `shouldBe` 19
120121
it "order of magnitude, nOuts = 20" $
121-
_estimateMaxNumberOfInputs (Quantity 4096) 20 `shouldBe` 10
122+
_estimateMaxNumberOfInputs proxy (Quantity 4096) 20 `shouldBe` 10
122123
it "order of magnitude, nOuts = 30" $
123-
_estimateMaxNumberOfInputs (Quantity 4096) 30 `shouldBe` 1
124+
_estimateMaxNumberOfInputs proxy (Quantity 4096) 30 `shouldBe` 1
124125

125126
prop "more outputs ==> less inputs" prop_moreOutputsMeansLessInputs
126127
prop "less outputs ==> more inputs" prop_lessOutputsMeansMoreInputs
@@ -187,9 +188,11 @@ prop_moreOutputsMeansLessInputs
187188
-> Property
188189
prop_moreOutputsMeansLessInputs size nOuts = withMaxSuccess 1000 $
189190
nOuts < maxBound ==>
190-
_estimateMaxNumberOfInputs size nOuts
191+
_estimateMaxNumberOfInputs proxy size nOuts
191192
>=
192-
_estimateMaxNumberOfInputs size (nOuts + 1)
193+
_estimateMaxNumberOfInputs proxy size (nOuts + 1)
194+
where
195+
proxy = Proxy @'Mainnet
193196

194197
-- | REducing the number of outputs increases the number of inputs.
195198
prop_lessOutputsMeansMoreInputs
@@ -198,10 +201,11 @@ prop_lessOutputsMeansMoreInputs
198201
-> Property
199202
prop_lessOutputsMeansMoreInputs size nOuts = withMaxSuccess 1000 $
200203
nOuts > minBound ==>
201-
_estimateMaxNumberOfInputs size (nOuts - 1)
204+
_estimateMaxNumberOfInputs proxy size (nOuts - 1)
202205
>=
203-
_estimateMaxNumberOfInputs size nOuts
204-
206+
_estimateMaxNumberOfInputs proxy size nOuts
207+
where
208+
proxy = Proxy @'Mainnet
205209

206210
-- | Increasing the max size automatically increased the number of inputs
207211
prop_biggerMaxSizeMeansMoreInputs
@@ -210,9 +214,11 @@ prop_biggerMaxSizeMeansMoreInputs
210214
-> Property
211215
prop_biggerMaxSizeMeansMoreInputs (Quantity size) nOuts = withMaxSuccess 1000 $
212216
size < maxBound `div` 2 ==>
213-
_estimateMaxNumberOfInputs (Quantity size) nOuts
217+
_estimateMaxNumberOfInputs proxy (Quantity size) nOuts
214218
<=
215-
_estimateMaxNumberOfInputs (Quantity (size * 2)) nOuts
219+
_estimateMaxNumberOfInputs proxy (Quantity (size * 2)) nOuts
220+
where
221+
proxy = Proxy @'Mainnet
216222

217223
testCoinSelOpts :: CoinSelectionOptions ()
218224
testCoinSelOpts = coinSelOpts testTxLayer (Quantity 4096)

0 commit comments

Comments
 (0)