Skip to content

Commit e50c779

Browse files
committed
wip: time <-> slot conversions
1 parent 629023e commit e50c779

File tree

5 files changed

+125
-11
lines changed

5 files changed

+125
-11
lines changed

bot-plutus-interface.cabal

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ source-repository head
2525
common common-lang
2626
ghc-options:
2727
-Wall -Wcompat -Wincomplete-record-updates
28-
-Wincomplete-uni-patterns -Wredundant-constraints -Werror
28+
-Wincomplete-uni-patterns -Wredundant-constraints
29+
-- -Werror
2930
-fobject-code -fno-ignore-interface-pragmas
3031
-fno-omit-interface-pragmas -fplugin=RecordDotPreprocessor
3132

@@ -87,6 +88,7 @@ library
8788
BotPlutusInterface.Helpers
8889
BotPlutusInterface.QueryNode
8990
BotPlutusInterface.Server
91+
BotPlutusInterface.TimeSlot
9092
BotPlutusInterface.Types
9193
BotPlutusInterface.UtxoParser
9294

@@ -143,6 +145,9 @@ library
143145
, wai
144146
, warp
145147
, websockets
148+
, cardano-ledger-core
149+
, ouroboros-consensus
150+
, time
146151

147152
hs-source-dirs: src
148153

src/BotPlutusInterface/Contract.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -18,8 +18,9 @@ import BotPlutusInterface.Effects (
1818
queryChainIndex,
1919
readFileTextEnvelope,
2020
saveBudget,
21+
slotToPOSIXTime,
2122
threadDelay,
22-
uploadDir,
23+
uploadDir, posixTimeToSlot
2324
)
2425
import BotPlutusInterface.Files (DummyPrivKey (FromSKey, FromVKey))
2526
import BotPlutusInterface.Files qualified as Files
@@ -33,7 +34,7 @@ import Cardano.Api (AsType (..), EraInMode (..), Tx (Tx))
3334
import Control.Lens (preview, (^.))
3435
import Control.Monad (join, void, when)
3536
import Control.Monad.Freer (Eff, Member, interpret, reinterpret, runM, subsume, type (~>))
36-
import Control.Monad.Freer.Error (runError)
37+
import Control.Monad.Freer.Error (runError, throwError)
3738
import Control.Monad.Freer.Extras.Log (handleLogIgnore)
3839
import Control.Monad.Freer.Extras.Modify (raiseEnd)
3940
import Control.Monad.Freer.Writer (Writer (Tell))
@@ -353,10 +354,11 @@ awaitTime ::
353354
ContractEnvironment w ->
354355
POSIXTime ->
355356
Eff effs POSIXTime
356-
awaitTime ce = fmap fromSlot . awaitSlot ce . toSlot
357-
where
358-
toSlot = posixTimeToEnclosingSlot ce.cePABConfig.pcSlotConfig
359-
fromSlot = slotToEndPOSIXTime ce.cePABConfig.pcSlotConfig
357+
awaitTime ce pTime = do
358+
slotFromTime <- posixTimeToSlot @w pTime >>= either (error . show) return
359+
slot' <- awaitSlot ce slotFromTime
360+
ethTime <- slotToPOSIXTime @w slot'
361+
either (error . show) return ethTime
360362

361363
currentSlot ::
362364
forall (w :: Type) (effs :: [Type -> Type]).
@@ -380,4 +382,6 @@ currentTime ::
380382
ContractEnvironment w ->
381383
Eff effs POSIXTime
382384
currentTime contractEnv =
383-
slotToEndPOSIXTime contractEnv.cePABConfig.pcSlotConfig <$> currentSlot @w contractEnv
385+
currentSlot @w contractEnv
386+
>>= slotToPOSIXTime @w
387+
>>= either (error . show) return

src/BotPlutusInterface/Effects.hs

Lines changed: 22 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,10 +22,13 @@ module BotPlutusInterface.Effects (
2222
callCommand,
2323
estimateBudget,
2424
saveBudget,
25+
slotToPOSIXTime,
26+
posixTimeToSlot,
2527
) where
2628

2729
import BotPlutusInterface.ChainIndex (handleChainIndexReq)
2830
import BotPlutusInterface.ExBudget qualified as ExBudget
31+
import BotPlutusInterface.TimeSlot qualified as TimeSlot
2932
import BotPlutusInterface.Types (
3033
BudgetEstimationError,
3134
CLILocation (..),
@@ -55,7 +58,7 @@ import Data.Text qualified as Text
5558
import Ledger qualified
5659
import Plutus.Contract.Effects (ChainIndexQuery, ChainIndexResponse)
5760
import Plutus.PAB.Core.ContractInstance.STM (Activity)
58-
import PlutusTx.Builtins.Internal (BuiltinByteString (BuiltinByteString))
61+
import PlutusTx.Builtins.Internal (BuiltinByteString (BuiltinByteString), error)
5962
import System.Directory qualified as Directory
6063
import System.Exit (ExitCode (ExitFailure, ExitSuccess))
6164
import System.Process (readProcess, readProcessWithExitCode)
@@ -97,6 +100,8 @@ data PABEffect (w :: Type) (r :: Type) where
97100
QueryChainIndex :: ChainIndexQuery -> PABEffect w ChainIndexResponse
98101
EstimateBudget :: TxFile -> PABEffect w (Either BudgetEstimationError TxBudget)
99102
SaveBudget :: Ledger.TxId -> TxBudget -> PABEffect w ()
103+
SlotToPOSIXTime :: Ledger.Slot -> PABEffect w (Either TimeSlot.TimeSlotConversionError Ledger.POSIXTime)
104+
POSIXTimeToSlot :: Ledger.POSIXTime -> PABEffect w (Either TimeSlot.TimeSlotConversionError Ledger.Slot)
100105

101106
handlePABEffect ::
102107
forall (w :: Type) (effs :: [Type -> Type]).
@@ -146,6 +151,8 @@ handlePABEffect contractEnv =
146151
EstimateBudget txPath ->
147152
ExBudget.estimateBudget contractEnv.cePABConfig txPath
148153
SaveBudget txId exBudget -> saveBudgetImpl contractEnv txId exBudget
154+
SlotToPOSIXTime slot -> TimeSlot.slotToPOSIXTimeImpl contractEnv.cePABConfig slot
155+
POSIXTimeToSlot pTime -> TimeSlot.posixTimeToSlotImpl contractEnv.cePABConfig pTime
149156
)
150157

151158
printLog' :: LogLevel -> LogLevel -> String -> IO ()
@@ -302,3 +309,17 @@ saveBudget ::
302309
TxBudget ->
303310
Eff effs ()
304311
saveBudget txId budget = send @(PABEffect w) $ SaveBudget txId budget
312+
313+
slotToPOSIXTime ::
314+
forall (w :: Type) (effs :: [Type -> Type]).
315+
Member (PABEffect w) effs =>
316+
Ledger.Slot ->
317+
Eff effs (Either TimeSlot.TimeSlotConversionError Ledger.POSIXTime)
318+
slotToPOSIXTime = send @(PABEffect w) . SlotToPOSIXTime
319+
320+
posixTimeToSlot ::
321+
forall (w :: Type) (effs :: [Type -> Type]).
322+
Member (PABEffect w) effs =>
323+
Ledger.POSIXTime ->
324+
Eff effs (Either TimeSlot.TimeSlotConversionError Ledger.Slot)
325+
posixTimeToSlot = send @(PABEffect w) . POSIXTimeToSlot

src/BotPlutusInterface/ExBudget.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -30,9 +30,9 @@ import Prelude
3030
minting to `MintingPolicyHash`'es
3131
-}
3232
estimateBudget :: PABConfig -> TxFile -> IO (Either BudgetEstimationError TxBudget)
33-
estimateBudget bapConf txFile = do
33+
estimateBudget pabConf txFile = do
3434
sock <- getEnv "CARDANO_NODE_SOCKET_PATH"
35-
let debugNodeInf = NodeInfo (pcNetwork bapConf) sock
35+
let debugNodeInf = NodeInfo (pcNetwork pabConf) sock
3636
txBody <- case txFile of
3737
Raw rp -> deserialiseRaw rp
3838
Signed sp -> fmap CAPI.getTxBody <$> deserialiseSigned sp

src/BotPlutusInterface/TimeSlot.hs

Lines changed: 84 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,84 @@
1+
module BotPlutusInterface.TimeSlot (
2+
TimeSlotConversionError,
3+
slotToPOSIXTimeImpl,
4+
posixTimeToSlotImpl,
5+
) where
6+
7+
import Cardano.Ledger.Alonzo.TxInfo (slotToPOSIXTime)
8+
import Ledger qualified
9+
import Prelude
10+
11+
import BotPlutusInterface.QueryNode (NodeInfo (NodeInfo), queryEraHistory, querySystemStart)
12+
import BotPlutusInterface.Types (PABConfig, pcNetwork, pcProtocolParams)
13+
import Cardano.Api qualified as CAPI
14+
import Cardano.Ledger.Alonzo.PParams (_protocolVersion)
15+
import Cardano.Ledger.Slot (EpochInfo)
16+
import Cardano.Slotting.EpochInfo (hoistEpochInfo)
17+
import Control.Monad.Except (runExcept)
18+
import Control.Monad.IO.Class (liftIO)
19+
import Control.Monad.Trans.Either (EitherT, firstEitherT, hoistEither, newEitherT, runEitherT)
20+
import Data.Bifunctor (first)
21+
import Data.Text (Text)
22+
import Data.Text qualified as Text
23+
import Ouroboros.Consensus.HardFork.History qualified as Consensus
24+
import System.Environment (getEnv)
25+
26+
import Cardano.Slotting.Time (RelativeTime, toRelativeTime)
27+
import Data.Time (secondsToNominalDiffTime)
28+
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
29+
import Ouroboros.Consensus.HardFork.History.Qry qualified as HF
30+
31+
data TimeSlotConversionError
32+
= TimeSlotConversionError !Text
33+
deriving stock (Show)
34+
35+
slotToPOSIXTimeImpl :: PABConfig -> Ledger.Slot -> IO (Either TimeSlotConversionError Ledger.POSIXTime)
36+
slotToPOSIXTimeImpl pabConf (Ledger.Slot s) = runEitherT $ do
37+
let pparams =
38+
CAPI.toLedgerPParams
39+
CAPI.ShelleyBasedEraAlonzo -- TODO: should era be passed as an argument?
40+
(pcProtocolParams pabConf)
41+
42+
sock <- liftIO $ getEnv "CARDANO_NODE_SOCKET_PATH"
43+
let nodeInfo = NodeInfo (pcNetwork pabConf) sock
44+
45+
epochInfo <- toLedgerEpochInfo <$> newET (queryEraHistory nodeInfo)
46+
sysStart <- newET $ querySystemStart nodeInfo
47+
48+
let slotNo = CAPI.SlotNo $ fromInteger s
49+
firstEitherT toError $
50+
hoistEither $
51+
slotToPOSIXTime pparams epochInfo sysStart slotNo
52+
53+
toLedgerEpochInfo ::
54+
CAPI.EraHistory mode ->
55+
EpochInfo (Either CAPI.TransactionValidityError)
56+
toLedgerEpochInfo (CAPI.EraHistory _ interpreter) =
57+
hoistEpochInfo (first CAPI.TransactionValidityIntervalError . runExcept) $
58+
Consensus.interpreterToEpochInfo interpreter
59+
60+
posixTimeToSlotImpl :: PABConfig -> Ledger.POSIXTime -> IO (Either TimeSlotConversionError Ledger.Slot)
61+
posixTimeToSlotImpl pabConf pTime = runEitherT $ do
62+
sock <- liftIO $ getEnv "CARDANO_NODE_SOCKET_PATH"
63+
let nodeInfo = NodeInfo (pcNetwork pabConf) sock
64+
65+
(CAPI.EraHistory _ interpreter) <- newET (queryEraHistory nodeInfo)
66+
sysStart <- newET $ querySystemStart nodeInfo
67+
68+
let time :: RelativeTime = toRelativeTime sysStart (toUtc pTime)
69+
timeQuery = HF.wallclockToSlot time
70+
int = HF.interpretQuery interpreter timeQuery
71+
(CAPI.SlotNo s, _, _) <- firstEitherT toError $ hoistEither int
72+
73+
return $ Ledger.Slot (toInteger s)
74+
where
75+
toUtc (Ledger.POSIXTime milliseconds) =
76+
posixSecondsToUTCTime $
77+
secondsToNominalDiffTime
78+
(fromInteger $ milliseconds `div` 1000) -- FIXME: is it safe?
79+
80+
newET :: Show e => IO (Either e a) -> EitherT TimeSlotConversionError IO a
81+
newET = firstEitherT toError . newEitherT
82+
83+
toError :: Show e => e -> TimeSlotConversionError
84+
toError = TimeSlotConversionError . Text.pack . show

0 commit comments

Comments
 (0)