ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.Name.Occurrence

Description

GHC uses several kinds of name internally:

Synopsis

The NameSpace type

Construction

There are two forms of data constructor:

Source data constructors
The data constructors mentioned in Haskell source code
Real data constructors
The data constructors of the representation type, which may not be the same as the source type

For example:

data T = T !(Int, Int)

The source datacon has type (Int, Int) -> T The real datacon has type Int -> Int -> T

GHC chooses a representation based on the strictness etc.

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

Uniquable 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

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

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

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 name => HasOccName (IEWrappedName name) 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 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

The OccEnv type

data OccEnv a Source #

Instances

Instances details
Data a => Data (OccEnv a) 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) -> OccEnv a -> c (OccEnv a) Source #

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

toConstr :: OccEnv a -> Constr Source #

dataTypeOf :: OccEnv a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc Source #

pprPrec :: Rational -> OccEnv a -> SDoc Source #

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

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

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

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

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

extendOccEnv_C :: (a -> a -> a) -> OccEnv a -> OccName -> a -> OccEnv a Source #

extendOccEnv_Acc :: (a -> b -> b) -> (a -> b) -> OccEnv b -> OccName -> a -> OccEnv b Source #

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

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

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

The OccSet type

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.