Add generation of PR dictionaries
[ghc-hetmet.git] / compiler / nativeGen / AsmCodeGen.lhs
index 29ffb89..bc63e81 100644 (file)
@@ -19,11 +19,11 @@ import PprMach
 import RegAllocInfo
 import NCGMonad
 import PositionIndependentCode
-import RegAllocLinear
-import RegAllocStats
 import RegLiveness
 import RegCoalesce
+import qualified RegAllocLinear        as Linear
 import qualified RegAllocColor as Color
+import qualified RegAllocStats as Color
 import qualified GraphColor    as Color
 
 import Cmm
@@ -213,7 +213,8 @@ data CmmNativeGenDump
        , cdNative              :: [NatCmmTop]
        , cdLiveness            :: [LiveCmmTop]
        , cdCoalesce            :: Maybe [LiveCmmTop]
-       , cdRegAllocStats       :: Maybe [RegAllocStats]
+       , cdRegAllocStats       :: Maybe [Color.RegAllocStats]
+       , cdRegAllocStatsLinear :: [Linear.RegAllocStats]
        , cdColoredGraph        :: Maybe (Color.Graph Reg RegClass Reg)
        , cdAlloced             :: [NatCmmTop] }
 
@@ -229,6 +230,11 @@ dchooses dflags opts a b
 --     Unless they're being dumped, intermediate data structures are squashed after
 --     every stage to avoid creating space leaks.
 --
+-- TODO: passing data via CmmNativeDump/squashing structs has become a horrible mess.
+--      it might be better to forgo trying to keep all the outputs for each
+--      stage together and just thread IO() through cmmNativeGen so we can dump
+--      what we want to after each stage.
+--
 cmmNativeGen :: DynFlags -> RawCmmTop -> UniqSM (CmmNativeGenDump, Pretty.Doc, [CLabel])
 cmmNativeGen dflags cmm
  = do  
@@ -274,7 +280,8 @@ cmmNativeGen dflags cmm
                native
 
        ---- allocate registers
-       (alloced, ppr_alloced, ppr_coalesce, ppr_regAllocStats, ppr_coloredGraph)
+       (  alloced, ppr_alloced, ppr_coalesce
+        , ppr_regAllocStats, ppr_regAllocStatsLinear, ppr_coloredGraph)
         <- (\withLiveness
         -> {-# SCC "regAlloc" #-}
           do
@@ -298,21 +305,31 @@ cmmNativeGen dflags cmm
                                        coalesced
 
                        return  ( alloced
-                               , dchoose  dflags Opt_D_dump_asm_regalloc       alloced []
-                               , dchoose  dflags Opt_D_dump_asm_coalesce       (Just coalesced)     Nothing
+                               , dchoose  dflags Opt_D_dump_asm_regalloc
+                                       alloced []
+                               , dchoose  dflags Opt_D_dump_asm_coalesce
+                                       (Just coalesced)     Nothing
                                , dchooses dflags
                                        [ Opt_D_dump_asm_regalloc_stages
                                        , Opt_D_drop_asm_stats]
                                        (Just regAllocStats) Nothing
-                               , dchoose  dflags Opt_D_dump_asm_conflicts      Nothing Nothing)
+                               , []
+                               , dchoose  dflags Opt_D_dump_asm_conflicts
+                                       Nothing Nothing)
 
                 else do
                        -- do linear register allocation
-                       alloced <- mapUs regAlloc withLiveness
+                       (alloced, stats)
+                               <- liftM unzip
+                               $ mapUs Linear.regAlloc withLiveness
+
                        return  ( alloced
-                               , dchoose dflags Opt_D_dump_asm_regalloc        alloced []
+                               , dchoose dflags Opt_D_dump_asm_regalloc
+                                       alloced []
                                , Nothing
                                , Nothing
+                               , dchoose dflags Opt_D_drop_asm_stats
+                                       (catMaybes stats) []
                                , Nothing )) 
                withLiveness
                        
@@ -348,6 +365,7 @@ cmmNativeGen dflags cmm
                , cdLiveness            = ppr_withLiveness
                , cdCoalesce            = ppr_coalesce
                , cdRegAllocStats       = ppr_regAllocStats
+               , cdRegAllocStatsLinear = ppr_regAllocStatsLinear
                , cdColoredGraph        = ppr_coloredGraph
                , cdAlloced             = ppr_alloced }
 
@@ -371,51 +389,50 @@ x86fp_kludge top@(CmmProc info lbl params code) =
 cmmNativeGenDump :: DynFlags -> Module -> ModLocation -> [CmmNativeGenDump] -> IO ()
 cmmNativeGenDump dflags mod modLocation dump
  = do
-
        dumpIfSet_dyn dflags
                Opt_D_dump_opt_cmm "Optimised Cmm"
                (pprCmm $ Cmm $ map cdCmmOpt dump)
 
        dumpIfSet_dyn dflags
-               Opt_D_dump_asm_native   "(asm-native) Native code"
+               Opt_D_dump_asm_native   "Native code"
                (vcat $ map (docToSDoc . pprNatCmmTop)  $ concatMap cdNative dump)
 
        dumpIfSet_dyn dflags
-               Opt_D_dump_asm_liveness "(asm-liveness) Liveness info added"
+               Opt_D_dump_asm_liveness "Liveness annotations added"
                (vcat $ map (ppr . cdLiveness) dump)
 
        dumpIfSet_dyn dflags
-               Opt_D_dump_asm_coalesce "(asm-coalesce) Register moves coalesced."
-               (vcat $ map (ppr . (\(Just c) -> c) . cdCoalesce) dump)
+               Opt_D_dump_asm_coalesce "Reg-Reg moves coalesced"
+               (vcat $ map (fromMaybe empty . liftM ppr . cdCoalesce) dump)
 
        dumpIfSet_dyn dflags
-               Opt_D_dump_asm_regalloc "(asm-regalloc) Registers allocated"
+               Opt_D_dump_asm_regalloc "Registers allocated"
                (vcat $ map (docToSDoc . pprNatCmmTop) $ concatMap cdAlloced dump)
 
        -- with the graph coloring allocator, show the result of each build/spill stage
        --        for each block in turn.
-       mapM_ (\codeGraphs
-        -> dumpIfSet_dyn dflags
-               Opt_D_dump_asm_regalloc_stages "(asm-regalloc-stages)"
-               (vcat $ map (\(stage, stats) ->
-                                text "-- Stage " <> int stage
-                                $$ ppr stats)
-                               (zip [0..] codeGraphs)))
-        $ map ((\(Just c) -> c) . cdRegAllocStats) dump
-
+       when (dopt Opt_D_dump_asm_regalloc_stages dflags)
+        $ do   mapM_ (\stats
+                        -> printDump
+                        $  vcat $ map (\(stage, stats) ->
+                                        text "-- Stage " <> int stage
+                                        $$ ppr stats)
+                                       (zip [0..] stats))
+                $ map (fromMaybe [] . cdRegAllocStats) dump
 
        -- Build a global register conflict graph.
        --      If you want to see the graph for just one basic block then use asm-regalloc-stages instead.
        dumpIfSet_dyn dflags
-               Opt_D_dump_asm_conflicts "(asm-conflicts) Register conflict graph"
+               Opt_D_dump_asm_conflicts "Register conflict graph"
                $ Color.dotGraph Color.regDotColor trivColorable
                $ foldl Color.union Color.initGraph
                $ catMaybes $ map cdColoredGraph dump
 
-
-       -- Drop native code gen statistics.
-       --      This is potentially a large amount of information, so we make a new file instead
-       --      of dumping it to stdout.
+       -- Drop native code generator statistics.
+       --      This is potentially a large amount of information, and we want to be able
+       --      to collect it while running nofib. Drop a new file instead of emitting
+       --      it to stdout/stderr.
+       --
        when (dopt Opt_D_drop_asm_stats dflags)
         $ do   -- make the drop file name based on the object file name
                let dropFile    = (init $ ml_obj_file modLocation) ++ "drop-asm-stats"
@@ -424,19 +441,17 @@ cmmNativeGenDump dflags mod modLocation dump
                let stats       = concat $ catMaybes $ map cdRegAllocStats dump
 
                -- build a global conflict graph
-               let graph       = foldl Color.union Color.initGraph $ map raGraph stats
+               let graph       = foldl Color.union Color.initGraph $ map Color.raGraph stats
 
                -- pretty print the various sections and write out the file.
-               let outSpills   = pprStatsSpills    stats
-               let outLife     = pprStatsLifetimes stats
-               let outConflict = pprStatsConflict  stats
-               let outScatter  = pprStatsLifeConflict stats graph
+               let outSpills   = Color.pprStatsSpills    stats
+               let outLife     = Color.pprStatsLifetimes stats
+               let outConflict = Color.pprStatsConflict  stats
+               let outScatter  = Color.pprStatsLifeConflict stats graph
 
                writeFile dropFile
                        (showSDoc $ vcat [outSpills, outLife, outConflict, outScatter])
 
-               return ()
-
        return ()
 
 -- -----------------------------------------------------------------------------