Skip to content

Commit e62fba2

Browse files
goodlyrottenapplegithub-actionsgeo2a
authored
JSON logging cleanup (#3881)
* Re-add the `test-log-simplify-json` rpc test with a much smaller footprint, as we want to just track the context logging format * Clean up the equation contexts a bit in booster, as we weren't consistently logging messages around functions/equations * Closes #3864 by adding a conversion from the old custom log levels to contextual log filters. * Closes #3866 by removing the SimplifyJson log level which has been replaced by `-l Simplify --log-format json` --------- Co-authored-by: github-actions <[email protected]> Co-authored-by: Georgy Lukyanov <[email protected]>
1 parent 8b7ed67 commit e62fba2

File tree

14 files changed

+4942
-122
lines changed

14 files changed

+4942
-122
lines changed

booster/library/Booster/CLOptions.hs

Lines changed: 46 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE QuasiQuotes #-}
12
{-# LANGUAGE TemplateHaskell #-}
23

34
module Booster.CLOptions (
@@ -6,6 +7,7 @@ module Booster.CLOptions (
67
LogFormat (..),
78
clOptionsParser,
89
adjustLogLevels,
10+
levelToContext,
911
versionInfoParser,
1012
) where
1113

@@ -22,9 +24,11 @@ import Text.Casing (fromHumps, fromKebab, toKebab, toPascal)
2224
import Text.Read (readMaybe)
2325

2426
import Booster.GlobalState (EquationOptions (..))
25-
import Booster.Log.Context (ContextFilter, readContextFilter)
27+
import Booster.Log.Context (ContextFilter, ctxt, readContextFilter)
2628
import Booster.SMT.Interface (SMTOptions (..), defaultSMTOptions)
2729
import Booster.SMT.LowLevelCodec qualified as SMT (parseSExpr)
30+
import Data.Map (Map)
31+
import Data.Map qualified as Map
2832

2933
data CLOptions = CLOptions
3034
{ definitionFile :: FilePath
@@ -35,7 +39,7 @@ data CLOptions = CLOptions
3539
, logTimeStamps :: Bool
3640
, logFormat :: LogFormat
3741
, logContexts :: [ContextFilter]
38-
, simplificationLogFile :: Maybe FilePath
42+
, logFile :: Maybe FilePath
3943
, smtOptions :: Maybe SMTOptions
4044
, equationOptions :: EquationOptions
4145
, -- developer options below
@@ -116,10 +120,10 @@ clOptionsParser =
116120
)
117121
<*> optional
118122
( strOption
119-
( metavar "JSON_LOG_FILE"
120-
<> long "simplification-log-file"
123+
( metavar "LOG_FILE"
124+
<> long "log-file"
121125
<> help
122-
"Log file for the JSON simplification logs"
126+
"Log file to output the logs into"
123127
)
124128
)
125129
<*> parseSMTOptions
@@ -171,14 +175,50 @@ allowedLogLevels =
171175
, ("RewriteKore", "Log all rewriting in kore-rpc fall-backs")
172176
, ("RewriteSuccess", "Log successful rewrites (booster and kore-rpc)")
173177
, ("Simplify", "Log all simplification/evaluation in booster")
174-
, ("SimplifyJson", "Log simplification/evaluation in booster as JSON")
175178
, ("SimplifyKore", "Log all simplification in kore-rpc")
176179
, ("SimplifySuccess", "Log successful simplifications (booster and kore-rpc)")
177180
, ("Depth", "Log the current depth of the state")
178181
, ("SMT", "Log the SMT-solver interactions")
179182
, ("ErrorDetails", "Log error conditions with extensive details")
180183
]
181184

185+
levelToContext :: Map Text [ContextFilter]
186+
levelToContext =
187+
Map.fromList
188+
[
189+
( "Simplify"
190+
,
191+
[ [ctxt| booster|kore>function*|simplification*,success|failure|abort|detail |]
192+
, [ctxt| booster|kore>function*|simplification*,match,failure|abort |]
193+
]
194+
)
195+
,
196+
( "SimplifySuccess"
197+
,
198+
[ [ctxt| booster|kore>function*|simplification*,success|detail |]
199+
]
200+
)
201+
,
202+
( "Rewrite"
203+
,
204+
[ [ctxt| booster|kore>rewrite*,success|failure|abort|detail |]
205+
, [ctxt| booster|kore>rewrite*,match,failure|abort |]
206+
]
207+
)
208+
,
209+
( "RewriteSuccess"
210+
,
211+
[ [ctxt| booster|kore>rewrite*,success|detail |]
212+
]
213+
)
214+
,
215+
( "SMT"
216+
,
217+
[ [ctxt| booster|kore>smt |]
218+
]
219+
)
220+
]
221+
182222
-- Partition provided log levels into standard and custom ones, and
183223
-- select the lowest standard level. Default to 'LevelInfo' if no
184224
-- standard log level was given.

booster/library/Booster/Log/Context.hs

Lines changed: 27 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,25 +1,31 @@
1-
module Booster.Log.Context (ContextFilter, mustMatch, readContextFilter, readMatch) where
1+
{-# LANGUAGE DeriveDataTypeable #-}
2+
{-# LANGUAGE TemplateHaskellQuotes #-}
3+
4+
module Booster.Log.Context (ContextFilter, mustMatch, readContextFilter, readMatch, ctxt) where
25

36
import Control.Applicative ((<|>))
47
import Data.Attoparsec.ByteString.Char8 qualified as A
58
import Data.ByteString.Char8 qualified as BS
69
import Data.Char (isSpace)
10+
import Data.Generics (Data, extQ)
711
import Data.List.Extra (replace)
12+
import Language.Haskell.TH (ExpQ, Lit (StringL), appE, litE, varE)
13+
import Language.Haskell.TH.Quote (QuasiQuoter (..), dataToExpQ)
814

915
data ContextFilterSingle
1016
= Exact BS.ByteString
1117
| Prefix BS.ByteString
1218
| Suffix BS.ByteString
1319
| Infix BS.ByteString
1420
| Negate ContextFilterSingle
15-
deriving (Show)
21+
deriving (Show, Data)
1622

1723
data ContextFilter
1824
= First [ContextFilterSingle]
1925
| ThenDirectChild [ContextFilterSingle] ContextFilter
2026
| ThenChild [ContextFilterSingle] ContextFilter
2127
| Last [ContextFilterSingle]
22-
deriving (Show)
28+
deriving (Show, Data)
2329

2430
reserved :: String
2531
reserved = "|*!>,."
@@ -79,3 +85,21 @@ readMatch :: BS.ByteString -> [BS.ByteString] -> Either String Bool
7985
readMatch pat' xs = do
8086
pat <- A.parseOnly (contextFilterP <* A.skipSpace <* A.endOfInput) pat'
8187
pure $ mustMatch pat xs
88+
89+
ctxt :: QuasiQuoter
90+
ctxt =
91+
QuasiQuoter
92+
{ quoteExp =
93+
dataToExpQ (const Nothing `extQ` handleBS)
94+
. either (error . show) id
95+
. readContextFilter
96+
, quotePat = undefined
97+
, quoteType = undefined
98+
, quoteDec = undefined
99+
}
100+
where
101+
handleBS :: BS.ByteString -> Maybe ExpQ
102+
handleBS x =
103+
-- convert the byte string to a string literal
104+
-- and wrap it back with BS.pack
105+
Just $ appE (varE 'BS.pack) $ litE $ StringL $ BS.unpack x

booster/library/Booster/Pattern/ApplyEquations.hs

Lines changed: 8 additions & 61 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@ module Booster.Pattern.ApplyEquations (
2828
evaluateConstraints,
2929
) where
3030

31-
import Control.Applicative (Alternative (..))
3231
import Control.Monad
3332
import Control.Monad.Extra (fromMaybeM, whenJust)
3433
import Control.Monad.IO.Class (MonadIO (..))
@@ -45,7 +44,6 @@ import Control.Monad.Trans.Except
4544
import Control.Monad.Trans.Reader (ReaderT (..), ask, asks, withReaderT)
4645
import Control.Monad.Trans.State
4746
import Data.Aeson (object, (.=))
48-
import Data.Aeson.Text (encodeToLazyText)
4947
import Data.Bifunctor (bimap)
5048
import Data.ByteString.Char8 qualified as BS
5149
import Data.Coerce (coerce)
@@ -62,7 +60,6 @@ import Data.Set qualified as Set
6260
import Data.Text (Text, pack)
6361
import Data.Text qualified as Text
6462
import Data.Text.Encoding qualified as Text
65-
import Data.Text.Lazy qualified as Text (toStrict)
6663
import GHC.TypeLits (KnownSymbol)
6764
import Prettyprinter
6865

@@ -82,7 +79,6 @@ import Booster.Prettyprinter (renderDefault, renderOneLineText)
8279
import Booster.SMT.Interface qualified as SMT
8380
import Booster.Syntax.Json.Externalise (externaliseTerm)
8481
import Booster.Util (Bound (..))
85-
import Kore.JsonRpc.Types.Log qualified as KoreRpcLog
8682
import Kore.Util (showHashHex)
8783

8884
newtype EquationT io a
@@ -254,52 +250,6 @@ isMatchFailure _ = False
254250
isSuccess EquationApplied{} = True
255251
isSuccess _ = False
256252

257-
{- | Attempt to get an equation's unique id, falling back to it's label or eventually to UNKNOWN.
258-
The fallbacks are useful in case of cached equation applications or the ones done via LLVM,
259-
as neither of these categories have unique IDs.
260-
-}
261-
equationRuleIdWithFallbacks :: EquationMetadata -> Text
262-
equationRuleIdWithFallbacks metadata =
263-
fromMaybe "UNKNOWN" (fmap getUniqueId metadata.ruleId <|> metadata.label)
264-
265-
equationTraceToLogEntry :: EquationTrace Term -> KoreRpcLog.LogEntry
266-
equationTraceToLogEntry = \case
267-
EquationApplied _subjectTerm metadata _rewritten ->
268-
KoreRpcLog.Simplification
269-
{ originalTerm
270-
, originalTermIndex
271-
, origin
272-
, result =
273-
KoreRpcLog.Success Nothing Nothing _ruleId
274-
}
275-
where
276-
originalTerm = Nothing
277-
originalTermIndex = Nothing
278-
origin = KoreRpcLog.Booster
279-
_ruleId = equationRuleIdWithFallbacks metadata
280-
EquationNotApplied _subjectTerm metadata failure ->
281-
KoreRpcLog.Simplification
282-
{ originalTerm
283-
, originalTermIndex
284-
, origin
285-
, result = KoreRpcLog.Failure (failureDescription failure) (Just _ruleId)
286-
}
287-
where
288-
originalTerm = Nothing
289-
originalTermIndex = Nothing
290-
origin = KoreRpcLog.Booster
291-
_ruleId = equationRuleIdWithFallbacks metadata
292-
293-
failureDescription :: ApplyEquationFailure -> Text.Text
294-
failureDescription = \case
295-
FailedMatch{} -> "Failed match"
296-
IndeterminateMatch -> "IndeterminateMatch"
297-
IndeterminateCondition{} -> "IndeterminateCondition"
298-
ConditionFalse{} -> "ConditionFalse"
299-
EnsuresFalse{} -> "EnsuresFalse"
300-
RuleNotPreservingDefinedness -> "RuleNotPreservingDefinedness"
301-
MatchConstraintViolated{} -> "MatchConstraintViolated"
302-
303253
startState :: SimplifierCache -> EquationState
304254
startState cache =
305255
EquationState
@@ -426,9 +376,7 @@ iterateEquations ::
426376
Term ->
427377
EquationT io Term
428378
iterateEquations direction preference startTerm = do
429-
result <- pushRecursion startTerm >>= checkCounter >> go startTerm <* popRecursion
430-
when (startTerm /= result) $ withContext "success" $ withTermContext result $ pure ()
431-
pure result
379+
pushRecursion startTerm >>= checkCounter >> go startTerm <* popRecursion
432380
where
433381
checkCounter counter = do
434382
config <- getConfig
@@ -832,13 +780,15 @@ applyEquations theory handler term = do
832780
processEquations [] =
833781
pure term -- nothing to do, term stays the same
834782
processEquations (eq : rest) = do
835-
res <- applyEquation term eq
783+
res <- withRuleContext eq $ applyEquation term eq
836784
emitEquationTrace term eq.attributes.location eq.attributes.ruleLabel eq.attributes.uniqueId res
837785
handler
838-
(\t -> setChanged >> pure t)
786+
( \t -> setChanged >> (withContext (LogContext eq) $ withContext "success" $ withTermContext t $ pure t)
787+
)
839788
(processEquations rest)
840-
( withContext "abort" $
841-
logMessage ("Aborting simplification/function evaluation" :: Text) >> pure term
789+
( withContext (LogContext eq) $
790+
withContext "abort" $
791+
logMessage ("Aborting simplification/function evaluation" :: Text) >> pure term
842792
)
843793
res
844794

@@ -861,9 +811,6 @@ emitEquationTrace t loc lbl uid res = do
861811
Failure failure -> EquationNotApplied t (EquationMetadata loc lbl uid) failure
862812
prettyItem = pack . renderDefault . pretty $ newTraceItem
863813
logOther (LevelOther "Simplify") prettyItem
864-
logOther
865-
(LevelOther "SimplifyJson")
866-
(Text.toStrict . encodeToLazyText $ equationTraceToLogEntry newTraceItem)
867814
case res of
868815
Success{} -> logOther (LevelOther "SimplifySuccess") prettyItem
869816
_ -> pure ()
@@ -875,7 +822,7 @@ applyEquation ::
875822
Term ->
876823
RewriteRule tag ->
877824
EquationT io ApplyEquationResult
878-
applyEquation term rule = withRuleContext rule $ fmap (either Failure Success) $ runExceptT $ do
825+
applyEquation term rule = fmap (either Failure Success) $ runExceptT $ do
879826
-- ensured by internalisation: no existentials in equations
880827
unless (null rule.existentials) $ do
881828
withContext "abort" $

booster/library/Booster/Util.hs

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -118,19 +118,13 @@ decodeLabel' orig =
118118
-- logging helpers, some are adapted from monad-logger-aeson
119119
handleOutput ::
120120
FastLogger ->
121-
Maybe FastLogger ->
122121
Log.Loc ->
123122
Log.LogSource ->
124123
Log.LogLevel ->
125124
Log.LogStr ->
126125
IO ()
127-
handleOutput stderrLogger mFileLogger loc src level msg =
128-
case level of
129-
Log.LevelOther "SimplifyJson" ->
130-
case mFileLogger of
131-
Nothing -> stderrLogger $ "[SimplifyJson] " <> msg <> "\n"
132-
Just fileLogger -> fileLogger $ msg <> "\n"
133-
_ -> stderrLogger $ Log.defaultLogStr loc src level msg
126+
handleOutput stderrLogger loc src level msg =
127+
stderrLogger $ Log.defaultLogStr loc src level msg
134128

135129
newFastLoggerMaybeWithTime :: Maybe (IO FormattedTime) -> LogType -> IO (LogStr -> IO (), IO ())
136130
newFastLoggerMaybeWithTime = \case

booster/test/rpc-integration/resources/log-simplify-json.kore

Lines changed: 0 additions & 1 deletion
This file was deleted.

0 commit comments

Comments
 (0)