Skip to content

Commit 12704fc

Browse files
committed
Use splitToken check and some improvements
Add haddocks, remove unused imports Signed-off-by: Sasha Bogicevic <[email protected]>
1 parent a0fa076 commit 12704fc

File tree

4 files changed

+16
-5
lines changed

4 files changed

+16
-5
lines changed

hydra-node/src/Hydra/API/HTTPServer.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Data.Text (pack)
1515
import Hydra.API.APIServerLog (APIServerLog (..), Method (..), PathInfo (..))
1616
import Hydra.API.ClientInput (ClientInput (..))
1717
import Hydra.API.ServerOutput (ClientMessage (..), CommitInfo (..), ServerOutput (..), TimedServerOutput (..), getConfirmedSnapshot, getSeenSnapshot, getSnapshotUtxo)
18-
import Hydra.Cardano.Api (AssetName, Coin, LedgerEra, PolicyAssets, PolicyId, Quantity, Tx)
18+
import Hydra.Cardano.Api (Coin, LedgerEra, PolicyAssets, PolicyId, Tx)
1919
import Hydra.Chain (Chain (..), PostTxError (..), draftCommitTx)
2020
import Hydra.Chain.ChainState (IsChainState)
2121
import Hydra.Chain.Direct.State ()

hydra-node/src/Hydra/Chain.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,13 +17,11 @@ import Cardano.Ledger.Core (PParams)
1717
import Data.List.NonEmpty ((<|))
1818
import Hydra.Cardano.Api (
1919
Address,
20-
AssetName,
2120
ByronAddr,
2221
Coin (..),
2322
LedgerEra,
2423
PolicyAssets,
2524
PolicyId,
26-
Quantity,
2725
)
2826
import Hydra.Chain.ChainState (ChainSlot, IsChainState (..))
2927
import Hydra.Tx (
@@ -211,7 +209,7 @@ data PostTxError tx
211209
| DepositTooLow {providedValue :: Coin, minimumValue :: Coin}
212210
| AmountTooLow {providedValue :: Coin, totalUTxOValue :: Coin}
213211
| MissingTokenPolicies [PolicyId]
214-
| InvalidTokenRequest [(PolicyId, (AssetName, Quantity))]
212+
| InvalidTokenRequest [(PolicyId, PolicyAssets)]
215213
deriving stock (Generic)
216214

217215
deriving stock instance IsChainState tx => Eq (PostTxError tx)

hydra-node/src/Hydra/Chain/Direct/Handlers.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ import Cardano.Slotting.Slot (SlotNo (..))
1515
import Control.Concurrent.Class.MonadSTM (modifyTVar, writeTVar)
1616
import Control.Monad.Class.MonadSTM (throwSTM)
1717
import Data.List qualified as List
18+
import Data.Map.Strict qualified as Map
1819
import Hydra.Cardano.Api (
1920
BlockHeader,
2021
ChainPoint (..),
@@ -194,7 +195,10 @@ mkChain tracer queryTimeHandle wallet ctx LocalChainState{getLatest} submitTx =
194195
liftEither $ do
195196
checkAmount lookupUTxO amount
196197
rejectLowDeposits pparams lookupUTxO amount
197-
let (validTokens, _invalidTokens) = splitTokens lookupUTxO (fromMaybe mempty tokens)
198+
let (validTokens, invalidTokens) = splitTokens lookupUTxO (fromMaybe mempty tokens)
199+
unless (null invalidTokens) $
200+
throwError $
201+
InvalidTokenRequest (Map.assocs invalidTokens)
198202
(currentSlot, currentTime) <- case currentPointInTime of
199203
Left failureReason -> throwError FailedToConstructDepositTx{failureReason}
200204
Right (s, t) -> pure (s, t)

hydra-tx/src/Hydra/Tx/Deposit.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -132,6 +132,15 @@ mkDepositOutput networkId headId depositUTxO deadline =
132132
depositAddress :: NetworkId -> AddressInEra
133133
depositAddress networkId = mkScriptAddress networkId depositValidatorScript
134134

135+
-- | Splits the specified tokens into those that are available in sufficient quantities in the user's UTxO
136+
-- and those that are not (either because the policy is missing or the asset quantities are insufficient).
137+
--
138+
-- This function takes a user's UTxO and a map of specified policy IDs to their desired assets and quantities.
139+
-- It checks the total value in the UTxO, converts it to a policy-assets map, and then partitions the specified
140+
-- tokens into "ok" (available) and "invalid" (unavailable or insufficient).
141+
--
142+
-- If no tokens are specified, it returns two empty maps. Otherwise, it returns the partitioned maps, ensuring
143+
-- that if there are no invalid tokens, the second map is empty.
135144
splitTokens :: UTxO.UTxO -> Map PolicyId PolicyAssets -> (Map PolicyId PolicyAssets, Map PolicyId PolicyAssets)
136145
splitTokens userUTxO specifiedTokens
137146
| Map.null specifiedTokens = (mempty, mempty) -- Trivial case: no tokens specified

0 commit comments

Comments
 (0)