Safe Haskell | None |
---|---|
Language | Haskell2010 |
Technique.Translate
Description
Given a Technique Procedure (concrete syntax tree), translate it into an internalized representation (abstract syntax tree) that can be subsequently executed (that is, interpreted; evaluated).
Synopsis
- data Environment = Environment {}
- emptyEnvironment :: Environment
- newtype Translate a = Translate (StateT Environment (Except CompilationError) a)
- runTranslate :: Environment -> Translate a -> Either CompilationError (a, Environment)
- translateTechnique :: Technique -> Translate [Function]
- translateProcedure :: Procedure -> Translate Function
- translateBlock :: Block -> Translate Step
- translateStatement :: Statement -> Translate ()
- translateExpression :: Expression -> Translate Step
- registerProcedure :: Offset -> Function -> Translate ()
- failBecause :: Offset -> FailureReason -> Translate a
- lookupVariable :: Offset -> Identifier -> Translate Name
- insertVariable :: Offset -> Identifier -> Translate Name
- appendStep :: Step -> Translate ()
- applyRestriction :: Attribute -> Block -> Translate Step
- resolveFunctions :: Step -> Translate Step
- lookupFunction :: Offset -> Function -> Translate Function
- setLocationFrom :: Located a => a -> Translate ()
Documentation
data Environment Source #
Environment in the type-theory sense of the word: the map(s) between names and their bindings.
Constructors
Environment | |
Instances
Eq Environment Source # | |
Defined in Technique.Translate | |
Show Environment Source # | |
Defined in Technique.Translate Methods showsPrec :: Int -> Environment -> ShowS # show :: Environment -> String # showList :: [Environment] -> ShowS # | |
MonadState Environment Translate Source # | |
Defined in Technique.Translate Methods get :: Translate Environment # put :: Environment -> Translate () # state :: (Environment -> (a, Environment)) -> Translate a # |
Constructors
Translate (StateT Environment (Except CompilationError) a) |
Instances
Monad Translate Source # | |
Functor Translate Source # | |
Applicative Translate Source # | |
MonadState Environment Translate Source # | |
Defined in Technique.Translate Methods get :: Translate Environment # put :: Environment -> Translate () # state :: (Environment -> (a, Environment)) -> Translate a # | |
MonadError CompilationError Translate Source # | |
Defined in Technique.Translate Methods throwError :: CompilationError -> Translate a # catchError :: Translate a -> (CompilationError -> Translate a) -> Translate a # |
runTranslate :: Environment -> Translate a -> Either CompilationError (a, Environment) Source #
Take a translator action and an environment and spin it up into a Step or nest of Steps (Subroutine) suitable for interpretation. In other words, translate between the concrete syntax types and the abstract syntax we can feed to an evaluator.
translateBlock :: Block -> Translate Step Source #
Blocks are scoping mechanisms, so accumulated environment is discarded once we finish resolving names within it.
translateStatement :: Statement -> Translate () Source #
translateExpression :: Expression -> Translate Step Source #
Note that this does NOT add the steps to the Environment.
registerProcedure :: Offset -> Function -> Translate () Source #
A given procedure call can either be to a user declared in-scope procedure or to a primative builtin. We have Invocation as the Step constructors for these cases.
failBecause :: Offset -> FailureReason -> Translate a Source #
lookupVariable :: Offset -> Identifier -> Translate Name Source #
insertVariable :: Offset -> Identifier -> Translate Name Source #
Identifiers are valid names but Names are unique, so that we can put them into the environment map. This is where we check for reuse of an already declared name (TODO) and given the local use of the identifier a scope-local (or globally?) unique name.
appendStep :: Step -> Translate () Source #
Accumulate a Step.
applyRestriction :: Attribute -> Block -> Translate Step Source #
This begins a new (more refined) scope and does *not* add its declarations or variables to the current environment.
resolveFunctions :: Step -> Translate Step Source #
The second stage of translation phase: iterate through the Steps and where a function call is made, look up to see if we actually know what it is.
setLocationFrom :: Located a => a -> Translate () Source #
Update the environment's idea of where in the source we are, so that if we need to generate an error message we can offer one with position information.