mirror of
https://github.com/github/semantic.git
synced 2024-12-20 21:31:48 +03:00
Add newPreludeScope and Prelude relation
So we can filter out built int scopes and preludes from the database
This commit is contained in:
parent
5c7a8a823d
commit
fa09de3872
@ -201,7 +201,7 @@ withChildFrame :: ( Member (Allocator address) sig
|
||||
-> (address -> Evaluator term address value m a)
|
||||
-> Evaluator term address value m a
|
||||
withChildFrame declaration body = do
|
||||
scope <- newScope mempty
|
||||
scope <- newPreludeScope mempty
|
||||
putDeclarationScope declaration scope
|
||||
frame <- newFrame scope mempty
|
||||
withScopeAndFrame frame (body frame)
|
||||
|
@ -39,7 +39,7 @@ defineBuiltIn :: ( HasCallStack
|
||||
defineBuiltIn declaration rel value = withCurrentCallStack callStack $ do
|
||||
currentScope' <- currentScope
|
||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||
associatedScope <- newScope lexicalEdges
|
||||
associatedScope <- newPreludeScope lexicalEdges
|
||||
-- TODO: This span is still wrong.
|
||||
declare declaration rel emptySpan (Just associatedScope)
|
||||
|
||||
@ -79,7 +79,7 @@ defineClass declaration superclasses body = void . define declaration Default $
|
||||
let superclassEdges = (Superclass, ) <$> (fmap pure . catMaybes $ superScopes)
|
||||
current = fmap (Lexical, ) . pure . pure $ currentScope'
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
childScope <- newScope edges
|
||||
childScope <- newPreludeScope edges
|
||||
putDeclarationScope declaration childScope
|
||||
|
||||
withScope childScope $ do
|
||||
|
@ -5,6 +5,7 @@ module Control.Abstract.ScopeGraph
|
||||
, declare
|
||||
, reference
|
||||
, newScope
|
||||
, newPreludeScope
|
||||
, Declaration(..)
|
||||
, ScopeGraph
|
||||
, ScopeError(..)
|
||||
@ -132,6 +133,21 @@ newScope edges = do
|
||||
address <- alloc name
|
||||
address <$ modify (ScopeGraph.newScope address edges)
|
||||
|
||||
-- | Inserts a new scope into the scope graph with the given edges.
|
||||
newPreludeScope :: ( Member (Allocator address) sig
|
||||
, Member (State (ScopeGraph address)) sig
|
||||
, Member Fresh sig
|
||||
, Carrier sig m
|
||||
, Ord address
|
||||
)
|
||||
=> Map EdgeLabel [address]
|
||||
-> Evaluator term address value m address
|
||||
newPreludeScope edges = do
|
||||
-- Take the edges and construct a new scope
|
||||
name <- gensym
|
||||
address <- alloc name
|
||||
address <$ modify (ScopeGraph.newPreludeScope address edges)
|
||||
|
||||
newtype CurrentScope address = CurrentScope { unCurrentScope :: address }
|
||||
|
||||
currentScope :: ( Carrier sig m
|
||||
|
@ -174,7 +174,7 @@ defineSelf :: ( AbstractValue term address value m
|
||||
=> Evaluator term address value m ()
|
||||
defineSelf = do
|
||||
let self = Declaration X.__self
|
||||
declare self Default emptySpan Nothing
|
||||
declare self Prelude emptySpan Nothing
|
||||
slot <- lookupDeclaration self
|
||||
assign slot =<< object =<< currentFrame
|
||||
|
||||
|
@ -12,6 +12,7 @@ module Data.Abstract.ScopeGraph
|
||||
, insertDeclarationSpan
|
||||
, insertImportReference
|
||||
, newScope
|
||||
, newPreludeScope
|
||||
, insertScope
|
||||
, insertEdge
|
||||
, Path(..)
|
||||
@ -45,7 +46,7 @@ import Prologue
|
||||
data Slot address = Slot { frameAddress :: address, position :: Position }
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
data Relation = Default | Instance
|
||||
data Relation = Default | Instance | Prelude
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
data Info scopeAddress = Info
|
||||
@ -56,11 +57,18 @@ data Info scopeAddress = Info
|
||||
} deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
-- Offsets and frame addresses in the heap should be addresses?
|
||||
data Scope address = Scope
|
||||
{ edges :: Map EdgeLabel [address]
|
||||
, references :: Map Reference (Path address)
|
||||
, declarations :: Seq (Info address)
|
||||
} deriving (Eq, Show, Ord, Generic, NFData)
|
||||
data Scope address =
|
||||
Scope {
|
||||
edges :: Map EdgeLabel [address]
|
||||
, references :: Map Reference (Path address)
|
||||
, declarations :: Seq (Info address)
|
||||
}
|
||||
| PreludeScope {
|
||||
edges :: Map EdgeLabel [address]
|
||||
, references :: Map Reference (Path address)
|
||||
, declarations :: Seq (Info address)
|
||||
}
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
instance Lower (Scope scopeAddress) where
|
||||
lowerBound = Scope mempty mempty mempty
|
||||
@ -236,6 +244,10 @@ insertDeclarationSpan decl@Declaration{..} span g = fromMaybe g $ do
|
||||
newScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
|
||||
newScope address edges = insertScope address (Scope edges mempty mempty)
|
||||
|
||||
-- | Insert a new scope with the given address and edges into the scope graph.
|
||||
newPreludeScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
|
||||
newPreludeScope address edges = insertScope address (PreludeScope edges mempty mempty)
|
||||
|
||||
insertScope :: Ord address => address -> Scope address -> ScopeGraph address -> ScopeGraph address
|
||||
insertScope address scope = ScopeGraph . Map.insert address scope . unScopeGraph
|
||||
|
||||
|
@ -92,7 +92,7 @@ instance Evaluatable Method where
|
||||
|
||||
params <- withScope associatedScope $ do
|
||||
-- TODO: Should we give `self` a special Relation?
|
||||
declare (Declaration __self) Default emptySpan Nothing
|
||||
declare (Declaration __self) Prelude emptySpan Nothing
|
||||
for methodParameters $ \paramNode -> do
|
||||
param <- maybeM (throwNoNameError paramNode) (declaredName paramNode)
|
||||
param <$ declare (Declaration param) Default span Nothing
|
||||
|
@ -93,7 +93,7 @@ evaluate lang perModule runTerm modules = do
|
||||
let (scopeEdges, frameLinks) = case (parentScope, parentFrame) of
|
||||
(Just parentScope, Just parentFrame) -> (Map.singleton Lexical [ parentScope ], Map.singleton Lexical (Map.singleton parentScope parentFrame))
|
||||
_ -> mempty
|
||||
scopeAddress <- newScope scopeEdges
|
||||
scopeAddress <- if Prologue.null scopeEdges then newPreludeScope scopeEdges else newScope scopeEdges
|
||||
frameAddress <- newFrame scopeAddress frameLinks
|
||||
val <- runInModule scopeAddress frameAddress (perModule (runValueEffects . moduleBody) m)
|
||||
pure ((scopeAddress, frameAddress), val)
|
||||
|
Loading…
Reference in New Issue
Block a user