Agda-2.4.2.1: A dependently typed functional programming language and proof assistant

Safe HaskellNone
LanguageHaskell98

Agda.Syntax.Abstract.Name

Contents

Description

Abstract names carry unique identifiers and stuff.

Synopsis

Documentation

data Name Source

A name is a unique identifier and a suggestion for a concrete name. The concrete name contains the source location (if any) of the name. The source location of the binding site is also recorded.

Instances

Eq Name 
Ord Name 
Show Name

Only use this show function in debugging! To convert an abstract Name into a string use prettyShow.

Hashable Name 
Pretty Name 
KillRange Name 
SetRange Name 
HasRange Name 
IsNoName Name

An abstract name is empty if its concrete name is empty.

Subst Name 
AddContext Name 
PrettyTCM Name 
EmbPrj Name 
InstantiateFull Name 
Typeable * Name 
ToConcrete Name Name 
Reify Name Name 
AddContext (Dom (Name, Type)) 
ToAbstract (NewName Name) Name 
ToAbstract (NewName BoundName) Name 
(Free i, Reify i a) => Reify (Abs i) (Name, a) 
AddContext ([Name], Dom Type) 
AddContext (Name, Dom Type) 

data QName Source

Qualified names are non-empty lists of names. Equality on qualified names are just equality on the last name, i.e. the module part is just for show.

The SetRange instance for qualified names sets all individual ranges (including those of the module prefix) to the given one.

Constructors

QName 

data QNamed a Source

Something preceeded by a qualified name.

Constructors

QNamed 

Fields

qname :: QName
 
qnamed :: a
 

newtype ModuleName Source

A module name is just a qualified name.

The SetRange instance for module names sets all individual ranges to the given one.

Constructors

MName 

Fields

mnameToList :: [Name]
 

newtype AmbiguousQName Source

Ambiguous qualified names. Used for overloaded constructors.

Invariant: All the names in the list must have the same concrete, unqualified name. (This implies that they all have the same Range).

Constructors

AmbQ 

Fields

unAmbQ :: [QName]
 

Instances

Eq AmbiguousQName 
Show AmbiguousQName 
KillRange AmbiguousQName 
HasRange AmbiguousQName

The range of an AmbiguousQName is the range of any of its disambiguations (they are the same concrete name).

EmbPrj AmbiguousQName 
Typeable * AmbiguousQName 
UniverseBi Declaration AmbiguousQName 

isAnonymousModuleName :: ModuleName -> Bool Source

A module is anonymous if the qualification path ends in an underscore.

withRangesOf :: ModuleName -> [Name] -> ModuleName Source

Sets the ranges of the individual names in the module name to match those of the corresponding concrete names. If the concrete names are fewer than the number of module name name parts, then the initial name parts get the range noRange.

C.D.E `withRangesOf` [A, B] returns C.D.E but with ranges set as follows:

  • C: noRange.
  • D: the range of A.
  • E: the range of B.

Precondition: The number of module name name parts has to be at least as large as the length of the list.

withRangesOfQ :: ModuleName -> QName -> ModuleName Source

Like withRangesOf, but uses the name parts (qualifier + name) of the qualified name as the list of concrete names.

class MkName a where Source

Make a Name from some kind of string.

Minimal complete definition

mkName

Methods

mkName :: Range -> NameId -> a -> Name Source

The Range sets the definition site of the name, not the use site.

mkName_ :: NameId -> a -> Name Source

Instances

qnameToConcrete :: QName -> QName Source

Turn a qualified name into a concrete name. This should only be used as a fallback when looking up the right concrete name in the scope fails.

toTopLevelModuleName :: ModuleName -> TopLevelModuleName Source

Computes the TopLevelModuleName corresponding to the given module name, which is assumed to represent a top-level module name.

Precondition: The module name must be well-formed.

qualify_ :: Name -> QName Source

Convert a Name to a QName (add no module name).

isOperator :: QName -> Bool Source

Is the name an operator?

nextName :: Name -> Name Source

Get the next version of the concrete name. For instance, nextName "x" = "x₁". The name must not be a NoName.

Important instances: Eq, Ord, Hashable

IsNoName instances (checking for "_")

Show instances

Pretty instances

Range instances

HasRange

SetRange

KillRange

Sized instances

class IsNoName a where Source

Check whether a name is the empty name "_".

Methods

isNoName :: a -> Bool Source

Instances

IsNoName String 
IsNoName ByteString 
IsNoName QName 
IsNoName Name 
IsNoName Name

An abstract name is empty if its concrete name is empty.