Skip to content

Commit

Permalink
Add an option to request only accurate symbols
Browse files Browse the repository at this point in the history
Summary:
The new "matching_revision" request option does two things:

* it includes snapshots when selecting the closest revision
* it discards responses that are not UPNU correct

Initially will be used only by Phabricator for:

1. Landed revisions, for which code navigation often breaks when the Diff is no longer the latest version of the file.
2. Left hand sides, where code navigation can be available as soon as a version is submitted (instead of waiting for diff-time indexing to finish)

For 2, we want to make sure that we don't record an inaccurate result in the ThriftCache as that would override the diff-time indexing exact snapshot for a period of time.

The cost of computing the UPNU property is lower than the Manifold retrieval cost, so I have made them happen in parallel:

{F1508813775}

Reviewed By: simonmar

Differential Revision: D57113978

fbshipit-source-id: 625cdd56c3f83162f1a02bf8515e5153aa3edba7
  • Loading branch information
Pepe Iborra authored and facebook-github-bot committed May 10, 2024
1 parent 9cce65e commit 9c9f0d3
Show file tree
Hide file tree
Showing 8 changed files with 239 additions and 87 deletions.
147 changes: 111 additions & 36 deletions glean/glass/Glean/Glass/Handler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ module Glean.Glass.Handler

) where

import Control.Concurrent.Async (async, wait)
import Control.Monad
import Control.Exception ( throwIO, SomeException )
import Control.Monad.Catch ( throwM, try )
Expand All @@ -54,7 +55,7 @@ import Data.List as List ( sortOn )
import Data.List.Extra ( nubOrd, nubOrdOn, groupOn, groupSortOn )
import Data.List.NonEmpty (NonEmpty(..), nonEmpty)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Maybe ( mapMaybe, catMaybes, fromMaybe, listToMaybe )
import Data.Maybe ( mapMaybe, catMaybes, fromMaybe, listToMaybe, maybeToList )
import Data.Ord ( comparing )
import Data.Text ( Text )
import Data.Tuple.Extra ( fst3 )
Expand Down Expand Up @@ -135,7 +136,9 @@ import Glean.Glass.SnapshotBackend
SnapshotStatus() )
import qualified Glean.Glass.SnapshotBackend as Snapshot
import Glean.Glass.SymbolKind (findSymbolKind)
import Glean.Glass.Env (Env' (tracer))
import Glean.Glass.Env (Env' (tracer, sourceControl))
import Glean.Glass.SourceControl
(SourceControl (checkMatchingRevisions, getGeneration))
import Glean.Glass.Tracing (GlassTracer, traceSpan)

-- | Runner for methods that are keyed by a file path
Expand Down Expand Up @@ -175,7 +178,7 @@ documentSymbolListX [email protected]{tracer} r opts =
fst3 <$>
runRepoFile
"documentSymbolListX"
(fetchSymbolsAndAttributes tracer)
(fetchSymbolsAndAttributes tracer (sourceControl env))
env r opts

-- | Same as documentSymbolList() but construct a line-indexed map for easy
Expand All @@ -185,11 +188,11 @@ documentSymbolIndex
-> DocumentSymbolsRequest
-> RequestOptions
-> IO DocumentSymbolIndex
documentSymbolIndex env@Glass.Env{tracer} r opts =
documentSymbolIndex env@Glass.Env{sourceControl, tracer} r opts =
fst3 <$>
runRepoFile
"documentSymbolIndex"
(fetchDocumentSymbolIndex tracer)
(fetchDocumentSymbolIndex tracer sourceControl)
env r opts

-- | Symbol-based find-refernces.
Expand Down Expand Up @@ -920,6 +923,7 @@ fetchSymbolsAndAttributesGlean tracer repoMapping dbInfo req opts be mlang = do
fetchSymbolsAndAttributes
:: (Glean.Backend b, SnapshotBackend snapshotBackend)
=> GlassTracer
-> Some SourceControl
-> RepoMapping
-> GleanDBInfo
-> DocumentSymbolsRequest
Expand All @@ -929,55 +933,123 @@ fetchSymbolsAndAttributes
-> Maybe Language
-> IO ((DocumentSymbolListXResult, SnapshotStatus, QueryEachRepoLog)
, Maybe ErrorLogger)
fetchSymbolsAndAttributes tracer repoMapping dbInfo req opts be
snapshotbe mlang = do
fetchSymbolsAndAttributes tracer scs repoMapping dbInfo req
opts@RequestOptions{..} be snapshotbe mlang = do
res <- case mrevision of
Nothing ->
addStatus Snapshot.Unrequested <$> getFromGlean
Just revision -> do
(esnapshot, glean) <- Async.concurrently
(traceSpan tracer "getSnapshot" $
getSnapshot tracer snapshotbe repo file (Just revision))
(traceSpan tracer "getFromGlean"
getFromGlean)
return $ case esnapshot of
Right queryResult | not (isRevisionHit revision glean) ->
((queryResult, Snapshot.ExactMatch, QueryEachRepoUnrequested),
Nothing)
_otherwise ->
(traceSpan tracer "getSnapshot" $ getFromSnapshot revision)
(traceSpan tracer "getFromGlean" getFromGlean)

snapshotResult <- case esnapshot of
Right (_, fetch) -> do
a <- async fetch
return $ do
res <- wait a
return $ maybe (Left Snapshot.InternalError) Right res
Left e -> return $ pure (Left e)

let
snapshotRevision = either (const Nothing) (Just . fst) esnapshot

returnGlean = return $
addStatus (either id (const Snapshot.Ignored) esnapshot) glean
_ -> addStatus Snapshot.Unrequested <$> getFromGlean

snapshotOrGlean = returnSnapshotOr snapshotResult (`addStatus` glean)

snapshotOrFailWith error = returnSnapshotOr snapshotResult $ \s ->
((toDocumentSymbolResult(emptyDocumentSymbols revision)
, s
, FoundNone)
, return $ logError error)

doMatching = do
let candidates =
getGleanResultRevision glean : maybeToList snapshotRevision
matchingResults <- traceSpan tracer "checkMatchingRevisions" $
checkMatchingRevisions
scs
(documentSymbolsRequest_repository req)
(documentSymbolsRequest_filepath req)
revision
candidates
case matchingResults of
gleanMatch : snapshotMatch
| gleanMatch
-> return $ addStatus Snapshot.Ignored glean
| [True] <- snapshotMatch
-> snapshotOrFailWith
(GlassExceptionReason_matchingRevisionNotAvailable $
unRevision revision)
Snapshot.CompatibleMatch
_ ->
return
((toDocumentSymbolResult(emptyDocumentSymbols revision)
, Snapshot.NotFound
, FoundNone)
, Just $ logError $
GlassExceptionReason_matchingRevisionNotAvailable $
unRevision revision
)

if | isRevisionHit revision glean
-> returnGlean
| snapshotRevision == Just revision
-> snapshotOrGlean Snapshot.ExactMatch
| requestOptions_matching_revision &&
not requestOptions_exact_revision
-> doMatching
| otherwise
-> returnGlean

-- Fall back to the best snapshot available for new files (not yet in repo)
case res of
((_,_,_), Just ErrorLogger {errorTy})
case (res, mrevision) of
(((_,_,_), Just ErrorLogger {errorTy}), Just revision)
-- assume it's a new file if no src.File fact
| all isNoSrcFileFact errorTy
&& not (requestOptions_exact_revision opts)
&& not requestOptions_exact_revision
-> do
bestSnapshot <- getSnapshot tracer snapshotbe repo file Nothing
gen <- getGeneration scs repo revision
bestSnapshot <-
getSnapshot tracer snapshotbe repo file Nothing gen
case bestSnapshot of
Right result ->
return
(( result
, Snapshot.Latest
, QueryEachRepoUnrequested)
, Nothing)
Right (_, fetchSnapshot) -> returnSnapshotOr
(maybe (Left ()) Right <$> fetchSnapshot)
(const res) Snapshot.Latest
Left _ ->
return res
_ ->
return res
where
addStatus st ((res, gleanLog), mlogger) = ((res, st, gleanLog), mlogger)
getFromSnapshot revision
| requestOptions_matching_revision && not requestOptions_exact_revision
= do
gen <- getGeneration scs repo revision
getSnapshot tracer snapshotbe repo file (Just revision) gen
| otherwise =
getSnapshot tracer snapshotbe repo file (Just revision) Nothing
getFromGlean =
fetchSymbolsAndAttributesGlean tracer repoMapping dbInfo req opts be mlang
file = documentSymbolsRequest_filepath req
repo = documentSymbolsRequest_repository req
mrevision = requestOptions_revision opts
mrevision = requestOptions_revision
-- Note: not selectRevision, this is used to control snapshot use
-- not DB selection.
isNoSrcFileFact GlassExceptionReason_noSrcFileFact{} = True
isNoSrcFileFact _ = False

isRevisionHit rev ((res, _), _) =
documentSymbolListXResult_revision res == rev
getGleanResultRevision ((x, _), _) = documentSymbolListXResult_revision x
isRevisionHit rev = (== rev) . getGleanResultRevision

returnSnapshotOr tryFetch fallback match = do
result <- tryFetch
return $ case result of
Left e -> fallback e
Right queryResult ->
((queryResult, match, QueryEachRepoUnrequested), Nothing)

-- Find all references and definitions in a file that might be in a set of repos
fetchDocumentSymbols
Expand Down Expand Up @@ -1020,10 +1092,8 @@ fetchDocumentSymbols (FileReference scsrepo path) mlimit

case efile of
Left err -> do
let emptyResponse = DocumentSymbols [] []
(revision b) False Nothing mempty
logs = logError err <> logError (gleanDBs b)
return (emptyResponse, FoundNone, Just logs)
let logs = logError err <> logError (gleanDBs b)
return (emptyDocumentSymbols (revision b), FoundNone, Just logs)

where
-- Use first db's revision
Expand Down Expand Up @@ -1107,6 +1177,10 @@ data DocumentSymbols = DocumentSymbols
, xref_digests :: Map.Map Text FileDigestMap
}

emptyDocumentSymbols :: Revision -> DocumentSymbols
emptyDocumentSymbols revision =
DocumentSymbols [] [] revision False Nothing mempty

-- | Drop any remnant entities after we are done with them
toDocumentSymbolResult :: DocumentSymbols -> DocumentSymbolListXResult
toDocumentSymbolResult DocumentSymbols{..} = DocumentSymbolListXResult{..}
Expand Down Expand Up @@ -1149,6 +1223,7 @@ documentSymbolsForLanguage mlimit _ includeRefs _ fileId = do
fetchDocumentSymbolIndex
:: (Glean.Backend b, SnapshotBackend snapshotBackend)
=> GlassTracer
-> Some SourceControl
-> RepoMapping
-> GleanDBInfo
-> DocumentSymbolsRequest
Expand All @@ -1158,11 +1233,11 @@ fetchDocumentSymbolIndex
-> Maybe Language
-> IO ((DocumentSymbolIndex, SnapshotStatus, QueryEachRepoLog),
Maybe ErrorLogger)
fetchDocumentSymbolIndex tracer repoMapping latest req opts be
fetchDocumentSymbolIndex tracer scs repoMapping latest req opts be
snapshotbe mlang = do
((DocumentSymbolListXResult{..}, status, gleanDataLog), merr1) <-
fetchSymbolsAndAttributes
tracer repoMapping latest req opts be snapshotbe mlang
tracer scs repoMapping latest req opts be snapshotbe mlang

-- refs defs revision truncated digest = result
let lineIndex = toSymbolIndex documentSymbolListXResult_references
Expand Down
5 changes: 5 additions & 0 deletions glean/glass/Glean/Glass/Logging.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,6 +65,7 @@ instance LogRequest RequestOptions where
maybe mempty (Logger.setRevision . unRevision) requestOptions_revision <>
maybe mempty (Logger.setLimit . fromIntegral) requestOptions_limit <>
Logger.setExactRevision requestOptions_exact_revision <>
Logger.setMatchingRevision requestOptions_matching_revision <>
logRequest requestOptions_feature_flags

instance LogRequest FeatureFlags where
Expand Down Expand Up @@ -257,6 +258,7 @@ errorText e = case e of
GlassExceptionReason_entityNotSupported t -> t
GlassExceptionReason_attributesError t -> t
GlassExceptionReason_exactRevisionNotAvailable t -> t
GlassExceptionReason_matchingRevisionNotAvailable t -> t
GlassExceptionReason_EMPTY -> ""

errorsText :: NonEmpty GlassExceptionReason -> Text
Expand Down Expand Up @@ -295,6 +297,8 @@ instance LogResult ErrorLogger where
GlassExceptionReason_notIndexedFile{} -> "NotIndexedFile"
GlassExceptionReason_exactRevisionNotAvailable{} ->
"ExactRevisionNotAvaiable"
GlassExceptionReason_matchingRevisionNotAvailable{} ->
"MatchingRevisionNotAvailable"
GlassExceptionReason_EMPTY{} -> "EMPTY"
)
(e:es) ->
Expand Down Expand Up @@ -366,5 +370,6 @@ logSnapshotStatus st = case st of
Timeout -> Logger.setSnapshot "Timeout"
NotFound -> Logger.setSnapshot "Not found"
ExactMatch -> Logger.setSnapshot "Exact"
CompatibleMatch -> Logger.setSnapshot "Matching"
Ignored -> Logger.setSnapshot "Ignored"
Latest -> Logger.setSnapshot "Latest"
11 changes: 6 additions & 5 deletions glean/glass/Glean/Glass/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ import Glean.Glass.GlassService.Service ( GlassServiceCommand(..) )

import Glean.Glass.Types
( GlassException (GlassException, glassException_reasons),
GlassExceptionReason (GlassExceptionReason_exactRevisionNotAvailable))
GlassExceptionReason (..))
import Glean.Glass.Env (Env'(tracer), Env)
import Glean.Glass.Tracer ( isTracingEnabled )
import Glean.Glass.Tracing
Expand Down Expand Up @@ -140,11 +140,12 @@ assignHeaders _ (Left e) | isRevisionNotAvailableException e =
where
isRevisionNotAvailableException e = case fromException e of
Just GlassException{glassException_reasons} ->
all isExactRevisionNotAvailable glassException_reasons
all isRevisionNotAvailable glassException_reasons
_ -> False
isRevisionNotAvailable e = case e of
GlassExceptionReason_exactRevisionNotAvailable{} -> True
GlassExceptionReason_matchingRevisionNotAvailable{} -> True
_ -> False
isExactRevisionNotAvailable GlassExceptionReason_exactRevisionNotAvailable{}
= True
isExactRevisionNotAvailable _ = False
assignHeaders _ _ = []

-- | Perform an operation with the latest RepoMapping
Expand Down
7 changes: 5 additions & 2 deletions glean/glass/Glean/Glass/SnapshotBackend.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Options.Applicative

import qualified Glean.Glass.Types as Types
import Glean.Util.Some (Some(..))
import Glean.Glass.SourceControl (ScmGeneration)
import Glean.Glass.Types (
Revision,
Path,
Expand All @@ -39,7 +40,8 @@ class SnapshotBackend backend where
-> RepoName
-> Path
-> Maybe Revision
-> IO (Either SnapshotStatus Types.DocumentSymbolListXResult)
-> Maybe ScmGeneration
-> IO (Either SnapshotStatus (Revision, IO (Maybe Types.DocumentSymbolListXResult)))

instance SnapshotBackend (Some SnapshotBackend) where
getSnapshot t (Some backend) = getSnapshot t backend
Expand All @@ -51,6 +53,7 @@ data SnapshotStatus
| Timeout
| NotFound
| ExactMatch
| CompatibleMatch
| Ignored
| Latest
deriving Show
Expand All @@ -66,4 +69,4 @@ snapshotBackendParser = Some NilSnapshotBackend <$ (option auto (mconcat
data NilSnapshotBackend = NilSnapshotBackend

instance SnapshotBackend NilSnapshotBackend where
getSnapshot _ _ _ _ _ = return $ Left Unrequested
getSnapshot _ _ _ _ _ _ = return $ Left Unrequested
8 changes: 7 additions & 1 deletion glean/glass/Glean/Glass/SourceControl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,16 +20,22 @@ import Glean.Util.Some

-- | Source control generation, used for ordering revisions
newtype ScmGeneration = ScmGeneration Int64
deriving (Hashable, Show)
deriving (Eq, Hashable, Ord, Show)

-- | Interface to source control operations
class SourceControl scm where
getGeneration :: scm -> RepoName -> Revision -> IO (Maybe ScmGeneration)
-- | @checkMatchingRevisions repo file rev0 revs@ answers the question
-- "Which of revs satisfy that the contents of filepath match rev0?"
checkMatchingRevisions
:: scm -> RepoName -> Path -> Revision -> [Revision] -> IO [Bool]

data NilSourceControl = NilSourceControl

instance SourceControl NilSourceControl where
getGeneration _ _ _ = return Nothing
checkMatchingRevisions _ _ _ _ revs = return $ map (const False) revs

instance SourceControl (Some SourceControl) where
getGeneration (Some scm) = getGeneration scm
checkMatchingRevisions (Some scm) = checkMatchingRevisions scm
6 changes: 4 additions & 2 deletions glean/glass/Glean/Glass/Tracing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,8 @@ glassTraceEvent (GlassTraceWithId tid (TraceCommand cmd)) = case cmd of
"filepath" .= documentSymbolsRequest_filepath <>
"repository" .= documentSymbolsRequest_repository <>
"revision" .= requestOptions_revision opts <>
"exact" .= requestOptions_exact_revision opts
"exact" .= requestOptions_exact_revision opts <>
"matching" .= requestOptions_matching_revision opts
)
Glass.DocumentSymbolIndex DocumentSymbolsRequest{..} opts ->
("DocumentSymbolIndex"
Expand All @@ -66,7 +67,8 @@ glassTraceEvent (GlassTraceWithId tid (TraceCommand cmd)) = case cmd of
"filepath" .= documentSymbolsRequest_filepath <>
"repository" .= documentSymbolsRequest_repository <>
"revision" .= requestOptions_revision opts <>
"exact" .= requestOptions_exact_revision opts
"exact" .= requestOptions_exact_revision opts <>
"matching" .= requestOptions_matching_revision opts
)
Glass.FindReferences r opts ->
( "FindReferences", tid, json $ toEncoding r)
Expand Down
Loading

0 comments on commit 9c9f0d3

Please sign in to comment.