Skip to content

Commit

Permalink
Add ChainState's UTxO to the observable Chain UTxO
Browse files Browse the repository at this point in the history
  • Loading branch information
abailly committed Sep 19, 2022
1 parent 14f680e commit f43c546
Showing 1 changed file with 5 additions and 1 deletion.
6 changes: 5 additions & 1 deletion hydra-node/src/Hydra/Chain/Direct/Handlers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module Hydra.Chain.Direct.Handlers where
import Hydra.Prelude

import Cardano.Api.UTxO (fromPairs)
import qualified Cardano.Api.UTxO as UTxO
import Cardano.Ledger.Babbage.Tx (ValidatedTx)
import Cardano.Ledger.Crypto (StandardCrypto)
import Cardano.Ledger.Era (SupportsSegWit (fromTxSeq))
Expand Down Expand Up @@ -115,7 +116,10 @@ mkChain tracer queryTimeHandle wallet@TinyWallet{getUTxO} headState submitTx =
>>= finalizeTx tx wallet headState . toLedgerTx
)
submitTx vtx
, getUTxO = fromPairs . fmap toLedger . Map.assocs <$> atomically getUTxO
, getUTxO = atomically $ do
walletUtxo <- fmap toLedger . Map.assocs <$> getUTxO
knownUtxo <- Map.assocs . UTxO.toMap . getKnownUTxO . currentChainState <$> readTVar headState
pure $ fromPairs $ walletUtxo <> knownUtxo
}
where
toLedger (txIn, txOut) = (fromLedgerTxIn txIn, fromLedgerTxOut txOut)
Expand Down

0 comments on commit f43c546

Please sign in to comment.