mirror of
https://github.com/github/semantic.git
synced 2025-01-01 19:55:34 +03:00
Make currentScope optional so we can have empty graphs
This commit is contained in:
parent
f902cac04f
commit
cc994b0af9
@ -18,7 +18,6 @@ module Data.Abstract.ScopeGraph
|
|||||||
, emptyGraph
|
, emptyGraph
|
||||||
, reference
|
, reference
|
||||||
, create
|
, create
|
||||||
, currentScope
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Abstract.Live
|
import Data.Abstract.Live
|
||||||
@ -36,10 +35,10 @@ data Scope scopeAddress = Scope {
|
|||||||
} deriving (Eq, Show, Ord)
|
} deriving (Eq, Show, Ord)
|
||||||
|
|
||||||
|
|
||||||
data ScopeGraph scope = ScopeGraph { unScopeGraph :: (Map scope (Scope scope), scope) }
|
data ScopeGraph scope = ScopeGraph { graph :: Map scope (Scope scope), currentScope :: Maybe scope }
|
||||||
|
|
||||||
emptyGraph :: scope -> ScopeGraph scope
|
emptyGraph :: Ord scope => ScopeGraph scope
|
||||||
emptyGraph scope = ScopeGraph (Map.singleton scope (Scope mempty mempty mempty), scope)
|
emptyGraph = ScopeGraph mempty Nothing
|
||||||
|
|
||||||
deriving instance Eq address => Eq (ScopeGraph address)
|
deriving instance Eq address => Eq (ScopeGraph address)
|
||||||
deriving instance Show address => Show (ScopeGraph address)
|
deriving instance Show address => Show (ScopeGraph address)
|
||||||
@ -58,65 +57,58 @@ pathDeclaration (DPath d) = d
|
|||||||
pathDeclaration (EPath _ _ p) = pathDeclaration p
|
pathDeclaration (EPath _ _ p) = pathDeclaration p
|
||||||
|
|
||||||
pathsOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map Reference (Path scope))
|
pathsOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map Reference (Path scope))
|
||||||
pathsOfScope scope = fmap references . Map.lookup scope . fst . unScopeGraph
|
pathsOfScope scope = fmap references . Map.lookup scope . graph
|
||||||
|
|
||||||
ddataOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map Declaration Span)
|
ddataOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map Declaration Span)
|
||||||
ddataOfScope scope = fmap declarations . Map.lookup scope . fst . unScopeGraph
|
ddataOfScope scope = fmap declarations . Map.lookup scope . graph
|
||||||
|
|
||||||
linksOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map EdgeLabel [scope])
|
linksOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map EdgeLabel [scope])
|
||||||
linksOfScope scope = fmap edges . Map.lookup scope . fst . unScopeGraph
|
linksOfScope scope = fmap edges . Map.lookup scope . graph
|
||||||
|
|
||||||
lookupScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Scope scope)
|
lookupScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Scope scope)
|
||||||
lookupScope scope = Map.lookup scope . fst . unScopeGraph
|
lookupScope scope = Map.lookup scope . graph
|
||||||
|
|
||||||
currentScope :: ScopeGraph scope -> scope
|
|
||||||
currentScope = snd . unScopeGraph
|
|
||||||
|
|
||||||
scopeGraph :: ScopeGraph scope -> Map scope (Scope scope)
|
|
||||||
scopeGraph = fst . unScopeGraph
|
|
||||||
|
|
||||||
declare :: Ord scope => Declaration -> Span -> ScopeGraph scope -> ScopeGraph scope
|
declare :: Ord scope => Declaration -> Span -> ScopeGraph scope -> ScopeGraph scope
|
||||||
declare declaration ddata graph = let scopeKey = currentScope graph
|
declare declaration ddata g@ScopeGraph{..} = fromMaybe g $ do
|
||||||
in case lookupScope scopeKey graph of
|
scopeKey <- currentScope
|
||||||
Just scope -> let newScope = scope { declarations = Map.insert declaration ddata (declarations scope) }
|
scope <- lookupScope scopeKey g
|
||||||
in graph { unScopeGraph = (Map.insert scopeKey newScope (fst $ unScopeGraph graph), scopeKey) }
|
let newScope = scope { declarations = Map.insert declaration ddata (declarations scope) }
|
||||||
Nothing -> graph
|
pure $ g { graph = (Map.insert scopeKey newScope graph) }
|
||||||
|
|
||||||
reference :: Ord scope => Reference -> Declaration -> ScopeGraph scope -> ScopeGraph scope
|
reference :: Ord scope => Reference -> Declaration -> ScopeGraph scope -> ScopeGraph scope
|
||||||
reference ref declaration graph = let
|
reference ref declaration g@ScopeGraph{..} = fromMaybe g $ do
|
||||||
currentAddress = currentScope graph
|
currentAddress <- currentScope
|
||||||
declDataOfScope address = do
|
currentScope' <- lookupScope currentAddress g
|
||||||
dataMap <- ddataOfScope address graph
|
go currentAddress currentScope' currentAddress id
|
||||||
Map.lookup declaration dataMap
|
where
|
||||||
go currentScope address path =
|
declDataOfScope address = do
|
||||||
case declDataOfScope address of
|
dataMap <- ddataOfScope address g
|
||||||
Just ddata ->
|
Map.lookup declaration dataMap
|
||||||
let newScope = currentScope { references = Map.insert ref (path (DPath declaration)) (references currentScope) }
|
go currentAddress currentScope address path =
|
||||||
in Just (graph { unScopeGraph = (Map.insert currentAddress newScope (scopeGraph graph), currentAddress) })
|
case declDataOfScope address of
|
||||||
Nothing -> let
|
Just ddata ->
|
||||||
traverseEdges edge = do
|
let newScope = currentScope { references = Map.insert ref (path (DPath declaration)) (references currentScope) }
|
||||||
linkMap <- linksOfScope address graph
|
in Just (g { graph = Map.insert currentAddress newScope graph })
|
||||||
scopes <- Map.lookup edge linkMap
|
Nothing -> let
|
||||||
-- Return the first path to the declaration through the scopes.
|
traverseEdges edge = do
|
||||||
getFirst (foldMap (First . ap (go currentScope) ((path .) . EPath edge)) scopes)
|
linkMap <- linksOfScope address g
|
||||||
in traverseEdges P <|> traverseEdges I
|
scopes <- Map.lookup edge linkMap
|
||||||
in case lookupScope currentAddress graph of
|
-- Return the first path to the declaration through the scopes.
|
||||||
Just currentScope -> fromMaybe graph (go currentScope currentAddress id)
|
getFirst (foldMap (First . ap (go currentAddress currentScope) ((path .) . EPath edge)) scopes)
|
||||||
Nothing -> graph
|
in traverseEdges P <|> traverseEdges I
|
||||||
|
|
||||||
create :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
|
create :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
|
||||||
create address edges graph = graph { unScopeGraph = (Map.insert address newScope (scopeGraph graph), address) }
|
create address edges g@ScopeGraph{..} = g { graph = Map.insert address newScope graph, currentScope = Just address }
|
||||||
where
|
where
|
||||||
newScope = Scope edges mempty mempty
|
newScope = Scope edges mempty mempty
|
||||||
|
|
||||||
scopeOfRef :: Ord scope => Reference -> ScopeGraph scope -> Maybe scope
|
scopeOfRef :: Ord scope => Reference -> ScopeGraph scope -> Maybe scope
|
||||||
scopeOfRef ref graph = go . Map.keys . fst $ unScopeGraph graph
|
scopeOfRef ref g@ScopeGraph{..} = go (Map.keys graph)
|
||||||
where
|
where
|
||||||
go (s : scopes') = case pathsOfScope s graph of
|
go (s : scopes') = fromMaybe (go scopes') $ do
|
||||||
Just pathMap -> case Map.lookup ref pathMap of
|
pathMap <- pathsOfScope s g
|
||||||
Just _ -> Just s
|
_ <- Map.lookup ref pathMap
|
||||||
Nothing -> go scopes'
|
pure (Just s)
|
||||||
Nothing -> go scopes'
|
|
||||||
go [] = Nothing
|
go [] = Nothing
|
||||||
|
|
||||||
pathOfRef :: (Ord scope) => Reference -> ScopeGraph scope -> Maybe (Path scope)
|
pathOfRef :: (Ord scope) => Reference -> ScopeGraph scope -> Maybe (Path scope)
|
||||||
@ -126,13 +118,12 @@ pathOfRef ref graph = do
|
|||||||
Map.lookup ref pathsMap
|
Map.lookup ref pathsMap
|
||||||
|
|
||||||
scopeOfDeclaration :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
|
scopeOfDeclaration :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
|
||||||
scopeOfDeclaration declaration graph = go . Map.keys . fst $ unScopeGraph graph
|
scopeOfDeclaration declaration g@ScopeGraph{..} = go (Map.keys graph)
|
||||||
where
|
where
|
||||||
go (s : scopes') = case ddataOfScope s graph of
|
go (s : scopes') = fromMaybe (go scopes') $ do
|
||||||
Just ddataMap -> case Map.lookup declaration ddataMap of
|
ddataMap <- ddataOfScope s g
|
||||||
Just _ -> Just s
|
_ <- Map.lookup declaration ddataMap
|
||||||
Nothing -> go scopes'
|
pure (Just s)
|
||||||
Nothing -> go scopes'
|
|
||||||
go [] = Nothing
|
go [] = Nothing
|
||||||
|
|
||||||
newtype Reference = Reference Name
|
newtype Reference = Reference Name
|
||||||
|
Loading…
Reference in New Issue
Block a user