@@ -33,6 +33,7 @@ import Prettyprinter (pretty, (<+>))
3333import Prelude
3434
3535data Search = Greedy
36+ | GreedyPruning
3637 deriving stock (Show )
3738
3839selectTxIns ::
@@ -67,7 +68,7 @@ selectTxIns originalTxIns utxosIndex outValue =
6768 txInsVec <-
6869 hoistEither $
6970 if Value. isZero txInsValue
70- then Right $ zeroVec (toInteger $ length allAssetClasses)
71+ then Right $ zeroVec (length allAssetClasses)
7172 else valueToVec allAssetClasses txInsValue
7273
7374 outVec <- hoistEither $ valueToVec allAssetClasses outValue
@@ -79,7 +80,7 @@ selectTxIns originalTxIns utxosIndex outValue =
7980 lift $ printBpiLog @ w (Debug CoinSelectionLog ) $ " " <+> " Selected UTxOs Index: " <+> pretty selectedUtxosIdxs
8081
8182 let selectedUtxos :: [(TxOutRef , TxOut )]
82- selectedUtxos = mapMaybe (\ idx -> remainingUtxos ^? ix ( fromInteger idx) ) selectedUtxosIdxs
83+ selectedUtxos = mapMaybe (\ idx -> remainingUtxos ^? ix idx) selectedUtxosIdxs
8384
8485 selectedTxIns <- hoistEither $ mapM txOutToTxIn selectedUtxos
8586
@@ -90,7 +91,7 @@ selectTxIns originalTxIns utxosIndex outValue =
9091 isSufficient :: Vector Integer -> Vector Integer -> Bool
9192 isSufficient outVec txInsVec =
9293 Vec. all (== True ) (Vec. zipWith (<=) outVec txInsVec)
93- && txInsVec /= zeroVec (toInteger $ length txInsVec)
94+ && txInsVec /= zeroVec (length txInsVec)
9495
9596selectTxIns' ::
9697 forall (w :: Type ) (effs :: [Type -> Type ]).
@@ -100,8 +101,19 @@ selectTxIns' ::
100101 Vector Integer ->
101102 Vector Integer ->
102103 [Vector Integer ] ->
103- Eff effs (Either Text [Integer ])
104- selectTxIns' Greedy stopSearch outVec txInsVec utxosVec
104+ Eff effs (Either Text [Int ])
105+ selectTxIns' Greedy = greedySearch @ w
106+ selectTxIns' GreedyPruning = undefined
107+
108+ greedySearch ::
109+ forall (w :: Type ) (effs :: [Type -> Type ]).
110+ Member (PABEffect w ) effs =>
111+ (Vector Integer -> Bool ) ->
112+ Vector Integer ->
113+ Vector Integer ->
114+ [Vector Integer ] ->
115+ Eff effs (Either Text [Int ])
116+ greedySearch stopSearch outVec txInsVec utxosVec
105117 | null utxosVec =
106118 printBpiLog @ w (Debug CoinSelectionLog ) " The list of remanining UTxO vectors in null."
107119 >> return (Right mempty )
@@ -113,14 +125,15 @@ selectTxIns' Greedy stopSearch outVec txInsVec utxosVec
113125 x <- hoistEither $ mapM (addVec txInsVec) utxosVec
114126 utxosDist <- hoistEither $ mapM (l2norm outVec) x
115127
116- let sortedDist :: [(Integer , Float )]
128+ let sortedDist :: [(Int , Float )]
117129 sortedDist =
118130 List. sortBy (\ a b -> compare (snd a) (snd b)) $
119- zip [0 .. toInteger ( length utxosVec) - 1 ] utxosDist
131+ zip [0 .. length utxosVec - 1 ] utxosDist
120132
121133 newEitherT $ loop sortedDist txInsVec
134+
122135 where
123- loop :: [(Integer , Float )] -> Vector Integer -> Eff effs (Either Text [Integer ])
136+ loop :: [(Int , Float )] -> Vector Integer -> Eff effs (Either Text [Int ])
124137 loop [] _ = return $ Right mempty
125138 loop ((idx, _) : remSortedDist) newTxInsVec =
126139 if stopSearch newTxInsVec
@@ -130,7 +143,7 @@ selectTxIns' Greedy stopSearch outVec txInsVec utxosVec
130143 hoistEither $
131144 maybeToRight
132145 " Out of bounds"
133- (utxosVec ^? ix ( fromInteger idx) )
146+ (utxosVec ^? ix idx)
134147 newTxInsVec' <- hoistEither $ addVec newTxInsVec selectedUtxoVec
135148
136149 lift $
@@ -141,6 +154,31 @@ selectTxIns' Greedy stopSearch outVec txInsVec utxosVec
141154
142155 (idx : ) <$> newEitherT (loop remSortedDist newTxInsVec')
143156
157+ greedyPruning ::
158+ forall (w :: Type ) (effs :: [Type -> Type ]).
159+ Member (PABEffect w ) effs =>
160+ (Vector Integer -> Bool ) ->
161+ Vector Integer ->
162+ Vector Integer ->
163+ [Vector Integer ] ->
164+ Eff effs (Either Text [Int ])
165+ greedyPruning stopSearch outVec txInsVec utxosVec
166+ | null utxosVec =
167+ printBpiLog @ w (Debug CoinSelectionLog ) " The list of remanining UTxO vectors in null."
168+ >> return (Right mempty )
169+ | stopSearch txInsVec =
170+ printBpiLog @ w (Debug CoinSelectionLog ) " Stopping search early."
171+ >> return (Right mempty )
172+ | otherwise =
173+ runEitherT $ do
174+ selectedUtxosIdxs <- newEitherT $ greedySearch @ w stopSearch outVec txInsVec utxosVec
175+ return undefined
176+
177+
178+ combinations :: Set Int -> Set (Set Int )
179+ combinations = undefined
180+
181+
144182l2norm :: Vector Integer -> Vector Integer -> Either Text Float
145183l2norm v1 v2
146184 | length v1 == length v2 = Right $ sqrt $ fromInteger $ sum $ Vec. zipWith formula v1 v2
@@ -172,8 +210,8 @@ addVec v1 v2
172210 <> show (length v2)
173211 <> " ."
174212
175- zeroVec :: Integer -> Vector Integer
176- zeroVec n = Vec. fromList $ replicate ( fromInteger n) 0
213+ zeroVec :: Int -> Vector Integer
214+ zeroVec n = Vec. fromList $ replicate n 0
177215
178216valueToVec :: Set AssetClass -> Value -> Either Text (Vector Integer )
179217valueToVec allAssetClasses v =
0 commit comments