Skip to content

Commit

Permalink
Add structured logs interface and script fees recording
Browse files Browse the repository at this point in the history
Also updates CLB dep
  • Loading branch information
uhbif19 committed Jul 1, 2024
1 parent beadd21 commit b4ef56b
Show file tree
Hide file tree
Showing 8 changed files with 138 additions and 31 deletions.
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -19,10 +19,10 @@ tests: true
source-repository-package
type: git
location: https://github.com/mlabs-haskell/clb
tag: 925f80a9755d2292edf4589afb50dc1146b36ac2
tag: d5b0e7ce07258482d53704ce19383013b1fa6610
--sha256: 6+Os/mQDzBOU+TkTD+n/T1MFcI+Mn0/tcBMJhLRfqyA=

-- Cannot use new commit, because it requires `plutus-ledger-api==1.29`
-- FIXME: Cannot use new commit, because it requires `plutus-ledger-api==1.29`
source-repository-package
type: git
location: https://github.com/Plutonomicon/plutarch-plutus
Expand Down
23 changes: 22 additions & 1 deletion src/Cardano/CEM/Monads.hs
Original file line number Diff line number Diff line change
Expand Up @@ -60,13 +60,34 @@ data BlockchainParams = MkBlockchainParams
}
deriving stock (Show)

data Fees = MkFees
{ fee :: Coin
, usedMemory :: Natural
, usedCpu :: Natural
}
deriving stock (Show)

data BlockchainMonadEvent
= SubmittedTxSpec TxSpec (Either TxResolutionError TxId)
| UserSpentFee
{ txId :: TxId
, signer :: SigningKey PaymentKey
, fees :: Fees
}
| AwaitedTx TxId
deriving stock (Show)

{- | This monad gives access to all information about Cardano params,
| which is various kind of Ledger params and ValidityBound/Slots semantics
which is various kind of Ledger params and ValidityBound/Slots semantics
Also contains common structured log support.
-}
class (MonadFail m) => MonadBlockchainParams m where
askNetworkId :: m NetworkId
queryCurrentSlot :: m SlotNo
queryBlockchainParams :: m BlockchainParams
logEvent :: BlockchainMonadEvent -> m ()
eventList :: m [BlockchainMonadEvent]

-- MonadQuery

Expand Down
44 changes: 33 additions & 11 deletions src/Cardano/CEM/Monads/CLB.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Cardano.CEM.Monads.CLB where

import Prelude

import Control.Concurrent.MVar (MVar, modifyMVar, modifyMVar_, newMVar, readMVar)
import Control.Monad.State (StateT (..), gets)
import Data.Map qualified as Map
import Data.Set qualified as Set
Expand Down Expand Up @@ -34,12 +35,23 @@ import Clb.TimeSlot (posixTimeToUTCTime)
import Cardano.CEM.Monads
import Cardano.CEM.Monads.L1Commons
import Cardano.CEM.OffChain (fromPlutusAddressInMonad)
import Control.Monad.Reader (MonadReader (..), ReaderT (..))

instance (MonadFail m) => MonadBlockchainParams (ClbT m) where
askNetworkId :: ClbT m NetworkId
instance (MonadReader r m) => MonadReader r (ClbT m) where
ask = lift ask
local f action = ClbT $ local f $ unwrapClbT action

type ClbRunner = ClbT (ReaderT (MVar [BlockchainMonadEvent]) IO)

instance
( MonadFail m
, MonadIO m
, MonadReader (MVar [BlockchainMonadEvent]) m
) =>
MonadBlockchainParams (ClbT m)
where
askNetworkId = gets (mockConfigNetworkId . mockConfig)

queryCurrentSlot :: ClbT m SlotNo
queryCurrentSlot = getCurrentSlot

queryBlockchainParams = do
Expand All @@ -56,8 +68,14 @@ instance (MonadFail m) => MonadBlockchainParams (ClbT m) where
, -- Staking is not supported
stakePools = Set.empty
}
logEvent e = do
logVar <- ask
liftIO $ modifyMVar_ logVar (return . (:) e)
eventList = do
events <- ask
liftIO $ readMVar events

instance (MonadFail m) => MonadQueryUtxo (ClbT m) where
instance (Monad m, MonadBlockchainParams (ClbT m)) => MonadQueryUtxo (ClbT m) where
queryUtxo query = do
utxos <- fromLedgerUTxO shelleyBasedEra <$> gets getUtxosAtState
predicate <- mkPredicate
Expand All @@ -69,7 +87,7 @@ instance (MonadFail m) => MonadQueryUtxo (ClbT m) where
return $ \_ (TxOut a _ _ _) -> a `elem` cardanoAddresses
ByTxIns txIns -> return $ \txIn _ -> txIn `elem` txIns

instance (MonadFail m) => MonadSubmitTx (ClbT m) where
instance (Monad m, MonadBlockchainParams (ClbT m)) => MonadSubmitTx (ClbT m) where
submitResolvedTx :: ResolvedTx -> ClbT m (Either TxSubmittingError TxId)
submitResolvedTx tx = do
cardanoTxBodyFromResolvedTx tx >>= \case
Expand All @@ -82,16 +100,20 @@ instance (MonadFail m) => MonadSubmitTx (ClbT m) where
Right (_, _) -> fail "Unsupported tx format"
Left e -> return $ Left $ UnhandledAutobalanceError e

instance (MonadFail m) => MonadTest (ClbT m) where
instance (Monad m, MonadBlockchainParams (ClbT m)) => MonadTest (ClbT m) where
getTestWalletSks = return $ map intToCardanoSk [1 .. 10]

genesisClbState :: Value -> ClbState
genesisClbState genesisValue =
initClb defaultBabbage genesisValue genesisValue

execOnIsolatedClb :: Value -> ClbT IO a -> IO a
execOnIsolatedClb genesisValue action =
execOnIsolatedClb :: Value -> ClbRunner a -> IO a
execOnIsolatedClb genesisValue action = do
emptyLog <- newMVar []
fst
<$> runStateT
(unwrapClbT action)
(genesisClbState genesisValue)
<$> runReaderT
( runStateT
(unwrapClbT action)
(genesisClbState genesisValue)
)
emptyLog
4 changes: 4 additions & 0 deletions src/Cardano/CEM/Monads/L1.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,10 @@ instance MonadBlockchainParams L1Runner where
<*> (toLedgerEpochInfo <$> queryCardanoNode QueryEraHistory)
<*> queryCardanoNodeWrapping QueryStakePools

-- FIXME
logEvent _ = return ()
eventList = return []

queryCardanoNodeWrapping :: QueryInShelleyBasedEra Era b -> L1Runner b
queryCardanoNodeWrapping query =
handleEitherEra =<< queryCardanoNode wrapped
Expand Down
38 changes: 37 additions & 1 deletion src/Cardano/CEM/Monads/L1Commons.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,12 +10,13 @@ import Data.Map qualified as Map

-- Cardano imports
import Cardano.Api hiding (queryUtxo)
import Cardano.Api.Shelley (LedgerProtocolParameters (..))
import Cardano.Api.Shelley (LedgerProtocolParameters (..), Tx (..))

-- Project imports
import Cardano.CEM.Monads
import Cardano.CEM.OffChain
import Cardano.Extras
import Data.Maybe (mapMaybe)

-- Main function

Expand Down Expand Up @@ -89,7 +90,42 @@ cardanoTxBodyFromResolvedTx (MkResolvedTx {..}) = do
let
tx = makeSignedTransactionWithKeys [signer] body
txInMode = TxInMode ShelleyBasedEraBabbage tx

lift $ recordFee txInsUtxo body

return (body, txInMode)
where
recordFee txInsUtxo body@(TxBody content) = do
case txFee content of
TxFeeExplicit era coin -> do
MkBlockchainParams {protocolParameters, systemStart, eraHistory} <-
queryBlockchainParams
let
Right report =
evaluateTransactionExecutionUnits
(shelleyBasedToCardanoEra era)
systemStart
eraHistory
(LedgerProtocolParameters protocolParameters)
txInsUtxo
body
rights = mapMaybe $ \case
Right x -> Just x
Left _ -> Nothing
budgets = rights $ map snd $ Map.toList report
usedMemory = sum $ executionMemory <$> budgets
usedCpu = sum $ executionSteps <$> budgets
logEvent $
UserSpentFee
{ fees =
MkFees
{ fee = coin
, usedMemory
, usedCpu
}
, txId = getTxId body
, signer = signer
}

-- Utils

Expand Down
13 changes: 8 additions & 5 deletions src/Cardano/CEM/OffChain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ awaitTx txId = do
exists <- checkTxIdExists txId
liftIO $ threadDelay 1_000_000
if exists
then return ()
then logEvent $ AwaitedTx txId
else go $ n - 1

failLeft :: (MonadFail m, Show s) => Either s a -> m a
Expand Down Expand Up @@ -221,7 +221,10 @@ resolveTxAndSubmit ::
(MonadQueryUtxo m, MonadSubmitTx m, MonadIO m) =>
TxSpec ->
m (Either TxResolutionError TxId)
resolveTxAndSubmit spec = runExceptT $ do
resolved <- ExceptT $ resolveTx spec
let result = submitResolvedTx resolved
ExceptT $ first UnhandledSubmittingError <$> result
resolveTxAndSubmit spec = do
result <- runExceptT $ do
resolved <- ExceptT $ resolveTx spec
let result = submitResolvedTx resolved
ExceptT $ first UnhandledSubmittingError <$> result
logEvent $ SubmittedTxSpec spec result
return result
8 changes: 4 additions & 4 deletions src/Cardano/CEM/Testing/StateMachine.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,8 +40,8 @@ import Text.Show.Pretty (ppShow)

import Cardano.CEM (CEMParams (..))
import Cardano.CEM hiding (scriptParams)
import Cardano.CEM.Monads (MonadSubmitTx (..), ResolvedTx (..))
import Cardano.CEM.Monads.CLB (execOnIsolatedClb)
import Cardano.CEM.Monads (CEMAction (..), MonadSubmitTx (..), ResolvedTx (..), SomeCEMAction (..), TxSpec (..))
import Cardano.CEM.Monads.CLB (ClbRunner, execOnIsolatedClb)
import Cardano.CEM.OffChain
import Cardano.CEM.OnChain (CEMScriptCompiled)
import Cardano.Extras (signingKeyToPKH)
Expand Down Expand Up @@ -329,14 +329,14 @@ instance

runActionsInClb ::
forall state.
(StateModel (ScriptState state), RunModel (ScriptState state) (ClbT IO)) =>
(StateModel (ScriptState state), RunModel (ScriptState state) ClbRunner) =>
Value ->
Actions (ScriptState state) ->
Property
runActionsInClb genesisValue actions =
monadic (ioProperty . execOnIsolatedClb genesisValue) $
void $
runActions @(ScriptState state) @(ClbT IO) actions
runActions @(ScriptState state) @(ClbRunner) actions

-- Orphans

Expand Down
35 changes: 28 additions & 7 deletions test/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@ module Utils where
import Prelude

import Data.Map (keys)
import Data.Map qualified as Map
import Data.Maybe (mapMaybe)

import PlutusLedgerApi.V1.Interval (always)
import PlutusLedgerApi.V1.Value (assetClassValue)
Expand All @@ -17,28 +19,31 @@ import Cardano.Api.Shelley (
import Test.Hspec (shouldSatisfy)
import Text.Show.Pretty (ppShow)

import Clb (ClbT)

import Cardano.CEM.Monads (
BlockchainMonadEvent (..),
CEMAction (..),
Fees (..),
MonadBlockchainParams (..),
MonadQueryUtxo (..),
MonadSubmitTx (..),
ResolvedTx (..),
SomeCEMAction (..),
TxSpec (..),
UtxoQuery (..),
submitResolvedTx,
)
import Cardano.CEM.Monads.CLB (execOnIsolatedClb)
import Cardano.CEM.Monads.CLB (ClbRunner, execOnIsolatedClb)
import Cardano.CEM.OffChain (
CEMAction (..),
SomeCEMAction (..),
TxSpec (..),
awaitTx,
fromPlutusAddressInMonad,
resolveTxAndSubmit,
)
import Cardano.Extras
import Data.Spine (HasSpine (..))

import TestNFT

execClb :: ClbT IO a -> IO a
execClb :: ClbRunner a -> IO a
execClb = execOnIsolatedClb $ lovelaceToValue $ fromInteger 300_000_000

mintTestTokens ::
Expand Down Expand Up @@ -108,3 +113,19 @@ submitAndCheck spec = do
MkSomeCEMAction (MkCEMAction _ transition) ->
liftIO $ putStrLn $ "Doing " <> show transition
awaitEitherTx =<< resolveTxAndSubmit spec

perTransitionStats :: (MonadBlockchainParams m) => m (Map.Map String Fees)
perTransitionStats = do
events <- eventList
let feesByTxId = Map.fromList $ mapMaybe txIdFeePair events
return $ Map.fromList $ mapMaybe (transitionFeePair feesByTxId) events
where
txIdFeePair (UserSpentFee {fees, txId}) = Just (txId, fees)
txIdFeePair _ = Nothing
transitionFeePair feesByTxId event = case event of
( SubmittedTxSpec
(MkTxSpec [MkSomeCEMAction (MkCEMAction _ transition)] _)
(Right txId)
) ->
Just (show (getSpine transition), feesByTxId Map.! txId)
_ -> Nothing

0 comments on commit b4ef56b

Please sign in to comment.