mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
server: Improve test failure error message in Data Connector agent test suite
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5304 GitOrigin-RevId: 8238c1b59c378b7fe37ae0c9afecbf04f8841e2e
This commit is contained in:
parent
2494cfa949
commit
b24b12b2e6
@ -143,13 +143,11 @@ constraints: any.Cabal ==3.2.1.0,
|
||||
any.hourglass ==0.2.12,
|
||||
any.hpc ==0.6.1.0,
|
||||
any.hsc2hs ==0.68.8,
|
||||
any.hscolour ==1.24.4,
|
||||
any.hspec ==2.10.0,
|
||||
any.hspec-core ==2.10.0,
|
||||
any.hspec-discover ==2.10.0,
|
||||
any.hspec-expectations ==0.8.2,
|
||||
any.hspec-expectations-lifted ==0.10.0,
|
||||
any.hspec-expectations-pretty-diff ==0.7.2.6,
|
||||
any.hspec-hedgehog ==0.0.1.2,
|
||||
any.http-api-data ==0.4.3,
|
||||
any.http-client ==0.7.11,
|
||||
@ -207,7 +205,6 @@ constraints: any.Cabal ==3.2.1.0,
|
||||
any.network-info ==0.2.1,
|
||||
any.network-ip ==0.3.0.3,
|
||||
any.network-uri ==2.6.4.1,
|
||||
any.nicify-lib ==1.0.1,
|
||||
any.nonempty-containers ==0.3.4.4,
|
||||
any.nonempty-vector ==0.2.1.0,
|
||||
any.odbc ==0.2.6,
|
||||
@ -315,7 +312,6 @@ constraints: any.Cabal ==3.2.1.0,
|
||||
any.type-equality ==1,
|
||||
any.type-hint ==0.1,
|
||||
any.typed-process ==0.2.8.0,
|
||||
any.unicode-show ==0.1.1.0,
|
||||
any.unix ==2.7.2.2,
|
||||
any.unix-compat ==0.5.4,
|
||||
any.unix-time ==0.4.7,
|
||||
|
@ -1316,7 +1316,9 @@ test-suite tests-dc-api
|
||||
import: common-all, common-exe
|
||||
type: exitcode-stdio-1.0
|
||||
build-depends:
|
||||
, Diff
|
||||
, aeson
|
||||
, ansi-terminal
|
||||
, autodocodec
|
||||
, autodocodec-openapi3
|
||||
, base
|
||||
@ -1328,7 +1330,6 @@ test-suite tests-dc-api
|
||||
, hashable
|
||||
, hspec
|
||||
, hspec-core
|
||||
, hspec-expectations-pretty-diff
|
||||
, http-client
|
||||
, lens
|
||||
, lens-aeson
|
||||
@ -1346,6 +1347,7 @@ test-suite tests-dc-api
|
||||
, vector
|
||||
, xml-conduit
|
||||
, xml-lens
|
||||
, yaml
|
||||
, zlib
|
||||
hs-source-dirs: tests-dc-api
|
||||
-- Turning off optimizations is intentional; tests aren't
|
||||
@ -1357,6 +1359,7 @@ test-suite tests-dc-api
|
||||
, Paths_graphql_engine
|
||||
, Test.Data
|
||||
, Test.CapabilitiesSpec
|
||||
, Test.Expectations
|
||||
, Test.HealthSpec
|
||||
, Test.QuerySpec
|
||||
, Test.QuerySpec.AggregatesSpec
|
||||
|
@ -3,16 +3,16 @@ module Test.CapabilitiesSpec (spec) where
|
||||
import Hasura.Backends.DataConnector.API (Capabilities, CapabilitiesResponse (..), Config, Routes (..), validateConfigAgainstConfigSchema)
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Expectations (jsonShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Expectations.Pretty (shouldBe)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> Config -> Capabilities -> Spec
|
||||
spec api config expectedCapabilities = describe "capabilities API" $ do
|
||||
it "returns the expected capabilities" $ do
|
||||
CapabilitiesResponse capabilities _ <- api // _capabilities
|
||||
capabilities `shouldBe` expectedCapabilities
|
||||
capabilities `jsonShouldBe` expectedCapabilities
|
||||
|
||||
it "returns a schema that can be used to validate the current config" $ do
|
||||
CapabilitiesResponse _ configSchema <- api // _capabilities
|
||||
validateConfigAgainstConfigSchema configSchema config `shouldBe` []
|
||||
validateConfigAgainstConfigSchema configSchema config `jsonShouldBe` []
|
||||
|
99
server/tests-dc-api/Test/Expectations.hs
Normal file
99
server/tests-dc-api/Test/Expectations.hs
Normal file
@ -0,0 +1,99 @@
|
||||
module Test.Expectations
|
||||
( jsonShouldBe,
|
||||
rowsShouldBe,
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Lens ((%~), (&))
|
||||
import Control.Monad (unless)
|
||||
import Control.Monad.IO.Class (MonadIO, liftIO)
|
||||
import Data.Aeson (ToJSON (..), Value)
|
||||
import Data.Aeson.KeyMap (KeyMap)
|
||||
import Data.Algorithm.Diff (Diff, PolyDiff (..), getDiff)
|
||||
import Data.Text qualified as T
|
||||
import Data.Text.Encoding qualified as TE
|
||||
import Data.Text.Encoding.Error qualified as TE
|
||||
import Data.Yaml qualified as Yaml
|
||||
import GHC.Stack (HasCallStack)
|
||||
import Hasura.Backends.DataConnector.API (FieldValue, deserializeAsRelationshipFieldValue, mkRelationshipFieldValue, qrRows)
|
||||
import System.Console.ANSI (Color (..), ColorIntensity (..), ConsoleLayer (..), SGR (..), hSupportsANSIColor, setSGRCode)
|
||||
import System.IO (stdout)
|
||||
import Test.Hspec (Expectation, expectationFailure)
|
||||
import Prelude
|
||||
|
||||
newtype YamlShow = YamlShow {unYamlShow :: Value}
|
||||
deriving newtype (Eq)
|
||||
|
||||
instance Show YamlShow where
|
||||
show = T.unpack . TE.decodeUtf8With TE.lenientDecode . Yaml.encode . unYamlShow
|
||||
|
||||
-- | Compares two JSON values for equality, but prints their diff upon failure
|
||||
-- as formatted YAML, which is a much nicer way to visualise the difference in
|
||||
-- expected vs actual.
|
||||
jsonShouldBe :: (HasCallStack, ToJSON value) => value -> value -> Expectation
|
||||
jsonShouldBe actual expected =
|
||||
shouldBeWithLineDiff (YamlShow $ toJSON actual) (YamlShow $ toJSON expected)
|
||||
|
||||
-- | Compares two lists of response rows, but normalizes them first to remove
|
||||
-- immaterial differences that show up when diffing in JSON/YAML
|
||||
rowsShouldBe :: HasCallStack => [KeyMap FieldValue] -> [KeyMap FieldValue] -> Expectation
|
||||
rowsShouldBe actual expected =
|
||||
(normalize <$> actual) `jsonShouldBe` (normalize <$> expected)
|
||||
|
||||
-- | Normalizes a response row so that immaterial differences are removed.
|
||||
--
|
||||
-- Immaterial differences can show up because 'FieldValue's are not actually decoded
|
||||
-- into Haskell types and are instead decoded as appropriate while traversing the Query
|
||||
-- IR (see 'FieldType' Haddocks for more info).
|
||||
-- This causes any JSON-based diff to show up immaterial differences even though two
|
||||
-- 'FieldValue's are equal, because the JSON contains differences that are ignored
|
||||
-- for equality purposes (eg the difference between a missing rows property and a
|
||||
-- null one).
|
||||
-- Normalization simply removes these differences by fully deserializing and then
|
||||
-- reserializing the JSON. It can do this by making the assumption that there are no
|
||||
-- custom scalar types that look like relationship field values (true for the Chinook
|
||||
-- data set used by the agent tests).
|
||||
normalize :: KeyMap FieldValue -> KeyMap FieldValue
|
||||
normalize =
|
||||
fmap
|
||||
( \fieldValue ->
|
||||
case deserializeAsRelationshipFieldValue fieldValue of
|
||||
Left _ -> fieldValue
|
||||
Right queryResponse ->
|
||||
mkRelationshipFieldValue $
|
||||
queryResponse & qrRows . traverse . traverse %~ normalize
|
||||
)
|
||||
|
||||
shouldBeWithLineDiff :: (HasCallStack, Show value, Eq value) => value -> value -> Expectation
|
||||
shouldBeWithLineDiff actual expected =
|
||||
unless (actual == expected) $
|
||||
expectationFailure =<< renderDiffError actual expected
|
||||
|
||||
renderDiffError :: (Show value, MonadIO m) => value -> value -> m String
|
||||
renderDiffError actual expected = do
|
||||
useColor <- liftIO $ hSupportsANSIColor stdout
|
||||
pure $ renderDiffString useColor (show actual) (show expected)
|
||||
|
||||
renderDiffString :: Bool -> String -> String -> String
|
||||
renderDiffString useColor actual expected =
|
||||
unlines $ resetHspecErrorColor <$> explanation <> diffLines
|
||||
where
|
||||
resetHspecErrorColor line = colorCode Reset ++ line
|
||||
|
||||
explanation =
|
||||
[ "━━━",
|
||||
colorSpan Green "--- expected, but not present",
|
||||
colorSpan Red "+++ present, but not expected",
|
||||
"━━━"
|
||||
]
|
||||
|
||||
diffLines = annotateDiffLine <$> getDiff (lines actual) (lines expected)
|
||||
|
||||
annotateDiffLine :: Diff String -> String
|
||||
annotateDiffLine = \case
|
||||
Both _ s -> " " ++ s
|
||||
First s -> colorSpan Green $ "--- " ++ s
|
||||
Second s -> colorSpan Red $ "+++ " ++ s
|
||||
|
||||
colorSpan c s = colorCode (SetColor Foreground Dull c) ++ s ++ colorCode Reset
|
||||
colorCode sgr = if useColor then setSGRCode [sgr] else ""
|
@ -3,8 +3,7 @@ module Test.HealthSpec (spec) where
|
||||
import Hasura.Backends.DataConnector.API (Config, Routes (..), SourceName)
|
||||
import Servant.API (NamedRoutes, NoContent (..))
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Expectations.Pretty (shouldBe)
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
|
@ -14,8 +14,8 @@ import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Expectations.Pretty (shouldBe)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
@ -29,8 +29,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let invoiceCount = length Data.invoicesRows
|
||||
let expectedAggregates = KeyMap.fromList [("count_all", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "counts all rows, after applying filters" $ do
|
||||
let where' = ApplyBinaryComparisonOperator Equal (Data.localComparisonColumn "BillingCity") (ScalarValue (String "Oslo"))
|
||||
@ -41,8 +41,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let invoiceCount = length $ filter ((^? ix "BillingCity" . Data._ColumnFieldString) >>> (== Just "Oslo")) Data.invoicesRows
|
||||
let expectedAggregates = KeyMap.fromList [("count_all", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "counts all rows, after applying pagination" $ do
|
||||
let aggregates = KeyMap.fromList [("count_all", StarCount)]
|
||||
@ -52,8 +52,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let invoiceCount = length . take 20 $ drop 400 Data.invoicesRows
|
||||
let expectedAggregates = KeyMap.fromList [("count_all", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
describe "Column Count" $ do
|
||||
it "counts all rows with non-null columns" $ do
|
||||
@ -64,8 +64,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let invoiceCount = length $ filter ((^? ix "BillingState" . Data._ColumnFieldString) >>> (/= Nothing)) Data.invoicesRows
|
||||
let expectedAggregates = KeyMap.fromList [("count_cols", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can count all rows with non-null values in a column, after applying pagination and filtering" $ do
|
||||
let where' = ApplyBinaryComparisonOperator GreaterThanOrEqual (Data.localComparisonColumn "InvoiceId") (ScalarValue (Number 380))
|
||||
@ -82,8 +82,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
|
||||
let expectedAggregates = KeyMap.fromList [("count_cols", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can count all rows with distinct non-null values in a column" $ do
|
||||
let aggregates = KeyMap.fromList [("count_cols", ColumnCount $ ColumnCountAggregate (ColumnName "BillingState") True)]
|
||||
@ -93,8 +93,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let billingStateCount = length . HashSet.fromList $ mapMaybe ((^? ix "BillingState" . Data._ColumnFieldString)) Data.invoicesRows
|
||||
let expectedAggregates = KeyMap.fromList [("count_cols", Number $ fromIntegral billingStateCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can count all rows with distinct non-null values in a column, after applying pagination and filtering" $ do
|
||||
let where' = ApplyBinaryComparisonOperator GreaterThanOrEqual (Data.localComparisonColumn "InvoiceId") (ScalarValue (Number 380))
|
||||
@ -112,8 +112,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
|
||||
let expectedAggregates = KeyMap.fromList [("count_cols", Number $ fromIntegral billingStateCount)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
describe "Single Column Function" $ do
|
||||
it "can get the max total from all rows" $ do
|
||||
@ -124,8 +124,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let maxTotal = maximum $ mapMaybe ((^? ix "Total" . Data._ColumnFieldNumber)) Data.invoicesRows
|
||||
let expectedAggregates = KeyMap.fromList [("max", Number maxTotal)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can get the max total from all rows, after applying pagination, filtering and ordering" $ do
|
||||
let where' = ApplyBinaryComparisonOperator Equal (Data.localComparisonColumn "BillingCountry") (ScalarValue (String "USA"))
|
||||
@ -144,8 +144,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
|
||||
let expectedAggregates = KeyMap.fromList [("max", Number maxTotal)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can get the min and max of a non-numeric comparable type such as a string" $ do
|
||||
let aggregates =
|
||||
@ -163,8 +163,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
("max", aggregate (String . maximum) names)
|
||||
]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "aggregates over empty row lists results in nulls" $ do
|
||||
let where' = ApplyBinaryComparisonOperator LessThan (Data.localComparisonColumn "ArtistId") (ScalarValue (Number 0))
|
||||
@ -174,8 +174,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
|
||||
let expectedAggregates = KeyMap.fromList [("min", Null)]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
describe "Multiple Aggregates and Returning Rows" $ do
|
||||
it "can get the max total from all rows, the count and the distinct count, simultaneously" $ do
|
||||
@ -199,8 +199,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
("maxTotal", maxTotal)
|
||||
]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can reuse the same aggregate twice" $ do
|
||||
let aggregates =
|
||||
@ -220,8 +220,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
("minTotal", maxTotal)
|
||||
]
|
||||
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `shouldBe` []
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` []
|
||||
|
||||
it "can also query for the rows involved in the aggregate" $ do
|
||||
let fields =
|
||||
@ -249,8 +249,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
let expectedAggregates = KeyMap.fromList [("min", maxTotal)]
|
||||
let expectedRows = Data.filterColumnsByQueryFields (_qrQuery queryRequest) <$> invoiceRows
|
||||
|
||||
Data.responseRows response `shouldBe` expectedRows
|
||||
Data.responseAggregates response `shouldBe` expectedAggregates
|
||||
Data.responseRows response `rowsShouldBe` expectedRows
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
|
||||
describe "Aggregates via Relationships" $ do
|
||||
it "can query aggregates via an array relationship" $ do
|
||||
@ -270,8 +270,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
& take 5
|
||||
& fmap joinInAlbums
|
||||
|
||||
Data.responseRows receivedArtists `shouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `shouldBe` mempty
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `jsonShouldBe` mempty
|
||||
|
||||
it "can query aggregates via an array relationship and include the rows in that relationship" $ do
|
||||
let albumFields =
|
||||
@ -296,8 +296,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
& take 5
|
||||
& fmap joinInAlbums
|
||||
|
||||
Data.responseRows receivedArtists `shouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `shouldBe` mempty
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `jsonShouldBe` mempty
|
||||
|
||||
it "can query with many nested relationships, with aggregates at multiple levels, with filtering, pagination and ordering" $ do
|
||||
receivedArtists <- (api // _query) sourceName config deeplyNestedArtistsQuery
|
||||
@ -354,8 +354,8 @@ spec api sourceName config = describe "Aggregate Queries" $ do
|
||||
& fmap joinInAlbums
|
||||
& Data.filterColumns ["Name", "Albums_aggregate"]
|
||||
|
||||
Data.responseRows receivedArtists `shouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `shouldBe` mempty
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `jsonShouldBe` mempty
|
||||
|
||||
artistsWithAlbumsQuery :: (Query -> Query) -> QueryRequest
|
||||
artistsWithAlbumsQuery modifySubquery =
|
||||
|
@ -10,8 +10,8 @@ import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Expectations.Pretty (shouldBe)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
@ -22,8 +22,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
receivedArtists <- Data.sortResponseRowsBy "ArtistId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedArtists = Data.artistsRows
|
||||
Data.responseRows receivedArtists `shouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `shouldBe` Nothing
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
it "can query for a list of albums with a subset of columns" $ do
|
||||
let fields = KeyMap.fromList [("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
@ -34,8 +34,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
KeyMap.filterWithKey (\propName _value -> propName == "ArtistId" || propName == "Title")
|
||||
|
||||
let expectedAlbums = Data.sortBy "Title" $ filterToRequiredProperties <$> Data.albumsRows
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can project columns into fields with different names" $ do
|
||||
let fields = KeyMap.fromList [("Artist_Id", Data.columnField "ArtistId"), ("Artist_Name", Data.columnField "Name")]
|
||||
@ -52,8 +52,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
id
|
||||
|
||||
let expectedArtists = Data.sortBy "ArtistId" $ renameProperties <$> Data.artistsRows
|
||||
Data.responseRows receivedArtists `shouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `shouldBe` Nothing
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
describe "Limit & Offset" $ do
|
||||
it "can use limit and offset to paginate results" $ do
|
||||
@ -65,8 +65,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
page1Artists <- Data.responseRows <$> (api // _query) sourceName config page1Query
|
||||
page2Artists <- Data.responseRows <$> (api // _query) sourceName config page2Query
|
||||
|
||||
page1Artists `shouldBe` take 10 allArtists
|
||||
page2Artists `shouldBe` take 10 (drop 10 allArtists)
|
||||
page1Artists `rowsShouldBe` take 10 allArtists
|
||||
page2Artists `rowsShouldBe` take 10 (drop 10 allArtists)
|
||||
|
||||
describe "Order By" $ do
|
||||
it "can use order by to order results in ascending order" $ do
|
||||
@ -75,8 +75,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums = sortOn (^? ix "Title") Data.albumsRows
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can use order by to order results in descending order" $ do
|
||||
let orderBy = OrderBy (ColumnName "Title") Descending :| []
|
||||
@ -84,8 +84,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums = sortOn (Down . (^? ix "Title")) Data.albumsRows
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can use multiple order bys to order results" $ do
|
||||
let orderBy = OrderBy (ColumnName "ArtistId") Ascending :| [OrderBy (ColumnName "Title") Descending]
|
||||
@ -95,8 +95,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
sortOn (\album -> (album ^? ix "ArtistId", Down (album ^? ix "Title"))) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
describe "Where" $ do
|
||||
it "can filter using an equality expression" $ do
|
||||
@ -107,8 +107,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter ((== Just 2) . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter using an inequality expression" $ do
|
||||
let where' = Not (ApplyBinaryComparisonOperator Equal (Data.localComparisonColumn "AlbumId") (ScalarValue (Number 2)))
|
||||
@ -118,8 +118,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter ((/= Just 2) . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter using an in expression" $ do
|
||||
let where' = ApplyBinaryArrayComparisonOperator In (Data.localComparisonColumn "AlbumId") [Number 2, Number 3]
|
||||
@ -129,8 +129,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter (flip elem [Just 2, Just 3] . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can negate an in expression filter using a not expression" $ do
|
||||
let where' = Not (ApplyBinaryArrayComparisonOperator In (Data.localComparisonColumn "AlbumId") [Number 2, Number 3])
|
||||
@ -140,8 +140,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter (flip notElem [Just 2, Just 3] . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can combine filters using an and expression" $ do
|
||||
let where1 = ApplyBinaryComparisonOperator Equal (Data.localComparisonColumn "ArtistId") (ScalarValue (Number 58))
|
||||
@ -157,8 +157,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
)
|
||||
Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can combine filters using an or expression" $ do
|
||||
let where1 = ApplyBinaryComparisonOperator Equal (Data.localComparisonColumn "AlbumId") (ScalarValue (Number 2))
|
||||
@ -170,8 +170,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter (flip elem [Just 2, Just 3] . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter by applying the greater than operator" $ do
|
||||
let where' = ApplyBinaryComparisonOperator GreaterThan (Data.localComparisonColumn "AlbumId") (ScalarValue (Number 300))
|
||||
@ -181,8 +181,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter ((> Just 300) . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter by applying the greater than or equal operator" $ do
|
||||
let where' = ApplyBinaryComparisonOperator GreaterThanOrEqual (Data.localComparisonColumn "AlbumId") (ScalarValue (Number 300))
|
||||
@ -192,8 +192,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter ((>= Just 300) . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter by applying the less than operator" $ do
|
||||
let where' = ApplyBinaryComparisonOperator LessThan (Data.localComparisonColumn "AlbumId") (ScalarValue (Number 100))
|
||||
@ -203,8 +203,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter ((< Just 100) . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter by applying the less than or equal operator" $ do
|
||||
let where' = ApplyBinaryComparisonOperator LessThanOrEqual (Data.localComparisonColumn "AlbumId") (ScalarValue (Number 100))
|
||||
@ -214,8 +214,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter ((<= Just 100) . (^? ix "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can filter using a greater than operator with a column comparison" $ do
|
||||
let where' = ApplyBinaryComparisonOperator GreaterThan (Data.localComparisonColumn "AlbumId") (AnotherColumn (Data.localComparisonColumn "ArtistId"))
|
||||
@ -225,8 +225,8 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let expectedAlbums =
|
||||
filter (\album -> (album ^? ix "AlbumId" . Data._ColumnFieldNumber) > (album ^? ix "ArtistId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
|
@ -9,8 +9,8 @@ import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Expectations.Pretty (shouldBe)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
@ -26,8 +26,8 @@ spec api sourceName config = describe "Relationship Queries" $ do
|
||||
let removeArtistId = KeyMap.delete "ArtistId"
|
||||
|
||||
let expectedAlbums = (removeArtistId . joinInArtist) <$> Data.albumsRows
|
||||
Data.responseRows receivedAlbums `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `shouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "perform an array relationship query by joining albums to artists" $ do
|
||||
let query = artistsWithAlbumsQuery id
|
||||
@ -41,8 +41,8 @@ spec api sourceName config = describe "Relationship Queries" $ do
|
||||
in KeyMap.insert "Albums" (mkSubqueryResponse albums') artist
|
||||
|
||||
let expectedAlbums = joinInAlbums <$> Data.artistsRows
|
||||
Data.responseRows receivedArtists `shouldBe` expectedAlbums
|
||||
_qrAggregates receivedArtists `shouldBe` Nothing
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
it "perform an object relationship query by joining employee to customers and filter comparing columns across the object relationship" $ do
|
||||
-- Join Employee to Customers via SupportRep, and only get those customers that have a rep
|
||||
@ -68,8 +68,8 @@ spec api sourceName config = describe "Relationship Queries" $ do
|
||||
in maybe False (`elem` supportRepCountry) customerCountry
|
||||
|
||||
let expectedCustomers = filter filterCustomersBySupportRepCountry $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInSupportRep <$> Data.customersRows
|
||||
Data.responseRows receivedCustomers `shouldBe` expectedCustomers
|
||||
_qrAggregates receivedCustomers `shouldBe` Nothing
|
||||
Data.responseRows receivedCustomers `rowsShouldBe` expectedCustomers
|
||||
_qrAggregates receivedCustomers `jsonShouldBe` Nothing
|
||||
|
||||
it "perform an array relationship query by joining customers to employees and filter comparing columns across the array relationship" $ do
|
||||
-- Join Customers to Employees via SupportRepForCustomers, and only get those employees that are reps for
|
||||
@ -97,8 +97,8 @@ spec api sourceName config = describe "Relationship Queries" $ do
|
||||
in maybe False (`elem` customerCountries) employeeCountry
|
||||
|
||||
let expectedEmployees = filter filterEmployeesByCustomerCountry $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInCustomers <$> Data.employeesRows
|
||||
Data.responseRows receivedEmployees `shouldBe` expectedEmployees
|
||||
_qrAggregates receivedEmployees `shouldBe` Nothing
|
||||
Data.responseRows receivedEmployees `rowsShouldBe` expectedEmployees
|
||||
_qrAggregates receivedEmployees `jsonShouldBe` Nothing
|
||||
|
||||
albumsWithArtistQuery :: (Query -> Query) -> QueryRequest
|
||||
albumsWithArtistQuery modifySubquery =
|
||||
|
@ -6,8 +6,8 @@ import Hasura.Backends.DataConnector.API.V0.Column (ColumnInfo (..))
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.Expectations.Pretty (shouldBe)
|
||||
import Prelude
|
||||
|
||||
removeDescriptionFromColumn :: ColumnInfo -> ColumnInfo
|
||||
@ -22,4 +22,4 @@ spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
spec api sourceName config = describe "schema API" $ do
|
||||
it "returns Chinook schema" $ do
|
||||
tables <- (map removeDescription . sortOn dtiName . srTables) <$> (api // _schema) sourceName config
|
||||
tables `shouldBe` map removeDescription Data.schemaTables
|
||||
tables `jsonShouldBe` map removeDescription Data.schemaTables
|
||||
|
Loading…
Reference in New Issue
Block a user