Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
The core Futhark AST does not contain type information when we use a variable. Therefore, most transformations expect to be able to access some kind of symbol table that maps names to their types.
This module defines the concept of a type environment as a mapping
from variable names to NameInfo
s. Convenience facilities are
also provided to communicate that some monad or applicative functor
maintains type information.
Synopsis
- class (Applicative m, Decorations lore) => HasScope lore m | m -> lore where
- lookupType :: VName -> m Type
- lookupInfo :: VName -> m (NameInfo lore)
- askScope :: m (Scope lore)
- asksScope :: (Scope lore -> a) -> m a
- data NameInfo lore
- = LetName (LetDec lore)
- | FParamName (FParamInfo lore)
- | LParamName (LParamInfo lore)
- | IndexName IntType
- class (HasScope lore m, Monad m) => LocalScope lore m where
- localScope :: Scope lore -> m a -> m a
- type Scope lore = Map VName (NameInfo lore)
- class Scoped lore a | a -> lore where
- inScopeOf :: (Scoped lore a, LocalScope lore m) => a -> m b -> m b
- scopeOfLParams :: LParamInfo lore ~ dec => [Param dec] -> Scope lore
- scopeOfFParams :: FParamInfo lore ~ dec => [Param dec] -> Scope lore
- scopeOfPattern :: LetDec lore ~ dec => PatternT dec -> Scope lore
- scopeOfPatElem :: LetDec lore ~ dec => PatElemT dec -> Scope lore
- type SameScope lore1 lore2 = (LetDec lore1 ~ LetDec lore2, FParamInfo lore1 ~ FParamInfo lore2, LParamInfo lore1 ~ LParamInfo lore2)
- castScope :: SameScope fromlore tolore => Scope fromlore -> Scope tolore
- data ExtendedScope lore m a
- extendedScope :: ExtendedScope lore m a -> Scope lore -> m a
Documentation
class (Applicative m, Decorations lore) => HasScope lore m | m -> lore where Source #
The class of applicative functors (or more common in practice:
monads) that permit the lookup of variable types. A default method
for lookupType
exists, which is sufficient (if not always
maximally efficient, and using error
to fail) when askScope
is defined.
lookupType :: VName -> m Type Source #
Return the type of the given variable, or fail if it is not in the type environment.
lookupInfo :: VName -> m (NameInfo lore) Source #
Return the info of the given variable, or fail if it is not in the type environment.
askScope :: m (Scope lore) Source #
Return the type environment contained in the applicative functor.
asksScope :: (Scope lore -> a) -> m a Source #
Return the result of applying some function to the type environment.
Instances
How some name in scope was bound.
LetName (LetDec lore) | |
FParamName (FParamInfo lore) | |
LParamName (LParamInfo lore) | |
IndexName IntType |
Instances
class (HasScope lore m, Monad m) => LocalScope lore m where Source #
The class of monads that not only provide a Scope
, but also
the ability to locally extend it. A Reader
containing a
Scope
is the prototypical example of such a monad.
localScope :: Scope lore -> m a -> m a Source #
Run a computation with an extended type environment. Note that this is intended to *add* to the current type environment, it does not replace it.
Instances
type Scope lore = Map VName (NameInfo lore) Source #
A scope is a mapping from variable names to information about that name.
class Scoped lore a | a -> lore where Source #
The class of things that can provide a scope. There is no
overarching rule for what this means. For a Stm
, it is the
corresponding pattern. For a Lambda
, is is the parameters.
Instances
inScopeOf :: (Scoped lore a, LocalScope lore m) => a -> m b -> m b Source #
Extend the monadic scope with the scopeOf
the given value.
scopeOfLParams :: LParamInfo lore ~ dec => [Param dec] -> Scope lore Source #
The scope of some lambda parameters.
scopeOfFParams :: FParamInfo lore ~ dec => [Param dec] -> Scope lore Source #
The scope of some function or loop parameters.
scopeOfPatElem :: LetDec lore ~ dec => PatElemT dec -> Scope lore Source #
The scope of a pattern element.
type SameScope lore1 lore2 = (LetDec lore1 ~ LetDec lore2, FParamInfo lore1 ~ FParamInfo lore2, LParamInfo lore1 ~ LParamInfo lore2) Source #
A constraint that indicates two lores have the same NameInfo
representation.
castScope :: SameScope fromlore tolore => Scope fromlore -> Scope tolore Source #
If two scopes are really the same, then you can convert one to the other.
Extended type environment
data ExtendedScope lore m a Source #
A monad transformer that carries around an extended Scope
.
Its lookupType
method will first look in the extended Scope
,
and then use the lookupType
method of the underlying monad.
Instances
extendedScope :: ExtendedScope lore m a -> Scope lore -> m a Source #
Run a computation in the extended type environment.