diff options
author | Bartosz Nitka <niteria@gmail.com> | 2016-07-07 03:07:20 -0700 |
---|---|---|
committer | Bartosz Nitka <niteria@gmail.com> | 2016-07-07 03:57:44 -0700 |
commit | 6ed7c4793fe1acd491646a8312afbbda6be1fd0b (patch) | |
tree | 206c1a844201486bfdbfdf9cdca7efe9f2ab7d52 /compiler | |
parent | bedd62037f588321312feaf16923fa04d443e3d8 (diff) | |
download | haskell-6ed7c4793fe1acd491646a8312afbbda6be1fd0b.tar.gz |
Document some codegen nondeterminism
Bit-for-bit reproducible binaries are not a goal for now,
so this is just marking places that could be a problem.
Doing this will allow eltsUFM to be removed and will
leave only nonDetEltsUFM.
GHC Trac: #4012
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/cmm/CmmCommonBlockElim.hs | 3 | ||||
-rw-r--r-- | compiler/cmm/CmmLayoutStack.hs | 12 | ||||
-rw-r--r-- | compiler/nativeGen/AsmCodeGen.hs | 4 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/Main.hs | 3 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/Spill.hs | 5 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 6 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/Stats.hs | 14 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 3 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Linear/Stats.hs | 3 | ||||
-rw-r--r-- | compiler/utils/GraphOps.hs | 23 | ||||
-rw-r--r-- | compiler/utils/GraphPpr.hs | 5 |
11 files changed, 50 insertions, 31 deletions
diff --git a/compiler/cmm/CmmCommonBlockElim.hs b/compiler/cmm/CmmCommonBlockElim.hs index 3217c9394a..80acae11d4 100644 --- a/compiler/cmm/CmmCommonBlockElim.hs +++ b/compiler/cmm/CmmCommonBlockElim.hs @@ -297,5 +297,6 @@ groupByLabel = go (TM.emptyTM :: TM.ListMap UniqDFM a) groupByInt :: (a -> Int) -> [a] -> [[a]] -groupByInt f xs = eltsUFM $ List.foldl' go emptyUFM xs +groupByInt f xs = nonDetEltsUFM $ List.foldl' go emptyUFM xs + -- See Note [Unique Determinism and code generation] where go m x = alterUFM (Just . maybe [x] (x:)) m (f x) diff --git a/compiler/cmm/CmmLayoutStack.hs b/compiler/cmm/CmmLayoutStack.hs index 25a0ad6169..5c3be17e44 100644 --- a/compiler/cmm/CmmLayoutStack.hs +++ b/compiler/cmm/CmmLayoutStack.hs @@ -184,7 +184,7 @@ instance Outputable StackMap where text "Sp = " <> int sm_sp $$ text "sm_args = " <> int sm_args $$ text "sm_ret_off = " <> int sm_ret_off $$ - text "sm_regs = " <> ppr (eltsUFM sm_regs) + text "sm_regs = " <> pprUFM sm_regs ppr cmmLayoutStack :: DynFlags -> ProcPointSet -> ByteOff -> CmmGraph @@ -684,7 +684,8 @@ allocate dflags ret_off live stackmap@StackMap{ sm_sp = sp0 | x <- [ 1 .. toWords dflags ret_off] ] live_words = [ (toWords dflags x, Occupied) - | (r,off) <- eltsUFM regs1, + | (r,off) <- nonDetEltsUFM regs1, + -- See Note [Unique Determinism and code generation] let w = localRegBytes dflags r, x <- [ off, off - wORD_SIZE dflags .. off - w + 1] ] in @@ -964,7 +965,9 @@ stackMapToLiveness dflags StackMap{..} = toWords dflags (sm_sp - sm_args)) live_words where live_words = [ (toWords dflags off, False) - | (r,off) <- eltsUFM sm_regs, isGcPtrType (localRegType r) ] + | (r,off) <- nonDetEltsUFM sm_regs + , isGcPtrType (localRegType r) ] + -- See Note [Unique Determinism and code generation] -- ----------------------------------------------------------------------------- @@ -1118,4 +1121,5 @@ insertReloads stackmap = stackSlotRegs :: StackMap -> [(LocalReg, StackLoc)] -stackSlotRegs sm = eltsUFM (sm_regs sm) +stackSlotRegs sm = nonDetEltsUFM (sm_regs sm) + -- See Note [Unique Determinism and code generation] diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index 094a9085be..46c6fa4763 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -432,7 +432,9 @@ cmmNativeGens dflags this_mod modLoc ncgImpl h dbgMap us -- Generate .file directives for every new file that has been -- used. Note that it is important that we generate these in -- ascending order, as Clang's 3.6 assembler complains. - let newFileIds = sortBy (comparing snd) $ eltsUFM $ fileIds' `minusUFM` fileIds + let newFileIds = sortBy (comparing snd) $ + nonDetEltsUFM $ fileIds' `minusUFM` fileIds + -- See Note [Unique Determinism and code generation] pprDecl (f,n) = text "\t.file " <> ppr n <+> doubleQuotes (ftext f) diff --git a/compiler/nativeGen/RegAlloc/Graph/Main.hs b/compiler/nativeGen/RegAlloc/Graph/Main.hs index f7b3d0179d..0b10f3c1e3 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Main.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Main.hs @@ -401,7 +401,8 @@ patchRegsFromGraph platform graph code -- We need to deepSeq the whole graph before trying to colour it to avoid -- space leaks. seqGraph :: Color.Graph VirtualReg RegClass RealReg -> () -seqGraph graph = seqNodes (eltsUFM (Color.graphMap graph)) +seqGraph graph = seqNodes (nonDetEltsUFM (Color.graphMap graph)) + -- See Note [Unique Determinism and code generation] seqNodes :: [Color.Node VirtualReg RegClass RealReg] -> () seqNodes ns diff --git a/compiler/nativeGen/RegAlloc/Graph/Spill.hs b/compiler/nativeGen/RegAlloc/Graph/Spill.hs index 9c3ccae315..a1d46cbc1b 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Spill.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Spill.hs @@ -376,6 +376,5 @@ makeSpillStats s instance Outputable SpillStats where ppr stats - = (vcat $ map (\(r, s, l) -> ppr r <+> int s <+> int l) - $ eltsUFM (spillStoreLoad stats)) - + = pprUFM (spillStoreLoad stats) + (vcat . map (\(r, s, l) -> ppr r <+> int s <+> int l)) diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs index beffde97bb..198be622e1 100644 --- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs +++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs @@ -153,7 +153,8 @@ chooseSpill chooseSpill info graph = let cost = spillCost_length info graph node = minimumBy (\n1 n2 -> compare (cost $ nodeId n1) (cost $ nodeId n2)) - $ eltsUFM $ graphMap graph + $ nonDetEltsUFM $ graphMap graph + -- See Note [Unique Determinism and code generation] in nodeId node @@ -241,7 +242,8 @@ lifeMapFromSpillCostInfo :: SpillCostInfo -> UniqFM (VirtualReg, Int) lifeMapFromSpillCostInfo info = listToUFM $ map (\(r, _, _, life) -> (r, (r, life))) - $ eltsUFM info + $ nonDetEltsUFM info + -- See Note [Unique Determinism and code generation] -- | Determine the degree (number of neighbors) of this node which diff --git a/compiler/nativeGen/RegAlloc/Graph/Stats.hs b/compiler/nativeGen/RegAlloc/Graph/Stats.hs index cfd8f83122..9a8d0068ff 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Stats.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Stats.hs @@ -129,7 +129,7 @@ instance (Outputable statics, Outputable instr) $$ (if (not $ isNullUFM $ raCoalesced s) then text "# Registers coalesced." - $$ (pprUFMWithKeys (raCoalesced s) (vcat . map ppr)) + $$ pprUFMWithKeys (raCoalesced s) (vcat . map ppr) $$ text "" else empty) @@ -160,7 +160,7 @@ instance (Outputable statics, Outputable instr) $$ (if (not $ isNullUFM $ raCoalesced s) then text "# Registers coalesced." - $$ (pprUFMWithKeys (raCoalesced s) (vcat . map ppr)) + $$ pprUFMWithKeys (raCoalesced s) (vcat . map ppr) $$ text "" else empty) @@ -232,7 +232,7 @@ pprStatsLifetimes stats in ( text "-- vreg-population-lifetimes" $$ text "-- (instruction_count, number_of_vregs_that_lived_that_long)" - $$ (vcat $ map ppr $ eltsUFM lifeBins) + $$ pprUFM lifeBins (vcat . map ppr) $$ text "\n") @@ -240,7 +240,8 @@ binLifetimeCount :: UniqFM (VirtualReg, Int) -> UniqFM (Int, Int) binLifetimeCount fm = let lifes = map (\l -> (l, (l, 1))) $ map snd - $ eltsUFM fm + $ nonDetEltsUFM fm + -- See Note [Unique Determinism and code generation] in addListToUFM_C (\(l1, c1) (_, c2) -> (l1, c1 + c2)) @@ -260,7 +261,7 @@ pprStatsConflict stats in ( text "-- vreg-conflicts" $$ text "-- (conflict_count, number_of_vregs_that_had_that_many_conflicts)" - $$ (vcat $ map ppr $ eltsUFM confMap) + $$ pprUFM confMap (vcat . map ppr) $$ text "\n") @@ -285,7 +286,8 @@ pprStatsLifeConflict stats graph , ppr $ sizeUniqSet (Color.nodeConflicts node) , ppr $ lifetime ]) $ map Color.nodeId - $ eltsUFM + $ nonDetEltsUFM + -- See Note [Unique Determinism and code generation] $ Color.graphMap graph in ( text "-- vreg-conflict-lifetime" diff --git a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs index 4bbf5d4c88..a40bec16e4 100644 --- a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs +++ b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs @@ -59,7 +59,8 @@ accSqueeze -> UniqFM reg -> Int -accSqueeze count maxCount squeeze ufm = acc count (eltsUFM ufm) +accSqueeze count maxCount squeeze ufm = acc count (nonDetEltsUFM ufm) + -- See Note [Unique Determinism and code generation] where acc count [] = count acc count _ | count >= maxCount = count acc count (r:rs) = acc (count + squeeze r) rs diff --git a/compiler/nativeGen/RegAlloc/Linear/Stats.hs b/compiler/nativeGen/RegAlloc/Linear/Stats.hs index c55df6bee8..71dedaeb55 100644 --- a/compiler/nativeGen/RegAlloc/Linear/Stats.hs +++ b/compiler/nativeGen/RegAlloc/Linear/Stats.hs @@ -66,7 +66,8 @@ pprStats code statss spillTotals = foldl' (zipWith (+)) [0, 0, 0, 0, 0] - $ eltsUFM spills + $ nonDetEltsUFM spills + -- See Note [Unique Determinism and code generation] -- count how many reg-reg-moves remain in the code moves = sum $ map countRegRegMovesNat code diff --git a/compiler/utils/GraphOps.hs b/compiler/utils/GraphOps.hs index a4c565f2eb..b4b3bd6d8e 100644 --- a/compiler/utils/GraphOps.hs +++ b/compiler/utils/GraphOps.hs @@ -307,7 +307,8 @@ coalesceGraph' aggressive triv graph kkPairsAcc = let -- find all the nodes that have coalescence edges cNodes = filter (\node -> not $ isEmptyUniqSet (nodeCoalesce node)) - $ eltsUFM $ graphMap graph + $ nonDetEltsUFM $ graphMap graph + -- See Note [Unique Determinism and code generation] -- build a list of pairs of keys for node's we'll try and coalesce -- every pair of nodes will appear twice in this list @@ -528,7 +529,8 @@ freezeAllInGraph freezeAllInGraph graph = foldr freezeNode graph $ map nodeId - $ eltsUFM $ graphMap graph + $ nonDetEltsUFM $ graphMap graph + -- See Note [Unique Determinism and code generation] -- | Find all the nodes in the graph that meet some criteria @@ -539,7 +541,8 @@ scanGraph -> [Node k cls color] scanGraph match graph - = filter match $ eltsUFM $ graphMap graph + = filter match $ nonDetEltsUFM $ graphMap graph + -- See Note [Unique Determinism and code generation] -- | validate the internal structure of a graph @@ -557,10 +560,10 @@ validateGraph doc isColored graph -- Check that all edges point to valid nodes. | edges <- unionManyUniqSets - ( (map nodeConflicts $ eltsUFM $ graphMap graph) - ++ (map nodeCoalesce $ eltsUFM $ graphMap graph)) + ( (map nodeConflicts $ nonDetEltsUFM $ graphMap graph) + ++ (map nodeCoalesce $ nonDetEltsUFM $ graphMap graph)) - , nodes <- mkUniqSet $ map nodeId $ eltsUFM $ graphMap graph + , nodes <- mkUniqSet $ map nodeId $ nonDetEltsUFM $ graphMap graph , badEdges <- minusUniqSet edges nodes , not $ isEmptyUniqSet badEdges = pprPanic "GraphOps.validateGraph" @@ -570,7 +573,8 @@ validateGraph doc isColored graph -- Check that no conflicting nodes have the same color | badNodes <- filter (not . (checkNode graph)) - $ eltsUFM $ graphMap graph + $ nonDetEltsUFM $ graphMap graph + -- See Note [Unique Determinism and code generation] , not $ null badNodes = pprPanic "GraphOps.validateGraph" ( text "Node has same color as one of it's conflicts" @@ -581,7 +585,7 @@ validateGraph doc isColored graph -- check that all nodes have a color. | isColored , badNodes <- filter (\n -> isNothing $ nodeColor n) - $ eltsUFM $ graphMap graph + $ nonDetEltsUFM $ graphMap graph , not $ null badNodes = pprPanic "GraphOps.validateGraph" ( text "Supposably colored graph has uncolored nodes." @@ -630,7 +634,8 @@ slurpNodeConflictCount graph $ map (\node -> let count = sizeUniqSet $ nodeConflicts node in (count, (count, 1))) - $ eltsUFM + $ nonDetEltsUFM + -- See Note [Unique Determinism and code generation] $ graphMap graph diff --git a/compiler/utils/GraphPpr.hs b/compiler/utils/GraphPpr.hs index 9c246893f7..f5276842aa 100644 --- a/compiler/utils/GraphPpr.hs +++ b/compiler/utils/GraphPpr.hs @@ -25,7 +25,7 @@ dumpGraph dumpGraph graph = text "Graph" - $$ (vcat $ map dumpNode $ eltsUFM $ graphMap graph) + $$ pprUFM (graphMap graph) (vcat . map dumpNode) dumpNode :: (Outputable k, Outputable color) @@ -65,7 +65,8 @@ dotGraph -> Graph k cls color -> SDoc dotGraph colorMap triv graph - = let nodes = eltsUFM $ graphMap graph + = let nodes = nonDetEltsUFM $ graphMap graph + -- See Note [Unique Determinism and code generation] in vcat ( [ text "graph G {" ] ++ map (dotNode colorMap triv) nodes |