Skip to content

Commit

Permalink
compute correct spans for xlang entities
Browse files Browse the repository at this point in the history
Summary:
Glass doesn't resolve entity locations and currently uses [the first line of the file](https://fb.workplace.com/groups/csi.eng/permalink/1825973911235009/)

This diff modifies the DocumentSymbol/List methods handler so it
  - determines the idl db used by idl xrefs
  - fetches location from this db by using a custom glean query
  - updates the `toReferenceSymbol*` functions which convert the plain/idl xrefs (as Glean facts)  to a common internal representation `XRefData` so they can execute in different RepoHaxl instances.

This happens only for Cxx files which have idl xrefs, and won't have any effect in other cases.

We only use the "entity" field of the codemarkup.IdlEntity to resolve the file/span. The other fields (file and span) may be used if want to support minimal xlang navigation for languages we don't index.

## Caveat

- we don't enforce exact revision option for these xlang ref since in most cases, there won't be an exact match for both dbs.
- Need to be a bit careful when comparing/querying entities from different dbs, the types don't help to know if an entity is fully evaluated or if we're using the facts ids in a wrong context
- we don't generate digests for the idl db files (and we don't have digest on fbsource.fbthrift)

Reviewed By: nhawkes

Differential Revision: D55895695

fbshipit-source-id: 8348c09e548597cd13a432f964cd4e1e5813266a
  • Loading branch information
Philippe Bidinger authored and facebook-github-bot committed Apr 15, 2024
1 parent de16c5f commit 2654ffe
Show file tree
Hide file tree
Showing 5 changed files with 151 additions and 234 deletions.
108 changes: 70 additions & 38 deletions glean/glass/Glean/Glass/Handler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,7 @@ import Glean.Glass.Query (
QueryExpr(..)
)
import qualified Glean.Glass.Query.Cxx as Cxx
import Glean.Glass.XRefs ( GenXRef(..) )
import Glean.Glass.XRefs ( GenXRef(..), XRef, resolveEntitiesRange)

import Glean.Glass.SymbolMap ( toSymbolIndex )
import Glean.Glass.Search as Search
Expand Down Expand Up @@ -900,7 +900,7 @@ fetchSymbolsAndAttributesGlean
fetchSymbolsAndAttributesGlean tracer scm repoMapping dbInfo req opts be mlang = do
(res1, gLogs, elogs) <- traceSpan tracer "fetchDocumentSymbols" $
fetchDocumentSymbols file mlimit
specificRev includeRefs includeXlangRefs be mlang
specificRev includeRefs includeXlangRefs be mlang repoMapping dbInfo
res2 <- traceSpan tracer "addDynamicAttributes" $
addDynamicAttributes scm repoMapping dbInfo repo opts
file mlimit be res1
Expand Down Expand Up @@ -996,9 +996,12 @@ fetchDocumentSymbols
-> Bool -- ^ include xlang references?
-> GleanBackend b
-> Maybe Language
-> RepoMapping
-> GleanDBInfo
-> IO (DocumentSymbols, QueryEachRepoLog, Maybe ErrorLogger)
fetchDocumentSymbols (FileReference scsrepo path) mlimit
revSpec includeRefs includeXlangRefs b mlang = backendRunHaxl b $ do
revSpec includeRefs includeXlangRefs b mlang repoMapping dbInfo =
backendRunHaxl b $ do
--
-- we pick the first db in the list that has the full FileInfo{..}
-- and in exact_revision mode the rev also has to match precisely
Expand Down Expand Up @@ -1043,14 +1046,38 @@ fetchDocumentSymbols (FileReference scsrepo path) mlimit
(kindMap, merr) <- withRepo fileRepo $
documentSymbolKinds mlimit mlang fileId

let xrefsPlain = [ (refloc, ent) | PlainXRef (refloc, ent) <- xrefs ]
-- TODO handle IdlEntities without entity or with range annotations
let xrefsIdl = [ (ent, rangeSpan) |
IdlXRef (rangeSpan, Code.IdlEntity {
idlEntity_entity = Just ent }) <- xrefs ]

-- mark up symbols into normal format with static attributes
refs1 <- withRepo fileRepo $ catMaybes <$>
mapM (toReferenceSymbol scsrepo srcFile offsets) xrefs
-- Idl xrefs also needs db determination and range resolution

refsPlain <- withRepo fileRepo $
mapM (toReferenceSymbolPlain scsrepo srcFile offsets) xrefsPlain

refsIdl <- case xrefsIdl of
[] -> return []
(ent, _) : _ ->
-- TODO we assume all idl xrefs belong to the same db
let lang = entityLanguage ent in
case getLatestRepo repoMapping dbInfo scsrepo lang of
Nothing -> return []
Just idlRepo -> do
xrefs <- withRepo idlRepo $
resolveEntitiesRange scsrepo fst xrefsIdl
withRepo idlRepo $
mapM (toReferenceSymbolIdl scsrepo srcFile offsets lang) xrefs

let refs1 = refsPlain ++ refsIdl

defs1 <- withRepo fileRepo $
mapM (toDefinitionSymbol scsrepo srcFile offsets) defns

xref_digests <- withRepo fileRepo $ do
let fileMap = xrefFileMap refs1
let fileMap = xrefFileMap refsPlain
results <- fetchFileDigests (Map.size fileMap) (Map.keys fileMap)
toDigestMap fileMap results

Expand Down Expand Up @@ -1280,19 +1307,21 @@ data XRefData = XRefData
, xrefFile :: {-# UNPACK #-}!(Glean.IdOf Src.File)
}

-- | Convert an Idl/Plain xref to a normal format
-- (includes attribute, source/target spans, symbol id)
toReferenceSymbolGen
:: RepoName
-> Src.File
-> Maybe Range.LineOffsets
-> Code.RangeSpan
-> Src.File
-> Code.Entity
-> Code.RangeSpan
-> LocationRange
-> Maybe Src.FileLocation
-> Maybe Code.Language
-> Maybe Language
-> Glean.RepoHaxl u w XRefData
toReferenceSymbolGen repoName file srcOffsets
rangeSpanSrc xrefFile xrefEntity xrefRangeSpan mDestination mLang = do
toReferenceSymbolGen repoName file srcOffsets rangeSpanSrc xrefFile xrefEntity
xrefRange mDestination mLang = do
path <- GleanPath <$> Glean.keyOf file
sym <- toSymbolId (fromGleanPath repoName path) xrefEntity
attributes <- getStaticAttributes xrefEntity repoName sym mLang
Expand All @@ -1303,40 +1332,43 @@ toReferenceSymbolGen repoName file srcOffsets
t <- rangeSpanToLocationRange repoName fileLocation_file rangeSpan
return (t, Glean.getId fileLocation_file)
_ -> do
t <- rangeSpanToLocationRange repoName xrefFile xrefRangeSpan
return (t, Glean.getId xrefFile)
return (xrefRange, Glean.getId xrefFile)
-- resolved the local span to a location
let range = rangeSpanToRange srcOffsets rangeSpanSrc
xrefSymbol = ReferenceRangeSymbolX sym range target attributes
return $ XRefData xrefEntity xrefSymbol xrefFile

-- | Convert a generic XRef ("plain" or idl) defined from
-- Codemarkup types into a common type which can be
-- returned a Glasss
toReferenceSymbol
-- | Convert plain entity to normal format
-- adapter to toReferenceSymbolGen
toReferenceSymbolPlain
:: RepoName
-> Src.File
-> Maybe Range.LineOffsets
-> GenXRef
-> Glean.RepoHaxl u w (Maybe XRefData)
toReferenceSymbol repoName file srcOffsets xref = case xref of
PlainXRef (Code.XRefLocation{..}, xrefEntity) ->
-> XRef
-> Glean.RepoHaxl u w XRefData
toReferenceSymbolPlain
repoName file srcOffsets (Code.XRefLocation{..}, xrefEntity) = do
-- reference target is a Declaration and an Entity
let Code.Location{..} = xRefLocation_target in
Just <$> toReferenceSymbolGen repoName file srcOffsets xRefLocation_source
location_file xrefEntity location_location location_destination Nothing
IdlXRef (rangeSpanSrc, Code.IdlEntity lang idlFile (Just xrefEntity)
mRange) ->
-- if idl range isn't provided by Codemarkup, we use a
-- default location. TODO have glass resolve it
let one = Glean.Nat 1
firstCharSpan = Src.Range file one one one one
destRangeSpan = Code.RangeSpan_range $ fromMaybe firstCharSpan mRange in
Just <$> toReferenceSymbolGen repoName file srcOffsets rangeSpanSrc idlFile
xrefEntity destRangeSpan Nothing (Just lang)
-- we filtered out idl without entity for now.
-- TODO return a location and unknown symbol id
IdlXRef (_, Code.IdlEntity _ _ Nothing _) -> return Nothing
let Code.Location{..} = xRefLocation_target
xrefRange <- rangeSpanToLocationRange repoName location_file
location_location
toReferenceSymbolGen repoName file srcOffsets xRefLocation_source
location_file xrefEntity xrefRange location_destination Nothing

-- | Convert idl entity to normal format
-- adapter to toReferenceSymbolGen
toReferenceSymbolIdl
:: RepoName
-> Src.File
-> Maybe Range.LineOffsets
-> Language
-> ((Code.Entity, Code.RangeSpan), (Src.File, LocationRange))
-> Glean.RepoHaxl u w XRefData
toReferenceSymbolIdl
repoName file srcOffsets lang
((xrefEntity, rangeSpanSrc), (idlFile, xrefRange)) = do
toReferenceSymbolGen repoName file srcOffsets rangeSpanSrc idlFile
xrefEntity xrefRange Nothing (Just lang)

-- | Building a resolved definition symbol is just taking a direct xref to it,
-- and converting the bytespan, adding any static attributes
Expand Down Expand Up @@ -1375,7 +1407,7 @@ getStaticAttributes
:: Code.Entity
-> RepoName
-> SymbolId
-> Maybe Code.Language -- Idl language
-> Maybe Language -- Idl language
-> Glean.RepoHaxl u w AttributeList
getStaticAttributes e repo sym mLang = do
mLocalName <- toSymbolLocalName e
Expand All @@ -1402,10 +1434,10 @@ getStaticAttributes e repo sym mLang = do
Attribute_aInteger (fromIntegral $ fromThriftEnum lang))
asDefinitionType kind = ("symbolDefinitionType",
Attribute_aInteger (fromIntegral $ fromThriftEnum kind))
asLangDeprecated Code.Language_Thrift = Just ("symbolIdl",
asLangDeprecated Language_Thrift = Just ("symbolIdl",
Attribute_aString "thrift")
asLangDeprecated _ = Nothing
asLang Code.Language_Thrift = Just ("crossLanguage",
asLang Language_Thrift = Just ("crossLanguage",
Attribute_aString "thrift")
asLang _ = Nothing

Expand Down
11 changes: 11 additions & 0 deletions glean/glass/Glean/Glass/Repos.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ module Glean.Glass.Repos
, selectGleanDBs
, getRepoHash
, getRepoHashForLocation
, getLatestRepo
) where

import Control.Concurrent.Stream
Expand Down Expand Up @@ -534,3 +535,13 @@ getRepoHashForLocation LocationRange{..} scmRevs repo =
fromMaybe (getRepoHash repo) $ do
scmRepoToHash <- HashMap.lookup repo scmRevs
scmRevision <$> HashMap.lookup locationRange_repository scmRepoToHash

getLatestRepo
:: RepoMapping -> GleanDBInfo -> RepoName -> Language -> Maybe Glean.Repo
getLatestRepo repoMapping dbInfo repoName lang =
let GleanDBInfo{
latestRepos = Glean.LatestRepos { latestRepos = repos }
} = dbInfo in
case fromSCSRepo repoMapping repoName (Just lang) of
[] -> Nothing
GleanDBName repo : _ -> Map.lookup repo repos
72 changes: 69 additions & 3 deletions glean/glass/Glean/Glass/XRefs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,21 +12,30 @@ module Glean.Glass.XRefs
(
GenXRef(..),
XRef,
resolveEntitiesRange,
fetchCxxIdlXRefs
) where

import Data.Map.Strict ( Map )
import qualified Data.Map as Map
import Data.Bifunctor ( bimap )
import Data.Bifunctor ( bimap, Bifunctor (first) )
import Data.List ( foldl' )
import Data.List.NonEmpty

import qualified Glean
import Glean.Angle
import Glean.Util.ToAngle ( ToAngleFull(toAngleFull), Normalize(normalize) )
import Glean.Haxl.Repos as Glean
import Glean.Glass.Range ( rangeSpanToLocationRange )
import Glean.Glass.Utils
import Glean.Glass.Types ( LocationRange, RepoName(..) )
import qualified Glean.Schema.CodemarkupTypes.Types as Code
import qualified Glean.Schema.Code.Types as Code
import qualified Glean.Schema.Cxx1.Types as Cxx
import qualified Glean.Schema.CodemarkupCxx.Types as Code
import Glean.Glass.Utils
import qualified Glean.Schema.Codemarkup.Types as Code
import qualified Glean.Schema.Src.Types as Src
import Data.Maybe (catMaybes)

type XRef = (Code.XRefLocation, Code.Entity)
type IdlXRef = (Code.RangeSpan, Code.IdlEntity)
Expand All @@ -35,7 +44,6 @@ data GenXRef = PlainXRef XRef | IdlXRef IdlXRef
type EntityIdlMap = Map Code.Entity Code.IdlEntity

-- | extract idl xrefs from the regular ones
-- simply ignore idl xrefs which don't have an entity.
extractIdlXRefs
:: EntityIdlMap -> [(Code.XRefLocation, Code.Entity)] -> [GenXRef]
extractIdlXRefs entityIdlMap xRefs =
Expand Down Expand Up @@ -80,3 +88,61 @@ fetchCxxIdlXRefs mlimit xrefId =
do
(map, trunc) <- entityIdlCxxMap mlimit xrefId
return $ Data.Bifunctor.bimap (extractIdlXRefs map)(trunc ||)

fetchEntityLocation
:: [Code.Entity]
-> Glean.RepoHaxl u w [(Code.Entity, Code.Location)]
fetchEntityLocation ents = do
-- careful to not rely on fact ids in this query
let angleEntities = toAngleFull <$> ents
case angleEntities of
[] -> return []
hd : tl ->
fst <$> searchRecursiveWithLimit Nothing (declarationLocation (hd :| tl))
where
declarationLocation
:: NonEmpty (Angle Code.Entity)
-> Angle (Code.Entity, Code.Location)
declarationLocation (hd :| tl) =
let or_ents = foldl' (.|) hd tl in
vars $ \ent loc ->
tuple (ent, loc) `where_` [
or_ents .= ent,
wild .= predicate @Code.EntityLocation (
rec $
field @"entity" ent $
field @"location" loc
end)
]

-- | Annotate a list of items keyed by an entity, with the
-- LocationRange/File for that entity. This can't be done
-- in Codemarkup for xlang entities as the entity facts
-- and ent EntityLocation facts may live in different dbs.
resolveEntitiesRange
:: RepoName
-> (a -> Code.Entity)
-> [a]
-> Glean.RepoHaxl u w [(a, (Src.File, LocationRange))]
resolveEntitiesRange repo key xrefs = do
let entsToResolve = key <$> xrefs
entsRange <- entityLocRange repo entsToResolve
-- normalize fact ids so we can compare entities from
-- different dbs
let normalizedEnts = first normalize <$> entsRange
entityLocRangeMap = Map.fromList normalizedEnts
return $ catMaybes $ annotate entityLocRangeMap <$> xrefs
where
annotate map item =
let ent = key item in
(item,) <$> Map.lookup (normalize ent) map

-- | fetch idl entity location and compute location range
entityLocRange reponame ents =
fetchEntityLocation ents >>= mapM convertSpan
where
convertSpan (ent, loc) = do
let file = Code.location_file loc
range <- rangeSpanToLocationRange reponame file
(Code.location_location loc)
return (ent, (file, range))
Loading

0 comments on commit 2654ffe

Please sign in to comment.