2021-12-15 20:07:21 +03:00
|
|
|
{-# LANGUAGE ApplicativeDo #-}
|
2022-06-08 02:24:42 +03:00
|
|
|
{-# LANGUAGE PatternGuards #-}
|
2022-04-27 16:57:28 +03:00
|
|
|
{-# LANGUAGE TemplateHaskellQuotes #-}
|
2021-12-15 20:07:21 +03:00
|
|
|
|
2022-02-08 12:24:34 +03:00
|
|
|
-- | Postgres Schema OnConflict
|
|
|
|
--
|
|
|
|
-- This module contains the building blocks for parsing @on_conflict@ clauses,
|
2021-12-15 20:07:21 +03:00
|
|
|
-- which in the Postgres backend are used to implement upsert functionality.
|
|
|
|
-- These are used by 'Hasura.Backends.Postgres.Instances.Schema.backendInsertParser' to
|
|
|
|
-- construct a postgres-specific schema parser for insert (and upsert) mutations.
|
|
|
|
module Hasura.Backends.Postgres.Schema.OnConflict
|
|
|
|
( onConflictFieldParser,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2022-05-26 14:54:30 +03:00
|
|
|
import Data.Has (getter)
|
2022-06-08 02:24:42 +03:00
|
|
|
import Data.HashMap.Strict qualified as HM
|
|
|
|
import Data.HashSet qualified as HS
|
2021-12-15 20:07:21 +03:00
|
|
|
import Data.Text.Extended
|
2022-06-08 02:24:42 +03:00
|
|
|
import Hasura.Backends.Postgres.SQL.Types (showPGCols)
|
2021-12-15 20:07:21 +03:00
|
|
|
import Hasura.GraphQL.Parser
|
|
|
|
( InputFieldsParser,
|
|
|
|
Kind (..),
|
|
|
|
Parser,
|
|
|
|
)
|
|
|
|
import Hasura.GraphQL.Parser qualified as P
|
|
|
|
import Hasura.GraphQL.Parser.Class
|
|
|
|
import Hasura.GraphQL.Schema.Backend
|
|
|
|
import Hasura.GraphQL.Schema.BoolExp
|
|
|
|
import Hasura.GraphQL.Schema.Common
|
|
|
|
import Hasura.GraphQL.Schema.Table
|
2022-06-23 12:14:24 +03:00
|
|
|
import Hasura.Name qualified as Name
|
2021-12-15 20:07:21 +03:00
|
|
|
import Hasura.Prelude
|
2022-05-31 01:07:02 +03:00
|
|
|
import Hasura.RQL.IR.BoolExp qualified as IR
|
2021-12-15 20:07:21 +03:00
|
|
|
import Hasura.RQL.IR.Insert qualified as IR
|
2022-05-31 01:07:02 +03:00
|
|
|
import Hasura.RQL.IR.Value qualified as IR
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.SchemaCache
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
import Hasura.RQL.Types.Source
|
2022-05-26 14:54:30 +03:00
|
|
|
import Hasura.RQL.Types.SourceCustomization (applyFieldNameCaseCust)
|
2022-04-27 16:57:28 +03:00
|
|
|
import Hasura.RQL.Types.Table
|
|
|
|
import Hasura.SQL.Backend
|
2021-12-15 20:07:21 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
|
|
|
|
-- | Parser for a field name @on_conflict@ of type @tablename_on_conflict@.
|
|
|
|
--
|
|
|
|
-- The @tablename_on_conflict@ object is used to generate the @ON CONFLICT@
|
|
|
|
-- SQL clause, indicating what should be done if an insert raises a conflict.
|
|
|
|
--
|
|
|
|
-- The types ordinarily produced by this parser are only created if the table has
|
|
|
|
-- unique or primary keys constraints.
|
|
|
|
--
|
|
|
|
-- If there are no columns for which the current role has update permissions, we
|
2022-06-08 02:24:42 +03:00
|
|
|
-- must still accept an empty list for @update_columns@ to support the "ON
|
|
|
|
-- CONFLICT DO NOTHING" case. We do this by adding a placeholder value to the
|
2021-12-15 20:07:21 +03:00
|
|
|
-- enum. See <https://github.com/hasura/graphql-engine/issues/6804>.
|
|
|
|
onConflictFieldParser ::
|
|
|
|
forall pgKind r m n.
|
|
|
|
MonadBuildSchema ('Postgres pgKind) r m n =>
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
SourceInfo ('Postgres pgKind) ->
|
2021-12-15 20:07:21 +03:00
|
|
|
TableInfo ('Postgres pgKind) ->
|
2022-05-31 01:07:02 +03:00
|
|
|
m (InputFieldsParser n (Maybe (IR.OnConflictClause ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind)))))
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
onConflictFieldParser sourceInfo tableInfo = do
|
2022-05-26 14:54:30 +03:00
|
|
|
tCase <- asks getter
|
2022-06-08 02:24:42 +03:00
|
|
|
permissions <- tablePermissions tableInfo
|
2021-12-15 20:07:21 +03:00
|
|
|
let maybeConstraints = tciUniqueOrPrimaryKeyConstraints . _tiCoreInfo $ tableInfo
|
2022-06-08 02:24:42 +03:00
|
|
|
maybeConflictObject = conflictObjectParser sourceInfo tableInfo (_permUpd permissions) <$> maybeConstraints
|
2021-12-15 20:07:21 +03:00
|
|
|
case maybeConflictObject of
|
2022-06-23 12:14:24 +03:00
|
|
|
Just conflictObject -> conflictObject <&> P.fieldOptional (applyFieldNameCaseCust tCase Name._on_conflict) (Just "upsert condition")
|
2021-12-15 20:07:21 +03:00
|
|
|
Nothing -> return $ pure Nothing
|
|
|
|
|
|
|
|
-- | Create a parser for the @_on_conflict@ object of the given table.
|
|
|
|
conflictObjectParser ::
|
|
|
|
forall pgKind r m n.
|
|
|
|
MonadBuildSchema ('Postgres pgKind) r m n =>
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
SourceInfo ('Postgres pgKind) ->
|
2021-12-15 20:07:21 +03:00
|
|
|
TableInfo ('Postgres pgKind) ->
|
2022-06-08 02:24:42 +03:00
|
|
|
Maybe (UpdPermInfo ('Postgres pgKind)) ->
|
|
|
|
NonEmpty (UniqueConstraint ('Postgres pgKind)) ->
|
2022-05-31 01:07:02 +03:00
|
|
|
m (Parser 'Input n (IR.OnConflictClause ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind))))
|
2022-06-08 02:24:42 +03:00
|
|
|
conflictObjectParser sourceInfo tableInfo maybeUpdatePerms constraints = do
|
Role-invariant schema constructors
We build the GraphQL schema by combining building blocks such as `tableSelectionSet` and `columnParser`. These building blocks individually build `{InputFields,Field,}Parser` objects. Those object specify the valid GraphQL schema.
Since the GraphQL schema is role-dependent, at some point we need to know what fragment of the GraphQL schema a specific role is allowed to access, and this is stored in `{Sel,Upd,Ins,Del}PermInfo` objects.
We have passed around these permission objects as function arguments to the schema building blocks since we first started dealing with permissions during the PDV refactor - see hasura/graphql-engine@5168b99e463199b1934d8645bd6cd37eddb64ae1 in hasura/graphql-engine#4111. This means that, for instance, `tableSelectionSet` has as its type:
```haskell
tableSelectionSet ::
forall b r m n.
MonadBuildSchema b r m n =>
SourceName ->
TableInfo b ->
SelPermInfo b ->
m (Parser 'Output n (AnnotatedFields b))
```
There are three reasons to change this.
1. We often pass a `Maybe (xPermInfo b)` instead of a proper `xPermInfo b`, and it's not clear what the intended semantics of this is. Some potential improvements on the data types involved are discussed in issue hasura/graphql-engine-mono#3125.
2. In most cases we also already pass a `TableInfo b`, and together with the `MonadRole` that is usually also in scope, this means that we could look up the required permissions regardless: so passing the permissions explicitly undermines the "single source of truth" principle. Breaking this principle also makes the code more difficult to read.
3. We are working towards role-based parsers (see hasura/graphql-engine-mono#2711), where the `{InputFields,Field,}Parser` objects are constructed in a role-invariant way, so that we have a single object that can be used for all roles. In particular, this means that the schema building blocks _need_ to be constructed in a role-invariant way. While this PR doesn't accomplish that, it does reduce the amount of role-specific arguments being passed, thus fixing hasura/graphql-engine-mono#3068.
Concretely, this PR simply drops the `xPermInfo b` argument from almost all schema building blocks. Instead these objects are looked up from the `TableInfo b` as-needed. The resulting code is considerably simpler and shorter.
One way to interpret this change is as follows. Before this PR, we figured out permissions at the top-level in `Hasura.GraphQL.Schema`, passing down the obtained `xPermInfo` objects as required. After this PR, we have a bottom-up approach where the schema building blocks themselves decide whether they want to be included for a particular role.
So this moves some permission logic out of `Hasura.GraphQL.Schema`, which is very complex.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3608
GitOrigin-RevId: 51a744f34ec7d57bc8077667ae7f9cb9c4f6c962
2022-02-17 11:16:20 +03:00
|
|
|
updateColumnsEnum <- updateColumnsPlaceholderParser tableInfo
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
constraintParser <- conflictConstraint constraints sourceInfo tableInfo
|
|
|
|
whereExpParser <- boolExp sourceInfo tableInfo
|
2021-12-15 20:07:21 +03:00
|
|
|
tableGQLName <- getTableGQLName tableInfo
|
2022-06-23 12:14:24 +03:00
|
|
|
objectName <- P.mkTypename $ tableGQLName <> Name.__on_conflict
|
2021-12-15 20:07:21 +03:00
|
|
|
|
2022-06-08 02:24:42 +03:00
|
|
|
let objectDesc = G.Description $ "on_conflict condition type for table " <>> tableName
|
|
|
|
(presetColumns, updateFilter) = fromMaybe (HM.empty, IR.gBoolExpTrue) $ do
|
|
|
|
UpdPermInfo {..} <- maybeUpdatePerms
|
|
|
|
pure
|
|
|
|
( partialSQLExpToUnpreparedValue <$> upiSet,
|
|
|
|
fmap partialSQLExpToUnpreparedValue <$> upiFilter
|
|
|
|
)
|
2021-12-15 20:07:21 +03:00
|
|
|
|
|
|
|
pure $
|
|
|
|
P.object objectName (Just objectDesc) $ do
|
2022-06-23 12:14:24 +03:00
|
|
|
constraintField <- P.field Name._constraint Nothing constraintParser
|
|
|
|
let updateColumnsField = P.fieldWithDefault Name._update_columns Nothing (G.VList []) (P.list updateColumnsEnum)
|
2022-06-08 02:24:42 +03:00
|
|
|
|
2022-06-23 12:14:24 +03:00
|
|
|
whereExp <- P.fieldOptional Name._where Nothing whereExpParser
|
2022-06-08 02:24:42 +03:00
|
|
|
|
2021-12-15 20:07:21 +03:00
|
|
|
updateColumns <-
|
2022-06-08 02:24:42 +03:00
|
|
|
updateColumnsField `P.bindFields` \updateColumnsMaybe ->
|
|
|
|
onNothing
|
|
|
|
(sequenceA @[] @Maybe updateColumnsMaybe)
|
|
|
|
-- this can only happen if the placeholder was used
|
|
|
|
(parseError "erroneous column name")
|
|
|
|
|
2021-12-15 20:07:21 +03:00
|
|
|
pure $
|
2022-06-08 02:24:42 +03:00
|
|
|
let UniqueConstraint (Constraint {_cName}) _ = constraintField
|
|
|
|
constraintTarget = IR.CTConstraint _cName
|
|
|
|
in case updateColumns of
|
|
|
|
[] -> IR.OCCDoNothing $ Just constraintTarget
|
|
|
|
_ ->
|
|
|
|
IR.OCCUpdate $
|
|
|
|
IR.OnConflictClauseData constraintTarget updateColumns presetColumns $
|
|
|
|
IR.BoolAnd $ updateFilter : maybeToList whereExp
|
2021-12-15 20:07:21 +03:00
|
|
|
where
|
|
|
|
tableName = tableInfoName tableInfo
|
|
|
|
|
|
|
|
-- | Constructs a Parser for the name of the constraints on a given table.
|
|
|
|
--
|
|
|
|
-- The TableCoreInfo of a given table contains a list of unique or primary key
|
|
|
|
-- constraints. Given the list of such constraints, this function creates a
|
|
|
|
-- parser for an enum type that matches it. This function makes no attempt at
|
|
|
|
-- de-duplicating contraint names, and assumes they are correct.
|
|
|
|
--
|
|
|
|
-- This function can fail if a constraint has a name that cannot be translated
|
|
|
|
-- to a GraphQL name (see hasura/graphql-engine-mono#1748).
|
|
|
|
conflictConstraint ::
|
|
|
|
forall pgKind r m n.
|
|
|
|
MonadBuildSchema ('Postgres pgKind) r m n =>
|
2022-06-08 02:24:42 +03:00
|
|
|
NonEmpty (UniqueConstraint ('Postgres pgKind)) ->
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
SourceInfo ('Postgres pgKind) ->
|
2021-12-15 20:07:21 +03:00
|
|
|
TableInfo ('Postgres pgKind) ->
|
2022-06-08 02:24:42 +03:00
|
|
|
m (Parser 'Both n (UniqueConstraint ('Postgres pgKind)))
|
Remove circular dependency in schema building code
### Description
The main goal of this PR is, as stated, to remove the circular dependency in the schema building code. This cycle arises from the existence of remote relationships: when we build the schema for a source A, a remote relationship might force us to jump to the schema of a source B, or some remote schema. As a result, we end up having to do a dispatch from a "leaf" of the schema, similar to the one done at the root. In turn, this forces us to carry along in the schema a lot of information required for that dispatch, AND it forces us to import the instances in scope, creating an import loop.
As discussed in #4489, this PR implements the "dependency injection" solution: we pass to the schema a function to call to do the dispatch, and to get a generated field for a remote relationship. That way, this function can be chosen at the root level, and the leaves need not be aware of the overall context.
This PR grew a bit bigger than that, however; in an attempt to try and remove the `SourceCache` from the schema altogether, it changed a lot of functions across the schema building code, to thread along the `SourceInfo b` of the source being built. This avoids having to do cache lookups within a given source. A few cases remain, such as relay, that we might try to tackle in a subsequent PR.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4557
GitOrigin-RevId: 9388e48372877520a72a9fd1677005df9f7b2d72
2022-05-27 20:21:22 +03:00
|
|
|
conflictConstraint constraints sourceInfo tableInfo =
|
|
|
|
memoizeOn 'conflictConstraint (_siName sourceInfo, tableName) $ do
|
2021-12-15 20:07:21 +03:00
|
|
|
tableGQLName <- getTableGQLName tableInfo
|
2022-06-08 02:24:42 +03:00
|
|
|
constraintEnumValues <- for
|
|
|
|
constraints
|
|
|
|
\c@(UniqueConstraint (Constraint {_cName}) cCols) -> do
|
|
|
|
name <- textToName $ toTxt $ _cName
|
|
|
|
pure
|
|
|
|
( P.Definition
|
|
|
|
name
|
|
|
|
(Just $ "unique or primary key constraint on columns " <> coerce (showPGCols (HS.toList cCols)))
|
|
|
|
P.EnumValueInfo,
|
|
|
|
c
|
|
|
|
)
|
2022-06-23 12:14:24 +03:00
|
|
|
enumName <- P.mkTypename $ tableGQLName <> Name.__constraint
|
2021-12-15 20:07:21 +03:00
|
|
|
let enumDesc = G.Description $ "unique or primary key constraints on table " <>> tableName
|
|
|
|
pure $ P.enum enumName (Just enumDesc) constraintEnumValues
|
|
|
|
where
|
|
|
|
tableName = tableInfoName tableInfo
|