@@ -6,7 +6,7 @@ import Control.Lens (Cons, cons, ix, uncons, (^?))
66import Control.Monad.Freer (Eff , Member )
77
88import Control.Monad.Trans.Class (lift )
9- import Control.Monad.Trans.Either (hoistEither , runEitherT , newEitherT )
9+ import Control.Monad.Trans.Either (hoistEither , newEitherT , runEitherT )
1010import Data.Either.Combinators (isRight , maybeToRight )
1111import Data.Kind (Type )
1212import Data.List qualified as List
@@ -44,7 +44,6 @@ selectTxIns ::
4444 Eff effs (Either Text (Set TxIn ))
4545selectTxIns originalTxIns utxosIndex outValue =
4646 runEitherT $ do
47-
4847 let txInsValue :: Value
4948 txInsValue =
5049 mconcat $ map txOutValue $ mapMaybe ((`Map.lookup` utxosIndex) . txInRef) $ Set. toList originalTxIns
@@ -89,8 +88,9 @@ selectTxIns originalTxIns utxosIndex outValue =
8988 return $ originalTxIns <> Set. fromList selectedTxIns
9089 where
9190 isSufficient :: Vector Integer -> Vector Integer -> Bool
92- isSufficient outVec txInsVec = Vec. all (== True ) (Vec. zipWith (<=) outVec txInsVec)
93- && txInsVec /= zeroVec (toInteger $ length txInsVec)
91+ isSufficient outVec txInsVec =
92+ Vec. all (== True ) (Vec. zipWith (<=) outVec txInsVec)
93+ && txInsVec /= zeroVec (toInteger $ length txInsVec)
9494
9595selectTxIns' ::
9696 forall (w :: Type ) (effs :: [Type -> Type ]).
@@ -102,42 +102,45 @@ selectTxIns' ::
102102 [Vector Integer ] ->
103103 Eff effs (Either Text [Integer ])
104104selectTxIns' Greedy stopSearch outVec txInsVec utxosVec
105- | null utxosVec = printBpiLog @ w Debug " The list of remanining UTxO vectors in null.\n\n "
106- >> return (Right mempty )
107-
108- | stopSearch txInsVec = printBpiLog @ w Debug " Stopping search early.\n\n " >>
109- return (Right mempty )
105+ | null utxosVec =
106+ printBpiLog @ w Debug " The list of remanining UTxO vectors in null.\n\n "
107+ >> return (Right mempty )
108+ | stopSearch txInsVec =
109+ printBpiLog @ w Debug " Stopping search early.\n\n "
110+ >> return (Right mempty )
110111 | otherwise =
111112 runEitherT $ do
112-
113113 x <- hoistEither $ mapM (addVec txInsVec) utxosVec
114114 utxosDist <- hoistEither $ mapM (l2norm outVec) x
115-
115+
116116 let sortedDist :: [(Integer , Float )]
117- sortedDist = List. sortBy (\ a b -> compare (snd a) (snd b))
118- $ zip [0 .. toInteger (length utxosVec) - 1 ] utxosDist
117+ sortedDist =
118+ List. sortBy (\ a b -> compare (snd a) (snd b)) $
119+ zip [0 .. toInteger (length utxosVec) - 1 ] utxosDist
119120
120121 newEitherT $ loop sortedDist txInsVec
121-
122122 where
123-
124123 loop :: [(Integer , Float )] -> Vector Integer -> Eff effs (Either Text [Integer ])
125- loop [] _ = return $ Right mempty
126- loop ((idx,_) : remSortedDist) newTxInsVec =
124+ loop [] _ = return $ Right mempty
125+ loop ((idx, _) : remSortedDist) newTxInsVec =
127126 if stopSearch newTxInsVec
128127 then return $ Right mempty
129- else
130- runEitherT $ do
131- selectedUtxoVec <- hoistEither $ maybeToRight " Out of bounds"
132- (utxosVec ^? ix (fromInteger idx))
133- newTxInsVec' <- hoistEither $ addVec newTxInsVec selectedUtxoVec
134-
135- lift $ printBpiLog @ w Debug
136- $ " Loop Info: Stop search -> " <+> pretty (stopSearch newTxInsVec')
137- <+> " Selected UTxo Idx : " <+> pretty idx
138- <+> " \n\n "
139-
140- (idx: ) <$> newEitherT (loop remSortedDist newTxInsVec')
128+ else runEitherT $ do
129+ selectedUtxoVec <-
130+ hoistEither $
131+ maybeToRight
132+ " Out of bounds"
133+ (utxosVec ^? ix (fromInteger idx))
134+ newTxInsVec' <- hoistEither $ addVec newTxInsVec selectedUtxoVec
135+
136+ lift $
137+ printBpiLog @ w Debug $
138+ " Loop Info: Stop search -> " <+> pretty (stopSearch newTxInsVec')
139+ <+> " Selected UTxo Idx : "
140+ <+> pretty idx
141+ <+> " \n\n "
142+
143+ (idx : ) <$> newEitherT (loop remSortedDist newTxInsVec')
141144
142145l2norm :: Vector Integer -> Vector Integer -> Either Text Float
143146l2norm v1 v2
0 commit comments