2021-06-15 18:53:20 +03:00
|
|
|
{- | This module defines the BackendSchema class, that a backend must implement
|
|
|
|
for its schema to be generated. From the top level of the schema down to its
|
|
|
|
leaf values, every component has a matching function in the
|
|
|
|
schema. Combinators in other modules provide a default implementation at all
|
|
|
|
layers.
|
|
|
|
|
|
|
|
Consider, for example, the following query, for a given table "author":
|
|
|
|
|
|
|
|
query {
|
|
|
|
author(where: {id: {_eq: 2}}) {
|
|
|
|
name
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
The chain of functions leading to a parser for this RootField will be along
|
|
|
|
the lines of:
|
|
|
|
|
|
|
|
> buildTableQueryFields
|
|
|
|
> selectTable
|
|
|
|
> tableArgs
|
|
|
|
> tableWhere
|
|
|
|
> boolExp
|
|
|
|
> comparisonExp
|
|
|
|
> columnParser
|
|
|
|
> tableSelectionSet
|
|
|
|
> fieldSelection
|
|
|
|
|
|
|
|
Several of those steps are part of the class, meaning that a backend can
|
|
|
|
customize part of this tree without having to reimplement all of it. For
|
|
|
|
instance, a backend that supports a different set ot table arguments can
|
|
|
|
choose to reimplement @tableArgs@, but can still use @tableWhere@ in its
|
|
|
|
custom implementation.
|
|
|
|
-}
|
|
|
|
|
2020-12-01 18:50:18 +03:00
|
|
|
module Hasura.GraphQL.Schema.Backend where
|
|
|
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
2021-02-03 19:17:20 +03:00
|
|
|
import qualified Language.GraphQL.Draft.Syntax as G
|
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
import Data.Has
|
2021-02-03 19:17:20 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax (Nullability)
|
2020-12-01 18:50:18 +03:00
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
import qualified Hasura.RQL.IR.Select as IR
|
2021-01-08 22:45:33 +03:00
|
|
|
import qualified Hasura.RQL.IR.Update as IR
|
2020-12-01 18:50:18 +03:00
|
|
|
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2021-02-03 19:17:20 +03:00
|
|
|
import Hasura.GraphQL.Parser
|
2020-12-01 18:50:18 +03:00
|
|
|
import Hasura.GraphQL.Schema.Common
|
2021-06-11 06:26:50 +03:00
|
|
|
import Hasura.RQL.IR
|
2020-12-28 15:56:00 +03:00
|
|
|
import Hasura.RQL.Types hiding (EnumValueInfo)
|
2020-12-01 18:50:18 +03:00
|
|
|
|
|
|
|
|
2021-02-03 19:17:20 +03:00
|
|
|
-- TODO: it might make sense to add those constraints to MonadSchema directly?
|
|
|
|
type MonadBuildSchema b r m n =
|
|
|
|
( Backend b
|
|
|
|
, BackendSchema b
|
|
|
|
, MonadError QErr m
|
|
|
|
, MonadSchema n m
|
|
|
|
, MonadTableInfo r m
|
|
|
|
, MonadRole r m
|
|
|
|
, Has QueryContext r
|
|
|
|
)
|
|
|
|
|
2020-12-01 18:50:18 +03:00
|
|
|
class Backend b => BackendSchema (b :: BackendType) where
|
2021-02-03 19:17:20 +03:00
|
|
|
-- top level parsers
|
|
|
|
buildTableQueryFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> TableName b
|
|
|
|
-> TableInfo b
|
|
|
|
-> G.Name
|
|
|
|
-> SelPermInfo b
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (QueryRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildTableRelayQueryFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> TableName b
|
|
|
|
-> TableInfo b
|
|
|
|
-> G.Name
|
|
|
|
-> NESeq (ColumnInfo b)
|
|
|
|
-> SelPermInfo b
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (QueryRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildTableInsertMutationFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> TableName b
|
|
|
|
-> TableInfo b
|
|
|
|
-> G.Name
|
|
|
|
-> InsPermInfo b
|
|
|
|
-> Maybe (SelPermInfo b)
|
|
|
|
-> Maybe (UpdPermInfo b)
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (MutationRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildTableUpdateMutationFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> TableName b
|
|
|
|
-> TableInfo b
|
|
|
|
-> G.Name
|
|
|
|
-> UpdPermInfo b
|
|
|
|
-> Maybe (SelPermInfo b)
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (MutationRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildTableDeleteMutationFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> TableName b
|
|
|
|
-> TableInfo b
|
|
|
|
-> G.Name
|
|
|
|
-> DelPermInfo b
|
|
|
|
-> Maybe (SelPermInfo b)
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (MutationRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildFunctionQueryFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> FunctionName b
|
|
|
|
-> FunctionInfo b
|
|
|
|
-> TableName b
|
|
|
|
-> SelPermInfo b
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (QueryRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildFunctionRelayQueryFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> FunctionName b
|
|
|
|
-> FunctionInfo b
|
|
|
|
-> TableName b
|
|
|
|
-> NESeq (ColumnInfo b)
|
|
|
|
-> SelPermInfo b
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (QueryRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
buildFunctionMutationFields
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> SourceConfig b
|
|
|
|
-> FunctionName b
|
|
|
|
-> FunctionInfo b
|
|
|
|
-> TableName b
|
|
|
|
-> SelPermInfo b
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-> m [FieldParser n (MutationRootField UnpreparedValue UnpreparedValue)]
|
2021-02-03 19:17:20 +03:00
|
|
|
|
2021-06-15 18:53:20 +03:00
|
|
|
-- table components
|
|
|
|
tableArguments
|
|
|
|
:: MonadBuildSchema b r m n
|
|
|
|
=> SourceName
|
|
|
|
-> TableInfo b
|
|
|
|
-> SelPermInfo b
|
|
|
|
-> m (InputFieldsParser n (IR.SelectArgsG b (UnpreparedValue b)))
|
|
|
|
|
2021-02-03 19:17:20 +03:00
|
|
|
-- backend extensions
|
2021-06-09 16:02:15 +03:00
|
|
|
relayExtension :: Maybe (XRelay b)
|
|
|
|
nodesAggExtension :: Maybe (XNodesAgg b)
|
2021-02-03 19:17:20 +03:00
|
|
|
|
|
|
|
-- individual components
|
2020-12-01 18:50:18 +03:00
|
|
|
columnParser
|
|
|
|
:: (MonadSchema n m, MonadError QErr m)
|
|
|
|
=> ColumnType b
|
|
|
|
-> Nullability
|
|
|
|
-> m (Parser 'Both n (Opaque (ColumnValue b)))
|
|
|
|
-- | The "path" argument for json column fields
|
|
|
|
jsonPathArg
|
|
|
|
:: MonadParse n
|
|
|
|
=> ColumnType b
|
|
|
|
-> InputFieldsParser n (Maybe (IR.ColumnOp b))
|
|
|
|
orderByOperators
|
|
|
|
:: NonEmpty (Definition EnumValueInfo, (BasicOrderType b, NullsOrderType b))
|
|
|
|
comparisonExps
|
2021-04-08 11:25:11 +03:00
|
|
|
:: MonadBuildSchema b r m n
|
2020-12-01 18:50:18 +03:00
|
|
|
=> ColumnType b
|
|
|
|
-> m (Parser 'Input n [ComparisonExp b])
|
2021-01-08 22:45:33 +03:00
|
|
|
updateOperators
|
2021-01-20 03:31:53 +03:00
|
|
|
:: (MonadSchema n m, MonadTableInfo r m)
|
2021-05-18 16:06:42 +03:00
|
|
|
=> TableInfo b
|
2021-01-08 22:45:33 +03:00
|
|
|
-> UpdPermInfo b
|
|
|
|
-> m (Maybe (InputFieldsParser n [(Column b, IR.UpdOpExpG (UnpreparedValue b))]))
|
2020-12-01 18:50:18 +03:00
|
|
|
mkCountType :: Maybe Bool -> Maybe [Column b] -> CountType b
|
|
|
|
aggregateOrderByCountType :: ScalarType b
|
|
|
|
-- | Computed field parser
|
|
|
|
computedField
|
2021-02-03 19:17:20 +03:00
|
|
|
:: MonadBuildSchema b r m n
|
2021-05-18 16:06:42 +03:00
|
|
|
=> SourceName
|
|
|
|
-> ComputedFieldInfo b
|
2021-05-20 09:28:35 +03:00
|
|
|
-> TableName b
|
2020-12-01 18:50:18 +03:00
|
|
|
-> SelPermInfo b
|
|
|
|
-> m (Maybe (FieldParser n (AnnotatedField b)))
|
|
|
|
-- | The 'node' root field of a Relay request.
|
|
|
|
node
|
2021-02-03 19:17:20 +03:00
|
|
|
:: MonadBuildSchema b r m n
|
2020-12-28 15:56:00 +03:00
|
|
|
=> m (Parser 'Output n (HashMap (TableName b) (SourceName, SourceConfig b, SelPermInfo b, PrimaryKeyColumns b, AnnotatedFields b)))
|
2020-12-01 18:50:18 +03:00
|
|
|
|
2021-02-08 13:39:59 +03:00
|
|
|
-- SQL literals
|
|
|
|
columnDefaultValue :: Column b -> SQLExpression b
|
|
|
|
|
2020-12-01 18:50:18 +03:00
|
|
|
type ComparisonExp b = OpExpG b (UnpreparedValue b)
|
2021-02-03 19:17:20 +03:00
|
|
|
|
|
|
|
data BackendExtension b = BackendExtension
|
|
|
|
{ backendRelay :: Maybe (XRelay b)
|
|
|
|
, backendNodesAgg :: Maybe (XNodesAgg b)
|
|
|
|
}
|