Migrate all HSpec tests to unified setup/teardown

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3901
GitOrigin-RevId: 3aa35b6f12c28f997dca1a1f9287a12c814152cb
This commit is contained in:
Aniket Deshpande 2022-03-10 16:48:13 +05:30 committed by hasura-bot
parent 4ccc830bb8
commit 45af1d99f4
18 changed files with 1084 additions and 1179 deletions

View File

@ -1,4 +1,5 @@
{-# OPTIONS -Wno-redundant-constraints #-}
{-# LANGUAGE ViewPatterns #-}
-- | BigQuery helpers.
module Harness.Backend.BigQuery
@ -84,19 +85,23 @@ createTable Schema.Table {tableName, tableColumns} = do
-- Foreign keys are not support by BigQuery
");"
]
where
scalarType :: Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT64"
Schema.TStr -> "STRING"
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
scalarType :: HasCallStack => Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT64"
Schema.TStr -> "STRING"
Schema.TUTCTime -> "DATETIME"
Schema.TBool -> "BIT"
t -> error $ "Unexpected scalar type used for BigQuery: " <> show t
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
-- | Serialize tableData into an SQL insert statement and execute it.
insertTable :: Schema.Table -> IO ()
@ -117,26 +122,28 @@ insertTable Schema.Table {tableName, tableColumns, tableData} = do
commaSeparated $ mkRow <$> tableData,
";"
]
where
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
-- | Post an http request to start tracking the table
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
-- | Post an http request to start tracking
-- Overriding here because bigquery's API is uncommon
trackTable :: State -> Schema.Table -> IO ()
trackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.bigqueryDataset
GraphqlEngine.postMetadata_ state $
let datasetName = T.pack Constants.bigqueryDataset
GraphqlEngine.postMetadata_
state
[yaml|
type: bigquery_track_table
args:
source: bigquery
table:
dataset: *schemaName
dataset: *datasetName
name: *tableName
|]
@ -150,22 +157,24 @@ dropTable Schema.Table {tableName} = do
projectId
$ T.unpack $
T.unwords
[ "DROP TABLE",
[ "DROP TABLE", -- we don't want @IF EXISTS@ here, because we don't want this to fail silently
T.pack Constants.bigqueryDataset <> "." <> tableName,
";"
]
-- | Post an http request to stop tracking the table
-- Overriding `Schema.trackTable` here because bigquery's API expects a `dataset` key
untrackTable :: State -> Schema.Table -> IO ()
untrackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.bigqueryDataset
GraphqlEngine.postMetadata_ state $
let datasetName = T.pack Constants.bigqueryDataset
GraphqlEngine.postMetadata_
state
[yaml|
type: bigquery_untrack_table
args:
source: bigquery
table:
dataset: *schemaName
dataset: *datasetName
name: *tableName
|]
@ -192,17 +201,24 @@ args:
project_id: *projectId
datasets: [*dataset]
|]
-- Setup and track tables
for_ tables $ \table -> do
createTable table
insertTable table
trackTable state table
-- Setup relationships
for_ tables $ \table -> do
Schema.trackObjectRelationships "bigquery" (T.pack Constants.bigqueryDataset) table state
Schema.trackArrayRelationships "bigquery" (T.pack Constants.bigqueryDataset) table state
-- | Teardown the schema and tracking in the most expected way.
-- NOTE: Certain test modules may warrant having their own version.
teardown :: [Schema.Table] -> (State, ()) -> IO ()
teardown tables (state, _) =
teardown (reverse -> tables) (state, _) = do
-- Teardown relationships first
for_ tables $ \table ->
Schema.untrackRelationships "bigquery" (T.pack Constants.bigqueryDataset) table state
-- Then teardown tables
for_ tables $ \table -> do
untrackTable state table
dropTable table

View File

@ -1,4 +1,5 @@
{-# OPTIONS -Wno-redundant-constraints #-}
{-# LANGUAGE ViewPatterns #-}
-- | CitusQL helpers. Pretty much the same as postgres. Could refactor
-- if we add more things here.
@ -108,40 +109,48 @@ createTable Schema.Table {tableName, tableColumns, tablePrimaryKey = pk, tableRe
<> (mkReference <$> tableReferences),
");"
]
where
scalarType :: Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "SERIAL"
Schema.TStr -> "VARCHAR"
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "CONSTRAINT FOREIGN KEY",
referenceLocalColumn,
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
scalarType :: HasCallStack => Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "SERIAL"
Schema.TStr -> "VARCHAR"
Schema.TUTCTime -> "TIMESTAMP"
Schema.TBool -> "BOOLEAN"
t -> error $ "Unexpected scalar type used for Citus: " <> show t
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "CONSTRAINT FOREIGN KEY",
"(",
referenceLocalColumn,
")",
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
-- | Serialize tableData into a Citus-SQL insert statement and execute it.
insertTable :: Schema.Table -> IO ()
@ -158,28 +167,18 @@ insertTable Schema.Table {tableName, tableColumns, tableData} =
commaSeparated $ mkRow <$> tableData,
";"
]
where
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
-- | Post an http request to start tracking the table
trackTable :: State -> Schema.Table -> IO ()
trackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.citusDb
GraphqlEngine.postMetadata_ state $
[yaml|
type: citus_track_table
args:
source: citus
table:
schema: *schemaName
name: *tableName
|]
trackTable state table = Schema.trackTable "citus" "citus" (T.pack Constants.citusDb) table state
-- | Serialize Table into a Citus-SQL DROP statement and execute it
dropTable :: Schema.Table -> IO ()
@ -187,24 +186,14 @@ dropTable Schema.Table {tableName} = do
run_ $
T.unpack $
T.unwords
[ "DROP TABLE IF EXISTS",
[ "DROP TABLE", -- we don't want @IF EXISTS@ here, because we don't want this to fail silently
T.pack Constants.citusDb <> "." <> tableName,
";"
]
-- | Post an http request to stop tracking the table
untrackTable :: State -> Schema.Table -> IO ()
untrackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.citusDb
GraphqlEngine.postMetadata_ state $
[yaml|
type: citus_untrack_table
args:
source: citus
table:
schema: *schemaName
name: *tableName
|]
untrackTable state table = Schema.untrackTable "citus" "citus" (T.pack Constants.citusDb) table state
-- | Setup the schema in the most expected way.
-- NOTE: Certain test modules may warrant having their own local version.
@ -212,17 +201,24 @@ setup :: [Schema.Table] -> (State, ()) -> IO ()
setup tables (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state defaultSourceMetadata
-- Setup and track tables
for_ tables $ \table -> do
createTable table
insertTable table
trackTable state table
-- Setup relationships
for_ tables $ \table -> do
Schema.trackObjectRelationships "citus" (T.pack Constants.citusDb) table state
Schema.trackArrayRelationships "citus" (T.pack Constants.citusDb) table state
-- | Teardown the schema and tracking in the most expected way.
-- NOTE: Certain test modules may warrant having their own version.
teardown :: [Schema.Table] -> (State, ()) -> IO ()
teardown tables (state, _) =
teardown (reverse -> tables) (state, _) = do
-- Teardown relationships first
for_ tables $ \table ->
Schema.untrackRelationships "citus" (T.pack Constants.citusDb) table state
-- Then teardown tables
for_ tables $ \table -> do
untrackTable state table
dropTable table

View File

@ -1,4 +1,5 @@
{-# OPTIONS -Wno-redundant-constraints #-}
{-# LANGUAGE ViewPatterns #-}
-- | MySQL helpers.
module Harness.Backend.Mysql
@ -105,40 +106,48 @@ createTable Schema.Table {tableName, tableColumns, tablePrimaryKey = pk, tableRe
<> (mkReference <$> tableReferences),
");"
]
where
scalarType :: Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT UNSIGNED"
Schema.TStr -> "TEXT"
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "CONSTRAINT FOREIGN KEY",
referenceLocalColumn,
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
scalarType :: HasCallStack => Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT UNSIGNED"
Schema.TStr -> "TEXT"
Schema.TUTCTime -> "DATETIME"
Schema.TBool -> "BIT"
t -> error $ "Unexpected scalar type used for MySQL: " <> show t
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "FOREIGN KEY",
"(",
referenceLocalColumn,
")",
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
-- | Serialize tableData into an SQL insert statement and execute it.
insertTable :: Schema.Table -> IO ()
@ -155,28 +164,18 @@ insertTable Schema.Table {tableName, tableColumns, tableData} =
commaSeparated $ mkRow <$> tableData,
";"
]
where
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
-- | Post an http request to start tracking the table
trackTable :: State -> Schema.Table -> IO ()
trackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.mysqlDatabase
GraphqlEngine.postMetadata_ state $
[yaml|
type: mysql_track_table
args:
source: mysql
table:
schema: *schemaName
name: *tableName
|]
trackTable state table = Schema.trackTable "mysql" "mysql" (T.pack Constants.mysqlDatabase) table state
-- | Serialize Table into an SQL DROP statement and execute it
dropTable :: Schema.Table -> IO ()
@ -184,24 +183,14 @@ dropTable Schema.Table {tableName} = do
run_ $
T.unpack $
T.unwords
[ "DROP TABLE",
[ "DROP TABLE", -- we don't want @IF EXISTS@ here, because we don't want this to fail silently
T.pack Constants.mysqlDatabase <> "." <> tableName,
";"
]
-- | Post an http request to stop tracking the table
untrackTable :: State -> Schema.Table -> IO ()
untrackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.mysqlDatabase
GraphqlEngine.postMetadata_ state $
[yaml|
type: mysql_untrack_table
args:
source: mysql
table:
schema: *schemaName
name: *tableName
|]
untrackTable state table = Schema.untrackTable "mysql" "mysql" (T.pack Constants.mysqlDatabase) table state
-- | Setup the schema in the most expected way.
-- NOTE: Certain test modules may warrant having their own local version.
@ -209,17 +198,24 @@ setup :: [Schema.Table] -> (State, ()) -> IO ()
setup tables (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state defaultSourceMetadata
-- Setup and track tables
for_ tables $ \table -> do
createTable table
insertTable table
trackTable state table
-- Setup relationships
for_ tables $ \table -> do
Schema.trackObjectRelationships "mysql" (T.pack Constants.mysqlDatabase) table state
Schema.trackArrayRelationships "mysql" (T.pack Constants.mysqlDatabase) table state
-- | Teardown the schema and tracking in the most expected way.
-- NOTE: Certain test modules may warrant having their own version.
teardown :: [Schema.Table] -> (State, ()) -> IO ()
teardown tables (state, _) =
teardown (reverse -> tables) (state, _) = do
-- Teardown relationships first
for_ tables $ \table ->
Schema.untrackRelationships "mysql" (T.pack Constants.mysqlDatabase) table state
-- Then teardown tables
for_ tables $ \table -> do
untrackTable state table
dropTable table

View File

@ -1,4 +1,5 @@
{-# OPTIONS -Wno-redundant-constraints #-}
{-# LANGUAGE ViewPatterns #-}
-- | PostgreSQL helpers.
module Harness.Backend.Postgres
@ -113,40 +114,48 @@ createTable Schema.Table {tableName, tableColumns, tablePrimaryKey = pk, tableRe
<> (mkReference <$> tableReferences),
");"
]
where
scalarType :: Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "SERIAL"
Schema.TStr -> "VARCHAR"
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "CONSTRAINT FOREIGN KEY",
referenceLocalColumn,
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
scalarType :: HasCallStack => Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT"
Schema.TStr -> "VARCHAR"
Schema.TUTCTime -> "TIMESTAMP"
Schema.TBool -> "BOOLEAN"
t -> error $ "Unexpected scalar type used for Postgres: " <> show t
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "CONSTRAINT FOREIGN KEY",
"(",
referenceLocalColumn,
")",
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
-- | Serialize tableData into a PL-SQL insert statement and execute it.
insertTable :: Schema.Table -> IO ()
@ -163,28 +172,18 @@ insertTable Schema.Table {tableName, tableColumns, tableData} =
commaSeparated $ mkRow <$> tableData,
";"
]
where
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
-- | Post an http request to start tracking the table
trackTable :: State -> Schema.Table -> IO ()
trackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.postgresDb
GraphqlEngine.postMetadata_ state $
[yaml|
type: postgres_track_table
args:
source: postgres
table:
schema: *schemaName
name: *tableName
|]
trackTable state table = Schema.trackTable "postgres" "postgres" (T.pack Constants.postgresDb) table state
-- | Serialize Table into a PL-SQL DROP statement and execute it
dropTable :: Schema.Table -> IO ()
@ -192,24 +191,14 @@ dropTable Schema.Table {tableName} = do
run_ $
T.unpack $
T.unwords
[ "DROP TABLE",
[ "DROP TABLE", -- we don't want @IF EXISTS@ here, because we don't want this to fail silently
T.pack Constants.postgresDb <> "." <> tableName,
";"
]
-- | Post an http request to stop tracking the table
untrackTable :: State -> Schema.Table -> IO ()
untrackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.postgresDb
GraphqlEngine.postMetadata_ state $
[yaml|
type: postgres_untrack_table
args:
source: postgres
table:
schema: *schemaName
name: *tableName
|]
untrackTable state table = Schema.untrackTable "postgres" "postgres" (T.pack Constants.postgresDb) table state
-- | Setup the schema in the most expected way.
-- NOTE: Certain test modules may warrant having their own local version.
@ -217,17 +206,24 @@ setup :: [Schema.Table] -> (State, ()) -> IO ()
setup tables (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state defaultSourceMetadata
-- Setup and track tables
for_ tables $ \table -> do
createTable table
insertTable table
trackTable state table
-- Setup relationships
for_ tables $ \table -> do
Schema.trackObjectRelationships "postgres" (T.pack Constants.postgresDb) table state
Schema.trackArrayRelationships "postgres" (T.pack Constants.postgresDb) table state
-- | Teardown the schema and tracking in the most expected way.
-- NOTE: Certain test modules may warrant having their own version.
teardown :: [Schema.Table] -> (State, ()) -> IO ()
teardown tables (state, _) =
teardown (reverse -> tables) (state, _) = do
-- Teardown relationships first
for_ tables $ \table ->
Schema.untrackRelationships "postgres" (T.pack Constants.postgresDb) table state
-- Then teardown tables
for_ tables $ \table -> do
untrackTable state table
dropTable table

View File

@ -1,4 +1,5 @@
{-# OPTIONS -Wno-redundant-constraints #-}
{-# LANGUAGE ViewPatterns #-}
-- | SQLServer helpers.
module Harness.Backend.Sqlserver
@ -28,7 +29,7 @@ import Data.Text qualified as T (pack, unpack, unwords)
import Data.Text.Extended (commaSeparated)
import Database.ODBC.SQLServer qualified as Sqlserver
import GHC.Stack
import Harness.Constants as Constants
import Harness.Constants qualified as Constants
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Yaml (yaml)
import Harness.State (State)
@ -92,6 +93,8 @@ connection_info:
database_url: *sqlserverConnectInfo
pool_settings: {}
|]
where
sqlserverConnectInfo = Constants.sqlserverConnectInfo
-- | Serialize Table into a T-SQL statement, as needed, and execute it on the Sqlserver backend
createTable :: Schema.Table -> IO ()
@ -108,40 +111,48 @@ createTable Schema.Table {tableName, tableColumns, tablePrimaryKey = pk, tableRe
<> (mkReference <$> tableReferences),
");"
]
where
scalarType :: Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT"
Schema.TStr -> "TEXT"
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "CONSTRAINT FOREIGN KEY",
referenceLocalColumn,
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
scalarType :: HasCallStack => Schema.ScalarType -> Text
scalarType = \case
Schema.TInt -> "INT"
Schema.TStr -> "NVARCHAR(127)"
Schema.TUTCTime -> "DATETIME"
Schema.TBool -> "BOOLEAN"
Schema.TVarchar50 -> "VARCHAR(50)"
mkColumn :: Schema.Column -> Text
mkColumn Schema.Column {columnName, columnType, columnNullable, columnDefault} =
T.unwords
[ columnName,
scalarType columnType,
bool "NOT NULL" "DEFAULT NULL" columnNullable,
maybe "" ("DEFAULT " <>) columnDefault
]
mkPrimaryKey :: [Text] -> Text
mkPrimaryKey key =
T.unwords
[ "PRIMARY KEY",
"(",
commaSeparated key,
")"
]
mkReference :: Schema.Reference -> Text
mkReference Schema.Reference {referenceLocalColumn, referenceTargetTable, referenceTargetColumn} =
T.unwords
[ "FOREIGN KEY",
"(",
referenceLocalColumn,
")",
"REFERENCES",
referenceTargetTable,
"(",
referenceTargetColumn,
")",
"ON DELETE CASCADE",
"ON UPDATE CASCADE"
]
-- | Serialize tableData into a T-SQL insert statement and execute it.
insertTable :: Schema.Table -> IO ()
@ -158,28 +169,18 @@ insertTable Schema.Table {tableName, tableColumns, tableData} =
commaSeparated $ mkRow <$> tableData,
";"
]
where
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
mkRow :: [Schema.ScalarValue] -> Text
mkRow row =
T.unwords
[ "(",
commaSeparated $ Schema.serialize <$> row,
")"
]
-- | Post an http request to start tracking the table
trackTable :: State -> Schema.Table -> IO ()
trackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.sqlserverDb
GraphqlEngine.postMetadata_ state $
[yaml|
type: mssql_track_table
args:
source: mssql
table:
schema: *schemaName
name: *tableName
|]
trackTable state table = Schema.trackTable "mssql" "mssql" (T.pack Constants.sqlserverDb) table state
-- | Serialize Table into a T-SQL DROP statement and execute it
dropTable :: Schema.Table -> IO ()
@ -187,24 +188,14 @@ dropTable Schema.Table {tableName} = do
run_ $
T.unpack $
T.unwords
[ "DROP TABLE",
[ "DROP TABLE", -- we don't want @IF EXISTS@ here, because we don't want this to fail silently
T.pack Constants.sqlserverDb <> "." <> tableName,
";"
]
-- | Post an http request to stop tracking the table
untrackTable :: State -> Schema.Table -> IO ()
untrackTable state Schema.Table {tableName} = do
let schemaName = T.pack Constants.sqlserverDb
GraphqlEngine.postMetadata_ state $
[yaml|
type: mssql_untrack_table
args:
source: mssql
table:
schema: *schemaName
name: *tableName
|]
untrackTable state table = Schema.untrackTable "mssql" "mssql" (T.pack Constants.sqlserverDb) table state
-- | Setup the schema in the most expected way.
-- NOTE: Certain test modules may warrant having their own local version.
@ -212,17 +203,24 @@ setup :: [Schema.Table] -> (State, ()) -> IO ()
setup tables (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state defaultSourceMetadata
-- Setup and track tables
for_ tables $ \table -> do
createTable table
insertTable table
trackTable state table
-- Setup relationships
for_ tables $ \table -> do
Schema.trackObjectRelationships "mssql" (T.pack Constants.sqlserverDb) table state
Schema.trackArrayRelationships "mssql" (T.pack Constants.sqlserverDb) table state
-- | Teardown the schema and tracking in the most expected way.
-- NOTE: Certain test modules may warrant having their own version.
teardown :: [Schema.Table] -> (State, ()) -> IO ()
teardown tables (state, _) =
teardown (reverse -> tables) (state, _) = do
-- Teardown relationship first
for_ tables $ \table ->
Schema.untrackRelationships "mssql" (T.pack Constants.sqlserverDb) table state
-- Then teardown tables
for_ tables $ \table -> do
untrackTable state table
dropTable table

View File

@ -7,10 +7,23 @@ module Harness.Test.Schema
ScalarValue (..),
serialize,
column,
columnNull,
parseUTCTimeOrError,
trackTable,
untrackTable,
trackObjectRelationships,
trackArrayRelationships,
untrackRelationships,
)
where
import Data.Text (Text, replace)
import Data.Foldable (for_)
import Data.Text (Text, pack, replace)
import Data.Time (UTCTime, defaultTimeLocale, formatTime)
import Data.Time.Format (parseTimeOrError)
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Yaml (yaml)
import Harness.State (State)
import Hasura.Prelude (tshow)
import Prelude
@ -25,11 +38,13 @@ import Prelude
-- need to be just a bit careful while constructing Tables.
data Table = Table
{ tableName :: Text,
-- | Columns that are references (foreign keys) should be null-able
tableColumns :: [Column],
tablePrimaryKey :: [Text],
tableReferences :: [Reference],
tableData :: [[ScalarValue]]
}
deriving (Show, Eq)
-- | Foreign keys for backends that support it.
data Reference = Reference
@ -37,6 +52,7 @@ data Reference = Reference
referenceTargetTable :: Text,
referenceTargetColumn :: Text
}
deriving (Show, Eq)
-- | Generic type to construct columns for all backends
data Column = Column
@ -45,6 +61,7 @@ data Column = Column
columnNullable :: Bool,
columnDefault :: Maybe Text
}
deriving (Show, Eq)
-- | Generic scalar type for all backends, for simplicity.
-- Ideally, we would be wiring in @'Backend@ specific scalar types here to make
@ -53,12 +70,23 @@ data Column = Column
data ScalarType
= TInt
| TStr
| TUTCTime
| TBool
| -- | Specialized. See: https://github.com/hasura/graphql-engine/issues/8158
-- session variable string values are not truncated to default (30) length in Test.RequestHeadersSpec
-- works with VStr
TVarchar50
deriving (Show, Eq)
-- | Generic scalar value type for all backends, that should directly correspond
-- to 'ScalarType'
data ScalarValue
= VInt Int
| VStr Text
| VUTCTime UTCTime
| VBool Bool
| VNull
deriving (Show, Eq)
-- | Generic 'ScalarValue' serializer.
--
@ -68,7 +96,132 @@ serialize :: ScalarValue -> Text
serialize = \case
VInt i -> tshow i
VStr s -> "'" <> replace "'" "\'" s <> "'"
VUTCTime t -> pack $ formatTime defaultTimeLocale "'%F %T'" t
VBool b -> tshow @Int $ if b then 1 else 0
VNull -> "NULL"
-- | Helper function to construct 'Column's with common defaults
column :: Text -> ScalarType -> Column
column name typ = Column name typ False Nothing
-- | Helper function to construct 'Column's that are null-able
columnNull :: Text -> ScalarType -> Column
columnNull name typ = Column name typ True Nothing
-- | Helper to construct UTCTime using @%F %T@ format. For e.g. @YYYY-MM-DD HH:MM:SS@
parseUTCTimeOrError :: String -> ScalarValue
parseUTCTimeOrError = VUTCTime . parseTimeOrError True defaultTimeLocale "%F %T"
-- | Unified track table
trackTable :: Text -> Text -> Text -> Table -> State -> IO ()
trackTable backendType sourceName schema Table {tableName} state = do
let requestType = backendType <> "_track_table"
GraphqlEngine.postMetadata_
state
[yaml|
type: *requestType
args:
source: *sourceName
table:
schema: *schema
name: *tableName
|]
-- | Unified untrack table
untrackTable :: Text -> Text -> Text -> Table -> State -> IO ()
untrackTable backendType sourceName schema Table {tableName} state = do
let requestType = backendType <> "_untrack_table"
GraphqlEngine.postMetadata_
state
[yaml|
type: *requestType
args:
source: *sourceName
table:
schema: *schema
name: *tableName
|]
-- | Helper to create the object relationship name
mkObjectRelationshipName :: Reference -> Text
mkObjectRelationshipName Reference {referenceLocalColumn, referenceTargetTable} = referenceTargetTable <> "_by_" <> referenceLocalColumn
-- | Unified track object relationships
trackObjectRelationships :: Text -> Text -> Table -> State -> IO ()
trackObjectRelationships source schema Table {tableName, tableReferences} state = do
let requestType = source <> "_create_object_relationship"
for_ tableReferences $ \ref@Reference {referenceLocalColumn} -> do
let relationshipName = mkObjectRelationshipName ref
GraphqlEngine.postMetadata_
state
[yaml|
type: *requestType
args:
source: *source
table:
name: *tableName
schema: *schema
name: *relationshipName
using:
foreign_key_constraint_on: *referenceLocalColumn
|]
-- | Helper to create the array relationship name
mkArrayRelationshipName :: Text -> Text -> Text
mkArrayRelationshipName tableName referenceLocalColumn = tableName <> "s_by_" <> referenceLocalColumn
-- | Unified track array relationships
trackArrayRelationships :: Text -> Text -> Table -> State -> IO ()
trackArrayRelationships source schema Table {tableName, tableReferences} state = do
let requestType = source <> "_create_array_relationship"
for_ tableReferences $ \Reference {referenceLocalColumn, referenceTargetTable} -> do
let relationshipName = mkArrayRelationshipName tableName referenceLocalColumn
GraphqlEngine.postMetadata_
state
[yaml|
type: *requestType
args:
source: *source
table:
name: *referenceTargetTable
schema: *schema
name: *relationshipName
using:
foreign_key_constraint_on:
table:
name: *tableName
schema: *schema
column: *referenceLocalColumn
|]
-- | Unified untrack relationships
untrackRelationships :: Text -> Text -> Table -> State -> IO ()
untrackRelationships source schema Table {tableName, tableReferences} state = do
let requestType = source <> "_drop_relationship"
for_ tableReferences $ \ref@Reference {referenceLocalColumn, referenceTargetTable} -> do
let arrayRelationshipName = mkArrayRelationshipName tableName referenceLocalColumn
objectRelationshipName = mkObjectRelationshipName ref
-- drop array relationships
GraphqlEngine.postMetadata_
state
[yaml|
type: *requestType
args:
source: *source
table:
schema: *schema
name: *referenceTargetTable
relationship: *arrayRelationshipName
|]
-- drop object relationships
GraphqlEngine.postMetadata_
state
[yaml|
type: *requestType
args:
source: *source
table:
schema: *schema
name: *tableName
relationship: *objectRelationshipName
|]

View File

@ -4,10 +4,10 @@ module Test.ArrayRelationshipsSpec (spec) where
import Harness.Backend.Mysql as Mysql
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -20,114 +20,74 @@ spec =
[ Context.Context
{ name = Context.MySQL,
mkLocalState = Context.noLocalState,
setup = mysqlSetup,
teardown = mysqlTeardown,
setup = Mysql.setup schema,
teardown = Mysql.teardown schema,
customOptions = Nothing
}
]
tests
--------------------------------------------------------------------------------
-- MySQL backend
-- Schema
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
schema :: [Schema.Table]
schema = [author, article]
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY,
createdAt DATETIME
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name, createdAt)
VALUES
( 'Author 1', '2017-09-21 09:39:44' ),
( 'Author 2', '2017-09-21 09:50:44' );
|]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr,
Schema.column "createdAt" Schema.TUTCTime
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1", Schema.parseUTCTimeOrError "2017-09-21 09:39:44"],
[Schema.VInt 2, Schema.VStr "Author 2", Schema.parseUTCTimeOrError "2017-09-21 09:50:44"]
]
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE article (
id INT NOT NULL AUTO_INCREMENT PRIMARY KEY,
title TEXT,
content TEXT,
is_published BIT,
published_on TIMESTAMP,
author_id INT UNSIGNED,
co_author_id INT UNSIGNED,
FOREIGN KEY (author_id) REFERENCES author(id),
FOREIGN KEY (co_author_id) REFERENCES author(id)
);
|]
Mysql.run_
[sql|
INSERT INTO article
(title, content, author_id, is_published)
VALUES
( 'Article 1', 'Sample article content 1', 1, 0 ),
( 'Article 2', 'Sample article content 2', 1, 1 ),
( 'Article 3', 'Sample article content 3', 2, 1 );
|]
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: bulk
args:
- type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: author
- type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: article
|]
-- Setup relationships
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_create_array_relationship
args:
source: mysql
table:
name: author
schema: hasura
name: articles
using:
foreign_key_constraint_on:
table:
name: article
schema: hasura
column: author_id
|]
mysqlTeardown :: (State, ()) -> IO ()
mysqlTeardown _ = do
Mysql.run_
[sql|
DROP TABLE article;
|]
Mysql.run_
[sql|
DROP TABLE author;
|]
article :: Schema.Table
article =
Schema.Table
"article"
[ Schema.column "id" Schema.TInt,
Schema.column "title" Schema.TStr,
Schema.column "content" Schema.TStr,
Schema.column "is_published" Schema.TBool,
Schema.column "published_on" Schema.TUTCTime,
Schema.columnNull "author_id" Schema.TInt,
Schema.columnNull "co_author_id" Schema.TInt
]
["id"]
[ Schema.Reference "author_id" "author" "id",
Schema.Reference "co_author_id" "author" "id"
]
[ [ Schema.VInt 1,
Schema.VStr "Article 1",
Schema.VStr "Sample article content 1",
Schema.VBool False,
Schema.parseUTCTimeOrError "2022-01-01 00:00:00",
Schema.VInt 1,
Schema.VInt 2
],
[ Schema.VInt 2,
Schema.VStr "Article 2",
Schema.VStr "Sample article content 2",
Schema.VBool True,
Schema.parseUTCTimeOrError "2022-01-01 00:00:00",
Schema.VInt 1,
Schema.VInt 2
],
[ Schema.VInt 3,
Schema.VStr "Article 3",
Schema.VStr "Sample article content 3",
Schema.VBool True,
Schema.parseUTCTimeOrError "2022-01-01 00:00:00",
Schema.VInt 2,
Schema.VInt 1
]
]
--------------------------------------------------------------------------------
-- Tests
@ -144,7 +104,8 @@ query {
# we put id=1 restrictions here because we don't assume ordering support
hasura_author(where: {id: {_eq: 1}}) {
id
articles(where: {id: {_eq: 1}}) {
# the _by_author_id part is necessary to distinguish between multiple foreign key relationships between the same two tables
articles_by_author_id(where: {id: {_eq: 1}}) {
id
}
}
@ -155,6 +116,6 @@ query {
data:
hasura_author:
- id: 1
articles:
articles_by_author_id:
- id: 1
|]

View File

@ -5,10 +5,10 @@ import Data.Aeson (Value)
import Harness.Backend.Mysql as Mysql
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -21,57 +21,31 @@ spec =
[ Context.Context
{ name = Context.MySQL,
mkLocalState = Context.noLocalState,
setup = mysqlSetup,
teardown = mysqlTeardown,
setup = Mysql.setup schema,
teardown = Mysql.teardown schema,
customOptions = Nothing
}
]
tests
--------------------------------------------------------------------------------
-- MySQL backend
-- Schema
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, ()) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
schema :: [Schema.Table]
schema = [author]
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name)
VALUES
( 'Author 1'),
( 'Author 2');
|]
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: author
|]
mysqlTeardown :: (State, ()) -> IO ()
mysqlTeardown _ = do
Mysql.run_
[sql|
DROP TABLE author;
|]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1"],
[Schema.VInt 2, Schema.VStr "Author 2"]
]
--------------------------------------------------------------------------------
-- Tests

View File

@ -4,10 +4,10 @@ module Test.LimitOffsetSpec (spec) where
import Harness.Backend.Mysql as Mysql
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -20,59 +20,33 @@ spec =
[ Context.Context
{ name = Context.MySQL,
mkLocalState = Context.noLocalState,
setup = mysqlSetup,
teardown = mysqlTeardown,
setup = Mysql.setup schema,
teardown = Mysql.teardown schema,
customOptions = Nothing
}
]
tests
--------------------------------------------------------------------------------
-- MySQL backend
-- Schema
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
schema :: [Schema.Table]
schema = [author]
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name)
VALUES
( 'Author 1'),
( 'Author 2'),
( 'Author 3'),
( 'Author 4');
|]
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: author
|]
mysqlTeardown :: (State, ()) -> IO ()
mysqlTeardown _ = do
Mysql.run_
[sql|
DROP TABLE author;
|]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1"],
[Schema.VInt 2, Schema.VStr "Author 2"],
[Schema.VInt 3, Schema.VStr "Author 3"],
[Schema.VInt 4, Schema.VStr "Author 4"]
]
--------------------------------------------------------------------------------
-- Tests

View File

@ -6,10 +6,10 @@ module Test.ObjectRelationshipsLimitSpec (spec) where
import Harness.Backend.Postgres as Postgres
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -32,6 +32,83 @@ spec =
--------------------------------------------------------------------------------
-- * Schema
schema :: [Schema.Table]
schema = [author, article]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr,
Schema.column "createdAt" Schema.TUTCTime
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1", Schema.parseUTCTimeOrError "2017-09-21 09:39:44"],
[Schema.VInt 2, Schema.VStr "Author 2", Schema.parseUTCTimeOrError "2017-09-21 09:50:44"],
[Schema.VInt 3, Schema.VStr "Author 1", Schema.parseUTCTimeOrError "2017-09-21 09:55:44"]
]
article :: Schema.Table
article =
Schema.Table
"article"
[ Schema.column "id" Schema.TInt,
Schema.column "author_name" Schema.TStr
]
["id"]
[] -- No references; we are using @manual_configuration@ to make the object relationship
[ [Schema.VInt 1, Schema.VStr "Author 1"],
[Schema.VInt 2, Schema.VStr "Author 2"]
]
--------------------------------------------------------------------------------
-- ** Setup and teardown override
postgresSetup :: (State, ()) -> IO ()
postgresSetup (state, ()) = do
Postgres.setup schema (state, ())
-- also setup special relationship
GraphqlEngine.postMetadata_ state $
[yaml|
type: pg_create_object_relationship
args:
source: postgres
table:
schema: hasura
name: article
name: author
using:
manual_configuration:
remote_table:
schema: hasura
name: author
column_mapping:
author_name: name
|]
postgresTeardown :: (State, ()) -> IO ()
postgresTeardown (state, ()) = do
-- first teardown special relationship
GraphqlEngine.postMetadata_ state $
[yaml|
type: pg_drop_relationship
args:
source: postgres
table:
schema: hasura
name: article
relationship: author
|]
-- and then rest of the teardown
Postgres.teardown schema (state, ())
--------------------------------------------------------------------------------
-- * Tests
-- | Many of these may return non-deterministic results because graphql-engine
@ -203,121 +280,3 @@ data:
aggregate:
count: 2
|]
--------------------------------------------------------------------------------
-- * Postgres backend
----------------------
-- ** Setup
postgresSetup :: (State, ()) -> IO ()
postgresSetup (state, ()) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Postgres.defaultSourceMetadata
postgresSetupTables
postgresInsertValues
postgresTrackTables state
postgresCreateRelationships state
postgresSetupTables :: IO ()
postgresSetupTables = do
-- Setup tables
Postgres.run_
[sql|
CREATE TABLE hasura.author
(
id SERIAL PRIMARY KEY,
name TEXT,
created_at TIMESTAMP
);
|]
Postgres.run_
[sql|
CREATE TABLE hasura.article (
id SERIAL PRIMARY KEY,
author_name TEXT
);
|]
postgresInsertValues :: IO ()
postgresInsertValues = do
Postgres.run_
[sql|
INSERT INTO hasura.author
(name, created_at)
VALUES
( 'Author 1', '2017-09-21 09:39:44' ),
( 'Author 2', '2017-09-21 09:50:44' ),
( 'Author 1', '2017-09-21 09:55:44' );
|]
Postgres.run_
[sql|
INSERT INTO hasura.article
(author_name)
VALUES
( 'Author 1' ),
( 'Author 2' );
|]
postgresTrackTables :: State -> IO ()
postgresTrackTables state = do
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_track_table
args:
source: postgres
table:
schema: hasura
name: author
|]
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_track_table
args:
source: postgres
table:
schema: hasura
name: article
|]
postgresCreateRelationships :: State -> IO ()
postgresCreateRelationships state = do
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_create_object_relationship
args:
source: postgres
table:
schema: hasura
name: article
name: author
using:
manual_configuration:
remote_table:
schema: hasura
name: author
column_mapping:
author_name: name
|]
----------------------
-- ** Teardown
postgresTeardown :: (State, ()) -> IO ()
postgresTeardown _ = do
Postgres.run_
[sql|
DROP TABLE IF EXISTS hasura.article;
|]
Postgres.run_
[sql|
DROP TABLE IF EXISTS hasura.author;
|]

View File

@ -1,15 +1,14 @@
-- | Testing object relationships.
module Test.ObjectRelationshipsSpec (spec) where
import Data.Text (Text)
import Harness.Backend.Mysql qualified as Mysql
import Harness.Backend.Sqlserver qualified as Sqlserver
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -22,8 +21,8 @@ spec = do
[ Context.Context
{ name = Context.SQLServer,
mkLocalState = Context.noLocalState,
setup = mssqlSetup,
teardown = \_ -> mssqlTeardown,
setup = Sqlserver.setup schema,
teardown = Sqlserver.teardown schema,
customOptions = Nothing
}
]
@ -33,15 +32,63 @@ spec = do
[ Context.Context
{ name = Context.MySQL,
mkLocalState = Context.noLocalState,
setup = mysqlSetup,
teardown = \_ -> mysqlTeardown,
setup = Mysql.setup schema,
teardown = Mysql.teardown schema,
customOptions = Nothing
}
]
mysqlTests
--------------------------------------------------------------------------------
-- Schema
schema :: [Schema.Table]
schema = [author, article]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1"],
[Schema.VInt 2, Schema.VStr "Author 2"]
]
article :: Schema.Table
article =
Schema.Table
"article"
[ Schema.column "id" Schema.TInt,
Schema.columnNull "author_id" Schema.TInt
]
["id"]
[Schema.Reference "author_id" "author" "id"]
[ [ Schema.VInt 1,
Schema.VInt 1
],
[ Schema.VInt 2,
Schema.VInt 1
],
[ Schema.VInt 3,
Schema.VInt 2
],
[ Schema.VInt 4,
Schema.VNull
]
]
--------------------------------------------------------------------------------
-- Tests
mssqlTests :: Context.Options -> SpecWith State
mssqlTests opts = do
usingWhereClause opts
nullField opts
mysqlTests :: Context.Options -> SpecWith State
mysqlTests opts = do
usingWhereClause opts
@ -50,11 +97,6 @@ mysqlTests opts = do
\ (https://github.com/hasura/graphql-engine-mono/issues/3650)"
(nullField opts)
mssqlTests :: Context.Options -> SpecWith State
mssqlTests opts = do
usingWhereClause opts
nullField opts
usingWhereClause :: Context.Options -> SpecWith State
usingWhereClause opts = do
it "Author of article where id=1" $ \state ->
@ -66,7 +108,7 @@ usingWhereClause opts = do
query {
hasura_article(where: {id: {_eq: 1}}) {
id
author {
author_by_author_id {
id
}
}
@ -77,7 +119,7 @@ query {
data:
hasura_article:
- id: 1
author:
author_by_author_id:
id: 1
|]
@ -92,7 +134,7 @@ nullField opts = do
query {
hasura_article(where: {id: {_eq: 4}}) {
id
author {
author_by_author_id {
id
}
}
@ -102,179 +144,6 @@ query {
[yaml|
data:
hasura_article:
- author: null
- author_by_author_id: null
id: 4
|]
--------------------------------------------------------------------------------
-- Unified test setup/teardown definitions
trackTableAuthor :: Text -> State -> IO ()
trackTableAuthor backendSource state = do
let requestType = backendSource <> "_track_table"
GraphqlEngine.post_
state
"/v1/metadata"
[yaml|
type: *requestType
args:
source: *backendSource
table:
schema: hasura
name: author
|]
trackTableArticle :: Text -> State -> IO ()
trackTableArticle backendSource state = do
let requestType = backendSource <> "_track_table"
GraphqlEngine.post_
state
"/v1/metadata"
[yaml|
type: *requestType
args:
source: *backendSource
table:
schema: hasura
name: article
|]
trackRelationshipArticleAuthor :: Text -> State -> IO ()
trackRelationshipArticleAuthor backendSource state = do
let requestType = backendSource <> "_create_object_relationship"
GraphqlEngine.post_
state
"/v1/metadata"
[yaml|
type: *requestType
args:
source: *backendSource
table:
name: article
schema: hasura
name: author
using:
foreign_key_constraint_on: author_id
|]
--------------------------------------------------------------------------------
-- MySQL backend
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
mysqlCreateTableAuthor
mysqlCreateTableArticle
trackTableAuthor "mysql" state
trackTableArticle "mysql" state
trackRelationshipArticleAuthor "mysql" state
mysqlCreateTableAuthor :: IO ()
mysqlCreateTableAuthor = do
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name)
VALUES
( 'Author 1' ),
( 'Author 2' );
|]
mysqlCreateTableArticle :: IO ()
mysqlCreateTableArticle = do
Mysql.run_
[sql|
CREATE TABLE article (
id INT NOT NULL AUTO_INCREMENT PRIMARY KEY,
author_id INT UNSIGNED,
FOREIGN KEY (author_id) REFERENCES author(id)
);
|]
Mysql.run_
[sql|
INSERT INTO article
(author_id)
VALUES
( 1 ),
( 1 ),
( 2 ),
( null );
|]
mysqlTeardown :: IO ()
mysqlTeardown = do
Mysql.run_ [sql| DROP TABLE article; |]
Mysql.run_ [sql| DROP TABLE author; |]
--------------------------------------------------------------------------------
-- MSSQL backend
mssqlSetup :: (State, ()) -> IO ()
mssqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Sqlserver.defaultSourceMetadata
mssqlCreateTableAuthor
mssqlCreateTableArticle
trackTableAuthor "mssql" state
trackTableArticle "mssql" state
trackRelationshipArticleAuthor "mssql" state
mssqlCreateTableAuthor :: IO ()
mssqlCreateTableAuthor = do
Sqlserver.run_
[sql|
CREATE TABLE author
(
id INT IDENTITY PRIMARY KEY,
name VARCHAR(45) UNIQUE
);
|]
Sqlserver.run_
[sql|
INSERT INTO author
(name)
VALUES
( 'Author 1' ),
( 'Author 2' );
|]
-- Setup tables
mssqlCreateTableArticle :: IO ()
mssqlCreateTableArticle = do
Sqlserver.run_
[sql|
CREATE TABLE article
(
id INT IDENTITY PRIMARY KEY,
author_id INT ,
FOREIGN KEY (author_id) REFERENCES author(id)
);
|]
Sqlserver.run_
[sql|
INSERT INTO article
(author_id)
VALUES
( 1 ),
( 1 ),
( 2 ),
( null );
|]
mssqlTeardown :: IO ()
mssqlTeardown = do
Sqlserver.run_ [sql| DROP TABLE article; |]
Sqlserver.run_ [sql| DROP TABLE author; |]

View File

@ -4,10 +4,10 @@ module Test.OrderingSpec (spec) where
import Harness.Backend.Mysql as Mysql
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -20,57 +20,31 @@ spec =
[ Context.Context
{ name = Context.MySQL,
mkLocalState = Context.noLocalState,
setup = mysqlSetup,
teardown = mysqlTeardown,
setup = Mysql.setup schema,
teardown = Mysql.teardown schema,
customOptions = Nothing
}
]
tests
--------------------------------------------------------------------------------
-- MySQL backend
-- Schema
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
schema :: [Schema.Table]
schema = [author]
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name)
VALUES
( 'Author 1'),
( 'Author 2');
|]
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: author
|]
mysqlTeardown :: (State, ()) -> IO ()
mysqlTeardown _ = do
Mysql.run_
[sql|
DROP TABLE author;
|]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1"],
[Schema.VInt 2, Schema.VStr "Author 2"]
]
--------------------------------------------------------------------------------
-- Tests

View File

@ -15,14 +15,16 @@ import Data.Aeson (Value)
import Data.Aeson.Lens (key, values, _String)
import Data.Foldable (for_)
import Data.Maybe qualified as Unsafe (fromJust)
import Data.Text qualified as T
import Harness.Backend.Postgres qualified as Postgres
import Harness.Constants qualified as Constants
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Sql (sql)
import Harness.Quoter.Yaml (shouldBeYaml, shouldReturnYaml, yaml)
import Harness.State (Server, State)
import Harness.Test.Context (Context (..))
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec (SpecWith, describe, it)
import Prelude
@ -127,6 +129,41 @@ rhsMSSQL :: (Value, Context)
rhsMSSQL = ([yaml|{"schema":"hasura", "name":"album"}|], Context "MSSQL" rhsMSSQLSetup rhsMSSQLTeardown)
-}
--------------------------------------------------------------------------------
-- Schema
-- | LHS
artist :: Schema.Table
artist =
Schema.Table
"artist"
[ Schema.columnNull "id" Schema.TInt,
Schema.column "name" Schema.TStr
]
[]
[]
[ [Schema.VInt 1, Schema.VStr "artist1"],
[Schema.VInt 2, Schema.VStr "artist2"],
[Schema.VInt 3, Schema.VStr "artist_no_albums"],
[Schema.VNull, Schema.VStr "artist_no_id"]
]
-- | RHS
album :: Schema.Table
album =
Schema.Table
"album"
[ Schema.column "id" Schema.TInt,
Schema.column "title" Schema.TStr,
Schema.columnNull "artist_id" Schema.TInt
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "album1_artist1", Schema.VInt 1],
[Schema.VInt 2, Schema.VStr "album2_artist1", Schema.VInt 1],
[Schema.VInt 3, Schema.VStr "album3_artist2", Schema.VInt 2]
]
--------------------------------------------------------------------------------
-- LHS Postgres
@ -135,53 +172,54 @@ lhsPostgresMkLocalState _ = pure Nothing
lhsPostgresSetup :: Value -> (State, Maybe Server) -> IO ()
lhsPostgresSetup rhsTableName (state, _) = do
Postgres.run_
[sql|
create table hasura.artist (
id int null,
name text not null
);
insert into hasura.artist (id, name) values
(1, 'artist1'),
(2, 'artist2'),
(3, 'artist_no_albums'),
(null, 'artist_no_id');
|]
let lhsTableName = [yaml|{"schema":"hasura", "name":"artist"}|]
let sourceName = "source"
sourceConfig = Postgres.defaultSourceConfiguration
schemaName = T.pack Constants.postgresDb
-- Add remote source
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_add_source
args:
name: *sourceName
configuration: *sourceConfig
|]
-- setup tables only
Postgres.createTable artist
Postgres.insertTable artist
Schema.trackTable "postgres" sourceName schemaName artist state
GraphqlEngine.postMetadata_
state
[yaml|
type: bulk
args:
- type: pg_add_source
args:
name: source
configuration: *sourceConfig
- type: pg_track_table
args:
source: source
table: *lhsTableName
- type: pg_create_select_permission
args:
source: source
source: *sourceName
role: role1
table: *lhsTableName
table:
schema: *schemaName
name: artist
permission:
columns: '*'
filter: {}
- type: pg_create_select_permission
args:
source: source
source: *sourceName
role: role2
table: *lhsTableName
table:
schema: *schemaName
name: artist
permission:
columns: '*'
filter: {}
- type: pg_create_remote_relationship
args:
source: source
table: *lhsTableName
source: *sourceName
table:
schema: *schemaName
name: artist
name: albums
definition:
to_source:
@ -193,50 +231,46 @@ args:
|]
lhsPostgresTeardown :: (State, Maybe Server) -> IO ()
lhsPostgresTeardown _ =
Postgres.run_
[sql|
DROP TABLE hasura.artist;
|]
lhsPostgresTeardown (state, _) = do
let sourceName = "source"
schemaName = T.pack Constants.postgresDb
Schema.untrackTable "postgres" sourceName schemaName artist state
Postgres.dropTable artist
--------------------------------------------------------------------------------
-- RHS Postgres
rhsPostgresSetup :: (State, ()) -> IO ()
rhsPostgresSetup (state, _) = do
Postgres.run_
[sql|
create table hasura.album (
id serial primary key,
title text not null,
artist_id int null
);
insert into hasura.album (title, artist_id) values
('album1_artist1', 1),
('album2_artist1', 1),
('album3_artist2', 2);
|]
let rhsTableName = [yaml|{"schema":"hasura", "name":"album"}|]
let sourceName = "target"
sourceConfig = Postgres.defaultSourceConfiguration
schemaName = T.pack Constants.postgresDb
-- Add remote source
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_add_source
args:
name: *sourceName
configuration: *sourceConfig
|]
-- setup tables only
Postgres.createTable album
Postgres.insertTable album
Schema.trackTable "postgres" sourceName schemaName album state
GraphqlEngine.postMetadata_
state
[yaml|
type: bulk
args:
- type: pg_add_source
args:
name: target
configuration: *sourceConfig
- type: pg_track_table
args:
source: target
table: *rhsTableName
- type: pg_create_select_permission
args:
source: target
source: *sourceName
role: role1
table: *rhsTableName
table:
schema: *schemaName
name: album
permission:
columns:
- title
@ -246,9 +280,11 @@ args:
_eq: x-hasura-artist-id
- type: pg_create_select_permission
args:
source: target
source: *sourceName
role: role2
table: *rhsTableName
table:
schema: *schemaName
name: album
permission:
columns: [id, title, artist_id]
filter:
@ -259,11 +295,11 @@ args:
|]
rhsPostgresTeardown :: (State, ()) -> IO ()
rhsPostgresTeardown _ =
Postgres.run_
[sql|
DROP TABLE hasura.album;
|]
rhsPostgresTeardown (state, _) = do
let sourceName = "target"
schemaName = T.pack Constants.postgresDb
Schema.untrackTable "postgres" sourceName schemaName album state
Postgres.dropTable album
--------------------------------------------------------------------------------
-- Tests
@ -376,8 +412,7 @@ schemaTests _opts =
[ albumsField ^?! key "args",
albumsAggregateField ^?! key "args"
]
\schema ->
schema `shouldBeYaml` relationshipFieldArgsSchema
(`shouldBeYaml` relationshipFieldArgsSchema)
-- check the return type of albums field
shouldBeYaml

View File

@ -9,14 +9,16 @@
module Test.RemoteRelationship.XToDBObjectRelationshipSpec (spec) where
import Data.Aeson (Value)
import Data.Text qualified as T
import Harness.Backend.Postgres qualified as Postgres
import Harness.Constants qualified as Constants
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Sql (sql)
import Harness.Quoter.Yaml (shouldReturnYaml, yaml)
import Harness.State (Server, State)
import Harness.Test.Context (Context (..))
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec (SpecWith, describe, it)
import Prelude
@ -121,6 +123,46 @@ rhsMSSQL :: (Value, Context)
rhsMSSQL = ([yaml|{"schema":"hasura", "name":"album"}|], Context "MSSQL" rhsMSSQLSetup rhsMSSQLTeardown)
-}
--------------------------------------------------------------------------------
-- Schema
-- | LHS
track :: Schema.Table
track =
Schema.Table
"track"
[ Schema.column "id" Schema.TInt,
Schema.column "title" Schema.TStr,
Schema.columnNull "album_id" Schema.TInt
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "track1_album1", Schema.VInt 1],
[Schema.VInt 2, Schema.VStr "track2_album1", Schema.VInt 1],
[Schema.VInt 3, Schema.VStr "track3_album1", Schema.VInt 1],
[Schema.VInt 4, Schema.VStr "track1_album2", Schema.VInt 2],
[Schema.VInt 5, Schema.VStr "track2_album2", Schema.VInt 2],
[Schema.VInt 6, Schema.VStr "track1_album3", Schema.VInt 3],
[Schema.VInt 7, Schema.VStr "track2_album3", Schema.VInt 3],
[Schema.VInt 8, Schema.VStr "track_no_album", Schema.VNull]
]
-- | RHS
album :: Schema.Table
album =
Schema.Table
"album"
[ Schema.column "id" Schema.TInt,
Schema.column "title" Schema.TStr,
Schema.columnNull "artist_id" Schema.TInt
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "album1_artist1", Schema.VInt 1],
[Schema.VInt 2, Schema.VStr "album2_artist1", Schema.VInt 1],
[Schema.VInt 3, Schema.VStr "album3_artist2", Schema.VInt 2]
]
--------------------------------------------------------------------------------
-- LHS Postgres
@ -129,58 +171,53 @@ lhsPostgresMkLocalState _ = pure Nothing
lhsPostgresSetup :: Value -> (State, Maybe Server) -> IO ()
lhsPostgresSetup rhsTableName (state, _) = do
Postgres.run_
[sql|
create table hasura.track (
id serial primary key,
title text not null,
album_id int null
);
insert into hasura.track (title, album_id) values
('track1_album1', 1),
('track2_album1', 1),
('track3_album1', 1),
('track1_album2', 2),
('track2_album2', 2),
('track1_album3', 3),
('track2_album3', 3),
('track_no_album', null);
|]
let lhsTableName = [yaml|{"schema":"hasura", "name":"track"}|]
let sourceName = "source"
sourceConfig = Postgres.defaultSourceConfiguration
schemaName = T.pack Constants.postgresDb
-- Add remote source
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_add_source
args:
name: *sourceName
configuration: *sourceConfig
|]
-- setup tables only
Postgres.createTable track
Postgres.insertTable track
Schema.trackTable "postgres" sourceName schemaName track state
GraphqlEngine.postMetadata_
state
[yaml|
type: bulk
args:
- type: pg_add_source
args:
name: source
configuration: *sourceConfig
- type: pg_track_table
args:
source: source
table: *lhsTableName
- type: pg_create_select_permission
args:
source: source
source: *sourceName
role: role1
table: *lhsTableName
table:
schema: *schemaName
name: track
permission:
columns: '*'
filter: {}
- type: pg_create_select_permission
args:
source: source
source: *sourceName
role: role2
table: *lhsTableName
table:
schema: *schemaName
name: track
permission:
columns: '*'
filter: {}
- type: pg_create_remote_relationship
args:
source: source
table: *lhsTableName
source: *sourceName
table:
schema: *schemaName
name: track
name: album
definition:
to_source:
@ -192,46 +229,46 @@ args:
|]
lhsPostgresTeardown :: (State, Maybe Server) -> IO ()
lhsPostgresTeardown _ = Postgres.run_ [sql|drop table hasura.track;|]
lhsPostgresTeardown (state, _) = do
let sourceName = "source"
schemaName = T.pack Constants.postgresDb
Schema.untrackTable "postgres" sourceName schemaName track state
Postgres.dropTable track
--------------------------------------------------------------------------------
-- RHS Postgres
rhsPostgresSetup :: (State, ()) -> IO ()
rhsPostgresSetup (state, _) = do
Postgres.run_
[sql|
create table hasura.album (
id serial primary key,
title text not null,
artist_id int null
);
insert into hasura.album (title, artist_id) values
('album1_artist1', 1),
('album2_artist1', 1),
('album3_artist2', 2);
|]
let rhsTableName = [yaml|{"schema":"hasura", "name":"album"}|]
let sourceName = "target"
sourceConfig = Postgres.defaultSourceConfiguration
schemaName = T.pack Constants.postgresDb
-- Add remote source
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_add_source
args:
name: *sourceName
configuration: *sourceConfig
|]
-- setup tables only
Postgres.createTable album
Postgres.insertTable album
Schema.trackTable "postgres" sourceName schemaName album state
GraphqlEngine.postMetadata_
state
[yaml|
type: bulk
args:
- type: pg_add_source
args:
name: target
configuration: *sourceConfig
- type: pg_track_table
args:
source: target
table: *rhsTableName
- type: pg_create_select_permission
args:
source: target
source: *sourceName
role: role1
table: *rhsTableName
table:
schema: *schemaName
name: album
permission:
columns:
- title
@ -241,9 +278,11 @@ args:
_eq: x-hasura-artist-id
- type: pg_create_select_permission
args:
source: target
source: *sourceName
role: role2
table: *rhsTableName
table:
schema: *schemaName
name: album
permission:
columns: [id, title, artist_id]
filter:
@ -254,17 +293,17 @@ args:
|]
rhsPostgresTeardown :: (State, ()) -> IO ()
rhsPostgresTeardown _ =
Postgres.run_
[sql|
DROP TABLE hasura.album;
|]
rhsPostgresTeardown (state, _) = do
let sourceName = "target"
schemaName = T.pack Constants.postgresDb
Schema.untrackTable "postgres" sourceName schemaName album state
Postgres.dropTable album
--------------------------------------------------------------------------------
-- Tests
tests :: Context.Options -> SpecWith (State, Maybe Server)
tests opts = do
tests opts = describe "object-relationship" $ do
schemaTests opts
executionTests opts
permissionTests opts

View File

@ -10,15 +10,17 @@ module Test.RemoteRelationship.XToRemoteSchemaRelationshipSpec (spec) where
import Data.Morpheus.Document (gqlDocument)
import Data.Morpheus.Types (Arg (..))
import Data.Text (Text)
import Data.Text qualified as T
import Harness.Backend.Postgres qualified as Postgres
import Harness.Constants qualified as Constants
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Sql (sql)
import Harness.Quoter.Yaml (shouldReturnYaml, yaml)
import Harness.RemoteServer qualified as RemoteServer
import Harness.State (Server, State)
import Harness.Test.Context (Context (..))
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec (SpecWith, describe, it)
import Prelude
@ -71,6 +73,32 @@ data LocalTestState = LocalTestState
_rhsServer :: Server
}
--------------------------------------------------------------------------------
-- Schema
-- | LHS
track :: Schema.Table
track =
Schema.Table
"track"
[ Schema.column "id" Schema.TInt,
Schema.column "title" Schema.TStr,
Schema.columnNull "album_id" Schema.TInt
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "track1_album1", Schema.VInt 1],
[Schema.VInt 2, Schema.VStr "track2_album1", Schema.VInt 1],
[Schema.VInt 3, Schema.VStr "track3_album1", Schema.VInt 1],
[Schema.VInt 4, Schema.VStr "track1_album2", Schema.VInt 2],
[Schema.VInt 5, Schema.VStr "track2_album2", Schema.VInt 2],
[Schema.VInt 6, Schema.VStr "track1_album3", Schema.VInt 3],
[Schema.VInt 7, Schema.VStr "track2_album3", Schema.VInt 3],
[Schema.VInt 8, Schema.VStr "track_no_album", Schema.VNull]
]
-- RHS schema is defined by the @gqlDocument@
--------------------------------------------------------------------------------
-- LHS Postgres
@ -79,42 +107,33 @@ lhsPostgresMkLocalState _ = pure Nothing
lhsPostgresSetup :: (State, Maybe Server) -> IO ()
lhsPostgresSetup (state, _) = do
Postgres.run_
[sql|
create table hasura.track (
id serial primary key,
title text not null,
album_id int null
);
insert into hasura.track (title, album_id) values
('track1_album1', 1),
('track2_album1', 1),
('track3_album1', 1),
('track1_album2', 2),
('track2_album2', 2),
('track1_album3', 3),
('track2_album3', 3),
('track_no_album', null);
|]
let lhsTableName = [yaml|{"schema":"hasura", "name":"track"}|]
let sourceName = "source"
sourceConfig = Postgres.defaultSourceConfiguration
schemaName = T.pack Constants.postgresDb
-- Add remote source
GraphqlEngine.postMetadata_
state
[yaml|
type: pg_add_source
args:
name: *sourceName
configuration: *sourceConfig
|]
-- setup tables only
Postgres.createTable track
Postgres.insertTable track
Schema.trackTable "postgres" sourceName schemaName track state
GraphqlEngine.postMetadata_
state
[yaml|
type: bulk
args:
- type: pg_add_source
args:
name: source
configuration: *sourceConfig
- type: pg_track_table
args:
source: source
table: *lhsTableName
- type: pg_create_remote_relationship
args:
source: source
table: *lhsTableName
table:
schema: *schemaName
name: track
name: album
definition:
to_remote_schema:
@ -127,7 +146,11 @@ args:
|]
lhsPostgresTeardown :: (State, Maybe Server) -> IO ()
lhsPostgresTeardown _ = Postgres.run_ [sql|drop table hasura.track;|]
lhsPostgresTeardown (state, _) = do
let sourceName = "source"
schemaName = T.pack Constants.postgresDb
Schema.untrackTable "postgres" sourceName schemaName track state
Postgres.dropTable track
--------------------------------------------------------------------------------
-- RHS Remote Server
@ -156,7 +179,7 @@ rhsRemoteServerMkLocalState _ =
(2, ("album2_artist1", Just 1)),
(3, ("album3_artist2", Just 2))
]
album (Arg albumId) = pure $ fmap (mkAlbum albumId) $ lookup albumId albums
album (Arg albumId) = pure $ mkAlbum albumId <$> lookup albumId albums
mkAlbum albumId (title, artist_id) =
Album
{ id = pure albumId,
@ -184,7 +207,7 @@ rhsRemoteSchemaTeardown (_, server) = GraphqlEngine.stopServer server
-- Tests
tests :: Context.Options -> SpecWith (State, LocalTestState)
tests opts = do
tests opts = describe "remote-schema-relationship" $ do
schemaTests opts
executionTests opts

View File

@ -4,10 +4,10 @@ module Test.RequestHeadersSpec (spec) where
import Harness.Backend.Sqlserver qualified as Sqlserver
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql (graphql)
import Harness.Quoter.Sql (sql)
import Harness.Quoter.Yaml (shouldReturnYaml, yaml)
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec (SpecWith, it)
import Prelude
@ -29,8 +29,66 @@ spec =
tests
--------------------------------------------------------------------------------
-- Schema
-- * Tests
schema :: [Schema.Table]
schema = [author]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "uuid" Schema.TVarchar50,
Schema.column "name" Schema.TStr
]
["uuid"]
[]
[ [Schema.VStr "36a6257b-08bb-45ef-a5cf-c1b7a7997087", Schema.VStr "Author 1"],
[Schema.VStr "36a6257b-08bb-45ef-a5cf-c1b7a7", Schema.VStr "Author 2"]
]
--------------------------------------------------------------------------------
-- Setup and teardown override
sqlserverSetup :: (State, ()) -> IO ()
sqlserverSetup (state, _) = do
Sqlserver.setup schema (state, ())
-- create permissions
GraphqlEngine.postMetadata_
state
[yaml|
type: mssql_create_select_permission
args:
source: mssql
table:
schema: hasura
name: author
role: user
permission:
filter:
uuid: X-Hasura-User-Id
columns: '*'
|]
sqlserverTeardown :: (State, ()) -> IO ()
sqlserverTeardown (state, _) = do
-- drop permissions
GraphqlEngine.postMetadata_
state
[yaml|
type: mssql_drop_select_permission
args:
source: mssql
table:
schema: hasura
name: author
role: user
|]
-- rest of the teardown
Sqlserver.teardown schema (state, ())
--------------------------------------------------------------------------------
-- Tests
tests :: Context.Options -> SpecWith State
tests opts = do
@ -58,88 +116,3 @@ data:
- name: 'Author 1'
uuid: '36a6257b-08bb-45ef-a5cf-c1b7a7997087'
|]
--------------------------------------------------------------------------------
-- * SQL Server backend
-- ** Setup
sqlserverSetup :: (State, ()) -> IO ()
sqlserverSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Sqlserver.defaultSourceMetadata
-- Setup
sqlserverSetupTables
sqlserverInsertValues
sqlserverTrackTables state
sqlserverCreateRelationships state
sqlserverCreatePermissions state
sqlserverSetupTables :: IO ()
sqlserverSetupTables = do
-- Setup tables
Sqlserver.run_
[sql|
CREATE TABLE hasura.author
(
uuid VARCHAR(50) NOT NULL PRIMARY KEY,
name NVARCHAR(50) NOT NULL
);
|]
sqlserverInsertValues :: IO ()
sqlserverInsertValues = do
Sqlserver.run_
[sql|
INSERT INTO hasura.author
(uuid, name)
VALUES
('36a6257b-08bb-45ef-a5cf-c1b7a7997087', 'Author 1'),
('36a6257b-08bb-45ef-a5cf-c1b7a7', 'Author 2');
|]
sqlserverTrackTables :: State -> IO ()
sqlserverTrackTables state = do
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: mssql_track_table
args:
source: mssql
table:
schema: hasura
name: author
|]
sqlserverCreateRelationships :: State -> IO ()
sqlserverCreateRelationships _ = do
pure ()
sqlserverCreatePermissions :: State -> IO ()
sqlserverCreatePermissions state = do
GraphqlEngine.postMetadata_
state
[yaml|
type: mssql_create_select_permission
args:
source: mssql
table:
schema: hasura
name: author
role: user
permission:
filter:
uuid: X-Hasura-User-Id
columns: '*'
|]
-- ** Teardown
sqlserverTeardown :: (State, ()) -> IO ()
sqlserverTeardown _ = do
Sqlserver.run_
[sql|
DROP TABLE hasura.author;
|]

View File

@ -8,6 +8,7 @@ import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -28,52 +29,38 @@ spec =
tests
--------------------------------------------------------------------------------
-- MySQL backend
-- Schema
schema :: [Schema.Table]
schema = [author]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr,
Schema.column "createdAt" Schema.TUTCTime
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1", Schema.parseUTCTimeOrError "2017-09-21 09:39:44"],
[Schema.VInt 2, Schema.VStr "Author 2", Schema.parseUTCTimeOrError "2017-09-21 09:50:44"]
]
--------------------------------------------------------------------------------
-- Setup and Teardown
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY,
createdAt DATETIME
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name, createdAt)
VALUES
( 'Author 1', '2017-09-21 09:39:44' ),
( 'Author 2', '2017-09-21 09:50:44' );
|]
Mysql.setup schema (state, ())
-- Setup views
Mysql.run_
[sql|
CREATE OR REPLACE VIEW search_author_view AS
SELECT * FROM author;
|]
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: author
|]
-- Track the views
GraphqlEngine.postMetadata_
state
[yaml|
@ -86,14 +73,22 @@ args:
|]
mysqlTeardown :: (State, ()) -> IO ()
mysqlTeardown _ = do
Mysql.run_
[sql|
DROP VIEW IF EXISTS search_author_view;
mysqlTeardown (state, _) = do
Mysql.teardown schema (state, ())
-- unrack the views
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_untrack_table
args:
source: mysql
table:
name: search_author_view
schema: hasura
|]
Mysql.run_
[sql|
DROP TABLE author;
DROP VIEW IF EXISTS search_author_view;
|]
--------------------------------------------------------------------------------

View File

@ -4,10 +4,10 @@ module Test.WhereSpec (spec) where
import Harness.Backend.Mysql as Mysql
import Harness.GraphqlEngine qualified as GraphqlEngine
import Harness.Quoter.Graphql
import Harness.Quoter.Sql
import Harness.Quoter.Yaml
import Harness.State (State)
import Harness.Test.Context qualified as Context
import Harness.Test.Schema qualified as Schema
import Test.Hspec
import Prelude
@ -20,57 +20,31 @@ spec =
[ Context.Context
{ name = Context.MySQL,
mkLocalState = Context.noLocalState,
setup = mysqlSetup,
teardown = mysqlTeardown,
setup = Mysql.setup schema,
teardown = Mysql.teardown schema,
customOptions = Nothing
}
]
tests
--------------------------------------------------------------------------------
-- MySQL backend
-- Schema
mysqlSetup :: (State, ()) -> IO ()
mysqlSetup (state, _) = do
-- Clear and reconfigure the metadata
GraphqlEngine.setSource state Mysql.defaultSourceMetadata
schema :: [Schema.Table]
schema = [author]
-- Setup tables
Mysql.run_
[sql|
CREATE TABLE author
(
id INT UNSIGNED NOT NULL AUTO_INCREMENT PRIMARY KEY,
name VARCHAR(45) UNIQUE KEY
);
|]
Mysql.run_
[sql|
INSERT INTO author
(name)
VALUES
( 'Author 1'),
( 'Author 2');
|]
-- Track the tables
GraphqlEngine.postMetadata_
state
[yaml|
type: mysql_track_table
args:
source: mysql
table:
schema: hasura
name: author
|]
mysqlTeardown :: (State, ()) -> IO ()
mysqlTeardown _ = do
Mysql.run_
[sql|
DROP TABLE author;
|]
author :: Schema.Table
author =
Schema.Table
"author"
[ Schema.column "id" Schema.TInt,
Schema.column "name" Schema.TStr
]
["id"]
[]
[ [Schema.VInt 1, Schema.VStr "Author 1"],
[Schema.VInt 2, Schema.VStr "Author 2"]
]
--------------------------------------------------------------------------------
-- Tests