Skip to content

Commit f0b3596

Browse files
authored
Fixes to simplification diff, request statistics, process-logs (#3992)
* Add some context lines to simplification diff * compute request statistics in seconds (and output in seconds in the json format) * Make `process-logs` fail immediately on parse errors, and process lines incrementally (less heap)
1 parent 698c143 commit f0b3596

File tree

4 files changed

+46
-48
lines changed

4 files changed

+46
-48
lines changed

booster/library/Booster/JsonRpc/Utils.hs

+6-3
Original file line numberDiff line numberDiff line change
@@ -224,12 +224,15 @@ methodOfRpcCall = \case
224224
renderDiff :: BS.ByteString -> BS.ByteString -> Maybe String
225225
renderDiff first second
226226
| first == second = Nothing
227-
renderDiff first second = unsafePerformIO . withTempDir $ \dir -> do
227+
| otherwise = renderDiff' ["-w"] first second
228+
229+
renderDiff' :: [String] -> BS.ByteString -> BS.ByteString -> Maybe String
230+
renderDiff' diffOptions first second = unsafePerformIO . withTempDir $ \dir -> do
228231
let path1 = dir </> "diff_file1.txt"
229232
path2 = dir </> "diff_file2.txt"
230233
BS.writeFile path1 first
231234
BS.writeFile path2 second
232-
(result, str, _) <- readProcessWithExitCode "diff" ["-w", path1, path2] ""
235+
(result, str, _) <- readProcessWithExitCode "diff" (diffOptions <> [path1, path2]) ""
233236
case result of
234237
ExitSuccess -> pure Nothing
235238
ExitFailure 1 -> pure $ Just str
@@ -240,7 +243,7 @@ renderDiff first second = unsafePerformIO . withTempDir $ \dir -> do
240243
-- This uses the `pretty` instance for a textual diff.
241244
diffBy :: Internal.KoreDefinition -> KorePattern -> KorePattern -> Maybe String
242245
diffBy def pat1 pat2 =
243-
renderDiff (internalise pat1) (internalise pat2)
246+
renderDiff' ["-c", "-w"] (internalise pat1) (internalise pat2)
244247
where
245248
renderBS :: TermOrPredicates -> BS.ByteString
246249
renderBS (Predicates ps) =

booster/tools/booster/Proxy.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ import Kore.Log qualified
4949
import Kore.Syntax.Definition (SentenceAxiom)
5050
import Kore.Syntax.Json.Types qualified as KoreJson
5151
import SMT qualified
52-
import Stats (MethodTiming (..), StatsVar, addStats, microsWithUnit, timed)
52+
import Stats (MethodTiming (..), StatsVar, addStats, secWithUnit, timed)
5353

5454
data KoreServer = KoreServer
5555
{ serverState :: MVar.MVar Kore.ServerState
@@ -396,7 +396,7 @@ respondEither cfg@ProxyConfig{boosterState} booster kore req = case req of
396396
, koreTime = kTime
397397
}
398398
)
399-
("Kore fall-back in " <> microsWithUnit kTime)
399+
("Kore fall-back in " <> secWithUnit kTime)
400400
case kResult of
401401
Right (Execute koreResult) -> do
402402
let

booster/tools/booster/Stats.hs

+32-32
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ module Stats (
33
addStats,
44
finaliseStats,
55
timed,
6-
microsWithUnit,
6+
secWithUnit,
77
RequestStats (..),
88
StatsVar,
99
MethodTiming (..),
@@ -25,7 +25,7 @@ import Booster.Log
2525
import Booster.Prettyprinter
2626
import Kore.JsonRpc.Types (APIMethod)
2727

28-
-- server statistics
28+
-- | Statistics for duration measurement time series (in seconds)
2929
data RequestStats a = RequestStats
3030
{ count :: Int
3131
, average :: a
@@ -60,31 +60,30 @@ instance (Floating a, PrintfArg a, Ord a) => Pretty (RequestStats a) where
6060
<+> withUnit stats.koreMax
6161
]
6262
where
63-
withUnit = pretty . microsWithUnit
63+
withUnit = pretty . secWithUnit
6464

65-
microsWithUnit :: (Floating a, Ord a, PrintfArg a) => a -> String
66-
microsWithUnit x
67-
| x > 10 ** 5 = printf "%.2fs" $ x / 10 ** 6
68-
| x > 10 ** 2 = printf "%.3fms" $ x / 10 ** 3
69-
| otherwise = printf "%.1fμs" x
65+
secWithUnit :: (Floating a, Ord a, PrintfArg a) => a -> String
66+
secWithUnit x
67+
| x > 0.1 = printf "%.2fs" x
68+
| x > 0.0001 = printf "%.3fms" $ x * 10 ** 3
69+
| otherwise = printf "%.1fμs" $ x * 10 ** 6
7070

7171
-- internal helper type
72-
-- all values are in microseconds
73-
data Stats' a = Stats'
72+
-- all values are in seconds
73+
data Stats' = Stats'
7474
{ count :: Int
75-
, total :: a
76-
, squares :: a
77-
, maxVal :: a
78-
, minVal :: a
79-
, koreTotal :: a
80-
, koreMax :: a
75+
, total :: Double
76+
, squares :: Double
77+
, maxVal :: Double
78+
, minVal :: Double
79+
, koreTotal :: Double
80+
, koreMax :: Double
8181
}
8282

83-
instance (Ord a, Num a) => Semigroup (Stats' a) where
83+
instance Semigroup Stats' where
8484
(<>) = addStats'
8585

86-
{-# SPECIALIZE addStats' :: Stats' Double -> Stats' Double -> Stats' Double #-}
87-
addStats' :: (Ord a, Num a) => Stats' a -> Stats' a -> Stats' a
86+
addStats' :: Stats' -> Stats' -> Stats'
8887
addStats' stats1 stats2 =
8988
Stats'
9089
{ count = stats1.count + stats2.count
@@ -96,7 +95,7 @@ addStats' stats1 stats2 =
9695
, koreMax = max stats1.koreMax stats2.koreMax
9796
}
9897

99-
singleStats' :: Num a => a -> a -> Stats' a
98+
singleStats' :: Double -> Double -> Stats'
10099
singleStats' x korePart =
101100
Stats'
102101
{ count = 1
@@ -108,43 +107,44 @@ singleStats' x korePart =
108107
, koreMax = korePart
109108
}
110109

111-
type StatsVar = MVar (Map APIMethod (Stats' Double))
110+
type StatsVar = MVar (Map APIMethod Stats')
112111

113112
-- helper type mainly for json logging
114-
data MethodTiming a = MethodTiming {method :: APIMethod, time :: a, koreTime :: a}
113+
data MethodTiming = MethodTiming {method :: APIMethod, time :: Double, koreTime :: Double}
115114
deriving stock (Eq, Show, Generic)
116115
deriving
117116
(ToJSON, FromJSON)
118-
via CustomJSON '[FieldLabelModifier '[CamelToKebab]] (MethodTiming a)
117+
via CustomJSON '[FieldLabelModifier '[CamelToKebab]] MethodTiming
119118

120-
instance ToLogFormat (MethodTiming Double) where
119+
instance ToLogFormat MethodTiming where
121120
toTextualLog mt =
122121
pack $
123122
printf
124123
"Performed %s in %s (%s kore time)"
125124
(show mt.method)
126-
(microsWithUnit mt.time)
127-
(microsWithUnit mt.koreTime)
125+
(secWithUnit mt.time)
126+
(secWithUnit mt.koreTime)
128127
toJSONLog = toJSON
129128

130129
addStats ::
131130
MonadIO m =>
132-
MVar (Map APIMethod (Stats' Double)) ->
133-
MethodTiming Double ->
131+
MVar (Map APIMethod Stats') ->
132+
MethodTiming ->
134133
m ()
135134
addStats statVar MethodTiming{method, time, koreTime} =
136135
liftIO . modifyMVar_ statVar $
137136
pure . Map.insertWith (<>) method (singleStats' time koreTime)
138137

139-
newStats :: MonadIO m => m (MVar (Map APIMethod (Stats' Double)))
138+
newStats :: MonadIO m => m (MVar (Map APIMethod Stats'))
140139
newStats = liftIO $ newMVar Map.empty
141140

141+
-- returns time taken by the given action (in seconds)
142142
timed :: MonadIO m => m a -> m (a, Double)
143143
timed action = do
144144
start <- liftIO $ getTime Monotonic
145145
result <- action
146146
stop <- liftIO $ getTime Monotonic
147-
let time = fromIntegral (toNanoSecs (diffTimeSpec stop start)) / 1000.0
147+
let time = fromIntegral (toNanoSecs (diffTimeSpec stop start)) / 10 ** 9
148148
pure (result, time)
149149

150150
newtype FinalStats = FinalStats (Map APIMethod (RequestStats Double))
@@ -164,10 +164,10 @@ instance ToLogFormat FinalStats where
164164
toTextualLog = renderText . pretty
165165
toJSONLog = toJSON
166166

167-
finaliseStats :: MVar (Map APIMethod (Stats' Double)) -> IO FinalStats
167+
finaliseStats :: MVar (Map APIMethod Stats') -> IO FinalStats
168168
finaliseStats var = FinalStats . Map.map finalise <$> readMVar var
169169
where
170-
finalise :: Floating a => Stats' a -> RequestStats a
170+
finalise :: Stats' -> RequestStats Double
171171
finalise Stats'{count, total, squares, maxVal, minVal, koreTotal, koreMax} =
172172
let average = total / fromIntegral count
173173
stddev = sqrt $ squares / fromIntegral count - average * average

dev-tools/process-logs/Main.hs

+6-11
Original file line numberDiff line numberDiff line change
@@ -7,12 +7,10 @@ module Main (
77
main,
88
) where
99

10-
import Control.Monad (unless)
1110
import Data.Aeson qualified as JSON
1211
import Data.Aeson.Encode.Pretty qualified as JSON
1312
import Data.ByteString.Char8 qualified as BSS
1413
import Data.ByteString.Lazy.Char8 qualified as BS
15-
import Data.Either (partitionEithers)
1614
import Data.Foldable (toList)
1715
import Data.List (foldl', maximumBy, sortBy)
1816
import Data.Map (Map)
@@ -24,7 +22,6 @@ import Data.Sequence qualified as Seq
2422
import Data.Time.Clock
2523
import Data.Time.Clock.System (systemToUTCTime)
2624
import Options.Applicative
27-
import System.Exit
2825
import Text.Printf
2926

3027
import Booster.Log.Context (ContextFilter, mustMatch, readContextFilter)
@@ -37,17 +34,15 @@ import Kore.JsonRpc.Types.ContextLog
3734
main :: IO ()
3835
main = do
3936
Options{cmd, input, output} <- execParser parse
40-
(errors, inputJson) <-
41-
partitionEithers
42-
. map JSON.eitherDecode
37+
inputData <-
38+
map JSON.eitherDecode
4339
. BS.lines
4440
<$> maybe BS.getContents BS.readFile input
45-
unless (null errors) $ do
46-
putStrLn "JSON parse errors in log file:"
47-
mapM_ putStrLn errors
48-
exitWith (ExitFailure 1)
4941
let writeOut = maybe BS.putStrLn BS.writeFile output . BS.unlines
50-
writeOut $ process cmd inputJson
42+
writeOut $ process cmd $ stopOnErrors inputData
43+
where
44+
stopOnErrors :: [Either String LogLine] -> [LogLine]
45+
stopOnErrors = map (either (error . ("JSON parse error: " <>)) id)
5146

5247
data Options = Options
5348
{ cmd :: Command

0 commit comments

Comments
 (0)