mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
Unified setup for NestedRelationshipsSpec
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4378 GitOrigin-RevId: 3881591ad0ec109352e09a989377121550632fdd
This commit is contained in:
parent
5008b54813
commit
c199215947
@ -1076,6 +1076,7 @@ test-suite tests-hspec
|
||||
Harness.Http
|
||||
Harness.RemoteServer
|
||||
Harness.TestEnvironment
|
||||
Harness.Yaml
|
||||
|
||||
-- Harness.Backend
|
||||
Harness.Backend.BigQuery
|
||||
|
@ -3,7 +3,9 @@
|
||||
|
||||
{-# OPTIONS -Wno-redundant-constraints #-}
|
||||
|
||||
-- | BigQuery helpers.
|
||||
-- | BigQuery helpers. This module contains BigQuery specific schema
|
||||
-- setup/teardown functions because BigQuery API has a different API
|
||||
-- (dataset field, manual_configuration field etc)
|
||||
module Harness.Backend.BigQuery
|
||||
( run_,
|
||||
runSql_,
|
||||
@ -16,13 +18,18 @@ module Harness.Backend.BigQuery
|
||||
dropTable,
|
||||
untrackTable,
|
||||
setup,
|
||||
setupWithAdditionalRelationship,
|
||||
teardown,
|
||||
teardownWithAdditionalRelationship,
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Monad (void)
|
||||
import Data.Aeson (Value)
|
||||
import Data.Bool (bool)
|
||||
import Data.Aeson
|
||||
( Value (..),
|
||||
object,
|
||||
(.=),
|
||||
)
|
||||
import Data.Foldable (for_)
|
||||
import Data.String
|
||||
import Data.Text (Text, pack, replace)
|
||||
@ -35,8 +42,19 @@ import Harness.Env
|
||||
import Harness.Exceptions
|
||||
import Harness.GraphqlEngine qualified as GraphqlEngine
|
||||
import Harness.Quoter.Yaml (yaml)
|
||||
import Harness.Test.Context (BackendType (BigQuery), defaultBackendTypeString, defaultSource)
|
||||
import Harness.Test.Schema (BackendScalarType (..), BackendScalarValue (..), ScalarValue (..))
|
||||
import Harness.Test.Context
|
||||
( BackendType (BigQuery),
|
||||
defaultBackendTypeString,
|
||||
defaultSource,
|
||||
)
|
||||
import Harness.Test.Schema
|
||||
( BackendScalarType (..),
|
||||
BackendScalarValue (..),
|
||||
ManualRelationship (..),
|
||||
Reference (..),
|
||||
ScalarValue (..),
|
||||
Table (..),
|
||||
)
|
||||
import Harness.Test.Schema qualified as Schema
|
||||
import Harness.TestEnvironment (TestEnvironment)
|
||||
import Hasura.Backends.BigQuery.Connection (initConnection)
|
||||
@ -123,13 +141,13 @@ scalarType = \case
|
||||
Schema.TBool -> "BIT"
|
||||
Schema.TCustomType txt -> Schema.getBackendScalarType txt bstBigQuery
|
||||
|
||||
-- | Create column. BigQuery doesn't support default values. Also,
|
||||
-- currently we don't support specifying NOT NULL constraint.
|
||||
mkColumn :: Schema.Column -> Text
|
||||
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
|
||||
mkColumn Schema.Column {columnName, columnType} =
|
||||
T.unwords
|
||||
[ columnName,
|
||||
scalarType columnType,
|
||||
bool "NOT NULL" "DEFAULT NULL" columnNullable,
|
||||
maybe "" ("DEFAULT " <>) columnDefault
|
||||
scalarType columnType
|
||||
]
|
||||
|
||||
-- | Serialize tableData into an SQL insert statement and execute it.
|
||||
@ -244,6 +262,34 @@ args:
|
||||
datasets: [*dataset]
|
||||
|]
|
||||
|
||||
-- | Converts 'ManualRelationship' to 'Table'. Should be only used for
|
||||
-- building the relationship.
|
||||
relationshipToTable :: ManualRelationship -> Schema.Table
|
||||
relationshipToTable ManualRelationship {..} =
|
||||
Table
|
||||
{ tableName = relSourceTable,
|
||||
tablePrimaryKey = [],
|
||||
tableColumns = [],
|
||||
tableData = [],
|
||||
tableReferences =
|
||||
[ Reference
|
||||
{ referenceLocalColumn = relSourceColumn,
|
||||
referenceTargetTable = relTargetTable,
|
||||
referenceTargetColumn = relTargetColumn
|
||||
}
|
||||
]
|
||||
}
|
||||
|
||||
-- | Same as 'setup' but also additional sets up the manual
|
||||
-- relationship that might be required for some cases.
|
||||
setupWithAdditionalRelationship :: [Schema.Table] -> [ManualRelationship] -> (TestEnvironment, ()) -> IO ()
|
||||
setupWithAdditionalRelationship tables rels (testEnvironment, _) = do
|
||||
setup tables (testEnvironment, ())
|
||||
let relTables = map relationshipToTable rels
|
||||
for_ relTables $ \table -> do
|
||||
trackObjectRelationships BigQuery table testEnvironment
|
||||
trackArrayRelationships BigQuery table testEnvironment
|
||||
|
||||
-- | Setup the schema in the most expected way.
|
||||
-- NOTE: Certain test modules may warrant having their own local version.
|
||||
setup :: [Schema.Table] -> (TestEnvironment, ()) -> IO ()
|
||||
@ -276,8 +322,8 @@ args:
|
||||
trackTable testEnvironment table
|
||||
-- Setup relationships
|
||||
for_ tables $ \table -> do
|
||||
Schema.trackObjectRelationships BigQuery table testEnvironment
|
||||
Schema.trackArrayRelationships BigQuery table testEnvironment
|
||||
trackObjectRelationships BigQuery table testEnvironment
|
||||
trackArrayRelationships BigQuery table testEnvironment
|
||||
|
||||
-- | Teardown the schema and tracking in the most expected way.
|
||||
-- NOTE: Certain test modules may warrant having their own version.
|
||||
@ -285,8 +331,127 @@ teardown :: [Schema.Table] -> (TestEnvironment, ()) -> IO ()
|
||||
teardown (reverse -> tables) (testEnvironment, _) = do
|
||||
-- Teardown relationships first
|
||||
forFinally_ tables $ \table ->
|
||||
Schema.untrackRelationships BigQuery table testEnvironment
|
||||
untrackRelationships BigQuery table testEnvironment
|
||||
-- Then teardown tables
|
||||
forFinally_ tables $ \table -> do
|
||||
untrackTable testEnvironment table
|
||||
dropTable table
|
||||
|
||||
-- | Same as 'teardown' but also tears the manual relationship that
|
||||
-- was setup.
|
||||
teardownWithAdditionalRelationship :: [Schema.Table] -> [ManualRelationship] -> (TestEnvironment, ()) -> IO ()
|
||||
teardownWithAdditionalRelationship tables rels (testEnvironment, _) = do
|
||||
let relTables = map relationshipToTable rels
|
||||
for_ relTables $ \table -> do
|
||||
untrackRelationships BigQuery table testEnvironment
|
||||
-- We do teardown in the reverse order to ensure that the tables
|
||||
-- that have dependency are removed first. This has to be only done
|
||||
-- for BigQuery backend since the metadata tracks the relationship
|
||||
-- between them.
|
||||
teardown (reverse tables) (testEnvironment, ())
|
||||
|
||||
-- | Bigquery specific function for tracking array relationships
|
||||
trackArrayRelationships :: HasCallStack => BackendType -> Table -> TestEnvironment -> IO ()
|
||||
trackArrayRelationships backend Table {tableName, tableReferences} testEnvironment = do
|
||||
let source = defaultSource backend
|
||||
dataset = Constants.bigqueryDataset
|
||||
requestType = source <> "_create_array_relationship"
|
||||
for_ tableReferences $ \Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} -> do
|
||||
let relationshipName = Schema.mkArrayRelationshipName referenceTargetTable referenceTargetColumn
|
||||
manualConfiguration :: Value
|
||||
manualConfiguration =
|
||||
object
|
||||
[ "remote_table"
|
||||
.= object
|
||||
[ "dataset" .= String (T.pack dataset),
|
||||
"name" .= String referenceTargetTable
|
||||
],
|
||||
"column_mapping"
|
||||
.= object [referenceLocalColumn .= referenceTargetColumn]
|
||||
]
|
||||
payload =
|
||||
[yaml|
|
||||
type: *requestType
|
||||
args:
|
||||
source: *source
|
||||
table:
|
||||
dataset: *dataset
|
||||
name: *tableName
|
||||
name: *relationshipName
|
||||
using:
|
||||
manual_configuration: *manualConfiguration
|
||||
|]
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
payload
|
||||
|
||||
-- | Bigquery specific function for tracking object relationships
|
||||
trackObjectRelationships :: HasCallStack => BackendType -> Table -> TestEnvironment -> IO ()
|
||||
trackObjectRelationships backend Table {tableName, tableReferences} testEnvironment = do
|
||||
let source = defaultSource backend
|
||||
dataset = Constants.bigqueryDataset
|
||||
requestType = source <> "_create_object_relationship"
|
||||
for_ tableReferences $ \ref@Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} -> do
|
||||
let relationshipName = Schema.mkObjectRelationshipName ref
|
||||
manualConfiguration :: Value
|
||||
manualConfiguration =
|
||||
object
|
||||
[ "remote_table"
|
||||
.= object
|
||||
[ "dataset" .= String (T.pack dataset),
|
||||
"name" .= String referenceTargetTable
|
||||
],
|
||||
"column_mapping"
|
||||
.= object [referenceLocalColumn .= referenceTargetColumn]
|
||||
]
|
||||
payload =
|
||||
[yaml|
|
||||
type: *requestType
|
||||
args:
|
||||
source: *source
|
||||
table:
|
||||
dataset: *dataset
|
||||
name: *tableName
|
||||
name: *relationshipName
|
||||
using:
|
||||
manual_configuration: *manualConfiguration
|
||||
|]
|
||||
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
payload
|
||||
|
||||
-- | Bigquery specific function for untracking relationships
|
||||
-- Overriding `Schema.untrackRelationships` here because bigquery's API expects a `dataset` key
|
||||
untrackRelationships :: HasCallStack => BackendType -> Table -> TestEnvironment -> IO ()
|
||||
untrackRelationships backend Table {tableName, tableReferences} testEnvironment = do
|
||||
let source = defaultSource backend
|
||||
dataset = Constants.bigqueryDataset
|
||||
requestType = source <> "_drop_relationship"
|
||||
for_ tableReferences $ \ref@Reference {referenceTargetTable, referenceTargetColumn} -> do
|
||||
let arrayRelationshipName = Schema.mkArrayRelationshipName referenceTargetTable referenceTargetColumn
|
||||
objectRelationshipName = Schema.mkObjectRelationshipName ref
|
||||
-- drop array relationships
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: *requestType
|
||||
args:
|
||||
source: *source
|
||||
table:
|
||||
dataset: *dataset
|
||||
name: *tableName
|
||||
relationship: *arrayRelationshipName
|
||||
|]
|
||||
-- drop object relationships
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: *requestType
|
||||
args:
|
||||
source: *source
|
||||
table:
|
||||
dataset: *dataset
|
||||
name: *tableName
|
||||
relationship: *objectRelationshipName
|
||||
|]
|
||||
|
@ -10,6 +10,7 @@ module Harness.Test.Schema
|
||||
BackendScalarType (..),
|
||||
BackendScalarValue (..),
|
||||
BackendScalarValueType (..),
|
||||
ManualRelationship (..),
|
||||
quotedValue,
|
||||
unquotedValue,
|
||||
backendScalarValue,
|
||||
@ -25,6 +26,8 @@ module Harness.Test.Schema
|
||||
trackObjectRelationships,
|
||||
trackArrayRelationships,
|
||||
untrackRelationships,
|
||||
mkObjectRelationshipName,
|
||||
mkArrayRelationshipName,
|
||||
)
|
||||
where
|
||||
|
||||
@ -66,6 +69,17 @@ data Reference = Reference
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- | Type representing manual relationship between tables. This is
|
||||
-- only used for BigQuery backend currently where additional
|
||||
-- relationships has to be manually specified.
|
||||
data ManualRelationship = ManualRelationship
|
||||
{ relSourceTable :: Text,
|
||||
relTargetTable :: Text,
|
||||
relSourceColumn :: Text,
|
||||
relTargetColumn :: Text
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- | Generic type to construct columns for all backends
|
||||
data Column = Column
|
||||
{ columnName :: Text,
|
||||
|
42
server/tests-hspec/Harness/Yaml.hs
Normal file
42
server/tests-hspec/Harness/Yaml.hs
Normal file
@ -0,0 +1,42 @@
|
||||
-- | Utility functions related to yaml
|
||||
module Harness.Yaml
|
||||
( combinationsObject,
|
||||
fromObject,
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Aeson
|
||||
( Object,
|
||||
Value (..),
|
||||
)
|
||||
import Data.Vector qualified as V
|
||||
import Data.Word (Word8)
|
||||
import Hasura.Prelude
|
||||
|
||||
fromObject :: Value -> Object
|
||||
fromObject (Object x) = x
|
||||
fromObject v = error $ "fromObject: Expected object, received" <> show v
|
||||
|
||||
-- | Compute all variations of an object and construct a list of
|
||||
-- 'Value' based on the higher order function that is passed to it. A
|
||||
-- single variation of 'Object' is constructed as an 'Array' before
|
||||
-- it's transformed by the passed function.
|
||||
--
|
||||
-- Typical usecase of this function is to use it with
|
||||
-- 'shouldReturnOneOfYaml' function.
|
||||
combinationsObject :: (Value -> Value) -> [Object] -> [Value]
|
||||
combinationsObject fn variants =
|
||||
let nSubsets :: [[Object]]
|
||||
nSubsets = subsets (fromIntegral $ length variants) variants
|
||||
|
||||
toArray :: [Value]
|
||||
toArray = map ((Array . V.fromList) . (map Object)) nSubsets
|
||||
in map fn toArray
|
||||
|
||||
-- | 'subsets' n xs computes subsets with that the constraint that the
|
||||
-- length of the subset should be equal to n provided that the list is
|
||||
-- non empty.
|
||||
subsets :: Word8 -> [a] -> [[a]]
|
||||
subsets 0 _ = [[]]
|
||||
subsets _ [] = []
|
||||
subsets n (x : xs) = map (x :) (subsets (n - 1) xs) <> subsets n xs
|
@ -5,7 +5,9 @@
|
||||
-- Original inspiration for this module Test.is <https://github.com/hasura/graphql-engine-mono/blob/08caf7df10cad0aea0916327736147a0a8f808d1/server/tests-py/queries/graphql_query/mysql/nested_select_query_deep.yaml>
|
||||
module Test.NestedRelationshipsSpec (spec) where
|
||||
|
||||
import Data.Aeson (Value)
|
||||
import Data.Text (Text)
|
||||
import Harness.Backend.BigQuery qualified as Bigquery
|
||||
import Harness.Backend.Citus qualified as Citus
|
||||
import Harness.Backend.Mysql as Mysql
|
||||
import Harness.Backend.Postgres qualified as Postgres
|
||||
@ -17,6 +19,7 @@ import Harness.Test.Context qualified as Context
|
||||
import Harness.Test.Schema
|
||||
( BackendScalarType (..),
|
||||
BackendScalarValue (..),
|
||||
ManualRelationship (..),
|
||||
ScalarType (..),
|
||||
ScalarValue (..),
|
||||
defaultBackendScalarType,
|
||||
@ -24,6 +27,7 @@ import Harness.Test.Schema
|
||||
)
|
||||
import Harness.Test.Schema qualified as Schema
|
||||
import Harness.TestEnvironment (TestEnvironment)
|
||||
import Harness.Yaml
|
||||
import Hasura.Prelude (tshow)
|
||||
import Test.Hspec
|
||||
import Prelude
|
||||
@ -61,6 +65,23 @@ spec =
|
||||
setup = Sqlserver.setup schema,
|
||||
teardown = Sqlserver.teardown schema,
|
||||
customOptions = Nothing
|
||||
},
|
||||
Context.Context
|
||||
{ name = Context.Backend Context.BigQuery,
|
||||
mkLocalTestEnvironment = Context.noLocalTestEnvironment,
|
||||
setup =
|
||||
Bigquery.setupWithAdditionalRelationship
|
||||
schema
|
||||
[authorArticles],
|
||||
teardown =
|
||||
Bigquery.teardownWithAdditionalRelationship
|
||||
schema
|
||||
[authorArticles],
|
||||
customOptions =
|
||||
Just $
|
||||
Context.Options
|
||||
{ stringifyNumbers = True
|
||||
}
|
||||
}
|
||||
]
|
||||
tests
|
||||
@ -70,6 +91,15 @@ spec =
|
||||
schema :: [Schema.Table]
|
||||
schema = [author, article]
|
||||
|
||||
authorArticles :: ManualRelationship
|
||||
authorArticles =
|
||||
ManualRelationship
|
||||
{ relSourceTable = "author",
|
||||
relTargetTable = "article",
|
||||
relSourceColumn = "id",
|
||||
relTargetColumn = "author_id"
|
||||
}
|
||||
|
||||
author :: Schema.Table
|
||||
author =
|
||||
Schema.Table
|
||||
@ -87,7 +117,8 @@ author =
|
||||
{ bsvMysql = Schema.quotedValue "2017-09-21 09:39:44",
|
||||
bsvCitus = Schema.quotedValue "2017-09-21T09:39:44",
|
||||
bsvMssql = Schema.quotedValue "2017-09-21T09:39:44Z",
|
||||
bsvPostgres = Schema.quotedValue "2017-09-21T09:39:44"
|
||||
bsvPostgres = Schema.quotedValue "2017-09-21T09:39:44",
|
||||
bsvBigQuery = Schema.quotedValue "2017-09-21T09:39:44"
|
||||
}
|
||||
],
|
||||
[ Schema.VInt 2,
|
||||
@ -97,7 +128,8 @@ author =
|
||||
{ bsvMysql = Schema.quotedValue "2017-09-21 09:50:44",
|
||||
bsvCitus = Schema.quotedValue "2017-09-21T09:50:44",
|
||||
bsvMssql = Schema.quotedValue "2017-09-21T09:50:44Z",
|
||||
bsvPostgres = Schema.quotedValue "2017-09-21T09:50:44"
|
||||
bsvPostgres = Schema.quotedValue "2017-09-21T09:50:44",
|
||||
bsvBigQuery = Schema.quotedValue "2017-09-21T09:50:44"
|
||||
}
|
||||
]
|
||||
]
|
||||
@ -109,7 +141,8 @@ author =
|
||||
{ bstMysql = Just "DATETIME",
|
||||
bstMssql = Just "DATETIME",
|
||||
bstCitus = Just "TIMESTAMP",
|
||||
bstPostgres = Just "TIMESTAMP"
|
||||
bstPostgres = Just "TIMESTAMP",
|
||||
bstBigQuery = Just "DATETIME"
|
||||
}
|
||||
|
||||
article :: Schema.Table
|
||||
@ -127,9 +160,9 @@ article =
|
||||
["id"]
|
||||
[ Schema.Reference "author_id" "author" "id"
|
||||
]
|
||||
[ mkArticle 1 "Article 1" "Sample article content 1" 1 0,
|
||||
mkArticle 2 "Article 2" "Sample article content 2" 1 1,
|
||||
mkArticle 3 "Article 3" "Sample article content 3" 2 1
|
||||
[ mkArticle 1 "Article 1" "Sample article content 1" 1 False,
|
||||
mkArticle 2 "Article 2" "Sample article content 2" 1 True,
|
||||
mkArticle 3 "Article 3" "Sample article content 3" 2 True
|
||||
]
|
||||
where
|
||||
textType :: ScalarType
|
||||
@ -139,7 +172,8 @@ article =
|
||||
{ bstMysql = Just "TEXT",
|
||||
bstMssql = Just "TEXT",
|
||||
bstCitus = Just "TEXT",
|
||||
bstPostgres = Just "TEXT"
|
||||
bstPostgres = Just "TEXT",
|
||||
bstBigQuery = Just "STRING"
|
||||
}
|
||||
|
||||
bitType :: ScalarType
|
||||
@ -149,7 +183,8 @@ article =
|
||||
{ bstMysql = Just "BIT",
|
||||
bstMssql = Just "BIT",
|
||||
bstCitus = Just "BOOLEAN",
|
||||
bstPostgres = Just "BOOLEAN"
|
||||
bstPostgres = Just "BOOLEAN",
|
||||
bstBigQuery = Just "BOOL"
|
||||
}
|
||||
|
||||
timestampType :: ScalarType
|
||||
@ -159,7 +194,8 @@ article =
|
||||
{ bstMysql = Just "TIMESTAMP NULL",
|
||||
bstMssql = Just "DATETIME",
|
||||
bstCitus = Just "TIMESTAMP",
|
||||
bstPostgres = Just "TIMESTAMP"
|
||||
bstPostgres = Just "TIMESTAMP",
|
||||
bstBigQuery = Just "DATETIME"
|
||||
}
|
||||
|
||||
intUnsingedType :: ScalarType
|
||||
@ -169,28 +205,35 @@ article =
|
||||
{ bstMysql = Just "INT UNSIGNED",
|
||||
bstMssql = Just "INT",
|
||||
bstCitus = Just "INT",
|
||||
bstPostgres = Just "INT"
|
||||
bstPostgres = Just "INT",
|
||||
bstBigQuery = Just "INT64"
|
||||
}
|
||||
|
||||
mkArticle :: Int -> Text -> Text -> Int -> Int -> [ScalarValue]
|
||||
mkArticle pid title content author_id is_published =
|
||||
backendBool :: Bool -> Int
|
||||
backendBool True = 1
|
||||
backendBool False = 0
|
||||
|
||||
mkArticle :: Int -> Text -> Text -> Int -> Bool -> [ScalarValue]
|
||||
mkArticle pid title content authorId isPublished =
|
||||
[ Schema.VInt pid,
|
||||
Schema.VStr title,
|
||||
Schema.VStr content,
|
||||
Schema.VCustomValue $
|
||||
defaultBackendScalarValue
|
||||
{ bsvMysql = Schema.unquotedValue (tshow is_published),
|
||||
bsvCitus = Schema.quotedValue (tshow is_published),
|
||||
bsvPostgres = Schema.quotedValue (tshow is_published),
|
||||
bsvMssql = Schema.unquotedValue (tshow is_published)
|
||||
{ bsvMysql = Schema.unquotedValue (tshow $ backendBool isPublished),
|
||||
bsvCitus = Schema.quotedValue (tshow $ backendBool isPublished),
|
||||
bsvPostgres = Schema.quotedValue (tshow $ backendBool isPublished),
|
||||
bsvMssql = Schema.unquotedValue (tshow $ backendBool isPublished),
|
||||
bsvBigQuery = Schema.unquotedValue (tshow isPublished)
|
||||
},
|
||||
Schema.VNull,
|
||||
Schema.VCustomValue $
|
||||
defaultBackendScalarValue
|
||||
{ bsvMysql = Schema.unquotedValue (tshow author_id),
|
||||
bsvCitus = Schema.unquotedValue (tshow author_id),
|
||||
bsvPostgres = Schema.unquotedValue (tshow author_id),
|
||||
bsvMssql = Schema.unquotedValue (tshow author_id)
|
||||
{ bsvMysql = Schema.unquotedValue (tshow authorId),
|
||||
bsvCitus = Schema.unquotedValue (tshow authorId),
|
||||
bsvPostgres = Schema.unquotedValue (tshow authorId),
|
||||
bsvMssql = Schema.unquotedValue (tshow authorId),
|
||||
bsvBigQuery = Schema.unquotedValue (tshow authorId)
|
||||
},
|
||||
Schema.VNull
|
||||
]
|
||||
@ -202,7 +245,7 @@ article =
|
||||
-- https://github.com/hasura/graphql-engine/blob/369d1ab2f119634b0e27e9ed353fa3d08c22d3fb/server/tests-py/test_graphql_queries.py#L280
|
||||
tests :: Context.Options -> SpecWith TestEnvironment
|
||||
tests opts = do
|
||||
it "Nested select on article" $ \testEnvironment ->
|
||||
it "Deep nested select with where" $ \testEnvironment ->
|
||||
shouldReturnYaml
|
||||
opts
|
||||
( GraphqlEngine.postGraphql
|
||||
@ -278,8 +321,35 @@ data:
|
||||
|]
|
||||
-- Equivalent python suite: test_nested_select_query_article_author
|
||||
-- https://github.com/hasura/graphql-engine/blob/369d1ab2f119634b0e27e9ed353fa3d08c22d3fb/server/tests-py/test_graphql_queries.py#L277
|
||||
it "Nested select on article" $ \testEnvironment ->
|
||||
shouldReturnYaml
|
||||
it "Nested select on article" $ \testEnvironment -> do
|
||||
let articleOne =
|
||||
[yaml|
|
||||
id: 1
|
||||
title: Article 1
|
||||
content: Sample article content 1
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
|]
|
||||
articleTwo =
|
||||
[yaml|
|
||||
id: 2
|
||||
title: Article 2
|
||||
content: Sample article content 2
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
|]
|
||||
articleThree =
|
||||
[yaml|
|
||||
id: 3
|
||||
title: Article 3
|
||||
content: Sample article content 3
|
||||
author_by_author_id:
|
||||
id: 2
|
||||
name: Author 2
|
||||
|]
|
||||
shouldReturnOneOfYaml
|
||||
opts
|
||||
( GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
@ -298,32 +368,11 @@ query {
|
||||
|
||||
|]
|
||||
)
|
||||
[yaml|
|
||||
data:
|
||||
hasura_article:
|
||||
- id: 1
|
||||
title: Article 1
|
||||
content: Sample article content 1
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
- id: 2
|
||||
title: Article 2
|
||||
content: Sample article content 2
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
- id: 3
|
||||
title: Article 3
|
||||
content: Sample article content 3
|
||||
author_by_author_id:
|
||||
id: 2
|
||||
name: Author 2
|
||||
|]
|
||||
(combinationsObject response (map fromObject [articleOne, articleTwo, articleThree]))
|
||||
-- Equivalent python suite: test_nested_select_query_where_on_relationship
|
||||
-- https://github.com/hasura/graphql-engine/blob/369d1ab2f119634b0e27e9ed353fa3d08c22d3fb/server/tests-py/test_graphql_queries.py#L286
|
||||
it "Nested select on article with where condition" $ \testEnvironment ->
|
||||
shouldReturnYaml
|
||||
shouldReturnOneOfYaml
|
||||
opts
|
||||
( GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
@ -341,19 +390,33 @@ query {
|
||||
}
|
||||
|]
|
||||
)
|
||||
[yaml|
|
||||
data:
|
||||
hasura_article:
|
||||
- id: 1
|
||||
title: Article 1
|
||||
content: Sample article content 1
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
- id: 2
|
||||
title: Article 2
|
||||
content: Sample article content 2
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
( combinationsObject
|
||||
response
|
||||
( map
|
||||
fromObject
|
||||
[ [yaml|
|
||||
id: 1
|
||||
title: Article 1
|
||||
content: Sample article content 1
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
|],
|
||||
[yaml|
|
||||
id: 2
|
||||
title: Article 2
|
||||
content: Sample article content 2
|
||||
author_by_author_id:
|
||||
id: 1
|
||||
name: Author 1
|
||||
|]
|
||||
]
|
||||
)
|
||||
)
|
||||
|
||||
response :: Value -> Value
|
||||
response articles =
|
||||
[yaml|
|
||||
data:
|
||||
hasura_article: *articles
|
||||
|]
|
||||
|
Loading…
Reference in New Issue
Block a user