module GHC.CmmToAsm.Reg.Linear.Base (
BlockAssignment,
Loc(..),
regsOfLoc,
SpillReason(..),
RegAllocStats(..),
RA_State(..),
)
where
import GHC.Prelude
import GHC.CmmToAsm.Reg.Linear.StackMap
import GHC.CmmToAsm.Reg.Liveness
import GHC.CmmToAsm.Config
import GHC.Platform.Reg
import GHC.Utils.Outputable
import GHC.Types.Unique
import GHC.Types.Unique.FM
import GHC.Types.Unique.Supply
import GHC.Cmm.BlockId
data ReadingOrWriting = Reading | Writing deriving (ReadingOrWriting -> ReadingOrWriting -> Bool
(ReadingOrWriting -> ReadingOrWriting -> Bool)
-> (ReadingOrWriting -> ReadingOrWriting -> Bool)
-> Eq ReadingOrWriting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c/= :: ReadingOrWriting -> ReadingOrWriting -> Bool
== :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c== :: ReadingOrWriting -> ReadingOrWriting -> Bool
Eq,Eq ReadingOrWriting
Eq ReadingOrWriting
-> (ReadingOrWriting -> ReadingOrWriting -> Ordering)
-> (ReadingOrWriting -> ReadingOrWriting -> Bool)
-> (ReadingOrWriting -> ReadingOrWriting -> Bool)
-> (ReadingOrWriting -> ReadingOrWriting -> Bool)
-> (ReadingOrWriting -> ReadingOrWriting -> Bool)
-> (ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting)
-> (ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting)
-> Ord ReadingOrWriting
ReadingOrWriting -> ReadingOrWriting -> Bool
ReadingOrWriting -> ReadingOrWriting -> Ordering
ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
$cmin :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
max :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
$cmax :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
>= :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c>= :: ReadingOrWriting -> ReadingOrWriting -> Bool
> :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c> :: ReadingOrWriting -> ReadingOrWriting -> Bool
<= :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c<= :: ReadingOrWriting -> ReadingOrWriting -> Bool
< :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c< :: ReadingOrWriting -> ReadingOrWriting -> Bool
compare :: ReadingOrWriting -> ReadingOrWriting -> Ordering
$ccompare :: ReadingOrWriting -> ReadingOrWriting -> Ordering
Instance of class: Eq of the constraint type Eq ReadingOrWriting
Instance of class: Ord of the constraint type Ord ReadingOrWriting
Instance of class: Eq of the constraint type Eq ReadingOrWriting
Ord)
type BlockAssignment freeRegs
= BlockMap (freeRegs, RegMap Loc)
data Loc
= InReg !RealReg
| InMem {-# UNPACK #-} !StackSlot
| InBoth !RealReg
{-# UNPACK #-} !StackSlot
deriving (Loc -> Loc -> Bool
(Loc -> Loc -> Bool) -> (Loc -> Loc -> Bool) -> Eq Loc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Loc -> Loc -> Bool
$c/= :: Loc -> Loc -> Bool
== :: Loc -> Loc -> Bool
$c== :: Loc -> Loc -> Bool
External instance of the constraint type Eq StackSlot
External instance of the constraint type Eq StackSlot
External instance of the constraint type Eq RealReg
External instance of the constraint type Eq RealReg
Eq, StackSlot -> Loc -> ShowS
[Loc] -> ShowS
Loc -> String
(StackSlot -> Loc -> ShowS)
-> (Loc -> String) -> ([Loc] -> ShowS) -> Show Loc
forall a.
(StackSlot -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Loc] -> ShowS
$cshowList :: [Loc] -> ShowS
show :: Loc -> String
$cshow :: Loc -> String
showsPrec :: StackSlot -> Loc -> ShowS
$cshowsPrec :: StackSlot -> Loc -> ShowS
External instance of the constraint type Show StackSlot
External instance of the constraint type Show StackSlot
External instance of the constraint type Show RealReg
External instance of the constraint type Show RealReg
External instance of the constraint type Ord StackSlot
External instance of the constraint type Ord StackSlot
Show, Eq Loc
Eq Loc
-> (Loc -> Loc -> Ordering)
-> (Loc -> Loc -> Bool)
-> (Loc -> Loc -> Bool)
-> (Loc -> Loc -> Bool)
-> (Loc -> Loc -> Bool)
-> (Loc -> Loc -> Loc)
-> (Loc -> Loc -> Loc)
-> Ord Loc
Loc -> Loc -> Bool
Loc -> Loc -> Ordering
Loc -> Loc -> Loc
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Loc -> Loc -> Loc
$cmin :: Loc -> Loc -> Loc
max :: Loc -> Loc -> Loc
$cmax :: Loc -> Loc -> Loc
>= :: Loc -> Loc -> Bool
$c>= :: Loc -> Loc -> Bool
> :: Loc -> Loc -> Bool
$c> :: Loc -> Loc -> Bool
<= :: Loc -> Loc -> Bool
$c<= :: Loc -> Loc -> Bool
< :: Loc -> Loc -> Bool
$c< :: Loc -> Loc -> Bool
compare :: Loc -> Loc -> Ordering
$ccompare :: Loc -> Loc -> Ordering
External instance of the constraint type Ord StackSlot
External instance of the constraint type Ord RealReg
External instance of the constraint type Ord StackSlot
External instance of the constraint type Ord RealReg
External instance of the constraint type Ord RealReg
Instance of class: Eq of the constraint type Eq Loc
External instance of the constraint type Ord StackSlot
Instance of class: Ord of the constraint type Ord Loc
Instance of class: Eq of the constraint type Eq Loc
Ord)
instance Outputable Loc where
ppr :: Loc -> SDoc
ppr Loc
l = String -> SDoc
text (Loc -> String
forall a. Show a => a -> String
Instance of class: Show of the constraint type Show Loc
show Loc
l)
regsOfLoc :: Loc -> [RealReg]
regsOfLoc :: Loc -> [RealReg]
regsOfLoc (InReg RealReg
r) = [RealReg
r]
regsOfLoc (InBoth RealReg
r StackSlot
_) = [RealReg
r]
regsOfLoc (InMem StackSlot
_) = []
data SpillReason
= SpillAlloc !Unique
| SpillClobber !Unique
| SpillLoad !Unique
| SpillJoinRR !Unique
| SpillJoinRM !Unique
data RegAllocStats
= RegAllocStats
{ RegAllocStats -> UniqFM [StackSlot]
ra_spillInstrs :: UniqFM [Int]
, RegAllocStats -> [(BlockId, BlockId, BlockId)]
ra_fixupList :: [(BlockId,BlockId,BlockId)]
}
data RA_State freeRegs
= RA_State
{
RA_State freeRegs -> BlockAssignment freeRegs
ra_blockassig :: BlockAssignment freeRegs
, RA_State freeRegs -> freeRegs
ra_freeregs :: !freeRegs
, RA_State freeRegs -> RegMap Loc
ra_assig :: RegMap Loc
, RA_State freeRegs -> StackSlot
ra_delta :: Int
, RA_State freeRegs -> StackMap
ra_stack :: StackMap
, RA_State freeRegs -> UniqSupply
ra_us :: UniqSupply
, RA_State freeRegs -> [SpillReason]
ra_spills :: [SpillReason]
, RA_State freeRegs -> NCGConfig
ra_config :: !NCGConfig
, RA_State freeRegs -> [(BlockId, BlockId, BlockId)]
ra_fixups :: [(BlockId,BlockId,BlockId)]
}