Skip to content

Commit 77681e9

Browse files
Catherine Gasnierfacebook-github-bot
authored andcommitted
xlang navigation
Summary: This diff implements cross-language navigation in glass from swift to objc. Note that schema changes have been split out in previous diff. The way this works is roughly: * do a glean query to get all the "dangling" references from the swift file. By "dangling", we mean references to things that don't have a definition in the DB. By "reference", we really mean a USR, which is a unique symbol identifier use in the swift/objc/cxx compiler toolchains. * then use those collected USR to query the cxx DB for definitions. * Caveat: from the Swift DB, we get plain USR, but in the cxx DB, we only have USR hashes. So we need to hash the USRs before querying the cxx DB. This diff ensures that the hashing function is the same between the cxx indexer and glass, by FFI-ing into the cxx hashing function. There is a bit of refactor done to that purpose. This way of doing xlang references, although very simple since there are common symbol identifiers across the two DBs, is unfortunately not well adapted to how glass / codemarkup does xlang references for other languages, so we had to adapt the codemarkup schema a bit, see GenericEntity in codemarkup.angle, which uses a new code.SymbolId type. Suggested review order: * angle code: * codemarkup.angle, code.angle, code.scip.angle, code.cxx.angle * "dangling" references on swift side: scip.angle, codemarkup.scip.angle * USR resolution on cxx side: codemarkup.cxx.angle, codemarkup.angle * haskell code: * Document.hs * Xrefs.hs * other stuff Reviewed By: phlalx Differential Revision: D74811891 fbshipit-source-id: 5956c0364ce2dcbe5eb654e3010e56856db15943
1 parent 9eb77bc commit 77681e9

19 files changed

+6596
-126
lines changed

glean.cabal.in

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1202,6 +1202,8 @@ library glass-lib
12021202
visibility: public
12031203
default-extensions: CPP
12041204
hs-source-dirs: glean/glass
1205+
build-depends:
1206+
glean-hash:glean-hash,
12051207
exposed-modules:
12061208
Glean.Glass.Annotations
12071209
Glean.Glass.Attributes

glean/glass/Glean/Glass/Handler/Documents.hs

Lines changed: 75 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -66,23 +66,32 @@ import Glean.Glass.RepoMapping (
6666
)
6767
import qualified Glean.Glass.Env as Glass
6868
import Glean.Glass.XRefs
69-
( GenXRef(..), XRef, resolveEntitiesRange )
69+
( GenXRef(..), XRef, resolveEntitiesRange, XlangXRef )
7070
import Glean.Glass.SymbolMap ( toSymbolIndex )
7171

7272
import Glean.Glass.SnapshotBackend
7373
( SnapshotBackend(getSnapshot),
7474
SnapshotStatus() )
7575
import qualified Glean.Glass.SnapshotBackend as Snapshot
76-
import Glean.Glass.Env (Env' (tracer, sourceControl, useSnapshotsForSymbolsList))
76+
import Glean.Glass.Env (
77+
Env' (tracer, sourceControl, useSnapshotsForSymbolsList))
7778
import Glean.Glass.SourceControl (SourceControl(..), NilSourceControl(..))
7879
import Glean.Glass.Tracing (traceSpan)
7980
import qualified Glean.Glass.Utils as Utils
8081
import Glean.Glass.Utils ( fst4 )
8182
import Logger.GleanGlass (GleanGlassLogger)
8283
import qualified Glean.Glass.Attributes.Frame as Attributes
84+
import qualified Glean.Schema.Scip.Types as Scip
85+
import Foreign.C (CString, peekCString, withCString)
86+
import Foreign.C.Types (CSize(..), CInt(..), CChar(..))
87+
import Foreign.Ptr (Ptr)
88+
import Foreign.Marshal.Alloc (allocaBytes)
89+
import Data.Either (partitionEithers, fromLeft)
90+
import Control.Monad.Extra (mapMaybeM)
8391

8492

85-
-- | Runner for methods that are keyed by a file path
93+
-- | Runner for methods that are keyed by a file path.
94+
-- Select the right Glean DBs and pass them to the function (via a GleanBackend)
8695
runRepoFile
8796
:: (LogResult t)
8897
=> Text
@@ -100,7 +109,7 @@ runRepoFile
100109
runRepoFile sym fn env@Glass.Env{..} req opts =
101110
withRepoFile sym env opts req repo file $ \gleanDBs dbInfo mlang ->
102111
fn dbInfo req opts
103-
GleanBackend{..}
112+
GleanBackend{gleanBackend, gleanDBs, tracer}
104113
snapshotBackend
105114
mlang
106115
where
@@ -224,7 +233,7 @@ fetchSymbolsAndAttributesGlean
224233
file mlimit be res1
225234

226235
let be = fromMaybe (gleanBackend, dbInfo) mOtherBackend
227-
res3 <- resolveXlangXrefs env path res2 repo be
236+
res3 <- resolveXlangXrefs env path res2 repo be mlang
228237

229238
let res4 = toDocumentSymbolResult res3
230239
let res5 = translateMirroredRepoListXResult req res4
@@ -282,7 +291,7 @@ chooseGleanOrSnapshot RequestOptions{..} revision glean esnapshot
282291
returnGlean
283292
where
284293
returnGlean = return $
285-
addStatus (either id (const Snapshot.Ignored) esnapshot) glean
294+
addStatus (fromLeft Snapshot.Ignored esnapshot) glean
286295

287296
doMatching
288297
| Just True <- resultContentMatch glean = returnGlean
@@ -344,9 +353,8 @@ fallbackForNewFiles Glass.Env{..} RequestOptions{..} snapshotbe repo file res
344353
gen <- getGeneration sourceControl repo revision
345354
bestSnapshot <- getSnapshot tracer snapshotbe repo file Nothing gen
346355
case bestSnapshot of
347-
Right (_, fetch) -> do
348-
snap <- fetch
349-
return $ maybe res (`returnSnapshot` Snapshot.Latest) snap
356+
Right (_, fetch) ->
357+
maybe res (`returnSnapshot` Snapshot.Latest) <$> fetch
350358
Left _ ->
351359
return res
352360
| otherwise =
@@ -524,9 +532,7 @@ fetchDocumentSymbols [email protected]{..} (FileReference scsrepo path)
524532
let digest = toDigest <$> fileDigest
525533

526534
-- only handle XlangEntities with known entity
527-
let unresolvedXrefsXlang = [ (ent, rangeSpan) |
528-
XlangXRef (rangeSpan, Code.IdlEntity {
529-
idlEntity_entity = Just ent }) <- xrefs ]
535+
let unresolvedXrefsXlang = [ ref | XlangXRef ref <- xrefs ]
530536

531537
let (refs2, defs2, _) = Attributes.augmentSymbols
532538
Attributes.SymbolKindAttr
@@ -583,33 +589,78 @@ resolveXlangXrefs
583589
-> DocumentSymbols
584590
-> RepoName
585591
-> (b, GleanDBInfo)
592+
-> Maybe Language
586593
-> IO DocumentSymbols
587594
resolveXlangXrefs
588-
env@Glass.Env{tracer, sourceControl, repoMapping}
589-
path
590-
docSyms@DocumentSymbols{..}
591-
scsrepo
592-
(gleanBackend, dbInfo) = do
595+
env@Glass.Env{tracer, sourceControl, repoMapping}
596+
path
597+
docSyms@DocumentSymbols{..}
598+
scsrepo
599+
(gleanBackend, dbInfo)
600+
sourceLang = do
593601
case (unresolvedXrefsXlang, srcFile) of
594-
((ent, _) : _, Just srcFile) -> do
602+
((_, xref) : _, Just srcFile) -> do
595603
-- we assume all xlang xrefs belong to the same db
596604
-- we pick the xlang dbs based on target lang and
597605
-- repo. Corner case: the document is in a mirror repo,
598606
-- use to origin repo to determine xlang db
599-
let lang = entityLanguage ent
607+
let targetLang = targetLanguage xref sourceLang
600608
targetRepo = case repoPathToMirror scsrepo path of
601609
Just (Mirror _mirror _prefix origin) -> origin
602610
Nothing -> scsrepo
603611
gleanDBs <- getGleanRepos tracer sourceControl repoMapping dbInfo
604-
targetRepo (Just lang) Nothing ChooseLatest Nothing
612+
targetRepo (Just targetLang) Nothing ChooseLatest Nothing
605613
let gleanBe = GleanBackend {gleanDBs, tracer, gleanBackend}
614+
(ents, symbols) <-
615+
partitionEithers <$> mapMaybeM (mangle targetLang) unresolvedXrefsXlang
606616
xlangRefs <- backendRunHaxl gleanBe env $ do
607-
xrefsXlang <- withRepo (snd (NonEmpty.head gleanDBs)) $ do
608-
xrefs <- resolveEntitiesRange targetRepo fst unresolvedXrefsXlang
609-
mapM (toReferenceSymbolXlang targetRepo srcFile offsets lang) xrefs
617+
xrefsXlang <- join <$>
618+
mapM (\gleanDB -> withRepo (snd gleanDB) $ do
619+
xrefs <- resolveEntitiesRange targetRepo symbols ents
620+
mapM
621+
(toReferenceSymbolXlang targetRepo srcFile offsets targetLang)
622+
xrefs)
623+
(NonEmpty.toList gleanDBs)
610624
return $ xRefDataToRefEntitySymbol <$> xrefsXlang
611625
return $ docSyms { refs = refs ++ xlangRefs, unresolvedXrefsXlang = [] }
612626
_ -> return docSyms
627+
where
628+
targetLanguage xref mlang =
629+
case xref of
630+
Left (Code.IdlEntity _ _ ent _) ->
631+
maybe (Language__UNKNOWN 0) entityLanguage ent
632+
Right _ ->
633+
case mlang of
634+
Just Language_Swift -> Language_Cpp
635+
_ -> Language__UNKNOWN 0
636+
637+
mangle :: Language -> XlangXRef
638+
-> IO (Maybe (Either
639+
(Code.Entity, Code.RangeSpan) (Code.SymbolId, Code.RangeSpan)))
640+
mangle targetLang (range, ref) = case ref of
641+
Left (Code.IdlEntity _ _ mEnt _) ->
642+
pure $ Left . (,range) <$> mEnt
643+
Right symbol -> do
644+
Just . Right . (,range) <$> translateSymbol sourceLang targetLang symbol
645+
646+
translateSymbol ::
647+
Maybe Language -> Language -> Code.SymbolId -> IO Code.SymbolId
648+
translateSymbol
649+
(Just Language_Swift)
650+
Language_Cpp
651+
(Code.SymbolId_scip (Scip.Symbol _ (Just usr))) =
652+
Code.SymbolId_cxx . Text.pack <$>
653+
withCString (Text.unpack usr) (\usr ->
654+
let size = 32 in
655+
allocaBytes size $ \hash -> do
656+
ret <- hash_ffi usr hash size
657+
if ret == 0
658+
then peekCString hash
659+
else error "hash_ffi buffer too small")
660+
translateSymbol _ _ symId = return symId
661+
662+
foreign import ccall unsafe
663+
hash_ffi :: CString -> Ptr CChar -> CSize -> IO CInt
613664

614665
-- | Wrapper for tracking symbol/entity pairs through processing
615666
data DocumentSymbols = DocumentSymbols
@@ -620,7 +671,7 @@ data DocumentSymbols = DocumentSymbols
620671
, truncated :: !Bool
621672
, digest :: Maybe FileDigest
622673
, xref_digests :: Map.Map Text FileDigestMap
623-
, unresolvedXrefsXlang :: [(Code.Entity, Code.RangeSpan)]
674+
, unresolvedXrefsXlang :: [XlangXRef]
624675
, srcFile :: Maybe Src.File
625676
, offsets :: Maybe Range.LineOffsets
626677
, attributes :: Maybe AttributeList

glean/glass/Glean/Glass/Query.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,8 @@ module Glean.Glass.Query
3838
-- * Query helpers
3939
, entityLocation
4040

41+
, symbolToEntity
42+
4143
) where
4244

4345
import Data.Text (Text)
@@ -247,3 +249,14 @@ entityLocation entity file rangespan name =
247249
field @"location" rangespan
248250
end)
249251
end)
252+
253+
symbolToEntity :: Angle Code.SymbolId -> Angle (Code.SymbolId, Code.Entity)
254+
symbolToEntity symbol =
255+
vars $ \(entity :: Angle Code.Entity) ->
256+
tuple (symbol, entity) `where_` [
257+
wild .= predicate @Code.SymbolToEntity (
258+
rec $
259+
field @"symbol" symbol $
260+
field @"entity" entity
261+
end)
262+
]

0 commit comments

Comments
 (0)