mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
server/fix: stringify-numeric-types
option in remote database relationships (fix #8387)
Fix bug where `stringify-numeric-types` option is not respected in remote database relationships PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7302 GitOrigin-RevId: a649b00b45ca0f67dc84ad893d3d98529b064c77
This commit is contained in:
parent
07be94c4eb
commit
a8500b44ed
@ -157,6 +157,7 @@ library
|
||||
Test.Regression.NullRemoteRelationship8345Spec
|
||||
Test.Regression.NullsOrderParsing8780Spec
|
||||
Test.Regression.ObjectRelationshipsLimit7936Spec
|
||||
Test.Regression.RemoteRelationshipStringifyNum8387Spec
|
||||
Test.Regression.StreamConflictSpec
|
||||
Test.Regression.UsingTheSameFunctionForRootFieldAndComputedField8643Spec
|
||||
Test.Schema.ComputedFields.ScalarSpec
|
||||
|
@ -0,0 +1,514 @@
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
|
||||
-- Regression test for https://github.com/hasura/graphql-engine/issues/8387
|
||||
module Test.Regression.RemoteRelationshipStringifyNum8387Spec (spec) where
|
||||
|
||||
import Data.Aeson (Value)
|
||||
import Data.Char (isUpper, toLower)
|
||||
import Data.List.NonEmpty qualified as NE
|
||||
import Data.List.Split (dropBlanks, keepDelimsL, split, whenElt)
|
||||
import Data.Morpheus.Document (gqlDocument)
|
||||
import Data.Morpheus.Types qualified as Morpheus
|
||||
import Data.Typeable (Typeable)
|
||||
import Harness.Backend.Postgres qualified as Postgres
|
||||
import Harness.GraphqlEngine qualified as GraphqlEngine
|
||||
import Harness.Quoter.Graphql (graphql)
|
||||
import Harness.Quoter.Yaml (yaml)
|
||||
import Harness.RemoteServer qualified as RemoteServer
|
||||
import Harness.Test.Fixture qualified as Fixture
|
||||
import Harness.Test.Schema (Table (..))
|
||||
import Harness.Test.Schema qualified as Schema
|
||||
import Harness.Test.TestResource (Managed)
|
||||
import Harness.TestEnvironment (GlobalTestEnvironment, Server, TestEnvironment, backendTypeConfig, stopServer)
|
||||
import Harness.Yaml (shouldReturnYaml)
|
||||
import Hasura.Prelude
|
||||
import Test.Hspec (SpecWith, describe, it)
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Preamble
|
||||
|
||||
spec :: SpecWith GlobalTestEnvironment
|
||||
spec = Fixture.runWithLocalTestEnvironment contexts tests
|
||||
where
|
||||
lhsFixtures = [lhsPostgresStringifyNums, lhsRemoteServerStringifyNums]
|
||||
rhsFixtures = [rhsPostgresStringifyNums]
|
||||
contexts = NE.fromList $ Fixture.combineFixtures <$> lhsFixtures <*> rhsFixtures
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
-- | Left-hand-side (LHS) fixtures
|
||||
lhsPostgresStringifyNums :: Fixture.LHSFixture
|
||||
lhsPostgresStringifyNums tableName =
|
||||
(Fixture.fixture $ Fixture.Backend Postgres.backendTypeMetadata)
|
||||
{ Fixture.mkLocalTestEnvironment = lhsPostgresMkLocalTestEnvironment,
|
||||
Fixture.setupTeardown = \testEnv ->
|
||||
[ Fixture.SetupAction
|
||||
{ Fixture.setupAction = lhsPostgresSetup tableName testEnv,
|
||||
Fixture.teardownAction = \_ -> lhsPostgresTeardown testEnv
|
||||
}
|
||||
],
|
||||
Fixture.customOptions =
|
||||
Just $
|
||||
Fixture.defaultOptions
|
||||
{ Fixture.stringifyNumbers = True
|
||||
}
|
||||
}
|
||||
|
||||
lhsRemoteServerStringifyNums :: Fixture.LHSFixture
|
||||
lhsRemoteServerStringifyNums tableName =
|
||||
(Fixture.fixture $ Fixture.RemoteGraphQLServer)
|
||||
{ Fixture.mkLocalTestEnvironment = lhsRemoteServerMkLocalTestEnvironment,
|
||||
Fixture.setupTeardown = \testEnv ->
|
||||
[ Fixture.SetupAction
|
||||
{ Fixture.setupAction = lhsRemoteServerSetup tableName testEnv,
|
||||
Fixture.teardownAction = \_ -> lhsRemoteServerTeardown testEnv
|
||||
}
|
||||
],
|
||||
Fixture.customOptions =
|
||||
Just $
|
||||
Fixture.defaultOptions
|
||||
{ Fixture.stringifyNumbers = True
|
||||
}
|
||||
}
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
-- | Right-hand-side (RHS) fixtures
|
||||
rhsPostgresStringifyNums :: Fixture.RHSFixture
|
||||
rhsPostgresStringifyNums =
|
||||
let table =
|
||||
[yaml|
|
||||
schema: hasura
|
||||
name: album
|
||||
|]
|
||||
context =
|
||||
(Fixture.fixture $ Fixture.Backend Postgres.backendTypeMetadata)
|
||||
{ Fixture.setupTeardown = \testEnv ->
|
||||
[ Fixture.SetupAction
|
||||
{ Fixture.setupAction = rhsPostgresSetup testEnv,
|
||||
Fixture.teardownAction = \_ -> rhsPostgresTeardown testEnv
|
||||
}
|
||||
],
|
||||
Fixture.customOptions =
|
||||
Just $
|
||||
Fixture.defaultOptions
|
||||
{ Fixture.stringifyNumbers = True
|
||||
}
|
||||
}
|
||||
in (table, context)
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Schema
|
||||
|
||||
-- | LHS
|
||||
track :: Schema.Table
|
||||
track =
|
||||
(Schema.table "track")
|
||||
{ tableColumns =
|
||||
[ Schema.column "id" Schema.TInt,
|
||||
Schema.columnNull "album_id" Schema.TInt
|
||||
],
|
||||
tablePrimaryKey = ["id"],
|
||||
tableData =
|
||||
[ [Schema.VInt 1, Schema.VInt 1]
|
||||
]
|
||||
}
|
||||
|
||||
-- | RHS
|
||||
album :: Schema.Table
|
||||
album =
|
||||
(Schema.table "album")
|
||||
{ tableColumns =
|
||||
[ Schema.column "id" Schema.TInt,
|
||||
Schema.column "title" Schema.TStr,
|
||||
Schema.columnNull "artist_id" Schema.TInt,
|
||||
Schema.column "play_count" bigIntType,
|
||||
Schema.column "version" floatType
|
||||
],
|
||||
tablePrimaryKey = ["id"],
|
||||
tableData =
|
||||
[ [Schema.VInt 1, Schema.VStr "album1", Schema.VInt 1, mkBigIntValue "1000000000000", mkFloatValue "1.075"]
|
||||
]
|
||||
}
|
||||
|
||||
floatType :: Schema.ScalarType
|
||||
floatType =
|
||||
Schema.TCustomType $
|
||||
Schema.defaultBackendScalarType
|
||||
{ Schema.bstPostgres = Just "NUMERIC"
|
||||
}
|
||||
|
||||
mkFloatValue :: Text -> Schema.ScalarValue
|
||||
mkFloatValue int =
|
||||
Schema.VCustomValue $
|
||||
Schema.defaultBackendScalarValue
|
||||
{ Schema.bsvPostgres = Just (Schema.Unquoted int)
|
||||
}
|
||||
|
||||
bigIntType :: Schema.ScalarType
|
||||
bigIntType =
|
||||
Schema.TCustomType $
|
||||
Schema.defaultBackendScalarType
|
||||
{ Schema.bstPostgres = Just "BIGINT"
|
||||
}
|
||||
|
||||
mkBigIntValue :: Text -> Schema.ScalarValue
|
||||
mkBigIntValue int =
|
||||
Schema.VCustomValue $
|
||||
Schema.defaultBackendScalarValue
|
||||
{ Schema.bsvPostgres = Just (Schema.Unquoted int)
|
||||
}
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- LHS Postgres
|
||||
|
||||
lhsPostgresMkLocalTestEnvironment :: TestEnvironment -> Managed (Maybe Server)
|
||||
lhsPostgresMkLocalTestEnvironment _ = pure Nothing
|
||||
|
||||
lhsPostgresSetup :: Value -> (TestEnvironment, Maybe Server) -> IO ()
|
||||
lhsPostgresSetup rhsTableName (testEnvironment, _) = do
|
||||
let sourceName = "source"
|
||||
sourceConfig = Postgres.defaultSourceConfiguration testEnvironment
|
||||
schemaName = Schema.getSchemaName testEnvironment
|
||||
-- Add remote source
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: pg_add_source
|
||||
args:
|
||||
name: *sourceName
|
||||
configuration: *sourceConfig
|
||||
|]
|
||||
-- setup tables only
|
||||
Postgres.createTable testEnvironment track
|
||||
Postgres.insertTable testEnvironment track
|
||||
Schema.trackTable sourceName track (testEnvironment {backendTypeConfig = Just (Postgres.backendTypeMetadata)})
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: pg_create_select_permission
|
||||
args:
|
||||
source: *sourceName
|
||||
role: role1
|
||||
table:
|
||||
schema: *schemaName
|
||||
name: track
|
||||
permission:
|
||||
columns: '*'
|
||||
filter: {}
|
||||
- type: pg_create_select_permission
|
||||
args:
|
||||
source: *sourceName
|
||||
role: role2
|
||||
table:
|
||||
schema: *schemaName
|
||||
name: track
|
||||
permission:
|
||||
columns: '*'
|
||||
filter: {}
|
||||
- type: pg_create_remote_relationship
|
||||
args:
|
||||
source: *sourceName
|
||||
table:
|
||||
schema: *schemaName
|
||||
name: track
|
||||
name: album
|
||||
definition:
|
||||
to_source:
|
||||
source: target
|
||||
table: *rhsTableName
|
||||
relationship_type: object
|
||||
field_mapping:
|
||||
album_id: id
|
||||
|]
|
||||
|
||||
lhsPostgresTeardown :: (TestEnvironment, Maybe Server) -> IO ()
|
||||
lhsPostgresTeardown (_testEnvironment, _) =
|
||||
pure ()
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- LHS Remote Server
|
||||
|
||||
-- TODO AS: factor out
|
||||
|
||||
-- | To circumvent Morpheus' default behaviour, which is to capitalize type
|
||||
-- names and field names for Haskell records to be consistent with their
|
||||
-- corresponding GraphQL equivalents, we define most of the schema manually with
|
||||
-- the following options.
|
||||
hasuraTypeOptions :: Morpheus.GQLTypeOptions
|
||||
hasuraTypeOptions =
|
||||
Morpheus.defaultTypeOptions
|
||||
{ -- transformation to apply to constructors, for enums; we simply map to
|
||||
-- lower case:
|
||||
-- Asc -> asc
|
||||
Morpheus.constructorTagModifier = map toLower,
|
||||
-- transformation to apply to field names; we drop all characters up to and
|
||||
-- including the first underscore:
|
||||
-- hta_where -> where
|
||||
Morpheus.fieldLabelModifier = tail . dropWhile (/= '_'),
|
||||
-- transformation to apply to type names; we split the name on uppercase
|
||||
-- letters, intercalate with underscore, and map everything to lowercase:
|
||||
-- HasuraTrack -> hasura_track
|
||||
Morpheus.typeNameModifier = \_ ->
|
||||
map toLower
|
||||
. intercalate "_"
|
||||
. split (dropBlanks $ keepDelimsL $ whenElt isUpper)
|
||||
}
|
||||
|
||||
data Query m = Query
|
||||
{ hasura_track :: HasuraTrackArgs -> m [HasuraTrack m]
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
instance Typeable m => Morpheus.GQLType (Query m)
|
||||
|
||||
data HasuraTrackArgs = HasuraTrackArgs
|
||||
{ ta_where :: Maybe HasuraTrackBoolExp,
|
||||
ta_order_by :: Maybe [HasuraTrackOrderBy],
|
||||
ta_limit :: Maybe Int
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
instance Morpheus.GQLType HasuraTrackArgs where
|
||||
typeOptions _ _ = hasuraTypeOptions
|
||||
|
||||
data HasuraTrack m = HasuraTrack
|
||||
{ t_id :: m (Maybe Int),
|
||||
t_album_id :: m (Maybe Int)
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
instance Typeable m => Morpheus.GQLType (HasuraTrack m) where
|
||||
typeOptions _ _ = hasuraTypeOptions
|
||||
|
||||
data HasuraTrackOrderBy = HasuraTrackOrderBy
|
||||
{ tob_id :: Maybe OrderType,
|
||||
tob_album_id :: Maybe OrderType
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
instance Morpheus.GQLType HasuraTrackOrderBy where
|
||||
typeOptions _ _ = hasuraTypeOptions
|
||||
|
||||
data HasuraTrackBoolExp = HasuraTrackBoolExp
|
||||
{ tbe__and :: Maybe [HasuraTrackBoolExp],
|
||||
tbe__or :: Maybe [HasuraTrackBoolExp],
|
||||
tbe__not :: Maybe HasuraTrackBoolExp,
|
||||
tbe_id :: Maybe IntCompExp,
|
||||
tbe_album_id :: Maybe IntCompExp
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
instance Morpheus.GQLType HasuraTrackBoolExp where
|
||||
typeOptions _ _ = hasuraTypeOptions
|
||||
|
||||
data OrderType = Asc | Desc
|
||||
deriving (Show, Generic)
|
||||
|
||||
instance Morpheus.GQLType OrderType where
|
||||
typeOptions _ _ = hasuraTypeOptions
|
||||
|
||||
[gqlDocument|
|
||||
|
||||
input IntCompExp {
|
||||
_eq: Int
|
||||
}
|
||||
|
||||
input StringCompExp {
|
||||
_eq: String
|
||||
}
|
||||
|
||||
|]
|
||||
|
||||
lhsRemoteServerMkLocalTestEnvironment :: TestEnvironment -> Managed (Maybe Server)
|
||||
lhsRemoteServerMkLocalTestEnvironment _ =
|
||||
Just <$> RemoteServer.run (RemoteServer.generateQueryInterpreter (Query {hasura_track}))
|
||||
where
|
||||
-- Implements the @hasura_track@ field of the @Query@ type.
|
||||
hasura_track (HasuraTrackArgs {..}) = do
|
||||
let filterFunction = case ta_where of
|
||||
Nothing -> const True
|
||||
Just whereArg -> flip matchTrack whereArg
|
||||
orderByFunction = case ta_order_by of
|
||||
Nothing -> \_ _ -> EQ
|
||||
Just orderByArg -> orderTrack orderByArg
|
||||
limitFunction = maybe Hasura.Prelude.id take ta_limit
|
||||
pure $
|
||||
tracks
|
||||
& filter filterFunction
|
||||
& sortBy orderByFunction
|
||||
& limitFunction
|
||||
& map mkTrack
|
||||
-- Returns True iif the given track matches the given boolean expression.
|
||||
matchTrack trackInfo@(trackId, maybeAlbumId) (HasuraTrackBoolExp {..}) =
|
||||
and
|
||||
[ all (all (matchTrack trackInfo)) tbe__and,
|
||||
all (any (matchTrack trackInfo)) tbe__or,
|
||||
not (any (matchTrack trackInfo) tbe__not),
|
||||
all (matchInt trackId) tbe_id,
|
||||
all (matchMaybeInt maybeAlbumId) tbe_album_id
|
||||
]
|
||||
matchInt intField IntCompExp {..} = Just intField == _eq
|
||||
matchMaybeInt maybeIntField IntCompExp {..} = maybeIntField == _eq
|
||||
-- Returns an ordering between the two given tracks.
|
||||
orderTrack
|
||||
orderByList
|
||||
(trackId1, trackAlbumId1)
|
||||
(trackId2, trackAlbumId2) =
|
||||
flip foldMap orderByList \HasuraTrackOrderBy {..} ->
|
||||
if
|
||||
| Just idOrder <- tob_id -> case idOrder of
|
||||
Asc -> compare trackId1 trackId2
|
||||
Desc -> compare trackId2 trackId1
|
||||
| Just albumIdOrder <- tob_album_id ->
|
||||
compareWithNullLast albumIdOrder trackAlbumId1 trackAlbumId2
|
||||
| otherwise ->
|
||||
error "empty order_by object"
|
||||
compareWithNullLast Desc x1 x2 = compareWithNullLast Asc x2 x1
|
||||
compareWithNullLast Asc Nothing Nothing = EQ
|
||||
compareWithNullLast Asc (Just _) Nothing = LT
|
||||
compareWithNullLast Asc Nothing (Just _) = GT
|
||||
compareWithNullLast Asc (Just x1) (Just x2) = compare x1 x2
|
||||
tracks = [(1, Just 1)]
|
||||
mkTrack (trackId, albumId) =
|
||||
HasuraTrack
|
||||
{ t_id = pure $ Just trackId,
|
||||
t_album_id = pure albumId
|
||||
}
|
||||
|
||||
lhsRemoteServerSetup :: Value -> (TestEnvironment, Maybe Server) -> IO ()
|
||||
lhsRemoteServerSetup tableName (testEnvironment, maybeRemoteServer) = case maybeRemoteServer of
|
||||
Nothing -> error "XToDBObjectRelationshipSpec: remote server local testEnvironment did not succesfully create a server"
|
||||
Just remoteServer -> do
|
||||
let remoteSchemaEndpoint = GraphqlEngine.serverUrl remoteServer ++ "/graphql"
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: add_remote_schema
|
||||
args:
|
||||
name: source
|
||||
definition:
|
||||
url: *remoteSchemaEndpoint
|
||||
- type: create_remote_schema_remote_relationship
|
||||
args:
|
||||
remote_schema: source
|
||||
type_name: hasura_track
|
||||
name: album
|
||||
definition:
|
||||
to_source:
|
||||
source: target
|
||||
table: *tableName
|
||||
relationship_type: object
|
||||
field_mapping:
|
||||
album_id: id
|
||||
|]
|
||||
|
||||
lhsRemoteServerTeardown :: (TestEnvironment, Maybe Server) -> IO ()
|
||||
lhsRemoteServerTeardown (_, maybeServer) = traverse_ stopServer maybeServer
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- RHS Postgres
|
||||
|
||||
rhsPostgresSetup :: (TestEnvironment, ()) -> IO ()
|
||||
rhsPostgresSetup (testEnvironment, _) = do
|
||||
let sourceName = "target"
|
||||
sourceConfig = Postgres.defaultSourceConfiguration testEnvironment
|
||||
schemaName = Schema.getSchemaName testEnvironment
|
||||
|
||||
-- Add remote source
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: pg_add_source
|
||||
args:
|
||||
name: *sourceName
|
||||
configuration: *sourceConfig
|
||||
|]
|
||||
-- setup tables only
|
||||
Postgres.createTable testEnvironment album
|
||||
Postgres.insertTable testEnvironment album
|
||||
Schema.trackTable sourceName album (testEnvironment {backendTypeConfig = Just (Postgres.backendTypeMetadata)})
|
||||
|
||||
GraphqlEngine.postMetadata_
|
||||
testEnvironment
|
||||
[yaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: pg_create_select_permission
|
||||
args:
|
||||
source: *sourceName
|
||||
role: role1
|
||||
table:
|
||||
schema: *schemaName
|
||||
name: album
|
||||
permission:
|
||||
columns:
|
||||
- title
|
||||
- artist_id
|
||||
- play_count
|
||||
- version
|
||||
filter:
|
||||
artist_id:
|
||||
_eq: x-hasura-artist-id
|
||||
- type: pg_create_select_permission
|
||||
args:
|
||||
source: *sourceName
|
||||
role: role2
|
||||
table:
|
||||
schema: *schemaName
|
||||
name: album
|
||||
permission:
|
||||
columns: [id, title, artist_id, play_count, version]
|
||||
filter:
|
||||
artist_id:
|
||||
_eq: x-hasura-artist-id
|
||||
limit: 1
|
||||
allow_aggregations: true
|
||||
|]
|
||||
|
||||
rhsPostgresTeardown :: (TestEnvironment, ()) -> IO ()
|
||||
rhsPostgresTeardown (_testEnvironment, _) =
|
||||
pure ()
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Tests
|
||||
|
||||
tests :: Fixture.Options -> SpecWith (TestEnvironment, Maybe Server)
|
||||
tests opts = describe "object-relationship" $ do
|
||||
executionTests opts
|
||||
|
||||
-- | Basic queries using *-to-DB joins
|
||||
executionTests :: Fixture.Options -> SpecWith (TestEnvironment, Maybe Server)
|
||||
executionTests opts = describe "execution" $ do
|
||||
-- fetches the relationship data
|
||||
it "related-data" $ \(testEnvironment, _) -> do
|
||||
let query =
|
||||
[graphql|
|
||||
query {
|
||||
track: hasura_track {
|
||||
album {
|
||||
title
|
||||
play_count
|
||||
version
|
||||
}
|
||||
}
|
||||
}
|
||||
|]
|
||||
expectedResponse =
|
||||
[yaml|
|
||||
data:
|
||||
track:
|
||||
- album:
|
||||
title: "album1"
|
||||
play_count: "1000000000000"
|
||||
version: "1.075"
|
||||
|]
|
||||
shouldReturnYaml
|
||||
opts
|
||||
(GraphqlEngine.postGraphql testEnvironment query)
|
||||
expectedResponse
|
@ -17,6 +17,7 @@ import Data.Aeson
|
||||
import Data.Aeson qualified as Aeson
|
||||
import Data.Aeson.KeyMap qualified as KM
|
||||
import Data.List (permutations)
|
||||
import Data.Scientific (FPFormat (Fixed), formatScientific, toBoundedInteger)
|
||||
import Data.Set (Set)
|
||||
import Data.Set qualified as Set
|
||||
import Data.Text qualified as T
|
||||
@ -85,22 +86,26 @@ shouldReturnYaml = shouldReturnYamlF pure
|
||||
-- If the zipping doesn't line up, we assume this is probably a bad result and
|
||||
-- consequently should result in a failing test. In these cases, we leave the
|
||||
-- actual output exactly as-is, and wait for the test to fail.
|
||||
parseToMatch :: Value -> Value -> Value
|
||||
parseToMatch (Array expected) (Array actual) =
|
||||
Array (Vector.zipWith parseToMatch expected actual)
|
||||
parseToMatch (Number _) (String text) =
|
||||
tryToMatch :: Value -> Value -> Value
|
||||
tryToMatch (Array expected) (Array actual) =
|
||||
Array (Vector.zipWith tryToMatch expected actual)
|
||||
tryToMatch (Number _) (String text) =
|
||||
case readMaybe (T.unpack text) of
|
||||
Just actual -> Number actual
|
||||
Nothing -> String text
|
||||
parseToMatch (Object expected) (Object actual) = do
|
||||
tryToMatch (String _) (Number actual) = do
|
||||
-- format floats with decimal places and ints without, as we do in production
|
||||
let decimalPlaces = 0 <$ (toBoundedInteger actual :: Maybe Int)
|
||||
String $ T.pack $ formatScientific Fixed decimalPlaces actual
|
||||
tryToMatch (Object expected) (Object actual) = do
|
||||
let walk :: KM.KeyMap Value -> Aeson.Key -> Value -> Value
|
||||
walk reference key current =
|
||||
case KM.lookup key reference of
|
||||
Just this -> parseToMatch this current
|
||||
Just this -> tryToMatch this current
|
||||
Nothing -> current
|
||||
|
||||
Object (KM.mapWithKey (walk expected) actual)
|
||||
parseToMatch _ actual = actual
|
||||
tryToMatch _ actual = actual
|
||||
|
||||
-- | The function @transform@ converts the returned YAML
|
||||
-- prior to comparison. It exists in IO in order to be able
|
||||
@ -117,7 +122,7 @@ shouldReturnYamlF transform options actualIO expected = do
|
||||
actualIO >>= transform >>= \actual ->
|
||||
pure
|
||||
if Fixture.stringifyNumbers options
|
||||
then parseToMatch expected actual
|
||||
then tryToMatch expected actual
|
||||
else actual
|
||||
|
||||
actual `shouldBe` expected
|
||||
@ -136,7 +141,7 @@ shouldReturnOneOfYaml Fixture.Options {stringifyNumbers} actualIO candidates = d
|
||||
|
||||
actuals :: Set Value
|
||||
actuals
|
||||
| stringifyNumbers = Set.map (`parseToMatch` actual) expecteds
|
||||
| stringifyNumbers = Set.map (`tryToMatch` actual) expecteds
|
||||
| otherwise = Set.singleton actual
|
||||
|
||||
case Set.lookupMin (Set.intersection expecteds actuals) of
|
||||
|
@ -44,6 +44,7 @@ library
|
||||
, resourcet
|
||||
, safe-exceptions
|
||||
, servant-server
|
||||
, scientific
|
||||
, sop-core
|
||||
, stm
|
||||
, string-interpolate
|
||||
|
@ -199,8 +199,9 @@ bqDBRemoteRelationshipPlan ::
|
||||
-- response along with the relationship.
|
||||
FieldName ->
|
||||
(FieldName, SourceRelationshipSelection 'BigQuery Void UnpreparedValue) ->
|
||||
Options.StringifyNumbers ->
|
||||
m (DBStepInfo 'BigQuery)
|
||||
bqDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship = do
|
||||
bqDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship stringifyNumbers = do
|
||||
flip runReaderT emptyQueryTagsComment $ bqDBQueryPlan userInfo Env.emptyEnvironment sourceName sourceConfig rootSelection
|
||||
where
|
||||
coerceToColumn = BigQuery.ColumnName . getFieldNameTxt
|
||||
@ -233,3 +234,4 @@ bqDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argume
|
||||
(BigQuery.ColumnName $ getFieldNameTxt argumentId)
|
||||
(ColumnScalar BigQuery.IntegerScalarType)
|
||||
relationship
|
||||
stringifyNumbers
|
||||
|
@ -67,7 +67,7 @@ instance BackendExecute 'DataConnector where
|
||||
throw400 NotSupported "mkLiveQuerySubscriptionPlan: not implemented for the Data Connector backend."
|
||||
mkDBStreamingSubscriptionPlan _ _ _ _ =
|
||||
throw400 NotSupported "mkLiveQuerySubscriptionPlan: not implemented for the Data Connector backend."
|
||||
mkDBRemoteRelationshipPlan _ _ _ _ _ _ _ =
|
||||
mkDBRemoteRelationshipPlan _ _ _ _ _ _ _ _ =
|
||||
throw500 "mkDBRemoteRelationshipPlan: not implemented for the Data Connector backend."
|
||||
mkSubscriptionExplain _ =
|
||||
throw400 NotSupported "mkSubscriptionExplain: not implemented for the Data Connector backend."
|
||||
|
@ -427,8 +427,11 @@ msDBRemoteRelationshipPlan ::
|
||||
-- response along with the relationship.
|
||||
RQLTypes.FieldName ->
|
||||
(RQLTypes.FieldName, SourceRelationshipSelection 'MSSQL Void UnpreparedValue) ->
|
||||
Options.StringifyNumbers ->
|
||||
m (DBStepInfo 'MSSQL)
|
||||
msDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship = do
|
||||
msDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship _stringifyNumbers = do
|
||||
-- TODO: handle `stringifyNumbers` in remote database relationships
|
||||
-- https://hasurahq.atlassian.net/browse/NDAT-438
|
||||
statement <- planSourceRelationship (_uiSession userInfo) lhs lhsSchema argumentId relationship
|
||||
|
||||
let printer = fromSelect statement
|
||||
|
@ -467,8 +467,9 @@ pgDBRemoteRelationshipPlan ::
|
||||
-- response along with the relationship.
|
||||
FieldName ->
|
||||
(FieldName, IR.SourceRelationshipSelection ('Postgres pgKind) Void UnpreparedValue) ->
|
||||
Options.StringifyNumbers ->
|
||||
m (DBStepInfo ('Postgres pgKind))
|
||||
pgDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship = do
|
||||
pgDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argumentId relationship stringifyNumbers = do
|
||||
-- NOTE: 'QueryTags' currently cannot support remote relationship queries.
|
||||
--
|
||||
-- In the future if we want to add support we'll need to add a new type of
|
||||
@ -503,3 +504,4 @@ pgDBRemoteRelationshipPlan userInfo sourceName sourceConfig lhs lhsSchema argume
|
||||
(Postgres.unsafePGCol $ getFieldNameTxt argumentId)
|
||||
(ColumnScalar Postgres.PGBigInt)
|
||||
relationship
|
||||
stringifyNumbers
|
||||
|
@ -150,6 +150,7 @@ class
|
||||
-- to be returned as either a number or a string with a number in it
|
||||
FieldName ->
|
||||
(FieldName, SourceRelationshipSelection b Void UnpreparedValue) ->
|
||||
Options.StringifyNumbers ->
|
||||
m (DBStepInfo b)
|
||||
|
||||
-- | This is a helper function to convert a remote source's relationship to a
|
||||
@ -173,13 +174,15 @@ convertRemoteSourceRelationship ::
|
||||
-- | The relationship column and its name (how it should be selected in the
|
||||
-- response)
|
||||
(FieldName, SourceRelationshipSelection b Void UnpreparedValue) ->
|
||||
Options.StringifyNumbers ->
|
||||
QueryDB b Void (UnpreparedValue b)
|
||||
convertRemoteSourceRelationship
|
||||
columnMapping
|
||||
selectFrom
|
||||
argumentIdColumn
|
||||
argumentIdColumnType
|
||||
(relationshipName, relationship) =
|
||||
(relationshipName, relationship)
|
||||
stringifyNumbers =
|
||||
QDBMultipleRows simpleSelect
|
||||
where
|
||||
-- TODO: FieldName should have also been a wrapper around NonEmptyText
|
||||
@ -211,7 +214,7 @@ convertRemoteSourceRelationship
|
||||
_asnFrom = selectFrom,
|
||||
_asnPerm = TablePerm annBoolExpTrue Nothing,
|
||||
_asnArgs = noSelectArgs,
|
||||
_asnStrfyNum = Options.Don'tStringifyNumbers,
|
||||
_asnStrfyNum = stringifyNumbers,
|
||||
_asnNamingConvention = Nothing
|
||||
}
|
||||
|
||||
|
@ -642,6 +642,7 @@ createRemoteJoin joinColumnAliases = \case
|
||||
_rssConfig
|
||||
transformedSourceRelationship
|
||||
joinColumns
|
||||
_rssStringifyNums
|
||||
in RemoteJoinSource anySourceJoin sourceRelationshipJoins
|
||||
|
||||
-- | Constructs a 'JoinColumnAlias' for a given field in a selection set.
|
||||
|
@ -119,6 +119,7 @@ buildSourceJoinCall userInfo jaFieldName joinArguments remoteSourceJoin = do
|
||||
rowSchema
|
||||
(FieldName "__argument_id__")
|
||||
(FieldName "f", _rsjRelationship remoteSourceJoin)
|
||||
(_rsjStringifyNum remoteSourceJoin)
|
||||
-- This should never fail, as field names in remote relationships are
|
||||
-- validated when building the schema cache.
|
||||
fieldName <-
|
||||
@ -143,7 +144,7 @@ buildSourceJoinCall userInfo jaFieldName joinArguments remoteSourceJoin = do
|
||||
buildJoinIndex :: (MonadError QErr m) => BL.ByteString -> m (IntMap.IntMap JO.Value)
|
||||
buildJoinIndex response = do
|
||||
json <-
|
||||
JO.eitherDecode response {-( response)-} `onLeft` \err ->
|
||||
JO.eitherDecode response `onLeft` \err ->
|
||||
throwInvalidJsonErr $ T.pack err
|
||||
case json of
|
||||
JO.Array arr -> fmap IntMap.fromList $ for (toList arr) \case
|
||||
|
@ -34,6 +34,7 @@ import Data.Aeson.Ordered qualified as AO
|
||||
import Data.HashMap.Strict qualified as Map
|
||||
import Data.HashMap.Strict.NonEmpty qualified as NEMap
|
||||
import Hasura.GraphQL.Parser qualified as P
|
||||
import Hasura.GraphQL.Schema.Options qualified as Options
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.IR.RemoteSchema qualified as IR
|
||||
import Hasura.RQL.IR.Select qualified as IR
|
||||
@ -207,7 +208,8 @@ data RemoteSourceJoin b = RemoteSourceJoin
|
||||
{ _rsjSource :: !SourceName,
|
||||
_rsjSourceConfig :: !(SourceConfig b),
|
||||
_rsjRelationship :: !(IR.SourceRelationshipSelection b Void IR.UnpreparedValue),
|
||||
_rsjJoinColumns :: !(Map.HashMap FieldName (JoinColumnAlias, (Column b, ScalarType b)))
|
||||
_rsjJoinColumns :: !(Map.HashMap FieldName (JoinColumnAlias, (Column b, ScalarType b))),
|
||||
_rsjStringifyNum :: Options.StringifyNumbers
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
|
@ -227,4 +227,4 @@ remoteRelationshipToSourceField context options sourceCache RemoteSourceFieldInf
|
||||
]
|
||||
pure $
|
||||
parsers <&> fmap \select ->
|
||||
IR.RemoteSourceSelect _rsfiSource _rsfiSourceConfig select _rsfiMapping
|
||||
IR.RemoteSourceSelect _rsfiSource _rsfiSourceConfig select _rsfiMapping (soStringifyNumbers options)
|
||||
|
@ -1020,7 +1020,8 @@ data
|
||||
-- from src
|
||||
-- (Column tgt) so that an appropriate join condition / IN clause can be built
|
||||
-- by the remote
|
||||
_rssJoinMapping :: (HM.HashMap FieldName (ScalarType tgt, Column tgt))
|
||||
_rssJoinMapping :: (HM.HashMap FieldName (ScalarType tgt, Column tgt)),
|
||||
_rssStringifyNums :: StringifyNumbers
|
||||
}
|
||||
|
||||
deriving stock instance
|
||||
|
Loading…
Reference in New Issue
Block a user