Skip to content

Commit a847a9d

Browse files
authored
Merge pull request #95 from mlabs-haskell/uhbif19/structured-logs
Add structured logs interface and script fees recording
2 parents 80b0f23 + 7e39ee5 commit a847a9d

File tree

9 files changed

+185
-72
lines changed

9 files changed

+185
-72
lines changed

cabal.project

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,10 +19,10 @@ tests: true
1919
source-repository-package
2020
type: git
2121
location: https://github.com/mlabs-haskell/clb
22-
tag: 925f80a9755d2292edf4589afb50dc1146b36ac2
22+
tag: d5b0e7ce07258482d53704ce19383013b1fa6610
2323
--sha256: 6+Os/mQDzBOU+TkTD+n/T1MFcI+Mn0/tcBMJhLRfqyA=
2424

25-
-- Cannot use new commit, because it requires `plutus-ledger-api==1.29`
25+
-- FIXME: Cannot use new commit, because it requires `plutus-ledger-api==1.29`
2626
source-repository-package
2727
type: git
2828
location: https://github.com/Plutonomicon/plutarch-plutus

src/Cardano/CEM/Monads.hs

Lines changed: 67 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Cardano.CEM.Monads where
33
import Prelude
44

55
import Data.Set (Set)
6+
import GHC.Natural (Natural)
67

78
import PlutusLedgerApi.V1.Address (Address)
89
import PlutusLedgerApi.V2 (
@@ -14,10 +15,39 @@ import PlutusLedgerApi.V2 (
1415
import Cardano.Api hiding (Address, In, Out, queryUtxo, txIns)
1516
import Cardano.Api.Shelley (PoolId)
1617
import Cardano.Ledger.Core (PParams)
17-
import Cardano.Ledger.Shelley.API (ApplyTxError (..))
18+
import Cardano.Ledger.Shelley.API (ApplyTxError (..), Coin)
1819

20+
import Cardano.CEM
21+
import Cardano.CEM.OnChain
1922
import Cardano.Extras
2023

24+
-- CEMAction and TxSpec
25+
26+
data CEMAction script
27+
= MkCEMAction (CEMParams script) (Transition script)
28+
29+
deriving stock instance
30+
(CEMScript script) => Show (CEMAction script)
31+
32+
-- FIXME: use generic Some
33+
data SomeCEMAction where
34+
MkSomeCEMAction ::
35+
forall script.
36+
(CEMScriptCompiled script) =>
37+
CEMAction script ->
38+
SomeCEMAction
39+
40+
instance Show SomeCEMAction where
41+
-- FIXME: show script name
42+
show :: SomeCEMAction -> String
43+
show (MkSomeCEMAction action) = show action
44+
45+
data TxSpec = MkTxSpec
46+
{ actions :: [SomeCEMAction]
47+
, specSigner :: SigningKey PaymentKey
48+
}
49+
deriving stock (Show)
50+
2151
-- MonadBlockchainParams
2252

2353
-- | Params of blockchain required for transaction-building
@@ -30,13 +60,34 @@ data BlockchainParams = MkBlockchainParams
3060
}
3161
deriving stock (Show)
3262

63+
data Fees = MkFees
64+
{ fee :: Coin
65+
, usedMemory :: Natural
66+
, usedCpu :: Natural
67+
}
68+
deriving stock (Show)
69+
70+
data BlockchainMonadEvent
71+
= SubmittedTxSpec TxSpec (Either TxResolutionError TxId)
72+
| UserSpentFee
73+
{ txId :: TxId
74+
, txSigner :: SigningKey PaymentKey
75+
, fees :: Fees
76+
}
77+
| AwaitedTx TxId
78+
deriving stock (Show)
79+
3380
{- | This monad gives access to all information about Cardano params,
34-
| which is various kind of Ledger params and ValidityBound/Slots semantics
81+
which is various kind of Ledger params and ValidityBound/Slots semantics
82+
83+
Also contains common structured log support.
3584
-}
3685
class (MonadFail m) => MonadBlockchainParams m where
3786
askNetworkId :: m NetworkId
3887
queryCurrentSlot :: m SlotNo
3988
queryBlockchainParams :: m BlockchainParams
89+
logEvent :: BlockchainMonadEvent -> m ()
90+
eventList :: m [BlockchainMonadEvent]
4091

4192
-- MonadQuery
4293

@@ -73,6 +124,20 @@ data TxSubmittingError
73124
| UnhandledNodeSubmissionError (ApplyTxError LedgerEra)
74125
deriving stock (Show)
75126

127+
-- | Error occurred while trying to execute CEMScript transition
128+
data TransitionError
129+
= StateMachineError
130+
{ errorMessage :: String
131+
}
132+
| MissingTransitionInput
133+
deriving stock (Show, Eq)
134+
135+
data TxResolutionError
136+
= TxSpecIsIncorrect
137+
| MkTransitionError SomeCEMAction TransitionError
138+
| UnhandledSubmittingError TxSubmittingError
139+
deriving stock (Show)
140+
76141
-- | Ability to send transaction to chain
77142
class (MonadQueryUtxo m) => MonadSubmitTx m where
78143
submitResolvedTx :: ResolvedTx -> m (Either TxSubmittingError TxId)

src/Cardano/CEM/Monads/CLB.hs

Lines changed: 33 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ module Cardano.CEM.Monads.CLB where
44

55
import Prelude
66

7+
import Control.Concurrent.MVar (MVar, modifyMVar_, newMVar, readMVar)
78
import Control.Monad.State (StateT (..), gets)
89
import Data.Map qualified as Map
910
import Data.Set qualified as Set
@@ -34,12 +35,23 @@ import Clb.TimeSlot (posixTimeToUTCTime)
3435
import Cardano.CEM.Monads
3536
import Cardano.CEM.Monads.L1Commons
3637
import Cardano.CEM.OffChain (fromPlutusAddressInMonad)
38+
import Control.Monad.Reader (MonadReader (..), ReaderT (..))
3739

38-
instance (MonadFail m) => MonadBlockchainParams (ClbT m) where
39-
askNetworkId :: ClbT m NetworkId
40+
instance (MonadReader r m) => MonadReader r (ClbT m) where
41+
ask = lift ask
42+
local f action = ClbT $ local f $ unwrapClbT action
43+
44+
type ClbRunner = ClbT (ReaderT (MVar [BlockchainMonadEvent]) IO)
45+
46+
instance
47+
( MonadFail m
48+
, MonadIO m
49+
, MonadReader (MVar [BlockchainMonadEvent]) m
50+
) =>
51+
MonadBlockchainParams (ClbT m)
52+
where
4053
askNetworkId = gets (mockConfigNetworkId . mockConfig)
4154

42-
queryCurrentSlot :: ClbT m SlotNo
4355
queryCurrentSlot = getCurrentSlot
4456

4557
queryBlockchainParams = do
@@ -56,8 +68,14 @@ instance (MonadFail m) => MonadBlockchainParams (ClbT m) where
5668
, -- Staking is not supported
5769
stakePools = Set.empty
5870
}
71+
logEvent e = do
72+
logVar <- ask
73+
liftIO $ modifyMVar_ logVar (return . (:) e)
74+
eventList = do
75+
events <- ask
76+
liftIO $ readMVar events
5977

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

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

85-
instance (MonadFail m) => MonadTest (ClbT m) where
103+
instance (Monad m, MonadBlockchainParams (ClbT m)) => MonadTest (ClbT m) where
86104
getTestWalletSks = return $ map intToCardanoSk [1 .. 10]
87105

88106
genesisClbState :: Value -> ClbState
89107
genesisClbState genesisValue =
90108
initClb defaultBabbage genesisValue genesisValue
91109

92-
execOnIsolatedClb :: Value -> ClbT IO a -> IO a
93-
execOnIsolatedClb genesisValue action =
110+
execOnIsolatedClb :: Value -> ClbRunner a -> IO a
111+
execOnIsolatedClb genesisValue action = do
112+
emptyLog <- newMVar []
94113
fst
95-
<$> runStateT
96-
(unwrapClbT action)
97-
(genesisClbState genesisValue)
114+
<$> runReaderT
115+
( runStateT
116+
(unwrapClbT action)
117+
(genesisClbState genesisValue)
118+
)
119+
emptyLog

src/Cardano/CEM/Monads/L1.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,10 @@ instance MonadBlockchainParams L1Runner where
6363
<*> (toLedgerEpochInfo <$> queryCardanoNode QueryEraHistory)
6464
<*> queryCardanoNodeWrapping QueryStakePools
6565

66+
-- FIXME
67+
logEvent _ = return ()
68+
eventList = return []
69+
6670
queryCardanoNodeWrapping :: QueryInShelleyBasedEra Era b -> L1Runner b
6771
queryCardanoNodeWrapping query =
6872
handleEitherEra =<< queryCardanoNode wrapped

src/Cardano/CEM/Monads/L1Commons.hs

Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ import Cardano.Api.Shelley (LedgerProtocolParameters (..))
1616
import Cardano.CEM.Monads
1717
import Cardano.CEM.OffChain
1818
import Cardano.Extras
19+
import Data.Maybe (mapMaybe)
1920

2021
-- Main function
2122

@@ -89,7 +90,43 @@ cardanoTxBodyFromResolvedTx (MkResolvedTx {..}) = do
8990
let
9091
tx = makeSignedTransactionWithKeys [signer] body
9192
txInMode = TxInMode ShelleyBasedEraBabbage tx
93+
94+
lift $ recordFee txInsUtxo body
95+
9296
return (body, txInMode)
97+
where
98+
recordFee txInsUtxo body@(TxBody content) = do
99+
case txFee content of
100+
TxFeeExplicit era coin -> do
101+
MkBlockchainParams {protocolParameters, systemStart, eraHistory} <-
102+
queryBlockchainParams
103+
Right report <-
104+
return $
105+
evaluateTransactionExecutionUnits
106+
(shelleyBasedToCardanoEra era)
107+
systemStart
108+
eraHistory
109+
(LedgerProtocolParameters protocolParameters)
110+
txInsUtxo
111+
body
112+
let
113+
rights = mapMaybe $ \case
114+
Right x -> Just x
115+
Left _ -> Nothing
116+
budgets = rights $ map snd $ Map.toList report
117+
usedMemory = sum $ executionMemory <$> budgets
118+
usedCpu = sum $ executionSteps <$> budgets
119+
logEvent $
120+
UserSpentFee
121+
{ fees =
122+
MkFees
123+
{ fee = coin
124+
, usedMemory
125+
, usedCpu
126+
}
127+
, txId = getTxId body
128+
, txSigner = signer
129+
}
93130

94131
-- Utils
95132

src/Cardano/CEM/OffChain.hs

Lines changed: 9 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -56,48 +56,9 @@ awaitTx txId = do
5656
exists <- checkTxIdExists txId
5757
liftIO $ threadDelay 1_000_000
5858
if exists
59-
then return ()
59+
then logEvent $ AwaitedTx txId
6060
else go $ n - 1
6161

62-
data CEMAction script
63-
= MkCEMAction (CEMParams script) (Transition script)
64-
65-
deriving stock instance
66-
(CEMScript script) => Show (CEMAction script)
67-
68-
-- FIXME: use generic Some
69-
data SomeCEMAction where
70-
MkSomeCEMAction ::
71-
forall script.
72-
(CEMScriptCompiled script) =>
73-
CEMAction script ->
74-
SomeCEMAction
75-
76-
instance Show SomeCEMAction where
77-
-- FIXME: show script name
78-
show :: SomeCEMAction -> String
79-
show (MkSomeCEMAction action) = show action
80-
81-
data TxSpec = MkTxSpec
82-
{ actions :: [SomeCEMAction]
83-
, specSigner :: SigningKey PaymentKey
84-
}
85-
deriving stock (Show)
86-
87-
-- | Error occurred while trying to execute CEMScript transition
88-
data TransitionError
89-
= StateMachineError
90-
{ errorMessage :: String
91-
}
92-
| MissingTransitionInput
93-
deriving stock (Show, Eq)
94-
95-
data TxResolutionError
96-
= TxSpecIsIncorrect
97-
| MkTransitionError SomeCEMAction TransitionError
98-
| UnhandledSubmittingError TxSubmittingError
99-
deriving stock (Show)
100-
10162
failLeft :: (MonadFail m, Show s) => Either s a -> m a
10263
failLeft (Left errorMsg) = fail $ show errorMsg
10364
failLeft (Right value) = return value
@@ -252,15 +213,18 @@ resolveTx spec = runExceptT $ do
252213
-- Merge specs
253214
let
254215
mergedSpec' = head actionsSpecs
255-
mergedSpec = mergedSpec' {signer = specSigner spec}
216+
mergedSpec = (mergedSpec' :: ResolvedTx) {signer = specSigner spec}
256217

257218
return mergedSpec
258219

259220
resolveTxAndSubmit ::
260221
(MonadQueryUtxo m, MonadSubmitTx m, MonadIO m) =>
261222
TxSpec ->
262223
m (Either TxResolutionError TxId)
263-
resolveTxAndSubmit spec = runExceptT $ do
264-
resolved <- ExceptT $ resolveTx spec
265-
let result = submitResolvedTx resolved
266-
ExceptT $ first UnhandledSubmittingError <$> result
224+
resolveTxAndSubmit spec = do
225+
result <- runExceptT $ do
226+
resolved <- ExceptT $ resolveTx spec
227+
let result = submitResolvedTx resolved
228+
ExceptT $ first UnhandledSubmittingError <$> result
229+
logEvent $ SubmittedTxSpec spec result
230+
return result

src/Cardano/CEM/Testing/StateMachine.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ import Text.Show.Pretty (ppShow)
4040

4141
import Cardano.CEM (CEMParams (..))
4242
import Cardano.CEM hiding (scriptParams)
43-
import Cardano.CEM.Monads (MonadSubmitTx (..), ResolvedTx (..))
44-
import Cardano.CEM.Monads.CLB (execOnIsolatedClb)
43+
import Cardano.CEM.Monads (CEMAction (..), MonadSubmitTx (..), ResolvedTx (..), SomeCEMAction (..), TxSpec (..))
44+
import Cardano.CEM.Monads.CLB (ClbRunner, execOnIsolatedClb)
4545
import Cardano.CEM.OffChain
4646
import Cardano.CEM.OnChain (CEMScriptCompiled)
4747
import Cardano.Extras (signingKeyToPKH)
@@ -329,14 +329,14 @@ instance
329329

330330
runActionsInClb ::
331331
forall state.
332-
(StateModel (ScriptState state), RunModel (ScriptState state) (ClbT IO)) =>
332+
(StateModel (ScriptState state), RunModel (ScriptState state) ClbRunner) =>
333333
Value ->
334334
Actions (ScriptState state) ->
335335
Property
336336
runActionsInClb genesisValue actions =
337337
monadic (ioProperty . execOnIsolatedClb genesisValue) $
338338
void $
339-
runActions @(ScriptState state) @(ClbT IO) actions
339+
runActions @(ScriptState state) @(ClbRunner) actions
340340

341341
-- Orphans
342342

0 commit comments

Comments
 (0)