Daniel Chambers 2023-01-10 12:54:40 +11:00 committed by hasura-bot
parent aefdf0dd81
commit 57607f5295
33 changed files with 766 additions and 840 deletions

View File

@ -176,7 +176,7 @@ common common-all
-- Use O1 over O2, as (as of writing) it improves compile times a little, without
-- hurting performance:
-O1
-- This seems like a better default for us, lowering memory residency without
-- This seems like a better default for us, lowering memory residency without
-- impacting compile times too much, though it does increase binary size:
-funfolding-use-threshold=640
else
@ -651,6 +651,7 @@ library
, Hasura.Backends.DataConnector.Adapter.SchemaCache
, Hasura.Backends.DataConnector.Adapter.Transport
, Hasura.Backends.DataConnector.Adapter.Types
, Hasura.Backends.DataConnector.Adapter.Types.Mutations
, Hasura.Backends.DataConnector.Agent.Client
, Hasura.Backends.DataConnector.Logging
, Hasura.Backends.DataConnector.Plan
@ -847,6 +848,7 @@ library
, Hasura.RQL.IR.Select
, Hasura.RQL.IR.RemoteSchema
, Hasura.RQL.IR.Update
, Hasura.RQL.IR.Update.Batch
, Hasura.RQL.IR.Value
, Hasura.RQL.IR.Root
, Hasura.RQL.IR
@ -908,6 +910,7 @@ library
, Hasura.GraphQL.Schema.Table
, Hasura.GraphQL.Schema.Typename
, Hasura.GraphQL.Schema.Update
, Hasura.GraphQL.Schema.Update.Batch
, Hasura.GraphQL.Transport.Backend
, Hasura.GraphQL.Transport.HTTP
, Hasura.GraphQL.Transport.HTTP.Protocol

View File

@ -58,7 +58,7 @@ instance BackendSchema 'BigQuery where
buildTableRelayQueryFields _ _ _ _ _ = pure []
buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields _ _ _ _ _ = pure []
buildTableUpdateMutationFields _ _ _ _ _ = pure []
buildTableUpdateMutationFields _ _ _ = pure []
buildTableDeleteMutationFields _ _ _ _ _ = pure []
buildFunctionQueryFields _ _ _ _ = pure []
buildFunctionRelayQueryFields _ _ _ _ _ = pure []

View File

@ -19,6 +19,7 @@ import Data.Text.Casing qualified as C
import Data.Text.Extended ((<<>))
import Hasura.Backends.DataConnector.API qualified as API
import Hasura.Backends.DataConnector.Adapter.Types qualified as DC
import Hasura.Backends.DataConnector.Adapter.Types.Mutations qualified as DC
import Hasura.Base.Error (Code (ValidationFailed), QErr, runAesonParser, throw400)
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
@ -68,8 +69,8 @@ instance Backend 'DataConnector where
type ComputedFieldImplicitArguments 'DataConnector = Unimplemented
type ComputedFieldReturn 'DataConnector = Unimplemented
type UpdateVariant 'DataConnector = DC.DataConnectorUpdateVariant
type BackendInsert 'DataConnector = DC.BackendInsert
type BackendUpdate 'DataConnector = DC.BackendUpdate
type XComputedField 'DataConnector = XDisable
type XRelay 'DataConnector = XDisable

View File

@ -16,9 +16,10 @@ import Data.Text.Extended ((<<>))
import Hasura.Backends.DataConnector.API qualified as API
import Hasura.Backends.DataConnector.Adapter.Backend (CustomBooleanOperator (..), columnTypeToScalarType)
import Hasura.Backends.DataConnector.Adapter.Types qualified as DC
import Hasura.Backends.DataConnector.Adapter.Types.Mutations qualified as DC
import Hasura.Base.Error
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Schema.Backend (BackendSchema (..), BackendTableSelectSchema (..), ComparisonExp, MonadBuildSchema)
import Hasura.GraphQL.Schema.Backend (BackendSchema (..), BackendTableSelectSchema (..), BackendUpdateOperatorsSchema (..), ComparisonExp, MonadBuildSchema)
import Hasura.GraphQL.Schema.BoolExp qualified as GS.BE
import Hasura.GraphQL.Schema.Build qualified as GS.B
import Hasura.GraphQL.Schema.Common qualified as GS.C
@ -27,6 +28,7 @@ import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select qualified as GS.S
import Hasura.GraphQL.Schema.Update qualified as GS.U
import Hasura.GraphQL.Schema.Update.Batch qualified as GS.U.B
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp qualified as IR
@ -84,6 +86,11 @@ instance BackendTableSelectSchema 'DataConnector where
selectTableAggregate = GS.S.defaultSelectTableAggregate
tableSelectionSet = GS.S.defaultTableSelectionSet
instance BackendUpdateOperatorsSchema 'DataConnector where
type UpdateOperators 'DataConnector = DC.UpdateOperator
parseUpdateOperators = parseUpdateOperators'
--------------------------------------------------------------------------------
buildTableInsertMutationFields' ::
@ -109,34 +116,31 @@ mkBackendInsertParser _tableInfo =
buildTableUpdateMutationFields' ::
MonadBuildSchema 'DataConnector r m n =>
RQL.MkRootFieldName ->
GS.C.Scenario ->
RQL.TableName 'DataConnector ->
RQL.TableInfo 'DataConnector ->
GQLNameIdentifier ->
GS.C.SchemaT r m [P.FieldParser n (IR.AnnotatedUpdateG 'DataConnector (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue 'DataConnector))]
buildTableUpdateMutationFields' mkRootFieldName scenario tableName tableInfo gqlName = do
buildTableUpdateMutationFields' scenario tableInfo gqlName = do
API.Capabilities {..} <- DC._scCapabilities . RQL._siConfiguration @('DataConnector) <$> asks getter
fieldParsers <- runMaybeT $ do
_updateCapabilities <- hoistMaybe $ _cMutations >>= API._mcUpdateCapabilities
roleName <- GS.C.retrieve GS.C.scRole
updatePerms <- hoistMaybe $ RQL._permUpd $ RQL.getRolePermInfo roleName tableInfo
let mkBackendUpdate backendUpdateTableInfo =
(fmap . fmap) DC.BackendUpdate $
GS.U.buildUpdateOperators
(DC.UpdateSet <$> GS.U.presetColumns updatePerms)
[ DC.UpdateSet <$> GS.U.setOp
]
backendUpdateTableInfo
lift $
GS.B.buildTableUpdateMutationFields
mkBackendUpdate
mkRootFieldName
scenario
tableName
tableInfo
gqlName
pure $ fromMaybe [] fieldParsers
case _cMutations >>= API._mcUpdateCapabilities of
Just _updateCapabilities -> do
updateRootFields <- GS.B.buildSingleBatchTableUpdateMutationFields DC.SingleBatch scenario tableInfo gqlName
updateManyRootField <- GS.U.B.updateTableMany DC.MultipleBatches scenario tableInfo gqlName
pure $ updateRootFields ++ (maybeToList updateManyRootField)
Nothing -> pure []
parseUpdateOperators' ::
forall m n r.
MonadBuildSchema 'DataConnector r m n =>
RQL.TableInfo 'DataConnector ->
RQL.UpdPermInfo 'DataConnector ->
GS.C.SchemaT r m (P.InputFieldsParser n (HashMap (RQL.Column 'DataConnector) (DC.UpdateOperator (IR.UnpreparedValue 'DataConnector))))
parseUpdateOperators' tableInfo updatePermissions = do
GS.U.buildUpdateOperators
(DC.UpdateSet <$> GS.U.presetColumns updatePermissions)
[ DC.UpdateSet <$> GS.U.setOp
]
tableInfo
buildTableDeleteMutationFields' ::
MonadBuildSchema 'DataConnector r m n =>

View File

@ -30,9 +30,6 @@ module Hasura.Backends.DataConnector.Adapter.Types
ScalarType (..),
mkScalarType,
fromGQLType,
BackendInsert (..),
BackendUpdate (..),
UpdateOperator (..),
)
where
@ -372,33 +369,4 @@ fromGQLType typeName =
--------------------------------------------------------------------------------
-- | The Data Connector-specific data of an Insert expression. Currently, we don't
-- have any.
--
-- This is parameterised over @v@ which enables different phases of IR
-- transformation to maintain the overall structure while enriching/transforming
-- the data at the leaves.
data BackendInsert v = BackendInsert
deriving stock (Functor, Foldable, Traversable)
--------------------------------------------------------------------------------
-- | The Data Connector-specific data of an Update expression.
--
-- This is parameterised over @v@ which enables different phases of IR
-- transformation to maintain the overall structure while enriching/transforming
-- the data at the leaves.
data BackendUpdate v = BackendUpdate
{_buUpdateOperations :: HashMap ColumnName (UpdateOperator v)}
deriving stock (Functor, Foldable, Traversable)
--------------------------------------------------------------------------------
-- | The operators that are used to mutate specific columns on a table
data UpdateOperator v
= UpdateSet v
deriving stock (Functor, Foldable, Traversable)
--------------------------------------------------------------------------------
$(makeLenses ''SourceConfig)

View File

@ -0,0 +1,43 @@
{-# LANGUAGE UndecidableInstances #-}
module Hasura.Backends.DataConnector.Adapter.Types.Mutations
( BackendInsert (..),
DataConnectorUpdateVariant (..),
UpdateOperator (..),
)
where
import Hasura.Prelude
import Hasura.RQL.IR.Update.Batch (UpdateBatch)
import Hasura.RQL.Types.Backend (Backend)
import Hasura.SQL.Backend (BackendType (..))
--------------------------------------------------------------------------------
-- | The Data Connector-specific data of an Insert expression. Currently, we don't
-- have any.
--
-- This is parameterised over @v@ which enables different phases of IR
-- transformation to maintain the overall structure while enriching/transforming
-- the data at the leaves.
data BackendInsert v = BackendInsert
deriving stock (Functor, Foldable, Traversable)
--------------------------------------------------------------------------------
data DataConnectorUpdateVariant v
= SingleBatch (UpdateBatch 'DataConnector UpdateOperator v)
| MultipleBatches [UpdateBatch 'DataConnector UpdateOperator v]
deriving stock instance Backend 'DataConnector => Functor DataConnectorUpdateVariant
deriving stock instance Backend 'DataConnector => Foldable DataConnectorUpdateVariant
deriving stock instance Backend 'DataConnector => Traversable DataConnectorUpdateVariant
--------------------------------------------------------------------------------
-- | The operators that are used to mutate specific columns on a table
data UpdateOperator v
= UpdateSet v
deriving stock (Functor, Foldable, Traversable)

View File

@ -22,7 +22,6 @@ import Hasura.Backends.MSSQL.Plan
import Hasura.Backends.MSSQL.SQL.Error
import Hasura.Backends.MSSQL.ToQuery as TQ
import Hasura.Backends.MSSQL.Types.Internal as TSQL
import Hasura.Backends.MSSQL.Types.Update
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Schema.Options qualified as Options
@ -30,6 +29,7 @@ import Hasura.Prelude
import Hasura.QueryTags (QueryTagsComment)
import Hasura.RQL.IR
import Hasura.RQL.IR qualified as IR
import Hasura.RQL.IR.Update.Batch qualified as IR
import Hasura.RQL.Types.Backend
import Hasura.SQL.Backend
import Hasura.Session
@ -46,7 +46,7 @@ executeUpdate userInfo stringifyNum sourceConfig updateOperation = do
queryTags <- ask
let mssqlExecCtx = (_mscExecCtx sourceConfig)
preparedUpdate <- traverse (prepareValueQuery $ _uiSession userInfo) updateOperation
if null $ updateOperations . _auBackend $ updateOperation
if IR.updateBatchIsEmpty $ _auUpdateVariant updateOperation
then pure $ pure $ IR.buildEmptyMutResp $ _auOutput preparedUpdate
else pure $ (mssqlRunReadWrite mssqlExecCtx) (buildUpdateTx preparedUpdate stringifyNum queryTags)

View File

@ -12,19 +12,20 @@ import Hasura.Backends.MSSQL.FromIr
import Hasura.Backends.MSSQL.FromIr.Constants (tempTableNameUpdated)
import Hasura.Backends.MSSQL.FromIr.Expression (fromGBoolExp)
import Hasura.Backends.MSSQL.Instances.Types ()
import Hasura.Backends.MSSQL.Types.Internal as TSQL
import Hasura.Backends.MSSQL.Types.Update as TSQL (BackendUpdate (..), Update (..))
import Hasura.Backends.MSSQL.Types.Internal
import Hasura.Backends.MSSQL.Types.Update
import Hasura.Prelude
import Hasura.RQL.IR qualified as IR
import Hasura.RQL.IR.Update.Batch qualified as IR
import Hasura.RQL.Types.Column qualified as IR
import Hasura.SQL.Backend
fromUpdate :: IR.AnnotatedUpdate 'MSSQL -> FromIr Update
fromUpdate (IR.AnnotatedUpdateG table (permFilter, whereClause) _ backendUpdate _ allColumns _tCase) = do
fromUpdate (IR.AnnotatedUpdateG table updatePermFilter _ (IR.UpdateBatch updateOperations whereClause) _ allColumns _tCase) = do
tableAlias <- generateAlias (TableTemplate (tableName table))
runReaderT
( do
permissionsFilter <- fromGBoolExp permFilter
permissionsFilter <- fromGBoolExp updatePermFilter
whereExpression <- fromGBoolExp whereClause
let columnNames = map IR.ciColumn allColumns
pure
@ -34,7 +35,7 @@ fromUpdate (IR.AnnotatedUpdateG table (permFilter, whereClause) _ backendUpdate
{ aliasedAlias = tableAlias,
aliasedThing = table
},
updateSet = updateOperations backendUpdate,
updateSet = updateOperations,
updateOutput = Output Inserted (map OutputColumn columnNames),
updateTempTable = TempTable tempTableNameUpdated columnNames,
updateWhere = Where [permissionsFilter, whereExpression]

View File

@ -11,14 +11,13 @@ import Data.Char qualified as Char
import Data.HashMap.Strict qualified as Map
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Text.Casing qualified as C
import Data.Text.Encoding as TE
import Data.Text.Extended
import Database.ODBC.SQLServer qualified as ODBC
import Hasura.Backends.MSSQL.Schema.IfMatched
import Hasura.Backends.MSSQL.Types.Insert (BackendInsert (..))
import Hasura.Backends.MSSQL.Types.Internal qualified as MSSQL
import Hasura.Backends.MSSQL.Types.Update (BackendUpdate (..), UpdateOperator (..))
import Hasura.Backends.MSSQL.Types.Update (UpdateOperator (..))
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (toErrorMessage)
import Hasura.GraphQL.Schema.Backend
@ -28,8 +27,7 @@ import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser
( FieldParser,
InputFieldsParser,
( InputFieldsParser,
Kind (..),
MonadParse,
Parser,
@ -46,7 +44,6 @@ import Hasura.RQL.Types.Column
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.Backend
import Language.GraphQL.Draft.Syntax qualified as G
@ -61,7 +58,7 @@ instance BackendSchema 'MSSQL where
buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields = GSB.buildTableInsertMutationFields backendInsertParser
buildTableDeleteMutationFields = GSB.buildTableDeleteMutationFields
buildTableUpdateMutationFields = msBuildTableUpdateMutationFields
buildTableUpdateMutationFields = GSB.buildSingleBatchTableUpdateMutationFields id
buildFunctionQueryFields _ _ _ _ = pure []
buildFunctionRelayQueryFields _ _ _ _ _ = pure []
@ -101,6 +98,11 @@ instance BackendTableSelectSchema 'MSSQL where
selectTableAggregate = defaultSelectTableAggregate
tableSelectionSet = defaultTableSelectionSet
instance BackendUpdateOperatorsSchema 'MSSQL where
type UpdateOperators 'MSSQL = UpdateOperator
parseUpdateOperators = msParseUpdateOperators
----------------------------------------------------------------
-- * Top level parsers
@ -117,36 +119,6 @@ backendInsertParser tableInfo = do
_biIfMatched <- ifMatched
pure $ BackendInsert {..}
msBuildTableUpdateMutationFields ::
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName ->
Scenario ->
TableName 'MSSQL ->
TableInfo 'MSSQL ->
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (AnnotatedUpdateG 'MSSQL (RemoteRelationshipField UnpreparedValue) (UnpreparedValue 'MSSQL))]
msBuildTableUpdateMutationFields mkRootFieldName scenario tableName tableInfo gqlName = do
roleName <- retrieve scRole
fieldParsers <- runMaybeT do
updatePerms <- hoistMaybe $ _permUpd $ getRolePermInfo roleName tableInfo
let mkBackendUpdate backendUpdateTableInfo =
(fmap . fmap) BackendUpdate $
SU.buildUpdateOperators
(UpdateSet <$> SU.presetColumns updatePerms)
[ UpdateSet <$> SU.setOp,
UpdateInc <$> SU.incOp
]
backendUpdateTableInfo
lift $
GSB.buildTableUpdateMutationFields
mkBackendUpdate
mkRootFieldName
scenario
tableName
tableInfo
gqlName
pure . fold @Maybe @[_] $ fieldParsers
----------------------------------------------------------------
-- * Table arguments
@ -415,3 +387,17 @@ msCountTypeInput = \case
mkCountType _ Nothing = MSSQL.StarCountable
mkCountType IR.SelectCountDistinct (Just col) = MSSQL.DistinctCountable col
mkCountType IR.SelectCountNonDistinct (Just col) = MSSQL.NonNullFieldCountable col
msParseUpdateOperators ::
forall m n r.
MonadBuildSchema 'MSSQL r m n =>
TableInfo 'MSSQL ->
UpdPermInfo 'MSSQL ->
SchemaT r m (InputFieldsParser n (HashMap (Column 'MSSQL) (UpdateOperators 'MSSQL (UnpreparedValue 'MSSQL))))
msParseUpdateOperators tableInfo updatePermissions = do
SU.buildUpdateOperators
(UpdateSet <$> SU.presetColumns updatePermissions)
[ UpdateSet <$> SU.setOp,
UpdateInc <$> SU.incOp
]
tableInfo

View File

@ -13,9 +13,10 @@ import Hasura.Backends.MSSQL.Connection qualified as MSSQL
import Hasura.Backends.MSSQL.ToQuery ()
import Hasura.Backends.MSSQL.Types.Insert qualified as MSSQL (BackendInsert)
import Hasura.Backends.MSSQL.Types.Internal qualified as MSSQL
import Hasura.Backends.MSSQL.Types.Update qualified as MSSQL (BackendUpdate)
import Hasura.Backends.MSSQL.Types.Update qualified as MSSQL (UpdateOperator)
import Hasura.Base.Error
import Hasura.Prelude
import Hasura.RQL.IR.Update.Batch (UpdateBatch)
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common (TriggerOnReplication (..))
import Hasura.RQL.Types.HealthCheck
@ -47,8 +48,6 @@ instance Backend 'MSSQL where
type SQLExpression 'MSSQL = MSSQL.Expression
type ScalarSelectionArguments 'MSSQL = Void
type BackendUpdate 'MSSQL = MSSQL.BackendUpdate
type ComputedFieldDefinition 'MSSQL = Void
type FunctionArgumentExp 'MSSQL = Const Void
type ComputedFieldImplicitArguments 'MSSQL = Void
@ -56,6 +55,7 @@ instance Backend 'MSSQL where
type ExtraTableMetadata 'MSSQL = [MSSQL.ColumnName] -- List of identity columns
type BackendInsert 'MSSQL = MSSQL.BackendInsert
type UpdateVariant 'MSSQL = UpdateBatch 'MSSQL MSSQL.UpdateOperator
type XComputedField 'MSSQL = XDisable
type XRelay 'MSSQL = XDisable

View File

@ -2,8 +2,7 @@
--
-- This module defines the Update-related IR types specific to MSSQL.
module Hasura.Backends.MSSQL.Types.Update
( BackendUpdate (..),
UpdateOperator (..),
( UpdateOperator (..),
Update (..),
UpdateSet,
UpdateOutput,
@ -14,22 +13,6 @@ import Hasura.Backends.MSSQL.Types.Instances ()
import Hasura.Backends.MSSQL.Types.Internal
import Hasura.Prelude
-- | The MSSQL-specific data of an Update expression.
--
-- This is parameterised over @v@ which enables different phases of IR
-- transformation to maintain the overall structure while enriching/transforming
-- the data at the leaves.
data BackendUpdate v = BackendUpdate
{ -- | The update operations to perform on each column.
--
-- This HashMap will also contain the update operators for the presets.
-- They are populated as part of the schema building in
-- 'Hasura.Backends.MSSQL.Instances.Schema.msBuildTableUpdateMutationFields'
-- in the call to @buildUpdateOperators@.
updateOperations :: HashMap ColumnName (UpdateOperator v)
}
deriving (Functor, Foldable, Traversable, Generic, Data)
-- | The various @update operators@ supported by MSSQL,
-- i.e. the @_set@, @_inc@ operators that appear in the schema.
--

View File

@ -40,7 +40,7 @@ instance BackendSchema 'MySQL where
buildTableRelayQueryFields _ _ _ _ _ = pure []
buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields _ _ _ _ _ = pure []
buildTableUpdateMutationFields _ _ _ _ _ = pure []
buildTableUpdateMutationFields _ _ _ = pure []
buildTableDeleteMutationFields _ _ _ _ _ = pure []
buildFunctionQueryFields _ _ _ _ = pure []
buildFunctionRelayQueryFields _ _ _ _ _ = pure []

View File

@ -40,7 +40,7 @@ import Hasura.Backends.Postgres.SQL.Value qualified as Postgres
import Hasura.Backends.Postgres.Translate.Select (PostgresAnnotatedFieldJSON)
import Hasura.Backends.Postgres.Translate.Select qualified as DS
import Hasura.Backends.Postgres.Types.Function qualified as Postgres
import Hasura.Backends.Postgres.Types.Update qualified as BackendUpdate
import Hasura.Backends.Postgres.Types.Update qualified as Postgres
import Hasura.Base.Error (QErr)
import Hasura.EncJSON (EncJSON, encJFromJValue)
import Hasura.GraphQL.Execute.Backend
@ -221,7 +221,7 @@ convertUpdate ::
convertUpdate userInfo updateOperation stringifyNum = do
queryTags <- ask
preparedUpdate <- traverse (prepareWithoutPlan userInfo) updateOperation
if BackendUpdate.isEmpty $ IR._auBackend updateOperation
if Postgres.updateVariantIsEmpty $ IR._auUpdateVariant updateOperation
then pure $ pure $ IR.buildEmptyMutResp $ IR._auOutput preparedUpdate
else
pure $

View File

@ -38,6 +38,7 @@ import Hasura.GraphQL.ApolloFederation (ApolloFederationParserFunction)
import Hasura.GraphQL.Schema.Backend
( BackendSchema,
BackendTableSelectSchema,
BackendUpdateOperatorsSchema,
ComparisonExp,
MonadBuildSchema,
)
@ -62,14 +63,13 @@ import Hasura.GraphQL.Schema.Parser
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.Table (getTableIdentifierName, tableColumns)
import Hasura.GraphQL.Schema.Typename
import Hasura.GraphQL.Schema.Update qualified as SU
import Hasura.GraphQL.Schema.Update.Batch qualified as SUB
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.Returning (MutationOutputG (..))
import Hasura.RQL.IR.Root (RemoteRelationshipField)
import Hasura.RQL.IR.Root qualified as IR
import Hasura.RQL.IR.Select
( QueryDB (QDBConnection),
)
@ -81,7 +81,7 @@ import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Function (FunctionInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table (CustomRootField (..), RolePermInfo (..), TableConfig (..), TableCoreInfoG (..), TableCustomRootFields (..), TableInfo (..), UpdPermInfo (..), ViewInfo (..), getRolePermInfo, isMutable, tableInfoName)
import Hasura.RQL.Types.Table (TableInfo (..), UpdPermInfo (..))
import Hasura.SQL.Backend (BackendType (Postgres), PostgresKind (Citus, Cockroach, Vanilla))
import Hasura.SQL.Types
import Language.GraphQL.Draft.Syntax qualified as G
@ -324,6 +324,11 @@ instance
aggregateOrderByCountType = Postgres.PGInteger
computedField = computedFieldPG
instance Backend ('Postgres pgKind) => BackendUpdateOperatorsSchema ('Postgres pgKind) where
type UpdateOperators ('Postgres pgKind) = UpdateOpExpression
parseUpdateOperators = pgkParseUpdateOperators
backendInsertParser ::
forall pgKind m r n.
MonadBuildSchema ('Postgres pgKind) r m n =>
@ -356,133 +361,6 @@ buildTableRelayQueryFields mkRootFieldName tableName tableInfo gqlName pkeyColum
optionalFieldParser QDBConnection $
selectTableConnection tableInfo rootFieldName fieldDesc pkeyColumns
pgkBuildTableUpdateMutationFields ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
Scenario ->
-- | The name of the table being acted on
TableName ('Postgres pgKind) ->
-- | table info
TableInfo ('Postgres pgKind) ->
-- | field display name
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (IR.AnnotatedUpdateG ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
pgkBuildTableUpdateMutationFields mkRootFieldName scenario tableName tableInfo gqlName = do
-- check in schema options whether we should include multiple updates field
roleName <- retrieve scRole
includeUpdateManyFields <- retrieve Options.soIncludeUpdateManyFields
concat . maybeToList <$> runMaybeT do
updatePerms <- hoistMaybe $ _permUpd $ getRolePermInfo roleName tableInfo
lift $ do
-- update_table and update_table_by_pk
singleUpdates <-
GSB.buildTableUpdateMutationFields
-- TODO: https://github.com/hasura/graphql-engine-mono/issues/2955
(\ti -> fmap BackendUpdate <$> updateOperators ti updatePerms)
mkRootFieldName
scenario
tableName
tableInfo
gqlName
-- update_table_many
multiUpdate <-
updateTableMany
mkRootFieldName
scenario
tableInfo
gqlName
-- we only include the multiUpdate field if the
-- experimental feature 'hide_update_many_fields' is off
pure $ case includeUpdateManyFields of
Options.IncludeUpdateManyFields ->
singleUpdates ++ maybeToList multiUpdate
Options.Don'tIncludeUpdateManyFields ->
singleUpdates
-- | Create a parser for 'update_table_many'. This function is very similar to
-- both 'GSB.buildTableUpdateMutationFields' and
-- 'Hasura.GraphQL.Schema.Update.updateTable'.
--
-- It is similar to the former because of its shape: has to deal with grabbing
-- the casing, deals with update permissions, etc.
--
-- It is similar to the latter because it deals with creating the
-- parser/subselection/etc.
--
-- The reason this function exists here is because it is Postgres specific. It
-- would not fit very well next to the functions mentioned above.
--
-- However, if you are trying to implement this feature for other backends,
-- please consider making this function similar to /updateTable/ and moving it
-- there.
-- Note: this will likely require adding a type or a function to
-- 'BackendSchema'.
updateTableMany ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
Scenario ->
TableInfo ('Postgres pgKind) ->
C.GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (IR.AnnotatedUpdateG ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))))
updateTableMany mkRootFieldName scenario tableInfo gqlName = runMaybeT do
sourceInfo :: SourceInfo ('Postgres pgKind) <- asks getter
roleName <- retrieve scRole
let customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
columns = tableColumns tableInfo
viewInfo = _tciViewInfo $ _tiCoreInfo tableInfo
guard $ isMutable viIsUpdatable viewInfo
updatePerms <- hoistMaybe $ _permUpd $ getRolePermInfo roleName tableInfo
guard $ not $ scenario == Frontend && upiBackendOnly updatePerms
updates <- lift (mkMultiRowUpdateParser tableInfo updatePerms)
selection <- lift $ P.multiple <$> GSB.mutationSelectionSet tableInfo
let updateName = runMkRootFieldName mkRootFieldName $ GSB.setFieldNameCase tCase tableInfo _tcrfUpdateMany mkUpdateManyField gqlName
argsParser = liftA2 (,) updates (pure annBoolExpTrue)
pure $
P.subselection updateName updateDesc argsParser selection
<&> SU.mkUpdateObject tableName columns updatePerms (Just tCase) . fmap MOutMultirowFields
where
tableName = tableInfoName tableInfo
defaultUpdateDesc = "update multiples rows of table: " <>> tableName
updateDesc = GSB.buildFieldDescription defaultUpdateDesc $ _crfComment _tcrfUpdateMany
TableCustomRootFields {..} = _tcCustomRootFields . _tciCustomConfig $ _tiCoreInfo tableInfo
-- | Create a parser for the updates section of the `update_table_many` update.
--
-- It parses a list with two fields: 'where', and an update expression
-- (set/inc/etc).
mkMultiRowUpdateParser ::
forall pgKind r m n.
MonadBuildSchema ('Postgres pgKind) r m n =>
TableInfo ('Postgres pgKind) ->
UpdPermInfo ('Postgres pgKind) ->
SchemaT r m (P.InputFieldsParser n (PGIR.BackendUpdate pgKind (IR.UnpreparedValue ('Postgres pgKind))))
mkMultiRowUpdateParser tableInfo updatePerms = do
sourceInfo :: SourceInfo ('Postgres pgKind) <- asks getter
let customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
mkTypename = runMkTypename $ _rscTypeNames customization
tableGQLName <- getTableIdentifierName tableInfo -- getTableGQLName tableInfo
let updatesObjectName = mkTypename $ applyTypeNameCaseIdentifier tCase $ mkMultiRowUpdateTypeName tableGQLName
fmap BackendMultiRowUpdate
. P.field Name._updates (Just updatesDesc)
. P.list
. P.object updatesObjectName Nothing
<$> do
mruWhere <- P.field Name._where Nothing <$> boolExp tableInfo
mruExpression <- updateOperators tableInfo updatePerms
pure $ MultiRowUpdate <$> mruWhere <*> mruExpression
where
updatesDesc = "updates to execute, in order"
buildFunctionRelayQueryFields ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
@ -500,6 +378,18 @@ buildFunctionRelayQueryFields mkRootFieldName functionName functionInfo tableNam
optionalFieldParser QDBConnection $
selectFunctionConnection mkRootFieldName functionInfo fieldDesc pkeyColumns
pgkBuildTableUpdateMutationFields ::
forall r m n pgKind.
(MonadBuildSchema ('Postgres pgKind) r m n, PostgresSchema pgKind) =>
Scenario ->
TableInfo ('Postgres pgKind) ->
C.GQLNameIdentifier ->
SchemaT r m [P.FieldParser n (IR.AnnotatedUpdateG ('Postgres pgKind) (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
pgkBuildTableUpdateMutationFields scenario tableInfo gqlName = do
updateRootFields <- GSB.buildSingleBatchTableUpdateMutationFields SingleBatch scenario tableInfo gqlName
updateManyRootField <- SUB.updateTableMany MultipleBatches scenario tableInfo gqlName
pure $ updateRootFields ++ (maybeToList updateManyRootField)
----------------------------------------------------------------
-- Individual components
@ -1176,13 +1066,13 @@ deleteAtPathOp = SU.UpdateOperator {..}
desc
-- | The update operators that we support on Postgres.
updateOperators ::
pgkParseUpdateOperators ::
forall pgKind m n r.
MonadBuildSchema ('Postgres pgKind) r m n =>
TableInfo ('Postgres pgKind) ->
UpdPermInfo ('Postgres pgKind) ->
SchemaT r m (InputFieldsParser n (HashMap (Column ('Postgres pgKind)) (UpdateOpExpression (IR.UnpreparedValue ('Postgres pgKind)))))
updateOperators tableInfo updatePermissions = do
pgkParseUpdateOperators tableInfo updatePermissions = do
SU.buildUpdateOperators
(PGIR.UpdateSet <$> SU.presetColumns updatePermissions)
[ PGIR.UpdateSet <$> SU.setOp,

View File

@ -108,7 +108,7 @@ instance
type ComputedFieldImplicitArguments ('Postgres pgKind) = Postgres.ComputedFieldImplicitArguments
type ComputedFieldReturn ('Postgres pgKind) = Postgres.ComputedFieldReturn
type BackendUpdate ('Postgres pgKind) = Postgres.BackendUpdate pgKind
type UpdateVariant ('Postgres pgKind) = Postgres.PgUpdateVariant pgKind
type AggregationPredicates ('Postgres pgKind) = Agg.AggregationPredicatesImplementation ('Postgres pgKind)

View File

@ -17,6 +17,7 @@ import Hasura.Backends.Postgres.Types.Update
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.Update
import Hasura.RQL.IR.Update.Batch
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.SQL.Backend
@ -35,49 +36,43 @@ mkUpdateCTE ::
Backend ('Postgres pgKind) =>
AnnotatedUpdate ('Postgres pgKind) ->
UpdateCTE
mkUpdateCTE (AnnotatedUpdateG tn (permFltr, wc) chk backendUpdate _ columnsInfo _tCase) =
let mkWhere =
Just
. S.WhereFrag
. S.simplifyBoolExp
. toSQLBoolExp (S.QualTable tn)
. andAnnBoolExps permFltr
checkConstraint =
Just $
S.RetExp
[ S.selectStar,
asCheckErrorExtractor
. insertCheckConstraint
. toSQLBoolExp (S.QualTable tn)
$ chk
]
in case backendUpdate of
BackendUpdate opExps ->
Update $ S.CTEUpdate update
where
update =
S.SQLUpdate
{ upTable = tn,
upSet =
S.SetExp $ map (expandOperator columnsInfo) (Map.toList opExps),
upFrom = Nothing,
upWhere = mkWhere wc,
upRet = checkConstraint
}
BackendMultiRowUpdate updates ->
MultiUpdate $ translateUpdate <$> updates
where
translateUpdate :: MultiRowUpdate pgKind S.SQLExp -> S.TopLevelCTE
translateUpdate MultiRowUpdate {..} =
S.CTEUpdate
S.SQLUpdate
{ upTable = tn,
upSet =
S.SetExp $ map (expandOperator columnsInfo) (Map.toList mruExpression),
upFrom = Nothing,
upWhere = mkWhere mruWhere,
upRet = checkConstraint
}
mkUpdateCTE (AnnotatedUpdateG tn permFltr chk updateVariant _ columnsInfo _tCase) =
case updateVariant of
SingleBatch update ->
Update $ translateUpdate update
MultipleBatches updates ->
MultiUpdate $ translateUpdate <$> updates
where
mkWhere :: AnnBoolExp ('Postgres pgKind) S.SQLExp -> Maybe S.WhereFrag
mkWhere =
Just
. S.WhereFrag
. S.simplifyBoolExp
. toSQLBoolExp (S.QualTable tn)
. andAnnBoolExps permFltr
checkConstraint :: Maybe S.RetExp
checkConstraint =
Just $
S.RetExp
[ S.selectStar,
asCheckErrorExtractor
. insertCheckConstraint
. toSQLBoolExp (S.QualTable tn)
$ chk
]
translateUpdate :: UpdateBatch ('Postgres pgKind) UpdateOpExpression S.SQLExp -> S.TopLevelCTE
translateUpdate UpdateBatch {..} =
S.CTEUpdate
S.SQLUpdate
{ upTable = tn,
upSet =
S.SetExp $ map (expandOperator columnsInfo) (Map.toList _ubOperations),
upFrom = Nothing,
upWhere = mkWhere _ubWhere,
upRet = checkConstraint
}
expandOperator :: [ColumnInfo ('Postgres pgKind)] -> (PGCol, UpdateOpExpression S.SQLExp) -> S.SetExpItem
expandOperator infos (column, op) = S.SetExpItem $

View File

@ -4,113 +4,17 @@
--
-- This module defines the Update-related IR types specific to Postgres.
module Hasura.Backends.Postgres.Types.Update
( BackendUpdate (..),
isEmpty,
UpdateOpExpression (..),
MultiRowUpdate (..),
( UpdateOpExpression (..),
PgUpdateVariant (..),
updateVariantIsEmpty,
)
where
import Data.HashMap.Strict qualified as Map
import Data.Monoid (All (..))
import Data.Typeable (Typeable)
import Hasura.Backends.Postgres.SQL.Types (PGCol)
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp (AnnBoolExp, AnnBoolExpFld)
import Hasura.RQL.IR.Update.Batch (UpdateBatch (..), updateBatchIsEmpty)
import Hasura.RQL.Types.Backend (Backend)
import Hasura.SQL.Backend (BackendType (Postgres))
-- | Represents an entry in an /update_table_many/ update.
data MultiRowUpdate pgKind v = MultiRowUpdate
{ -- | The /where/ clause for each individual update.
--
-- Note that the /single/ updates do not have a where clause, because it
-- uses the one found in 'Hasura.RQL.IR.Update.AnnotatedUpdateG'. However,
-- we have one for each update for /update_many/.
mruWhere :: AnnBoolExp ('Postgres pgKind) v,
-- | The /update/ expression, e.g, "set", "inc", etc., for each column.
mruExpression :: HashMap PGCol (UpdateOpExpression v)
}
deriving stock (Generic)
deriving instance Backend ('Postgres pgKind) => Functor (MultiRowUpdate pgKind)
deriving instance Backend ('Postgres pgKind) => Foldable (MultiRowUpdate pgKind)
deriving instance Backend ('Postgres pgKind) => Traversable (MultiRowUpdate pgKind)
deriving instance
( Data v,
Typeable pgKind,
Data (AnnBoolExpFld ('Postgres pgKind) v),
Backend ('Postgres pgKind)
) =>
Data (MultiRowUpdate pgKind v)
deriving instance
( Show (AnnBoolExpFld ('Postgres pgKind) v),
Show (UpdateOpExpression v),
Backend ('Postgres pgKind)
) =>
Show (MultiRowUpdate pgKind v)
deriving instance
( Eq (AnnBoolExpFld ('Postgres pgKind) v),
Eq (UpdateOpExpression v),
Backend ('Postgres pgKind)
) =>
Eq (MultiRowUpdate pgKind v)
-- | The PostgreSQL-specific data of an Update expression.
--
-- This is parameterised over @v@ which enables different phases of IR
-- transformation to maintain the overall structure while enriching/transforming
-- the data at the leaves.
data BackendUpdate pgKind v
= -- | The update operations to perform on each colum.
BackendUpdate (HashMap PGCol (UpdateOpExpression v))
| -- | The update operations to perform, in sequence, for an
-- /update_table_many/ operation.
BackendMultiRowUpdate [MultiRowUpdate pgKind v]
deriving stock (Generic)
deriving instance Backend ('Postgres pgKind) => Functor (BackendUpdate pgKind)
deriving instance Backend ('Postgres pgKind) => Foldable (BackendUpdate pgKind)
deriving instance Backend ('Postgres pgKind) => Traversable (BackendUpdate pgKind)
deriving instance
( Data v,
Typeable pgKind,
Data (AnnBoolExpFld ('Postgres pgKind) v),
Backend ('Postgres pgKind)
) =>
Data (BackendUpdate pgKind v)
deriving instance
( Backend ('Postgres pgKind),
Show (MultiRowUpdate pgKind v),
Show (UpdateOpExpression v)
) =>
Show (BackendUpdate pgKind v)
deriving instance
( Backend ('Postgres pgKind),
Eq (MultiRowUpdate pgKind v),
Eq (UpdateOpExpression v)
) =>
Eq (BackendUpdate pgKind v)
-- | Are we updating anything?
isEmpty :: BackendUpdate pgKind v -> Bool
isEmpty =
\case
BackendUpdate hm ->
Map.null hm
BackendMultiRowUpdate xs ->
getAll $ foldMap (All . Map.null . mruExpression) xs
-- | The various @update operators@ supported by PostgreSQL,
-- i.e. the @_set@, @_inc@ operators that appear in the schema.
--
@ -124,3 +28,28 @@ data UpdateOpExpression v
| UpdateDeleteElem v
| UpdateDeleteAtPath [v]
deriving (Functor, Foldable, Traversable, Generic, Data, Show, Eq)
-- | The different 'variants' of updates that the Postgres backend supports.
--
-- This is parameterised over @v@ which enables different phases of IR
-- transformation to maintain the overall structure while enriching/transforming
-- the data at the leaves.
data PgUpdateVariant pgKind v
= SingleBatch (UpdateBatch ('Postgres pgKind) UpdateOpExpression v)
| MultipleBatches [UpdateBatch ('Postgres pgKind) UpdateOpExpression v]
deriving stock instance Eq (UpdateBatch ('Postgres pgKind) UpdateOpExpression v) => Eq (PgUpdateVariant pgKind v)
deriving stock instance Show (UpdateBatch ('Postgres pgKind) UpdateOpExpression v) => Show (PgUpdateVariant pgKind v)
deriving stock instance Backend ('Postgres pgKind) => Functor (PgUpdateVariant pgKind)
deriving stock instance Backend ('Postgres pgKind) => Foldable (PgUpdateVariant pgKind)
deriving stock instance Backend ('Postgres pgKind) => Traversable (PgUpdateVariant pgKind)
-- | Are we updating anything?
updateVariantIsEmpty :: PgUpdateVariant b v -> Bool
updateVariantIsEmpty = \case
SingleBatch b -> updateBatchIsEmpty b
MultipleBatches batches -> all updateBatchIsEmpty batches

View File

@ -730,7 +730,7 @@ buildMutationFields mkRootFieldName scenario sourceInfo tables (takeExposedAs FE
inserts <-
mkRFs (MDBR . MDBInsert) $ buildTableInsertMutationFields mkRootFieldName scenario tableName tableInfo tableIdentifierName
updates <-
mkRFs (MDBR . MDBUpdate) $ buildTableUpdateMutationFields mkRootFieldName scenario tableName tableInfo tableIdentifierName
mkRFs (MDBR . MDBUpdate) $ buildTableUpdateMutationFields scenario tableInfo tableIdentifierName
deletes <-
mkRFs (MDBR . MDBDelete) $ buildTableDeleteMutationFields mkRootFieldName scenario tableName tableInfo tableIdentifierName
pure $ concat [inserts, updates, deletes]

View File

@ -26,6 +26,7 @@ module Hasura.GraphQL.Schema.Backend
( -- * Main Types
BackendSchema (..),
BackendTableSelectSchema (..),
BackendUpdateOperatorsSchema (..),
MonadBuildSchema,
-- * Auxiliary Types
@ -36,6 +37,7 @@ module Hasura.GraphQL.Schema.Backend
)
where
import Data.Kind (Type)
import Data.Text.Casing (GQLNameIdentifier)
import Hasura.GraphQL.ApolloFederation (ApolloFederationParserFunction)
import Hasura.GraphQL.Schema.Common
@ -137,10 +139,7 @@ class
-- its namesake @GSB.@'Hasura.GraphQL.Schema.Build.buildTableUpdateMutationFields'.
buildTableUpdateMutationFields ::
MonadBuildSchema b r m n =>
MkRootFieldName ->
Scenario ->
-- | The name of the table being acted on
TableName b ->
-- | table info
TableInfo b ->
-- | field display name
@ -291,6 +290,21 @@ class Backend b => BackendTableSelectSchema (b :: BackendType) where
type ComparisonExp b = OpExpG b (UnpreparedValue b)
class Backend b => BackendUpdateOperatorsSchema (b :: BackendType) where
-- | Intermediate Representation of the set of update operators that act
-- upon table fields during an update mutation. (For example, _set and _inc)
--
-- It is parameterised over the type of fields, which changes during the IR
-- translation phases.
type UpdateOperators b :: Type -> Type
parseUpdateOperators ::
forall m n r.
MonadBuildSchema b r m n =>
TableInfo b ->
UpdPermInfo b ->
SchemaT r m (InputFieldsParser n (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
-- $modelling
-- #modelling#
--

View File

@ -48,7 +48,7 @@ module Hasura.GraphQL.Schema.Build
buildTableInsertMutationFields,
buildTableQueryAndSubscriptionFields,
buildTableStreamingSubscriptionFields,
buildTableUpdateMutationFields,
buildSingleBatchTableUpdateMutationFields,
setFieldNameCase,
buildFieldDescription,
)
@ -58,20 +58,20 @@ import Data.Has (getter)
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Hasura.GraphQL.ApolloFederation
import Hasura.GraphQL.Schema.Backend (BackendTableSelectSchema (..), MonadBuildSchema)
import Hasura.GraphQL.Schema.Backend (BackendTableSelectSchema (..), BackendUpdateOperatorsSchema (..), MonadBuildSchema)
import Hasura.GraphQL.Schema.BoolExp (AggregationPredicatesSchema)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.SubscriptionStream (selectStreamTable)
import Hasura.GraphQL.Schema.Table (getTableIdentifierName, tableSelectPermissions)
import Hasura.GraphQL.Schema.Typename
import Hasura.GraphQL.Schema.Update (updateTable, updateTableByPk)
import Hasura.GraphQL.Schema.Update.Batch (updateTable, updateTableByPk)
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.IR.Update.Batch
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Permission
@ -81,23 +81,6 @@ import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Language.GraphQL.Draft.Syntax qualified as G
-- | Builds field name with proper case. Please note that this is a pure
-- function as all the validation has already been done while preparing
-- @GQLNameIdentifier@.
setFieldNameCase ::
NamingCase ->
TableInfo b ->
CustomRootField ->
(C.GQLNameIdentifier -> C.GQLNameIdentifier) ->
C.GQLNameIdentifier ->
G.Name
setFieldNameCase tCase tInfo crf getFieldName tableName =
(applyFieldNameCaseIdentifier tCase fieldIdentifier)
where
tccName = fmap C.fromCustomName . _tcCustomName . _tciCustomConfig . _tiCoreInfo $ tInfo
crfName = fmap C.fromCustomName (_crfName crf)
fieldIdentifier = fromMaybe (getFieldName (fromMaybe tableName tccName)) crfName
-- | buildTableQueryAndSubscriptionFields builds the field parsers of a table.
-- It returns a tuple with array of field parsers that correspond to the field
-- parsers of the query root and the field parsers of the subscription root
@ -266,71 +249,33 @@ buildTableInsertMutationFields backendInsertAction mkRootFieldName scenario tabl
defaultInsertOneDesc = "insert a single row into the table: " <>> tableName
TableCustomRootFields {..} = _tcCustomRootFields . _tciCustomConfig $ _tiCoreInfo tableInfo
-- | This function is the basic building block for update mutations. It
-- | This function implements the parsers for the basic, single batch, update mutations. It
-- implements the mutation schema in the general shape described in
-- @https://hasura.io/docs/latest/graphql/core/databases/postgres/mutations/update.html@.
-- (ie. update_<table> and update_<table>_by_pk root fields)
--
-- Something that varies between backends is the @update operators@ that they
-- support (i.e. the schema fields @_set@, @_inc@, etc., see
-- <src/Hasura.Backends.Postgres.Instances.Schema.html#updateOperators Hasura.Backends.Postgres.Instances.Schema.updateOperators> for an example
-- implementation). Therefore, this function is parameterised over a monadic
-- action that produces the operators that the backend supports in the context
-- of some table and associated update permissions.
--
-- Apart from this detail, the rest of the arguments are the same as those
-- of @BackendSchema.@'Hasura.GraphQL.Schema.Backend.buildTableUpdateMutationFields'.
--
-- The suggested way to use this is like:
--
-- > instance BackendSchema MyBackend where
-- > ...
-- > buildTableUpdateMutationFields = GSB.buildTableUpdateMutationFields myBackendUpdateOperators
-- > ...
buildTableUpdateMutationFields ::
-- Different backends can have different update types (single batch, multiple batches, etc),
-- and so the parsed UpdateBatch needs to be embedded in the custom UpdateVariant defined
-- by the backend, which is done by passing a function to this function.
buildSingleBatchTableUpdateMutationFields ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
BackendTableSelectSchema b,
BackendUpdateOperatorsSchema b
) =>
-- | an action that builds @BackendUpdate@ with the
-- backend-specific data needed to perform an update mutation
( TableInfo b ->
SchemaT
r
m
(InputFieldsParser n (BackendUpdate b (UnpreparedValue b)))
) ->
MkRootFieldName ->
-- | Embed the UpdateBack in the backend-specific UpdateVariant
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b) -> UpdateVariant b (UnpreparedValue b)) ->
Scenario ->
-- | The name of the table being acted on
TableName b ->
-- | table info
TableInfo b ->
-- | field display name
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableUpdateMutationFields mkBackendUpdate mkRootFieldName scenario tableName tableInfo gqlName = do
sourceInfo :: SourceInfo b <- asks getter
let customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
-- update table
updateName = runMkRootFieldName mkRootFieldName $ setFieldNameCase tCase tableInfo _tcrfUpdate mkUpdateField gqlName
-- update table by pk
updatePKName = runMkRootFieldName mkRootFieldName $ setFieldNameCase tCase tableInfo _tcrfUpdateByPk mkUpdateByPkField gqlName
backendUpdate <- mkBackendUpdate tableInfo
update <- updateTable backendUpdate scenario 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
-- that make up the key.
updateByPk <- updateTableByPk backendUpdate scenario tableInfo updatePKName updatePKDesc
buildSingleBatchTableUpdateMutationFields mkSingleBatchUpdateVariant scenario tableInfo gqlName = do
update <- updateTable mkSingleBatchUpdateVariant scenario tableInfo gqlName
updateByPk <- updateTableByPk mkSingleBatchUpdateVariant scenario tableInfo gqlName
pure $ catMaybes [update, updateByPk]
where
updateDesc = buildFieldDescription defaultUpdateDesc $ _crfComment _tcrfUpdate
updatePKDesc = buildFieldDescription defaultUpdatePKDesc $ _crfComment _tcrfUpdateByPk
defaultUpdateDesc = "update data of the table: " <>> tableName
defaultUpdatePKDesc = "update single row of the table: " <>> tableName
TableCustomRootFields {..} = _tcCustomRootFields . _tciCustomConfig $ _tiCoreInfo tableInfo
buildTableDeleteMutationFields ::
forall b r m n.

View File

@ -10,9 +10,6 @@ module Hasura.GraphQL.Schema.Update
presetColumns,
setOp,
incOp,
updateTable,
updateTableByPk,
mkUpdateObject,
)
where
@ -21,30 +18,21 @@ import Data.HashMap.Strict qualified as M
import Data.HashMap.Strict.Extended qualified as M
import Data.List.NonEmpty qualified as NE
import Data.Text.Casing (GQLNameIdentifier, fromAutogeneratedName)
import Data.Text.Extended (toTxt, (<>>))
import Data.Text.Extended ((<>>))
import Hasura.Base.ToErrorValue
import Hasura.GraphQL.Schema.Backend (BackendSchema (..), BackendTableSelectSchema (..), MonadBuildSchema, columnParser)
import Hasura.GraphQL.Schema.BoolExp (AggregationPredicatesSchema, boolExp)
import Hasura.GraphQL.Schema.Backend (BackendSchema (..), MonadBuildSchema, columnParser)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation (mutationSelectionSet, primaryKeysArguments)
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Table (getTableIdentifierName, tableColumns, tableUpdateColumns)
import Hasura.GraphQL.Schema.Table (getTableIdentifierName, tableUpdateColumns)
import Hasura.GraphQL.Schema.Typename
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp (AnnBoolExp, annBoolExpTrue)
import Hasura.RQL.IR.Returning (MutationOutputG (..))
import Hasura.RQL.IR.Root (RemoteRelationshipField)
import Hasura.RQL.IR.Update (AnnotatedUpdateG (..))
import Hasura.RQL.IR.Value
import Hasura.RQL.Types.Backend (Backend (..))
import Hasura.RQL.Types.Column (ColumnInfo (..), isNumCol)
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.AnyBackend qualified as AB
import Language.GraphQL.Draft.Syntax (Description (..), Name (..), Nullability (..), litName)
import Language.GraphQL.Draft.Syntax (Description (..), Nullability (..), litName)
-- | @UpdateOperator b m n op@ represents one single update operator for a
-- backend @b@.
@ -241,112 +229,3 @@ incOp = UpdateOperator {..}
columns
"increments the numeric columns with given value of the filtered values"
(Description $ "input type for incrementing numeric columns in table " <>> tableName)
-- | Construct a root field, normally called update_tablename, that can be used
-- to update rows in a DB table specified by filters. Only returns a parser if
-- there are columns the user is allowed to update; otherwise returns Nothing.
updateTable ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
) =>
-- | backend-specific data needed to perform an update mutation
P.InputFieldsParser n (BackendUpdate b (UnpreparedValue b)) ->
Scenario ->
-- | table info
TableInfo b ->
-- | field display name
Name ->
-- | field description, if any
Maybe Description ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTable backendUpdate scenario tableInfo fieldName description = runMaybeT do
sourceInfo :: SourceInfo b <- asks getter
roleName <- retrieve scRole
let sourceName = _siName sourceInfo
tableName = tableInfoName tableInfo
customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
columns = tableColumns tableInfo
viewInfo = _tciViewInfo $ _tiCoreInfo tableInfo
whereName = $$(litName "where")
whereDesc = "filter the rows which have to be updated"
guard $ isMutable viIsUpdatable viewInfo
updatePerms <- hoistMaybe $ _permUpd $ getRolePermInfo roleName tableInfo
-- If we're in a frontend scenario, we should not include backend_only updates
-- For more info see Note [Backend only permissions]
guard $ not $ scenario == Frontend && upiBackendOnly updatePerms
whereArg <- lift $ P.field whereName (Just whereDesc) <$> boolExp tableInfo
selection <- lift $ mutationSelectionSet tableInfo
let argsParser = liftA2 (,) backendUpdate whereArg
pure $
P.setFieldParserOrigin (MOSourceObjId sourceName (AB.mkAnyBackend $ SMOTable @b tableName)) $
P.subselection fieldName description argsParser selection
<&> mkUpdateObject tableName columns updatePerms (Just tCase) . fmap MOutMultirowFields
-- | Construct a root field, normally called 'update_tablename_by_pk', that can be used
-- to update a single in a DB table, specified by primary key. Only returns a
-- parser if there are columns the user is allowed to update and if the user has
-- select permissions on all primary keys; otherwise returns Nothing.
updateTableByPk ::
forall b r m n.
MonadBuildSchema b r m n =>
BackendTableSelectSchema b =>
-- | backend-specific data needed to perform an update mutation
P.InputFieldsParser n (BackendUpdate b (UnpreparedValue b)) ->
Scenario ->
-- | table info
TableInfo b ->
-- | field display name
Name ->
-- | field description, if any
Maybe Description ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableByPk backendUpdate scenario tableInfo fieldName description = runMaybeT $ do
sourceInfo :: SourceInfo b <- asks getter
roleName <- retrieve scRole
let sourceName = _siName sourceInfo
tableName = tableInfoName tableInfo
customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
mkTypename = runMkTypename $ _rscTypeNames customization
columns = tableColumns tableInfo
viewInfo = _tciViewInfo $ _tiCoreInfo tableInfo
guard $ isMutable viIsUpdatable viewInfo
updatePerms <- hoistMaybe $ _permUpd $ getRolePermInfo roleName tableInfo
-- If we're in a frontend scenario, we should not include backend_only updates
-- For more info see Note [Backend only permissions]
guard $ not $ scenario == Frontend && upiBackendOnly updatePerms
pkArgs <- MaybeT $ primaryKeysArguments tableInfo
selection <- MaybeT $ tableSelectionSet tableInfo
lift $ do
tableGQLName <- getTableIdentifierName tableInfo
let pkObjectName = mkTypename $ applyTypeNameCaseIdentifier tCase $ mkTablePkColumnsInputTypeName tableGQLName
pkFieldName = $$(litName "pk_columns")
pkObjectDesc = Description $ "primary key columns input for table: " <> toTxt tableName
pkParser = P.object pkObjectName (Just pkObjectDesc) pkArgs
argsParser = (,) <$> backendUpdate <*> P.field pkFieldName Nothing pkParser
pure $
P.setFieldParserOrigin (MOSourceObjId sourceName (AB.mkAnyBackend $ SMOTable @b tableName)) $
P.subselection fieldName description argsParser selection
<&> mkUpdateObject tableName columns updatePerms (Just tCase) . fmap MOutSinglerowObject
mkUpdateObject ::
Backend b =>
TableName b ->
[ColumnInfo b] ->
UpdPermInfo b ->
(Maybe NamingCase) ->
( ( BackendUpdate b (UnpreparedValue b),
AnnBoolExp b (UnpreparedValue b)
),
MutationOutputG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
) ->
AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkUpdateObject _auTable _auAllCols updatePerms _auNamingConvention ((_auBackend, whereExp), _auOutput) =
AnnotatedUpdateG {..}
where
permissionFilter = fmap partialSQLExpToUnpreparedValue <$> upiFilter updatePerms
_auWhere = (permissionFilter, whereExp)
_auCheck = maybe annBoolExpTrue ((fmap . fmap) partialSQLExpToUnpreparedValue) $ upiCheck updatePerms

View File

@ -0,0 +1,217 @@
{-# LANGUAGE TemplateHaskell #-}
module Hasura.GraphQL.Schema.Update.Batch
( updateTable,
updateTableMany,
updateTableByPk,
)
where
import Data.Has (Has (getter))
import Data.Text.Casing (GQLNameIdentifier)
import Data.Text.Extended (toTxt, (<>>))
import Hasura.GraphQL.Schema.Backend (BackendTableSelectSchema (..), BackendUpdateOperatorsSchema (..), MonadBuildSchema)
import Hasura.GraphQL.Schema.BoolExp (AggregationPredicatesSchema, boolExp)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation (mutationSelectionSet, primaryKeysArguments)
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Table (tableColumns)
import Hasura.GraphQL.Schema.Typename
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp (annBoolExpTrue)
import Hasura.RQL.IR.Returning (MutationOutputG (..))
import Hasura.RQL.IR.Root (RemoteRelationshipField)
import Hasura.RQL.IR.Update (AnnotatedUpdateG (..))
import Hasura.RQL.IR.Update.Batch (UpdateBatch (..))
import Hasura.RQL.IR.Value
import Hasura.RQL.Types.Backend (Backend (..))
import Hasura.RQL.Types.Column (ColumnInfo (..))
import Hasura.RQL.Types.Common (Comment (..))
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.AnyBackend qualified as AB
import Language.GraphQL.Draft.Syntax (Description (..), Name (..), litName)
buildAnnotatedUpdateGField ::
forall b r m n.
MonadBuildSchema b r m n =>
Scenario ->
TableInfo b ->
-- | field display name
Name ->
-- | field description, if any
Maybe Description ->
-- | parser of 'MutationOutputG'
MaybeT (SchemaT r m) (P.Parser 'P.Output n (MutationOutputG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))) ->
-- | parser of the backend-specific 'UpdateVariant'
(UpdPermInfo b -> MaybeT (SchemaT r m) (P.InputFieldsParser n (UpdateVariant b (UnpreparedValue b)))) ->
MaybeT (SchemaT r m) (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
buildAnnotatedUpdateGField scenario tableInfo fieldName description parseOutput mkUpdateVariantParser = do
roleName <- retrieve scRole
updatePerms <- hoistMaybe $ _permUpd $ getRolePermInfo roleName tableInfo
guard $ not $ scenario == Frontend && upiBackendOnly updatePerms
(sourceInfo :: SourceInfo b) <- asks getter
let sourceName = _siName sourceInfo
customization = _siCustomization sourceInfo
tCase = _rscNamingConvention customization
columns = tableColumns tableInfo
viewInfo = _tciViewInfo $ _tiCoreInfo tableInfo
tableName = tableInfoName tableInfo
guard $ isMutable viIsUpdatable viewInfo
outputParser <- parseOutput
updateVariantParser <- mkUpdateVariantParser updatePerms
pure $
P.setFieldParserOrigin (MOSourceObjId sourceName (AB.mkAnyBackend $ SMOTable @b tableName)) $
mkAnnotatedUpdateG tableName columns updatePerms (Just tCase)
<$> P.subselection fieldName description updateVariantParser outputParser
-- | Construct a root field, normally called update_tablename, that can be used
-- to update rows in a DB table specified by filters. Only returns a parser if
-- there are columns the user is allowed to update; otherwise returns Nothing.
updateTable ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b,
BackendUpdateOperatorsSchema b
) =>
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b) -> UpdateVariant b (UnpreparedValue b)) ->
Scenario ->
TableInfo b ->
-- | table field display name
GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTable mkSingleBatchUpdateVariant scenario tableInfo tableGqlName = runMaybeT $ do
customization <- asks (_siCustomization . getter @(SourceInfo b))
let (MkRootFieldName mkRootFieldName) = _rscRootFields customization
tCase = _rscNamingConvention customization
updateTableFieldName = mkRootFieldName $ setFieldNameCase tCase tableInfo _tcrfUpdate mkUpdateField tableGqlName
let parseOutput = lift $ fmap MOutMultirowFields <$> mutationSelectionSet tableInfo
buildAnnotatedUpdateGField scenario tableInfo updateTableFieldName updateTableFieldDescription parseOutput $ \updatePerms -> lift $ do
whereArg <- P.field Name._where (Just whereDesc) <$> boolExp tableInfo
updateOperators <- parseUpdateOperators tableInfo updatePerms
pure $ mkSingleBatchUpdateVariant <$> (UpdateBatch <$> updateOperators <*> whereArg)
where
tableName = tableInfoName tableInfo
updateTableFieldDescription = buildFieldDescription defaultUpdateDesc $ _crfComment _tcrfUpdate
defaultUpdateDesc = "update data of the table: " <>> tableName
whereDesc = "filter the rows which have to be updated"
TableCustomRootFields {..} = _tcCustomRootFields . _tciCustomConfig $ _tiCoreInfo tableInfo
updateTableMany ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b,
BackendUpdateOperatorsSchema b
) =>
([UpdateBatch b (UpdateOperators b) (UnpreparedValue b)] -> UpdateVariant b (UnpreparedValue b)) ->
Scenario ->
TableInfo b ->
-- | table field display name
GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableMany mkSingleBatchUpdateVariant scenario tableInfo tableGqlName = runMaybeT $ do
validateShouldIncludeUpdateManyFields
customization <- asks (_siCustomization . getter @(SourceInfo b))
let (MkRootFieldName mkRootFieldName) = _rscRootFields customization
mkTypename = runMkTypename $ _rscTypeNames customization
tCase = _rscNamingConvention customization
updatesObjectName = mkTypename $ applyTypeNameCaseIdentifier tCase $ mkMultiRowUpdateTypeName tableGqlName
updateTableManyFieldName = mkRootFieldName $ setFieldNameCase tCase tableInfo _tcrfUpdateMany mkUpdateManyField tableGqlName
let parseOutput = lift $ fmap MOutMultirowFields . P.multiple <$> mutationSelectionSet tableInfo
buildAnnotatedUpdateGField scenario tableInfo updateTableManyFieldName updateManyFieldDescription parseOutput $ \updatePerms -> lift $ do
updateOperators <- parseUpdateOperators tableInfo updatePerms
fmap mkSingleBatchUpdateVariant
. P.field Name._updates (Just updatesDesc)
. P.list
. P.object updatesObjectName Nothing
<$> do
whereExp <- P.field Name._where (Just whereDesc) <$> boolExp tableInfo
pure $ UpdateBatch <$> updateOperators <*> whereExp
where
tableName = tableInfoName tableInfo
updateManyFieldDescription = buildFieldDescription defaultUpdateManyDesc $ _crfComment _tcrfUpdateMany
defaultUpdateManyDesc = "update multiples rows of table: " <>> tableName
whereDesc = "filter the rows which have to be updated"
updatesDesc = "updates to execute, in order"
TableCustomRootFields {..} = _tcCustomRootFields . _tciCustomConfig $ _tiCoreInfo tableInfo
-- we only include the multiUpdate field if the
-- experimental feature 'hide_update_many_fields' is off
validateShouldIncludeUpdateManyFields =
retrieve Options.soIncludeUpdateManyFields >>= \case
Options.IncludeUpdateManyFields -> hoistMaybe $ Just ()
Options.Don'tIncludeUpdateManyFields -> hoistMaybe $ Nothing
-- | Construct a root field, normally called 'update_tablename_by_pk', that can be used
-- to update a single in a DB table, specified by primary key. Only returns a
-- parser if there are columns the user is allowed to update and if the user has
-- select permissions on all primary keys; otherwise returns Nothing.
updateTableByPk ::
forall b r m n.
( MonadBuildSchema b r m n,
BackendTableSelectSchema b,
BackendUpdateOperatorsSchema b
) =>
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b) -> UpdateVariant b (UnpreparedValue b)) ->
Scenario ->
TableInfo b ->
-- | table field display name
GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableByPk mkSingleBatchUpdateVariant scenario tableInfo tableGqlName = runMaybeT do
customization <- asks (_siCustomization . getter @(SourceInfo b))
let (MkRootFieldName mkRootFieldName) = _rscRootFields customization
mkTypename = runMkTypename $ _rscTypeNames customization
tCase = _rscNamingConvention customization
updateTableFieldName = mkRootFieldName $ setFieldNameCase tCase tableInfo _tcrfUpdateByPk mkUpdateByPkField tableGqlName
pkObjectName = mkTypename $ applyTypeNameCaseIdentifier tCase $ mkTablePkColumnsInputTypeName tableGqlName
let parseOutput = fmap MOutSinglerowObject <$> MaybeT (tableSelectionSet tableInfo)
buildAnnotatedUpdateGField scenario tableInfo updateTableFieldName updateByPkFieldDescription parseOutput $ \updatePerms -> do
pkArgs <- MaybeT $ primaryKeysArguments tableInfo
lift $ do
updateOperators <- parseUpdateOperators tableInfo updatePerms
let pkParser = P.object pkObjectName (Just pkObjectDesc) pkArgs
let whereParser = P.field pkFieldName Nothing pkParser
pure $ mkSingleBatchUpdateVariant <$> (UpdateBatch <$> updateOperators <*> whereParser)
where
tableName = tableInfoName tableInfo
updateByPkFieldDescription = buildFieldDescription defaultUpdateByPkDesc $ _crfComment _tcrfUpdateByPk
defaultUpdateByPkDesc = "update single row of the table: " <>> tableName
pkObjectDesc = Description $ "primary key columns input for table: " <> toTxt tableName
pkFieldName = $$(litName "pk_columns")
TableCustomRootFields {..} = _tcCustomRootFields . _tciCustomConfig $ _tiCoreInfo tableInfo
mkAnnotatedUpdateG ::
Backend b =>
TableName b ->
[ColumnInfo b] ->
UpdPermInfo b ->
(Maybe NamingCase) ->
( UpdateVariant b (UnpreparedValue b),
MutationOutputG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
) ->
AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkAnnotatedUpdateG _auTable _auAllCols updatePerms _auNamingConvention (_auUpdateVariant, _auOutput) =
AnnotatedUpdateG {..}
where
_auUpdatePermissions = fmap partialSQLExpToUnpreparedValue <$> upiFilter updatePerms
_auCheck = maybe annBoolExpTrue ((fmap . fmap) partialSQLExpToUnpreparedValue) $ upiCheck updatePerms
buildFieldDescription :: Text -> Comment -> Maybe Description
buildFieldDescription defaultDescription = \case
Automatic -> Just $ Description defaultDescription
Explicit comment -> Description . toTxt <$> comment

View File

@ -25,6 +25,7 @@ import Hasura.RQL.DML.Internal
import Hasura.RQL.DML.Types
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.Update
import Hasura.RQL.IR.Update.Batch
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Metadata
@ -190,9 +191,13 @@ validateUpdateQueryWith sessVarBldr prepValBldr uq = do
return $
AnnotatedUpdateG
tableName
(resolvedUpdFltr, annSQLBoolExp)
resolvedUpdFltr
resolvedUpdCheck
(BackendUpdate $ Map.fromList $ fmap UpdateSet <$> setExpItems)
( SingleBatch $
UpdateBatch
(Map.fromList $ fmap UpdateSet <$> setExpItems)
annSQLBoolExp
)
(mkDefaultMutFlds mAnnRetCols)
allCols
Nothing

View File

@ -5,9 +5,9 @@ module Hasura.RQL.IR.Update
( AnnotatedUpdate,
AnnotatedUpdateG (..),
auTable,
auWhere,
auUpdatePermissions,
auCheck,
auBackend,
auUpdateVariant,
auOutput,
auAllCols,
auNamingConvention,
@ -24,16 +24,13 @@ import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.SQL.Backend
--------------------------------------------------------------------------------
data AnnotatedUpdateG (b :: BackendType) (r :: Type) v = AnnotatedUpdateG
{ _auTable :: TableName b,
-- | The where clause for /update_table/ and /update_table_by_pk/ along with
-- the permissions filter.
-- In the case of /update_table_many/, this will be empty and the actual
-- where clauses (one per update) are found in 'BackendUpdate'.
_auWhere :: (AnnBoolExp b v, AnnBoolExp b v),
_auUpdatePermissions :: AnnBoolExp b v,
_auCheck :: AnnBoolExp b v,
-- | All the backend-specific data related to an update mutation
_auBackend :: BackendUpdate b v,
_auUpdateVariant :: UpdateVariant b v,
-- we don't prepare the arguments for returning
-- however the session variable can still be
-- converted as desired
@ -47,23 +44,23 @@ data AnnotatedUpdateG (b :: BackendType) (r :: Type) v = AnnotatedUpdateG
deriving stock instance
( Backend b,
Eq (AnnBoolExp b v),
Eq (MutationOutputG b r v),
Eq (BackendUpdate b v),
Eq r,
Eq v
Show v,
Show r,
Show (AnnBoolExp b v),
Show (UpdateVariant b v),
Show (MutationOutputG b r v)
) =>
Eq (AnnotatedUpdateG b r v)
Show (AnnotatedUpdateG b r v)
deriving stock instance
( Backend b,
Show (AnnBoolExp b v),
Show (MutationOutputG b r v),
Show (BackendUpdate b v),
Show r,
Show v
Eq v,
Eq r,
Eq (AnnBoolExp b v),
Eq (UpdateVariant b v),
Eq (MutationOutputG b r v)
) =>
Show (AnnotatedUpdateG b r v)
Eq (AnnotatedUpdateG b r v)
type AnnotatedUpdate b = AnnotatedUpdateG b Void (SQLExpression b)

View File

@ -0,0 +1,50 @@
{-# LANGUAGE UndecidableInstances #-}
-- | Contains types that can be used by backends to structure updates
-- to batches of rows in a table
module Hasura.RQL.IR.Update.Batch
( UpdateBatch (..),
updateBatchIsEmpty,
)
where
import Data.HashMap.Strict qualified as HashMap
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.Types.Backend
import Hasura.SQL.Backend
-- | Represents a set of update operations ('_ubOperations') applied to a batch of rows selected
-- from a table by filtering it with a boolean expression ('_ubWhere').
--
-- This type may be used by specific backends as a part their 'UpdateVariant'.
-- See 'Hasura.Backends.Postgres.Types.Update.PgUpdateVariant' for an example.
--
-- The actual operators used to affect changes against columns in '_ubOperations' are abstract
-- here and are specified by the specific backends based on what they actually support
data UpdateBatch (b :: BackendType) updateOperators v = UpdateBatch
{ _ubOperations :: HashMap (Column b) (updateOperators v),
_ubWhere :: AnnBoolExp b v
}
deriving stock (Functor, Foldable, Traversable)
deriving stock instance
( Backend b,
Show v,
Show (updateOperators v),
Show (AnnBoolExp b v)
) =>
Show (UpdateBatch b updateOperators v)
deriving stock instance
( Backend b,
Eq v,
Eq (updateOperators v),
Eq (AnnBoolExp b v)
) =>
Eq (UpdateBatch b updateOperators v)
-- | Are we actually updating anything in the batch?
updateBatchIsEmpty :: UpdateBatch b updateOperators v -> Bool
updateBatchIsEmpty UpdateBatch {..} =
HashMap.null _ubOperations

View File

@ -170,9 +170,9 @@ class
Show (XStreamingSubscription b),
-- Intermediate Representations
Traversable (BooleanOperators b),
Functor (BackendUpdate b),
Foldable (BackendUpdate b),
Traversable (BackendUpdate b),
Functor (UpdateVariant b),
Foldable (UpdateVariant b),
Traversable (UpdateVariant b),
Functor (BackendInsert b),
Foldable (BackendInsert b),
Traversable (BackendInsert b),
@ -288,14 +288,17 @@ class
type AggregationPredicates b = Const Void
-- | Intermediate Representation of Update Mutations.
-- | The different variants of update supported by a backend for their
-- intermediate representation. For example, a backend could use a sum type
-- encapsulating either a single batch update or multiple batch updates.
--
-- The default implementation makes update expressions uninstantiable.
--
-- It is parameterised over the type of fields, which changes during the IR
-- translation phases.
type BackendUpdate b :: Type -> Type
type UpdateVariant b :: Type -> Type
type BackendUpdate b = Const Void
type UpdateVariant b = Const Void
-- | Intermediate Representation of Insert Mutations.
-- The default implementation makes insert expressions uninstantiable.

View File

@ -23,6 +23,7 @@ module Hasura.RQL.Types.SourceCustomization
getNamingCase,
getTextFieldName,
getTextTypeName,
setFieldNameCase,
-- * Field name builders
mkSelectField,
@ -81,6 +82,7 @@ import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.Types.Backend (SupportedNamingCase (..))
import Hasura.RQL.Types.Instances ()
import Hasura.RQL.Types.Table
import Language.GraphQL.Draft.Syntax qualified as G
data RootFieldsCustomization = RootFieldsCustomization
@ -173,6 +175,23 @@ applyEnumValueCase tCase v = case tCase of
HasuraCase -> v
GraphqlCase -> C.transformNameWith (T.toUpper) v
-- | Builds field name with proper case. Please note that this is a pure
-- function as all the validation has already been done while preparing
-- @GQLNameIdentifier@.
setFieldNameCase ::
NamingCase ->
TableInfo b ->
CustomRootField ->
(C.GQLNameIdentifier -> C.GQLNameIdentifier) ->
C.GQLNameIdentifier ->
G.Name
setFieldNameCase tCase tInfo crf getFieldName tableName =
(applyFieldNameCaseIdentifier tCase fieldIdentifier)
where
tccName = fmap C.fromCustomName . _tcCustomName . _tciCustomConfig . _tiCoreInfo $ tInfo
crfName = fmap C.fromCustomName (_crfName crf)
fieldIdentifier = fromMaybe (getFieldName (fromMaybe tableName tccName)) crfName
-- | append/prepend the suffix/prefix in the graphql name
applyPrefixSuffix :: Maybe G.Name -> Maybe G.Name -> NamingCase -> Bool -> G.Name -> G.Name
applyPrefixSuffix Nothing Nothing tCase isTypeName name = concatPrefixSuffix tCase isTypeName $ NE.fromList [(name, C.CustomName)]

View File

@ -24,16 +24,20 @@ spec =
table = Expect.mkTable "test",
columns = [P.idColumn, P.nameColumn],
mutationOutput = MOutMultirowFields [("affected_rows", MCount)],
where_ = [(P.idColumn, [AEQ True P.integerOne])],
update = Expect.UpdateTable [(P.nameColumn, UpdateSet P.textNew)],
updateVariant =
Expect.SingleBatchUpdate $
Expect.UpdateBatchBuilder
{ ubbOperations = [(P.nameColumn, UpdateSet P.textNew)],
ubbWhere = [(P.idColumn, [AEQ True P.integerOne])]
},
expectedSQL =
[QQ.sql|
UPDATE "public"."test"
SET "name" = ('new name'):: text
WHERE
(("public"."test"."id") = (('1')::integer))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
UPDATE "public"."test"
SET "name" = ('new name'):: text
WHERE
(("public"."test"."id") = (('1')::integer))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
}
Test.runTest
@ -42,20 +46,23 @@ UPDATE "public"."test"
table = Expect.mkTable "test",
columns = [P.idColumn, P.nameColumn, P.descColumn],
mutationOutput = MOutMultirowFields [("affected_rows", MCount)],
where_ = [(P.idColumn, [AEQ True P.integerOne])],
update =
Expect.UpdateTable
[ (P.nameColumn, UpdateSet P.textNew),
(P.descColumn, UpdateSet P.textOther)
],
updateVariant =
Expect.SingleBatchUpdate $
Expect.UpdateBatchBuilder
{ ubbOperations =
[ (P.nameColumn, UpdateSet P.textNew),
(P.descColumn, UpdateSet P.textOther)
],
ubbWhere = [(P.idColumn, [AEQ True P.integerOne])]
},
expectedSQL =
[QQ.sql|
UPDATE "public"."test"
SET "name" = ('new name')::text, "description" = ('other')::text
WHERE
(("public"."test"."id") = (('1')::integer))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
UPDATE "public"."test"
SET "name" = ('new name')::text, "description" = ('other')::text
WHERE
(("public"."test"."id") = (('1')::integer))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
}
Test.runTest
@ -64,25 +71,29 @@ UPDATE "public"."test"
table = Expect.mkTable "test",
columns = [P.idColumn, P.nameColumn, P.descColumn],
mutationOutput = MOutMultirowFields [("affected_rows", MCount)],
where_ =
[ (P.idColumn, [AEQ True P.integerOne]),
(P.nameColumn, [AEQ False P.textOld])
],
update = Expect.UpdateTable [(P.nameColumn, UpdateSet P.textNew)],
updateVariant =
Expect.SingleBatchUpdate $
Expect.UpdateBatchBuilder
{ ubbOperations = [(P.nameColumn, UpdateSet P.textNew)],
ubbWhere =
[ (P.idColumn, [AEQ True P.integerOne]),
(P.nameColumn, [AEQ False P.textOld])
]
},
expectedSQL =
[QQ.sql|
UPDATE "public"."test"
SET "name" = ('new name')::text
WHERE
((("public"."test"."id") = (('1')::integer))
AND
((("public"."test"."name") = (('old name')::text))
OR
((("public"."test"."name") IS NULL)
AND ((('old name')::text) IS NULL))
))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
UPDATE "public"."test"
SET "name" = ('new name')::text
WHERE
((("public"."test"."id") = (('1')::integer))
AND
((("public"."test"."name") = (('old name')::text))
OR
((("public"."test"."name") IS NULL)
AND ((('old name')::text) IS NULL))
))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
}
Test.runMultipleUpdates
@ -91,41 +102,40 @@ UPDATE "public"."test"
table = Expect.mkTable "test",
columns = [P.idColumn, P.nameColumn, P.descColumn],
mutationOutput = MOutMultirowFields [("affected_rows", MCount)],
where_ = [],
update =
Expect.UpdateMany $
[ Expect.MultiRowUpdateBuilder
{ mrubWhere =
updateVariant =
Expect.MultipleBatchesUpdate
[ Expect.UpdateBatchBuilder
{ ubbOperations = [(P.nameColumn, UpdateSet P.textNew)],
ubbWhere =
[ (P.idColumn, [AEQ True P.integerOne]),
(P.nameColumn, [AEQ False P.textNew])
],
mrubUpdate = [(P.nameColumn, UpdateSet P.textNew)]
]
},
Expect.MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumn, [AEQ True P.integerOne])],
mrubUpdate = [(P.descColumn, UpdateSet P.textNew)]
Expect.UpdateBatchBuilder
{ ubbOperations = [(P.descColumn, UpdateSet P.textNew)],
ubbWhere = [(P.idColumn, [AEQ True P.integerOne])]
}
],
expectedSQL =
[ [QQ.sql|
UPDATE "public"."test"
SET "name" = ('new name')::text
WHERE
((("public"."test"."id") = (('1')::integer))
AND
((("public"."test"."name") = (('new name')::text))
OR
((("public"."test"."name") IS NULL)
AND ((('new name')::text) IS NULL))
))
RETURNING * , ('true')::boolean AS "check__constraint"
UPDATE "public"."test"
SET "name" = ('new name')::text
WHERE
((("public"."test"."id") = (('1')::integer))
AND
((("public"."test"."name") = (('new name')::text))
OR
((("public"."test"."name") IS NULL)
AND ((('new name')::text) IS NULL))
))
RETURNING * , ('true')::boolean AS "check__constraint"
|],
[QQ.sql|
UPDATE "public"."test"
SET "description" = ('new name')::text
WHERE
(("public"."test"."id") = (('1')::integer))
RETURNING * , ('true')::boolean AS "check__constraint"
UPDATE "public"."test"
SET "description" = ('new name')::text
WHERE
(("public"."test"."id") = (('1')::integer))
RETURNING * , ('true')::boolean AS "check__constraint"
|]
]
}

View File

@ -33,18 +33,22 @@ spec = do
utsExpect =
UpdateExpectationBuilder
{ utbOutput = MOutMultirowFields [("affected_rows", MCount)],
utbWhere = [(P.nameColumnBuilder, [AEQ True P.textOld])],
utbUpdate = UpdateTable [(P.nameColumnBuilder, UpdateSet P.textNew)]
utbUpdate =
SingleBatchUpdate $
UpdateBatchBuilder
{ ubbOperations = [(P.nameColumnBuilder, UpdateSet P.textNew)],
ubbWhere = [(P.nameColumnBuilder, [AEQ True P.textOld])]
}
},
utsField =
[GQL.field|
update_artist(
where: { name: { _eq: "old name"}},
_set: { name: "new name" }
) {
affected_rows
}
|]
update_artist(
where: { name: { _eq: "old name"}},
_set: { name: "new name" }
) {
affected_rows
}
|]
}
it "two columns" do
@ -55,22 +59,25 @@ update_artist(
utsExpect =
UpdateExpectationBuilder
{ utbOutput = MOutMultirowFields [("affected_rows", MCount)],
utbWhere = [(P.nameColumnBuilder, [AEQ True P.textOld])],
utbUpdate =
UpdateTable
[ (P.nameColumnBuilder, UpdateSet P.textNew),
(P.descColumnBuilder, UpdateSet P.textOther)
]
SingleBatchUpdate $
UpdateBatchBuilder
{ ubbOperations =
[ (P.nameColumnBuilder, UpdateSet P.textNew),
(P.descColumnBuilder, UpdateSet P.textOther)
],
ubbWhere = [(P.nameColumnBuilder, [AEQ True P.textOld])]
}
},
utsField =
[GQL.field|
update_artist(
where: { name: { _eq: "old name"}},
_set: { name: "new name", description: "other" }
) {
affected_rows
}
|]
update_artist(
where: { name: { _eq: "old name"}},
_set: { name: "new name", description: "other" }
) {
affected_rows
}
|]
}
describe "update many" do
it "one update" do
@ -81,30 +88,29 @@ update_artist(
utsExpect =
UpdateExpectationBuilder
{ utbOutput = MOutMultirowFields [("affected_rows", MCount)],
utbWhere = [],
utbUpdate =
UpdateMany
[ MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])],
mrubUpdate =
MultipleBatchesUpdate
[ UpdateBatchBuilder
{ ubbOperations =
[ (P.nameColumnBuilder, UpdateSet P.textNew),
(P.descColumnBuilder, UpdateSet P.textOther)
]
],
ubbWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])]
}
]
},
utsField =
[GQL.field|
update_artist_many(
updates: [
{ where: { id: { _eq: 1 } },
_set: { name: "new name", description: "other" }
}
]
) {
affected_rows
}
|]
update_artist_many(
updates: [
{ where: { id: { _eq: 1 } },
_set: { name: "new name", description: "other" }
}
]
) {
affected_rows
}
|]
}
it "two updates, complex where clause" do
@ -115,37 +121,36 @@ update_artist_many(
utsExpect =
UpdateExpectationBuilder
{ utbOutput = MOutMultirowFields [("affected_rows", MCount)],
utbWhere = [],
utbUpdate =
UpdateMany
[ MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])],
mrubUpdate =
MultipleBatchesUpdate
[ UpdateBatchBuilder
{ ubbOperations =
[ (P.nameColumnBuilder, UpdateSet P.textNew),
(P.descColumnBuilder, UpdateSet P.textOther)
]
],
ubbWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])]
},
MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumnBuilder, [AEQ True P.integerTwo])],
mrubUpdate = [(P.descColumnBuilder, UpdateSet P.textOther)]
UpdateBatchBuilder
{ ubbOperations = [(P.descColumnBuilder, UpdateSet P.textOther)],
ubbWhere = [(P.idColumnBuilder, [AEQ True P.integerTwo])]
}
]
},
utsField =
[GQL.field|
update_artist_many(
updates: [
{ where: { id: { _eq: 1 } }
_set: { name: "new name", description: "other" }
}
{ where: { id: { _eq: 2 } }
_set: { description: "other" }
}
]
) {
affected_rows
}
|]
update_artist_many(
updates: [
{ where: { id: { _eq: 1 } }
_set: { name: "new name", description: "other" }
}
{ where: { id: { _eq: 2 } }
_set: { description: "other" }
}
]
) {
affected_rows
}
|]
}
it "three updates, ordering" do
@ -156,39 +161,38 @@ update_artist_many(
utsExpect =
UpdateExpectationBuilder
{ utbOutput = MOutMultirowFields [("affected_rows", MCount)],
utbWhere = [],
utbUpdate =
UpdateMany
[ MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])],
mrubUpdate = [(P.nameColumnBuilder, UpdateSet P.textNew)]
MultipleBatchesUpdate
[ UpdateBatchBuilder
{ ubbOperations = [(P.nameColumnBuilder, UpdateSet P.textNew)],
ubbWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])]
},
MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])],
mrubUpdate = [(P.nameColumnBuilder, UpdateSet P.textOld)]
UpdateBatchBuilder
{ ubbOperations = [(P.nameColumnBuilder, UpdateSet P.textOld)],
ubbWhere = [(P.idColumnBuilder, [AEQ True P.integerOne])]
},
MultiRowUpdateBuilder
{ mrubWhere = [(P.idColumnBuilder, [AEQ True P.integerTwo])],
mrubUpdate = [(P.nameColumnBuilder, UpdateSet P.textOther)]
UpdateBatchBuilder
{ ubbOperations = [(P.nameColumnBuilder, UpdateSet P.textOther)],
ubbWhere = [(P.idColumnBuilder, [AEQ True P.integerTwo])]
}
]
},
utsField =
[GQL.field|
update_artist_many(
updates: [
{ where: { id: { _eq: 1 } }
_set: { name: "new name" }
}
{ where: { id: { _eq: 1 } }
_set: { name: "old name" }
}
{ where: { id: { _eq: 2 } }
_set: { name: "other" }
}
]
) {
affected_rows
}
|]
update_artist_many(
updates: [
{ where: { id: { _eq: 1 } }
_set: { name: "new name" }
}
{ where: { id: { _eq: 1 } }
_set: { name: "old name" }
}
{ where: { id: { _eq: 2 } }
_set: { name: "other" }
}
]
) {
affected_rows
}
|]
}

View File

@ -15,7 +15,6 @@ where
import Hasura.Backends.Postgres.SQL.Types (QualifiedTable)
import Hasura.Backends.Postgres.Translate.Update qualified as Update
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp (OpExpG (..))
import Hasura.RQL.IR.Returning (MutationOutputG (..))
import Hasura.RQL.IR.Value (UnpreparedValue (..))
import Hasura.RQL.Types.Column (ColumnInfo)
@ -37,10 +36,8 @@ data TestBuilder e = TestBuilder
columns :: [ColumnInfo PG],
-- | expected output fields
mutationOutput :: MutationOutputG PG Void (UnpreparedValue PG),
-- | where clause for the query (usually empty for /update_many/)
where_ :: [(ColumnInfo PG, [OpExpG PG (UnpreparedValue PG)])],
-- | update clause
update :: Expect.BackendUpdateBuilder (ColumnInfo PG),
updateVariant :: Expect.UpdateVariantBuilder (ColumnInfo PG),
-- | expected result; this is either 'Text' or '[Text]'
expectedSQL :: e
}
@ -56,8 +53,7 @@ runTest TestBuilder {..} =
{ Expect.aubTable = table,
Expect.aubOutput = mutationOutput,
Expect.aubColumns = columns,
Expect.aubWhere = where_,
Expect.aubUpdate = update
Expect.aubUpdateVariant = updateVariant
}
case Update.mkUpdateCTE @'Vanilla upd of
(Update.Update cte) ->
@ -75,11 +71,10 @@ runMultipleUpdates TestBuilder {..} =
{ Expect.aubTable = table,
Expect.aubOutput = mutationOutput,
Expect.aubColumns = columns,
Expect.aubWhere = where_,
Expect.aubUpdate = update
Expect.aubUpdateVariant = updateVariant
}
case Update.mkUpdateCTE @'Vanilla upd of
(Update.MultiUpdate ctes) ->
SI.fromText . toSQLTxt <$> ctes
`shouldBe` SI.fromText <$> expectedSQL
_ -> assertFailure "expedted update_many, got single update"
_ -> assertFailure "expected update_many, got single update"

View File

@ -5,8 +5,8 @@
module Test.Parser.Expectation
( UpdateTestSetup (..),
UpdateExpectationBuilder (..),
BackendUpdateBuilder (..),
MultiRowUpdateBuilder (..),
UpdateVariantBuilder (..),
UpdateBatchBuilder (..),
runUpdateFieldTest,
module I,
AnnotatedUpdateBuilder (..),
@ -15,10 +15,9 @@ module Test.Parser.Expectation
)
where
import Data.Bifunctor (bimap)
import Data.HashMap.Strict qualified as HM
import Hasura.Backends.Postgres.SQL.Types (QualifiedTable)
import Hasura.Backends.Postgres.Types.Update (BackendUpdate (..), MultiRowUpdate (..), UpdateOpExpression (..))
import Hasura.Backends.Postgres.Types.Update (PgUpdateVariant (..), UpdateOpExpression (..))
import Hasura.GraphQL.Parser.Internal.Parser (FieldParser (..))
import Hasura.GraphQL.Parser.Schema (Definition (..))
import Hasura.GraphQL.Parser.Variable (Variable (..))
@ -28,6 +27,7 @@ import Hasura.RQL.IR.BoolExp (AnnBoolExpFld (..), GBoolExp (..), OpExpG (..))
import Hasura.RQL.IR.Returning (MutationOutputG (..))
import Hasura.RQL.IR.Root (RemoteRelationshipField)
import Hasura.RQL.IR.Update (AnnotatedUpdateG (..))
import Hasura.RQL.IR.Update.Batch (UpdateBatch (..))
import Hasura.RQL.IR.Value (UnpreparedValue)
import Hasura.RQL.Types.Column (ColumnInfo (..))
import Hasura.RQL.Types.Common (SourceName (..))
@ -50,9 +50,7 @@ type Output r = MutationOutputG PG r (UnpreparedValue PG)
type Field = Syntax.Field Syntax.NoFragments Variable
type Where = (ColumnInfoBuilder, [OpExpG PG (UnpreparedValue PG)])
type Update = BackendUpdateBuilder ColumnInfoBuilder
type Update = UpdateVariantBuilder ColumnInfoBuilder
-- | Holds all the information required to setup and run a field parser update
-- test.
@ -73,15 +71,11 @@ data UpdateExpectationBuilder = UpdateExpectationBuilder
--
-- > MOutMultirowFields [("affected_rows", MCount)]
utbOutput :: Output (RemoteRelationshipFieldWrapper UnpreparedValue),
-- | expected where condition(s), e.g. given a @nameColumn ::
-- ColumnInfoBuilder@ and @oldValue :: UnpreparedValue PG@:
-- | expected update clause(s), including the where condition as update operations,
-- e.g. given a @nameColumn :: ColumnInfoBuilder@ and
-- @newValue :: UnpreparedValue PG@:
--
-- > [(nameColumn, [AEQ true oldvalue])]
utbWhere :: [Where],
-- | expected update clause(s), e.g. given a @nameColumn ::
-- ColumnInfoBuilder@ and @newValue :: UnpreparedValue PG@:
--
-- > [(namecolumn, UpdateSet newValue)]
-- > SingleBatchUpdate (UpdateBatchBuilder [(nameColumn, [AEQ true oldvalue])] [(nameColumn, UpdateSet newValue)])
utbUpdate :: Update
}
@ -132,10 +126,9 @@ runUpdateFieldTest UpdateTestSetup {..} =
{ aubTable = table,
aubOutput = utbOutput,
aubColumns = mkColumnInfo <$> utsColumns,
aubWhere = first mkColumnInfo <$> utbWhere,
aubUpdate = mkUpdateColumns utbUpdate
aubUpdateVariant = mkUpdateColumns utbUpdate
}
mkUpdateColumns :: BackendUpdateBuilder ColumnInfoBuilder -> BackendUpdateBuilder (ColumnInfo PG)
mkUpdateColumns :: UpdateVariantBuilder ColumnInfoBuilder -> UpdateVariantBuilder (ColumnInfo PG)
mkUpdateColumns = fmap mkColumnInfo
-- | Internal use only. The intended use is through 'runUpdateFieldTest'.
@ -148,20 +141,18 @@ data AnnotatedUpdateBuilder r = AnnotatedUpdateBuilder
aubOutput :: Output r,
-- | the table columns (all of them)
aubColumns :: [ColumnInfo PG],
-- | the where clause(s)
aubWhere :: [(ColumnInfo PG, [OpExpG PG (UnpreparedValue PG)])],
-- | the update statement(s)
aubUpdate :: BackendUpdateBuilder (ColumnInfo PG)
aubUpdateVariant :: UpdateVariantBuilder (ColumnInfo PG)
}
data BackendUpdateBuilder col
= UpdateTable [(col, UpdateOpExpression (UnpreparedValue PG))]
| UpdateMany [MultiRowUpdateBuilder col]
data UpdateVariantBuilder col
= SingleBatchUpdate (UpdateBatchBuilder col)
| MultipleBatchesUpdate [UpdateBatchBuilder col]
deriving stock (Functor)
data MultiRowUpdateBuilder col = MultiRowUpdateBuilder
{ mrubWhere :: [(col, [OpExpG PG (UnpreparedValue PG)])],
mrubUpdate :: [(col, UpdateOpExpression (UnpreparedValue PG))]
data UpdateBatchBuilder col = UpdateBatchBuilder
{ ubbWhere :: [(col, [OpExpG PG (UnpreparedValue PG)])],
ubbOperations :: [(col, UpdateOpExpression (UnpreparedValue PG))]
}
deriving stock (Functor)
@ -187,27 +178,22 @@ mkAnnotatedUpdate AnnotatedUpdateBuilder {..} = AnnotatedUpdateG {..}
_auTable :: QualifiedTable
_auTable = aubTable
_auWhere :: (BoolExp, BoolExp)
_auWhere = (column, toBoolExp aubWhere)
_auCheck :: BoolExp
_auCheck = BoolAnd []
_auBackend :: BackendUpdate 'Vanilla (UnpreparedValue PG)
_auBackend =
case aubUpdate of
UpdateTable items ->
BackendUpdate $
HM.fromList $
fmap (first ciColumn) items
UpdateMany rows ->
BackendMultiRowUpdate $ fmap mapRows rows
_auUpdateVariant :: PgUpdateVariant 'Vanilla (UnpreparedValue PG)
_auUpdateVariant =
case aubUpdateVariant of
SingleBatchUpdate batch ->
SingleBatch $ mapUpdateBatch batch
MultipleBatchesUpdate batches ->
MultipleBatches $ mapUpdateBatch <$> batches
mapRows :: MultiRowUpdateBuilder (ColumnInfo PG) -> MultiRowUpdate 'Vanilla (UnpreparedValue PG)
mapRows MultiRowUpdateBuilder {..} =
MultiRowUpdate
{ mruWhere = toBoolExp mrubWhere,
mruExpression = HM.fromList $ fmap (bimap ciColumn id) mrubUpdate
mapUpdateBatch :: UpdateBatchBuilder (ColumnInfo PG) -> UpdateBatch ('Postgres 'Vanilla) UpdateOpExpression (UnpreparedValue PG)
mapUpdateBatch UpdateBatchBuilder {..} =
UpdateBatch
{ _ubWhere = toBoolExp ubbWhere,
_ubOperations = HM.fromList $ fmap (first ciColumn) ubbOperations
}
_auOutput :: Output r
@ -216,8 +202,8 @@ mkAnnotatedUpdate AnnotatedUpdateBuilder {..} = AnnotatedUpdateG {..}
_auAllCols :: [ColumnInfo PG]
_auAllCols = aubColumns
column :: BoolExp
column =
_auUpdatePermissions :: BoolExp
_auUpdatePermissions =
BoolAnd
. fmap (\c -> BoolField . AVColumn c $ [])
$ aubColumns

View File

@ -94,9 +94,7 @@ mkColumnInfo ColumnInfoBuilder {..} =
mkParser :: TableInfoBuilder -> SchemaTest [Parser]
mkParser tib =
buildTableUpdateMutationFields
mempty
Frontend
(table tib)
(buildTableInfo tib)
name
where

View File

@ -7,7 +7,8 @@ response:
Encountered conflicting definitions in the selection set for 'mutation_root'
for fields: ['update_article' defined in [table article in source default,
table author in source default], 'delete_article' defined in [table article
in source default, table author in source default], 'update_article_many',
in source default, table author in source default], 'update_article_many'
defined in [table article in source default, table author in source default],
'insert_article_one' defined in [table article in source default, table
author in source default], 'update_article_by_pk' defined in [table article
in source default, table author in source default], 'delete_article_by_pk'