1+ {-# LANGUAGE NumericUnderscores #-}
12{-# LANGUAGE QuasiQuotes #-}
23{-# LANGUAGE ScopedTypeVariables #-}
4+ {-# LANGUAGE TupleSections #-}
35{-# LANGUAGE TypeOperators #-}
46
57module QuickBench
@@ -9,10 +11,11 @@ module QuickBench
911where
1012
1113-- import Debug.Trace
12- import Control.Exception
14+ import Control.Exception hiding ( handle )
1315import Control.Monad
1416import Data.Char (isSpace )
15- import Data.List
17+ import Data.Functor
18+ import Data.List hiding (group )
1619import Data.List.Split (splitOn )
1720import Data.Maybe
1821import Data.Time.Clock
@@ -29,6 +32,7 @@ import Text.Megaparsec (ParsecT, Stream (Token), between, many, noneOf, runParse
2932import Text.Megaparsec.Char (char )
3033import Text.Show.Pretty
3134import Text.Printf
35+ import Text.Read
3236import Text.Tabular
3337import qualified Text.Tabular.AsciiArt as TA
3438
@@ -58,6 +62,7 @@ Options:
5862 -n, --iterations=N run each command this many times [default: 1]
5963 -N, --cycles=N run the whole suite this many times [default: 1]
6064 -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)
6166 -v, --verbose show the commands being run
6267 -V, --more-verbose show the commands' output
6368 --debug show this program's debug output
@@ -74,6 +79,7 @@ data Opts = Opts {
7479 ,iterations :: Int
7580 ,cycles :: Int
7681 ,precision :: Int
82+ ,maxBytesUsed :: Bool
7783 ,verbose :: Bool
7884 ,moreVerbose :: Bool
7985 ,debug :: Bool
@@ -109,6 +115,7 @@ getOpts = do
109115 ,precision = precision'
110116 ,verbose = flag " verbose"
111117 ,moreVerbose = flag " more-verbose"
118+ ,maxBytesUsed= flag " max-bytes-used"
112119 ,debug = flag " debug"
113120 ,help = flag " help"
114121 ,clicmds = args
@@ -186,14 +193,29 @@ getCurrentZonedTime = do
186193 tz <- getCurrentTimeZone
187194 return $ utcToZonedTime tz t
188195
189- runTestWithExes :: Opts -> [String ] -> String -> IO [[Float ]]
196+ runTestWithExes :: Opts -> [String ] -> String -> IO [[( Float , Maybe Int ) ]]
190197runTestWithExes opts exes cmd = mapM (runTestWithExe opts cmd) exes
191198
192- runTestWithExe :: Opts -> String -> String -> IO [Float ]
199+ runTestWithExe :: Opts -> String -> String -> IO [( Float , Maybe Int ) ]
193200runTestWithExe opts cmd exe = mapM (runTestOnce opts cmd exe) [1 .. iterations opts]
194201
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
197219 let (cmd',exe',args) = replaceExecutable exe cmd
198220 when (not $ null exe) $ dbg opts $ " replaced executable with " <> show exe
199221 outv opts (show iteration ++ " : " ++ cmd' ++ " \n " )
@@ -231,7 +253,7 @@ readProcessWithExitCode' exe args inp =
231253 readProcessWithExitCode exe args inp
232254 `catch` \ (e :: IOException ) -> return (ExitFailure 1 , " " , show e)
233255
234- printSummary :: Opts -> [String ] -> [String ] -> Int -> [[[Float ]]] -> IO ()
256+ printSummary :: Opts -> [String ] -> [String ] -> Int -> [[[( Float , Maybe Int ) ]]] -> IO ()
235257printSummary opts cmds exes cyc results = do
236258 out opts $ printf " \n Best times%s:\n " (if cycles opts > 1 then " " ++ show cyc else " " )
237259 let t = maketable opts cmds' exes results
@@ -246,15 +268,43 @@ printSummary opts cmds exes cyc results = do
246268 [e] -> [c | (c,_,_) <- map (replaceExecutable e) cmds]
247269 _ -> map (unwords . drop 1 . words ) cmds
248270
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+ ]
251284 where
252- rowhdrs = Group NoLine $ map Header $ padright rownames
253- colhdrs = Group SingleLine $ map Header colnames
254- rows = map (map (showtime opts . minimum )) results
255285 padright ss = map (printf (printf " %%-%ds" w)) ss
256286 where w = maximum $ map length ss
257287
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+
258308---------------------------------------
259309-- utils
260310
@@ -278,6 +328,23 @@ dbg opts s = when (debug opts) $ err s
278328showtime :: Opts -> (Float -> String )
279329showtime opts = printf $ " %." ++ show (precision opts) ++ " f"
280330
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+
281348-- Strings
282349
283350-- | Remove leading and trailing whitespace.
0 commit comments