Skip to content

Commit 205b35f

Browse files
committed
resolving TODOs and review comments
1 parent 1a91e94 commit 205b35f

File tree

4 files changed

+54
-48
lines changed

4 files changed

+54
-48
lines changed

src/BotPlutusInterface/CardanoCLI.hs

Lines changed: 34 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,11 @@ import BotPlutusInterface.Types (
3434
spendBudgets,
3535
)
3636
import BotPlutusInterface.UtxoParser qualified as UtxoParser
37-
import Cardano.Api.Shelley (NetworkId (Mainnet, Testnet), NetworkMagic (..), serialiseAddress)
37+
import Cardano.Api.Shelley (
38+
NetworkId (Mainnet, Testnet),
39+
NetworkMagic (NetworkMagic),
40+
serialiseAddress,
41+
)
3842
import Control.Monad (join)
3943
import Control.Monad.Freer (Eff, Member)
4044
import Data.Aeson qualified as JSON
@@ -53,7 +57,7 @@ import Data.Maybe (fromMaybe)
5357
import Data.Text (Text)
5458
import Data.Text qualified as Text
5559
import Data.Text.Encoding (decodeUtf8)
56-
import Ledger (Slot (Slot), SlotRange)
60+
import Ledger (Slot (Slot), SlotRange, TxInType (ConsumeScriptAddress))
5761
import Ledger qualified
5862
import Ledger.Ada (fromValue, getLovelace)
5963
import Ledger.Ada qualified as Ada
@@ -67,17 +71,39 @@ import Ledger.Interval (
6771
)
6872
import Ledger.Scripts (Datum, DatumHash (..))
6973
import Ledger.Scripts qualified as Scripts
70-
import Ledger.Tx (RedeemerPtr (..), Redeemers, ScriptTag (..), Tx (..), TxId (..), TxIn (..), TxInType (..), TxOut (..), TxOutRef (..), txId)
74+
import Ledger.Tx (
75+
RedeemerPtr (RedeemerPtr),
76+
Redeemers,
77+
ScriptTag (Mint),
78+
Tx (
79+
txCollateral,
80+
txData,
81+
txFee,
82+
txInputs,
83+
txMint,
84+
txMintScripts,
85+
txOutputs,
86+
txRedeemers,
87+
txSignatures,
88+
txValidRange
89+
),
90+
TxId (TxId),
91+
TxIn (TxIn),
92+
TxInType (ConsumePublicKeyAddress, ConsumeSimpleScriptAddress),
93+
TxOut (TxOut),
94+
TxOutRef (TxOutRef),
95+
txId,
96+
)
7197
import Ledger.Tx.CardanoAPI (toCardanoAddressInEra)
7298
import Ledger.Value (Value)
7399
import Ledger.Value qualified as Value
74100
import Plutus.Script.Utils.Scripts qualified as ScriptUtils
75101
import Plutus.V1.Ledger.Api (
76-
CurrencySymbol (..),
77-
ExBudget (..),
78-
ExCPU (..),
79-
ExMemory (..),
80-
TokenName (..),
102+
CurrencySymbol (unCurrencySymbol),
103+
ExBudget (ExBudget),
104+
ExCPU (ExCPU),
105+
ExMemory (ExMemory),
106+
TokenName (unTokenName),
81107
)
82108
import PlutusTx.Builtins (fromBuiltin)
83109
import Prelude

src/BotPlutusInterface/Contract.hs

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -225,22 +225,6 @@ handlePABReq contractEnv req = do
225225
printBpiLog @w (Debug [PABLog]) $ pretty resp
226226
pure resp
227227

228-
-- do-not-remove yet, could be handy for debugging of "own" implementation below
229-
-- "own" implementation will be tested with https://github.com/mlabs-haskell/plutip/issues/119
230-
-- on local network
231-
-- adjustUnbalancedTx' ::
232-
-- forall (w :: Type) (effs :: [Type -> Type]).
233-
-- ContractEnvironment w ->
234-
-- UnbalancedTx ->
235-
-- Eff effs (Either Tx.ToCardanoError UnbalancedTx)
236-
-- adjustUnbalancedTx' contractEnv unbalancedTx = do
237-
-- let slotConfig = SlotConfig 200 1654524000
238-
-- networkId = contractEnv.cePABConfig.pcNetwork
239-
-- maybeParams = contractEnv.cePABConfig.pcProtocolParams >>= \pparams -> pure $ Params slotConfig pparams networkId
240-
-- case maybeParams of
241-
-- Just params -> pure $ snd <$> adjustUnbalancedTx params unbalancedTx
242-
-- _ -> pure . Left $ Tx.TxBodyError "no protocol params"
243-
244228
adjustUnbalancedTx' ::
245229
forall (w :: Type) (effs :: [Type -> Type]).
246230
Member (PABEffect w) effs =>

test/Spec/BotPlutusInterface/Contract.hs

Lines changed: 20 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -257,16 +257,15 @@ sendAdaStaking = do
257257
--protocol-params-file ./protocol.json --out-file ./txs/tx-?.raw
258258
|]
259259
)
260-
-- TODO: figure out exact index for this command.
261-
-- ,
262-
-- ( 8
263-
-- , [text|
264-
-- cardano-cli transaction sign
265-
-- --tx-body-file ./txs/tx-?.raw
266-
-- --signing-key-file ./signing-keys/signing-key-${pkh1'}.skey
267-
-- --out-file ./txs/tx-?.signed
268-
-- |]
269-
-- )
260+
,
261+
( 14
262+
, [text|
263+
cardano-cli transaction sign
264+
--tx-body-file ./txs/tx-?.raw
265+
--signing-key-file ./signing-keys/signing-key-${pkh1'}.skey
266+
--out-file ./txs/tx-?.signed
267+
|]
268+
)
270269
]
271270

272271
multisigSupport :: Assertion
@@ -300,17 +299,16 @@ multisigSupport = do
300299
--protocol-params-file ./protocol.json --out-file ./txs/tx-?.raw
301300
|]
302301
)
303-
-- TODO: figure out exact index for this command.
304-
-- ,
305-
-- ( 8
306-
-- , [text|
307-
-- cardano-cli transaction sign
308-
-- --tx-body-file ./txs/tx-?.raw
309-
-- --signing-key-file ./signing-keys/signing-key-${pkh1'}.skey
310-
-- --signing-key-file ./signing-keys/signing-key-${pkh3'}.skey
311-
-- --out-file ./txs/tx-?.signed
312-
-- |]
313-
-- )
302+
,
303+
( 14
304+
, [text|
305+
cardano-cli transaction sign
306+
--tx-body-file ./txs/tx-?.raw
307+
--signing-key-file ./signing-keys/signing-key-${pkh1'}.skey
308+
--signing-key-file ./signing-keys/signing-key-${pkh3'}.skey
309+
--out-file ./txs/tx-?.signed
310+
|]
311+
)
314312
]
315313

316314
withoutSigning :: Assertion
@@ -662,8 +660,7 @@ redeemFromValidator = do
662660
assertContract contract initState $ \state -> do
663661
assertCommandHistory
664662
state
665-
[ -- TODO: Figure out why we need collateralTxId ?
666-
663+
[
667664
( 1
668665
, [text|
669666
cardano-cli transaction build-raw --babbage-era

test/Spec/MockContract.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -723,7 +723,6 @@ converCiTxOut (ScriptChainIndexTxOut addr val eitherDatum maybeRefSc _) =
723723

724724
convertMaybeDatum :: Maybe (DatumHash, Maybe Datum) -> OutputDatum
725725
convertMaybeDatum = \case
726-
-- FIXME" tmp implementation, check if something exists already for such conversion
727726
Nothing -> NoOutputDatum
728727
Just (dh, Nothing) -> OutputDatumHash dh
729728
Just (_dh, Just d) -> OutputDatum d

0 commit comments

Comments
 (0)