{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
module GHC.CmmToAsm.Reg.Linear.Base (
BlockAssignment,
lookupBlockAssignment,
lookupFirstUsed,
emptyBlockAssignment,
updateBlockAssignment,
VLoc(..), Loc(..), IgnoreFormat(..),
regsOfLoc,
RealRegUsage(..),
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.DSM
import GHC.Cmm.BlockId
import GHC.Cmm.Dataflow.Label
import GHC.CmmToAsm.Reg.Utils
import GHC.CmmToAsm.Format
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
$c== :: ReadingOrWriting -> ReadingOrWriting -> Bool
== :: ReadingOrWriting -> ReadingOrWriting -> Bool
$c/= :: ReadingOrWriting -> ReadingOrWriting -> Bool
/= :: 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
$ccompare :: ReadingOrWriting -> ReadingOrWriting -> Ordering
compare :: ReadingOrWriting -> ReadingOrWriting -> Ordering
$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
>= :: ReadingOrWriting -> ReadingOrWriting -> Bool
$cmax :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
max :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
$cmin :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
min :: ReadingOrWriting -> ReadingOrWriting -> ReadingOrWriting
Ord)
data BlockAssignment freeRegs
= BlockAssignment { forall freeRegs.
BlockAssignment freeRegs -> BlockMap (freeRegs, RegMap Loc)
blockMap :: !(BlockMap (freeRegs, RegMap Loc))
, forall freeRegs.
BlockAssignment freeRegs -> UniqFM VirtualReg RealReg
firstUsed :: !(UniqFM VirtualReg RealReg) }
lookupBlockAssignment :: BlockId -> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
lookupBlockAssignment :: forall freeRegs.
BlockId -> BlockAssignment freeRegs -> Maybe (freeRegs, RegMap Loc)
lookupBlockAssignment BlockId
bid BlockAssignment freeRegs
ba = BlockId
-> LabelMap (freeRegs, RegMap Loc) -> Maybe (freeRegs, RegMap Loc)
forall a. BlockId -> LabelMap a -> Maybe a
mapLookup BlockId
bid (BlockAssignment freeRegs -> LabelMap (freeRegs, RegMap Loc)
forall freeRegs.
BlockAssignment freeRegs -> BlockMap (freeRegs, RegMap Loc)
blockMap BlockAssignment freeRegs
ba)
lookupFirstUsed :: VirtualReg -> BlockAssignment freeRegs -> Maybe RealReg
lookupFirstUsed :: forall freeRegs.
VirtualReg -> BlockAssignment freeRegs -> Maybe RealReg
lookupFirstUsed VirtualReg
vr BlockAssignment freeRegs
ba = UniqFM VirtualReg RealReg -> VirtualReg -> Maybe RealReg
forall key elt. Uniquable key => UniqFM key elt -> key -> Maybe elt
lookupUFM (BlockAssignment freeRegs -> UniqFM VirtualReg RealReg
forall freeRegs.
BlockAssignment freeRegs -> UniqFM VirtualReg RealReg
firstUsed BlockAssignment freeRegs
ba) VirtualReg
vr
emptyBlockAssignment :: BlockAssignment freeRegs
emptyBlockAssignment :: forall freeRegs. BlockAssignment freeRegs
emptyBlockAssignment = BlockMap (freeRegs, RegMap Loc)
-> UniqFM VirtualReg RealReg -> BlockAssignment freeRegs
forall freeRegs.
BlockMap (freeRegs, RegMap Loc)
-> UniqFM VirtualReg RealReg -> BlockAssignment freeRegs
BlockAssignment BlockMap (freeRegs, RegMap Loc)
forall v. LabelMap v
mapEmpty UniqFM VirtualReg RealReg
forall a. Monoid a => a
mempty
updateBlockAssignment :: BlockId
-> (freeRegs, RegMap Loc)
-> BlockAssignment freeRegs
-> BlockAssignment freeRegs
updateBlockAssignment :: forall freeRegs.
BlockId
-> (freeRegs, RegMap Loc)
-> BlockAssignment freeRegs
-> BlockAssignment freeRegs
updateBlockAssignment BlockId
dest (freeRegs
freeRegs, RegMap Loc
regMap) (BlockAssignment {UniqFM VirtualReg RealReg
BlockMap (freeRegs, RegMap Loc)
blockMap :: forall freeRegs.
BlockAssignment freeRegs -> BlockMap (freeRegs, RegMap Loc)
firstUsed :: forall freeRegs.
BlockAssignment freeRegs -> UniqFM VirtualReg RealReg
blockMap :: BlockMap (freeRegs, RegMap Loc)
firstUsed :: UniqFM VirtualReg RealReg
..}) =
BlockMap (freeRegs, RegMap Loc)
-> UniqFM VirtualReg RealReg -> BlockAssignment freeRegs
forall freeRegs.
BlockMap (freeRegs, RegMap Loc)
-> UniqFM VirtualReg RealReg -> BlockAssignment freeRegs
BlockAssignment
(BlockId
-> (freeRegs, RegMap Loc)
-> BlockMap (freeRegs, RegMap Loc)
-> BlockMap (freeRegs, RegMap Loc)
forall v. BlockId -> v -> LabelMap v -> LabelMap v
mapInsert BlockId
dest (freeRegs
freeRegs, RegMap Loc
regMap) BlockMap (freeRegs, RegMap Loc)
blockMap)
((RealReg -> Loc -> Maybe RealReg)
-> (UniqFM VirtualReg RealReg -> UniqFM VirtualReg RealReg)
-> (UniqFM VirtualReg Loc -> UniqFM VirtualReg RealReg)
-> UniqFM VirtualReg RealReg
-> UniqFM VirtualReg Loc
-> UniqFM VirtualReg RealReg
forall {k} elta eltb eltc (key :: k).
(elta -> eltb -> Maybe eltc)
-> (UniqFM key elta -> UniqFM key eltc)
-> (UniqFM key eltb -> UniqFM key eltc)
-> UniqFM key elta
-> UniqFM key eltb
-> UniqFM key eltc
mergeUFM RealReg -> Loc -> Maybe RealReg
combWithExisting UniqFM VirtualReg RealReg -> UniqFM VirtualReg RealReg
forall a. a -> a
id
((Loc -> Maybe RealReg)
-> UniqFM VirtualReg Loc -> UniqFM VirtualReg RealReg
forall {k} elt1 elt2 (key :: k).
(elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2
mapMaybeUFM (VLoc -> Maybe RealReg
fromVLoc (VLoc -> Maybe RealReg) -> (Loc -> VLoc) -> Loc -> Maybe RealReg
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Loc -> VLoc
locWithFormat_loc))
UniqFM VirtualReg RealReg
firstUsed
(RegMap Loc -> UniqFM VirtualReg Loc
forall elt. UniqFM Reg elt -> UniqFM VirtualReg elt
toVRegMap RegMap Loc
regMap)
)
where
combWithExisting :: RealReg -> Loc -> Maybe RealReg
combWithExisting :: RealReg -> Loc -> Maybe RealReg
combWithExisting RealReg
old_reg Loc
_ = RealReg -> Maybe RealReg
RealReg -> Maybe RealReg
forall a. a -> Maybe a
Just (RealReg -> Maybe RealReg) -> RealReg -> Maybe RealReg
forall a b. (a -> b) -> a -> b
$ RealReg
old_reg
fromVLoc :: VLoc -> Maybe RealReg
fromVLoc :: VLoc -> Maybe RealReg
fromVLoc (InReg RealReg
rr) = RealReg -> Maybe RealReg
forall a. a -> Maybe a
Just RealReg
rr
fromVLoc (InBoth RealReg
rr StackSlot
_) = RealReg -> Maybe RealReg
forall a. a -> Maybe a
Just RealReg
rr
fromVLoc VLoc
_ = Maybe RealReg
forall a. Maybe a
Nothing
data VLoc
= InReg {-# UNPACK #-} !RealReg
| InMem {-# UNPACK #-} !StackSlot
| InBoth {-# UNPACK #-} !RealReg
{-# UNPACK #-} !StackSlot
deriving (VLoc -> VLoc -> Bool
(VLoc -> VLoc -> Bool) -> (VLoc -> VLoc -> Bool) -> Eq VLoc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VLoc -> VLoc -> Bool
== :: VLoc -> VLoc -> Bool
$c/= :: VLoc -> VLoc -> Bool
/= :: VLoc -> VLoc -> Bool
Eq, Eq VLoc
Eq VLoc =>
(VLoc -> VLoc -> Ordering)
-> (VLoc -> VLoc -> Bool)
-> (VLoc -> VLoc -> Bool)
-> (VLoc -> VLoc -> Bool)
-> (VLoc -> VLoc -> Bool)
-> (VLoc -> VLoc -> VLoc)
-> (VLoc -> VLoc -> VLoc)
-> Ord VLoc
VLoc -> VLoc -> Bool
VLoc -> VLoc -> Ordering
VLoc -> VLoc -> VLoc
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
$ccompare :: VLoc -> VLoc -> Ordering
compare :: VLoc -> VLoc -> Ordering
$c< :: VLoc -> VLoc -> Bool
< :: VLoc -> VLoc -> Bool
$c<= :: VLoc -> VLoc -> Bool
<= :: VLoc -> VLoc -> Bool
$c> :: VLoc -> VLoc -> Bool
> :: VLoc -> VLoc -> Bool
$c>= :: VLoc -> VLoc -> Bool
>= :: VLoc -> VLoc -> Bool
$cmax :: VLoc -> VLoc -> VLoc
max :: VLoc -> VLoc -> VLoc
$cmin :: VLoc -> VLoc -> VLoc
min :: VLoc -> VLoc -> VLoc
Ord, StackSlot -> VLoc -> ShowS
[VLoc] -> ShowS
VLoc -> String
(StackSlot -> VLoc -> ShowS)
-> (VLoc -> String) -> ([VLoc] -> ShowS) -> Show VLoc
forall a.
(StackSlot -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: StackSlot -> VLoc -> ShowS
showsPrec :: StackSlot -> VLoc -> ShowS
$cshow :: VLoc -> String
show :: VLoc -> String
$cshowList :: [VLoc] -> ShowS
showList :: [VLoc] -> ShowS
Show)
data Loc
= Loc
{ Loc -> VLoc
locWithFormat_loc :: {-# UNPACK #-} !VLoc
, Loc -> Format
locWithFormat_format :: Format
}
newtype IgnoreFormat a = IgnoreFormat a
instance Eq (IgnoreFormat Loc) where
IgnoreFormat (Loc VLoc
l1 Format
_) == :: IgnoreFormat Loc -> IgnoreFormat Loc -> Bool
== IgnoreFormat (Loc VLoc
l2 Format
_) = VLoc
l1 VLoc -> VLoc -> Bool
forall a. Eq a => a -> a -> Bool
== VLoc
l2
instance Ord (IgnoreFormat Loc) where
compare :: IgnoreFormat Loc -> IgnoreFormat Loc -> Ordering
compare (IgnoreFormat (Loc VLoc
l1 Format
_)) (IgnoreFormat (Loc VLoc
l2 Format
_)) = VLoc -> VLoc -> Ordering
forall a. Ord a => a -> a -> Ordering
compare VLoc
l1 VLoc
l2
instance Outputable VLoc where
ppr :: VLoc -> SDoc
ppr VLoc
l = String -> SDoc
forall doc. IsLine doc => String -> doc
text (VLoc -> String
forall a. Show a => a -> String
show VLoc
l)
instance Outputable Loc where
ppr :: Loc -> SDoc
ppr (Loc VLoc
loc Format
fmt) = SDoc -> SDoc
forall doc. IsLine doc => doc -> doc
parens (VLoc -> SDoc
forall a. Outputable a => a -> SDoc
ppr VLoc
loc SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Format -> SDoc
forall a. Outputable a => a -> SDoc
ppr Format
fmt)
data RealRegUsage
= RealRegUsage
{ RealRegUsage -> RealReg
realReg :: !RealReg
, RealRegUsage -> Format
realRegFormat :: !Format
} deriving StackSlot -> RealRegUsage -> ShowS
[RealRegUsage] -> ShowS
RealRegUsage -> String
(StackSlot -> RealRegUsage -> ShowS)
-> (RealRegUsage -> String)
-> ([RealRegUsage] -> ShowS)
-> Show RealRegUsage
forall a.
(StackSlot -> a -> ShowS)
-> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: StackSlot -> RealRegUsage -> ShowS
showsPrec :: StackSlot -> RealRegUsage -> ShowS
$cshow :: RealRegUsage -> String
show :: RealRegUsage -> String
$cshowList :: [RealRegUsage] -> ShowS
showList :: [RealRegUsage] -> ShowS
Show
instance Outputable RealRegUsage where
ppr :: RealRegUsage -> SDoc
ppr (RealRegUsage RealReg
r Format
fmt) = RealReg -> SDoc
forall a. Outputable a => a -> SDoc
ppr RealReg
r SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
dcolon SDoc -> SDoc -> SDoc
forall doc. IsLine doc => doc -> doc -> doc
<+> Format -> SDoc
forall a. Outputable a => a -> SDoc
ppr Format
fmt
regsOfLoc :: VLoc -> [RealReg]
regsOfLoc :: VLoc -> [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 Unique [StackSlot]
ra_spillInstrs :: UniqFM Unique [Int]
, RegAllocStats -> [(BlockId, BlockId, BlockId)]
ra_fixupList :: [(BlockId,BlockId,BlockId)]
}
data RA_State freeRegs
= RA_State
{
forall freeRegs. RA_State freeRegs -> BlockAssignment freeRegs
ra_blockassig :: BlockAssignment freeRegs
, forall freeRegs. RA_State freeRegs -> freeRegs
ra_freeregs :: !freeRegs
, forall freeRegs. RA_State freeRegs -> RegMap Loc
ra_assig :: RegMap Loc
, forall freeRegs. RA_State freeRegs -> StackSlot
ra_delta :: Int
, forall freeRegs. RA_State freeRegs -> StackMap
ra_stack :: StackMap
, forall freeRegs. RA_State freeRegs -> DUniqSupply
ra_us :: DUniqSupply
, forall freeRegs. RA_State freeRegs -> [SpillReason]
ra_spills :: [SpillReason]
, forall freeRegs. RA_State freeRegs -> NCGConfig
ra_config :: !NCGConfig
, forall freeRegs. RA_State freeRegs -> [(BlockId, BlockId, BlockId)]
ra_fixups :: [(BlockId,BlockId,BlockId)]
}