mirror of
https://github.com/github/semantic.git
synced 2024-12-15 01:51:39 +03:00
Build up paths using foldrGraph.
Co-Authored-By: Rick Winfrey <rick.winfrey@gmail.com>
This commit is contained in:
parent
c278733fd7
commit
db698dbd98
@ -132,36 +132,33 @@ reference ref decl currentAddress g = fromMaybe g $ do
|
|||||||
-- Start from the current address
|
-- Start from the current address
|
||||||
currentScope' <- lookupScope currentAddress g
|
currentScope' <- lookupScope currentAddress g
|
||||||
-- Build a path up to the declaration
|
-- Build a path up to the declaration
|
||||||
go lowerBound currentScope' currentAddress id
|
flip (insertScope currentAddress) g . flip (insertReference ref) currentScope' . snd <$> foldrGraph combine currentAddress g
|
||||||
where
|
where combine address path = fmap (address, )
|
||||||
go visited currentScope address path
|
$ pathToDeclaration decl address g
|
||||||
| address `Set.member` visited = Nothing
|
<|> uncurry (EPath Superclass) <$> path Superclass
|
||||||
| otherwise
|
<|> uncurry (EPath Import) <$> path Import
|
||||||
= flip (insertScope currentAddress) g . flip (insertReference ref) currentScope . path <$> pathToDeclaration decl address g
|
<|> uncurry (EPath Export) <$> path Export
|
||||||
<|> traverseEdges' Superclass <|> traverseEdges' Import <|> traverseEdges' Export <|> traverseEdges' Lexical
|
<|> uncurry (EPath Lexical) <$> path Lexical
|
||||||
where traverseEdges' edge = linksOfScope address g >>= Map.lookup edge >>= traverseEdges path (go (Set.insert address visited) currentScope) edge
|
|
||||||
|
|
||||||
-- | Insert a reference into the given scope by constructing a resolution path to the declaration within the given scope graph.
|
-- | Insert a reference into the given scope by constructing a resolution path to the declaration within the given scope graph.
|
||||||
insertImportReference :: Ord address => Reference -> Declaration -> address -> ScopeGraph address -> Scope address -> Maybe (Scope address)
|
insertImportReference :: Ord address => Reference -> Declaration -> address -> ScopeGraph address -> Scope address -> Maybe (Scope address)
|
||||||
insertImportReference ref decl currentAddress g scope = go lowerBound currentAddress (EPath Import currentAddress)
|
insertImportReference ref decl currentAddress g scope = flip (insertReference ref) scope . EPath Import currentAddress . snd <$> foldrGraph combine currentAddress g
|
||||||
where
|
where combine address path = fmap (address, )
|
||||||
go visited address path
|
$ pathToDeclaration decl address g
|
||||||
| address `Set.member` visited = Nothing
|
<|> uncurry (EPath Superclass) <$> path Superclass
|
||||||
| otherwise
|
<|> uncurry (EPath Import) <$> path Import
|
||||||
= flip (insertReference ref) scope . path <$> pathToDeclaration decl address g
|
<|> uncurry (EPath Export) <$> path Export
|
||||||
<|> traverseEdges' Superclass <|> traverseEdges' Import <|> traverseEdges' Export <|> traverseEdges' Lexical
|
<|> uncurry (EPath Lexical) <$> path Lexical
|
||||||
where traverseEdges' edge = linksOfScope address g >>= Map.lookup edge >>= traverseEdges path (go (Set.insert address visited)) edge
|
|
||||||
|
|
||||||
lookupScopePath :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
|
lookupScopePath :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
|
||||||
lookupScopePath declaration currentAddress g = go lowerBound currentAddress id
|
lookupScopePath declaration currentAddress g = snd <$> foldrGraph combine currentAddress g
|
||||||
where
|
where combine address path = fmap (address, )
|
||||||
go visited address path
|
$ pathToDeclaration (Declaration declaration) address g
|
||||||
| address `Set.member` visited = Nothing
|
<|> lookupReference declaration address g
|
||||||
| otherwise
|
<|> uncurry (EPath Superclass) <$> path Superclass
|
||||||
= path <$> pathToDeclaration (Declaration declaration) address g
|
<|> uncurry (EPath Import) <$> path Import
|
||||||
<|> path <$> lookupReference declaration address g
|
<|> uncurry (EPath Export) <$> path Export
|
||||||
<|> traverseEdges' Superclass <|> traverseEdges' Import <|> traverseEdges' Export <|> traverseEdges' Lexical
|
<|> uncurry (EPath Lexical) <$> path Lexical
|
||||||
where traverseEdges' edge = linksOfScope address g >>= Map.lookup edge >>= traverseEdges path (go (Set.insert address visited)) edge
|
|
||||||
|
|
||||||
foldrGraph :: Ord scopeAddress => (scopeAddress -> (EdgeLabel -> Maybe a) -> Maybe a) -> scopeAddress -> ScopeGraph scopeAddress -> Maybe a
|
foldrGraph :: Ord scopeAddress => (scopeAddress -> (EdgeLabel -> Maybe a) -> Maybe a) -> scopeAddress -> ScopeGraph scopeAddress -> Maybe a
|
||||||
foldrGraph combine address graph = go lowerBound address
|
foldrGraph combine address graph = go lowerBound address
|
||||||
@ -178,10 +175,6 @@ pathToDeclaration decl address g = DPath decl . snd <$> lookupDeclaration (unDec
|
|||||||
insertReference :: Reference -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
|
insertReference :: Reference -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
|
||||||
insertReference ref path scope = scope { references = Map.insert ref path (references scope) }
|
insertReference ref path scope = scope { references = Map.insert ref path (references scope) }
|
||||||
|
|
||||||
traverseEdges :: Foldable t => (Path scopeAddress -> Path scopeAddress) -> (scopeAddress -> (Path scopeAddress -> Path scopeAddress) -> Maybe a) -> EdgeLabel -> t scopeAddress -> Maybe a
|
|
||||||
-- Return the first path to the declaration through the scopes.
|
|
||||||
traverseEdges path go edge = getFirst . foldMap (First . (go <*> fmap path . EPath edge))
|
|
||||||
|
|
||||||
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe ((Declaration, (Span, Maybe scopeAddress)), Position)
|
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe ((Declaration, (Span, Maybe scopeAddress)), Position)
|
||||||
lookupDeclaration declaration scope g = do
|
lookupDeclaration declaration scope g = do
|
||||||
dataSeq <- ddataOfScope scope g
|
dataSeq <- ddataOfScope scope g
|
||||||
|
Loading…
Reference in New Issue
Block a user