{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
module Hasura.GraphQL.Schema.Mutation
( insertIntoTable,
insertOneIntoTable,
deleteFromTable,
deleteFromTableByPk,
mkDefaultRelationshipParser,
mutationSelectionSet,
primaryKeysArguments,
)
where
import Data.Has (getter)
import Data.HashMap.Strict qualified as Map
import Data.HashSet qualified as Set
import Data.Text.Extended
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.NamingCase (NamingCase)
import Hasura.GraphQL.Schema.Parser
( FieldParser,
InputFieldsParser,
Kind (..),
Parser,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.Table
import Hasura.GraphQL.Schema.Typename (mkTypename)
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.Delete qualified as IR
import Hasura.RQL.IR.Insert qualified as IR
import Hasura.RQL.IR.Returning qualified as IR
import Hasura.RQL.IR.Root qualified as IR
import Hasura.RQL.IR.Value qualified as IR
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Relationships.Local
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Language.GraphQL.Draft.Syntax qualified as G
insertIntoTable ::
forall b r m n.
MonadBuildSchema b r m n =>
BackendTableSelectSchema b =>
(SourceInfo b -> TableInfo b -> m (InputFieldsParser n (BackendInsert b (IR.UnpreparedValue b)))) ->
Scenario ->
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (IR.AnnotatedInsert b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b))))
insertIntoTable :: (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> Scenario
-> SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
insertIntoTable SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction Scenario
scenario SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT
m
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
let 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
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ViewInfo -> Bool) -> Maybe ViewInfo -> Bool
isMutable ViewInfo -> Bool
viIsInsertable Maybe ViewInfo
viewInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
let permissions :: RolePermInfo b
permissions = RoleName -> TableInfo b -> RolePermInfo b
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo b
tableInfo
InsPermInfo b
insertPerms <- Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b))
-> Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (InsPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (InsPermInfo b)
_permIns RolePermInfo b
permissions
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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
&& InsPermInfo b -> Bool
forall (b :: BackendType). InsPermInfo b -> Bool
ipiBackendOnly InsPermInfo b
insertPerms
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
m
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift do
let updatePerms :: Maybe (UpdPermInfo b)
updatePerms = RolePermInfo b -> Maybe (UpdPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd RolePermInfo b
permissions
Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser <- SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
tableFieldsInput SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
tableInfo
Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
selectionParser <- SourceInfo b
-> TableInfo b
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
mutationSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
let argsParser :: InputFieldsParser
MetadataObjId n (AnnotatedInsertData b [] (UnpreparedValue b))
argsParser = do
BackendInsert b (UnpreparedValue b)
backendInsert <- InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser
[AnnotatedInsertRow b (UnpreparedValue b)]
objects <- Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n [AnnotatedInsertRow b (UnpreparedValue b)]
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> InputFieldsParser origin m [a]
mkObjectsArg Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser
pure $ [AnnotatedInsertRow b (UnpreparedValue b)]
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b [] (UnpreparedValue b)
forall (b :: BackendType) (f :: * -> *).
BackendSchema b =>
f (AnnotatedInsertRow b (UnpreparedValue b))
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b f (UnpreparedValue b)
mkInsertObject [AnnotatedInsertRow b (UnpreparedValue b)]
objects TableInfo b
tableInfo BackendInsert b (UnpreparedValue b)
backendInsert InsPermInfo b
insertPerms Maybe (UpdPermInfo b)
updatePerms
FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertData b [] (UnpreparedValue b))
-> Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(AnnotatedInsertData b [] (UnpreparedValue b),
MutFldsG
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
MetadataObjId n (AnnotatedInsertData b [] (UnpreparedValue b))
argsParser Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
selectionParser
FieldParser
MetadataObjId
n
(AnnotatedInsertData b [] (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ((AnnotatedInsertData b [] (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(AnnotatedInsertData b [] (UnpreparedValue b)
insertObject, MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
output) -> Text
-> Bool
-> AnnotatedInsertData b [] (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> Maybe NamingCase
-> AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
Text
-> Bool
-> MultiObjectInsert b v
-> MutationOutputG b r v
-> Maybe NamingCase
-> AnnotatedInsert b r v
IR.AnnotatedInsert (Name -> Text
G.unName Name
fieldName) Bool
False AnnotatedInsertData b [] (UnpreparedValue b)
insertObject (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
IR.MOutMultirowFields MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
output) (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase)
where
mkObjectsArg :: Parser origin k m a -> InputFieldsParser origin m [a]
mkObjectsArg Parser origin k m a
objectParser =
Name
-> Maybe Description
-> Parser origin k m [a]
-> InputFieldsParser origin m [a]
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._objects
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"the rows to be inserted")
(Parser origin k m a -> Parser origin k m [a]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list Parser origin k m a
objectParser)
insertOneIntoTable ::
forall b r m n.
MonadBuildSchema b r m n =>
BackendTableSelectSchema b =>
(SourceInfo b -> TableInfo b -> m (InputFieldsParser n (BackendInsert b (IR.UnpreparedValue b)))) ->
Scenario ->
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (IR.AnnotatedInsert b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b))))
insertOneIntoTable :: (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> Scenario
-> SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
insertOneIntoTable SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction Scenario
scenario SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT
m
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
let 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
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ViewInfo -> Bool) -> Maybe ViewInfo -> Bool
isMutable ViewInfo -> Bool
viIsInsertable Maybe ViewInfo
viewInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
let permissions :: RolePermInfo b
permissions = RoleName -> TableInfo b -> RolePermInfo b
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo b
tableInfo
InsPermInfo b
insertPerms <- Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b))
-> Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (InsPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (InsPermInfo b)
_permIns RolePermInfo b
permissions
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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
&& InsPermInfo b -> Bool
forall (b :: BackendType). InsPermInfo b -> Bool
ipiBackendOnly InsPermInfo b
insertPerms
Parser 'Output n (AnnotatedFields b)
selectionParser <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
m
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift do
let updatePerms :: Maybe (UpdPermInfo b)
updatePerms = RolePermInfo b -> Maybe (UpdPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd RolePermInfo b
permissions
Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser <- SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
tableFieldsInput SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
tableInfo
let argsParser :: InputFieldsParser
MetadataObjId n (AnnotatedInsertData b [] (UnpreparedValue b))
argsParser = do
BackendInsert b (UnpreparedValue b)
backendInsert <- InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser
AnnotatedInsertRow b (UnpreparedValue b)
object <- Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> InputFieldsParser origin m a
mkObjectArg Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser
pure $ [AnnotatedInsertRow b (UnpreparedValue b)]
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b [] (UnpreparedValue b)
forall (b :: BackendType) (f :: * -> *).
BackendSchema b =>
f (AnnotatedInsertRow b (UnpreparedValue b))
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b f (UnpreparedValue b)
mkInsertObject [AnnotatedInsertRow b (UnpreparedValue b)
object] TableInfo b
tableInfo BackendInsert b (UnpreparedValue b)
backendInsert InsPermInfo b
insertPerms Maybe (UpdPermInfo b)
updatePerms
FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertData b [] (UnpreparedValue b))
-> Parser 'Output n (AnnotatedFields b)
-> FieldParser
MetadataObjId
n
(AnnotatedInsertData b [] (UnpreparedValue b), AnnotatedFields 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
MetadataObjId n (AnnotatedInsertData b [] (UnpreparedValue b))
argsParser Parser 'Output n (AnnotatedFields b)
selectionParser
FieldParser
MetadataObjId
n
(AnnotatedInsertData b [] (UnpreparedValue b), AnnotatedFields b)
-> ((AnnotatedInsertData b [] (UnpreparedValue b),
AnnotatedFields b)
-> AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(AnnotatedInsertData b [] (UnpreparedValue b)
insertObject, AnnotatedFields b
output) -> Text
-> Bool
-> AnnotatedInsertData b [] (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> Maybe NamingCase
-> AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
Text
-> Bool
-> MultiObjectInsert b v
-> MutationOutputG b r v
-> Maybe NamingCase
-> AnnotatedInsert b r v
IR.AnnotatedInsert (Name -> Text
G.unName Name
fieldName) Bool
True AnnotatedInsertData b [] (UnpreparedValue b)
insertObject (AnnotatedFields b
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnFieldsG b r v -> MutationOutputG b r v
IR.MOutSinglerowObject AnnotatedFields b
output) (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase)
where
mkObjectArg :: Parser origin k m a -> InputFieldsParser origin m a
mkObjectArg Parser origin k m a
objectParser =
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
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._object
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"the row to be inserted")
Parser origin k m a
objectParser
tableFieldsInput ::
forall b r m n.
MonadBuildSchema b r m n =>
SourceInfo b ->
TableInfo b ->
m (Parser 'Input n (IR.AnnotatedInsertRow b (IR.UnpreparedValue b)))
tableFieldsInput :: SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
tableFieldsInput SourceInfo b
sourceInfo TableInfo b
tableInfo =
Name
-> (SourceName, TableName b)
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall (m :: * -> *) a (p :: (* -> *) -> * -> *) (n :: * -> *) b.
(MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n,
Typeable b) =>
Name -> a -> m (p n b) -> m (p n b)
P.memoizeOn 'tableFieldsInput (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName) do
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
GQLNameIdentifier
tableGQLName <- TableInfo b -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
[Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
objectFields <- (FieldInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))))
-> [FieldInfo b]
-> m [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse FieldInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
mkFieldParser (HashMap FieldName (FieldInfo b) -> [FieldInfo b]
forall k v. HashMap k v -> [v]
Map.elems HashMap FieldName (FieldInfo b)
allFields)
Name
objectName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m 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
mkTableInsertInputTypeName GQLNameIdentifier
tableGQLName
let objectDesc :: Description
objectDesc = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"input type for inserting data into table " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))))
-> Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
-> Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
objectName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
objectDesc) (InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
-> Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
-> Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
coalesceFields [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
objectFields
where
allFields :: HashMap FieldName (FieldInfo b)
allFields = TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> HashMap FieldName (FieldInfo b)
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> FieldInfoMap field
_tciFieldInfoMap (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> HashMap FieldName (FieldInfo b))
-> (TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b))
-> TableInfo b
-> HashMap FieldName (FieldInfo b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo (TableInfo b -> HashMap FieldName (FieldInfo b))
-> TableInfo b -> HashMap FieldName (FieldInfo b)
forall a b. (a -> b) -> a -> b
$ TableInfo b
tableInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
coalesceFields ::
[Maybe (InputFieldsParser n (Maybe (IR.AnnotatedInsertField b (IR.UnpreparedValue b))))] ->
InputFieldsParser n (IR.AnnotatedInsertRow b (IR.UnpreparedValue b))
coalesceFields :: [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
coalesceFields = ([Maybe (AnnotatedInsertField b (UnpreparedValue b))]
-> AnnotatedInsertRow b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
[Maybe (AnnotatedInsertField b (UnpreparedValue b))]
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe (AnnotatedInsertField b (UnpreparedValue b))]
-> AnnotatedInsertRow b (UnpreparedValue b)
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (InputFieldsParser
MetadataObjId
n
[Maybe (AnnotatedInsertField b (UnpreparedValue b))]
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b)))
-> ([Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> InputFieldsParser
MetadataObjId
n
[Maybe (AnnotatedInsertField b (UnpreparedValue b))])
-> [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))]
-> InputFieldsParser
MetadataObjId
n
[Maybe (AnnotatedInsertField b (UnpreparedValue b))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))]
-> InputFieldsParser
MetadataObjId
n
[Maybe (AnnotatedInsertField b (UnpreparedValue b))])
-> ([Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> [InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))])
-> [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> InputFieldsParser
MetadataObjId
n
[Maybe (AnnotatedInsertField b (UnpreparedValue b))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))]
-> [InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
mkFieldParser ::
FieldInfo b ->
m (Maybe (InputFieldsParser n (Maybe (IR.AnnotatedInsertField b (IR.UnpreparedValue b)))))
mkFieldParser :: FieldInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
mkFieldParser = \case
FIComputedField ComputedFieldInfo b
_ -> Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
forall a. Maybe a
Nothing
FIRemoteRelationship RemoteFieldInfo (DBJoinField b)
_ -> Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
forall a. Maybe a
Nothing
FIColumn ColumnInfo b
columnInfo -> do
if (ColumnMutability -> Bool
_cmIsInsertable (ColumnMutability -> Bool) -> ColumnMutability -> Bool
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> ColumnMutability
forall (b :: BackendType). ColumnInfo b -> ColumnMutability
ciMutability ColumnInfo b
columnInfo)
then ColumnInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
mkColumnParser ColumnInfo b
columnInfo
else Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
forall a. Maybe a
Nothing
FIRelationship RelInfo b
relInfo -> SourceInfo b
-> RelInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
SourceInfo b
-> RelInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
mkRelationshipParser SourceInfo b
sourceInfo RelInfo b
relInfo
mkColumnParser ::
ColumnInfo b ->
m (Maybe (InputFieldsParser n (Maybe (IR.AnnotatedInsertField b (IR.UnpreparedValue b)))))
mkColumnParser :: ColumnInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
mkColumnParser ColumnInfo b
columnInfo = MaybeT
m
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))))
-> MaybeT
m
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall a b. (a -> b) -> a -> b
$ do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
InsPermInfo b
insertPerms <- Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b))
-> Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (InsPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (InsPermInfo b)
_permIns (RolePermInfo b -> Maybe (InsPermInfo b))
-> RolePermInfo b -> Maybe (InsPermInfo 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
let columnName :: Name
columnName = ColumnInfo b -> Name
forall (b :: BackendType). ColumnInfo b -> Name
ciName ColumnInfo b
columnInfo
columnDesc :: Maybe Description
columnDesc = ColumnInfo b -> Maybe Description
forall (b :: BackendType). ColumnInfo b -> Maybe Description
ciDescription ColumnInfo b
columnInfo
isAllowed :: Bool
isAllowed = Column b -> HashSet (Column b) -> Bool
forall a. (Eq a, Hashable a) => a -> HashSet a -> Bool
Set.member (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo) (InsPermInfo b -> HashSet (Column b)
forall (b :: BackendType). InsPermInfo b -> HashSet (Column b)
ipiCols InsPermInfo b
insertPerms)
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
isAllowed
Parser 'Both n (ValueWithOrigin (ColumnValue b))
fieldParser <- m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT m (Parser 'Both n (ValueWithOrigin (ColumnValue b))))
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall a b. (a -> b) -> a -> b
$ ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) (Bool -> Nullability
G.Nullability (Bool -> Nullability) -> Bool -> Nullability
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Bool
forall (b :: BackendType). ColumnInfo b -> Bool
ciIsNullable ColumnInfo b
columnInfo)
pure $
Name
-> Maybe Description
-> Parser 'Both n (ValueWithOrigin (ColumnValue b))
-> InputFieldsParser
MetadataObjId n (Maybe (ValueWithOrigin (ColumnValue b)))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m (Maybe a)
P.fieldOptional Name
columnName Maybe Description
columnDesc Parser 'Both n (ValueWithOrigin (ColumnValue b))
fieldParser InputFieldsParser
MetadataObjId n (Maybe (ValueWithOrigin (ColumnValue b)))
-> (ValueWithOrigin (ColumnValue b)
-> AnnotatedInsertField b (UnpreparedValue b))
-> InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))
forall (m :: * -> *) a b.
Functor m =>
InputFieldsParser m (Maybe a)
-> (a -> b) -> InputFieldsParser m (Maybe b)
`mapField` \ValueWithOrigin (ColumnValue b)
value ->
(Column b, UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b)
forall (b :: BackendType) v.
(Column b, v) -> AnnotatedInsertField b v
IR.AIColumn (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo, ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter ValueWithOrigin (ColumnValue b)
value)
mkDefaultRelationshipParser ::
forall b r m n.
MonadBuildSchema b r m n =>
(SourceInfo b -> TableInfo b -> m (InputFieldsParser n (BackendInsert b (IR.UnpreparedValue b)))) ->
XNestedInserts b ->
SourceInfo b ->
RelInfo b ->
m (Maybe (InputFieldsParser n (Maybe (IR.AnnotatedInsertField b (IR.UnpreparedValue b)))))
mkDefaultRelationshipParser :: (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> XNestedInserts b
-> SourceInfo b
-> RelInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
mkDefaultRelationshipParser SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction XNestedInserts b
xNestedInserts SourceInfo b
sourceInfo RelInfo b
relationshipInfo = MaybeT
m
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
let otherTableName :: TableName b
otherTableName = RelInfo b -> TableName b
forall (b :: BackendType). RelInfo b -> TableName b
riRTable RelInfo b
relationshipInfo
relName :: RelName
relName = RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
relationshipInfo
TableInfo b
otherTableInfo <- SourceInfo b -> TableName b -> MaybeT m (TableInfo b)
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo b
sourceInfo TableName b
otherTableName
Name
relFieldName <- m Name -> MaybeT m Name
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m Name -> MaybeT m Name) -> m Name -> MaybeT m Name
forall a b. (a -> b) -> a -> b
$ Text -> m Name
forall (m :: * -> *). MonadError QErr m => Text -> m Name
textToName (Text -> m Name) -> Text -> m Name
forall a b. (a -> b) -> a -> b
$ RelName -> Text
relNameToTxt RelName
relName
case RelInfo b -> RelType
forall (b :: BackendType). RelInfo b -> RelType
riType RelInfo b
relationshipInfo of
RelType
ObjRel -> do
Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
parser <- m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
(SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
objectRelationshipInput SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
otherTableInfo
pure $
Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
(Maybe (SingleObjectInsert b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe (SingleObjectInsert b (UnpreparedValue b))))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m (Maybe a)
P.fieldOptional Name
relFieldName Maybe Description
forall a. Maybe a
Nothing (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
(Maybe (SingleObjectInsert b (UnpreparedValue b)))
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
parser) InputFieldsParser
MetadataObjId
n
(Maybe (Maybe (SingleObjectInsert b (UnpreparedValue b))))
-> (Maybe (Maybe (SingleObjectInsert b (UnpreparedValue b)))
-> Maybe (AnnotatedInsertField b (UnpreparedValue b)))
-> InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Maybe (Maybe (SingleObjectInsert b (UnpreparedValue b)))
objRelIns -> do
SingleObjectInsert b (UnpreparedValue b)
rel <- Maybe (Maybe (SingleObjectInsert b (UnpreparedValue b)))
-> Maybe (SingleObjectInsert b (UnpreparedValue b))
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe (SingleObjectInsert b (UnpreparedValue b)))
objRelIns
AnnotatedInsertField b (UnpreparedValue b)
-> Maybe (AnnotatedInsertField b (UnpreparedValue b))
forall a. a -> Maybe a
Just (AnnotatedInsertField b (UnpreparedValue b)
-> Maybe (AnnotatedInsertField b (UnpreparedValue b)))
-> AnnotatedInsertField b (UnpreparedValue b)
-> Maybe (AnnotatedInsertField b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ XNestedInserts b
-> ObjectRelationInsert b (UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b)
forall (b :: BackendType) v.
XNestedInserts b
-> ObjectRelationInsert b v -> AnnotatedInsertField b v
IR.AIObjectRelationship XNestedInserts b
xNestedInserts (ObjectRelationInsert b (UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b))
-> ObjectRelationInsert b (UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SingleObjectInsert b (UnpreparedValue b)
-> RelInfo b -> ObjectRelationInsert b (UnpreparedValue b)
forall (b :: BackendType) a. a -> RelInfo b -> RelationInsert b a
IR.RelationInsert SingleObjectInsert b (UnpreparedValue b)
rel RelInfo b
relationshipInfo
RelType
ArrRel -> do
Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
parser <- m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
(SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
arrayRelationshipInput SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
otherTableInfo
pure $
Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
(Maybe (MultiObjectInsert b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe (MultiObjectInsert b (UnpreparedValue b))))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m (Maybe a)
P.fieldOptional Name
relFieldName Maybe Description
forall a. Maybe a
Nothing (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
-> Parser
MetadataObjId
'Input
n
(Maybe (MultiObjectInsert b (UnpreparedValue b)))
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
parser) InputFieldsParser
MetadataObjId
n
(Maybe (Maybe (MultiObjectInsert b (UnpreparedValue b))))
-> (Maybe (Maybe (MultiObjectInsert b (UnpreparedValue b)))
-> Maybe (AnnotatedInsertField b (UnpreparedValue b)))
-> InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Maybe (Maybe (MultiObjectInsert b (UnpreparedValue b)))
arrRelIns -> do
MultiObjectInsert b (UnpreparedValue b)
rel <- Maybe (Maybe (MultiObjectInsert b (UnpreparedValue b)))
-> Maybe (MultiObjectInsert b (UnpreparedValue b))
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe (MultiObjectInsert b (UnpreparedValue b)))
arrRelIns
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [AnnotatedInsertRow b (UnpreparedValue b)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([AnnotatedInsertRow b (UnpreparedValue b)] -> Bool)
-> [AnnotatedInsertRow b (UnpreparedValue b)] -> Bool
forall a b. (a -> b) -> a -> b
$ MultiObjectInsert b (UnpreparedValue b)
-> [AnnotatedInsertRow b (UnpreparedValue b)]
forall (b :: BackendType) (f :: * -> *) v.
AnnotatedInsertData b f v -> f (AnnotatedInsertRow b v)
IR._aiInsertObject MultiObjectInsert b (UnpreparedValue b)
rel
AnnotatedInsertField b (UnpreparedValue b)
-> Maybe (AnnotatedInsertField b (UnpreparedValue b))
forall a. a -> Maybe a
Just (AnnotatedInsertField b (UnpreparedValue b)
-> Maybe (AnnotatedInsertField b (UnpreparedValue b)))
-> AnnotatedInsertField b (UnpreparedValue b)
-> Maybe (AnnotatedInsertField b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ XNestedInserts b
-> ArrayRelationInsert b (UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b)
forall (b :: BackendType) v.
XNestedInserts b
-> ArrayRelationInsert b v -> AnnotatedInsertField b v
IR.AIArrayRelationship XNestedInserts b
xNestedInserts (ArrayRelationInsert b (UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b))
-> ArrayRelationInsert b (UnpreparedValue b)
-> AnnotatedInsertField b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ MultiObjectInsert b (UnpreparedValue b)
-> RelInfo b -> ArrayRelationInsert b (UnpreparedValue b)
forall (b :: BackendType) a. a -> RelInfo b -> RelationInsert b a
IR.RelationInsert MultiObjectInsert b (UnpreparedValue b)
rel RelInfo b
relationshipInfo
objectRelationshipInput ::
forall b r m n.
MonadBuildSchema b r m n =>
(SourceInfo b -> TableInfo b -> m (InputFieldsParser n (BackendInsert b (IR.UnpreparedValue b)))) ->
SourceInfo b ->
TableInfo b ->
m (Maybe (Parser 'Input n (IR.SingleObjectInsert b (IR.UnpreparedValue b))))
objectRelationshipInput :: (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
objectRelationshipInput SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
tableInfo = MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> m (Maybe
(Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
let permissions :: RolePermInfo b
permissions = RoleName -> TableInfo b -> RolePermInfo b
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo b
tableInfo
updatePerms :: Maybe (UpdPermInfo b)
updatePerms = RolePermInfo b -> Maybe (UpdPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd RolePermInfo b
permissions
InsPermInfo b
insertPerms <- Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b))
-> Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (InsPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (InsPermInfo b)
_permIns RolePermInfo b
permissions
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
-> m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> MaybeT
m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b)
-> m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
-> m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall (m :: * -> *) a (p :: (* -> *) -> * -> *) (n :: * -> *) b.
(MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n,
Typeable b) =>
Name -> a -> m (p n b) -> m (p n b)
P.memoizeOn 'objectRelationshipInput (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName) do
GQLNameIdentifier
tableGQLName <- TableInfo b -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser <- SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
tableFieldsInput SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
tableInfo
Name
inputName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m 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
mkTableObjRelInsertInputTypeName (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier -> GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier
tableGQLName
let objectName :: Name
objectName = Name
Name._data
inputDesc :: Description
inputDesc = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"input type for inserting object relation for remote table " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
inputParser :: InputFieldsParser
MetadataObjId n (SingleObjectInsert b (UnpreparedValue b))
inputParser = do
BackendInsert b (UnpreparedValue b)
backendInsert <- InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser
AnnotatedInsertRow b (UnpreparedValue b)
object <- Name
-> Maybe Description
-> Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (AnnotatedInsertRow 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
objectName Maybe Description
forall a. Maybe a
Nothing Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser
pure $ Single (AnnotatedInsertRow b (UnpreparedValue b))
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> SingleObjectInsert b (UnpreparedValue b)
forall (b :: BackendType) (f :: * -> *).
BackendSchema b =>
f (AnnotatedInsertRow b (UnpreparedValue b))
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b f (UnpreparedValue b)
mkInsertObject (AnnotatedInsertRow b (UnpreparedValue b)
-> Single (AnnotatedInsertRow b (UnpreparedValue b))
forall a. a -> Single a
IR.Single AnnotatedInsertRow b (UnpreparedValue b)
object) TableInfo b
tableInfo BackendInsert b (UnpreparedValue b)
backendInsert InsPermInfo b
insertPerms Maybe (UpdPermInfo b)
updatePerms
Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
-> m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
-> m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))))
-> Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
-> m (Parser 'Input n (SingleObjectInsert b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (SingleObjectInsert b (UnpreparedValue b))
-> Parser 'Input n (SingleObjectInsert b (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
inputName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
inputDesc) InputFieldsParser
MetadataObjId n (SingleObjectInsert b (UnpreparedValue b))
inputParser
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
arrayRelationshipInput ::
forall b r m n.
MonadBuildSchema b r m n =>
(SourceInfo b -> TableInfo b -> m (InputFieldsParser n (BackendInsert b (IR.UnpreparedValue b)))) ->
SourceInfo b ->
TableInfo b ->
m (Maybe (Parser 'Input n (IR.MultiObjectInsert b (IR.UnpreparedValue b))))
arrayRelationshipInput :: (SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
arrayRelationshipInput SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
tableInfo = MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> m (Maybe
(Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
let permissions :: RolePermInfo b
permissions = RoleName -> TableInfo b -> RolePermInfo b
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo b
tableInfo
updatePerms :: Maybe (UpdPermInfo b)
updatePerms = RolePermInfo b -> Maybe (UpdPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd RolePermInfo b
permissions
InsPermInfo b
insertPerms <- Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b))
-> Maybe (InsPermInfo b) -> MaybeT m (InsPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (InsPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (InsPermInfo b)
_permIns RolePermInfo b
permissions
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
-> m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> MaybeT
m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b)
-> m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
-> m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall (m :: * -> *) a (p :: (* -> *) -> * -> *) (n :: * -> *) b.
(MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n,
Typeable b) =>
Name -> a -> m (p n b) -> m (p n b)
P.memoizeOn 'arrayRelationshipInput (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName) do
GQLNameIdentifier
tableGQLName <- TableInfo b -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser <- SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b)))
tableFieldsInput SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction SourceInfo b
sourceInfo TableInfo b
tableInfo
Name
inputName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m 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
mkTableArrRelInsertInputTypeName GQLNameIdentifier
tableGQLName
let objectsName :: Name
objectsName = Name
Name._data
inputDesc :: Description
inputDesc = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"input type for inserting array relation for remote table " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
inputParser :: InputFieldsParser
MetadataObjId n (MultiObjectInsert b (UnpreparedValue b))
inputParser = do
BackendInsert b (UnpreparedValue b)
backendInsert <- InputFieldsParser n (BackendInsert b (UnpreparedValue b))
backendInsertParser
[AnnotatedInsertRow b (UnpreparedValue b)]
objects <- Name
-> Maybe Description
-> Parser
MetadataObjId 'Input n [AnnotatedInsertRow b (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId n [AnnotatedInsertRow 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
objectsName Maybe Description
forall a. Maybe a
Nothing (Parser
MetadataObjId 'Input n [AnnotatedInsertRow b (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId n [AnnotatedInsertRow b (UnpreparedValue b)])
-> Parser
MetadataObjId 'Input n [AnnotatedInsertRow b (UnpreparedValue b)]
-> InputFieldsParser
MetadataObjId n [AnnotatedInsertRow b (UnpreparedValue b)]
forall a b. (a -> b) -> a -> b
$ Parser 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
-> Parser
MetadataObjId 'Input n [AnnotatedInsertRow 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 'Input n (AnnotatedInsertRow b (UnpreparedValue b))
objectParser
pure $ [AnnotatedInsertRow b (UnpreparedValue b)]
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> MultiObjectInsert b (UnpreparedValue b)
forall (b :: BackendType) (f :: * -> *).
BackendSchema b =>
f (AnnotatedInsertRow b (UnpreparedValue b))
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b f (UnpreparedValue b)
mkInsertObject [AnnotatedInsertRow b (UnpreparedValue b)]
objects TableInfo b
tableInfo BackendInsert b (UnpreparedValue b)
backendInsert InsPermInfo b
insertPerms Maybe (UpdPermInfo b)
updatePerms
Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
-> m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
-> m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))))
-> Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
-> m (Parser 'Input n (MultiObjectInsert b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (MultiObjectInsert b (UnpreparedValue b))
-> Parser 'Input n (MultiObjectInsert b (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
inputName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
inputDesc) InputFieldsParser
MetadataObjId n (MultiObjectInsert b (UnpreparedValue b))
inputParser
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
mkInsertObject ::
forall b f.
BackendSchema b =>
f (IR.AnnotatedInsertRow b (IR.UnpreparedValue b)) ->
TableInfo b ->
BackendInsert b (IR.UnpreparedValue b) ->
InsPermInfo b ->
Maybe (UpdPermInfo b) ->
IR.AnnotatedInsertData b f (IR.UnpreparedValue b)
mkInsertObject :: f (AnnotatedInsertRow b (UnpreparedValue b))
-> TableInfo b
-> BackendInsert b (UnpreparedValue b)
-> InsPermInfo b
-> Maybe (UpdPermInfo b)
-> AnnotatedInsertData b f (UnpreparedValue b)
mkInsertObject f (AnnotatedInsertRow b (UnpreparedValue b))
objects TableInfo b
tableInfo BackendInsert b (UnpreparedValue b)
backendInsert InsPermInfo b
insertPerms Maybe (UpdPermInfo b)
updatePerms =
AnnotatedInsertData :: forall (b :: BackendType) (f :: * -> *) v.
f (AnnotatedInsertRow b v)
-> TableName b
-> (AnnBoolExp b v, Maybe (AnnBoolExp b v))
-> [ColumnInfo b]
-> PreSetColsG b v
-> BackendInsert b v
-> AnnotatedInsertData b f v
IR.AnnotatedInsertData
{ _aiInsertObject :: f (AnnotatedInsertRow b (UnpreparedValue b))
_aiInsertObject = f (AnnotatedInsertRow b (UnpreparedValue b))
objects,
_aiTableName :: TableName b
_aiTableName = TableName b
table,
_aiCheckCondition :: (AnnBoolExp b (UnpreparedValue b),
Maybe (AnnBoolExp b (UnpreparedValue b)))
_aiCheckCondition = (AnnBoolExp b (UnpreparedValue b)
insertCheck, Maybe (AnnBoolExp b (UnpreparedValue b))
updateCheck),
_aiTableColumns :: [ColumnInfo b]
_aiTableColumns = [ColumnInfo b]
columns,
_aiPresetValues :: PreSetColsG b (UnpreparedValue b)
_aiPresetValues = PreSetColsG b (UnpreparedValue b)
presetValues,
_aiBackendInsert :: BackendInsert b (UnpreparedValue b)
_aiBackendInsert = BackendInsert b (UnpreparedValue b)
backendInsert
}
where
table :: TableName b
table = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
columns :: [ColumnInfo b]
columns = TableInfo b -> [ColumnInfo b]
forall (b :: BackendType). TableInfo b -> [ColumnInfo b]
tableColumns TableInfo b
tableInfo
insertCheck :: AnnBoolExp b (UnpreparedValue b)
insertCheck = (PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue 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
<$> InsPermInfo b -> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
forall (b :: BackendType). InsPermInfo b -> AnnBoolExpPartialSQL b
ipiCheck InsPermInfo b
insertPerms
updateCheck :: Maybe (AnnBoolExp b (UnpreparedValue b))
updateCheck = ((GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> Maybe (AnnBoolExp b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> Maybe (AnnBoolExp b (UnpreparedValue b)))
-> ((PartialSQLExp b -> UnpreparedValue b)
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b))
-> (PartialSQLExp b -> UnpreparedValue b)
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> Maybe (AnnBoolExp b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (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
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 (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)))
-> Maybe (AnnBoolExp b (UnpreparedValue b)))
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
-> Maybe (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
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))))
-> Maybe (UpdPermInfo b)
-> Maybe (GBoolExp b (AnnBoolExpFld b (PartialSQLExp b)))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe (UpdPermInfo b)
updatePerms
presetValues :: PreSetColsG b (UnpreparedValue b)
presetValues = PartialSQLExp b -> UnpreparedValue b
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue (PartialSQLExp b -> UnpreparedValue b)
-> HashMap (Column b) (PartialSQLExp b)
-> PreSetColsG b (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InsPermInfo b -> HashMap (Column b) (PartialSQLExp b)
forall (b :: BackendType). InsPermInfo b -> PreSetColsPartial b
ipiSet InsPermInfo b
insertPerms
deleteFromTable ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
) =>
Scenario ->
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (IR.AnnDelG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b))))
deleteFromTable :: Scenario
-> SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
deleteFromTable Scenario
scenario SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
let 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
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ViewInfo -> Bool) -> Maybe ViewInfo -> Bool
isMutable ViewInfo -> Bool
viIsInsertable Maybe ViewInfo
viewInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
DelPermInfo b
deletePerms <- Maybe (DelPermInfo b) -> MaybeT m (DelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (DelPermInfo b) -> MaybeT m (DelPermInfo b))
-> Maybe (DelPermInfo b) -> MaybeT m (DelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (DelPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (DelPermInfo b)
_permDel (RolePermInfo b -> Maybe (DelPermInfo b))
-> RolePermInfo b -> Maybe (DelPermInfo 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 m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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
&& DelPermInfo b -> Bool
forall (b :: BackendType). DelPermInfo b -> Bool
dpiBackendOnly DelPermInfo b
deletePerms
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
m (FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift do
let whereName :: Name
whereName = Name
Name._where
whereDesc :: Description
whereDesc = Description
"filter the rows which have to be deleted"
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
whereName (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)))
-> m (Parser
MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b)))
-> m (InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo b
-> TableInfo b
-> m (Parser
MetadataObjId 'Input n (AnnBoolExp b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
boolExp SourceInfo b
sourceInfo TableInfo b
tableInfo
Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
selection <- SourceInfo b
-> TableInfo b
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
mutationSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
let columns :: [ColumnInfo b]
columns = TableInfo b -> [ColumnInfo b]
forall (b :: BackendType). TableInfo b -> [ColumnInfo b]
tableColumns TableInfo b
tableInfo
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
-> Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b),
MutFldsG
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
MetadataObjId n (AnnBoolExp b (UnpreparedValue b))
whereArg Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
selection
FieldParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ((AnnBoolExp b (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> TableName b
-> [ColumnInfo b]
-> DelPermInfo b
-> Maybe NamingCase
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
TableName b
-> [ColumnInfo b]
-> DelPermInfo b
-> Maybe NamingCase
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkDeleteObject (TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo) [ColumnInfo b]
columns DelPermInfo b
deletePerms (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase) ((AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ((AnnBoolExp b (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (AnnBoolExp b (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (AnnBoolExp b (UnpreparedValue b),
MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue 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
IR.MOutMultirowFields
deleteFromTableByPk ::
forall b r m n.
MonadBuildSchema b r m n =>
BackendTableSelectSchema b =>
Scenario ->
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (IR.AnnDelG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b))))
deleteFromTableByPk :: Scenario
-> SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
deleteFromTableByPk Scenario
scenario SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
let 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
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ViewInfo -> Bool) -> Maybe ViewInfo -> Bool
isMutable ViewInfo -> Bool
viIsInsertable Maybe ViewInfo
viewInfo
InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
pkArgs <- m (Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
primaryKeysArguments TableInfo b
tableInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
DelPermInfo b
deletePerms <- Maybe (DelPermInfo b) -> MaybeT m (DelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (DelPermInfo b) -> MaybeT m (DelPermInfo b))
-> Maybe (DelPermInfo b) -> MaybeT m (DelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RolePermInfo b -> Maybe (DelPermInfo b)
forall (b :: BackendType). RolePermInfo b -> Maybe (DelPermInfo b)
_permDel (RolePermInfo b -> Maybe (DelPermInfo b))
-> RolePermInfo b -> Maybe (DelPermInfo 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 m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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
&& DelPermInfo b -> Bool
forall (b :: BackendType). DelPermInfo b -> Bool
dpiBackendOnly DelPermInfo b
deletePerms
Parser 'Output n (AnnotatedFields b)
selection <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
let columns :: [ColumnInfo b]
columns = TableInfo b -> [ColumnInfo b]
forall (b :: BackendType). TableInfo b -> [ColumnInfo b]
tableColumns TableInfo b
tableInfo
pure $
Name
-> Maybe Description
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
-> Parser 'Output n (AnnotatedFields b)
-> FieldParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b), AnnotatedFields 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 (AnnBoolExp b (UnpreparedValue b))
pkArgs Parser 'Output n (AnnotatedFields b)
selection
FieldParser
MetadataObjId
n
(AnnBoolExp b (UnpreparedValue b), AnnotatedFields b)
-> ((AnnBoolExp b (UnpreparedValue b), AnnotatedFields b)
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> TableName b
-> [ColumnInfo b]
-> DelPermInfo b
-> Maybe NamingCase
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
TableName b
-> [ColumnInfo b]
-> DelPermInfo b
-> Maybe NamingCase
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkDeleteObject (TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo) [ColumnInfo b]
columns DelPermInfo b
deletePerms (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase) ((AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ((AnnBoolExp b (UnpreparedValue b), AnnotatedFields b)
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (AnnBoolExp b (UnpreparedValue b), AnnotatedFields b)
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnotatedFields b
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (AnnBoolExp b (UnpreparedValue b), AnnotatedFields b)
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AnnotatedFields b
-> MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnFieldsG b r v -> MutationOutputG b r v
IR.MOutSinglerowObject
mkDeleteObject ::
Backend b =>
TableName b ->
[ColumnInfo b] ->
DelPermInfo b ->
Maybe NamingCase ->
(AnnBoolExp b (IR.UnpreparedValue b), IR.MutationOutputG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b)) ->
IR.AnnDelG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b)
mkDeleteObject :: TableName b
-> [ColumnInfo b]
-> DelPermInfo b
-> Maybe NamingCase
-> (AnnBoolExp b (UnpreparedValue b),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mkDeleteObject TableName b
table [ColumnInfo b]
columns DelPermInfo b
deletePerms Maybe NamingCase
tCase (AnnBoolExp b (UnpreparedValue b)
whereExp, MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mutationOutput) =
AnnDel :: forall (b :: BackendType) r v.
TableName b
-> (AnnBoolExp b v, AnnBoolExp b v)
-> MutationOutputG b r v
-> [ColumnInfo b]
-> Maybe NamingCase
-> AnnDelG b r v
IR.AnnDel
{ _adTable :: TableName b
IR._adTable = TableName b
table,
_adWhere :: (AnnBoolExp b (UnpreparedValue b),
AnnBoolExp b (UnpreparedValue b))
IR._adWhere = (AnnBoolExp b (UnpreparedValue b)
permissionFilter, AnnBoolExp b (UnpreparedValue b)
whereExp),
_adOutput :: MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
IR._adOutput = MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
mutationOutput,
_adAllCols :: [ColumnInfo b]
IR._adAllCols = [ColumnInfo b]
columns,
_adNamingConvention :: Maybe NamingCase
IR._adNamingConvention = Maybe NamingCase
tCase
}
where
permissionFilter :: AnnBoolExp b (UnpreparedValue b)
permissionFilter = (PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue 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
<$> DelPermInfo b -> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
forall (b :: BackendType). DelPermInfo b -> AnnBoolExpPartialSQL b
dpiFilter DelPermInfo b
deletePerms
mutationSelectionSet ::
forall b r m n.
MonadBuildSchema b r m n =>
BackendTableSelectSchema b =>
SourceInfo b ->
TableInfo b ->
m (Parser 'Output n (IR.MutFldsG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b)))
mutationSelectionSet :: SourceInfo b
-> TableInfo b
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
mutationSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo =
Name
-> (SourceName, TableName b)
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) a (p :: (* -> *) -> * -> *) (n :: * -> *) b.
(MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n,
Typeable b) =>
Name -> a -> m (p n b) -> m (p n b)
P.memoizeOn 'mutationSelectionSet (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName) do
RoleName
roleName <- (SchemaContext -> RoleName) -> m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
GQLNameIdentifier
tableGQLName <- TableInfo b -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
returning <- MaybeT
m
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> m (Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
SelPermInfo b
_permissions <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
Parser 'Output n (AnnotatedFields b)
tableSet <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall r (m :: * -> *) (n :: * -> *) (b :: BackendType).
(MonadBuildSchemaBase r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList SourceInfo b
sourceInfo TableInfo b
tableInfo
let returningName :: Name
returningName = Name
Name._returning
returningDesc :: Description
returningDesc = Description
"data from the rows affected by the mutation"
pure $ AnnotatedFields b
-> MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. AnnFieldsG b r v -> MutFldG b r v
IR.MRet (AnnotatedFields b
-> MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser MetadataObjId n (AnnotatedFields b)
-> FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Output n (AnnotatedFields b)
-> FieldParser MetadataObjId n (AnnotatedFields b)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
returningName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
returningDesc) Parser 'Output n (AnnotatedFields b)
tableSet
Name
selectionName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m 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
mkTableMutationResponseTypeName GQLNameIdentifier
tableGQLName
let affectedRowsName :: Name
affectedRowsName = Name
Name._affected_rows
affectedRowsDesc :: Description
affectedRowsDesc = Description
"number of rows affected by the mutation"
selectionDesc :: Description
selectionDesc = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"response of any mutation on the table " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
selectionFields :: [FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
selectionFields =
[Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[ FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a. a -> Maybe a
Just (FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$
MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. MutFldG b r v
IR.MCount
MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> FieldParser MetadataObjId n ()
-> FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Int32
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
affectedRowsName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
affectedRowsDesc) Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int,
Maybe
(FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
returning
]
Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet Name
selectionName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
selectionDesc) [FieldParser
MetadataObjId
n
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
selectionFields
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (InsOrdHashMap
Name
(ParsedSelection
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text
-> MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> MutFldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. Text -> MutFldG b r v
IR.MExp
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
primaryKeysArguments ::
forall b r m n.
MonadBuildSchema b r m n =>
TableInfo b ->
m (Maybe (InputFieldsParser n (AnnBoolExp b (IR.UnpreparedValue b))))
primaryKeysArguments :: TableInfo b
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
primaryKeysArguments TableInfo b
tableInfo = MaybeT m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> m (Maybe
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPerms <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
PrimaryKey b (ColumnInfo b)
primaryKeys <- Maybe (PrimaryKey b (ColumnInfo b))
-> MaybeT m (PrimaryKey b (ColumnInfo b))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (PrimaryKey b (ColumnInfo b))
-> MaybeT m (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> MaybeT m (PrimaryKey b (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Maybe (PrimaryKey b (ColumnInfo b))
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn
-> Maybe (PrimaryKey b primaryKeyColumn)
_tciPrimaryKey (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Maybe (PrimaryKey b (ColumnInfo b)))
-> (TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b))
-> TableInfo b
-> Maybe (PrimaryKey b (ColumnInfo b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo (TableInfo b -> Maybe (PrimaryKey b (ColumnInfo b)))
-> TableInfo b -> Maybe (PrimaryKey b (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
tableInfo
let columns :: NESeq (ColumnInfo b)
columns = PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b)
forall (b :: BackendType) a. PrimaryKey b a -> NESeq a
_pkColumns PrimaryKey b (ColumnInfo b)
primaryKeys
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ColumnInfo b -> Bool) -> NESeq (ColumnInfo b) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\ColumnInfo b
c -> ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
c Column b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`Map.member` SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
forall (b :: BackendType).
SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiCols SelPermInfo b
selectPerms) NESeq (ColumnInfo b)
columns
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> MaybeT
m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$
(NESeq (AnnBoolExp b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (NESeq (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([AnnBoolExp b (UnpreparedValue b)]
-> AnnBoolExp b (UnpreparedValue b)
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd ([AnnBoolExp b (UnpreparedValue b)]
-> AnnBoolExp b (UnpreparedValue b))
-> (NESeq (AnnBoolExp b (UnpreparedValue b))
-> [AnnBoolExp b (UnpreparedValue b)])
-> NESeq (AnnBoolExp b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq (AnnBoolExp b (UnpreparedValue b))
-> [AnnBoolExp b (UnpreparedValue b)]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) (InputFieldsParser
MetadataObjId n (NESeq (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> (NESeq (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (NESeq (AnnBoolExp b (UnpreparedValue b))))
-> NESeq (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NESeq (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (NESeq (AnnBoolExp b (UnpreparedValue b)))
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (NESeq (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
-> m (NESeq
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NESeq (ColumnInfo b)
-> (ColumnInfo b
-> m (InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
-> m (NESeq
(InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for NESeq (ColumnInfo b)
columns \ColumnInfo b
columnInfo -> do
Parser 'Both n (ValueWithOrigin (ColumnValue b))
field <- ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) (Bool -> Nullability
G.Nullability Bool
False)
pure $
AnnBoolExpFld b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall (backend :: BackendType) field.
field -> GBoolExp backend field
BoolField (AnnBoolExpFld b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b))
-> (ValueWithOrigin (ColumnValue b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> ValueWithOrigin (ColumnValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo b
-> [OpExpG b (UnpreparedValue b)]
-> AnnBoolExpFld b (UnpreparedValue b)
forall (backend :: BackendType) leaf.
ColumnInfo backend
-> [OpExpG backend leaf] -> AnnBoolExpFld backend leaf
AVColumn ColumnInfo b
columnInfo ([OpExpG b (UnpreparedValue b)]
-> AnnBoolExpFld b (UnpreparedValue b))
-> (ValueWithOrigin (ColumnValue b)
-> [OpExpG b (UnpreparedValue b)])
-> ValueWithOrigin (ColumnValue b)
-> AnnBoolExpFld b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OpExpG b (UnpreparedValue b) -> [OpExpG b (UnpreparedValue b)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (OpExpG b (UnpreparedValue b) -> [OpExpG b (UnpreparedValue b)])
-> (ValueWithOrigin (ColumnValue b)
-> OpExpG b (UnpreparedValue b))
-> ValueWithOrigin (ColumnValue b)
-> [OpExpG b (UnpreparedValue b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UnpreparedValue b -> OpExpG b (UnpreparedValue b)
forall (backend :: BackendType) field.
Bool -> field -> OpExpG backend field
AEQ Bool
True (UnpreparedValue b -> OpExpG b (UnpreparedValue b))
-> (ValueWithOrigin (ColumnValue b) -> UnpreparedValue b)
-> ValueWithOrigin (ColumnValue b)
-> OpExpG b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter
(ValueWithOrigin (ColumnValue b)
-> AnnBoolExp b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue b))
-> InputFieldsParser n (AnnBoolExp b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Both n (ValueWithOrigin (ColumnValue b))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue 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 (ColumnInfo b -> Name
forall (b :: BackendType). ColumnInfo b -> Name
ciName ColumnInfo b
columnInfo) (ColumnInfo b -> Maybe Description
forall (b :: BackendType). ColumnInfo b -> Maybe Description
ciDescription ColumnInfo b
columnInfo) Parser 'Both n (ValueWithOrigin (ColumnValue b))
field