Skip to content

Commit

Permalink
Trace more stuff
Browse files Browse the repository at this point in the history
Summary:
* Trace DB selection so that we can see the time spent in SCS calls
* Trace `runHaxl` calls to see the time spent in Glean computations
* Trace the `exact` request option to better understand outcomes

Reviewed By: malanka

Differential Revision: D55995229

fbshipit-source-id: 083bd2bd706a010c440330151733ad11797118a9
  • Loading branch information
Pepe Iborra authored and facebook-github-bot committed Apr 11, 2024
1 parent fe43ce2 commit 91d763e
Show file tree
Hide file tree
Showing 4 changed files with 47 additions and 36 deletions.
26 changes: 13 additions & 13 deletions glean/glass/Glean/Glass/Handler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -157,9 +157,9 @@ runRepoFile
-> RequestOptions
-> IO t
runRepoFile sym fn env@Glass.Env{..} req opts =
withRepoFile sym env opts (req, opts) repo file $ \dbs dbInfo mlang ->
withRepoFile sym env opts (req, opts) repo file $ \gleanDBs dbInfo mlang ->
fn sourceControl (Glass.repoMapping env) dbInfo req opts
(GleanBackend gleanBackend dbs)
GleanBackend{..}
snapshotBackend
mlang
where
Expand All @@ -173,11 +173,11 @@ documentSymbolListX
-> DocumentSymbolsRequest
-> RequestOptions
-> IO DocumentSymbolListXResult
documentSymbolListX env r opts =
documentSymbolListX env@Glass.Env{tracer} r opts =
fst3 <$>
runRepoFile
"documentSymbolListX"
(fetchSymbolsAndAttributes (tracer env))
(fetchSymbolsAndAttributes tracer)
env r opts

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

-- | Symbol-based find-refernces.
Expand All @@ -202,9 +202,9 @@ findReferences
-> IO [Location]
findReferences env@Glass.Env{..} sym opts@RequestOptions{..} =
withSymbol "findReferences" env opts sym $
\dbs _dbInfo (repo, lang, toks) ->
\gleanDBs _dbInfo (repo, lang, toks) ->
fetchSymbolReferences repo lang toks limit
(GleanBackend gleanBackend dbs)
GleanBackend{..}
where
limit = fmap fromIntegral requestOptions_limit

Expand All @@ -216,9 +216,9 @@ findReferenceRanges
-> IO [LocationRange]
findReferenceRanges env@Glass.Env{..} sym opts@RequestOptions{..} =
withSymbol "findReferenceRanges" env opts sym
$ \db _dbInfo (repo, lang, toks) ->
$ \gleanDBs _dbInfo (repo, lang, toks) ->
fetchSymbolReferenceRanges repo lang toks limit
(GleanBackend gleanBackend db)
GleanBackend{..}
where
limit = fmap fromIntegral requestOptions_limit

Expand All @@ -231,8 +231,8 @@ resolveSymbolRange
-> IO LocationRange
resolveSymbolRange env@Glass.Env{..} sym opts = do
withSymbol "resolveSymbolRange" env opts sym
$ \db _dbInfo (repo, lang, toks) ->
findSymbolLocationRange (GleanBackend gleanBackend db) repo lang toks
$ \gleanDBs _dbInfo (repo, lang, toks) ->
findSymbolLocationRange GleanBackend{..} repo lang toks

-- | Describe characteristics of a symbol
describeSymbol
Expand Down Expand Up @@ -1208,7 +1208,7 @@ getSymbolAttributes
getSymbolAttributes scm repoMapping dbInfo repo opts repofile mlimit
be@GleanBackend{..} = do
mAttrDBs <- forM (map fst $ toList gleanDBs) $
getLatestAttrDB scm repoMapping dbInfo repo opts
getLatestAttrDB tracer scm repoMapping dbInfo repo opts
attrs <- backendRunHaxl be $ do
forM (catMaybes mAttrDBs) $
\(attrDB, attr@(GleanDBAttrName _ attrKey){- existential key -}) ->
Expand Down
36 changes: 21 additions & 15 deletions glean/glass/Glean/Glass/Handler/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ import Glean.Glass.Logging
import Glean.Glass.Repos
import Glean.Glass.SourceControl
import Glean.Glass.SymbolId
import Glean.Glass.Tracing
import Glean.Glass.Types

import qualified Glean.Glass.Env as Glass
Expand Down Expand Up @@ -94,13 +95,15 @@ allOrError = go (Right [])
data GleanBackend b =
GleanBackend {
gleanBackend :: b,
gleanDBs :: NonEmpty (GleanDBName, Glean.Repo)
gleanDBs :: NonEmpty (GleanDBName, Glean.Repo),
tracer :: GlassTracer
}

backendRunHaxl
:: Glean.Backend b => GleanBackend b -> (forall u. ReposHaxl u w a) -> IO a
backendRunHaxl GleanBackend{..} =
runHaxlAllRepos gleanBackend (fmap snd gleanDBs)
backendRunHaxl GleanBackend{..} haxl =
traceSpan tracer "glean" $
runHaxlAllRepos gleanBackend (fmap snd gleanDBs) haxl

-- | Whether the user requires the exact revision specified
data RevisionSpecifier = ExactOnly Revision | AnyRevision
Expand All @@ -123,18 +126,19 @@ dbChooser repo opts =

-- | Get glean db for an attribute type
getLatestAttrDB
:: Some SourceControl
:: GlassTracer
-> Some SourceControl
-> RepoMapping
-> GleanDBInfo
-> RepoName
-> RequestOptions
-> GleanDBName
-> IO (Maybe (Glean.Repo, GleanDBAttrName))
getLatestAttrDB scm repoMapping dbInfo repo opts gleanDBName =
getLatestAttrDB tracer scm repoMapping dbInfo repo opts gleanDBName =
case firstAttrDB repoMapping gleanDBName of
Nothing -> return Nothing
Just attrDBName -> do
dbs <- chooseGleanDBs scm dbInfo (dbChooser repo opts)
dbs <- chooseGleanDBs tracer scm dbInfo (dbChooser repo opts)
[gleanAttrDBName attrDBName]
return $ case dbs of
[] -> Nothing
Expand All @@ -153,7 +157,7 @@ withGleanDBs
-> IO (b, Maybe ErrorLogger)
withGleanDBs method env@Glass.Env{..} opts req repo dbNames fn = do
dbInfo <- readTVarIO latestGleanRepos
dbs <- getSpecificGleanDBs sourceControl dbInfo (dbChooser repo opts) dbNames
dbs <- getSpecificGleanDBs tracer sourceControl dbInfo (dbChooser repo opts) dbNames
withLog method env req $ \log ->
withLogDB dbs log $
fn dbs dbInfo
Expand Down Expand Up @@ -194,7 +198,7 @@ withRepoLanguage
-> IO b
withRepoLanguage method env@Glass.Env{..} req repo mlanguage opts fn =
withRequest method env req opts $ \dbInfo logger -> do
dbs <- getGleanRepos sourceControl repoMapping dbInfo repo
dbs <- getGleanRepos tracer sourceControl repoMapping dbInfo repo
mlanguage (dbChooser repo opts) gleanDB
withLogDB dbs logger $
fn dbs dbInfo mlanguage
Expand Down Expand Up @@ -233,7 +237,7 @@ withSymbol method [email protected]{..} opts sym fn =
case symbolTokens sym of
Left err -> throwM $ ServerException err
Right req@(repo, lang, _toks) -> do
dbs <- getGleanRepos sourceControl repoMapping dbInfo repo
dbs <- getGleanRepos tracer sourceControl repoMapping dbInfo repo
(Just lang) (dbChooser repo opts) gleanDB
withLogDB dbs log $ fn dbs dbInfo req

Expand Down Expand Up @@ -302,35 +306,37 @@ withLogDB dbs log fn = do
-- throw. Returns the chosen db name and Glean repo handle.
-- If a Glean.Repo is given, use it instead.
getGleanRepos
:: Some SourceControl
:: GlassTracer
-> Some SourceControl
-> RepoMapping
-> GleanDBInfo
-> RepoName
-> Maybe Language
-> ChooseGleanDBs
-> Maybe Glean.Repo
-> IO (NonEmpty (GleanDBName,Glean.Repo))
getGleanRepos scm repoMapping dbInfo scsrepo mlanguage chooser mGleanDB =
getGleanRepos tracer scm repoMapping dbInfo scsrepo mlanguage chooser mGleanDB =
case mGleanDB of
Nothing ->
case fromSCSRepo repoMapping scsrepo mlanguage of
[] -> throwIO $ ServerException $ "No repository found for: " <>
unRepoName scsrepo <>
maybe "" (\x -> " (" <> toShortCode x <> ")") mlanguage
(x:xs) ->
getSpecificGleanDBs scm dbInfo chooser (x :| xs)
getSpecificGleanDBs tracer scm dbInfo chooser (x :| xs)
Just gleanDB@Glean.Repo{repo_name} ->
return ((GleanDBName repo_name, gleanDB) :| [])

-- | If you already know the set of dbs you need, just get them.
getSpecificGleanDBs
:: Some SourceControl
:: GlassTracer
-> Some SourceControl
-> GleanDBInfo
-> ChooseGleanDBs
-> NonEmpty GleanDBName
-> IO (NonEmpty (GleanDBName,Glean.Repo))
getSpecificGleanDBs scm dbInfo chooser gleanDBNames = do
dbs <- chooseGleanDBs scm dbInfo chooser (toList gleanDBNames)
getSpecificGleanDBs tracer scm dbInfo chooser gleanDBNames = do
dbs <- chooseGleanDBs tracer scm dbInfo chooser (toList gleanDBNames)
case dbs of
[] -> throwIO $ ServerException $ "No Glean dbs found for: " <>
Text.intercalate ", " (map unGleanDBName $ toList gleanDBNames)
Expand Down
15 changes: 9 additions & 6 deletions glean/glass/Glean/Glass/Repos.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,7 @@ import Glean.Glass.SymbolId ( toShortCode )
import Glean.Glass.Types
import qualified Glean.Glass.RepoMapping as Mapping -- site-specific
import Glean.Repo (LatestRepos)
import Glean.Glass.Tracing (GlassTracer, traceSpan)

-- | mapping from Glean DB to info about the scm repositories it covers
type ScmRevisions = HashMap Glean.Repo (HashMap RepoName ScmRevisionInfo)
Expand Down Expand Up @@ -453,17 +454,18 @@ data ChooseGleanDBs

-- | Choose DBs for the given DB names and ChooseGleanDBs spec
chooseGleanDBs
:: Some SourceControl
:: GlassTracer
-> Some SourceControl
-> GleanDBInfo
-> ChooseGleanDBs
-> [GleanDBName]
-> IO [(GleanDBName, Glean.Repo)]
chooseGleanDBs _ dbInfo ChooseLatest repoNames =
chooseGleanDBs _ _ dbInfo ChooseLatest repoNames =
return $ catMaybes
[ (dbName,) <$> Map.lookup name (Glean.latestRepos (latestRepos dbInfo))
| dbName@(GleanDBName name) <- repoNames
]
chooseGleanDBs _ dbInfo (ChooseExactOrLatest rev) repoNames =
chooseGleanDBs _ _ dbInfo (ChooseExactOrLatest rev) repoNames =
return $ catMaybes
[ (dbName,) <$> (dbForRevision <|> latestDb)
| dbName@(GleanDBName name) <- repoNames
Expand All @@ -473,10 +475,11 @@ chooseGleanDBs _ dbInfo (ChooseExactOrLatest rev) repoNames =
HashMap.lookup dbName (dbByRevision dbInfo) >>= \(byrev, _) ->
HashMap.lookup rev byrev
]
chooseGleanDBs scm dbInfo (ChooseNearest repo rev) repoNames = do
maybeGen <- getGeneration scm repo rev
chooseGleanDBs tracer scm dbInfo (ChooseNearest repo rev) repoNames = do
maybeGen <- traceSpan tracer "getGeneration" $ getGeneration scm repo rev
case maybeGen of
Nothing -> chooseGleanDBs scm dbInfo (ChooseExactOrLatest rev) repoNames
Nothing ->
chooseGleanDBs tracer scm dbInfo (ChooseExactOrLatest rev) repoNames
Just (ScmGeneration gen) -> do
return $ catMaybes
[ (dbName,) <$> (dbForRevision <|> latestDb)
Expand Down
6 changes: 4 additions & 2 deletions glean/glass/Glean/Glass/Tracing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,14 +43,16 @@ glassTraceEvent (TraceCommand cmd) = case cmd of
, json $ pairs $
"filepath" .= documentSymbolsRequest_filepath <>
"repository" .= documentSymbolsRequest_repository <>
"revision" .= requestOptions_revision opts
"revision" .= requestOptions_revision opts <>
"exact" .= requestOptions_exact_revision opts
)
Glass.DocumentSymbolIndex DocumentSymbolsRequest{..} opts ->
("DocumentSymbolIndex"
, json $ pairs $
"filepath" .= documentSymbolsRequest_filepath <>
"repository" .= documentSymbolsRequest_repository <>
"revision" .= requestOptions_revision opts
"revision" .= requestOptions_revision opts <>
"exact" .= requestOptions_exact_revision opts
)
Glass.FindReferences r opts ->
( "FindReferences" , json $ toEncoding r)
Expand Down

0 comments on commit 91d763e

Please sign in to comment.