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, tableBoolExp)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation (mutationSelectionSet, primaryKeysArguments)
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 (..), ResolvedWebhook)
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.NamingCase
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.Schema.Options qualified as Options
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.Table.Cache
import Language.GraphQL.Draft.Syntax (Description (..), Name (..))
buildAnnotatedUpdateGField ::
forall b r m n.
(MonadBuildSchema b r m n) =>
Scenario ->
TableInfo b ->
Name ->
Maybe Description ->
MaybeT (SchemaT r m) (P.Parser 'P.Output n (MutationOutputG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))) ->
(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 :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
buildAnnotatedUpdateGField Scenario
scenario TableInfo b
tableInfo Name
fieldName Maybe Description
description MaybeT
(SchemaT r m)
(Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (UpdateVariant b (UnpreparedValue b)))
mkUpdateVariantParser = do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
UpdPermInfo b
updatePerms <- Maybe (UpdPermInfo b) -> MaybeT (SchemaT r m) (UpdPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (UpdPermInfo b) -> MaybeT (SchemaT r m) (UpdPermInfo b))
-> Maybe (UpdPermInfo b) -> MaybeT (SchemaT r m) (UpdPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (UpdPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd (RolePermInfo b -> Maybe (UpdPermInfo b))
-> RolePermInfo b -> Maybe (UpdPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> RolePermInfo b
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo b
tableInfo
Bool -> MaybeT (SchemaT r m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT (SchemaT r m) ())
-> Bool -> MaybeT (SchemaT r m) ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Scenario
scenario Scenario -> Scenario -> Bool
forall a. Eq a => a -> a -> Bool
== Scenario
Frontend Bool -> Bool -> Bool
&& UpdPermInfo b -> Bool
forall (b :: BackendType). UpdPermInfo b -> Bool
upiBackendOnly UpdPermInfo b
updatePerms
(SourceInfo b
sourceInfo :: SourceInfo b) <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
customization :: ResolvedSourceCustomization
customization = SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
columns :: [ColumnInfo b]
columns = TableInfo b -> [ColumnInfo b]
forall (b :: BackendType). TableInfo b -> [ColumnInfo b]
tableColumns TableInfo b
tableInfo
viewInfo :: Maybe ViewInfo
viewInfo = TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> Maybe ViewInfo
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> Maybe ViewInfo
_tciViewInfo (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> Maybe ViewInfo)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> Maybe ViewInfo
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
validateInput :: Maybe (ValidateInput ResolvedWebhook)
validateInput = UpdPermInfo b -> Maybe (ValidateInput ResolvedWebhook)
forall (b :: BackendType).
UpdPermInfo b -> Maybe (ValidateInput ResolvedWebhook)
upiValidateInput UpdPermInfo b
updatePerms
Bool -> MaybeT (SchemaT r m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT (SchemaT r m) ())
-> Bool -> MaybeT (SchemaT r m) ()
forall a b. (a -> b) -> a -> b
$ (ViewInfo -> Bool) -> Maybe ViewInfo -> Bool
isMutable ViewInfo -> Bool
viIsUpdatable Maybe ViewInfo
viewInfo
Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
outputParser <- MaybeT
(SchemaT r m)
(Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput
InputFieldsParser n (UpdateVariant b (UnpreparedValue b))
updateVariantParser <- UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (UpdateVariant b (UnpreparedValue b)))
mkUpdateVariantParser UpdPermInfo b
updatePerms
FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ MetadataObjId
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (m :: * -> *) origin a.
origin -> FieldParser origin m a -> FieldParser origin m a
P.setFieldParserOrigin (SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
sourceName (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). TableName b -> SourceMetadataObjId b
SMOTable @b TableName b
tableName))
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ TableName b
-> [ColumnInfo b]
-> UpdPermInfo b
-> Maybe NamingCase
-> Maybe (ValidateInput ResolvedWebhook)
-> (UpdateVariant b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
TableName b
-> [ColumnInfo b]
-> UpdPermInfo b
-> Maybe NamingCase
-> Maybe (ValidateInput ResolvedWebhook)
-> (UpdateVariant b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkAnnotatedUpdateG TableName b
tableName [ColumnInfo b]
columns UpdPermInfo b
updatePerms (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase) Maybe (ValidateInput ResolvedWebhook)
validateInput
((UpdateVariant b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(UpdateVariant b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> InputFieldsParser n (UpdateVariant b (UnpreparedValue b))
-> Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(UpdateVariant b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Output m b
-> FieldParser origin m (a, b)
P.subselection Name
fieldName Maybe Description
description InputFieldsParser n (UpdateVariant b (UnpreparedValue b))
updateVariantParser Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
outputParser
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 ->
GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTable :: forall (b :: BackendType) 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
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTable UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant Scenario
scenario TableInfo b
tableInfo GQLNameIdentifier
tableGqlName = MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
ResolvedSourceCustomization
customization <- (r -> ResolvedSourceCustomization)
-> MaybeT (SchemaT r m) ResolvedSourceCustomization
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization (SourceInfo b -> ResolvedSourceCustomization)
-> (r -> SourceInfo b) -> r -> ResolvedSourceCustomization
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a t. Has a t => t -> a
getter @(SourceInfo b))
let (MkRootFieldName Name -> Name
mkRootFieldName) = ResolvedSourceCustomization -> MkRootFieldName
_rscRootFields ResolvedSourceCustomization
customization
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
updateTableFieldName :: Name
updateTableFieldName = Name -> Name
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfUpdate GQLNameIdentifier -> GQLNameIdentifier
mkUpdateField GQLNameIdentifier
tableGqlName
let parseOutput :: MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput = SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ (MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a b.
(a -> b)
-> Parser MetadataObjId 'Output n a
-> Parser MetadataObjId 'Output n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
MutFldsG b r v -> MutationOutputG b r v
MOutMultirowFields (Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT
r
m
(Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
mutationSelectionSet TableInfo b
tableInfo
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
buildAnnotatedUpdateGField Scenario
scenario TableInfo b
tableInfo Name
updateTableFieldName Maybe Description
updateTableFieldDescription MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput ((UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ \UpdPermInfo b
updatePerms -> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ do
InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
whereArg <- Name
-> Maybe Description
-> Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
P.field Name
Name._where (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
whereDesc) (Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b)))
-> SchemaT
r
m
(Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b)))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r
m
(Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
TableInfo b
-> SchemaT r m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
tableBoolExp TableInfo b
tableInfo
InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
updateOperators <- TableInfo b
-> UpdPermInfo b
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) r.
(BackendUpdateOperatorsSchema b, MonadBuildSchema b r m n) =>
TableInfo b
-> UpdPermInfo b
-> SchemaT
r
m
(InputFieldsParser
n (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
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))))
parseUpdateOperators TableInfo b
tableInfo UpdPermInfo b
updatePerms
InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant (UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
forall (b :: BackendType) (updateOperators :: * -> *) v.
HashMap (Column b) (updateOperators v)
-> AnnBoolExp b v -> UpdateBatch b updateOperators v
UpdateBatch (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
updateOperators InputFieldsParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall a b.
InputFieldsParser MetadataObjId n (a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
whereArg)
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
updateTableFieldDescription :: Maybe Description
updateTableFieldDescription = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultUpdateDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfUpdate
defaultUpdateDesc :: Text
defaultUpdateDesc = Text
"update data of the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
whereDesc :: Description
whereDesc = Description
"filter the rows which have to be updated"
TableCustomRootFields {CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfSelect :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfInsert :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfUpdateMany :: CustomRootField
_tcrfDelete :: CustomRootField
_tcrfDeleteByPk :: CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
..} = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
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 ->
GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableMany :: forall (b :: BackendType) 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
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableMany [UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant Scenario
scenario TableInfo b
tableInfo GQLNameIdentifier
tableGqlName = MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
MaybeT (SchemaT r m) ()
validateShouldIncludeUpdateManyFields
ResolvedSourceCustomization
customization <- (r -> ResolvedSourceCustomization)
-> MaybeT (SchemaT r m) ResolvedSourceCustomization
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization (SourceInfo b -> ResolvedSourceCustomization)
-> (r -> SourceInfo b) -> r -> ResolvedSourceCustomization
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a t. Has a t => t -> a
getter @(SourceInfo b))
let (MkRootFieldName Name -> Name
mkRootFieldName) = ResolvedSourceCustomization -> MkRootFieldName
_rscRootFields ResolvedSourceCustomization
customization
mkTypename :: Name -> Name
mkTypename = MkTypename -> Name -> Name
runMkTypename (MkTypename -> Name -> Name) -> MkTypename -> Name -> Name
forall a b. (a -> b) -> a -> b
$ ResolvedSourceCustomization -> MkTypename
_rscTypeNames ResolvedSourceCustomization
customization
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
updatesObjectName :: Name
updatesObjectName = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkMultiRowUpdateTypeName GQLNameIdentifier
tableGqlName
updateTableManyFieldName :: Name
updateTableManyFieldName = Name -> Name
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfUpdateMany GQLNameIdentifier -> GQLNameIdentifier
mkUpdateManyField GQLNameIdentifier
tableGqlName
let parseOutput :: MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput = SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ (MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a b.
(a -> b)
-> Parser MetadataObjId 'Output n a
-> Parser MetadataObjId 'Output n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
MutFldsG b r v -> MutationOutputG b r v
MOutMultirowFields (Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.multiple (Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT
r
m
(Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
mutationSelectionSet TableInfo b
tableInfo
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
buildAnnotatedUpdateGField Scenario
scenario TableInfo b
tableInfo Name
updateTableManyFieldName Maybe Description
updateManyFieldDescription MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput ((UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ \UpdPermInfo b
updatePerms -> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ do
InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
updateOperators <- TableInfo b
-> UpdPermInfo b
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) r.
(BackendUpdateOperatorsSchema b, MonadBuildSchema b r m n) =>
TableInfo b
-> UpdPermInfo b
-> SchemaT
r
m
(InputFieldsParser
n (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
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))))
parseUpdateOperators TableInfo b
tableInfo UpdPermInfo b
updatePerms
([UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> UpdateVariant b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant
(InputFieldsParser
MetadataObjId
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> (InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)])
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
P.field Name
Name._updates (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
updatesDesc)
(Parser
MetadataObjId
'Input
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)])
-> (InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)])
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser
MetadataObjId
'Input
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list
(Parser
MetadataObjId
'Input
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)])
-> (InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
[UpdateBatch b (UpdateOperators b) (UnpreparedValue b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
updatesObjectName Maybe Description
forall a. Maybe a
Nothing
(InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
whereExp <- Name
-> Maybe Description
-> Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
P.field Name
Name._where (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
whereDesc) (Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b)))
-> SchemaT
r
m
(Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b)))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r
m
(Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
TableInfo b
-> SchemaT r m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
tableBoolExp TableInfo b
tableInfo
InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ HashMap (Column b) (UpdateOperators b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
forall (b :: BackendType) (updateOperators :: * -> *) v.
HashMap (Column b) (updateOperators v)
-> AnnBoolExp b v -> UpdateBatch b updateOperators v
UpdateBatch (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
updateOperators InputFieldsParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall a b.
InputFieldsParser MetadataObjId n (a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
whereExp
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
updateManyFieldDescription :: Maybe Description
updateManyFieldDescription = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultUpdateManyDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfUpdateMany
defaultUpdateManyDesc :: Text
defaultUpdateManyDesc = Text
"update multiples rows of table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
whereDesc :: Description
whereDesc = Description
"filter the rows which have to be updated"
updatesDesc :: Description
updatesDesc = Description
"updates to execute, in order"
TableCustomRootFields {CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: CustomRootField
_tcrfSelect :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfInsert :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfDelete :: CustomRootField
_tcrfDeleteByPk :: CustomRootField
..} = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
validateShouldIncludeUpdateManyFields :: MaybeT (SchemaT r m) ()
validateShouldIncludeUpdateManyFields =
(SchemaOptions -> IncludeUpdateManyFields)
-> MaybeT (SchemaT r m) IncludeUpdateManyFields
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> IncludeUpdateManyFields
Options.soIncludeUpdateManyFields MaybeT (SchemaT r m) IncludeUpdateManyFields
-> (IncludeUpdateManyFields -> MaybeT (SchemaT r m) ())
-> MaybeT (SchemaT r m) ()
forall a b.
MaybeT (SchemaT r m) a
-> (a -> MaybeT (SchemaT r m) b) -> MaybeT (SchemaT r m) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
IncludeUpdateManyFields
Options.IncludeUpdateManyFields -> Maybe () -> MaybeT (SchemaT r m) ()
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe () -> MaybeT (SchemaT r m) ())
-> Maybe () -> MaybeT (SchemaT r m) ()
forall a b. (a -> b) -> a -> b
$ () -> Maybe ()
forall a. a -> Maybe a
Just ()
IncludeUpdateManyFields
Options.Don'tIncludeUpdateManyFields -> Maybe () -> MaybeT (SchemaT r m) ()
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe () -> MaybeT (SchemaT r m) ())
-> Maybe () -> MaybeT (SchemaT r m) ()
forall a b. (a -> b) -> a -> b
$ Maybe ()
forall a. Maybe a
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 ->
GQLNameIdentifier ->
SchemaT r m (Maybe (P.FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableByPk :: forall (b :: BackendType) 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
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableByPk UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant Scenario
scenario TableInfo b
tableInfo GQLNameIdentifier
tableGqlName = MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
ResolvedSourceCustomization
customization <- (r -> ResolvedSourceCustomization)
-> MaybeT (SchemaT r m) ResolvedSourceCustomization
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization (SourceInfo b -> ResolvedSourceCustomization)
-> (r -> SourceInfo b) -> r -> ResolvedSourceCustomization
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a t. Has a t => t -> a
getter @(SourceInfo b))
let (MkRootFieldName Name -> Name
mkRootFieldName) = ResolvedSourceCustomization -> MkRootFieldName
_rscRootFields ResolvedSourceCustomization
customization
mkTypename :: Name -> Name
mkTypename = MkTypename -> Name -> Name
runMkTypename (MkTypename -> Name -> Name) -> MkTypename -> Name -> Name
forall a b. (a -> b) -> a -> b
$ ResolvedSourceCustomization -> MkTypename
_rscTypeNames ResolvedSourceCustomization
customization
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
updateTableFieldName :: Name
updateTableFieldName = Name -> Name
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfUpdateByPk GQLNameIdentifier -> GQLNameIdentifier
mkUpdateByPkField GQLNameIdentifier
tableGqlName
pkObjectName :: Name
pkObjectName = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkTablePkColumnsInputTypeName GQLNameIdentifier
tableGqlName
pkFieldName :: Name
pkFieldName = NamingCase -> GQLNameIdentifier -> Name
applyFieldNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
pkColumnsFieldName
let parseOutput :: MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput = (AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a b.
(a -> b)
-> Parser MetadataObjId 'Output n a
-> Parser MetadataObjId 'Output n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnFieldsG b r v -> MutationOutputG b r v
MOutSinglerowObject (Parser
MetadataObjId
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (TableInfo b
-> SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe
(Parser
'Output
n
(AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSourceSchema b r m n) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet TableInfo b
tableInfo)
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
buildAnnotatedUpdateGField Scenario
scenario TableInfo b
tableInfo Name
updateTableFieldName Maybe Description
updateByPkFieldDescription MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Output
n
(MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
parseOutput ((UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (UpdPermInfo b
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ \UpdPermInfo b
updatePerms -> do
InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
pkArgs <- SchemaT
r
m
(Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT
r
m
(Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> SchemaT
r
m
(Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
primaryKeysArguments TableInfo b
tableInfo
SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ do
InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
updateOperators <- TableInfo b
-> UpdPermInfo b
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) r.
(BackendUpdateOperatorsSchema b, MonadBuildSchema b r m n) =>
TableInfo b
-> UpdPermInfo b
-> SchemaT
r
m
(InputFieldsParser
n (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))))
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))))
parseUpdateOperators TableInfo b
tableInfo UpdPermInfo b
updatePerms
let pkParser :: Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
pkParser = Name
-> Maybe Description
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
-> Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
pkObjectName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
pkObjectDesc) InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
pkArgs
let whereParser :: InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
whereParser = Name
-> Maybe Description
-> Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
P.field Name
pkFieldName Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b))
pkParser
InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant (UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (UpdateVariant b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
forall (b :: BackendType) (updateOperators :: * -> *) v.
HashMap (Column b) (updateOperators v)
-> AnnBoolExp b v -> UpdateBatch b updateOperators v
UpdateBatch (HashMap (Column b) (UpdateOperators b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser
MetadataObjId
n
(HashMap (Column b) (UpdateOperators b (UnpreparedValue b)))
updateOperators InputFieldsParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b)
-> UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b))
forall a b.
InputFieldsParser MetadataObjId n (a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
whereParser)
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
updateByPkFieldDescription :: Maybe Description
updateByPkFieldDescription = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultUpdateByPkDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfUpdateByPk
defaultUpdateByPkDesc :: Text
defaultUpdateByPkDesc = Text
"update single row of the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
pkObjectDesc :: Description
pkObjectDesc = Text -> Description
Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"primary key columns input for table: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableName b -> Text
forall a. ToTxt a => a -> Text
toTxt TableName b
tableName
TableCustomRootFields {CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfSelect :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfInsert :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfUpdateMany :: CustomRootField
_tcrfDelete :: CustomRootField
_tcrfDeleteByPk :: CustomRootField
..} = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
mkAnnotatedUpdateG ::
(Backend b) =>
TableName b ->
[ColumnInfo b] ->
UpdPermInfo b ->
(Maybe NamingCase) ->
Maybe (ValidateInput ResolvedWebhook) ->
( UpdateVariant b (UnpreparedValue b),
MutationOutputG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
) ->
AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkAnnotatedUpdateG :: forall (b :: BackendType).
Backend b =>
TableName b
-> [ColumnInfo b]
-> UpdPermInfo b
-> Maybe NamingCase
-> Maybe (ValidateInput ResolvedWebhook)
-> (UpdateVariant b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkAnnotatedUpdateG TableName b
_auTable [ColumnInfo b]
_auAllCols UpdPermInfo b
updatePerms Maybe NamingCase
_auNamingConvention Maybe (ValidateInput ResolvedWebhook)
_auValidateInput (UpdateVariant b (UnpreparedValue b)
_auUpdateVariant, MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
_auOutput) =
AnnotatedUpdateG {[ColumnInfo b]
Maybe NamingCase
Maybe (ValidateInput ResolvedWebhook)
TableName b
UpdateVariant b (UnpreparedValue b)
AnnBoolExp b (UnpreparedValue b)
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
_auTable :: TableName b
_auAllCols :: [ColumnInfo b]
_auNamingConvention :: Maybe NamingCase
_auValidateInput :: Maybe (ValidateInput ResolvedWebhook)
_auUpdateVariant :: UpdateVariant b (UnpreparedValue b)
_auOutput :: MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
_auUpdatePermissions :: AnnBoolExp b (UnpreparedValue b)
_auCheck :: AnnBoolExp b (UnpreparedValue b)
_auTable :: TableName b
_auUpdatePermissions :: AnnBoolExp b (UnpreparedValue b)
_auCheck :: AnnBoolExp b (UnpreparedValue b)
_auUpdateVariant :: UpdateVariant b (UnpreparedValue b)
_auOutput :: MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
_auAllCols :: [ColumnInfo b]
_auNamingConvention :: Maybe NamingCase
_auValidateInput :: Maybe (ValidateInput ResolvedWebhook)
..}
where
_auUpdatePermissions :: AnnBoolExp b (UnpreparedValue b)
_auUpdatePermissions = (PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b)
forall a b. (a -> b) -> AnnBoolExpFld b a -> AnnBoolExpFld b b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PartialSQLExp b -> UnpreparedValue b
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue (AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdPermInfo b -> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
forall (b :: BackendType). UpdPermInfo b -> AnnBoolExpPartialSQL b
upiFilter UpdPermInfo b
updatePerms
_auCheck :: AnnBoolExp b (UnpreparedValue b)
_auCheck = AnnBoolExp b (UnpreparedValue b)
-> (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> AnnBoolExp b (UnpreparedValue b)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe AnnBoolExp b (UnpreparedValue b)
forall (backend :: BackendType) scalar. AnnBoolExp backend scalar
annBoolExpTrue (((AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b)
forall a b. (a -> b) -> GBoolExp b a -> GBoolExp b b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b))
-> ((PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> (PartialSQLExp b -> UnpreparedValue b)
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b)
forall a b. (a -> b) -> AnnBoolExpFld b a -> AnnBoolExpFld b b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) PartialSQLExp b -> UnpreparedValue b
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue) (Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> AnnBoolExp b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> AnnBoolExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ UpdPermInfo b
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
forall (b :: BackendType).
UpdPermInfo b -> Maybe (AnnBoolExpPartialSQL b)
upiCheck UpdPermInfo b
updatePerms
buildFieldDescription :: Text -> Comment -> Maybe Description
buildFieldDescription :: Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultDescription = \case
Comment
Automatic -> Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
Description Text
defaultDescription
Explicit Maybe NonEmptyText
comment -> Text -> Description
Description (Text -> Description)
-> (NonEmptyText -> Text) -> NonEmptyText -> Description
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyText -> Text
forall a. ToTxt a => a -> Text
toTxt (NonEmptyText -> Description)
-> Maybe NonEmptyText -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NonEmptyText
comment