Store postdominators as Array Node [Node] for a significant win
This commit is contained in:
parent
04db46381f
commit
77069f7445
|
@ -47,6 +47,8 @@ import ShellCheck.Regex
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Identity
|
import Control.Monad.Identity
|
||||||
|
import Data.Array.Unboxed
|
||||||
|
import Data.Array.ST
|
||||||
import Data.List hiding (map)
|
import Data.List hiding (map)
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -174,10 +176,10 @@ data CFGResult = CFGResult {
|
||||||
cfIdToRange :: M.Map Id (Node, Node),
|
cfIdToRange :: M.Map Id (Node, Node),
|
||||||
-- A set of all nodes belonging to an Id, recursively
|
-- A set of all nodes belonging to an Id, recursively
|
||||||
cfIdToNodes :: M.Map Id (S.Set Node),
|
cfIdToNodes :: M.Map Id (S.Set Node),
|
||||||
-- A map to nodes that the given node postdominates
|
-- An array (from,to) saying whether 'from' postdominates 'to'
|
||||||
cfPostDominators :: M.Map Node (S.Set Node)
|
cfPostDominators :: Array Node [Node]
|
||||||
}
|
}
|
||||||
deriving (Show, Generic, NFData)
|
deriving (Show)
|
||||||
|
|
||||||
buildGraph :: CFGParameters -> Token -> CFGResult
|
buildGraph :: CFGParameters -> Token -> CFGResult
|
||||||
buildGraph params root =
|
buildGraph params root =
|
||||||
|
@ -200,7 +202,7 @@ buildGraph params root =
|
||||||
cfPostDominators = findPostDominators mainExit $ mkGraph nodes onlyRealEdges
|
cfPostDominators = findPostDominators mainExit $ mkGraph nodes onlyRealEdges
|
||||||
}
|
}
|
||||||
in
|
in
|
||||||
deepseq result result
|
result
|
||||||
|
|
||||||
remapGraph :: M.Map Node Node -> CFW -> CFW
|
remapGraph :: M.Map Node Node -> CFW -> CFW
|
||||||
remapGraph remap (nodes, edges, mapping, assoc) =
|
remapGraph remap (nodes, edges, mapping, assoc) =
|
||||||
|
@ -1256,8 +1258,8 @@ findTerminalNodes graph = ufold find [] graph
|
||||||
f (IdTagged _ (CFDefineFunction _ id start end):rest) list = f rest (end:list)
|
f (IdTagged _ (CFDefineFunction _ id start end):rest) list = f rest (end:list)
|
||||||
f (_:rest) list = f rest list
|
f (_:rest) list = f rest list
|
||||||
|
|
||||||
findPostDominators :: Node -> CFGraph -> M.Map Node (S.Set Node)
|
findPostDominators :: Node -> CFGraph -> Array Node [Node]
|
||||||
findPostDominators mainexit graph = asSetMap
|
findPostDominators mainexit graph = asArray
|
||||||
where
|
where
|
||||||
inlined = inlineSubshells graph
|
inlined = inlineSubshells graph
|
||||||
terminals = findTerminalNodes inlined
|
terminals = findTerminalNodes inlined
|
||||||
|
@ -1265,7 +1267,8 @@ findPostDominators mainexit graph = asSetMap
|
||||||
withExitEdges = (incoming ++ map (\c -> (CFEFlow, c)) terminals, mainexit, label, outgoing) `safeUpdate` inlined
|
withExitEdges = (incoming ++ map (\c -> (CFEFlow, c)) terminals, mainexit, label, outgoing) `safeUpdate` inlined
|
||||||
reversed = grev withExitEdges
|
reversed = grev withExitEdges
|
||||||
postDoms = dom reversed mainexit
|
postDoms = dom reversed mainexit
|
||||||
asSetMap = M.fromList $ map (\(node, list) -> (node, S.fromList list)) postDoms
|
(_, maxNode) = nodeRange graph
|
||||||
|
asArray = array (0, maxNode) postDoms
|
||||||
|
|
||||||
return []
|
return []
|
||||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
||||||
|
|
|
@ -69,6 +69,7 @@ import Control.Monad
|
||||||
import Control.Monad.ST
|
import Control.Monad.ST
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
import Data.List hiding (map)
|
import Data.List hiding (map)
|
||||||
|
import Data.Array.Unboxed
|
||||||
import Data.STRef
|
import Data.STRef
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -100,9 +101,9 @@ data CFGAnalysis = CFGAnalysis {
|
||||||
graph :: CFGraph,
|
graph :: CFGraph,
|
||||||
tokenToRange :: M.Map Id (Node, Node),
|
tokenToRange :: M.Map Id (Node, Node),
|
||||||
tokenToNodes :: M.Map Id (S.Set Node),
|
tokenToNodes :: M.Map Id (S.Set Node),
|
||||||
postDominators :: M.Map Node (S.Set Node),
|
postDominators :: Array Node [Node],
|
||||||
nodeToData :: M.Map Node (ProgramState, ProgramState)
|
nodeToData :: M.Map Node (ProgramState, ProgramState)
|
||||||
} deriving (Show, Generic, NFData)
|
} deriving (Show)
|
||||||
|
|
||||||
-- The program state we expose externally
|
-- The program state we expose externally
|
||||||
data ProgramState = ProgramState {
|
data ProgramState = ProgramState {
|
||||||
|
@ -147,8 +148,7 @@ doesPostDominate :: CFGAnalysis -> Id -> Id -> Bool
|
||||||
doesPostDominate analysis target base = fromMaybe False $ do
|
doesPostDominate analysis target base = fromMaybe False $ do
|
||||||
(_, baseEnd) <- M.lookup base $ tokenToRange analysis
|
(_, baseEnd) <- M.lookup base $ tokenToRange analysis
|
||||||
(targetStart, _) <- M.lookup target $ tokenToRange analysis
|
(targetStart, _) <- M.lookup target $ tokenToRange analysis
|
||||||
postDoms <- M.lookup baseEnd $ postDominators analysis
|
return $ targetStart `elem` (postDominators analysis ! baseEnd)
|
||||||
return $ S.member targetStart postDoms
|
|
||||||
|
|
||||||
getDataForNode analysis node = M.lookup node $ nodeToData analysis
|
getDataForNode analysis node = M.lookup node $ nodeToData analysis
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue