Skip to content

Commit fcaae28

Browse files
geo2agithub-actionsjbertholdrv-jenkins
authored
One-line contextual logging of Kore actions (#3837)
Combines #3833 and #3831 - in Kore, implement rendering of oneline logs prefixed with the context stack, in the spirit of #3826 - add `--log-format <standard|oneline|json> (default:oneline)` to `kore-rpc-booster`. - to recover the old behaviour of `-l Rewrite` and friends, use `--log-format standard`, i.e. `kore-rpc-booster --log-format standard -l Rewrite` - if any `--log-context` is passed, the log format is effectively override to be `oneline` - in `booster/tools/booster/Server.hs`, construct a log action to be passed to Kore. If no `--log-context` options are passed, then the old `-l RewriteKore` and fields levels still work with `--log-format standard`. If `--log-context` is passed, then the complete set of proxy-compatible Kore log entries is enabled, and the filtering is done using the glob context filter late in the colog pipeline. Things to do in a follow-up: - json logging is inconsistent, both the interface and the implementation: - to get simplification JSON logs from both Booster and Kore, we currently need to give two options: `kore-rpc-booster --log-format json -l SimplifyJson`, which is not ideal. We need to remove `-l SimplifyJson` and forward the log format to Booster instead. - To implement the previous item in a clean way, we actually need to stop emitting the logs at `SimplifyJson` level and instead render the regular log items as json. - file logging is inconsistent. It is currently not possible to redirect Booster's contextual logs into a file. - the performance of context filtering in Kore is likely terrible, since we match the while log message, as a string, against the glob pattern. There is not penalty if the contextual logging is off however. --------- Co-authored-by: github-actions <[email protected]> Co-authored-by: Jost Berthold <[email protected]> Co-authored-by: rv-jenkins <[email protected]>
1 parent 88ef647 commit fcaae28

File tree

26 files changed

+855
-614
lines changed

26 files changed

+855
-614
lines changed

booster/library/Booster/CLOptions.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
module Booster.CLOptions (
44
CLOptions (..),
55
EquationOptions (..),
6+
LogFormat (..),
67
clOptionsParser,
78
adjustLogLevels,
89
versionInfoParser,
@@ -31,6 +32,7 @@ data CLOptions = CLOptions
3132
, port :: Int
3233
, logLevels :: [LogLevel]
3334
, logTimeStamps :: Bool
35+
, logFormat :: LogFormat
3436
, logContexts :: [String]
3537
, notLogContexts :: [String]
3638
, simplificationLogFile :: Maybe FilePath
@@ -41,6 +43,18 @@ data CLOptions = CLOptions
4143
}
4244
deriving (Show)
4345

46+
data LogFormat
47+
= Standard
48+
| OneLine
49+
| Json
50+
deriving (Eq)
51+
52+
instance Show LogFormat where
53+
show = \case
54+
OneLine -> "oneline"
55+
Standard -> "standard"
56+
Json -> "json"
57+
4458
clOptionsParser :: Parser CLOptions
4559
clOptionsParser =
4660
CLOptions
@@ -82,6 +96,14 @@ clOptionsParser =
8296
)
8397
)
8498
<*> switch (long "log-timestamps" <> help "Add timestamps to logs")
99+
<*> option
100+
(eitherReader readLogFormat)
101+
( metavar "LOGFORMAT"
102+
<> value OneLine
103+
<> long "log-format"
104+
<> help "Format to output logs in"
105+
<> showDefault
106+
)
85107
<*> many
86108
( option
87109
str
@@ -143,6 +165,13 @@ clOptionsParser =
143165
. toPascal
144166
. fromKebab
145167

168+
readLogFormat :: String -> Either String LogFormat
169+
readLogFormat = \case
170+
"oneline" -> Right OneLine
171+
"standard" -> Right Standard
172+
"json" -> Right Json
173+
other -> Left $ other <> ": Unsupported log format"
174+
146175
-- custom log levels that can be selected
147176
allowedLogLevels :: [(String, String)]
148177
allowedLogLevels =

booster/library/Booster/Log.hs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -39,12 +39,10 @@ import Data.List.Extra (splitOn, takeEnd)
3939
import Data.Set qualified as Set
4040
import Data.String (IsString)
4141
import Data.Text (Text, pack)
42-
import Data.Text qualified as Text
4342
import Data.Text.Lazy qualified as LazyText
44-
import Data.Word (Word64)
4543
import GHC.Exts (IsString (..))
4644
import GHC.TypeLits (KnownSymbol, symbolVal)
47-
import Numeric (showHex)
45+
import Kore.Util (showHashHex)
4846
import Prettyprinter (Pretty, pretty)
4947

5048
newtype Logger a = Logger (a -> IO ())
@@ -97,9 +95,6 @@ withContext c = withLogger (\(Logger l) -> Logger $ l . (\(LogMessage ctxt m) ->
9795

9896
newtype TermCtxt = TermCtxt Int
9997

100-
showHashHex :: Int -> Text
101-
showHashHex h = let w64 :: Word64 = fromIntegral h in Text.take 7 $ pack $ showHex w64 ""
102-
10398
instance ToLogFormat TermCtxt where
10499
toTextualLog (TermCtxt hsh) = "term " <> (showHashHex hsh)
105100

booster/library/Booster/Pattern/ApplyEquations.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,7 @@ import Booster.Prettyprinter (renderDefault, renderOneLineText)
8484
import Booster.SMT.Interface qualified as SMT
8585
import Booster.Util (Bound (..), Flag (..))
8686
import Kore.JsonRpc.Types.Log qualified as KoreRpcLog
87+
import Kore.Util (showHashHex)
8788

8889
newtype EquationT io a
8990
= EquationT (ReaderT EquationConfig (ExceptT EquationFailure (StateT EquationState io)) a)

booster/test/rpc-integration/test-log-simplify-json/simplify-log.txt.golden

Lines changed: 277 additions & 270 deletions
Large diffs are not rendered by default.

booster/tools/booster/Server.hs

Lines changed: 47 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,6 @@ import Control.Monad.Logger (
2020
LoggingT (runLoggingT),
2121
MonadLoggerIO (askLoggerIO),
2222
ToLogStr (toLogStr),
23-
defaultLoc,
2423
runNoLoggingT,
2524
)
2625
import Control.Monad.Logger qualified as Logger
@@ -37,6 +36,7 @@ import Data.Text.Encoding qualified as Text (decodeUtf8)
3736
import Options.Applicative
3837
import System.Clock (
3938
Clock (..),
39+
TimeSpec (..),
4040
getTime,
4141
)
4242
import System.Environment qualified as Env
@@ -72,21 +72,25 @@ import Kore.JsonRpc.Error hiding (Aborted, error)
7272
import Kore.JsonRpc.Server
7373
import Kore.JsonRpc.Types (API, HaltReason (..), ReqOrRes (Req, Res))
7474
import Kore.JsonRpc.Types.Depth (Depth (..))
75-
import Kore.Log (
75+
import Kore.Log.BoosterAdaptor (
7676
ExeName (..),
7777
KoreLogType (..),
7878
LogAction (LogAction),
79-
LogSomeActionData (..),
8079
TimestampsSwitch (TimestampsDisable),
8180
defaultKoreLogOptions,
81+
koreSomeEntryLogAction,
82+
renderJson,
83+
renderOnelinePretty,
84+
renderStandardPretty,
8285
swappableLogger,
8386
withLogger,
8487
)
85-
import Kore.Log qualified as Log
88+
import Kore.Log.BoosterAdaptor qualified as Log
8689
import Kore.Log.DebugSolver qualified as Log
8790
import Kore.Log.Registry qualified as Log
8891
import Kore.Rewrite.SMT.Lemma (declareSMTLemmas)
8992
import Kore.Syntax.Definition (ModuleName (ModuleName), SentenceAxiom)
93+
import Kore.Util (extractLogMessageContext)
9094
import Options.SMT as KoreSMT (KoreSolverOptions (..), Solver (..))
9195
import Prettyprinter qualified as Pretty
9296
import Proxy (KoreServer (..), ProxyConfig (..))
@@ -115,6 +119,7 @@ main = do
115119
, port
116120
, llvmLibraryFile
117121
, logLevels
122+
, logFormat
118123
, logTimeStamps
119124
, logContexts
120125
, notLogContexts
@@ -136,6 +141,7 @@ main = do
136141
(logLevel, customLevels) = adjustLogLevels logLevels
137142
globPatterns = map (Glob.compile . filter (\c -> not (c == '\'' || c == '"'))) logContexts
138143
negGlobPatterns = map (Glob.compile . filter (\c -> not (c == '\'' || c == '"'))) notLogContexts
144+
contexLoggingEnabled = not (null logContexts) || not (null notLogContexts)
139145
levelFilter :: Logger.LogSource -> LogLevel -> Bool
140146
levelFilter _source lvl =
141147
lvl `elem` customLevels
@@ -145,8 +151,6 @@ main = do
145151
&& any (flip Glob.match (Text.unpack l)) globPatterns
146152
_ -> False
147153
|| lvl >= logLevel && lvl <= LevelError
148-
koreLogExtraLevels =
149-
Set.unions $ mapMaybe (`Map.lookup` koreExtraLogs) customLevels
150154
koreSolverOptions = translateSMTOpts smtOptions
151155

152156
mTimeCache <- if logTimeStamps then Just <$> (newTimeCache "%Y-%m-%d %T") else pure Nothing
@@ -165,39 +169,52 @@ main = do
165169

166170
monadLogger <- askLoggerIO
167171

168-
koreLogEntriesAsJsonSelector <-
169-
if Logger.LevelOther "SimplifyJson" `elem` customLevels
170-
then case Map.lookup (Logger.LevelOther "SimplifyJson") logLevelToKoreLogEntryMap of
171-
Nothing -> do
172-
Logger.logWarnNS
173-
"proxy"
174-
"Could not find out which Kore log entries correspond to the SimplifyJson level"
175-
pure (const False)
176-
Just koreSimplificationLogEntries -> pure (`elem` koreSimplificationLogEntries)
177-
else pure (const False)
172+
let koreLogRenderer = case logFormat of
173+
Standard -> renderStandardPretty (ExeName "") (TimeSpec 0 0) TimestampsDisable
174+
OneLine -> renderOnelinePretty (ExeName "") (TimeSpec 0 0) TimestampsDisable
175+
Json -> renderJson (ExeName "") (TimeSpec 0 0) TimestampsDisable
176+
koreLogLateFilter = case logFormat of
177+
OneLine ->
178+
if contexLoggingEnabled
179+
then \txt ->
180+
let contextStr = Text.unpack $ extractLogMessageContext txt
181+
in -- FIXME: likely terrible performance! Use something that does not unpack Text
182+
not (any (flip Glob.match contextStr) negGlobPatterns)
183+
&& any (flip Glob.match contextStr) globPatterns
184+
else const True
185+
_ -> const True
186+
187+
koreLogEntries =
188+
if contexLoggingEnabled
189+
then -- context logging: enable all Proxy-required Kore log entries
190+
Set.unions . Map.elems $ koreExtraLogs
191+
else -- no context logging: only enable Kore log entries for the given Proxy log levels
192+
Set.unions . mapMaybe (`Map.lookup` koreExtraLogs) $ customLevels
193+
194+
koreLogActions :: forall m. MonadIO m => [LogAction m Log.SomeEntry]
195+
koreLogActions = [koreLogAction]
196+
where
197+
koreLogAction =
198+
koreSomeEntryLogAction
199+
koreLogRenderer
200+
(const True)
201+
koreLogLateFilter
202+
( LogAction $ \txt -> liftIO $
203+
case mFileLogger of
204+
Just fileLogger -> fileLogger $ toLogStr $ txt <> "\n"
205+
Nothing -> stderrLogger $ toLogStr $ txt <> "\n"
206+
)
178207

179208
liftIO $ void $ withBugReport (ExeName "kore-rpc-booster") BugReportOnError $ \_reportDirectory -> withMDLib llvmLibraryFile $ \mdl -> do
180209
let coLogLevel = fromMaybe Log.Info $ toSeverity logLevel
181210
koreLogOptions =
182211
(defaultKoreLogOptions (ExeName "") startTime)
183212
{ Log.logLevel = coLogLevel
184-
, Log.logEntries = koreLogExtraLevels
213+
, Log.logEntries = koreLogEntries
185214
, Log.timestampsSwitch = TimestampsDisable
186215
, Log.debugSolverOptions =
187216
Log.DebugSolverOptions . fmap (<> ".kore") $ smtOptions >>= (.transcript)
188-
, Log.logType =
189-
LogSomeAction $
190-
LogSomeActionData
191-
{ entrySelector = koreLogEntriesAsJsonSelector
192-
, standardLogAction =
193-
(LogAction $ \txt -> liftIO $ monadLogger defaultLoc "kore" logLevel $ toLogStr txt)
194-
, jsonLogAction =
195-
( LogAction $ \txt -> liftIO $
196-
case mFileLogger of
197-
Just fileLogger -> fileLogger $ toLogStr $ txt <> "\n"
198-
Nothing -> stderrLogger $ toLogStr $ "[SimplifyJson] " <> txt <> "\n"
199-
)
200-
}
217+
, Log.logType = LogProxy (mconcat koreLogActions)
201218
, Log.logFormat = Log.Standard
202219
}
203220
srvSettings = serverSettings port "*"

0 commit comments

Comments
 (0)