module Hasura.GraphQL.Schema.Build
( buildTableDeleteMutationFields,
buildTableInsertMutationFields,
buildTableQueryAndSubscriptionFields,
buildTableStreamingSubscriptionFields,
buildSingleBatchTableUpdateMutationFields,
setFieldNameCase,
buildFieldDescription,
)
where
import Data.Has (getter)
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Hasura.GraphQL.ApolloFederation
import Hasura.GraphQL.Schema.Backend (BackendTableSelectSchema (..), BackendUpdateOperatorsSchema (..), MonadBuildSchema)
import Hasura.GraphQL.Schema.BoolExp (AggregationPredicatesSchema)
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation
import Hasura.GraphQL.Schema.Parser hiding (EnumValueInfo, field)
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.SubscriptionStream (selectStreamTable)
import Hasura.GraphQL.Schema.Table (getTableIdentifierName, tableSelectPermissions)
import Hasura.GraphQL.Schema.Typename
import Hasura.GraphQL.Schema.Update.Batch (updateTable, updateTableByPk)
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.IR.Update.Batch
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.Schema.Options qualified as Options
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.Table.Cache
import Language.GraphQL.Draft.Syntax qualified as G
buildTableQueryAndSubscriptionFields ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
) =>
MkRootFieldName ->
TableName b ->
TableInfo b ->
C.GQLNameIdentifier ->
SchemaT
r
m
( [FieldParser n (QueryDB b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser n (QueryDB b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (G.Name, Parser 'Output n (ApolloFederationParserFunction n))
)
buildTableQueryAndSubscriptionFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
buildTableQueryAndSubscriptionFields MkRootFieldName
mkRootFieldName TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
gqlName = do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> SchemaT r m (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> SchemaT r m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
let customization :: ResolvedSourceCustomization
customization = SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
mkTypename :: Name -> Name
mkTypename = MkTypename -> Name -> Name
runMkTypename (MkTypename -> Name -> Name) -> MkTypename -> Name -> Name
forall a b. (a -> b) -> a -> b
$ ResolvedSourceCustomization -> MkTypename
_rscTypeNames ResolvedSourceCustomization
customization
selectName :: Name
selectName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfSelect GQLNameIdentifier -> GQLNameIdentifier
mkSelectField GQLNameIdentifier
gqlName
selectPKName :: Name
selectPKName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfSelectByPk GQLNameIdentifier -> GQLNameIdentifier
mkSelectByPkField GQLNameIdentifier
gqlName
selectAggName :: Name
selectAggName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfSelectAggregate GQLNameIdentifier -> GQLNameIdentifier
mkSelectAggregateField GQLNameIdentifier
gqlName
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectTableParser <- (AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnSimpleSelectG b r v -> QueryDB b r v
QDBMultipleRows (SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSourceSchema b r m n) =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (SelectExp b)))
selectTable TableInfo b
tableInfo Name
selectName Maybe Description
selectDesc
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectTableByPkParser <- (AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnSimpleSelectG b r v -> QueryDB b r v
QDBSingleRow (SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (SelectExp b)))
selectTableByPk TableInfo b
tableInfo Name
selectPKName Maybe Description
selectPKDesc
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectTableAggregateParser <- (AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnAggregateSelectG b r v -> QueryDB b r v
QDBAggregation (SchemaT
r
m
(Maybe
(FieldParser
n
(AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSourceSchema b r m n) =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
selectTableAggregate TableInfo b
tableInfo Name
selectAggName Maybe Description
selectAggDesc
case RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo of
Maybe (SelPermInfo b)
Nothing -> ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> SchemaT
r
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Monoid a => a
mempty, [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Monoid a => a
mempty, Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))
forall a. Maybe a
Nothing)
Just SelPermInfo {Bool
Maybe Int
HashMap ComputedFieldName (AnnRedactionExpPartialSQL b)
HashMap (Column b) (AnnRedactionExpPartialSQL b)
HashSet Text
AnnBoolExpPartialSQL b
AllowedRootFields SubscriptionRootFieldType
AllowedRootFields QueryRootFieldType
spiCols :: HashMap (Column b) (AnnRedactionExpPartialSQL b)
spiComputedFields :: HashMap ComputedFieldName (AnnRedactionExpPartialSQL b)
spiFilter :: AnnBoolExpPartialSQL b
spiLimit :: Maybe Int
spiAllowAgg :: Bool
spiRequiredHeaders :: HashSet Text
spiAllowedQueryRootFields :: AllowedRootFields QueryRootFieldType
spiAllowedSubscriptionRootFields :: AllowedRootFields SubscriptionRootFieldType
spiCols :: forall (b :: BackendType).
SelPermInfo b -> HashMap (Column b) (AnnRedactionExpPartialSQL b)
spiComputedFields :: forall (b :: BackendType).
SelPermInfo b
-> HashMap ComputedFieldName (AnnRedactionExpPartialSQL b)
spiFilter :: forall (b :: BackendType). SelPermInfo b -> AnnBoolExpPartialSQL b
spiLimit :: forall (b :: BackendType). SelPermInfo b -> Maybe Int
spiAllowAgg :: forall (b :: BackendType). SelPermInfo b -> Bool
spiRequiredHeaders :: forall (b :: BackendType). SelPermInfo b -> HashSet Text
spiAllowedQueryRootFields :: forall (b :: BackendType).
SelPermInfo b -> AllowedRootFields QueryRootFieldType
spiAllowedSubscriptionRootFields :: forall (b :: BackendType).
SelPermInfo b -> AllowedRootFields SubscriptionRootFieldType
..} -> do
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
selectStreamParser <-
if (SubscriptionRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed SubscriptionRootFieldType
SRFTSelectStream AllowedRootFields SubscriptionRootFieldType
spiAllowedSubscriptionRootFields)
then MkRootFieldName
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableStreamingSubscriptionFields MkRootFieldName
mkRootFieldName TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
gqlName
else [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Monoid a => a
mempty
let (Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
querySelectTableParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
subscriptionSelectTableParser) =
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Bool
-> Bool
-> (Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))),
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall {a}. Maybe a -> Bool -> Bool -> (Maybe a, Maybe a)
getQueryAndSubscriptionRootFields
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectTableParser
(QueryRootFieldType -> AllowedRootFields QueryRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed QueryRootFieldType
QRFTSelect AllowedRootFields QueryRootFieldType
spiAllowedQueryRootFields)
(SubscriptionRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed SubscriptionRootFieldType
SRFTSelect AllowedRootFields SubscriptionRootFieldType
spiAllowedSubscriptionRootFields)
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
querySelectTableByPkParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
subscriptionSelectTableByPkParser) =
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Bool
-> Bool
-> (Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))),
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall {a}. Maybe a -> Bool -> Bool -> (Maybe a, Maybe a)
getQueryAndSubscriptionRootFields
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectTableByPkParser
(QueryRootFieldType -> AllowedRootFields QueryRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed QueryRootFieldType
QRFTSelectByPk AllowedRootFields QueryRootFieldType
spiAllowedQueryRootFields)
(SubscriptionRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed SubscriptionRootFieldType
SRFTSelectByPk AllowedRootFields SubscriptionRootFieldType
spiAllowedSubscriptionRootFields)
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
querySelectTableAggParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
subscriptionSelectTableAggParser) =
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Bool
-> Bool
-> (Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))),
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall {a}. Maybe a -> Bool -> Bool -> (Maybe a, Maybe a)
getQueryAndSubscriptionRootFields
Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectTableAggregateParser
(QueryRootFieldType -> AllowedRootFields QueryRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed QueryRootFieldType
QRFTSelectAggregate AllowedRootFields QueryRootFieldType
spiAllowedQueryRootFields)
(SubscriptionRootFieldType
-> AllowedRootFields SubscriptionRootFieldType -> Bool
forall rootField.
Eq rootField =>
rootField -> AllowedRootFields rootField -> Bool
isRootFieldAllowed SubscriptionRootFieldType
SRFTSelectAggregate AllowedRootFields SubscriptionRootFieldType
spiAllowedSubscriptionRootFields)
queryRootFields :: [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
queryRootFields = [Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
querySelectTableParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
querySelectTableByPkParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
querySelectTableAggParser]
subscriptionRootFields :: [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
subscriptionRootFields =
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
selectStreamParser
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Semigroup a => a -> a -> a
<> [Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
subscriptionSelectTableParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
subscriptionSelectTableByPkParser, Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
subscriptionSelectTableAggParser]
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))
apolloFedTableParser <- MaybeT
(SchemaT r m)
(Name, Parser 'Output n (ApolloFederationParserFunction n))
-> SchemaT
r
m
(Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
Bool -> MaybeT (SchemaT r m) ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT (SchemaT r m) ())
-> Bool -> MaybeT (SchemaT r m) ()
forall a b. (a -> b) -> a -> b
$ Maybe ApolloFederationConfig -> Bool
isApolloFedV1enabled (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Maybe ApolloFederationConfig
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn
-> Maybe ApolloFederationConfig
_tciApolloFederationConfig (TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo))
Parser 'Output n (AnnotatedFields b)
tableSelSet <- SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b)))
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSourceSchema b r m n) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet TableInfo b
tableInfo
SelPermInfo b
selectPerm <- Maybe (SelPermInfo b) -> MaybeT (SchemaT r m) (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT (SchemaT r m) (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT (SchemaT r 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
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers)
-> MaybeT (SchemaT r m) StringifyNumbers
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> StringifyNumbers
Options.soStringifyNumbers
NESeq (ColumnInfo b)
primaryKeys <- Maybe (NESeq (ColumnInfo b))
-> MaybeT (SchemaT r m) (NESeq (ColumnInfo b))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (NESeq (ColumnInfo b))
-> MaybeT (SchemaT r m) (NESeq (ColumnInfo b)))
-> Maybe (NESeq (ColumnInfo b))
-> MaybeT (SchemaT r m) (NESeq (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ (PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Maybe (NESeq (ColumnInfo b))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b)
forall (b :: BackendType) a. PrimaryKey b a -> NESeq a
_pkColumns (Maybe (PrimaryKey b (ColumnInfo b))
-> Maybe (NESeq (ColumnInfo b)))
-> (TableInfo b -> Maybe (PrimaryKey b (ColumnInfo b)))
-> TableInfo b
-> Maybe (NESeq (ColumnInfo b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (NESeq (ColumnInfo b)))
-> TableInfo b -> Maybe (NESeq (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
tableInfo
let tableSelPerm :: TablePerms b
tableSelPerm = SelPermInfo b -> TablePerms b
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPerm
GQLNameIdentifier
tableGQLName <- TableInfo b -> MaybeT (SchemaT r m) GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
let objectTypename :: Name
objectTypename = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkTableTypeName (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier -> GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier
tableGQLName
(Name, Parser 'Output n (ApolloFederationParserFunction n))
-> MaybeT
(SchemaT r m)
(Name, Parser 'Output n (ApolloFederationParserFunction n))
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Name, Parser 'Output n (ApolloFederationParserFunction n))
-> MaybeT
(SchemaT r m)
(Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> (Name, Parser 'Output n (ApolloFederationParserFunction n))
-> MaybeT
(SchemaT r m)
(Name, Parser 'Output n (ApolloFederationParserFunction n))
forall a b. (a -> b) -> a -> b
$ (Name
objectTypename, SourceInfo b
-> TableInfo b
-> TablePerms b
-> StringifyNumbers
-> Maybe NamingCase
-> NESeq (ColumnInfo b)
-> Parser 'Output n (AnnotatedFields b)
-> Parser 'Output n (ApolloFederationParserFunction n)
forall (n :: * -> *) (b :: BackendType).
(MonadParse n, Backend b) =>
SourceInfo b
-> TableInfo b
-> TablePermG b (UnpreparedValue b)
-> StringifyNumbers
-> Maybe NamingCase
-> NESeq (ColumnInfo b)
-> Parser 'Output n (AnnotatedFields b)
-> Parser 'Output n (ApolloFederationParserFunction n)
convertToApolloFedParserFunc SourceInfo b
sourceInfo TableInfo b
tableInfo TablePerms b
tableSelPerm StringifyNumbers
stringifyNumbers (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase) NESeq (ColumnInfo b)
primaryKeys Parser 'Output n (AnnotatedFields b)
tableSelSet)
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
-> SchemaT
r
m
([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
queryRootFields, [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
subscriptionRootFields, Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n))
apolloFedTableParser)
where
selectDesc :: Maybe Description
selectDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultSelectDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfSelect
selectPKDesc :: Maybe Description
selectPKDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultSelectPKDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfSelectByPk
selectAggDesc :: Maybe Description
selectAggDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultSelectAggDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfSelectAggregate
defaultSelectDesc :: Text
defaultSelectDesc = Text
"fetch data from the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
defaultSelectPKDesc :: Text
defaultSelectPKDesc = Text
"fetch data from the table: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TableName b
tableName TableName b -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" using primary key columns"
defaultSelectAggDesc :: Text
defaultSelectAggDesc = Text
"fetch aggregated fields from the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
TableCustomRootFields {CustomRootField
_tcrfSelect :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfInsert :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfUpdateMany :: CustomRootField
_tcrfDelete :: CustomRootField
_tcrfDeleteByPk :: CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
..} = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
getQueryAndSubscriptionRootFields :: Maybe a -> Bool -> Bool -> (Maybe a, Maybe a)
getQueryAndSubscriptionRootFields Maybe a
parser Bool
allowedInQuery Bool
allowedInSubscription =
case (Bool
allowedInQuery, Bool
allowedInSubscription) of
(Bool
True, Bool
True) -> (Maybe a
parser, Maybe a
parser)
(Bool
True, Bool
False) -> (Maybe a
parser, Maybe a
forall a. Maybe a
Nothing)
(Bool
False, Bool
True) -> (Maybe a
forall a. Maybe a
Nothing, Maybe a
parser)
(Bool
False, Bool
False) -> (Maybe a
forall a. Maybe a
Nothing, Maybe a
forall a. Maybe a
Nothing)
buildTableStreamingSubscriptionFields ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
) =>
MkRootFieldName ->
TableName b ->
TableInfo b ->
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (QueryDB b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableStreamingSubscriptionFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableStreamingSubscriptionFields MkRootFieldName
mkRootFieldName TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
tableIdentifier = do
IncludeStreamFields
include <- (SchemaOptions -> IncludeStreamFields)
-> SchemaT r m IncludeStreamFields
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> IncludeStreamFields
Options.soIncludeStreamFields
case IncludeStreamFields
include of
IncludeStreamFields
Options.Don'tIncludeStreamFields -> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Monoid a => a
mempty
IncludeStreamFields
Options.IncludeStreamFields -> do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> SchemaT r m (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let customization :: ResolvedSourceCustomization
customization = SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
customRootFields :: TableCustomRootFields
customRootFields = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> TableConfig b -> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
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
selectDesc :: Maybe Description
selectDesc = Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"fetch data from the table in a streaming manner: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
selectStreamName :: Name
selectStreamName =
MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName
(Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo (TableCustomRootFields -> CustomRootField
_tcrfSelectStream TableCustomRootFields
customRootFields) GQLNameIdentifier -> GQLNameIdentifier
mkSelectStreamField GQLNameIdentifier
tableIdentifier
[Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
([Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))])
-> SchemaT
r
m
[Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> SchemaT
r
m
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))]
-> SchemaT
r
m
[Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => [f a] -> f [a]
sequenceA
[ (AnnSimpleStreamSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleStreamSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser AnnSimpleStreamSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnSimpleStreamSelectG b r v -> QueryDB b r v
QDBStreamMultipleRows (SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleStreamSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleStreamSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnSimpleStreamSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (StreamSelectExp b)))
selectStreamTable TableInfo b
tableInfo Name
selectStreamName Maybe Description
selectDesc
]
buildTableInsertMutationFields ::
forall b r m n.
( MonadBuildSchema b r m n,
BackendTableSelectSchema b
) =>
(TableInfo b -> SchemaT r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))) ->
MkRootFieldName ->
Scenario ->
TableName b ->
TableInfo b ->
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (AnnotatedInsert b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableInsertMutationFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
(TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> MkRootFieldName
-> Scenario
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
[FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableInsertMutationFields TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction MkRootFieldName
mkRootFieldName Scenario
scenario TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
gqlName = do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> SchemaT r m (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let customization :: ResolvedSourceCustomization
customization = SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
insertName :: Name
insertName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfInsert GQLNameIdentifier -> GQLNameIdentifier
mkInsertField GQLNameIdentifier
gqlName
insertOneName :: Name
insertOneName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfInsertOne GQLNameIdentifier -> GQLNameIdentifier
mkInsertOneField GQLNameIdentifier
gqlName
Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
insert <- (TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
(TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
insertIntoTable TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction Scenario
scenario TableInfo b
tableInfo Name
insertName Maybe Description
insertDesc
Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
insertOne <- (TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
(TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
insertOneIntoTable TableInfo b
-> SchemaT
r m (InputFieldsParser n (BackendInsert b (UnpreparedValue b)))
backendInsertAction Scenario
scenario TableInfo b
tableInfo Name
insertOneName Maybe Description
insertOneDesc
[FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))])
-> [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a b. (a -> b) -> a -> b
$ [Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
insert, Maybe
(FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
insertOne]
where
insertDesc :: Maybe Description
insertDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultInsertDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfInsert
insertOneDesc :: Maybe Description
insertOneDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultInsertOneDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfInsertOne
defaultInsertDesc :: Text
defaultInsertDesc = Text
"insert data into the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
defaultInsertOneDesc :: Text
defaultInsertOneDesc = Text
"insert a single row into the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
TableCustomRootFields {CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfSelect :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfUpdateMany :: CustomRootField
_tcrfDelete :: CustomRootField
_tcrfDeleteByPk :: CustomRootField
..} = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
buildSingleBatchTableUpdateMutationFields ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b,
BackendUpdateOperatorsSchema b
) =>
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b) -> UpdateVariant b (UnpreparedValue b)) ->
Scenario ->
TableInfo b ->
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (AnnotatedUpdateG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildSingleBatchTableUpdateMutationFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b, BackendUpdateOperatorsSchema b) =>
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> Scenario
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
[FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildSingleBatchTableUpdateMutationFields UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant Scenario
scenario TableInfo b
tableInfo GQLNameIdentifier
gqlName = do
Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
update <- (UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> Scenario
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b, BackendUpdateOperatorsSchema b) =>
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> Scenario
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTable UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant Scenario
scenario TableInfo b
tableInfo GQLNameIdentifier
gqlName
Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
updateByPk <- (UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> Scenario
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b,
BackendUpdateOperatorsSchema b) =>
(UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b))
-> Scenario
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
updateTableByPk UpdateBatch b (UpdateOperators b) (UnpreparedValue b)
-> UpdateVariant b (UnpreparedValue b)
mkSingleBatchUpdateVariant Scenario
scenario TableInfo b
tableInfo GQLNameIdentifier
gqlName
[FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))])
-> [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a b. (a -> b) -> a -> b
$ [Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
update, Maybe
(FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
updateByPk]
buildTableDeleteMutationFields ::
forall b r m n.
( MonadBuildSchema b r m n,
AggregationPredicatesSchema b,
BackendTableSelectSchema b
) =>
MkRootFieldName ->
Scenario ->
TableName b ->
TableInfo b ->
C.GQLNameIdentifier ->
SchemaT r m [FieldParser n (AnnDelG b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableDeleteMutationFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> Scenario
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> SchemaT
r
m
[FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
buildTableDeleteMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario TableName b
tableName TableInfo b
tableInfo GQLNameIdentifier
gqlName = do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> SchemaT r m (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let customization :: ResolvedSourceCustomization
customization = SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
deleteName :: Name
deleteName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfDelete GQLNameIdentifier -> GQLNameIdentifier
mkDeleteField GQLNameIdentifier
gqlName
deletePKName :: Name
deletePKName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
setFieldNameCase NamingCase
tCase TableInfo b
tableInfo CustomRootField
_tcrfDeleteByPk GQLNameIdentifier -> GQLNameIdentifier
mkDeleteByPkField GQLNameIdentifier
gqlName
Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
delete <- Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
deleteFromTable Scenario
scenario TableInfo b
tableInfo Name
deleteName Maybe Description
deleteDesc
Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
deleteByPk <- Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
Scenario
-> TableInfo b
-> Name
-> Maybe Description
-> SchemaT
r
m
(Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
deleteFromTableByPk Scenario
scenario TableInfo b
tableInfo Name
deletePKName Maybe Description
deletePKDesc
[FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))])
-> [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> SchemaT
r
m
[FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a b. (a -> b) -> a -> b
$ [Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))]
-> [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
delete, Maybe
(FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
deleteByPk]
where
deleteDesc :: Maybe Description
deleteDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultDeleteDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfDelete
deletePKDesc :: Maybe Description
deletePKDesc = Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultDeletePKDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfDeleteByPk
defaultDeleteDesc :: Text
defaultDeleteDesc = Text
"delete data from the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
defaultDeletePKDesc :: Text
defaultDeletePKDesc = Text
"delete single row from the table: " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
TableCustomRootFields {CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: CustomRootField
_tcrfDeleteByPk :: CustomRootField
_tcrfSelect :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfInsert :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfUpdateMany :: CustomRootField
..} = TableConfig b -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig b -> TableCustomRootFields)
-> (TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG b (FieldInfo b) (ColumnInfo b) -> TableConfig b
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields)
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
buildFieldDescription :: Text -> Comment -> Maybe G.Description
buildFieldDescription :: Text -> Comment -> Maybe Description
buildFieldDescription Text
defaultDescription = \case
Comment
Automatic -> Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description Text
defaultDescription
Explicit Maybe NonEmptyText
comment -> Text -> Description
G.Description (Text -> Description)
-> (NonEmptyText -> Text) -> NonEmptyText -> Description
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmptyText -> Text
forall a. ToTxt a => a -> Text
toTxt (NonEmptyText -> Description)
-> Maybe NonEmptyText -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NonEmptyText
comment