{-# 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 GHC.CmmToAsm.Reg.Target
import GHC.CmmToAsm.Reg.Liveness
import GHC.CmmToAsm.Instr
import GHC.CmmToAsm.Config
import GHC.Platform.Reg
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.Platform
import Data.Maybe
import Data.List
import Control.Monad
import Control.Applicative
regAlloc
:: (Outputable instr, Instruction instr)
=> NCGConfig
-> LiveCmmDecl statics instr
-> UniqSM ( NatCmmDecl statics instr
, Maybe Int
, Maybe RegAllocStats
)
regAlloc :: NCGConfig
-> LiveCmmDecl statics instr
-> UniqSM
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
regAlloc NCGConfig
_ (CmmData Section
sec statics
d)
= (NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
-> UniqSM
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad UniqSM
return
( Section -> statics -> NatCmmDecl statics instr
forall d h g. Section -> d -> GenCmmDecl d h g
CmmData Section
sec statics
d
, Maybe Int
forall a. Maybe a
Nothing
, Maybe RegAllocStats
forall a. Maybe a
Nothing )
regAlloc NCGConfig
_ (CmmProc (LiveInfo LabelMap RawCmmStatics
info [BlockId]
_ BlockMap RegSet
_ BlockMap IntSet
_) CLabel
lbl [GlobalReg]
live [])
= (NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
-> UniqSM
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad UniqSM
return ( LabelMap RawCmmStatics
-> CLabel
-> [GlobalReg]
-> ListGraph instr
-> NatCmmDecl statics instr
forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalReg]
live ([GenBasicBlock instr] -> ListGraph instr
forall i. [GenBasicBlock i] -> ListGraph i
ListGraph [])
, Maybe Int
forall a. Maybe a
Nothing
, Maybe RegAllocStats
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
([GenBasicBlock instr]
final_blocks, RegAllocStats
stats, Int
stack_use)
<- NCGConfig
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([GenBasicBlock instr], RegAllocStats, Int)
forall instr.
(Outputable instr, Instruction instr) =>
NCGConfig
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type Outputable instr
linearRegAlloc NCGConfig
config [BlockId]
entry_ids BlockMap RegSet
block_live [SCC (LiveBasicBlock instr)]
sccs
let ((GenBasicBlock instr
first':[GenBasicBlock instr]
_), [GenBasicBlock instr]
rest')
= (GenBasicBlock instr -> Bool)
-> [GenBasicBlock instr]
-> ([GenBasicBlock instr], [GenBasicBlock instr])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition ((BlockId -> BlockId -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq BlockId
== BlockId
first_id) (BlockId -> Bool)
-> (GenBasicBlock instr -> BlockId) -> GenBasicBlock instr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenBasicBlock instr -> BlockId
forall i. GenBasicBlock i -> BlockId
blockId) [GenBasicBlock 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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
max_spill_slots
= Int -> Maybe Int
forall a. a -> Maybe a
Just (Int
stack_use Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
max_spill_slots)
| Bool
otherwise
= Maybe Int
forall a. Maybe a
Nothing
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
-> UniqSM
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad UniqSM
return ( LabelMap RawCmmStatics
-> CLabel
-> [GlobalReg]
-> ListGraph instr
-> NatCmmDecl statics instr
forall d h g. h -> CLabel -> [GlobalReg] -> g -> GenCmmDecl d h g
CmmProc LabelMap RawCmmStatics
info CLabel
lbl [GlobalReg]
live ([GenBasicBlock instr] -> ListGraph instr
forall i. [GenBasicBlock i] -> ListGraph i
ListGraph (GenBasicBlock instr
first' GenBasicBlock instr
-> [GenBasicBlock instr] -> [GenBasicBlock instr]
forall a. a -> [a] -> [a]
: [GenBasicBlock instr]
rest'))
, Maybe Int
extra_stack
, RegAllocStats -> Maybe RegAllocStats
forall a. a -> Maybe a
Just RegAllocStats
stats)
regAlloc NCGConfig
_ (CmmProc LiveInfo
_ CLabel
_ [GlobalReg]
_ [SCC (LiveBasicBlock instr)]
_)
= String
-> UniqSM
(NatCmmDecl statics instr, Maybe Int, Maybe RegAllocStats)
forall a. String -> a
panic String
"RegAllocLinear.regAlloc: no match"
linearRegAlloc
:: (Outputable instr, Instruction instr)
=> NCGConfig
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc :: 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 -> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall {freeRegs}.
(FR freeRegs, Outputable freeRegs) =>
freeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
External instance of the constraint type Outputable FreeRegs
External instance of the constraint type FR FreeRegs
go (FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int))
-> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a b. (a -> b) -> a -> b
$ (Platform -> FreeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
External instance of the constraint type FR FreeRegs
frInitFreeRegs Platform
platform :: X86.FreeRegs)
Arch
ArchX86_64 -> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall {freeRegs}.
(FR freeRegs, Outputable freeRegs) =>
freeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
External instance of the constraint type Outputable FreeRegs
External instance of the constraint type FR FreeRegs
go (FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int))
-> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a b. (a -> b) -> a -> b
$ (Platform -> FreeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
External instance of the constraint type FR FreeRegs
frInitFreeRegs Platform
platform :: X86_64.FreeRegs)
Arch
ArchS390X -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchS390X"
Arch
ArchSPARC -> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall {freeRegs}.
(FR freeRegs, Outputable freeRegs) =>
freeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
External instance of the constraint type Outputable FreeRegs
External instance of the constraint type FR FreeRegs
go (FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int))
-> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a b. (a -> b) -> a -> b
$ (Platform -> FreeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
External instance of the constraint type FR FreeRegs
frInitFreeRegs Platform
platform :: SPARC.FreeRegs)
Arch
ArchSPARC64 -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchSPARC64"
Arch
ArchPPC -> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall {freeRegs}.
(FR freeRegs, Outputable freeRegs) =>
freeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
External instance of the constraint type Outputable FreeRegs
External instance of the constraint type FR FreeRegs
go (FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int))
-> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a b. (a -> b) -> a -> b
$ (Platform -> FreeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
External instance of the constraint type FR FreeRegs
frInitFreeRegs Platform
platform :: PPC.FreeRegs)
ArchARM ArmISA
_ [ArmISAExt]
_ ArmABI
_ -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchARM"
Arch
ArchARM64 -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchARM64"
ArchPPC_64 PPC_64ABI
_ -> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall {freeRegs}.
(FR freeRegs, Outputable freeRegs) =>
freeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
External instance of the constraint type Outputable FreeRegs
External instance of the constraint type FR FreeRegs
go (FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int))
-> FreeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a b. (a -> b) -> a -> b
$ (Platform -> FreeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
External instance of the constraint type FR FreeRegs
frInitFreeRegs Platform
platform :: PPC.FreeRegs)
Arch
ArchAlpha -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchAlpha"
Arch
ArchMipseb -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchMipseb"
Arch
ArchMipsel -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchMipsel"
Arch
ArchJavaScript -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchJavaScript"
Arch
ArchUnknown -> String -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall a. String -> a
panic String
"linearRegAlloc ArchUnknown"
where
go :: freeRegs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go freeRegs
f = NCGConfig
-> freeRegs
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
NCGConfig
-> freeRegs
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
Evidence bound by a type signature of the constraint type FR freeRegs
Evidence bound by a type signature of the constraint type Outputable freeRegs
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type Instruction instr
linearRegAlloc' NCGConfig
config freeRegs
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, Outputable instr, Instruction instr)
linearRegAlloc'
:: OutputableRegConstraint freeRegs instr
=> NCGConfig
-> freeRegs
-> [BlockId]
-> BlockMap RegSet
-> [SCC (LiveBasicBlock instr)]
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
linearRegAlloc' :: 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 <- UniqSM UniqSupply
forall (m :: * -> *). MonadUnique m => m UniqSupply
External instance of the constraint type MonadUnique UniqSM
getUniqueSupplyM
let (BlockAssignment freeRegs
_, StackMap
stack, RegAllocStats
stats, [NatBasicBlock instr]
blocks) =
NCGConfig
-> BlockAssignment freeRegs
-> freeRegs
-> RegMap Loc
-> StackMap
-> UniqSupply
-> RegM freeRegs [NatBasicBlock instr]
-> (BlockAssignment freeRegs, StackMap, RegAllocStats,
[NatBasicBlock instr])
forall freeRegs a.
NCGConfig
-> BlockAssignment freeRegs
-> freeRegs
-> RegMap Loc
-> StackMap
-> UniqSupply
-> RegM freeRegs a
-> (BlockAssignment freeRegs, StackMap, RegAllocStats, a)
runR NCGConfig
config BlockAssignment freeRegs
forall (map :: * -> *) a. IsMap map => map a
External instance of the constraint type IsMap LabelMap
mapEmpty freeRegs
initFreeRegs RegMap Loc
forall a. UniqFM a
emptyRegMap StackMap
emptyStackMap UniqSupply
us
(RegM freeRegs [NatBasicBlock instr]
-> (BlockAssignment freeRegs, StackMap, RegAllocStats,
[NatBasicBlock instr]))
-> RegM freeRegs [NatBasicBlock instr]
-> (BlockAssignment freeRegs, StackMap, RegAllocStats,
[NatBasicBlock instr])
forall a b. (a -> b) -> a -> b
$ [BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c2
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live [] [SCC (LiveBasicBlock instr)]
sccs
([NatBasicBlock instr], RegAllocStats, Int)
-> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad UniqSM
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 :: [BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
linearRA_SCCs [BlockId]
_ BlockMap RegSet
_ [NatBasicBlock instr]
blocksAcc []
= [NatBasicBlock instr] -> RegM freeRegs [NatBasicBlock instr]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([NatBasicBlock instr] -> RegM freeRegs [NatBasicBlock instr])
-> [NatBasicBlock instr] -> RegM freeRegs [NatBasicBlock instr]
forall a b. (a -> b) -> a -> b
$ [NatBasicBlock instr] -> [NatBasicBlock instr]
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' <- BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
processBlock BlockMap RegSet
block_live LiveBasicBlock instr
block
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live
(([NatBasicBlock instr] -> [NatBasicBlock instr]
forall a. [a] -> [a]
reverse [NatBasicBlock instr]
blocks') [NatBasicBlock instr]
-> [NatBasicBlock instr] -> [NatBasicBlock instr]
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' <- [BlockId]
-> BlockMap RegSet
-> [LiveBasicBlock instr]
-> [LiveBasicBlock instr]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
process [BlockId]
entry_ids BlockMap RegSet
block_live [LiveBasicBlock instr]
blocks [] ([NatBasicBlock instr] -> [[NatBasicBlock instr]]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad []
return []) Bool
False
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [NatBasicBlock instr]
-> [SCC (LiveBasicBlock instr)]
-> RegM freeRegs [NatBasicBlock instr]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
linearRA_SCCs [BlockId]
entry_ids BlockMap RegSet
block_live
([NatBasicBlock instr] -> [NatBasicBlock instr]
forall a. [a] -> [a]
reverse ([[NatBasicBlock instr]] -> [NatBasicBlock instr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
External instance of the constraint type Foldable []
concat [[NatBasicBlock instr]]
blockss') [NatBasicBlock instr]
-> [NatBasicBlock instr] -> [NatBasicBlock instr]
forall a. [a] -> [a] -> [a]
++ [NatBasicBlock instr]
blocksAcc)
[SCC (LiveBasicBlock instr)]
sccs
process :: OutputableRegConstraint freeRegs instr
=> [BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
process :: [BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
process [BlockId]
_ BlockMap RegSet
_ [] [] [[NatBasicBlock instr]]
accum Bool
_
= [[NatBasicBlock instr]] -> RegM freeRegs [[NatBasicBlock instr]]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([[NatBasicBlock instr]] -> RegM freeRegs [[NatBasicBlock instr]])
-> [[NatBasicBlock instr]] -> RegM freeRegs [[NatBasicBlock instr]]
forall a b. (a -> b) -> a -> b
$ [[NatBasicBlock instr]] -> [[NatBasicBlock instr]]
forall a. [a] -> [a]
reverse [[NatBasicBlock instr]]
accum
process [BlockId]
entry_ids BlockMap RegSet
block_live [] [GenBasicBlock (LiveInstr instr)]
next_round [[NatBasicBlock instr]]
accum Bool
madeProgress
| Bool -> Bool
not Bool
madeProgress
= [[NatBasicBlock instr]] -> RegM freeRegs [[NatBasicBlock instr]]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([[NatBasicBlock instr]] -> RegM freeRegs [[NatBasicBlock instr]])
-> [[NatBasicBlock instr]] -> RegM freeRegs [[NatBasicBlock instr]]
forall a b. (a -> b) -> a -> b
$ [[NatBasicBlock instr]] -> [[NatBasicBlock instr]]
forall a. [a] -> [a]
reverse [[NatBasicBlock instr]]
accum
| Bool
otherwise
= [BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
process [BlockId]
entry_ids BlockMap RegSet
block_live
[GenBasicBlock (LiveInstr instr)]
next_round [] [[NatBasicBlock instr]]
accum Bool
False
process [BlockId]
entry_ids BlockMap RegSet
block_live (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 <- RegM freeRegs (BlockAssignment freeRegs)
forall freeRegs. RegM freeRegs (BlockAssignment freeRegs)
getBlockAssigR
if Maybe (freeRegs, RegMap Loc) -> Bool
forall a. Maybe a -> Bool
isJust (KeyOf LabelMap
-> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup KeyOf LabelMap
BlockId
id BlockAssignment freeRegs
block_assig)
Bool -> Bool -> Bool
|| BlockId
id BlockId -> [BlockId] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq BlockId
External instance of the constraint type Foldable []
`elem` [BlockId]
entry_ids
then do
[NatBasicBlock instr]
b' <- BlockMap RegSet
-> GenBasicBlock (LiveInstr instr)
-> RegM freeRegs [NatBasicBlock instr]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
processBlock BlockMap RegSet
block_live GenBasicBlock (LiveInstr instr)
b
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
process [BlockId]
entry_ids BlockMap RegSet
block_live [GenBasicBlock (LiveInstr instr)]
blocks
[GenBasicBlock (LiveInstr instr)]
next_round ([NatBasicBlock instr]
b' [NatBasicBlock instr]
-> [[NatBasicBlock instr]] -> [[NatBasicBlock instr]]
forall a. a -> [a] -> [a]
: [[NatBasicBlock instr]]
accum) Bool
True
else [BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
[BlockId]
-> BlockMap RegSet
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
-> [[NatBasicBlock instr]]
-> Bool
-> RegM freeRegs [[NatBasicBlock instr]]
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
process [BlockId]
entry_ids BlockMap RegSet
block_live [GenBasicBlock (LiveInstr instr)]
blocks
(GenBasicBlock (LiveInstr instr)
b GenBasicBlock (LiveInstr instr)
-> [GenBasicBlock (LiveInstr instr)]
-> [GenBasicBlock (LiveInstr instr)]
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 :: BlockMap RegSet
-> LiveBasicBlock instr -> RegM freeRegs [NatBasicBlock instr]
processBlock BlockMap RegSet
block_live (BasicBlock BlockId
id [LiveInstr instr]
instrs)
= do
BlockId -> BlockMap RegSet -> RegM freeRegs ()
forall freeRegs.
FR freeRegs =>
BlockId -> BlockMap RegSet -> RegM freeRegs ()
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
initBlock BlockId
id BlockMap RegSet
block_live
([instr]
instrs', [NatBasicBlock instr]
fixups)
<- BlockMap RegSet
-> [instr]
-> [NatBasicBlock instr]
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> [NatBasicBlock instr]
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
linearRA BlockMap RegSet
block_live [] [] BlockId
id [LiveInstr instr]
instrs
[NatBasicBlock instr] -> RegM freeRegs [NatBasicBlock instr]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([NatBasicBlock instr] -> RegM freeRegs [NatBasicBlock instr])
-> [NatBasicBlock instr] -> RegM freeRegs [NatBasicBlock instr]
forall a b. (a -> b) -> a -> b
$ BlockId -> [instr] -> NatBasicBlock instr
forall i. BlockId -> [i] -> GenBasicBlock i
BasicBlock BlockId
id [instr]
instrs' NatBasicBlock instr
-> [NatBasicBlock instr] -> [NatBasicBlock instr]
forall a. a -> [a] -> [a]
: [NatBasicBlock instr]
fixups
initBlock :: FR freeRegs
=> BlockId -> BlockMap RegSet -> RegM freeRegs ()
initBlock :: BlockId -> BlockMap RegSet -> RegM freeRegs ()
initBlock BlockId
id BlockMap RegSet
block_live
= do Platform
platform <- RegM freeRegs Platform
forall a. RegM a Platform
getPlatform
BlockAssignment freeRegs
block_assig <- RegM freeRegs (BlockAssignment freeRegs)
forall freeRegs. RegM freeRegs (BlockAssignment freeRegs)
getBlockAssigR
case KeyOf LabelMap
-> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
forall (map :: * -> *) a.
IsMap map =>
KeyOf map -> map a -> Maybe a
External instance of the constraint type IsMap LabelMap
mapLookup KeyOf LabelMap
BlockId
id BlockAssignment freeRegs
block_assig of
Maybe (freeRegs, RegMap Loc)
Nothing
-> do
case 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
id BlockMap RegSet
block_live of
Maybe RegSet
Nothing ->
freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (Platform -> freeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frInitFreeRegs Platform
platform)
Just RegSet
live ->
freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (freeRegs -> RegM freeRegs ()) -> freeRegs -> RegM freeRegs ()
forall a b. (a -> b) -> a -> b
$ (freeRegs -> RealReg -> freeRegs)
-> freeRegs -> [RealReg] -> freeRegs
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' ((RealReg -> freeRegs -> freeRegs)
-> freeRegs -> RealReg -> freeRegs
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((RealReg -> freeRegs -> freeRegs)
-> freeRegs -> RealReg -> freeRegs)
-> (RealReg -> freeRegs -> freeRegs)
-> freeRegs
-> RealReg
-> freeRegs
forall a b. (a -> b) -> a -> b
$ Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frAllocateReg Platform
platform) (Platform -> freeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frInitFreeRegs Platform
platform)
[ RealReg
r | RegReal RealReg
r <- RegSet -> [Reg]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet RegSet
live ]
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
forall a. UniqFM a
emptyRegMap
Just (freeRegs
freeregs, RegMap Loc
assig)
-> do freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR freeRegs
freeregs
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig
linearRA
:: OutputableRegConstraint freeRegs instr
=> BlockMap RegSet
-> [instr]
-> [NatBasicBlock instr]
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs
( [instr]
, [NatBasicBlock instr])
linearRA :: BlockMap RegSet
-> [instr]
-> [NatBasicBlock instr]
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
linearRA BlockMap RegSet
_ [instr]
accInstr [NatBasicBlock instr]
accFixup BlockId
_ []
= ([instr], [NatBasicBlock instr])
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return
( [instr] -> [instr]
forall a. [a] -> [a]
reverse [instr]
accInstr
, [NatBasicBlock instr]
accFixup)
linearRA BlockMap RegSet
block_live [instr]
accInstr [NatBasicBlock instr]
accFixups BlockId
id (LiveInstr instr
instr:[LiveInstr instr]
instrs)
= do
([instr]
accInstr', [NatBasicBlock instr]
new_fixups) <- BlockMap RegSet
-> [instr]
-> BlockId
-> LiveInstr instr
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> BlockId
-> LiveInstr instr
-> RegM freeRegs ([instr], [NatBasicBlock instr])
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
raInsn BlockMap RegSet
block_live [instr]
accInstr BlockId
id LiveInstr instr
instr
BlockMap RegSet
-> [instr]
-> [NatBasicBlock instr]
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> [NatBasicBlock instr]
-> BlockId
-> [LiveInstr instr]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
linearRA BlockMap RegSet
block_live [instr]
accInstr' ([NatBasicBlock instr]
new_fixups [NatBasicBlock instr]
-> [NatBasicBlock instr] -> [NatBasicBlock instr]
forall a. [a] -> [a] -> [a]
++ [NatBasicBlock instr]
accFixups) BlockId
id [LiveInstr instr]
instrs
raInsn
:: OutputableRegConstraint freeRegs instr
=> BlockMap RegSet
-> [instr]
-> BlockId
-> LiveInstr instr
-> RegM freeRegs
( [instr]
, [NatBasicBlock instr])
raInsn :: 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 <- InstrSR instr -> Maybe Int
forall instr. Instruction instr => instr -> Maybe Int
External instance of the constraint type forall instr. Instruction instr => Instruction (InstrSR instr)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
takeDeltaInstr InstrSR instr
ii
= do Int -> RegM freeRegs ()
forall freeRegs. Int -> RegM freeRegs ()
setDeltaR Int
n
([instr], [NatBasicBlock instr])
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([instr]
new_instrs, [])
raInsn BlockMap RegSet
_ [instr]
new_instrs BlockId
_ (LiveInstr ii :: InstrSR instr
ii@(Instr instr
i) Maybe Liveness
Nothing)
| InstrSR instr -> Bool
forall instr. Instruction instr => instr -> Bool
External instance of the constraint type forall instr. Instruction instr => Instruction (InstrSR instr)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
isMetaInstr InstrSR instr
ii
= ([instr], [NatBasicBlock instr])
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return (instr
i instr -> [instr] -> [instr]
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 <- RegM freeRegs (RegMap Loc)
forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
case instr -> Maybe (Reg, Reg)
forall instr. Instruction instr => instr -> Maybe (Reg, Reg)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
takeRegRegMoveInstr instr
instr of
Just (Reg
src,Reg
dst) | Reg
src Reg -> RegSet -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
External instance of the constraint type Uniquable Reg
`elementOfUniqSet` (Liveness -> RegSet
liveDieRead Liveness
live),
Reg -> Bool
isVirtualReg Reg
dst,
Bool -> Bool
not (Reg
dst Reg -> RegMap Loc -> Bool
forall key elt. Uniquable key => key -> UniqFM elt -> Bool
External instance of the constraint type Uniquable Reg
`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) -> RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (RegMap Loc -> Reg -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable Reg
addToUFM RegMap Loc
assig Reg
dst (RealReg -> Loc
InReg RealReg
rr))
Reg
_virt -> case RegMap Loc -> Reg -> Maybe Loc
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable Reg
lookupUFM RegMap Loc
assig Reg
src of
Maybe Loc
Nothing -> String -> RegM freeRegs ()
forall a. String -> a
panic String
"raInsn"
Just Loc
loc ->
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (RegMap Loc -> Reg -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable Reg
addToUFM (RegMap Loc -> Reg -> RegMap Loc
forall key elt. Uniquable key => UniqFM elt -> key -> UniqFM elt
External instance of the constraint type Uniquable Reg
delFromUFM RegMap Loc
assig Reg
src) Reg
dst Loc
loc)
([instr], [NatBasicBlock instr])
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([instr]
new_instrs, [])
Maybe (Reg, Reg)
_ -> BlockMap RegSet
-> [instr]
-> BlockId
-> instr
-> [Reg]
-> [Reg]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall freeRegs instr.
OutputableRegConstraint freeRegs instr =>
BlockMap RegSet
-> [instr]
-> BlockId
-> instr
-> [Reg]
-> [Reg]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
genRaInsn BlockMap RegSet
block_live [instr]
new_instrs BlockId
id instr
instr
(RegSet -> [Reg]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet (RegSet -> [Reg]) -> RegSet -> [Reg]
forall a b. (a -> b) -> a -> b
$ Liveness -> RegSet
liveDieRead Liveness
live)
(RegSet -> [Reg]
forall elt. UniqSet elt -> [elt]
nonDetEltsUniqSet (RegSet -> [Reg]) -> RegSet -> [Reg]
forall a b. (a -> b) -> a -> b
$ Liveness -> RegSet
liveDieWrite Liveness
live)
raInsn BlockMap RegSet
_ [instr]
_ BlockId
_ LiveInstr instr
instr
= String -> SDoc -> RegM freeRegs ([instr], [NatBasicBlock instr])
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"raInsn" (String -> SDoc
text String
"no match for:" SDoc -> SDoc -> SDoc
<> LiveInstr instr -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall instr. Outputable instr => Outputable (LiveInstr instr)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
ppr LiveInstr instr
instr)
isInReg :: Reg -> RegMap Loc -> Bool
isInReg :: Reg -> RegMap Loc -> Bool
isInReg Reg
src RegMap Loc
assig | Just (InReg RealReg
_) <- RegMap Loc -> Reg -> Maybe Loc
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable Reg
lookupUFM RegMap Loc
assig Reg
src = Bool
True
| Bool
otherwise = Bool
False
genRaInsn :: OutputableRegConstraint freeRegs instr
=> BlockMap RegSet
-> [instr]
-> BlockId
-> instr
-> [Reg]
-> [Reg]
-> RegM freeRegs ([instr], [NatBasicBlock instr])
genRaInsn :: 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 <- RegM freeRegs Platform
forall a. RegM a Platform
getPlatform
case Platform -> instr -> RegUsage
forall instr. Instruction instr => Platform -> instr -> RegUsage
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
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 ]
let virt_written :: [VirtualReg]
virt_written = [ VirtualReg
vr | (RegVirtual VirtualReg
vr) <- [Reg]
written ]
let virt_read :: [VirtualReg]
virt_read = [VirtualReg] -> [VirtualReg]
forall a. Eq a => [a] -> [a]
External instance of the constraint type Eq VirtualReg
nub [ VirtualReg
vr | (RegVirtual VirtualReg
vr) <- [Reg]
read ]
([instr]
r_spills, [RealReg]
r_allocd) <-
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
allocateRegsAndSpill Bool
True [VirtualReg]
virt_read [] [] [VirtualReg]
virt_read
[instr]
clobber_saves <- [RealReg] -> [Reg] -> RegM freeRegs [instr]
forall instr freeRegs.
(Instruction instr, FR freeRegs) =>
[RealReg] -> [Reg] -> RegM freeRegs [instr]
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
saveClobberedTemps [RealReg]
real_written [Reg]
r_dying
([NatBasicBlock instr]
fixup_blocks, instr
adjusted_instr)
<- BlockMap RegSet
-> BlockId -> instr -> RegM freeRegs ([NatBasicBlock instr], instr)
forall freeRegs instr.
(FR freeRegs, Instruction instr, Outputable instr) =>
BlockMap RegSet
-> BlockId -> instr -> RegM freeRegs ([NatBasicBlock instr], instr)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
joinToTargets BlockMap RegSet
block_live BlockId
block_id instr
instr
[Reg] -> RegM freeRegs ()
forall freeRegs. FR freeRegs => [Reg] -> RegM freeRegs ()
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
releaseRegs [Reg]
r_dying
[RealReg] -> RegM freeRegs ()
forall freeRegs. FR freeRegs => [RealReg] -> RegM freeRegs ()
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
clobberRegs [RealReg]
real_written
([instr]
w_spills, [RealReg]
w_allocd) <-
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c3
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
allocateRegsAndSpill Bool
False [VirtualReg]
virt_written [] [] [VirtualReg]
virt_written
[Reg] -> RegM freeRegs ()
forall freeRegs. FR freeRegs => [Reg] -> RegM freeRegs ()
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c1
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
releaseRegs [Reg]
w_dying
let
patch_map :: UniqFM Reg
patch_map
= [(VirtualReg, Reg)] -> UniqFM Reg
forall key elt. Uniquable key => [(key, elt)] -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
listToUFM
[ (VirtualReg
t, RealReg -> Reg
RegReal RealReg
r)
| (VirtualReg
t, RealReg
r) <- [VirtualReg] -> [RealReg] -> [(VirtualReg, RealReg)]
forall a b. [a] -> [b] -> [(a, b)]
zip [VirtualReg]
virt_read [RealReg]
r_allocd
[(VirtualReg, RealReg)]
-> [(VirtualReg, RealReg)] -> [(VirtualReg, RealReg)]
forall a. [a] -> [a] -> [a]
++ [VirtualReg] -> [RealReg] -> [(VirtualReg, RealReg)]
forall a b. [a] -> [b] -> [(a, b)]
zip [VirtualReg]
virt_written [RealReg]
w_allocd ]
patched_instr :: instr
patched_instr
= instr -> (Reg -> Reg) -> instr
forall instr. Instruction instr => instr -> (Reg -> Reg) -> instr
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
patchRegsOfInstr instr
adjusted_instr Reg -> Reg
patchLookup
patchLookup :: Reg -> Reg
patchLookup Reg
x
= case UniqFM Reg -> Reg -> Maybe Reg
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable Reg
lookupUFM UniqFM Reg
patch_map Reg
x of
Maybe Reg
Nothing -> Reg
x
Just Reg
y -> Reg
y
let squashed_instr :: [instr]
squashed_instr = case instr -> Maybe (Reg, Reg)
forall instr. Instruction instr => instr -> Maybe (Reg, Reg)
External instance of the constraint type forall (c1 :: Constraint) (c2 :: Constraint) (c3 :: Constraint)
(c4 :: Constraint).
(c1, c2, c3, c4) =>
c4
Evidence bound by a type signature of the constraint type OutputableRegConstraint freeRegs instr
takeRegRegMoveInstr instr
patched_instr of
Just (Reg
src, Reg
dst)
| Reg
src Reg -> Reg -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Reg
== Reg
dst -> []
Maybe (Reg, Reg)
_ -> [instr
patched_instr]
let code :: [instr]
code = [instr]
squashed_instr [instr] -> [instr] -> [instr]
forall a. [a] -> [a] -> [a]
++ [instr]
w_spills [instr] -> [instr] -> [instr]
forall a. [a] -> [a] -> [a]
++ [instr] -> [instr]
forall a. [a] -> [a]
reverse [instr]
r_spills
[instr] -> [instr] -> [instr]
forall a. [a] -> [a] -> [a]
++ [instr]
clobber_saves [instr] -> [instr] -> [instr]
forall a. [a] -> [a] -> [a]
++ [instr]
new_instrs
([instr], [NatBasicBlock instr])
-> RegM freeRegs ([instr], [NatBasicBlock instr])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([instr]
code, [NatBasicBlock instr]
fixup_blocks)
}
releaseRegs :: FR freeRegs => [Reg] -> RegM freeRegs ()
releaseRegs :: [Reg] -> RegM freeRegs ()
releaseRegs [Reg]
regs = do
Platform
platform <- RegM freeRegs Platform
forall a. RegM a Platform
getPlatform
RegMap Loc
assig <- RegM freeRegs (RegMap Loc)
forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
freeRegs
free <- RegM freeRegs freeRegs
forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
let loop :: RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop RegMap Loc
assig !freeRegs
free [] = do RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig; freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR freeRegs
free; () -> RegM freeRegs ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ()
loop RegMap Loc
assig !freeRegs
free (RegReal RealReg
rr : [Reg]
rs) = RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop RegMap Loc
assig (Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frReleaseReg Platform
platform RealReg
rr freeRegs
free) [Reg]
rs
loop RegMap Loc
assig !freeRegs
free (Reg
r:[Reg]
rs) =
case RegMap Loc -> Reg -> Maybe Loc
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable Reg
lookupUFM RegMap Loc
assig Reg
r of
Just (InBoth RealReg
real Int
_) -> RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop (RegMap Loc -> Reg -> RegMap Loc
forall key elt. Uniquable key => UniqFM elt -> key -> UniqFM elt
External instance of the constraint type Uniquable Reg
delFromUFM RegMap Loc
assig Reg
r)
(Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frReleaseReg Platform
platform RealReg
real freeRegs
free) [Reg]
rs
Just (InReg RealReg
real) -> RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop (RegMap Loc -> Reg -> RegMap Loc
forall key elt. Uniquable key => UniqFM elt -> key -> UniqFM elt
External instance of the constraint type Uniquable Reg
delFromUFM RegMap Loc
assig Reg
r)
(Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frReleaseReg Platform
platform RealReg
real freeRegs
free) [Reg]
rs
Maybe Loc
_ -> RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
loop (RegMap Loc -> Reg -> RegMap Loc
forall key elt. Uniquable key => UniqFM elt -> key -> UniqFM elt
External instance of the constraint type Uniquable Reg
delFromUFM RegMap Loc
assig Reg
r) freeRegs
free [Reg]
rs
RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
forall {freeRegs}.
FR freeRegs =>
RegMap Loc -> freeRegs -> [Reg] -> RegM freeRegs ()
Evidence bound by a type signature of the constraint type FR freeRegs
loop RegMap Loc
assig freeRegs
free [Reg]
regs
saveClobberedTemps
:: (Instruction instr, FR freeRegs)
=> [RealReg]
-> [Reg]
-> RegM freeRegs [instr]
saveClobberedTemps :: [RealReg] -> [Reg] -> RegM freeRegs [instr]
saveClobberedTemps [] [Reg]
_
= [instr] -> RegM freeRegs [instr]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return []
saveClobberedTemps [RealReg]
clobbered [Reg]
dying
= do
RegMap Loc
assig <- RegM freeRegs (RegMap Loc)
forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
let to_spill :: [(Unique, RealReg)]
to_spill
= [ (Unique
temp,RealReg
reg)
| (Unique
temp, InReg RealReg
reg) <- RegMap Loc -> [(Unique, Loc)]
forall elt. UniqFM elt -> [(Unique, elt)]
nonDetUFMToList RegMap Loc
assig
, (RealReg -> Bool) -> [RealReg] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
any (RealReg -> RealReg -> Bool
realRegsAlias RealReg
reg) [RealReg]
clobbered
, Unique
temp Unique -> [Unique] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq Unique
External instance of the constraint type Foldable []
`notElem` (Reg -> Unique) -> [Reg] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map Reg -> Unique
forall a. Uniquable a => a -> Unique
External instance of the constraint type Uniquable Reg
getUnique [Reg]
dying ]
([instr]
instrs,RegMap Loc
assig') <- RegMap Loc
-> [instr]
-> [(Unique, RealReg)]
-> RegM freeRegs ([instr], RegMap Loc)
forall {freeRegs} {a}.
(FR freeRegs, Instruction a) =>
RegMap Loc
-> [a] -> [(Unique, RealReg)] -> RegM freeRegs ([a], RegMap Loc)
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type FR freeRegs
clobber RegMap Loc
assig [] [(Unique, RealReg)]
to_spill
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig'
[instr] -> RegM freeRegs [instr]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return [instr]
instrs
where
clobber :: RegMap Loc
-> [a] -> [(Unique, RealReg)] -> RegM freeRegs ([a], RegMap Loc)
clobber RegMap Loc
assig [a]
instrs []
= ([a], RegMap Loc) -> RegM freeRegs ([a], RegMap Loc)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([a]
instrs, RegMap Loc
assig)
clobber RegMap Loc
assig [a]
instrs ((Unique
temp, RealReg
reg) : [(Unique, RealReg)]
rest)
= do Platform
platform <- RegM freeRegs Platform
forall a. RegM a Platform
getPlatform
freeRegs
freeRegs <- RegM 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 = Platform -> RegClass -> freeRegs -> [RealReg]
forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
Evidence bound by a type signature of the constraint type FR freeRegs
frGetFreeRegs Platform
platform RegClass
regclass freeRegs
freeRegs
case (RealReg -> Bool) -> [RealReg] -> [RealReg]
forall a. (a -> Bool) -> [a] -> [a]
filter (RealReg -> [RealReg] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq RealReg
External instance of the constraint type Foldable []
`notElem` [RealReg]
clobbered) [RealReg]
freeRegs_thisClass of
(RealReg
my_reg : [RealReg]
_) -> do
freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frAllocateReg Platform
platform RealReg
my_reg freeRegs
freeRegs)
let new_assign :: RegMap Loc
new_assign = RegMap Loc -> Unique -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable Unique
addToUFM RegMap Loc
assig Unique
temp (RealReg -> Loc
InReg RealReg
my_reg)
let instr :: a
instr = Platform -> Reg -> Reg -> a
forall instr. Instruction instr => Platform -> Reg -> Reg -> instr
Evidence bound by a type signature of the constraint type Instruction a
mkRegRegMoveInstr Platform
platform
(RealReg -> Reg
RegReal RealReg
reg) (RealReg -> Reg
RegReal RealReg
my_reg)
RegMap Loc
-> [a] -> [(Unique, RealReg)] -> RegM freeRegs ([a], RegMap Loc)
clobber RegMap Loc
new_assign (a
instr a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
instrs) [(Unique, RealReg)]
rest
[] -> do
(a
spill, Int
slot) <- Reg -> Unique -> RegM freeRegs (a, Int)
forall instr freeRegs.
Instruction instr =>
Reg -> Unique -> RegM freeRegs (instr, Int)
Evidence bound by a type signature of the constraint type Instruction a
spillR (RealReg -> Reg
RegReal RealReg
reg) Unique
temp
SpillReason -> RegM freeRegs ()
forall freeRegs. SpillReason -> RegM freeRegs ()
recordSpill (Unique -> SpillReason
SpillClobber Unique
temp)
let new_assign :: RegMap Loc
new_assign = RegMap Loc -> Unique -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable Unique
addToUFM RegMap Loc
assig Unique
temp (RealReg -> Int -> Loc
InBoth RealReg
reg Int
slot)
RegMap Loc
-> [a] -> [(Unique, RealReg)] -> RegM freeRegs ([a], RegMap Loc)
clobber RegMap Loc
new_assign (a
spill a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
instrs) [(Unique, RealReg)]
rest
clobberRegs :: FR freeRegs => [RealReg] -> RegM freeRegs ()
clobberRegs :: [RealReg] -> RegM freeRegs ()
clobberRegs []
= () -> RegM freeRegs ()
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ()
clobberRegs [RealReg]
clobbered
= do Platform
platform <- RegM freeRegs Platform
forall a. RegM a Platform
getPlatform
freeRegs
freeregs <- RegM freeRegs freeRegs
forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (freeRegs -> RegM freeRegs ()) -> freeRegs -> RegM freeRegs ()
forall a b. (a -> b) -> a -> b
$! (freeRegs -> RealReg -> freeRegs)
-> freeRegs -> [RealReg] -> freeRegs
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldl' ((RealReg -> freeRegs -> freeRegs)
-> freeRegs -> RealReg -> freeRegs
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((RealReg -> freeRegs -> freeRegs)
-> freeRegs -> RealReg -> freeRegs)
-> (RealReg -> freeRegs -> freeRegs)
-> freeRegs
-> RealReg
-> freeRegs
forall a b. (a -> b) -> a -> b
$ Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frAllocateReg Platform
platform) freeRegs
freeregs [RealReg]
clobbered
RegMap Loc
assig <- RegM freeRegs (RegMap Loc)
forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (RegMap Loc -> RegM freeRegs ()) -> RegMap Loc -> RegM freeRegs ()
forall a b. (a -> b) -> a -> b
$! RegMap Loc -> [(Unique, Loc)] -> RegMap Loc
forall {key}.
Uniquable key =>
RegMap Loc -> [(key, Loc)] -> RegMap Loc
External instance of the constraint type Uniquable Unique
clobber RegMap Loc
assig (RegMap Loc -> [(Unique, Loc)]
forall elt. UniqFM elt -> [(Unique, elt)]
nonDetUFMToList RegMap Loc
assig)
where
clobber :: RegMap Loc -> [(key, Loc)] -> RegMap Loc
clobber RegMap Loc
assig []
= RegMap Loc
assig
clobber RegMap Loc
assig ((key
temp, InBoth RealReg
reg Int
slot) : [(key, Loc)]
rest)
| (RealReg -> Bool) -> [RealReg] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
External instance of the constraint type Foldable []
any (RealReg -> RealReg -> Bool
realRegsAlias RealReg
reg) [RealReg]
clobbered
= RegMap Loc -> [(key, Loc)] -> RegMap Loc
clobber (RegMap Loc -> key -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
Evidence bound by a type signature of the constraint type Uniquable key
addToUFM RegMap Loc
assig key
temp (Int -> Loc
InMem Int
slot)) [(key, Loc)]
rest
clobber RegMap Loc
assig ((key, Loc)
_:[(key, Loc)]
rest)
= RegMap Loc -> [(key, Loc)] -> RegMap Loc
clobber RegMap Loc
assig [(key, Loc)]
rest
data SpillLoc = ReadMem StackSlot
| WriteNew
| WriteMem
allocateRegsAndSpill
:: forall freeRegs instr. (FR freeRegs, Outputable instr, Instruction instr)
=> Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ( [instr] , [RealReg])
allocateRegsAndSpill :: Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
allocateRegsAndSpill Bool
_ [VirtualReg]
_ [instr]
spills [RealReg]
alloc []
= ([instr], [RealReg]) -> RegM freeRegs ([instr], [RealReg])
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([instr]
spills, [RealReg] -> [RealReg]
forall a. [a] -> [a]
reverse [RealReg]
alloc)
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills [RealReg]
alloc (VirtualReg
r:[VirtualReg]
rs)
= do RegMap Loc
assig <- RegM freeRegs (RegMap Loc)
forall freeRegs. RegM freeRegs (RegMap Loc)
getAssigR :: RegM freeRegs (RegMap Loc)
let doSpill :: SpillLoc -> RegM freeRegs ([instr], [RealReg])
doSpill = Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> RegMap Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Instruction instr, Outputable instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> RegMap Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type FR freeRegs
allocRegsAndSpill_spill Bool
reading [VirtualReg]
keep [instr]
spills [RealReg]
alloc VirtualReg
r [VirtualReg]
rs RegMap Loc
assig
case RegMap Loc -> VirtualReg -> Maybe Loc
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
External instance of the constraint type Uniquable VirtualReg
lookupUFM RegMap Loc
assig VirtualReg
r of
Just (InReg RealReg
my_reg) ->
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type FR freeRegs
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills (RealReg
my_regRealReg -> [RealReg] -> [RealReg]
forall a. a -> [a] -> [a]
:[RealReg]
alloc) [VirtualReg]
rs
Just (InBoth RealReg
my_reg Int
_)
-> do Bool -> RegM freeRegs () -> RegM freeRegs ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type forall freeRegs. Applicative (RegM freeRegs)
when (Bool -> Bool
not Bool
reading) (RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (RegMap Loc -> VirtualReg -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM RegMap Loc
assig VirtualReg
r (RealReg -> Loc
InReg RealReg
my_reg)))
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type FR freeRegs
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills (RealReg
my_regRealReg -> [RealReg] -> [RealReg]
forall 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 ->
String -> SDoc -> RegM freeRegs ([instr], [RealReg])
forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"allocateRegsAndSpill: Cannot read from uninitialized register" (VirtualReg -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable VirtualReg
ppr VirtualReg
r)
| Bool
otherwise -> SpillLoc -> RegM freeRegs ([instr], [RealReg])
doSpill SpillLoc
WriteNew
findPrefRealReg :: forall freeRegs u. Uniquable u
=> u -> RegM freeRegs (Maybe RealReg)
findPrefRealReg :: u -> RegM freeRegs (Maybe RealReg)
findPrefRealReg u
vreg = do
BlockMap (freeRegs, RegMap Loc)
bassig <- RegM freeRegs (BlockMap (freeRegs, RegMap Loc))
forall freeRegs. RegM freeRegs (BlockAssignment freeRegs)
getBlockAssigR :: RegM freeRegs (BlockMap (freeRegs,RegMap Loc))
Maybe RealReg -> RegM freeRegs (Maybe RealReg)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return (Maybe RealReg -> RegM freeRegs (Maybe RealReg))
-> Maybe RealReg -> RegM freeRegs (Maybe RealReg)
forall a b. (a -> b) -> a -> b
$ ((freeRegs, RegMap Loc) -> Maybe RealReg -> Maybe RealReg)
-> Maybe RealReg
-> BlockMap (freeRegs, RegMap Loc)
-> Maybe RealReg
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable LabelMap
foldr ((freeRegs, RegMap Loc) -> Maybe RealReg -> Maybe RealReg
findVirtRegAssig) Maybe RealReg
forall a. Maybe a
Nothing BlockMap (freeRegs, RegMap Loc)
bassig
where
findVirtRegAssig :: (freeRegs,RegMap Loc) -> Maybe RealReg -> Maybe RealReg
findVirtRegAssig :: (freeRegs, RegMap Loc) -> Maybe RealReg -> Maybe RealReg
findVirtRegAssig (freeRegs, RegMap Loc)
assig Maybe RealReg
z =
Maybe RealReg
z Maybe RealReg -> Maybe RealReg -> Maybe RealReg
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
External instance of the constraint type Alternative Maybe
<|> case RegMap Loc -> u -> Maybe Loc
forall key elt. Uniquable key => UniqFM elt -> key -> Maybe elt
Evidence bound by a type signature of the constraint type Uniquable u
lookupUFM ((freeRegs, RegMap Loc) -> RegMap Loc
forall a b. (a, b) -> b
snd (freeRegs, RegMap Loc)
assig) u
vreg of
Just (InReg RealReg
real_reg) -> RealReg -> Maybe RealReg
forall a. a -> Maybe a
Just RealReg
real_reg
Just (InBoth RealReg
real_reg Int
_) -> RealReg -> Maybe RealReg
forall a. a -> Maybe a
Just RealReg
real_reg
Maybe Loc
_ -> Maybe RealReg
z
allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr, Outputable instr)
=> Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> UniqFM Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
allocRegsAndSpill_spill :: Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> VirtualReg
-> [VirtualReg]
-> RegMap Loc
-> SpillLoc
-> RegM freeRegs ([instr], [RealReg])
allocRegsAndSpill_spill Bool
reading [VirtualReg]
keep [instr]
spills [RealReg]
alloc VirtualReg
r [VirtualReg]
rs RegMap Loc
assig SpillLoc
spill_loc
= do Platform
platform <- RegM freeRegs Platform
forall a. RegM a Platform
getPlatform
freeRegs
freeRegs <- RegM freeRegs freeRegs
forall freeRegs. RegM freeRegs freeRegs
getFreeRegsR
let freeRegs_thisClass :: [RealReg]
freeRegs_thisClass = Platform -> RegClass -> freeRegs -> [RealReg]
forall freeRegs.
FR freeRegs =>
Platform -> RegClass -> freeRegs -> [RealReg]
Evidence bound by a type signature of the constraint type FR freeRegs
frGetFreeRegs Platform
platform (VirtualReg -> RegClass
classOfVirtualReg VirtualReg
r) freeRegs
freeRegs :: [RealReg]
Maybe RealReg
pref_reg <- VirtualReg -> RegM freeRegs (Maybe RealReg)
forall freeRegs u.
Uniquable u =>
u -> RegM freeRegs (Maybe RealReg)
External instance of the constraint type Uniquable VirtualReg
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 RealReg -> [RealReg] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq RealReg
External instance of the constraint type Foldable []
`elem` [RealReg]
freeRegs_thisClass
= RealReg
reg
| Bool
otherwise
= RealReg
first_free
[instr]
spills' <- VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
Evidence bound by a type signature of the constraint type Instruction instr
loadTemp VirtualReg
r SpillLoc
spill_loc RealReg
final_reg [instr]
spills
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR (RegMap Loc -> VirtualReg -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM RegMap Loc
assig VirtualReg
r (Loc -> RegMap Loc) -> Loc -> RegMap Loc
forall a b. (a -> b) -> a -> b
$! SpillLoc -> RealReg -> Loc
newLocation SpillLoc
spill_loc RealReg
final_reg)
freeRegs -> RegM freeRegs ()
forall freeRegs. freeRegs -> RegM freeRegs ()
setFreeRegsR (freeRegs -> RegM freeRegs ()) -> freeRegs -> RegM freeRegs ()
forall a b. (a -> b) -> a -> b
$ Platform -> RealReg -> freeRegs -> freeRegs
forall freeRegs.
FR freeRegs =>
Platform -> RealReg -> freeRegs -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frAllocateReg Platform
platform RealReg
final_reg freeRegs
freeRegs
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type FR freeRegs
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills' (RealReg
final_reg RealReg -> [RealReg] -> [RealReg]
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 Loc
candidates' :: RegMap Loc
candidates' =
(RegMap Loc -> [VirtualReg] -> RegMap Loc)
-> [VirtualReg] -> RegMap Loc -> RegMap Loc
forall a b c. (a -> b -> c) -> b -> a -> c
flip RegMap Loc -> [VirtualReg] -> RegMap Loc
forall key elt. Uniquable key => UniqFM elt -> [key] -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
delListFromUFM [VirtualReg]
keep (RegMap Loc -> RegMap Loc) -> RegMap Loc -> RegMap Loc
forall a b. (a -> b) -> a -> b
$
(Loc -> Bool) -> RegMap Loc -> RegMap Loc
forall elt. (elt -> Bool) -> UniqFM elt -> UniqFM elt
filterUFM Loc -> Bool
inRegOrBoth (RegMap Loc -> RegMap Loc) -> RegMap Loc -> RegMap Loc
forall a b. (a -> b) -> a -> b
$
RegMap Loc
assig
let candidates :: [(Unique, Loc)]
candidates = RegMap Loc -> [(Unique, Loc)]
forall elt. UniqFM elt -> [(Unique, elt)]
nonDetUFMToList RegMap Loc
candidates'
let 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 RegClass -> RegClass -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq RegClass
== 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 RegClass -> RegClass -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq RegClass
== 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' <- VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
Evidence bound by a type signature of the constraint type Instruction instr
loadTemp VirtualReg
r SpillLoc
spill_loc RealReg
my_reg [instr]
spills
let assig1 :: RegMap Loc
assig1 = RegMap Loc -> Unique -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable Unique
addToUFM RegMap Loc
assig Unique
temp (Int -> Loc
InMem Int
slot)
let assig2 :: RegMap Loc
assig2 = RegMap Loc -> VirtualReg -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM RegMap Loc
assig1 VirtualReg
r (Loc -> RegMap Loc) -> Loc -> RegMap Loc
forall a b. (a -> b) -> a -> b
$! SpillLoc -> RealReg -> Loc
newLocation SpillLoc
spill_loc RealReg
my_reg
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig2
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type FR freeRegs
allocateRegsAndSpill Bool
reading [VirtualReg]
keep [instr]
spills' (RealReg
my_regRealReg -> [RealReg] -> [RealReg]
forall 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_insn, Int
slot) <- Reg -> Unique -> RegM freeRegs (instr, Int)
forall instr freeRegs.
Instruction instr =>
Reg -> Unique -> RegM freeRegs (instr, Int)
Evidence bound by a type signature of the constraint type Instruction instr
spillR (RealReg -> Reg
RegReal RealReg
my_reg) Unique
temp_to_push_out
let spill_store :: [instr]
spill_store = (if Bool
reading then [instr] -> [instr]
forall a. a -> a
id else [instr] -> [instr]
forall a. [a] -> [a]
reverse)
[
instr
spill_insn ]
SpillReason -> RegM freeRegs ()
forall freeRegs. SpillReason -> RegM freeRegs ()
recordSpill (Unique -> SpillReason
SpillAlloc Unique
temp_to_push_out)
let assig1 :: RegMap Loc
assig1 = RegMap Loc -> Unique -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable Unique
addToUFM RegMap Loc
assig Unique
temp_to_push_out (Int -> Loc
InMem Int
slot)
let assig2 :: RegMap Loc
assig2 = RegMap Loc -> VirtualReg -> Loc -> RegMap Loc
forall key elt.
Uniquable key =>
UniqFM elt -> key -> elt -> UniqFM elt
External instance of the constraint type Uniquable VirtualReg
addToUFM RegMap Loc
assig1 VirtualReg
r (Loc -> RegMap Loc) -> Loc -> RegMap Loc
forall a b. (a -> b) -> a -> b
$! SpillLoc -> RealReg -> Loc
newLocation SpillLoc
spill_loc RealReg
my_reg
RegMap Loc -> RegM freeRegs ()
forall freeRegs. RegMap Loc -> RegM freeRegs ()
setAssigR RegMap Loc
assig2
[instr]
spills' <- VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
forall instr freeRegs.
Instruction instr =>
VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
Evidence bound by a type signature of the constraint type Instruction instr
loadTemp VirtualReg
r SpillLoc
spill_loc RealReg
my_reg [instr]
spills
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
forall freeRegs instr.
(FR freeRegs, Outputable instr, Instruction instr) =>
Bool
-> [VirtualReg]
-> [instr]
-> [RealReg]
-> [VirtualReg]
-> RegM freeRegs ([instr], [RealReg])
Evidence bound by a type signature of the constraint type Instruction instr
Evidence bound by a type signature of the constraint type Outputable instr
Evidence bound by a type signature of the constraint type FR freeRegs
allocateRegsAndSpill Bool
reading [VirtualReg]
keep
([instr]
spill_store [instr] -> [instr] -> [instr]
forall a. [a] -> [a] -> [a]
++ [instr]
spills')
(RealReg
my_regRealReg -> [RealReg] -> [RealReg]
forall a. a -> [a] -> [a]
:[RealReg]
alloc) [VirtualReg]
rs
| Bool
otherwise
= String -> SDoc -> RegM freeRegs ([instr], [RealReg])
forall a. HasCallStack => String -> SDoc -> a
pprPanic (String
"RegAllocLinear.allocRegsAndSpill: no spill candidates\n")
(SDoc -> RegM freeRegs ([instr], [RealReg]))
-> SDoc -> RegM freeRegs ([instr], [RealReg])
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
vcat
[ String -> SDoc
text String
"allocating vreg: " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (VirtualReg -> String
forall a. Show a => a -> String
External instance of the constraint type Show VirtualReg
show VirtualReg
r)
, String -> SDoc
text String
"assignment: " SDoc -> SDoc -> SDoc
<> RegMap Loc -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type forall a. Outputable a => Outputable (UniqFM a)
External instance of the constraint type Outputable Loc
ppr RegMap Loc
assig
, String -> SDoc
text String
"freeRegs: " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (freeRegs -> String
forall a. Show a => a -> String
External instance of the constraint type forall freeRegs. FR freeRegs => Show freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
show freeRegs
freeRegs)
, String -> SDoc
text String
"initFreeRegs: " SDoc -> SDoc -> SDoc
<> String -> SDoc
text (freeRegs -> String
forall a. Show a => a -> String
External instance of the constraint type forall freeRegs. FR freeRegs => Show freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
show (Platform -> freeRegs
forall freeRegs. FR freeRegs => Platform -> freeRegs
Evidence bound by a type signature of the constraint type FR freeRegs
frInitFreeRegs Platform
platform freeRegs -> freeRegs -> freeRegs
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 :: VirtualReg
-> SpillLoc -> RealReg -> [instr] -> RegM freeRegs [instr]
loadTemp VirtualReg
vreg (ReadMem Int
slot) RealReg
hreg [instr]
spills
= do
instr
insn <- Reg -> Int -> RegM freeRegs instr
forall instr freeRegs.
Instruction instr =>
Reg -> Int -> RegM freeRegs instr
Evidence bound by a type signature of the constraint type Instruction instr
loadR (RealReg -> Reg
RegReal RealReg
hreg) Int
slot
SpillReason -> RegM freeRegs ()
forall freeRegs. SpillReason -> RegM freeRegs ()
recordSpill (Unique -> SpillReason
SpillLoad (Unique -> SpillReason) -> Unique -> SpillReason
forall a b. (a -> b) -> a -> b
$ VirtualReg -> Unique
forall a. Uniquable a => a -> Unique
External instance of the constraint type Uniquable VirtualReg
getUnique VirtualReg
vreg)
[instr] -> RegM freeRegs [instr]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return ([instr] -> RegM freeRegs [instr])
-> [instr] -> RegM freeRegs [instr]
forall a b. (a -> b) -> a -> b
$ instr
insn instr -> [instr] -> [instr]
forall a. a -> [a] -> [a]
: [instr]
spills
loadTemp VirtualReg
_ SpillLoc
_ RealReg
_ [instr]
spills =
[instr] -> RegM freeRegs [instr]
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type forall freeRegs. Monad (RegM freeRegs)
return [instr]
spills