[commit: nofib] master: Allow per module stats to be listed as columns in the summary table. (a82ea5f)

git at git.haskell.org git at git.haskell.org
Fri Oct 23 09:47:46 UTC 2015


Repository : ssh://git@git.haskell.org/nofib

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/a82ea5f29607275b56bc03fc1747734af1cae575/nofib

>---------------------------------------------------------------

commit a82ea5f29607275b56bc03fc1747734af1cae575
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Fri Oct 23 11:49:05 2015 +0200

    Allow per module stats to be listed as columns in the summary table.


>---------------------------------------------------------------

a82ea5f29607275b56bc03fc1747734af1cae575
 nofib-analyse/Main.hs | 25 +++++++++++++++++++------
 1 file changed, 19 insertions(+), 6 deletions(-)

diff --git a/nofib-analyse/Main.hs b/nofib-analyse/Main.hs
index 6200a77..f5019b8 100644
--- a/nofib-analyse/Main.hs
+++ b/nofib-analyse/Main.hs
@@ -105,6 +105,18 @@ data PerModuleTableSpec =
                 (Results -> Map String a)       -- get the module map
                 (a -> Bool)             -- Result within reasonable limits?
 
+aggregateModuleTable :: PerModuleTableSpec -> PerProgTableSpec
+aggregateModuleTable (SpecM long_name short_name html_tag get_results is_ok)
+ = SpecP long_name short_name html_tag (mapToMaybe . get_results) (const Success) is_ok
+  where
+    mapToMaybe m = if Map.null m then Nothing else Just (sumResult (Map.elems m))
+
+progTableHasName :: PerProgTableSpec -> String -> Bool
+progTableHasName (SpecP ln sn _ _ _ _) n = n == ln || n == sn
+
+modTableHasName :: PerModuleTableSpec -> String -> Bool
+modTableHasName (SpecM ln sn _ _ _) n = n == ln || n == sn
+
 -- The various per-program aspects of execution that we can generate results for.
 size_spec, alloc_spec, runtime_spec, elapsedtime_spec, muttime_spec, mutetime_spec,
     gctime_spec, gcelap_spec,
@@ -161,8 +173,9 @@ all_specs = [
 namedColumns :: [String] -> IO [PerProgTableSpec]
 namedColumns ss = mapM findSpec ss
   where findSpec s =
-           case [ spec | spec@(SpecP _ short_name _ _ _ _) <- all_specs,
-                         short_name == s ] of
+           case filter (`progTableHasName` s) all_specs ++
+                map aggregateModuleTable (filter (`modTableHasName` s) per_module_result_tab)
+           of
                 [] -> die ("unknown column: " ++ s)
                 (spec:_) -> return spec
 
@@ -250,10 +263,10 @@ latexOutput :: [ResultTable] -> Maybe String -> [String] -> [PerProgTableSpec]
 latexOutput results (Just table_name) _ _ _ norm inc_baseline
   = case
         [ latexProgTable results spec norm inc_baseline "\n"
-        | spec@(SpecP ln sn _ _ _ _) <- per_prog_result_tab, table_name `elem` [ln, sn]]
+        | spec <- per_prog_result_tab, spec `progTableHasName` table_name]
         ++
         [ latexModTable results spec norm inc_baseline "\n"
-        | spec@(SpecM ln sn _ _ _) <- per_module_result_tab, table_name `elem` [ln, sn]]
+        | spec <- per_module_result_tab, spec `modTableHasName` table_name]
     of
         [] -> error ("can't find table named: " ++ table_name)
         (r:_) -> r
@@ -543,10 +556,10 @@ csvTable :: [ResultTable] -> String -> Normalise -> Bool -> String
 csvTable results table_name norm stddev
   = case
         [ csvProgTable results spec norm stddev "\n"
-        | spec@(SpecP ln sn _ _ _ _) <- per_prog_result_tab, table_name `elem` [ln, sn]]
+        | spec <- per_prog_result_tab, spec `progTableHasName` table_name]
         ++
         [ csvModTable results spec norm stddev "\n"
-        | spec@(SpecM ln sn _ _ _) <- per_module_result_tab, table_name `elem` [ln, sn]]
+        | spec <- per_module_result_tab, spec `modTableHasName` table_name]
     of
         [] -> error ("can't find table named: " ++ table_name)
         (r:_) -> r



More information about the ghc-commits mailing list