1
1
{-# LANGUAGE DeriveAnyClass #-}
2
+ {-# LANGUAGE DeriveDataTypeable #-}
2
3
{-# LANGUAGE RankNTypes #-}
3
4
{-# LANGUAGE TemplateHaskell #-}
4
5
@@ -9,6 +10,7 @@ module BotPlutusInterface.Types (
9
10
LogContext (.. ),
10
11
LogLevel (.. ),
11
12
LogType (.. ),
13
+ LogLine (.. ),
12
14
ContractEnvironment (.. ),
13
15
Tip (Tip , epoch , hash , slot , block , era , syncProgress ),
14
16
ContractState (.. ),
@@ -30,6 +32,7 @@ module BotPlutusInterface.Types (
30
32
addBudget ,
31
33
readCollateralUtxo ,
32
34
collateralValue ,
35
+ sufficientLogLevel ,
33
36
) where
34
37
35
38
import Cardano.Api (NetworkId (Testnet ), NetworkMagic (.. ), ScriptExecutionError , ScriptWitnessIndex )
@@ -38,8 +41,10 @@ import Control.Concurrent.STM (TVar, readTVarIO)
38
41
import Data.Aeson (ToJSON )
39
42
import Data.Aeson qualified as JSON
40
43
import Data.Aeson.TH (Options (.. ), defaultOptions , deriveJSON )
44
+ import Data.Data (Data (toConstr ), constrIndex , dataTypeOf , eqT , fromConstrB , indexConstr , type (:~: ) (Refl ))
41
45
import Data.Default (Default (def ))
42
46
import Data.Kind (Type )
47
+ import Data.List (intersect )
43
48
import Data.Map (Map )
44
49
import Data.Map qualified as Map
45
50
import Data.Text (Text )
@@ -177,13 +182,29 @@ newtype ContractStats = ContractStats
177
182
instance Show (TVar ContractStats ) where
178
183
show _ = " <ContractStats>"
179
184
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.
181
199
newtype LogsList = LogsList
182
- { getLogsList :: [( LogContext , LogLevel , PP. Doc () ) ]
200
+ { getLogsList :: [LogLine ]
183
201
}
184
202
deriving stock (Show )
185
203
deriving newtype (Semigroup , Monoid )
186
204
205
+ instance Pretty LogsList where
206
+ pretty = PP. vcat . map pretty . getLogsList
207
+
187
208
instance Show (TVar LogsList ) where
188
209
show _ = " <ContractLogs>"
189
210
@@ -252,7 +273,7 @@ data LogType
252
273
| CollateralLog
253
274
| PABLog
254
275
| AnyLog
255
- deriving stock (Eq , Ord , Show )
276
+ deriving stock (Eq , Ord , Show , Data )
256
277
257
278
instance Pretty LogType where
258
279
pretty CoinSelectionLog = " CoinSelection"
@@ -267,7 +288,16 @@ data LogLevel
267
288
| Notice { ltLogTypes :: [LogType ]}
268
289
| Info { ltLogTypes :: [LogType ]}
269
290
| 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."
271
301
272
302
instance Pretty LogLevel where
273
303
pretty = \ case
@@ -277,6 +307,18 @@ instance Pretty LogLevel where
277
307
Warn a -> " [WARNING " <> pretty a <> " ]"
278
308
Error a -> " [ERROR " <> pretty a <> " ]"
279
309
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
+
280
322
data LogContext = BpiLog | ContractLog
281
323
deriving stock (Bounded , Enum , Eq , Ord , Show )
282
324
0 commit comments