{-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} module GHC.Cmm.Liveness ( CmmLocalLive , cmmLocalLiveness , cmmGlobalLiveness , liveLattice , gen_kill ) where import GHC.Prelude import GHC.Platform import GHC.Cmm.BlockId import GHC.Cmm import GHC.Cmm.Ppr.Expr () -- For Outputable instances import GHC.Cmm.Dataflow.Block import GHC.Cmm.Dataflow.Collections import GHC.Cmm.Dataflow import GHC.Cmm.Dataflow.Label import GHC.Data.Maybe import GHC.Utils.Outputable import GHC.Utils.Panic ----------------------------------------------------------------------------- -- Calculating what variables are live on entry to a basic block ----------------------------------------------------------------------------- -- | The variables live on entry to a block type CmmLive r = RegSet r type CmmLocalLive = CmmLive LocalReg -- | The dataflow lattice liveLattice :: Ord r => DataflowLattice (CmmLive r) {-# SPECIALIZE liveLattice :: DataflowLattice (CmmLive LocalReg) #-} {-# SPECIALIZE liveLattice :: DataflowLattice (CmmLive GlobalReg) #-} liveLattice = DataflowLattice emptyRegSet add where add (OldFact old) (NewFact new) = let !join = plusRegSet old new in changedIf (sizeRegSet join > sizeRegSet old) join -- | A mapping from block labels to the variables live on entry type BlockEntryLiveness r = LabelMap (CmmLive r) ----------------------------------------------------------------------------- -- | Calculated liveness info for a CmmGraph ----------------------------------------------------------------------------- cmmLocalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness LocalReg cmmLocalLiveness platform graph = check $ analyzeCmmBwd liveLattice (xferLive platform) graph mapEmpty where entry = g_entry graph check facts = noLiveOnEntry entry (expectJust "check" $ mapLookup entry facts) facts cmmGlobalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness GlobalReg cmmGlobalLiveness platform graph = analyzeCmmBwd liveLattice (xferLive platform) graph mapEmpty -- | On entry to the procedure, there had better not be any LocalReg's live-in. noLiveOnEntry :: BlockId -> CmmLive LocalReg -> a -> a noLiveOnEntry bid in_fact x = if nullRegSet in_fact then x else pprPanic "LocalReg's live-in to graph" (ppr bid <+> ppr in_fact) gen_kill :: (DefinerOfRegs r n, UserOfRegs r n) => Platform -> n -> CmmLive r -> CmmLive r gen_kill platform node set = let !afterKill = foldRegsDefd platform deleteFromRegSet set node in foldRegsUsed platform extendRegSet afterKill node {-# INLINE gen_kill #-} xferLive :: forall r. ( UserOfRegs r (CmmNode O O) , DefinerOfRegs r (CmmNode O O) , UserOfRegs r (CmmNode O C) , DefinerOfRegs r (CmmNode O C) ) => Platform -> TransferFun (CmmLive r) xferLive platform (BlockCC eNode middle xNode) fBase = let joined = gen_kill platform xNode $! joinOutFacts liveLattice xNode fBase !result = foldNodesBwdOO (gen_kill platform) middle joined in mapSingleton (entryLabel eNode) result {-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive LocalReg) #-} {-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive GlobalReg) #-}