ghc-lib-parser-9.8.2.20240223: The GHC API, decoupled from GHC versions
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.GREInfo

Contents

Description

Renamer-level information about Names.

Renamer equivalent of TyThing.

Synopsis

* * GREInfo * * ************************************************************************ Note [GREInfo] ~~~~~~~~~~~~~~ In the renamer, we sometimes need a bit more information about a Name, e.g. whether it is a type constructor, class, data constructor, record field, etc. For example, when typechecking record construction, the renamer needs to look up the fields of the data constructor being used (see e.g. GHC.Rename.Pat.rnHsRecFields). Extra information also allows us to provide better error messages when a fatal error occurs in the renamer, as it allows us to distinguish classes, type families, type synonyms, etc. For imported Names, we have access to the full type information in the form of a TyThing (although see Note [Retrieving the GREInfo from interfaces]). However, for Names in the module currently being renamed, we don't yet have full information. Instead of using TyThing, we use the GREInfo type, and this information gets affixed to each element in the GlobalRdrEnv. This allows us to treat imported and local Names in a consistent manner: always look at the GREInfo. Note [Retrieving the GREInfo from interfaces] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we have a TyThing, we can easily compute the corresponding GREInfo: this is done in GHC.Types.TyThing.tyThingGREInfo. However, one often needs to produce GlobalRdrElts (and thus their GREInfos) directly after loading interface files, before they are typechecked. For example: - GHC.Tc.Module.tcRnModuleTcRnM first calls tcRnImports, which starts off calling rnImports which transitively calls filterImports. That function is responsible for coughing up GlobalRdrElts (and their GREInfos) obtained from interfaces, but we will only typecheck the interfaces after we have finished processing the imports (see e.g. the logic at the start of tcRnImports which sets eps_is_boot, which decides whether we should look in the boot or non-boot interface for any particular module). - GHC.Tc.Utils.Backpack.mergeSignatures first loads the relevant signature interfaces to merge them, but only later on does it typecheck them. In both of these examples, what's important is that we **lazily** produce the GREInfo: it should only be consulted once the interfaces have been typechecked, which will add the necessary information to the type-level environment. In particular, the respective functions filterImports and mergeSignatures should NOT force the gre_info field. We delay the loading of interfaces by making the gre_info field of GlobalRdrElt a thunk which, when forced, loads the interface, looks up the Name in the type environment to get its associated TyThing, and computes the GREInfo from that. See lookupGREInfo. A possible alternative design would be to change the AvailInfo datatype to also store GREInfo. We currently don't do that, as this would mean that every time an interface re-exports something it has to also provide its GREInfo, which could lead to bloat. Note [Forcing GREInfo] ~~~~~~~~~~~~~~~~~~~~~~ The GREInfo field of a GlobalRdrElt needs to be lazy, as explained in Note [Retrieving the GREInfo from interfaces]. For imported things, this field is usually a thunk which looks up the GREInfo in a type environment (see GHC.Rename.Env.lookupGREInfo). We thus need to be careful not to introduce space leaks: such thunks could end up retaining old type environments, which would violate invariant (5) of Note [GHC Heap Invariants] in GHC.Driver.Make. This can happen, for example, when reloading in GHCi (see e.g. test T15369, which can trigger the ghci leak check if we're not careful). A naive approach is to simply deeply force the whole GlobalRdrEnv. However, forcing the GREInfo thunks can force the loading of interface files which we otherwise might not need to load, so it leads to wasted work. Instead, whenever we are about to store the GlobalRdrEnv somewhere (such as in ModDetails), we dehydrate it by stripping away the GREInfo field, turning it into (). See forceGlobalRdrEnv and its cousin hydrateGlobalRdrEnv, as well as Note [IfGlobalRdrEnv] in GHC.Types.Name.Reader. Search for references to this note in the code for illustration.

data GREInfo Source #

Information about a Name that is pertinent to the renamer.

See Note [GREInfo]

Constructors

Vanilla

No particular information... e.g. a function

UnboundGRE

An unbound GRE... could be anything

IAmTyCon !(TyConFlavour Name)

TyCon

IAmConLike

ConLike

Fields

  • !ConInfo

    The constructor fields. See Note [Local constructor info in the renamer]. | Record field

IAmRecField !RecFieldInfo 

Instances

Instances details
Data GREInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GREInfo -> c GREInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GREInfo #

toConstr :: GREInfo -> Constr #

dataTypeOf :: GREInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GREInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GREInfo) #

gmapT :: (forall b. Data b => b -> b) -> GREInfo -> GREInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GREInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GREInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> GREInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GREInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GREInfo -> m GREInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GREInfo -> m GREInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GREInfo -> m GREInfo #

NFData GREInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: GREInfo -> () #

Outputable GREInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

ppr :: GREInfo -> SDoc Source #

* * Constructor info * * ************************************************************************ Note [Local constructor info in the renamer] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ As explained in Note [GREInfo], information pertinent to the renamer is stored using the GREInfo datatype. What information do we need about constructors? Consider the following example: data T = T1 { x, y :: Int } | T2 { x :: Int } | T3 | T4 Int Bool We need to know: * The fields of the data constructor, so that - We can complain if you say `T1 { v = 3 }`, where v is not a field of T1 See the following call stack * GHC.Rename.Expr.rnExpr (RecordCon case) * GHC.Rename.Pat.rnHsRecFields * GHC.Rename.Env.lookupRecFieldOcc - Ditto if you pattern match on `T1 { v = x }`. See the following call stack * GHC.Rename.Pat.rnHsRecPatsAndThen * GHC.Rename.Pat.rnHsRecFields * GHC.Rename.Env.lookupRecFieldOcc - We can fill in the dots if you say `T1 {..}` in construction or pattern matching See GHC.Rename.Pat.rnHsRecFields.rn_dotdot * Whether the contructor is nullary. We need to know this to accept `T2 {..}`, and `T3 {..}`, but reject `T4 {..}`, in both construction and pattern matching. See GHC.Rename.Pat.rnHsRecFields.rn_dotdot and Note [Nullary constructors and empty record wildcards] Note [Nullary constructors and empty record wildcards] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A nullary constructor is one with no arguments. For example, both `data T = MkT` and `data T = MkT {}` are nullary. For consistency and TH convenience, it was agreed that a `{..}` match or usage on nullary constructors would be accepted. This is done as as per https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0496-empty-record-wildcards.rst

data ConInfo Source #

Information about the record fields of a constructor.

See Note [Local constructor info in the renamer]

Instances

Instances details
Data ConInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConInfo -> c ConInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConInfo #

toConstr :: ConInfo -> Constr #

dataTypeOf :: ConInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConInfo) #

gmapT :: (forall b. Data b => b -> b) -> ConInfo -> ConInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConInfo -> m ConInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConInfo -> m ConInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConInfo -> m ConInfo #

NFData ConInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: ConInfo -> () #

Outputable ConInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

ppr :: ConInfo -> SDoc Source #

Eq ConInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

(==) :: ConInfo -> ConInfo -> Bool #

(/=) :: ConInfo -> ConInfo -> Bool #

data ConLikeName Source #

The Name of a ConLike.

Useful when we are in the renamer and don't yet have a full DataCon or PatSyn to hand.

Constructors

DataConName 
PatSynName 

Instances

Instances details
Data ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConLikeName -> c ConLikeName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConLikeName #

toConstr :: ConLikeName -> Constr #

dataTypeOf :: ConLikeName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConLikeName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConLikeName) #

gmapT :: (forall b. Data b => b -> b) -> ConLikeName -> ConLikeName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConLikeName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConLikeName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConLikeName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConLikeName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConLikeName -> m ConLikeName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLikeName -> m ConLikeName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConLikeName -> m ConLikeName #

NFData ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: ConLikeName -> () #

Uniquable ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Outputable ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

ppr :: ConLikeName -> SDoc Source #

Eq ConLikeName Source # 
Instance details

Defined in GHC.Types.GREInfo

* * Record field info * * **********************************************************************

data RecFieldInfo Source #

Constructors

RecFieldInfo 

Fields

  • recFieldLabel :: !FieldLabel
     
  • recFieldCons :: !(UniqSet ConLikeName)

    The constructors which have this field label. Always non-empty.

    NB: these constructors will always share a single parent, as the field label disambiguates between parents in the presence of duplicate record fields.

Instances

Instances details
Data RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFieldInfo -> c RecFieldInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFieldInfo #

toConstr :: RecFieldInfo -> Constr #

dataTypeOf :: RecFieldInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFieldInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFieldInfo) #

gmapT :: (forall b. Data b => b -> b) -> RecFieldInfo -> RecFieldInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFieldInfo -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFieldInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> RecFieldInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFieldInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFieldInfo -> m RecFieldInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFieldInfo -> m RecFieldInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFieldInfo -> m RecFieldInfo #

NFData RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Methods

rnf :: RecFieldInfo -> () #

Outputable RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo

Eq RecFieldInfo Source # 
Instance details

Defined in GHC.Types.GREInfo