summaryrefslogtreecommitdiff
path: root/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs')
-rw-r--r--compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs34
1 files changed, 15 insertions, 19 deletions
diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
index a5016abc6f..fec35cb6bc 100644
--- a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE CPP #-}
+{-# LANGUAGE ScopedTypeVariables #-}
-- | Clean out unneeded spill\/reload instructions.
--
@@ -340,7 +341,7 @@ cleanBackward liveSlotsOnEntry noReloads acc lis
cleanBackward'
:: Instruction instr
=> BlockMap IntSet
- -> UniqFM [BlockId]
+ -> UniqFM Store [BlockId]
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
@@ -438,17 +439,17 @@ type CleanM
data CleanS
= CleanS
{ -- | Regs which are valid at the start of each block.
- sJumpValid :: UniqFM (Assoc Store)
+ sJumpValid :: UniqFM BlockId (Assoc Store)
-- | Collecting up what regs were valid across each jump.
-- in the next pass we can collate these and write the results
-- to sJumpValid.
- , sJumpValidAcc :: UniqFM [Assoc Store]
+ , sJumpValidAcc :: UniqFM BlockId [Assoc Store]
-- | Map of (slot -> blocks which reload from this slot)
-- used to decide if whether slot spilled to will ever be
-- reloaded from on this path.
- , sReloadedBy :: UniqFM [BlockId]
+ , sReloadedBy :: UniqFM Store [BlockId]
-- | Spills and reloads cleaned each pass (latest at front)
, sCleanedCount :: [(Int, Int)]
@@ -533,7 +534,8 @@ instance Outputable Store where
-- In the spill cleaner, two store locations are associated if they are known
-- to hold the same value.
--
-type Assoc a = UniqFM (UniqSet a)
+-- TODO: Monomorphize: I think we only ever use this with a ~ Store
+type Assoc a = UniqFM a (UniqSet a)
-- | An empty association
emptyAssoc :: Assoc a
@@ -541,8 +543,9 @@ emptyAssoc = emptyUFM
-- | Add an association between these two things.
-addAssoc :: Uniquable a
- => a -> a -> Assoc a -> Assoc a
+-- addAssoc :: Uniquable a
+-- => a -> a -> Assoc a -> Assoc a
+addAssoc :: Store -> Store -> Assoc Store -> Assoc Store
addAssoc a b m
= let m1 = addToUFM_C unionUniqSets m a (unitUniqSet b)
@@ -551,9 +554,7 @@ addAssoc a b m
-- | Delete all associations to a node.
-delAssoc :: (Uniquable a)
- => a -> Assoc a -> Assoc a
-
+delAssoc :: Store -> Assoc Store -> Assoc Store
delAssoc a m
| Just aSet <- lookupUFM m a
, m1 <- delFromUFM m a
@@ -565,9 +566,7 @@ delAssoc a m
-- | Delete a single association edge (a -> b).
-delAssoc1 :: Uniquable a
- => a -> a -> Assoc a -> Assoc a
-
+delAssoc1 :: Store -> Store -> Assoc Store -> Assoc Store
delAssoc1 a b m
| Just aSet <- lookupUFM m a
= addToUFM m a (delOneFromUniqSet aSet b)
@@ -576,17 +575,14 @@ delAssoc1 a b m
-- | Check if these two things are associated.
-elemAssoc :: (Uniquable a)
- => a -> a -> Assoc a -> Bool
+elemAssoc :: Store -> Store -> Assoc Store -> Bool
elemAssoc a b m
= elementOfUniqSet b (closeAssoc a m)
-- | Find the refl. trans. closure of the association from this point.
-closeAssoc :: (Uniquable a)
- => a -> Assoc a -> UniqSet a
-
+closeAssoc :: Store -> Assoc Store -> UniqSet Store
closeAssoc a assoc
= closeAssoc' assoc emptyUniqSet (unitUniqSet a)
where
@@ -615,6 +611,6 @@ closeAssoc a assoc
(unionUniqSets toVisit neighbors)
-- | Intersect two associations.
-intersectAssoc :: Assoc a -> Assoc a -> Assoc a
+intersectAssoc :: Assoc Store -> Assoc Store -> Assoc Store
intersectAssoc a b
= intersectUFM_C (intersectUniqSets) a b