module GHC.Types.IPE (
DCMap,
ClosureMap,
InfoTableProvMap(..),
emptyInfoTableProvMap,
IpeSourceLocation
) where
import GHC.Prelude
import GHC.Types.Name
import GHC.Types.SrcLoc
import GHC.Core.DataCon
import GHC.Types.Unique.Map
import GHC.Core.Type
import Data.List.NonEmpty
import GHC.Cmm.CLabel (CLabel)
import qualified Data.Map.Strict as Map
type IpeSourceLocation = (RealSrcSpan, String)
type ClosureMap = UniqMap Name
(Type, Maybe IpeSourceLocation)
type DCMap = UniqMap DataCon (NonEmpty (Int, Maybe IpeSourceLocation))
type InfoTableToSourceLocationMap = Map.Map CLabel (Maybe IpeSourceLocation)
data InfoTableProvMap = InfoTableProvMap
{ InfoTableProvMap -> DCMap
provDC :: DCMap
, InfoTableProvMap -> ClosureMap
provClosure :: ClosureMap
, InfoTableProvMap -> InfoTableToSourceLocationMap
provInfoTables :: InfoTableToSourceLocationMap
}
emptyInfoTableProvMap :: InfoTableProvMap
emptyInfoTableProvMap :: InfoTableProvMap
emptyInfoTableProvMap = DCMap
-> ClosureMap -> InfoTableToSourceLocationMap -> InfoTableProvMap
InfoTableProvMap DCMap
forall k a. UniqMap k a
emptyUniqMap ClosureMap
forall k a. UniqMap k a
emptyUniqMap InfoTableToSourceLocationMap
forall k a. Map k a
Map.empty