1
+ {-# LANGUAGE NumericUnderscores #-}
1
2
{-# LANGUAGE QuasiQuotes #-}
2
3
{-# LANGUAGE ScopedTypeVariables #-}
4
+ {-# LANGUAGE TupleSections #-}
3
5
{-# LANGUAGE TypeOperators #-}
4
6
5
7
module QuickBench
@@ -9,10 +11,11 @@ module QuickBench
9
11
where
10
12
11
13
-- import Debug.Trace
12
- import Control.Exception
14
+ import Control.Exception hiding ( handle )
13
15
import Control.Monad
14
16
import Data.Char (isSpace )
15
- import Data.List
17
+ import Data.Functor
18
+ import Data.List hiding (group )
16
19
import Data.List.Split (splitOn )
17
20
import Data.Maybe
18
21
import Data.Time.Clock
@@ -29,6 +32,7 @@ import Text.Megaparsec (ParsecT, Stream (Token), between, many, noneOf, runParse
29
32
import Text.Megaparsec.Char (char )
30
33
import Text.Show.Pretty
31
34
import Text.Printf
35
+ import Text.Read
32
36
import Text.Tabular
33
37
import qualified Text.Tabular.AsciiArt as TA
34
38
@@ -58,6 +62,7 @@ Options:
58
62
-n, --iterations=N run each command this many times [default: 1]
59
63
-N, --cycles=N run the whole suite this many times [default: 1]
60
64
-p, --precision=N show times with this many decimal places [default: 2]
65
+ -m, --max-bytes-used measure max residency (Haskell programs compiled with `-rtsopts` only)
61
66
-v, --verbose show the commands being run
62
67
-V, --more-verbose show the commands' output
63
68
--debug show this program's debug output
@@ -74,6 +79,7 @@ data Opts = Opts {
74
79
,iterations :: Int
75
80
,cycles :: Int
76
81
,precision :: Int
82
+ ,maxBytesUsed :: Bool
77
83
,verbose :: Bool
78
84
,moreVerbose :: Bool
79
85
,debug :: Bool
@@ -109,6 +115,7 @@ getOpts = do
109
115
,precision = precision'
110
116
,verbose = flag " verbose"
111
117
,moreVerbose = flag " more-verbose"
118
+ ,maxBytesUsed= flag " max-bytes-used"
112
119
,debug = flag " debug"
113
120
,help = flag " help"
114
121
,clicmds = args
@@ -186,14 +193,29 @@ getCurrentZonedTime = do
186
193
tz <- getCurrentTimeZone
187
194
return $ utcToZonedTime tz t
188
195
189
- runTestWithExes :: Opts -> [String ] -> String -> IO [[Float ]]
196
+ runTestWithExes :: Opts -> [String ] -> String -> IO [[( Float , Maybe Int ) ]]
190
197
runTestWithExes opts exes cmd = mapM (runTestWithExe opts cmd) exes
191
198
192
- runTestWithExe :: Opts -> String -> String -> IO [Float ]
199
+ runTestWithExe :: Opts -> String -> String -> IO [( Float , Maybe Int ) ]
193
200
runTestWithExe opts cmd exe = mapM (runTestOnce opts cmd exe) [1 .. iterations opts]
194
201
195
- runTestOnce :: Opts -> String -> String -> Int -> IO Float
196
- runTestOnce opts cmd exe iteration = do
202
+ runTestOnce :: Opts -> String -> String -> Int -> IO (Float , Maybe Int )
203
+ runTestOnce opts cmd exe iteration = if maxBytesUsed opts
204
+ then runTimeAndResidencyTest opts cmd exe iteration
205
+ else runTimeTest opts cmd exe iteration <&> (,Nothing )
206
+
207
+ runTimeAndResidencyTest :: Opts -> String -> String -> Int -> IO (Float , Maybe Int )
208
+ runTimeAndResidencyTest opts cmd exe iteration = withTempFile $ \ name handle -> do
209
+ t <- runTimeTest opts (cmd ++ " +RTS --machine-readable -t" ++ name) exe iteration
210
+ _ <- hGetLine handle -- skip first line
211
+ stats <- hGetContents' handle
212
+ return (t, readMaybe stats >>= findMaxBytesUsed)
213
+ where
214
+ findMaxBytesUsed :: [(String , String )] -> Maybe Int
215
+ findMaxBytesUsed pairs = find ((== " max_bytes_used" ) . fst ) pairs >>= readMaybe . snd
216
+
217
+ runTimeTest :: Opts -> String -> String -> Int -> IO Float
218
+ runTimeTest opts cmd exe iteration = do
197
219
let (cmd',exe',args) = replaceExecutable exe cmd
198
220
when (not $ null exe) $ dbg opts $ " replaced executable with " <> show exe
199
221
outv opts (show iteration ++ " : " ++ cmd' ++ " \n " )
@@ -231,7 +253,7 @@ readProcessWithExitCode' exe args inp =
231
253
readProcessWithExitCode exe args inp
232
254
`catch` \ (e :: IOException ) -> return (ExitFailure 1 , " " , show e)
233
255
234
- printSummary :: Opts -> [String ] -> [String ] -> Int -> [[[Float ]]] -> IO ()
256
+ printSummary :: Opts -> [String ] -> [String ] -> Int -> [[[( Float , Maybe Int ) ]]] -> IO ()
235
257
printSummary opts cmds exes cyc results = do
236
258
out opts $ printf " \n Best times%s:\n " (if cycles opts > 1 then " " ++ show cyc else " " )
237
259
let t = maketable opts cmds' exes results
@@ -246,15 +268,43 @@ printSummary opts cmds exes cyc results = do
246
268
[e] -> [c | (c,_,_) <- map (replaceExecutable e) cmds]
247
269
_ -> map (unwords . drop 1 . words ) cmds
248
270
249
- maketable :: Opts -> [String ] -> [String ] -> [[[Float ]]] -> Table String String String
250
- maketable opts rownames colnames results = Table rowhdrs colhdrs rows
271
+ maketable :: Opts -> [String ] -> [String ] -> [[[(Float , Maybe Int )]]] -> Table String String String
272
+ maketable opts rownames colnames results = Table rowhdrs grouphdrs (firstrow: rows)
273
+ where
274
+ rowhdrs = makeRowHeaders rownames
275
+ grouphdrs = makeGroupHeaders opts colnames
276
+ firstrow = colnames ++ colnames
277
+ rows = map (makeRow opts) results
278
+
279
+ makeRowHeaders :: [String ] -> Header String
280
+ makeRowHeaders rownames = Group DoubleLine [
281
+ Group NoLine [Header " " ],
282
+ Group NoLine $ map Header $ padright rownames
283
+ ]
251
284
where
252
- rowhdrs = Group NoLine $ map Header $ padright rownames
253
- colhdrs = Group SingleLine $ map Header colnames
254
- rows = map (map (showtime opts . minimum )) results
255
285
padright ss = map (printf (printf " %%-%ds" w)) ss
256
286
where w = maximum $ map length ss
257
287
288
+ {-
289
+ makeColumnHeaders :: Opts -> [String] -> Header String
290
+ makeColumnHeaders opts colnames =
291
+ Group DoubleLine . replicate (if maxBytesUsed opts then 2 else 1) . Group SingleLine $ map Header colnames
292
+ -}
293
+
294
+ -- Workaround for https://github.com/bgamari/tabular/issues/4
295
+ makeGroupHeaders :: Opts -> [String ] -> Header String
296
+ makeGroupHeaders opts colnames =
297
+ Group DoubleLine $ map (Group NoLine . headers) groups
298
+ where
299
+ groups = if maxBytesUsed opts then [" Time (s)" , " Max bytes used" ] else [" Time (s)" ]
300
+ headers group = take (length colnames) . map Header $ group: repeat " "
301
+
302
+ makeRow :: Opts -> [[(Float , Maybe Int )]] -> [String ]
303
+ makeRow opts results = if maxBytesUsed opts then times ++ bytes else times
304
+ where
305
+ times = map (showtime opts . minimum . map fst ) results
306
+ bytes = map (showbytes opts . minimum . map (fromMaybe 0 . snd )) results
307
+
258
308
---------------------------------------
259
309
-- utils
260
310
@@ -278,6 +328,23 @@ dbg opts s = when (debug opts) $ err s
278
328
showtime :: Opts -> (Float -> String )
279
329
showtime opts = printf $ " %." ++ show (precision opts) ++ " f"
280
330
331
+ showbytes :: Opts -> Int -> String
332
+ showbytes opts n
333
+ | abs n >= 1000_000_000 = printf (" %." ++ show (precision opts) ++ " fG" ) (fromIntegral n / 1000_0000_0000 :: Double )
334
+ | abs n >= 1000_000 = printf (" %." ++ show (precision opts) ++ " fM" ) (fromIntegral n / 1000_0000 :: Double )
335
+ | abs n >= 1000 = printf (" %." ++ show (precision opts) ++ " fK" ) (fromIntegral n / 1000 :: Double )
336
+ | otherwise = show n
337
+
338
+ withTempFile :: (FilePath -> Handle -> IO a ) -> IO a
339
+ withTempFile action = do
340
+ tmp_dir <- getTemporaryDirectory >>= canonicalizePath
341
+ bracket
342
+ (openTempFile tmp_dir " quickbench-" )
343
+ (\ (name, handle) -> hClose handle >> ignoringIOErrors (removeFile name))
344
+ (uncurry action)
345
+ where
346
+ ignoringIOErrors = void . (try :: IO a -> IO (Either IOException a ))
347
+
281
348
-- Strings
282
349
283
350
-- | Remove leading and trailing whitespace.
0 commit comments