Skip to content

Commit bd88edc

Browse files
committed
remove QueryNode to avoid code duplication
1 parent 6944c3b commit bd88edc

File tree

8 files changed

+156
-240
lines changed

8 files changed

+156
-240
lines changed

bot-plutus-interface.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,6 @@ library
9191
BotPlutusInterface.ExBudget
9292
BotPlutusInterface.Files
9393
BotPlutusInterface.Helpers
94-
BotPlutusInterface.QueryNode
9594
BotPlutusInterface.Server
9695
BotPlutusInterface.TimeSlot
9796
BotPlutusInterface.Types

src/BotPlutusInterface/Balance.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -133,8 +133,8 @@ balanceTxIO' balanceCfg pabConf ownPkh unbalancedTx =
133133

134134
requiredSigs :: [PubKeyHash]
135135
requiredSigs =
136-
map Ledger.unPaymentPubKeyHash $
137-
Set.toList (unBalancedTxRequiredSignatories unbalancedTx)
136+
unBalancedTxRequiredSignatories unbalancedTx
137+
^.. folded . to Ledger.unPaymentPubKeyHash
138138

139139
lift $ printBpiLog @w (Debug [TxBalancingLog]) $ viaShow utxoIndex
140140

src/BotPlutusInterface/CardanoNode/Effects.hs

Lines changed: 8 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,12 @@
11
{-# LANGUAGE RankNTypes #-}
22

33
{- This is ongoing effort on replacing `cardano-cli` calls with `Cardano.Api` queries, see issues
4-
https://github.com/mlabs-haskell/bot-plutus-interface/issues/109
5-
https://github.com/mlabs-haskell/bot-plutus-interface/issues/101
6-
We decided to provide single replacement for `BotPlutusInterface.CardanoCLI.utxosAt`
7-
early on to enable inline Datum support from one side and avoid extending
8-
`cardano-cli` output parser from the other side.
9-
See https://github.com/mlabs-haskell/bot-plutus-interface/issues/145
4+
https://github.com/mlabs-haskell/bot-plutus-interface/issues/109
5+
https://github.com/mlabs-haskell/bot-plutus-interface/issues/101
6+
We decided to provide single replacement for `BotPlutusInterface.CardanoCLI.utxosAt`
7+
early on to enable inline Datum support from one side and avoid extending
8+
`cardano-cli` output parser from the other side.
9+
See https://github.com/mlabs-haskell/bot-plutus-interface/issues/145
1010
-}
1111
module BotPlutusInterface.CardanoNode.Effects (
1212
utxosAt,
@@ -23,7 +23,6 @@ import BotPlutusInterface.CardanoNode.Query (
2323
QueryConstraint,
2424
connectionInfo,
2525
queryBabbageEra,
26-
queryInCardanoMode,
2726
toQueryError,
2827
)
2928

@@ -44,7 +43,6 @@ import Control.Monad.Freer (Eff, Members, interpret, runM, send, type (~>))
4443
import Control.Monad.Freer.Reader (Reader, ask, runReader)
4544
import Control.Monad.Trans.Class (lift)
4645
import Control.Monad.Trans.Either (firstEitherT, hoistEither, newEitherT, runEitherT)
47-
import Control.Monad.Trans.Except (throwE)
4846
import Data.Map (Map)
4947
import Data.Map qualified as Map
5048
import Data.Set qualified as Set
@@ -89,7 +87,7 @@ handleNodeQuery ::
8987
handleNodeQuery =
9088
interpret $ \case
9189
UtxosAt addr -> handleUtxosAt addr
92-
PParams -> queryPParams
90+
PParams -> queryBabbageEra CApi.QueryProtocolParameters
9391
MinUtxo txout -> handleMinUtxo txout
9492

9593
handleUtxosAt ::
@@ -129,7 +127,7 @@ handleMinUtxo ::
129127
handleMinUtxo txout = runEitherT $ do
130128
conn <- lift $ ask @NodeConn
131129

132-
params <- newEitherT queryPParams
130+
params <- newEitherT $ queryBabbageEra CApi.QueryProtocolParameters
133131

134132
let pparamsInEra = CApi.toLedgerPParams CApi.ShelleyBasedEraBabbage params
135133
netId = localNodeNetworkId conn
@@ -157,20 +155,3 @@ runNodeQuery conf effs = do
157155
runM $
158156
runReader conn $
159157
handleNodeQuery effs
160-
161-
-- Helpers
162-
163-
queryPParams ::
164-
forall effs.
165-
QueryConstraint effs =>
166-
Eff effs (Either NodeQueryError CApi.S.ProtocolParameters)
167-
queryPParams = runEitherT $ do
168-
let query =
169-
CApi.QueryInEra CApi.BabbageEraInCardanoMode $
170-
CApi.QueryInShelleyBasedEra CApi.ShelleyBasedEraBabbage CApi.QueryProtocolParameters
171-
172-
result <- newEitherT $ queryInCardanoMode query
173-
174-
case result of
175-
Right params -> return params
176-
Left err -> throwE $ toQueryError err

src/BotPlutusInterface/CardanoNode/Query.hs

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,16 +22,22 @@ import System.Environment (getEnv)
2222
import Prelude
2323

2424
{- | Error returned in case any error happened querying local node
25-
(wraps whatever received in `Text`)
25+
(wraps whatever received in `Text`)
2626
-}
2727
data NodeQueryError
2828
= NodeQueryError Text
2929
deriving stock (Eq, Show)
3030

31+
-- | Represents the connection to the local node.
3132
type NodeConn = CApi.LocalNodeConnectInfo CApi.CardanoMode
3233

34+
-- | Constraints that are required to query local node.
3335
type QueryConstraint effs = (Member (Reader NodeConn) effs, LastMember IO effs)
3436

37+
{- | 'queryInCardanoMode' establishes connection with local node and execute a single query.
38+
The Query has a type of 'QueryInMode CardanoMode a', hence we don't need any information
39+
about current era of the local node to execute certain queries, unlike `queryBabbageEra`.
40+
-}
3541
queryInCardanoMode ::
3642
forall effs a.
3743
(QueryConstraint effs) =>
@@ -45,6 +51,9 @@ queryInCardanoMode query =
4551
send $
4652
CApi.queryNodeLocalState conn Nothing query
4753

54+
{- | 'queryBabbageEra' expects that every query must be in 'BabbageEra' and
55+
it expects that the local node's current era should be 'BabbageEra'.
56+
-}
4857
queryBabbageEra ::
4958
forall effs a.
5059
(QueryConstraint effs) =>
@@ -61,7 +70,11 @@ queryBabbageEra query =
6170
Right a -> return a
6271
Left e -> throwE $ toQueryError e
6372

64-
connectionInfo :: PABConfig -> IO (CApi.LocalNodeConnectInfo CApi.CardanoMode)
73+
{- | create connection info from 'PABConfig', this function excepts that there's
74+
"CARDANO_NODE_SOCKET_PATH" environment variable present in the shell and has a
75+
value that contains path for local node's socket.
76+
-}
77+
connectionInfo :: PABConfig -> IO NodeConn
6578
connectionInfo pabConf =
6679
CApi.LocalNodeConnectInfo
6780
(CApi.CardanoModeParams epochSlots)

src/BotPlutusInterface/Contract.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -551,6 +551,9 @@ handleCollateral ::
551551
handleCollateral cEnv = do
552552
result <- (fmap swapEither . runEitherT) $
553553
do
554+
let helperLog :: PP.Doc () -> ExceptT CollateralUtxo (Eff effs) ()
555+
helperLog msg = newEitherT $ Right <$> printBpiLog @w (Debug [CollateralLog]) msg
556+
554557
collateralNotInMem <-
555558
newEitherT $
556559
maybeToLeft "Collateral UTxO not found in contract env."
@@ -577,10 +580,6 @@ handleCollateral cEnv = do
577580
setInMemCollateral @w collteralUtxo
578581
>> Right <$> printBpiLog @w (Debug [CollateralLog]) "successfully set the collateral utxo in env."
579582
Left err -> pure $ Left $ "Failed to make collateral: " <> err
580-
where
581-
--
582-
helperLog :: PP.Doc () -> ExceptT CollateralUtxo (Eff effs) ()
583-
helperLog msg = newEitherT $ Right <$> printBpiLog @w (Debug [CollateralLog]) msg
584583

585584
{- | Create collateral UTxO by submitting Tx.
586585
Then try to find created UTxO at own PKH address.

0 commit comments

Comments
 (0)