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

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

Derived OccNames

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