SQLite Data Connectors HSpec Tests - GDW-183

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5731
GitOrigin-RevId: 0af22a85bd6b1cb8888562e05cde640047e56b41
This commit is contained in:
Lyndon Maydwell 2022-09-07 13:42:20 +10:00 committed by hasura-bot
parent 36860c8fb2
commit cd6fe41b99
14 changed files with 462 additions and 263 deletions

View File

@ -108,6 +108,9 @@ services:
- "65007:8100" - "65007:8100"
volumes: volumes:
- "./dc-agents/sqlite/test/db.chinook.sqlite:/db.chinook.sqlite" - "./dc-agents/sqlite/test/db.chinook.sqlite:/db.chinook.sqlite"
environment:
PRETTY_PRINT_LOGS: y
LOG_LEVEL: debug
volumes: volumes:
citus-data: citus-data:

View File

@ -15,6 +15,8 @@ MSSQL_DBPASSWORD = Hasura1!
CITUS_PORT = 65004 CITUS_PORT = 65004
DC_REFERENCE_PORT = 65005 DC_REFERENCE_PORT = 65005
DC_REFERENCE_AGENT_URL = localhost:$(DC_REFERENCE_PORT)/health DC_REFERENCE_AGENT_URL = localhost:$(DC_REFERENCE_PORT)/health
DC_SQLITE_PORT = 65007
DC_SQLITE_AGENT_URL = localhost:$(DC_SQLITE_PORT)/health
COCKROACH_PORT = 65008 COCKROACH_PORT = 65008
COCKROACH_DBNAME = hasura COCKROACH_DBNAME = hasura
COCKROACH_DBUSER = root COCKROACH_DBUSER = root
@ -128,11 +130,21 @@ spawn-dc-reference-agent:
wait-for-dc-reference-agent: wait-for-dc-reference-agent:
$(DB_UTILS) wait_for_http_success $(DC_REFERENCE_AGENT_URL) "dc-reference-agent" $(DB_UTILS) wait_for_http_success $(DC_REFERENCE_AGENT_URL) "dc-reference-agent"
.PHONY: spawn-sqlite-reference-agent
spawn-sqlite-reference-agent:
docker compose up -d --build dc-sqlite-agent
.PHONY: wait-for-dc-sqlite-agent
## wait-for-dc-sqlite-agent: call health endpoint of DataConnector SQLite agent until it is ready
wait-for-dc-sqlite-agent:
$(DB_UTILS) wait_for_http_success $(DC_SQLITE_AGENT_URL) "dc-sqlite-agent"
.PHONY: start-backends .PHONY: start-backends
## start-backends: start local PostgreSQL, MariaDB, and MS SQL Server in Docker and wait for them to be ready ## start-backends: start local PostgreSQL, MariaDB, and MS SQL Server in Docker and wait for them to be ready
start-backends: \ start-backends: \
spawn-postgres spawn-sqlserver spawn-mysql spawn-citus spawn-dc-reference-agent spawn-cockroach\ spawn-postgres spawn-sqlserver spawn-mysql spawn-citus spawn-dc-reference-agent spawn-dc-sqlite-agent spawn-cockroach\
wait-for-postgres wait-for-sqlserver wait-for-mysql wait-for-citus wait-for-dc-reference-agent wait-for-cockroach wait-for-postgres wait-for-sqlserver wait-for-mysql wait-for-citus wait-for-dc-reference-agent wait-for-cockroach\
wait-for-dc-sqlite-agent wait-for-dc-reference-agent
.PHONY: stop-everything .PHONY: stop-everything
## stop-everything: tear down test databases ## stop-everything: tear down test databases

View File

@ -5,8 +5,11 @@ module Harness.Backend.DataConnector
( -- * Reference Agent ( -- * Reference Agent
setupFixture, setupFixture,
teardown, teardown,
defaultBackendConfig, backendConfigs,
referenceBackendConfig,
sqliteBackendConfig,
chinookStockMetadata, chinookStockMetadata,
TestSourceConfig (..),
-- * Mock Agent -- * Mock Agent
MockConfig (..), MockConfig (..),
@ -31,11 +34,12 @@ import Control.Concurrent.Async (Async)
import Control.Concurrent.Async qualified as Async import Control.Concurrent.Async qualified as Async
import Data.Aeson qualified as Aeson import Data.Aeson qualified as Aeson
import Data.IORef qualified as I import Data.IORef qualified as I
import Data.List.NonEmpty qualified as NE
import Harness.Backend.DataConnector.MockAgent import Harness.Backend.DataConnector.MockAgent
import Harness.GraphqlEngine qualified as GraphqlEngine import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Http (RequestHeaders, healthCheck) import Harness.Http (RequestHeaders, healthCheck)
import Harness.Quoter.Yaml (yaml) import Harness.Quoter.Yaml (yaml)
import Harness.Test.Fixture (BackendType (DataConnector), Options, SetupAction (..), defaultBackendTypeString, defaultSource) import Harness.Test.Fixture (BackendType (DataConnectorMock, DataConnectorReference, DataConnectorSqlite), Options, SetupAction (..), defaultBackendTypeString, defaultSource)
import Harness.TestEnvironment (TestEnvironment) import Harness.TestEnvironment (TestEnvironment)
import Harness.Yaml (shouldReturnYaml) import Harness.Yaml (shouldReturnYaml)
import Hasura.Backends.DataConnector.API qualified as API import Hasura.Backends.DataConnector.API qualified as API
@ -44,18 +48,40 @@ import Test.Hspec (shouldBe)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
defaultBackendConfig :: Aeson.Value data TestSourceConfig = TestSourceConfig
defaultBackendConfig = { typeConfig :: BackendType,
let backendType = defaultBackendTypeString $ DataConnector backendConfig :: Aeson.Value,
sourceConfig :: Aeson.Value,
metadataConfig :: Aeson.Value
}
deriving (Show, Eq)
backendConfigs :: NE.NonEmpty TestSourceConfig
backendConfigs =
TestSourceConfig DataConnectorReference referenceBackendConfig emptyConfig chinookStockMetadata
NE.:| [TestSourceConfig DataConnectorSqlite sqliteBackendConfig sqliteConfig chinookSqliteMetadata]
referenceBackendConfig :: Aeson.Value
referenceBackendConfig =
let backendType = defaultBackendTypeString $ DataConnectorReference
in [yaml| in [yaml|
dataconnector: dataconnector:
*backendType: *backendType:
uri: "http://127.0.0.1:65005/" uri: "http://127.0.0.1:65005/"
|] |]
sqliteBackendConfig :: Aeson.Value
sqliteBackendConfig =
let backendType = defaultBackendTypeString DataConnectorSqlite
in [yaml|
dataconnector:
*backendType:
uri: "http://127.0.0.1:65007/"
|]
mockBackendConfig :: Aeson.Value mockBackendConfig :: Aeson.Value
mockBackendConfig = mockBackendConfig =
let backendType = defaultBackendTypeString $ DataConnector let backendType = defaultBackendTypeString $ DataConnectorMock
agentUri = "http://127.0.0.1:" <> show mockAgentPort <> "/" agentUri = "http://127.0.0.1:" <> show mockAgentPort <> "/"
in [yaml| in [yaml|
dataconnector: dataconnector:
@ -63,6 +89,15 @@ dataconnector:
uri: *agentUri uri: *agentUri
|] |]
emptyConfig :: Aeson.Value
emptyConfig = [yaml| {} |]
sqliteConfig :: Aeson.Value
sqliteConfig =
[yaml|
db: "/db.chinook.sqlite"
|]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Chinook Agent -- Chinook Agent
@ -84,12 +119,18 @@ teardown (testEnvironment, _) = do
GraphqlEngine.clearMetadata testEnvironment GraphqlEngine.clearMetadata testEnvironment
chinookStockMetadata :: Aeson.Value chinookStockMetadata :: Aeson.Value
chinookStockMetadata = chinookStockMetadata = chinookMetadata DataConnectorReference emptyConfig
let source = defaultSource DataConnector
backendType = defaultBackendTypeString DataConnector chinookSqliteMetadata :: Aeson.Value
chinookSqliteMetadata = chinookMetadata DataConnectorSqlite sqliteConfig
chinookMetadata :: BackendType -> Aeson.Value -> Aeson.Value
chinookMetadata backendType config =
let source = defaultSource backendType
backendTypeString = defaultBackendTypeString backendType
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendTypeString
tables: tables:
- table: [Album] - table: [Album]
configuration: configuration:
@ -157,7 +198,8 @@ tables:
custom_name: birth_date custom_name: birth_date
LastName: LastName:
custom_name: last_name custom_name: last_name
configuration: {} configuration:
*config
|] |]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------

View File

@ -1,16 +1,25 @@
{-# LANGUAGE QuasiQuotes #-}
-- | Definition of backend types and a few helper functions. -- | Definition of backend types and a few helper functions.
module Harness.Test.BackendType module Harness.Test.BackendType
( BackendType (..), ( BackendType (..),
defaultSource, defaultSource,
defaultBackendTypeString, defaultBackendTypeString,
defaultBackendServerUrl,
defaultBackendCapabilities,
schemaKeyword, schemaKeyword,
) )
where where
import Data.Aeson (Value)
import Data.Aeson.Key (Key) import Data.Aeson.Key (Key)
import Harness.Quoter.Yaml (yaml)
import Hasura.Prelude import Hasura.Prelude
-- | A supported backend type. -- | A supported backend type.
-- NOTE: Different data-connector agents are represented by seperate constructors
-- If we want to be able to test these generatively we may want to have a
-- parameterized constructor for data-connectors in future.
data BackendType data BackendType
= Postgres = Postgres
| MySQL | MySQL
@ -18,7 +27,9 @@ data BackendType
| BigQuery | BigQuery
| Citus | Citus
| Cockroach | Cockroach
| DataConnector | DataConnectorMock
| DataConnectorReference
| DataConnectorSqlite
deriving (Eq, Show) deriving (Eq, Show)
-- | The default hasura metadata source name used for a given backend in this test suite project. -- | The default hasura metadata source name used for a given backend in this test suite project.
@ -30,7 +41,36 @@ defaultSource = \case
BigQuery -> "bigquery" BigQuery -> "bigquery"
Citus -> "citus" Citus -> "citus"
Cockroach -> "cockroach" Cockroach -> "cockroach"
DataConnector -> "chinook" DataConnectorMock -> "chinook_mock"
DataConnectorReference -> "chinook_reference"
DataConnectorSqlite -> "chinook_sqlite"
-- | The default hasura metadata backend type used for a given backend in this test suite project.
defaultBackendCapabilities :: BackendType -> Maybe Value
defaultBackendCapabilities = \case
DataConnectorSqlite ->
Just
[yaml|
relationships: {}
explain: {}
queries:
supportsPrimaryKeys: true
|]
DataConnectorReference ->
Just
[yaml|
graphqlSchema: |-
scalar DateTime
input DateTimeComparisons {in_year: Int
same_day_as: DateTime
}
relationships: {}
scalarTypes:
DateTime:
comparisonType: DateTimeComparisons
|]
_ -> Nothing
-- | The default hasura metadata backend type used for a given backend in this test suite project. -- | The default hasura metadata backend type used for a given backend in this test suite project.
defaultBackendTypeString :: BackendType -> String defaultBackendTypeString :: BackendType -> String
@ -41,7 +81,22 @@ defaultBackendTypeString = \case
BigQuery -> "bigquery" BigQuery -> "bigquery"
Citus -> "citus" Citus -> "citus"
Cockroach -> "cockroach" Cockroach -> "cockroach"
DataConnector -> "reference" DataConnectorMock -> "mock"
DataConnectorReference -> "reference"
DataConnectorSqlite -> "sqlite"
-- | The default hasura metadata backend type used for a given backend in this test suite project.
defaultBackendServerUrl :: BackendType -> Maybe String
defaultBackendServerUrl = \case
Postgres -> Nothing
MySQL -> Nothing
SQLServer -> Nothing
BigQuery -> Nothing
Citus -> Nothing
Cockroach -> Nothing
DataConnectorMock -> Nothing
DataConnectorReference -> Just "http://localhost:65005"
DataConnectorSqlite -> Just "http://localhost:65007"
schemaKeyword :: BackendType -> Key schemaKeyword :: BackendType -> Key
schemaKeyword = \case schemaKeyword = \case
@ -51,4 +106,6 @@ schemaKeyword = \case
BigQuery -> "dataset" BigQuery -> "dataset"
Citus -> "schema" Citus -> "schema"
Cockroach -> "schema" Cockroach -> "schema"
DataConnector -> "schema" DataConnectorMock -> "schema"
DataConnectorReference -> "schema"
DataConnectorSqlite -> "schema"

View File

@ -56,7 +56,9 @@ getSchemaName testEnv = case backendType testEnv of
<> showUUID (uniqueTestId testEnv) <> showUUID (uniqueTestId testEnv)
Citus -> SchemaName $ T.pack Constants.citusDb Citus -> SchemaName $ T.pack Constants.citusDb
Cockroach -> SchemaName $ T.pack Constants.cockroachDb Cockroach -> SchemaName $ T.pack Constants.cockroachDb
DataConnector -> SchemaName $ T.pack Constants.dataConnectorDb DataConnectorMock -> SchemaName $ T.pack Constants.dataConnectorDb
DataConnectorReference -> SchemaName $ T.pack Constants.dataConnectorDb
DataConnectorSqlite -> SchemaName $ T.pack Constants.dataConnectorDb
-- | Sanitise UUID for use in BigQuery dataset name -- | Sanitise UUID for use in BigQuery dataset name
-- must be alphanumeric (plus underscores) -- must be alphanumeric (plus underscores)

View File

@ -4,6 +4,7 @@ module Harness.Yaml
fromObject, fromObject,
combinationsObjectUsingValue, combinationsObjectUsingValue,
shouldReturnYaml, shouldReturnYaml,
shouldReturnYamlF,
shouldReturnOneOfYaml, shouldReturnOneOfYaml,
shouldBeYaml, shouldBeYaml,
) )
@ -63,15 +64,29 @@ combinationsObjectUsingValue fn variants = combinationsObject fn (map fromObject
-- We use 'Visual' internally to easily display the 'Value' as YAML -- We use 'Visual' internally to easily display the 'Value' as YAML
-- when the test suite uses its 'Show' instance. -- when the test suite uses its 'Show' instance.
shouldReturnYaml :: HasCallStack => Fixture.Options -> IO Value -> Value -> IO () shouldReturnYaml :: HasCallStack => Fixture.Options -> IO Value -> Value -> IO ()
shouldReturnYaml options actualIO rawExpected = do shouldReturnYaml = shouldReturnYamlF pure
actual <- actualIO
-- | The function @transform@ converts the returned YAML
-- prior to comparison. It exists in IO in order to be able
-- to easily throw exceptions for hspec purposes.
--
-- The action @actualIO@ should produce the @expected@ YAML,
-- represented (by the yaml package) as an aeson 'Value'.
--
-- We use 'Visual' internally to easily display the 'Value' as YAML
-- when the test suite uses its 'Show' instance.
shouldReturnYamlF :: HasCallStack => (Value -> IO Value) -> Fixture.Options -> IO Value -> Value -> IO ()
shouldReturnYamlF transform options actualIO rawExpected = do
actual <- transform =<< actualIO
let Fixture.Options {stringifyNumbers} = options let Fixture.Options {stringifyNumbers} = options
expected = expected' =
if stringifyNumbers if stringifyNumbers
then stringifyExpectedToActual rawExpected actual then stringifyExpectedToActual rawExpected actual
else rawExpected else rawExpected
expected <- transform expected'
shouldBeYaml actual expected shouldBeYaml actual expected
-- | TODO(jkachmar): Document. -- | TODO(jkachmar): Document.

View File

@ -6,7 +6,6 @@ module Test.DataConnector.AggregateQuerySpec
where where
import Data.Aeson qualified as Aeson import Data.Aeson qualified as Aeson
import Data.List.NonEmpty qualified as NE
import Harness.Backend.DataConnector qualified as DataConnector import Harness.Backend.DataConnector qualified as DataConnector
import Harness.GraphqlEngine qualified as GraphqlEngine import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql) import Harness.Quoter.Graphql (graphql)
@ -14,6 +13,7 @@ import Harness.Quoter.Yaml (yaml)
import Harness.Test.BackendType (BackendType (..), defaultBackendTypeString, defaultSource) import Harness.Test.BackendType (BackendType (..), defaultBackendTypeString, defaultSource)
import Harness.Test.Fixture qualified as Fixture import Harness.Test.Fixture qualified as Fixture
import Harness.TestEnvironment (TestEnvironment) import Harness.TestEnvironment (TestEnvironment)
import Harness.TestEnvironment qualified as TE
import Harness.Yaml (shouldReturnYaml) import Harness.Yaml (shouldReturnYaml)
import Hasura.Prelude import Hasura.Prelude
import Test.Hspec (SpecWith, describe, it) import Test.Hspec (SpecWith, describe, it)
@ -21,26 +21,23 @@ import Test.Hspec (SpecWith, describe, it)
spec :: SpecWith TestEnvironment spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( ( \(DataConnector.TestSourceConfig backendType backendConfig sourceConfig _md) ->
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) (Fixture.fixture $ Fixture.Backend backendType)
{ Fixture.setupTeardown = \(testEnv, _) -> { Fixture.setupTeardown =
[ DataConnector.setupFixtureAction \(testEnv, _) -> [DataConnector.setupFixtureAction (sourceMetadata backendType sourceConfig) backendConfig testEnv]
sourceMetadata
DataConnector.defaultBackendConfig
testEnv
]
} }
] )
<$> DataConnector.backendConfigs
) )
tests tests
sourceMetadata :: Aeson.Value sourceMetadata :: BackendType -> Aeson.Value -> Aeson.Value
sourceMetadata = sourceMetadata backendType config =
let source = defaultSource DataConnector let source = defaultSource backendType
backendType = defaultBackendTypeString DataConnector backendTypeString = defaultBackendTypeString backendType
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendTypeString
tables: tables:
- table: [Album] - table: [Album]
object_relationships: object_relationships:
@ -74,7 +71,7 @@ sourceMetadata =
remote_table: [Invoice] remote_table: [Invoice]
column_mapping: column_mapping:
InvoiceId: InvoiceId InvoiceId: InvoiceId
configuration: {} configuration: *config
|] |]
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -137,14 +134,15 @@ tests opts = describe "Aggregate Query Tests" $ do
- Title: Balls to the Wall - Title: Balls to the Wall
|] |]
it "works with object relations" $ \(testEnvironment, _) -> it "works with object relations" $ \(testEnvironment, _) -> do
-- NOTE: Ordering is required due to datasets non-matching orders
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
testEnvironment testEnvironment
[graphql| [graphql|
query getAlbum { query getAlbum {
Album_aggregate(limit: 2) { Album_aggregate(order_by: {AlbumId: asc}, limit: 2) {
nodes { nodes {
AlbumId AlbumId
Artist { Artist {
@ -230,48 +228,43 @@ tests opts = describe "Aggregate Query Tests" $ do
countColumnDistinct: 25 countColumnDistinct: 25
|] |]
it "works with single column queries" $ \(testEnvironment, _) -> it "works with single column queries" $ \(testEnvironment, _) -> do
shouldReturnYaml -- NOTE: This test is specialized for the reference agent to support more statistical functions.
opts -- This should really be derived from the agent's capabilities.
( GraphqlEngine.postGraphql let referenceQuery =
testEnvironment
[graphql| [graphql|
query getInvoices { query getInvoices {
Invoice_aggregate { Invoice_aggregate {
aggregate { aggregate {
max { max { Total }
Total min { Total }
} stddev { Total }
min { stddev_pop { Total }
Total stddev_samp { Total }
} sum { Total }
stddev { var_pop { Total }
Total var_samp { Total }
} variance { Total }
stddev_pop {
Total
}
stddev_samp {
Total
}
sum {
Total
}
var_pop {
Total
}
var_samp {
Total
}
variance {
Total
}
}
}
} }
|] }
) }
[yaml| |]
generalQuery =
[graphql|
query getInvoices {
Invoice_aggregate {
aggregate {
max { Total }
min { Total }
sum { Total }
}
}
}
|]
referenceResults =
[yaml|
data: data:
Invoice_aggregate: Invoice_aggregate:
aggregate: aggregate:
@ -295,6 +288,37 @@ tests opts = describe "Aggregate Query Tests" $ do
Total: 22.518058994165273 Total: 22.518058994165273
|] |]
generalResults =
[yaml|
data:
Invoice_aggregate:
aggregate:
max:
Total: 25.86
min:
Total: 0.99
sum:
Total: 2328.6
|]
if (TE.backendType testEnvironment == Just Fixture.DataConnectorReference)
then
shouldReturnYaml
opts
( GraphqlEngine.postGraphql
testEnvironment
referenceQuery
)
referenceResults
else
shouldReturnYaml
opts
( GraphqlEngine.postGraphql
testEnvironment
generalQuery
)
generalResults
it "min and max works on string fields" $ \(testEnvironment, _) -> it "min and max works on string fields" $ \(testEnvironment, _) ->
shouldReturnYaml shouldReturnYaml
opts opts
@ -325,14 +349,15 @@ tests opts = describe "Aggregate Query Tests" $ do
Name: A Cor Do Som Name: A Cor Do Som
|] |]
it "works across array relationships from regular queries" $ \(testEnvironment, _) -> it "works across array relationships from regular queries" $ \(testEnvironment, _) -> do
-- NOTE: Ordering is added to allow SQLite chinook dataset to return ordered results
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
testEnvironment testEnvironment
[graphql| [graphql|
query getInvoices { query getInvoices {
Invoice(limit: 5) { Invoice(limit: 5, order_by: {InvoiceId: asc}) {
InvoiceId InvoiceId
InvoiceLines_aggregate { InvoiceLines_aggregate {
aggregate { aggregate {
@ -368,14 +393,15 @@ tests opts = describe "Aggregate Query Tests" $ do
count: 14 count: 14
|] |]
it "works across array relationships from aggregate queries via nodes" $ \(testEnvironment, _) -> it "works across array relationships from aggregate queries via nodes" $ \(testEnvironment, _) -> do
-- NOTE: Ordering present so that out-of-order rows are sorted for SQLite
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
testEnvironment testEnvironment
[graphql| [graphql|
query getInvoices { query getInvoices {
Invoice_aggregate(limit: 5) { Invoice_aggregate(limit: 5, order_by: {InvoiceId: asc}) {
nodes { nodes {
InvoiceId InvoiceId
InvoiceLines_aggregate { InvoiceLines_aggregate {

View File

@ -8,43 +8,49 @@ where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Data.List.NonEmpty qualified as NE import Data.Aeson qualified as J
import Data.Aeson.KeyMap qualified as KM
import Data.Vector qualified as Vector
import Harness.Backend.DataConnector qualified as DataConnector import Harness.Backend.DataConnector qualified as DataConnector
import Harness.GraphqlEngine qualified as GraphqlEngine import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Yaml (yaml) import Harness.Quoter.Yaml (yaml)
import Harness.Test.Fixture (emptySetupAction) import Harness.Test.BackendType (defaultBackendCapabilities, defaultBackendServerUrl)
import Harness.Test.Fixture (defaultBackendTypeString, defaultSource, emptySetupAction)
import Harness.Test.Fixture qualified as Fixture import Harness.Test.Fixture qualified as Fixture
import Harness.TestEnvironment (TestEnvironment) import Harness.TestEnvironment (TestEnvironment)
import Harness.Yaml (shouldReturnYaml) import Harness.TestEnvironment qualified as TE
import Harness.Yaml (shouldReturnYaml, shouldReturnYamlF)
import Hasura.Prelude import Hasura.Prelude
import Test.Hspec (SpecWith, describe, it) import Test.Hspec (SpecWith, describe, it, pendingWith)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Reference Agent Query Tests -- DataConnector Agent Query Tests
spec :: SpecWith TestEnvironment spec :: SpecWith TestEnvironment
spec = do spec = do
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( ( \(DataConnector.TestSourceConfig backendType _backendConfig _sourceConfig _md) ->
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) (Fixture.fixture $ Fixture.Backend backendType)
{ Fixture.setupTeardown = \(testEnv, _) -> { Fixture.setupTeardown = \(testEnv, _) ->
[emptySetupAction testEnv] [emptySetupAction testEnv]
} }
] )
<$> DataConnector.backendConfigs
) )
schemaCrudTests schemaCrudTests
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( ( \(DataConnector.TestSourceConfig backendType backendConfig _sourceConfig md) ->
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) (Fixture.fixture $ Fixture.Backend backendType)
{ Fixture.setupTeardown = \(testEnv, _) -> { Fixture.setupTeardown = \(testEnv, _) ->
[ DataConnector.setupFixtureAction [ DataConnector.setupFixtureAction
DataConnector.chinookStockMetadata md
DataConnector.defaultBackendConfig backendConfig
testEnv testEnv
] ]
} }
] )
<$> DataConnector.backendConfigs
) )
schemaInspectionTests schemaInspectionTests
@ -54,136 +60,154 @@ schemaInspectionTests :: Fixture.Options -> SpecWith (TestEnvironment, a)
schemaInspectionTests opts = describe "Schema and Source Inspection" $ do schemaInspectionTests opts = describe "Schema and Source Inspection" $ do
describe "get_source_tables" $ do describe "get_source_tables" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
shouldReturnYaml let sortYamlArray :: J.Value -> IO J.Value
opts sortYamlArray (J.Array a) = pure $ J.Array (Vector.fromList (sort (Vector.toList a)))
( GraphqlEngine.postMetadata sortYamlArray _ = fail "Should return Array"
testEnvironment
case defaultSource <$> TE.backendType testEnvironment of
Nothing -> pendingWith "Backend not found for testEnvironment"
Just sourceString -> do
shouldReturnYamlF
sortYamlArray
opts
( GraphqlEngine.postMetadata
testEnvironment
[yaml|
type: get_source_tables
args:
source: *sourceString
|]
)
[yaml| [yaml|
type: get_source_tables - Artist
args: - Album
source: chinook - Customer
|] - Employee
) - Genre
[yaml| - Invoice
- Artist - InvoiceLine
- Album - MediaType
- Customer - Playlist
- Employee - PlaylistTrack
- Genre - Track
- Invoice |]
- InvoiceLine
- MediaType
- Playlist
- PlaylistTrack
- Track
|]
describe "get_table_info" $ do describe "get_table_info" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
shouldReturnYaml let removeDescriptions (J.Object o) = J.Object (KM.delete "description" (removeDescriptions <$> o))
opts removeDescriptions (J.Array a) = J.Array (removeDescriptions <$> a)
( GraphqlEngine.postMetadata removeDescriptions x = x
testEnvironment
case defaultSource <$> TE.backendType testEnvironment of
Nothing -> pendingWith "Backend not found for testEnvironment"
Just sourceString -> do
shouldReturnYamlF
(pure . removeDescriptions)
opts
( GraphqlEngine.postMetadata
testEnvironment
[yaml|
type: get_table_info
args:
source: *sourceString
table:
- Genre
|]
)
[yaml| [yaml|
type: get_table_info columns:
args: - name: GenreId
source: chinook nullable: false
table: type: number
- Genre - name: Name
|] nullable: true
) type: string
[yaml| name:
columns: - Genre
- description: Genre primary key identifier primary_key:
name: GenreId - GenreId
nullable: false |]
type: number
- description: The name of the genre
name: Name
nullable: true
type: string
description: Genres of music
name:
- Genre
primary_key:
- GenreId
|]
describe "get_source_kind_capabilities" $ do describe "get_source_kind_capabilities" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
shouldReturnYaml case ( defaultBackendCapabilities =<< TE.backendType testEnvironment,
opts defaultBackendTypeString <$> TE.backendType testEnvironment
( GraphqlEngine.postMetadata ) of
testEnvironment (Nothing, _) -> pendingWith "Capabilities not found in testEnvironment"
[yaml| (_, Nothing) -> pendingWith "Backend Type not found in testEnvironment"
type: get_source_kind_capabilities (Just backendCapabilities, Just backendString) -> do
args: shouldReturnYaml
name: reference opts
|] ( GraphqlEngine.postMetadata
) testEnvironment
[yaml| [yaml|
graphqlSchema: |- type: get_source_kind_capabilities
scalar DateTime args:
name: *backendString
input DateTimeComparisons {in_year: Int |]
same_day_as: DateTime )
} backendCapabilities
relationships: {}
scalarTypes:
DateTime:
comparisonType: DateTimeComparisons
|]
schemaCrudTests :: Fixture.Options -> SpecWith (TestEnvironment, a) schemaCrudTests :: Fixture.Options -> SpecWith (TestEnvironment, a)
schemaCrudTests opts = describe "A series of actions to setup and teardown a source with tracked tables and relationships" $ do schemaCrudTests opts = describe "A series of actions to setup and teardown a source with tracked tables and relationships" $ do
describe "dc_add_agent" $ do describe "dc_add_agent" $ do
it "Success" $ \(testEnvironment, _) -> do it "Success" $ \(testEnvironment, _) -> do
shouldReturnYaml case ( defaultBackendServerUrl =<< TE.backendType testEnvironment,
opts defaultBackendTypeString <$> TE.backendType testEnvironment
( GraphqlEngine.postMetadata ) of
testEnvironment (Nothing, _) -> pendingWith "Capabilities not found in testEnvironment"
(_, Nothing) -> pendingWith "Backend Type not found in testEnvironment"
(Just serverString, Just backendString) -> do
shouldReturnYaml
opts
( GraphqlEngine.postMetadata
testEnvironment
[yaml|
type: dc_add_agent
args:
name: *backendString
url: *serverString
|]
)
[yaml| [yaml|
type: dc_add_agent message: success
args: |]
name: reference
url: http://localhost:65005
|]
)
[yaml|
message: success
|]
describe "list_source_kinds" $ do describe "list_source_kinds" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
shouldReturnYaml case defaultBackendTypeString <$> TE.backendType testEnvironment of
opts Nothing -> pendingWith "Backend Type not found in testEnvironment"
( GraphqlEngine.postMetadata Just backendString -> do
testEnvironment shouldReturnYaml
opts
( GraphqlEngine.postMetadata
testEnvironment
[yaml|
type: list_source_kinds
args: {}
|]
)
[yaml| [yaml|
type: list_source_kinds sources:
args: {} - builtin: true
|] kind: pg
) - builtin: true
[yaml| kind: citus
sources: - builtin: true
- builtin: true kind: cockroach
kind: pg - builtin: true
- builtin: true kind: mssql
kind: citus - builtin: true
- builtin: true kind: bigquery
kind: cockroach - builtin: true
- builtin: true kind: mysql
kind: mssql - builtin: false
- builtin: true kind: *backendString
kind: bigquery |]
- builtin: true
kind: mysql
- builtin: false
kind: reference
|]
describe "<kind>_add_source" $ do describe "<kind>_add_source" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -202,6 +226,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "<kind>_track_table" $ do describe "<kind>_track_table" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -219,6 +244,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "<kind>_create_object_relationship" $ do describe "<kind>_create_object_relationship" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
GraphqlEngine.postMetadata_ GraphqlEngine.postMetadata_
testEnvironment testEnvironment
[yaml| [yaml|
@ -249,6 +275,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "<kind>_create_array_relationship" $ do describe "<kind>_create_array_relationship" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -272,6 +299,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "export_metadata" $ do describe "export_metadata" $ do
it "produces the expected metadata structure" $ \(testEnvironment, _) -> do it "produces the expected metadata structure" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -314,6 +342,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "<kind>_drop_relationship" $ do describe "<kind>_drop_relationship" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -332,6 +361,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "<kind>_untrack_table" $ do describe "<kind>_untrack_table" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -350,6 +380,7 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "<kind>_drop_source" $ do describe "<kind>_drop_source" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postMetadata ( GraphqlEngine.postMetadata
@ -367,16 +398,19 @@ schemaCrudTests opts = describe "A series of actions to setup and teardown a sou
describe "dc_delete_agent" $ do describe "dc_delete_agent" $ do
it "success" $ \(testEnvironment, _) -> do it "success" $ \(testEnvironment, _) -> do
shouldReturnYaml case defaultBackendTypeString <$> TE.backendType testEnvironment of
opts Nothing -> pendingWith "Backend Type not found in testEnvironment"
( GraphqlEngine.postMetadata Just backendString -> do
testEnvironment shouldReturnYaml
opts
( GraphqlEngine.postMetadata
testEnvironment
[yaml|
type: dc_delete_agent
args:
name: *backendString
|]
)
[yaml| [yaml|
type: dc_delete_agent message: success
args: |]
name: reference
|]
)
[yaml|
message: success
|]

View File

@ -24,7 +24,7 @@ spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( NE.fromList
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) [ (Fixture.fixture $ Fixture.Backend Fixture.DataConnectorMock)
{ Fixture.mkLocalTestEnvironment = { Fixture.mkLocalTestEnvironment =
DataConnector.mkLocalTestEnvironmentMock, DataConnector.mkLocalTestEnvironmentMock,
Fixture.setupTeardown = \(testEnv, mockEnv) -> Fixture.setupTeardown = \(testEnv, mockEnv) ->
@ -36,8 +36,8 @@ spec =
sourceMetadata :: Aeson.Value sourceMetadata :: Aeson.Value
sourceMetadata = sourceMetadata =
let source = defaultSource DataConnector let source = defaultSource DataConnectorMock
backendType = defaultBackendTypeString DataConnector backendType = defaultBackendTypeString DataConnectorMock
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendType

View File

@ -28,7 +28,7 @@ spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( NE.fromList
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) [ (Fixture.fixture $ Fixture.Backend Fixture.DataConnectorMock)
{ Fixture.mkLocalTestEnvironment = DataConnector.mkLocalTestEnvironmentMock, { Fixture.mkLocalTestEnvironment = DataConnector.mkLocalTestEnvironmentMock,
Fixture.setupTeardown = \(testEnv, mockEnv) -> Fixture.setupTeardown = \(testEnv, mockEnv) ->
[DataConnector.setupMockAction sourceMetadata DataConnector.mockBackendConfig (testEnv, mockEnv)] [DataConnector.setupMockAction sourceMetadata DataConnector.mockBackendConfig (testEnv, mockEnv)]
@ -39,8 +39,8 @@ spec =
sourceMetadata :: Aeson.Value sourceMetadata :: Aeson.Value
sourceMetadata = sourceMetadata =
let source = defaultSource DataConnector let source = defaultSource DataConnectorMock
backendType = defaultBackendTypeString DataConnector backendType = defaultBackendTypeString DataConnectorMock
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendType

View File

@ -25,7 +25,7 @@ spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( NE.fromList
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) [ (Fixture.fixture $ Fixture.Backend Fixture.DataConnectorMock)
{ Fixture.mkLocalTestEnvironment = DataConnector.mkLocalTestEnvironmentMock, { Fixture.mkLocalTestEnvironment = DataConnector.mkLocalTestEnvironmentMock,
Fixture.setupTeardown = \(testEnv, mockEnv) -> Fixture.setupTeardown = \(testEnv, mockEnv) ->
[DataConnector.setupMockAction sourceMetadata DataConnector.mockBackendConfig (testEnv, mockEnv)] [DataConnector.setupMockAction sourceMetadata DataConnector.mockBackendConfig (testEnv, mockEnv)]
@ -39,8 +39,8 @@ testRoleName = "test-role"
sourceMetadata :: Aeson.Value sourceMetadata :: Aeson.Value
sourceMetadata = sourceMetadata =
let source = defaultSource DataConnector let source = defaultSource DataConnectorMock
backendType = defaultBackendTypeString DataConnector backendType = defaultBackendTypeString DataConnectorMock
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendType

View File

@ -28,7 +28,7 @@ spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( NE.fromList
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) [ (Fixture.fixture $ Fixture.Backend Fixture.DataConnectorMock)
{ Fixture.mkLocalTestEnvironment = DataConnector.mkLocalTestEnvironmentMock, { Fixture.mkLocalTestEnvironment = DataConnector.mkLocalTestEnvironmentMock,
Fixture.setupTeardown = \(testEnv, mockEnv) -> Fixture.setupTeardown = \(testEnv, mockEnv) ->
[ DataConnector.setupMockAction [ DataConnector.setupMockAction
@ -43,8 +43,8 @@ spec =
sourceMetadata :: Aeson.Value sourceMetadata :: Aeson.Value
sourceMetadata = sourceMetadata =
let source = defaultSource DataConnector let source = defaultSource DataConnectorMock
backendType = defaultBackendTypeString DataConnector backendType = defaultBackendTypeString DataConnectorMock
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendType

View File

@ -8,16 +8,16 @@ where
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
import Data.List.NonEmpty qualified as NE
import Harness.Backend.DataConnector qualified as DataConnector import Harness.Backend.DataConnector qualified as DataConnector
import Harness.GraphqlEngine qualified as GraphqlEngine import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql) import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Yaml (yaml) import Harness.Quoter.Yaml (yaml)
import Harness.Test.Fixture qualified as Fixture import Harness.Test.Fixture qualified as Fixture
import Harness.TestEnvironment (TestEnvironment) import Harness.TestEnvironment (TestEnvironment)
import Harness.TestEnvironment qualified as TE
import Harness.Yaml (shouldReturnYaml) import Harness.Yaml (shouldReturnYaml)
import Hasura.Prelude import Hasura.Prelude
import Test.Hspec (SpecWith, describe, it) import Test.Hspec (SpecWith, describe, it, pendingWith)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Reference Agent Query Tests -- Reference Agent Query Tests
@ -25,16 +25,17 @@ import Test.Hspec (SpecWith, describe, it)
spec :: SpecWith TestEnvironment spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( ( \(DataConnector.TestSourceConfig backendType backendConfig _sourceConfig md) ->
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) (Fixture.fixture $ Fixture.Backend backendType)
{ Fixture.setupTeardown = \(testEnv, _) -> { Fixture.setupTeardown = \(testEnv, _) ->
[ DataConnector.setupFixtureAction [ DataConnector.setupFixtureAction
DataConnector.chinookStockMetadata md
DataConnector.defaultBackendConfig backendConfig
testEnv testEnv
] ]
} }
] )
<$> DataConnector.backendConfigs
) )
tests tests
@ -131,14 +132,15 @@ tests opts = describe "Queries" $ do
Name: "Balls to the Wall" Name: "Balls to the Wall"
|] |]
it "works with pagination" $ \(testEnvironment, _) -> it "works with pagination" $ \(testEnvironment, _) -> do
-- NOTE: We order by in this pagination test to ensure that the rows are ordered correctly (which they are not in db.chinook.sqlite)
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
testEnvironment testEnvironment
[graphql| [graphql|
query getAlbum { query getAlbum {
albums (limit: 3, offset: 2) { albums (limit: 3, offset: 2, order_by: {id: asc}) {
id id
} }
} }
@ -181,8 +183,9 @@ tests opts = describe "Queries" $ do
- title: Let There Be Rock - title: Let There Be Rock
|] |]
describe "Foreign Key Constraint On" $ do describe "Foreign Key Constraint On" do
it "joins on PlaylistId" $ \(testEnvironment, _) -> it "joins on PlaylistId" $ \(testEnvironment, _) -> do
-- NOTE: Ordering is used for the query due to inconsistencies in data-set ordering.
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
@ -190,7 +193,7 @@ tests opts = describe "Queries" $ do
[graphql| [graphql|
query getPlaylist { query getPlaylist {
Playlist_by_pk(PlaylistId: 1) { Playlist_by_pk(PlaylistId: 1) {
Tracks (limit: 3) { Tracks (order_by: {TrackId: desc}, limit: 3) {
TrackId TrackId
} }
} }
@ -201,13 +204,13 @@ tests opts = describe "Queries" $ do
data: data:
Playlist_by_pk: Playlist_by_pk:
Tracks: Tracks:
- TrackId: 3402 - TrackId: 3503
- TrackId: 3389 - TrackId: 3502
- TrackId: 3390 - TrackId: 3501
|] |]
describe "Object Relationships" $ do describe "Object Relationships" do
describe "Manual" $ do describe "Manual" do
it "joins on artist id" $ \(testEnvironment, _) -> it "joins on artist id" $ \(testEnvironment, _) ->
shouldReturnYaml shouldReturnYaml
opts opts
@ -489,7 +492,8 @@ tests opts = describe "Queries" $ do
title: 'Monteverdi: L''Orfeo' title: 'Monteverdi: L''Orfeo'
|] |]
it "can order by an aggregate" $ \(testEnvironment, _) -> it "can order by an aggregate" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
@ -524,7 +528,8 @@ tests opts = describe "Queries" $ do
count: 11 count: 11
|] |]
it "can order by a related field" $ \(testEnvironment, _) -> it "can order by a related field" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql
@ -557,7 +562,9 @@ tests opts = describe "Queries" $ do
title: Worlds title: Worlds
|] |]
describe "Custom scalar types and operators" $ do describe "Custom scalar types and operators" $ do
it "works with custom scalar types and comparison operators" $ \(testEnvironment, _) -> it "works with custom scalar types and comparison operators" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) do
pendingWith "TODO: Test currently broken for SQLite DataConnector"
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphql ( GraphqlEngine.postGraphql

View File

@ -8,8 +8,6 @@ where
import Data.Aeson (Value) import Data.Aeson (Value)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.List.NonEmpty qualified as NE
import Harness.Backend.DataConnector (defaultBackendConfig)
import Harness.Backend.DataConnector qualified as DataConnector import Harness.Backend.DataConnector qualified as DataConnector
import Harness.GraphqlEngine qualified as GraphqlEngine import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql) import Harness.Quoter.Graphql (graphql)
@ -17,9 +15,10 @@ import Harness.Quoter.Yaml (yaml)
import Harness.Test.BackendType (BackendType (..), defaultBackendTypeString, defaultSource) import Harness.Test.BackendType (BackendType (..), defaultBackendTypeString, defaultSource)
import Harness.Test.Fixture qualified as Fixture import Harness.Test.Fixture qualified as Fixture
import Harness.TestEnvironment (TestEnvironment) import Harness.TestEnvironment (TestEnvironment)
import Harness.TestEnvironment qualified as TE
import Harness.Yaml (shouldReturnYaml) import Harness.Yaml (shouldReturnYaml)
import Hasura.Prelude import Hasura.Prelude
import Test.Hspec (SpecWith, describe, it) import Test.Hspec (SpecWith, describe, it, pendingWith)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Preamble -- Preamble
@ -27,25 +26,26 @@ import Test.Hspec (SpecWith, describe, it)
spec :: SpecWith TestEnvironment spec :: SpecWith TestEnvironment
spec = spec =
Fixture.runWithLocalTestEnvironment Fixture.runWithLocalTestEnvironment
( NE.fromList ( ( \(DataConnector.TestSourceConfig backendType backendConfig sourceConfig _md) ->
[ (Fixture.fixture $ Fixture.Backend Fixture.DataConnector) (Fixture.fixture $ Fixture.Backend backendType)
{ Fixture.setupTeardown = \(testEnv, _) -> { Fixture.setupTeardown = \(testEnv, _) ->
[DataConnector.setupFixtureAction sourceMetadata defaultBackendConfig testEnv] [DataConnector.setupFixtureAction (sourceMetadata backendType sourceConfig) backendConfig testEnv]
} }
] )
<$> DataConnector.backendConfigs
) )
tests tests
testRoleName :: ByteString testRoleName :: ByteString
testRoleName = "test-role" testRoleName = "test-role"
sourceMetadata :: Value sourceMetadata :: BackendType -> Value -> Value
sourceMetadata = sourceMetadata backendType config =
let source = defaultSource DataConnector let source = defaultSource backendType
backendType = defaultBackendTypeString DataConnector backendTypeString = defaultBackendTypeString backendType
in [yaml| in [yaml|
name : *source name : *source
kind: *backendType kind: *backendTypeString
tables: tables:
- table: [Employee] - table: [Employee]
array_relationships: array_relationships:
@ -88,7 +88,7 @@ sourceMetadata =
SupportRep: SupportRep:
Country: Country:
_ceq: [ "$", "Country" ] _ceq: [ "$", "Country" ]
configuration: {} configuration: *config
|] |]
tests :: Fixture.Options -> SpecWith (TestEnvironment, a) tests :: Fixture.Options -> SpecWith (TestEnvironment, a)
@ -265,7 +265,8 @@ tests opts = describe "SelectPermissionsSpec" $ do
LastName: Silk LastName: Silk
|] |]
it "Query that orders by a related table that has a permissions filter" $ \(testEnvironment, _) -> it "Query that orders by a related table that has a permissions filter" $ \(testEnvironment, _) -> do
when (TE.backendType testEnvironment == Just Fixture.DataConnectorSqlite) (pendingWith "TODO: Test currently broken for SQLite DataConnector")
shouldReturnYaml shouldReturnYaml
opts opts
( GraphqlEngine.postGraphqlWithHeaders ( GraphqlEngine.postGraphqlWithHeaders