11{-# LANGUAGE AllowAmbiguousTypes #-}
22{-# LANGUAGE RankNTypes #-}
33
4- module BotPlutusInterface.CoinSelection (valueToVec , valuesToVecs , selectTxIns , uniqueAssetClasses ) where
4+ module BotPlutusInterface.CoinSelection (
5+ valueToVec ,
6+ valuesToVecs ,
7+ selectTxIns ,
8+ uniqueAssetClasses ,
9+ ) where
510
611import BotPlutusInterface.Effects (PABEffect , printBpiLog )
712import BotPlutusInterface.Types (LogLevel (Debug ), LogType (CoinSelectionLog ))
@@ -104,7 +109,7 @@ Now, let's see how the coin selection works by looking at an example:
104109 utxo3-vector: [3, 6]
105110
106111 Now, as stated above our goal is to get as close to output-vector as possible,
107- but we also need to satisfiy the following condition:
112+ but we also need to satisfy the following condition:
108113
109114 1. Each column of the resultant vector must be greater than or equal to the corresponding
110115 column of the output vector.
@@ -118,7 +123,7 @@ Now, let's see how the coin selection works by looking at an example:
118123
119124 input-vector: [0, 0]
120125
121- Now, we can start searching for utxos that can statisfy our goal and mission:
126+ Now, we can start searching for utxos that can satisfy our goal and mission:
122127
123128 step 1. Add input vector to all the utxo vectors. In this case these vectors will be
124129 utxo1-vector, utxo2-vector, utxo3-vector.
@@ -133,10 +138,10 @@ Now, let's see how the coin selection works by looking at an example:
133138 ]
134139
135140 As, we can see the distance between utxo1-vector and output-vector is very large
136- which is to be expected as utxo1-vector contains lots of "value" of different assetclass .
141+ which is to be expected as utxo1-vector contains lots of "value" of different AssetClass .
137142
138143 step 3. sort the distances, and select the utxos with least distances
139- until all the conditions are statisfied .
144+ until all the conditions are satisfied .
140145
141146 Result: [ 1.41
142147 , 2.00
@@ -145,7 +150,7 @@ Now, let's see how the coin selection works by looking at an example:
145150
146151 Since, utxo2-vector has the least distance we will select that utxo.
147152
148- But, selecting utxo2-vector alone doesn't statisfy all our conditions,
153+ But, selecting utxo2-vector alone doesn't satisfy all our conditions,
149154 hence we will have to continue selecting. After utxo2-vector, the vector with
150155 least distance is utxo3-vector, hence we will select that vector.
151156
@@ -161,7 +166,7 @@ data SearchStrategy
161166 = -- | This is a greedy search that searches for nearest utxo using l2norm.
162167 Greedy
163168 | -- | This is like greedy search, but here there's
164- -- additonal goal that the change utxo should be equal to the output utxo.
169+ -- additional goal that the change utxo should be equal to the output utxo.
165170 GreedyApprox
166171 deriving stock (Eq , Show )
167172
@@ -170,8 +175,9 @@ defaultSearchStrategy = GreedyApprox
170175
171176type ValueVector = Vector Integer
172177
173- -- 'selectTxIns' selects utxos using default search strategy, it also preprocesses
174- -- the utxos values in to normalized vectors. So that distances between utxos can be calculated.
178+ {- | 'selectTxIns' selects utxos using default search strategy, it also preprocesses
179+ the utxos values in to normalized vectors. So that distances between utxos can be calculated.
180+ -}
175181selectTxIns ::
176182 forall (w :: Type ) (effs :: [Type -> Type ]).
177183 Member (PABEffect w ) effs =>
@@ -250,7 +256,7 @@ selectTxIns originalTxIns utxosIndex outValue =
250256 where
251257 -- This represents the condition when we can stop searching for utxos.
252258 -- First condition is that the input vector must not be zero vector, i.e.
253- -- There must be atleast some input to the transaction.
259+ -- There must be at least some input to the transaction.
254260 -- Second condition is that all the values of input vector must be greater than
255261 -- or equal to the output vector.
256262 isSufficient :: ValueVector -> ValueVector -> Bool
@@ -291,7 +297,7 @@ greedySearch stopSearch outVec txInsVec utxosVec
291297 -- we stop the search if there are no utxos vectors left, as we will not be able to
292298 -- select any further utxos as input to a transaction.
293299 | null utxosVec =
294- printBpiLog @ w (Debug [CoinSelectionLog ]) " Greedy: The list of remanining UTxO vectors in null."
300+ printBpiLog @ w (Debug [CoinSelectionLog ]) " Greedy: The list of remaining UTxO vectors in null."
295301 >> pure (Right mempty )
296302 -- we stop the search if the predicate `stopSearch` is true.
297303 | stopSearch txInsVec =
@@ -361,7 +367,7 @@ greedyApprox stopSearch outVec txInsVec utxosVec
361367 -- we stop the search if there are no utxos vectors left, as we will not be able to
362368 -- select any further utxos as input to a transaction.
363369 | null utxosVec =
364- printBpiLog @ w (Debug [CoinSelectionLog ]) " Greedy Pruning: The list of remanining UTxO vectors in null."
370+ printBpiLog @ w (Debug [CoinSelectionLog ]) " Greedy Pruning: The list of remaining UTxO vectors in null."
365371 >> pure (Right mempty )
366372 -- we stop the search if the predicate `stopSearch` is true.
367373 | stopSearch txInsVec =
@@ -408,7 +414,7 @@ greedyApprox stopSearch outVec txInsVec utxosVec
408414 -- We add the current utxo vector.
409415 _ -> (idx : ) <$> loop newTxInsVec' idxs vecs
410416 loop _newTxInsVec [] [] = pure mempty
411- loop _newTxInsVec _idxs _vecs = Left " Length of idxs and list of vecs are not same."
417+ loop _newTxInsVec _idxs _vecs = Left " Lengths of indexes and list of vectors are not same."
412418
413419-- calculate euclidean distance of two vectors, of same length/dimension.
414420l2norm :: ValueVector -> ValueVector -> Either Text Float
@@ -440,13 +446,13 @@ subVec = opVec (-)
440446zeroVec :: Int -> Vector Integer
441447zeroVec n = Vec. replicate n 0
442448
443- -- convert a value to a vector.
449+ -- | Convert a value to a vector.
444450valueToVec :: Set AssetClass -> Value -> Either Text ValueVector
445451valueToVec allAssetClasses v =
446452 maybeToRight " Error: Not able to uncons from empty vector." $
447453 (over _Just fst . uncons) $ valuesToVecs allAssetClasses [v]
448454
449- -- convert values to a list of vectors.
455+ -- | Convert values to a list of vectors.
450456valuesToVecs :: Set AssetClass -> [Value ] -> Vector ValueVector
451457valuesToVecs allAssetClasses values = Vec. fromList $ map toVec values
452458 where
@@ -455,7 +461,7 @@ valuesToVecs allAssetClasses values = Vec.fromList $ map toVec values
455461 fmap (Value. assetClassValueOf v) $
456462 allAssetClasses & id %~ (Vec. fromList . Set. toList)
457463
458- -- As the name suggests, we get a set of all the unique assetclass from given the lists of values.
464+ -- | As the name suggests, we get a set of all the unique AssetClass from given the lists of values.
459465uniqueAssetClasses :: [Value ] -> Set AssetClass
460466uniqueAssetClasses = Set. fromList . concatMap valueToAssetClass
461467 where
0 commit comments