2 ( DataflowLattice(..) , DataflowAnalysis
3 , markFactsUnchanged, factsStatus, getFact, setFact, getExitFact, setExitFact
4 , forgetFact, botFact, setAllFacts, getAllFacts, factsEnv
5 , addLastOutFact, bareLastOutFacts, forgetLastOutFacts, checkFactMatch
8 , DFM, runDFM, liftToDFM
9 , markGraphRewritten, graphWasRewritten
10 , module OptimizationFuel
17 import OptimizationFuel
25 A dataflow monad maintains a mapping from BlockIds to dataflow facts,
26 where a dataflow fact is a value of type [[a]]. Values of type [[a]]
27 must form a lattice, as described by type [[Fact a]].
29 The dataflow engine uses the lattice structure to compute a least
30 solution to a set of dataflow equations. To compute a greatest
31 solution, flip the lattice over.
33 The engine works by starting at the bottom and iterating to a fixed
34 point, so in principle we require the bottom element, a join (least
35 upper bound) operation, and a comparison to find out if a value has
36 changed (grown). In practice, the comparison is only ever used in
37 conjunction with the join, so we have [[fact_add_to]]:
40 let j = join new old in
41 if j <= old then noTx old -- nothing changed
42 else aTx j -- the fact changed
46 data DataflowLattice a = DataflowLattice {
47 fact_name :: String, -- documentation
48 fact_bot :: a, -- lattice bottom element
49 fact_add_to :: a -> a -> TxRes a, -- lattice join and compare
50 -- ^ compute join of two args; something changed iff join is greater than 2nd arg
51 fact_do_logging :: Bool -- log changes
55 -- DFM is the monad of combined analysis and transformation,
56 -- which needs a UniqSupply and may consume optimization fuel
57 -- DFM is defined using a monad transformer, DFM', which is the general
58 -- case of DFM, parameterized over any monad.
59 -- In practice, we apply DFM' to the FuelMonad, which provides optimization fuel and
61 data DFState f = DFState { df_rewritten :: !ChangeFlag
62 , df_facts :: !(BlockEnv f)
64 , df_last_outs :: ![(BlockId, f)]
65 , df_facts_change :: !ChangeFlag
68 newtype DFM' m fact a = DFM' (DataflowLattice fact -> DFState fact
69 -> m (a, DFState fact))
70 type DFM fact a = DFM' FuelMonad fact a
73 runDFM :: Monad m => DataflowLattice f -> DFM' m f a -> m a
74 runDFM lattice (DFM' f) =
75 (f lattice $ DFState NoChange emptyBlockEnv (fact_bot lattice) [] NoChange)
78 class DataflowAnalysis m where
79 markFactsUnchanged :: m f () -- ^ Useful for starting a new iteration
80 factsStatus :: m f ChangeFlag
81 subAnalysis :: m f a -> m f a -- ^ Do a new analysis and then throw away
82 -- /all/ the related state.
84 getFact :: BlockId -> m f f
85 setFact :: Outputable f => BlockId -> f -> m f ()
87 setExitFact :: Outputable f => f -> m f ()
88 checkFactMatch :: Outputable f =>
89 BlockId -> f -> m f () -- ^ assert fact already at this val
91 forgetFact :: BlockId -> m f ()
92 -- | It might be surprising these next two are needed in a pure analysis,
93 -- but for some problems we do a 'shallow' rewriting in which a rewritten
94 -- graph is not itself considered for further rewriting but merely undergoes
95 -- an analysis. In this case the results of a forward analysis might produce
96 -- new facts that go on BlockId's that reside outside the graph being analyzed.
97 -- Thus these 'lastOutFacts' need to be available even in a pure analysis.
98 addLastOutFact :: (BlockId, f) -> m f ()
99 bareLastOutFacts :: m f [(BlockId, f)]
100 forgetLastOutFacts :: m f ()
101 getAllFacts :: m f (BlockEnv f)
102 setAllFacts :: BlockEnv f -> m f ()
103 factsEnv :: Monad (m f) => m f (BlockId -> f)
105 lattice :: m f (DataflowLattice f)
106 factsEnv = do { map <- getAllFacts
108 ; return $ \id -> lookupBlockEnv map id `orElse` bot }
110 instance Monad m => DataflowAnalysis (DFM' m) where
111 markFactsUnchanged = DFM' f
112 where f _ s = return ((), s {df_facts_change = NoChange})
113 factsStatus = DFM' f'
114 where f' _ s = return (df_facts_change s, s)
115 subAnalysis (DFM' f) = DFM' f'
116 where f' l s = do (a, _) <- f l (subAnalysisState s)
118 getFact id = DFM' get
119 where get lattice s =
120 return (lookupBlockEnv (df_facts s) id `orElse` fact_bot lattice, s)
121 setFact id a = DFM' set
122 where set (DataflowLattice name bot add_fact log) s =
123 case add_fact a old of
124 TxRes NoChange _ -> if initialized then return ((), s) else update old old
125 TxRes SomeChange join -> update join old
126 where (old, initialized) =
127 case lookupBlockEnv (df_facts s) id of
129 Nothing -> (bot, False)
131 let facts' = extendBlockEnv (df_facts s) id join
132 debug = if log then pprTrace else \_ _ a -> a
133 in debug name (pprSetFact id old a join) $
134 return ((), s { df_facts = facts', df_facts_change = SomeChange })
135 getExitFact = DFM' get
136 where get _ s = return (df_exit_fact s, s)
138 do DataflowLattice { fact_name = name, fact_do_logging = log} <- lattice
140 let debug = if log then pprTrace else \_ _ a -> a
141 in debug name (pprSetFact "exit" a a a) $
142 return ((), s { df_exit_fact = a })
144 where f _ s = return (df_facts s, s)
145 setAllFacts env = DFM' f
146 where f _ s = return ((), s { df_facts = env})
148 where f lattice s = return (fact_bot lattice, s)
149 forgetFact id = DFM' f
150 where f _ s = return ((), s { df_facts = delFromBlockEnv (df_facts s) id })
151 addLastOutFact pair = DFM' f
152 where f _ s = return ((), s { df_last_outs = pair : df_last_outs s })
153 bareLastOutFacts = DFM' f
154 where f _ s = return (df_last_outs s, s)
155 forgetLastOutFacts = DFM' f
156 where f _ s = return ((), s { df_last_outs = [] })
157 checkFactMatch id a =
159 ; old_a <- getFact id
160 ; case fact_add_to fact a old_a of
161 TxRes NoChange _ -> return ()
162 TxRes SomeChange new ->
163 do { facts <- getAllFacts
164 ; pprPanic "checkFactMatch"
165 (f4sep [text (fact_name fact), text "at id" <+> ppr id,
166 text "changed from", nest 4 (ppr old_a), text "to",
168 text "after supposedly reaching fixed point;",
169 text "env is", pprFacts facts]) }
171 where pprFacts env = vcat (map pprFact (blockEnvToList env))
172 pprFact (id, a) = hang (ppr id <> colon) 4 (ppr a)
175 where f l s = return (l, s)
177 subAnalysisState :: DFState f -> DFState f
178 subAnalysisState s = s {df_facts_change = NoChange}
181 markGraphRewritten :: Monad m => DFM' m f ()
182 markGraphRewritten = DFM' f
183 where f _ s = return ((), s {df_rewritten = SomeChange})
185 graphWasRewritten :: DFM f ChangeFlag
186 graphWasRewritten = DFM' f
187 where f _ s = return (df_rewritten s, s)
189 instance Monad m => Monad (DFM' m f) where
190 DFM' f >>= k = DFM' (\l s -> do (a, s') <- f l s
191 s' `seq` case k a of DFM' f' -> f' l s')
192 return a = DFM' (\_ s -> return (a, s))
193 -- The `seq` is essential to ensure that entire passes of the dataflow engine
194 -- aren't postponed in a thunk. By making the sequence strict in the state,
195 -- we ensure that each action in the monad is executed immediately, preventing
196 -- stack overflows that previously occurred when finally forcing the old state thunks.
198 instance FuelUsingMonad (DFM' FuelMonad f) where
199 fuelRemaining = liftToDFM' fuelRemaining
200 lastFuelPass = liftToDFM' lastFuelPass
201 fuelExhausted = liftToDFM' fuelExhausted
202 fuelDecrement p f f' = liftToDFM' (fuelDecrement p f f')
203 fuelDec1 = liftToDFM' fuelDec1
204 instance MonadUnique (DFM' FuelMonad f) where
205 getUniqueSupplyM = liftToDFM' getUniqueSupplyM
206 getUniqueM = liftToDFM' getUniqueM
207 getUniquesM = liftToDFM' getUniquesM
209 liftToDFM' :: Monad m => m x -> DFM' m f x
210 liftToDFM' m = DFM' (\ _ s -> m >>= (\a -> return (a, s)))
211 liftToDFM :: FuelMonad x -> DFM f x
212 liftToDFM m = DFM' (\ _ s -> m >>= (\a -> return (a, s)))
215 pprSetFact :: (Show a, Outputable f) => a -> f -> f -> f -> SDoc
216 pprSetFact id old a join =
217 f4sep [text "at" <+> text (show id),
218 text "added" <+> ppr a, text "to" <+> ppr old,
219 text "yielding" <+> ppr join]
221 f4sep :: [SDoc] -> SDoc
223 f4sep (d:ds) = fsep (d : map (nest 4) ds)