Skip to content

Commit

Permalink
Fix logging with strict error handling
Browse files Browse the repository at this point in the history
Summary:
When a response to a request setting "strict errors" is an error, Glass doesn't log anything. Neither to `glean_glass_server` nor to `glean_glass_server_error_events`. We only noticed this thanks to the user experience metrics for diff-time navigation. The reason is that the logging handler is bypassed by the exception when the stack is unwound. For example, this is what happens for a documentSymbolIndex request:

```
documentSymbolIndex
  -> runRepoFile
    -> withRepoFile
      -> withStrictErrorHandling
        -> exception is thrown here
      -> runLog called here
```

The solution is to move the exception site above the logging site, so that the exception is only ever raised **after logging**.

Reviewed By: phlalx

Differential Revision: D51118704

fbshipit-source-id: 7c4b27c9d7cc4e4aec75346b6f920f5686ee8048
  • Loading branch information
Pepe Iborra authored and facebook-github-bot committed Nov 9, 2023
1 parent dade780 commit d06b888
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 36 deletions.
76 changes: 40 additions & 36 deletions glean/glass/Glean/Glass/Handler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -157,8 +157,8 @@ runRepoFile
-> RequestOptions
-> IO t
runRepoFile sym fn env req opts =
withStrictErrorHandling opts $
withRepoFile sym env (req, opts) repo file $ \(dbs,_) mlang ->
withStrictErrorHandling opts $
fn repos req opts
(GleanBackend (Glass.gleanBackend env) dbs)
(Glass.snapshotBackend env)
Expand Down Expand Up @@ -230,8 +230,8 @@ findReferences
-> RequestOptions
-> IO [Location]
findReferences env@Glass.Env{..} sym opts@RequestOptions{..} =
withStrictErrorHandling opts $
withSymbol "findReferences" env sym (\(dbs,_revs,(repo, lang, toks)) ->
withStrictErrorHandling opts $
fetchSymbolReferences repo lang toks limit
(GleanBackend gleanBackend dbs))
where
Expand All @@ -244,8 +244,8 @@ findReferenceRanges
-> RequestOptions
-> IO [LocationRange]
findReferenceRanges env@Glass.Env{..} sym opts@RequestOptions{..} =
withStrictErrorHandling opts $
withSymbol "findReferenceRanges" env sym $ \(db,_revs,(repo, lang, toks)) ->
withStrictErrorHandling opts $
fetchSymbolReferenceRanges repo lang toks limit
(GleanBackend gleanBackend db)
where
Expand All @@ -259,8 +259,8 @@ resolveSymbolRange
-> RequestOptions
-> IO LocationRange
resolveSymbolRange env@Glass.Env{..} sym opts =
withSymbol "resolveSymbolRange" env sym $ \(db,_revs,(repo, lang, toks)) ->
withStrictErrorHandling opts $
withStrictErrorHandling opts $
withSymbol "resolveSymbolRange" env sym $ \(db,_revs,(repo, lang, toks)) ->
findSymbolLocationRange (GleanBackend gleanBackend db) repo lang toks

-- | Describe characteristics of a symbol
Expand All @@ -270,9 +270,9 @@ describeSymbol
-> RequestOptions
-> IO SymbolDescription
describeSymbol env@Glass.Env{..} symId opts =
withStrictErrorHandling opts $
withSymbol "describeSymbol" env symId $
\(gleanDBs, scmRevs, (scmRepo, lang, toks)) ->
withStrictErrorHandling opts $
backendRunHaxl GleanBackend{..} $ do
r <- Search.searchEntity lang toks
(first :| rest, err) <- case r of
Expand Down Expand Up @@ -321,8 +321,8 @@ fileIncludeLocations
-> IO FileIncludeLocationResults
fileIncludeLocations env@Glass.Env{..} req opts =
fmap fst $
withStrictErrorHandling opts $
withRepoFile "fileIncludeLocations" env req repo rootfile $ \(gleanDBs,_) _ ->
withStrictErrorHandling opts $
backendRunHaxl GleanBackend{..} $ do
result <- firstOrErrors $ do
rev <- getRepoHash <$> Glean.haxlRepo
Expand Down Expand Up @@ -351,9 +351,10 @@ clangUSRToDefinition
-> USR
-> RequestOptions
-> IO (USRSymbolDefinition, QueryEachRepoLog)
clangUSRToDefinition env@Glass.Env{..} usr@(USR hash) opts = withRepoLanguage
"clangUSRToDefinition" env usr repo mlang $ \(gleanDBs,_) _ -> do
withStrictErrorHandling opts $
clangUSRToDefinition env@Glass.Env{..} usr@(USR hash) opts =
withStrictErrorHandling opts $
withRepoLanguage "clangUSRToDefinition" env usr repo mlang
$ \(gleanDBs,_) _ -> do
backendRunHaxl GleanBackend{..} $ do
result <- firstOrErrors $ do
rev <- getRepoHash <$> Glean.haxlRepo
Expand Down Expand Up @@ -419,11 +420,12 @@ searchSymbol [email protected]{..} req@SymbolSearchRequest{..} RequestOptions{..} =
Left err -> throwIO $ ServerException err
Right rs -> case sFeelingLucky of
Normal -> joinSearchResults mlimit terse sorted <$> Async.mapConcurrently
(uncurry searchSymbolsIn) (Map.toList rs)
(continueOnErrors. uncurry searchSymbolsIn) (Map.toList rs)
-- lucky mode is quite different, as it has to make priority choices
FeelingLucky -> joinLuckyResults <$> Async.mapConcurrently
(uncurry searchLuckySymbolsIn) (Map.toList rs)
(continueOnErrors . uncurry searchLuckySymbolsIn) (Map.toList rs)
where
continueOnErrors = fmap fst -- TODO support strict errors
scmRepo = symbolSearchRequest_repo_name
languageSet = symbolSearchRequest_language
SymbolSearchOptions{..} = symbolSearchRequest_options
Expand All @@ -449,9 +451,9 @@ searchSymbol [email protected]{..} req@SymbolSearchRequest{..} RequestOptions{..} =
searchSymbolsIn
:: RepoName
-> Set GleanDBName
-> IO Query.RepoSearchResult
-> IO (Query.RepoSearchResult, Maybe ErrorLogger)
searchSymbolsIn repo dbs = case nonEmpty (Set.toList dbs) of
Nothing -> pure []
Nothing -> pure ([], Nothing)
Just names -> withGleanDBs "searchSymbol" env req names $
\gleanDBs scmRevs -> do
res <- backendRunHaxl GleanBackend{..} $ Glean.queryAllRepos $ do
Expand All @@ -463,9 +465,9 @@ searchSymbol [email protected]{..} req@SymbolSearchRequest{..} RequestOptions{..} =
-- In lucky mode, we avoid flattening, instead selecting from the first
-- unique result found in priority order. We don't de-dup as we go.
searchLuckySymbolsIn
:: RepoName -> Set GleanDBName -> IO FeelingLuckyResult
:: RepoName -> Set GleanDBName -> IO (FeelingLuckyResult, Maybe ErrorLogger)
searchLuckySymbolsIn repo dbs = case nonEmpty (Set.toList dbs) of
Nothing -> pure (FeelingLuckyResult [])
Nothing -> pure (FeelingLuckyResult [], Nothing)
Just names ->
withGleanDBs "feelingLucky" env req names $ \gleanDBs scmRevs -> do
res <- backendRunHaxl GleanBackend{..} $ Glean.queryEachRepo $ do
Expand Down Expand Up @@ -726,24 +728,25 @@ searchBySymbolId
:: Glass.Env
-> SymbolId
-> RequestOptions
-> IO SearchBySymbolIdResult
searchBySymbolId env@Glass.Env{..} symbolPrefix opts = do
-> IO (SearchBySymbolIdResult)
searchBySymbolId env@Glass.Env{..} symbolPrefix opts =
withStrictErrorHandling opts $
withLog "searchBySymbolId" env symbolPrefix $ \log -> do
symids <- case partialSymbolTokens symbolPrefix of
(Left pRepo, Left _, []) -> pure $ findRepos pRepo
(symids, merr) <- case partialSymbolTokens symbolPrefix of
(Left pRepo, Left _, []) -> pure (findRepos pRepo, Nothing)
(Left pRepo, _, _) -> throwM $
ServerException $ pRepo <> " is not a known repo"
(Right repo, Left pLang, []) -> pure $
findLanguages repo $ fromMaybe (Text.pack "") pLang
(Right repo, Left pLang, []) -> pure
(findLanguages repo $ fromMaybe (Text.pack "") pLang, Nothing)
(Right (RepoName repo), Left (Just pLang), _) -> throwM $
ServerException $ pLang <> " is not a supported language in "<> repo
(Right (RepoName repo), Left Nothing, _) -> throwM $
ServerException $ "Missing language for " <> repo
(Right repo, Right lang, tokens) -> findSymbols repo lang tokens
return (SearchBySymbolIdResult symids, log, Nothing)
return (SearchBySymbolIdResult symids, log, merr)

where
findSymbols :: RepoName -> Language -> [Text] -> IO [SymbolId]
findSymbols :: RepoName -> Language -> [Text] -> IO ([SymbolId], Maybe ErrorLogger)
findSymbols repo lang tokens =
withRepoLanguage "findSymbols" env symbolPrefix repo (Just lang) $
\(gleanDBs, _) _ -> do
Expand Down Expand Up @@ -1361,15 +1364,16 @@ withLog
-> Glass.Env
-> req
-> (GleanGlassLogger -> IO (res, GleanGlassLogger, Maybe ErrorLogger))
-> IO res
-> IO (res, Maybe ErrorLogger)
withLog cmd env req action = do
fst <$> loggingAction
(res, _) <- loggingAction
(runLog env cmd)
logResult
(do
(res, log, merr) <- action $ logRequest req
forM_ merr $ \e -> runErrorLog env cmd (e <> logError req)
return (res, log))
return ((res, merr), log))
return res

-- | Wrapper to enable perf logging, log the db names, and stats for
-- intermediate steps, and internal errors.
Expand All @@ -1381,7 +1385,7 @@ withLogDB
-> IO dbs
-> Maybe Language
-> (dbs -> Maybe Language -> IO (res, Maybe ErrorLogger))
-> IO res
-> IO (res, Maybe ErrorLogger)
withLogDB cmd env req fetch mlanguage run =
withLog cmd env req $ \log -> do
dbs <- fetch
Expand All @@ -1397,7 +1401,7 @@ withGleanDBs
-> NonEmpty GleanDBName
-> (NonEmpty (GleanDBName, Glean.Repo)
-> ScmRevisions -> IO (b, Maybe ErrorLogger))
-> IO b
-> IO (b, Maybe ErrorLogger)
withGleanDBs method env@Glass.Env{..} req dbNames fn = do
withLogDB method env req
(getSpecificGleanDBs latestGleanRepos repoScmRevisions dbNames)
Expand All @@ -1415,7 +1419,7 @@ withRepoLanguage
-> ( (NonEmpty (GleanDBName,Glean.Repo), ScmRevisions)
-> Maybe Language
-> IO (b, Maybe ErrorLogger))
-> IO b
-> IO (b, Maybe ErrorLogger)
withRepoLanguage method env@Glass.Env{..} req repo mlanguage fn = do
withLogDB method env req
(getGleanRepos latestGleanRepos repoScmRevisions repo mlanguage gleanDB)
Expand All @@ -1431,7 +1435,7 @@ withRepoFile :: (LogError a, LogRequest a, LogResult b) => Text
-> ( (NonEmpty (GleanDBName,Glean.Repo), ScmRevisions)
-> Maybe Language
-> IO (b, Maybe ErrorLogger))
-> IO b
-> IO (b, Maybe ErrorLogger)
withRepoFile method env req repo file fn = do
withRepoLanguage method env req repo (filetype file) fn

Expand All @@ -1444,7 +1448,7 @@ withSymbol
-> ((NonEmpty (GleanDBName, Glean.Repo),
ScmRevisions, (RepoName, Language, [Text]))
-> IO (c, Maybe ErrorLogger))
-> IO c
-> IO (c, Maybe ErrorLogger)
withSymbol method env@Glass.Env{..} sym fn =
withLogDB method env sym
(case symbolTokens sym of
Expand All @@ -1460,7 +1464,7 @@ withSymbol method [email protected]{..} sym fn =
withStrictErrorHandling
:: RequestOptions
-> IO (res, Maybe ErrorLogger)
-> IO (res, Maybe ErrorLogger)
-> IO res
withStrictErrorHandling opts action = do
(res, merr) <- action
case merr of
Expand All @@ -1474,7 +1478,7 @@ withStrictErrorHandling opts action = do
else throwM $ GlassException
(errorTy err)
(map (Revision . Glean.repo_hash) $ errorGleanRepo err)
_ -> return (res, merr)
_ -> return res
where
isRevisionNotAvailable GlassExceptionReason_exactRevisionNotAvailable{} =
True
Expand Down Expand Up @@ -1536,9 +1540,9 @@ searchRelated
-> IO SearchRelatedResult
searchRelated env@Glass.Env{..} sym opts@RequestOptions{..}
SearchRelatedRequest{..} =
withStrictErrorHandling opts $
withSymbol "searchRelated" env sym $
\(gleanDBs, scmRevs, (repo, lang, toks)) ->
withStrictErrorHandling opts $
backendRunHaxl GleanBackend{..} $ do
entity <- searchFirstEntity lang toks
withRepo (entityRepo entity) $ do
Expand Down Expand Up @@ -1704,9 +1708,9 @@ searchRelatedNeighborhood
-> RelatedNeighborhoodRequest
-> IO RelatedNeighborhoodResult
searchRelatedNeighborhood env@Glass.Env{..} sym opts@RequestOptions{..} req =
withStrictErrorHandling opts $
withSymbol "searchRelatedNeighborhood" env sym $
\(gleanDBs, scmRevs, (repo, lang, toks)) ->
withStrictErrorHandling opts $
backendRunHaxl GleanBackend{..} $ do
baseEntity <- searchFirstEntity lang toks
let lang = entityLanguage (decl baseEntity)
Expand Down
3 changes: 3 additions & 0 deletions glean/glass/Glean/Glass/Logging.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,9 @@ instance LogResult SnapshotStatus where
logResult (st, log) =
log <> logSnapshotStatus st

instance LogResult (Maybe ErrorLogger) where
logResult = mempty

data QueryEachRepoLog
= FoundMultiple { _discarded :: NonEmpty Glean.Repo}
| FoundNone
Expand Down

0 comments on commit d06b888

Please sign in to comment.