Skip to content

Commit 8809969

Browse files
authored
Add Pretty instance for log lines. (#138)
* Add Pretty instance for log lines. - new LogLine newtype with pretty instance - new sufficientLogLevel - fixes bug where logContext and logLevel were printed twice * Use Enum for LogLevel. Co-authored-by: IAmPara0x
1 parent afbafe3 commit 8809969

File tree

2 files changed

+61
-27
lines changed

2 files changed

+61
-27
lines changed

src/BotPlutusInterface/Effects.hs

Lines changed: 15 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -44,11 +44,13 @@ import BotPlutusInterface.Types (
4444
ContractState (ContractState),
4545
LogContext (BpiLog, ContractLog),
4646
LogLevel (..),
47+
LogLine (..),
4748
LogType (..),
4849
LogsList (LogsList),
4950
TxBudget,
5051
TxFile,
5152
addBudget,
53+
sufficientLogLevel,
5254
)
5355
import Cardano.Api (AsType, FileError (FileIOError), HasTextEnvelope, TextEnvelopeDescr, TextEnvelopeError)
5456
import Cardano.Api qualified
@@ -65,7 +67,6 @@ import Data.Aeson qualified as JSON
6567
import Data.Bifunctor (second)
6668
import Data.ByteString qualified as ByteString
6769
import Data.Kind (Type)
68-
import Data.List (intersect)
6970
import Data.Maybe (catMaybes)
7071
import Data.String (IsString, fromString)
7172
import Data.Text (Text)
@@ -74,7 +75,7 @@ import Ledger qualified
7475
import Plutus.Contract.Effects (ChainIndexQuery, ChainIndexResponse)
7576
import Plutus.PAB.Core.ContractInstance.STM (Activity)
7677
import PlutusTx.Builtins.Internal (BuiltinByteString (BuiltinByteString))
77-
import Prettyprinter (Pretty (pretty), defaultLayoutOptions, layoutPretty, (<+>))
78+
import Prettyprinter (Pretty (pretty), defaultLayoutOptions, layoutPretty)
7879
import Prettyprinter qualified as PP
7980
import Prettyprinter.Render.String qualified as Render
8081
import System.Directory qualified as Directory
@@ -147,12 +148,11 @@ handlePABEffect contractEnv =
147148
case contractEnv.cePABConfig.pcCliLocation of
148149
Local -> Directory.createDirectoryIfMissing createParents filePath
149150
Remote ipAddr -> createDirectoryIfMissingRemote ipAddr createParents filePath
150-
PrintLog logCtx logLevel txt ->
151-
let logMsg = prettyLog logCtx logLevel txt
152-
in do
153-
printLog' contractEnv.cePABConfig.pcLogLevel logCtx logLevel logMsg
154-
when contractEnv.cePABConfig.pcCollectLogs $
155-
collectLog contractEnv.ceContractLogs logCtx logLevel logMsg
151+
PrintLog logCtx logLevel msg -> do
152+
let logLine = LogLine logCtx logLevel msg
153+
printLog' contractEnv.cePABConfig.pcLogLevel logLine
154+
when contractEnv.cePABConfig.pcCollectLogs $
155+
collectLog contractEnv.ceContractLogs logLine
156156
UpdateInstanceState s -> do
157157
atomically $
158158
modifyTVar contractEnv.ceContractState $
@@ -191,27 +191,19 @@ handlePABEffect contractEnv =
191191
SetInMemCollateral c -> Collateral.setInMemCollateral contractEnv c
192192
)
193193

194-
printLog' :: LogLevel -> LogContext -> LogLevel -> PP.Doc () -> IO ()
195-
printLog' logLevelSetting msgCtx msgLogLvl msg =
194+
printLog' :: LogLevel -> LogLine -> IO ()
195+
printLog' logLevelSetting logLine =
196196
when
197-
( logLevelSetting {ltLogTypes = mempty} >= msgLogLvl {ltLogTypes = mempty}
198-
&& not (null intersectLogTypes)
199-
)
197+
(sufficientLogLevel logLevelSetting (logLineLevel logLine))
200198
$ putStrLn target
201199
where
202200
target =
203-
Render.renderString . layoutPretty defaultLayoutOptions $
204-
prettyLog msgCtx msgLogLvl msg
205-
206-
intersectLogTypes = ltLogTypes logLevelSetting `intersect` (ltLogTypes msgLogLvl <> [AnyLog])
207-
208-
prettyLog :: LogContext -> LogLevel -> PP.Doc () -> PP.Doc ()
209-
prettyLog msgCtx msgLogLvl msg = pretty msgCtx <+> pretty msgLogLvl <+> msg
201+
Render.renderString . layoutPretty defaultLayoutOptions . pretty $ logLine
210202

211-
collectLog :: TVar LogsList -> LogContext -> LogLevel -> PP.Doc () -> IO ()
212-
collectLog logs logCtx logLvl msg = atomically $ modifyTVar' logs appendLog
203+
collectLog :: TVar LogsList -> LogLine -> IO ()
204+
collectLog logs logLine = atomically $ modifyTVar' logs appendLog
213205
where
214-
appendLog (LogsList ls) = LogsList $ (logCtx, logLvl, msg) : ls
206+
appendLog (LogsList ls) = LogsList $ logLine : ls
215207

216208
-- | Reinterpret contract logs to be handled by PABEffect later down the line.
217209
handleContractLog :: forall w a effs. Member (PABEffect w) effs => Pretty a => Eff (LogMsg a ': effs) ~> Eff effs

src/BotPlutusInterface/Types.hs

Lines changed: 46 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE DeriveAnyClass #-}
2+
{-# LANGUAGE DeriveDataTypeable #-}
23
{-# LANGUAGE RankNTypes #-}
34
{-# LANGUAGE TemplateHaskell #-}
45

@@ -9,6 +10,7 @@ module BotPlutusInterface.Types (
910
LogContext (..),
1011
LogLevel (..),
1112
LogType (..),
13+
LogLine (..),
1214
ContractEnvironment (..),
1315
Tip (Tip, epoch, hash, slot, block, era, syncProgress),
1416
ContractState (..),
@@ -30,6 +32,7 @@ module BotPlutusInterface.Types (
3032
addBudget,
3133
readCollateralUtxo,
3234
collateralValue,
35+
sufficientLogLevel,
3336
) where
3437

3538
import Cardano.Api (NetworkId (Testnet), NetworkMagic (..), ScriptExecutionError, ScriptWitnessIndex)
@@ -38,8 +41,10 @@ import Control.Concurrent.STM (TVar, readTVarIO)
3841
import Data.Aeson (ToJSON)
3942
import Data.Aeson qualified as JSON
4043
import Data.Aeson.TH (Options (..), defaultOptions, deriveJSON)
44+
import Data.Data (Data (toConstr), constrIndex, dataTypeOf, eqT, fromConstrB, indexConstr, type (:~:) (Refl))
4145
import Data.Default (Default (def))
4246
import Data.Kind (Type)
47+
import Data.List (intersect)
4348
import Data.Map (Map)
4449
import Data.Map qualified as Map
4550
import Data.Text (Text)
@@ -177,13 +182,29 @@ newtype ContractStats = ContractStats
177182
instance Show (TVar ContractStats) where
178183
show _ = "<ContractStats>"
179184

180-
-- | List of string logs.
185+
{- | Single log message
186+
Defined for pretty instance.
187+
-}
188+
data LogLine = LogLine
189+
{ logLineContext :: LogContext
190+
, logLineLevel :: LogLevel
191+
, logLineMsg :: PP.Doc ()
192+
}
193+
deriving stock (Show)
194+
195+
instance Pretty LogLine where
196+
pretty (LogLine msgCtx msgLogLvl msg) = pretty msgCtx <+> pretty msgLogLvl <+> PP.unAnnotate msg
197+
198+
-- | List of logs.
181199
newtype LogsList = LogsList
182-
{ getLogsList :: [(LogContext, LogLevel, PP.Doc ())]
200+
{ getLogsList :: [LogLine]
183201
}
184202
deriving stock (Show)
185203
deriving newtype (Semigroup, Monoid)
186204

205+
instance Pretty LogsList where
206+
pretty = PP.vcat . map pretty . getLogsList
207+
187208
instance Show (TVar LogsList) where
188209
show _ = "<ContractLogs>"
189210

@@ -252,7 +273,7 @@ data LogType
252273
| CollateralLog
253274
| PABLog
254275
| AnyLog
255-
deriving stock (Eq, Ord, Show)
276+
deriving stock (Eq, Ord, Show, Data)
256277

257278
instance Pretty LogType where
258279
pretty CoinSelectionLog = "CoinSelection"
@@ -267,7 +288,16 @@ data LogLevel
267288
| Notice {ltLogTypes :: [LogType]}
268289
| Info {ltLogTypes :: [LogType]}
269290
| Debug {ltLogTypes :: [LogType]}
270-
deriving stock (Eq, Ord, Show)
291+
deriving stock (Eq, Show, Data)
292+
293+
instance Enum LogLevel where
294+
fromEnum = (\a -> a - 1) . constrIndex . toConstr
295+
toEnum = fromConstrB field . indexConstr (dataTypeOf $ Notice []) . (+ 1)
296+
where
297+
field :: forall a. Data a => a
298+
field = case eqT :: Maybe (a :~: [LogType]) of
299+
Just Refl -> [AnyLog]
300+
Nothing -> error "Expected a value of type LogType."
271301

272302
instance Pretty LogLevel where
273303
pretty = \case
@@ -277,6 +307,18 @@ instance Pretty LogLevel where
277307
Warn a -> "[WARNING " <> pretty a <> "]"
278308
Error a -> "[ERROR " <> pretty a <> "]"
279309

310+
{- | if sufficientLogLevel settingLogLevel msgLogLvl
311+
then message should be displayed with this log level setting.
312+
-}
313+
sufficientLogLevel :: LogLevel -> LogLevel -> Bool
314+
sufficientLogLevel logLevelSetting msgLogLvl =
315+
msgLogLvl `constrLEq` logLevelSetting -- the log is important enough
316+
&& not (null intersectLogTypes) -- log is of type we're interested in
317+
where
318+
intersectLogTypes = ltLogTypes logLevelSetting `intersect` (ltLogTypes msgLogLvl <> [AnyLog])
319+
320+
constrLEq a b = fromEnum a <= fromEnum b
321+
280322
data LogContext = BpiLog | ContractLog
281323
deriving stock (Bounded, Enum, Eq, Ord, Show)
282324

0 commit comments

Comments
 (0)