{-# LANGUAGE ScopedTypeVariables, GADTs, BangPatterns #-}
module GHC.CmmToAsm.Reg.Graph.SpillCost (
SpillCostRecord,
plusSpillCostRecord,
pprSpillCostRecord,
SpillCostInfo,
zeroSpillCostInfo,
plusSpillCostInfo,
slurpSpillCostInfo,
chooseSpill,
lifeMapFromSpillCostInfo
) where
import GHC.Prelude
import GHC.CmmToAsm.Reg.Liveness
import GHC.CmmToAsm.Instr
import GHC.Platform.Reg.Class
import GHC.Platform.Reg
import GHC.Data.Graph.Base
import GHC.Cmm.Dataflow.Collections (mapLookup)
import GHC.Cmm.Dataflow.Label
import GHC.Cmm
import GHC.Types.Unique.FM
import GHC.Types.Unique.Set
import GHC.Data.Graph.Directed (flattenSCCs)
import GHC.Utils.Outputable
import GHC.Platform
import GHC.Utils.Monad.State
import GHC.CmmToAsm.CFG
import Data.List (nub, minimumBy)
import Data.Maybe
import Control.Monad (join)
type SpillCostRecord
= ( VirtualReg
, Int
, Int
, Int)
type SpillCostInfo
= UniqFM SpillCostRecord
type SpillCostState = State (UniqFM SpillCostRecord) ()
zeroSpillCostInfo :: SpillCostInfo
zeroSpillCostInfo :: SpillCostInfo
zeroSpillCostInfo = SpillCostInfo
forall elt. UniqFM elt
emptyUFM
plusSpillCostInfo :: SpillCostInfo -> SpillCostInfo -> SpillCostInfo
plusSpillCostInfo :: SpillCostInfo -> SpillCostInfo -> SpillCostInfo
plusSpillCostInfo SpillCostInfo
sc1 SpillCostInfo
sc2
= (SpillCostRecord -> SpillCostRecord -> SpillCostRecord)
-> SpillCostInfo -> SpillCostInfo -> SpillCostInfo
forall elt.
(elt -> elt -> elt) -> UniqFM elt -> UniqFM elt -> UniqFM elt
plusUFM_C SpillCostRecord -> SpillCostRecord -> SpillCostRecord
plusSpillCostRecord SpillCostInfo
sc1 SpillCostInfo
sc2
plusSpillCostRecord :: SpillCostRecord -> SpillCostRecord -> SpillCostRecord
plusSpillCostRecord :: SpillCostRecord -> SpillCostRecord -> SpillCostRecord
plusSpillCostRecord (VirtualReg
r1, Int
a1, Int
b1, Int
c1) (VirtualReg
r2, Int
a2, Int
b2, Int
c2)
| VirtualReg
r1 VirtualReg -> VirtualReg -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq VirtualReg
== VirtualReg
r2 = (VirtualReg
r1, Int
a1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
a2, Int
b1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
b2, Int
c1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
c2)
| Bool
otherwise = [Char] -> SpillCostRecord
forall a. HasCallStack => [Char] -> a
error [Char]
"RegSpillCost.plusRegInt: regs don't match"
slurpSpillCostInfo :: forall instr statics. (Outputable instr, Instruction instr)
=> Platform
-> Maybe CFG
-> LiveCmmDecl statics instr
-> SpillCostInfo
slurpSpillCostInfo :: Platform -> Maybe CFG -> LiveCmmDecl statics instr -> SpillCostInfo
slurpSpillCostInfo Platform
platform Maybe CFG
cfg LiveCmmDecl statics instr
cmm
= State SpillCostInfo () -> SpillCostInfo -> SpillCostInfo
forall s a. State s a -> s -> s
execState (LiveCmmDecl statics instr -> State SpillCostInfo ()
countCmm LiveCmmDecl statics instr
cmm) SpillCostInfo
zeroSpillCostInfo
where
countCmm :: LiveCmmDecl statics instr -> State SpillCostInfo ()
countCmm CmmData{} = () -> State SpillCostInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (State s)
return ()
countCmm (CmmProc LiveInfo
info CLabel
_ [GlobalReg]
_ [SCC (GenBasicBlock (LiveInstr instr))]
sccs)
= (GenBasicBlock (LiveInstr instr) -> State SpillCostInfo ())
-> [GenBasicBlock (LiveInstr instr)] -> State SpillCostInfo ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type forall s. Monad (State s)
External instance of the constraint type Foldable []
mapM_ (LiveInfo
-> Maybe (LabelMap Double)
-> GenBasicBlock (LiveInstr instr)
-> State SpillCostInfo ()
countBlock LiveInfo
info Maybe (LabelMap Double)
freqMap)
([GenBasicBlock (LiveInstr instr)] -> State SpillCostInfo ())
-> [GenBasicBlock (LiveInstr instr)] -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ [SCC (GenBasicBlock (LiveInstr instr))]
-> [GenBasicBlock (LiveInstr instr)]
forall a. [SCC a] -> [a]
flattenSCCs [SCC (GenBasicBlock (LiveInstr instr))]
sccs
where
LiveInfo LabelMap RawCmmStatics
_ [BlockId]
entries BlockMap RegSet
_ BlockMap IntSet
_ = LiveInfo
info
freqMap :: Maybe (LabelMap Double)
freqMap = ((LabelMap Double, LabelMap (LabelMap Double)) -> LabelMap Double
forall a b. (a, b) -> a
fst ((LabelMap Double, LabelMap (LabelMap Double)) -> LabelMap Double)
-> (CFG -> (LabelMap Double, LabelMap (LabelMap Double)))
-> CFG
-> LabelMap Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasDebugCallStack =>
BlockId -> CFG -> (LabelMap Double, LabelMap (LabelMap Double))
BlockId -> CFG -> (LabelMap Double, LabelMap (LabelMap Double))
External instance of the constraint type HasDebugCallStack
mkGlobalWeights ([BlockId] -> BlockId
forall a. [a] -> a
head [BlockId]
entries)) (CFG -> LabelMap Double) -> Maybe CFG -> Maybe (LabelMap Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$> Maybe CFG
cfg
countBlock :: LiveInfo
-> Maybe (LabelMap Double)
-> GenBasicBlock (LiveInstr instr)
-> State SpillCostInfo ()
countBlock LiveInfo
info Maybe (LabelMap Double)
freqMap (BasicBlock BlockId
blockId [LiveInstr instr]
instrs)
| LiveInfo LabelMap RawCmmStatics
_ [BlockId]
_ BlockMap RegSet
blockLive BlockMap IntSet
_ <- LiveInfo
info
, Just RegSet
rsLiveEntry <- KeyOf LabelMap -> BlockMap RegSet -> Maybe RegSet
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup KeyOf LabelMap
BlockId
blockId BlockMap RegSet
blockLive
, UniqSet VirtualReg
rsLiveEntry_virt <- RegSet -> UniqSet VirtualReg
takeVirtuals RegSet
rsLiveEntry
= Int
-> UniqSet VirtualReg
-> [LiveInstr instr]
-> State SpillCostInfo ()
countLIs (Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
External instance of the constraint type Integral Int
External instance of the constraint type RealFrac Double
ceiling (Double -> Int) -> Double -> Int
forall a b. (a -> b) -> a -> b
$ Maybe (LabelMap Double) -> BlockId -> Double
blockFreq Maybe (LabelMap Double)
freqMap BlockId
blockId) UniqSet VirtualReg
rsLiveEntry_virt [LiveInstr instr]
instrs
| Bool
otherwise
= [Char] -> State SpillCostInfo ()
forall a. HasCallStack => [Char] -> a
error [Char]
"RegAlloc.SpillCost.slurpSpillCostInfo: bad block"
countLIs :: Int -> UniqSet VirtualReg -> [LiveInstr instr] -> SpillCostState
countLIs :: Int
-> UniqSet VirtualReg
-> [LiveInstr instr]
-> State SpillCostInfo ()
countLIs Int
_ UniqSet VirtualReg
_ []
= () -> State SpillCostInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall s. Monad (State s)
return ()
countLIs Int
scale UniqSet VirtualReg
rsLive (LiveInstr InstrSR instr
instr Maybe Liveness
Nothing : [LiveInstr instr]
lis)
| InstrSR instr -> Bool
forall instr. Instruction instr => instr -> Bool
External instance of the constraint type forall instr. Instruction instr => Instruction (InstrSR instr)
Evidence bound by a type signature of the constraint type Instruction instr
isMetaInstr InstrSR instr
instr
= Int
-> UniqSet VirtualReg
-> [LiveInstr instr]
-> State SpillCostInfo ()
countLIs Int
scale UniqSet VirtualReg
rsLive [LiveInstr instr]
lis
| Bool
otherwise
= [Char] -> SDoc -> State SpillCostInfo ()
forall a. HasCallStack => [Char] -> SDoc -> a
pprPanic [Char]
"RegSpillCost.slurpSpillCostInfo"
(SDoc -> State SpillCostInfo ()) -> SDoc -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ [Char] -> SDoc
text [Char]
"no liveness information on instruction " SDoc -> SDoc -> SDoc
<> InstrSR instr -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall instr. Outputable instr => Outputable (InstrSR instr)
Evidence bound by a type signature of the constraint type Outputable instr
ppr InstrSR instr
instr
countLIs Int
scale UniqSet VirtualReg
rsLiveEntry (LiveInstr InstrSR instr
instr (Just Liveness
live) : [LiveInstr instr]
lis)
= do
(VirtualReg -> State SpillCostInfo ())
-> [VirtualReg] -> State SpillCostInfo ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type forall s. Monad (State s)
External instance of the constraint type Foldable []
mapM_ VirtualReg -> State SpillCostInfo ()
incLifetime ([VirtualReg] -> State SpillCostInfo ())
-> [VirtualReg] -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ UniqSet VirtualReg -> [VirtualReg]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet UniqSet VirtualReg
rsLiveEntry
let (RU [Reg]
read [Reg]
written) = Platform -> InstrSR instr -> RegUsage
forall instr. Instruction instr => Platform -> instr -> RegUsage
External instance of the constraint type forall instr. Instruction instr => Instruction (InstrSR instr)
Evidence bound by a type signature of the constraint type Instruction instr
regUsageOfInstr Platform
platform InstrSR instr
instr
(VirtualReg -> State SpillCostInfo ())
-> [VirtualReg] -> State SpillCostInfo ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type forall s. Monad (State s)
External instance of the constraint type Foldable []
mapM_ (Int -> VirtualReg -> State SpillCostInfo ()
incUses Int
scale) ([VirtualReg] -> State SpillCostInfo ())
-> [VirtualReg] -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ [Maybe VirtualReg] -> [VirtualReg]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe VirtualReg] -> [VirtualReg])
-> [Maybe VirtualReg] -> [VirtualReg]
forall a b. (a -> b) -> a -> b
$ (Reg -> Maybe VirtualReg) -> [Reg] -> [Maybe VirtualReg]
forall a b. (a -> b) -> [a] -> [b]
map Reg -> Maybe VirtualReg
takeVirtualReg ([Reg] -> [Maybe VirtualReg]) -> [Reg] -> [Maybe VirtualReg]
forall a b. (a -> b) -> a -> b
$ [Reg] -> [Reg]
forall a. Eq a => [a] -> [a]
External instance of the constraint type Eq Reg
nub [Reg]
read
(VirtualReg -> State SpillCostInfo ())
-> [VirtualReg] -> State SpillCostInfo ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
External instance of the constraint type forall s. Monad (State s)
External instance of the constraint type Foldable []
mapM_ (Int -> VirtualReg -> State SpillCostInfo ()
incDefs Int
scale) ([VirtualReg] -> State SpillCostInfo ())
-> [VirtualReg] -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ [Maybe VirtualReg] -> [VirtualReg]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe VirtualReg] -> [VirtualReg])
-> [Maybe VirtualReg] -> [VirtualReg]
forall a b. (a -> b) -> a -> b
$ (Reg -> Maybe VirtualReg) -> [Reg] -> [Maybe VirtualReg]
forall a b. (a -> b) -> [a] -> [b]
map Reg -> Maybe VirtualReg
takeVirtualReg ([Reg] -> [Maybe VirtualReg]) -> [Reg] -> [Maybe VirtualReg]
forall a b. (a -> b) -> a -> b
$ [Reg] -> [Reg]
forall a. Eq a => [a] -> [a]
External instance of the constraint type Eq Reg
nub [Reg]
written
let liveDieRead_virt :: UniqSet VirtualReg
liveDieRead_virt = RegSet -> UniqSet VirtualReg
takeVirtuals (Liveness -> RegSet
liveDieRead Liveness
live)
let liveDieWrite_virt :: UniqSet VirtualReg
liveDieWrite_virt = RegSet -> UniqSet VirtualReg
takeVirtuals (Liveness -> RegSet
liveDieWrite Liveness
live)
let liveBorn_virt :: UniqSet VirtualReg
liveBorn_virt = RegSet -> UniqSet VirtualReg
takeVirtuals (Liveness -> RegSet
liveBorn Liveness
live)
let rsLiveAcross :: UniqSet VirtualReg
rsLiveAcross
= UniqSet VirtualReg
rsLiveEntry UniqSet VirtualReg -> UniqSet VirtualReg -> UniqSet VirtualReg
forall a. UniqSet a -> UniqSet a -> UniqSet a
`minusUniqSet` UniqSet VirtualReg
liveDieRead_virt
let rsLiveNext :: UniqSet VirtualReg
rsLiveNext
= (UniqSet VirtualReg
rsLiveAcross UniqSet VirtualReg -> UniqSet VirtualReg -> UniqSet VirtualReg
forall a. UniqSet a -> UniqSet a -> UniqSet a
`unionUniqSets` UniqSet VirtualReg
liveBorn_virt)
UniqSet VirtualReg -> UniqSet VirtualReg -> UniqSet VirtualReg
forall a. UniqSet a -> UniqSet a -> UniqSet a
`minusUniqSet` UniqSet VirtualReg
liveDieWrite_virt
Int
-> UniqSet VirtualReg
-> [LiveInstr instr]
-> State SpillCostInfo ()
countLIs Int
scale UniqSet VirtualReg
rsLiveNext [LiveInstr instr]
lis
incDefs :: Int -> VirtualReg -> State SpillCostInfo ()
incDefs Int
count VirtualReg
reg = (SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ()
forall s. (s -> s) -> State s ()
modify ((SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ())
-> (SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ \SpillCostInfo
s -> (SpillCostRecord -> SpillCostRecord -> SpillCostRecord)
-> SpillCostInfo -> VirtualReg -> SpillCostRecord -> SpillCostInfo
forall key elt.
Uniquable key =>
(elt -> elt -> elt) -> UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM_C SpillCostRecord -> SpillCostRecord -> SpillCostRecord
plusSpillCostRecord SpillCostInfo
s VirtualReg
reg (VirtualReg
reg, Int
count, Int
0, Int
0)
incUses :: Int -> VirtualReg -> State SpillCostInfo ()
incUses Int
count VirtualReg
reg = (SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ()
forall s. (s -> s) -> State s ()
modify ((SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ())
-> (SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ \SpillCostInfo
s -> (SpillCostRecord -> SpillCostRecord -> SpillCostRecord)
-> SpillCostInfo -> VirtualReg -> SpillCostRecord -> SpillCostInfo
forall key elt.
Uniquable key =>
(elt -> elt -> elt) -> UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM_C SpillCostRecord -> SpillCostRecord -> SpillCostRecord
plusSpillCostRecord SpillCostInfo
s VirtualReg
reg (VirtualReg
reg, Int
0, Int
count, Int
0)
incLifetime :: VirtualReg -> State SpillCostInfo ()
incLifetime VirtualReg
reg = (SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ()
forall s. (s -> s) -> State s ()
modify ((SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ())
-> (SpillCostInfo -> SpillCostInfo) -> State SpillCostInfo ()
forall a b. (a -> b) -> a -> b
$ \SpillCostInfo
s -> (SpillCostRecord -> SpillCostRecord -> SpillCostRecord)
-> SpillCostInfo -> VirtualReg -> SpillCostRecord -> SpillCostInfo
forall key elt.
Uniquable key =>
(elt -> elt -> elt) -> UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM_C SpillCostRecord -> SpillCostRecord -> SpillCostRecord
plusSpillCostRecord SpillCostInfo
s VirtualReg
reg (VirtualReg
reg, Int
0, Int
0, Int
1)
blockFreq :: Maybe (LabelMap Double) -> Label -> Double
blockFreq :: Maybe (LabelMap Double) -> BlockId -> Double
blockFreq Maybe (LabelMap Double)
freqs BlockId
bid
| Just Double
freq <- Maybe (Maybe Double) -> Maybe Double
forall (m :: * -> *) a. Monad m => m (m a) -> m a
External instance of the constraint type Monad Maybe
join (KeyOf LabelMap -> LabelMap Double -> Maybe Double
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup KeyOf LabelMap
BlockId
bid (LabelMap Double -> Maybe Double)
-> Maybe (LabelMap Double) -> Maybe (Maybe Double)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
<$> Maybe (LabelMap Double)
freqs)
= Double -> Double -> Double
forall a. Ord a => a -> a -> a
External instance of the constraint type Ord Double
max Double
1.0 (Double
10000 Double -> Double -> Double
forall a. Num a => a -> a -> a
External instance of the constraint type Num Double
* Double
freq)
| Bool
otherwise
= Double
1.0
takeVirtuals :: UniqSet Reg -> UniqSet VirtualReg
takeVirtuals :: RegSet -> UniqSet VirtualReg
takeVirtuals RegSet
set = [VirtualReg] -> UniqSet VirtualReg
forall a. Uniquable a => [a] -> UniqSet a
External instance of the constraint type Uniquable VirtualReg
mkUniqSet
[ VirtualReg
vr | RegVirtual VirtualReg
vr <- RegSet -> [Reg]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet RegSet
set ]
chooseSpill
:: SpillCostInfo
-> Graph VirtualReg RegClass RealReg
-> VirtualReg
chooseSpill :: SpillCostInfo -> Graph VirtualReg RegClass RealReg -> VirtualReg
chooseSpill SpillCostInfo
info Graph VirtualReg RegClass RealReg
graph
= let cost :: VirtualReg -> Float
cost = SpillCostInfo
-> Graph VirtualReg RegClass RealReg -> VirtualReg -> Float
spillCost_length SpillCostInfo
info Graph VirtualReg RegClass RealReg
graph
node :: Node VirtualReg RegClass RealReg
node = (Node VirtualReg RegClass RealReg
-> Node VirtualReg RegClass RealReg -> Ordering)
-> [Node VirtualReg RegClass RealReg]
-> Node VirtualReg RegClass RealReg
forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
External instance of the constraint type Foldable []
minimumBy (\Node VirtualReg RegClass RealReg
n1 Node VirtualReg RegClass RealReg
n2 -> Float -> Float -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Float
compare (VirtualReg -> Float
cost (VirtualReg -> Float) -> VirtualReg -> Float
forall a b. (a -> b) -> a -> b
$ Node VirtualReg RegClass RealReg -> VirtualReg
forall k cls color. Node k cls color -> k
nodeId Node VirtualReg RegClass RealReg
n1) (VirtualReg -> Float
cost (VirtualReg -> Float) -> VirtualReg -> Float
forall a b. (a -> b) -> a -> b
$ Node VirtualReg RegClass RealReg -> VirtualReg
forall k cls color. Node k cls color -> k
nodeId Node VirtualReg RegClass RealReg
n2))
([Node VirtualReg RegClass RealReg]
-> Node VirtualReg RegClass RealReg)
-> [Node VirtualReg RegClass RealReg]
-> Node VirtualReg RegClass RealReg
forall a b. (a -> b) -> a -> b
$ UniqFM (Node VirtualReg RegClass RealReg)
-> [Node VirtualReg RegClass RealReg]
forall elt. UniqFM elt -> [elt]
nonDetEltsUFM (UniqFM (Node VirtualReg RegClass RealReg)
-> [Node VirtualReg RegClass RealReg])
-> UniqFM (Node VirtualReg RegClass RealReg)
-> [Node VirtualReg RegClass RealReg]
forall a b. (a -> b) -> a -> b
$ Graph VirtualReg RegClass RealReg
-> UniqFM (Node VirtualReg RegClass RealReg)
forall k cls color. Graph k cls color -> UniqFM (Node k cls color)
graphMap Graph VirtualReg RegClass RealReg
graph
in Node VirtualReg RegClass RealReg -> VirtualReg
forall k cls color. Node k cls color -> k
nodeId Node VirtualReg RegClass RealReg
node
spillCost_length
:: SpillCostInfo
-> Graph VirtualReg RegClass RealReg
-> VirtualReg
-> Float
spillCost_length :: SpillCostInfo
-> Graph VirtualReg RegClass RealReg -> VirtualReg -> Float
spillCost_length SpillCostInfo
info Graph VirtualReg RegClass RealReg
_ VirtualReg
reg
| Int
lifetime Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
1 = Float
1Float -> Float -> Float
forall a. Fractional a => a -> a -> a
External instance of the constraint type Fractional Float
/Float
0
| Bool
otherwise = Float
1 Float -> Float -> Float
forall a. Fractional a => a -> a -> a
External instance of the constraint type Fractional Float
/ Int -> Float
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Float
External instance of the constraint type Integral Int
fromIntegral Int
lifetime
where (VirtualReg
_, Int
_, Int
_, Int
lifetime)
= SpillCostRecord -> Maybe SpillCostRecord -> SpillCostRecord
forall a. a -> Maybe a -> a
fromMaybe (VirtualReg
reg, Int
0, Int
0, Int
0)
(Maybe SpillCostRecord -> SpillCostRecord)
-> Maybe SpillCostRecord -> SpillCostRecord
forall a b. (a -> b) -> a -> b
$ SpillCostInfo -> VirtualReg -> Maybe SpillCostRecord
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable VirtualReg
lookupUFM SpillCostInfo
info VirtualReg
reg
lifeMapFromSpillCostInfo :: SpillCostInfo -> UniqFM (VirtualReg, Int)
lifeMapFromSpillCostInfo :: SpillCostInfo -> UniqFM (VirtualReg, Int)
lifeMapFromSpillCostInfo SpillCostInfo
info
= [(VirtualReg, (VirtualReg, Int))] -> UniqFM (VirtualReg, Int)
forall key elt. Uniquable key => [(key, elt)] -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
listToUFM
([(VirtualReg, (VirtualReg, Int))] -> UniqFM (VirtualReg, Int))
-> [(VirtualReg, (VirtualReg, Int))] -> UniqFM (VirtualReg, Int)
forall a b. (a -> b) -> a -> b
$ (SpillCostRecord -> (VirtualReg, (VirtualReg, Int)))
-> [SpillCostRecord] -> [(VirtualReg, (VirtualReg, Int))]
forall a b. (a -> b) -> [a] -> [b]
map (\(VirtualReg
r, Int
_, Int
_, Int
life) -> (VirtualReg
r, (VirtualReg
r, Int
life)))
([SpillCostRecord] -> [(VirtualReg, (VirtualReg, Int))])
-> [SpillCostRecord] -> [(VirtualReg, (VirtualReg, Int))]
forall a b. (a -> b) -> a -> b
$ SpillCostInfo -> [SpillCostRecord]
forall elt. UniqFM elt -> [elt]
nonDetEltsUFM SpillCostInfo
info
nodeDegree
:: (VirtualReg -> RegClass)
-> Graph VirtualReg RegClass RealReg
-> VirtualReg
-> Int
nodeDegree :: (VirtualReg -> RegClass)
-> Graph VirtualReg RegClass RealReg -> VirtualReg -> Int
nodeDegree VirtualReg -> RegClass
classOfVirtualReg Graph VirtualReg RegClass RealReg
graph VirtualReg
reg
| Just Node VirtualReg RegClass RealReg
node <- UniqFM (Node VirtualReg RegClass RealReg)
-> VirtualReg -> Maybe (Node VirtualReg RegClass RealReg)
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable VirtualReg
lookupUFM (Graph VirtualReg RegClass RealReg
-> UniqFM (Node VirtualReg RegClass RealReg)
forall k cls color. Graph k cls color -> UniqFM (Node k cls color)
graphMap Graph VirtualReg RegClass RealReg
graph) VirtualReg
reg
, Int
virtConflicts
<- [VirtualReg] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
External instance of the constraint type Foldable []
length
([VirtualReg] -> Int) -> [VirtualReg] -> Int
forall a b. (a -> b) -> a -> b
$ (VirtualReg -> Bool) -> [VirtualReg] -> [VirtualReg]
forall a. (a -> Bool) -> [a] -> [a]
filter (\VirtualReg
r -> VirtualReg -> RegClass
classOfVirtualReg VirtualReg
r RegClass -> RegClass -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq RegClass
== VirtualReg -> RegClass
classOfVirtualReg VirtualReg
reg)
([VirtualReg] -> [VirtualReg]) -> [VirtualReg] -> [VirtualReg]
forall a b. (a -> b) -> a -> b
$ UniqSet VirtualReg -> [VirtualReg]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet
(UniqSet VirtualReg -> [VirtualReg])
-> UniqSet VirtualReg -> [VirtualReg]
forall a b. (a -> b) -> a -> b
$ Node VirtualReg RegClass RealReg -> UniqSet VirtualReg
forall k cls color. Node k cls color -> UniqSet k
nodeConflicts Node VirtualReg RegClass RealReg
node
= Int
virtConflicts Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ UniqSet RealReg -> Int
forall a. UniqSet a -> Int
sizeUniqSet (Node VirtualReg RegClass RealReg -> UniqSet RealReg
forall k cls color. Node k cls color -> UniqSet color
nodeExclusions Node VirtualReg RegClass RealReg
node)
| Bool
otherwise
= Int
0
pprSpillCostRecord
:: (VirtualReg -> RegClass)
-> (Reg -> SDoc)
-> Graph VirtualReg RegClass RealReg
-> SpillCostRecord
-> SDoc
pprSpillCostRecord :: (VirtualReg -> RegClass)
-> (Reg -> SDoc)
-> Graph VirtualReg RegClass RealReg
-> SpillCostRecord
-> SDoc
pprSpillCostRecord VirtualReg -> RegClass
regClass Reg -> SDoc
pprReg Graph VirtualReg RegClass RealReg
graph (VirtualReg
reg, Int
uses, Int
defs, Int
life)
= [SDoc] -> SDoc
hsep
[ Reg -> SDoc
pprReg (VirtualReg -> Reg
RegVirtual VirtualReg
reg)
, Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Int
ppr Int
uses
, Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Int
ppr Int
defs
, Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Int
ppr Int
life
, Int -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Int
ppr (Int -> SDoc) -> Int -> SDoc
forall a b. (a -> b) -> a -> b
$ (VirtualReg -> RegClass)
-> Graph VirtualReg RegClass RealReg -> VirtualReg -> Int
nodeDegree VirtualReg -> RegClass
regClass Graph VirtualReg RegClass RealReg
graph VirtualReg
reg
, [Char] -> SDoc
text ([Char] -> SDoc) -> [Char] -> SDoc
forall a b. (a -> b) -> a -> b
$ Float -> [Char]
forall a. Show a => a -> [Char]
External instance of the constraint type Show Float
show (Float -> [Char]) -> Float -> [Char]
forall a b. (a -> b) -> a -> b
$ (Int -> Float
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Float
External instance of the constraint type Integral Int
fromIntegral (Int
uses Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
defs)
Float -> Float -> Float
forall a. Fractional a => a -> a -> a
External instance of the constraint type Fractional Float
/ Int -> Float
forall a b. (Integral a, Num b) => a -> b
External instance of the constraint type Num Float
External instance of the constraint type Integral Int
fromIntegral ((VirtualReg -> RegClass)
-> Graph VirtualReg RegClass RealReg -> VirtualReg -> Int
nodeDegree VirtualReg -> RegClass
regClass Graph VirtualReg RegClass RealReg
graph VirtualReg
reg) :: Float) ]