Copyright | (c) 1999 - 2004 Wolfgang Lux 2011 - 2013 Björn Peemöller 2016 Finn Teegen |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module provides the implementation of identifiers and some utility functions for identifiers.
Identifiers comprise the name of the denoted entity and an id,
which can be used for renaming identifiers, e.g., in order to resolve
name conflicts between identifiers from different scopes. An
identifier with an id 0
is considered as not being renamed
and, hence, its id will not be shown.
Qualified identifiers may optionally be prefixed by a module name.
Synopsis
- data ModuleIdent = ModuleIdent {
- midSpanInfo :: SpanInfo
- midQualifiers :: [String]
- mkMIdent :: [String] -> ModuleIdent
- moduleName :: ModuleIdent -> String
- escModuleName :: ModuleIdent -> String
- fromModuleName :: String -> ModuleIdent
- isValidModuleName :: String -> Bool
- addPositionModuleIdent :: Position -> ModuleIdent -> ModuleIdent
- mIdentLength :: ModuleIdent -> Int
- data Ident = Ident {}
- mkIdent :: String -> Ident
- showIdent :: Ident -> String
- escName :: Ident -> String
- identSupply :: [Ident]
- globalScope :: Integer
- hasGlobalScope :: Ident -> Bool
- isRenamed :: Ident -> Bool
- renameIdent :: Ident -> Integer -> Ident
- unRenameIdent :: Ident -> Ident
- updIdentName :: (String -> String) -> Ident -> Ident
- addPositionIdent :: Position -> Ident -> Ident
- isInfixOp :: Ident -> Bool
- identLength :: Ident -> Int
- data QualIdent = QualIdent {}
- qualName :: QualIdent -> String
- escQualName :: QualIdent -> String
- isQInfixOp :: QualIdent -> Bool
- qualify :: Ident -> QualIdent
- qualifyWith :: ModuleIdent -> Ident -> QualIdent
- qualQualify :: ModuleIdent -> QualIdent -> QualIdent
- qualifyLike :: QualIdent -> Ident -> QualIdent
- isQualified :: QualIdent -> Bool
- unqualify :: QualIdent -> Ident
- qualUnqualify :: ModuleIdent -> QualIdent -> QualIdent
- localIdent :: ModuleIdent -> QualIdent -> Maybe Ident
- isLocalIdent :: ModuleIdent -> QualIdent -> Bool
- updQualIdent :: (ModuleIdent -> ModuleIdent) -> (Ident -> Ident) -> QualIdent -> QualIdent
- qIdentLength :: QualIdent -> Int
- emptyMIdent :: ModuleIdent
- mainMIdent :: ModuleIdent
- preludeMIdent :: ModuleIdent
- arrowId :: Ident
- unitId :: Ident
- boolId :: Ident
- charId :: Ident
- intId :: Ident
- floatId :: Ident
- listId :: Ident
- ioId :: Ident
- successId :: Ident
- eqId :: Ident
- ordId :: Ident
- enumId :: Ident
- boundedId :: Ident
- readId :: Ident
- showId :: Ident
- numId :: Ident
- fractionalId :: Ident
- monadId :: Ident
- trueId :: Ident
- falseId :: Ident
- nilId :: Ident
- consId :: Ident
- tupleId :: Int -> Ident
- isTupleId :: Ident -> Bool
- tupleArity :: Ident -> Int
- mainId :: Ident
- minusId :: Ident
- fminusId :: Ident
- applyId :: Ident
- errorId :: Ident
- failedId :: Ident
- idId :: Ident
- succId :: Ident
- predId :: Ident
- toEnumId :: Ident
- fromEnumId :: Ident
- enumFromId :: Ident
- enumFromThenId :: Ident
- enumFromToId :: Ident
- enumFromThenToId :: Ident
- maxBoundId :: Ident
- minBoundId :: Ident
- lexId :: Ident
- readsPrecId :: Ident
- readParenId :: Ident
- showsPrecId :: Ident
- showParenId :: Ident
- showStringId :: Ident
- andOpId :: Ident
- eqOpId :: Ident
- leqOpId :: Ident
- ltOpId :: Ident
- orOpId :: Ident
- appendOpId :: Ident
- dotOpId :: Ident
- anonId :: Ident
- isAnonId :: Ident -> Bool
- qArrowId :: QualIdent
- qUnitId :: QualIdent
- qBoolId :: QualIdent
- qCharId :: QualIdent
- qIntId :: QualIdent
- qFloatId :: QualIdent
- qListId :: QualIdent
- qIOId :: QualIdent
- qSuccessId :: QualIdent
- isPrimTypeId :: QualIdent -> Bool
- qEqId :: QualIdent
- qOrdId :: QualIdent
- qEnumId :: QualIdent
- qBoundedId :: QualIdent
- qReadId :: QualIdent
- qShowId :: QualIdent
- qNumId :: QualIdent
- qFractionalId :: QualIdent
- qMonadId :: QualIdent
- qTrueId :: QualIdent
- qFalseId :: QualIdent
- qNilId :: QualIdent
- qConsId :: QualIdent
- qTupleId :: Int -> QualIdent
- isQTupleId :: QualIdent -> Bool
- qTupleArity :: QualIdent -> Int
- qApplyId :: QualIdent
- qErrorId :: QualIdent
- qFailedId :: QualIdent
- qIdId :: QualIdent
- qFromEnumId :: QualIdent
- qEnumFromId :: QualIdent
- qEnumFromThenId :: QualIdent
- qEnumFromToId :: QualIdent
- qEnumFromThenToId :: QualIdent
- qMaxBoundId :: QualIdent
- qMinBoundId :: QualIdent
- qLexId :: QualIdent
- qReadsPrecId :: QualIdent
- qReadParenId :: QualIdent
- qShowsPrecId :: QualIdent
- qShowParenId :: QualIdent
- qShowStringId :: QualIdent
- qAndOpId :: QualIdent
- qEqOpId :: QualIdent
- qLeqOpId :: QualIdent
- qLtOpId :: QualIdent
- qOrOpId :: QualIdent
- qAppendOpId :: QualIdent
- qDotOpId :: QualIdent
- fpSelectorId :: Int -> Ident
- isFpSelectorId :: Ident -> Bool
- isQualFpSelectorId :: QualIdent -> Bool
- recSelectorId :: QualIdent -> Ident -> Ident
- qualRecSelectorId :: ModuleIdent -> QualIdent -> Ident -> QualIdent
- recUpdateId :: QualIdent -> Ident -> Ident
- qualRecUpdateId :: ModuleIdent -> QualIdent -> Ident -> QualIdent
- recordExt :: String
- recordExtId :: Ident -> Ident
- isRecordExtId :: Ident -> Bool
- fromRecordExtId :: Ident -> Ident
- labelExt :: String
- labelExtId :: Ident -> Ident
- isLabelExtId :: Ident -> Bool
- fromLabelExtId :: Ident -> Ident
- renameLabel :: Ident -> Ident
- mkLabelIdent :: String -> Ident
Module identifiers
data ModuleIdent Source #
Module identifier
ModuleIdent | |
|
Instances
mkMIdent :: [String] -> ModuleIdent Source #
Construct a ModuleIdent
from a list of String
s forming the
the hierarchical module name.
moduleName :: ModuleIdent -> String Source #
Retrieve the hierarchical name of a module
escModuleName :: ModuleIdent -> String Source #
Show the name of an ModuleIdent
escaped by ticks
fromModuleName :: String -> ModuleIdent Source #
isValidModuleName :: String -> Bool Source #
Check whether a String
is a valid module name.
Valid module names must satisfy the following conditions:
- The name must not be empty
- The name must consist of one or more single identifiers, seperated by dots
- Each single identifier must be non-empty, start with a letter and consist of letter, digits, single quotes or underscores only
addPositionModuleIdent :: Position -> ModuleIdent -> ModuleIdent Source #
Add a source code Position
to a ModuleIdent
mIdentLength :: ModuleIdent -> Int Source #
Local identifiers
Simple identifier
identSupply :: [Ident] Source #
Infinite list of different Ident
s
globalScope :: Integer Source #
Global scope for renaming
hasGlobalScope :: Ident -> Bool Source #
Has the identifier global scope?
unRenameIdent :: Ident -> Ident Source #
Revert the renaming of an Ident
by resetting its unique number
updIdentName :: (String -> String) -> Ident -> Ident Source #
Change the name of an Ident
using a renaming function
identLength :: Ident -> Int Source #
Qualified identifiers
Qualified identifier
QualIdent | |
|
qualifyWith :: ModuleIdent -> Ident -> QualIdent Source #
Convert an Ident
to a QualIdent
with a given ModuleIdent
qualQualify :: ModuleIdent -> QualIdent -> QualIdent Source #
Convert an QualIdent
to a new QualIdent
with a given ModuleIdent
.
If the original QualIdent
already contains an ModuleIdent
it
remains unchanged.
qualifyLike :: QualIdent -> Ident -> QualIdent Source #
Qualify an Ident
with the ModuleIdent
of the given QualIdent
,
if present.
isQualified :: QualIdent -> Bool Source #
Check whether a QualIdent
contains a ModuleIdent
qualUnqualify :: ModuleIdent -> QualIdent -> QualIdent Source #
Remove the qualification with a specific ModuleIdent
. If the
original QualIdent
has no ModuleIdent
or a different one, it
remains unchanged.
localIdent :: ModuleIdent -> QualIdent -> Maybe Ident Source #
Extract the Ident
of an QualIdent
if it is local to the
ModuleIdent
, i.e. if the Ident
is either unqualified or qualified
with the given ModuleIdent
.
isLocalIdent :: ModuleIdent -> QualIdent -> Bool Source #
Check whether the given QualIdent
is local to the given ModuleIdent
.
updQualIdent :: (ModuleIdent -> ModuleIdent) -> (Ident -> Ident) -> QualIdent -> QualIdent Source #
Update a QualIdent
by applying functions to its components
qIdentLength :: QualIdent -> Int Source #
Predefined simple identifiers
Identifiers for modules
emptyMIdent :: ModuleIdent Source #
ModuleIdent
for the empty module
mainMIdent :: ModuleIdent Source #
ModuleIdent
for the main module
preludeMIdent :: ModuleIdent Source #
ModuleIdent
for the Prelude
Identifiers for types
Identifiers for type classes
fractionalId :: Ident Source #
Ident
for the Fractional
class
Identifiers for constructors
tupleArity :: Ident -> Int Source #
Compute the arity of a tuple identifier
Identifiers for values
fromEnumId :: Ident Source #
Ident
for the fromEnum function
enumFromId :: Ident Source #
Ident
for the enumFrom function
enumFromThenId :: Ident Source #
Ident
for the enumFromThen function
enumFromToId :: Ident Source #
Ident
for the enumFromTo function
enumFromThenToId :: Ident Source #
Ident
for the enumFromThenTo function
maxBoundId :: Ident Source #
Ident
for the maxBound function
minBoundId :: Ident Source #
Ident
for the minBound function
readsPrecId :: Ident Source #
Ident
for the readsPrec function
readParenId :: Ident Source #
Ident
for the readParen function
showsPrecId :: Ident Source #
Ident
for the showsPrec function
showParenId :: Ident Source #
Ident
for the showParen function
showStringId :: Ident Source #
Ident
for the showString function
Predefined qualified identifiers
Identifiers for types
qSuccessId :: QualIdent Source #
QualIdent
for the type Success
Identifiers for type classes
qFractionalId :: QualIdent Source #
QualIdent
for the Fractional
class
Identifiers for constructors
isQTupleId :: QualIdent -> Bool Source #
Check whether an QualIdent
is an identifier for an tuple type
qTupleArity :: QualIdent -> Int Source #
Compute the arity of an qualified tuple identifier
Identifiers for values
qFromEnumId :: QualIdent Source #
QualIdent
for the fromEnum function
qEnumFromId :: QualIdent Source #
QualIdent
for the enumFrom function
qEnumFromThenId :: QualIdent Source #
QualIdent
for the enumFromThen function
qEnumFromToId :: QualIdent Source #
QualIdent
for the enumFromTo function
qEnumFromThenToId :: QualIdent Source #
QualIdent
for the enumFromThenTo function
qMaxBoundId :: QualIdent Source #
QualIdent
for the maxBound function
qMinBoundId :: QualIdent Source #
QualIdent
for the minBound function
qReadsPrecId :: QualIdent Source #
QualIdent
for the readsPrec function
qReadParenId :: QualIdent Source #
QualIdent
for the readParen function
qShowsPrecId :: QualIdent Source #
QualIdent
for the showsPrec function
qShowParenId :: QualIdent Source #
QualIdent
for the showParen function
qShowStringId :: QualIdent Source #
QualIdent
for the showString function
Extended functionality
Functional patterns
isFpSelectorId :: Ident -> Bool Source #
Check whether an Ident
is an identifier for a functional pattern
isQualFpSelectorId :: QualIdent -> Bool Source #
Check whether an QualIdent
is an identifier for a function pattern
Records
Construct an Ident
for a record selection pattern
:: ModuleIdent | default module |
-> QualIdent | record identifier |
-> Ident | label identifier |
-> QualIdent |
Construct a QualIdent
for a record selection pattern
Construct an Ident
for a record update pattern
:: ModuleIdent | default module |
-> QualIdent | record identifier |
-> Ident | label identifier |
-> QualIdent |
Construct a QualIdent
for a record update pattern