Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class (IsString i, Ord i, Show i) => Identifiable i where
- class IsString a where
- fromString :: String -> a
- fromId :: (Identifiable a, Identifiable b) => a -> b
- showId :: (Show a, Identifiable b) => a -> b
- newtype TConId = TConId Identifier
- newtype TVarId = TVarId Identifier
- newtype DConId = DConId Identifier
- newtype VarId = VarId Identifier
- newtype TVarIdx = TVarIdx Int
- newtype CSym = CSym Identifier
- class Identifiable i => HasFreeVars t i | t -> i where
- newtype Identifier = Identifier String
- isCons :: Identifiable a => a -> Bool
- isVar :: Identifiable a => a -> Bool
- mangle :: (Identifiable i, Data i, Data a) => Proxy i -> a -> a
- mangleVars :: Data a => a -> a
- isReserved :: Identifiable a => a -> Bool
- reserved :: Identifiable a => a -> a
- isGenerated :: Identifiable a => a -> Bool
- genId :: Identifiable a => a -> a
- ungenId :: Identifiable a => a -> Maybe a
- cons :: Identifier
- nil :: Identifier
Documentation
class (IsString i, Ord i, Show i) => Identifiable i where Source #
A type that may be used as a Sslang identifier.
Instances
Identifiable CSym Source # | |
Identifiable VarId Source # | |
Identifiable DConId Source # | |
Identifiable TVarId Source # | |
Identifiable TConId Source # | |
Identifiable Identifier Source # | |
Defined in Common.Identifiers Methods ident :: Identifier -> String Source # | |
Identifiable CIdent Source # | |
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a #
Instances
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.
Identifier for type constructors, e.g., Option
.
Constructors
TConId Identifier |
Instances
Eq TConId Source # | |
Data TConId Source # | |
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 # | |
Show TConId Source # | |
IsString TConId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> TConId # | |
Semigroup TConId Source # | |
Monoid TConId Source # | |
Pretty TConId Source # | |
Defined in Common.Identifiers | |
ToIdent TConId Source # | |
Defined in Common.Identifiers | |
Identifiable TConId Source # | |
ToIdentifier for type variable, e.g., a
.
Constructors
TVarId Identifier |
Instances
Eq TVarId Source # | |
Data TVarId Source # | |
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 # | |
Show TVarId Source # | |
IsString TVarId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> TVarId # | |
Semigroup TVarId Source # | |
Monoid TVarId Source # | |
Pretty TVarId Source # | |
Defined in Common.Identifiers | |
ToIdent TVarId Source # | |
Defined in Common.Identifiers | |
Identifiable TVarId Source # | |
HasFreeVars Scheme TVarId Source # | |
HasFreeVars Type TVarId Source # | |
Identifier for data constructors, e.g., None
.
Constructors
DConId Identifier |
Instances
Eq DConId Source # | |
Data DConId Source # | |
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 # | |
Show DConId Source # | |
IsString DConId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> DConId # | |
Semigroup DConId Source # | |
Monoid DConId Source # | |
Pretty DConId Source # | |
Defined in Common.Identifiers | |
ToIdent DConId Source # | |
Defined in Common.Identifiers | |
Identifiable DConId Source # | |
Identifier for data variables, e.g., x
.
Constructors
VarId Identifier |
Instances
Eq VarId Source # | |
Data VarId Source # | |
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 # 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 # | |
Show VarId Source # | |
IsString VarId Source # | |
Defined in Common.Identifiers Methods fromString :: String -> VarId # | |
Semigroup VarId Source # | |
Monoid VarId Source # | |
Pretty VarId Source # | |
Defined in Common.Identifiers | |
ToIdent VarId Source # | |
Defined in Common.Identifiers | |
Identifiable VarId Source # | |
HasFreeVars (Expr t) VarId Source # | |
de Bruijn index for type variables, e.g., '0
Instances
Eq TVarIdx Source # | |
Data TVarIdx Source # | |
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 # | |
Show TVarIdx Source # | |
Pretty TVarIdx Source # | |
Defined in Common.Identifiers |
Identifier for C symbols, e.g., printf
.
Constructors
CSym Identifier |
Instances
Eq CSym Source # | |
Data CSym Source # | |
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 # 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 # | |
Show CSym Source # | |
IsString CSym Source # | |
Defined in Common.Identifiers Methods fromString :: String -> CSym # | |
Semigroup CSym Source # | |
Monoid CSym Source # | |
Pretty CSym Source # | |
Defined in Common.Identifiers | |
ToIdent CSym Source # | |
Defined in Common.Identifiers | |
Identifiable CSym Source # | |
class Identifiable i => HasFreeVars t i | t -> i where Source #
Terms t
that have free variables i
Instances
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
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