ghc-8.2.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

OccName

Contents

Description

GHC uses several kinds of name internally:

  • OccName represents names as strings with just a little more information: the "namespace" that the name came from, e.g. the namespace of value, type constructors or data constructors
  • RdrName: see RdrName
  • Name: see Name
  • Id: see Id
  • Var: see Var

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

Eq OccName Source # 

Methods

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

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

Data OccName Source # 

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OccName Source # 
NFData OccName Source # 

Methods

rnf :: OccName -> () #

OutputableBndr OccName Source # 
Outputable OccName Source # 
Uniquable OccName Source # 
Binary OccName Source # 
HasOccName OccName Source # 

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.

Minimal complete definition

occName

Methods

occName :: name -> OccName Source #

Derived OccNames

isDerivedOccName :: OccName -> Bool Source #

Test for definitions internally generated by GHC. This predicte 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 TcTypeable.

mkDataTOcc Source #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

mkDataCOcc Source #

Arguments

:: OccName

TyCon or data con string

-> OccSet

avoid these Occs

-> OccName

E.g. $f3OrdMaybe data T = MkT ... deriving( Data ) needs definitions for $tT :: Data.Generics.Basics.DataType $cMkT :: Data.Generics.Basics.Constr

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 unsed names in a pattern if they start with _: this implements that test

The OccEnv type

data OccEnv a Source #

Instances

Data a => Data (OccEnv a) Source # 

Methods

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

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

toConstr :: OccEnv a -> Constr #

dataTypeOf :: OccEnv a -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable a => Outputable (OccEnv a) Source # 

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 a Source #

A non-deterministic set of FastStrings. See Note [Deterministic UniqFM] in UniqDFM 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.