mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
Block adding remote relationships where they are not supported by the Data Connector agent
[GDC-1015]: https://hasurahq.atlassian.net/browse/GDC-1015?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8232 GitOrigin-RevId: 0cc3b7b1f17b2e6d4cdfa713b1581357de62f359
This commit is contained in:
parent
650e17df3c
commit
1727b5236a
@ -5,11 +5,12 @@ module Test.DataConnector.MockAgent.RemoteRelationshipsSpec (spec) where
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
import Control.Lens ((.~), _Just)
|
||||
import Data.Aeson qualified as Aeson
|
||||
import Data.HashMap.Strict qualified as HashMap
|
||||
import Data.List.NonEmpty qualified as NE
|
||||
import Data.List.NonEmpty qualified as NonEmpty
|
||||
import Harness.Backend.DataConnector.Mock (AgentRequest (..), MockRequestResults (..), mockAgentGraphqlTest, mockQueryResponse)
|
||||
import Harness.Backend.DataConnector.Mock (AgentRequest (..), MockConfig, MockRequestResults (..), mockAgentGraphqlTest, mockQueryResponse)
|
||||
import Harness.Backend.DataConnector.Mock qualified as Mock
|
||||
import Harness.Backend.Postgres qualified as Postgres
|
||||
import Harness.GraphqlEngine qualified as GraphqlEngine
|
||||
@ -20,19 +21,35 @@ import Harness.Test.Fixture qualified as Fixture
|
||||
import Harness.Test.Schema (Table (..))
|
||||
import Harness.Test.Schema qualified as Schema
|
||||
import Harness.TestEnvironment (GlobalTestEnvironment, TestEnvironment)
|
||||
import Harness.Yaml (shouldBeYaml)
|
||||
import Harness.Yaml (shouldBeYaml, shouldReturnYaml)
|
||||
import Hasura.Backends.DataConnector.API qualified as API
|
||||
import Hasura.Prelude
|
||||
import Test.Hspec (HasCallStack, SpecWith, describe, shouldBe)
|
||||
import Test.Hspec (HasCallStack, SpecWith, describe, it, shouldBe)
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
spec :: SpecWith GlobalTestEnvironment
|
||||
spec =
|
||||
spec = describe "Remote Relationships Tests" $ do
|
||||
Fixture.runWithLocalTestEnvironment
|
||||
( NE.fromList
|
||||
[ (Fixture.fixture $ Fixture.Backend Mock.backendTypeMetadata)
|
||||
{ Fixture.mkLocalTestEnvironment = Mock.mkLocalTestEnvironment,
|
||||
Fixture.setupTeardown = \(testEnv, mockEnv) ->
|
||||
[ -- First set up the mock server source, which will be the remote relationship target
|
||||
Mock.setupAction sourceMetadata Mock.agentConfig (testEnv, mockEnv),
|
||||
-- Then set up the postgres source which will be the remote relationship source
|
||||
-- including registering the remote relationships
|
||||
Fixture.SetupAction (setupPostgres testEnv >> registerRemoteRelationships testEnv) (const (teardownPostgres testEnv))
|
||||
]
|
||||
}
|
||||
]
|
||||
)
|
||||
tests
|
||||
|
||||
Fixture.runWithLocalTestEnvironment
|
||||
( NE.fromList
|
||||
[ (Fixture.fixture $ Fixture.Backend Mock.backendTypeMetadata)
|
||||
{ Fixture.mkLocalTestEnvironment = Mock.mkLocalTestEnvironment' chinookMockThatDoesNotSupportForeachQueries,
|
||||
Fixture.setupTeardown = \(testEnv, mockEnv) ->
|
||||
[ -- First set up the mock server source, which will be the remote relationship target
|
||||
Mock.setupAction sourceMetadata Mock.agentConfig (testEnv, mockEnv),
|
||||
@ -42,7 +59,11 @@ spec =
|
||||
}
|
||||
]
|
||||
)
|
||||
tests
|
||||
errorTests
|
||||
where
|
||||
chinookMockThatDoesNotSupportForeachQueries :: MockConfig
|
||||
chinookMockThatDoesNotSupportForeachQueries =
|
||||
Mock.chinookMock {Mock._capabilitiesResponse = Mock._capabilitiesResponse Mock.chinookMock & API.crCapabilities . API.cQueries . _Just . API.qcForeach .~ Nothing}
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
@ -86,11 +107,12 @@ postgresTables =
|
||||
}
|
||||
]
|
||||
|
||||
pgSourceName :: String
|
||||
pgSourceName = "pg_source"
|
||||
|
||||
setupPostgres :: HasCallStack => TestEnvironment -> IO ()
|
||||
setupPostgres testEnv = do
|
||||
let pgSourceName :: String = "pg_source"
|
||||
mockAgentSourceName = BackendType.backendSourceName Mock.backendTypeMetadata
|
||||
sourceConfig = Postgres.defaultSourceConfiguration testEnv
|
||||
let sourceConfig = Postgres.defaultSourceConfiguration testEnv
|
||||
schemaName = Schema.getSchemaName testEnv
|
||||
|
||||
Postgres.createDatabase testEnv
|
||||
@ -119,6 +141,11 @@ setupPostgres testEnv = do
|
||||
name: #{tableName table}
|
||||
|]
|
||||
|
||||
registerRemoteRelationships :: HasCallStack => TestEnvironment -> IO ()
|
||||
registerRemoteRelationships testEnv = do
|
||||
let mockAgentSourceName = BackendType.backendSourceName Mock.backendTypeMetadata
|
||||
schemaName = Schema.getSchemaName testEnv
|
||||
|
||||
-- Postgres.PgArtist -> MockAgent.Album array relationship
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnv
|
||||
@ -166,7 +193,7 @@ teardownPostgres testEnv = do
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
tests :: Fixture.Options -> SpecWith (TestEnvironment, Mock.MockAgentEnvironment)
|
||||
tests _opts = describe "Remote Relationships Tests" $ do
|
||||
tests _opts = do
|
||||
mockAgentGraphqlTest "can act as the target of a remote array relationship" $ \testEnv performGraphqlRequest -> do
|
||||
let pgSchemaName = Schema.getSchemaName testEnv
|
||||
let headers = []
|
||||
@ -483,3 +510,57 @@ mkRowsResponse rows = API.QueryResponse (Just $ HashMap.fromList <$> rows) Nothi
|
||||
|
||||
mkQueryResponse :: [[(API.FieldName, API.FieldValue)]] -> [(API.FieldName, Aeson.Value)] -> API.QueryResponse
|
||||
mkQueryResponse rows aggregates = API.QueryResponse (Just $ HashMap.fromList <$> rows) (Just $ HashMap.fromList aggregates)
|
||||
|
||||
errorTests :: Fixture.Options -> SpecWith (TestEnvironment, Mock.MockAgentEnvironment)
|
||||
errorTests opts = do
|
||||
it "creating a remote relationship returns an error when it is unsupported by the target" $ \(testEnv, _) -> do
|
||||
let mockAgentSourceName = BackendType.backendSourceName Mock.backendTypeMetadata
|
||||
schemaName = Schema.getSchemaName testEnv
|
||||
|
||||
shouldReturnYaml
|
||||
opts
|
||||
( GraphqlEngine.postMetadataWithStatus
|
||||
400
|
||||
testEnv
|
||||
[yaml|
|
||||
type: pg_create_remote_relationship
|
||||
args:
|
||||
source: *pgSourceName
|
||||
table:
|
||||
schema: *schemaName
|
||||
name: PgArtist
|
||||
name: RemoteAlbums
|
||||
definition:
|
||||
to_source:
|
||||
source: *mockAgentSourceName
|
||||
table: [Album]
|
||||
relationship_type: array
|
||||
field_mapping:
|
||||
ArtistId: ArtistId
|
||||
|]
|
||||
)
|
||||
[interpolateYaml|
|
||||
code: invalid-configuration
|
||||
error: 'Inconsistent object: in table "#{schemaName}.PgArtist": in remote relationship "RemoteAlbums":
|
||||
source #{mockAgentSourceName} does not support being used as the target of a remote relationship'
|
||||
internal:
|
||||
- definition:
|
||||
definition:
|
||||
to_source:
|
||||
field_mapping:
|
||||
ArtistId: ArtistId
|
||||
relationship_type: array
|
||||
source: #{mockAgentSourceName}
|
||||
table:
|
||||
- Album
|
||||
name: RemoteAlbums
|
||||
source: #{pgSourceName}
|
||||
table:
|
||||
name: PgArtist
|
||||
schema: #{schemaName}
|
||||
name: remote_relationship RemoteAlbums in table #{schemaName}.PgArtist in source #{pgSourceName}
|
||||
reason: 'Inconsistent object: in table "#{schemaName}.PgArtist": in remote relationship "RemoteAlbums":
|
||||
source #{mockAgentSourceName} does not support being used as the target of a remote relationship'
|
||||
type: remote_relationship
|
||||
path: $.args
|
||||
|]
|
||||
|
@ -1,16 +1,29 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE OverloadedLists #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
|
||||
|
||||
{-# HLINT ignore "Use onNothing" #-}
|
||||
|
||||
module Hasura.Backends.DataConnector.API.V0.Capabilities
|
||||
( Capabilities (..),
|
||||
cDataSchema,
|
||||
cQueries,
|
||||
cMutations,
|
||||
cSubscriptions,
|
||||
cScalarTypes,
|
||||
cRelationships,
|
||||
cComparisons,
|
||||
cMetrics,
|
||||
cExplain,
|
||||
cRaw,
|
||||
cDatasets,
|
||||
defaultCapabilities,
|
||||
DataSchemaCapabilities (..),
|
||||
defaultDataSchemaCapabilities,
|
||||
ColumnNullability (..),
|
||||
QueryCapabilities (..),
|
||||
qcForeach,
|
||||
ForeachCapabilities (..),
|
||||
MutationCapabilities (..),
|
||||
InsertCapabilities (..),
|
||||
@ -35,6 +48,10 @@ module Hasura.Backends.DataConnector.API.V0.Capabilities
|
||||
RawCapabilities (..),
|
||||
DatasetCapabilities (..),
|
||||
CapabilitiesResponse (..),
|
||||
crCapabilities,
|
||||
crConfigSchemaResponse,
|
||||
crDisplayName,
|
||||
crReleaseName,
|
||||
)
|
||||
where
|
||||
|
||||
@ -42,6 +59,7 @@ import Autodocodec
|
||||
import Autodocodec.OpenAPI ()
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.DeepSeq (NFData)
|
||||
import Control.Lens.TH (makeLenses)
|
||||
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
|
||||
import Data.Data (Data, Proxy (..))
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
@ -517,3 +535,7 @@ instance ToSchema CapabilitiesResponse where
|
||||
}
|
||||
|
||||
pure $ NamedSchema (Just "CapabilitiesResponse") schema
|
||||
|
||||
$(makeLenses ''CapabilitiesResponse)
|
||||
$(makeLenses ''Capabilities)
|
||||
$(makeLenses ''QueryCapabilities)
|
||||
|
@ -9,6 +9,7 @@ module Harness.Backend.DataConnector.Mock
|
||||
teardown,
|
||||
agentConfig,
|
||||
mkLocalTestEnvironment,
|
||||
mkLocalTestEnvironment',
|
||||
|
||||
-- * Mock Test Construction
|
||||
MockConfig (..),
|
||||
@ -134,8 +135,11 @@ data MockAgentEnvironment = MockAgentEnvironment
|
||||
|
||||
-- | Create the 'I.IORef's and launch the servant mock agent.
|
||||
mkLocalTestEnvironment :: TestEnvironment -> Managed MockAgentEnvironment
|
||||
mkLocalTestEnvironment _ = mkTestResource do
|
||||
maeConfig <- I.newIORef chinookMock
|
||||
mkLocalTestEnvironment = mkLocalTestEnvironment' chinookMock
|
||||
|
||||
mkLocalTestEnvironment' :: MockConfig -> TestEnvironment -> Managed MockAgentEnvironment
|
||||
mkLocalTestEnvironment' mockConfig _ = mkTestResource do
|
||||
maeConfig <- I.newIORef mockConfig
|
||||
maeRecordedRequest <- I.newIORef Nothing
|
||||
maeRecordedRequestConfig <- I.newIORef Nothing
|
||||
maeThread <- Async.async $ runMockServer maeConfig maeRecordedRequest maeRecordedRequestConfig
|
||||
|
@ -23,3 +23,4 @@ instance BackendMetadata 'BigQuery where
|
||||
postDropSourceHook = BigQuery.postDropSourceHook
|
||||
buildComputedFieldBooleanExp _ _ _ _ _ _ =
|
||||
throw400 UnexpectedPayload "Computed fields are not supported in boolean expressions"
|
||||
supportsBeingRemoteRelationshipTarget _ = True
|
||||
|
@ -73,6 +73,7 @@ instance BackendMetadata 'DataConnector where
|
||||
postDropSourceHook _sourceConfig _tableTriggerMap = pure ()
|
||||
buildComputedFieldBooleanExp _ _ _ _ _ _ =
|
||||
error "buildComputedFieldBooleanExp: not implemented for the Data Connector backend."
|
||||
supportsBeingRemoteRelationshipTarget = supportsBeingRemoteRelationshipTarget'
|
||||
|
||||
resolveBackendInfo' ::
|
||||
( ArrowChoice arr,
|
||||
@ -377,3 +378,7 @@ mkTypedSessionVar columnType =
|
||||
|
||||
errorAction :: MonadError QErr m => API.ErrorResponse -> m a
|
||||
errorAction e = throw400WithDetail DataConnectorError (errorResponseSummary e) (_crDetails e)
|
||||
|
||||
supportsBeingRemoteRelationshipTarget' :: DC.SourceConfig -> Bool
|
||||
supportsBeingRemoteRelationshipTarget' DC.SourceConfig {..} =
|
||||
isJust $ API._qcForeach =<< API._cQueries _scCapabilities
|
||||
|
@ -8,6 +8,7 @@ module Hasura.Backends.MSSQL.Instances.Metadata () where
|
||||
|
||||
import Hasura.Backends.MSSQL.DDL qualified as MSSQL
|
||||
import Hasura.Base.Error (throw500)
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.Types.Metadata.Backend
|
||||
import Hasura.SQL.Backend
|
||||
|
||||
@ -24,3 +25,4 @@ instance BackendMetadata 'MSSQL where
|
||||
postDropSourceHook = MSSQL.postDropSourceHook
|
||||
buildComputedFieldBooleanExp _ _ _ _ _ _ =
|
||||
throw500 "Computed fields are not yet defined for MSSQL backends"
|
||||
supportsBeingRemoteRelationshipTarget _ = True
|
||||
|
@ -22,3 +22,4 @@ instance BackendMetadata 'MySQL where
|
||||
postDropSourceHook = MySQL.postDropSourceHook
|
||||
buildComputedFieldBooleanExp _ _ _ _ _ _ =
|
||||
error "buildComputedFieldBooleanExp: MySQL backend does not support this operation yet."
|
||||
supportsBeingRemoteRelationshipTarget _ = False
|
||||
|
@ -138,3 +138,4 @@ instance
|
||||
validateRelationship = validateRel @pgKind
|
||||
buildComputedFieldBooleanExp = Postgres.buildComputedFieldBooleanExp
|
||||
validateLogicalModel = Postgres.validateLogicalModel
|
||||
supportsBeingRemoteRelationshipTarget _ = True
|
||||
|
@ -331,8 +331,11 @@ buildRemoteFieldInfo lhsIdentifier lhsJoinFields RemoteRelationship {..} allSour
|
||||
targetTables <-
|
||||
Map.lookup _tsrdSource allSources
|
||||
`onNothing` throw400 NotFound ("source not found: " <>> _tsrdSource)
|
||||
AB.dispatchAnyBackend @Backend targetTables \(partiallyResolvedSource :: PartiallyResolvedSource b') -> do
|
||||
AB.dispatchAnyBackendWithTwoConstraints @Backend @BackendMetadata targetTables \(partiallyResolvedSource :: PartiallyResolvedSource b') -> do
|
||||
let PartiallyResolvedSource _ sourceConfig _ targetTablesInfo _ = partiallyResolvedSource
|
||||
unless (supportsBeingRemoteRelationshipTarget @b' sourceConfig) $
|
||||
throw400 NotSupported ("source " <> sourceNameToText _tsrdSource <> " does not support being used as the target of a remote relationship")
|
||||
|
||||
(targetTable :: TableName b') <- runAesonParser J.parseJSON _tsrdTable
|
||||
targetColumns <-
|
||||
fmap _tciFieldInfoMap $
|
||||
|
@ -1244,7 +1244,7 @@ buildRemoteSchemaRemoteRelationship allSources remoteSchemaMap remoteSchema remo
|
||||
toJSON $
|
||||
CreateRemoteSchemaRemoteRelationship remoteSchema typeName _rrName _rrDefinition
|
||||
schemaObj = SORemoteSchemaRemoteRelationship remoteSchema typeName _rrName
|
||||
addRemoteRelationshipContext e = "in remote relationship" <> _rrName <<> ": " <> e
|
||||
addRemoteRelationshipContext e = "in remote relationship " <> _rrName <<> ": " <> e
|
||||
-- buildRemoteFieldInfo only knows how to construct dependencies on the RHS of the join condition,
|
||||
-- so the dependencies on the remote relationship on the LHS entity have to be computed here
|
||||
lhsDependency =
|
||||
|
@ -307,7 +307,7 @@ buildRemoteRelationship allSources allColumns remoteSchemaMap source table rr@Re
|
||||
AB.mkAnyBackend $
|
||||
SOITableObj @b table $
|
||||
TORemoteRel _rrName
|
||||
addRemoteRelationshipContext e = "in remote relationship" <> _rrName <<> ": " <> e
|
||||
addRemoteRelationshipContext e = "in remote relationship " <> _rrName <<> ": " <> e
|
||||
withRecordInconsistencyM metadataObject $
|
||||
modifyErr (addTableContext @b table . addRemoteRelationshipContext) $ do
|
||||
(remoteField, rhsDependencies) <-
|
||||
|
@ -195,3 +195,7 @@ class
|
||||
m ()
|
||||
validateLogicalModel _ _ _ =
|
||||
throw500 "validateLogicalModel: not implemented for this backend."
|
||||
|
||||
-- | Allows the backend to control whether or not a particular source supports being
|
||||
-- the target of remote relationships or not
|
||||
supportsBeingRemoteRelationshipTarget :: SourceConfig b -> Bool
|
||||
|
Loading…
Reference in New Issue
Block a user