Skip to content

Commit

Permalink
refactor logging of attributes (Simon's version)
Browse files Browse the repository at this point in the history
Summary:
pair programming with simonmar

to make the logging for attributes a bit more general and to log something or nothing a bit more flexibly per atttribute

Differential Revision: D68440841

fbshipit-source-id: c0007f7eda9a89ba56b8fc85d979b32d159c7be2
  • Loading branch information
Simon Marlow authored and facebook-github-bot committed Jan 22, 2025
1 parent 9ad2c1e commit f19384b
Show file tree
Hide file tree
Showing 6 changed files with 65 additions and 63 deletions.
17 changes: 4 additions & 13 deletions glean/glass/Glean/Glass/Attributes/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,6 @@ module Glean.Glass.Attributes.Class
, extendAttributes
, attrListToMap
, attrMapToList
, AttributesMetricsLog(..)
, emptyAttributesMetricsLog
) where

import qualified Data.Map as Map
Expand All @@ -34,23 +32,16 @@ import Glean.Glass.Types
DefinitionSymbolX(..),
KeyedAttribute(KeyedAttribute),
ReferenceRangeSymbolX(..) )
import Glean.Glass.Logging
import qualified Glean.Schema.Src.Types as Src ( File )
import qualified Glean.Schema.Code.Types as Code


data AttributesMetricsLog = AttributesMetricsLog
{ numPerFile :: Int
, numAssignedPerFile :: Int
}


emptyAttributesMetricsLog :: AttributesMetricsLog
emptyAttributesMetricsLog = AttributesMetricsLog 0 0

-- | Class for querying attributes and converting them to thrift
class ToAttributes key where
class LogResult (AttrLog key) => ToAttributes key where

type AttrRep key :: *
type AttrLog key :: *

-- | Fetch the data for this attribute type for a file
queryForFile
Expand All @@ -65,7 +56,7 @@ class ToAttributes key where
-> [AttrRep key]
-> [RefEntitySymbol]
-> [DefEntitySymbol]
-> ([RefEntitySymbol], [DefEntitySymbol], AttributesMetricsLog)
-> ([RefEntitySymbol], [DefEntitySymbol], AttrLog key)

type RefEntitySymbol = (Code.Entity, ReferenceRangeSymbolX)
type DefEntitySymbol = (Code.Entity, DefinitionSymbolX)
Expand Down
3 changes: 2 additions & 1 deletion glean/glass/Glean/Glass/Attributes/SymbolKind.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ type EntityKindLabel = (Code.Entity, Code.SymbolKind)

instance ToAttributes SymbolKindAttr where
type AttrRep SymbolKindAttr = EntityKindLabel
type AttrLog SymbolKindAttr = ()

queryForFile _ lim fileId =
fst <$> Utils.searchRecursiveWithLimit lim q
Expand All @@ -54,7 +55,7 @@ instance ToAttributes SymbolKindAttr where
q = fileEntityKinds fileId .| fileEntityXRefKinds fileId

augmentSymbols _ kinds refs defs =
(refs_result, defs_result, emptyAttributesMetricsLog)
(refs_result, defs_result, ())
where
(refs_result, defs_result) =
extendAttributes (\_ ent -> ent) attrMap refs defs
Expand Down
23 changes: 22 additions & 1 deletion glean/glass/Glean/Glass/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,20 +14,41 @@ module Glean.Glass.Base
, RepoMapping(..)
) where

import Data.Function
import Data.Hashable
import Data.List.NonEmpty(NonEmpty(..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as Map
import Data.String
import Data.Text (Text)
import qualified Data.Text as Text

import Glean.Glass.Attributes.Class as Attributes
import qualified Logger.GleanGlass as Logger

import Glean ( Repo(..) )
import qualified Glean.Glass.Types as Glass
import Glean.Glass.Logging
import Glean.Glass.Attributes.Class as Attributes

-- | Type of glean dbs
newtype GleanDBName = GleanDBName { unGleanDBName :: Text }
deriving (Eq, Ord, Show, Hashable)

instance IsString GleanDBName where fromString = GleanDBName . fromString

instance LogResult (NonEmpty (GleanDBName, Glean.Repo)) where
logResult ((_, repo) :| []) =
Logger.setRepoName (Glean.repo_name repo) <>
Logger.setRepoHash (Glean.repo_hash repo)
logResult rs0@(_ :| _) =
Logger.setRepoName (commas repo_name rs) <>
Logger.setRepoHash (commas (Text.take 12 . repo_hash) rs)
where
rs = NE.sortBy (compare `on` Glean.repo_name) (fmap snd rs0)

commas :: (Glean.Repo -> Text) -> NonEmpty Glean.Repo -> Text
commas f = Text.intercalate "," . map f . NE.toList

--
-- | A glean path for www is prefixed with www/
-- For all other repos, it is relative to the repo root.
Expand Down
39 changes: 20 additions & 19 deletions glean/glass/Glean/Glass/Handler/Documents.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,9 +77,7 @@ import Glean.Glass.SourceControl
import Glean.Glass.Tracing (traceSpan)
import qualified Glean.Glass.Utils as Utils
import Glean.Glass.Utils ( fst4 )
import Glean.Glass.Attributes.Class (
AttributesMetricsLog(..),
emptyAttributesMetricsLog)
import Logger.GleanGlass (GleanGlassLogger)


-- | Runner for methods that are keyed by a file path
Expand Down Expand Up @@ -206,7 +204,7 @@ fetchSymbolsAndAttributesGlean
-> Maybe (Some Glean.Backend, GleanDBInfo)
-> Maybe Language
-> IO (
(DocumentSymbolListXResult, QueryEachRepoLog, AttributesMetricsLog),
(DocumentSymbolListXResult, QueryEachRepoLog, GleanGlassLogger),
Maybe ErrorLogger
)
fetchSymbolsAndAttributesGlean
Expand Down Expand Up @@ -252,7 +250,7 @@ shouldFetchContentHash opts =

type FetchDocumentSymbols =
((DocumentSymbolListXResult, SnapshotStatus,
QueryEachRepoLog, AttributesMetricsLog), Maybe ErrorLogger)
QueryEachRepoLog, GleanGlassLogger), Maybe ErrorLogger)

-- | When an explicit revision is requested, we attempt to fetch both
-- Glean results and a snapshot. This function chooses which result to
Expand All @@ -262,7 +260,7 @@ chooseGleanOrSnapshot
:: RequestOptions
-> Revision
-> (
(DocumentSymbolListXResult, QueryEachRepoLog, AttributesMetricsLog),
(DocumentSymbolListXResult, QueryEachRepoLog, GleanGlassLogger),
Maybe ErrorLogger
)
-- ^ Glean result
Expand Down Expand Up @@ -295,7 +293,7 @@ chooseGleanOrSnapshot RequestOptions{..} revision glean esnapshot
empty status =
((toDocumentSymbolResult(emptyDocumentSymbols revision)
, status
, FoundNone, emptyAttributesMetricsLog)
, FoundNone, mempty)
, Just $ logError $
GlassExceptionReason_matchingRevisionNotAvailable $
unRevision revision
Expand All @@ -316,7 +314,7 @@ returnSnapshot
-> FetchDocumentSymbols
returnSnapshot queryResult match =
((setContentMatch queryResult, match,
QueryEachRepoUnrequested, emptyAttributesMetricsLog), Nothing)
QueryEachRepoUnrequested, mempty), Nothing)
where
-- set the content_match field appropriately if we used a snapshot
setContentMatch res = case match of
Expand Down Expand Up @@ -365,9 +363,11 @@ fetchSymbolsAndAttributes
-> GleanBackend b
-> snapshotBackend
-> Maybe Language
-> IO ((DocumentSymbolListXResult, SnapshotStatus, QueryEachRepoLog,
AttributesMetricsLog)
, Maybe ErrorLogger)
-> IO (
(DocumentSymbolListXResult, SnapshotStatus, QueryEachRepoLog,
GleanGlassLogger),
Maybe ErrorLogger
)
fetchSymbolsAndAttributes env@Glass.Env{..} dbInfo req
opts@RequestOptions{..} be snapshotbe mlang = do
res <- case requestOptions_revision of
Expand Down Expand Up @@ -634,7 +634,7 @@ fetchDocumentSymbolIndex
-> Maybe Language
-> IO ((
DocumentSymbolIndex, SnapshotStatus,
QueryEachRepoLog, AttributesMetricsLog),
QueryEachRepoLog, GleanGlassLogger),
Maybe ErrorLogger)
fetchDocumentSymbolIndex env latest req opts be
snapshotbe mlang = do
Expand Down Expand Up @@ -869,28 +869,27 @@ addDynamicAttributes
-> Maybe Int
-> GleanBackend b
-> DocumentSymbols
-> IO (DocumentSymbols, AttributesMetricsLog)
-> IO (DocumentSymbols, GleanGlassLogger)
addDynamicAttributes env dbInfo repo opts repofile mlimit be syms = do
-- combine additional dynamic attributes
mattrs <- getSymbolAttributes env
dbInfo repo opts repofile mlimit be
return $ extend mattrs emptyAttributesMetricsLog syms
return $ extend mattrs mempty syms
where
extend [] log syms = (syms, log)
extend (augment : xs) log syms =
extend xs newLog (syms { refs = refs' , defs = defs' })
where
(refs',defs',log') = augment (refs syms) (defs syms)
newLog = AttributesMetricsLog
(numPerFile log' + numPerFile log)
(numAssignedPerFile log' + numAssignedPerFile log)
newLog = log <> log'
-- Note: it'll only log one if multiple attrs use the same fields

type Augment =
[Attributes.RefEntitySymbol] ->
[Attributes.DefEntitySymbol] ->
([Attributes.RefEntitySymbol],
[Attributes.DefEntitySymbol],
AttributesMetricsLog)
GleanGlassLogger)

-- Work out if we have extra attribute dbs and then run the queries
getSymbolAttributes
Expand All @@ -914,7 +913,9 @@ getSymbolAttributes env dbInfo repo opts repofile mlimit
withRepo attrDB $ do
(attrs,_merr2) <- genericFetchFileAttributes attrKey
(theGleanPath repofile) mlimit
return (Attributes.augmentSymbols attrKey attrs)
return $ \refs defs ->
case Attributes.augmentSymbols attrKey attrs refs defs of
(refs, defs, log) -> (refs, defs, logResult log)

-- | External (non-local db) Attributes of symbols. Just Hack only for now
genericFetchFileAttributes
Expand Down
38 changes: 9 additions & 29 deletions glean/glass/Glean/Glass/Logging.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,11 +40,8 @@ import Logger.GleanGlass (GleanGlassLogger)
import qualified Logger.GleanGlass as Logger

import Glean ( Repo(..) )
import Glean.Glass.Base ( GleanDBName )
import Glean.Glass.Types
import Glean.Glass.NameSearch (FeelingLuckyResult(..), RepoSearchResult)
import Glean.Glass.SnapshotBackend ( SnapshotStatus(..) )
import Glean.Glass.Attributes.Class (AttributesMetricsLog(..))

instance ActionLog GleanGlassLogger where
successLog = Logger.setSuccess True
Expand Down Expand Up @@ -97,6 +94,12 @@ instance LogRequest FileIncludeLocationRequest where
class LogResult a where
logResult :: a -> GleanGlassLogger

instance LogResult () where
logResult = mempty

instance LogResult GleanGlassLogger where
logResult = id

instance LogResult a => LogResult (Maybe a) where
logResult = maybe mempty logResult

Expand Down Expand Up @@ -144,11 +147,6 @@ instance LogResult QueryEachRepoLog where
else Logger.setRepoOther (map Glean.repo_name more)
_ -> mempty

instance LogResult AttributesMetricsLog where
logResult AttributesMetricsLog{..} =
Logger.setNumAttributeSamples numPerFile <>
Logger.setNumAssignedAttributeSamples numAssignedPerFile

instance LogResult DocumentSymbolIndex where
logResult DocumentSymbolIndex{..} =
Logger.setItemCount (fromIntegral documentSymbolIndex_size)
Expand Down Expand Up @@ -188,18 +186,13 @@ instance LogResult SymbolId where
instance LogResult [SymbolId] where
logResult xs = Logger.setItemCount (length xs)

instance LogResult [(SymbolResult, Maybe SymbolDescription)] where
logResult rs = Logger.setItemCount (length rs)

instance LogResult SymbolSearchResult where
logResult SymbolSearchResult{..} =
Logger.setItemCount (length symbolSearchResult_symbols)

instance LogResult RepoSearchResult where
logResult rs = Logger.setItemCount (length rs)

instance LogResult FeelingLuckyResult where
logResult (FeelingLuckyResult rs) =
Logger.setItemCount
(sum (map (sum . map length) rs))

instance LogResult SearchRelatedResult where
logResult SearchRelatedResult{..} =
logResult searchRelatedResult_edges
Expand Down Expand Up @@ -233,19 +226,6 @@ instance LogResult [USRSymbolReference] where
instance LogResult [RelatedSymbols] where
logResult edges = Logger.setItemCount (length edges)

instance LogResult (NonEmpty (GleanDBName, Glean.Repo)) where
logResult ((_, repo) :| []) =
Logger.setRepoName (Glean.repo_name repo) <>
Logger.setRepoHash (Glean.repo_hash repo)
logResult rs0@(_ :| _) =
Logger.setRepoName (commas repo_name rs) <>
Logger.setRepoHash (commas (Text.take 12 . repo_hash) rs)
where
rs = NE.sortBy (compare `on` Glean.repo_name) (fmap snd rs0)

commas :: (Glean.Repo -> Text) -> NonEmpty Glean.Repo -> Text
commas f = Text.intercalate "," . map f . NE.toList

--
-- | Intern error logging
--
Expand Down
8 changes: 8 additions & 0 deletions glean/glass/Glean/Glass/NameSearch.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,10 +47,13 @@ import Data.Maybe
import Data.List.NonEmpty as NonEmpty (NonEmpty(..), toList)
import qualified Data.List.NonEmpty as NonEmpty

import qualified Logger.GleanGlass as Logger

import qualified Glean
import Glean.Angle as Angle
import Glean.Haxl.Repos (RepoHaxl)

import Glean.Glass.Logging
import Glean.Glass.Types (SymbolResult(..), SymbolDescription(..))
import Glean.Glass.Utils (splitOnAny, QueryType )

Expand Down Expand Up @@ -669,4 +672,9 @@ dedupSearchResult results = Map.toList $ Map.fromListWith max results
-- within one scm repo, across dbs, across queries, a set of result symbols.
newtype FeelingLuckyResult = FeelingLuckyResult [[RepoSearchResult]]

instance LogResult FeelingLuckyResult where
logResult (FeelingLuckyResult rs) =
Logger.setItemCount
(sum (map (sum . map length) rs))

type SingleSymbol = (SymbolResult,Maybe SymbolDescription)

0 comments on commit f19384b

Please sign in to comment.