Skip to content

Commit

Permalink
test: verify the indexed error content
Browse files Browse the repository at this point in the history
  • Loading branch information
TristanCacqueray committed Dec 22, 2023
1 parent 5e660b0 commit 37656c9
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 8 deletions.
12 changes: 8 additions & 4 deletions src/Macroscope/Test.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
-- | Tests for the macroscope process
module Macroscope.Test where

import Data.ByteString.Base64.Lazy qualified as B64
import Effectful.Env
import Effectful.Prometheus
import Effectful.Reader.Static qualified as E
Expand All @@ -17,6 +18,7 @@ import Monocle.Backend.Queries qualified as Q
import Monocle.Backend.Test (fakeChangePB, withTenantConfig)
import Monocle.Backend.Test qualified as BT (fakeChange, fakeDate, fakeDateAlt)
import Monocle.Client
import Monocle.Client.Api (crawlerErrors)
import Monocle.Config qualified as Config
import Monocle.Effects
import Monocle.Entity (CrawlerName (..), Entity (Project))
Expand All @@ -26,7 +28,6 @@ import Monocle.Protob.Crawler qualified as CrawlerPB
import Streaming.Prelude qualified as Streaming
import Test.Tasty
import Test.Tasty.HUnit
import Monocle.Client.Api (crawlerErrors)

runLentilleM :: MonocleClient -> Eff [E.Reader CrawlerEnv, MonoClientEffect, LoggerEffect, GerritEffect, BZEffect, TimeEffect, HttpEffect, PrometheusEffect, EnvEffect, Fail, Retry, Concurrent, IOE] a -> IO a
runLentilleM client action = do
Expand Down Expand Up @@ -56,11 +57,14 @@ testCrawlingPoint = do
(currentOldestAge, _) <- getOldest
liftIO $ assertBool "Commit date is updated on failure" (currentOldestAge > oldestAge)

-- Check that the error got indexed
errorResponse <- crawlerErrors client (CrawlerPB.ErrorsRequest (from indexName) "from:2020")
case errorResponse of
CrawlerPB.ErrorsResponse Nothing -> error "Bad response"
CrawlerPB.ErrorsResponse (Just (CrawlerPB.ErrorsResponseResultError err)) -> error $ from err
CrawlerPB.ErrorsResponse (Just (CrawlerPB.ErrorsResponseResultSuccess errors)) -> liftIO $ assertEqual "Error got indexed" (length errors.errorsListErrors) 1
CrawlerPB.ErrorsResponse (Just (CrawlerPB.ErrorsResponseResultSuccess (CrawlerPB.ErrorsList (toList -> [e])))) -> liftIO do
e.crawlerErrorMessage @?= "decode"
(B64.decode . encodeUtf8 $ e.crawlerErrorBody) @?= Right "[\"Oops\"]"
(from <$> e.crawlerErrorEntity) @?= Just (Project "opendev/neutron")
_ -> error $ "Expected one error, got: " <> show errorResponse

Macroscope.runStream apiKey indexName (CrawlerName crawlerName) (Macroscope.Changes $ goodStream currentOldestAge)

Expand Down
14 changes: 12 additions & 2 deletions src/Monocle/Backend/Documents.hs
Original file line number Diff line number Diff line change
Expand Up @@ -197,6 +197,17 @@ instance From ETaskData SearchPB.TaskData where
taskDataPrefix = from $ fromMaybe "" $ tdPrefix td
in SearchPB.TaskData {..}

newtype EErrorData = EErrorData
{ eeErrorData :: EError
}
deriving (Show, Eq, Generic)

instance ToJSON EErrorData where
toJSON = genericToJSON $ aesonPrefix snakeCase

instance FromJSON EErrorData where
parseJSON = genericParseJSON $ aesonPrefix snakeCase

data EError = EError
{ erCrawlerName :: Text
, erEntity :: Entity
Expand Down Expand Up @@ -229,8 +240,7 @@ instance ToJSON EError where
]

instance FromJSON EError where
parseJSON = withObject "EError" $ \root -> do
v <- root .: "error_data"
parseJSON = withObject "EError" $ \v -> do
erCrawlerName <- v .: "crawler_name"
erCreatedAt <- v .: "created_at"
evalue <- v .: "entity_value"
Expand Down
8 changes: 6 additions & 2 deletions src/Monocle/Backend/Queries.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ import Database.Bloodhound qualified as BH
import Database.Bloodhound.Raw (TermsCompositeAggBucket)
import Database.Bloodhound.Raw qualified as BHR
import Json.Extras qualified as Json
import Monocle.Backend.Documents (EChange (..), EChangeEvent (..), EChangeState (..), EDocType (..), EError, allEventTypes)
import Monocle.Backend.Documents (EChange (..), EChangeEvent (..), EChangeState (..), EDocType (..), EError, EErrorData, allEventTypes, eeErrorData)
import Monocle.Config qualified as Config
import Monocle.Prelude
import Monocle.Protob.Metric qualified as MetricPB
Expand Down Expand Up @@ -248,8 +248,12 @@ crawlerErrors = do
dropQuery do
withFilter queryFilter do
withDocTypes [EErrorDoc] (QueryFlavor Author CreatedAt) do
doSearch (Just order) 500
fmap toError <$> doSearch (Just order) 500
where
-- it is necessary to request the EErrorData so that the source fields are correctly set in BHR.search
toError :: EErrorData -> EError
toError = eeErrorData

order =
SearchPB.Order
{ orderField = "error_data.created_at"
Expand Down

0 comments on commit 37656c9

Please sign in to comment.