curry-base-1.1.1: Functions for manipulating Curry programs

Copyright(c) 1999 - 2004 Wolfgang Lux
2011 - 2013 Björn Peemöller
2016 Finn Teegen
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.Base.Ident

Contents

Description

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

Module identifiers

data ModuleIdent Source #

Module identifier

Constructors

ModuleIdent 

Fields

Instances
Eq ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

Ord ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

Read ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

Show ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

Pretty ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

HasPosition ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

HasSpanInfo ModuleIdent Source # 
Instance details

Defined in Curry.Base.Ident

mkMIdent :: [String] -> ModuleIdent Source #

Construct a ModuleIdent from a list of Strings 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 #

Resemble the hierarchical module name from a String by splitting the String at inner dots.

Note: This function does not check the String to be a valid module identifier, use isValidModuleName for this purpose.

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

Local identifiers

data Ident Source #

Simple identifier

Constructors

Ident 

Fields

Instances
Eq Ident Source # 
Instance details

Defined in Curry.Base.Ident

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 
Instance details

Defined in Curry.Base.Ident

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Read Ident Source # 
Instance details

Defined in Curry.Base.Ident

Show Ident Source # 
Instance details

Defined in Curry.Base.Ident

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Pretty Ident Source # 
Instance details

Defined in Curry.Base.Ident

HasPosition Ident Source # 
Instance details

Defined in Curry.Base.Ident

HasSpanInfo Ident Source # 
Instance details

Defined in Curry.Base.Ident

mkIdent :: String -> Ident Source #

Construct an Ident from a String

showIdent :: Ident -> String Source #

Show function for an Ident

escName :: Ident -> String Source #

Show the name of an Ident escaped by ticks

identSupply :: [Ident] Source #

Infinite list of different Idents

globalScope :: Integer Source #

Global scope for renaming

hasGlobalScope :: Ident -> Bool Source #

Has the identifier global scope?

isRenamed :: Ident -> Bool Source #

Is the Ident renamed?

renameIdent :: Ident -> Integer -> Ident Source #

Rename an Ident by changing its unique number

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

isInfixOp :: Ident -> Bool Source #

Check whether an Ident identifies an infix operation

Qualified identifiers

data QualIdent Source #

Qualified identifier

Constructors

QualIdent 

Fields

Instances
Eq QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

Ord QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

Read QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

Show QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

Pretty QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

HasPosition QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

HasSpanInfo QualIdent Source # 
Instance details

Defined in Curry.Base.Ident

qualName :: QualIdent -> String Source #

show function for qualified identifiers)=

escQualName :: QualIdent -> String Source #

Show the name of an QualIdent escaped by ticks

isQInfixOp :: QualIdent -> Bool Source #

Check whether an QualIdent identifies an infix operation

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

unqualify :: QualIdent -> Ident Source #

Remove the qualification of an QualIdent

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

Predefined simple identifiers

Identifiers for modules

emptyMIdent :: ModuleIdent Source #

ModuleIdent for the empty module

mainMIdent :: ModuleIdent Source #

ModuleIdent for the main module

Identifiers for types

arrowId :: Ident Source #

Ident for the type '(->)'

unitId :: Ident Source #

Ident for the type/value unit ('()')

boolId :: Ident Source #

Ident for the type Bool

charId :: Ident Source #

Ident for the type Char

intId :: Ident Source #

Ident for the type Int

floatId :: Ident Source #

Ident for the type Float

listId :: Ident Source #

Ident for the type '[]'

ioId :: Ident Source #

Ident for the type IO

successId :: Ident Source #

Ident for the type Success

Identifiers for type classes

eqId :: Ident Source #

Ident for the Eq class

ordId :: Ident Source #

Ident for the Ord class

enumId :: Ident Source #

Ident for the Enum class

readId :: Ident Source #

Ident for the Read class

showId :: Ident Source #

Ident for the Show class

numId :: Ident Source #

Ident for the Num class

monadId :: Ident Source #

Ident for the Monad class

Identifiers for constructors

trueId :: Ident Source #

Ident for the value True

falseId :: Ident Source #

Ident for the value False

nilId :: Ident Source #

Ident for the value '[]'

consId :: Ident Source #

Ident for the function :

tupleId :: Int -> Ident Source #

Construct an Ident for an n-ary tuple where n > 1

isTupleId :: Ident -> Bool Source #

Check whether an Ident is an identifier for an tuple type

tupleArity :: Ident -> Int Source #

Compute the arity of a tuple identifier

Identifiers for values

mainId :: Ident Source #

Ident for the main function

minusId :: Ident Source #

Ident for the minus function

fminusId :: Ident Source #

Ident for the minus function for Floats

applyId :: Ident Source #

Ident for the apply function

errorId :: Ident Source #

Ident for the error function

failedId :: Ident Source #

Ident for the failed function

idId :: Ident Source #

Ident for the id function

succId :: Ident Source #

Ident for the succ function

predId :: Ident Source #

Ident for the pred function

toEnumId :: Ident Source #

Ident for the toEnum function

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

lexId :: Ident Source #

Ident for the lex 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

andOpId :: Ident Source #

Ident for the && operator

eqOpId :: Ident Source #

Ident for the == operator

leqOpId :: Ident Source #

Ident for the <= operator

ltOpId :: Ident Source #

Ident for the < operator

orOpId :: Ident Source #

Ident for the || operator

appendOpId :: Ident Source #

Ident for the ++ operator

dotOpId :: Ident Source #

Ident for the . operator

anonId :: Ident Source #

Ident for anonymous variable

isAnonId :: Ident -> Bool Source #

Check whether an Ident represents an anonymous identifier (anonId)

Predefined qualified identifiers

Identifiers for types

qArrowId :: QualIdent Source #

QualIdent for the type '(->)'

qUnitId :: QualIdent Source #

QualIdent for the type/value unit ('()')

qListId :: QualIdent Source #

QualIdent for the type '[]'

qSuccessId :: QualIdent Source #

QualIdent for the type Success

isPrimTypeId :: QualIdent -> Bool Source #

Check whether an QualIdent is an primary type constructor

Identifiers for type classes

Identifiers for constructors

qTrueId :: QualIdent Source #

QualIdent for the constructor True

qFalseId :: QualIdent Source #

QualIdent for the constructor False

qNilId :: QualIdent Source #

QualIdent for the constructor '[]'

qConsId :: QualIdent Source #

QualIdent for the constructor :

qTupleId :: Int -> QualIdent Source #

QualIdent for the type of n-ary tuples

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

qApplyId :: QualIdent Source #

QualIdent for the apply function

qErrorId :: QualIdent Source #

QualIdent for the error function

qFailedId :: QualIdent Source #

QualIdent for the failed function

qIdId :: QualIdent Source #

QualIdent for the id function

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

qLexId :: QualIdent Source #

QualIdent for the lex 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

qAndOpId :: QualIdent Source #

QualIdent for the && operator

qEqOpId :: QualIdent Source #

QualIdent for the == operator

qLeqOpId :: QualIdent Source #

QualIdent for the <= operator

qLtOpId :: QualIdent Source #

QualIdent for the < operator

qOrOpId :: QualIdent Source #

QualIdent for the || operator

qDotOpId :: QualIdent Source #

QualIdent for the . operator

Extended functionality

Functional patterns

fpSelectorId :: Int -> Ident Source #

Construct an Ident for a functional pattern

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

recSelectorId Source #

Arguments

:: QualIdent

identifier of the record

-> Ident

identifier of the label

-> Ident 

Construct an Ident for a record selection pattern

qualRecSelectorId Source #

Arguments

:: ModuleIdent

default module

-> QualIdent

record identifier

-> Ident

label identifier

-> QualIdent 

Construct a QualIdent for a record selection pattern

recUpdateId Source #

Arguments

:: QualIdent

record identifier

-> Ident

label identifier

-> Ident 

Construct an Ident for a record update pattern

qualRecUpdateId Source #

Arguments

:: ModuleIdent

default module

-> QualIdent

record identifier

-> Ident

label identifier

-> QualIdent 

Construct a QualIdent for a record update pattern

recordExt :: String Source #

Annotation for record identifiers

recordExtId :: Ident -> Ident Source #

Construct an Ident for a record

isRecordExtId :: Ident -> Bool Source #

Check whether an Ident is an identifier for a record

fromRecordExtId :: Ident -> Ident Source #

Retrieve the Ident from a record identifier

labelExt :: String Source #

Annotation for record label identifiers

labelExtId :: Ident -> Ident Source #

Construct an Ident for a record label

isLabelExtId :: Ident -> Bool Source #

Check whether an Ident is an identifier for a record label

fromLabelExtId :: Ident -> Ident Source #

Retrieve the Ident from a record label identifier

renameLabel :: Ident -> Ident Source #

Rename an Ident for a record label

mkLabelIdent :: String -> Ident Source #

Construct an Ident for a record label