mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-15 09:22:43 +03:00
Add the ability to test against tables in configurable schemas in Data Connector Agent test suite
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6083 GitOrigin-RevId: 5a7ee37ed3a62224a062dbaac7d322dfd95b83c4
This commit is contained in:
parent
940d1fb2e0
commit
6af3fa2d78
@ -1,8 +1,14 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
--
|
||||
module Hasura.Backends.DataConnector.API.V0.Table
|
||||
( TableInfo (..),
|
||||
tiName,
|
||||
tiColumns,
|
||||
tiPrimaryKey,
|
||||
tiForeignKeys,
|
||||
tiDescription,
|
||||
TableName (..),
|
||||
ForeignKeys (..),
|
||||
ConstraintName (..),
|
||||
@ -15,6 +21,7 @@ where
|
||||
import Autodocodec
|
||||
import Autodocodec.OpenAPI ()
|
||||
import Control.DeepSeq (NFData)
|
||||
import Control.Lens.TH (makeLenses)
|
||||
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
|
||||
import Data.Data (Data)
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
@ -95,3 +102,5 @@ instance HasCodec Constraint where
|
||||
Constraint
|
||||
<$> requiredField "foreign_table" "The table referenced by the foreign key in the child table." .= _cForeignTable
|
||||
<*> requiredField "column_mapping" "The columns on which you want want to define the foreign key." .= _cColumnMapping
|
||||
|
||||
$(makeLenses ''TableInfo)
|
||||
|
@ -2,6 +2,7 @@
|
||||
|
||||
module Command
|
||||
( Command (..),
|
||||
TestConfig (..),
|
||||
TestOptions (..),
|
||||
AgentCapabilities (..),
|
||||
parseCommandLine,
|
||||
@ -13,7 +14,7 @@ import Control.Lens (contains, modifying, use, (^.), _2)
|
||||
import Control.Lens.TH (makeLenses)
|
||||
import Control.Monad (when)
|
||||
import Control.Monad.State (State, runState)
|
||||
import Data.Aeson (eitherDecodeStrict')
|
||||
import Data.Aeson (FromJSON (..), eitherDecodeStrict')
|
||||
import Data.HashSet (HashSet)
|
||||
import Data.HashSet qualified as HashSet
|
||||
import Data.Text (Text)
|
||||
@ -30,10 +31,14 @@ data Command
|
||||
= Test TestOptions
|
||||
| ExportOpenAPISpec
|
||||
|
||||
data TestConfig = TestConfig
|
||||
{_tcTableNamePrefix :: [Text]}
|
||||
|
||||
data TestOptions = TestOptions
|
||||
{ _toAgentBaseUrl :: BaseUrl,
|
||||
_toAgentConfig :: API.Config,
|
||||
_toAgentCapabilities :: AgentCapabilities,
|
||||
_toTestConfig :: TestConfig,
|
||||
_toParallelDegree :: Maybe Int,
|
||||
_toMatch :: Maybe String,
|
||||
_toSkip :: [String],
|
||||
@ -93,6 +98,18 @@ commandParser =
|
||||
(progDesc "Exports the OpenAPI specification of the Data Connector API that agents must implement")
|
||||
)
|
||||
|
||||
testConfigParser :: Parser TestConfig
|
||||
testConfigParser =
|
||||
TestConfig
|
||||
<$> option
|
||||
jsonValue
|
||||
( long "table-name-prefix"
|
||||
<> short 't'
|
||||
<> metavar "PREFIX"
|
||||
<> help "The prefix to use for all table names, as a JSON array of strings"
|
||||
<> value []
|
||||
)
|
||||
|
||||
testOptionsParser :: Parser TestOptions
|
||||
testOptionsParser =
|
||||
TestOptions
|
||||
@ -111,6 +128,7 @@ testOptionsParser =
|
||||
<> help "The configuration JSON to be sent to the agent via the X-Hasura-DataConnector-Config header"
|
||||
)
|
||||
<*> agentCapabilitiesParser
|
||||
<*> testConfigParser
|
||||
<*> optional
|
||||
( option
|
||||
positiveNonZeroInt
|
||||
@ -157,7 +175,10 @@ positiveNonZeroInt =
|
||||
if int <= 0 then readerError "Must be a positive, non-zero integer" else pure int
|
||||
|
||||
configValue :: ReadM API.Config
|
||||
configValue = eitherReader $ (fmap API.Config . eitherDecodeStrict' . Text.encodeUtf8 . Text.pack)
|
||||
configValue = fmap API.Config jsonValue
|
||||
|
||||
jsonValue :: FromJSON v => ReadM v
|
||||
jsonValue = eitherReader (eitherDecodeStrict' . Text.encodeUtf8 . Text.pack)
|
||||
|
||||
agentCapabilitiesParser :: Parser AgentCapabilities
|
||||
agentCapabilitiesParser =
|
||||
|
@ -17,6 +17,7 @@ import Network.HTTP.Client (defaultManagerSettings, newManager)
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, ClientError, hoistClient, mkClientEnv, runClientM, (//))
|
||||
import Test.CapabilitiesSpec qualified
|
||||
import Test.Data (TestData, mkTestData)
|
||||
import Test.ExplainSpec qualified
|
||||
import Test.HealthSpec qualified
|
||||
import Test.Hspec (Spec)
|
||||
@ -34,14 +35,14 @@ import Prelude
|
||||
testSourceName :: API.SourceName
|
||||
testSourceName = "dc-api-tests"
|
||||
|
||||
tests :: Client IO (NamedRoutes Routes) -> API.SourceName -> API.Config -> API.Capabilities -> Spec
|
||||
tests api sourceName agentConfig capabilities = do
|
||||
tests :: TestData -> Client IO (NamedRoutes Routes) -> API.SourceName -> API.Config -> API.Capabilities -> Spec
|
||||
tests testData api sourceName agentConfig capabilities = do
|
||||
Test.HealthSpec.spec api sourceName agentConfig
|
||||
Test.CapabilitiesSpec.spec api agentConfig capabilities
|
||||
Test.SchemaSpec.spec api sourceName agentConfig
|
||||
Test.QuerySpec.spec api sourceName agentConfig capabilities
|
||||
Test.SchemaSpec.spec testData api sourceName agentConfig
|
||||
Test.QuerySpec.spec testData api sourceName agentConfig capabilities
|
||||
for_ (API._cMetrics capabilities) \m -> Test.MetricsSpec.spec api m
|
||||
for_ (API._cExplain capabilities) \_ -> Test.ExplainSpec.spec api sourceName agentConfig capabilities
|
||||
for_ (API._cExplain capabilities) \_ -> Test.ExplainSpec.spec testData api sourceName agentConfig capabilities
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
@ -50,7 +51,8 @@ main = do
|
||||
Test testOptions@TestOptions {..} -> do
|
||||
api <- mkIOApiClient testOptions
|
||||
agentCapabilities <- getAgentCapabilities api _toAgentCapabilities
|
||||
let spec = tests api testSourceName _toAgentConfig agentCapabilities
|
||||
let testData = mkTestData _toTestConfig
|
||||
let spec = tests testData api testSourceName _toAgentConfig agentCapabilities
|
||||
case _toExportMatchStrings of
|
||||
False -> runSpec spec (applyTestConfig defaultConfig testOptions) >>= evaluateSummary
|
||||
True -> do
|
||||
|
@ -2,53 +2,9 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Test.Data
|
||||
( -- = Schema
|
||||
schemaTables,
|
||||
-- = Artists table
|
||||
artistsTableName,
|
||||
artistsRows,
|
||||
artistsRowsById,
|
||||
artistsTableRelationships,
|
||||
-- = Albums table
|
||||
albumsTableName,
|
||||
albumsRelationshipName,
|
||||
albumsRows,
|
||||
albumsRowsById,
|
||||
albumsTableRelationships,
|
||||
artistRelationshipName,
|
||||
tracksRelationshipName,
|
||||
-- = Customers table
|
||||
customersTableName,
|
||||
customersRows,
|
||||
customersTableRelationships,
|
||||
supportRepRelationshipName,
|
||||
-- = Employees table
|
||||
employeesTableName,
|
||||
employeesRows,
|
||||
employeesRowsById,
|
||||
employeesTableRelationships,
|
||||
supportRepForCustomersRelationshipName,
|
||||
-- = Invoices table
|
||||
invoicesTableName,
|
||||
invoicesRows,
|
||||
-- = InvoiceLines table
|
||||
invoiceLinesTableName,
|
||||
invoiceLinesRows,
|
||||
-- = MediaTypes table
|
||||
mediaTypesTableName,
|
||||
mediaTypesRows,
|
||||
-- = Tracks table
|
||||
tracksTableName,
|
||||
tracksRows,
|
||||
tracksTableRelationships,
|
||||
invoiceLinesRelationshipName,
|
||||
mediaTypeRelationshipName,
|
||||
albumRelationshipName,
|
||||
genreRelationshipName,
|
||||
-- = Genres table
|
||||
genresTableName,
|
||||
genresRows,
|
||||
genresTableRelationships,
|
||||
( -- = Test Data
|
||||
TestData (..),
|
||||
mkTestData,
|
||||
-- = Utilities
|
||||
emptyQuery,
|
||||
sortBy,
|
||||
@ -75,6 +31,7 @@ module Test.Data
|
||||
where
|
||||
|
||||
import Codec.Compression.GZip qualified as GZip
|
||||
import Command (TestConfig (..))
|
||||
import Control.Arrow (first, (>>>))
|
||||
import Control.Lens (Index, IxValue, Ixed, Traversal', ix, (%~), (&), (^.), (^..), (^?))
|
||||
import Data.Aeson (eitherDecodeStrict)
|
||||
@ -310,6 +267,109 @@ genresTableRelationships =
|
||||
]
|
||||
)
|
||||
|
||||
data TestData = TestData
|
||||
{ -- = Schema
|
||||
_tdSchemaTables :: [API.TableInfo],
|
||||
-- = Artists table
|
||||
_tdArtistsTableName :: API.TableName,
|
||||
_tdArtistsRows :: [HashMap API.FieldName API.FieldValue],
|
||||
_tdArtistsRowsById :: HashMap Scientific (HashMap API.FieldName API.FieldValue),
|
||||
_tdArtistsTableRelationships :: API.TableRelationships,
|
||||
_tdAlbumsRelationshipName :: API.RelationshipName,
|
||||
-- = Albums table
|
||||
_tdAlbumsTableName :: API.TableName,
|
||||
_tdAlbumsRows :: [HashMap API.FieldName API.FieldValue],
|
||||
_tdAlbumsRowsById :: HashMap Scientific (HashMap API.FieldName API.FieldValue),
|
||||
_tdAlbumsTableRelationships :: API.TableRelationships,
|
||||
_tdArtistRelationshipName :: API.RelationshipName,
|
||||
_tdTracksRelationshipName :: API.RelationshipName,
|
||||
-- = Customers table
|
||||
_tdCustomersTableName :: API.TableName,
|
||||
_tdCustomersRows :: [HashMap API.FieldName API.FieldValue],
|
||||
_tdCustomersTableRelationships :: API.TableRelationships,
|
||||
_tdSupportRepRelationshipName :: API.RelationshipName,
|
||||
-- = Employees table
|
||||
_tdEmployeesTableName :: API.TableName,
|
||||
_tdEmployeesRows :: [HashMap API.FieldName API.FieldValue],
|
||||
_tdEmployeesRowsById :: HashMap Scientific (HashMap API.FieldName API.FieldValue),
|
||||
_tdEmployeesTableRelationships :: API.TableRelationships,
|
||||
_tdSupportRepForCustomersRelationshipName :: API.RelationshipName,
|
||||
-- = Invoices table
|
||||
_tdInvoicesTableName :: API.TableName,
|
||||
_tdInvoicesRows :: [HashMap API.FieldName API.FieldValue],
|
||||
-- = InvoiceLines table
|
||||
_tdInvoiceLinesTableName :: API.TableName,
|
||||
_tdInvoiceLinesRows :: [HashMap API.FieldName API.FieldValue],
|
||||
-- = MediaTypes table
|
||||
_tdMediaTypesTableName :: API.TableName,
|
||||
_tdMediaTypesRows :: [HashMap API.FieldName API.FieldValue],
|
||||
-- = Tracks table
|
||||
_tdTracksTableName :: API.TableName,
|
||||
_tdTracksRows :: [HashMap API.FieldName API.FieldValue],
|
||||
_tdTracksTableRelationships :: API.TableRelationships,
|
||||
_tdInvoiceLinesRelationshipName :: API.RelationshipName,
|
||||
_tdMediaTypeRelationshipName :: API.RelationshipName,
|
||||
_tdAlbumRelationshipName :: API.RelationshipName,
|
||||
_tdGenreRelationshipName :: API.RelationshipName,
|
||||
-- = Genres table
|
||||
_tdGenresTableName :: API.TableName,
|
||||
_tdGenresRows :: [HashMap API.FieldName API.FieldValue],
|
||||
_tdGenresTableRelationships :: API.TableRelationships
|
||||
}
|
||||
|
||||
mkTestData :: TestConfig -> TestData
|
||||
mkTestData TestConfig {..} =
|
||||
TestData
|
||||
{ _tdSchemaTables = (API.tiName %~ applyTableNamePrefix _tcTableNamePrefix) <$> schemaTables,
|
||||
_tdArtistsTableName = applyTableNamePrefix _tcTableNamePrefix artistsTableName,
|
||||
_tdArtistsRows = artistsRows,
|
||||
_tdArtistsRowsById = artistsRowsById,
|
||||
_tdArtistsTableRelationships = prefixTableRelationships artistsTableRelationships,
|
||||
_tdAlbumsRelationshipName = albumsRelationshipName,
|
||||
_tdAlbumsTableName = applyTableNamePrefix _tcTableNamePrefix albumsTableName,
|
||||
_tdAlbumsRows = albumsRows,
|
||||
_tdAlbumsRowsById = albumsRowsById,
|
||||
_tdAlbumsTableRelationships = prefixTableRelationships albumsTableRelationships,
|
||||
_tdArtistRelationshipName = artistRelationshipName,
|
||||
_tdTracksRelationshipName = tracksRelationshipName,
|
||||
_tdCustomersTableName = applyTableNamePrefix _tcTableNamePrefix customersTableName,
|
||||
_tdCustomersRows = customersRows,
|
||||
_tdCustomersTableRelationships = prefixTableRelationships customersTableRelationships,
|
||||
_tdSupportRepRelationshipName = supportRepRelationshipName,
|
||||
_tdEmployeesTableName = applyTableNamePrefix _tcTableNamePrefix employeesTableName,
|
||||
_tdEmployeesRows = employeesRows,
|
||||
_tdEmployeesRowsById = employeesRowsById,
|
||||
_tdEmployeesTableRelationships = prefixTableRelationships employeesTableRelationships,
|
||||
_tdSupportRepForCustomersRelationshipName = supportRepForCustomersRelationshipName,
|
||||
_tdInvoicesTableName = applyTableNamePrefix _tcTableNamePrefix invoicesTableName,
|
||||
_tdInvoicesRows = invoicesRows,
|
||||
_tdInvoiceLinesTableName = applyTableNamePrefix _tcTableNamePrefix invoiceLinesTableName,
|
||||
_tdInvoiceLinesRows = invoiceLinesRows,
|
||||
_tdMediaTypesTableName = applyTableNamePrefix _tcTableNamePrefix mediaTypesTableName,
|
||||
_tdMediaTypesRows = mediaTypesRows,
|
||||
_tdTracksTableName = applyTableNamePrefix _tcTableNamePrefix tracksTableName,
|
||||
_tdTracksRows = tracksRows,
|
||||
_tdTracksTableRelationships = prefixTableRelationships tracksTableRelationships,
|
||||
_tdInvoiceLinesRelationshipName = invoiceLinesRelationshipName,
|
||||
_tdMediaTypeRelationshipName = mediaTypeRelationshipName,
|
||||
_tdAlbumRelationshipName = albumRelationshipName,
|
||||
_tdGenreRelationshipName = genreRelationshipName,
|
||||
_tdGenresTableName = applyTableNamePrefix _tcTableNamePrefix genresTableName,
|
||||
_tdGenresRows = genresRows,
|
||||
_tdGenresTableRelationships = prefixTableRelationships genresTableRelationships
|
||||
}
|
||||
where
|
||||
prefixTableRelationships :: API.TableRelationships -> API.TableRelationships
|
||||
prefixTableRelationships =
|
||||
API.trSourceTable %~ applyTableNamePrefix _tcTableNamePrefix
|
||||
>>> API.trRelationships . traverse . API.rTargetTable %~ applyTableNamePrefix _tcTableNamePrefix
|
||||
|
||||
applyTableNamePrefix :: [Text] -> API.TableName -> API.TableName
|
||||
applyTableNamePrefix prefix tableName@(API.TableName rawTableName) =
|
||||
case NonEmpty.nonEmpty prefix of
|
||||
Just prefix' -> API.TableName (prefix' <> rawTableName)
|
||||
Nothing -> tableName
|
||||
|
||||
emptyQuery :: API.Query
|
||||
emptyQuery = API.Query Nothing Nothing Nothing Nothing Nothing Nothing
|
||||
|
||||
|
@ -4,6 +4,7 @@ import Control.Lens ((&), (?~))
|
||||
import Hasura.Backends.DataConnector.API (Capabilities (..), Config, ExplainResponse (..), QueryRequest (..), Routes (..), SourceName, qFields)
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Hspec (Spec, describe, it, shouldNotBe)
|
||||
import Prelude
|
||||
@ -12,17 +13,17 @@ import Prelude
|
||||
-- We currently simply check that for a basic query the explain plan is not empty.
|
||||
-- There may be additional tests for explain-plans in HGE that we can leverage.
|
||||
--
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Capabilities -> Spec
|
||||
spec api sourceName config _ = do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Capabilities -> Spec
|
||||
spec TestData {..} api sourceName config _ = do
|
||||
describe "Explain API" do
|
||||
it "can generate an explain plan a query for a list of artists" $ do
|
||||
let query = artistsQueryRequest
|
||||
ExplainResponse {..} <- (api // _explain) sourceName config query
|
||||
_erQuery `shouldNotBe` ""
|
||||
_erLines `shouldNotBe` []
|
||||
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.artistsTableName [] query
|
||||
where
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdArtistsTableName [] query
|
||||
|
@ -5,6 +5,7 @@ import Data.Maybe (isJust)
|
||||
import Hasura.Backends.DataConnector.API (Capabilities (..), ComparisonCapabilities (..), Config, Routes (..), SourceName)
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client)
|
||||
import Test.Data (TestData)
|
||||
import Test.Hspec
|
||||
import Test.QuerySpec.AggregatesSpec qualified
|
||||
import Test.QuerySpec.BasicSpec qualified
|
||||
@ -13,12 +14,12 @@ import Test.QuerySpec.OrderBySpec qualified
|
||||
import Test.QuerySpec.RelationshipsSpec qualified
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Capabilities -> Spec
|
||||
spec api sourceName config capabilities@Capabilities {..} = do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Capabilities -> Spec
|
||||
spec testData api sourceName config capabilities@Capabilities {..} = do
|
||||
describe "query API" do
|
||||
Test.QuerySpec.BasicSpec.spec api sourceName config
|
||||
Test.QuerySpec.FilteringSpec.spec api sourceName config _cComparisons
|
||||
Test.QuerySpec.OrderBySpec.spec api sourceName config capabilities
|
||||
Test.QuerySpec.BasicSpec.spec testData api sourceName config
|
||||
Test.QuerySpec.FilteringSpec.spec testData api sourceName config _cComparisons
|
||||
Test.QuerySpec.OrderBySpec.spec testData api sourceName config capabilities
|
||||
when (isJust _cRelationships) $
|
||||
Test.QuerySpec.RelationshipsSpec.spec api sourceName config (_cComparisons >>= _ccSubqueryComparisonCapabilities)
|
||||
Test.QuerySpec.AggregatesSpec.spec api sourceName config _cRelationships
|
||||
Test.QuerySpec.RelationshipsSpec.spec testData api sourceName config (_cComparisons >>= _ccSubqueryComparisonCapabilities)
|
||||
Test.QuerySpec.AggregatesSpec.spec testData api sourceName config _cRelationships
|
||||
|
@ -14,20 +14,21 @@ import Data.Ord (Down (..))
|
||||
import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Maybe RelationshipCapabilities -> Spec
|
||||
spec api sourceName config relationshipCapabilities = describe "Aggregate Queries" $ do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Maybe RelationshipCapabilities -> Spec
|
||||
spec TestData {..} api sourceName config relationshipCapabilities = describe "Aggregate Queries" $ do
|
||||
describe "Star Count" $ do
|
||||
it "counts all rows" $ do
|
||||
let aggregates = Data.mkFieldsMap [("count_all", StarCount)]
|
||||
let queryRequest = invoicesQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceCount = length Data.invoicesRows
|
||||
let invoiceCount = length _tdInvoicesRows
|
||||
let expectedAggregates = Data.mkFieldsMap [("count_all", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
@ -39,7 +40,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates & qrQuery . qWhere ?~ where'
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceCount = length $ filter ((^? Data.field "BillingCity" . Data._ColumnFieldString) >>> (== Just "Oslo")) Data.invoicesRows
|
||||
let invoiceCount = length $ filter ((^? Data.field "BillingCity" . Data._ColumnFieldString) >>> (== Just "Oslo")) _tdInvoicesRows
|
||||
let expectedAggregates = Data.mkFieldsMap [("count_all", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
@ -50,7 +51,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates & qrQuery %~ (qLimit ?~ 20 >>> qOffset ?~ 400)
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceCount = length . take 20 $ drop 400 Data.invoicesRows
|
||||
let invoiceCount = length . take 20 $ drop 400 _tdInvoicesRows
|
||||
let expectedAggregates = Data.mkFieldsMap [("count_all", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
@ -62,7 +63,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceCount = length $ filter ((^? Data.field "BillingState" . Data._ColumnFieldString) >>> (/= Nothing)) Data.invoicesRows
|
||||
let invoiceCount = length $ filter ((^? Data.field "BillingState" . Data._ColumnFieldString) >>> (/= Nothing)) _tdInvoicesRows
|
||||
let expectedAggregates = Data.mkFieldsMap [("count_cols", Number $ fromIntegral invoiceCount)]
|
||||
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
@ -75,7 +76,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceCount =
|
||||
Data.invoicesRows
|
||||
_tdInvoicesRows
|
||||
& filter ((^? Data.field "InvoiceId" . Data._ColumnFieldNumber) >>> (>= Just 380))
|
||||
& take 20
|
||||
& mapMaybe ((^? Data.field "BillingState" . Data._ColumnFieldString))
|
||||
@ -91,7 +92,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let billingStateCount = length . HashSet.fromList $ mapMaybe ((^? Data.field "BillingState" . Data._ColumnFieldString)) Data.invoicesRows
|
||||
let billingStateCount = length . HashSet.fromList $ mapMaybe ((^? Data.field "BillingState" . Data._ColumnFieldString)) _tdInvoicesRows
|
||||
let expectedAggregates = Data.mkFieldsMap [("count_cols", Number $ fromIntegral billingStateCount)]
|
||||
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
@ -104,7 +105,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let billingStateCount =
|
||||
Data.invoicesRows
|
||||
_tdInvoicesRows
|
||||
& filter ((^? Data.field "InvoiceId" . Data._ColumnFieldNumber) >>> (>= Just 380))
|
||||
& take 20
|
||||
& mapMaybe ((^? Data.field "BillingState" . Data._ColumnFieldString))
|
||||
@ -122,7 +123,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let maxTotal = maximum $ mapMaybe ((^? Data.field "Total" . Data._ColumnFieldNumber)) Data.invoicesRows
|
||||
let maxTotal = maximum $ mapMaybe ((^? Data.field "Total" . Data._ColumnFieldNumber)) _tdInvoicesRows
|
||||
let expectedAggregates = Data.mkFieldsMap [("max", Number maxTotal)]
|
||||
|
||||
Data.responseAggregates response `jsonShouldBe` expectedAggregates
|
||||
@ -136,7 +137,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let maxTotal =
|
||||
Data.invoicesRows
|
||||
_tdInvoicesRows
|
||||
& filter ((^? Data.field "BillingCountry" . Data._ColumnFieldString) >>> (== Just "USA"))
|
||||
& sortOn (Down . (^? Data.field "BillingPostalCode"))
|
||||
& take 20
|
||||
@ -157,7 +158,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = artistsQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let names = mapMaybe ((^? Data.field "Name" . Data._ColumnFieldString)) Data.artistsRows
|
||||
let names = mapMaybe ((^? Data.field "Name" . Data._ColumnFieldString)) _tdArtistsRows
|
||||
let expectedAggregates =
|
||||
Data.mkFieldsMap
|
||||
[ ("min", aggregate (String . minimum) names),
|
||||
@ -189,9 +190,9 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceCount = length Data.invoicesRows
|
||||
let billingStateCount = length . HashSet.fromList $ mapMaybe ((^? Data.field "BillingState" . Data._ColumnFieldString)) Data.invoicesRows
|
||||
let maxTotal = aggregate (Number . maximum) $ mapMaybe ((^? Data.field "Total" . Data._ColumnFieldNumber)) Data.invoicesRows
|
||||
let invoiceCount = length _tdInvoicesRows
|
||||
let billingStateCount = length . HashSet.fromList $ mapMaybe ((^? Data.field "BillingState" . Data._ColumnFieldString)) _tdInvoicesRows
|
||||
let maxTotal = aggregate (Number . maximum) $ mapMaybe ((^? Data.field "Total" . Data._ColumnFieldNumber)) _tdInvoicesRows
|
||||
|
||||
let expectedAggregates =
|
||||
Data.mkFieldsMap
|
||||
@ -212,8 +213,8 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let queryRequest = invoicesQueryRequest aggregates
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let maxInvoiceId = aggregate (Number . minimum) $ mapMaybe ((^? Data.field "InvoiceId" . Data._ColumnFieldNumber)) Data.invoicesRows
|
||||
let maxTotal = aggregate (Number . minimum) $ mapMaybe ((^? Data.field "Total" . Data._ColumnFieldNumber)) Data.invoicesRows
|
||||
let maxInvoiceId = aggregate (Number . minimum) $ mapMaybe ((^? Data.field "InvoiceId" . Data._ColumnFieldNumber)) _tdInvoicesRows
|
||||
let maxTotal = aggregate (Number . minimum) $ mapMaybe ((^? Data.field "Total" . Data._ColumnFieldNumber)) _tdInvoicesRows
|
||||
|
||||
let expectedAggregates =
|
||||
Data.mkFieldsMap
|
||||
@ -237,7 +238,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
response <- (api // _query) sourceName config queryRequest
|
||||
|
||||
let invoiceRows =
|
||||
Data.invoicesRows
|
||||
_tdInvoicesRows
|
||||
& filter ((^? Data.field "BillingCountry" . Data._ColumnFieldString) >>> (== Just "Canada"))
|
||||
& sortOn (^? Data.field "BillingAddress")
|
||||
& take 30
|
||||
@ -262,13 +263,13 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let joinInAlbums (artist :: HashMap FieldName FieldValue) = fromMaybe artist $ do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums =
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
& filter ((^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>> (== Just artistId))
|
||||
let aggregates = Data.mkFieldsMap [("count", Number . fromIntegral $ length albums)]
|
||||
pure $ Data.insertField "Albums" (mkSubqueryResponse Nothing (Just aggregates)) artist
|
||||
|
||||
let expectedArtists =
|
||||
Data.artistsRows
|
||||
_tdArtistsRows
|
||||
& take 5
|
||||
& fmap joinInAlbums
|
||||
|
||||
@ -287,14 +288,14 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let joinInAlbums (artist :: HashMap FieldName FieldValue) = fromMaybe artist $ do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums =
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
& filter ((^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>> (== Just artistId))
|
||||
& Data.filterColumns ["AlbumId", "Title"]
|
||||
let aggregates = Data.mkFieldsMap [("count", Number . fromIntegral $ length albums)]
|
||||
pure $ Data.insertField "Albums" (mkSubqueryResponse (Just albums) (Just aggregates)) artist
|
||||
|
||||
let expectedArtists =
|
||||
Data.artistsRows
|
||||
_tdArtistsRows
|
||||
& take 5
|
||||
& fmap joinInAlbums
|
||||
|
||||
@ -307,7 +308,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let joinInMediaType (track :: HashMap FieldName FieldValue) = fromMaybe track $ do
|
||||
mediaTypeId <- track ^? Data.field "MediaTypeId" . Data._ColumnFieldNumber
|
||||
let mediaTypes =
|
||||
Data.mediaTypesRows
|
||||
_tdMediaTypesRows
|
||||
& filter ((^? Data.field "MediaTypeId" . Data._ColumnFieldNumber) >>> (== Just mediaTypeId))
|
||||
& Data.filterColumns ["Name"]
|
||||
pure $ Data.insertField "nodes_MediaType" (mkSubqueryResponse (Just mediaTypes) Nothing) track
|
||||
@ -315,7 +316,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let joinInInvoiceLines (track :: HashMap FieldName FieldValue) = fromMaybe track $ do
|
||||
trackId <- track ^? Data.field "TrackId" . Data._ColumnFieldNumber
|
||||
let invoiceLines =
|
||||
Data.invoiceLinesRows
|
||||
_tdInvoiceLinesRows
|
||||
& filter ((^? Data.field "TrackId" . Data._ColumnFieldNumber) >>> (== Just trackId))
|
||||
let getQuantity invoiceLine = invoiceLine ^? Data.field "Quantity" . Data._ColumnFieldNumber
|
||||
let invoiceLinesAggregates = Data.mkFieldsMap [("aggregate_sum_Quantity", aggregate (Number . sum) $ mapMaybe getQuantity invoiceLines)]
|
||||
@ -324,7 +325,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let joinInTracks (album :: HashMap FieldName FieldValue) = fromMaybe album $ do
|
||||
albumId <- album ^? Data.field "AlbumId" . Data._ColumnFieldNumber
|
||||
let tracks =
|
||||
Data.tracksRows
|
||||
_tdTracksRows
|
||||
& filter
|
||||
( \track ->
|
||||
track ^? Data.field "AlbumId" . Data._ColumnFieldNumber == Just albumId
|
||||
@ -340,7 +341,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
let joinInAlbums (artist :: HashMap FieldName FieldValue) = fromMaybe artist $ do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums =
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
& filter ((^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>> (== Just artistId))
|
||||
& fmap joinInTracks
|
||||
& Data.renameColumns [("Title", "nodes_Title")]
|
||||
@ -348,7 +349,7 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
pure $ Data.insertField "Albums_aggregate" (mkSubqueryResponse (Just albums) Nothing) artist
|
||||
|
||||
let expectedArtists =
|
||||
Data.artistsRows
|
||||
_tdArtistsRows
|
||||
& sortOn (Down . (^? Data.field "Name"))
|
||||
& filter ((^? Data.field "Name" . Data._ColumnFieldString) >>> (\name -> name > Just "A" && name < Just "B"))
|
||||
& drop 1
|
||||
@ -358,109 +359,109 @@ spec api sourceName config relationshipCapabilities = describe "Aggregate Querie
|
||||
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
Data.responseAggregates receivedArtists `jsonShouldBe` mempty
|
||||
where
|
||||
artistsWithAlbumsQuery :: (Query -> Query) -> QueryRequest
|
||||
artistsWithAlbumsQuery modifySubquery =
|
||||
let albumAggregates = Data.mkFieldsMap [("count", StarCount)]
|
||||
albumsSubquery = Data.emptyQuery & qAggregates ?~ albumAggregates & modifySubquery
|
||||
artistFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("ArtistId", Data.columnField "ArtistId"),
|
||||
("Name", Data.columnField "Name"),
|
||||
("Albums", RelField $ RelationshipField _tdAlbumsRelationshipName albumsSubquery)
|
||||
]
|
||||
artistOrderBy = OrderBy mempty $ Data.orderByColumn [] "ArtistId" Ascending :| []
|
||||
artistQuery = Data.emptyQuery & qFields ?~ artistFields & qOrderBy ?~ artistOrderBy
|
||||
artistsTableRelationships = Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships
|
||||
in QueryRequest _tdArtistsTableName [artistsTableRelationships] artistQuery
|
||||
|
||||
artistsWithAlbumsQuery :: (Query -> Query) -> QueryRequest
|
||||
artistsWithAlbumsQuery modifySubquery =
|
||||
let albumAggregates = Data.mkFieldsMap [("count", StarCount)]
|
||||
albumsSubquery = Data.emptyQuery & qAggregates ?~ albumAggregates & modifySubquery
|
||||
artistFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("ArtistId", Data.columnField "ArtistId"),
|
||||
("Name", Data.columnField "Name"),
|
||||
("Albums", RelField $ RelationshipField Data.albumsRelationshipName albumsSubquery)
|
||||
]
|
||||
artistOrderBy = OrderBy mempty $ Data.orderByColumn [] "ArtistId" Ascending :| []
|
||||
artistQuery = Data.emptyQuery & qFields ?~ artistFields & qOrderBy ?~ artistOrderBy
|
||||
artistsTableRelationships = Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships
|
||||
in QueryRequest Data.artistsTableName [artistsTableRelationships] artistQuery
|
||||
-- This query is basically what would be generated by this complex HGE GraphQL query
|
||||
-- @
|
||||
-- query {
|
||||
-- Artist(where: {_and: [{Name: {_gt: "A"}}, {Name: {_lt: "B"}}]}, limit: 3, offset: 1, order_by: {Name: desc}) {
|
||||
-- Name
|
||||
-- Albums_aggregate {
|
||||
-- nodes {
|
||||
-- Title
|
||||
-- Tracks_aggregate(where: {Milliseconds: {_lt: 300000}}, order_by: {Name: desc}) {
|
||||
-- aggregate {
|
||||
-- count
|
||||
-- }
|
||||
-- nodes {
|
||||
-- Name
|
||||
-- MediaType {
|
||||
-- Name
|
||||
-- }
|
||||
-- InvoiceLines_aggregate {
|
||||
-- aggregate {
|
||||
-- sum {
|
||||
-- Quantity
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- @
|
||||
deeplyNestedArtistsQuery :: QueryRequest
|
||||
deeplyNestedArtistsQuery =
|
||||
let invoiceLinesAggregates = Data.mkFieldsMap [("aggregate_sum_Quantity", SingleColumn $ SingleColumnAggregate Sum (ColumnName "Quantity"))]
|
||||
invoiceLinesSubquery = Data.emptyQuery & qAggregates ?~ invoiceLinesAggregates
|
||||
mediaTypeFields = Data.mkFieldsMap [("Name", Data.columnField "Name")]
|
||||
mediaTypeSubquery = Data.emptyQuery & qFields ?~ mediaTypeFields
|
||||
tracksFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("nodes_Name", Data.columnField "Name"),
|
||||
("nodes_MediaType", RelField $ RelationshipField _tdMediaTypeRelationshipName mediaTypeSubquery),
|
||||
("nodes_InvoiceLines_aggregate", RelField $ RelationshipField _tdInvoiceLinesRelationshipName invoiceLinesSubquery)
|
||||
]
|
||||
tracksAggregates = Data.mkFieldsMap [("aggregate_count", StarCount)]
|
||||
tracksWhere = ApplyBinaryComparisonOperator LessThan (Data.currentComparisonColumn "Milliseconds") (ScalarValue $ Number 300000)
|
||||
tracksOrderBy = OrderBy mempty $ Data.orderByColumn [] "Name" Descending :| []
|
||||
tracksSubquery = Query (Just tracksFields) (Just tracksAggregates) Nothing Nothing (Just tracksWhere) (Just tracksOrderBy)
|
||||
albumsFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("nodes_Title", Data.columnField "Title"),
|
||||
("nodes_Tracks_aggregate", RelField $ RelationshipField _tdTracksRelationshipName tracksSubquery)
|
||||
]
|
||||
albumsSubquery = Data.emptyQuery & qFields ?~ albumsFields
|
||||
artistFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("Name", Data.columnField "Name"),
|
||||
("Albums_aggregate", RelField $ RelationshipField _tdAlbumsRelationshipName albumsSubquery)
|
||||
]
|
||||
artistWhere =
|
||||
And
|
||||
[ ApplyBinaryComparisonOperator GreaterThan (Data.currentComparisonColumn "Name") (ScalarValue $ String "A"),
|
||||
ApplyBinaryComparisonOperator LessThan (Data.currentComparisonColumn "Name") (ScalarValue $ String "B")
|
||||
]
|
||||
artistOrderBy = OrderBy mempty $ Data.orderByColumn [] "Name" Descending :| []
|
||||
artistQuery = Query (Just artistFields) Nothing (Just 3) (Just 1) (Just artistWhere) (Just artistOrderBy)
|
||||
in QueryRequest
|
||||
_tdArtistsTableName
|
||||
[ Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships,
|
||||
Data.onlyKeepRelationships [_tdTracksRelationshipName] _tdAlbumsTableRelationships,
|
||||
Data.onlyKeepRelationships [_tdInvoiceLinesRelationshipName, _tdMediaTypeRelationshipName] _tdTracksTableRelationships
|
||||
]
|
||||
artistQuery
|
||||
|
||||
-- | This query is basically what would be generated by this complex HGE GraphQL query
|
||||
-- @
|
||||
-- query {
|
||||
-- Artist(where: {_and: [{Name: {_gt: "A"}}, {Name: {_lt: "B"}}]}, limit: 3, offset: 1, order_by: {Name: desc}) {
|
||||
-- Name
|
||||
-- Albums_aggregate {
|
||||
-- nodes {
|
||||
-- Title
|
||||
-- Tracks_aggregate(where: {Milliseconds: {_lt: 300000}}, order_by: {Name: desc}) {
|
||||
-- aggregate {
|
||||
-- count
|
||||
-- }
|
||||
-- nodes {
|
||||
-- Name
|
||||
-- MediaType {
|
||||
-- Name
|
||||
-- }
|
||||
-- InvoiceLines_aggregate {
|
||||
-- aggregate {
|
||||
-- sum {
|
||||
-- Quantity
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- }
|
||||
-- @
|
||||
deeplyNestedArtistsQuery :: QueryRequest
|
||||
deeplyNestedArtistsQuery =
|
||||
let invoiceLinesAggregates = Data.mkFieldsMap [("aggregate_sum_Quantity", SingleColumn $ SingleColumnAggregate Sum (ColumnName "Quantity"))]
|
||||
invoiceLinesSubquery = Data.emptyQuery & qAggregates ?~ invoiceLinesAggregates
|
||||
mediaTypeFields = Data.mkFieldsMap [("Name", Data.columnField "Name")]
|
||||
mediaTypeSubquery = Data.emptyQuery & qFields ?~ mediaTypeFields
|
||||
tracksFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("nodes_Name", Data.columnField "Name"),
|
||||
("nodes_MediaType", RelField $ RelationshipField Data.mediaTypeRelationshipName mediaTypeSubquery),
|
||||
("nodes_InvoiceLines_aggregate", RelField $ RelationshipField Data.invoiceLinesRelationshipName invoiceLinesSubquery)
|
||||
]
|
||||
tracksAggregates = Data.mkFieldsMap [("aggregate_count", StarCount)]
|
||||
tracksWhere = ApplyBinaryComparisonOperator LessThan (Data.currentComparisonColumn "Milliseconds") (ScalarValue $ Number 300000)
|
||||
tracksOrderBy = OrderBy mempty $ Data.orderByColumn [] "Name" Descending :| []
|
||||
tracksSubquery = Query (Just tracksFields) (Just tracksAggregates) Nothing Nothing (Just tracksWhere) (Just tracksOrderBy)
|
||||
albumsFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("nodes_Title", Data.columnField "Title"),
|
||||
("nodes_Tracks_aggregate", RelField $ RelationshipField Data.tracksRelationshipName tracksSubquery)
|
||||
]
|
||||
albumsSubquery = Data.emptyQuery & qFields ?~ albumsFields
|
||||
artistFields =
|
||||
Data.mkFieldsMap
|
||||
[ ("Name", Data.columnField "Name"),
|
||||
("Albums_aggregate", RelField $ RelationshipField Data.albumsRelationshipName albumsSubquery)
|
||||
]
|
||||
artistWhere =
|
||||
And
|
||||
[ ApplyBinaryComparisonOperator GreaterThan (Data.currentComparisonColumn "Name") (ScalarValue $ String "A"),
|
||||
ApplyBinaryComparisonOperator LessThan (Data.currentComparisonColumn "Name") (ScalarValue $ String "B")
|
||||
]
|
||||
artistOrderBy = OrderBy mempty $ Data.orderByColumn [] "Name" Descending :| []
|
||||
artistQuery = Query (Just artistFields) Nothing (Just 3) (Just 1) (Just artistWhere) (Just artistOrderBy)
|
||||
in QueryRequest
|
||||
Data.artistsTableName
|
||||
[ Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships,
|
||||
Data.onlyKeepRelationships [Data.tracksRelationshipName] Data.albumsTableRelationships,
|
||||
Data.onlyKeepRelationships [Data.invoiceLinesRelationshipName, Data.mediaTypeRelationshipName] Data.tracksTableRelationships
|
||||
]
|
||||
artistQuery
|
||||
artistsQueryRequest :: HashMap FieldName Aggregate -> QueryRequest
|
||||
artistsQueryRequest aggregates =
|
||||
let query = Data.emptyQuery & qAggregates ?~ aggregates
|
||||
in QueryRequest _tdArtistsTableName [] query
|
||||
|
||||
artistsQueryRequest :: HashMap FieldName Aggregate -> QueryRequest
|
||||
artistsQueryRequest aggregates =
|
||||
let query = Data.emptyQuery & qAggregates ?~ aggregates
|
||||
in QueryRequest Data.artistsTableName [] query
|
||||
invoicesQueryRequest :: HashMap FieldName Aggregate -> QueryRequest
|
||||
invoicesQueryRequest aggregates =
|
||||
let query = Data.emptyQuery & qAggregates ?~ aggregates
|
||||
in QueryRequest _tdInvoicesTableName [] query
|
||||
|
||||
invoicesQueryRequest :: HashMap FieldName Aggregate -> QueryRequest
|
||||
invoicesQueryRequest aggregates =
|
||||
let query = Data.emptyQuery & qAggregates ?~ aggregates
|
||||
in QueryRequest Data.invoicesTableName [] query
|
||||
mkSubqueryResponse :: Maybe [HashMap FieldName FieldValue] -> Maybe (HashMap FieldName Value) -> FieldValue
|
||||
mkSubqueryResponse rows aggregates =
|
||||
mkRelationshipFieldValue $ QueryResponse rows aggregates
|
||||
|
||||
mkSubqueryResponse :: Maybe [HashMap FieldName FieldValue] -> Maybe (HashMap FieldName Value) -> FieldValue
|
||||
mkSubqueryResponse rows aggregates =
|
||||
mkRelationshipFieldValue $ QueryResponse rows aggregates
|
||||
|
||||
aggregate :: (NonEmpty a -> Value) -> [a] -> Value
|
||||
aggregate aggFn values =
|
||||
maybe Null aggFn $ NonEmpty.nonEmpty values
|
||||
aggregate :: (NonEmpty a -> Value) -> [a] -> Value
|
||||
aggregate aggFn values =
|
||||
maybe Null aggFn $ NonEmpty.nonEmpty values
|
||||
|
@ -6,19 +6,20 @@ import Data.HashMap.Strict qualified as HashMap
|
||||
import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
spec api sourceName config = describe "Basic Queries" $ do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
spec TestData {..} api sourceName config = describe "Basic Queries" $ do
|
||||
describe "Column Fields" $ do
|
||||
it "can query for a list of artists" $ do
|
||||
let query = artistsQueryRequest
|
||||
receivedArtists <- Data.sortResponseRowsBy "ArtistId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedArtists = Data.artistsRows
|
||||
let expectedArtists = _tdArtistsRows
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
@ -30,7 +31,7 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
let filterToRequiredProperties =
|
||||
HashMap.filterWithKey (\(FieldName propName) _value -> propName == "ArtistId" || propName == "Title")
|
||||
|
||||
let expectedAlbums = Data.sortBy (FieldName "Title") $ filterToRequiredProperties <$> Data.albumsRows
|
||||
let expectedAlbums = Data.sortBy (FieldName "Title") $ filterToRequiredProperties <$> _tdAlbumsRows
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
@ -47,7 +48,7 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
other -> other
|
||||
)
|
||||
|
||||
let expectedArtists = Data.sortBy (FieldName "ArtistId") $ renameProperties <$> Data.artistsRows
|
||||
let expectedArtists = Data.sortBy (FieldName "ArtistId") $ renameProperties <$> _tdArtistsRows
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
@ -63,15 +64,15 @@ spec api sourceName config = describe "Basic Queries" $ do
|
||||
|
||||
page1Artists `rowsShouldBe` take 10 allArtists
|
||||
page2Artists `rowsShouldBe` take 10 (drop 10 allArtists)
|
||||
where
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdArtistsTableName [] query
|
||||
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.artistsTableName [] query
|
||||
|
||||
albumsQueryRequest :: QueryRequest
|
||||
albumsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.albumsTableName [] query
|
||||
albumsQueryRequest :: QueryRequest
|
||||
albumsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdAlbumsTableName [] query
|
||||
|
@ -11,20 +11,21 @@ import Data.Maybe (isJust, mapMaybe)
|
||||
import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Maybe ComparisonCapabilities -> Spec
|
||||
spec api sourceName config comparisonCapabilities = describe "Filtering in Queries" $ do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Maybe ComparisonCapabilities -> Spec
|
||||
spec TestData {..} api sourceName config comparisonCapabilities = describe "Filtering in Queries" $ do
|
||||
it "can filter using an equality expression" $ do
|
||||
let where' = ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "AlbumId") (ScalarValue (Number 2))
|
||||
let query = albumsQueryRequest & qrQuery . qWhere ?~ where'
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter ((== Just 2) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter ((== Just 2) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -35,7 +36,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter ((/= Just 2) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter ((/= Just 2) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -46,7 +47,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter (flip elem [Just 2, Just 3] . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter (flip elem [Just 2, Just 3] . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -57,7 +58,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter (flip notElem [Just 2, Just 3] . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter (flip notElem [Just 2, Just 3] . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -74,7 +75,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
( \album ->
|
||||
(album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just 58) && (album ^? Data.field "Title" . Data._ColumnFieldString == Just "Stormbringer")
|
||||
)
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -84,7 +85,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
let query = albumsQueryRequest & qrQuery . qWhere ?~ where'
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` Data.albumsRows
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` _tdAlbumsRows
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can combine filters using an or expression" $ do
|
||||
@ -95,7 +96,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter (flip elem [Just 2, Just 3] . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter (flip elem [Just 2, Just 3] . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -114,7 +115,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter ((> Just 300) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter ((> Just 300) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -125,7 +126,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter ((>= Just 300) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter ((>= Just 300) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -136,7 +137,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter ((< Just 100) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter ((< Just 100) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -147,7 +148,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter ((<= Just 100) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter ((<= Just 100) . (^? Data.field "AlbumId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -158,7 +159,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
filter (\album -> (album ^? Data.field "AlbumId" . Data._ColumnFieldNumber) > (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber)) Data.albumsRows
|
||||
filter (\album -> (album ^? Data.field "AlbumId" . Data._ColumnFieldNumber) > (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber)) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
@ -169,19 +170,19 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
describe "compare against a single column" $ do
|
||||
it "returns all rows if matching rows exist" $ do
|
||||
let where' =
|
||||
Exists (UnrelatedTable Data.employeesTableName) $
|
||||
Exists (UnrelatedTable _tdEmployeesTableName) $
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "EmployeeId") (ScalarValue (Number 1))
|
||||
let query = albumsQueryRequest & qrQuery . qWhere ?~ where'
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums = Data.albumsRows
|
||||
let expectedAlbums = _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "returns no rows if matching rows do not exist" $ do
|
||||
let where' =
|
||||
Exists (UnrelatedTable Data.employeesTableName) $
|
||||
Exists (UnrelatedTable _tdEmployeesTableName) $
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "EmployeeId") (ScalarValue (Number 0))
|
||||
let query = albumsQueryRequest & qrQuery . qWhere ?~ where'
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
@ -192,7 +193,7 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
describe "compare against multiple columns" $ do
|
||||
it "returns all rows if matching rows exist" $ do
|
||||
let where' =
|
||||
Exists (UnrelatedTable Data.employeesTableName) $
|
||||
Exists (UnrelatedTable _tdEmployeesTableName) $
|
||||
And
|
||||
[ ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "EmployeeId") (ScalarValue (Number 1)),
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "City") (ScalarValue (String "Edmonton"))
|
||||
@ -200,14 +201,14 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
let query = albumsQueryRequest & qrQuery . qWhere ?~ where'
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums = Data.albumsRows
|
||||
let expectedAlbums = _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "returns no rows if matching rows do not exist" $ do
|
||||
let where' =
|
||||
Exists (UnrelatedTable Data.employeesTableName) $
|
||||
Exists (UnrelatedTable _tdEmployeesTableName) $
|
||||
And
|
||||
[ ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "EmployeeId") (ScalarValue (Number 1)),
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "City") (ScalarValue (String "Calgary"))
|
||||
@ -222,21 +223,21 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
describe "Comparisons in related tables" $ do
|
||||
it "can filter by comparing against rows in a related table" $ do
|
||||
let where' =
|
||||
Exists (RelatedTable Data.artistRelationshipName) $
|
||||
Exists (RelatedTable _tdArtistRelationshipName) $
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "Name") (ScalarValue (String "AC/DC"))
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [Data.artistRelationshipName] Data.albumsTableRelationships]
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [_tdArtistRelationshipName] _tdAlbumsTableRelationships]
|
||||
& qrQuery . qWhere ?~ where'
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let artistId =
|
||||
Data.artistsRows
|
||||
_tdArtistsRows
|
||||
& find (\artist -> (artist ^? Data.field "Name" . Data._ColumnFieldString) == Just "AC/DC")
|
||||
>>= (^? Data.field "ArtistId" . Data._ColumnFieldNumber)
|
||||
|
||||
let albums =
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
& filter (\album -> (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) == artistId)
|
||||
& sortOn (^? Data.field "AlbumId")
|
||||
|
||||
@ -245,36 +246,36 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
|
||||
it "can filter by comparing against rows in a deeply related table" $ do
|
||||
let where' =
|
||||
Exists (RelatedTable Data.albumsRelationshipName) . Exists (RelatedTable Data.tracksRelationshipName) . Exists (RelatedTable Data.genreRelationshipName) $
|
||||
Exists (RelatedTable _tdAlbumsRelationshipName) . Exists (RelatedTable _tdTracksRelationshipName) . Exists (RelatedTable _tdGenreRelationshipName) $
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "Name") (ScalarValue (String "Metal"))
|
||||
let query =
|
||||
artistsQueryRequest
|
||||
& qrTableRelationships
|
||||
.~ [ Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships,
|
||||
Data.onlyKeepRelationships [Data.tracksRelationshipName] Data.albumsTableRelationships,
|
||||
Data.onlyKeepRelationships [Data.genreRelationshipName] Data.tracksTableRelationships
|
||||
.~ [ Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships,
|
||||
Data.onlyKeepRelationships [_tdTracksRelationshipName] _tdAlbumsTableRelationships,
|
||||
Data.onlyKeepRelationships [_tdGenreRelationshipName] _tdTracksTableRelationships
|
||||
]
|
||||
& qrQuery . qWhere ?~ where'
|
||||
receivedArtists <- Data.sortResponseRowsBy "ArtistId" <$> (api // _query) sourceName config query
|
||||
|
||||
let genreId =
|
||||
Data.genresRows
|
||||
_tdGenresRows
|
||||
& find (\genre -> (genre ^? Data.field "Name" . Data._ColumnFieldString) == Just "Metal")
|
||||
>>= (^? Data.field "GenreId" . Data._ColumnFieldNumber)
|
||||
|
||||
let albumIds =
|
||||
Data.tracksRows
|
||||
_tdTracksRows
|
||||
& filter (\track -> (track ^? Data.field "GenreId" . Data._ColumnFieldNumber) == genreId)
|
||||
& map (\track -> (track ^? Data.field "AlbumId" . Data._ColumnFieldNumber))
|
||||
& HashSet.fromList
|
||||
|
||||
let artists =
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
& filter (\album -> HashSet.member (album ^? Data.field "AlbumId" . Data._ColumnFieldNumber) albumIds)
|
||||
& mapMaybe (\album -> album ^? Data.field "ArtistId" . Data._ColumnFieldNumber)
|
||||
& HashSet.fromList
|
||||
& HashSet.toList
|
||||
& mapMaybe (\artistId -> HashMap.lookup artistId Data.artistsRowsById)
|
||||
& mapMaybe (\artistId -> HashMap.lookup artistId _tdArtistsRowsById)
|
||||
& sortOn (^? Data.field "ArtistId")
|
||||
|
||||
Data.responseRows receivedArtists `rowsShouldBe` artists
|
||||
@ -282,37 +283,37 @@ spec api sourceName config comparisonCapabilities = describe "Filtering in Queri
|
||||
|
||||
it "can filter by comparing against multiple columns in a related table" $ do
|
||||
let where' =
|
||||
Exists (RelatedTable Data.albumsRelationshipName) $
|
||||
Exists (RelatedTable _tdAlbumsRelationshipName) $
|
||||
And
|
||||
[ ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "AlbumId") (ScalarValue (Number 1)),
|
||||
ApplyBinaryComparisonOperator Equal (Data.currentComparisonColumn "Title") (ScalarValue (String "Let There Be Rock"))
|
||||
]
|
||||
let query =
|
||||
artistsQueryRequest
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships]
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships]
|
||||
& qrQuery . qWhere ?~ where'
|
||||
receivedArtists <- Data.sortResponseRowsBy "ArtistId" <$> (api // _query) sourceName config query
|
||||
|
||||
let albums =
|
||||
Data.albumsRows
|
||||
_tdAlbumsRows
|
||||
& filter (\album -> (album ^? Data.field "AlbumId" . Data._ColumnFieldNumber) == Just 1 && (album ^? Data.field "Title" . Data._ColumnFieldString) == Just "Let There Be Rock")
|
||||
|
||||
let artists =
|
||||
Data.artistsRows
|
||||
_tdArtistsRows
|
||||
& filter (\artist -> isJust $ find (\album -> (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) == (artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber)) albums)
|
||||
& sortOn (^? Data.field "ArtistId")
|
||||
|
||||
Data.responseRows receivedArtists `rowsShouldBe` artists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
where
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdArtistsTableName [] query
|
||||
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.artistsTableName [] query
|
||||
|
||||
albumsQueryRequest :: QueryRequest
|
||||
albumsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.albumsTableName [] query
|
||||
albumsQueryRequest :: QueryRequest
|
||||
albumsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdAlbumsTableName [] query
|
||||
|
@ -14,19 +14,20 @@ import Data.Ord (Down (..))
|
||||
import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Capabilities -> Spec
|
||||
spec api sourceName config Capabilities {..} = describe "Order By in Queries" $ do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Capabilities -> Spec
|
||||
spec TestData {..} api sourceName config Capabilities {..} = describe "Order By in Queries" $ do
|
||||
it "can order results in ascending order" $ do
|
||||
let orderBy = OrderBy mempty $ Data.orderByColumn [] "Title" Ascending :| []
|
||||
let query = albumsQueryRequest & qrQuery . qOrderBy ?~ orderBy
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums = sortOn (^? Data.field "Title") Data.albumsRows
|
||||
let expectedAlbums = sortOn (^? Data.field "Title") _tdAlbumsRows
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
@ -35,7 +36,7 @@ spec api sourceName config Capabilities {..} = describe "Order By in Queries" $
|
||||
let query = albumsQueryRequest & qrQuery . qOrderBy ?~ orderBy
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums = sortOn (Down . (^? Data.field "Title")) Data.albumsRows
|
||||
let expectedAlbums = sortOn (Down . (^? Data.field "Title")) _tdAlbumsRows
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
@ -45,216 +46,213 @@ spec api sourceName config Capabilities {..} = describe "Order By in Queries" $
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
let expectedAlbums =
|
||||
sortOn (\album -> (album ^? Data.field "ArtistId", Down (album ^? Data.field "Title"))) Data.albumsRows
|
||||
sortOn (\album -> (album ^? Data.field "ArtistId", Down (album ^? Data.field "Title"))) _tdAlbumsRows
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
when (isJust _cRelationships) $ orderByWithRelationshipsSpec api sourceName config
|
||||
when (isJust _cRelationships) . describe "involving relationships" $ do
|
||||
it "can order results by a column in a related table" $ do
|
||||
let orderByRelations = HashMap.fromList [(_tdArtistRelationshipName, OrderByRelation Nothing mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ Data.orderByColumn [_tdArtistRelationshipName] "Name" Ascending :| []
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [_tdArtistRelationshipName] _tdAlbumsTableRelationships]
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
orderByWithRelationshipsSpec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Spec
|
||||
orderByWithRelationshipsSpec api sourceName config = describe "involving relationships" $ do
|
||||
it "can order results by a column in a related table" $ do
|
||||
let orderByRelations = HashMap.fromList [(Data.artistRelationshipName, OrderByRelation Nothing mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ Data.orderByColumn [Data.artistRelationshipName] "Name" Ascending :| []
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [Data.artistRelationshipName] Data.albumsTableRelationships]
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
let getRelatedArtist (album :: HashMap FieldName FieldValue) =
|
||||
(album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>= \artistId -> _tdArtistsRowsById ^? ix artistId
|
||||
|
||||
let getRelatedArtist (album :: HashMap FieldName FieldValue) =
|
||||
(album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>= \artistId -> Data.artistsRowsById ^? ix artistId
|
||||
let expectedAlbums =
|
||||
_tdAlbumsRows
|
||||
& fmap (\album -> (album, getRelatedArtist album))
|
||||
& sortOn ((^? _2 . _Just . Data.field "Name"))
|
||||
& fmap fst
|
||||
|
||||
let expectedAlbums =
|
||||
Data.albumsRows
|
||||
& fmap (\album -> (album, getRelatedArtist album))
|
||||
& sortOn ((^? _2 . _Just . Data.field "Name"))
|
||||
& fmap fst
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
it "can order results by a column in a related table where the related table is filtered" $ do
|
||||
let artistTableFilter = ApplyBinaryComparisonOperator GreaterThan (Data.currentComparisonColumn "Name") (ScalarValue $ String "N")
|
||||
let orderByRelations = HashMap.fromList [(_tdArtistRelationshipName, OrderByRelation (Just artistTableFilter) mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ Data.orderByColumn [_tdArtistRelationshipName] "Name" Ascending :| []
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [_tdArtistRelationshipName] _tdAlbumsTableRelationships]
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
it "can order results by a column in a related table where the related table is filtered" $ do
|
||||
let artistTableFilter = ApplyBinaryComparisonOperator GreaterThan (Data.currentComparisonColumn "Name") (ScalarValue $ String "N")
|
||||
let orderByRelations = HashMap.fromList [(Data.artistRelationshipName, OrderByRelation (Just artistTableFilter) mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ Data.orderByColumn [Data.artistRelationshipName] "Name" Ascending :| []
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [Data.artistRelationshipName] Data.albumsTableRelationships]
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
let getRelatedArtist (album :: HashMap FieldName FieldValue) = do
|
||||
artist <- (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>= \artistId -> _tdArtistsRowsById ^? ix artistId
|
||||
if artist ^? Data.field "Name" . Data._ColumnFieldString > Just "N"
|
||||
then pure artist
|
||||
else Nothing
|
||||
|
||||
let getRelatedArtist (album :: HashMap FieldName FieldValue) = do
|
||||
artist <- (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>= \artistId -> Data.artistsRowsById ^? ix artistId
|
||||
if artist ^? Data.field "Name" . Data._ColumnFieldString > Just "N"
|
||||
then pure artist
|
||||
else Nothing
|
||||
let expectedAlbums =
|
||||
_tdAlbumsRows
|
||||
& fmap (\album -> (album, getRelatedArtist album))
|
||||
& sortOn ((^? _2 . _Just . Data.field "Name") >>> toNullsLastOrdering)
|
||||
& fmap fst
|
||||
|
||||
let expectedAlbums =
|
||||
Data.albumsRows
|
||||
& fmap (\album -> (album, getRelatedArtist album))
|
||||
& sortOn ((^? _2 . _Just . Data.field "Name") >>> toNullsLastOrdering)
|
||||
& fmap fst
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
it "can order results by a column in a related table of a related table" $ do
|
||||
let orderByRelations =
|
||||
HashMap.fromList
|
||||
[ ( Data.albumRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
( HashMap.fromList
|
||||
[ ( Data.artistRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
mempty
|
||||
)
|
||||
]
|
||||
)
|
||||
)
|
||||
]
|
||||
let orderBy =
|
||||
OrderBy orderByRelations $
|
||||
NonEmpty.fromList
|
||||
[ Data.orderByColumn [Data.albumRelationshipName, Data.artistRelationshipName] "Name" Descending,
|
||||
Data.orderByColumn [] "Name" Ascending
|
||||
it "can order results by a column in a related table of a related table" $ do
|
||||
let orderByRelations =
|
||||
HashMap.fromList
|
||||
[ ( _tdAlbumRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
( HashMap.fromList
|
||||
[ ( _tdArtistRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
mempty
|
||||
)
|
||||
]
|
||||
)
|
||||
)
|
||||
]
|
||||
let query =
|
||||
tracksQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships
|
||||
.~ [ Data.onlyKeepRelationships [Data.albumRelationshipName] Data.tracksTableRelationships,
|
||||
Data.onlyKeepRelationships [Data.artistRelationshipName] Data.albumsTableRelationships
|
||||
]
|
||||
receivedTracks <- (api // _query) sourceName config query
|
||||
let orderBy =
|
||||
OrderBy orderByRelations $
|
||||
NonEmpty.fromList
|
||||
[ Data.orderByColumn [_tdAlbumRelationshipName, _tdArtistRelationshipName] "Name" Descending,
|
||||
Data.orderByColumn [] "Name" Ascending
|
||||
]
|
||||
let query =
|
||||
tracksQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships
|
||||
.~ [ Data.onlyKeepRelationships [_tdAlbumRelationshipName] _tdTracksTableRelationships,
|
||||
Data.onlyKeepRelationships [_tdArtistRelationshipName] _tdAlbumsTableRelationships
|
||||
]
|
||||
receivedTracks <- (api // _query) sourceName config query
|
||||
|
||||
let getRelatedArtist (track :: HashMap FieldName FieldValue) = do
|
||||
albumId <- track ^? Data.field "AlbumId" . Data._ColumnFieldNumber
|
||||
album <- Data.albumsRowsById ^? ix albumId
|
||||
artistId <- album ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
Data.artistsRowsById ^? ix artistId
|
||||
let getRelatedArtist (track :: HashMap FieldName FieldValue) = do
|
||||
albumId <- track ^? Data.field "AlbumId" . Data._ColumnFieldNumber
|
||||
album <- _tdAlbumsRowsById ^? ix albumId
|
||||
artistId <- album ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
_tdArtistsRowsById ^? ix artistId
|
||||
|
||||
let expectedTracks =
|
||||
Data.tracksRows
|
||||
& fmap (\track -> (Data.filterColumnsByQueryFields (_qrQuery tracksQueryRequest) track, getRelatedArtist track, track ^? Data.field "Name"))
|
||||
& sortOn (\row -> (Down (row ^? _2 . _Just . Data.field "Name"), row ^. _3))
|
||||
& fmap (^. _1)
|
||||
let expectedTracks =
|
||||
_tdTracksRows
|
||||
& fmap (\track -> (Data.filterColumnsByQueryFields (_qrQuery tracksQueryRequest) track, getRelatedArtist track, track ^? Data.field "Name"))
|
||||
& sortOn (\row -> (Down (row ^? _2 . _Just . Data.field "Name"), row ^. _3))
|
||||
& fmap (^. _1)
|
||||
|
||||
Data.responseRows receivedTracks `rowsShouldBe` expectedTracks
|
||||
_qrAggregates receivedTracks `jsonShouldBe` Nothing
|
||||
Data.responseRows receivedTracks `rowsShouldBe` expectedTracks
|
||||
_qrAggregates receivedTracks `jsonShouldBe` Nothing
|
||||
|
||||
it "can order results by an aggregate of a related table" $ do
|
||||
let orderByRelations = HashMap.fromList [(Data.albumsRelationshipName, OrderByRelation Nothing mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ OrderByElement [Data.albumsRelationshipName] OrderByStarCountAggregate Descending :| []
|
||||
let query =
|
||||
artistsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships]
|
||||
receivedArtists <- (api // _query) sourceName config query
|
||||
it "can order results by an aggregate of a related table" $ do
|
||||
let orderByRelations = HashMap.fromList [(_tdAlbumsRelationshipName, OrderByRelation Nothing mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ OrderByElement [_tdAlbumsRelationshipName] OrderByStarCountAggregate Descending :| []
|
||||
let query =
|
||||
artistsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships]
|
||||
receivedArtists <- (api // _query) sourceName config query
|
||||
|
||||
let getAlbumsCount (artist :: HashMap FieldName FieldValue) = do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums = filter (\album -> album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId) Data.albumsRows
|
||||
pure $ length albums
|
||||
let getAlbumsCount (artist :: HashMap FieldName FieldValue) = do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums = filter (\album -> album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId) _tdAlbumsRows
|
||||
pure $ length albums
|
||||
|
||||
let expectedArtists =
|
||||
Data.artistsRows
|
||||
& fmap (\artist -> (artist, getAlbumsCount artist))
|
||||
& sortOn (Down . (^. _2))
|
||||
& fmap fst
|
||||
let expectedArtists =
|
||||
_tdArtistsRows
|
||||
& fmap (\artist -> (artist, getAlbumsCount artist))
|
||||
& sortOn (Down . (^. _2))
|
||||
& fmap fst
|
||||
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
it "can order results by an aggregate of a related table where the related table is filtered" $ do
|
||||
let albumTableFilter = ApplyBinaryComparisonOperator GreaterThan (Data.currentComparisonColumn "Title") (ScalarValue $ String "N")
|
||||
let orderByRelations = HashMap.fromList [(Data.albumsRelationshipName, OrderByRelation (Just albumTableFilter) mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ OrderByElement [Data.albumsRelationshipName] OrderByStarCountAggregate Descending :| []
|
||||
let query =
|
||||
artistsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships]
|
||||
receivedArtists <- (api // _query) sourceName config query
|
||||
it "can order results by an aggregate of a related table where the related table is filtered" $ do
|
||||
let albumTableFilter = ApplyBinaryComparisonOperator GreaterThan (Data.currentComparisonColumn "Title") (ScalarValue $ String "N")
|
||||
let orderByRelations = HashMap.fromList [(_tdAlbumsRelationshipName, OrderByRelation (Just albumTableFilter) mempty)]
|
||||
let orderBy = OrderBy orderByRelations $ OrderByElement [_tdAlbumsRelationshipName] OrderByStarCountAggregate Descending :| []
|
||||
let query =
|
||||
artistsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships .~ [Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships]
|
||||
receivedArtists <- (api // _query) sourceName config query
|
||||
|
||||
let getAlbumsCount (artist :: HashMap FieldName FieldValue) = do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums = filter (\album -> album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId && album ^? Data.field "Title" . Data._ColumnFieldString > Just "N") Data.albumsRows
|
||||
pure $ length albums
|
||||
let getAlbumsCount (artist :: HashMap FieldName FieldValue) = do
|
||||
artistId <- artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums = filter (\album -> album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId && album ^? Data.field "Title" . Data._ColumnFieldString > Just "N") _tdAlbumsRows
|
||||
pure $ length albums
|
||||
|
||||
let expectedArtists =
|
||||
Data.artistsRows
|
||||
& fmap (\artist -> (artist, getAlbumsCount artist))
|
||||
& sortOn (Down . (^. _2))
|
||||
& fmap fst
|
||||
let expectedArtists =
|
||||
_tdArtistsRows
|
||||
& fmap (\artist -> (artist, getAlbumsCount artist))
|
||||
& sortOn (Down . (^. _2))
|
||||
& fmap fst
|
||||
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
it "can order results by an aggregate of a related table's related table" $ do
|
||||
let orderByRelations =
|
||||
HashMap.fromList
|
||||
[ ( Data.artistRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
( HashMap.fromList
|
||||
[ ( Data.albumsRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
mempty
|
||||
)
|
||||
]
|
||||
)
|
||||
)
|
||||
]
|
||||
let orderBy =
|
||||
OrderBy orderByRelations $
|
||||
NonEmpty.fromList
|
||||
[ OrderByElement [Data.artistRelationshipName, Data.albumsRelationshipName] OrderByStarCountAggregate Descending,
|
||||
OrderByElement [] (OrderByColumn $ ColumnName "Title") Ascending
|
||||
it "can order results by an aggregate of a related table's related table" $ do
|
||||
let orderByRelations =
|
||||
HashMap.fromList
|
||||
[ ( _tdArtistRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
( HashMap.fromList
|
||||
[ ( _tdAlbumsRelationshipName,
|
||||
OrderByRelation
|
||||
Nothing
|
||||
mempty
|
||||
)
|
||||
]
|
||||
)
|
||||
)
|
||||
]
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships
|
||||
.~ [ Data.onlyKeepRelationships [Data.artistRelationshipName] Data.albumsTableRelationships,
|
||||
Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships
|
||||
]
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
let orderBy =
|
||||
OrderBy orderByRelations $
|
||||
NonEmpty.fromList
|
||||
[ OrderByElement [_tdArtistRelationshipName, _tdAlbumsRelationshipName] OrderByStarCountAggregate Descending,
|
||||
OrderByElement [] (OrderByColumn $ ColumnName "Title") Ascending
|
||||
]
|
||||
let query =
|
||||
albumsQueryRequest
|
||||
& qrQuery . qOrderBy ?~ orderBy
|
||||
& qrTableRelationships
|
||||
.~ [ Data.onlyKeepRelationships [_tdArtistRelationshipName] _tdAlbumsTableRelationships,
|
||||
Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships
|
||||
]
|
||||
receivedAlbums <- (api // _query) sourceName config query
|
||||
|
||||
let getTotalArtistAlbumsCount (album :: HashMap FieldName FieldValue) = do
|
||||
artistId <- album ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums = filter (\album' -> album' ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId) Data.albumsRows
|
||||
pure $ length albums
|
||||
let getTotalArtistAlbumsCount (album :: HashMap FieldName FieldValue) = do
|
||||
artistId <- album ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
let albums = filter (\album' -> album' ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId) _tdAlbumsRows
|
||||
pure $ length albums
|
||||
|
||||
let expectedArtists =
|
||||
Data.albumsRows
|
||||
& fmap (\album -> (album, getTotalArtistAlbumsCount album, album ^? Data.field "Title"))
|
||||
& sortOn (\row -> (Down (row ^. _2), (row ^. _3)))
|
||||
& fmap (^. _1)
|
||||
let expectedArtists =
|
||||
_tdAlbumsRows
|
||||
& fmap (\album -> (album, getTotalArtistAlbumsCount album, album ^? Data.field "Title"))
|
||||
& sortOn (\row -> (Down (row ^. _2), (row ^. _3)))
|
||||
& fmap (^. _1)
|
||||
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedArtists
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
where
|
||||
albumsQueryRequest :: QueryRequest
|
||||
albumsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdAlbumsTableName [] query
|
||||
|
||||
albumsQueryRequest :: QueryRequest
|
||||
albumsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.albumsTableName [] query
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdArtistsTableName [] query
|
||||
|
||||
artistsQueryRequest :: QueryRequest
|
||||
artistsQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.artistsTableName [] query
|
||||
|
||||
tracksQueryRequest :: QueryRequest
|
||||
tracksQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("TrackId", Data.columnField "TrackId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest Data.tracksTableName [] query
|
||||
tracksQueryRequest :: QueryRequest
|
||||
tracksQueryRequest =
|
||||
let fields = Data.mkFieldsMap [("TrackId", Data.columnField "TrackId"), ("Name", Data.columnField "Name")]
|
||||
query = Data.emptyQuery & qFields ?~ fields
|
||||
in QueryRequest _tdTracksTableName [] query
|
||||
|
||||
data NullableOrdered a
|
||||
= NullFirst
|
||||
|
@ -11,24 +11,25 @@ import Data.Maybe (maybeToList)
|
||||
import Hasura.Backends.DataConnector.API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Expectations (jsonShouldBe, rowsShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Prelude
|
||||
|
||||
spec :: Client IO (NamedRoutes Routes) -> SourceName -> Config -> Maybe SubqueryComparisonCapabilities -> Spec
|
||||
spec api sourceName config subqueryComparisonCapabilities = describe "Relationship Queries" $ do
|
||||
spec :: TestData -> Client IO (NamedRoutes Routes) -> SourceName -> Config -> Maybe SubqueryComparisonCapabilities -> Spec
|
||||
spec TestData {..} api sourceName config subqueryComparisonCapabilities = describe "Relationship Queries" $ do
|
||||
it "perform an object relationship query by joining artist to albums" $ do
|
||||
let query = albumsWithArtistQuery id
|
||||
receivedAlbums <- Data.sortResponseRowsBy "AlbumId" <$> (api // _query) sourceName config query
|
||||
|
||||
let joinInArtist (album :: HashMap FieldName FieldValue) =
|
||||
let artist = (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>= \artistId -> Data.artistsRowsById ^? ix artistId
|
||||
let artist = (album ^? Data.field "ArtistId" . Data._ColumnFieldNumber) >>= \artistId -> _tdArtistsRowsById ^? ix artistId
|
||||
artistPropVal = maybeToList artist
|
||||
in Data.insertField "Artist" (mkSubqueryResponse artistPropVal) album
|
||||
let removeArtistId = Data.deleteField "ArtistId"
|
||||
|
||||
let expectedAlbums = (removeArtistId . joinInArtist) <$> Data.albumsRows
|
||||
let expectedAlbums = (removeArtistId . joinInArtist) <$> _tdAlbumsRows
|
||||
Data.responseRows receivedAlbums `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedAlbums `jsonShouldBe` Nothing
|
||||
|
||||
@ -39,11 +40,11 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
let joinInAlbums (artist :: HashMap FieldName FieldValue) =
|
||||
let artistId = artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
albumFilter artistId' album = album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId'
|
||||
albums = maybe [] (\artistId' -> filter (albumFilter artistId') Data.albumsRows) artistId
|
||||
albums = maybe [] (\artistId' -> filter (albumFilter artistId') _tdAlbumsRows) artistId
|
||||
albums' = Data.deleteField "ArtistId" <$> albums
|
||||
in Data.insertField "Albums" (mkSubqueryResponse albums') artist
|
||||
|
||||
let expectedAlbums = joinInAlbums <$> Data.artistsRows
|
||||
let expectedAlbums = joinInAlbums <$> _tdArtistsRows
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
@ -55,12 +56,12 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
let joinInAlbums (artist :: HashMap FieldName FieldValue) = do
|
||||
let artistId = artist ^? Data.field "ArtistId" . Data._ColumnFieldNumber
|
||||
albumFilter artistId' album = album ^? Data.field "ArtistId" . Data._ColumnFieldNumber == Just artistId'
|
||||
albums = maybe [] (\artistId' -> filter (albumFilter artistId') Data.albumsRows) artistId
|
||||
albums = maybe [] (\artistId' -> filter (albumFilter artistId') _tdAlbumsRows) artistId
|
||||
paginatedAlbums = albums & sortOn (^? Data.field "ArtistId") & drop 1 & take 2
|
||||
paginatedAlbums' = Data.deleteField "ArtistId" <$> paginatedAlbums
|
||||
in Data.insertField "Albums" (mkSubqueryResponse paginatedAlbums') artist
|
||||
|
||||
let expectedAlbums = joinInAlbums <$> Data.artistsRows
|
||||
let expectedAlbums = joinInAlbums <$> _tdArtistsRows
|
||||
Data.responseRows receivedArtists `rowsShouldBe` expectedAlbums
|
||||
_qrAggregates receivedArtists `jsonShouldBe` Nothing
|
||||
|
||||
@ -72,7 +73,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
-- This sort of thing would come from a permissions filter on Customer that looks like:
|
||||
-- { SupportRep: { Country: { _ceq: [ "$", "Country" ] } } }
|
||||
let where' =
|
||||
Exists (RelatedTable Data.supportRepRelationshipName) $
|
||||
Exists (RelatedTable _tdSupportRepRelationshipName) $
|
||||
ApplyBinaryComparisonOperator
|
||||
Equal
|
||||
(Data.currentComparisonColumn "Country")
|
||||
@ -81,7 +82,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
receivedCustomers <- Data.sortResponseRowsBy "CustomerId" <$> (api // _query) sourceName config query
|
||||
|
||||
let joinInSupportRep (customer :: HashMap FieldName FieldValue) =
|
||||
let supportRep = (customer ^? Data.field "SupportRepId" . Data._ColumnFieldNumber) >>= \employeeId -> Data.employeesRowsById ^? ix employeeId
|
||||
let supportRep = (customer ^? Data.field "SupportRepId" . Data._ColumnFieldNumber) >>= \employeeId -> _tdEmployeesRowsById ^? ix employeeId
|
||||
supportRepPropVal = maybeToList $ Data.filterColumnsByQueryFields employeesQuery <$> supportRep
|
||||
in Data.insertField "SupportRep" (mkSubqueryResponse supportRepPropVal) customer
|
||||
|
||||
@ -90,7 +91,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
supportRepCountry = customer ^.. Data.field "SupportRep" . subqueryRows . Data.field "Country" . Data._ColumnFieldString
|
||||
in maybe False (`elem` supportRepCountry) customerCountry
|
||||
|
||||
let expectedCustomers = filter filterCustomersBySupportRepCountry $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInSupportRep <$> Data.customersRows
|
||||
let expectedCustomers = filter filterCustomersBySupportRepCountry $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInSupportRep <$> _tdCustomersRows
|
||||
Data.responseRows receivedCustomers `rowsShouldBe` expectedCustomers
|
||||
_qrAggregates receivedCustomers `jsonShouldBe` Nothing
|
||||
|
||||
@ -100,7 +101,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
-- This sort of thing would come from a permissions filter on Employees that looks like:
|
||||
-- { SupportRepForCustomers: { Country: { _ceq: [ "$", "Country" ] } } }
|
||||
let where' =
|
||||
Exists (RelatedTable Data.supportRepForCustomersRelationshipName) $
|
||||
Exists (RelatedTable _tdSupportRepForCustomersRelationshipName) $
|
||||
ApplyBinaryComparisonOperator
|
||||
Equal
|
||||
(Data.currentComparisonColumn "Country")
|
||||
@ -111,7 +112,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
let joinInCustomers (employee :: HashMap FieldName FieldValue) =
|
||||
let employeeId = employee ^? Data.field "EmployeeId" . Data._ColumnFieldNumber
|
||||
customerFilter employeeId' customer = customer ^? Data.field "SupportRepId" . Data._ColumnFieldNumber == Just employeeId'
|
||||
customers = maybe [] (\employeeId' -> filter (customerFilter employeeId') Data.customersRows) employeeId
|
||||
customers = maybe [] (\employeeId' -> filter (customerFilter employeeId') _tdCustomersRows) employeeId
|
||||
customers' = Data.filterColumnsByQueryFields customersQuery <$> customers
|
||||
in Data.insertField "SupportRepForCustomers" (mkSubqueryResponse customers') employee
|
||||
|
||||
@ -120,7 +121,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
customerCountries = employee ^.. Data.field "SupportRepForCustomers" . subqueryRows . Data.field "Country" . Data._ColumnFieldString
|
||||
in maybe False (`elem` customerCountries) employeeCountry
|
||||
|
||||
let expectedEmployees = filter filterEmployeesByCustomerCountry $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInCustomers <$> Data.employeesRows
|
||||
let expectedEmployees = filter filterEmployeesByCustomerCountry $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInCustomers <$> _tdEmployeesRows
|
||||
Data.responseRows receivedEmployees `rowsShouldBe` expectedEmployees
|
||||
_qrAggregates receivedEmployees `jsonShouldBe` Nothing
|
||||
|
||||
@ -130,7 +131,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
-- This Employee table permissions filter would look like:
|
||||
-- { FirstName: { _cgt: ["LastName"] } }
|
||||
let customersWhere =
|
||||
Exists (RelatedTable Data.supportRepRelationshipName) $
|
||||
Exists (RelatedTable _tdSupportRepRelationshipName) $
|
||||
And
|
||||
[ ( ApplyBinaryComparisonOperator
|
||||
GreaterThan
|
||||
@ -152,7 +153,7 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
let joinInSupportRep (customer :: HashMap FieldName FieldValue) =
|
||||
let supportRep = do
|
||||
employeeId <- (customer ^? Data.field "SupportRepId" . Data._ColumnFieldNumber)
|
||||
employee <- Data.employeesRowsById ^? ix employeeId
|
||||
employee <- _tdEmployeesRowsById ^? ix employeeId
|
||||
firstName <- employee ^? Data.field "FirstName"
|
||||
lastName <- employee ^? Data.field "LastName"
|
||||
if firstName > lastName then pure employee else Nothing
|
||||
@ -163,95 +164,95 @@ spec api sourceName config subqueryComparisonCapabilities = describe "Relationsh
|
||||
let supportRep = customer ^.. Data.field "SupportRep" . subqueryRows
|
||||
in not (null supportRep)
|
||||
|
||||
let expectedCustomers = filter filterCustomersBySupportRepExistence $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInSupportRep <$> Data.customersRows
|
||||
let expectedCustomers = filter filterCustomersBySupportRepExistence $ Data.filterColumnsByQueryFields (query ^. qrQuery) . joinInSupportRep <$> _tdCustomersRows
|
||||
Data.responseRows receivedCustomers `rowsShouldBe` expectedCustomers
|
||||
_qrAggregates receivedCustomers `jsonShouldBe` Nothing
|
||||
where
|
||||
albumsWithArtistQuery :: (Query -> Query) -> QueryRequest
|
||||
albumsWithArtistQuery modifySubquery =
|
||||
let artistsSubquery = modifySubquery artistsQuery
|
||||
fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("AlbumId", Data.columnField "AlbumId"),
|
||||
("Title", Data.columnField "Title"),
|
||||
("Artist", RelField $ RelationshipField _tdArtistRelationshipName artistsSubquery)
|
||||
]
|
||||
query = albumsQuery & qFields ?~ fields
|
||||
in QueryRequest _tdAlbumsTableName [Data.onlyKeepRelationships [_tdArtistRelationshipName] _tdAlbumsTableRelationships] query
|
||||
|
||||
albumsWithArtistQuery :: (Query -> Query) -> QueryRequest
|
||||
albumsWithArtistQuery modifySubquery =
|
||||
let artistsSubquery = modifySubquery artistsQuery
|
||||
fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("AlbumId", Data.columnField "AlbumId"),
|
||||
("Title", Data.columnField "Title"),
|
||||
("Artist", RelField $ RelationshipField Data.artistRelationshipName artistsSubquery)
|
||||
]
|
||||
query = albumsQuery & qFields ?~ fields
|
||||
in QueryRequest Data.albumsTableName [Data.onlyKeepRelationships [Data.artistRelationshipName] Data.albumsTableRelationships] query
|
||||
artistsWithAlbumsQuery :: (Query -> Query) -> QueryRequest
|
||||
artistsWithAlbumsQuery modifySubquery =
|
||||
let albumFields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("Title", Data.columnField "Title")]
|
||||
albumsSort = OrderBy mempty $ Data.orderByColumn [] "AlbumId" Ascending :| []
|
||||
albumsSubquery = albumsQuery & qFields ?~ albumFields & qOrderBy ?~ albumsSort & modifySubquery
|
||||
fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("ArtistId", Data.columnField "ArtistId"),
|
||||
("Name", Data.columnField "Name"),
|
||||
("Albums", RelField $ RelationshipField _tdAlbumsRelationshipName albumsSubquery)
|
||||
]
|
||||
query = artistsQuery & qFields ?~ fields
|
||||
in QueryRequest _tdArtistsTableName [Data.onlyKeepRelationships [_tdAlbumsRelationshipName] _tdArtistsTableRelationships] query
|
||||
|
||||
artistsWithAlbumsQuery :: (Query -> Query) -> QueryRequest
|
||||
artistsWithAlbumsQuery modifySubquery =
|
||||
let albumFields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("Title", Data.columnField "Title")]
|
||||
albumsSort = OrderBy mempty $ Data.orderByColumn [] "AlbumId" Ascending :| []
|
||||
albumsSubquery = albumsQuery & qFields ?~ albumFields & qOrderBy ?~ albumsSort & modifySubquery
|
||||
fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("ArtistId", Data.columnField "ArtistId"),
|
||||
("Name", Data.columnField "Name"),
|
||||
("Albums", RelField $ RelationshipField Data.albumsRelationshipName albumsSubquery)
|
||||
]
|
||||
query = artistsQuery & qFields ?~ fields
|
||||
in QueryRequest Data.artistsTableName [Data.onlyKeepRelationships [Data.albumsRelationshipName] Data.artistsTableRelationships] query
|
||||
employeesWithCustomersQuery :: (Query -> Query) -> QueryRequest
|
||||
employeesWithCustomersQuery modifySubquery =
|
||||
let customersSort = OrderBy mempty $ Data.orderByColumn [] "CustomerId" Ascending :| []
|
||||
customersSubquery = customersQuery & qOrderBy ?~ customersSort & modifySubquery
|
||||
fields =
|
||||
Data.queryFields employeesQuery
|
||||
<> Data.mkFieldsMap
|
||||
[ ("SupportRepForCustomers", RelField $ RelationshipField _tdSupportRepForCustomersRelationshipName customersSubquery)
|
||||
]
|
||||
query = employeesQuery & qFields ?~ fields
|
||||
in QueryRequest _tdEmployeesTableName [Data.onlyKeepRelationships [_tdSupportRepForCustomersRelationshipName] _tdEmployeesTableRelationships] query
|
||||
|
||||
employeesWithCustomersQuery :: (Query -> Query) -> QueryRequest
|
||||
employeesWithCustomersQuery modifySubquery =
|
||||
let customersSort = OrderBy mempty $ Data.orderByColumn [] "CustomerId" Ascending :| []
|
||||
customersSubquery = customersQuery & qOrderBy ?~ customersSort & modifySubquery
|
||||
fields =
|
||||
Data.queryFields employeesQuery
|
||||
<> Data.mkFieldsMap
|
||||
[ ("SupportRepForCustomers", RelField $ RelationshipField Data.supportRepForCustomersRelationshipName customersSubquery)
|
||||
]
|
||||
query = employeesQuery & qFields ?~ fields
|
||||
in QueryRequest Data.employeesTableName [Data.onlyKeepRelationships [Data.supportRepForCustomersRelationshipName] Data.employeesTableRelationships] query
|
||||
customersWithSupportRepQuery :: (Query -> Query) -> QueryRequest
|
||||
customersWithSupportRepQuery modifySubquery =
|
||||
let supportRepSubquery = employeesQuery & modifySubquery
|
||||
fields =
|
||||
Data.queryFields customersQuery
|
||||
<> Data.mkFieldsMap
|
||||
[ ("SupportRep", RelField $ RelationshipField _tdSupportRepRelationshipName supportRepSubquery)
|
||||
]
|
||||
query = customersQuery & qFields ?~ fields
|
||||
in QueryRequest _tdCustomersTableName [Data.onlyKeepRelationships [_tdSupportRepRelationshipName] _tdCustomersTableRelationships] query
|
||||
|
||||
customersWithSupportRepQuery :: (Query -> Query) -> QueryRequest
|
||||
customersWithSupportRepQuery modifySubquery =
|
||||
let supportRepSubquery = employeesQuery & modifySubquery
|
||||
fields =
|
||||
Data.queryFields customersQuery
|
||||
<> Data.mkFieldsMap
|
||||
[ ("SupportRep", RelField $ RelationshipField Data.supportRepRelationshipName supportRepSubquery)
|
||||
]
|
||||
query = customersQuery & qFields ?~ fields
|
||||
in QueryRequest Data.customersTableName [Data.onlyKeepRelationships [Data.supportRepRelationshipName] Data.customersTableRelationships] query
|
||||
artistsQuery :: Query
|
||||
artistsQuery =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
|
||||
artistsQuery :: Query
|
||||
artistsQuery =
|
||||
let fields = Data.mkFieldsMap [("ArtistId", Data.columnField "ArtistId"), ("Name", Data.columnField "Name")]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
albumsQuery :: Query
|
||||
albumsQuery =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
|
||||
albumsQuery :: Query
|
||||
albumsQuery =
|
||||
let fields = Data.mkFieldsMap [("AlbumId", Data.columnField "AlbumId"), ("ArtistId", Data.columnField "ArtistId"), ("Title", Data.columnField "Title")]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
customersQuery :: Query
|
||||
customersQuery =
|
||||
let fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("CustomerId", Data.columnField "CustomerId"),
|
||||
("FirstName", Data.columnField "FirstName"),
|
||||
("LastName", Data.columnField "LastName"),
|
||||
("Country", Data.columnField "Country"),
|
||||
("SupportRepId", Data.columnField "SupportRepId")
|
||||
]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
|
||||
customersQuery :: Query
|
||||
customersQuery =
|
||||
let fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("CustomerId", Data.columnField "CustomerId"),
|
||||
("FirstName", Data.columnField "FirstName"),
|
||||
("LastName", Data.columnField "LastName"),
|
||||
("Country", Data.columnField "Country"),
|
||||
("SupportRepId", Data.columnField "SupportRepId")
|
||||
]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
employeesQuery :: Query
|
||||
employeesQuery =
|
||||
let fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("EmployeeId", Data.columnField "EmployeeId"),
|
||||
("FirstName", Data.columnField "FirstName"),
|
||||
("LastName", Data.columnField "LastName"),
|
||||
("Country", Data.columnField "Country")
|
||||
]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
|
||||
employeesQuery :: Query
|
||||
employeesQuery =
|
||||
let fields =
|
||||
Data.mkFieldsMap
|
||||
[ ("EmployeeId", Data.columnField "EmployeeId"),
|
||||
("FirstName", Data.columnField "FirstName"),
|
||||
("LastName", Data.columnField "LastName"),
|
||||
("Country", Data.columnField "Country")
|
||||
]
|
||||
in Data.emptyQuery & qFields ?~ fields
|
||||
mkSubqueryResponse :: [HashMap FieldName FieldValue] -> FieldValue
|
||||
mkSubqueryResponse rows =
|
||||
mkRelationshipFieldValue $ QueryResponse (Just rows) Nothing
|
||||
|
||||
mkSubqueryResponse :: [HashMap FieldName FieldValue] -> FieldValue
|
||||
mkSubqueryResponse rows =
|
||||
mkRelationshipFieldValue $ QueryResponse (Just rows) Nothing
|
||||
|
||||
subqueryRows :: Traversal' FieldValue (HashMap FieldName FieldValue)
|
||||
subqueryRows = _RelationshipFieldValue . qrRows . _Just . traverse
|
||||
subqueryRows :: Traversal' FieldValue (HashMap FieldName FieldValue)
|
||||
subqueryRows = _RelationshipFieldValue . qrRows . _Just . traverse
|
||||
|
@ -7,7 +7,7 @@ import Data.List (sort, sortOn)
|
||||
import Hasura.Backends.DataConnector.API qualified as API
|
||||
import Servant.API (NamedRoutes)
|
||||
import Servant.Client (Client, (//))
|
||||
import Test.Data qualified as Data
|
||||
import Test.Data (TestData (..))
|
||||
import Test.Expectations (jsonShouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Prelude
|
||||
@ -28,13 +28,13 @@ removeForeignKeys t = t {API._tiForeignKeys = Nothing}
|
||||
extractForeignKeys :: API.TableInfo -> [API.Constraint]
|
||||
extractForeignKeys = foldMap (HashMap.elems . API.unConstraints) . API._tiForeignKeys
|
||||
|
||||
spec :: Client IO (NamedRoutes API.Routes) -> API.SourceName -> API.Config -> Spec
|
||||
spec api sourceName config = describe "schema API" $ do
|
||||
spec :: TestData -> Client IO (NamedRoutes API.Routes) -> API.SourceName -> API.Config -> Spec
|
||||
spec TestData {..} api sourceName config = describe "schema API" $ do
|
||||
it "returns Chinook schema" $ do
|
||||
tables <- (map removeDescription . sortOn API._tiName . API._srTables) <$> (api // API._schema) sourceName config
|
||||
|
||||
-- NOTE: Constraint names arent guaranteed to be the same across
|
||||
-- Chinook backends so we compare Constraints without their names
|
||||
-- independently from the rest of the schema.
|
||||
(map removeForeignKeys tables) `jsonShouldBe` map (removeForeignKeys . removeDescription) Data.schemaTables
|
||||
(map (sort . extractForeignKeys) tables) `jsonShouldBe` map (sort . extractForeignKeys) Data.schemaTables
|
||||
(map removeForeignKeys tables) `jsonShouldBe` map (removeForeignKeys . removeDescription) _tdSchemaTables
|
||||
(map (sort . extractForeignKeys) tables) `jsonShouldBe` map (sort . extractForeignKeys) _tdSchemaTables
|
||||
|
Loading…
Reference in New Issue
Block a user