libcspm-1.0.0: A library providing a parser, type checker and evaluator for CSPM.

Safe HaskellNone

CSPM.DataStructures.Names

Contents

Description

Names used by the evaluator. This is heavily inspired by GHC.

Synopsis

Data Types

data OccName Source

A name that occurs in the source code somewhere.

Constructors

OccName String 

data Name Source

A renamed name and is the exclusive type used after the renamer. Names are guaranteed to be unique, meaning that two names are equal iff they refer to the same binding instance. For example, consider the following CSPM code:

      f = 1
      g = let f = 2 within (f, f)

This will be renamed to:

      f0 = 1
      g = let f1 = 2 within (f1, f1)

Constructors

Name 

Fields

nameType :: NameType

The type of this name.

nameFullyQualified :: !UnRenamedName

The original occurence of this name (used for error messages).

nameDefinition :: !SrcSpan

Where this name was defined. If this occurs in a pattern, then it will be equal to the location of the pattern, otherwise it will be equal to the location of the definition that this name binds to.

nameUnique :: !Int

The unique identifier for this name. Inserted by the renamer.

nameIsConstructor :: Bool

Is this name a type constructor, i.e. a datatype or a channel?

Instances

Eq Name 
Ord Name 
Show Name 
Typeable Name 
Hashable Name 
PrettyPrintable Name 
(Applicative m, Monad m) => MonadicPrettyPrintable m Name 
(Applicative m, Monad m) => MonadicPrettyPrintable m TCExp 
TypeCheckable TCSType Type 
TypeCheckable TCSTypeScheme TypeScheme 
TypeCheckable TCInteractiveStmt () 
TypeCheckable TCAssertion () 
TypeCheckable TCExp Type 
TypeCheckable TCPat Type 
TypeCheckable TCMatch Type 
(Applicative m, Monad m) => MonadicPrettyPrintable m (Exp Name) 
TypeCheckable TCDecl [(Name, Type)] 
TypeCheckable TCDataTypeClause (Name, [Type]) 
FreeVars (Pat Name) 
FreeVars (Match Name) 
FreeVars (DataTypeClause Name) 
FreeVars (ModelOption Name) 
FreeVars (Assertion Name) 
FreeVars (Decl Name) 
FreeVars (Stmt Name) 
FreeVars (Field Name) 
FreeVars (Exp Name) 
BoundNames (Pat Name) 
BoundNames (DataTypeClause Name) 
BoundNames (Decl Name) 
BoundNames (Stmt Name) 
BoundNames (Field Name) 
Desugarable (Pat Name) 
Desugarable (Match Name) 
Desugarable (DataTypeClause Name) 
Desugarable (ModelOption Name) 
Desugarable (Assertion Name) 
Desugarable (InteractiveStmt Name) 
Desugarable (Stmt Name) 
Desugarable (Field Name) 
Desugarable (Exp Name) 
Desugarable (CSPMFile Name) 
Evaluatable (Exp Name) 
Bindable (Pat Name) 
TypeCheckable (SType Name) Type 
TypeCheckable (STypeScheme Name) TypeScheme 
TypeCheckable (Pat Name) Type 
TypeCheckable (Match Name) Type 
TypeCheckable (ModelOption Name) () 
TypeCheckable (Assertion Name) () 
TypeCheckable (InteractiveStmt Name) () 
TypeCheckable (Exp Name) Type 
TypeCheckable (CSPMFile Name) () 
TypeCheckable (AnCSPMFile Name) () 
TypeCheckable (Decl Name) [(Name, Type)] 
TypeCheckable (DataTypeClause Name) (Name, [Type]) 
Compressable a => Compressable (Annotated (Maybe SymbolTable, PSymbolTable) a) 

data NameType Source

Constructors

ExternalName

An externally visible name (like a top level definition).

InternalName

A name created by the renamer, but from the users' source (e.g. from a lambda).

WiredInName

A built in name.

Instances

Construction Helpers

mkWiredInName :: MonadIO m => UnRenamedName -> Bool -> m NameSource

Utility Functions

isNameDataConstructor :: Name -> BoolSource

Does the given Name correspond to a data type or a channel definition.