Morguing dead code
[ghc-hetmet.git] / compiler / cmm / CmmCPSZ.hs
1 module CmmCPSZ (
2   -- | Converts C-- with full proceedures and parameters
3   -- to a CPS transformed C-- with the stack made manifest.
4   -- Well, sort of.
5   protoCmmCPSZ
6 ) where
7
8 import CLabel
9 import Cmm
10 import CmmBuildInfoTables
11 import CmmCommonBlockElimZ
12 import CmmProcPointZ
13 import CmmSpillReload
14 import CmmStackLayout
15 import DFMonad
16 import PprCmmZ()
17 import ZipCfgCmmRep
18
19 import DynFlags
20 import ErrUtils
21 import FiniteMap
22 import HscTypes
23 import Data.Maybe
24 import Control.Monad
25 import Outputable
26 import StaticFlags
27
28 -----------------------------------------------------------------------------
29 -- |Top level driver for the CPS pass
30 -----------------------------------------------------------------------------
31 -- There are two complications here:
32 -- 1. We need to compile the procedures in two stages because we need
33 --    an analysis of the procedures to tell us what CAFs they use.
34 --    The first stage returns a map from procedure labels to CAFs,
35 --    along with a closure that will compute SRTs and attach them to
36 --    the compiled procedures.
37 --    The second stage is to combine the CAF information into a top-level
38 --    CAF environment mapping non-static closures to the CAFs they keep live,
39 --    then pass that environment to the closures returned in the first
40 --    stage of compilation.
41 -- 2. We need to thread the module's SRT around when the SRT tables
42 --    are computed for each procedure.
43 --    The SRT needs to be threaded because it is grown lazily.
44 protoCmmCPSZ :: HscEnv -- Compilation env including
45                        -- dynamic flags: -dcmm-lint -ddump-cps-cmm
46              -> (TopSRT, [CmmZ])  -- SRT table and accumulating list of compiled procs
47              -> CmmZ              -- Input C-- with Procedures
48              -> IO (TopSRT, [CmmZ]) -- Output CPS transformed C--
49 protoCmmCPSZ hsc_env (topSRT, rst) (Cmm tops) =
50   do let dflags = hsc_dflags hsc_env
51      showPass dflags "CPSZ"
52      (cafEnvs, tops) <- liftM unzip $ mapM (cpsTop hsc_env) tops
53      let topCAFEnv = mkTopCAFInfo (concat cafEnvs)
54      (topSRT, tops) <- foldM (toTops hsc_env topCAFEnv) (topSRT, []) tops
55      -- (topSRT, tops) <- foldM (\ z f -> f topCAFEnv z) (topSRT, []) toTops 
56      let cmms = Cmm (reverse (concat tops))
57      dumpIfSet_dyn dflags Opt_D_dump_cps_cmm "Post CPS Cmm" (ppr cmms)
58      return (topSRT, cmms : rst)
59
60 {- [Note global fuel]
61 ~~~~~~~~~~~~~~~~~~~~~
62 The identity and the last pass are stored in
63 mutable reference cells in an 'HscEnv' and are
64 global to one compiler session.
65 -}
66
67 cpsTop :: HscEnv -> CmmTopZ ->
68           IO ([(CLabel, CAFSet)],
69               [(CAFSet, CmmTopForInfoTables)])
70 cpsTop _ p@(CmmData {}) = return ([], [(emptyFM, NoInfoTable p)])
71 cpsTop hsc_env (CmmProc h l args (stackInfo@(entry_off, _), g)) =
72     do 
73        dump Opt_D_dump_cmmz "Pre Proc Points Added"  g
74        let callPPs = callProcPoints g
75        -- Why bother doing it this early?
76        -- g <- dual_rewrite Opt_D_dump_cmmz "spills and reloads"
77        --                       (dualLivenessWithInsertion callPPs) g
78        -- g <- run $ insertLateReloads g -- Duplicate reloads just before uses
79        -- g <- dual_rewrite Opt_D_dump_cmmz "Dead Assignment Elimination"
80        --                   (removeDeadAssignmentsAndReloads callPPs) g
81        dump Opt_D_dump_cmmz "Pre common block elimination" g
82        g <- return $ elimCommonBlocks g
83        dump Opt_D_dump_cmmz "Post common block elimination" g
84
85        ----------- Proc points -------------------
86        procPoints <- run $ minimalProcPointSet callPPs g
87        g <- run $ addProcPointProtocols callPPs procPoints g
88        dump Opt_D_dump_cmmz "Post Proc Points Added" g
89
90        ----------- Spills and reloads -------------------
91        g     <- 
92               -- pprTrace "pre Spills" (ppr g) $
93                 dual_rewrite Opt_D_dump_cmmz "spills and reloads"
94                              (dualLivenessWithInsertion procPoints) g
95                     -- Insert spills at defns; reloads at return points
96        g     <-
97               -- pprTrace "pre insertLateReloads" (ppr g) $
98                 run $ insertLateReloads g -- Duplicate reloads just before uses
99        dump Opt_D_dump_cmmz "Post late reloads" g
100        g     <-
101                -- pprTrace "post insertLateReloads" (ppr g) $
102                 dual_rewrite Opt_D_dump_cmmz "Dead Assignment Elimination"
103                                         (removeDeadAssignmentsAndReloads procPoints) g
104                     -- Remove redundant reloads (and any other redundant asst)
105
106        ----------- Debug only: add code to put zero in dead stack slots----
107        -- Debugging: stubbing slots on death can cause crashes early
108        g <-  
109            -- trace "post dead-assign elim" $
110             if opt_StubDeadValues then run $ stubSlotsOnDeath g else return g
111
112
113        --------------- Stack layout ----------------
114        slotEnv <- run $ liveSlotAnal g
115        mbpprTrace "live slot analysis results: " (ppr slotEnv) $ return ()
116        -- cafEnv <- -- trace "post liveSlotAnal" $ run $ cafAnal g
117        -- (cafEnv, slotEnv) <-
118        --  -- trace "post print cafAnal" $
119        --    return $ extendEnvsForSafeForeignCalls cafEnv slotEnv g
120        slotEnv <- return $ extendEnvWithSafeForeignCalls liveSlotTransfers slotEnv g
121        mbpprTrace "slotEnv extended for safe foreign calls: " (ppr slotEnv) $ return ()
122        let areaMap = layout procPoints slotEnv entry_off g
123        mbpprTrace "areaMap" (ppr areaMap) $ return ()
124
125        ------------  Manifest the the stack pointer --------
126        g  <- run $ manifestSP areaMap entry_off g
127        dump Opt_D_dump_cmmz "after manifestSP" g
128        -- UGH... manifestSP can require updates to the procPointMap.
129        -- We can probably do something quicker here for the update...
130
131        ------------- Split into separate procedures ------------
132        procPointMap  <- run $ procPointAnalysis procPoints g
133        dump Opt_D_dump_cmmz "procpoint map" procPointMap
134        gs <- run $ splitAtProcPoints l callPPs procPoints procPointMap
135                                        (CmmProc h l args (stackInfo, g))
136        mapM_ (dump Opt_D_dump_cmmz "after splitting") gs
137
138        ------------- More CAFs and foreign calls ------------
139        cafEnv <- run $ cafAnal g
140        cafEnv <- return $ extendEnvWithSafeForeignCalls cafTransfers cafEnv  g
141        let localCAFs = catMaybes $ map (localCAFInfo cafEnv) gs
142        mbpprTrace "localCAFs" (ppr localCAFs) $ return ()
143
144        gs <- liftM concat $ run $ foldM lowerSafeForeignCalls [] gs
145        mapM_ (dump Opt_D_dump_cmmz "after lowerSafeForeignCalls") gs
146
147        -- NO MORE GRAPH TRANSFORMATION AFTER HERE -- JUST MAKING INFOTABLES
148        let gs' = map (setInfoTableStackMap slotEnv areaMap) gs
149        mapM_ (dump Opt_D_dump_cmmz "after setInfoTableStackMap") gs'
150        let gs'' = map (bundleCAFs cafEnv) gs'
151        mapM_ (dump Opt_D_dump_cmmz "after bundleCAFs") gs''
152        return (localCAFs, gs'')
153   where dflags = hsc_dflags hsc_env
154         mbpprTrace x y z = if dopt Opt_D_dump_cmmz dflags then pprTrace x y z else z
155         dump f txt g = dumpIfSet_dyn dflags f txt (ppr g)
156         run = runFuelIO (hsc_OptFuel hsc_env)
157         dual_rewrite flag txt pass g =
158           do dump flag ("Pre " ++ txt)  g
159              g <- run $ pass g
160              dump flag ("Post " ++ txt) $ g
161              return g
162
163 -- This probably belongs in CmmBuildInfoTables?
164 -- We're just finishing the job here: once we know what CAFs are defined
165 -- in non-static closures, we can build the SRTs.
166 toTops :: HscEnv -> FiniteMap CLabel CAFSet -> (TopSRT, [[CmmTopZ]])
167                  -> [(CAFSet, CmmTopForInfoTables)] -> IO (TopSRT, [[CmmTopZ]])
168
169 toTops hsc_env topCAFEnv (topSRT, tops) gs =
170   do let setSRT (topSRT, rst) g =
171            do (topSRT, gs) <- setInfoTableSRT topCAFEnv topSRT g
172               return (topSRT, gs : rst)
173      (topSRT, gs') <- runFuelIO (hsc_OptFuel hsc_env) $ foldM setSRT (topSRT, []) gs
174      gs' <- mapM finishInfoTables (concat gs')
175      return (topSRT, concat gs' : tops)