ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.CmmToAsm.Reg.Liveness

Synopsis

Documentation

type RegSet = UniqSet Reg Source #

type RegMap a = UniqFM Reg a Source #

Map from some kind of register to a.

While we give the type for keys as Reg which is the common case sometimes we end up using VirtualReq or naked Uniques. See Note [UniqFM and the register allocator]

type BlockMap a = LabelMap a Source #

mapEmpty :: IsMap map => map a #

type LiveCmmDecl statics instr = GenCmmDecl statics LiveInfo [SCC (LiveBasicBlock instr)] Source #

A top level thing which carries liveness information.

data InstrSR instr Source #

The register allocator also wants to use SPILL/RELOAD meta instructions, so we'll keep those here.

Constructors

Instr instr

A real machine instruction

SPILL Reg Int

spill this reg to a stack slot

RELOAD Int Reg

reload this reg from a stack slot

Instances

Instances details
Functor InstrSR Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

fmap :: (a -> b) -> InstrSR a -> InstrSR b #

(<$) :: a -> InstrSR b -> InstrSR a #

Outputable instr => Outputable (InstrSR instr) Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

ppr :: InstrSR instr -> SDoc

Instruction instr => Instruction (InstrSR instr) Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

regUsageOfInstr :: Platform -> InstrSR instr -> RegUsage Source #

patchRegsOfInstr :: InstrSR instr -> (Reg -> Reg) -> InstrSR instr Source #

isJumpishInstr :: InstrSR instr -> Bool Source #

jumpDestsOfInstr :: InstrSR instr -> [BlockId] Source #

patchJumpInstr :: InstrSR instr -> (BlockId -> BlockId) -> InstrSR instr Source #

mkSpillInstr :: NCGConfig -> Reg -> Int -> Int -> InstrSR instr Source #

mkLoadInstr :: NCGConfig -> Reg -> Int -> Int -> InstrSR instr Source #

takeDeltaInstr :: InstrSR instr -> Maybe Int Source #

isMetaInstr :: InstrSR instr -> Bool Source #

mkRegRegMoveInstr :: Platform -> Reg -> Reg -> InstrSR instr Source #

takeRegRegMoveInstr :: InstrSR instr -> Maybe (Reg, Reg) Source #

mkJumpInstr :: BlockId -> [InstrSR instr] Source #

mkStackAllocInstr :: Platform -> Int -> [InstrSR instr] Source #

mkStackDeallocInstr :: Platform -> Int -> [InstrSR instr] Source #

pprInstr :: Platform -> InstrSR instr -> SDoc Source #

data LiveInstr instr Source #

An instruction with liveness information.

Constructors

LiveInstr (InstrSR instr) (Maybe Liveness) 

Instances

Instances details
Functor LiveInstr Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

fmap :: (a -> b) -> LiveInstr a -> LiveInstr b #

(<$) :: a -> LiveInstr b -> LiveInstr a #

OutputableP env instr => OutputableP env (LiveInstr instr) Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

pdoc :: env -> LiveInstr instr -> SDoc

Outputable instr => Outputable (LiveInstr instr) Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

ppr :: LiveInstr instr -> SDoc

data Liveness Source #

Liveness information. The regs which die are ones which are no longer live in the *next* instruction in this sequence. (NB. if the instruction is a jump, these registers might still be live at the jump target(s) - you have to check the liveness at the destination block to find out).

Constructors

Liveness

registers that died because they were clobbered by something.

Fields

data LiveInfo Source #

Stash regs live on entry to each basic block in the info part of the cmm code.

Constructors

LiveInfo (LabelMap RawCmmStatics) [BlockId] (BlockMap RegSet) (BlockMap IntSet) 

Instances

Instances details
OutputableP Platform LiveInfo Source # 
Instance details

Defined in GHC.CmmToAsm.Reg.Liveness

Methods

pdoc :: Platform -> LiveInfo -> SDoc

type LiveBasicBlock instr = GenBasicBlock (LiveInstr instr) Source #

A basic block with liveness information.

mapBlockTop :: (LiveBasicBlock instr -> LiveBasicBlock instr) -> LiveCmmDecl statics instr -> LiveCmmDecl statics instr Source #

map a function across all the basic blocks in this code

mapBlockTopM :: Monad m => (LiveBasicBlock instr -> m (LiveBasicBlock instr)) -> LiveCmmDecl statics instr -> m (LiveCmmDecl statics instr) Source #

map a function across all the basic blocks in this code (monadic version)

mapSCCM :: Monad m => (a -> m b) -> SCC a -> m (SCC b) Source #

mapGenBlockTop :: (GenBasicBlock i -> GenBasicBlock i) -> GenCmmDecl d h (ListGraph i) -> GenCmmDecl d h (ListGraph i) Source #

mapGenBlockTopM :: Monad m => (GenBasicBlock i -> m (GenBasicBlock i)) -> GenCmmDecl d h (ListGraph i) -> m (GenCmmDecl d h (ListGraph i)) Source #

map a function across all the basic blocks in this code (monadic version)

mapLiveCmmDecl :: (instr -> b) -> LiveCmmDecl statics instr -> LiveCmmDecl statics b Source #

Map over instruction type in LiveCmmDecl

pprLiveCmmDecl :: (OutputableP Platform statics, Instruction instr) => Platform -> LiveCmmDecl statics instr -> SDoc Source #

Pretty-print a LiveCmmDecl

stripLive :: (OutputableP Platform statics, Instruction instr) => NCGConfig -> LiveCmmDecl statics instr -> NatCmmDecl statics instr Source #

Strip away liveness information, yielding NatCmmDecl

stripLiveBlock :: Instruction instr => NCGConfig -> LiveBasicBlock instr -> NatBasicBlock instr Source #

Strip away liveness information from a basic block, and make real spill instructions out of SPILL, RELOAD pseudos along the way.

slurpConflicts :: Instruction instr => LiveCmmDecl statics instr -> (Bag (UniqSet Reg), Bag (Reg, Reg)) Source #

Slurp out the list of register conflicts and reg-reg moves from this top level thing. Slurping of conflicts and moves is wrapped up together so we don't have to make two passes over the same code when we want to build the graph.

slurpReloadCoalesce :: forall statics instr. Instruction instr => LiveCmmDecl statics instr -> Bag (Reg, Reg) Source #

For spill/reloads

SPILL v1, slot1 ... RELOAD slot1, v2

If we can arrange that v1 and v2 are allocated to the same hreg it's more likely the spill/reload instrs can be cleaned and replaced by a nop reg-reg move.

eraseDeltasLive :: Instruction instr => LiveCmmDecl statics instr -> LiveCmmDecl statics instr Source #

Erase Delta instructions.

patchEraseLive :: Instruction instr => (Reg -> Reg) -> LiveCmmDecl statics instr -> LiveCmmDecl statics instr Source #

Patch the registers in this code according to this register mapping. also erase reg -> reg moves when the reg is the same. also erase reg -> reg moves when the destination dies in this instr.

patchRegsLiveInstr :: Instruction instr => (Reg -> Reg) -> LiveInstr instr -> LiveInstr instr Source #

Patch registers in this LiveInstr, including the liveness information.

reverseBlocksInTops :: LiveCmmDecl statics instr -> LiveCmmDecl statics instr Source #

If we've compute liveness info for this code already we have to reverse the SCCs in each top to get them back to the right order so we can do it again.

regLiveness :: Instruction instr => Platform -> LiveCmmDecl statics instr -> UniqSM (LiveCmmDecl statics instr) Source #

cmmTopLiveness :: Instruction instr => Maybe CFG -> Platform -> NatCmmDecl statics instr -> UniqSM (LiveCmmDecl statics instr) Source #

Convert a NatCmmDecl to a LiveCmmDecl, with liveness information