{-# LANGUAGE BangPatterns, CPP, ScopedTypeVariables #-}
{-# LANGUAGE ConstraintKinds #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.CmmToAsm.Reg.Linear (
regAlloc,
module GHC.CmmToAsm.Reg.Linear.Base,
module GHC.CmmToAsm.Reg.Linear.Stats
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.CmmToAsm.Reg.Linear.State
import GHC.CmmToAsm.Reg.Linear.Base
import GHC.CmmToAsm.Reg.Linear.StackMap
import GHC.CmmToAsm.Reg.Linear.FreeRegs
import GHC.CmmToAsm.Reg.Linear.Stats
import GHC.CmmToAsm.Reg.Linear.JoinToTargets
import qualified GHC.CmmToAsm.Reg.Linear.PPC as PPC
import qualified GHC.CmmToAsm.Reg.Linear.SPARC as SPARC
import qualified GHC.CmmToAsm.Reg.Linear.X86 as X86
import qualified GHC.CmmToAsm.Reg.Linear.X86_64 as X86_64
import qualified GHC.CmmToAsm.Reg.Linear.AArch64 as AArch64
import GHC.CmmToAsm.Reg.Target
import GHC.CmmToAsm.Reg.Liveness
import GHC.CmmToAsm.Reg.Utils
import GHC.CmmToAsm.Instr
import GHC.CmmToAsm.Config
import GHC.CmmToAsm.Types
import GHC.Platform.Reg
import GHC.Platform.Reg.Class (RegClass(..))
import GHC.Cmm.BlockId
import GHC.Cmm.Dataflow.Collections
import GHC.Cmm hiding (RegSet)
import GHC.Data.Graph.Directed
import GHC.Types.Unique
import GHC.Types.Unique.Set
import GHC.Types.Unique.FM
import GHC.Types.Unique.Supply
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Platform
import Data.Maybe
import Data.List (partition, nub)
import Control.Monad
regAlloc
:: Instruction instr
=> NCGConfig
-> LiveCmmDecl statics instr
-> UniqSM ( NatCmmDecl statics instr
, Maybe Int
, Maybe RegAllocStats
)
regAlloc :: forall instr statics.
Instruction instr =>
NCGConfig
-> LiveCmmDecl statics instr
-> UniqSM
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
regAlloc NCGConfig
_ (CmmData Section
sec statics
d)
= forall (m :: * -> *) a. Monad m => a -> m a
return
( forall d h g. Section -> d -> GenCmmDecl d h g
CmmData Section
sec statics
d
, forall a. Maybe a
Nothing
, forall a. Maybe a
Nothing )
regAlloc NCGConfig
_ (CmmProc (LiveInfo LabelMap RawCmmStatics
info [BlockId]
_ BlockMap RegSet
_ BlockMap IntSet
_) CLabel
lbl [GlobalReg]
live [])
= forall (m :: * -> *) a. Monad m => a -> m a
return ( forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalReg]
live (forall i. [GenBasicBlock i] -> ListGraph i
ListGraph [])
, forall a. Maybe a
Nothing
, forall a. Maybe a
Nothing )
regAlloc NCGConfig
config (CmmProc LiveInfo
static CLabel
lbl [GlobalReg]
live [SCC (LiveBasicBlock instr)]
sccs)
| LiveInfo LabelMap RawCmmStatics
info entry_ids :: [BlockId]
entry_ids@(BlockId
first_id:[BlockId]
_) BlockMap RegSet
block_live BlockMap IntSet
_ <- LiveInfo
static
= do
!(![NatBasicBlock instr]
final_blocks, !RegAllocStats
stats, !Int
stack_use)
<- forall instr.
Instruction instr =>
NCGConfig
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc NCGConfig
config [BlockId]
entry_ids BlockMap RegSet
block_live [SCC (LiveBasicBlock instr)]
sccs
let !(!(!NatBasicBlock instr
first':[NatBasicBlock instr]
_), ![NatBasicBlock instr]
rest')
= forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((forall a. Eq a => a -> a -> Bool
== BlockId
first_id) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i. GenBasicBlock i -> BlockId
blockId) [NatBasicBlock instr]
final_blocks
let max_spill_slots :: Int
max_spill_slots = NCGConfig -> Int
maxSpillSlots NCGConfig
config
extra_stack :: Maybe Int
extra_stack
| Int
stack_use forall a. Ord a => a -> a -> Bool
> Int
max_spill_slots
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! Int
stack_use forall a. Num a => a -> a -> a
- Int
max_spill_slots
| Bool
otherwise
= forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return ( forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalReg]
live (forall i. [GenBasicBlock i] -> ListGraph i
ListGraph (NatBasicBlock instr
first' forall a. a -> [a] -> [a]
: [NatBasicBlock instr]
rest'))
, Maybe Int
extra_stack
, forall a. a -> Maybe a
Just RegAllocStats
stats)
regAlloc NCGConfig
_ (CmmProc LiveInfo
_ CLabel
_ [GlobalReg]
_ [SCC (LiveBasicBlock instr)]
_)
= forall a. String -> a
panic String
"RegAllocLinear.regAlloc: no match"
linearRegAlloc
:: forall instr. (Instruction instr)
=> NCGConfig
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc :: forall instr.
Instruction instr =>
NCGConfig
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc NCGConfig
config [BlockId]
entry_ids BlockMap RegSet
block_live [SCC (LiveBasicBlock instr)]
sccs
= case Platform -> Arch
platformArch Platform
platform of
Arch
ArchX86 -> forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go forall a b. (a -> b) -> a -> b
$ (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform :: X86.FreeRegs)
Arch
ArchX86_64 -> forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go forall a b. (a -> b) -> a -> b
$ (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform :: X86_64.FreeRegs)
Arch
ArchS390X -> forall a. String -> a
panic String
"linearRegAlloc ArchS390X"
Arch
ArchSPARC -> forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go forall a b. (a -> b) -> a -> b
$ (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform :: SPARC.FreeRegs)
Arch
ArchSPARC64 -> forall a. String -> a
panic String
"linearRegAlloc ArchSPARC64"
Arch
ArchPPC -> forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go forall a b. (a -> b) -> a -> b
$ (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform :: PPC.FreeRegs)
ArchARM ArmISA
_ [ArmISAExt]
_ ArmABI
_ -> forall a. String -> a
panic String
"linearRegAlloc ArchARM"
Arch
ArchAArch64 -> forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go forall a b. (a -> b) -> a -> b
$ (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform :: AArch64.FreeRegs)
ArchPPC_64 PPC_64ABI
_ -> forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go forall a b. (a -> b) -> a -> b
$ (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform :: PPC.FreeRegs)
Arch
ArchAlpha -> forall a. String -> a
panic String
"linearRegAlloc ArchAlpha"
Arch
ArchMipseb -> forall a. String -> a
panic String
"linearRegAlloc ArchMipseb"
Arch
ArchMipsel -> forall a. String -> a
panic String
"linearRegAlloc ArchMipsel"
Arch
ArchRISCV64 -> forall a. String -> a
panic String
"linearRegAlloc ArchRISCV64"
Arch
ArchJavaScript -> forall a. String -> a
panic String
"linearRegAlloc ArchJavaScript"
Arch
ArchUnknown -> forall a. String -> a
panic String
"linearRegAlloc ArchUnknown"
where
go :: (FR regs, Outputable regs)
=> regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go :: forall regs.
(FR regs, Outputable regs) =>
regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go regs
f = forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
NCGConfig
-> freeRegs
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc' NCGConfig
config regs
f [BlockId]
entry_ids BlockMap RegSet
block_live [SCC (LiveBasicBlock instr)]
sccs
platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
type OutputableRegConstraint freeRegs instr =
(FR freeRegs, Outputable freeRegs, Instruction instr)
linearRegAlloc'
:: OutputableRegConstraint freeRegs instr
=> NCGConfig
-> freeRegs
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc' :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
NCGConfig
-> freeRegs
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc' NCGConfig
config freeRegs
initFreeRegs [BlockId]
entry_ids BlockMap RegSet
block_live [SCC (LiveBasicBlock instr)]
sccs
= do UniqSupply
us <- forall (m :: * -> *). MonadUnique m => m UniqSupply
getUniqueSupplyM
let !(BlockAssignment freeRegs
_, !StackMap
stack, !RegAllocStats
stats, ![NatBasicBlock instr]
blocks) =
forall freeRegs a.
NCGConfig
-> BlockAssignment freeRegs
-> freeRegs
-> RegMap Loc
-> StackMap
-> UniqSupply
-> RegM freeRegs a
-> (BlockAssignment freeRegs, StackMap, RegAllocStats, a)
runR NCGConfig
config forall freeRegs. BlockAssignment freeRegs
emptyBlockAssignment freeRegs
initFreeRegs forall a. RegMap a
emptyRegMap StackMap
emptyStackMap UniqSupply
us
forall a b. (a -> b) -> a -> b
$ forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live [] [SCC (LiveBasicBlock instr)]
sccs
forall (m :: * -> *) a. Monad m => a -> m a
return ([NatBasicBlock instr]
blocks, RegAllocStats
stats, StackMap -> Int
getStackUse StackMap
stack)
linearRA_SCCs :: OutputableRegConstraint freeRegs instr
=> [BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
linearRA_SCCs :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
linearRA_SCCs [BlockId]
_ BlockMap RegSet
_ [NatBasicBlock instr]
blocksAcc []
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [NatBasicBlock instr]
blocksAcc
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live [NatBasicBlock instr]
blocksAcc (AcyclicSCC LiveBasicBlock instr
block : [SCC (LiveBasicBlock instr)]
sccs)
= do [NatBasicBlock instr]
blocks' <- forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
processBlock BlockMap RegSet
block_live LiveBasicBlock instr
block
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live
((forall a. [a] -> [a]
reverse [NatBasicBlock instr]
blocks') forall a. [a] -> [a] -> [a]
++ [NatBasicBlock instr]
blocksAcc)
[SCC (LiveBasicBlock instr)]
sccs
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live [NatBasicBlock instr]
blocksAcc (CyclicSCC [LiveBasicBlock instr]
blocks : [SCC (LiveBasicBlock instr)]
sccs)
= do
[[NatBasicBlock instr]]
blockss' <- forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> RegM freeRegs [[NatBasicBlock instr]]
process [BlockId]
entry_ids BlockMap RegSet
block_live [LiveBasicBlock instr]
blocks
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live
(forall a. [a] -> [a]
reverse (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[NatBasicBlock instr]]
blockss') forall a. [a] -> [a] -> [a]
++ [NatBasicBlock instr]
blocksAcc)
[SCC (LiveBasicBlock instr)]
sccs
process :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr)
=> [BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> RegM freeRegs [[NatBasicBlock instr]]
process :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> RegM freeRegs [[NatBasicBlock instr]]
process [BlockId]
entry_ids BlockMap RegSet
block_live =
\[GenBasicBlock (LiveInstr instr)]
blocks -> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
go [GenBasicBlock (LiveInstr instr)]
blocks [] (forall (m :: * -> *) a. Monad m => a -> m a
return []) Bool
False
where
go :: [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
go :: [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
go [] [] [[NatBasicBlock instr]]
accum Bool
_madeProgress
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [[NatBasicBlock instr]]
accum
go [] [GenBasicBlock (LiveInstr instr)]
next_round [[NatBasicBlock instr]]
accum Bool
madeProgress
| Bool -> Bool
not Bool
madeProgress
= forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [[NatBasicBlock instr]]
accum
| Bool
otherwise
= [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
go [GenBasicBlock (LiveInstr instr)]
next_round [] [[NatBasicBlock instr]]
accum Bool
False
go (b :: GenBasicBlock (LiveInstr instr)
b@(BasicBlock BlockId
id [LiveInstr instr]
_) : [GenBasicBlock (LiveInstr instr)]
blocks) [GenBasicBlock (LiveInstr instr)]
next_round [[NatBasicBlock instr]]
accum Bool
madeProgress
= do
BlockAssignment freeRegs
block_assig <- forall freeRegs. RegM freeRegs (BlockAssignment freeRegs)
getBlockAssigR
if forall a. Maybe a -> Bool
isJust (forall freeRegs.
BlockId -> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
lookupBlockAssignment BlockId
id BlockAssignment freeRegs
block_assig) Bool -> Bool -> Bool
|| BlockId
id forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [BlockId]
entry_ids
then do [NatBasicBlock instr]
b' <- forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
processBlock BlockMap RegSet
block_live GenBasicBlock (LiveInstr instr)
b
[GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
go [GenBasicBlock (LiveInstr instr)]
blocks [GenBasicBlock (LiveInstr instr)]
next_round ([NatBasicBlock instr]
b' forall a. a -> [a] -> [a]
: [[NatBasicBlock instr]]
accum) Bool
True
else do [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
go [GenBasicBlock (LiveInstr instr)]
blocks (GenBasicBlock (LiveInstr instr)
b forall a. a -> [a] -> [a]
: [GenBasicBlock (LiveInstr instr)]
next_round) [[NatBasicBlock instr]]
accum Bool
madeProgress
processBlock
:: OutputableRegConstraint freeRegs instr
=> BlockMap RegSet
-> LiveBasicBlock instr
-> RegM freeRegs [NatBasicBlock instr]
processBlock :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
processBlock BlockMap RegSet
block_live (BasicBlock BlockId
id [LiveInstr instr]
instrs)
= do
forall freeRegs.
FR freeRegs =>
BlockId -> BlockMap RegSet -> RegM freeRegs ()
initBlock BlockId
id BlockMap RegSet
block_live
([instr]
instrs', [NatBasicBlock instr]
fixups)
<- forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
linearRA BlockMap RegSet
block_live BlockId
id [LiveInstr instr]
instrs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
id [instr]
instrs' forall a. a -> [a] -> [a]
: [NatBasicBlock instr]
fixups
initBlock :: FR freeRegs
=> BlockId -> BlockMap RegSet -> RegM freeRegs ()
initBlock :: forall freeRegs.
FR freeRegs =>
BlockId -> BlockMap RegSet -> RegM freeRegs ()
initBlock BlockId
id BlockMap RegSet
block_live
= do Platform
platform <- forall a. RegM a Platform
getPlatform
BlockAssignment freeRegs
block_assig <- forall freeRegs. RegM freeRegs (BlockAssignment freeRegs)
getBlockAssigR
case forall freeRegs.
BlockId -> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
lookupBlockAssignment BlockId
id BlockAssignment freeRegs
block_assig of
Maybe (freeRegs, RegMap Loc)
Nothing
-> do
case forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
mapLookup BlockId
id BlockMap RegSet
block_live of
Maybe RegSet
Nothing ->
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform)
Just RegSet
live ->
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frAllocateReg Platform
platform) (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform)
[ RealReg
r | RegReal RealReg
r <- forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet RegSet
live ]
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR forall a. RegMap a
emptyRegMap
Just (freeRegs
freeregs, RegMap Loc
assig)
-> do forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR freeRegs
freeregs
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig
linearRA
:: forall freeRegs instr. (OutputableRegConstraint freeRegs instr)
=> BlockMap RegSet
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs
( [instr]
, [NatBasicBlock instr])
linearRA :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
linearRA BlockMap RegSet
block_live BlockId
block_id = [instr]
-> [NatBasicBlock instr]
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
go [] []
where
go :: [instr]
-> [NatBasicBlock instr]
-> [LiveInstr instr]
-> RegM freeRegs
( [instr]
, [NatBasicBlock instr] )
go :: [instr]
-> [NatBasicBlock instr]
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
go ![instr]
accInstr ![NatBasicBlock instr]
accFixups [] = do
forall (m :: * -> *) a. Monad m => a -> m a
return ( forall a. [a] -> [a]
reverse [instr]
accInstr
, [NatBasicBlock instr]
accFixups )
go [instr]
accInstr [NatBasicBlock instr]
accFixups (LiveInstr instr
instr:[LiveInstr instr]
instrs) = do
([instr]
accInstr', [NatBasicBlock instr]
new_fixups) <- forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> BlockId
-> LiveInstr instr
-> RegM freeRegs ([instr], [NatBasicBlock instr])
raInsn BlockMap RegSet
block_live [instr]
accInstr BlockId
block_id LiveInstr instr
instr
[instr]
-> [NatBasicBlock instr]
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
go [instr]
accInstr' ([NatBasicBlock instr]
new_fixups forall a. [a] -> [a] -> [a]
++ [NatBasicBlock instr]
accFixups) [LiveInstr instr]
instrs
raInsn
:: OutputableRegConstraint freeRegs instr
=> BlockMap RegSet
-> [instr]
-> BlockId
-> LiveInstr instr
-> RegM freeRegs
( [instr]
, [NatBasicBlock instr])
raInsn :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> BlockId
-> LiveInstr instr
-> RegM freeRegs ([instr], [NatBasicBlock instr])
raInsn BlockMap RegSet
_ [instr]
new_instrs BlockId
_ (LiveInstr InstrSR instr
ii Maybe Liveness
Nothing)
| Just Int
n <- forall instr. Instruction instr => instr -> Maybe Int
takeDeltaInstr InstrSR instr
ii
= do forall freeRegs. Int -> RegM freeRegs ()
setDeltaR Int
n
forall (m :: * -> *) a. Monad m => a -> m a
return ([instr]
new_instrs, [])
raInsn BlockMap RegSet
_ [instr]
new_instrs BlockId
_ (LiveInstr ii :: InstrSR instr
ii@(Instr instr
i) Maybe Liveness
Nothing)
| forall instr. Instruction instr => instr -> Bool
isMetaInstr InstrSR instr
ii
= forall (m :: * -> *) a. Monad m => a -> m a
return (instr
i forall a. a -> [a] -> [a]
: [instr]
new_instrs, [])
raInsn BlockMap RegSet
block_live [instr]
new_instrs BlockId
id (LiveInstr (Instr instr
instr) (Just Liveness
live))
= do
RegMap Loc
assig <- forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR :: RegM freeRegs (UniqFM Reg Loc)
case forall instr. Instruction instr => instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr instr
instr of
Just (Reg
src,Reg
dst) | Reg
src forall a. Uniquable a => a -> UniqSet a -> Bool
`elementOfUniqSet` (Liveness -> RegSet
liveDieRead Liveness
live),
Reg -> Bool
isVirtualReg Reg
dst,
Bool -> Bool
not (Reg
dst forall key elt. Uniquable key => key -> UniqFM key elt -> Bool
`elemUFM` RegMap Loc
assig),
Reg -> Bool
isRealReg Reg
src Bool -> Bool -> Bool
|| Reg -> RegMap Loc -> Bool
isInReg Reg
src RegMap Loc
assig -> do
case Reg
src of
(RegReal RealReg
rr) -> forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM RegMap Loc
assig Reg
dst (RealReg -> Loc
InReg RealReg
rr))
Reg
_virt -> case forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM RegMap Loc
assig Reg
src of
Maybe Loc
Nothing -> forall a. String -> a
panic String
"raInsn"
Just Loc
loc ->
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> UniqFM key elt
delFromUFM RegMap Loc
assig Reg
src) Reg
dst Loc
loc)
forall (m :: * -> *) a. Monad m => a -> m a
return ([instr]
new_instrs, [])
Maybe (Reg, Reg)
_ -> forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> BlockId
-> instr
-> [Reg]
-> [Reg]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
genRaInsn BlockMap RegSet
block_live [instr]
new_instrs BlockId
id instr
instr
(forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet forall a b. (a -> b) -> a -> b
$ Liveness -> RegSet
liveDieRead Liveness
live)
(forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet forall a b. (a -> b) -> a -> b
$ Liveness -> RegSet
liveDieWrite Liveness
live)
raInsn BlockMap RegSet
_ [instr]
_ BlockId
_ LiveInstr instr
instr
= do
Platform
platform <- forall a. RegM a Platform
getPlatform
let instr' :: LiveInstr SDoc
instr' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall instr. Instruction instr => Platform -> instr -> SDoc
pprInstr Platform
platform) LiveInstr instr
instr
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"raInsn" (String -> SDoc
text String
"no match for:" SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr LiveInstr SDoc
instr')
isInReg :: Reg -> RegMap Loc -> Bool
isInReg :: Reg -> RegMap Loc -> Bool
isInReg Reg
src RegMap Loc
assig | Just (InReg RealReg
_) <- forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM RegMap Loc
assig Reg
src = Bool
True
| Bool
otherwise = Bool
False
genRaInsn :: forall freeRegs instr.
(OutputableRegConstraint freeRegs instr)
=> BlockMap RegSet
-> [instr]
-> BlockId
-> instr
-> [Reg]
-> [Reg]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
genRaInsn :: forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> BlockId
-> instr
-> [Reg]
-> [Reg]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
genRaInsn BlockMap RegSet
block_live [instr]
new_instrs BlockId
block_id instr
instr [Reg]
r_dying [Reg]
w_dying = do
Platform
platform <- forall a. RegM a Platform
getPlatform
case forall instr. Instruction instr => Platform -> instr -> RegUsage
regUsageOfInstr Platform
platform instr
instr of { RU [Reg]
read [Reg]
written ->
do
let real_written :: [RealReg]
real_written = [ RealReg
rr | (RegReal RealReg
rr) <- [Reg]
written ] :: [RealReg]
let virt_written :: [VirtualReg]
virt_written = [ VirtualReg
vr | (RegVirtual VirtualReg
vr) <- [Reg]
written ]
let virt_read :: [VirtualReg]
virt_read = forall a. Eq a => [a] -> [a]
nub [ VirtualReg
vr | (RegVirtual VirtualReg
vr) <- [Reg]
read ] :: [VirtualReg]
([instr]
r_spills, [RealReg]
r_allocd) <-
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
True [VirtualReg]
virt_read [] [] [VirtualReg]
virt_read
[instr]
clobber_saves <- forall instr freeRegs.
(Instruction instr, FR freeRegs) =>
[RealReg] -> [Reg] -> RegM freeRegs [instr]
saveClobberedTemps [RealReg]
real_written [Reg]
r_dying
([NatBasicBlock instr]
fixup_blocks, instr
adjusted_instr)
<- forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
BlockMap RegSet
-> BlockId -> instr -> RegM freeRegs ([NatBasicBlock instr], instr)
joinToTargets BlockMap RegSet
block_live BlockId
block_id instr
instr
forall freeRegs. FR freeRegs => [Reg] -> RegM freeRegs ()
releaseRegs [Reg]
r_dying
forall freeRegs. FR freeRegs => [RealReg] -> RegM freeRegs ()
clobberRegs [RealReg]
real_written
([instr]
w_spills, [RealReg]
w_allocd) <-
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
False [VirtualReg]
virt_written [] [] [VirtualReg]
virt_written
forall freeRegs. FR freeRegs => [Reg] -> RegM freeRegs ()
releaseRegs [Reg]
w_dying
let
patch_map :: UniqFM Reg Reg
patch_map :: UniqFM Reg Reg
patch_map
= forall elt. UniqFM VirtualReg elt -> UniqFM Reg elt
toRegMap forall a b. (a -> b) -> a -> b
$
forall key elt. Uniquable key => [(key, elt)] -> UniqFM key elt
listToUFM
[ (VirtualReg
t, RealReg -> Reg
RegReal RealReg
r)
| (VirtualReg
t, RealReg
r) <- forall a b. [a] -> [b] -> [(a, b)]
zip [VirtualReg]
virt_read [RealReg]
r_allocd
forall a. [a] -> [a] -> [a]
++ forall a b. [a] -> [b] -> [(a, b)]
zip [VirtualReg]
virt_written [RealReg]
w_allocd ]
patched_instr :: instr
patched_instr :: instr
patched_instr
= forall instr. Instruction instr => instr -> (Reg -> Reg) -> instr
patchRegsOfInstr instr
adjusted_instr Reg -> Reg
patchLookup
patchLookup :: Reg -> Reg
patchLookup :: Reg -> Reg
patchLookup Reg
x
= case forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM Reg Reg
patch_map Reg
x of
Maybe Reg
Nothing -> Reg
x
Just Reg
y -> Reg
y
let squashed_instr :: [instr]
squashed_instr = case forall instr. Instruction instr => instr -> Maybe (Reg, Reg)
takeRegRegMoveInstr instr
patched_instr of
Just (Reg
src, Reg
dst)
| Reg
src forall a. Eq a => a -> a -> Bool
== Reg
dst -> []
Maybe (Reg, Reg)
_ -> [instr
patched_instr]
let code :: [instr]
code = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [
[instr]
squashed_instr
, forall a. [a] -> [a]
reverse [instr]
w_spills
, forall a. [a] -> [a]
reverse [instr]
r_spills
, forall a. [a] -> [a]
reverse [instr]
clobber_saves
, [instr]
new_instrs
]
forall (m :: * -> *) a. Monad m => a -> m a
return ([instr]
code, [NatBasicBlock instr]
fixup_blocks)
}
releaseRegs :: FR freeRegs => [Reg] -> RegM freeRegs ()
releaseRegs :: forall freeRegs. FR freeRegs => [Reg] -> RegM freeRegs ()
releaseRegs [Reg]
regs = do
Platform
platform <- forall a. RegM a Platform
getPlatform
RegMap Loc
assig <- forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
freeRegs
free <- forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
let loop :: RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop RegMap Loc
assig !freeRegs
free [] = do forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig; forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR freeRegs
free; forall (m :: * -> *) a. Monad m => a -> m a
return ()
loop RegMap Loc
assig !freeRegs
free (RegReal RealReg
rr : [Reg]
rs) = RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop RegMap Loc
assig (forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frReleaseReg Platform
platform RealReg
rr freeRegs
free) [Reg]
rs
loop RegMap Loc
assig !freeRegs
free (Reg
r:[Reg]
rs) =
case forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM RegMap Loc
assig Reg
r of
Just (InBoth RealReg
real Int
_) -> RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> UniqFM key elt
delFromUFM RegMap Loc
assig Reg
r)
(forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frReleaseReg Platform
platform RealReg
real freeRegs
free) [Reg]
rs
Just (InReg RealReg
real) -> RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> UniqFM key elt
delFromUFM RegMap Loc
assig Reg
r)
(forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frReleaseReg Platform
platform RealReg
real freeRegs
free) [Reg]
rs
Maybe Loc
_ -> RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> UniqFM key elt
delFromUFM RegMap Loc
assig Reg
r) freeRegs
free [Reg]
rs
RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop RegMap Loc
assig freeRegs
free [Reg]
regs
saveClobberedTemps
:: forall instr freeRegs.
(Instruction instr, FR freeRegs)
=> [RealReg]
-> [Reg]
-> RegM freeRegs [instr]
saveClobberedTemps :: forall instr freeRegs.
(Instruction instr, FR freeRegs) =>
[RealReg] -> [Reg] -> RegM freeRegs [instr]
saveClobberedTemps [] [Reg]
_
= forall (m :: * -> *) a. Monad m => a -> m a
return []
saveClobberedTemps [RealReg]
clobbered [Reg]
dying
= do
RegMap Loc
assig <- forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR :: RegM freeRegs (UniqFM Reg Loc)
let to_spill :: [(Unique, RealReg)]
to_spill :: [(Unique, RealReg)]
to_spill
= [ (Unique
temp,RealReg
reg)
| (Unique
temp, InReg RealReg
reg) <- forall key elt. UniqFM key elt -> [(Unique, elt)]
nonDetUFMToList RegMap Loc
assig
, forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (RealReg -> RealReg -> Bool
realRegsAlias RealReg
reg) [RealReg]
clobbered
, Unique
temp forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` forall a b. (a -> b) -> [a] -> [b]
map forall a. Uniquable a => a -> Unique
getUnique [Reg]
dying ]
([instr]
instrs,RegMap Loc
assig') <- RegMap Loc
-> [instr]
-> [(Unique, RealReg)]
-> RegM freeRegs ([instr], RegMap Loc)
clobber RegMap Loc
assig [] [(Unique, RealReg)]
to_spill
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
[instr]
instrs
where
clobber :: RegMap Loc -> [instr] -> [(Unique,RealReg)] -> RegM freeRegs ([instr], RegMap Loc)
clobber :: RegMap Loc
-> [instr]
-> [(Unique, RealReg)]
-> RegM freeRegs ([instr], RegMap Loc)
clobber RegMap Loc
assig [instr]
instrs []
= forall (m :: * -> *) a. Monad m => a -> m a
return ([instr]
instrs, RegMap Loc
assig)
clobber RegMap Loc
assig [instr]
instrs ((Unique
temp, RealReg
reg) : [(Unique, RealReg)]
rest)
= do Platform
platform <- forall a. RegM a Platform
getPlatform
freeRegs
freeRegs <- forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
let regclass :: RegClass
regclass = Platform -> RealReg -> RegClass
targetClassOfRealReg Platform
platform RealReg
reg
freeRegs_thisClass :: [RealReg]
freeRegs_thisClass = forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
frGetFreeRegs Platform
platform RegClass
regclass freeRegs
freeRegs
case forall a. (a -> Bool) -> [a] -> [a]
filter (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [RealReg]
clobbered) [RealReg]
freeRegs_thisClass of
(RealReg
my_reg : [RealReg]
_) -> do
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frAllocateReg Platform
platform RealReg
my_reg freeRegs
freeRegs)
let new_assign :: RegMap Loc
new_assign = forall key elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
addToUFM_Directly RegMap Loc
assig Unique
temp (RealReg -> Loc
InReg RealReg
my_reg)
let instr :: instr
instr = forall instr. Instruction instr => Platform -> Reg -> Reg -> instr
mkRegRegMoveInstr Platform
platform
(RealReg -> Reg
RegReal RealReg
reg) (RealReg -> Reg
RegReal RealReg
my_reg)
RegMap Loc
-> [instr]
-> [(Unique, RealReg)]
-> RegM freeRegs ([instr], RegMap Loc)
clobber RegMap Loc
new_assign (instr
instr forall a. a -> [a] -> [a]
: [instr]
instrs) [(Unique, RealReg)]
rest
[] -> do
([instr]
spill, Int
slot) <- forall instr freeRegs.
Instruction instr =>
Reg -> Unique -> RegM freeRegs ([instr], Int)
spillR (RealReg -> Reg
RegReal RealReg
reg) Unique
temp
forall freeRegs. SpillReason -> RegM freeRegs ()
recordSpill (Unique -> SpillReason
SpillClobber Unique
temp)
let new_assign :: RegMap Loc
new_assign = forall key elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
addToUFM_Directly RegMap Loc
assig Unique
temp (RealReg -> Int -> Loc
InBoth RealReg
reg Int
slot)
RegMap Loc
-> [instr]
-> [(Unique, RealReg)]
-> RegM freeRegs ([instr], RegMap Loc)
clobber RegMap Loc
new_assign ([instr]
spill forall a. [a] -> [a] -> [a]
++ [instr]
instrs) [(Unique, RealReg)]
rest
clobberRegs :: FR freeRegs => [RealReg] -> RegM freeRegs ()
clobberRegs :: forall freeRegs. FR freeRegs => [RealReg] -> RegM freeRegs ()
clobberRegs []
= forall (m :: * -> *) a. Monad m => a -> m a
return ()
clobberRegs [RealReg]
clobbered
= do Platform
platform <- forall a. RegM a Platform
getPlatform
freeRegs
freeregs <- forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
let gpRegs :: [RealReg]
gpRegs = forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
frGetFreeRegs Platform
platform RegClass
RcInteger freeRegs
freeregs :: [RealReg]
fltRegs :: [RealReg]
fltRegs = forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
frGetFreeRegs Platform
platform RegClass
RcFloat freeRegs
freeregs :: [RealReg]
dblRegs :: [RealReg]
dblRegs = forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
frGetFreeRegs Platform
platform RegClass
RcDouble freeRegs
freeregs :: [RealReg]
let extra_clobbered :: [RealReg]
extra_clobbered = [ RealReg
r | RealReg
r <- [RealReg]
clobbered
, RealReg
r forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ([RealReg]
gpRegs forall a. [a] -> [a] -> [a]
++ [RealReg]
fltRegs forall a. [a] -> [a] -> [a]
++ [RealReg]
dblRegs) ]
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR forall a b. (a -> b) -> a -> b
$! forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frAllocateReg Platform
platform) freeRegs
freeregs [RealReg]
extra_clobbered
RegMap Loc
assig <- forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR forall a b. (a -> b) -> a -> b
$! RegMap Loc -> [(Unique, Loc)] -> RegMap Loc
clobber RegMap Loc
assig (forall key elt. UniqFM key elt -> [(Unique, elt)]
nonDetUFMToList RegMap Loc
assig)
where
clobber :: RegMap Loc -> [(Unique,Loc)] -> RegMap Loc
clobber :: RegMap Loc -> [(Unique, Loc)] -> RegMap Loc
clobber RegMap Loc
assig []
= RegMap Loc
assig
clobber RegMap Loc
assig ((Unique
temp, InBoth RealReg
reg Int
slot) : [(Unique, Loc)]
rest)
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (RealReg -> RealReg -> Bool
realRegsAlias RealReg
reg) [RealReg]
clobbered
= RegMap Loc -> [(Unique, Loc)] -> RegMap Loc
clobber (forall key elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
addToUFM_Directly RegMap Loc
assig Unique
temp (Int -> Loc
InMem Int
slot)) [(Unique, Loc)]
rest
clobber RegMap Loc
assig ((Unique, Loc)
_:[(Unique, Loc)]
rest)
= RegMap Loc -> [(Unique, Loc)] -> RegMap Loc
clobber RegMap Loc
assig [(Unique, Loc)]
rest
data SpillLoc = ReadMem StackSlot
| WriteNew
| WriteMem
allocateRegsAndSpill
:: forall freeRegs instr. (FR freeRegs, Instruction instr)
=> Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ( [instr] , [RealReg])
allocateRegsAndSpill :: forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
_ [VirtualReg]
_ [instr]
spills [RealReg]
alloc []
= forall (m :: * -> *) a. Monad m => a -> m a
return ([instr]
spills, forall a. [a] -> [a]
reverse [RealReg]
alloc)
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills [RealReg]
alloc (VirtualReg
r:[VirtualReg]
rs)
= do UniqFM VirtualReg Loc
assig <- forall elt. UniqFM Reg elt -> UniqFM VirtualReg elt
toVRegMap forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
let doSpill :: SpillLoc -> RegM freeRegs ([instr], [RealReg])
doSpill = forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> UniqFM VirtualReg Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
allocRegsAndSpill_spill Bool
reading [VirtualReg]
keep [instr]
spills [RealReg]
alloc VirtualReg
r [VirtualReg]
rs UniqFM VirtualReg Loc
assig
case forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM UniqFM VirtualReg Loc
assig VirtualReg
r of
Just (InReg RealReg
my_reg) ->
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills (RealReg
my_regforall a. a -> [a] -> [a]
:[RealReg]
alloc) [VirtualReg]
rs
Just (InBoth RealReg
my_reg Int
_)
-> do forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
reading) (forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR forall a b. (a -> b) -> a -> b
$ forall elt. UniqFM VirtualReg elt -> UniqFM Reg elt
toRegMap (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM UniqFM VirtualReg Loc
assig VirtualReg
r (RealReg -> Loc
InReg RealReg
my_reg)))
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills (RealReg
my_regforall a. a -> [a] -> [a]
:[RealReg]
alloc) [VirtualReg]
rs
Just (InMem Int
slot) | Bool
reading -> SpillLoc -> RegM freeRegs ([instr], [RealReg])
doSpill (Int -> SpillLoc
ReadMem Int
slot)
| Bool
otherwise -> SpillLoc -> RegM freeRegs ([instr], [RealReg])
doSpill SpillLoc
WriteMem
Maybe Loc
Nothing | Bool
reading ->
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"allocateRegsAndSpill: Cannot read from uninitialized register" (forall a. Outputable a => a -> SDoc
ppr VirtualReg
r)
| Bool
otherwise -> SpillLoc -> RegM freeRegs ([instr], [RealReg])
doSpill SpillLoc
WriteNew
findPrefRealReg :: VirtualReg -> RegM freeRegs (Maybe RealReg)
findPrefRealReg :: forall freeRegs. VirtualReg -> RegM freeRegs (Maybe RealReg)
findPrefRealReg VirtualReg
vreg = do
BlockAssignment freeRegs
bassig <- forall freeRegs. RegM freeRegs (BlockAssignment freeRegs)
getBlockAssigR :: RegM freeRegs (BlockAssignment freeRegs)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall freeRegs.
VirtualReg -> BlockAssignment freeRegs -> Maybe RealReg
lookupFirstUsed VirtualReg
vreg BlockAssignment freeRegs
bassig
allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr)
=> Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> UniqFM VirtualReg Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
allocRegsAndSpill_spill :: forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> UniqFM VirtualReg Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
allocRegsAndSpill_spill Bool
reading [VirtualReg]
keep [instr]
spills [RealReg]
alloc VirtualReg
r [VirtualReg]
rs UniqFM VirtualReg Loc
assig SpillLoc
spill_loc
= do Platform
platform <- forall a. RegM a Platform
getPlatform
freeRegs
freeRegs <- forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
let freeRegs_thisClass :: [RealReg]
freeRegs_thisClass = forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
frGetFreeRegs Platform
platform (VirtualReg -> RegClass
classOfVirtualReg VirtualReg
r) freeRegs
freeRegs :: [RealReg]
Maybe RealReg
pref_reg <- forall freeRegs. VirtualReg -> RegM freeRegs (Maybe RealReg)
findPrefRealReg VirtualReg
r
case [RealReg]
freeRegs_thisClass of
(RealReg
first_free : [RealReg]
_) ->
do let !final_reg :: RealReg
final_reg
| Just RealReg
reg <- Maybe RealReg
pref_reg
, RealReg
reg forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [RealReg]
freeRegs_thisClass
= RealReg
reg
| Bool
otherwise
= RealReg
first_free
[instr]
spills' <- forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
loadTemp VirtualReg
r SpillLoc
spill_loc RealReg
final_reg [instr]
spills
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR forall a b. (a -> b) -> a -> b
$ forall elt. UniqFM VirtualReg elt -> UniqFM Reg elt
toRegMap
forall a b. (a -> b) -> a -> b
$ (forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM UniqFM VirtualReg Loc
assig VirtualReg
r forall a b. (a -> b) -> a -> b
$! SpillLoc -> RealReg -> Loc
newLocation SpillLoc
spill_loc RealReg
final_reg)
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR forall a b. (a -> b) -> a -> b
$ forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
frAllocateReg Platform
platform RealReg
final_reg freeRegs
freeRegs
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills' (RealReg
final_reg forall a. a -> [a] -> [a]
: [RealReg]
alloc) [VirtualReg]
rs
[] ->
do let inRegOrBoth :: Loc -> Bool
inRegOrBoth (InReg RealReg
_) = Bool
True
inRegOrBoth (InBoth RealReg
_ Int
_) = Bool
True
inRegOrBoth Loc
_ = Bool
False
let candidates' :: UniqFM VirtualReg Loc
candidates' :: UniqFM VirtualReg Loc
candidates' =
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall key elt.
Uniquable key =>
UniqFM key elt -> [key] -> UniqFM key elt
delListFromUFM [VirtualReg]
keep forall a b. (a -> b) -> a -> b
$
forall elt key. (elt -> Bool) -> UniqFM key elt -> UniqFM key elt
filterUFM Loc -> Bool
inRegOrBoth forall a b. (a -> b) -> a -> b
$
UniqFM VirtualReg Loc
assig
let candidates :: [(Unique, Loc)]
candidates = forall key elt. UniqFM key elt -> [(Unique, elt)]
nonDetUFMToList UniqFM VirtualReg Loc
candidates'
let candidates_inBoth :: [(Unique, RealReg, StackSlot)]
candidates_inBoth :: [(Unique, RealReg, Int)]
candidates_inBoth
= [ (Unique
temp, RealReg
reg, Int
mem)
| (Unique
temp, InBoth RealReg
reg Int
mem) <- [(Unique, Loc)]
candidates
, Platform -> RealReg -> RegClass
targetClassOfRealReg Platform
platform RealReg
reg forall a. Eq a => a -> a -> Bool
== VirtualReg -> RegClass
classOfVirtualReg VirtualReg
r ]
let candidates_inReg :: [(Unique, RealReg)]
candidates_inReg
= [ (Unique
temp, RealReg
reg)
| (Unique
temp, InReg RealReg
reg) <- [(Unique, Loc)]
candidates
, Platform -> RealReg -> RegClass
targetClassOfRealReg Platform
platform RealReg
reg forall a. Eq a => a -> a -> Bool
== VirtualReg -> RegClass
classOfVirtualReg VirtualReg
r ]
let result :: RegM freeRegs ([instr], [RealReg])
result
| (Unique
temp, RealReg
my_reg, Int
slot) : [(Unique, RealReg, Int)]
_ <- [(Unique, RealReg, Int)]
candidates_inBoth
= do [instr]
spills' <- forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
loadTemp VirtualReg
r SpillLoc
spill_loc RealReg
my_reg [instr]
spills
let assig1 :: UniqFM VirtualReg Loc
assig1 = forall key elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
addToUFM_Directly UniqFM VirtualReg Loc
assig Unique
temp (Int -> Loc
InMem Int
slot)
let assig2 :: UniqFM VirtualReg Loc
assig2 = forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM UniqFM VirtualReg Loc
assig1 VirtualReg
r forall a b. (a -> b) -> a -> b
$! SpillLoc -> RealReg -> Loc
newLocation SpillLoc
spill_loc RealReg
my_reg
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR forall a b. (a -> b) -> a -> b
$ forall elt. UniqFM VirtualReg elt -> UniqFM Reg elt
toRegMap UniqFM VirtualReg Loc
assig2
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills' (RealReg
my_regforall a. a -> [a] -> [a]
:[RealReg]
alloc) [VirtualReg]
rs
| (Unique
temp_to_push_out, (RealReg
my_reg :: RealReg)) : [(Unique, RealReg)]
_
<- [(Unique, RealReg)]
candidates_inReg
= do
([instr]
spill_store, Int
slot) <- forall instr freeRegs.
Instruction instr =>
Reg -> Unique -> RegM freeRegs ([instr], Int)
spillR (RealReg -> Reg
RegReal RealReg
my_reg) Unique
temp_to_push_out
forall freeRegs. SpillReason -> RegM freeRegs ()
recordSpill (Unique -> SpillReason
SpillAlloc Unique
temp_to_push_out)
let assig1 :: UniqFM VirtualReg Loc
assig1 = forall key elt. UniqFM key elt -> Unique -> elt -> UniqFM key elt
addToUFM_Directly UniqFM VirtualReg Loc
assig Unique
temp_to_push_out (Int -> Loc
InMem Int
slot)
let assig2 :: UniqFM VirtualReg Loc
assig2 = forall key elt.
Uniquable key =>
UniqFM key elt -> key -> elt -> UniqFM key elt
addToUFM UniqFM VirtualReg Loc
assig1 VirtualReg
r forall a b. (a -> b) -> a -> b
$! SpillLoc -> RealReg -> Loc
newLocation SpillLoc
spill_loc RealReg
my_reg
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR forall a b. (a -> b) -> a -> b
$ forall elt. UniqFM VirtualReg elt -> UniqFM Reg elt
toRegMap UniqFM VirtualReg Loc
assig2
[instr]
spills' <- forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
loadTemp VirtualReg
r SpillLoc
spill_loc RealReg
my_reg [instr]
spills
forall freeRegs instr.
(FR freeRegs, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
reading [VirtualReg]
keep
([instr]
spill_store forall a. [a] -> [a] -> [a]
++ [instr]
spills')
(RealReg
my_regforall a. a -> [a] -> [a]
:[RealReg]
alloc) [VirtualReg]
rs
| Bool
otherwise
= forall a. HasCallStack => String -> SDoc -> a
pprPanic (String
"RegAllocLinear.allocRegsAndSpill: no spill candidates\n")
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat
[ String -> SDoc
text String
"allocating vreg: " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (forall a. Show a => a -> String
show VirtualReg
r)
, String -> SDoc
text String
"assignment: " SDoc -> SDoc -> SDoc
<> forall a. Outputable a => a -> SDoc
ppr UniqFM VirtualReg Loc
assig
, String -> SDoc
text String
"freeRegs: " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (forall a. Show a => a -> String
show freeRegs
freeRegs)
, String -> SDoc
text String
"initFreeRegs: " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (forall a. Show a => a -> String
show (forall freeRegs. FR freeRegs => Platform -> freeRegs
frInitFreeRegs Platform
platform forall a. a -> a -> a
`asTypeOf` freeRegs
freeRegs)) ]
RegM freeRegs ([instr], [RealReg])
result
newLocation :: SpillLoc -> RealReg -> Loc
newLocation :: SpillLoc -> RealReg -> Loc
newLocation (ReadMem Int
slot) RealReg
my_reg = RealReg -> Int -> Loc
InBoth RealReg
my_reg Int
slot
newLocation SpillLoc
_ RealReg
my_reg = RealReg -> Loc
InReg RealReg
my_reg
loadTemp
:: (Instruction instr)
=> VirtualReg
-> SpillLoc
-> RealReg
-> [instr]
-> RegM freeRegs [instr]
loadTemp :: forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
loadTemp VirtualReg
vreg (ReadMem Int
slot) RealReg
hreg [instr]
spills
= do
[instr]
insn <- forall instr freeRegs.
Instruction instr =>
Reg -> Int -> RegM freeRegs [instr]
loadR (RealReg -> Reg
RegReal RealReg
hreg) Int
slot
forall freeRegs. SpillReason -> RegM freeRegs ()
recordSpill (Unique -> SpillReason
SpillLoad forall a b. (a -> b) -> a -> b
$ forall a. Uniquable a => a -> Unique
getUnique VirtualReg
vreg)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [instr]
insn forall a. [a] -> [a] -> [a]
++ [instr]
spills
loadTemp VirtualReg
_ SpillLoc
_ RealReg
_ [instr]
spills =
forall (m :: * -> *) a. Monad m => a -> m a
return [instr]
spills