sslang-0.1.0.0
Safe HaskellNone
LanguageHaskell2010

Common.Identifiers

Description

The types of identifiers used across the compiler.

The types VarId, TVarId, DConId, and TConId are used in the IR for data variables, type variables, data constructors, and type constructors, which each inhabit a separate namespace. The underlying Identifier type is used in the AST, before these different kinds of identifiers are differentiated by the lowering phase.

These are defined as newtypes (rather than as type aliases) that ultimately abstract over the underlying String Identifier. We do this for a few reasons:

  • The particular newtype carries semantic meaning in the IR, e.g., VarId is an identifier for data variables and nothing else. This prevents semantically distinct items from being used in place of one another (without explicit coercion). For example, this will prevent accidentally using a type variable identifier as a data constructor.
  • In the future, this may be extended to carry other (non-semantic) metadata, such as source code location.
  • It allows us to freely attach typeclass instances to this type without FlexibleInstances (since String is a type synonym for [Char]).

Users should never need to specifically use the data constructor for each newtype, e.g., VarId (Identifier "foo"). Instead, each identifier belongs to the IsString typeclass, that can be written as fromString "foo", so that the appropriate type can be inferred from the context where the identifier is used. Furthermore, the fromString call can be automatically inserted by the OverloadedStrings GHC extension, meaning we can just write "foo".

All identifier types are instances of the Identifiable typeclass, which allows us to write generic functions that operate over any kind of identifier. One can explicitly convert from an identifier to another using the handy fromId helper; which specific type of identifier may be inferred from the outer context, or explicitly annotated (e.g., fromId i :: VarId to construct a VarId out of identifier i).

Synopsis

Documentation

class (IsString i, Ord i, Show i) => Identifiable i where Source #

A type that may be used as a Sslang identifier.

Methods

ident Source #

Arguments

:: i 
-> String

Obtain its underlying String representation.

Instances

Instances details
Identifiable CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: CSym -> String Source #

Identifiable VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: VarId -> String Source #

Identifiable DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: DConId -> String Source #

Identifiable TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: TVarId -> String Source #

Identifiable TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: TConId -> String Source #

Identifiable Identifier Source # 
Instance details

Defined in Common.Identifiers

Identifiable CIdent Source # 
Instance details

Defined in Codegen.LibSSM

Methods

ident :: CIdent -> String Source #

class IsString a where #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Methods

fromString :: String -> a #

Instances

Instances details
IsString ShortByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Short.Internal

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Lazy.Internal

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal

IsString Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

fromString :: String -> Doc #

IsString Id 
Instance details

Defined in Language.C.Syntax

Methods

fromString :: String -> Id #

IsString StringLit 
Instance details

Defined in Language.C.Syntax

Methods

fromString :: String -> StringLit #

IsString Doc 
Instance details

Defined in Text.PrettyPrint.Mainland

Methods

fromString :: String -> Doc #

IsString CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> CSym #

IsString VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> VarId #

IsString DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> DConId #

IsString TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> TVarId #

IsString TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> TConId #

IsString Identifier Source # 
Instance details

Defined in Common.Identifiers

IsString CIdent Source # 
Instance details

Defined in Codegen.LibSSM

Methods

fromString :: String -> CIdent #

IsString ErrorMsg Source # 
Instance details

Defined in Common.Compiler

a ~ Char => IsString [a]

(a ~ Char) context was introduced in 4.9.0.0

Since: base-2.1

Instance details

Defined in Data.String

Methods

fromString :: String -> [a] #

IsString a => IsString (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Identity a #

a ~ Char => IsString (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

fromString :: String -> Seq a #

IsString (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

fromString :: String -> Doc a #

IsString (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

fromString :: String -> Doc ann #

IsString a => IsString (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Const a b #

fromId :: (Identifiable a, Identifiable b) => a -> b Source #

Explicitly convert between two types of identifiers.

showId :: (Show a, Identifiable b) => a -> b Source #

Convert a showable instance to some kind of identifier.

newtype TConId Source #

Identifier for type constructors, e.g., Option.

Constructors

TConId Identifier 

Instances

Instances details
Eq TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

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

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

Data TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TConId -> c TConId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TConId #

toConstr :: TConId -> Constr #

dataTypeOf :: TConId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TConId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TConId) #

gmapT :: (forall b. Data b => b -> b) -> TConId -> TConId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TConId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TConId -> r #

gmapQ :: (forall d. Data d => d -> u) -> TConId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TConId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TConId -> m TConId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TConId -> m TConId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TConId -> m TConId #

Ord TConId Source # 
Instance details

Defined in Common.Identifiers

Show TConId Source # 
Instance details

Defined in Common.Identifiers

IsString TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> TConId #

Semigroup TConId Source # 
Instance details

Defined in Common.Identifiers

Monoid TConId Source # 
Instance details

Defined in Common.Identifiers

Pretty TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: TConId -> Doc ann

prettyList :: [TConId] -> Doc ann

ToIdent TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

toIdent :: TConId -> SrcLoc -> Id

Identifiable TConId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: TConId -> String Source #

newtype TVarId Source #

ToIdentifier for type variable, e.g., a.

Constructors

TVarId Identifier 

Instances

Instances details
Eq TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

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

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

Data TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TVarId -> c TVarId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TVarId #

toConstr :: TVarId -> Constr #

dataTypeOf :: TVarId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TVarId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TVarId) #

gmapT :: (forall b. Data b => b -> b) -> TVarId -> TVarId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TVarId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TVarId -> r #

gmapQ :: (forall d. Data d => d -> u) -> TVarId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TVarId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TVarId -> m TVarId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TVarId -> m TVarId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TVarId -> m TVarId #

Ord TVarId Source # 
Instance details

Defined in Common.Identifiers

Show TVarId Source # 
Instance details

Defined in Common.Identifiers

IsString TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> TVarId #

Semigroup TVarId Source # 
Instance details

Defined in Common.Identifiers

Monoid TVarId Source # 
Instance details

Defined in Common.Identifiers

Pretty TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: TVarId -> Doc ann

prettyList :: [TVarId] -> Doc ann

ToIdent TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

toIdent :: TVarId -> SrcLoc -> Id

Identifiable TVarId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: TVarId -> String Source #

HasFreeVars Scheme TVarId Source # 
Instance details

Defined in IR.Types.Type

HasFreeVars Type TVarId Source # 
Instance details

Defined in IR.Types.Type

newtype DConId Source #

Identifier for data constructors, e.g., None.

Constructors

DConId Identifier 

Instances

Instances details
Eq DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

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

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

Data DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DConId -> c DConId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DConId #

toConstr :: DConId -> Constr #

dataTypeOf :: DConId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DConId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DConId) #

gmapT :: (forall b. Data b => b -> b) -> DConId -> DConId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DConId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DConId -> r #

gmapQ :: (forall d. Data d => d -> u) -> DConId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DConId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DConId -> m DConId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DConId -> m DConId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DConId -> m DConId #

Ord DConId Source # 
Instance details

Defined in Common.Identifiers

Show DConId Source # 
Instance details

Defined in Common.Identifiers

IsString DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> DConId #

Semigroup DConId Source # 
Instance details

Defined in Common.Identifiers

Monoid DConId Source # 
Instance details

Defined in Common.Identifiers

Pretty DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: DConId -> Doc ann

prettyList :: [DConId] -> Doc ann

ToIdent DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

toIdent :: DConId -> SrcLoc -> Id

Identifiable DConId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: DConId -> String Source #

newtype VarId Source #

Identifier for data variables, e.g., x.

Constructors

VarId Identifier 

Instances

Instances details
Eq VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

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

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

Data VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarId -> c VarId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VarId #

toConstr :: VarId -> Constr #

dataTypeOf :: VarId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VarId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VarId) #

gmapT :: (forall b. Data b => b -> b) -> VarId -> VarId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarId -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarId -> r #

gmapQ :: (forall d. Data d => d -> u) -> VarId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VarId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarId -> m VarId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarId -> m VarId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarId -> m VarId #

Ord VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

compare :: VarId -> VarId -> Ordering #

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

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

(>) :: VarId -> VarId -> Bool #

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

max :: VarId -> VarId -> VarId #

min :: VarId -> VarId -> VarId #

Show VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

showsPrec :: Int -> VarId -> ShowS #

show :: VarId -> String #

showList :: [VarId] -> ShowS #

IsString VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> VarId #

Semigroup VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

(<>) :: VarId -> VarId -> VarId #

sconcat :: NonEmpty VarId -> VarId #

stimes :: Integral b => b -> VarId -> VarId #

Monoid VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

mempty :: VarId #

mappend :: VarId -> VarId -> VarId #

mconcat :: [VarId] -> VarId #

Pretty VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: VarId -> Doc ann

prettyList :: [VarId] -> Doc ann

ToIdent VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

toIdent :: VarId -> SrcLoc -> Id

Identifiable VarId Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: VarId -> String Source #

HasFreeVars (Expr t) VarId Source # 
Instance details

Defined in IR.IR

Methods

freeVars :: Expr t -> Set VarId Source #

newtype TVarIdx Source #

de Bruijn index for type variables, e.g., '0

Constructors

TVarIdx Int 

Instances

Instances details
Eq TVarIdx Source # 
Instance details

Defined in Common.Identifiers

Methods

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

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

Data TVarIdx Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TVarIdx -> c TVarIdx #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TVarIdx #

toConstr :: TVarIdx -> Constr #

dataTypeOf :: TVarIdx -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TVarIdx) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TVarIdx) #

gmapT :: (forall b. Data b => b -> b) -> TVarIdx -> TVarIdx #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TVarIdx -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TVarIdx -> r #

gmapQ :: (forall d. Data d => d -> u) -> TVarIdx -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TVarIdx -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TVarIdx -> m TVarIdx #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TVarIdx -> m TVarIdx #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TVarIdx -> m TVarIdx #

Ord TVarIdx Source # 
Instance details

Defined in Common.Identifiers

Show TVarIdx Source # 
Instance details

Defined in Common.Identifiers

Pretty TVarIdx Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: TVarIdx -> Doc ann

prettyList :: [TVarIdx] -> Doc ann

newtype CSym Source #

Identifier for C symbols, e.g., printf.

Constructors

CSym Identifier 

Instances

Instances details
Eq CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

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

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

Data CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CSym -> c CSym #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CSym #

toConstr :: CSym -> Constr #

dataTypeOf :: CSym -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CSym) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CSym) #

gmapT :: (forall b. Data b => b -> b) -> CSym -> CSym #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CSym -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CSym -> r #

gmapQ :: (forall d. Data d => d -> u) -> CSym -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CSym -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CSym -> m CSym #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CSym -> m CSym #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CSym -> m CSym #

Ord CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

compare :: CSym -> CSym -> Ordering #

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

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

(>) :: CSym -> CSym -> Bool #

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

max :: CSym -> CSym -> CSym #

min :: CSym -> CSym -> CSym #

Show CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

showsPrec :: Int -> CSym -> ShowS #

show :: CSym -> String #

showList :: [CSym] -> ShowS #

IsString CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

fromString :: String -> CSym #

Semigroup CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

(<>) :: CSym -> CSym -> CSym #

sconcat :: NonEmpty CSym -> CSym #

stimes :: Integral b => b -> CSym -> CSym #

Monoid CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

mempty :: CSym #

mappend :: CSym -> CSym -> CSym #

mconcat :: [CSym] -> CSym #

Pretty CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: CSym -> Doc ann

prettyList :: [CSym] -> Doc ann

ToIdent CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

toIdent :: CSym -> SrcLoc -> Id

Identifiable CSym Source # 
Instance details

Defined in Common.Identifiers

Methods

ident :: CSym -> String Source #

class Identifiable i => HasFreeVars t i | t -> i where Source #

Terms t that have free variables i

Methods

freeVars :: t -> Set i Source #

Instances

Instances details
HasFreeVars Scheme TVarId Source # 
Instance details

Defined in IR.Types.Type

HasFreeVars Type TVarId Source # 
Instance details

Defined in IR.Types.Type

HasFreeVars (Expr t) VarId Source # 
Instance details

Defined in IR.IR

Methods

freeVars :: Expr t -> Set VarId Source #

newtype Identifier Source #

A generic Sslang identifier.

Used as the type for identifiers in the AST.

Also used as the base type for other identifiers (e.g., TConId, VarId), which derive their typeclass instances from this.

Constructors

Identifier String 

Instances

Instances details
Eq Identifier Source # 
Instance details

Defined in Common.Identifiers

Data Identifier Source # 
Instance details

Defined in Common.Identifiers

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identifier -> c Identifier #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Identifier #

toConstr :: Identifier -> Constr #

dataTypeOf :: Identifier -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Identifier) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Identifier) #

gmapT :: (forall b. Data b => b -> b) -> Identifier -> Identifier #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identifier -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identifier -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identifier -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identifier -> m Identifier #

Ord Identifier Source # 
Instance details

Defined in Common.Identifiers

Show Identifier Source # 
Instance details

Defined in Common.Identifiers

IsString Identifier Source # 
Instance details

Defined in Common.Identifiers

Semigroup Identifier Source # 
Instance details

Defined in Common.Identifiers

Monoid Identifier Source # 
Instance details

Defined in Common.Identifiers

Pretty Identifier Source # 
Instance details

Defined in Common.Identifiers

Methods

pretty :: Identifier -> Doc ann

prettyList :: [Identifier] -> Doc ann

ToIdent Identifier Source # 
Instance details

Defined in Common.Identifiers

Methods

toIdent :: Identifier -> SrcLoc -> Id

Identifiable Identifier Source # 
Instance details

Defined in Common.Identifiers

isCons :: Identifiable a => a -> Bool Source #

Whether an identifier refers to a type or data constructor.

isVar :: Identifiable a => a -> Bool Source #

Whether an identifier refers to a type or data variable.

Note that internal variables (i.e., isIVar) are also considered variables.

mangle :: (Identifiable i, Data i, Data a) => Proxy i -> a -> a Source #

Mangle all identifiers in some data structure.

This function is useful for preserving the general syntactic structure of a datum without inspecting the specific identifiers used within. This is useful for comparing ASTs modulo alpha renaming.

The Proxy i parameter is used to specify exactly which kind of identifier to mangle. For instance, to mangle all VarId nodes:

mangleVarId :: Data a => a -> a
mangleVarId = mangle (Proxy :: VarId)

mangleVars :: Data a => a -> a Source #

Mangle all type and data variable identifiers.

isReserved :: Identifiable a => a -> Bool Source #

Whether an identifier is reserved.

reserved :: Identifiable a => a -> a Source #

Create a reserved identifier (that can be code-generated as long as a can)

isGenerated :: Identifiable a => a -> Bool Source #

Whether an identifier is an compiler-generated variable name.

genId :: Identifiable a => a -> a Source #

Generate an internal variable name (parenthesized) from some hint.

ungenId :: Identifiable a => a -> Maybe a Source #

Filter out generated identifiers.

cons :: Identifier Source #

Cons identifier for Lists

nil :: Identifier Source #

Nil identifier for Lists