mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-15 01:12:56 +03:00
BigQuery operators: like/nlike, geography
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2924 GitOrigin-RevId: 3748411cb4419a21a58283836adb5cb39d351d19
This commit is contained in:
parent
69ea0e7026
commit
47b9321ba4
@ -67,6 +67,7 @@
|
||||
- cli: fix cli-console failing to add migrations if there are tabs in SQL body (#7362)
|
||||
- cli: sign windows binary of Hasura CLI (#7147)
|
||||
- cli: core CLI features are not blocked in environments without internet (#7695)
|
||||
- server: add `_like`/`_nlike` and spatial operators for BigQuery
|
||||
|
||||
## v2.1.0-beta.2
|
||||
|
||||
|
@ -1544,8 +1544,9 @@ fromOpExpG expression op =
|
||||
Ir.AGTE val -> pure (OpExpression MoreOrEqualOp expression val)
|
||||
Ir.ALTE val -> pure (OpExpression LessOrEqualOp expression val)
|
||||
Ir.ACast _casts -> refute (pure (UnsupportedOpExpG op)) -- mkCastsExp casts
|
||||
Ir.ALIKE _val -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SLIKE lhs val
|
||||
Ir.ANLIKE _val -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SNLIKE lhs val
|
||||
Ir.ALIKE val -> pure (OpExpression LikeOp expression val)
|
||||
Ir.ANLIKE val -> pure (OpExpression NotLikeOp expression val)
|
||||
Ir.ABackendSpecific op' -> pure (fromBackendSpecificOpExpG expression op')
|
||||
Ir.CEQ _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SEQ lhs $ mkQCol rhsCol
|
||||
Ir.CNE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SNE lhs $ mkQCol rhsCol
|
||||
Ir.CGT _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SGT lhs $ mkQCol rhsCol
|
||||
@ -1554,6 +1555,18 @@ fromOpExpG expression op =
|
||||
Ir.CLTE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SLTE lhs $ mkQCol rhsCol
|
||||
-- These are new as of 2021-02-18 to this API. Not sure what to do with them at present, marking as unsupported.
|
||||
|
||||
fromBackendSpecificOpExpG :: Expression -> BigQuery.BooleanOperators Expression -> Expression
|
||||
fromBackendSpecificOpExpG expression op =
|
||||
let func name val = FunctionExpression name [expression, val]
|
||||
in case op of
|
||||
BigQuery.ASTContains v -> func "ST_CONTAINS" v
|
||||
BigQuery.ASTEquals v -> func "ST_EQUALS" v
|
||||
BigQuery.ASTTouches v -> func "ST_TOUCHES" v
|
||||
BigQuery.ASTWithin v -> func "ST_WITHIN" v
|
||||
BigQuery.ASTIntersects v -> func "ST_INTERSECTS" v
|
||||
BigQuery.ASTDWithin (Ir.DWithinGeogOp r v sph) ->
|
||||
FunctionExpression "ST_DWITHIN" [expression, v, r, sph]
|
||||
|
||||
nullableBoolEquality :: Expression -> Expression -> Expression
|
||||
nullableBoolEquality x y =
|
||||
OrExpression
|
||||
|
@ -157,7 +157,7 @@ bqColumnParser columnType (G.Nullability isNullable) =
|
||||
ColumnScalar scalarType -> case scalarType of
|
||||
-- bytestrings
|
||||
-- we only accept string literals
|
||||
BigQuery.BytesScalarType -> pure $ possiblyNullable scalarType $ BigQuery.StringValue <$> P.string
|
||||
BigQuery.BytesScalarType -> pure $ possiblyNullable scalarType $ BigQuery.StringValue <$> stringBased $$(G.litName "Bytes")
|
||||
-- text
|
||||
BigQuery.StringScalarType -> pure $ possiblyNullable scalarType $ BigQuery.StringValue <$> P.string
|
||||
-- floating point values
|
||||
@ -171,12 +171,13 @@ bqColumnParser columnType (G.Nullability isNullable) =
|
||||
BigQuery.BigDecimalScalarType -> pure $ possiblyNullable scalarType $ BigQuery.BigDecimalValue . BigQuery.doubleToBigDecimal <$> P.float
|
||||
-- boolean type
|
||||
BigQuery.BoolScalarType -> pure $ possiblyNullable scalarType $ BigQuery.BoolValue <$> P.boolean
|
||||
BigQuery.DateScalarType -> pure $ possiblyNullable scalarType $ BigQuery.DateValue . BigQuery.Date <$> P.string
|
||||
BigQuery.TimeScalarType -> pure $ possiblyNullable scalarType $ BigQuery.TimeValue . BigQuery.Time <$> P.string
|
||||
BigQuery.DatetimeScalarType -> pure $ possiblyNullable scalarType $ BigQuery.DatetimeValue . BigQuery.Datetime <$> P.string
|
||||
BigQuery.GeographyScalarType -> pure $ possiblyNullable scalarType $ BigQuery.GeographyValue . BigQuery.Geography <$> P.string
|
||||
BigQuery.DateScalarType -> pure $ possiblyNullable scalarType $ BigQuery.DateValue . BigQuery.Date <$> stringBased $$(G.litName "Date")
|
||||
BigQuery.TimeScalarType -> pure $ possiblyNullable scalarType $ BigQuery.TimeValue . BigQuery.Time <$> stringBased $$(G.litName "Time")
|
||||
BigQuery.DatetimeScalarType -> pure $ possiblyNullable scalarType $ BigQuery.DatetimeValue . BigQuery.Datetime <$> stringBased $$(G.litName "Datetime")
|
||||
BigQuery.GeographyScalarType ->
|
||||
pure $ possiblyNullable scalarType $ BigQuery.GeographyValue . BigQuery.Geography <$> throughJSON $$(G.litName "Geography")
|
||||
BigQuery.TimestampScalarType -> do
|
||||
let schemaType = P.TNamed P.Nullable $ P.Definition stringScalar Nothing P.TIScalar
|
||||
let schemaType = P.TNamed P.Nullable $ P.Definition $$(G.litName "Timestamp") Nothing P.TIScalar
|
||||
pure $
|
||||
possiblyNullable scalarType $
|
||||
Parser
|
||||
@ -212,6 +213,9 @@ bqColumnParser columnType (G.Nullability isNullable) =
|
||||
valueToJSON (P.toGraphQLType schemaType)
|
||||
>=> either (parseErrorWith ParseFailed . qeError) pure . runAesonParser J.parseJSON
|
||||
}
|
||||
stringBased :: MonadParse m => G.Name -> Parser 'Both m Text
|
||||
stringBased scalarName =
|
||||
P.string {pType = P.TNamed P.NonNullable $ P.Definition scalarName Nothing P.TIScalar}
|
||||
|
||||
bqJsonPathArg ::
|
||||
MonadParse n =>
|
||||
@ -255,6 +259,7 @@ bqComparisonExps ::
|
||||
m (Parser 'Input n [ComparisonExp 'BigQuery])
|
||||
bqComparisonExps = P.memoize 'comparisonExps $ \columnType -> do
|
||||
collapseIfNull <- asks $ qcDangerousBooleanCollapse . getter
|
||||
dWithinGeogOpParser <- geographyWithinDistanceInput
|
||||
-- see Note [Columns in comparison expression are never nullable]
|
||||
typedParser <- columnParser columnType (G.Nullability False)
|
||||
nullableTextParser <- columnParser (ColumnScalar @'BigQuery BigQuery.StringScalarType) (G.Nullability True)
|
||||
@ -275,14 +280,92 @@ bqComparisonExps = P.memoize 'comparisonExps $ \columnType -> do
|
||||
fmap catMaybes $
|
||||
sequenceA $
|
||||
concat
|
||||
[ equalityOperators
|
||||
[ -- from https://cloud.google.com/bigquery/docs/reference/standard-sql/data-types:
|
||||
-- GEOGRAPHY comparisons are not supported. To compare GEOGRAPHY values, use ST_Equals.
|
||||
guard (isScalarColumnWhere (/= BigQuery.GeographyScalarType) columnType)
|
||||
*> equalityOperators
|
||||
collapseIfNull
|
||||
(mkParameter <$> typedParser)
|
||||
(mkListLiteral <$> columnListParser),
|
||||
comparisonOperators
|
||||
guard (isScalarColumnWhere (/= BigQuery.GeographyScalarType) columnType)
|
||||
*> comparisonOperators
|
||||
collapseIfNull
|
||||
(mkParameter <$> typedParser)
|
||||
(mkParameter <$> typedParser),
|
||||
-- Ops for String type
|
||||
guard (isScalarColumnWhere (== BigQuery.StringScalarType) columnType)
|
||||
*> [ mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_like")
|
||||
(Just "does the column match the given pattern")
|
||||
(ALIKE . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_nlike")
|
||||
(Just "does the column NOT match the given pattern")
|
||||
(ANLIKE . mkParameter <$> typedParser)
|
||||
],
|
||||
-- Ops for Bytes type
|
||||
guard (isScalarColumnWhere (== BigQuery.BytesScalarType) columnType)
|
||||
*> [ mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_like")
|
||||
(Just "does the column match the given pattern")
|
||||
(ALIKE . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_nlike")
|
||||
(Just "does the column NOT match the given pattern")
|
||||
(ANLIKE . mkParameter <$> typedParser)
|
||||
],
|
||||
-- Ops for Geography type
|
||||
guard (isScalarColumnWhere (== BigQuery.GeographyScalarType) columnType)
|
||||
*> [ mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_st_contains")
|
||||
(Just "does the column contain the given geography value")
|
||||
(ABackendSpecific . BigQuery.ASTContains . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_st_equals")
|
||||
(Just "is the column equal to given geography value (directionality is ignored)")
|
||||
(ABackendSpecific . BigQuery.ASTEquals . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_st_touches")
|
||||
(Just "does the column have at least one point in common with the given geography value")
|
||||
(ABackendSpecific . BigQuery.ASTTouches . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_st_within")
|
||||
(Just "is the column contained in the given geography value")
|
||||
(ABackendSpecific . BigQuery.ASTWithin . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_st_intersects")
|
||||
(Just "does the column spatially intersect the given geography value")
|
||||
(ABackendSpecific . BigQuery.ASTIntersects . mkParameter <$> typedParser),
|
||||
mkBoolOperator
|
||||
collapseIfNull
|
||||
$$(G.litName "_st_d_within")
|
||||
(Just "is the column within a given distance from the given geometry value")
|
||||
(ABackendSpecific . BigQuery.ASTDWithin <$> dWithinGeogOpParser)
|
||||
]
|
||||
]
|
||||
|
||||
geographyWithinDistanceInput ::
|
||||
forall m n r.
|
||||
(MonadSchema n m, MonadError QErr m, MonadReader r m, Has MkTypename r) =>
|
||||
m (Parser 'Input n (DWithinGeogOp (UnpreparedValue 'BigQuery)))
|
||||
geographyWithinDistanceInput = do
|
||||
geographyParser <- columnParser (ColumnScalar BigQuery.GeographyScalarType) (G.Nullability False)
|
||||
-- practically BigQuery (as of 2021-11-19) doesn't support TRUE as use_spheroid parameter for ST_DWITHIN
|
||||
booleanParser <- columnParser (ColumnScalar BigQuery.BoolScalarType) (G.Nullability True)
|
||||
floatParser <- columnParser (ColumnScalar BigQuery.FloatScalarType) (G.Nullability False)
|
||||
pure $
|
||||
P.object $$(G.litName "st_dwithin_input") Nothing $
|
||||
DWithinGeogOp <$> (mkParameter <$> P.field $$(G.litName "distance") Nothing floatParser)
|
||||
<*> (mkParameter <$> P.field $$(G.litName "from") Nothing geographyParser)
|
||||
<*> (mkParameter <$> P.fieldWithDefault $$(G.litName "use_spheroid") Nothing (G.VBoolean False) booleanParser)
|
||||
|
||||
bqMkCountType ::
|
||||
-- | distinct values
|
||||
|
@ -28,7 +28,7 @@ instance Backend 'BigQuery where
|
||||
type ScalarType 'BigQuery = BigQuery.ScalarType
|
||||
type SQLExpression 'BigQuery = BigQuery.Expression
|
||||
type SQLOperator 'BigQuery = BigQuery.Op
|
||||
type BooleanOperators 'BigQuery = Const Void
|
||||
type BooleanOperators 'BigQuery = BigQuery.BooleanOperators
|
||||
|
||||
type XComputedField 'BigQuery = XDisable
|
||||
type XRelay 'BigQuery = XDisable
|
||||
|
@ -105,13 +105,15 @@ fromExpression =
|
||||
"(" <+> fromExpression x <+> ") != (" <+> fromExpression y <+> ")"
|
||||
ToStringExpression e -> "CONCAT(" <+> fromExpression e <+> ", '')"
|
||||
SelectExpression s -> "(" <+> IndentPrinter 1 (fromSelect s) <+> ")"
|
||||
ListExpression xs -> " UNNEST ([" <+> (SepByPrinter ", " $ fromExpression <$> xs) <+> "])"
|
||||
ListExpression xs -> " UNNEST ([" <+> SepByPrinter ", " (fromExpression <$> xs) <+> "])"
|
||||
OpExpression op x y ->
|
||||
"("
|
||||
<+> fromExpression x
|
||||
<+> ") "
|
||||
<+> fromOp op
|
||||
<+> fromExpression y
|
||||
FunctionExpression name args ->
|
||||
UnsafeTextPrinter name <+> "(" <+> SepByPrinter ", " (fromExpression <$> args) <+> ")"
|
||||
ConditionalProjection expression fieldName ->
|
||||
"(CASE WHEN(" <+> fromExpression expression
|
||||
<+> ") THEN "
|
||||
@ -144,6 +146,8 @@ fromOp =
|
||||
LessOrEqualOp -> "<="
|
||||
InOp -> "IN"
|
||||
NotInOp -> "NOT IN"
|
||||
LikeOp -> "LIKE"
|
||||
NotLikeOp -> "NOT LIKE"
|
||||
|
||||
fromPath :: JsonPath -> Printer
|
||||
fromPath path =
|
||||
|
@ -7,6 +7,7 @@ module Hasura.Backends.BigQuery.Types
|
||||
ArrayAgg (..),
|
||||
Base64,
|
||||
BigDecimal,
|
||||
BooleanOperators (..),
|
||||
Cardinality (..),
|
||||
ColumnName (ColumnName),
|
||||
Countable (..),
|
||||
@ -65,6 +66,7 @@ where
|
||||
|
||||
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
|
||||
import Data.Aeson qualified as J
|
||||
import Data.Aeson.Extended qualified as J
|
||||
import Data.Aeson.Types qualified as J
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.ByteString.Base64 qualified as Base64
|
||||
@ -83,6 +85,7 @@ import Data.Vector.Instances ()
|
||||
import Hasura.Base.Error
|
||||
import Hasura.Incremental.Internal.Dependency
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.IR.BoolExp
|
||||
import Hasura.RQL.Types.Common qualified as RQL
|
||||
import Language.GraphQL.Draft.Syntax qualified as G
|
||||
import Language.Haskell.TH.Syntax
|
||||
@ -402,6 +405,7 @@ data Expression
|
||||
| OpExpression Op Expression Expression
|
||||
| ListExpression [Expression]
|
||||
| CastExpression Expression ScalarType
|
||||
| FunctionExpression !Text [Expression]
|
||||
| ConditionalProjection Expression FieldName
|
||||
deriving (Eq, Ord, Show, Generic, Data, Lift)
|
||||
|
||||
@ -611,9 +615,9 @@ data Op
|
||||
| MoreOrEqualOp
|
||||
| InOp
|
||||
| NotInOp
|
||||
| LikeOp
|
||||
| NotLikeOp
|
||||
-- | SNE
|
||||
-- | SLIKE
|
||||
-- | SNLIKE
|
||||
-- | SILIKE
|
||||
-- | SNILIKE
|
||||
-- | SSIMILAR
|
||||
@ -858,6 +862,30 @@ data UnifiedOn = UnifiedOn
|
||||
newtype FunctionName = FunctionName Text -- TODO: Improve this type when SQL function support added
|
||||
deriving (FromJSON, ToJSON, ToJSONKey, ToTxt, Show, Eq, Ord, Hashable, Cacheable, NFData)
|
||||
|
||||
data BooleanOperators a
|
||||
= ASTContains !a
|
||||
| ASTEquals !a
|
||||
| ASTTouches !a
|
||||
| ASTWithin !a
|
||||
| ASTIntersects !a
|
||||
| ASTDWithin !(DWithinGeogOp a)
|
||||
deriving stock (Eq, Generic, Foldable, Functor, Traversable, Show)
|
||||
|
||||
instance NFData a => NFData (BooleanOperators a)
|
||||
|
||||
instance Hashable a => Hashable (BooleanOperators a)
|
||||
|
||||
instance Cacheable a => Cacheable (BooleanOperators a)
|
||||
|
||||
instance ToJSON a => J.ToJSONKeyValue (BooleanOperators a) where
|
||||
toJSONKeyValue = \case
|
||||
ASTContains a -> ("_st_contains", J.toJSON a)
|
||||
ASTEquals a -> ("_st_equals", J.toJSON a)
|
||||
ASTIntersects a -> ("_st_intersects", J.toJSON a)
|
||||
ASTTouches a -> ("_st_touches", J.toJSON a)
|
||||
ASTWithin a -> ("_st_within", J.toJSON a)
|
||||
ASTDWithin a -> ("_st_dwithin", J.toJSON a)
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
-- Backend-related stuff
|
||||
--
|
||||
|
@ -0,0 +1,18 @@
|
||||
type: bulk
|
||||
args:
|
||||
- type: bigquery_run_sql
|
||||
args:
|
||||
source: bigquery
|
||||
sql: |
|
||||
DROP TABLE IF EXISTS `hasura_test.city`;
|
||||
CREATE TABLE `hasura_test.city` (
|
||||
`name` STRING,
|
||||
`country` STRING
|
||||
);
|
||||
|
||||
INSERT INTO `hasura_test.city` (`name`, `country`)
|
||||
VALUES
|
||||
('Durham', 'USA'),
|
||||
('New York', 'USA'),
|
||||
('Framlingham', 'UK'),
|
||||
('New Orleans', 'USA');
|
@ -0,0 +1,21 @@
|
||||
description: Select cities ending with ham
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_city:
|
||||
- name: Durham
|
||||
country: USA
|
||||
- name: Framlingham
|
||||
country: UK
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_city (
|
||||
where: {name: {_like: "%ham" }},
|
||||
order_by: {name: asc}
|
||||
) {
|
||||
name
|
||||
country
|
||||
}
|
||||
}
|
@ -0,0 +1,21 @@
|
||||
description: Select cities not ending with ham
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_city:
|
||||
- name: New Orleans
|
||||
country: USA
|
||||
- name: New York
|
||||
country: USA
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_city (
|
||||
where: {name: {_nlike: "%ham" }},
|
||||
order_by: {name: asc}
|
||||
) {
|
||||
name
|
||||
country
|
||||
}
|
||||
}
|
@ -0,0 +1,10 @@
|
||||
type: bulk
|
||||
args:
|
||||
|
||||
#City table
|
||||
- type: bigquery_track_table
|
||||
args:
|
||||
source: bigquery
|
||||
table:
|
||||
dataset: hasura_test
|
||||
name: city
|
@ -0,0 +1,10 @@
|
||||
type: bulk
|
||||
args:
|
||||
|
||||
- type: bigquery_untrack_table
|
||||
args:
|
||||
source: bigquery
|
||||
table:
|
||||
dataset: hasura_test
|
||||
name: city
|
||||
cascade: true
|
@ -0,0 +1,45 @@
|
||||
type: bulk
|
||||
args:
|
||||
- type: bigquery_run_sql
|
||||
args:
|
||||
source: bigquery
|
||||
sql: |
|
||||
DROP TABLE IF EXISTS `hasura_test.spatial_types_geog`;
|
||||
CREATE TABLE `hasura_test.spatial_types_geog` (
|
||||
`point` GEOGRAPHY,
|
||||
`linestring` GEOGRAPHY,
|
||||
`polygon` GEOGRAPHY,
|
||||
`multipoint` GEOGRAPHY,
|
||||
`multilinestring` GEOGRAPHY,
|
||||
`multipolygon` GEOGRAPHY,
|
||||
`geometrycollection` GEOGRAPHY
|
||||
);
|
||||
INSERT INTO `hasura_test.spatial_types_geog` (
|
||||
`point`,
|
||||
`linestring`,
|
||||
`polygon`,
|
||||
`multipoint`,
|
||||
`multilinestring`,
|
||||
`multipolygon`,
|
||||
`geometrycollection`
|
||||
)
|
||||
VALUES (
|
||||
st_geogfromtext('POINT(3 4)'),
|
||||
st_geogfromtext('LINESTRING(1 1,2 3,4 8, -6 3)'),
|
||||
st_geogfromtext('POLYGON((1 1, 1 2, 2 1, 1 1))'),
|
||||
st_geogfromtext('MULTIPOINT((2 3), (7 8))'),
|
||||
st_geogfromtext(
|
||||
'MULTILINESTRING((1 1, 3 3, 5 5),(3 3, 5 5, 7 7))'
|
||||
),
|
||||
st_geogfromtext(
|
||||
-- for some odd reason this multipolygon from 3 polygons goes through a very odd conversion in BigQuery
|
||||
-- st_geogfromtext('MULTIPOLYGON(((-120.533 46.566, -118.283 46.1, -122.3 47.45, -120.533 46.566)),((2 2, 2 -2, -2 -2, -2 2, 2 2)),((1 1, 3 1, 3 3, 1 3, 1 1)))')
|
||||
-- ->
|
||||
-- MULTIPOLYGON(((-120.533 46.566, -118.283 46.1, -122.3 47.45, -120.533 46.566)), ((-2 2, -2 -2, 2 -2, 2 1.00015229710421, 3 1, 3 3, 1 3, 1 2.00091355021717, -2 2)))
|
||||
'MULTIPOLYGON(((-120.533 46.566, -118.283 46.1, -122.3 47.45, -120.533 46.566)),((2 2, 2 -2, -2 -2, -2 2, 2 2)))'
|
||||
),
|
||||
st_geogfromtext(
|
||||
'GEOMETRYCOLLECTION(LINESTRING(1 1, 3 5),POLYGON((-1 -1, -1 -5, -5 -5, -5 -1, -1 -1)))'
|
||||
)
|
||||
);
|
||||
|
@ -0,0 +1,30 @@
|
||||
description: GraphQL query to test different data types of SQL Server
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- point: POINT(3 4)
|
||||
linestring: LINESTRING(1 1, 2 3, 4 8, -6 3)
|
||||
polygon: POLYGON((2 1, 1 2, 1 1, 2 1))
|
||||
multipoint: MULTIPOINT(2 3, 7 8)
|
||||
multilinestring:
|
||||
LINESTRING(1 1, 3 3, 5 5, 7 7)
|
||||
multipolygon:
|
||||
MULTIPOLYGON(((-120.533 46.566, -118.283 46.1, -122.3 47.45, -120.533 46.566)), ((-2 2, -2 -2, 2 -2, 2 2, -2 2)))
|
||||
geometrycollection:
|
||||
GEOMETRYCOLLECTION(LINESTRING(1 1, 3 5), POLYGON((-5 -1, -5 -5, -1 -5, -1 -1, -5 -1)))
|
||||
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog {
|
||||
point
|
||||
linestring
|
||||
polygon
|
||||
multipoint
|
||||
multilinestring
|
||||
multipolygon
|
||||
geometrycollection
|
||||
}
|
||||
}
|
@ -0,0 +1,21 @@
|
||||
description: Query data from spatial_types_geo using _st_contains
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- multipolygon:
|
||||
MULTIPOLYGON(((-120.533 46.566, -118.283 46.1, -122.3 47.45, -120.533 46.566)), ((-2 2, -2 -2, 2 -2, 2 2, -2 2)))
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(
|
||||
where: {
|
||||
multipolygon: {
|
||||
_st_contains: "POINT(0.5 0)"
|
||||
}
|
||||
}
|
||||
) {
|
||||
multipolygon
|
||||
}
|
||||
}
|
@ -0,0 +1,20 @@
|
||||
description: Query data from spatial_types_geog using _st_d_within
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- multipoint: MULTIPOINT(2 3, 7 8)
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(
|
||||
where: {
|
||||
multipoint: {
|
||||
_st_d_within: { distance: 1, from: "POLYGON ((0 0, 10 10, 10 10, 10 0, 0 0))"}
|
||||
}
|
||||
}
|
||||
) {
|
||||
multipoint
|
||||
}
|
||||
}
|
@ -0,0 +1,20 @@
|
||||
description: Query data from spatial_types_geog using _st_d_within
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- multipoint: MULTIPOINT(2 3, 7 8)
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(
|
||||
where: {
|
||||
multipoint: {
|
||||
_st_d_within: { distance: 1, from: "POLYGON ((0 0, 10 10, 10 10, 10 0, 0 0))"}
|
||||
}
|
||||
}
|
||||
) {
|
||||
multipoint
|
||||
}
|
||||
}
|
@ -0,0 +1,24 @@
|
||||
description: Query data from spatial_types_geog using _st_equals
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- geometrycollection:
|
||||
GEOMETRYCOLLECTION(LINESTRING(1 1, 3 5), POLYGON((-5 -1, -5 -5, -1 -5, -1 -1, -5 -1)))
|
||||
query:
|
||||
# note: using GEOMETRYCOLLECTION(LINESTRING(1 1, 3 5),POLYGON((-1 -1, -1 -5, -5 -5, -5 -1, -1 -1)))
|
||||
# doesn't work with st_equals in BigQuery even when the docs say that the function should work with
|
||||
# any point order (probably the problem is in handling GEOGRAPHY params)
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(
|
||||
where: {
|
||||
geometrycollection: {
|
||||
_st_equals: "GEOMETRYCOLLECTION(LINESTRING(1 1, 3 5), POLYGON((-5 -1, -5 -5, -1 -5, -1 -1, -5 -1)))"
|
||||
}
|
||||
}
|
||||
) {
|
||||
geometrycollection
|
||||
}
|
||||
}
|
@ -0,0 +1,14 @@
|
||||
description: Query data from spatial_types_geog using _st_intersects
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- polygon: POLYGON((2 1, 1 2, 1 1, 2 1))
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(where: { polygon: { _st_intersects: "LINESTRING(0 0, 2 2)" } }) {
|
||||
polygon
|
||||
}
|
||||
}
|
@ -0,0 +1,20 @@
|
||||
description: Query data from spatial_types_geog using _st_touches
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- point: POINT(3 4)
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(
|
||||
where: {
|
||||
point: {
|
||||
_st_touches: "POLYGON ((3 4, 2 5, 5 5, 5 2, 3 4))"
|
||||
}
|
||||
}
|
||||
) {
|
||||
point
|
||||
}
|
||||
}
|
@ -0,0 +1,20 @@
|
||||
description: Query data from spatial_types_geog using _st_within
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
response:
|
||||
data:
|
||||
hasura_test_spatial_types_geog:
|
||||
- multipoint: MULTIPOINT(2 3, 7 8)
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
hasura_test_spatial_types_geog(
|
||||
where: {
|
||||
multipoint: {
|
||||
_st_within: "POLYGON ((0 0, 10 10, 10 10, 10 0, 0 0))"
|
||||
}
|
||||
}
|
||||
) {
|
||||
multipoint
|
||||
}
|
||||
}
|
@ -0,0 +1,9 @@
|
||||
type: bulk
|
||||
args:
|
||||
|
||||
- type: bigquery_track_table
|
||||
args:
|
||||
source: bigquery
|
||||
table:
|
||||
dataset: hasura_test
|
||||
name: spatial_types_geog
|
@ -0,0 +1,10 @@
|
||||
type: bulk
|
||||
args:
|
||||
|
||||
- type: bigquery_untrack_table
|
||||
args:
|
||||
source: bigquery
|
||||
table:
|
||||
dataset: hasura_test
|
||||
name: spatial_types_geog
|
||||
cascade: true
|
@ -223,6 +223,20 @@ class TestGraphQLQueryBasicBigquery:
|
||||
def dir(cls):
|
||||
return 'queries/graphql_query/bigquery'
|
||||
|
||||
@pytest.mark.parametrize("transport", ['http', 'websocket'])
|
||||
@pytest.mark.parametrize("backend", ['bigquery'])
|
||||
@usefixtures('per_class_tests_db_state')
|
||||
class TestGraphQLQueryBoolExpSearchBigquery:
|
||||
|
||||
def test_city_where_like(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_city_where_like_bigquery.yaml', transport)
|
||||
|
||||
def test_city_where_not_like(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_city_where_nlike_bigquery.yaml', transport)
|
||||
|
||||
@classmethod
|
||||
def dir(cls):
|
||||
return 'queries/graphql_query/boolexp/search'
|
||||
|
||||
@pytest.mark.parametrize("transport", ['http', 'websocket'])
|
||||
@pytest.mark.parametrize("backend", ['citus', 'mssql', 'postgres'])
|
||||
@ -1537,3 +1551,32 @@ class TestGraphQLQueryBoolExpSpatialMSSQL:
|
||||
@classmethod
|
||||
def dir(cls):
|
||||
return 'queries/graphql_query/boolexp/spatial'
|
||||
|
||||
@pytest.mark.parametrize("transport", ['http', 'websocket'])
|
||||
@pytest.mark.parametrize("backend", ['bigquery'])
|
||||
@usefixtures('per_class_tests_db_state')
|
||||
class TestGraphQLQueryBoolExpSpatialBigquery:
|
||||
def test_select_spatial_bigquery_types(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_bigquery.yaml', transport)
|
||||
|
||||
def test_select_spatial_bigquery_types_where_st_equals(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_where_st_equals_bigquery.yaml', transport)
|
||||
|
||||
def test_select_spatial_bigquery_types_where_st_contains(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_where_st_contains_bigquery.yaml', transport)
|
||||
|
||||
def test_select_spatial_bigquery_types_where_st_intersects(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_where_st_intersects_bigquery.yaml', transport)
|
||||
|
||||
def test_select_spatial_bigquery_types_where_st_within(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_where_st_within_bigquery.yaml', transport)
|
||||
|
||||
def test_select_spatial_bigquery_types_where_st_d_within(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_where_st_d_within_bigquery.yaml', transport)
|
||||
|
||||
def test_select_spatial_bigquery_types_where_st_touches(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_query_spatial_types_where_st_touches_bigquery.yaml', transport)
|
||||
|
||||
@classmethod
|
||||
def dir(cls):
|
||||
return 'queries/graphql_query/boolexp/spatial'
|
||||
|
Loading…
Reference in New Issue
Block a user