1- {-# LANGUAGE  ScopedTypeVariables, QuasiQuotes #-}
1+ {-# LANGUAGE  ScopedTypeVariables, QuasiQuotes, TupleSections, NumericUnderscores  #-}
22
33module  QuickBench  (
44  defaultMain 
55)
66where 
77
8- import  Control.Exception 
8+ import  Control.Exception   hiding  ( handle ) 
99import  Control.Monad 
10- import  Data.List 
10+ import  Data.Functor 
11+ import  Data.List  hiding  (group )
1112import  Data.List.Split  (splitOn )
1213import  Data.Maybe 
1314import  Data.Time.Clock 
@@ -22,6 +23,7 @@ import System.IO
2223import  System.Process 
2324import  Text.Show.Pretty 
2425import  Text.Printf 
26+ import  Text.Read 
2527import  Text.Tabular 
2628import  qualified  Text.Tabular.AsciiArt  as  TA 
2729
@@ -45,6 +47,7 @@ Options:
4547  -n, --iterations=N    run each test this many times [default: 1]
4648  -N, --cycles=N        run the whole suite this many times [default: 1]
4749  -p, --precision=N     show times with this many decimal places [default: 2]
50+   -m, --max-bytes-used  measure max residency (Haskell programs compiled with `-rtsopts` only)
4851  -v, --verbose         show commands being run
4952  -V, --more-verbose    show command output
5053      --debug           show debug output for this program
@@ -67,6 +70,7 @@ data Opts = Opts {
6770  ,iterations   ::  Int 
6871  ,cycles       ::  Int 
6972  ,precision    ::  Int 
73+   ,maxBytesUsed ::  Bool 
7074  ,verbose      ::  Bool 
7175  ,moreVerbose  ::  Bool 
7276  ,debug        ::  Bool 
@@ -97,6 +101,7 @@ getOpts = do
97101      ,precision   =  precision'
98102      ,verbose     =  flag " verbose" 
99103      ,moreVerbose =  flag " more-verbose" 
104+       ,maxBytesUsed=  flag " max-bytes-used" 
100105      ,debug       =  flag " debug" 
101106      ,help        =  flag " help" 
102107      ,clicmds     =  args
@@ -170,14 +175,29 @@ getCurrentZonedTime = do
170175  tz <-  getCurrentTimeZone
171176  return  $  utcToZonedTime tz t
172177
173- runTestWithExes  ::  Opts  ->  [String ->  String ->  IO Float 
178+ runTestWithExes  ::  Opts  ->  [String ->  String ->  IO ( Float ,  Maybe   Int ) ]]
174179runTestWithExes opts exes cmd =  mapM  (runTestWithExe opts cmd) exes
175180
176- runTestWithExe  ::  Opts  ->  String ->  String ->  IO Float 
181+ runTestWithExe  ::  Opts  ->  String ->  String ->  IO ( Float ,  Maybe   Int ) ]
177182runTestWithExe opts cmd exe =  mapM  (runTestOnce opts cmd exe) [1 .. iterations opts]
178183
179- runTestOnce  ::  Opts  ->  String ->  String ->  Int ->  IO Float 
180- runTestOnce opts cmd exe iteration =  do 
184+ runTestOnce  ::  Opts  ->  String ->  String ->  Int ->  IO Float Maybe Int 
185+ runTestOnce opts cmd exe iteration =  if  maxBytesUsed opts
186+   then  runTimeAndResidencyTest opts cmd exe iteration
187+   else  runTimeTest opts cmd exe iteration <&>  (,Nothing )
188+ 
189+ runTimeAndResidencyTest  ::  Opts  ->  String ->  String ->  Int ->  IO Float Maybe Int 
190+ runTimeAndResidencyTest opts cmd exe iteration =  withTempFile $  \ name handle ->  do 
191+   t <-  runTimeTest opts (cmd ++  "  +RTS --machine-readable -t" ++  name) exe iteration
192+   _ <-  hGetLine handle --  skip first line
193+   stats <-  hGetContents' handle
194+   return  (t, readMaybe stats >>=  findMaxBytesUsed)
195+  where 
196+   findMaxBytesUsed  ::  [(String String ->  Maybe Int 
197+   findMaxBytesUsed pairs =  find ((==  " max_bytes_used" .  fst ) pairs >>=  readMaybe .  snd 
198+ 
199+ runTimeTest  ::  Opts  ->  String ->  String ->  Int ->  IO Float 
200+ runTimeTest opts cmd exe iteration =  do 
181201  let  (cmd',exe',args) =  replaceExecutable exe cmd
182202  dbg opts $  printf " replaceExecutable: %s -> %s\n " show  (cmd,exe)) (show  (cmd',exe',args))
183203  outv opts (show  iteration ++  " : " ++  cmd' ++  " \n " 
@@ -210,7 +230,7 @@ readProcessWithExitCode' exe args inp =
210230  readProcessWithExitCode exe args inp
211231    `catch`  \ (e ::  IOException ) ->  return  (ExitFailure  1 , " " show  e)
212232
213- printSummary  ::  Opts  ->  [String ->  [String ->  Int ->  [[[Float ->  IO () 
233+ printSummary  ::  Opts  ->  [String ->  [String ->  Int ->  [[[( Float ,  Maybe   Int ) ]]] ->  IO () 
214234printSummary opts cmds exes cyc results =  do 
215235  out opts $  printf " \n Best times%s:\n " if  cycles opts >  1  then  "  " ++ show  cyc else  " " 
216236  let  t =  maketable opts cmds' exes results
@@ -225,18 +245,63 @@ printSummary opts cmds exes cyc results = do
225245        [e] ->  [c |  (c,_,_) <-  map  (replaceExecutable e) cmds]
226246        _   ->  map  (unwords  .  drop  1  .  words ) cmds
227247
228- maketable  ::  Opts  ->  [String ->  [String ->  [[[Float ->  Table  String String String 
229- maketable opts rownames colnames results =  Table  rowhdrs colhdrs rows
248+ maketable  ::  Opts  ->  [String ->  [String ->  [[[(Float Maybe Int ->  Table  String String String 
249+ maketable opts rownames colnames results =  Table  rowhdrs grouphdrs (firstrow: rows)
250+  where 
251+   rowhdrs =  makeRowHeaders rownames
252+   grouphdrs =  makeGroupHeaders opts colnames
253+   firstrow =  colnames ++  colnames
254+   rows =  map  (makeRow opts) results
255+ 
256+ makeRowHeaders  ::  [String ->  Header  String 
257+ makeRowHeaders rownames =  Group  DoubleLine  [
258+    Group  NoLine  [Header  " " 
259+    Group  NoLine  $  map  Header  $  padright rownames
260+  ]
230261 where 
231-   rowhdrs =  Group  NoLine  $  map  Header  $  padright rownames
232-   colhdrs =  Group  SingleLine  $  map  Header  colnames
233-   rows =  map  (map  (showtime opts .  minimum )) results
234262  padright ss =  map  (printf (printf " %%-%ds" 
235263      where  w =  maximum  $  map  length  ss
236264
265+ {- 
266+ makeColumnHeaders :: Opts -> [String] -> Header String 
267+ makeColumnHeaders opts colnames = 
268+   Group DoubleLine . replicate (if maxBytesUsed opts then 2 else 1) . Group SingleLine $ map Header colnames 
269+ -} 
270+ 
271+ --  Workaround for https://github.com/bgamari/tabular/issues/4
272+ makeGroupHeaders  ::  Opts  ->  [String ->  Header  String 
273+ makeGroupHeaders opts colnames = 
274+   Group  DoubleLine  $  map  (Group  NoLine  .  headers) groups
275+  where 
276+   groups =  if  maxBytesUsed opts then  [" Time (s)" " Max bytes used" else  [" Time (s)" 
277+   headers group =  take  (length  colnames) .  map  Header  $  group: repeat  " " 
278+ 
279+ makeRow  ::  Opts  ->  [[(Float Maybe Int ->  [String 
280+ makeRow opts results =  if  maxBytesUsed opts then  times ++  bytes else  times
281+  where 
282+   times =  map  (showtime opts .  minimum  .  map  fst ) results
283+   bytes =  map  (showbytes opts .  minimum  .  map  (fromMaybe 0  .  snd )) results
284+ 
237285showtime  ::  Opts  ->  (Float ->  String 
238286showtime opts =  printf $  " %." ++  show  (precision opts) ++  " f" 
239287
288+ showbytes  ::  Opts  ->  Int ->  String 
289+ showbytes opts n
290+   |  abs  n >=  1000_000_000  =  printf (" %." ++  show  (precision opts) ++  " fG" fromIntegral  n /  1000_1000_1000  ::  Double 
291+   |  abs  n >=  1000_000  =  printf (" %." ++  show  (precision opts) ++  " fM" fromIntegral  n /  1000_1000  ::  Double 
292+   |  abs  n >=  1000  =  printf (" %." ++  show  (precision opts) ++  " fK" fromIntegral  n /  1000  ::  Double 
293+   |  otherwise        =  show  n
294+ 
295+ withTempFile  ::  (FilePath ->  Handle  ->  IO a ) ->  IO a 
296+ withTempFile action =  do 
297+   tmp_dir <-  getTemporaryDirectory >>=  canonicalizePath
298+   bracket
299+     (openTempFile tmp_dir " quickbench-" 
300+     (\ (name, handle) ->  hClose handle >>  ignoringIOErrors (removeFile name))
301+     (uncurry  action)
302+  where 
303+   ignoringIOErrors =  void .  (try ::  IO a  ->  IO Either IOException  a ))
304+ 
240305istest  ::  String ->  Bool 
241306istest s =  not  (null  s' ||  (" #" `isPrefixOf`  s')) where  s' =  clean s
242307
0 commit comments