11{-# LANGUAGE FlexibleContexts #-}
2+ {-# LANGUAGE QuasiQuotes #-}
23{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
34
45{- |
@@ -13,7 +14,6 @@ import Control.DeepSeq (force)
1314import Control.Exception (AsyncException (UserInterrupt ), evaluate , handleJust )
1415import Control.Monad (forM_ , unless , void )
1516import Control.Monad.Catch (bracket )
16- import Control.Monad.Extra (whenJust )
1717import Control.Monad.IO.Class (MonadIO (liftIO ))
1818import Control.Monad.Logger (
1919 LogLevel (.. ),
@@ -58,7 +58,7 @@ import Booster.GlobalState
5858import Booster.JsonRpc qualified as Booster
5959import Booster.LLVM.Internal (mkAPI , withDLib )
6060import Booster.Log hiding (withLogger )
61- import Booster.Log.Context qualified
61+ import Booster.Log.Context qualified as Ctxt
6262import Booster.Pattern.Base (Predicate (.. ))
6363import Booster.Prettyprinter (renderOneLineText )
6464import Booster.SMT.Base qualified as SMT (SExpr (.. ), SMTId (.. ))
@@ -149,6 +149,7 @@ main = do
149149 logContextsWithcustomLevelContexts =
150150 logContexts
151151 <> concatMap (\ case LevelOther o -> fromMaybe [] $ levelToContext Map. !? o; _ -> [] ) customLevels
152+ <> [[Ctxt. ctxt | *>timing |] | printStats]
152153 contextLoggingEnabled = not (null logContextsWithcustomLevelContexts)
153154 koreSolverOptions = translateSMTOpts smtOptions
154155 timestampFlag = case timeStampsFormat of
@@ -177,7 +178,7 @@ main = do
177178 ( \ (Log. SomeEntry _ c) -> Text. encodeUtf8 <$> Log. oneLineContextDoc c
178179 )
179180 ctxt
180- in any (flip Booster.Log.Context . mustMatch contextStrs) logContextsWithcustomLevelContexts
181+ in any (flip Ctxt . mustMatch contextStrs) logContextsWithcustomLevelContexts
181182 )
182183
183184 koreLogEntries =
@@ -194,7 +195,7 @@ main = do
194195 flip Booster.Log. filterLogger boosterContextLogger $ \ (Booster.Log. LogMessage (Booster. Flag alwaysDisplay) ctxts _) ->
195196 alwaysDisplay
196197 || let ctxt = map (Text. encodeUtf8 . Booster.Log. toTextualLog) ctxts
197- in any (flip Booster.Log.Context . mustMatch ctxt) logContextsWithcustomLevelContexts
198+ in any (flip Ctxt . mustMatch ctxt) logContextsWithcustomLevelContexts
198199
199200 runBoosterLogger :: Booster.Log. LoggerT IO a -> IO a
200201 runBoosterLogger = flip runReaderT filteredBoosterContextLogger . Booster.Log. unLoggerT
@@ -303,7 +304,7 @@ main = do
303304 , mSMTOptions = if boosterSMT then smtOptions else Nothing
304305 , addedModules = mempty
305306 }
306- statsVar <- if printStats then Just <$> Stats. newStats else pure Nothing
307+ statsVar <- Stats. newStats
307308
308309 writeGlobalEquationOptions equationOptions
309310
@@ -343,8 +344,9 @@ main = do
343344 interruptHandler _ =
344345 runBoosterLogger . Booster.Log. withContext CtxProxy $ do
345346 Booster.Log. logMessage' @ _ @ Text " Server shutting down"
346- whenJust statsVar $ \ var ->
347- liftIO (Stats. finaliseStats var) >>= Booster.Log. logMessage'
347+ ( liftIO (Stats. finaliseStats statsVar)
348+ >>= Booster.Log. withContext CtxTiming . Booster.Log. logMessage
349+ )
348350 liftIO exitSuccess
349351 handleJust isInterrupt interruptHandler $ runBoosterLogger server
350352 where
0 commit comments