Skip to content

Commit

Permalink
Fix coercion between different Point
Browse files Browse the repository at this point in the history
Following upgrade, castPoint does not work anymore so I ended up
manually unwrapping the hash representations to get what I needed.
  • Loading branch information
abailly-iohk committed Oct 12, 2021
1 parent 9a7c00b commit 730694b
Showing 1 changed file with 10 additions and 5 deletions.
15 changes: 10 additions & 5 deletions hydra-node/src/Hydra/Chain/Direct/Wallet.hs
Expand Up @@ -5,7 +5,7 @@
module Hydra.Chain.Direct.Wallet where

import qualified Cardano.Crypto.DSIGN as Crypto
import Cardano.Crypto.Hash.Class (Hash (..))
import Cardano.Crypto.Hash.Class
import qualified Cardano.Ledger.Address as Ledger
import Cardano.Ledger.Alonzo.Tx (ValidatedTx (..))
import Cardano.Ledger.Alonzo.TxBody (collateral, inputs, outputs, txfee, pattern TxOut)
Expand Down Expand Up @@ -46,7 +46,8 @@ import Ouroboros.Consensus.Ledger.Query (Query (..))
import Ouroboros.Consensus.Network.NodeToClient (Codecs' (..))
import Ouroboros.Consensus.Shelley.Ledger.Block (ShelleyBlock (..), ShelleyHash (..))
import Ouroboros.Consensus.Shelley.Ledger.Query (BlockQuery (..))
import Ouroboros.Network.Block (Point (..), Tip (..), castPoint, blockPoint, genesisPoint)
import Ouroboros.Network.Block (Point (..), Tip (..), castPoint, blockPoint, genesisPoint,
pattern BlockPoint, pattern GenesisPoint)
import Ouroboros.Network.Magic (NetworkMagic (..))
import Ouroboros.Network.Mux (
MuxMode (..),
Expand Down Expand Up @@ -338,9 +339,13 @@ stateQueryClient tipVar utxoVar address =
-- case, we can't do much but logging and retrying later.
Left{} ->
handleEraMismatch
Right (castPoint -> tip) -> do
let query = QueryIfCurrentAlonzo $ GetUTxOByAddress (Set.singleton address)
pure $ LSQ.SendMsgQuery (BlockQuery query) (clientStQueryingUtxo tip)
Right tip -> do
let blk = case tip of
GenesisPoint -> GenesisPoint
(BlockPoint slot h) -> BlockPoint slot (fromShelleyHash h)
fromShelleyHash (Ledger.unHashHeader . unShelleyHash -> UnsafeHash h) = coerce h
query = QueryIfCurrentAlonzo $ GetUTxOByAddress (Set.singleton address)
pure $ LSQ.SendMsgQuery (BlockQuery query) (clientStQueryingUtxo blk)
}

clientStQueryingUtxo :: Point Block -> LSQ.ClientStQuerying Block (Point Block) (Query Block) m () (QueryResult UtxoSet)
Expand Down

0 comments on commit 730694b

Please sign in to comment.