@@ -105,12 +105,16 @@ import Data.Proxy
105105 ( Proxy (.. ) )
106106import Data.Quantity
107107 ( Quantity (.. ) )
108+ import Data.Type.Equality
109+ ( testEquality )
108110import Data.Word
109111 ( Word16 , Word64 , Word8 )
110112import Ouroboros.Consensus.Shelley.Protocol.Crypto
111113 ( Crypto (.. ) )
112114import Ouroboros.Network.Block
113115 ( SlotNo )
116+ import Type.Reflection
117+ ( Typeable , typeRep )
114118
115119import qualified Cardano.Api as Cardano
116120import qualified Cardano.Byron.Codec.Cbor as CBOR
@@ -157,17 +161,19 @@ emptyTxPayload :: Crypto c => TxPayload c
157161emptyTxPayload = TxPayload mempty mempty
158162
159163mkTx
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
312321dummyCoinSel :: 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
362373computeTxSize
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
461475mkWithdrawals
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.
0 commit comments