never executed always true always false
    1 module GHC.Types.IPE (
    2     DCMap,
    3     ClosureMap,
    4     InfoTableProvMap(..),
    5     emptyInfoTableProvMap,
    6     IpeSourceLocation
    7 ) where
    8 
    9 import GHC.Prelude
   10 
   11 import GHC.Types.Name
   12 import GHC.Types.SrcLoc
   13 import GHC.Core.DataCon
   14 
   15 import GHC.Types.Unique.Map
   16 import GHC.Core.Type
   17 import Data.List.NonEmpty
   18 import GHC.Cmm.CLabel (CLabel)
   19 import qualified Data.Map.Strict as Map
   20 
   21 -- | Position and information about an info table.
   22 -- For return frames these are the contents of a 'CoreSyn.SourceNote'.
   23 type IpeSourceLocation = (RealSrcSpan, String)
   24 
   25 -- | A map from a 'Name' to the best approximate source position that
   26 -- name arose from.
   27 type ClosureMap = UniqMap Name  -- The binding
   28                           (Type, Maybe IpeSourceLocation)
   29                           -- The best approximate source position.
   30                           -- (rendered type, source position, source note
   31                           -- label)
   32 
   33 -- | A map storing all the different uses of a specific data constructor and the
   34 -- approximate source position that usage arose from.
   35 -- The 'Int' is an incrementing identifier which distinguishes each usage
   36 -- of a constructor in a module. It is paired with the source position
   37 -- the constructor was used at, if possible and a string which names
   38 -- the source location. This is the same information as is the payload
   39 -- for the 'GHC.Core.SourceNote' constructor.
   40 type DCMap = UniqMap DataCon (NonEmpty (Int, Maybe IpeSourceLocation))
   41 
   42 type InfoTableToSourceLocationMap = Map.Map CLabel (Maybe IpeSourceLocation)
   43 
   44 data InfoTableProvMap = InfoTableProvMap
   45                           { provDC :: DCMap
   46                           , provClosure :: ClosureMap
   47                           , provInfoTables :: InfoTableToSourceLocationMap
   48                           }
   49 
   50 emptyInfoTableProvMap :: InfoTableProvMap
   51 emptyInfoTableProvMap = InfoTableProvMap emptyUniqMap emptyUniqMap Map.empty