Skip to content
Merged
Show file tree
Hide file tree
Changes from 9 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 0 additions & 2 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -84,8 +84,6 @@ main = do
, pcPort = 9080
, pcProtocolParams = protocolParams
, pcTipPollingInterval = 10_000_000
, -- | Slot configuration of the network, the default value can be used for the mainnet
pcSlotConfig = def
, pcOwnPubKeyHash = "0f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546"
, pcOwnStakePubKeyHash = Nothing
, -- Directory name of the script and data files
Expand Down
4 changes: 4 additions & 0 deletions bot-plutus-interface.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ library
BotPlutusInterface.Helpers
BotPlutusInterface.QueryNode
BotPlutusInterface.Server
BotPlutusInterface.TimeSlot
BotPlutusInterface.Types
BotPlutusInterface.UtxoParser

Expand All @@ -97,6 +98,7 @@ library
, cardano-api
, cardano-crypto
, cardano-ledger-alonzo
, cardano-ledger-core
, cardano-prelude
, cardano-slotting
, containers
Expand All @@ -113,6 +115,7 @@ library
, lens
, memory
, mtl
, ouroboros-consensus
, playground-common
, plutus-chain-index
, plutus-chain-index-core
Expand All @@ -136,6 +139,7 @@ library
, split
, stm
, text ^>=1.2.4.0
, time
, transformers
, transformers-either
, transformers-except
Expand Down
2 changes: 0 additions & 2 deletions examples/plutus-game/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,6 @@ import Cardano.PlutusExample.Game (
import Data.Aeson qualified as JSON
import Data.Aeson.TH (defaultOptions, deriveJSON)
import Data.ByteString.Lazy qualified as LazyByteString
import Data.Default (def)
import Data.Maybe (fromMaybe)
import Playground.Types (FunctionSchema)
import Schema (FormSchema)
Expand Down Expand Up @@ -59,7 +58,6 @@ main = do
, pcPort = 9080
, pcProtocolParams = protocolParams
, pcTipPollingInterval = 10_000_000
, pcSlotConfig = def
, pcOwnPubKeyHash = "0f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546"
, pcOwnStakePubKeyHash = Nothing
, pcScriptFileDir = "./scripts"
Expand Down
2 changes: 0 additions & 2 deletions examples/plutus-nft/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,6 @@ import Cardano.PlutusExample.NFT
import Data.Aeson qualified as JSON
import Data.Aeson.TH (defaultOptions, deriveJSON)
import Data.ByteString.Lazy qualified as LazyByteString
import Data.Default (def)
import Data.Maybe (fromMaybe)
import Playground.Types (FunctionSchema)
import Schema (FormSchema)
Expand Down Expand Up @@ -55,7 +54,6 @@ main = do
, pcPort = 9080
, pcProtocolParams = protocolParams
, pcTipPollingInterval = 10_000_000
, pcSlotConfig = def
, pcOwnPubKeyHash = "0f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546"
, pcOwnStakePubKeyHash = Nothing
, pcScriptFileDir = "./scripts"
Expand Down
2 changes: 0 additions & 2 deletions examples/plutus-transfer/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ import Cardano.PlutusExample.Transfer (
import Data.Aeson qualified as JSON
import Data.Aeson.TH (defaultOptions, deriveJSON)
import Data.ByteString.Lazy qualified as LazyByteString
import Data.Default (def)
import Data.Maybe (fromMaybe)
import Playground.Types (FunctionSchema)
import Schema (FormSchema)
Expand Down Expand Up @@ -58,7 +57,6 @@ main = do
, pcPort = 9080
, pcProtocolParams = protocolParams
, pcTipPollingInterval = 10_000_000
, pcSlotConfig = def
, pcOwnPubKeyHash = "0f45aaf1b2959db6e5ff94dbb1f823bf257680c3c723ac2d49f97546"
, pcOwnStakePubKeyHash = Nothing
, pcScriptFileDir = "./scripts"
Expand Down
34 changes: 24 additions & 10 deletions src/BotPlutusInterface/Balance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,12 @@ module BotPlutusInterface.Balance (
) where

import BotPlutusInterface.CardanoCLI qualified as CardanoCLI
import BotPlutusInterface.Effects (PABEffect, createDirectoryIfMissingCLI, printBpiLog)
import BotPlutusInterface.Effects (
PABEffect,
createDirectoryIfMissingCLI,
posixTimeRangeToContainedSlotRange,
printBpiLog,
)
import BotPlutusInterface.Files (DummyPrivKey, unDummyPrivateKey)
import BotPlutusInterface.Files qualified as Files
import BotPlutusInterface.Types (LogLevel (Debug), PABConfig)
Expand Down Expand Up @@ -42,7 +47,6 @@ import Ledger.Interval (
)
import Ledger.Scripts (Datum, DatumHash)
import Ledger.Time (POSIXTimeRange)
import Ledger.TimeSlot (posixTimeRangeToContainedSlotRange)
import Ledger.Tx (
Tx (..),
TxIn (..),
Expand All @@ -60,6 +64,7 @@ import Plutus.V1.Ledger.Api (
)

import BotPlutusInterface.BodyBuilder qualified as BodyBuilder
import Data.Bifunctor (bimap)
import Prettyprinter (pretty, viaShow, (<+>))
import Prelude

Expand All @@ -80,17 +85,17 @@ balanceTxIO pabConf ownPkh unbalancedTx =
privKeys <- newEitherT $ Files.readPrivateKeys @w pabConf
let utxoIndex = fmap Tx.toTxOut utxos <> unBalancedTxUtxoIndex unbalancedTx
requiredSigs = map Ledger.unPaymentPubKeyHash $ Map.keys (unBalancedTxRequiredSignatories unbalancedTx)

tx <-
hoistEither $
addValidRange
pabConf
newEitherT $
addValidRange @w
(unBalancedTxValidityTimeRange unbalancedTx)
(unBalancedTxTx unbalancedTx)

lift $ printBpiLog @w Debug $ viaShow utxoIndex

-- We need this folder on the CLI machine, which may not be the local machine
lift $ createDirectoryIfMissingCLI @w False (Text.unpack pabConf.pcTxFileDir)
lift $ createDirectoryIfMissingCLI @w False (Text.unpack "pcTxFileDir")

-- Adds required collaterals, only needs to happen once
-- Also adds signatures for fee calculation
Expand Down Expand Up @@ -352,11 +357,20 @@ addSignatories ownPkh privKeys pkhs tx =
tx
(ownPkh : pkhs)

addValidRange :: PABConfig -> POSIXTimeRange -> Tx -> Either Text Tx
addValidRange pabConf timeRange tx =
addValidRange ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
POSIXTimeRange ->
Tx ->
Eff effs (Either Text Tx)
addValidRange timeRange tx =
if validateRange timeRange
then Right $ tx {txValidRange = posixTimeRangeToContainedSlotRange pabConf.pcSlotConfig timeRange}
else Left "Invalid validity interval."
then
bimap (Text.pack . show) (setRange tx)
<$> posixTimeRangeToContainedSlotRange @w timeRange
else pure $ Left "Invalid validity interval."
where
setRange tx' range = tx' {txValidRange = range}

validateRange :: forall (a :: Type). Ord a => Interval a -> Bool
validateRange (Interval (LowerBound PosInf _) _) = False
Expand Down
22 changes: 13 additions & 9 deletions src/BotPlutusInterface/Contract.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,10 +16,13 @@ import BotPlutusInterface.Effects (
handleContractLog,
handlePABEffect,
logToContract,
posixTimeRangeToContainedSlotRange,
posixTimeToSlot,
printBpiLog,
queryChainIndex,
readFileTextEnvelope,
saveBudget,
slotToPOSIXTime,
threadDelay,
uploadDir,
)
Expand Down Expand Up @@ -55,7 +58,6 @@ import Ledger qualified
import Ledger.Address (PaymentPubKeyHash (PaymentPubKeyHash))
import Ledger.Constraints.OffChain (UnbalancedTx (..))
import Ledger.Slot (Slot (Slot))
import Ledger.TimeSlot (posixTimeRangeToContainedSlotRange, posixTimeToEnclosingSlot, slotToEndPOSIXTime)
import Ledger.Tx (CardanoTx)
import Ledger.Tx qualified as Tx
import Plutus.ChainIndex.TxIdState (fromTx, transactionStatus)
Expand Down Expand Up @@ -184,10 +186,8 @@ handlePABReq contractEnv req = do
CurrentSlotReq -> CurrentSlotResp <$> currentSlot @w contractEnv
CurrentTimeReq -> CurrentTimeResp <$> currentTime @w contractEnv
PosixTimeRangeToContainedSlotRangeReq posixTimeRange ->
pure $
PosixTimeRangeToContainedSlotRangeResp $
Right $
posixTimeRangeToContainedSlotRange contractEnv.cePABConfig.pcSlotConfig posixTimeRange
either (error . show) (PosixTimeRangeToContainedSlotRangeResp . Right)
<$> posixTimeRangeToContainedSlotRange @w posixTimeRange
AwaitTxStatusChangeReq txId -> AwaitTxStatusChangeResp txId <$> awaitTxStatusChange @w contractEnv txId
------------------------
-- Unhandled requests --
Expand Down Expand Up @@ -384,10 +384,12 @@ awaitTime ::
ContractEnvironment w ->
POSIXTime ->
Eff effs POSIXTime
awaitTime ce = fmap fromSlot . awaitSlot ce . toSlot
awaitTime ce pTime = do
slotFromTime <- rightOrErr <$> posixTimeToSlot @w pTime
slot' <- awaitSlot ce slotFromTime
rightOrErr <$> slotToPOSIXTime @w slot'
where
toSlot = posixTimeToEnclosingSlot ce.cePABConfig.pcSlotConfig
fromSlot = slotToEndPOSIXTime ce.cePABConfig.pcSlotConfig
rightOrErr = either (error . show) id

currentSlot ::
forall (w :: Type) (effs :: [Type -> Type]).
Expand All @@ -411,4 +413,6 @@ currentTime ::
ContractEnvironment w ->
Eff effs POSIXTime
currentTime contractEnv =
slotToEndPOSIXTime contractEnv.cePABConfig.pcSlotConfig <$> currentSlot @w contractEnv
currentSlot @w contractEnv
>>= slotToPOSIXTime @w
>>= either (error . show) return
38 changes: 38 additions & 0 deletions src/BotPlutusInterface/Effects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,10 +24,14 @@ module BotPlutusInterface.Effects (
callCommand,
estimateBudget,
saveBudget,
slotToPOSIXTime,
posixTimeToSlot,
posixTimeRangeToContainedSlotRange,
) where

import BotPlutusInterface.ChainIndex (handleChainIndexReq)
import BotPlutusInterface.ExBudget qualified as ExBudget
import BotPlutusInterface.TimeSlot qualified as TimeSlot
import BotPlutusInterface.Types (
BudgetEstimationError,
CLILocation (..),
Expand Down Expand Up @@ -106,6 +110,13 @@ data PABEffect (w :: Type) (r :: Type) where
QueryChainIndex :: ChainIndexQuery -> PABEffect w ChainIndexResponse
EstimateBudget :: TxFile -> PABEffect w (Either BudgetEstimationError TxBudget)
SaveBudget :: Ledger.TxId -> TxBudget -> PABEffect w ()
SlotToPOSIXTime ::
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I started to get a feeling that instead of introducing new effects here for each cardano-api related query, we should have a more general QueryNode that uses this (this would also make later attempts to use cardano-api instead of the cli or chain-index a bit simpler)

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This is great idea, I think. It will also make things more testable (e.g. like this one).
But not sure if it should be done under this PR. To make it right budget execution related logic need to be changed also.

Or maybe just change part related to slot/time conversions to QueryNode effect and leave ex-budget for separate issue?

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Agreed yes, let's make that a new issue (the problem with refactoring issues is that they tend to be forgotten, staying in the backlog forever, so I like to couple them with some useful feature)

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Made an issue #109

Ledger.Slot ->
PABEffect w (Either TimeSlot.TimeSlotConversionError Ledger.POSIXTime)
POSIXTimeToSlot :: Ledger.POSIXTime -> PABEffect w (Either TimeSlot.TimeSlotConversionError Ledger.Slot)
POSIXTimeRangeToSlotRange ::
Ledger.POSIXTimeRange ->
PABEffect w (Either TimeSlot.TimeSlotConversionError Ledger.SlotRange)

handlePABEffect ::
forall (w :: Type) (effs :: [Type -> Type]).
Expand Down Expand Up @@ -155,6 +166,12 @@ handlePABEffect contractEnv =
EstimateBudget txPath ->
ExBudget.estimateBudget contractEnv.cePABConfig txPath
SaveBudget txId exBudget -> saveBudgetImpl contractEnv txId exBudget
SlotToPOSIXTime slot ->
TimeSlot.slotToPOSIXTimeIO contractEnv.cePABConfig slot
POSIXTimeToSlot pTime ->
TimeSlot.posixTimeToSlotIO contractEnv.cePABConfig pTime
POSIXTimeRangeToSlotRange pTimeRange ->
TimeSlot.posixTimeRangeToContainedSlotRangeIO contractEnv.cePABConfig pTimeRange
)

printLog' :: LogLevel -> LogContext -> LogLevel -> PP.Doc () -> IO ()
Expand Down Expand Up @@ -345,3 +362,24 @@ saveBudget ::
TxBudget ->
Eff effs ()
saveBudget txId budget = send @(PABEffect w) $ SaveBudget txId budget

slotToPOSIXTime ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
Ledger.Slot ->
Eff effs (Either TimeSlot.TimeSlotConversionError Ledger.POSIXTime)
slotToPOSIXTime = send @(PABEffect w) . SlotToPOSIXTime

posixTimeToSlot ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
Ledger.POSIXTime ->
Eff effs (Either TimeSlot.TimeSlotConversionError Ledger.Slot)
posixTimeToSlot = send @(PABEffect w) . POSIXTimeToSlot

posixTimeRangeToContainedSlotRange ::
forall (w :: Type) (effs :: [Type -> Type]).
Member (PABEffect w) effs =>
Ledger.POSIXTimeRange ->
Eff effs (Either TimeSlot.TimeSlotConversionError Ledger.SlotRange)
posixTimeRangeToContainedSlotRange = send @(PABEffect w) . POSIXTimeRangeToSlotRange
4 changes: 2 additions & 2 deletions src/BotPlutusInterface/ExBudget.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,9 +30,9 @@ import Prelude
minting to `MintingPolicyHash`'es
-}
estimateBudget :: PABConfig -> TxFile -> IO (Either BudgetEstimationError TxBudget)
estimateBudget bapConf txFile = do
estimateBudget pabConf txFile = do
sock <- getEnv "CARDANO_NODE_SOCKET_PATH"
let debugNodeInf = NodeInfo (pcNetwork bapConf) sock
let debugNodeInf = NodeInfo (pcNetwork pabConf) sock
txBody <- case txFile of
Raw rp -> deserialiseRaw rp
Signed sp -> fmap CAPI.getTxBody <$> deserialiseSigned sp
Expand Down
Loading