never executed always true always false
    1 {-# LANGUAGE TypeSynonymInstances #-}
    2 {-# OPTIONS_GHC -fno-warn-orphans #-}
    3 
    4 {- BlockId module should probably go away completely, being superseded by Label -}
    5 module GHC.Cmm.BlockId
    6   ( BlockId, mkBlockId -- ToDo: BlockId should be abstract, but it isn't yet
    7   , newBlockId
    8   , blockLbl, infoTblLbl
    9   ) where
   10 
   11 import GHC.Prelude
   12 
   13 import GHC.Cmm.CLabel
   14 import GHC.Types.Id.Info
   15 import GHC.Types.Name
   16 import GHC.Types.Unique
   17 import GHC.Types.Unique.Supply
   18 
   19 import GHC.Cmm.Dataflow.Label (Label, mkHooplLabel)
   20 
   21 ----------------------------------------------------------------
   22 --- Block Ids, their environments, and their sets
   23 
   24 {- Note [Unique BlockId]
   25 ~~~~~~~~~~~~~~~~~~~~~~~~
   26 Although a 'BlockId' is a local label, for reasons of implementation,
   27 'BlockId's must be unique within an entire compilation unit.  The reason
   28 is that each local label is mapped to an assembly-language label, and in
   29 most assembly languages allow, a label is visible throughout the entire
   30 compilation unit in which it appears.
   31 -}
   32 
   33 type BlockId = Label
   34 
   35 mkBlockId :: Unique -> BlockId
   36 mkBlockId unique = mkHooplLabel $ getKey unique
   37 
   38 newBlockId :: MonadUnique m => m BlockId
   39 newBlockId = mkBlockId <$> getUniqueM
   40 
   41 blockLbl :: BlockId -> CLabel
   42 blockLbl label = mkLocalBlockLabel (getUnique label)
   43 
   44 infoTblLbl :: BlockId -> CLabel
   45 infoTblLbl label
   46   = mkBlockInfoTableLabel (mkFCallName (getUnique label) "block") NoCafRefs