ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Types.Name.Occurrence

Description

GHC uses several kinds of name internally:

Synopsis

The NameSpace type

Construction

Pretty Printing

The OccName type

data OccName Source #

Occurrence Name

In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"

Instances

Instances details
Data OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccName -> Constr Source #

dataTypeOf :: OccName -> DataType Source #

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

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

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

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

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

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

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

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

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

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

NFData OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () Source #

HasOccName OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Binary OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc Source #

OutputableBndr OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Eq OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

Ord OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

pprOccName :: IsLine doc => OccName -> doc Source #

occNameMangledFS :: OccName -> FastString Source #

Mangle field names to avoid duplicate symbols.

See Note [Mangling OccNames].

Construction

mkDFunOcc Source #

Arguments

:: String

Typically the class and type glommed together e.g. OrdMaybe. Only used in debug mode, for extra clarity

-> Bool

Is this a hs-boot instance DFun?

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe

class HasOccName name where Source #

Other names in the compiler add additional information to an OccName. This class provides a consistent way to access the underlying OccName.

Methods

occName :: name -> OccName Source #

Instances

Instances details
HasOccName IfaceClassOp Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceConDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName IfaceDecl Source # 
Instance details

Defined in GHC.Iface.Syntax

HasOccName HoleFitCandidate Source # 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

HasOccName TcBinder Source # 
Instance details

Defined in GHC.Tc.Types.BasicTypes

HasOccName FieldLabel Source # 
Instance details

Defined in GHC.Types.FieldLabel

HasOccName Name Source # 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName Source #

HasOccName OccName Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

HasOccName RdrName Source # 
Instance details

Defined in GHC.Types.Name.Reader

HasOccName Var Source # 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName Source #

HasOccName (GlobalRdrEltX info) Source # 
Instance details

Defined in GHC.Types.Name.Reader

(HasOccName (IdP (GhcPass p)), OutputableBndrId p) => HasOccName (IEWrappedName (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Derived OccNames

isDerivedOccName :: OccName -> Bool Source #

Test for definitions internally generated by GHC. This predicate is used to suppress printing of internal definitions in some debug prints

isTypeableBindOcc :: OccName -> Bool Source #

Is an OccName one of a Typeable TyCon or Module binding? This is needed as these bindings are renamed differently. See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.

mkSuperDictSelOcc Source #

Arguments

:: Int

Index of superclass, e.g. 3

-> OccName

Class, e.g. Ord

-> OccName

Derived Occname, e.g. $p3Ord

mkLocalOcc Source #

Arguments

:: Unique

Unique to combine with the OccName

-> OccName

Local name, e.g. sat

-> OccName

Nice unique version, e.g. $L23sat

mkInstTyTcOcc Source #

Arguments

:: String

Family name, e.g. Map

-> OccSet

avoid these Occs

-> OccName
R:Map

Derive a name for the representation type constructor of a data/newtype instance.

Deconstruction

isDataSymOcc :: OccName -> Bool Source #

Test if the OccName is a data constructor that starts with a symbol (e.g. :, or [])

isSymOcc :: OccName -> Bool Source #

Test if the OccName is that for any operator (whether it is a data constructor or variable or whatever)

isValOcc :: OccName -> Bool Source #

Value OccNamess are those that are either in the variable, field name or data constructor namespaces

parenSymOcc :: OccName -> SDoc -> SDoc Source #

Wrap parens around an operator

startsWithUnderscore :: OccName -> Bool Source #

Haskell 98 encourages compilers to suppress warnings about unused names in a pattern if they start with _: this implements that test

isTermVarOrFieldNameSpace :: NameSpace -> Bool Source #

Is this a term variable or field name namespace?

The OccEnv type

data OccEnv a Source #

A map keyed on OccName. See Note [OccEnv].

Instances

Instances details
Functor OccEnv Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

fmap :: (a -> b) -> OccEnv a -> OccEnv b Source #

(<$) :: a -> OccEnv b -> OccEnv a Source #

NFData a => NFData (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccEnv a -> () Source #

Outputable a => Outputable (OccEnv a) Source # 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

unitOccEnv :: OccName -> a -> OccEnv a Source #

A singleton OccEnv.

extendOccEnv :: OccEnv a -> OccName -> a -> OccEnv a Source #

Add a single element to an OccEnv.

mapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b Source #

Map over an OccEnv (Functor instance).

strictMapOccEnv :: (a -> b) -> OccEnv a -> OccEnv b Source #

Map over an OccEnv strictly.

mapMaybeOccEnv :: (a -> Maybe b) -> OccEnv a -> OccEnv b Source #

mapMaybe for b OccEnv.

lookupOccEnv :: OccEnv a -> OccName -> Maybe a Source #

Look an element up in an OccEnv.

lookupOccEnv_AllNameSpaces :: OccEnv a -> OccName -> [a] Source #

Lookup an element in an OccEnv, ignoring NameSpaces entirely.

lookupOccEnv_WithFields :: OccEnv a -> OccName -> [a] Source #

Lookup an element in an OccEnv, looking in the record field namespace for a variable.

lookupFieldsOccEnv :: OccEnv a -> FastString -> [a] Source #

Look up all the record fields that match with the given FastString in an OccEnv.

mkOccEnv :: [(OccName, a)] -> OccEnv a Source #

Create an OccEnv from a list.

OccNames later on in the list override earlier OccNames.

mkOccEnv_C Source #

Arguments

:: (a -> a -> a)

old -> new -> result

-> [(OccName, a)] 
-> OccEnv a 

Create an OccEnv from a list, combining different values with the same OccName using the combining function.

extendOccEnvList :: OccEnv a -> [(OccName, a)] -> OccEnv a Source #

Extend an OccEnv by a list.

OccNames later on in the list override earlier OccNames.

elemOccEnv :: OccName -> OccEnv a -> Bool Source #

Compute whether there is a value keyed by the given OccName.

nonDetOccEnvElts :: OccEnv a -> [a] Source #

Obtain the elements of an OccEnv.

The resulting order is non-deterministic.

nonDetFoldOccEnv :: (a -> b -> b) -> b -> OccEnv a -> b Source #

Fold over an OccEnv. Non-deterministic, unless the folding function is commutative (i.e. a1 f ( a2 f b ) == a2 f ( a1 f b ) for all a1, a2, b).

plusOccEnv :: OccEnv a -> OccEnv a -> OccEnv a Source #

Union of two OccEnvs, right-biased.

plusOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccEnv a -> OccEnv a Source #

Union of two OccEnvs with a combining function.

extendOccEnv_Acc Source #

Arguments

:: (a -> b -> b)

add to existing

-> (a -> b)

new element

-> OccEnv b

old

-> OccName 
-> a

new

-> OccEnv b 

Add a single element to an OccEnv, using a different function whether the OccName already exists or not.

filterOccEnv :: (a -> Bool) -> OccEnv a -> OccEnv a Source #

Filter out all elements in an OccEnv using a predicate.

delListFromOccEnv :: OccEnv a -> [OccName] -> OccEnv a Source #

Delete multiple elements from an OccEnv.

delFromOccEnv :: OccEnv a -> OccName -> OccEnv a Source #

Delete one element from an OccEnv.

alterOccEnv :: (Maybe a -> Maybe a) -> OccEnv a -> OccName -> OccEnv a Source #

Alter an OccEnv, adding or removing an element at the given key.

minusOccEnv :: OccEnv a -> OccEnv b -> OccEnv a Source #

Remove elements of the first OccEnv that appear in the second OccEnv.

minusOccEnv_C :: (a -> b -> Maybe a) -> OccEnv a -> OccEnv b -> OccEnv a Source #

Alters (replaces or removes) those elements of the first OccEnv that are mentioned in the second OccEnv.

Same idea as differenceWith.

pprOccEnv :: (a -> SDoc) -> OccEnv a -> SDoc Source #

forceOccEnv :: (a -> ()) -> OccEnv a -> () Source #

Force an OccEnv with the provided function.

intersectOccEnv_C :: (a -> b -> c) -> OccEnv a -> OccEnv b -> OccEnv c Source #

The OccSet type

Dealing with main

Tidying up

type FastStringEnv a = UniqFM FastString a Source #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DFastStringEnv if the set eventually gets converted into a list or folded over in a way where the order changes the generated code.