1
1
mirror of https://github.com/github/semantic.git synced 2024-12-24 23:42:31 +03:00

Merge branch 'indexer-prototype' of github.com:github/semantic into indexer-prototype

This commit is contained in:
Patrick Thomson 2019-01-22 09:50:16 -05:00
commit 245e021750
3 changed files with 29 additions and 17 deletions

View File

@ -57,6 +57,7 @@ lookup ref = ScopeGraph.scopeOfRef ref <$> get
declare :: ( Carrier sig m
, Member (State (ScopeGraph address)) sig
, Member (Reader (CurrentScope address)) sig
, Member (Reader ModuleInfo) sig
, Ord address
)
=> Declaration
@ -67,7 +68,8 @@ declare :: ( Carrier sig m
-> Evaluator term address value m ()
declare decl rel span kind scope = do
currentAddress <- currentScope
modify (fst . ScopeGraph.declare decl rel span kind scope currentAddress)
moduleInfo <- ask @ModuleInfo
modify (fst . ScopeGraph.declare decl moduleInfo rel span kind scope currentAddress)
putDeclarationScope :: (Ord address, Member (Reader (CurrentScope address)) sig, Member (State (ScopeGraph address)) sig, Carrier sig m) => Declaration -> address -> Evaluator term address value m ()
putDeclarationScope decl assocScope = do
@ -81,6 +83,7 @@ reference :: forall address sig m term value
. ( Ord address
, Member (State (ScopeGraph address)) sig
, Member (Reader (CurrentScope address)) sig
, Member (Reader ModuleInfo) sig
, Carrier sig m
)
=> Reference
@ -90,7 +93,8 @@ reference :: forall address sig m term value
-> Evaluator term address value m ()
reference ref span kind decl = do
currentAddress <- currentScope
modify @(ScopeGraph address) (ScopeGraph.reference ref span kind decl currentAddress)
moduleInfo <- ask @ModuleInfo
modify @(ScopeGraph address) (ScopeGraph.reference ref moduleInfo span kind decl currentAddress)
-- | Combinator to insert an export edge from the current scope to the provided scope address.
insertExportEdge :: (Member (Reader (CurrentScope scopeAddress)) sig, Member (State (ScopeGraph scopeAddress)) sig, Carrier sig m, Ord scopeAddress)
@ -198,7 +202,8 @@ insertImportReference ref span kind decl scopeAddress = do
scopeGraph <- get
scope <- lookupScope scopeAddress
currentAddress <- currentScope
newScope <- maybeM (throwScopeError ImportReferenceError) (ScopeGraph.insertImportReference ref span kind decl currentAddress scopeGraph scope)
moduleInfo <- ask @ModuleInfo
newScope <- maybeM (throwScopeError ImportReferenceError) (ScopeGraph.insertImportReference ref moduleInfo span kind decl currentAddress scopeGraph scope)
insertScope scopeAddress newScope
insertScope :: ( Member (State (ScopeGraph address)) sig

View File

@ -44,6 +44,7 @@ import qualified Data.Set as Set
import Data.Span
import Prelude hiding (lookup)
import Prologue
import Data.Abstract.Module
-- A slot is a location in the heap where a value is stored.
data Slot address = Slot { frameAddress :: address, position :: Position }
@ -54,6 +55,7 @@ data Relation = Default | Instance | Prelude
data Info scopeAddress = Info
{ infoDeclaration :: Declaration
, infoModule :: ModuleInfo
, infoRelation :: Relation
, infoSpan :: Span
, infoKind :: Kind
@ -63,6 +65,7 @@ data Info scopeAddress = Info
data ReferenceInfo = ReferenceInfo
{ refSpan :: Span
, refKind :: Kind
, refModule :: ModuleInfo
}
deriving (Eq, Show, Ord, Generic, NFData)
@ -154,29 +157,29 @@ lookupScope scope = Map.lookup scope . unScopeGraph
-- Declare a declaration with a span and an associated scope in the scope graph.
-- TODO: Return the whole value in Maybe or Either.
declare :: Ord scope => Declaration -> Relation -> Span -> Kind -> Maybe scope -> scope -> ScopeGraph scope -> (ScopeGraph scope, Maybe Position)
declare decl rel declSpan kind assocScope currentScope g = fromMaybe (g, Nothing) $ do
declare :: Ord scope => Declaration -> ModuleInfo -> Relation -> Span -> Kind -> Maybe scope -> scope -> ScopeGraph scope -> (ScopeGraph scope, Maybe Position)
declare decl moduleInfo rel declSpan kind assocScope currentScope g = fromMaybe (g, Nothing) $ do
scope <- lookupScope currentScope g
dataSeq <- ddataOfScope currentScope g
case Seq.findIndexR (\Info{..} -> decl == infoDeclaration && declSpan == infoSpan && rel == infoRelation) dataSeq of
Just index -> pure (g, Just (Position index))
Nothing -> do
let newScope = scope { declarations = declarations scope Seq.|> Info decl rel declSpan kind assocScope }
let newScope = scope { declarations = declarations scope Seq.|> Info decl moduleInfo rel declSpan kind assocScope }
pure (insertScope currentScope newScope g, Just (Position (length (declarations newScope))))
-- | Add a reference to a declaration in the scope graph.
-- Returns the original scope graph if the declaration could not be found.
reference :: Ord scope => Reference -> Span -> Kind -> Declaration -> scope -> ScopeGraph scope -> ScopeGraph scope
reference ref span kind decl currentAddress g = fromMaybe g $ do
reference :: Ord scope => Reference -> ModuleInfo -> Span -> Kind -> Declaration -> scope -> ScopeGraph scope -> ScopeGraph scope
reference ref moduleInfo span kind decl currentAddress g = fromMaybe g $ do
-- Start from the current address
currentScope' <- lookupScope currentAddress g
-- Build a path up to the declaration
flip (insertScope currentAddress) g . flip (insertReference ref span kind) currentScope' <$> findPath (const Nothing) decl currentAddress g
flip (insertScope currentAddress) g . flip (insertReference ref moduleInfo span kind) currentScope' <$> findPath (const Nothing) decl currentAddress g
-- | Insert a reference into the given scope by constructing a resolution path to the declaration within the given scope graph.
insertImportReference :: Ord address => Reference -> Span -> Kind -> Declaration -> address -> ScopeGraph address -> Scope address -> Maybe (Scope address)
insertImportReference ref span kind decl currentAddress g scope = flip (insertReference ref span kind) scope . EPath Import currentAddress <$> findPath (const Nothing) decl currentAddress g
insertImportReference :: Ord address => Reference -> ModuleInfo -> Span -> Kind -> Declaration -> address -> ScopeGraph address -> Scope address -> Maybe (Scope address)
insertImportReference ref moduleInfo span kind decl currentAddress g scope = flip (insertReference ref moduleInfo span kind) scope . EPath Import currentAddress <$> findPath (const Nothing) decl currentAddress g
lookupScopePath :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
lookupScopePath declaration currentAddress g = findPath (flip (lookupReference declaration) g) (Declaration declaration) currentAddress g
@ -203,10 +206,10 @@ foldGraph combine address graph = go lowerBound address
pathToDeclaration :: Ord scopeAddress => Declaration -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
pathToDeclaration decl address g = DPath decl . snd <$> lookupDeclaration (unDeclaration decl) address g
insertReference :: Reference -> Span -> Kind -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
insertReference ref span kind path scope = scope { references = Map.alter (\case
Nothing -> pure ([ ReferenceInfo span kind ], path)
Just (refInfos, path) -> pure (ReferenceInfo span kind : refInfos, path)) ref (references scope) }
insertReference :: Reference -> ModuleInfo -> Span -> Kind -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
insertReference ref moduleInfo span kind path scope = scope { references = Map.alter (\case
Nothing -> pure ([ ReferenceInfo span kind moduleInfo ], path)
Just (refInfos, path) -> pure (ReferenceInfo span kind moduleInfo : refInfos, path)) ref (references scope) }
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Info scopeAddress, Position)
lookupDeclaration name scope g = do

View File

@ -29,16 +29,19 @@ instance Diffable Function where
-- TODO: How should we represent function types, where applicable?
instance Evaluatable Function where
eval _ _ Function{..} = do
eval eval _ Function{..} = do
name <- maybeM (throwNoNameError functionName) (declaredName functionName)
span <- ask @Span
associatedScope <- declareFunction name span ScopeGraph.Function
params <- withScope associatedScope . for functionParameters $ \paramNode -> do
param <- maybeM (throwNoNameError paramNode) (declaredName paramNode)
-- TODO: Come up with an easier way to fetch the child node span instead of evaling it.
_ <- eval paramNode
paramSpan <- get @Span
-- TODO: This might be a motivation for a typeclass for `declarationKind` since we
-- sometimes create declarations for our children.
param <$ declare (Declaration param) Default span ScopeGraph.Parameter Nothing
param <$ declare (Declaration param) Default paramSpan ScopeGraph.Parameter Nothing
addr <- lookupDeclaration (Declaration name)
v <- function name params functionBody associatedScope
@ -48,6 +51,7 @@ declareFunction :: ( Carrier sig m
, Member (State (ScopeGraph address)) sig
, Member (Allocator address) sig
, Member (Reader (CurrentScope address)) sig
, Member (Reader ModuleInfo) sig
, Member Fresh sig
, Ord address
)