never executed always true always false
    1 {-# LANGUAGE BangPatterns #-}
    2 {-# LANGUAGE FlexibleContexts #-}
    3 {-# LANGUAGE GADTs #-}
    4 {-# LANGUAGE ScopedTypeVariables #-}
    5 
    6 module GHC.Cmm.Liveness
    7     ( CmmLocalLive
    8     , cmmLocalLiveness
    9     , cmmLocalLivenessL
   10     , cmmGlobalLiveness
   11     , liveLattice
   12     , liveLatticeL
   13     , gen_kill
   14     , gen_killL
   15     )
   16 where
   17 
   18 import GHC.Prelude
   19 
   20 import GHC.Platform
   21 import GHC.Cmm.BlockId
   22 import GHC.Cmm
   23 import GHC.Cmm.Ppr.Expr () -- For Outputable instances
   24 import GHC.Cmm.Dataflow.Block
   25 import GHC.Cmm.Dataflow.Collections
   26 import GHC.Cmm.Dataflow
   27 import GHC.Cmm.Dataflow.Label
   28 import GHC.Cmm.LRegSet
   29 
   30 import GHC.Data.Maybe
   31 import GHC.Utils.Outputable
   32 import GHC.Utils.Panic
   33 
   34 import GHC.Types.Unique
   35 
   36 -----------------------------------------------------------------------------
   37 -- Calculating what variables are live on entry to a basic block
   38 -----------------------------------------------------------------------------
   39 
   40 -- | The variables live on entry to a block
   41 type CmmLive r = RegSet r
   42 type CmmLocalLive = CmmLive LocalReg
   43 
   44 -- | The dataflow lattice
   45 liveLattice :: Ord r => DataflowLattice (CmmLive r)
   46 {-# SPECIALIZE liveLattice :: DataflowLattice (CmmLive LocalReg) #-}
   47 {-# SPECIALIZE liveLattice :: DataflowLattice (CmmLive GlobalReg) #-}
   48 liveLattice = DataflowLattice emptyRegSet add
   49   where
   50     add (OldFact old) (NewFact new) =
   51         let !join = plusRegSet old new
   52         in changedIf (sizeRegSet join > sizeRegSet old) join
   53 
   54 -- | A mapping from block labels to the variables live on entry
   55 type BlockEntryLiveness r = LabelMap (CmmLive r)
   56 
   57 -----------------------------------------------------------------------------
   58 -- | Calculated liveness info for a CmmGraph
   59 -----------------------------------------------------------------------------
   60 
   61 cmmLocalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness LocalReg
   62 cmmLocalLiveness platform graph =
   63     check $ analyzeCmmBwd liveLattice (xferLive platform) graph mapEmpty
   64   where
   65     entry = g_entry graph
   66     check facts =
   67         noLiveOnEntry entry (expectJust "check" $ mapLookup entry facts) facts
   68 
   69 cmmGlobalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness GlobalReg
   70 cmmGlobalLiveness platform graph =
   71     analyzeCmmBwd liveLattice (xferLive platform) graph mapEmpty
   72 
   73 -- | On entry to the procedure, there had better not be any LocalReg's live-in.
   74 noLiveOnEntry :: BlockId -> CmmLive LocalReg -> a -> a
   75 noLiveOnEntry bid in_fact x =
   76   if nullRegSet in_fact then x
   77   else pprPanic "LocalReg's live-in to graph" (ppr bid <+> ppr in_fact)
   78 
   79 gen_kill
   80     :: (DefinerOfRegs r n, UserOfRegs r n)
   81     => Platform -> n -> CmmLive r -> CmmLive r
   82 gen_kill platform node set =
   83     let !afterKill = foldRegsDefd platform deleteFromRegSet set node
   84     in foldRegsUsed platform extendRegSet afterKill node
   85 {-# INLINE gen_kill #-}
   86 
   87 xferLive
   88     :: forall r.
   89        ( UserOfRegs r (CmmNode O O)
   90        , DefinerOfRegs r (CmmNode O O)
   91        , UserOfRegs r (CmmNode O C)
   92        , DefinerOfRegs r (CmmNode O C)
   93        )
   94     => Platform -> TransferFun (CmmLive r)
   95 xferLive platform (BlockCC eNode middle xNode) fBase =
   96     let joined = gen_kill platform xNode $! joinOutFacts liveLattice xNode fBase
   97         !result = foldNodesBwdOO (gen_kill platform) middle joined
   98     in mapSingleton (entryLabel eNode) result
   99 {-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive LocalReg) #-}
  100 {-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive GlobalReg) #-}
  101 
  102 -----------------------------------------------------------------------------
  103 -- | Specialization that only retains the keys for local variables.
  104 --
  105 -- Local variablas are mostly glorified Ints, and some parts of the compiler
  106 -- really don't care about anything but the Int part. So we can avoid some
  107 -- overhead by computing a IntSet instead of a Set LocalReg which (unsurprisingly)
  108 -- is quite a bit faster.
  109 -----------------------------------------------------------------------------
  110 
  111 type BlockEntryLivenessL  = LabelMap LRegSet
  112 
  113 -- | The dataflow lattice
  114 liveLatticeL :: DataflowLattice LRegSet
  115 liveLatticeL = DataflowLattice emptyLRegSet add
  116   where
  117     add (OldFact old) (NewFact new) =
  118         let !join = plusLRegSet old new
  119         in changedIf (sizeLRegSet join > sizeLRegSet old) join
  120 
  121 
  122 cmmLocalLivenessL :: Platform -> CmmGraph -> BlockEntryLivenessL
  123 cmmLocalLivenessL platform graph =
  124     check $ analyzeCmmBwd liveLatticeL (xferLiveL platform) graph mapEmpty
  125   where
  126     entry = g_entry graph
  127     check facts =
  128         noLiveOnEntryL entry (expectJust "check" $ mapLookup entry facts) facts
  129 
  130 -- | On entry to the procedure, there had better not be any LocalReg's live-in.
  131 noLiveOnEntryL :: BlockId -> LRegSet -> a -> a
  132 noLiveOnEntryL bid in_fact x =
  133   if nullLRegSet in_fact then x
  134   else pprPanic "LocalReg's live-in to graph" (ppr bid <+> ppr reg_uniques)
  135     where
  136         -- We convert the int's to uniques so that the printing matches that
  137         -- of registers.
  138         reg_uniques = map mkUniqueGrimily $ elemsLRegSet in_fact
  139 
  140 
  141 
  142 
  143 gen_killL
  144     :: (DefinerOfRegs LocalReg n, UserOfRegs LocalReg n)
  145     => Platform -> n -> LRegSet -> LRegSet
  146 gen_killL platform node set =
  147     let !afterKill = foldRegsDefd platform deleteFromLRegSet set node
  148     in foldRegsUsed platform (flip insertLRegSet) afterKill node
  149 {-# INLINE gen_killL #-}
  150 
  151 xferLiveL
  152     :: ( UserOfRegs LocalReg (CmmNode O O)
  153        , DefinerOfRegs LocalReg (CmmNode O O)
  154        , UserOfRegs LocalReg (CmmNode O C)
  155        , DefinerOfRegs LocalReg (CmmNode O C)
  156        )
  157     => Platform -> TransferFun LRegSet
  158 xferLiveL platform (BlockCC eNode middle xNode) fBase =
  159     let joined = gen_killL platform xNode $! joinOutFacts liveLatticeL xNode fBase
  160         !result = foldNodesBwdOO (gen_killL platform) middle joined
  161     in mapSingleton (entryLabel eNode) result
  162 
  163