| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Tokstyle.Analysis.Scope
Description
This module implements the Scope Binding pass.
This pass traverses the AST and replaces all variable names (Text) with unique identifiers (ScopedId). This eliminates any ambiguity from name shadowing and is a prerequisite for a correct and precise points-to analysis.
Synopsis
- data ScopedId = ScopedId {}
- data ScopeState = ScopeState {}
- runScopePass :: [Node (Lexeme Text)] -> ([Node (Lexeme ScopedId)], ScopeState)
- initialScopeState :: ScopeState
- dummyScopedId :: Text -> ScopedId
Documentation
A unique identifier for a variable, including its original name and scope info.
Constructors
| ScopedId | |
Instances
| Eq ScopedId Source # | |
| Ord ScopedId Source # | |
Defined in Tokstyle.Analysis.Scope | |
| Show ScopedId Source # | |
| IsString ScopedId Source # | |
Defined in Tokstyle.Analysis.Scope Methods fromString :: String -> ScopedId # | |
| Hashable ScopedId Source # | |
Defined in Tokstyle.Analysis.Scope | |
| Pretty ScopedId Source # | |
Defined in Tokstyle.Analysis.Scope | |
| DataFlow PointsToAnalysis PointsToContext ScopedId PointsToFact RelevantInputState Source # | |
Defined in Tokstyle.Analysis.PointsTo Methods emptyFacts :: PointsToContext ScopedId -> PointsToAnalysis PointsToFact Source # transfer :: PointsToContext ScopedId -> ScopedId -> Int -> PointsToFact -> Node (Lexeme ScopedId) -> PointsToAnalysis (PointsToFact, Set (ScopedId, RelevantInputState)) Source # join :: PointsToContext ScopedId -> PointsToFact -> PointsToFact -> PointsToAnalysis PointsToFact Source # | |
data ScopeState Source #
The state for the scope analysis traversal.
Constructors
| ScopeState | |
Instances
| Show ScopeState Source # | |
Defined in Tokstyle.Analysis.Scope Methods showsPrec :: Int -> ScopeState -> ShowS # show :: ScopeState -> String # showList :: [ScopeState] -> ShowS # | |
runScopePass :: [Node (Lexeme Text)] -> ([Node (Lexeme ScopedId)], ScopeState) Source #
Runs the scope binding pass on a list of translation units.
initialScopeState :: ScopeState Source #
The initial state for the scope analysis.
dummyScopedId :: Text -> ScopedId Source #
Creates a dummy ScopedId for non-variable identifiers like struct fields.