Skip to content

Commit

Permalink
Merge pull request #650 from TristanCacqueray/fix-lifecycle-query
Browse files Browse the repository at this point in the history
[api] Add test for lifecycle stats
  • Loading branch information
mergify[bot] authored Oct 12, 2021
2 parents 9418d86 + 1e80c56 commit f0c4ea9
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 5 deletions.
12 changes: 7 additions & 5 deletions haskell/src/Monocle/Backend/Queries.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
-- The goal of this module is to transform 'Query' into list of items
module Monocle.Backend.Queries where

import Data.Aeson (Value (Object), (.:))
import Data.Aeson (Value (Object), (.:), (.:?))
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as Aeson
import qualified Data.HashMap.Strict as HM
Expand Down Expand Up @@ -319,7 +319,7 @@ data HistoBucket a = HistoBucket
{ hbKey :: Word64,
hbDate :: LText,
hbCount :: Word32,
hbSubBuckets :: a
hbSubBuckets :: Maybe a
}
deriving (Eq, Show)

Expand All @@ -343,8 +343,8 @@ instance (FromJSON a, BucketName a) => FromJSON (HistoBucket a) where
where
subKeyName = bucketName (Proxy @a)
parseSubBucket
| subKeyName == "unused" = pure $ error "no subbucket"
| otherwise = v .: subKeyName
| subKeyName == "unused" = pure Nothing
| otherwise = v .:? subKeyName
parseJSON _ = mzero

newtype HistoAgg a = HistoAgg
Expand Down Expand Up @@ -1086,7 +1086,9 @@ getActivityStats = do
fromInteger
. toInteger
. length
$ haBuckets hbSubBuckets
. haBuckets
. fromMaybe (error "subbucket not found")
$ hbSubBuckets
in SearchPB.Histo {..}

getSuggestions :: QueryMonad m => Config.Index -> m SearchPB.SuggestionsResponse
Expand Down
19 changes: 19 additions & 0 deletions haskell/src/Monocle/Backend/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -429,6 +429,25 @@ testGetNewContributors = withTenant doTest
[Q.TermResult {trTerm = "bob", trCount = 1}]
results

testLifecycleStats :: Assertion
testLifecycleStats = withTenant doTest
where
doTest :: QueryM ()
doTest = do
traverse_ (indexScenarioNM (SProject "openstack/nova" [alice] [bob] [eve])) ["42", "43"]
let query =
let queryGet _ = const []
queryBounds =
( addUTCTime (-3600) fakeDate,
addUTCTime (3600) fakeDate
)
queryMinBoundsSet = True
in Q.Query {..}

withQuery query $ do
res <- Q.getLifecycleStats
liftIO $ assertBool "stats exist" (not $ null $ SearchPB.lifecycleStatsCreatedHisto res)

testGetActivityStats :: Assertion
testGetActivityStats = withTenant doTest
where
Expand Down
1 change: 1 addition & 0 deletions haskell/src/Monocle/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ module Monocle.Prelude
-- * tests
Assertion,
assertEqual,
assertBool,
assertFailure,

-- * relude extra
Expand Down
1 change: 1 addition & 0 deletions nix/default.nix
Original file line number Diff line number Diff line change
Expand Up @@ -492,6 +492,7 @@ in rec {
export PROTOC_FLAGS="-I ${googleapis-src}/ -I ${protobuf-src}/src"
export PROTOBUF_SRC=${protobuf-src}/src
export NIX_PATH=nixpkgs=${nixpkgsPath}
export ELASTIC_URL=http://localhost:19200
'';
};
inherit pkgs;
Expand Down

0 comments on commit f0c4ea9

Please sign in to comment.