{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
module GHC.CmmToAsm.Reg.Graph.SpillClean (
cleanSpills
) where
import GHC.Prelude
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Reg.Liveness
import GHC.CmmToAsm.Format
import GHC.CmmToAsm.Instr
import GHC.Platform.Reg
import GHC.Cmm.BlockId
import GHC.Cmm
import GHC.Types.Unique.Set
import GHC.Types.Unique.FM
import GHC.Types.Unique
import GHC.Builtin.Uniques
import GHC.Utils.Monad.State.Strict
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Cmm.Dataflow.Label
import Data.List (nub, foldl1', find)
import Data.Maybe
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
type Slot = Int
cleanSpills
:: Instruction instr
=> NCGConfig
-> LiveCmmDecl statics instr
-> LiveCmmDecl statics instr
cleanSpills :: forall instr statics.
Instruction instr =>
NCGConfig -> LiveCmmDecl statics instr -> LiveCmmDecl statics instr
cleanSpills NCGConfig
config LiveCmmDecl statics instr
cmm
= State CleanS (LiveCmmDecl statics instr)
-> CleanS -> LiveCmmDecl statics instr
forall s a. State s a -> s -> a
evalState (NCGConfig
-> Int
-> LiveCmmDecl statics instr
-> State CleanS (LiveCmmDecl statics instr)
forall instr statics.
Instruction instr =>
NCGConfig
-> Int
-> LiveCmmDecl statics instr
-> CleanM (LiveCmmDecl statics instr)
cleanSpin NCGConfig
config Int
0 LiveCmmDecl statics instr
cmm) CleanS
initCleanS
cleanSpin
:: Instruction instr
=> NCGConfig
-> Int
-> LiveCmmDecl statics instr
-> CleanM (LiveCmmDecl statics instr)
cleanSpin :: forall instr statics.
Instruction instr =>
NCGConfig
-> Int
-> LiveCmmDecl statics instr
-> CleanM (LiveCmmDecl statics instr)
cleanSpin NCGConfig
config Int
spinCount LiveCmmDecl statics instr
code
= do
(CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s
{ sCleanedSpillsAcc = 0
, sCleanedReloadsAcc = 0
, sReloadedBy = emptyUFM }
code_forward <- (LiveBasicBlock instr -> State CleanS (LiveBasicBlock instr))
-> LiveCmmDecl statics instr
-> State CleanS (LiveCmmDecl statics instr)
forall (m :: * -> *) instr statics.
Monad m =>
(LiveBasicBlock instr -> m (LiveBasicBlock instr))
-> LiveCmmDecl statics instr -> m (LiveCmmDecl statics instr)
mapBlockTopM (NCGConfig
-> LiveBasicBlock instr -> State CleanS (LiveBasicBlock instr)
forall instr.
Instruction instr =>
NCGConfig -> LiveBasicBlock instr -> CleanM (LiveBasicBlock instr)
cleanBlockForward NCGConfig
config) LiveCmmDecl statics instr
code
code_backward <- cleanTopBackward code_forward
collateJoinPoints
spills <- gets sCleanedSpillsAcc
reloads <- gets sCleanedReloadsAcc
modify $ \CleanS
s -> CleanS
s
{ sCleanedCount = (spills, reloads) : sCleanedCount s }
cleanedCount <- gets sCleanedCount
if take 2 cleanedCount == [(0, 0), (0, 0)]
then return code
else cleanSpin config (spinCount + 1) code_backward
cleanBlockForward
:: Instruction instr
=> NCGConfig
-> LiveBasicBlock instr
-> CleanM (LiveBasicBlock instr)
cleanBlockForward :: forall instr.
Instruction instr =>
NCGConfig -> LiveBasicBlock instr -> CleanM (LiveBasicBlock instr)
cleanBlockForward NCGConfig
config (BasicBlock BlockId
blockId [LiveInstr instr]
instrs)
= do
jumpValid <- (CleanS -> UniqFM BlockId (Assoc Store))
-> State CleanS (UniqFM BlockId (Assoc Store))
forall s a. (s -> a) -> State s a
gets CleanS -> UniqFM BlockId (Assoc Store)
sJumpValid
let assoc = case UniqFM BlockId (Assoc Store) -> BlockId -> Maybe (Assoc Store)
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM BlockId (Assoc Store)
jumpValid BlockId
blockId of
Just Assoc Store
assoc -> Assoc Store
assoc
Maybe (Assoc Store)
Nothing -> Assoc Store
forall a. Assoc a
emptyAssoc
instrs_reload <- cleanForward config blockId assoc [] instrs
return $ BasicBlock blockId instrs_reload
cleanForward
:: Instruction instr
=> NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward :: forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
_ BlockId
_ Assoc Store
_ [LiveInstr instr]
acc []
= [LiveInstr instr] -> State CleanS [LiveInstr instr]
forall a. a -> State CleanS a
forall (m :: * -> *) a. Monad m => a -> m a
return [LiveInstr instr]
acc
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc [LiveInstr instr]
acc (LiveInstr instr
li1 : LiveInstr instr
li2 : [LiveInstr instr]
instrs)
| LiveInstr (SPILL RegWithFormat
reg1 Int
slot1) Maybe Liveness
_ <- LiveInstr instr
li1
, LiveInstr (RELOAD Int
slot2 RegWithFormat
reg2) Maybe Liveness
_ <- LiveInstr instr
li2
, Int
slot1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
slot2
= do
(CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 }
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc [LiveInstr instr]
acc
([LiveInstr instr] -> State CleanS [LiveInstr instr])
-> [LiveInstr instr] -> State CleanS [LiveInstr instr]
forall a b. (a -> b) -> a -> b
$ LiveInstr instr
li1 LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: InstrSR instr -> Maybe Liveness -> LiveInstr instr
forall instr. InstrSR instr -> Maybe Liveness -> LiveInstr instr
LiveInstr (NCGConfig -> Format -> Reg -> Reg -> InstrSR instr
forall instr.
(Instruction instr, HasDebugCallStack) =>
NCGConfig -> Format -> Reg -> Reg -> instr
mkRegRegMoveInstr NCGConfig
config (RegWithFormat -> Format
regWithFormat_format RegWithFormat
reg2) (RegWithFormat -> Reg
regWithFormat_reg RegWithFormat
reg1) (RegWithFormat -> Reg
regWithFormat_reg RegWithFormat
reg2)) Maybe Liveness
forall a. Maybe a
Nothing
LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
instrs
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc [LiveInstr instr]
acc (li :: LiveInstr instr
li@(LiveInstr InstrSR instr
i1 Maybe Liveness
_) : [LiveInstr instr]
instrs)
| Just (Reg
r1, Reg
r2) <- Platform -> InstrSR instr -> Maybe (Reg, Reg)
forall instr.
Instruction instr =>
Platform -> instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr (NCGConfig -> Platform
ncgPlatform NCGConfig
config) InstrSR instr
i1
= if Reg
r1 Reg -> Reg -> Bool
forall a. Eq a => a -> a -> Bool
== Reg
r2
then NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc [LiveInstr instr]
acc [LiveInstr instr]
instrs
else do let assoc' :: Assoc Store
assoc' = Store -> Store -> Assoc Store -> Assoc Store
addAssoc (Reg -> Store
SReg Reg
r1) (Reg -> Store
SReg Reg
r2)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Store -> Assoc Store -> Assoc Store
delAssoc (Reg -> Store
SReg Reg
r2)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Assoc Store
assoc
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc' (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc [LiveInstr instr]
acc (LiveInstr instr
li : [LiveInstr instr]
instrs)
| LiveInstr (SPILL RegWithFormat
reg Int
slot) Maybe Liveness
_ <- LiveInstr instr
li
= let assoc' :: Assoc Store
assoc' = Store -> Store -> Assoc Store -> Assoc Store
addAssoc (Reg -> Store
SReg (Reg -> Store) -> Reg -> Store
forall a b. (a -> b) -> a -> b
$ RegWithFormat -> Reg
regWithFormat_reg RegWithFormat
reg) (Int -> Store
SSlot Int
slot)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Store -> Assoc Store -> Assoc Store
delAssoc (Int -> Store
SSlot Int
slot)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Assoc Store
assoc
in NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc' (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
| LiveInstr (RELOAD{}) Maybe Liveness
_ <- LiveInstr instr
li
= do (assoc', mli) <- NCGConfig
-> BlockId
-> Assoc Store
-> LiveInstr instr
-> CleanM (Assoc Store, Maybe (LiveInstr instr))
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> LiveInstr instr
-> CleanM (Assoc Store, Maybe (LiveInstr instr))
cleanReload NCGConfig
config BlockId
blockId Assoc Store
assoc LiveInstr instr
li
case mli of
Maybe (LiveInstr instr)
Nothing -> NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc' [LiveInstr instr]
acc
[LiveInstr instr]
instrs
Just LiveInstr instr
li' -> NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc' (LiveInstr instr
li' LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc)
[LiveInstr instr]
instrs
| LiveInstr InstrSR instr
instr Maybe Liveness
_ <- LiveInstr instr
li
, [BlockId]
targets <- InstrSR instr -> [BlockId]
forall instr. Instruction instr => instr -> [BlockId]
jumpDestsOfInstr InstrSR instr
instr
, Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [BlockId] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [BlockId]
targets
= do (BlockId -> State CleanS ()) -> [BlockId] -> State CleanS ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Assoc Store -> BlockId -> State CleanS ()
accJumpValid Assoc Store
assoc) [BlockId]
targets
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
| LiveInstr InstrSR instr
instr Maybe Liveness
_ <- LiveInstr instr
li
, RU [RegWithFormat]
_ [RegWithFormat]
written <- Platform -> InstrSR instr -> RegUsage
forall instr. Instruction instr => Platform -> instr -> RegUsage
regUsageOfInstr (NCGConfig -> Platform
ncgPlatform NCGConfig
config) InstrSR instr
instr
= let assoc' :: Assoc Store
assoc' = (Store -> Assoc Store -> Assoc Store)
-> Assoc Store -> [Store] -> Assoc Store
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Store -> Assoc Store -> Assoc Store
delAssoc Assoc Store
assoc ((Reg -> Store) -> [Reg] -> [Store]
forall a b. (a -> b) -> [a] -> [b]
map Reg -> Store
SReg ([Reg] -> [Store]) -> [Reg] -> [Store]
forall a b. (a -> b) -> a -> b
$ [Reg] -> [Reg]
forall a. Eq a => [a] -> [a]
nub ([Reg] -> [Reg]) -> [Reg] -> [Reg]
forall a b. (a -> b) -> a -> b
$ (RegWithFormat -> Reg) -> [RegWithFormat] -> [Reg]
forall a b. (a -> b) -> [a] -> [b]
map RegWithFormat -> Reg
regWithFormat_reg [RegWithFormat]
written)
in NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanForward NCGConfig
config BlockId
blockId Assoc Store
assoc' (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
cleanReload
:: Instruction instr
=> NCGConfig
-> BlockId
-> Assoc Store
-> LiveInstr instr
-> CleanM (Assoc Store, Maybe (LiveInstr instr))
cleanReload :: forall instr.
Instruction instr =>
NCGConfig
-> BlockId
-> Assoc Store
-> LiveInstr instr
-> CleanM (Assoc Store, Maybe (LiveInstr instr))
cleanReload NCGConfig
config BlockId
blockId Assoc Store
assoc li :: LiveInstr instr
li@(LiveInstr (RELOAD Int
slot (RegWithFormat Reg
reg Format
fmt)) Maybe Liveness
_)
| Store -> Store -> Assoc Store -> Bool
elemAssoc (Int -> Store
SSlot Int
slot) (Reg -> Store
SReg Reg
reg) Assoc Store
assoc
= do (CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 }
(Assoc Store, Maybe (LiveInstr instr))
-> State CleanS (Assoc Store, Maybe (LiveInstr instr))
forall a. a -> State CleanS a
forall (m :: * -> *) a. Monad m => a -> m a
return (Assoc Store
assoc, Maybe (LiveInstr instr)
forall a. Maybe a
Nothing)
| Just Reg
reg2 <- Assoc Store -> Int -> Maybe Reg
findRegOfSlot Assoc Store
assoc Int
slot
= do (CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 }
let assoc' :: Assoc Store
assoc' = Store -> Store -> Assoc Store -> Assoc Store
addAssoc (Reg -> Store
SReg Reg
reg) (Reg -> Store
SReg Reg
reg2)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Store -> Assoc Store -> Assoc Store
delAssoc (Reg -> Store
SReg Reg
reg)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Assoc Store
assoc
(Assoc Store, Maybe (LiveInstr instr))
-> State CleanS (Assoc Store, Maybe (LiveInstr instr))
forall a. a -> State CleanS a
forall (m :: * -> *) a. Monad m => a -> m a
return ( Assoc Store
assoc'
, LiveInstr instr -> Maybe (LiveInstr instr)
forall a. a -> Maybe a
Just (LiveInstr instr -> Maybe (LiveInstr instr))
-> LiveInstr instr -> Maybe (LiveInstr instr)
forall a b. (a -> b) -> a -> b
$ InstrSR instr -> Maybe Liveness -> LiveInstr instr
forall instr. InstrSR instr -> Maybe Liveness -> LiveInstr instr
LiveInstr (NCGConfig -> Format -> Reg -> Reg -> InstrSR instr
forall instr.
(Instruction instr, HasDebugCallStack) =>
NCGConfig -> Format -> Reg -> Reg -> instr
mkRegRegMoveInstr NCGConfig
config Format
fmt Reg
reg2 Reg
reg) Maybe Liveness
forall a. Maybe a
Nothing )
| Bool
otherwise
= do
let assoc' :: Assoc Store
assoc'
= Store -> Store -> Assoc Store -> Assoc Store
addAssoc (Reg -> Store
SReg Reg
reg) (Int -> Store
SSlot Int
slot)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Store -> Assoc Store -> Assoc Store
delAssoc (Reg -> Store
SReg Reg
reg)
(Assoc Store -> Assoc Store) -> Assoc Store -> Assoc Store
forall a b. (a -> b) -> a -> b
$ Assoc Store
assoc
BlockId -> Int -> State CleanS ()
accBlockReloadsSlot BlockId
blockId Int
slot
(Assoc Store, Maybe (LiveInstr instr))
-> State CleanS (Assoc Store, Maybe (LiveInstr instr))
forall a. a -> State CleanS a
forall (m :: * -> *) a. Monad m => a -> m a
return (Assoc Store
assoc', LiveInstr instr -> Maybe (LiveInstr instr)
forall a. a -> Maybe a
Just LiveInstr instr
li)
cleanReload NCGConfig
_ BlockId
_ Assoc Store
_ LiveInstr instr
_
= String -> State CleanS (Assoc Store, Maybe (LiveInstr instr))
forall a. HasCallStack => String -> a
panic String
"RegSpillClean.cleanReload: unhandled instr"
cleanTopBackward
:: Instruction instr
=> LiveCmmDecl statics instr
-> CleanM (LiveCmmDecl statics instr)
cleanTopBackward :: forall instr statics.
Instruction instr =>
LiveCmmDecl statics instr -> CleanM (LiveCmmDecl statics instr)
cleanTopBackward LiveCmmDecl statics instr
cmm
= case LiveCmmDecl statics instr
cmm of
CmmData{}
-> LiveCmmDecl statics instr -> CleanM (LiveCmmDecl statics instr)
forall a. a -> State CleanS a
forall (m :: * -> *) a. Monad m => a -> m a
return LiveCmmDecl statics instr
cmm
CmmProc LiveInfo
info CLabel
label [GlobalRegUse]
live [SCC (LiveBasicBlock instr)]
sccs
| LiveInfo LabelMap RawCmmStatics
_ [BlockId]
_ BlockMap (UniqSet RegWithFormat)
_ BlockMap IntSet
liveSlotsOnEntry <- LiveInfo
info
-> do sccs' <- (SCC (LiveBasicBlock instr)
-> State CleanS (SCC (LiveBasicBlock instr)))
-> [SCC (LiveBasicBlock instr)]
-> State CleanS [SCC (LiveBasicBlock instr)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((LiveBasicBlock instr -> State CleanS (LiveBasicBlock instr))
-> SCC (LiveBasicBlock instr)
-> State CleanS (SCC (LiveBasicBlock instr))
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> SCC a -> m (SCC b)
mapSCCM (BlockMap IntSet
-> LiveBasicBlock instr -> State CleanS (LiveBasicBlock instr)
forall instr.
Instruction instr =>
BlockMap IntSet
-> LiveBasicBlock instr -> CleanM (LiveBasicBlock instr)
cleanBlockBackward BlockMap IntSet
liveSlotsOnEntry)) [SCC (LiveBasicBlock instr)]
sccs
return $ CmmProc info label live sccs'
cleanBlockBackward
:: Instruction instr
=> BlockMap IntSet
-> LiveBasicBlock instr
-> CleanM (LiveBasicBlock instr)
cleanBlockBackward :: forall instr.
Instruction instr =>
BlockMap IntSet
-> LiveBasicBlock instr -> CleanM (LiveBasicBlock instr)
cleanBlockBackward BlockMap IntSet
liveSlotsOnEntry (BasicBlock BlockId
blockId [LiveInstr instr]
instrs)
= do instrs_spill <- BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
forall a. UniqSet a
emptyUniqSet [] [LiveInstr instr]
instrs
return $ BasicBlock blockId instrs_spill
cleanBackward
:: Instruction instr
=> BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward :: forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
noReloads [LiveInstr instr]
acc [LiveInstr instr]
lis
= do reloadedBy <- (CleanS -> UniqFM Store [BlockId])
-> State CleanS (UniqFM Store [BlockId])
forall s a. (s -> a) -> State s a
gets CleanS -> UniqFM Store [BlockId]
sReloadedBy
cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc lis
cleanBackward'
:: Instruction instr
=> BlockMap IntSet
-> UniqFM Store [BlockId]
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
cleanBackward' :: forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqFM Store [BlockId]
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
cleanBackward' BlockMap IntSet
_ UniqFM Store [BlockId]
_ UniqSet Int
_ [LiveInstr instr]
acc []
= [LiveInstr instr] -> State CleanS [LiveInstr instr]
forall a. a -> State CleanS a
forall (m :: * -> *) a. Monad m => a -> m a
return [LiveInstr instr]
acc
cleanBackward' BlockMap IntSet
liveSlotsOnEntry UniqFM Store [BlockId]
reloadedBy UniqSet Int
noReloads [LiveInstr instr]
acc (LiveInstr instr
li : [LiveInstr instr]
instrs)
| LiveInstr (SPILL RegWithFormat
_ Int
slot) Maybe Liveness
_ <- LiveInstr instr
li
, Maybe [BlockId]
Nothing <- UniqFM Store [BlockId] -> Store -> Maybe [BlockId]
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM Store [BlockId]
reloadedBy (Int -> Store
SSlot Int
slot)
= do (CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s { sCleanedSpillsAcc = sCleanedSpillsAcc s + 1 }
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
noReloads [LiveInstr instr]
acc [LiveInstr instr]
instrs
| LiveInstr (SPILL RegWithFormat
_ Int
slot) Maybe Liveness
_ <- LiveInstr instr
li
= if Int -> UniqSet Int -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
elementOfUniqSet Int
slot UniqSet Int
noReloads
then do
(CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s { sCleanedSpillsAcc = sCleanedSpillsAcc s + 1 }
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
noReloads [LiveInstr instr]
acc [LiveInstr instr]
instrs
else do
let noReloads' :: UniqSet Int
noReloads' = UniqSet Int -> Int -> UniqSet Int
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
addOneToUniqSet UniqSet Int
noReloads Int
slot
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
noReloads' (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
| LiveInstr (RELOAD Int
slot RegWithFormat
_) Maybe Liveness
_ <- LiveInstr instr
li
, UniqSet Int
noReloads' <- UniqSet Int -> Int -> UniqSet Int
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
delOneFromUniqSet UniqSet Int
noReloads Int
slot
= BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
noReloads' (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
| LiveInstr InstrSR instr
instr Maybe Liveness
_ <- LiveInstr instr
li
, [BlockId]
targets <- InstrSR instr -> [BlockId]
forall instr. Instruction instr => instr -> [BlockId]
jumpDestsOfInstr InstrSR instr
instr
= do
let slotsReloadedByTargets :: IntSet
slotsReloadedByTargets
= [IntSet] -> IntSet
forall (f :: * -> *). Foldable f => f IntSet -> IntSet
IntSet.unions
([IntSet] -> IntSet) -> [IntSet] -> IntSet
forall a b. (a -> b) -> a -> b
$ (BlockId -> Maybe IntSet) -> [BlockId] -> [IntSet]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ((BlockId -> BlockMap IntSet -> Maybe IntSet)
-> BlockMap IntSet -> BlockId -> Maybe IntSet
forall a b c. (a -> b -> c) -> b -> a -> c
flip BlockId -> BlockMap IntSet -> Maybe IntSet
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockMap IntSet
liveSlotsOnEntry)
([BlockId] -> [IntSet]) -> [BlockId] -> [IntSet]
forall a b. (a -> b) -> a -> b
$ [BlockId]
targets
let noReloads' :: UniqSet Int
noReloads'
= (UniqSet Int -> Int -> UniqSet Int)
-> UniqSet Int -> [Int] -> UniqSet Int
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' UniqSet Int -> Int -> UniqSet Int
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
delOneFromUniqSet UniqSet Int
noReloads
([Int] -> UniqSet Int) -> [Int] -> UniqSet Int
forall a b. (a -> b) -> a -> b
$ IntSet -> [Int]
IntSet.toList IntSet
slotsReloadedByTargets
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> State CleanS [LiveInstr instr]
forall instr.
Instruction instr =>
BlockMap IntSet
-> UniqSet Int
-> [LiveInstr instr]
-> [LiveInstr instr]
-> CleanM [LiveInstr instr]
cleanBackward BlockMap IntSet
liveSlotsOnEntry UniqSet Int
noReloads' (LiveInstr instr
li LiveInstr instr -> [LiveInstr instr] -> [LiveInstr instr]
forall a. a -> [a] -> [a]
: [LiveInstr instr]
acc) [LiveInstr instr]
instrs
collateJoinPoints :: CleanM ()
collateJoinPoints :: State CleanS ()
collateJoinPoints
= (CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s
{ sJumpValid = mapUFM intersects (sJumpValidAcc s)
, sJumpValidAcc = emptyUFM }
intersects :: [Assoc Store] -> Assoc Store
intersects :: [Assoc Store] -> Assoc Store
intersects [] = Assoc Store
forall a. Assoc a
emptyAssoc
intersects [Assoc Store]
assocs = (Assoc Store -> Assoc Store -> Assoc Store)
-> [Assoc Store] -> Assoc Store
forall a. HasCallStack => (a -> a -> a) -> [a] -> a
foldl1' Assoc Store -> Assoc Store -> Assoc Store
intersectAssoc [Assoc Store]
assocs
findRegOfSlot :: Assoc Store -> Int -> Maybe Reg
findRegOfSlot :: Assoc Store -> Int -> Maybe Reg
findRegOfSlot Assoc Store
assoc Int
slot
| UniqSet Store
close <- Store -> Assoc Store -> UniqSet Store
closeAssoc (Int -> Store
SSlot Int
slot) Assoc Store
assoc
, Just (SReg Reg
reg) <- (Store -> Bool) -> [Store] -> Maybe Store
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find Store -> Bool
isStoreReg ([Store] -> Maybe Store) -> [Store] -> Maybe Store
forall a b. (a -> b) -> a -> b
$ UniqSet Store -> [Store]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet UniqSet Store
close
= Reg -> Maybe Reg
forall a. a -> Maybe a
Just Reg
reg
| Bool
otherwise
= Maybe Reg
forall a. Maybe a
Nothing
type CleanM
= State CleanS
data CleanS
= CleanS
{
CleanS -> UniqFM BlockId (Assoc Store)
sJumpValid :: UniqFM BlockId (Assoc Store)
, CleanS -> UniqFM BlockId [Assoc Store]
sJumpValidAcc :: UniqFM BlockId [Assoc Store]
, CleanS -> UniqFM Store [BlockId]
sReloadedBy :: UniqFM Store [BlockId]
, CleanS -> [(Int, Int)]
sCleanedCount :: [(Int, Int)]
, CleanS -> Int
sCleanedSpillsAcc :: Int
, CleanS -> Int
sCleanedReloadsAcc :: Int }
initCleanS :: CleanS
initCleanS :: CleanS
initCleanS
= CleanS
{ sJumpValid :: UniqFM BlockId (Assoc Store)
sJumpValid = UniqFM BlockId (Assoc Store)
forall {k} (key :: k) elt. UniqFM key elt
emptyUFM
, sJumpValidAcc :: UniqFM BlockId [Assoc Store]
sJumpValidAcc = UniqFM BlockId [Assoc Store]
forall {k} (key :: k) elt. UniqFM key elt
emptyUFM
, sReloadedBy :: UniqFM Store [BlockId]
sReloadedBy = UniqFM Store [BlockId]
forall {k} (key :: k) elt. UniqFM key elt
emptyUFM
, sCleanedCount :: [(Int, Int)]
sCleanedCount = []
, sCleanedSpillsAcc :: Int
sCleanedSpillsAcc = Int
0
, sCleanedReloadsAcc :: Int
sCleanedReloadsAcc = Int
0 }
accJumpValid :: Assoc Store -> BlockId -> CleanM ()
accJumpValid :: Assoc Store -> BlockId -> State CleanS ()
accJumpValid Assoc Store
assocs BlockId
target
= (CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s {
sJumpValidAcc = addToUFM_C (++)
(sJumpValidAcc s)
target
[assocs] }
accBlockReloadsSlot :: BlockId -> Slot -> CleanM ()
accBlockReloadsSlot :: BlockId -> Int -> State CleanS ()
accBlockReloadsSlot BlockId
blockId Int
slot
= (CleanS -> CleanS) -> State CleanS ()
forall s. (s -> s) -> State s ()
modify ((CleanS -> CleanS) -> State CleanS ())
-> (CleanS -> CleanS) -> State CleanS ()
forall a b. (a -> b) -> a -> b
$ \CleanS
s -> CleanS
s {
sReloadedBy = addToUFM_C (++)
(sReloadedBy s)
(SSlot slot)
[blockId] }
data Store
= SSlot Int
| SReg Reg
isStoreReg :: Store -> Bool
isStoreReg :: Store -> Bool
isStoreReg Store
ss
= case Store
ss of
SSlot Int
_ -> Bool
False
SReg Reg
_ -> Bool
True
instance Uniquable Store where
getUnique :: Store -> Unique
getUnique (SReg Reg
r)
| RegReal (RealRegSingle Int
i) <- Reg
r
= Int -> Unique
mkRegSingleUnique Int
i
| Bool
otherwise
= String -> Unique
forall a. HasCallStack => String -> a
error (String -> Unique) -> String -> Unique
forall a b. (a -> b) -> a -> b
$ String
"RegSpillClean.getUnique: found virtual reg during spill clean,"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"only real regs expected."
getUnique (SSlot Int
i) = Int -> Unique
mkRegSubUnique Int
i
instance Outputable Store where
ppr :: Store -> SDoc
ppr (SSlot Int
i) = String -> SDoc
forall doc. IsLine doc => String -> doc
text String
"slot" SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> Int -> SDoc
forall doc. IsLine doc => Int -> doc
int Int
i
ppr (SReg Reg
r) = Reg -> SDoc
forall a. Outputable a => a -> SDoc
ppr Reg
r
type Assoc a = UniqFM a (UniqSet a)
emptyAssoc :: Assoc a
emptyAssoc :: forall a. Assoc a
emptyAssoc = UniqFM a (UniqSet a)
forall {k} (key :: k) elt. UniqFM key elt
emptyUFM
addAssoc :: Store -> Store -> Assoc Store -> Assoc Store
addAssoc :: Store -> Store -> Assoc Store -> Assoc Store
addAssoc Store
a Store
b Assoc Store
m
= let m1 :: Assoc Store
m1 = (UniqSet Store -> UniqSet Store -> UniqSet Store)
-> Assoc Store -> Store -> UniqSet Store -> Assoc Store
forall key elt.
Uniquable key =>
(elt -> elt -> elt)
-> UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM_C UniqSet Store -> UniqSet Store -> UniqSet Store
forall a. UniqSet a -> UniqSet a -> UniqSet a
unionUniqSets Assoc Store
m Store
a (Store -> UniqSet Store
forall a. Uniquable a => a -> UniqSet a
unitUniqSet Store
b)
m2 :: Assoc Store
m2 = (UniqSet Store -> UniqSet Store -> UniqSet Store)
-> Assoc Store -> Store -> UniqSet Store -> Assoc Store
forall key elt.
Uniquable key =>
(elt -> elt -> elt)
-> UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM_C UniqSet Store -> UniqSet Store -> UniqSet Store
forall a. UniqSet a -> UniqSet a -> UniqSet a
unionUniqSets Assoc Store
m1 Store
b (Store -> UniqSet Store
forall a. Uniquable a => a -> UniqSet a
unitUniqSet Store
a)
in Assoc Store
m2
delAssoc :: Store -> Assoc Store -> Assoc Store
delAssoc :: Store -> Assoc Store -> Assoc Store
delAssoc Store
a Assoc Store
m
| Just UniqSet Store
aSet <- Assoc Store -> Store -> Maybe (UniqSet Store)
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM Assoc Store
m Store
a
, Assoc Store
m1 <- Assoc Store -> Store -> Assoc Store
forall key elt.
Uniquable key =>
UniqFM key elt -> key -> UniqFM key elt
delFromUFM Assoc Store
m Store
a
= (Store -> Assoc Store -> Assoc Store)
-> Assoc Store -> UniqSet Store -> Assoc Store
forall elt a. (elt -> a -> a) -> a -> UniqSet elt -> a
nonDetStrictFoldUniqSet (\Store
x Assoc Store
m -> Store -> Store -> Assoc Store -> Assoc Store
delAssoc1 Store
x Store
a Assoc Store
m) Assoc Store
m1 UniqSet Store
aSet
| Bool
otherwise = Assoc Store
m
delAssoc1 :: Store -> Store -> Assoc Store -> Assoc Store
delAssoc1 :: Store -> Store -> Assoc Store -> Assoc Store
delAssoc1 Store
a Store
b Assoc Store
m
| Just UniqSet Store
aSet <- Assoc Store -> Store -> Maybe (UniqSet Store)
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM Assoc Store
m Store
a
= Assoc Store -> Store -> UniqSet Store -> Assoc Store
forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM Assoc Store
m Store
a (UniqSet Store -> Store -> UniqSet Store
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
delOneFromUniqSet UniqSet Store
aSet Store
b)
| Bool
otherwise = Assoc Store
m
elemAssoc :: Store -> Store -> Assoc Store -> Bool
elemAssoc :: Store -> Store -> Assoc Store -> Bool
elemAssoc Store
a Store
b Assoc Store
m
= Store -> UniqSet Store -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
elementOfUniqSet Store
b (Store -> Assoc Store -> UniqSet Store
closeAssoc Store
a Assoc Store
m)
closeAssoc :: Store -> Assoc Store -> UniqSet Store
closeAssoc :: Store -> Assoc Store -> UniqSet Store
closeAssoc Store
a Assoc Store
assoc
= Assoc Store -> UniqSet Store -> UniqSet Store -> UniqSet Store
forall {key}.
Uniquable key =>
UniqFM key (UniqSet key)
-> UniqSet key -> UniqSet key -> UniqSet key
closeAssoc' Assoc Store
assoc UniqSet Store
forall a. UniqSet a
emptyUniqSet (Store -> UniqSet Store
forall a. Uniquable a => a -> UniqSet a
unitUniqSet Store
a)
where
closeAssoc' :: UniqFM key (UniqSet key)
-> UniqSet key -> UniqSet key -> UniqSet key
closeAssoc' UniqFM key (UniqSet key)
assoc UniqSet key
visited UniqSet key
toVisit
= case UniqSet key -> [key]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet UniqSet key
toVisit of
[] -> UniqSet key
visited
(key
x:[key]
_)
| key -> UniqSet key -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
elementOfUniqSet key
x UniqSet key
visited
-> UniqFM key (UniqSet key)
-> UniqSet key -> UniqSet key -> UniqSet key
closeAssoc' UniqFM key (UniqSet key)
assoc UniqSet key
visited (UniqSet key -> key -> UniqSet key
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
delOneFromUniqSet UniqSet key
toVisit key
x)
| Bool
otherwise
-> let neighbors :: UniqSet key
neighbors
= case UniqFM key (UniqSet key) -> key -> Maybe (UniqSet key)
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM key (UniqSet key)
assoc key
x of
Maybe (UniqSet key)
Nothing -> UniqSet key
forall a. UniqSet a
emptyUniqSet
Just UniqSet key
set -> UniqSet key
set
in UniqFM key (UniqSet key)
-> UniqSet key -> UniqSet key -> UniqSet key
closeAssoc' UniqFM key (UniqSet key)
assoc
(UniqSet key -> key -> UniqSet key
forall a. Uniquable a => UniqSet a -> a -> UniqSet a
addOneToUniqSet UniqSet key
visited key
x)
(UniqSet key -> UniqSet key -> UniqSet key
forall a. UniqSet a -> UniqSet a -> UniqSet a
unionUniqSets UniqSet key
toVisit UniqSet key
neighbors)
intersectAssoc :: Assoc Store -> Assoc Store -> Assoc Store
intersectAssoc :: Assoc Store -> Assoc Store -> Assoc Store
intersectAssoc Assoc Store
a Assoc Store
b
= (UniqSet Store -> UniqSet Store -> UniqSet Store)
-> Assoc Store -> Assoc Store -> Assoc Store
forall {k} elt1 elt2 elt3 (key :: k).
(elt1 -> elt2 -> elt3)
-> UniqFM key elt1 -> UniqFM key elt2 -> UniqFM key elt3
intersectUFM_C (UniqSet Store -> UniqSet Store -> UniqSet Store
forall a. UniqSet a -> UniqSet a -> UniqSet a
intersectUniqSets) Assoc Store
a Assoc Store
b