Replaces litName splices with name quasiquotes

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4267
GitOrigin-RevId: 2d93c35a7e34dbada3b72aabcae5fc2858bbfc29
This commit is contained in:
Solomon 2022-04-18 12:43:00 -07:00 committed by hasura-bot
parent bc999d8353
commit c945b2d391
39 changed files with 1211 additions and 431 deletions

View File

@ -749,6 +749,7 @@ library
, Hasura.GraphQL.Parser.Class.Parse
, Hasura.GraphQL.Parser.Collect
, Hasura.GraphQL.Parser.Column
, Hasura.GraphQL.Parser.Constants
, Hasura.GraphQL.Parser.Directives
, Hasura.GraphQL.Parser.Internal.Convert
, Hasura.GraphQL.Parser.Internal.Input

View File

@ -6,6 +6,7 @@ module Data.Text.NonEmpty
mkNonEmptyText,
unNonEmptyText,
nonEmptyText,
nonEmptyTextQQ,
)
where
@ -13,8 +14,9 @@ import Data.Aeson
import Data.Text qualified as T
import Data.Text.Extended
import Database.PG.Query qualified as Q
import Hasura.Prelude
import Language.Haskell.TH.Syntax (Lift, Q, TExp)
import Hasura.Prelude hiding (lift)
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax (Lift, Q, TExp, lift)
import Test.QuickCheck qualified as QC
newtype NonEmptyText = NonEmptyText {unNonEmptyText :: Text}
@ -36,6 +38,18 @@ parseNonEmptyText text = mkNonEmptyText text `onNothing` fail "empty string not
nonEmptyText :: Text -> Q (TExp NonEmptyText)
nonEmptyText = parseNonEmptyText >=> \text -> [||text||]
-- | Construct 'NonEmptyText' literals at compile-time via quasiquotation.
nonEmptyTextQQ :: QuasiQuoter
nonEmptyTextQQ =
QuasiQuoter {quoteExp, quotePat, quoteType, quoteDec}
where
quotePat _ = error "nonEmptyTextQQ does not support quoting patterns"
quoteType _ = error "nonEmptyTextQQ does not support quoting types"
quoteDec _ = error "nonEmptyTextQQ does not support quoting declarations"
quoteExp s = case mkNonEmptyText (T.pack s) of
Just result -> lift result
Nothing -> fail "empty string not allowed"
instance FromJSON NonEmptyText where
parseJSON = withText "String" parseNonEmptyText

View File

@ -14,6 +14,7 @@ import Hasura.Backends.BigQuery.Types qualified as BigQuery
import Hasura.Base.Error
import Hasura.GraphQL.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser hiding (field)
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
@ -148,7 +149,7 @@ bqColumnParser columnType (G.Nullability isNullable) =
ColumnScalar scalarType -> case scalarType of
-- bytestrings
-- we only accept string literals
BigQuery.BytesScalarType -> pure $ possiblyNullable scalarType $ BigQuery.StringValue <$> stringBased $$(G.litName "Bytes")
BigQuery.BytesScalarType -> pure $ possiblyNullable scalarType $ BigQuery.StringValue <$> stringBased G._Bytes
-- text
BigQuery.StringScalarType -> pure $ possiblyNullable scalarType $ BigQuery.StringValue <$> P.string
-- floating point values
@ -162,13 +163,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 <$> 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.DateScalarType -> pure $ possiblyNullable scalarType $ BigQuery.DateValue . BigQuery.Date <$> stringBased G._Date
BigQuery.TimeScalarType -> pure $ possiblyNullable scalarType $ BigQuery.TimeValue . BigQuery.Time <$> stringBased G._Time
BigQuery.DatetimeScalarType -> pure $ possiblyNullable scalarType $ BigQuery.DatetimeValue . BigQuery.Datetime <$> stringBased G._Datetime
BigQuery.GeographyScalarType ->
pure $ possiblyNullable scalarType $ BigQuery.GeographyValue . BigQuery.Geography <$> throughJSON $$(G.litName "Geography")
pure $ possiblyNullable scalarType $ BigQuery.GeographyValue . BigQuery.Geography <$> throughJSON G._Geography
BigQuery.TimestampScalarType ->
pure $ possiblyNullable scalarType $ BigQuery.TimestampValue . BigQuery.Timestamp <$> stringBased $$(G.litName "Timestamp")
pure $ possiblyNullable scalarType $ BigQuery.TimestampValue . BigQuery.Timestamp <$> stringBased G._Timestamp
ty -> throwError $ internalError $ T.pack $ "Type currently unsupported for BigQuery: " ++ show ty
ColumnEnumReference enumRef@(EnumReference _ enumValues _) ->
case nonEmpty (Map.toList enumValues) of
@ -210,22 +211,22 @@ bqOrderByOperators ::
)
bqOrderByOperators =
NE.fromList
[ ( define $$(G.litName "asc") "in ascending order, nulls first",
[ ( define G._asc "in ascending order, nulls first",
(BigQuery.AscOrder, BigQuery.NullsFirst)
),
( define $$(G.litName "asc_nulls_first") "in ascending order, nulls first",
( define G._asc_nulls_first "in ascending order, nulls first",
(BigQuery.AscOrder, BigQuery.NullsFirst)
),
( define $$(G.litName "asc_nulls_last") "in ascending order, nulls last",
( define G._asc_nulls_last "in ascending order, nulls last",
(BigQuery.AscOrder, BigQuery.NullsLast)
),
( define $$(G.litName "desc") "in descending order, nulls last",
( define G._desc "in descending order, nulls last",
(BigQuery.DescOrder, BigQuery.NullsLast)
),
( define $$(G.litName "desc_nulls_first") "in descending order, nulls first",
( define G._desc_nulls_first "in descending order, nulls first",
(BigQuery.DescOrder, BigQuery.NullsFirst)
),
( define $$(G.litName "desc_nulls_last") "in descending order, nulls last",
( define G._desc_nulls_last "in descending order, nulls last",
(BigQuery.DescOrder, BigQuery.NullsLast)
)
]
@ -242,9 +243,9 @@ bqComparisonExps = P.memoize 'comparisonExps $ \columnType -> do
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)
_nullableTextParser <- columnParser (ColumnScalar @'BigQuery BigQuery.StringScalarType) (G.Nullability True)
-- textParser <- columnParser (ColumnScalar @'BigQuery BigQuery.StringScalarType) (G.Nullability False)
let name = P.getName typedParser <> $$(G.litName "_BigQuery_comparison_exp")
let name = P.getName typedParser <> G.__BigQuery_comparison_exp
desc =
G.Description $
"Boolean expression to compare columns of type "
@ -275,12 +276,12 @@ bqComparisonExps = P.memoize 'comparisonExps $ \columnType -> do
guard (isScalarColumnWhere (== BigQuery.StringScalarType) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_like")
G.__like
(Just "does the column match the given pattern")
(ALIKE . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_nlike")
G.__nlike
(Just "does the column NOT match the given pattern")
(ANLIKE . mkParameter <$> typedParser)
],
@ -288,12 +289,12 @@ bqComparisonExps = P.memoize 'comparisonExps $ \columnType -> do
guard (isScalarColumnWhere (== BigQuery.BytesScalarType) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_like")
G.__like
(Just "does the column match the given pattern")
(ALIKE . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_nlike")
G.__nlike
(Just "does the column NOT match the given pattern")
(ANLIKE . mkParameter <$> typedParser)
],
@ -301,32 +302,32 @@ bqComparisonExps = P.memoize 'comparisonExps $ \columnType -> do
guard (isScalarColumnWhere (== BigQuery.GeographyScalarType) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_st_contains")
G.__st_contains
(Just "does the column contain the given geography value")
(ABackendSpecific . BigQuery.ASTContains . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_equals")
G.__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")
G.__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")
G.__st_within
(Just "is the column contained in the given geography value")
(ABackendSpecific . BigQuery.ASTWithin . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_intersects")
G.__st_intersects
(Just "does the column spatially intersect the given geography value")
(ABackendSpecific . BigQuery.ASTIntersects . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_d_within")
G.__st_d_within
(Just "is the column within a given distance from the given geometry value")
(ABackendSpecific . BigQuery.ASTDWithin <$> dWithinGeogOpParser)
]
@ -338,7 +339,7 @@ bqCountTypeInput ::
InputFieldsParser n (IR.CountDistinct -> CountType 'BigQuery)
bqCountTypeInput = \case
Just columnEnum -> do
columns <- P.fieldOptional $$(G.litName "columns") Nothing $ P.list columnEnum
columns <- P.fieldOptional G._columns Nothing $ P.list columnEnum
pure $ flip mkCountType columns
Nothing -> pure $ flip mkCountType Nothing
where
@ -359,10 +360,10 @@ geographyWithinDistanceInput = do
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)
P.object G._st_dwithin_input Nothing $
DWithinGeogOp <$> (mkParameter <$> P.field G._distance Nothing floatParser)
<*> (mkParameter <$> P.field G._from Nothing geographyParser)
<*> (mkParameter <$> P.fieldWithDefault G._use_spheroid Nothing (G.VBoolean False) booleanParser)
-- | Computed field parser.
-- Currently unsupported: returns Nothing for now.
@ -375,6 +376,8 @@ bqComputedField ::
m (Maybe (FieldParser n (AnnotatedField 'BigQuery)))
bqComputedField _sourceName _fieldInfo _table _tableInfo = pure Nothing
{-
NOTE: Unused. Should we remove?
-- | Remote join field parser.
-- Currently unsupported: returns Nothing for now.
bqRemoteRelationshipField ::
@ -382,6 +385,7 @@ bqRemoteRelationshipField ::
RemoteFieldInfo (DBJoinField 'BigQuery) ->
m (Maybe [FieldParser n (AnnotatedField 'BigQuery)])
bqRemoteRelationshipField _remoteFieldInfo = pure Nothing
-}
-- | The 'node' root field of a Relay request. Relay is currently unsupported on BigQuery,
-- meaning this parser will never be called: any attempt to create this parser should

View File

@ -20,6 +20,7 @@ import Hasura.Backends.MSSQL.Types.Update (BackendUpdate (..), UpdateOperator (.
import Hasura.Base.Error
import Hasura.GraphQL.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser hiding (field)
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
@ -129,6 +130,10 @@ msBuildTableUpdateMutationFields sourceName tableName tableInfo gqlName = do
gqlName
pure . fold @Maybe @[_] $ fieldParsers
{-
NOTE: We currently use 'GSB.buildTableDeleteMutationFields' instead of
this. Should we save it?
msBuildTableDeleteMutationFields ::
MonadBuildSchema 'MSSQL r m n =>
SourceName ->
@ -140,6 +145,7 @@ msBuildTableDeleteMutationFields ::
m [a]
msBuildTableDeleteMutationFields _sourceName _tableName _tableInfo _gqlName _delPerns _selPerms =
pure []
-}
msBuildFunctionQueryFields ::
MonadBuildSchema 'MSSQL r m n =>
@ -294,22 +300,22 @@ msOrderByOperators ::
)
msOrderByOperators =
NE.fromList
[ ( define $$(G.litName "asc") "in ascending order, nulls first",
[ ( define G._asc "in ascending order, nulls first",
(MSSQL.AscOrder, MSSQL.NullsFirst)
),
( define $$(G.litName "asc_nulls_first") "in ascending order, nulls first",
( define G._asc_nulls_first "in ascending order, nulls first",
(MSSQL.AscOrder, MSSQL.NullsFirst)
),
( define $$(G.litName "asc_nulls_last") "in ascending order, nulls last",
( define G._asc_nulls_last "in ascending order, nulls last",
(MSSQL.AscOrder, MSSQL.NullsLast)
),
( define $$(G.litName "desc") "in descending order, nulls last",
( define G._desc "in descending order, nulls last",
(MSSQL.DescOrder, MSSQL.NullsLast)
),
( define $$(G.litName "desc_nulls_first") "in descending order, nulls first",
( define G._desc_nulls_first "in descending order, nulls first",
(MSSQL.DescOrder, MSSQL.NullsFirst)
),
( define $$(G.litName "desc_nulls_last") "in descending order, nulls last",
( define G._desc_nulls_last "in descending order, nulls last",
(MSSQL.DescOrder, MSSQL.NullsLast)
)
]
@ -333,13 +339,13 @@ msComparisonExps = P.memoize 'comparisonExps \columnType -> do
-- parsers used for individual values
typedParser <- columnParser columnType (G.Nullability False)
nullableTextParser <- columnParser (ColumnScalar @'MSSQL MSSQL.VarcharType) (G.Nullability True)
_nullableTextParser <- columnParser (ColumnScalar @'MSSQL MSSQL.VarcharType) (G.Nullability True)
textParser <- columnParser (ColumnScalar @'MSSQL MSSQL.VarcharType) (G.Nullability False)
let columnListParser = fmap openValueOrigin <$> P.list typedParser
textListParser = fmap openValueOrigin <$> P.list textParser
_textListParser = fmap openValueOrigin <$> P.list textParser
-- field info
let name = P.getName typedParser <> $$(G.litName "_MSSQL_comparison_exp")
let name = P.getName typedParser <> G.__MSSQL_comparison_exp
desc =
G.Description $
"Boolean expression to compare columns of type "
@ -362,45 +368,45 @@ msComparisonExps = P.memoize 'comparisonExps \columnType -> do
-- Ops for String like types
guard (isScalarColumnWhere (`elem` MSSQL.stringTypes) columnType)
*> [ P.fieldOptional
$$(G.litName "_like")
G.__like
(Just "does the column match the given pattern")
(ALIKE . mkParameter <$> typedParser),
P.fieldOptional
$$(G.litName "_nlike")
G.__nlike
(Just "does the column NOT match the given pattern")
(ANLIKE . mkParameter <$> typedParser)
],
-- Ops for Geometry/Geography types
guard (isScalarColumnWhere (`elem` MSSQL.geoTypes) columnType)
*> [ P.fieldOptional
$$(G.litName "_st_contains")
G.__st_contains
(Just "does the column contain the given value")
(ABackendSpecific . MSSQL.ASTContains . mkParameter <$> typedParser),
P.fieldOptional
$$(G.litName "_st_equals")
G.__st_equals
(Just "is the column equal to given value (directionality is ignored)")
(ABackendSpecific . MSSQL.ASTEquals . mkParameter <$> typedParser),
P.fieldOptional
$$(G.litName "_st_intersects")
G.__st_intersects
(Just "does the column spatially intersect the given value")
(ABackendSpecific . MSSQL.ASTIntersects . mkParameter <$> typedParser),
P.fieldOptional
$$(G.litName "_st_overlaps")
G.__st_overlaps
(Just "does the column 'spatially overlap' (intersect but not completely contain) the given value")
(ABackendSpecific . MSSQL.ASTOverlaps . mkParameter <$> typedParser),
P.fieldOptional
$$(G.litName "_st_within")
G.__st_within
(Just "is the column contained in the given value")
(ABackendSpecific . MSSQL.ASTWithin . mkParameter <$> typedParser)
],
-- Ops for Geometry types
guard (isScalarColumnWhere (MSSQL.GeometryType ==) columnType)
*> [ P.fieldOptional
$$(G.litName "_st_crosses")
G.__st_crosses
(Just "does the column cross the given geometry value")
(ABackendSpecific . MSSQL.ASTCrosses . mkParameter <$> typedParser),
P.fieldOptional
$$(G.litName "_st_touches")
G.__st_touches
(Just "does the column have at least one point in common with the given geometry value")
(ABackendSpecific . MSSQL.ASTTouches . mkParameter <$> typedParser)
]
@ -416,7 +422,7 @@ msCountTypeInput ::
InputFieldsParser n (IR.CountDistinct -> CountType 'MSSQL)
msCountTypeInput = \case
Just columnEnum -> do
column <- P.fieldOptional $$(G.litName "column") Nothing columnEnum
column <- P.fieldOptional G._column Nothing columnEnum
pure $ flip mkCountType column
Nothing -> pure $ flip mkCountType Nothing
where
@ -436,6 +442,9 @@ msComputedField ::
m (Maybe (FieldParser n (AnnotatedField 'MSSQL)))
msComputedField _sourceName _fieldInfo _table _tableInfo = pure Nothing
{-
NOTE: Unused, should we remove?
-- | Remote join field parser.
-- Currently unsupported: returns Nothing for now.
msRemoteRelationshipField ::
@ -443,6 +452,7 @@ msRemoteRelationshipField ::
RemoteFieldInfo (DBJoinField 'MSSQL) ->
m (Maybe [FieldParser n (AnnotatedField 'MSSQL)])
msRemoteRelationshipField _remoteFieldInfo = pure Nothing
-}
-- | The 'node' root field of a Relay request. Relay is currently unsupported on MSSQL,
-- meaning this parser will never be called: any attempt to create this parser should

View File

@ -1,5 +1,4 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE TemplateHaskell #-}
-- | MSSQL Schema IfMatched
--
@ -25,6 +24,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
@ -54,7 +54,7 @@ ifMatchedFieldParser ::
m (InputFieldsParser n (Maybe (IfMatched (UnpreparedValue 'MSSQL))))
ifMatchedFieldParser sourceName tableInfo = do
maybeObject <- ifMatchedObjectParser sourceName tableInfo
return $ withJust maybeObject $ P.fieldOptional $$(G.litName "if_matched") (Just "upsert condition")
return $ withJust maybeObject $ P.fieldOptional G._if_matched (Just "upsert condition")
-- | Parse a @tablename_if_matched@ object.
ifMatchedObjectParser ::
@ -70,13 +70,13 @@ ifMatchedObjectParser sourceName tableInfo = runMaybeT do
lift do
updateColumnsEnum <- updateColumnsPlaceholderParser tableInfo
tableGQLName <- getTableGQLName tableInfo
objectName <- P.mkTypename $ tableGQLName <> $$(G.litName "_if_matched")
objectName <- P.mkTypename $ tableGQLName <> G.__if_matched
let _imColumnPresets = partialSQLExpToUnpreparedValue <$> upiSet updatePerms
updateFilter = fmap partialSQLExpToUnpreparedValue <$> upiFilter updatePerms
objectDesc = G.Description $ "upsert condition type for table " <>> tableInfoName tableInfo
matchColumnsName = $$(G.litName "match_columns")
updateColumnsName = $$(G.litName "update_columns")
whereName = $$(G.litName "where")
matchColumnsName = G._match_columns
updateColumnsName = G._update_columns
whereName = G._where
whereExpParser <- boolExp sourceName tableInfo
pure $
P.object objectName (Just objectDesc) do
@ -109,7 +109,7 @@ tableInsertMatchColumnsEnum ::
tableInsertMatchColumnsEnum sourceName tableInfo = do
tableGQLName <- getTableGQLName @'MSSQL tableInfo
columns <- tableSelectColumns sourceName tableInfo
enumName <- P.mkTypename $ tableGQLName <> $$(G.litName "_insert_match_column")
enumName <- P.mkTypename $ tableGQLName <> G.__insert_match_column
let description =
Just $
G.Description $

View File

@ -15,6 +15,7 @@ import Hasura.Backends.MySQL.Types qualified as MySQL
import Hasura.Base.Error
import Hasura.GraphQL.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser hiding (field)
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Build qualified as GSB
@ -208,22 +209,22 @@ jsonPathArg' _columnType = pure Nothing
orderByOperators' :: NonEmpty (Definition P.EnumValueInfo, (BasicOrderType 'MySQL, NullsOrderType 'MySQL))
orderByOperators' =
NE.fromList
[ ( define $$(G.litName "asc") "in ascending order, nulls first",
[ ( define G._asc "in ascending order, nulls first",
(MySQL.Asc, MySQL.NullsFirst)
),
( define $$(G.litName "asc_nulls_first") "in ascending order, nulls first",
( define G._asc_nulls_first "in ascending order, nulls first",
(MySQL.Asc, MySQL.NullsFirst)
),
( define $$(G.litName "asc_nulls_last") "in ascending order, nulls last",
( define G._asc_nulls_last "in ascending order, nulls last",
(MySQL.Asc, MySQL.NullsLast)
),
( define $$(G.litName "desc") "in descending order, nulls last",
( define G._desc "in descending order, nulls last",
(MySQL.Desc, MySQL.NullsLast)
),
( define $$(G.litName "desc_nulls_first") "in descending order, nulls first",
( define G._desc_nulls_first "in descending order, nulls first",
(MySQL.Desc, MySQL.NullsFirst)
),
( define $$(G.litName "desc_nulls_last") "in descending order, nulls last",
( define G._desc_nulls_last "in descending order, nulls last",
(MySQL.Desc, MySQL.NullsLast)
)
]
@ -239,32 +240,35 @@ comparisonExps' ::
comparisonExps' = P.memoize 'comparisonExps $ \columnType -> do
-- see Note [Columns in comparison expression are never nullable]
typedParser <- columnParser columnType (G.Nullability False)
nullableTextParser <- columnParser (ColumnScalar @'MySQL MySQL.VarChar) (G.Nullability True)
_nullableTextParser <- columnParser (ColumnScalar @'MySQL MySQL.VarChar) (G.Nullability True)
textParser <- columnParser (ColumnScalar @'MySQL MySQL.VarChar) (G.Nullability False)
let name = P.getName typedParser <> $$(G.litName "_MySQL_comparison_exp")
let name = P.getName typedParser <> G.__MySQL_comparison_exp
desc =
G.Description $
"Boolean expression to compare columns of type "
<> P.getName typedParser
<<> ". All fields are combined with logical 'AND'."
textListParser = fmap openValueOrigin <$> P.list textParser
columnListParser = fmap openValueOrigin <$> P.list typedParser
_textListParser = fmap openValueOrigin <$> P.list textParser
_columnListParser = fmap openValueOrigin <$> P.list typedParser
pure $
P.object name (Just desc) $
catMaybes
<$> sequenceA
[ P.fieldOptional $$(G.litName "_is_null") Nothing (bool ANISNOTNULL ANISNULL <$> P.boolean),
P.fieldOptional $$(G.litName "_eq") Nothing (AEQ True . mkParameter <$> typedParser),
P.fieldOptional $$(G.litName "_neq") Nothing (ANE True . mkParameter <$> typedParser),
P.fieldOptional $$(G.litName "_gt") Nothing (AGT . mkParameter <$> typedParser),
P.fieldOptional $$(G.litName "_lt") Nothing (ALT . mkParameter <$> typedParser),
P.fieldOptional $$(G.litName "_gte") Nothing (AGTE . mkParameter <$> typedParser),
P.fieldOptional $$(G.litName "_lte") Nothing (ALTE . mkParameter <$> typedParser)
[ P.fieldOptional G.__is_null Nothing (bool ANISNOTNULL ANISNULL <$> P.boolean),
P.fieldOptional G.__eq Nothing (AEQ True . mkParameter <$> typedParser),
P.fieldOptional G.__neq Nothing (ANE True . mkParameter <$> typedParser),
P.fieldOptional G.__gt Nothing (AGT . mkParameter <$> typedParser),
P.fieldOptional G.__lt Nothing (ALT . mkParameter <$> typedParser),
P.fieldOptional G.__gte Nothing (AGTE . mkParameter <$> typedParser),
P.fieldOptional G.__lte Nothing (ALTE . mkParameter <$> typedParser)
]
{-
NOTE: Should this be removed?
offsetParser' :: MonadParse n => Parser 'Both n (SQLExpression 'MySQL)
offsetParser' =
MySQL.ValueExpression . MySQL.BigValue . fromIntegral <$> P.int
-}
mysqlCountTypeInput ::
MonadParse n =>
@ -272,7 +276,7 @@ mysqlCountTypeInput ::
InputFieldsParser n (IR.CountDistinct -> CountType 'MySQL)
mysqlCountTypeInput = \case
Just columnEnum -> do
columns <- P.fieldOptional $$(G.litName "columns") Nothing $ P.list columnEnum
columns <- P.fieldOptional G._columns Nothing $ P.list columnEnum
pure $ flip mkCountType columns
Nothing -> pure $ flip mkCountType Nothing
where

View File

@ -30,6 +30,7 @@ import Hasura.Backends.Postgres.Types.Update as PGIR
import Hasura.Base.Error
import Hasura.GraphQL.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser hiding (field)
import Hasura.GraphQL.Schema.Backend
( BackendSchema,
@ -185,7 +186,7 @@ buildTableRelayQueryFields ::
m [FieldParser n (QueryDB ('Postgres pgKind) (RemoteRelationshipField UnpreparedValue) (UnpreparedValue ('Postgres pgKind)))]
buildTableRelayQueryFields sourceName tableName tableInfo gqlName pkeyColumns = do
let fieldDesc = Just $ G.Description $ "fetch data from the table: " <>> tableName
fieldName <- mkRootFieldName $ gqlName <> $$(G.litName "_connection")
fieldName <- mkRootFieldName $ gqlName <> G.__connection
fmap afold $
optionalFieldParser QDBConnection $
selectTableConnection sourceName tableInfo fieldName fieldDesc pkeyColumns
@ -294,7 +295,7 @@ jsonPathArg columnType
P.fieldOptional fieldName description P.string `P.bindFields` fmap join . traverse toColExp
| otherwise = pure Nothing
where
fieldName = $$(G.litName "path")
fieldName = G._path
description = Just "JSON select path"
toColExp textValue = case parseJSONPath textValue of
Left err -> parseError $ T.pack $ "parse json path error: " ++ err
@ -307,22 +308,22 @@ orderByOperators ::
NonEmpty (Definition P.EnumValueInfo, (BasicOrderType ('Postgres pgKind), NullsOrderType ('Postgres pgKind)))
orderByOperators =
NE.fromList
[ ( define $$(G.litName "asc") "in ascending order, nulls last",
[ ( define G._asc "in ascending order, nulls last",
(PG.OTAsc, PG.NLast)
),
( define $$(G.litName "asc_nulls_first") "in ascending order, nulls first",
( define G._asc_nulls_first "in ascending order, nulls first",
(PG.OTAsc, PG.NFirst)
),
( define $$(G.litName "asc_nulls_last") "in ascending order, nulls last",
( define G._asc_nulls_last "in ascending order, nulls last",
(PG.OTAsc, PG.NLast)
),
( define $$(G.litName "desc") "in descending order, nulls first",
( define G._desc "in descending order, nulls first",
(PG.OTDesc, PG.NFirst)
),
( define $$(G.litName "desc_nulls_first") "in descending order, nulls first",
( define G._desc_nulls_first "in descending order, nulls first",
(PG.OTDesc, PG.NFirst)
),
( define $$(G.litName "desc_nulls_last") "in descending order, nulls last",
( define G._desc_nulls_last "in descending order, nulls last",
(PG.OTDesc, PG.NLast)
)
]
@ -357,7 +358,7 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
-- `ltxtquery` represents a full-text-search-like pattern for matching `ltree` values.
ltxtqueryParser <- columnParser (ColumnScalar PGLtxtquery) (G.Nullability False)
maybeCastParser <- castExp columnType
let name = P.getName typedParser <> $$(G.litName "_comparison_exp")
let name = P.getName typedParser <> G.__comparison_exp
desc =
G.Description $
"Boolean expression to compare columns of type "
@ -372,7 +373,7 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
sequenceA $
concat
[ flip (maybe []) maybeCastParser $ \castParser ->
[ P.fieldOptional $$(G.litName "_cast") Nothing (ACast <$> castParser)
[ P.fieldOptional G.__cast Nothing (ACast <$> castParser)
],
-- Common ops for all types
equalityOperators
@ -388,17 +389,17 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
guard (isScalarColumnWhere (== PGRaster) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_st_intersects_rast")
G.__st_intersects_rast
Nothing
(ABackendSpecific . ASTIntersectsRast . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_intersects_nband_geom")
G.__st_intersects_nband_geom
Nothing
(ABackendSpecific . ASTIntersectsNbandGeom <$> ingInputParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_intersects_geom_nband")
G.__st_intersects_geom_nband
Nothing
(ABackendSpecific . ASTIntersectsGeomNband <$> ignInputParser)
],
@ -406,52 +407,52 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
guard (isScalarColumnWhere isStringType columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_like")
G.__like
(Just "does the column match the given pattern")
(ALIKE . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_nlike")
G.__nlike
(Just "does the column NOT match the given pattern")
(ANLIKE . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_ilike")
G.__ilike
(Just "does the column match the given case-insensitive pattern")
(ABackendSpecific . AILIKE . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_nilike")
G.__nilike
(Just "does the column NOT match the given case-insensitive pattern")
(ABackendSpecific . ANILIKE . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_similar")
G.__similar
(Just "does the column match the given SQL regular expression")
(ABackendSpecific . ASIMILAR . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_nsimilar")
G.__nsimilar
(Just "does the column NOT match the given SQL regular expression")
(ABackendSpecific . ANSIMILAR . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_regex")
G.__regex
(Just "does the column match the given POSIX regular expression, case sensitive")
(ABackendSpecific . AREGEX . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_iregex")
G.__iregex
(Just "does the column match the given POSIX regular expression, case insensitive")
(ABackendSpecific . AIREGEX . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_nregex")
G.__nregex
(Just "does the column NOT match the given POSIX regular expression, case sensitive")
(ABackendSpecific . ANREGEX . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_niregex")
G.__niregex
(Just "does the column NOT match the given POSIX regular expression, case insensitive")
(ABackendSpecific . ANIREGEX . mkParameter <$> typedParser)
],
@ -459,27 +460,27 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
guard (isScalarColumnWhere (== PGJSONB) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_contains")
G.__contains
(Just "does the column contain the given json value at the top level")
(ABackendSpecific . AContains . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_contained_in")
G.__contained_in
(Just "is the column contained in the given json value")
(ABackendSpecific . AContainedIn . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_has_key")
G.__has_key
(Just "does the string exist as a top-level key in the column")
(ABackendSpecific . AHasKey . mkParameter <$> nullableTextParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_has_keys_any")
G.__has_keys_any
(Just "do any of these strings exist as top-level keys in the column")
(ABackendSpecific . AHasKeysAny . mkListLiteral (ColumnScalar PGText) <$> textListParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_has_keys_all")
G.__has_keys_all
(Just "do all of these strings exist as top-level keys in the column")
(ABackendSpecific . AHasKeysAll . mkListLiteral (ColumnScalar PGText) <$> textListParser)
],
@ -487,12 +488,12 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
guard (isScalarColumnWhere (== PGGeography) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_st_intersects")
G.__st_intersects
(Just "does the column spatially intersect the given geography value")
(ABackendSpecific . ASTIntersects . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_d_within")
G.__st_d_within
(Just "is the column within a given distance from the given geography value")
(ABackendSpecific . ASTDWithinGeog <$> geogInputParser)
],
@ -500,52 +501,52 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
guard (isScalarColumnWhere (== PGGeometry) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_st_contains")
G.__st_contains
(Just "does the column contain the given geometry value")
(ABackendSpecific . ASTContains . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_crosses")
G.__st_crosses
(Just "does the column cross the given geometry value")
(ABackendSpecific . ASTCrosses . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_equals")
G.__st_equals
(Just "is the column equal to given geometry value (directionality is ignored)")
(ABackendSpecific . ASTEquals . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_overlaps")
G.__st_overlaps
(Just "does the column 'spatially overlap' (intersect but not completely contain) the given geometry value")
(ABackendSpecific . ASTOverlaps . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_touches")
G.__st_touches
(Just "does the column have atleast one point in common with the given geometry value")
(ABackendSpecific . ASTTouches . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_within")
G.__st_within
(Just "is the column contained in the given geometry value")
(ABackendSpecific . ASTWithin . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_intersects")
G.__st_intersects
(Just "does the column spatially intersect the given geometry value")
(ABackendSpecific . ASTIntersects . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_3d_intersects")
G.__st_3d_intersects
(Just "does the column spatially intersect the given geometry value in 3D")
(ABackendSpecific . AST3DIntersects . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_d_within")
G.__st_d_within
(Just "is the column within a given distance from the given geometry value")
(ABackendSpecific . ASTDWithinGeom <$> geomInputParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_st_3d_d_within")
G.__st_3d_d_within
(Just "is the column within a given 3D distance from the given geometry value")
(ABackendSpecific . AST3DDWithinGeom <$> geomInputParser)
],
@ -553,37 +554,37 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
guard (isScalarColumnWhere (== PGLtree) columnType)
*> [ mkBoolOperator
collapseIfNull
$$(G.litName "_ancestor")
G.__ancestor
(Just "is the left argument an ancestor of right (or equal)?")
(ABackendSpecific . AAncestor . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_ancestor_any")
G.__ancestor_any
(Just "does array contain an ancestor of `ltree`?")
(ABackendSpecific . AAncestorAny . mkListLiteral columnType <$> columnListParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_descendant")
G.__descendant
(Just "is the left argument a descendant of right (or equal)?")
(ABackendSpecific . ADescendant . mkParameter <$> typedParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_descendant_any")
G.__descendant_any
(Just "does array contain a descendant of `ltree`?")
(ABackendSpecific . ADescendantAny . mkListLiteral columnType <$> columnListParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_matches")
G.__matches
(Just "does `ltree` match `lquery`?")
(ABackendSpecific . AMatches . mkParameter <$> lqueryParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_matches_any")
G.__matches_any
(Just "does `ltree` match any `lquery` in array?")
(ABackendSpecific . AMatchesAny . mkListLiteral (ColumnScalar PGLquery) <$> textListParser),
mkBoolOperator
collapseIfNull
$$(G.litName "_matches_fulltext")
G.__matches_fulltext
(Just "does `ltree` match `ltxtquery`?")
(ABackendSpecific . AMatchesFulltext . mkParameter <$> ltxtqueryParser)
]
@ -605,7 +606,7 @@ comparisonExps = P.memoize 'comparisonExps \columnType -> do
_ -> Nothing
forM maybeScalars $ \(sourceScalar, targetScalar) -> do
sourceName <- mkScalarTypeName sourceScalar <&> (<> $$(G.litName "_cast_exp"))
sourceName <- mkScalarTypeName sourceScalar <&> (<> G.__cast_exp)
targetName <- mkScalarTypeName targetScalar
targetOpExps <- comparisonExps $ ColumnScalar targetScalar
let field = P.fieldOptional targetName Nothing $ (targetScalar,) <$> targetOpExps
@ -626,10 +627,10 @@ geographyWithinDistanceInput = do
booleanParser <- columnParser (ColumnScalar PGBoolean) (G.Nullability True)
floatParser <- columnParser (ColumnScalar PGFloat) (G.Nullability False)
pure $
P.object $$(G.litName "st_d_within_geography_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 True) booleanParser)
P.object G._st_d_within_geography_input Nothing $
DWithinGeogOp <$> (mkParameter <$> P.field G._distance Nothing floatParser)
<*> (mkParameter <$> P.field G._from Nothing geographyParser)
<*> (mkParameter <$> P.fieldWithDefault G._use_spheroid Nothing (G.VBoolean True) booleanParser)
geometryWithinDistanceInput ::
forall pgKind m n r.
@ -639,9 +640,9 @@ geometryWithinDistanceInput = do
geometryParser <- columnParser (ColumnScalar PGGeometry) (G.Nullability False)
floatParser <- columnParser (ColumnScalar PGFloat) (G.Nullability False)
pure $
P.object $$(G.litName "st_d_within_input") Nothing $
DWithinGeomOp <$> (mkParameter <$> P.field $$(G.litName "distance") Nothing floatParser)
<*> (mkParameter <$> P.field $$(G.litName "from") Nothing geometryParser)
P.object G._st_d_within_input Nothing $
DWithinGeomOp <$> (mkParameter <$> P.field G._distance Nothing floatParser)
<*> (mkParameter <$> P.field G._from Nothing geometryParser)
intersectsNbandGeomInput ::
forall pgKind m n r.
@ -651,9 +652,9 @@ intersectsNbandGeomInput = do
geometryParser <- columnParser (ColumnScalar PGGeometry) (G.Nullability False)
integerParser <- columnParser (ColumnScalar PGInteger) (G.Nullability False)
pure $
P.object $$(G.litName "st_intersects_nband_geom_input") Nothing $
STIntersectsNbandGeommin <$> (mkParameter <$> P.field $$(G.litName "nband") Nothing integerParser)
<*> (mkParameter <$> P.field $$(G.litName "geommin") Nothing geometryParser)
P.object G._st_intersects_nband_geom_input Nothing $
STIntersectsNbandGeommin <$> (mkParameter <$> P.field G._nband Nothing integerParser)
<*> (mkParameter <$> P.field G._geommin Nothing geometryParser)
intersectsGeomNbandInput ::
forall pgKind m n r.
@ -663,10 +664,10 @@ intersectsGeomNbandInput = do
geometryParser <- columnParser (ColumnScalar PGGeometry) (G.Nullability False)
integerParser <- columnParser (ColumnScalar PGInteger) (G.Nullability False)
pure $
P.object $$(G.litName "st_intersects_geom_nband_input") Nothing $
P.object G._st_intersects_geom_nband_input Nothing $
STIntersectsGeomminNband
<$> (mkParameter <$> P.field $$(G.litName "geommin") Nothing geometryParser)
<*> (fmap mkParameter <$> P.fieldOptional $$(G.litName "nband") Nothing integerParser)
<$> (mkParameter <$> P.field G._geommin Nothing geometryParser)
<*> (fmap mkParameter <$> P.fieldOptional G._nband Nothing integerParser)
countTypeInput ::
MonadParse n =>
@ -674,7 +675,7 @@ countTypeInput ::
InputFieldsParser n (IR.CountDistinct -> CountType ('Postgres pgKind))
countTypeInput = \case
Just columnEnum -> do
columns <- P.fieldOptional $$(G.litName "columns") Nothing (P.list columnEnum)
columns <- P.fieldOptional G._columns Nothing (P.list columnEnum)
pure $ flip mkCountType columns
Nothing -> pure $ flip mkCountType Nothing
where
@ -700,7 +701,7 @@ prependOp = SU.UpdateOperator {..}
where
updateOperatorApplicableColumn = isScalarColumnWhere (== PGJSONB) . ciType
updateOperatorParser tableGQLName tableName columns = do
updateOperatorParser tableGQLName _tableName columns = do
let typedParser columnInfo =
fmap P.mkParameter
<$> BS.columnParser
@ -711,7 +712,7 @@ prependOp = SU.UpdateOperator {..}
SU.updateOperator
tableGQLName
$$(G.litName "_prepend")
G.__prepend
typedParser
columns
desc
@ -734,7 +735,7 @@ appendOp = SU.UpdateOperator {..}
where
updateOperatorApplicableColumn = isScalarColumnWhere (== PGJSONB) . ciType
updateOperatorParser tableGQLName tableName columns = do
updateOperatorParser tableGQLName _tableName columns = do
let typedParser columnInfo =
fmap P.mkParameter
<$> BS.columnParser
@ -744,7 +745,7 @@ appendOp = SU.UpdateOperator {..}
desc = "append existing jsonb value of filtered columns with new jsonb value"
SU.updateOperator
tableGQLName
$$(G.litName "_append")
G.__append
typedParser
columns
desc
@ -768,13 +769,13 @@ deleteKeyOp = SU.UpdateOperator {..}
where
updateOperatorApplicableColumn = isScalarColumnWhere (== PGJSONB) . ciType
updateOperatorParser tableGQLName tableName columns = do
updateOperatorParser tableGQLName _tableName columns = do
let nullableTextParser _ = fmap P.mkParameter <$> columnParser (ColumnScalar PGText) (G.Nullability True)
desc = "delete key/value pair or string element. key/value pairs are matched based on their key value"
SU.updateOperator
tableGQLName
$$(G.litName "_delete_key")
G.__delete_key
nullableTextParser
columns
desc
@ -798,7 +799,7 @@ deleteElemOp = SU.UpdateOperator {..}
where
updateOperatorApplicableColumn = isScalarColumnWhere (== PGJSONB) . ciType
updateOperatorParser tableGQLName tableName columns = do
updateOperatorParser tableGQLName _tableName columns = do
let nonNullableIntParser _ = fmap P.mkParameter <$> columnParser (ColumnScalar PGInteger) (G.Nullability False)
desc =
"delete the array element with specified index (negative integers count from the end). "
@ -806,7 +807,7 @@ deleteElemOp = SU.UpdateOperator {..}
SU.updateOperator
tableGQLName
$$(G.litName "_delete_elem")
G.__delete_elem
nonNullableIntParser
columns
desc
@ -830,13 +831,13 @@ deleteAtPathOp = SU.UpdateOperator {..}
where
updateOperatorApplicableColumn = isScalarColumnWhere (== PGJSONB) . ciType
updateOperatorParser tableGQLName tableName columns = do
updateOperatorParser tableGQLName _tableName columns = do
let nonNullableTextListParser _ = P.list . fmap P.mkParameter <$> columnParser (ColumnScalar PGText) (G.Nullability False)
desc = "delete the field or element with specified path (for JSON arrays, negative integers count from the end)"
SU.updateOperator
tableGQLName
$$(G.litName "_delete_at_path")
G.__delete_at_path
nonNullableTextListParser
columns
desc

View File

@ -1,4 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
@ -30,6 +29,7 @@ import Hasura.GraphQL.Namespace
RootFieldMap,
mkUnNamespacedRootFieldAlias,
)
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Transport.Backend
import Hasura.GraphQL.Transport.HTTP.Protocol
import Hasura.Logging qualified as L
@ -39,7 +39,6 @@ import Hasura.Server.Types (RequestId)
import Hasura.Session
import Hasura.Tracing
import Hasura.Tracing qualified as Tracing
import Language.GraphQL.Draft.Syntax qualified as G
instance
( Backend ('Postgres pgKind),
@ -173,7 +172,7 @@ runPGMutationTransaction ::
RootFieldMap (DBStepInfo ('Postgres pgKind)) ->
m (DiffTime, RootFieldMap EncJSON)
runPGMutationTransaction reqId query userInfo logger sourceConfig mutations = do
logQueryLog logger $ mkQueryLog query (mkUnNamespacedRootFieldAlias $$(G.litName "transaction")) Nothing reqId
logQueryLog logger $ mkQueryLog query (mkUnNamespacedRootFieldAlias G._transaction) Nothing reqId
ctx <- Tracing.currentContext
withElapsedTime $ do
Tracing.interpTraceT

View File

@ -56,6 +56,7 @@ import Data.Text qualified as T
import Data.Text.Extended
import Database.PG.Query qualified as Q
import Hasura.Base.Error
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.Types.Common
@ -594,7 +595,7 @@ mkScalarTypeName (PGCompositeScalar compositeScalarType) =
-- both these types (scalar and object type with same name).
-- To avoid this, we suffix the table name with `_scalar`
-- and create a new scalar type
(<> $$(G.litName "_scalar")) <$> G.mkName compositeScalarType
(<> G.__scalar) <$> G.mkName compositeScalarType
`onNothing` throw400
ValidationFailed
( "cannot use SQL type " <> compositeScalarType <<> " in the GraphQL schema because its name is not a "

View File

@ -21,6 +21,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
@ -53,7 +54,7 @@ onConflictFieldParser sourceName tableInfo = do
let maybeConstraints = tciUniqueOrPrimaryKeyConstraints . _tiCoreInfo $ tableInfo
let maybeConflictObject = conflictObjectParser sourceName tableInfo <$> maybeConstraints <*> updatePerms
case maybeConflictObject of
Just conflictObject -> conflictObject <&> P.fieldOptional $$(G.litName "on_conflict") (Just "upsert condition")
Just conflictObject -> conflictObject <&> P.fieldOptional G._on_conflict (Just "upsert condition")
Nothing -> return $ pure Nothing
-- | Create a parser for the @_on_conflict@ object of the given table.
@ -70,14 +71,14 @@ conflictObjectParser sourceName tableInfo constraints updatePerms = do
constraintParser <- conflictConstraint constraints sourceName tableInfo
whereExpParser <- boolExp sourceName tableInfo
tableGQLName <- getTableGQLName tableInfo
objectName <- P.mkTypename $ tableGQLName <> $$(G.litName "_on_conflict")
objectName <- P.mkTypename $ tableGQLName <> G.__on_conflict
let presetColumns = partialSQLExpToUnpreparedValue <$> upiSet updatePerms
updateFilter = fmap partialSQLExpToUnpreparedValue <$> upiFilter updatePerms
objectDesc = G.Description $ "on_conflict condition type for table " <>> tableName
constraintName = $$(G.litName "constraint")
columnsName = $$(G.litName "update_columns")
whereExpName = $$(G.litName "where")
constraintName = G._constraint
columnsName = G._update_columns
whereExpName = G._where
pure $
P.object objectName (Just objectDesc) $ do
@ -119,7 +120,7 @@ conflictConstraint constraints sourceName tableInfo =
( P.Definition name (Just "unique or primary key constraint") P.EnumValueInfo,
_cName constraint
)
enumName <- P.mkTypename $ tableGQLName <> $$(G.litName "_constraint")
enumName <- P.mkTypename $ tableGQLName <> G.__constraint
let enumDesc = G.Description $ "unique or primary key constraints on table " <>> tableName
pure $ P.enum enumName (Just enumDesc) constraintEnumValues
where

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
-- | Tools to analyze the structure of a GraphQL request.
module Hasura.GraphQL.Analyse
( -- * Query structure
@ -18,6 +16,7 @@ import Control.Monad.Writer (Writer, runWriter)
import Data.HashMap.Strict qualified as Map
import Data.Sequence ((|>))
import Data.Text qualified as T
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Prelude
import Language.GraphQL.Draft.Syntax qualified as G
@ -339,24 +338,24 @@ render (AnalysisError path diagnosis) =
-- Special type names
queryRootName :: G.Name
queryRootName = $$(G.litName "query_root")
queryRootName = G._query_root
mutationRootName :: G.Name
mutationRootName = $$(G.litName "mutation_root")
mutationRootName = G._mutation_root
subscriptionRootName :: G.Name
subscriptionRootName = $$(G.litName "subscription_root")
subscriptionRootName = G._subscription_root
-- Reserved fields
typenameField :: G.FieldDefinition G.InputValueDefinition
typenameField = mkReservedField $$(G.litName "__typename") $$(G.litName "String")
typenameField = mkReservedField G.___typename G._String
schemaField :: G.FieldDefinition G.InputValueDefinition
schemaField = mkReservedField $$(G.litName "__schema") $$(G.litName "__Schema")
schemaField = mkReservedField G.___schema G.___Schema
typeField :: G.FieldDefinition G.InputValueDefinition
typeField = mkReservedField $$(G.litName "__type") $$(G.litName "__Type")
typeField = mkReservedField G.___type G.___Type
mkReservedField :: G.Name -> G.Name -> G.FieldDefinition G.InputValueDefinition
mkReservedField fieldName typeName =

View File

@ -1,5 +1,4 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Execute.Action
( fetchActionLogResponses,
@ -48,6 +47,7 @@ import Hasura.EncJSON
import Hasura.Eventing.Common
import Hasura.GraphQL.Execute.Action.Types as Types
import Hasura.GraphQL.Parser
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Transport.HTTP.Protocol as GH
import Hasura.HTTP
import Hasura.Logging qualified as L
@ -251,7 +251,7 @@ resolveAsyncActionQuery userInfo annAction =
asyncFields <&> second \case
AsyncTypename t -> RS.AFExpression t
AsyncOutput annFields ->
RS.AFComputedField () (ComputedFieldName $$(nonEmptyText "__action_computed_field")) $
RS.AFComputedField () (ComputedFieldName [nonEmptyTextQQ|__action_computed_field|]) $
RS.CFSTable jsonAggSelect $
processOutputSelectionSet RS.AEActionResponsePayload outputType definitionList annFields stringifyNumerics
AsyncId -> mkAnnFldFromPGCol idColumn
@ -300,7 +300,7 @@ resolveAsyncActionQuery userInfo annAction =
let actionIdColumnInfo =
ColumnInfo
{ ciColumn = unsafePGCol "id",
ciName = $$(G.litName "id"),
ciName = G._id,
ciPosition = 0,
ciType = ColumnScalar PGUUID,
ciIsNullable = False,

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Execute.RemoteJoin.Collect
( getRemoteJoinsQueryDB,
getRemoteJoinsMutationDB,
@ -18,6 +16,7 @@ import Data.HashMap.Strict.NonEmpty qualified as NEMap
import Data.Text qualified as T
import Hasura.GraphQL.Execute.RemoteJoin.Types
import Hasura.GraphQL.Parser.Column (UnpreparedValue (..))
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.Types
@ -517,7 +516,7 @@ transformObjectSelectionSet typename selectionSet = do
( mkPlaceholderField alias,
Just $ createRemoteJoin joinColumnAliases _srrsRelationship
)
let internalTypeAlias = $$(G.litName "__hasura_internal_typename")
let internalTypeAlias = G.___hasura_internal_typename
remoteJoins = OMap.mapMaybe snd annotatedFields
additionalFields =
if
@ -529,7 +528,7 @@ transformObjectSelectionSet typename selectionSet = do
OMap.singleton internalTypeAlias $
mkGraphQLField
(Just internalTypeAlias)
$$(G.litName "__typename")
G.___typename
mempty
mempty
SelectionSetNone
@ -551,7 +550,7 @@ transformObjectSelectionSet typename selectionSet = do
allAliases = map (nameToField . fst) $ OMap.toList selectionSet
mkPlaceholderField alias =
mkGraphQLField (Just alias) $$(G.litName "__typename") mempty mempty SelectionSetNone
mkGraphQLField (Just alias) G.___typename mempty mempty SelectionSetNone
-- A map of graphql scalar fields (without any arguments) to their aliases
-- in the selection set. We do not yet support lhs join fields which take

View File

@ -0,0 +1,729 @@
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
-- | QuasiQuoted GraphQL constants used througout the codebase. By
-- moving all the Quasiquotes here we can eliminate extraneous
-- rebuilds of larger modules.
--
-- See: https://www.parsonsmatt.org/2021/07/12/template_haskell_performance_tips.html#recompilation-avoidance
module Hasura.GraphQL.Parser.Constants where
import Language.GraphQL.Draft.Syntax as G
import Language.GraphQL.Draft.Syntax.QQ as G
_A :: G.Name
_A = [G.name|A|]
_Boolean :: G.Name
_Boolean = [G.name|Boolean|]
_Bool :: G.Name
_Bool = [G.name|Bool|]
_Bytes :: G.Name
_Bytes = [G.name|Bytes|]
_B :: G.Name
_B = [G.name|B|]
_Connection :: G.Name
_Connection = [G.name|Connection|]
_Datetime :: G.Name
_Datetime = [G.name|Datetime|]
_Date :: G.Name
_Date = [G.name|Date|]
_Double :: G.Name
_Double = [G.name|Double|]
_ENUM :: G.Name
_ENUM = [G.name|ENUM|]
_Edge :: G.Name
_Edge = [G.name|Edge|]
_Float :: G.Name
_Float = [G.name|Float|]
_Geography :: G.Name
_Geography = [G.name|Geography|]
_ID :: G.Name
_ID = [G.name|ID|]
_INPUT_OBJECT :: G.Name
_INPUT_OBJECT = [G.name|INPUT_OBJECT|]
_INTERFACE :: G.Name
_INTERFACE = [G.name|INTERFACE|]
_Int :: G.Name
_Int = [G.name|Int|]
_LIST :: G.Name
_LIST = [G.name|LIST|]
_Mutation :: G.Name
_Mutation = [G.name|Mutation|]
_NON_NULL :: G.Name
_NON_NULL = [G.name|NON_NULL|]
_Node :: G.Name
_Node = [G.name|Node|]
_Number :: G.Name
_Number = [G.name|Number|]
_OBJECT :: G.Name
_OBJECT = [G.name|OBJECT|]
_PageInfo :: G.Name
_PageInfo = [G.name|PageInfo|]
_PresetValue :: G.Name
_PresetValue = [G.name|PresetValue|]
_Query :: G.Name
_Query = [G.name|Query|]
_SCALAR :: G.Name
_SCALAR = [G.name|SCALAR|]
_String :: G.Name
_String = [G.name|String|]
_Subscription :: G.Name
_Subscription = [G.name|Subscription|]
_Timestamp :: G.Name
_Timestamp = [G.name|Timestamp|]
_Time :: G.Name
_Time = [G.name|Time|]
_UNION :: G.Name
_UNION = [G.name|UNION|]
_UUID :: G.Name
_UUID = [G.name|UUID|]
__BigQuery_comparison_exp :: G.Name
__BigQuery_comparison_exp = [G.name|_BigQuery_comparison_exp|]
__one :: G.Name
__one = [G.name|_one|]
__MSSQL_comparison_exp :: G.Name
__MSSQL_comparison_exp = [G.name|_MSSQL_comparison_exp|]
__MySQL_comparison_exp :: G.Name
__MySQL_comparison_exp = [G.name|_MySQL_comparison_exp|]
__PLACEHOLDER :: G.Name
__PLACEHOLDER = [G.name|_PLACEHOLDER|]
___Directive :: G.Name
___Directive = [G.name|__Directive|]
___EnumValue :: G.Name
___EnumValue = [G.name|__EnumValue|]
__fields :: G.Name
__fields = [G.name|_fields|]
___Field :: G.Name
___Field = [G.name|__Field|]
___InputValue :: G.Name
___InputValue = [G.name|__InputValue|]
___Schema :: G.Name
___Schema = [G.name|__Schema|]
___TypeKind :: G.Name
___TypeKind = [G.name|__TypeKind|]
___Type :: G.Name
___Type = [G.name|__Type|]
___hasura_internal_typename :: G.Name
___hasura_internal_typename = [G.name|__hasura_internal_typename|]
___schema :: G.Name
___schema = [G.name|__schema|]
___typename :: G.Name
___typename = [G.name|__typename|]
___type :: G.Name
___type = [G.name|__type|]
__aggregate_fields :: G.Name
__aggregate_fields = [G.name|_aggregate_fields|]
__aggregate_order_by :: G.Name
__aggregate_order_by = [G.name|_aggregate_order_by|]
__aggregate :: G.Name
__aggregate = [G.name|_aggregate|]
__ancestor_any :: G.Name
__ancestor_any = [G.name|_ancestor_any|]
__ancestor :: G.Name
__ancestor = [G.name|_ancestor|]
__and :: G.Name
__and = [G.name|_and|]
__append :: G.Name
__append = [G.name|_append|]
__args :: G.Name
__args = [G.name|_args|]
__arr_rel_insert_input :: G.Name
__arr_rel_insert_input = [G.name|_arr_rel_insert_input|]
__bool_exp :: G.Name
__bool_exp = [G.name|_bool_exp|]
__by_pk :: G.Name
__by_pk = [G.name|_by_pk|]
__cast_exp :: G.Name
__cast_exp = [G.name|_cast_exp|]
__cast :: G.Name
__cast = [G.name|_cast|]
__comparison_exp :: G.Name
__comparison_exp = [G.name|_comparison_exp|]
__connection :: G.Name
__connection = [G.name|_connection|]
__constraint :: G.Name
__constraint = [G.name|_constraint|]
__contained_in :: G.Name
__contained_in = [G.name|_contained_in|]
__contains :: G.Name
__contains = [G.name|_contains|]
__delete_at_path :: G.Name
__delete_at_path = [G.name|_delete_at_path|]
__delete_elem :: G.Name
__delete_elem = [G.name|_delete_elem|]
__delete_key :: G.Name
__delete_key = [G.name|_delete_key|]
__descendant_any :: G.Name
__descendant_any = [G.name|_descendant_any|]
__descendant :: G.Name
__descendant = [G.name|_descendant|]
__enum :: G.Name
__enum = [G.name|_enum|]
__eq :: G.Name
__eq = [G.name|_eq|]
__gte :: G.Name
__gte = [G.name|_gte|]
__gt :: G.Name
__gt = [G.name|_gt|]
__has_keys_all :: G.Name
__has_keys_all = [G.name|_has_keys_all|]
__has_keys_any :: G.Name
__has_keys_any = [G.name|_has_keys_any|]
__has_key :: G.Name
__has_key = [G.name|_has_key|]
__if_matched :: G.Name
__if_matched = [G.name|_if_matched|]
__ilike :: G.Name
__ilike = [G.name|_ilike|]
__insert_input :: G.Name
__insert_input = [G.name|_insert_input|]
__insert_match_column :: G.Name
__insert_match_column = [G.name|_insert_match_column|]
__in :: G.Name
__in = [G.name|_in|]
__iregex :: G.Name
__iregex = [G.name|_iregex|]
__is_null :: G.Name
__is_null = [G.name|_is_null|]
__like :: G.Name
__like = [G.name|_like|]
__lte :: G.Name
__lte = [G.name|_lte|]
__lt :: G.Name
__lt = [G.name|_lt|]
__matches_any :: G.Name
__matches_any = [G.name|_matches_any|]
__matches_fulltext :: G.Name
__matches_fulltext = [G.name|_matches_fulltext|]
__matches :: G.Name
__matches = [G.name|_matches|]
__multiple_top_level_fields :: G.Name
__multiple_top_level_fields = [G.name|_multiple_top_level_fields|]
__mutation_backend :: G.Name
__mutation_backend = [G.name|_mutation_backend|]
__mutation_frontend :: G.Name
__mutation_frontend = [G.name|_mutation_frontend|]
__mutation_response :: G.Name
__mutation_response = [G.name|_mutation_response|]
__neq :: G.Name
__neq = [G.name|_neq|]
__nilike :: G.Name
__nilike = [G.name|_nilike|]
__nin :: G.Name
__nin = [G.name|_nin|]
__niregex :: G.Name
__niregex = [G.name|_niregex|]
__nlike :: G.Name
__nlike = [G.name|_nlike|]
__not :: G.Name
__not = [G.name|_not|]
__nregex :: G.Name
__nregex = [G.name|_nregex|]
__nsimilar :: G.Name
__nsimilar = [G.name|_nsimilar|]
__obj_rel_insert_input :: G.Name
__obj_rel_insert_input = [G.name|_obj_rel_insert_input|]
__on_conflict :: G.Name
__on_conflict = [G.name|_on_conflict|]
__order_by :: G.Name
__order_by = [G.name|_order_by|]
__or :: G.Name
__or = [G.name|_or|]
__prepend :: G.Name
__prepend = [G.name|_prepend|]
__query :: G.Name
__query = [G.name|_query|]
__regex :: G.Name
__regex = [G.name|_regex|]
__remote_rel_ :: G.Name
__remote_rel_ = [G.name|_remote_rel_|]
__scalar :: G.Name
__scalar = [G.name|_scalar|]
__select_column :: G.Name
__select_column = [G.name|_select_column|]
__similar :: G.Name
__similar = [G.name|_similar|]
__st_3d_d_within :: G.Name
__st_3d_d_within = [G.name|_st_3d_d_within|]
__st_3d_intersects :: G.Name
__st_3d_intersects = [G.name|_st_3d_intersects|]
__st_contains :: G.Name
__st_contains = [G.name|_st_contains|]
__st_crosses :: G.Name
__st_crosses = [G.name|_st_crosses|]
__st_d_within :: G.Name
__st_d_within = [G.name|_st_d_within|]
__st_equals :: G.Name
__st_equals = [G.name|_st_equals|]
__st_intersects_geom_nband :: G.Name
__st_intersects_geom_nband = [G.name|_st_intersects_geom_nband|]
__st_intersects_nband_geom :: G.Name
__st_intersects_nband_geom = [G.name|_st_intersects_nband_geom|]
__st_intersects_rast :: G.Name
__st_intersects_rast = [G.name|_st_intersects_rast|]
__st_intersects :: G.Name
__st_intersects = [G.name|_st_intersects|]
__st_overlaps :: G.Name
__st_overlaps = [G.name|_st_overlaps|]
__st_touches :: G.Name
__st_touches = [G.name|_st_touches|]
__st_within :: G.Name
__st_within = [G.name|_st_within|]
__update_column :: G.Name
__update_column = [G.name|_update_column|]
__ :: G.Name
__ = [G.name|_|]
_affected_rows :: G.Name
_affected_rows = [G.name|affected_rows|]
_after :: G.Name
_after = [G.name|after|]
_aggregate :: G.Name
_aggregate = [G.name|aggregate|]
_args :: G.Name
_args = [G.name|args|]
_asc_nulls_first :: G.Name
_asc_nulls_first = [G.name|asc_nulls_first|]
_asc_nulls_last :: G.Name
_asc_nulls_last = [G.name|asc_nulls_last|]
_asc :: G.Name
_asc = [G.name|asc|]
_avg :: G.Name
_avg = [G.name|avg|]
_a :: G.Name
_a = [G.name|a|]
_before :: G.Name
_before = [G.name|before|]
_boolExp :: G.Name
_boolExp = [G.name|boolExp|]
_b :: G.Name
_b = [G.name|b|]
_cached :: G.Name
_cached = [G.name|cached|]
_columns :: G.Name
_columns = [G.name|columns|]
_column :: G.Name
_column = [G.name|column|]
_constraint :: G.Name
_constraint = [G.name|constraint|]
_count :: G.Name
_count = [G.name|count|]
_created_at :: G.Name
_created_at = [G.name|created_at|]
_cursor :: G.Name
_cursor = [G.name|cursor|]
_data :: G.Name
_data = [G.name|data|]
_defaultValue :: G.Name
_defaultValue = [G.name|defaultValue|]
_delete_ :: G.Name
_delete_ = [G.name|delete_|]
_deprecationReason :: G.Name
_deprecationReason = [G.name|deprecationReason|]
_desc_nulls_first :: G.Name
_desc_nulls_first = [G.name|desc_nulls_first|]
_desc_nulls_last :: G.Name
_desc_nulls_last = [G.name|desc_nulls_last|]
_description :: G.Name
_description = [G.name|description|]
_desc :: G.Name
_desc = [G.name|desc|]
_directives :: G.Name
_directives = [G.name|directives|]
_distance :: G.Name
_distance = [G.name|distance|]
_distinct_on :: G.Name
_distinct_on = [G.name|distinct_on|]
_distinct :: G.Name
_distinct = [G.name|distinct|]
_edges :: G.Name
_edges = [G.name|edges|]
_endCursor :: G.Name
_endCursor = [G.name|endCursor|]
_enumValues :: G.Name
_enumValues = [G.name|enumValues|]
_errors :: G.Name
_errors = [G.name|errors|]
_fields :: G.Name
_fields = [G.name|fields|]
_first :: G.Name
_first = [G.name|first|]
_float8 :: G.Name
_float8 = [G.name|float8|]
_from :: G.Name
_from = [G.name|from|]
_geommin :: G.Name
_geommin = [G.name|geommin|]
_hasNextPage :: G.Name
_hasNextPage = [G.name|hasNextPage|]
_hasPreviousPage :: G.Name
_hasPreviousPage = [G.name|hasPreviousPage|]
_id :: G.Name
_id = [G.name|id|]
_if_matched :: G.Name
_if_matched = [G.name|if_matched|]
_if :: G.Name
_if = [G.name|if|]
_includeDeprecated :: G.Name
_includeDeprecated = [G.name|includeDeprecated|]
_include :: G.Name
_include = [G.name|include|]
_inputFields :: G.Name
_inputFields = [G.name|inputFields|]
_insert_ :: G.Name
_insert_ = [G.name|insert_|]
_interfaces :: G.Name
_interfaces = [G.name|interfaces|]
_isDeprecated :: G.Name
_isDeprecated = [G.name|isDeprecated|]
_isRepeatable :: G.Name
_isRepeatable = [G.name|isRepeatable|]
_kind :: G.Name
_kind = [G.name|kind|]
_last :: G.Name
_last = [G.name|last|]
_limit :: G.Name
_limit = [G.name|limit|]
_locations :: G.Name
_locations = [G.name|locations|]
_match_columns :: G.Name
_match_columns = [G.name|match_columns|]
_mutationType :: G.Name
_mutationType = [G.name|mutationType|]
_mutation_root :: G.Name
_mutation_root = [G.name|mutation_root|]
_name :: G.Name
_name = [G.name|name|]
_nband :: G.Name
_nband = [G.name|nband|]
_no_queries_available :: G.Name
_no_queries_available = [G.name|no_queries_available|]
_nodes :: G.Name
_nodes = [G.name|nodes|]
_node :: G.Name
_node = [G.name|node|]
_numeric :: G.Name
_numeric = [G.name|numeric|]
_objects :: G.Name
_objects = [G.name|objects|]
_object :: G.Name
_object = [G.name|object|]
_ofType :: G.Name
_ofType = [G.name|ofType|]
_offset :: G.Name
_offset = [G.name|offset|]
_on_conflict :: G.Name
_on_conflict = [G.name|on_conflict|]
_order_by :: G.Name
_order_by = [G.name|order_by|]
_output :: G.Name
_output = [G.name|output|]
_pageInfo :: G.Name
_pageInfo = [G.name|pageInfo|]
_path :: G.Name
_path = [G.name|path|]
_possibleTypes :: G.Name
_possibleTypes = [G.name|possibleTypes|]
_preset :: G.Name
_preset = [G.name|preset|]
_queryType :: G.Name
_queryType = [G.name|queryType|]
_query_root :: G.Name
_query_root = [G.name|query_root|]
_refresh :: G.Name
_refresh = [G.name|refresh|]
_returning :: G.Name
_returning = [G.name|returning|]
_skip :: G.Name
_skip = [G.name|skip|]
_st_d_within_geography_input :: G.Name
_st_d_within_geography_input = [G.name|st_d_within_geography_input|]
_st_d_within_input :: G.Name
_st_d_within_input = [G.name|st_d_within_input|]
_st_dwithin_input :: G.Name
_st_dwithin_input = [G.name|st_dwithin_input|]
_st_intersects_geom_nband_input :: G.Name
_st_intersects_geom_nband_input = [G.name|st_intersects_geom_nband_input|]
_st_intersects_nband_geom_input :: G.Name
_st_intersects_nband_geom_input = [G.name|st_intersects_nband_geom_input|]
_startCursor :: G.Name
_startCursor = [G.name|startCursor|]
_static :: G.Name
_static = [G.name|static|]
_stddev_pop :: G.Name
_stddev_pop = [G.name|stddev_pop|]
_stddev_samp :: G.Name
_stddev_samp = [G.name|stddev_samp|]
_stddev :: G.Name
_stddev = [G.name|stddev|]
_subscriptionType :: G.Name
_subscriptionType = [G.name|subscriptionType|]
_subscription_root :: G.Name
_subscription_root = [G.name|subscription_root|]
_sum :: G.Name
_sum = [G.name|sum|]
_transaction :: G.Name
_transaction = [G.name|transaction|]
_ttl :: G.Name
_ttl = [G.name|ttl|]
_types :: G.Name
_types = [G.name|types|]
_type :: G.Name
_type = [G.name|type|]
_update_columns :: G.Name
_update_columns = [G.name|update_columns|]
_update_ :: G.Name
_update_ = [G.name|update_|]
_use_spheroid :: G.Name
_use_spheroid = [G.name|use_spheroid|]
_uuid :: G.Name
_uuid = [G.name|uuid|]
_value :: G.Name
_value = [G.name|value|]
_var_pop :: G.Name
_var_pop = [G.name|var_pop|]
_var_samp :: G.Name
_var_samp = [G.name|var_samp|]
_variance :: G.Name
_variance = [G.name|variance|]
_where :: G.Name
_where = [G.name|where|]
_x :: G.Name
_x = [G.name|x|]

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
-- | Definition of all supported GraphQL directives.
module Hasura.GraphQL.Parser.Directives
( -- list of directives, for the schema
@ -37,6 +35,7 @@ import Data.Parser.JSONPath
import Data.Text.Extended
import Data.Typeable (eqT)
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Input
import Hasura.GraphQL.Parser.Internal.Scalars
import Hasura.GraphQL.Parser.Schema
@ -156,7 +155,7 @@ withDirective dmap key callback = callback $ runIdentity <$> DM.lookup key dmap
cachedDirective :: forall m. MonadParse m => Directive m
cachedDirective =
mkDirective
$$(G.litName "cached")
G._cached
(Just "whether this query should be cached (Hasura Cloud only)")
True
[G.DLExecutable G.EDLQUERY]
@ -164,37 +163,37 @@ cachedDirective =
where
-- Optionally set the cache entry time to live
ttlArgument :: InputFieldsParser m Int
ttlArgument = fieldWithDefault $$(G.litName "ttl") (Just "measured in seconds") (G.VInt 60) $ fromIntegral <$> int
ttlArgument = fieldWithDefault G._ttl (Just "measured in seconds") (G.VInt 60) $ fromIntegral <$> int
-- Optionally Force a refresh of the cache entry
forcedArgument :: InputFieldsParser m Bool
forcedArgument = fieldWithDefault $$(G.litName "refresh") (Just "refresh the cache entry") (G.VBoolean False) boolean
forcedArgument = fieldWithDefault G._refresh (Just "refresh the cache entry") (G.VBoolean False) boolean
data CachedDirective = CachedDirective {cdTtl :: Int, cdRefresh :: Bool}
cached :: DirectiveKey CachedDirective
cached = DirectiveKey $$(G.litName "cached")
cached = DirectiveKey G._cached
-- Subscription tests custom directive.
multipleRootFieldsDirective :: forall m. MonadParse m => Directive m
multipleRootFieldsDirective =
mkDirective
$$(G.litName "_multiple_top_level_fields")
G.__multiple_top_level_fields
(Just "INTERNAL TESTING TOOL DO NOT USE")
False -- not advertised in the schema
[G.DLExecutable G.EDLSUBSCRIPTION]
(pure ())
multipleRootFields :: DirectiveKey ()
multipleRootFields = DirectiveKey $$(G.litName "_multiple_top_level_fields")
multipleRootFields = DirectiveKey G.__multiple_top_level_fields
-- Built-in inclusion directives
skipDirective :: MonadParse m => Directive m
skipDirective =
mkDirective
$$(G.litName "skip")
G._skip
(Just "whether this query should be skipped")
True
[ G.DLExecutable G.EDLFIELD,
@ -206,7 +205,7 @@ skipDirective =
includeDirective :: MonadParse m => Directive m
includeDirective =
mkDirective
$$(G.litName "include")
G._include
(Just "whether this query should be included")
True
[ G.DLExecutable G.EDLFIELD,
@ -216,13 +215,13 @@ includeDirective =
ifArgument
skip :: DirectiveKey Bool
skip = DirectiveKey $$(G.litName "skip")
skip = DirectiveKey G._skip
include :: DirectiveKey Bool
include = DirectiveKey $$(G.litName "include")
include = DirectiveKey G._include
ifArgument :: MonadParse m => InputFieldsParser m Bool
ifArgument = field $$(G.litName "if") Nothing boolean
ifArgument = field G._if Nothing boolean
-- Parser type for directives.

View File

@ -21,6 +21,7 @@ import Data.Text qualified as T
import Data.Text.Extended (dquoteList, (<<>))
import Hasura.Base.Error
import Hasura.GraphQL.Execute.Types
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Monad (ParseT, runSchemaT)
import Hasura.GraphQL.Schema.Common (QueryContext (..))
import Hasura.GraphQL.Schema.Remote (buildRemoteParser)
@ -95,8 +96,8 @@ fetchRemoteSchema env manager _rscName rsDef@ValidatedRemoteSchemaDef {..} = do
addDefaultRoots :: IntrospectionResult -> IntrospectionResult
addDefaultRoots IntrospectionResult {..} =
IntrospectionResult
{ irMutationRoot = getRootTypeName $$(G.litName "Mutation") irMutationRoot,
irSubscriptionRoot = getRootTypeName $$(G.litName "Subscription") irSubscriptionRoot,
{ irMutationRoot = getRootTypeName G._Mutation irMutationRoot,
irSubscriptionRoot = getRootTypeName G._Subscription irSubscriptionRoot,
..
}
where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ViewPatterns #-}
module Hasura.GraphQL.Schema
@ -27,6 +27,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser (FieldParser (..))
import Hasura.GraphQL.Parser.Schema.Convert (convertToSchemaIntrospection)
import Hasura.GraphQL.Schema.Backend
@ -238,15 +239,15 @@ buildRoleContext options sources remotes allActionInfos customTypes role remoteS
(,,)
<$> customizeFields
sourceCustomization
(mkTypename <> P.MkTypename (<> $$(G.litName "_query")))
(mkTypename <> P.MkTypename (<> G.__query))
(buildQueryFields sourceName sourceConfig validTables validFunctions queryTagsConfig)
<*> customizeFields
sourceCustomization
(mkTypename <> P.MkTypename (<> $$(G.litName "_mutation_frontend")))
(mkTypename <> P.MkTypename (<> G.__mutation_frontend))
(buildMutationFields Frontend sourceName sourceConfig validTables validFunctions queryTagsConfig)
<*> customizeFields
sourceCustomization
(mkTypename <> P.MkTypename (<> $$(G.litName "_mutation_backend")))
(mkTypename <> P.MkTypename (<> G.__mutation_backend))
(buildMutationFields Backend sourceName sourceConfig validTables validFunctions queryTagsConfig)
buildRelayRoleContext ::
@ -337,15 +338,15 @@ buildRelayRoleContext options sources allActionInfos customTypes role = do
(,,)
<$> customizeFields
sourceCustomization
(mkTypename <> P.MkTypename (<> $$(G.litName "_query")))
(mkTypename <> P.MkTypename (<> G.__query))
(buildRelayQueryFields sourceName sourceConfig validTables validFunctions queryTagsConfig)
<*> customizeFields
sourceCustomization
(mkTypename <> P.MkTypename (<> $$(G.litName "_mutation_frontend")))
(mkTypename <> P.MkTypename (<> G.__mutation_frontend))
(buildMutationFields Frontend sourceName sourceConfig validTables validFunctions queryTagsConfig)
<*> customizeFields
sourceCustomization
(mkTypename <> P.MkTypename (<> $$(G.litName "_mutation_backend")))
(mkTypename <> P.MkTypename (<> G.__mutation_backend))
(buildMutationFields Backend sourceName sourceConfig validTables validFunctions queryTagsConfig)
-- | Builds the schema context for unauthenticated users.
@ -380,7 +381,7 @@ unauthenticatedContext allRemotes remoteSchemaPermsCtx = do
remoteSchemaPermsCtx
False
-- chosen arbitrarily to be as improbable as possible
fakeRole = mkRoleNameSafe $$(NT.nonEmptyText "MyNameIsOzymandiasKingOfKingsLookOnMyWorksYeMightyAndDespair")
fakeRole = mkRoleNameSafe [NT.nonEmptyTextQQ|MyNameIsOzymandiasKingOfKingsLookOnMyWorksYeMightyAndDespair|]
-- we delete all references to remote joins
alteredRemoteSchemas =
allRemotes <&> first \context ->
@ -617,7 +618,7 @@ queryWithIntrospectionHelper basicQueryFP mutationP subscriptionP = do
-- provide any query. In such a case, to meet both of those, we introduce a placeholder query
-- in the schema.
placeholderText = "There are no queries available to the current role. Either there are no sources or remote schemas configured, or the current role doesn't have the required permissions."
placeholderField = NotNamespaced (RFRaw $ JO.String placeholderText) <$ P.selection_ $$(G.litName "no_queries_available") (Just $ G.Description placeholderText) P.string
placeholderField = NotNamespaced (RFRaw $ JO.String placeholderText) <$ P.selection_ G._no_queries_available (Just $ G.Description placeholderText) P.string
fixedQueryFP = if null basicQueryFP then [placeholderField] else basicQueryFP
basicQueryP <- queryRootFromFields fixedQueryFP
let buildIntrospectionResponse printResponseFromSchema = do
@ -721,13 +722,13 @@ takeExposedAs :: FunctionExposedAs -> FunctionCache b -> FunctionCache b
takeExposedAs x = Map.filter ((== x) . _fiExposedAs)
subscriptionRoot :: G.Name
subscriptionRoot = $$(G.litName "subscription_root")
subscriptionRoot = G._subscription_root
mutationRoot :: G.Name
mutationRoot = $$(G.litName "mutation_root")
mutationRoot = G._mutation_root
queryRoot :: G.Name
queryRoot = $$(G.litName "query_root")
queryRoot = G._query_root
finalizeParser :: Parser 'Output (P.ParseT Identity) a -> ParserFn a
finalizeParser parser = runIdentity . P.runParseT . P.runParser parser

View File

@ -25,6 +25,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Common
@ -145,19 +146,19 @@ actionAsyncQuery objectTypes actionInfo = runMaybeT do
let idField = P.selection_ idFieldName (Just idFieldDescription) actionIdParser $> AsyncId
createdAtField =
P.selection_
$$(G.litName "created_at")
G._created_at
(Just "the time at which this action was created")
createdAtFieldParser
$> AsyncCreatedAt
errorsField =
P.selection_
$$(G.litName "errors")
G._errors
(Just "errors related to the invocation")
errorsFieldParser
$> AsyncErrors
outputField =
P.subselection_
$$(G.litName "output")
G._output
(Just "the output fields of this action")
actionOutputParser
<&> AsyncOutput
@ -190,7 +191,7 @@ actionAsyncQuery objectTypes actionInfo = runMaybeT do
}
where
ActionInfo actionName (outputType, outputObject) definition permissions forwardClientHeaders comment = actionInfo
idFieldName = $$(G.litName "id")
idFieldName = G._id
idFieldDescription = "the unique id of an action"
-- | Async action's unique id

View File

@ -18,6 +18,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Common (askTableInfo, partialSQLExpToUnpreparedValue)
import Hasura.GraphQL.Schema.Table
@ -41,7 +42,7 @@ boolExp ::
m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
boolExp sourceName tableInfo = memoizeOn 'boolExp (sourceName, tableName) $ do
tableGQLName <- getTableGQLName tableInfo
name <- P.mkTypename $ tableGQLName <> $$(G.litName "_bool_exp")
name <- P.mkTypename $ tableGQLName <> G.__bool_exp
let description =
G.Description $
"Boolean expression to filter rows from the table " <> tableName
@ -53,9 +54,9 @@ boolExp sourceName tableInfo = memoizeOn 'boolExp (sourceName, tableName) $ do
-- Bafflingly, ApplicativeDo doesnt work if we inline this definition (I
-- think the TH splices throw it off), so we have to define it separately.
let specialFieldParsers =
[ P.fieldOptional $$(G.litName "_or") Nothing (BoolOr <$> P.list recur),
P.fieldOptional $$(G.litName "_and") Nothing (BoolAnd <$> P.list recur),
P.fieldOptional $$(G.litName "_not") Nothing (BoolNot <$> recur)
[ P.fieldOptional G.__or Nothing (BoolOr <$> P.list recur),
P.fieldOptional G.__and Nothing (BoolAnd <$> P.list recur),
P.fieldOptional G.__not Nothing (BoolNot <$> recur)
]
pure $
@ -192,11 +193,11 @@ equalityOperators ::
Parser k n (UnpreparedValue b) ->
[InputFieldsParser n (Maybe (OpExpG b (UnpreparedValue b)))]
equalityOperators collapseIfNull valueParser valueListParser =
[ mkBoolOperator collapseIfNull $$(G.litName "_is_null") Nothing $ bool ANISNOTNULL ANISNULL <$> P.boolean,
mkBoolOperator collapseIfNull $$(G.litName "_eq") Nothing $ AEQ True <$> valueParser,
mkBoolOperator collapseIfNull $$(G.litName "_neq") Nothing $ ANE True <$> valueParser,
mkBoolOperator collapseIfNull $$(G.litName "_in") Nothing $ AIN <$> valueListParser,
mkBoolOperator collapseIfNull $$(G.litName "_nin") Nothing $ ANIN <$> valueListParser
[ mkBoolOperator collapseIfNull G.__is_null Nothing $ bool ANISNOTNULL ANISNULL <$> P.boolean,
mkBoolOperator collapseIfNull G.__eq Nothing $ AEQ True <$> valueParser,
mkBoolOperator collapseIfNull G.__neq Nothing $ ANE True <$> valueParser,
mkBoolOperator collapseIfNull G.__in Nothing $ AIN <$> valueListParser,
mkBoolOperator collapseIfNull G.__nin Nothing $ ANIN <$> valueListParser
]
comparisonOperators ::
@ -207,8 +208,8 @@ comparisonOperators ::
Parser k n (UnpreparedValue b) ->
[InputFieldsParser n (Maybe (OpExpG b (UnpreparedValue b)))]
comparisonOperators collapseIfNull valueParser =
[ mkBoolOperator collapseIfNull $$(G.litName "_gt") Nothing $ AGT <$> valueParser,
mkBoolOperator collapseIfNull $$(G.litName "_lt") Nothing $ ALT <$> valueParser,
mkBoolOperator collapseIfNull $$(G.litName "_gte") Nothing $ AGTE <$> valueParser,
mkBoolOperator collapseIfNull $$(G.litName "_lte") Nothing $ ALTE <$> valueParser
[ mkBoolOperator collapseIfNull G.__gt Nothing $ AGT <$> valueParser,
mkBoolOperator collapseIfNull G.__lt Nothing $ ALT <$> valueParser,
mkBoolOperator collapseIfNull G.__gte Nothing $ AGTE <$> valueParser,
mkBoolOperator collapseIfNull G.__lte Nothing $ ALTE <$> valueParser
]

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
-- | This module provides building blocks for the GraphQL Schema that the
-- GraphQL Engine presents.
--
@ -57,6 +55,7 @@ where
import Data.Text.Extended
import Hasura.GraphQL.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend (MonadBuildSchema)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation
@ -79,9 +78,9 @@ buildTableQueryFields sourceName tableName tableInfo gqlName = do
-- select table
selectName <- mkRootFieldName . fromMaybe gqlName $ _crfName _tcrfSelect
-- select table by pk
selectPKName <- mkRootFieldName . fromMaybe (gqlName <> $$(G.litName "_by_pk")) $ _crfName _tcrfSelectByPk
selectPKName <- mkRootFieldName . fromMaybe (gqlName <> G.__by_pk) $ _crfName _tcrfSelectByPk
-- select table aggregate
selectAggName <- mkRootFieldName . fromMaybe (gqlName <> $$(G.litName "_aggregate")) $ _crfName _tcrfSelectAggregate
selectAggName <- mkRootFieldName . fromMaybe (gqlName <> G.__aggregate) $ _crfName _tcrfSelectAggregate
catMaybes
<$> sequenceA
[ optionalFieldParser QDBMultipleRows $ selectTable sourceName tableInfo selectName selectDesc,
@ -108,8 +107,8 @@ buildTableInsertMutationFields ::
G.Name ->
m [FieldParser n (AnnotatedInsert b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableInsertMutationFields backendInsertAction scenario sourceName tableName tableInfo gqlName = do
insertName <- mkRootFieldName . fromMaybe ($$(G.litName "insert_") <> gqlName) $ _crfName _tcrfInsert
insertOneName <- mkRootFieldName . fromMaybe ($$(G.litName "insert_") <> gqlName <> $$(G.litName "_one")) $ _crfName _tcrfInsertOne
insertName <- mkRootFieldName . fromMaybe (G._insert_ <> gqlName) $ _crfName _tcrfInsert
insertOneName <- mkRootFieldName . fromMaybe (G._insert_ <> gqlName <> G.__one) $ _crfName _tcrfInsertOne
insert <- insertIntoTable backendInsertAction scenario sourceName tableInfo insertName insertDesc
-- Select permissions are required for insertOne: the selection set is the
-- same as a select on that table, and it therefore can't be populated if the
@ -162,12 +161,12 @@ buildTableUpdateMutationFields ::
G.Name ->
m [FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableUpdateMutationFields mkBackendUpdate sourceName tableName tableInfo gqlName = do
let viewInfo = _tciViewInfo $ _tiCoreInfo tableInfo
let _viewInfo = _tciViewInfo $ _tiCoreInfo tableInfo
backendUpdate <- mkBackendUpdate tableInfo
-- update table
updateName <- mkRootFieldName . fromMaybe ($$(G.litName "update_") <> gqlName) $ _crfName _tcrfUpdate
updateName <- mkRootFieldName . fromMaybe (G._update_ <> gqlName) $ _crfName _tcrfUpdate
-- update table by pk
updatePKName <- mkRootFieldName . fromMaybe ($$(G.litName "update_") <> gqlName <> $$(G.litName "_by_pk")) $ _crfName _tcrfUpdateByPk
updatePKName <- mkRootFieldName . fromMaybe (G._update_ <> gqlName <> G.__by_pk) $ _crfName _tcrfUpdateByPk
update <- updateTable backendUpdate sourceName tableInfo updateName updateDesc
-- Primary keys can only be tested in the `where` clause if a primary key
-- exists on the table and if the user has select permissions on all columns
@ -191,9 +190,9 @@ buildTableDeleteMutationFields ::
m [FieldParser n (AnnDelG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableDeleteMutationFields sourceName tableName tableInfo gqlName = do
-- delete from table
deleteName <- mkRootFieldName . fromMaybe ($$(G.litName "delete_") <> gqlName) $ _crfName _tcrfDelete
deleteName <- mkRootFieldName . fromMaybe (G._delete_ <> gqlName) $ _crfName _tcrfDelete
-- delete from table by pk
deletePKName <- mkRootFieldName . fromMaybe ($$(G.litName "delete_") <> gqlName <> $$(G.litName "_by_pk")) $ _crfName _tcrfDeleteByPk
deletePKName <- mkRootFieldName . fromMaybe (G._delete_ <> gqlName <> G.__by_pk) $ _crfName _tcrfDeleteByPk
delete <- deleteFromTable sourceName tableInfo deleteName deleteDesc
-- Primary keys can only be tested in the `where` clause if the user has
-- select permissions for them, which at the very least requires select

View File

@ -50,6 +50,7 @@ import Hasura.Base.Error
import Hasura.GraphQL.Execute.Types qualified as ET (GraphQLQueryType)
import Hasura.GraphQL.Namespace (NamespacedField)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Prelude
import Hasura.RQL.IR.Action qualified as IR
import Hasura.RQL.IR.RemoteSchema qualified as IR
@ -166,14 +167,14 @@ parsedSelectionsToFields mkTypename =
numericAggOperators :: [G.Name]
numericAggOperators =
[ $$(G.litName "sum"),
$$(G.litName "avg"),
$$(G.litName "stddev"),
$$(G.litName "stddev_samp"),
$$(G.litName "stddev_pop"),
$$(G.litName "variance"),
$$(G.litName "var_samp"),
$$(G.litName "var_pop")
[ G._sum,
G._avg,
G._stddev,
G._stddev_samp,
G._stddev_pop,
G._variance,
G._var_samp,
G._var_pop
]
comparisonAggOperators :: [G.Name]
@ -247,7 +248,7 @@ mkEnumTypeName (EnumReference enumTableName _ enumTableCustomName) = do
addEnumSuffix enumTableGQLName enumTableCustomName
addEnumSuffix :: (MonadReader r m, Has MkTypename r) => G.Name -> Maybe G.Name -> m G.Name
addEnumSuffix enumTableGQLName enumTableCustomName = P.mkTypename $ (fromMaybe enumTableGQLName enumTableCustomName) <> $$(G.litName "_enum")
addEnumSuffix enumTableGQLName enumTableCustomName = P.mkTypename $ (fromMaybe enumTableGQLName enumTableCustomName) <> G.__enum
-- | Return the indirect dependencies on a source.
-- We return a [SchemaObjId] instead of [SourceObjId], because the latter has no

View File

@ -1,5 +1,4 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Schema.Introspect
( buildIntrospectionSchema,
@ -21,6 +20,7 @@ import Hasura.Base.Error
import Hasura.GraphQL.Parser (FieldParser, Kind (..), Parser, Schema (..))
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Directives
import Hasura.GraphQL.Parser.Internal.Parser (FieldParser (..))
import Hasura.Prelude
@ -133,7 +133,7 @@ like so (again, heavily simplified):
```
types :: FieldParser n J.Value
types = do
printer <- P.subselection_ $$(G.litName "types") Nothing typeField
printer <- P.subselection_ G._types Nothing typeField
return $ J.Array $ map printer $ allSchemaTypes
```
@ -266,8 +266,8 @@ typeIntrospection ::
{-# INLINE typeIntrospection #-}
typeIntrospection = do
let nameArg :: P.InputFieldsParser n Text
nameArg = P.field $$(G.litName "name") Nothing P.string
~(nameText, printer) <- P.subselection $$(G.litName "__type") Nothing nameArg typeField
nameArg = P.field G._name Nothing P.string
~(nameText, printer) <- P.subselection G.___type Nothing nameArg typeField
-- We pass around the GraphQL schema information under the name `partialSchema`,
-- because the GraphQL spec forces us to expose a hybrid between the
-- specification of valid queries (including introspection) and an
@ -283,7 +283,7 @@ schema ::
MonadParse n =>
FieldParser n (Schema -> J.Value)
{-# INLINE schema #-}
schema = P.subselection_ $$(G.litName "__schema") Nothing schemaSet
schema = P.subselection_ G.___schema Nothing schemaSet
{-
type __Type {
@ -320,11 +320,11 @@ typeField ::
typeField =
let includeDeprecated :: P.InputFieldsParser n Bool
includeDeprecated =
P.fieldWithDefault $$(G.litName "includeDeprecated") Nothing (G.VBoolean False) (P.nullable P.boolean)
P.fieldWithDefault G._includeDeprecated Nothing (G.VBoolean False) (P.nullable P.boolean)
<&> fromMaybe False
kind :: FieldParser n (SomeType -> J.Value)
kind =
P.selection_ $$(G.litName "kind") Nothing typeKind
P.selection_ G._kind Nothing typeKind
$> \case
SomeType tp ->
case tp of
@ -348,7 +348,7 @@ typeField =
J.String "UNION"
name :: FieldParser n (SomeType -> J.Value)
name =
P.selection_ $$(G.litName "name") Nothing P.string
P.selection_ G._name Nothing P.string
$> \case
SomeType tp ->
case tp of
@ -357,7 +357,7 @@ typeField =
_ -> J.Null
description :: FieldParser n (SomeType -> J.Value)
description =
P.selection_ $$(G.litName "description") Nothing P.string
P.selection_ G._description Nothing P.string
$> \case
SomeType (P.TNamed _ (P.Definition _ (Just desc) _)) ->
J.String (G.unDescription desc)
@ -365,7 +365,7 @@ typeField =
fields :: FieldParser n (SomeType -> J.Value)
fields = do
-- TODO handle the value of includeDeprecated
~(_includeDeprecated, printer) <- P.subselection $$(G.litName "fields") Nothing includeDeprecated fieldField
~(_includeDeprecated, printer) <- P.subselection G._fields Nothing includeDeprecated fieldField
return $
\case
SomeType tp ->
@ -377,7 +377,7 @@ typeField =
_ -> J.Null
interfaces :: FieldParser n (SomeType -> J.Value)
interfaces = do
printer <- P.subselection_ $$(G.litName "interfaces") Nothing typeField
printer <- P.subselection_ G._interfaces Nothing typeField
return $
\case
SomeType tp ->
@ -387,7 +387,7 @@ typeField =
_ -> J.Null
possibleTypes :: FieldParser n (SomeType -> J.Value)
possibleTypes = do
printer <- P.subselection_ $$(G.litName "possibleTypes") Nothing typeField
printer <- P.subselection_ G._possibleTypes Nothing typeField
return $
\case
SomeType tp ->
@ -400,7 +400,7 @@ typeField =
enumValues :: FieldParser n (SomeType -> J.Value)
enumValues = do
-- TODO handle the value of includeDeprecated
~(_includeDeprecated, printer) <- P.subselection $$(G.litName "enumValues") Nothing includeDeprecated enumValue
~(_includeDeprecated, printer) <- P.subselection G._enumValues Nothing includeDeprecated enumValue
return $
\case
SomeType tp ->
@ -410,7 +410,7 @@ typeField =
_ -> J.Null
inputFields :: FieldParser n (SomeType -> J.Value)
inputFields = do
printer <- P.subselection_ $$(G.litName "inputFields") Nothing inputValue
printer <- P.subselection_ G._inputFields Nothing inputValue
return $
\case
SomeType tp ->
@ -421,7 +421,7 @@ typeField =
-- ofType peels modalities off of types
ofType :: FieldParser n (SomeType -> J.Value)
ofType = do
printer <- P.subselection_ $$(G.litName "ofType") Nothing typeField
printer <- P.subselection_ G._ofType Nothing typeField
return $ \case
-- kind = "NON_NULL": !a -> a
SomeType (P.TNamed P.NonNullable x) ->
@ -435,7 +435,7 @@ typeField =
_ -> J.Null
in applyPrinter
<$> P.selectionSet
$$(G.litName "__Type")
G.___Type
Nothing
[ kind,
name,
@ -463,26 +463,26 @@ inputValue ::
inputValue =
let name :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
name =
P.selection_ $$(G.litName "name") Nothing P.string
P.selection_ G._name Nothing P.string
$> nameAsJSON . P.dName
description :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
description =
P.selection_ $$(G.litName "description") Nothing P.string
P.selection_ G._description Nothing P.string
$> maybe J.Null (J.String . G.unDescription) . P.dDescription
typeF :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
typeF = do
printer <- P.subselection_ $$(G.litName "type") Nothing typeField
printer <- P.subselection_ G._type Nothing typeField
return $ \defInfo -> case P.dInfo defInfo of
P.InputFieldInfo tp _ -> printer $ SomeType tp
defaultValue :: FieldParser n (P.Definition P.InputFieldInfo -> J.Value)
defaultValue =
P.selection_ $$(G.litName "defaultValue") Nothing P.string
P.selection_ G._defaultValue Nothing P.string
$> \defInfo -> case P.dInfo defInfo of
P.InputFieldInfo _ (Just val) -> J.String $ T.run $ GP.value val
_ -> J.Null
in applyPrinter
<$> P.selectionSet
$$(G.litName "__InputValue")
G.___InputValue
Nothing
[ name,
description,
@ -505,24 +505,24 @@ enumValue ::
enumValue =
let name :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
name =
P.selection_ $$(G.litName "name") Nothing P.string
P.selection_ G._name Nothing P.string
$> nameAsJSON . P.dName
description :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
description =
P.selection_ $$(G.litName "description") Nothing P.string
P.selection_ G._description Nothing P.string
$> maybe J.Null (J.String . G.unDescription) . P.dDescription
-- TODO We don't seem to support enum value deprecation
isDeprecated :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
isDeprecated =
P.selection_ $$(G.litName "isDeprecated") Nothing P.string
P.selection_ G._isDeprecated Nothing P.string
$> const (J.Bool False)
deprecationReason :: FieldParser n (P.Definition P.EnumValueInfo -> J.Value)
deprecationReason =
P.selection_ $$(G.litName "deprecationReason") Nothing P.string
P.selection_ G._deprecationReason Nothing P.string
$> const J.Null
in applyPrinter
<$> P.selectionSet
$$(G.litName "__EnumValue")
G.___EnumValue
Nothing
[ name,
description,
@ -548,17 +548,17 @@ typeKind ::
Parser 'Both n ()
typeKind =
P.enum
$$(G.litName "__TypeKind")
G.___TypeKind
Nothing
( NE.fromList
[ mkDefinition $$(G.litName "ENUM"),
mkDefinition $$(G.litName "INPUT_OBJECT"),
mkDefinition $$(G.litName "INTERFACE"),
mkDefinition $$(G.litName "LIST"),
mkDefinition $$(G.litName "NON_NULL"),
mkDefinition $$(G.litName "OBJECT"),
mkDefinition $$(G.litName "SCALAR"),
mkDefinition $$(G.litName "UNION")
[ mkDefinition G._ENUM,
mkDefinition G._INPUT_OBJECT,
mkDefinition G._INTERFACE,
mkDefinition G._LIST,
mkDefinition G._NON_NULL,
mkDefinition G._OBJECT,
mkDefinition G._SCALAR,
mkDefinition G._UNION
]
)
where
@ -581,34 +581,34 @@ fieldField ::
fieldField =
let name :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
name =
P.selection_ $$(G.litName "name") Nothing P.string
P.selection_ G._name Nothing P.string
$> nameAsJSON . P.dName
description :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
description =
P.selection_ $$(G.litName "description") Nothing P.string $> \defInfo ->
P.selection_ G._description Nothing P.string $> \defInfo ->
case P.dDescription defInfo of
Nothing -> J.Null
Just desc -> J.String (G.unDescription desc)
args :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
args = do
printer <- P.subselection_ $$(G.litName "args") Nothing inputValue
printer <- P.subselection_ G._args Nothing inputValue
return $ J.Array . V.fromList . map printer . sortOn P.dName . P.fArguments . P.dInfo
typeF :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
typeF = do
printer <- P.subselection_ $$(G.litName "type") Nothing typeField
printer <- P.subselection_ G._type Nothing typeField
return $ printer . (\case P.FieldInfo _ tp -> SomeType tp) . P.dInfo
-- TODO We don't seem to track deprecation info
isDeprecated :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
isDeprecated =
P.selection_ $$(G.litName "isDeprecated") Nothing P.string
P.selection_ G._isDeprecated Nothing P.string
$> const (J.Bool False)
deprecationReason :: FieldParser n (P.Definition P.FieldInfo -> J.Value)
deprecationReason =
P.selection_ $$(G.litName "deprecationReason") Nothing P.string
P.selection_ G._deprecationReason Nothing P.string
$> const J.Null
in applyPrinter
<$> P.selectionSet
$$(G.litName "__Field")
G.___Field
Nothing
[ name,
description,
@ -635,27 +635,27 @@ directiveSet ::
directiveSet =
let name :: FieldParser n (P.DirectiveInfo -> J.Value)
name =
P.selection_ $$(G.litName "name") Nothing P.string
P.selection_ G._name Nothing P.string
$> (J.toOrdered . P.diName)
description :: FieldParser n (P.DirectiveInfo -> J.Value)
description =
P.selection_ $$(G.litName "description") Nothing P.string
P.selection_ G._description Nothing P.string
$> (J.toOrdered . P.diDescription)
locations :: FieldParser n (P.DirectiveInfo -> J.Value)
locations =
P.selection_ $$(G.litName "locations") Nothing P.string
P.selection_ G._locations Nothing P.string
$> (J.toOrdered . map showDirLoc . P.diLocations)
args :: FieldParser n (P.DirectiveInfo -> J.Value)
args = do
printer <- P.subselection_ $$(G.litName "args") Nothing inputValue
printer <- P.subselection_ G._args Nothing inputValue
pure $ J.array . map printer . P.diArguments
isRepeatable :: FieldParser n (P.DirectiveInfo -> J.Value)
isRepeatable =
P.selection_ $$(G.litName "isRepeatable") Nothing P.string
P.selection_ G._isRepeatable Nothing P.string
$> const J.Null
in applyPrinter
<$> P.selectionSet
$$(G.litName "__Directive")
G.___Directive
Nothing
[ name,
description,
@ -687,13 +687,13 @@ schemaSet ::
schemaSet =
let description :: FieldParser n (Schema -> J.Value)
description =
P.selection_ $$(G.litName "description") Nothing P.string
P.selection_ G._description Nothing P.string
$> \partialSchema -> case sDescription partialSchema of
Nothing -> J.Null
Just s -> J.String $ G.unDescription s
types :: FieldParser n (Schema -> J.Value)
types = do
printer <- P.subselection_ $$(G.litName "types") Nothing typeField
printer <- P.subselection_ G._types Nothing typeField
return $
\partialSchema ->
J.Array $
@ -706,27 +706,27 @@ schemaSet =
SomeType $ P.TNamed P.Nullable def
queryType :: FieldParser n (Schema -> J.Value)
queryType = do
printer <- P.subselection_ $$(G.litName "queryType") Nothing typeField
printer <- P.subselection_ G._queryType Nothing typeField
return $ \partialSchema -> printer $ SomeType $ sQueryType partialSchema
mutationType :: FieldParser n (Schema -> J.Value)
mutationType = do
printer <- P.subselection_ $$(G.litName "mutationType") Nothing typeField
printer <- P.subselection_ G._mutationType Nothing typeField
return $ \partialSchema -> case sMutationType partialSchema of
Nothing -> J.Null
Just tp -> printer $ SomeType tp
subscriptionType :: FieldParser n (Schema -> J.Value)
subscriptionType = do
printer <- P.subselection_ $$(G.litName "subscriptionType") Nothing typeField
printer <- P.subselection_ G._subscriptionType Nothing typeField
return $ \partialSchema -> case sSubscriptionType partialSchema of
Nothing -> J.Null
Just tp -> printer $ SomeType tp
directives :: FieldParser n (Schema -> J.Value)
directives = do
printer <- P.subselection_ $$(G.litName "directives") Nothing directiveSet
printer <- P.subselection_ G._directives Nothing directiveSet
return $ \partialSchema -> J.array $ map printer $ sDirectives partialSchema
in applyPrinter
<$> P.selectionSet
$$(G.litName "__Schema")
G.___Schema
Nothing
[ description,
types,

View File

@ -25,6 +25,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
@ -82,7 +83,7 @@ insertIntoTable backendInsertAction scenario sourceName tableInfo fieldName desc
where
mkObjectsArg objectParser =
P.field
$$(G.litName "objects")
G._objects
(Just "the rows to be inserted")
(P.list objectParser)
@ -126,7 +127,7 @@ insertOneIntoTable backendInsertAction scenario sourceName tableInfo fieldName d
where
mkObjectArg objectParser =
P.field
$$(G.litName "object")
G._object
(Just "the row to be inserted")
objectParser
@ -157,7 +158,7 @@ tableFieldsInput sourceName tableInfo =
memoizeOn 'tableFieldsInput (sourceName, tableName) do
tableGQLName <- getTableGQLName tableInfo
objectFields <- traverse mkFieldParser (Map.elems allFields)
objectName <- P.mkTypename $ tableGQLName <> $$(G.litName "_insert_input")
objectName <- P.mkTypename $ tableGQLName <> G.__insert_input
let objectDesc = G.Description $ "input type for inserting data into table " <>> tableName
pure $ P.object objectName (Just objectDesc) $ coalesceFields objectFields
where
@ -246,12 +247,12 @@ objectRelationshipInput backendInsertAction sourceName tableInfo = runMaybeT $ d
insertPerms <- MaybeT $ (_permIns =<<) <$> tablePermissions tableInfo
lift $ memoizeOn 'objectRelationshipInput (sourceName, tableName) do
updatePerms <- (_permUpd =<<) <$> tablePermissions tableInfo
selectPerms <- (_permSel =<<) <$> tablePermissions tableInfo
_selectPerms <- (_permSel =<<) <$> tablePermissions tableInfo
tableGQLName <- getTableGQLName tableInfo
objectParser <- tableFieldsInput sourceName tableInfo
backendInsertParser <- backendInsertAction sourceName tableInfo
inputName <- P.mkTypename $ tableGQLName <> $$(G.litName "_obj_rel_insert_input")
let objectName = $$(G.litName "data")
inputName <- P.mkTypename $ tableGQLName <> G.__obj_rel_insert_input
let objectName = G._data
inputDesc = G.Description $ "input type for inserting object relation for remote table " <>> tableName
inputParser = do
backendInsert <- backendInsertParser
@ -279,12 +280,12 @@ arrayRelationshipInput backendInsertAction sourceName tableInfo = runMaybeT $ do
insertPerms <- MaybeT $ (_permIns =<<) <$> tablePermissions tableInfo
lift $ memoizeOn 'arrayRelationshipInput (sourceName, tableName) do
updatePerms <- (_permUpd =<<) <$> tablePermissions tableInfo
selectPerms <- (_permSel =<<) <$> tablePermissions tableInfo
_selectPerms <- (_permSel =<<) <$> tablePermissions tableInfo
tableGQLName <- getTableGQLName tableInfo
objectParser <- tableFieldsInput sourceName tableInfo
backendInsertParser <- backendInsertAction sourceName tableInfo
inputName <- P.mkTypename $ tableGQLName <> $$(G.litName "_arr_rel_insert_input")
let objectsName = $$(G.litName "data")
inputName <- P.mkTypename $ tableGQLName <> G.__arr_rel_insert_input
let objectsName = G._data
inputDesc = G.Description $ "input type for inserting array relation for remote table " <>> tableName
inputParser = do
backendInsert <- backendInsertParser
@ -348,7 +349,7 @@ deleteFromTable sourceName tableInfo fieldName description = runMaybeT $ do
guard $ isMutable viIsInsertable viewInfo
deletePerms <- MaybeT $ (_permDel =<<) <$> tablePermissions tableInfo
lift do
let whereName = $$(G.litName "where")
let whereName = G._where
whereDesc = "filter the rows which have to be deleted"
whereArg <- P.field whereName (Just whereDesc) <$> boolExp sourceName tableInfo
selection <- mutationSelectionSet sourceName tableInfo
@ -414,13 +415,13 @@ mutationSelectionSet sourceName tableInfo =
memoizeOn 'mutationSelectionSet (sourceName, tableName) do
tableGQLName <- getTableGQLName tableInfo
returning <- runMaybeT do
permissions <- MaybeT $ tableSelectPermissions tableInfo
_permissions <- MaybeT $ tableSelectPermissions tableInfo
tableSet <- MaybeT $ tableSelectionList sourceName tableInfo
let returningName = $$(G.litName "returning")
let returningName = G._returning
returningDesc = "data from the rows affected by the mutation"
pure $ IR.MRet <$> P.subselection_ returningName (Just returningDesc) tableSet
selectionName <- P.mkTypename $ tableGQLName <> $$(G.litName "_mutation_response")
let affectedRowsName = $$(G.litName "affected_rows")
selectionName <- P.mkTypename $ tableGQLName <> G.__mutation_response
let affectedRowsName = G._affected_rows
affectedRowsDesc = "number of rows affected by the mutation"
selectionDesc = G.Description $ "response of any mutation on the table " <>> tableName

View File

@ -16,6 +16,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Table
@ -43,7 +44,7 @@ orderByExp ::
m (Parser 'Input n [IR.AnnotatedOrderByItemG b (UnpreparedValue b)])
orderByExp sourceName tableInfo = memoizeOn 'orderByExp (sourceName, tableInfoName tableInfo) $ do
tableGQLName <- getTableGQLName tableInfo
name <- P.mkTypename $ tableGQLName <> $$(G.litName "_order_by")
name <- P.mkTypename $ tableGQLName <> G.__order_by
let description =
G.Description $
"Ordering options when selecting data from " <> tableInfoName tableInfo <<> "."
@ -73,7 +74,7 @@ orderByExp sourceName tableInfo = memoizeOn 'orderByExp (sourceName, tableInfoNa
otherTableOrderBy <- join <$> P.fieldOptional fieldName Nothing (P.nullable otherTableParser)
pure $ fmap (map $ fmap $ IR.AOCObjectRelation relationshipInfo newPerms) otherTableOrderBy
ArrRel -> do
let aggregateFieldName = fieldName <> $$(G.litName "_aggregate")
let aggregateFieldName = fieldName <> G.__aggregate
aggregationParser <- lift $ orderByAggregation sourceName remoteTableInfo
pure $ do
aggregationOrderBy <- join <$> P.fieldOptional aggregateFieldName Nothing (P.nullable aggregationParser)
@ -94,7 +95,7 @@ orderByExp sourceName tableInfo = memoizeOn 'orderByExp (sourceName, tableInfoNa
P.fieldOptional fieldName Nothing (orderByOperator @b)
<&> fmap (pure . mkOrderByItemG @b (IR.AOCComputedField computedFieldOrderBy)) . join
CFRSetofTable table -> do
let aggregateFieldName = fieldName <> $$(G.litName "_aggregate")
let aggregateFieldName = fieldName <> G.__aggregate
tableInfo' <- askTableInfo @b sourceName table
perms <- MaybeT $ tableSelectPermissions tableInfo'
let newPerms = fmap partialSQLExpToUnpreparedValue <$> spiFilter perms
@ -140,7 +141,7 @@ orderByAggregation sourceName tableInfo = memoizeOn 'orderByAggregation (sourceN
catMaybes
[ -- count
Just $
P.fieldOptional $$(G.litName "count") Nothing (orderByOperator @b)
P.fieldOptional G._count Nothing (orderByOperator @b)
<&> pure . fmap (pure . mkOrderByItemG @b IR.AAOCount) . join,
-- operators on numeric columns
if null numColumns
@ -155,7 +156,7 @@ orderByAggregation sourceName tableInfo = memoizeOn 'orderByAggregation (sourceN
for comparisonAggOperators \operator ->
parseOperator mkTypename operator tableGQLName compFields
]
objectName <- P.mkTypename $ tableGQLName <> $$(G.litName "_aggregate_order_by")
objectName <- P.mkTypename $ tableGQLName <> G.__aggregate_order_by
let description = G.Description $ "order by aggregate values of table " <>> tableName
pure $ P.object objectName (Just description) aggFields
where
@ -174,7 +175,7 @@ orderByAggregation sourceName tableInfo = memoizeOn 'orderByAggregation (sourceN
InputFieldsParser n (Maybe [IR.OrderByItemG b (IR.AnnotatedAggregateOrderBy b)])
parseOperator mkTypename operator tableGQLName columns =
let opText = G.unName operator
objectName = P.runMkTypename mkTypename $ tableGQLName <> $$(G.litName "_") <> operator <> $$(G.litName "_order_by")
objectName = P.runMkTypename mkTypename $ tableGQLName <> G.__ <> operator <> G.__order_by
objectDesc = Just $ G.Description $ "order by " <> opText <> "() on columns of table " <>> tableName
in P.fieldOptional operator Nothing (P.object objectName objectDesc columns)
`mapField` map (\(col, info) -> mkOrderByItemG (IR.AAOOp opText col) info)
@ -184,7 +185,7 @@ orderByOperator ::
(BackendSchema b, MonadParse n) =>
Parser 'Both n (Maybe (BasicOrderType b, NullsOrderType b))
orderByOperator =
P.nullable $ P.enum $$(G.litName "order_by") (Just "column ordering options") $ orderByOperators @b
P.nullable $ P.enum G._order_by (Just "column ordering options") $ orderByOperators @b
mkOrderByItemG :: forall b a. a -> (BasicOrderType b, NullsOrderType b) -> IR.OrderByItemG b a
mkOrderByItemG column (orderType, nullsOrder) =

View File

@ -21,6 +21,7 @@ import Data.Type.Equality
import Hasura.Base.Error
import Hasura.GraphQL.Namespace
import Hasura.GraphQL.Parser as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
import Hasura.GraphQL.Parser.Internal.TypeChecking qualified as P
import Hasura.GraphQL.Schema.Common
@ -59,7 +60,7 @@ makeResultCustomizer ::
RemoteSchemaCustomizer -> IR.GraphQLField (IR.RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable -> ResultCustomizer
makeResultCustomizer remoteSchemaCustomizer IR.GraphQLField {..} =
modifyFieldByName _fAlias $
if _fName == $$(G.litName "__typename")
if _fName == G.___typename
then customizeTypeNameString (_rscCustomizeTypeName remoteSchemaCustomizer)
else resultCustomizerFromSelection _fSelectionSet
where
@ -94,8 +95,8 @@ buildRawRemoteParser ::
)
buildRawRemoteParser (IntrospectionResult sdoc queryRoot mutationRoot subscriptionRoot) remoteRelationships info = do
queryT <- makeParsers queryRoot
mutationT <- makeNonQueryRootFieldParser mutationRoot $$(G.litName "Mutation")
subscriptionT <- makeNonQueryRootFieldParser subscriptionRoot $$(G.litName "Subscription")
mutationT <- makeNonQueryRootFieldParser mutationRoot G._Mutation
subscriptionT <- makeNonQueryRootFieldParser subscriptionRoot G._Subscription
return (queryT, mutationT, subscriptionT)
where
makeFieldParser :: G.Name -> G.FieldDefinition RemoteSchemaInputValueDefinition -> m (P.FieldParser n (IR.RemoteSchemaRootField (IR.RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
@ -591,7 +592,7 @@ remoteSchemaObject schemaDoc remoteRelationships defn@(G.ObjectTypeDefinition de
<&> OMap.mapWithKey \alias ->
handleTypename $
const $
IR.FieldGraphQL $ IR.mkGraphQLField (Just alias) $$(G.litName "__typename") mempty mempty IR.SelectionSetNone
IR.FieldGraphQL $ IR.mkGraphQLField (Just alias) G.___typename mempty mempty IR.SelectionSetNone
where
getInterface :: G.Name -> m (G.InterfaceTypeDefinition [G.Name] RemoteSchemaInputValueDefinition)
getInterface interfaceName =
@ -973,13 +974,16 @@ customizeRemoteNamespace remoteSchemaInfo@RemoteSchemaInfo {..} rootTypeName fie
handleTypename . const $
-- In P.selectionSet we lose the resultCustomizer from __typename fields so we need to put it back
let resultCustomizer = modifyFieldByName alias $ customizeTypeNameString $ _rscCustomizeTypeName rsCustomizer
in IR.RemoteSchemaRootField remoteSchemaInfo resultCustomizer $ IR.mkGraphQLField (Just alias) $$(G.litName "__typename") mempty mempty IR.SelectionSetNone
in IR.RemoteSchemaRootField remoteSchemaInfo resultCustomizer $ IR.mkGraphQLField (Just alias) G.___typename mempty mempty IR.SelectionSetNone
mkNamespaceTypename = MkTypename $ const $ runMkTypename (remoteSchemaCustomizeTypeName rsCustomizer) rootTypeName
{-
NOTE: Unused. Should we remove?
type MonadBuildRemoteSchema r m n = (MonadSchema n m, MonadError QErr m, MonadReader r m, Has MkTypename r, Has CustomizeRemoteFieldName r)
runMonadBuildRemoteSchema :: Monad m => SchemaT n (ReaderT (MkTypename, CustomizeRemoteFieldName) m) a -> m a
runMonadBuildRemoteSchema m = flip runReaderT (mempty, mempty) $ runSchemaT m
-}
withRemoteSchemaCustomization ::
forall m r a.

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Schema.RemoteRelationship
( remoteRelationshipField,
)
@ -14,6 +12,7 @@ import Hasura.Base.Error
import Hasura.GraphQL.Execute.Types qualified as ET
import Hasura.GraphQL.Parser
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Common
@ -195,7 +194,7 @@ remoteRelationshipToSourceField RemoteSourceFieldInfo {..} =
IR.SourceRelationshipObject $
IR.AnnObjectSelectG fields _rsfiTable $ IR._tpFilter $ tablePermissionsInfo tablePerms
ArrRel -> do
let aggFieldName = fieldName <> $$(G.litName "_aggregate")
let aggFieldName = fieldName <> G.__aggregate
selectionSetParser <- selectTable _rsfiSource tableInfo fieldName Nothing
aggSelectionSetParser <- selectTableAggregate _rsfiSource tableInfo aggFieldName Nothing
pure $

View File

@ -1,4 +1,5 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
@ -59,6 +60,7 @@ import Hasura.GraphQL.Parser
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
@ -260,15 +262,15 @@ selectTableAggregate sourceName tableInfo fieldName description = runMaybeT $ do
tableGQLName <- getTableGQLName tableInfo
tableArgsParser <- tableArguments sourceName tableInfo
aggregateParser <- tableAggregationFields sourceName tableInfo
selectionName <- P.mkTypename $ tableGQLName <> $$(G.litName "_aggregate")
selectionName <- P.mkTypename $ tableGQLName <> G.__aggregate
let aggregationParser =
P.nonNullableParser $
parsedSelectionsToFields IR.TAFExp
<$> P.selectionSet
selectionName
(Just $ G.Description $ "aggregated selection of " <>> tableName)
[ IR.TAFNodes xNodesAgg <$> P.subselection_ $$(G.litName "nodes") Nothing nodesParser,
IR.TAFAgg <$> P.subselection_ $$(G.litName "aggregate") Nothing aggregateParser
[ IR.TAFNodes xNodesAgg <$> P.subselection_ G._nodes Nothing nodesParser,
IR.TAFAgg <$> P.subselection_ G._aggregate Nothing aggregateParser
]
pure $
P.subselection fieldName description tableArgsParser aggregationParser
@ -352,7 +354,7 @@ tableSelectionSet ::
TableInfo b ->
m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet sourceName tableInfo = runMaybeT do
selectPermissions <- MaybeT $ tableSelectPermissions tableInfo
_selectPermissions <- MaybeT $ tableSelectPermissions tableInfo
lift $ memoizeOn 'tableSelectionSet (sourceName, tableName) do
tableGQLName <- getTableGQLName tableInfo
objectTypename <- P.mkTypename tableGQLName
@ -379,7 +381,7 @@ tableSelectionSet sourceName tableInfo = runMaybeT do
-- A relay table
(ET.QueryRelay, Just pkeyColumns, Just xRelayInfo) -> do
let nodeIdFieldParser =
P.selection_ $$(G.litName "id") Nothing P.identifier $> IR.AFNodeId xRelayInfo tableName pkeyColumns
P.selection_ G._id Nothing P.identifier $> IR.AFNodeId xRelayInfo tableName pkeyColumns
allFieldParsers = fieldParsers <> [nodeIdFieldParser]
nodeInterface <- node @b
pure $
@ -435,19 +437,19 @@ tableConnectionSelectionSet ::
m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet sourceName tableInfo = runMaybeT do
tableGQLName <- lift $ getTableGQLName tableInfo
selectPermissions <- MaybeT $ tableSelectPermissions tableInfo
_selectPermissions <- MaybeT $ tableSelectPermissions tableInfo
edgesParser <- MaybeT $ tableEdgesSelectionSet tableGQLName
lift $ memoizeOn 'tableConnectionSelectionSet (sourceName, tableName) do
connectionTypeName <- P.mkTypename $ tableGQLName <> $$(G.litName "Connection")
connectionTypeName <- P.mkTypename $ tableGQLName <> G._Connection
let pageInfo =
P.subselection_
$$(G.litName "pageInfo")
G._pageInfo
Nothing
pageInfoSelectionSet
<&> IR.ConnectionPageInfo
edges =
P.subselection_
$$(G.litName "edges")
G._edges
Nothing
edgesParser
<&> IR.ConnectionEdges
@ -463,25 +465,25 @@ tableConnectionSelectionSet sourceName tableInfo = runMaybeT do
pageInfoSelectionSet =
let startCursorField =
P.selection_
$$(G.litName "startCursor")
G._startCursor
Nothing
P.string
$> IR.PageInfoStartCursor
endCursorField =
P.selection_
$$(G.litName "endCursor")
G._endCursor
Nothing
P.string
$> IR.PageInfoEndCursor
hasNextPageField =
P.selection_
$$(G.litName "hasNextPage")
G._hasNextPage
Nothing
P.boolean
$> IR.PageInfoHasNextPage
hasPreviousPageField =
P.selection_
$$(G.litName "hasPreviousPage")
G._hasPreviousPage
Nothing
P.boolean
$> IR.PageInfoHasPreviousPage
@ -492,23 +494,23 @@ tableConnectionSelectionSet sourceName tableInfo = runMaybeT do
hasPreviousPageField
]
in P.nonNullableParser $
P.selectionSet $$(G.litName "PageInfo") Nothing allFields
P.selectionSet G._PageInfo Nothing allFields
<&> parsedSelectionsToFields IR.PageInfoTypename
tableEdgesSelectionSet ::
G.Name -> m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet tableGQLName = runMaybeT do
edgeNodeParser <- MaybeT $ fmap P.nonNullableParser <$> tableSelectionSet sourceName tableInfo
edgesType <- lift $ P.mkTypename $ tableGQLName <> $$(G.litName "Edge")
edgesType <- lift $ P.mkTypename $ tableGQLName <> G._Edge
let cursor =
P.selection_
$$(G.litName "cursor")
G._cursor
Nothing
P.string
$> IR.EdgeCursor
edgeNode =
P.subselection_
$$(G.litName "node")
G._node
Nothing
edgeNodeParser
<&> IR.EdgeNode
@ -577,7 +579,7 @@ selectFunctionAggregate sourceName fi@FunctionInfo {..} description = runMaybeT
tableArgsParser <- tableArguments sourceName tableInfo
functionArgsParser <- customSQLFunctionArgs fi _fiGQLAggregateName _fiGQLArgsName
aggregateParser <- tableAggregationFields sourceName tableInfo
selectionName <- P.mkTypename =<< pure (tableGQLName <> $$(G.litName "_aggregate"))
selectionName <- P.mkTypename =<< pure (tableGQLName <> G.__aggregate)
aggregateFieldName <- mkRootFieldName _fiGQLAggregateName
let argsParser = liftA2 (,) functionArgsParser tableArgsParser
aggregationParser =
@ -586,8 +588,8 @@ selectFunctionAggregate sourceName fi@FunctionInfo {..} description = runMaybeT
P.selectionSet
selectionName
Nothing
[ IR.TAFNodes xNodesAgg <$> P.subselection_ $$(G.litName "nodes") Nothing nodesParser,
IR.TAFAgg <$> P.subselection_ $$(G.litName "aggregate") Nothing aggregateParser
[ IR.TAFNodes xNodesAgg <$> P.subselection_ G._nodes Nothing nodesParser,
IR.TAFAgg <$> P.subselection_ G._aggregate Nothing aggregateParser
]
pure $
P.subselection aggregateFieldName description argsParser aggregationParser
@ -619,7 +621,7 @@ selectFunctionConnection sourceName fi@FunctionInfo {..} description pkeyColumns
tableInfo <- lift $ askTableInfo sourceName _fiReturnType
selectionSetParser <- MaybeT $ tableConnectionSelectionSet sourceName tableInfo
lift do
fieldName <- mkRootFieldName $ _fiGQLName <> $$(G.litName "_connection")
fieldName <- mkRootFieldName $ _fiGQLName <> G.__connection
stringifyNum <- asks $ qcStringifyNum . getter
tableConnectionArgsParser <- tableConnectionArgs pkeyColumns sourceName tableInfo
functionArgsParser <- customSQLFunctionArgs fi _fiGQLName _fiGQLArgsName
@ -715,7 +717,7 @@ tableWhereArg sourceName tableInfo = do
P.fieldOptional whereName whereDesc $
P.nullable boolExpParser
where
whereName = $$(G.litName "where")
whereName = G._where
whereDesc = Just $ G.Description "filter the rows returned"
-- | Argument to sort rows returned from table selection
@ -734,7 +736,7 @@ tableOrderByArg sourceName tableInfo = do
P.fieldOptional orderByName orderByDesc $ P.nullable $ P.list orderByParser
pure $ maybeOrderByExps >>= NE.nonEmpty . concat
where
orderByName = $$(G.litName "order_by")
orderByName = G._order_by
orderByDesc = Just $ G.Description "sort the rows by one or more columns"
-- | Argument to distinct select on columns returned from table selection
@ -755,7 +757,7 @@ tableDistinctArg sourceName tableInfo = do
(P.fieldOptional distinctOnName distinctOnDesc . P.nullable . P.list)
pure $ maybeDistinctOnColumns >>= NE.nonEmpty
where
distinctOnName = $$(G.litName "distinct_on")
distinctOnName = G._distinct_on
distinctOnDesc = Just $ G.Description "distinct select on columns"
-- | Argument to limit rows returned from table selection
@ -769,7 +771,7 @@ tableLimitArg =
P.fieldOptional limitName limitDesc $
P.nullable P.nonNegativeInt
where
limitName = $$(G.litName "limit")
limitName = G._limit
limitDesc = Just $ G.Description "limit the number of rows returned"
-- | Argument to skip some rows, in conjunction with order_by
@ -783,7 +785,7 @@ tableOffsetArg =
P.fieldOptional offsetName offsetDesc $
P.nullable P.bigInt
where
offsetName = $$(G.litName "offset")
offsetName = G._offset
offsetDesc = Just $ G.Description "skip the first n rows. Use only with order_by"
-- | Arguments for a table connection selection
@ -813,10 +815,10 @@ tableConnectionArgs pkeyColumns sourceName tableInfo = do
whereParser <- tableWhereArg sourceName tableInfo
orderByParser <- fmap (fmap appendPrimaryKeyOrderBy) <$> tableOrderByArg sourceName tableInfo
distinctParser <- tableDistinctArg sourceName tableInfo
let maybeFirst = fmap join $ P.fieldOptional $$(G.litName "first") Nothing $ P.nullable P.nonNegativeInt
maybeLast = fmap join $ P.fieldOptional $$(G.litName "last") Nothing $ P.nullable P.nonNegativeInt
maybeAfter = fmap join $ P.fieldOptional $$(G.litName "after") Nothing $ P.nullable base64Text
maybeBefore = fmap join $ P.fieldOptional $$(G.litName "before") Nothing $ P.nullable base64Text
let maybeFirst = fmap join $ P.fieldOptional G._first Nothing $ P.nullable P.nonNegativeInt
maybeLast = fmap join $ P.fieldOptional G._last Nothing $ P.nullable P.nonNegativeInt
maybeAfter = fmap join $ P.fieldOptional G._after Nothing $ P.nullable base64Text
maybeBefore = fmap join $ P.fieldOptional G._before Nothing $ P.nullable base64Text
firstAndLast = (,) <$> maybeFirst <*> maybeLast
afterBeforeAndOrderBy = (,,) <$> maybeAfter <*> maybeBefore <*> orderByParser
@ -953,7 +955,7 @@ tableAggregationFields sourceName tableInfo = memoizeOn 'tableAggregationFields
let numericColumns = onlyNumCols allColumns
comparableColumns = onlyComparableCols allColumns
description = G.Description $ "aggregate fields of " <>> tableInfoName tableInfo
selectName <- P.mkTypename $ tableGQLName <> $$(G.litName "_aggregate_fields")
selectName <- P.mkTypename $ tableGQLName <> G.__aggregate_fields
count <- countField
mkTypename <- asks getter
numericAndComparable <-
@ -983,7 +985,7 @@ tableAggregationFields sourceName tableInfo = memoizeOn 'tableAggregationFields
where
mkNumericAggFields :: G.Name -> [ColumnInfo b] -> m [FieldParser n (IR.ColFld b)]
mkNumericAggFields name
| name == $$(G.litName "sum") = traverse mkColumnAggField
| name == G._sum = traverse mkColumnAggField
| otherwise = traverse \columnInfo ->
pure $
P.selection_
@ -1005,7 +1007,7 @@ tableAggregationFields sourceName tableInfo = memoizeOn 'tableAggregationFields
countField :: m (FieldParser n (IR.AggregateField b))
countField = do
columnsEnum <- tableSelectColumnsEnum sourceName tableInfo
let distinctName = $$(G.litName "distinct")
let distinctName = G._distinct
args = do
distinct <- P.fieldOptional distinctName Nothing P.boolean
mkCountType <- countTypeInput @b columnsEnum
@ -1016,7 +1018,7 @@ tableAggregationFields sourceName tableInfo = memoizeOn 'tableAggregationFields
(bool IR.SelectCountNonDistinct IR.SelectCountDistinct)
distinct
pure $ IR.AFCount <$> P.selection $$(G.litName "count") Nothing args P.int
pure $ IR.AFCount <$> P.selection G._count Nothing args P.int
parseAggOperator ::
P.MkTypename ->
@ -1026,7 +1028,7 @@ tableAggregationFields sourceName tableInfo = memoizeOn 'tableAggregationFields
FieldParser n (IR.AggregateField b)
parseAggOperator mkTypename operator tableGQLName columns =
let opText = G.unName operator
setName = P.runMkTypename mkTypename $ tableGQLName <> $$(G.litName "_") <> operator <> $$(G.litName "_fields")
setName = P.runMkTypename mkTypename $ tableGQLName <> G.__ <> operator <> G.__fields
setDesc = Just $ G.Description $ "aggregate " <> opText <> " on columns"
subselectionParser =
P.selectionSet setName setDesc columns
@ -1051,7 +1053,7 @@ fieldSelection sourceName table tableInfo maybePkeyColumns = \case
maybeToList <$> runMaybeT do
queryType <- asks $ qcQueryType . getter
let fieldName = ciName columnInfo
if fieldName == $$(G.litName "id") && queryType == ET.QueryRelay
if fieldName == G._id && queryType == ET.QueryRelay
then do
xRelayInfo <- hoistMaybe $ relayExtension @b
pkeyColumns <- hoistMaybe maybePkeyColumns
@ -1297,19 +1299,19 @@ relationshipField sourceName table ri = runMaybeT do
IR.ASSimple $
IR.AnnRelationSelectG (riName ri) (riMapping ri) $
deduplicatePermissions' selectExp
relAggFieldName = relFieldName <> $$(G.litName "_aggregate")
relAggFieldName = relFieldName <> G.__aggregate
relAggDesc = Just $ G.Description "An aggregate relationship"
remoteAggField <- lift $ selectTableAggregate sourceName otherTableInfo relAggFieldName relAggDesc
remoteConnectionField <- runMaybeT $ do
-- Parse array connection field only for relay schema
queryType <- asks $ qcQueryType . getter
guard $ queryType == ET.QueryRelay
xRelayInfo <- hoistMaybe $ relayExtension @b
_xRelayInfo <- hoistMaybe $ relayExtension @b
pkeyColumns <-
MaybeT $
(^? tiCoreInfo . tciPrimaryKey . _Just . pkColumns)
<$> pure otherTableInfo
let relConnectionName = relFieldName <> $$(G.litName "_connection")
let relConnectionName = relFieldName <> G.__connection
relConnectionDesc = Just $ G.Description "An array relationship connection"
MaybeT $ lift $ selectTableConnection sourceName otherTableInfo relConnectionName relConnectionDesc pkeyColumns
pure $
@ -1459,10 +1461,10 @@ functionArgs functionTrackedAs (toList -> inputArgs) = do
tableInfo <- askTableInfo sourceName tableName
computedFieldGQLName <- textToName $ computedFieldNameToText computedFieldName
tableGQLName <- getTableGQLName @b tableInfo
pure $ computedFieldGQLName <> $$(G.litName "_") <> tableGQLName <> $$(G.litName "_args")
pure $ computedFieldGQLName <> G.__ <> tableGQLName <> G.__args
FTACustomFunction (CustomFunctionNames {cfnArgsName}) ->
pure cfnArgsName
let fieldName = $$(G.litName "args")
let fieldName = G._args
fieldDesc =
case functionTrackedAs of
FTAComputedField computedFieldName _sourceName tableName ->
@ -1638,7 +1640,7 @@ nodePG ::
)
nodePG = memoizeOn 'nodePG () do
let idDescription = G.Description "A globally unique identifier"
idField = P.selection_ $$(G.litName "id") (Just idDescription) P.identifier
idField = P.selection_ G._id (Just idDescription) P.identifier
nodeInterfaceDescription = G.Description "An object with globally unique ID"
sources :: SourceCache <- asks getter
let allTables = Map.fromList $ do
@ -1659,7 +1661,7 @@ nodePG = memoizeOn 'nodePG () do
pure $ (source,sourceConfig,selectPermissions,tablePkeyColumns,) <$> annotatedFieldsParser
pure $
P.selectionSetInterface
$$(G.litName "Node")
G._Node
(Just nodeInterfaceDescription)
[idField]
tables
@ -1670,11 +1672,11 @@ nodeField ::
m (P.FieldParser n (IR.QueryRootField UnpreparedValue))
nodeField = do
let idDescription = G.Description "A globally unique id"
idArgument = P.field $$(G.litName "id") (Just idDescription) P.identifier
idArgument = P.field G._id (Just idDescription) P.identifier
stringifyNum <- asks $ qcStringifyNum . getter
nodeObject <- node
return $
P.subselection $$(G.litName "node") Nothing idArgument nodeObject
P.subselection G._node Nothing idArgument nodeObject
`P.bindField` \(ident, parseds) -> do
NodeIdV1 (V1NodeId table columnValues) <- parseNodeId ident
(source, sourceConfig, perms, pkeyColumns, fields) <-

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
-- | Helper functions for generating the schema of database tables
module Hasura.GraphQL.Schema.Table
( getTableGQLName,
@ -22,6 +20,7 @@ import Data.Text.Extended
import Hasura.Base.Error (QErr)
import Hasura.GraphQL.Parser (Kind (..), Parser)
import Hasura.GraphQL.Parser qualified as P
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.Common
import Hasura.Prelude
@ -68,7 +67,7 @@ tableSelectColumnsEnum ::
tableSelectColumnsEnum sourceName tableInfo = do
tableGQLName <- getTableGQLName @b tableInfo
columns <- tableSelectColumns sourceName tableInfo
enumName <- P.mkTypename $ tableGQLName <> $$(G.litName "_select_column")
enumName <- P.mkTypename $ tableGQLName <> G.__select_column
let description =
Just $
G.Description $
@ -98,7 +97,7 @@ tableUpdateColumnsEnum ::
tableUpdateColumnsEnum tableInfo = do
tableGQLName <- getTableGQLName tableInfo
columns <- tableUpdateColumns tableInfo
enumName <- P.mkTypename $ tableGQLName <> $$(G.litName "_update_column")
enumName <- P.mkTypename $ tableGQLName <> G.__update_column
let tableName = tableInfoName tableInfo
enumDesc = Just $ G.Description $ "update columns of table " <>> tableName
enumValues = do
@ -121,11 +120,11 @@ updateColumnsPlaceholderParser tableInfo = do
Just e -> pure $ Just <$> e
Nothing -> do
tableGQLName <- getTableGQLName tableInfo
enumName <- P.mkTypename $ tableGQLName <> $$(G.litName "_update_column")
enumName <- P.mkTypename $ tableGQLName <> G.__update_column
pure $
P.enum enumName (Just $ G.Description $ "placeholder for update columns of table " <> tableInfoName tableInfo <<> " (current role has no relevant permissions)") $
pure
( P.Definition @P.EnumValueInfo $$(G.litName "_PLACEHOLDER") (Just $ G.Description "placeholder (do not use)") P.EnumValueInfo,
( P.Definition @P.EnumValueInfo G.__PLACEHOLDER (Just $ G.Description "placeholder (do not use)") P.EnumValueInfo,
Nothing
)

View File

@ -1,4 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
-- | Validate input queries against remote schemas.
@ -12,6 +11,7 @@ import Data.HashMap.Strict.Extended qualified as HM
import Data.HashSet qualified as HS
import Data.List.NonEmpty qualified as NE
import Data.Text.Extended
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Prelude hiding (first)
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Relationships.Remote
@ -337,7 +337,7 @@ renameTypeForRelationship (relNameToTxt -> relTxt) lhsIdentifier name = do
G.mkName relTxt
`onNothing` throwError (InvalidGraphQLName relTxt)
pure $
name <> $$(G.litName "_remote_rel_") <> lhsName <> relName
name <> G.__remote_rel_ <> lhsName <> relName
-- | Convert a field name to a variable name.
hasuraFieldToVariable ::
@ -464,7 +464,7 @@ isTypeCoercible actualType expectedType =
let (actualBaseType, actualNestingLevel) = getBaseTyWithNestedLevelsCount actualType
(expectedBaseType, expectedNestingLevel) = getBaseTyWithNestedLevelsCount expectedType
in if
| expectedBaseType == $$(G.litName "ID") ->
| expectedBaseType == G._ID ->
bool
(throwError $ IDTypeJoin actualBaseType)
(pure ())

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
-- |
-- = Remote Schema Permissions Validation
--
@ -47,6 +45,7 @@ import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Text.Extended
import Hasura.Base.Error
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Prelude
import Hasura.RQL.Types hiding (GraphQLType, defaultScalars)
import Hasura.Server.Utils (englishList, isSessionVariable)
@ -169,6 +168,9 @@ data RoleBasedSchemaValidationError
UnexpectedNonMatchingNames !G.Name !G.Name !GraphQLType
deriving (Show, Eq)
{-
NOTE: Unused. Should we remove?
convertTypeDef :: G.TypeDefinition [G.Name] a -> G.TypeDefinition () a
convertTypeDef (G.TypeDefinitionInterface (G.InterfaceTypeDefinition desc name dirs flds _)) =
G.TypeDefinitionInterface $ G.InterfaceTypeDefinition desc name dirs flds ()
@ -177,6 +179,7 @@ convertTypeDef (G.TypeDefinitionInputObject inpObj) = G.TypeDefinitionInputObjec
convertTypeDef (G.TypeDefinitionEnum s) = G.TypeDefinitionEnum s
convertTypeDef (G.TypeDefinitionUnion s) = G.TypeDefinitionUnion s
convertTypeDef (G.TypeDefinitionObject s) = G.TypeDefinitionObject s
-}
{- Note [Remote Schema Argument Presets]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@ -361,21 +364,25 @@ showRoleBasedSchemaValidationError = \case
Just defaultValue -> toTxt defaultValue
Nothing -> ""
{-
NOTE: Unused. Should we remove?
presetValueScalar :: G.ScalarTypeDefinition
presetValueScalar = G.ScalarTypeDefinition Nothing $$(G.litName "PresetValue") mempty
presetValueScalar = G.ScalarTypeDefinition Nothing G._PresetValue mempty
presetDirectiveDefn :: G.DirectiveDefinition G.InputValueDefinition
presetDirectiveDefn =
G.DirectiveDefinition Nothing $$(G.litName "preset") [directiveArg] directiveLocations
G.DirectiveDefinition Nothing G._preset [directiveArg] directiveLocations
where
gType = G.TypeNamed (G.Nullability False) $ G._stdName presetValueScalar
directiveLocations = map G.DLTypeSystem [G.TSDLARGUMENT_DEFINITION, G.TSDLINPUT_FIELD_DEFINITION]
directiveArg = G.InputValueDefinition Nothing $$(G.litName "value") gType Nothing mempty
directiveArg = G.InputValueDefinition Nothing G._value gType Nothing mempty
presetDirectiveName :: G.Name
presetDirectiveName = $$(G.litName "preset")
presetDirectiveName = G._preset
-}
lookupInputType ::
G.SchemaDocument ->
@ -488,15 +495,15 @@ parsePresetDirective ::
G.Name ->
G.Directive Void ->
m (G.Value RemoteSchemaVariable)
parsePresetDirective gType parentArgName (G.Directive name args) = do
parsePresetDirective gType parentArgName (G.Directive _name args) = do
if
| Map.null args -> refute $ pure $ NoPresetArgumentFound
| otherwise -> do
val <-
onNothing (Map.lookup $$(G.litName "value") args) $
onNothing (Map.lookup G._value args) $
refute $ pure $ InvalidPresetArgument parentArgName
isStatic <-
case (Map.lookup $$(G.litName "static") args) of
case (Map.lookup G._static args) of
Nothing -> pure False
(Just (G.VBoolean b)) -> pure b
_ -> refute $ pure $ InvalidStaticValue
@ -562,7 +569,7 @@ validateDirectives providedDirectives upstreamDirectives directiveLocation paren
where
upstreamDirectivesMap = mapFromL G._dName upstreamDirectives
presetFilterFn = (== $$(G.litName "preset")) . G._dName
presetFilterFn = (== G._preset) . G._dName
presetDirectives = filter presetFilterFn providedDirectives
@ -903,7 +910,7 @@ getSchemaDocIntrospection providedTypeDefns (queryRoot, mutationRoot, subscripti
G.TypeDefinitionUnion union' -> pure $ G.TypeDefinitionUnion union'
G.TypeDefinitionInputObject inpObj -> pure $ G.TypeDefinitionInputObject inpObj
remoteSchemaIntrospection = RemoteSchemaIntrospection $ Map.fromListOn getTypeName modifiedTypeDefns
in IntrospectionResult remoteSchemaIntrospection (fromMaybe $$(G.litName "Query") queryRoot) mutationRoot subscriptionRoot
in IntrospectionResult remoteSchemaIntrospection (fromMaybe G._Query queryRoot) mutationRoot subscriptionRoot
-- | validateRemoteSchema accepts two arguments, the `SchemaDocument` of
-- the role-based schema, that is provided by the user and the `SchemaIntrospection`

View File

@ -1,5 +1,4 @@
{-# LANGUAGE Arrows #-}
{-# LANGUAGE TemplateHaskell #-}
-- | Description: Create/delete SQL tables to/from Hasura metadata.
module Hasura.RQL.DDL.Schema.Table
@ -37,6 +36,7 @@ import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Context
import Hasura.GraphQL.Namespace
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Schema.Common (purgeDependencies, textToName)
import Hasura.Incremental qualified as Inc
import Hasura.Prelude
@ -143,25 +143,25 @@ checkConflictingNode sc tnGQL = do
[ G.SelectionField $
G.Field
Nothing
$$(G.litName "__schema")
G.___schema
mempty
[]
[ G.SelectionField $
G.Field
Nothing
$$(G.litName "queryType")
G._queryType
mempty
[]
[ G.SelectionField $
G.Field
Nothing
$$(G.litName "fields")
G._fields
mempty
[]
[ G.SelectionField $
G.Field
Nothing
$$(G.litName "name")
G._name
mempty
[]
[]
@ -172,7 +172,7 @@ checkConflictingNode sc tnGQL = do
case queryParser introspectionQuery of
Left _ -> pure ()
Right results -> do
case OMap.lookup (mkUnNamespacedRootFieldAlias $$(G.litName "__schema")) results of
case OMap.lookup (mkUnNamespacedRootFieldAlias G.___schema) results of
Just (RFRaw (JO.Object schema)) -> do
let names = do
JO.Object queryType <- JO.lookup "queryType" schema

View File

@ -39,6 +39,7 @@ import Data.HashMap.Strict qualified as Map
import Data.HashMap.Strict.InsOrd.Extended qualified as OMap
import Data.HashSet qualified as Set
import Data.List.Extended (longestCommonPrefix)
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Schema as G (InputValue)
import Hasura.Prelude
import Hasura.RQL.Types.Common (FieldName)
@ -89,7 +90,7 @@ mkInterfaceSelectionSet ::
DeduplicatedSelectionSet r var
mkInterfaceSelectionSet interfaceFields selectionSets =
DeduplicatedSelectionSet
(Set.insert $$(G.litName "__typename") interfaceFields)
(Set.insert G.___typename interfaceFields)
(Map.fromList selectionSets)
-- | Constructs an 'UnionSelectionSet' from a list of the fields, using a
@ -100,7 +101,7 @@ mkUnionSelectionSet ::
DeduplicatedSelectionSet r var
mkUnionSelectionSet selectionSets =
DeduplicatedSelectionSet
(Set.singleton $$(G.litName "__typename"))
(Set.singleton G.___typename)
(Map.fromList selectionSets)
-- | Representation of one individual field.

View File

@ -25,6 +25,7 @@ import Data.HashMap.Strict.Extended qualified as M
import Data.HashMap.Strict.InsOrd.Extended qualified as OM
import Data.HashSet qualified as S
import Data.Text.Extended ((<<>))
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Prelude
import Hasura.RQL.Types.QueryCollection
import Hasura.Session (RoleName)
@ -150,7 +151,7 @@ normalizeQuery =
filterSel :: G.Selection frag var' -> Maybe (G.Selection frag var')
filterSel s = case s of
G.SelectionField f ->
if G._fName f == $$(G.litName "__typename")
if G._fName f == G.___typename
then Nothing
else
let newSelset = filterSelSet $ G._fSelectionSet f

View File

@ -53,7 +53,6 @@ module Hasura.RQL.Types.Common
)
where
import Control.Lens (makeLenses)
import Data.Aeson
import Data.Aeson.Casing
import Data.Aeson.TH
@ -68,6 +67,7 @@ import Data.URL.Template
import Database.PG.Query qualified as Q
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.DDL.Headers ()
@ -362,7 +362,6 @@ instance Cacheable PGConnectionParams
instance Hashable PGConnectionParams
$(makeLenses ''PGConnectionParams)
$(deriveToJSON hasuraJSON {omitNothingFields = True} ''PGConnectionParams)
instance FromJSON PGConnectionParams where
@ -485,11 +484,11 @@ getEnv env k = do
-- default scalar names
intScalar, floatScalar, stringScalar, boolScalar, idScalar :: G.Name
intScalar = $$(G.litName "Int")
floatScalar = $$(G.litName "Float")
stringScalar = $$(G.litName "String")
boolScalar = $$(G.litName "Boolean")
idScalar = $$(G.litName "ID")
intScalar = G._Int
floatScalar = G._Float
stringScalar = G._String
boolScalar = G._Boolean
idScalar = G._ID
-- | Various user-controlled configuration for metrics used by Pro
data MetricsConfig = MetricsConfig

View File

@ -51,6 +51,7 @@ import Data.List.Extended as LE
import Data.Sequence qualified as Seq
import Data.Text qualified as T
import Data.Text.Extended
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.Types.Backend
@ -236,7 +237,7 @@ getFunctionArgsGQLName ::
getFunctionArgsGQLName
funcGivenName
FunctionConfig {..} =
fromMaybe funcGivenName _fcCustomName <> $$(G.litName "_args")
fromMaybe funcGivenName _fcCustomName <> G.__args
-- | Apply function name customization to the basic function variation, as
-- detailed in 'rfcs/function-root-field-customisation.md'.
@ -270,9 +271,9 @@ getFunctionAggregateGQLName
} =
choice
[ _fcrfFunctionAggregate,
_fcCustomName <&> (<> $$(G.litName "_aggregate"))
_fcCustomName <&> (<> G.__aggregate)
]
& fromMaybe (funcGivenName <> $$(G.litName "_aggregate"))
& fromMaybe (funcGivenName <> G.__aggregate)
getInputArgs :: FunctionInfo b -> Seq.Seq (FunctionArg b)
getInputArgs =

View File

@ -96,6 +96,7 @@ import Data.Text qualified as T
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as PG (PGDescription)
import Hasura.Base.Error
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
@ -278,7 +279,7 @@ fieldInfoGraphQLNames info = case info of
name <- fieldInfoGraphQLName info
pure $ case riType relationshipInfo of
ObjRel -> [name]
ArrRel -> [name, name <> $$(G.litName "_aggregate")]
ArrRel -> [name, name <> G.__aggregate]
FIComputedField _ -> maybeToList $ fieldInfoGraphQLName info
FIRemoteRelationship _ -> maybeToList $ fieldInfoGraphQLName info

View File

@ -1,5 +1,3 @@
{-# LANGUAGE TemplateHaskell #-}
module Hasura.Server.Rest
( runCustomEndpoint,
RestRequest (..),
@ -22,6 +20,7 @@ import Hasura.GraphQL.Execute qualified as E
import Hasura.GraphQL.Execute.Backend qualified as EB
import Hasura.GraphQL.Logging (MonadQueryLog)
import Hasura.GraphQL.ParameterizedQueryHash (ParameterizedQueryHashList (..))
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Transport.HTTP qualified as GH
import Hasura.GraphQL.Transport.HTTP.Protocol
import Hasura.HTTP
@ -66,22 +65,22 @@ resolveVar varName (These expectedVar providedVar) =
(Just J.Null, True) -> pure Nothing
(decoded, _)
| typeName == boolScalar && T.null l -> Right $ Just $ J.Bool True -- Key present but value missing for bools defaults to True.
| typeName == $$(G.litName "UUID") -> Right $ Just $ J.String l
| typeName == $$(G.litName "uuid") -> Right $ Just $ J.String l
| typeName == G._UUID -> Right $ Just $ J.String l
| typeName == G._uuid -> Right $ Just $ J.String l
| typeName == idScalar -> Right $ Just $ J.String l -- "ID" -- Note: Console doesn't expose this as a column type.
| otherwise -> case decoded of
(Just J.Null) -> Left $ "Null or missing value for non-nullable variable: " <> G.unName varName
(Just x@(J.Bool _))
| typeName == boolScalar -> pure $ Just x -- "Boolean"
| typeName == $$(G.litName "Bool") -> pure $ Just x
| typeName == G._Bool -> pure $ Just x
| otherwise -> Left $ "Expected " <> toTxt typeName <> " for variable " <> G.unName varName <> " got Bool"
(Just x@(J.Number _))
| typeName == intScalar -> pure $ Just x -- "Int"
| typeName == floatScalar -> pure $ Just x -- "Float"
| typeName == $$(G.litName "Number") -> pure $ Just x
| typeName == $$(G.litName "Double") -> pure $ Just x
| typeName == $$(G.litName "float8") -> pure $ Just x
| typeName == $$(G.litName "numeric") -> pure $ Just x
| typeName == G._Number -> pure $ Just x
| typeName == G._Double -> pure $ Just x
| typeName == G._float8 -> pure $ Just x
| typeName == G._numeric -> pure $ Just x
| otherwise -> Left $ "Expected " <> toTxt typeName <> " for variable " <> G.unName varName <> " got Number"
_ -> Left ("Type of URL parameter for variable " <> G.unName varName <> " not supported - Consider putting it in the request body: " <> tshow l)
-- TODO: This is a fallthrough case and is still required

View File

@ -1,5 +1,4 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Schema.RemoteTest (spec) where
@ -16,6 +15,7 @@ import Hasura.GraphQL.Execute.Remote (resolveRemoteVariable, runVariableCache)
import Hasura.GraphQL.Execute.Resolve
import Hasura.GraphQL.Namespace
import Hasura.GraphQL.Parser.Column (UnpreparedValue)
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
import Hasura.GraphQL.Parser.Monad
import Hasura.GraphQL.Parser.Schema
@ -70,12 +70,12 @@ mkTestRemoteSchema schema = RemoteSchemaIntrospection $
_rsitdPresetArgument =
choice $
G._ivdDirectives ivd <&> \dir -> do
guard $ G._dName dir == $$(G.litName "preset")
value <- M.lookup $$(G.litName "value") $ G._dArguments dir
guard $ G._dName dir == G._preset
value <- M.lookup G._value $ G._dArguments dir
Just $ case value of
G.VString "x-hasura-test" ->
G.VVariable $
SessionPresetVariable (mkSessionVariable "x-hasura-test") $$(G.litName "String") SessionArgumentPresetScalar
SessionPresetVariable (mkSessionVariable "x-hasura-test") G._String SessionArgumentPresetScalar
_ -> absurd <$> value
}
@ -108,7 +108,7 @@ buildQueryParsers ::
RemoteSchemaIntrospection ->
IO (P.FieldParser TestMonad (GraphQLField (RemoteRelationshipField UnpreparedValue) RemoteSchemaVariable))
buildQueryParsers introspection = do
let introResult = IntrospectionResult introspection $$(G.litName "Query") Nothing Nothing
let introResult = IntrospectionResult introspection G._Query Nothing Nothing
remoteSchemaInfo = RemoteSchemaInfo (ValidatedRemoteSchemaDef N.nullURI [] False 60 Nothing) identityCustomizer
remoteSchemaRels = mempty
-- Since remote schemas can theoretically join against tables, we need to
@ -219,13 +219,13 @@ query($a: A!) {
|]
let arg = head $ M.toList $ _fArguments field
arg
`shouldBe` ( $$(G.litName "a"),
`shouldBe` ( G._a,
-- the parser did not create a new JSON variable, and forwarded the query variable unmodified
G.VVariable $
QueryVariable $
Variable
(VIRequired $$(G.litName "a"))
(G.TypeNamed (G.Nullability False) $$(G.litName "A"))
(VIRequired G._a)
(G.TypeNamed (G.Nullability False) G._A)
(JSONValue $ J.Object $ M.fromList [("b", J.Object $ M.fromList [("c", J.Object $ M.fromList [("i", J.Number 0)])])])
)
@ -273,12 +273,12 @@ query($a: A) {
|]
let arg = head $ M.toList $ _fArguments field
arg
`shouldBe` ( $$(G.litName "a"),
`shouldBe` ( G._a,
-- fieldOptional has peeled the variable; all we see is a JSON blob, and in doubt
-- we repackage it as a newly minted JSON variable
G.VVariable $
RemoteJSONValue
(G.TypeNamed (G.Nullability True) $$(G.litName "A"))
(G.TypeNamed (G.Nullability True) G._A)
(J.Object $ M.fromList [("b", J.Object $ M.fromList [("c", J.Object $ M.fromList [("i", J.Number 0)])])])
)
@ -327,17 +327,17 @@ query($a: A!) {
|]
let arg = head $ M.toList $ _fArguments field
arg
`shouldBe` ( $$(G.litName "a"),
`shouldBe` ( G._a,
-- the preset has caused partial variable expansion, only up to where it's needed
G.VObject $
M.fromList
[ ( $$(G.litName "x"),
[ ( G._x,
G.VInt 0
),
( $$(G.litName "b"),
( G._b,
G.VVariable $
RemoteJSONValue
(G.TypeNamed (G.Nullability True) $$(G.litName "B"))
(G.TypeNamed (G.Nullability True) G._B)
(J.Object $ M.fromList [("c", J.Object $ M.fromList [("i", J.Number 0)])])
)
]

View File

@ -1,7 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Hasura.StreamingSubscriptionSpec (buildStreamingSubscriptionsSpec) where
@ -27,6 +26,7 @@ import Hasura.GraphQL.Execute.Subscription.Poll.StreamingQuery (pollStreamingQue
import Hasura.GraphQL.Execute.Subscription.State
import Hasura.GraphQL.Execute.Subscription.TMap qualified as TMap
import Hasura.GraphQL.ParameterizedQueryHash
import Hasura.GraphQL.Parser.Constants qualified as G
import Hasura.GraphQL.Transport.WebSocket.Protocol (unsafeMkOperationId)
import Hasura.GraphQL.Transport.WebSocket.Server qualified as WS
import Hasura.Logging
@ -179,7 +179,7 @@ streamingSubscriptionPollingSpec srcConfig = do
(subscriberId1, subscriberId2) <- runIO $ (,) <$> newSubscriberId <*> newSubscriberId
let subscriber1 = mkSubscriber subscriberId1
subscriber2 = mkSubscriber subscriberId2
let initialCursorValue = Map.singleton $$(G.litName "id") (TELit "1")
let initialCursorValue = Map.singleton G._id (TELit "1")
cohort1 <- runIO $
liftIO $
STM.atomically $ do