ghc-8.0.0.20160204: 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

 

Pretty Printing

The OccName type

data OccName Source

Instances

Eq OccName 

Methods

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

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

Data OccName 

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 (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c OccName) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) 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 :: (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

Ord OccName 
OutputableBndr OccName 
Outputable OccName 
Uniquable OccName 
Binary OccName 
HasOccName OccName 

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

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

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

foldOccSet :: (OccName -> b -> b) -> b -> OccSet -> b Source

Tidying up