{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE ViewPatterns #-}
module Hasura.GraphQL.Schema.Select
( selectTableByPk,
selectTableConnection,
defaultSelectTable,
defaultSelectTableAggregate,
defaultTableArgs,
defaultTableSelectionSet,
defaultArgsParser,
tableAggregationFields,
tableConnectionArgs,
tableConnectionSelectionSet,
tableWhereArg,
tableOrderByArg,
tableDistinctArg,
tableLimitArg,
tableOffsetArg,
tablePermissionsInfo,
tableSelectionList,
)
where
import Control.Lens hiding (index)
import Data.Aeson qualified as J
import Data.Aeson.Key qualified as K
import Data.Aeson.Types qualified as J
import Data.ByteString.Lazy qualified as BL
import Data.Has
import Data.HashMap.Strict.Extended qualified as HashMap
import Data.Int (Int64)
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Text.Casing (GQLNameIdentifier)
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as Postgres
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (toErrorMessage)
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Internal.Parser qualified as IP
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.OrderBy
import Hasura.GraphQL.Schema.Parser
( FieldParser,
InputFieldsParser,
Kind (..),
Parser,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Table
import Hasura.GraphQL.Schema.Typename
import Hasura.LogicalModel.Cache (LogicalModelCache, LogicalModelInfo (..))
import Hasura.LogicalModel.Types
( LogicalModelField (..),
LogicalModelName (..),
LogicalModelType (..),
LogicalModelTypeArray (..),
LogicalModelTypeReference (..),
LogicalModelTypeScalar (..),
)
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR qualified as IR
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.Select.Lenses qualified as IR
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.NamingCase
import Hasura.RQL.Types.Relationships.Local
import Hasura.RQL.Types.Relationships.Remote
import Hasura.RQL.Types.Schema.Options (OptimizePermissionFilters (..))
import Hasura.RQL.Types.Schema.Options qualified as Options
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.Server.Utils (executeJSONPath)
import Hasura.Table.Cache
import Language.GraphQL.Draft.Syntax qualified as G
defaultSelectTable ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b ->
G.Name ->
Maybe G.Description ->
SchemaT r m (Maybe (FieldParser n (SelectExp b)))
defaultSelectTable :: 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)))
defaultSelectTable TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
-> SchemaT r m (Maybe (FieldParser n (SelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> ResolvedSourceCustomization -> NamingCase
forall a b. (a -> b) -> a -> b
$ SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPermissions <- 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
Parser 'Output n (AnnotatedFields b)
selectionSetParser <- 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 (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList TableInfo b
tableInfo
SchemaT r m (FieldParser n (SelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (FieldParser n (SelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b)))
-> SchemaT r m (FieldParser n (SelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> SchemaT r m (FieldParser n (SelectExp b))
-> SchemaT r m (FieldParser n (SelectExp 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 'defaultSelectTable (SourceName
sourceName, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> SchemaT r m StringifyNumbers
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> StringifyNumbers
Options.soStringifyNumbers
InputFieldsParser n (SelectArgsG b (UnpreparedValue b))
tableArgsParser <- TableInfo b
-> SchemaT
r m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> SchemaT
r m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSourceSchema b r m n) =>
TableInfo b
-> SchemaT
r m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
tableArguments TableInfo b
tableInfo
pure
$ MetadataObjId
-> FieldParser n (SelectExp b) -> FieldParser n (SelectExp b)
forall (m :: * -> *) origin a.
origin -> FieldParser origin m a -> FieldParser origin m a
P.setFieldParserOrigin (SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
sourceName (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). TableName b -> SourceMetadataObjId b
SMOTable @b TableName b
tableName))
(FieldParser n (SelectExp b) -> FieldParser n (SelectExp b))
-> FieldParser n (SelectExp b) -> FieldParser n (SelectExp b)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser n (SelectArgsG b (UnpreparedValue b))
-> Parser 'Output n (AnnotatedFields b)
-> FieldParser
MetadataObjId
n
(SelectArgsG 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 (SelectArgsG b (UnpreparedValue b))
tableArgsParser Parser 'Output n (AnnotatedFields b)
selectionSetParser
FieldParser
MetadataObjId
n
(SelectArgsG b (UnpreparedValue b), AnnotatedFields b)
-> ((SelectArgsG b (UnpreparedValue b), AnnotatedFields b)
-> SelectExp b)
-> FieldParser n (SelectExp b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(SelectArgsG b (UnpreparedValue b)
args, AnnotatedFields b
fields) ->
IR.AnnSelectG
{ $sel:_asnFields:AnnSelectG :: AnnotatedFields b
IR._asnFields = AnnotatedFields b
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG b (UnpreparedValue b)
IR._asnFrom = TableName b -> SelectFromG b (UnpreparedValue b)
forall (b :: BackendType) v. TableName b -> SelectFromG b v
IR.FromTable TableName b
tableName,
$sel:_asnPerm:AnnSelectG :: TablePermG b (UnpreparedValue b)
IR._asnPerm = SelPermInfo b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions,
$sel:_asnArgs:AnnSelectG :: SelectArgsG b (UnpreparedValue b)
IR._asnArgs = SelectArgsG b (UnpreparedValue b)
args,
$sel:_asnStrfyNum:AnnSelectG :: StringifyNumbers
IR._asnStrfyNum = StringifyNumbers
stringifyNumbers,
$sel:_asnNamingConvention:AnnSelectG :: Maybe NamingCase
IR._asnNamingConvention = NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase
}
selectTableConnection ::
forall b r m n.
( MonadBuildSchema b r m n,
BackendTableSelectSchema b,
AggregationPredicatesSchema b
) =>
TableInfo b ->
G.Name ->
Maybe G.Description ->
PrimaryKeyColumns b ->
SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b,
AggregationPredicatesSchema b) =>
TableInfo b
-> Name
-> Maybe Description
-> PrimaryKeyColumns b
-> SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection TableInfo b
tableInfo Name
fieldName Maybe Description
description PrimaryKeyColumns b
pkeyColumns = MaybeT (SchemaT r m) (FieldParser n (ConnectionSelectExp b))
-> SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> ResolvedSourceCustomization -> NamingCase
forall a b. (a -> b) -> a -> b
$ SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
XRelay b
xRelayInfo <- Maybe (XRelay b) -> MaybeT (SchemaT r m) (XRelay b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (XRelay b) -> MaybeT (SchemaT r m) (XRelay b))
-> Maybe (XRelay b) -> MaybeT (SchemaT r m) (XRelay b)
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b
SelPermInfo b
selectPermissions <- 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
Parser MetadataObjId 'Output n (ConnectionFields b)
selectionSetParser <- (Parser MetadataObjId 'Output n (ConnectionFields b)
-> Parser MetadataObjId 'Output n (ConnectionFields b))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (ConnectionFields b))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (ConnectionFields b))
forall a b.
(a -> b) -> MaybeT (SchemaT r m) a -> MaybeT (SchemaT r m) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Parser MetadataObjId 'Output n (ConnectionFields b)
-> Parser MetadataObjId 'Output n (ConnectionFields b)
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser (MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (ConnectionFields b))
-> MaybeT
(SchemaT r m)
(Parser MetadataObjId 'Output n (ConnectionFields b)))
-> (SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (ConnectionFields b)))
-> MaybeT
(SchemaT r m)
(Parser MetadataObjId 'Output n (ConnectionFields b)))
-> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (ConnectionFields b)))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (ConnectionFields b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (ConnectionFields b)))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (ConnectionFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (ConnectionFields b)))
-> MaybeT
(SchemaT r m)
(Parser MetadataObjId 'Output n (ConnectionFields b)))
-> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (ConnectionFields b)))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (ConnectionFields b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (ConnectionFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet TableInfo b
tableInfo
SchemaT r m (FieldParser n (ConnectionSelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (ConnectionSelectExp b))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (FieldParser n (ConnectionSelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (ConnectionSelectExp b)))
-> SchemaT r m (FieldParser n (ConnectionSelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (ConnectionSelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> SchemaT r m (FieldParser n (ConnectionSelectExp b))
-> SchemaT r m (FieldParser n (ConnectionSelectExp 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 'selectTableConnection (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> SchemaT r m StringifyNumbers
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> StringifyNumbers
Options.soStringifyNumbers
InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice)
selectArgsParser <- PrimaryKeyColumns b
-> TableInfo b
-> SelPermInfo b
-> SchemaT
r
m
(InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
PrimaryKeyColumns b
-> TableInfo b
-> SelPermInfo b
-> SchemaT
r
m
(InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice))
tableConnectionArgs PrimaryKeyColumns b
pkeyColumns TableInfo b
tableInfo SelPermInfo b
selectPermissions
pure
$ Name
-> Maybe Description
-> InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice)
-> Parser MetadataObjId 'Output n (ConnectionFields b)
-> FieldParser
MetadataObjId
n
((SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice),
ConnectionFields 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
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice)
selectArgsParser Parser MetadataObjId 'Output n (ConnectionFields b)
selectionSetParser
FieldParser
MetadataObjId
n
((SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice),
ConnectionFields b)
-> (((SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice),
ConnectionFields b)
-> ConnectionSelectExp b)
-> FieldParser n (ConnectionSelectExp b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \((SelectArgs b
args, Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
split, Maybe ConnectionSlice
slice), ConnectionFields b
fields) ->
IR.ConnectionSelect
{ $sel:_csXRelay:ConnectionSelect :: XRelay b
IR._csXRelay = XRelay b
xRelayInfo,
$sel:_csPrimaryKeyColumns:ConnectionSelect :: PrimaryKeyColumns b
IR._csPrimaryKeyColumns = PrimaryKeyColumns b
pkeyColumns,
$sel:_csSplit:ConnectionSelect :: Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
IR._csSplit = Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
split,
$sel:_csSlice:ConnectionSelect :: Maybe ConnectionSlice
IR._csSlice = Maybe ConnectionSlice
slice,
$sel:_csSelect:ConnectionSelect :: AnnSelectG
b
(ConnectionField b (RemoteRelationshipField UnpreparedValue))
(UnpreparedValue b)
IR._csSelect =
IR.AnnSelectG
{ $sel:_asnFields:AnnSelectG :: ConnectionFields b
IR._asnFields = ConnectionFields b
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG b (UnpreparedValue b)
IR._asnFrom = TableName b -> SelectFromG b (UnpreparedValue b)
forall (b :: BackendType) v. TableName b -> SelectFromG b v
IR.FromTable TableName b
tableName,
$sel:_asnPerm:AnnSelectG :: TablePermG b (UnpreparedValue b)
IR._asnPerm = SelPermInfo b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions,
$sel:_asnArgs:AnnSelectG :: SelectArgs b
IR._asnArgs = SelectArgs b
args,
$sel:_asnStrfyNum:AnnSelectG :: StringifyNumbers
IR._asnStrfyNum = StringifyNumbers
stringifyNumbers,
$sel:_asnNamingConvention:AnnSelectG :: Maybe NamingCase
IR._asnNamingConvention = NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase
}
}
selectTableByPk ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b ->
G.Name ->
Maybe G.Description ->
SchemaT r m (Maybe (FieldParser n (SelectExp b)))
selectTableByPk :: 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
fieldName Maybe Description
description = MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
-> SchemaT r m (Maybe (FieldParser n (SelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
tCase :: NamingCase
tCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> ResolvedSourceCustomization -> NamingCase
forall a b. (a -> b) -> a -> b
$ SourceInfo b -> ResolvedSourceCustomization
forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization SourceInfo b
sourceInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPermissions <- 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
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
Parser 'Output n (AnnotatedFields b)
selectionSetParser <- 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
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
$ (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) (AnnRedactionExpPartialSQL b) -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`HashMap.member` SelPermInfo b -> HashMap (Column b) (AnnRedactionExpPartialSQL b)
forall (b :: BackendType).
SelPermInfo b -> HashMap (Column b) (AnnRedactionExpPartialSQL b)
spiCols SelPermInfo b
selectPermissions) NESeq (ColumnInfo b)
primaryKeys
SchemaT r m (FieldParser n (SelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (FieldParser n (SelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b)))
-> SchemaT r m (FieldParser n (SelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> SchemaT r m (FieldParser n (SelectExp b))
-> SchemaT r m (FieldParser n (SelectExp 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 'selectTableByPk (SourceName
sourceName, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> SchemaT r m StringifyNumbers
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> StringifyNumbers
Options.soStringifyNumbers
InputFieldsParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
argsParser <-
NESeq
(InputFieldsParser
MetadataObjId n (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => NESeq (f a) -> f (NESeq a)
sequenceA (NESeq
(InputFieldsParser
MetadataObjId n (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
-> SchemaT
r
m
(NESeq
(InputFieldsParser
MetadataObjId
n
(GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NESeq (ColumnInfo b)
-> (ColumnInfo b
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
-> SchemaT
r
m
(NESeq
(InputFieldsParser
MetadataObjId
n
(GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for NESeq (ColumnInfo b)
primaryKeys \ColumnInfo b
columnInfo -> do
Parser 'Both n (ValueWithOrigin (ColumnValue b))
field <- ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
ColumnType b
-> Nullability
-> SchemaT r 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
$ AnnBoolExpFld b (UnpreparedValue b)
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))
forall (backend :: BackendType) field.
field -> GBoolExp backend field
BoolField
(AnnBoolExpFld b (UnpreparedValue b)
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
-> (ValueWithOrigin (ColumnValue b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> ValueWithOrigin (ColumnValue b)
-> GBoolExp b (AnnBoolExpFld 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 a. a -> [a]
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
. ComparisonNullability
-> UnpreparedValue b -> OpExpG b (UnpreparedValue b)
forall (backend :: BackendType) field.
ComparisonNullability -> field -> OpExpG backend field
AEQ ComparisonNullability
NonNullableComparison
(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)
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue b))
-> InputFieldsParser
MetadataObjId n (GBoolExp b (AnnBoolExpFld 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
pure
$ MetadataObjId
-> FieldParser n (SelectExp b) -> FieldParser n (SelectExp b)
forall (m :: * -> *) origin a.
origin -> FieldParser origin m a -> FieldParser origin m a
P.setFieldParserOrigin (SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
sourceName (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). TableName b -> SourceMetadataObjId b
SMOTable @b TableName b
tableName))
(FieldParser n (SelectExp b) -> FieldParser n (SelectExp b))
-> FieldParser n (SelectExp b) -> FieldParser n (SelectExp b)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
-> Parser 'Output n (AnnotatedFields b)
-> FieldParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld 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
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
argsParser Parser 'Output n (AnnotatedFields b)
selectionSetParser
FieldParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))),
AnnotatedFields b)
-> ((NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))),
AnnotatedFields b)
-> SelectExp b)
-> FieldParser n (SelectExp b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
boolExpr, AnnotatedFields b
fields) ->
let defaultPerms :: TablePermG b (UnpreparedValue b)
defaultPerms = SelPermInfo b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions
permissions :: TablePermG b (UnpreparedValue b)
permissions = TablePermG b (UnpreparedValue b)
defaultPerms {$sel:_tpLimit:TablePerm :: Maybe Int
IR._tpLimit = Maybe Int
forall a. Maybe a
Nothing}
whereExpr :: Maybe (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
whereExpr = GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
forall a. a -> Maybe a
Just (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))
-> Maybe (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ [GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))]
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd ([GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))]
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
-> [GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))]
-> GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
-> [GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))]
forall a. NESeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
boolExpr
in IR.AnnSelectG
{ $sel:_asnFields:AnnSelectG :: AnnotatedFields b
IR._asnFields = AnnotatedFields b
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG b (UnpreparedValue b)
IR._asnFrom = TableName b -> SelectFromG b (UnpreparedValue b)
forall (b :: BackendType) v. TableName b -> SelectFromG b v
IR.FromTable TableName b
tableName,
$sel:_asnPerm:AnnSelectG :: TablePermG b (UnpreparedValue b)
IR._asnPerm = TablePermG b (UnpreparedValue b)
permissions,
$sel:_asnArgs:AnnSelectG :: SelectArgsG b (UnpreparedValue b)
IR._asnArgs = SelectArgsG b (UnpreparedValue b)
forall (backend :: BackendType) v. SelectArgsG backend v
IR.noSelectArgs {$sel:_saWhere:SelectArgs :: Maybe (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
IR._saWhere = Maybe (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
whereExpr},
$sel:_asnStrfyNum:AnnSelectG :: StringifyNumbers
IR._asnStrfyNum = StringifyNumbers
stringifyNumbers,
$sel:_asnNamingConvention:AnnSelectG :: Maybe NamingCase
IR._asnNamingConvention = NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase
}
defaultSelectTableAggregate ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b ->
G.Name ->
Maybe G.Description ->
SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
defaultSelectTableAggregate :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
defaultSelectTableAggregate TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT (SchemaT r m) (FieldParser n (AggSelectExp b))
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT (SchemaT r m) (FieldParser n (AggSelectExp b))
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b))))
-> MaybeT (SchemaT r m) (FieldParser n (AggSelectExp b))
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
forall a b. (a -> b) -> a -> b
$ do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
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
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPermissions <- 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
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
$ SelPermInfo b -> Bool
forall (b :: BackendType). SelPermInfo b -> Bool
spiAllowAgg SelPermInfo b
selectPermissions
XNodesAgg b
xNodesAgg <- Maybe (XNodesAgg b) -> MaybeT (SchemaT r m) (XNodesAgg b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (XNodesAgg b) -> MaybeT (SchemaT r m) (XNodesAgg b))
-> Maybe (XNodesAgg b) -> MaybeT (SchemaT r m) (XNodesAgg b)
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). BackendSchema b => Maybe (XNodesAgg b)
nodesAggExtension @b
Parser 'Output n (AnnotatedFields b)
nodesParser <- 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 (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList TableInfo b
tableInfo
SchemaT r m (FieldParser n (AggSelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (AggSelectExp b))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (FieldParser n (AggSelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (AggSelectExp b)))
-> SchemaT r m (FieldParser n (AggSelectExp b))
-> MaybeT (SchemaT r m) (FieldParser n (AggSelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> SchemaT r m (FieldParser n (AggSelectExp b))
-> SchemaT r m (FieldParser n (AggSelectExp 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 'defaultSelectTableAggregate (SourceName
sourceName, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> SchemaT r m StringifyNumbers
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> StringifyNumbers
Options.soStringifyNumbers
GQLNameIdentifier
tableGQLName <- TableInfo b -> SchemaT r m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
InputFieldsParser n (SelectArgsG b (UnpreparedValue b))
tableArgsParser <- TableInfo b
-> SchemaT
r m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> SchemaT
r m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSourceSchema b r m n) =>
TableInfo b
-> SchemaT
r m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
tableArguments TableInfo b
tableInfo
Parser 'Output n (AggregateFields b (UnpreparedValue b))
aggregateParser <- TableInfo b
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
tableAggregationFields TableInfo b
tableInfo
Maybe
(FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
groupByParser <- TableInfo b
-> SchemaT
r
m
(Maybe
(FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
groupBy TableInfo b
tableInfo
let aggregateFields :: [FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
aggregateFields =
[ XNodesAgg b
-> AnnotatedFields b
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
XNodesAgg b -> AnnFieldsG b r v -> TableAggregateFieldG b r v
IR.TAFNodes XNodesAgg b
xNodesAgg (AnnotatedFields b
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser MetadataObjId n (AnnotatedFields b)
-> FieldParser
MetadataObjId
n
(TableAggregateFieldG
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
Name._nodes Maybe Description
forall a. Maybe a
Nothing Parser 'Output n (AnnotatedFields b)
nodesParser,
AggregateFields b (UnpreparedValue b)
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AggregateFields b v -> TableAggregateFieldG b r v
IR.TAFAgg (AggregateFields b (UnpreparedValue b)
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId n (AggregateFields b (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Output n (AggregateFields b (UnpreparedValue b))
-> FieldParser
MetadataObjId n (AggregateFields b (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
Name._aggregate Maybe Description
forall a. Maybe a
Nothing Parser 'Output n (AggregateFields b (UnpreparedValue b))
aggregateParser
]
[FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> [FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Semigroup a => a -> a -> a
<> (Maybe
(FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> [FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall a. Maybe a -> [a]
maybeToList Maybe
(FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
groupByParser)
let selectionName :: Name
selectionName = 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
mkTableAggregateTypeName GQLNameIdentifier
tableGQLName
aggregationParser :: Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
aggregationParser =
Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
(Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ (Text
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. Text -> TableAggregateFieldG b r v
IR.TAFExp
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
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 -> 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
"aggregated selection of " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName)
[FieldParser
MetadataObjId
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
aggregateFields
pure
$ MetadataObjId
-> FieldParser n (AggSelectExp b) -> FieldParser n (AggSelectExp b)
forall (m :: * -> *) origin a.
origin -> FieldParser origin m a -> FieldParser origin m a
P.setFieldParserOrigin (SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
sourceName (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend (SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). TableName b -> SourceMetadataObjId b
SMOTable @b TableName b
tableName))
(FieldParser n (AggSelectExp b) -> FieldParser n (AggSelectExp b))
-> FieldParser n (AggSelectExp b) -> FieldParser n (AggSelectExp b)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser n (SelectArgsG b (UnpreparedValue b))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> FieldParser
MetadataObjId
n
(SelectArgsG b (UnpreparedValue b),
Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Output m b
-> FieldParser origin m (a, b)
P.subselection Name
fieldName Maybe Description
description InputFieldsParser n (SelectArgsG b (UnpreparedValue b))
tableArgsParser Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
aggregationParser
FieldParser
MetadataObjId
n
(SelectArgsG b (UnpreparedValue b),
Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> ((SelectArgsG b (UnpreparedValue b),
Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> AggSelectExp b)
-> FieldParser n (AggSelectExp b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \(SelectArgsG b (UnpreparedValue b)
args, Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
fields) ->
IR.AnnSelectG
{ $sel:_asnFields:AnnSelectG :: Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
IR._asnFields = Fields
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG b (UnpreparedValue b)
IR._asnFrom = TableName b -> SelectFromG b (UnpreparedValue b)
forall (b :: BackendType) v. TableName b -> SelectFromG b v
IR.FromTable TableName b
tableName,
$sel:_asnPerm:AnnSelectG :: TablePermG b (UnpreparedValue b)
IR._asnPerm = SelPermInfo b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions,
$sel:_asnArgs:AnnSelectG :: SelectArgsG b (UnpreparedValue b)
IR._asnArgs = SelectArgsG b (UnpreparedValue b)
args,
$sel:_asnStrfyNum:AnnSelectG :: StringifyNumbers
IR._asnStrfyNum = StringifyNumbers
stringifyNumbers,
$sel:_asnNamingConvention:AnnSelectG :: Maybe NamingCase
IR._asnNamingConvention = NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase
}
groupBy ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (Maybe (FieldParser n (IR.TableAggregateFieldG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b))))
groupBy :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
groupBy TableInfo b
tableInfo = MaybeT
(SchemaT r m)
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
(SchemaT r m)
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ do
XGroupBy b
xGroupBy <- MaybeT (SchemaT r m) (XGroupBy b)
guardGroupByFeatureSupported
InputFieldsParser n [GroupKeyField b]
groupByInputFieldsParser <- TableInfo b
-> MaybeT (SchemaT r m) (InputFieldsParser n [GroupKeyField b])
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> MaybeT (SchemaT r m) (InputFieldsParser n [GroupKeyField b])
groupByInputFields TableInfo b
tableInfo
NamingCase
namingCase <- (SourceInfo b -> NamingCase) -> MaybeT (SchemaT r m) NamingCase
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve (ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> (SourceInfo b -> ResolvedSourceCustomization)
-> SourceInfo b
-> NamingCase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b)
let groupByFieldName :: Name
groupByFieldName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
namingCase Name
Name._group_by
Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectionSetParser <- TableInfo b
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
groupBySelectionSet TableInfo b
tableInfo
Name
-> Maybe Description
-> InputFieldsParser n [GroupKeyField b]
-> Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> FieldParser
MetadataObjId
n
([GroupKeyField b],
Fields
(GroupByField
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
groupByFieldName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"Groups the table by the specified keys") InputFieldsParser n [GroupKeyField b]
groupByInputFieldsParser Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectionSetParser
FieldParser
MetadataObjId
n
([GroupKeyField b],
Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (([GroupKeyField b],
Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (\([GroupKeyField b]
keys, Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
fields) -> XGroupBy b
-> GroupByG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
XGroupBy b -> GroupByG b r v -> TableAggregateFieldG b r v
IR.TAFGroupBy XGroupBy b
xGroupBy ([GroupKeyField b]
-> Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> GroupByG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
[GroupKeyField b] -> Fields (GroupByField b r v) -> GroupByG b r v
IR.GroupByG [GroupKeyField b]
keys Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
fields))
FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. a -> (a -> b) -> b
& FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> MaybeT
(SchemaT r m)
(FieldParser
n
(TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
where
guardGroupByFeatureSupported :: MaybeT (SchemaT r m) (XGroupBy b)
guardGroupByFeatureSupported :: MaybeT (SchemaT r m) (XGroupBy b)
guardGroupByFeatureSupported = do
IncludeGroupByAggregateFields
includeGroupByAggregateFields <- (SchemaOptions -> IncludeGroupByAggregateFields)
-> MaybeT (SchemaT r m) IncludeGroupByAggregateFields
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> IncludeGroupByAggregateFields
Options.soIncludeGroupByAggregateFields
case IncludeGroupByAggregateFields
includeGroupByAggregateFields of
IncludeGroupByAggregateFields
Options.IncludeGroupByAggregateFields -> Maybe (XGroupBy b) -> MaybeT (SchemaT r m) (XGroupBy b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (forall (b :: BackendType). BackendSchema b => Maybe (XGroupBy b)
groupByExtension @b)
IncludeGroupByAggregateFields
Options.ExcludeGroupByAggregateFields -> Maybe (XGroupBy b) -> MaybeT (SchemaT r m) (XGroupBy b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe Maybe (XGroupBy b)
forall a. Maybe a
Nothing
groupByInputFields ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
MaybeT (SchemaT r m) (InputFieldsParser n [IR.GroupKeyField b])
groupByInputFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> MaybeT (SchemaT r m) (InputFieldsParser n [GroupKeyField b])
groupByInputFields TableInfo b
tableInfo = do
NamingCase
namingCase <- (SourceInfo b -> NamingCase) -> MaybeT (SchemaT r m) NamingCase
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve (ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> (SourceInfo b -> ResolvedSourceCustomization)
-> SourceInfo b
-> NamingCase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b)
let keyFieldName :: Name
keyFieldName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
namingCase Name
Name._keys
Parser 'Input n (GroupKeyField b)
keysFieldValueParser <- TableInfo b
-> MaybeT (SchemaT r m) (Parser 'Input n (GroupKeyField b))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> MaybeT (SchemaT r m) (Parser 'Input n (GroupKeyField b))
groupByKeyField TableInfo b
tableInfo
pure $ Name
-> Maybe Description
-> Parser MetadataObjId 'Input n [GroupKeyField b]
-> InputFieldsParser n [GroupKeyField 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
keyFieldName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"The keys on which to group by") (Parser 'Input n (GroupKeyField b)
-> Parser MetadataObjId 'Input n [GroupKeyField 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 (GroupKeyField b)
keysFieldValueParser)
groupByKeyField ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
MaybeT (SchemaT r m) (Parser 'Input n (IR.GroupKeyField b))
groupByKeyField :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> MaybeT (SchemaT r m) (Parser 'Input n (GroupKeyField b))
groupByKeyField TableInfo b
tableInfo = do
ResolvedSourceCustomization
customization <- (SourceInfo b -> ResolvedSourceCustomization)
-> MaybeT (SchemaT r m) ResolvedSourceCustomization
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve (forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b)
let namingCase :: NamingCase
namingCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
let 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
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 groupByKeyTypeName :: Name
groupByKeyTypeName = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
namingCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkGroupByKeyTypeName GQLNameIdentifier
tableGQLName
let columnFieldName :: Name
columnFieldName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
namingCase Name
Name._column
Parser
MetadataObjId 'Both n (Column b, AnnRedactionExpUnpreparedValue b)
tableColumnsEnumParser <- SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExpUnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId 'Both n (Column b, AnnRedactionExpUnpreparedValue b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExpUnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExpUnpreparedValue b)))
-> SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExpUnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
MetadataObjId 'Both n (Column b, AnnRedactionExpUnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExpUnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe
(Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b)))
tableSelectColumnsEnum TableInfo b
tableInfo
let groupByKeyFields :: InputFieldsParser MetadataObjId n (GroupKeyField b)
groupByKeyFields =
(\(Column b
column, AnnRedactionExpUnpreparedValue b
_redactionExp) -> Column b -> GroupKeyField b
forall (b :: BackendType). Column b -> GroupKeyField b
IR.GKFColumn Column b
column)
((Column b, AnnRedactionExpUnpreparedValue b) -> GroupKeyField b)
-> InputFieldsParser
MetadataObjId n (Column b, AnnRedactionExpUnpreparedValue b)
-> InputFieldsParser MetadataObjId n (GroupKeyField b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
MetadataObjId 'Both n (Column b, AnnRedactionExpUnpreparedValue b)
-> InputFieldsParser
MetadataObjId n (Column b, AnnRedactionExpUnpreparedValue 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
columnFieldName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"A column grouping key") Parser
MetadataObjId 'Both n (Column b, AnnRedactionExpUnpreparedValue b)
tableColumnsEnumParser
pure $ Name
-> Maybe Description
-> InputFieldsParser MetadataObjId n (GroupKeyField b)
-> Parser 'Input n (GroupKeyField b)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
groupByKeyTypeName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
groupByKeyDescription) InputFieldsParser MetadataObjId n (GroupKeyField b)
groupByKeyFields
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
groupByKeyDescription :: Description
groupByKeyDescription = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"Allows the selection of a grouping key from " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
groupBySelectionSet ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
MaybeT (SchemaT r m) (Parser 'Output n (Fields (IR.GroupByField b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b))))
groupBySelectionSet :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
groupBySelectionSet TableInfo b
tableInfo = do
ResolvedSourceCustomization
customization <- (SourceInfo b -> ResolvedSourceCustomization)
-> MaybeT (SchemaT r m) ResolvedSourceCustomization
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve (forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b)
let namingCase :: NamingCase
namingCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
let 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
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 groupByTypeName :: Name
groupByTypeName = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
namingCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkGroupByTypeName GQLNameIdentifier
tableGQLName
let aggregateFieldName :: Name
aggregateFieldName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
namingCase Name
Name._aggregate
let groupKeyName :: Name
groupKeyName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
namingCase Name
Name._group_key
Parser 'Output n (AggregateFields b (UnpreparedValue b))
aggregateParser <- SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser 'Output n (AggregateFields b (UnpreparedValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser 'Output n (AggregateFields b (UnpreparedValue b))))
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser 'Output n (AggregateFields b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
tableAggregationFields TableInfo b
tableInfo
Parser 'Output n (Fields (GroupKeyField b))
groupByKeyParser <- SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
-> MaybeT
(SchemaT r m) (Parser 'Output n (Fields (GroupKeyField b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
-> MaybeT
(SchemaT r m) (Parser 'Output n (Fields (GroupKeyField b))))
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
-> MaybeT
(SchemaT r m) (Parser 'Output n (Fields (GroupKeyField b)))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
groupByKeySelectionSet TableInfo b
tableInfo
Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(GroupByField
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
groupByTypeName
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
groupByDescription)
[ Fields (GroupKeyField b)
-> GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
Fields (GroupKeyField b) -> GroupByField b r v
IR.GBFGroupKey (Fields (GroupKeyField b)
-> GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser MetadataObjId n (Fields (GroupKeyField b))
-> FieldParser
MetadataObjId
n
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Output n (Fields (GroupKeyField b))
-> FieldParser MetadataObjId n (Fields (GroupKeyField b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
groupKeyName Maybe Description
forall a. Maybe a
Nothing Parser 'Output n (Fields (GroupKeyField b))
groupByKeyParser,
AggregateFields b (UnpreparedValue b)
-> GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AggregateFields b v -> GroupByField b r v
IR.GBFAggregate (AggregateFields b (UnpreparedValue b)
-> GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId n (AggregateFields b (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Output n (AggregateFields b (UnpreparedValue b))
-> FieldParser
MetadataObjId n (AggregateFields b (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
aggregateFieldName Maybe Description
forall a. Maybe a
Nothing Parser 'Output n (AggregateFields b (UnpreparedValue b))
aggregateParser
]
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (InsOrdHashMap
Name
(ParsedSelection
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text
-> GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. Text -> GroupByField b r v
IR.GBFExp
Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. a -> (a -> b) -> b
& Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. a -> (a -> b) -> b
& Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> MaybeT
(SchemaT r m)
(Parser
'Output
n
(Fields
(GroupByField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
groupByDescription :: Description
groupByDescription = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"Group by fields of " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
groupByKeySelectionSet ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (Parser 'Output n (Fields (IR.GroupKeyField b)))
groupByKeySelectionSet :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
groupByKeySelectionSet TableInfo b
tableInfo = do
ResolvedSourceCustomization
customization <- (SourceInfo b -> ResolvedSourceCustomization)
-> SchemaT r m ResolvedSourceCustomization
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve (forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b)
let namingCase :: NamingCase
namingCase = ResolvedSourceCustomization -> NamingCase
_rscNamingConvention ResolvedSourceCustomization
customization
let 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
GQLNameIdentifier
tableGQLName <- TableInfo b -> SchemaT r m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
let groupByKeyFieldsTypeName :: Name
groupByKeyFieldsTypeName = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
namingCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkGroupByKeyFieldsTypeName GQLNameIdentifier
tableGQLName
[ColumnInfo b]
scalarColumns <- ((StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Maybe (ColumnInfo b))
-> [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [ColumnInfo b]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe ((StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Getting
(First (ColumnInfo b))
(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
(ColumnInfo b)
-> Maybe (ColumnInfo b)
forall s a. s -> Getting (First a) s a -> Maybe a
^? (StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b))
-> (StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Const
(First (ColumnInfo b))
(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
forall s t a b. Field1 s t a b => Lens s t a b
Lens
(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
(StructuredColumnInfo b)
(StructuredColumnInfo b)
_1 ((StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b))
-> (StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Const
(First (ColumnInfo b))
(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b))
-> ((ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b))
-> Getting
(First (ColumnInfo b))
(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
(ColumnInfo b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b)
forall (b :: BackendType) (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (ColumnInfo b) (f (ColumnInfo b))
-> p (StructuredColumnInfo b) (f (StructuredColumnInfo b))
_SCIScalarColumn) ([(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [ColumnInfo b])
-> SchemaT
r m [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT r m [ColumnInfo b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r m [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
forall (b :: BackendType) r (m :: * -> *).
(Backend b, MonadError QErr m, MonadReader r m,
Has SchemaContext r, Has (SourceInfo b) r) =>
TableInfo b
-> m [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
tableSelectColumns TableInfo b
tableInfo
[FieldParser MetadataObjId n (GroupKeyField b)]
columnFieldParsers <-
[ColumnInfo b]
-> (ColumnInfo b
-> SchemaT r m (FieldParser MetadataObjId n (GroupKeyField b)))
-> SchemaT r m [FieldParser MetadataObjId n (GroupKeyField b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [ColumnInfo b]
scalarColumns ((ColumnInfo b
-> SchemaT r m (FieldParser MetadataObjId n (GroupKeyField b)))
-> SchemaT r m [FieldParser MetadataObjId n (GroupKeyField b)])
-> (ColumnInfo b
-> SchemaT r m (FieldParser MetadataObjId n (GroupKeyField b)))
-> SchemaT r m [FieldParser MetadataObjId n (GroupKeyField b)]
forall a b. (a -> b) -> a -> b
$ \ColumnInfo b
columnInfo -> do
let columnFieldName :: Name
columnFieldName = ColumnInfo b -> Name
forall (b :: BackendType). ColumnInfo b -> Name
ciName ColumnInfo b
columnInfo
let column :: Column b
column = ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo
Parser 'Both n (ValueWithOrigin (ColumnValue b))
columnParser' <- ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
ColumnType b
-> Nullability
-> SchemaT r 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
True)
pure $ (forall (b :: BackendType). Column b -> GroupKeyField b
IR.GKFColumn @b Column b
column) GroupKeyField b
-> FieldParser MetadataObjId n ()
-> FieldParser MetadataObjId n (GroupKeyField b)
forall a b.
a -> FieldParser MetadataObjId n b -> FieldParser MetadataObjId n a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Name
-> Maybe Description
-> Parser 'Both n (ValueWithOrigin (ColumnValue b))
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
columnFieldName (ColumnInfo b -> Maybe Description
forall (b :: BackendType). ColumnInfo b -> Maybe Description
ciDescription ColumnInfo b
columnInfo) Parser 'Both n (ValueWithOrigin (ColumnValue b))
columnParser'
Name
-> Maybe Description
-> [FieldParser MetadataObjId n (GroupKeyField b)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (GroupKeyField 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
groupByKeyFieldsTypeName
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
groupByKeyFieldsDescription)
[FieldParser MetadataObjId n (GroupKeyField b)]
columnFieldParsers
Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (GroupKeyField b)))
-> (InsOrdHashMap Name (ParsedSelection (GroupKeyField b))
-> Fields (GroupKeyField b))
-> Parser 'Output n (Fields (GroupKeyField b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> GroupKeyField b)
-> InsOrdHashMap Name (ParsedSelection (GroupKeyField b))
-> Fields (GroupKeyField b)
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> GroupKeyField b
forall (b :: BackendType). Text -> GroupKeyField b
IR.GKFExp
Parser 'Output n (Fields (GroupKeyField b))
-> (Parser 'Output n (Fields (GroupKeyField b))
-> Parser 'Output n (Fields (GroupKeyField b)))
-> Parser 'Output n (Fields (GroupKeyField b))
forall a b. a -> (a -> b) -> b
& Parser 'Output n (Fields (GroupKeyField b))
-> Parser 'Output n (Fields (GroupKeyField b))
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
Parser 'Output n (Fields (GroupKeyField b))
-> (Parser 'Output n (Fields (GroupKeyField b))
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b))))
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
forall a b. a -> (a -> b) -> b
& Parser 'Output n (Fields (GroupKeyField b))
-> SchemaT r m (Parser 'Output n (Fields (GroupKeyField b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
groupByKeyFieldsDescription :: Description
groupByKeyFieldsDescription = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"Allows the selection of fields from the grouping key of " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
defaultTableSelectionSet ::
forall b r m n.
( AggregationPredicatesSchema b,
BackendTableSelectSchema b,
Eq (AnnBoolExp b (IR.UnpreparedValue b)),
MonadBuildSchema b r m n
) =>
TableInfo b ->
SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
defaultTableSelectionSet :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
defaultTableSelectionSet TableInfo b
tableInfo = MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b))
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
tableCoreInfo :: TableCoreInfo b
tableCoreInfo = TableInfo b -> TableCoreInfo b
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
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
logicalModelCache :: LogicalModelCache b
logicalModelCache = SourceInfo b -> LogicalModelCache b
forall (b :: BackendType). SourceInfo b -> LogicalModelCache b
_siLogicalModels SourceInfo b
sourceInfo
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
_selectPermissions <- 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
SchemaKind
schemaKind <- SchemaT r m SchemaKind -> MaybeT (SchemaT r m) SchemaKind
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m SchemaKind -> MaybeT (SchemaT r m) SchemaKind)
-> SchemaT r m SchemaKind -> MaybeT (SchemaT r m) SchemaKind
forall a b. (a -> b) -> a -> b
$ (SchemaContext -> SchemaKind) -> SchemaT r m SchemaKind
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> SchemaKind
scSchemaKind
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
$ SchemaKind -> Bool
isHasuraSchema SchemaKind
schemaKind Bool -> Bool -> Bool
|| Maybe (XRelay b) -> Bool
forall a. Maybe a -> Bool
isJust (forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b)
SchemaT r m (Parser 'Output n (AnnotatedFields b))
-> MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (Parser 'Output n (AnnotatedFields b))
-> MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b)))
-> SchemaT r m (Parser 'Output n (AnnotatedFields b))
-> MaybeT (SchemaT r m) (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b)
-> SchemaT r m (Parser 'Output n (AnnotatedFields b))
-> SchemaT r m (Parser 'Output n (AnnotatedFields 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 'defaultTableSelectionSet (SourceName
sourceName, TableName b
tableName) do
GQLNameIdentifier
tableGQLName <- TableInfo b -> 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
tableGQLName
xRelay :: Maybe (XRelay b)
xRelay = forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b
tableFields :: [FieldInfo b]
tableFields = HashMap FieldName (FieldInfo b) -> [FieldInfo b]
forall k v. HashMap k v -> [v]
HashMap.elems (HashMap FieldName (FieldInfo b) -> [FieldInfo b])
-> HashMap FieldName (FieldInfo b) -> [FieldInfo b]
forall a b. (a -> b) -> a -> b
$ TableCoreInfo b -> HashMap FieldName (FieldInfo b)
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> FieldInfoMap field
_tciFieldInfoMap TableCoreInfo b
tableCoreInfo
tablePkeyColumns :: Maybe (NESeq (ColumnInfo b))
tablePkeyColumns = PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b)
forall (b :: BackendType) a. PrimaryKey b a -> NESeq a
_pkColumns (PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Maybe (NESeq (ColumnInfo b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableCoreInfo b -> Maybe (PrimaryKey b (ColumnInfo b))
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn
-> Maybe (PrimaryKey b primaryKeyColumn)
_tciPrimaryKey TableCoreInfo b
tableCoreInfo
pkFields :: [ColumnInfo b]
pkFields = (NESeq (ColumnInfo b) -> [ColumnInfo b])
-> Maybe (NESeq (ColumnInfo b)) -> [ColumnInfo b]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap NESeq (ColumnInfo b) -> [ColumnInfo b]
forall a. NESeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Maybe (NESeq (ColumnInfo b))
tablePkeyColumns
pkFieldDirective :: Text
pkFieldDirective = Text -> [Text] -> Text
T.intercalate Text
" " ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (ColumnInfo b -> Text) -> [ColumnInfo b] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Name -> Text
G.unName (Name -> Text) -> (ColumnInfo b -> Name) -> ColumnInfo b -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo b -> Name
forall (b :: BackendType). ColumnInfo b -> Name
ciName) [ColumnInfo b]
pkFields
pkDirectives :: [Directive Void]
pkDirectives =
if Maybe ApolloFederationConfig -> Bool
isApolloFedV1enabled (TableCoreInfo b -> Maybe ApolloFederationConfig
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn
-> Maybe ApolloFederationConfig
_tciApolloFederationConfig TableCoreInfo b
tableCoreInfo) Bool -> Bool -> Bool
&& (Bool -> Bool
not (Bool -> Bool)
-> ([ColumnInfo b] -> Bool) -> [ColumnInfo b] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ColumnInfo b] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [ColumnInfo b]
pkFields
then [(Name -> HashMap Name (Value Void) -> Directive Void
forall var. Name -> HashMap Name (Value var) -> Directive var
G.Directive Name
Name._key (HashMap Name (Value Void) -> Directive Void)
-> (Text -> HashMap Name (Value Void)) -> Text -> Directive Void
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Value Void -> HashMap Name (Value Void)
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton Name
Name._fields (Value Void -> HashMap Name (Value Void))
-> (Text -> Value Void) -> Text -> HashMap Name (Value Void)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value Void
forall var. Text -> Value var
G.VString) Text
pkFieldDirective]
else [Directive Void]
forall a. Monoid a => a
mempty
description :: Maybe Description
description = Text -> Description
G.Description (Text -> Description)
-> (PGDescription -> Text) -> PGDescription -> Description
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGDescription -> Text
Postgres.getPGDescription (PGDescription -> Description)
-> Maybe PGDescription -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableCoreInfo b -> Maybe PGDescription
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> Maybe PGDescription
_tciDescription TableCoreInfo b
tableCoreInfo
[FieldParser n (AnnotatedField b)]
fieldParsers <-
[[FieldParser n (AnnotatedField b)]]
-> [FieldParser n (AnnotatedField b)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
([[FieldParser n (AnnotatedField b)]]
-> [FieldParser n (AnnotatedField b)])
-> SchemaT r m [[FieldParser n (AnnotatedField b)]]
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldInfo b]
-> (FieldInfo b -> SchemaT r m [FieldParser n (AnnotatedField b)])
-> SchemaT r m [[FieldParser n (AnnotatedField b)]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for
[FieldInfo b]
tableFields
(LogicalModelCache b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
LogicalModelCache b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> SchemaT r m [FieldParser n (AnnotatedField b)]
fieldSelection LogicalModelCache b
logicalModelCache TableName b
tableName TableInfo b
tableInfo)
case (SchemaKind
schemaKind, Maybe (NESeq (ColumnInfo b))
tablePkeyColumns, Maybe (XRelay b)
xRelay) of
(RelaySchema NodeInterfaceParserBuilder
nodeBuilder, Just NESeq (ColumnInfo b)
pkeyColumns, Just XRelay b
xRelayInfo) -> do
let nodeIdFieldParser :: FieldParser n (AnnotatedField b)
nodeIdFieldParser =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
Name._id Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.identifier FieldParser MetadataObjId n ()
-> AnnotatedField b -> FieldParser n (AnnotatedField b)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> XRelay b
-> SourceName
-> TableName b
-> NESeq (ColumnInfo b)
-> AnnotatedField b
forall (b :: BackendType) r v.
XRelay b
-> SourceName
-> TableName b
-> PrimaryKeyColumns b
-> AnnFieldG b r v
IR.AFNodeId XRelay b
xRelayInfo SourceName
sourceName TableName b
tableName NESeq (ColumnInfo b)
pkeyColumns
allFieldParsers :: [FieldParser n (AnnotatedField b)]
allFieldParsers = [FieldParser n (AnnotatedField b)]
fieldParsers [FieldParser n (AnnotatedField b)]
-> [FieldParser n (AnnotatedField b)]
-> [FieldParser n (AnnotatedField b)]
forall a. Semigroup a => a -> a -> a
<> [FieldParser n (AnnotatedField b)
nodeIdFieldParser]
SchemaContext
context <- (r -> SchemaContext) -> SchemaT r m SchemaContext
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SchemaContext
forall a t. Has a t => t -> a
getter
SchemaOptions
options <- (r -> SchemaOptions) -> SchemaT r m SchemaOptions
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SchemaOptions
forall a t. Has a t => t -> a
getter
Parser 'Output n NodeMap
nodeInterface <- m (Parser 'Output n NodeMap)
-> SchemaT r m (Parser 'Output n NodeMap)
forall (m :: * -> *) a. Monad m => m a -> SchemaT r m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Output n NodeMap)
-> SchemaT r m (Parser 'Output n NodeMap))
-> m (Parser 'Output n NodeMap)
-> SchemaT r m (Parser 'Output n NodeMap)
forall a b. (a -> b) -> a -> b
$ NodeInterfaceParserBuilder
-> forall (m :: * -> *) (n :: * -> *).
MonadBuildSchemaBase m n =>
SchemaContext -> SchemaOptions -> m (Parser 'Output n NodeMap)
runNodeBuilder NodeInterfaceParserBuilder
nodeBuilder SchemaContext
context SchemaOptions
options
pure
$ Name
-> Maybe Description
-> [FieldParser n (AnnotatedField b)]
-> [Parser 'Output n NodeMap]
-> [Directive Void]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (AnnotatedField b)))
forall {m :: * -> *} {origin} {a} {b}.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> [Parser origin 'Output m b]
-> [Directive Void]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
selectionSetObjectWithDirective Name
objectTypename Maybe Description
description [FieldParser n (AnnotatedField b)]
allFieldParsers [Parser 'Output n NodeMap
nodeInterface] [Directive Void]
pkDirectives
Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (AnnotatedField b)))
-> (InsOrdHashMap Name (ParsedSelection (AnnotatedField b))
-> AnnotatedFields b)
-> Parser 'Output n (AnnotatedFields b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> AnnotatedField b)
-> InsOrdHashMap Name (ParsedSelection (AnnotatedField b))
-> AnnotatedFields b
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> AnnotatedField b
forall (b :: BackendType) r v. Text -> AnnFieldG b r v
IR.AFExpression
(SchemaKind, Maybe (NESeq (ColumnInfo b)), Maybe (XRelay b))
_ ->
Parser 'Output n (AnnotatedFields b)
-> SchemaT r m (Parser 'Output n (AnnotatedFields b))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Parser 'Output n (AnnotatedFields b)
-> SchemaT r m (Parser 'Output n (AnnotatedFields b)))
-> Parser 'Output n (AnnotatedFields b)
-> SchemaT r m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser n (AnnotatedField b)]
-> [Parser MetadataObjId 'Output n Any]
-> [Directive Void]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (AnnotatedField b)))
forall {m :: * -> *} {origin} {a} {b}.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> [Parser origin 'Output m b]
-> [Directive Void]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
selectionSetObjectWithDirective Name
objectTypename Maybe Description
description [FieldParser n (AnnotatedField b)]
fieldParsers [] [Directive Void]
pkDirectives
Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (AnnotatedField b)))
-> (InsOrdHashMap Name (ParsedSelection (AnnotatedField b))
-> AnnotatedFields b)
-> Parser 'Output n (AnnotatedFields b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> AnnotatedField b)
-> InsOrdHashMap Name (ParsedSelection (AnnotatedField b))
-> AnnotatedFields b
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> AnnotatedField b
forall (b :: BackendType) r v. Text -> AnnFieldG b r v
IR.AFExpression
where
selectionSetObjectWithDirective :: Name
-> Maybe Description
-> [FieldParser origin m a]
-> [Parser origin 'Output m b]
-> [Directive Void]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
selectionSetObjectWithDirective Name
name Maybe Description
description [FieldParser origin m a]
parsers [Parser origin 'Output m b]
implementsInterfaces [Directive Void]
directives =
[Directive Void]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
forall origin (k :: Kind) (m :: * -> *) a.
[Directive Void] -> Parser origin k m a -> Parser origin k m a
IP.setParserDirectives [Directive Void]
directives
(Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
-> Parser
origin 'Output m (InsOrdHashMap Name (ParsedSelection a)))
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser origin m a]
-> [Parser origin 'Output m b]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> [Parser origin 'Output m b]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSetObject Name
name Maybe Description
description [FieldParser origin m a]
parsers [Parser origin 'Output m b]
implementsInterfaces
tableSelectionList ::
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b ->
SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList TableInfo b
tableInfo =
(Parser 'Output n (AnnotatedFields b)
-> Parser 'Output n (AnnotatedFields b))
-> Maybe (Parser 'Output n (AnnotatedFields b))
-> Maybe (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Parser 'Output n (AnnotatedFields b)
-> Parser 'Output n (AnnotatedFields b)
forall (m :: * -> *) a. Parser 'Output m a -> Parser 'Output m a
nonNullableObjectList (Maybe (Parser 'Output n (AnnotatedFields b))
-> Maybe (Parser 'Output n (AnnotatedFields b)))
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> SchemaT r m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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
nonNullableObjectList :: Parser 'Output m a -> Parser 'Output m a
nonNullableObjectList :: forall (m :: * -> *) a. Parser 'Output m a -> Parser 'Output m a
nonNullableObjectList =
Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser (Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a)
-> (Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a)
-> Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.multiple (Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a)
-> (Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a)
-> Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Output m a
-> Parser MetadataObjId 'Output m a
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
tableConnectionSelectionSet ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b ->
SchemaT r m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
TableInfo b
-> SchemaT r m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet TableInfo b
tableInfo = MaybeT (SchemaT r m) (Parser 'Output n (ConnectionFields b))
-> SchemaT r m (Maybe (Parser 'Output n (ConnectionFields b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
SourceInfo b
sourceInfo :: SourceInfo b <- (r -> SourceInfo b) -> MaybeT (SchemaT r m) (SourceInfo b)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> SourceInfo b
forall a t. Has a t => t -> a
getter
let sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
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
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
GQLNameIdentifier
tableIdentifierName <- SchemaT r m GQLNameIdentifier
-> MaybeT (SchemaT r m) GQLNameIdentifier
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m GQLNameIdentifier
-> MaybeT (SchemaT r m) GQLNameIdentifier)
-> SchemaT r m GQLNameIdentifier
-> MaybeT (SchemaT r m) GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ TableInfo b -> SchemaT r m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
let tableGQLName :: Name
tableGQLName = NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
tableIdentifierName
MaybeT (SchemaT r m) (SelPermInfo b) -> MaybeT (SchemaT r m) ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MaybeT (SchemaT r m) (SelPermInfo b) -> MaybeT (SchemaT r m) ())
-> MaybeT (SchemaT r m) (SelPermInfo b) -> MaybeT (SchemaT r m) ()
forall a b. (a -> b) -> a -> b
$ 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
Parser 'Output n (EdgeFields b)
edgesParser <- SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
-> MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
-> MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b)))
-> SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
-> MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b))
forall a b. (a -> b) -> a -> b
$ (Name -> Name)
-> Name -> SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet Name -> Name
mkTypename Name
tableGQLName
SchemaT r m (Parser 'Output n (ConnectionFields b))
-> MaybeT (SchemaT r m) (Parser 'Output n (ConnectionFields b))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (Parser 'Output n (ConnectionFields b))
-> MaybeT (SchemaT r m) (Parser 'Output n (ConnectionFields b)))
-> SchemaT r m (Parser 'Output n (ConnectionFields b))
-> MaybeT (SchemaT r m) (Parser 'Output n (ConnectionFields b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b)
-> SchemaT r m (Parser 'Output n (ConnectionFields b))
-> SchemaT r m (Parser 'Output n (ConnectionFields 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 'tableConnectionSelectionSet (SourceName
sourceName, TableName b
tableName) do
let connectionTypeName :: Name
connectionTypeName = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Name
tableGQLName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name._Connection
pageInfo :: FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
pageInfo =
Name
-> Maybe Description
-> Parser MetadataObjId 'Output n PageInfoFields
-> FieldParser MetadataObjId n PageInfoFields
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_
Name
Name._pageInfo
Maybe Description
forall a. Maybe a
Nothing
Parser MetadataObjId 'Output n PageInfoFields
pageInfoSelectionSet
FieldParser MetadataObjId n PageInfoFields
-> (PageInfoFields
-> ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> PageInfoFields
-> ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
PageInfoFields -> ConnectionField b r v
IR.ConnectionPageInfo
edges :: FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
edges =
Name
-> Maybe Description
-> Parser 'Output n (EdgeFields b)
-> FieldParser MetadataObjId n (EdgeFields b)
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_
Name
Name._edges
Maybe Description
forall a. Maybe a
Nothing
Parser 'Output n (EdgeFields b)
edgesParser
FieldParser MetadataObjId n (EdgeFields b)
-> (EdgeFields b
-> ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> EdgeFields b
-> ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
EdgeFields b r v -> ConnectionField b r v
IR.ConnectionEdges
connectionDescription :: Description
connectionDescription = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"A Relay connection object on " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName b
tableName
Parser 'Output n (ConnectionFields b)
-> SchemaT r m (Parser 'Output n (ConnectionFields b))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Parser 'Output n (ConnectionFields b)
-> SchemaT r m (Parser 'Output n (ConnectionFields b)))
-> Parser 'Output n (ConnectionFields b)
-> SchemaT r m (Parser 'Output n (ConnectionFields b))
forall a b. (a -> b) -> a -> b
$ Parser 'Output n (ConnectionFields b)
-> Parser 'Output n (ConnectionFields b)
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
(Parser 'Output n (ConnectionFields b)
-> Parser 'Output n (ConnectionFields b))
-> Parser 'Output n (ConnectionFields b)
-> Parser 'Output n (ConnectionFields b)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(ConnectionField
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
connectionTypeName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
connectionDescription) [FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
pageInfo, FieldParser
MetadataObjId
n
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
edges]
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (InsOrdHashMap
Name
(ParsedSelection
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> ConnectionFields b)
-> Parser 'Output n (ConnectionFields b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text
-> ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> ConnectionFields b
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. Text -> ConnectionField b r v
IR.ConnectionTypename
where
pageInfoSelectionSet :: Parser 'Output n IR.PageInfoFields
pageInfoSelectionSet :: Parser MetadataObjId 'Output n PageInfoFields
pageInfoSelectionSet =
let startCursorField :: FieldParser origin n PageInfoField
startCursorField =
Name
-> Maybe Description
-> Parser origin 'Both n Text
-> FieldParser origin n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
Name
Name._startCursor
Maybe Description
forall a. Maybe a
Nothing
Parser origin 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser origin n ()
-> PageInfoField -> FieldParser origin n PageInfoField
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PageInfoField
IR.PageInfoStartCursor
endCursorField :: FieldParser origin n PageInfoField
endCursorField =
Name
-> Maybe Description
-> Parser origin 'Both n Text
-> FieldParser origin n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
Name
Name._endCursor
Maybe Description
forall a. Maybe a
Nothing
Parser origin 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser origin n ()
-> PageInfoField -> FieldParser origin n PageInfoField
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PageInfoField
IR.PageInfoEndCursor
hasNextPageField :: FieldParser origin n PageInfoField
hasNextPageField =
Name
-> Maybe Description
-> Parser origin 'Both n Bool
-> FieldParser origin n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
Name
Name._hasNextPage
Maybe Description
forall a. Maybe a
Nothing
Parser origin 'Both n Bool
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Bool
P.boolean
FieldParser origin n ()
-> PageInfoField -> FieldParser origin n PageInfoField
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PageInfoField
IR.PageInfoHasNextPage
hasPreviousPageField :: FieldParser origin n PageInfoField
hasPreviousPageField =
Name
-> Maybe Description
-> Parser origin 'Both n Bool
-> FieldParser origin n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
Name
Name._hasPreviousPage
Maybe Description
forall a. Maybe a
Nothing
Parser origin 'Both n Bool
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Bool
P.boolean
FieldParser origin n ()
-> PageInfoField -> FieldParser origin n PageInfoField
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> PageInfoField
IR.PageInfoHasPreviousPage
allFields :: [FieldParser MetadataObjId n PageInfoField]
allFields =
[ FieldParser MetadataObjId n PageInfoField
forall {origin}. FieldParser origin n PageInfoField
startCursorField,
FieldParser MetadataObjId n PageInfoField
forall {origin}. FieldParser origin n PageInfoField
endCursorField,
FieldParser MetadataObjId n PageInfoField
forall {origin}. FieldParser origin n PageInfoField
hasNextPageField,
FieldParser MetadataObjId n PageInfoField
forall {origin}. FieldParser origin n PageInfoField
hasPreviousPageField
]
in Parser MetadataObjId 'Output n PageInfoFields
-> Parser MetadataObjId 'Output n PageInfoFields
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
(Parser MetadataObjId 'Output n PageInfoFields
-> Parser MetadataObjId 'Output n PageInfoFields)
-> Parser MetadataObjId 'Output n PageInfoFields
-> Parser MetadataObjId 'Output n PageInfoFields
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser MetadataObjId n PageInfoField]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection PageInfoField))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> [FieldParser origin m a]
-> Parser origin 'Output m (InsOrdHashMap Name (ParsedSelection a))
P.selectionSet Name
Name._PageInfo Maybe Description
forall a. Maybe a
Nothing [FieldParser MetadataObjId n PageInfoField]
allFields
Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection PageInfoField))
-> (InsOrdHashMap Name (ParsedSelection PageInfoField)
-> PageInfoFields)
-> Parser MetadataObjId 'Output n PageInfoFields
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> PageInfoField)
-> InsOrdHashMap Name (ParsedSelection PageInfoField)
-> PageInfoFields
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> PageInfoField
IR.PageInfoTypename
tableEdgesSelectionSet ::
(G.Name -> G.Name) ->
G.Name ->
SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet :: (Name -> Name)
-> Name -> SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet Name -> Name
mkTypename Name
tableGQLName = MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b))
-> SchemaT r m (Maybe (Parser 'Output n (EdgeFields b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
Parser MetadataObjId 'Output n (AnnotatedFields b)
edgeNodeParser <- SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> MaybeT
(SchemaT r m) (Parser MetadataObjId 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ (Parser MetadataObjId 'Output n (AnnotatedFields b)
-> Parser MetadataObjId 'Output n (AnnotatedFields b))
-> Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b))
-> Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Parser MetadataObjId 'Output n (AnnotatedFields b)
-> Parser MetadataObjId 'Output n (AnnotatedFields b)
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b))
-> Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> SchemaT
r m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r m (Maybe (Parser MetadataObjId '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
let edgesType :: Name
edgesType = Name -> Name
mkTypename (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Name
tableGQLName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name._Edge
cursor :: FieldParser origin n (EdgeField b r v)
cursor =
Name
-> Maybe Description
-> Parser origin 'Both n Text
-> FieldParser origin n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
Name
Name._cursor
Maybe Description
forall a. Maybe a
Nothing
Parser origin 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
FieldParser origin n ()
-> EdgeField b r v -> FieldParser origin n (EdgeField b r v)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> EdgeField b r v
forall (b :: BackendType) r v. EdgeField b r v
IR.EdgeCursor
edgeNode :: FieldParser
MetadataObjId
n
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
edgeNode =
Name
-> Maybe Description
-> Parser MetadataObjId '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
Name._node
Maybe Description
forall a. Maybe a
Nothing
Parser MetadataObjId 'Output n (AnnotatedFields b)
edgeNodeParser
FieldParser MetadataObjId n (AnnotatedFields b)
-> (AnnotatedFields b
-> EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> AnnotatedFields b
-> EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. AnnFieldsG b r v -> EdgeField b r v
IR.EdgeNode
Parser 'Output n (EdgeFields b)
-> MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b))
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Parser 'Output n (EdgeFields b)
-> MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b)))
-> Parser 'Output n (EdgeFields b)
-> MaybeT (SchemaT r m) (Parser 'Output n (EdgeFields b))
forall a b. (a -> b) -> a -> b
$ Parser 'Output n (EdgeFields b) -> Parser 'Output n (EdgeFields b)
forall (m :: * -> *) a. Parser 'Output m a -> Parser 'Output m a
nonNullableObjectList
(Parser 'Output n (EdgeFields b)
-> Parser 'Output n (EdgeFields b))
-> Parser 'Output n (EdgeFields b)
-> Parser 'Output n (EdgeFields b)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(EdgeField
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
edgesType Maybe Description
forall a. Maybe a
Nothing [FieldParser
MetadataObjId
n
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall {origin} {b :: BackendType} {r} {v}.
FieldParser origin n (EdgeField b r v)
cursor, FieldParser
MetadataObjId
n
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
edgeNode]
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (InsOrdHashMap
Name
(ParsedSelection
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> EdgeFields b)
-> Parser 'Output n (EdgeFields b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text
-> EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> EdgeFields b
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> EdgeField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. Text -> EdgeField b r v
IR.EdgeTypename
defaultTableArgs ::
forall b r m n.
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
TableInfo b ->
SchemaT r m (InputFieldsParser n (SelectArgs b))
defaultTableArgs :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
TableInfo b -> SchemaT r m (InputFieldsParser n (SelectArgs b))
defaultTableArgs TableInfo b
tableInfo = do
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser <- TableInfo b
-> SchemaT
r
m
(InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, MonadBuildSchema b r m n) =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg TableInfo b
tableInfo
InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser <- TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg TableInfo b
tableInfo
InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
distinctParser <- TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))))
tableDistinctArg TableInfo b
tableInfo
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
-> SchemaT r m (InputFieldsParser n (SelectArgs b))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
-> SchemaT r m (InputFieldsParser n (SelectArgs b))
defaultArgsParser InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
distinctParser
tableWhereArg ::
forall b r m n.
( AggregationPredicatesSchema b,
MonadBuildSchema b r m n
) =>
TableInfo b ->
SchemaT r m (InputFieldsParser n (Maybe (IR.AnnBoolExp b (IR.UnpreparedValue b))))
tableWhereArg :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, MonadBuildSchema b r m n) =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg TableInfo b
tableInfo = do
Parser 'Input n (AnnBoolExp b (UnpreparedValue b))
boolExpParser <- TableInfo b
-> SchemaT r m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
TableInfo b
-> SchemaT r m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
tableBoolExp TableInfo b
tableInfo
pure
$ (Maybe (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (AnnBoolExp b (UnpreparedValue b))))
-> InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> Maybe (AnnBoolExp b (UnpreparedValue b))
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
(InputFieldsParser
MetadataObjId n (Maybe (Maybe (AnnBoolExp b (UnpreparedValue b))))
-> InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (AnnBoolExp b (UnpreparedValue b))))
-> InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser
MetadataObjId 'Input n (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (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 (Maybe a)
P.fieldOptional Name
whereName Maybe Description
whereDesc
(Parser
MetadataObjId 'Input n (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (AnnBoolExp b (UnpreparedValue b)))))
-> Parser
MetadataObjId 'Input n (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (AnnBoolExp b (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ Parser 'Input n (AnnBoolExp b (UnpreparedValue b))
-> Parser
MetadataObjId 'Input n (Maybe (AnnBoolExp 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 (AnnBoolExp b (UnpreparedValue b))
boolExpParser
where
whereName :: Name
whereName = Name
Name._where
whereDesc :: Maybe Description
whereDesc = 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
"filter the rows returned"
tableOrderByArg ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (InputFieldsParser n (Maybe (NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b)))))
tableOrderByArg :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg TableInfo b
tableInfo = do
NamingCase
tCase <- (SourceInfo b -> NamingCase) -> SchemaT r m NamingCase
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve ((SourceInfo b -> NamingCase) -> SchemaT r m NamingCase)
-> (SourceInfo b -> NamingCase) -> SchemaT r m NamingCase
forall a b. (a -> b) -> a -> b
$ ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> (SourceInfo b -> ResolvedSourceCustomization)
-> SourceInfo b
-> NamingCase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b
Parser 'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)]
orderByParser <- TableInfo b
-> SchemaT
r m (Parser 'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)])
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r m (Parser 'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)])
tableOrderByExp TableInfo b
tableInfo
let orderByName :: Name
orderByName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
tCase Name
Name._order_by
orderByDesc :: Maybe Description
orderByDesc = 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
"sort the rows by one or more columns"
InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall a b. (a -> b) -> a -> b
$ do
Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]
maybeOrderByExps <-
(Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
-> Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]))
-> InputFieldsParser
MetadataObjId
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
-> Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
(InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]))
-> InputFieldsParser
MetadataObjId
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]))
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]))
-> InputFieldsParser
MetadataObjId
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [[AnnotatedOrderByItemG 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
orderByName Maybe Description
orderByDesc
(Parser
MetadataObjId
'Input
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])))
-> Parser
MetadataObjId
'Input
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]))
forall a b. (a -> b) -> a -> b
$ Parser
MetadataObjId
'Input
n
[[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> Parser
MetadataObjId
'Input
n
(Maybe [[AnnotatedOrderByItemG 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
MetadataObjId
'Input
n
[[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> Parser
MetadataObjId
'Input
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]))
-> Parser
MetadataObjId
'Input
n
[[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> Parser
MetadataObjId
'Input
n
(Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]])
forall a b. (a -> b) -> a -> b
$ Parser 'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)]
-> Parser
MetadataObjId
'Input
n
[[AnnotatedOrderByItemG 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 [AnnotatedOrderByItemG b (UnpreparedValue b)]
orderByParser
pure $ Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]
maybeOrderByExps Maybe [[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> ([[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnnotatedOrderByItemG b (UnpreparedValue b)]
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty ([AnnotatedOrderByItemG b (UnpreparedValue b)]
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> ([[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> [AnnotatedOrderByItemG b (UnpreparedValue b)])
-> [[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[AnnotatedOrderByItemG b (UnpreparedValue b)]]
-> [AnnotatedOrderByItemG b (UnpreparedValue b)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
tableDistinctArg ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (InputFieldsParser n (Maybe (NonEmpty (IR.AnnDistinctColumn b (IR.UnpreparedValue b)))))
tableDistinctArg :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))))
tableDistinctArg TableInfo b
tableInfo = do
NamingCase
tCase <- (SourceInfo b -> NamingCase) -> SchemaT r m NamingCase
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve ((SourceInfo b -> NamingCase) -> SchemaT r m NamingCase)
-> (SourceInfo b -> NamingCase) -> SchemaT r m NamingCase
forall a b. (a -> b) -> a -> b
$ ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> (SourceInfo b -> ResolvedSourceCustomization)
-> SourceInfo b
-> NamingCase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b
Maybe
(Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b)))
columnsEnum <- (Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExp b (UnpreparedValue b))
-> Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b)))
-> Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExp b (UnpreparedValue b)))
-> Maybe
(Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (((Column b, AnnRedactionExp b (UnpreparedValue b))
-> AnnDistinctColumn b (UnpreparedValue b))
-> Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExp b (UnpreparedValue b))
-> Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
forall a b.
(a -> b)
-> Parser MetadataObjId 'Both n a -> Parser MetadataObjId 'Both n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Column b
-> AnnRedactionExp b (UnpreparedValue b)
-> AnnDistinctColumn b (UnpreparedValue b))
-> (Column b, AnnRedactionExp b (UnpreparedValue b))
-> AnnDistinctColumn b (UnpreparedValue b)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Column b
-> AnnRedactionExp b (UnpreparedValue b)
-> AnnDistinctColumn b (UnpreparedValue b)
forall (b :: BackendType) v.
Column b -> AnnRedactionExp b v -> AnnDistinctColumn b v
IR.AnnDistinctColumn)) (Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExp b (UnpreparedValue b)))
-> Maybe
(Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExp b (UnpreparedValue b))))
-> SchemaT
r
m
(Maybe
(Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r
m
(Maybe
(Parser
MetadataObjId
'Both
n
(Column b, AnnRedactionExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe
(Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b)))
tableSelectColumnsEnum TableInfo b
tableInfo
let distinctOnName :: Name
distinctOnName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
tCase Name
Name._distinct_on
distinctOnDesc :: Maybe Description
distinctOnDesc = 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
"distinct select on columns"
InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure do
Maybe [AnnDistinctColumn b (UnpreparedValue b)]
maybeDistinctOnColumns <-
Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])
-> Maybe [AnnDistinctColumn b (UnpreparedValue b)]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
(Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])
-> Maybe [AnnDistinctColumn b (UnpreparedValue b)])
-> (Maybe (Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> Maybe (Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> Maybe [AnnDistinctColumn b (UnpreparedValue b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
(Maybe (Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> Maybe [AnnDistinctColumn b (UnpreparedValue b)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])))
-> InputFieldsParser
MetadataObjId n (Maybe [AnnDistinctColumn b (UnpreparedValue b)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe
(Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b)))
-> (Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])))
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for
Maybe
(Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b)))
columnsEnum
(Name
-> Maybe Description
-> Parser
MetadataObjId
'Both
n
(Maybe [AnnDistinctColumn b (UnpreparedValue b)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [AnnDistinctColumn 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
distinctOnName Maybe Description
distinctOnDesc (Parser
MetadataObjId
'Both
n
(Maybe [AnnDistinctColumn b (UnpreparedValue b)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)])))
-> (Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
-> Parser
MetadataObjId
'Both
n
(Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
-> InputFieldsParser
MetadataObjId
n
(Maybe (Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser
MetadataObjId 'Both n [AnnDistinctColumn b (UnpreparedValue b)]
-> Parser
MetadataObjId
'Both
n
(Maybe [AnnDistinctColumn 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
MetadataObjId 'Both n [AnnDistinctColumn b (UnpreparedValue b)]
-> Parser
MetadataObjId
'Both
n
(Maybe [AnnDistinctColumn b (UnpreparedValue b)]))
-> (Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
-> Parser
MetadataObjId 'Both n [AnnDistinctColumn b (UnpreparedValue b)])
-> Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
-> Parser
MetadataObjId
'Both
n
(Maybe [AnnDistinctColumn b (UnpreparedValue b)])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser
MetadataObjId 'Both n (AnnDistinctColumn b (UnpreparedValue b))
-> Parser
MetadataObjId 'Both n [AnnDistinctColumn 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)
pure $ Maybe [AnnDistinctColumn b (UnpreparedValue b)]
maybeDistinctOnColumns Maybe [AnnDistinctColumn b (UnpreparedValue b)]
-> ([AnnDistinctColumn b (UnpreparedValue b)]
-> Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
-> Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnnDistinctColumn b (UnpreparedValue b)]
-> Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty
tableLimitArg ::
forall n.
(MonadParse n) =>
InputFieldsParser n (Maybe Int)
tableLimitArg :: forall (n :: * -> *).
MonadParse n =>
InputFieldsParser n (Maybe Int)
tableLimitArg =
(Maybe (Maybe Int32) -> Maybe Int)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
-> InputFieldsParser MetadataObjId n (Maybe Int)
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int32 -> Int) -> Maybe Int32 -> Maybe Int
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Maybe Int32 -> Maybe Int)
-> (Maybe (Maybe Int32) -> Maybe Int32)
-> Maybe (Maybe Int32)
-> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Maybe Int32) -> Maybe Int32
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join)
(InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
-> InputFieldsParser MetadataObjId n (Maybe Int))
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
-> InputFieldsParser MetadataObjId n (Maybe Int)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (Maybe Int32)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
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
limitName Maybe Description
limitDesc
(Parser MetadataObjId 'Both n (Maybe Int32)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32)))
-> Parser MetadataObjId 'Both n (Maybe Int32)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
forall a b. (a -> b) -> a -> b
$ Parser MetadataObjId 'Both n Int32
-> Parser MetadataObjId 'Both n (Maybe Int32)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.nonNegativeInt
where
limitName :: Name
limitName = Name
Name._limit
limitDesc :: Maybe Description
limitDesc = 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
"limit the number of rows returned"
tableOffsetArg ::
forall n.
(MonadParse n) =>
InputFieldsParser n (Maybe Int64)
tableOffsetArg :: forall (n :: * -> *).
MonadParse n =>
InputFieldsParser n (Maybe Int64)
tableOffsetArg =
(Maybe (Maybe Int64) -> Maybe Int64)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
-> InputFieldsParser MetadataObjId n (Maybe Int64)
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe Int64) -> Maybe Int64
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
(InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
-> InputFieldsParser MetadataObjId n (Maybe Int64))
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
-> InputFieldsParser MetadataObjId n (Maybe Int64)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (Maybe Int64)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
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
offsetName Maybe Description
offsetDesc
(Parser MetadataObjId 'Both n (Maybe Int64)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64)))
-> Parser MetadataObjId 'Both n (Maybe Int64)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
forall a b. (a -> b) -> a -> b
$ Parser MetadataObjId 'Both n Int64
-> Parser MetadataObjId 'Both n (Maybe Int64)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser MetadataObjId 'Both n Int64
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int64
P.bigInt
where
offsetName :: Name
offsetName = Name
Name._offset
offsetDesc :: Maybe Description
offsetDesc = 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
"skip the first n rows. Use only with order_by"
tableConnectionArgs ::
forall b r m n.
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
PrimaryKeyColumns b ->
TableInfo b ->
SelPermInfo b ->
SchemaT
r
m
( InputFieldsParser
n
( SelectArgs b,
Maybe (NonEmpty (IR.ConnectionSplit b (IR.UnpreparedValue b))),
Maybe IR.ConnectionSlice
)
)
tableConnectionArgs :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
PrimaryKeyColumns b
-> TableInfo b
-> SelPermInfo b
-> SchemaT
r
m
(InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice))
tableConnectionArgs PrimaryKeyColumns b
pkeyColumns TableInfo b
tableInfo SelPermInfo b
selectPermissions = do
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser <- TableInfo b
-> SchemaT
r
m
(InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, MonadBuildSchema b r m n) =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg TableInfo b
tableInfo
InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser <- (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
appendPrimaryKeyOrderBy) (InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r
m
(InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg TableInfo b
tableInfo
InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
distinctParser <- TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))))
tableDistinctArg TableInfo b
tableInfo
let maybeFirst :: InputFieldsParser origin n (Maybe Int32)
maybeFirst = (Maybe (Maybe Int32) -> Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32))
-> InputFieldsParser origin n (Maybe Int32)
forall a b.
(a -> b)
-> InputFieldsParser origin n a -> InputFieldsParser origin n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe Int32) -> Maybe Int32
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (InputFieldsParser origin n (Maybe (Maybe Int32))
-> InputFieldsParser origin n (Maybe Int32))
-> InputFieldsParser origin n (Maybe (Maybe Int32))
-> InputFieldsParser origin n (Maybe Int32)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser origin 'Both n (Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32))
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
Name._first Maybe Description
forall a. Maybe a
Nothing (Parser origin 'Both n (Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32)))
-> Parser origin 'Both n (Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32))
forall a b. (a -> b) -> a -> b
$ Parser origin 'Both n Int32 -> Parser origin 'Both n (Maybe Int32)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser origin 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.nonNegativeInt
maybeLast :: InputFieldsParser origin n (Maybe Int32)
maybeLast = (Maybe (Maybe Int32) -> Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32))
-> InputFieldsParser origin n (Maybe Int32)
forall a b.
(a -> b)
-> InputFieldsParser origin n a -> InputFieldsParser origin n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe Int32) -> Maybe Int32
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (InputFieldsParser origin n (Maybe (Maybe Int32))
-> InputFieldsParser origin n (Maybe Int32))
-> InputFieldsParser origin n (Maybe (Maybe Int32))
-> InputFieldsParser origin n (Maybe Int32)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser origin 'Both n (Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32))
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
Name._last Maybe Description
forall a. Maybe a
Nothing (Parser origin 'Both n (Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32)))
-> Parser origin 'Both n (Maybe Int32)
-> InputFieldsParser origin n (Maybe (Maybe Int32))
forall a b. (a -> b) -> a -> b
$ Parser origin 'Both n Int32 -> Parser origin 'Both n (Maybe Int32)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser origin 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.nonNegativeInt
maybeAfter :: InputFieldsParser MetadataObjId n (Maybe ByteString)
maybeAfter = (Maybe (Maybe ByteString) -> Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe ByteString)
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe ByteString) -> Maybe ByteString
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
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
Name._after Maybe Description
forall a. Maybe a
Nothing (Parser MetadataObjId 'Both n (Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString)))
-> Parser MetadataObjId 'Both n (Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
forall a b. (a -> b) -> a -> b
$ Parser MetadataObjId 'Both n ByteString
-> Parser MetadataObjId 'Both n (Maybe ByteString)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser MetadataObjId 'Both n ByteString
forall {origin}. Parser origin 'Both n ByteString
base64Text
maybeBefore :: InputFieldsParser MetadataObjId n (Maybe ByteString)
maybeBefore = (Maybe (Maybe ByteString) -> Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe ByteString)
forall a b.
(a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe ByteString) -> Maybe ByteString
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
-> InputFieldsParser MetadataObjId n (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
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
Name._before Maybe Description
forall a. Maybe a
Nothing (Parser MetadataObjId 'Both n (Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString)))
-> Parser MetadataObjId 'Both n (Maybe ByteString)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe ByteString))
forall a b. (a -> b) -> a -> b
$ Parser MetadataObjId 'Both n ByteString
-> Parser MetadataObjId 'Both n (Maybe ByteString)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser MetadataObjId 'Both n ByteString
forall {origin}. Parser origin 'Both n ByteString
base64Text
firstAndLast :: InputFieldsParser MetadataObjId n (Maybe Int32, Maybe Int32)
firstAndLast = (,) (Maybe Int32 -> Maybe Int32 -> (Maybe Int32, Maybe Int32))
-> InputFieldsParser MetadataObjId n (Maybe Int32)
-> InputFieldsParser
MetadataObjId n (Maybe Int32 -> (Maybe Int32, Maybe Int32))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser MetadataObjId n (Maybe Int32)
forall {origin}. InputFieldsParser origin n (Maybe Int32)
maybeFirst InputFieldsParser
MetadataObjId n (Maybe Int32 -> (Maybe Int32, Maybe Int32))
-> InputFieldsParser MetadataObjId n (Maybe Int32)
-> InputFieldsParser MetadataObjId n (Maybe Int32, Maybe Int32)
forall a b.
InputFieldsParser MetadataObjId n (a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser MetadataObjId n (Maybe Int32)
forall {origin}. InputFieldsParser origin n (Maybe Int32)
maybeLast
afterBeforeAndOrderBy :: InputFieldsParser
MetadataObjId
n
(Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
afterBeforeAndOrderBy = (,,) (Maybe ByteString
-> Maybe ByteString
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> (Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> InputFieldsParser MetadataObjId n (Maybe ByteString)
-> InputFieldsParser
MetadataObjId
n
(Maybe ByteString
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> (Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser MetadataObjId n (Maybe ByteString)
maybeAfter InputFieldsParser
MetadataObjId
n
(Maybe ByteString
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> (Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> InputFieldsParser MetadataObjId n (Maybe ByteString)
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> (Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall a b.
InputFieldsParser MetadataObjId n (a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser MetadataObjId n (Maybe ByteString)
maybeBefore InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> (Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
forall a b.
InputFieldsParser MetadataObjId n (a -> b)
-> InputFieldsParser MetadataObjId n a
-> InputFieldsParser MetadataObjId n b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser
ScalarTypeParsingContext b
scalarTypeParsingContext <- forall (b :: BackendType) r (m :: * -> *).
(MonadReader r m, Has (SourceInfo b) r,
Has (ScalarTypeParsingContext b) (SourceConfig b)) =>
m (ScalarTypeParsingContext b)
askScalarTypeParsingContext @b
pure $ do
Maybe (AnnBoolExp b (UnpreparedValue b))
whereF <- InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
orderBy <- InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser
Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
distinct <- InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
distinctParser
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
split <-
InputFieldsParser
MetadataObjId
n
(Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
afterBeforeAndOrderBy InputFieldsParser
MetadataObjId
n
(Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> ((Maybe ByteString, Maybe ByteString,
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> n (Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b)))))
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))))
forall (m :: * -> *) origin a b.
Monad m =>
InputFieldsParser origin m a
-> (a -> m b) -> InputFieldsParser origin m b
`P.bindFields` \(Maybe ByteString
after, Maybe ByteString
before, Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
orderBy') -> do
Maybe (ConnectionSplitKind, ByteString)
rawSplit <- case (Maybe ByteString
after, Maybe ByteString
before) of
(Maybe ByteString
Nothing, Maybe ByteString
Nothing) -> Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString))
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (ConnectionSplitKind, ByteString)
forall a. Maybe a
Nothing
(Just ByteString
_, Just ByteString
_) -> ErrorMessage -> n (Maybe (ConnectionSplitKind, ByteString))
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
parseError ErrorMessage
"\"after\" and \"before\" are not allowed at once"
(Just ByteString
v, Maybe ByteString
Nothing) -> Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString))
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString)))
-> Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString))
forall a b. (a -> b) -> a -> b
$ (ConnectionSplitKind, ByteString)
-> Maybe (ConnectionSplitKind, ByteString)
forall a. a -> Maybe a
Just (ConnectionSplitKind
IR.CSKAfter, ByteString
v)
(Maybe ByteString
Nothing, Just ByteString
v) -> Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString))
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString)))
-> Maybe (ConnectionSplitKind, ByteString)
-> n (Maybe (ConnectionSplitKind, ByteString))
forall a b. (a -> b) -> a -> b
$ (ConnectionSplitKind, ByteString)
-> Maybe (ConnectionSplitKind, ByteString)
forall a. a -> Maybe a
Just (ConnectionSplitKind
IR.CSKBefore, ByteString
v)
Maybe (ConnectionSplitKind, ByteString)
-> ((ConnectionSplitKind, ByteString)
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b))))
-> n (Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for Maybe (ConnectionSplitKind, ByteString)
rawSplit ((ConnectionSplitKind
-> ByteString
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b))))
-> (ConnectionSplitKind, ByteString)
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (ScalarTypeParsingContext b
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> ConnectionSplitKind
-> ByteString
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
parseConnectionSplit ScalarTypeParsingContext b
scalarTypeParsingContext Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
orderBy'))
Maybe ConnectionSlice
slice <-
InputFieldsParser MetadataObjId n (Maybe Int32, Maybe Int32)
firstAndLast InputFieldsParser MetadataObjId n (Maybe Int32, Maybe Int32)
-> ((Maybe Int32, Maybe Int32) -> n (Maybe ConnectionSlice))
-> InputFieldsParser MetadataObjId n (Maybe ConnectionSlice)
forall (m :: * -> *) origin a b.
Monad m =>
InputFieldsParser origin m a
-> (a -> m b) -> InputFieldsParser origin m b
`P.bindFields` \case
(Maybe Int32
Nothing, Maybe Int32
Nothing) -> Maybe ConnectionSlice -> n (Maybe ConnectionSlice)
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ConnectionSlice
forall a. Maybe a
Nothing
(Just Int32
_, Just Int32
_) -> ErrorMessage -> n (Maybe ConnectionSlice)
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
parseError ErrorMessage
"\"first\" and \"last\" are not allowed at once"
(Just Int32
v, Maybe Int32
Nothing) -> Maybe ConnectionSlice -> n (Maybe ConnectionSlice)
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ConnectionSlice -> n (Maybe ConnectionSlice))
-> Maybe ConnectionSlice -> n (Maybe ConnectionSlice)
forall a b. (a -> b) -> a -> b
$ ConnectionSlice -> Maybe ConnectionSlice
forall a. a -> Maybe a
Just (ConnectionSlice -> Maybe ConnectionSlice)
-> ConnectionSlice -> Maybe ConnectionSlice
forall a b. (a -> b) -> a -> b
$ Int -> ConnectionSlice
IR.SliceFirst (Int -> ConnectionSlice) -> Int -> ConnectionSlice
forall a b. (a -> b) -> a -> b
$ Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
v
(Maybe Int32
Nothing, Just Int32
v) -> Maybe ConnectionSlice -> n (Maybe ConnectionSlice)
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ConnectionSlice -> n (Maybe ConnectionSlice))
-> Maybe ConnectionSlice -> n (Maybe ConnectionSlice)
forall a b. (a -> b) -> a -> b
$ ConnectionSlice -> Maybe ConnectionSlice
forall a. a -> Maybe a
Just (ConnectionSlice -> Maybe ConnectionSlice)
-> ConnectionSlice -> Maybe ConnectionSlice
forall a b. (a -> b) -> a -> b
$ Int -> ConnectionSlice
IR.SliceLast (Int -> ConnectionSlice) -> Int -> ConnectionSlice
forall a b. (a -> b) -> a -> b
$ Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int32
v
pure
( Maybe (AnnBoolExp b (UnpreparedValue b))
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> Maybe Int
-> Maybe Int64
-> Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
-> SelectArgs b
forall (b :: BackendType) v.
Maybe (AnnBoolExp b v)
-> Maybe (NonEmpty (AnnotatedOrderByItemG b v))
-> Maybe Int
-> Maybe Int64
-> Maybe (NonEmpty (AnnDistinctColumn b v))
-> SelectArgsG b v
IR.SelectArgs Maybe (AnnBoolExp b (UnpreparedValue b))
whereF Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
orderBy Maybe Int
forall a. Maybe a
Nothing Maybe Int64
forall a. Maybe a
Nothing Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
distinct,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
split,
Maybe ConnectionSlice
slice
)
where
base64Text :: Parser origin 'Both n ByteString
base64Text = Text -> ByteString
base64Decode (Text -> ByteString)
-> Parser origin 'Both n Text -> Parser origin 'Both n ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser origin 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
appendPrimaryKeyOrderBy :: NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b)) -> NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b))
appendPrimaryKeyOrderBy :: NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
appendPrimaryKeyOrderBy orderBys :: NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBys@(AnnotatedOrderByItemG b (UnpreparedValue b)
h NE.:| [AnnotatedOrderByItemG b (UnpreparedValue b)]
t) =
let orderByColumnNames :: [Column b]
orderByColumnNames =
NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBys NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> Getting
(Endo [Column b])
(NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
(Column b)
-> [Column b]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (AnnotatedOrderByItemG b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> Const
(Endo [Column b])
(NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverse ((AnnotatedOrderByItemG b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> Const
(Endo [Column b])
(NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> Getting
(Endo [Column b])
(NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
(Column b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnotatedOrderByItemG b (UnpreparedValue b)
-> AnnotatedOrderByElement b (UnpreparedValue b))
-> (AnnotatedOrderByElement b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByElement b (UnpreparedValue b)))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByItemG b (UnpreparedValue b))
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to AnnotatedOrderByItemG b (UnpreparedValue b)
-> AnnotatedOrderByElement b (UnpreparedValue b)
forall (b :: BackendType) a. OrderByItemG b a -> a
IR.obiColumn ((AnnotatedOrderByElement b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByElement b (UnpreparedValue b)))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByElement b (UnpreparedValue b)))
-> (Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByItemG b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
-> Const
(Endo [Column b])
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b)))
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByElement b (UnpreparedValue b))
forall (b :: BackendType) v (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (ColumnInfo b, AnnRedactionExp b v)
(f (ColumnInfo b, AnnRedactionExp b v))
-> p (AnnotatedOrderByElement b v)
(f (AnnotatedOrderByElement b v))
IR._AOCColumn (((ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
-> Const
(Endo [Column b])
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b)))
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByElement b (UnpreparedValue b)))
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> (ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
-> Const
(Endo [Column b])
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b)))
-> (Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Const
(Endo [Column b]) (AnnotatedOrderByElement b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b -> Const (Endo [Column b]) (ColumnInfo b))
-> (ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
-> Const
(Endo [Column b])
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
forall s t a b. Field1 s t a b => Lens s t a b
Lens
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
(ColumnInfo b)
(ColumnInfo b)
_1 ((ColumnInfo b -> Const (Endo [Column b]) (ColumnInfo b))
-> (ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
-> Const
(Endo [Column b])
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b)))
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> ColumnInfo b -> Const (Endo [Column b]) (ColumnInfo b))
-> (Column b -> Const (Endo [Column b]) (Column b))
-> (ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
-> Const
(Endo [Column b])
(ColumnInfo b, AnnRedactionExp b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b -> Column b)
-> (Column b -> Const (Endo [Column b]) (Column b))
-> ColumnInfo b
-> Const (Endo [Column b]) (ColumnInfo b)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn
pkeyOrderBys :: [AnnotatedOrderByItemG b (UnpreparedValue b)]
pkeyOrderBys = ((ColumnInfo b
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> [ColumnInfo b] -> [AnnotatedOrderByItemG b (UnpreparedValue b)])
-> [ColumnInfo b]
-> (ColumnInfo b
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> [AnnotatedOrderByItemG b (UnpreparedValue b)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ColumnInfo b
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> [ColumnInfo b] -> [AnnotatedOrderByItemG b (UnpreparedValue b)]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe (PrimaryKeyColumns b -> [ColumnInfo b]
forall a. NESeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList PrimaryKeyColumns b
pkeyColumns) ((ColumnInfo b
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> [AnnotatedOrderByItemG b (UnpreparedValue b)])
-> (ColumnInfo b
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> [AnnotatedOrderByItemG b (UnpreparedValue b)]
forall a b. (a -> b) -> a -> b
$ \ColumnInfo b
columnInfo ->
if ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo Column b -> [Column b] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Column b]
orderByColumnNames
then Maybe (AnnotatedOrderByItemG b (UnpreparedValue b))
forall a. Maybe a
Nothing
else
let redactionExp :: AnnRedactionExp b (UnpreparedValue b)
redactionExp = AnnRedactionExp b (UnpreparedValue b)
-> Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b)
forall a. a -> Maybe a -> a
fromMaybe AnnRedactionExp b (UnpreparedValue b)
forall (b :: BackendType) v. AnnRedactionExp b v
NoRedaction (Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b))
-> Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SelPermInfo b
-> Column b -> Maybe (AnnRedactionExp b (UnpreparedValue b))
forall (b :: BackendType).
Backend b =>
SelPermInfo b
-> Column b -> Maybe (AnnRedactionExpUnpreparedValue b)
getRedactionExprForColumn SelPermInfo b
selectPermissions (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo)
in AnnotatedOrderByItemG b (UnpreparedValue b)
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b))
forall a. a -> Maybe a
Just (AnnotatedOrderByItemG b (UnpreparedValue b)
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> Maybe (AnnotatedOrderByItemG b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ Maybe (BasicOrderType b)
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Maybe (NullsOrderType b)
-> AnnotatedOrderByItemG b (UnpreparedValue b)
forall (b :: BackendType) a.
Maybe (BasicOrderType b)
-> a -> Maybe (NullsOrderType b) -> OrderByItemG b a
IR.OrderByItemG Maybe (BasicOrderType b)
forall a. Maybe a
Nothing (ColumnInfo b
-> AnnRedactionExp b (UnpreparedValue b)
-> AnnotatedOrderByElement b (UnpreparedValue b)
forall (b :: BackendType) v.
ColumnInfo b -> AnnRedactionExp b v -> AnnotatedOrderByElement b v
IR.AOCColumn ColumnInfo b
columnInfo AnnRedactionExp b (UnpreparedValue b)
redactionExp) Maybe (NullsOrderType b)
forall a. Maybe a
Nothing
in AnnotatedOrderByItemG b (UnpreparedValue b)
h AnnotatedOrderByItemG b (UnpreparedValue b)
-> [AnnotatedOrderByItemG b (UnpreparedValue b)]
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
forall a. a -> [a] -> NonEmpty a
NE.:| ([AnnotatedOrderByItemG b (UnpreparedValue b)]
t [AnnotatedOrderByItemG b (UnpreparedValue b)]
-> [AnnotatedOrderByItemG b (UnpreparedValue b)]
-> [AnnotatedOrderByItemG b (UnpreparedValue b)]
forall a. Semigroup a => a -> a -> a
<> [AnnotatedOrderByItemG b (UnpreparedValue b)]
pkeyOrderBys)
parseConnectionSplit ::
ScalarTypeParsingContext b ->
Maybe (NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b))) ->
IR.ConnectionSplitKind ->
BL.ByteString ->
n (NonEmpty (IR.ConnectionSplit b (IR.UnpreparedValue b)))
parseConnectionSplit :: ScalarTypeParsingContext b
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> ConnectionSplitKind
-> ByteString
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
parseConnectionSplit ScalarTypeParsingContext b
scalarTypeParsingContext Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
maybeOrderBys ConnectionSplitKind
splitKind ByteString
cursorSplit = do
Value
cursorValue <- ByteString -> Either String Value
forall a. FromJSON a => ByteString -> Either String a
J.eitherDecode ByteString
cursorSplit Either String Value -> (String -> n Value) -> n Value
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` n Value -> String -> n Value
forall a b. a -> b -> a
const n Value
forall {a}. n a
throwInvalidCursor
case Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
maybeOrderBys of
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
Nothing -> NonEmpty (ColumnInfo b)
-> (ColumnInfo b -> n (ConnectionSplit b (UnpreparedValue b)))
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (PrimaryKeyColumns b -> NonEmpty (ColumnInfo b)
forall a. NESeq a -> NonEmpty a
nonEmptySeqToNonEmptyList PrimaryKeyColumns b
pkeyColumns)
((ColumnInfo b -> n (ConnectionSplit b (UnpreparedValue b)))
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b))))
-> (ColumnInfo b -> n (ConnectionSplit b (UnpreparedValue b)))
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ \ColumnInfo b
columnInfo -> do
let columnJsonPath :: [JSONPathElement]
columnJsonPath = [Key -> JSONPathElement
J.Key (Key -> JSONPathElement) -> Key -> JSONPathElement
forall a b. (a -> b) -> a -> b
$ Text -> Key
K.fromText (Text -> Key) -> Text -> Key
forall a b. (a -> b) -> a -> b
$ Column b -> Text
forall a. ToTxt a => a -> Text
toTxt (Column b -> Text) -> Column b -> Text
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo]
columnType :: ColumnType b
columnType = ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo
redactionExp :: AnnRedactionExp b (UnpreparedValue b)
redactionExp = AnnRedactionExp b (UnpreparedValue b)
-> Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b)
forall a. a -> Maybe a -> a
fromMaybe AnnRedactionExp b (UnpreparedValue b)
forall (b :: BackendType) v. AnnRedactionExp b v
NoRedaction (Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b))
-> Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SelPermInfo b
-> Column b -> Maybe (AnnRedactionExp b (UnpreparedValue b))
forall (b :: BackendType).
Backend b =>
SelPermInfo b
-> Column b -> Maybe (AnnRedactionExpUnpreparedValue b)
getRedactionExprForColumn SelPermInfo b
selectPermissions (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo)
Value
columnValue <-
IResult Value -> Maybe Value
forall a. IResult a -> Maybe a
iResultToMaybe ([JSONPathElement] -> Value -> IResult Value
executeJSONPath [JSONPathElement]
columnJsonPath Value
cursorValue)
Maybe Value -> n Value -> n Value
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` n Value
forall {a}. n a
throwInvalidCursor
ScalarValue b
pgValue <- Except QErr (ScalarValue b) -> n (ScalarValue b)
forall {a}. Except QErr a -> n a
liftQErr (Except QErr (ScalarValue b) -> n (ScalarValue b))
-> Except QErr (ScalarValue b) -> n (ScalarValue b)
forall a b. (a -> b) -> a -> b
$ ScalarTypeParsingContext b
-> ColumnType b -> Value -> Except QErr (ScalarValue b)
forall (m :: * -> *) (b :: BackendType).
(MonadError QErr m, Backend b) =>
ScalarTypeParsingContext b
-> ColumnType b -> Value -> m (ScalarValue b)
parseScalarValueColumnTypeWithContext ScalarTypeParsingContext b
scalarTypeParsingContext ColumnType b
columnType Value
columnValue
let unresolvedValue :: UnpreparedValue b
unresolvedValue = Provenance -> ColumnValue b -> UnpreparedValue b
forall (b :: BackendType).
Provenance -> ColumnValue b -> UnpreparedValue b
IR.UVParameter Provenance
IR.FreshVar (ColumnValue b -> UnpreparedValue b)
-> ColumnValue b -> UnpreparedValue b
forall a b. (a -> b) -> a -> b
$ ColumnType b -> ScalarValue b -> ColumnValue b
forall (b :: BackendType).
ColumnType b -> ScalarValue b -> ColumnValue b
ColumnValue ColumnType b
columnType ScalarValue b
pgValue
ConnectionSplit b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b))
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(ConnectionSplit b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b)))
-> ConnectionSplit b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ ConnectionSplitKind
-> UnpreparedValue b
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> ConnectionSplit b (UnpreparedValue b)
forall (b :: BackendType) v.
ConnectionSplitKind
-> v
-> OrderByItemG b (AnnotatedOrderByElement b v)
-> ConnectionSplit b v
IR.ConnectionSplit ConnectionSplitKind
splitKind UnpreparedValue b
unresolvedValue
(AnnotatedOrderByItemG b (UnpreparedValue b)
-> ConnectionSplit b (UnpreparedValue b))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> ConnectionSplit b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ Maybe (BasicOrderType b)
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Maybe (NullsOrderType b)
-> AnnotatedOrderByItemG b (UnpreparedValue b)
forall (b :: BackendType) a.
Maybe (BasicOrderType b)
-> a -> Maybe (NullsOrderType b) -> OrderByItemG b a
IR.OrderByItemG Maybe (BasicOrderType b)
forall a. Maybe a
Nothing (ColumnInfo b
-> AnnRedactionExp b (UnpreparedValue b)
-> AnnotatedOrderByElement b (UnpreparedValue b)
forall (b :: BackendType) v.
ColumnInfo b -> AnnRedactionExp b v -> AnnotatedOrderByElement b v
IR.AOCColumn ColumnInfo b
columnInfo AnnRedactionExp b (UnpreparedValue b)
redactionExp) Maybe (NullsOrderType b)
forall a. Maybe a
Nothing
Just NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBys ->
NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> (AnnotatedOrderByItemG b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b)))
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBys ((AnnotatedOrderByItemG b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b)))
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b))))
-> (AnnotatedOrderByItemG b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b)))
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ \AnnotatedOrderByItemG b (UnpreparedValue b)
orderBy -> do
let IR.OrderByItemG Maybe (BasicOrderType b)
orderType AnnotatedOrderByElement b (UnpreparedValue b)
annObCol Maybe (NullsOrderType b)
nullsOrder = AnnotatedOrderByItemG b (UnpreparedValue b)
orderBy
columnType :: ColumnType b
columnType = AnnotatedOrderByElement b (UnpreparedValue b) -> ColumnType b
getOrderByColumnType AnnotatedOrderByElement b (UnpreparedValue b)
annObCol
Value
orderByItemValue <-
IResult Value -> Maybe Value
forall a. IResult a -> Maybe a
iResultToMaybe ([JSONPathElement] -> Value -> IResult Value
executeJSONPath ((Text -> JSONPathElement) -> [Text] -> [JSONPathElement]
forall a b. (a -> b) -> [a] -> [b]
map (Key -> JSONPathElement
J.Key (Key -> JSONPathElement)
-> (Text -> Key) -> Text -> JSONPathElement
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Key
K.fromText) (AnnotatedOrderByElement b (UnpreparedValue b) -> [Text]
getPathFromOrderBy AnnotatedOrderByElement b (UnpreparedValue b)
annObCol)) Value
cursorValue)
Maybe Value -> n Value -> n Value
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` n Value
forall {a}. n a
throwInvalidCursor
ScalarValue b
pgValue <- Except QErr (ScalarValue b) -> n (ScalarValue b)
forall {a}. Except QErr a -> n a
liftQErr (Except QErr (ScalarValue b) -> n (ScalarValue b))
-> Except QErr (ScalarValue b) -> n (ScalarValue b)
forall a b. (a -> b) -> a -> b
$ ScalarTypeParsingContext b
-> ColumnType b -> Value -> Except QErr (ScalarValue b)
forall (m :: * -> *) (b :: BackendType).
(MonadError QErr m, Backend b) =>
ScalarTypeParsingContext b
-> ColumnType b -> Value -> m (ScalarValue b)
parseScalarValueColumnTypeWithContext ScalarTypeParsingContext b
scalarTypeParsingContext ColumnType b
columnType Value
orderByItemValue
let unresolvedValue :: UnpreparedValue b
unresolvedValue = Provenance -> ColumnValue b -> UnpreparedValue b
forall (b :: BackendType).
Provenance -> ColumnValue b -> UnpreparedValue b
IR.UVParameter Provenance
IR.FreshVar (ColumnValue b -> UnpreparedValue b)
-> ColumnValue b -> UnpreparedValue b
forall a b. (a -> b) -> a -> b
$ ColumnType b -> ScalarValue b -> ColumnValue b
forall (b :: BackendType).
ColumnType b -> ScalarValue b -> ColumnValue b
ColumnValue ColumnType b
columnType ScalarValue b
pgValue
ConnectionSplit b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b))
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(ConnectionSplit b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b)))
-> ConnectionSplit b (UnpreparedValue b)
-> n (ConnectionSplit b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ ConnectionSplitKind
-> UnpreparedValue b
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> ConnectionSplit b (UnpreparedValue b)
forall (b :: BackendType) v.
ConnectionSplitKind
-> v
-> OrderByItemG b (AnnotatedOrderByElement b v)
-> ConnectionSplit b v
IR.ConnectionSplit ConnectionSplitKind
splitKind UnpreparedValue b
unresolvedValue
(AnnotatedOrderByItemG b (UnpreparedValue b)
-> ConnectionSplit b (UnpreparedValue b))
-> AnnotatedOrderByItemG b (UnpreparedValue b)
-> ConnectionSplit b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ Maybe (BasicOrderType b)
-> AnnotatedOrderByElement b (UnpreparedValue b)
-> Maybe (NullsOrderType b)
-> AnnotatedOrderByItemG b (UnpreparedValue b)
forall (b :: BackendType) a.
Maybe (BasicOrderType b)
-> a -> Maybe (NullsOrderType b) -> OrderByItemG b a
IR.OrderByItemG Maybe (BasicOrderType b)
orderType AnnotatedOrderByElement b (UnpreparedValue b)
annObCol Maybe (NullsOrderType b)
nullsOrder
where
throwInvalidCursor :: n a
throwInvalidCursor = ErrorMessage -> n a
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
parseError ErrorMessage
"the \"after\" or \"before\" cursor is invalid"
liftQErr :: Except QErr a -> n a
liftQErr = (QErr -> n a) -> (a -> n a) -> Either QErr a -> n a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ErrorMessage -> n a
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
parseError (ErrorMessage -> n a) -> (QErr -> ErrorMessage) -> QErr -> n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ErrorMessage
toErrorMessage (Text -> ErrorMessage) -> (QErr -> Text) -> QErr -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QErr -> Text
qeError) a -> n a
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either QErr a -> n a)
-> (Except QErr a -> Either QErr a) -> Except QErr a -> n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except QErr a -> Either QErr a
forall e a. Except e a -> Either e a
runExcept
mkAggregateOrderByPath :: AnnotatedAggregateOrderBy b v -> [Text]
mkAggregateOrderByPath = \case
AnnotatedAggregateOrderBy b v
IR.AAOCount -> [Text
"count"]
IR.AAOOp IR.AggregateOrderByColumn {Text
ColumnType b
ColumnInfo b
AnnRedactionExp b v
_aobcAggregateFunctionName :: Text
_aobcAggregateFunctionReturnType :: ColumnType b
_aobcColumn :: ColumnInfo b
_aobcRedactionExpression :: AnnRedactionExp b v
$sel:_aobcAggregateFunctionName:AggregateOrderByColumn :: forall (b :: BackendType) v. AggregateOrderByColumn b v -> Text
$sel:_aobcAggregateFunctionReturnType:AggregateOrderByColumn :: forall (b :: BackendType) v.
AggregateOrderByColumn b v -> ColumnType b
$sel:_aobcColumn:AggregateOrderByColumn :: forall (b :: BackendType) v.
AggregateOrderByColumn b v -> ColumnInfo b
$sel:_aobcRedactionExpression:AggregateOrderByColumn :: forall (b :: BackendType) v.
AggregateOrderByColumn b v -> AnnRedactionExp b v
..} -> [Text
_aobcAggregateFunctionName, Column b -> Text
forall a. ToTxt a => a -> Text
toTxt (Column b -> Text) -> Column b -> Text
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
_aobcColumn]
getPathFromOrderBy :: AnnotatedOrderByElement b (UnpreparedValue b) -> [Text]
getPathFromOrderBy = \case
IR.AOCColumn ColumnInfo b
columnInfo AnnRedactionExp b (UnpreparedValue b)
_redactionExp ->
let pathElement :: Text
pathElement = Column b -> Text
forall a. ToTxt a => a -> Text
toTxt (Column b -> Text) -> Column b -> Text
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo
in [Text
pathElement]
IR.AOCObjectRelation RelInfo b
relInfo AnnBoolExp b (UnpreparedValue b)
_ AnnotatedOrderByElement b (UnpreparedValue b)
obCol ->
let pathElement :: Text
pathElement = RelName -> Text
relNameToTxt (RelName -> Text) -> RelName -> Text
forall a b. (a -> b) -> a -> b
$ RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
relInfo
in Text
pathElement Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: AnnotatedOrderByElement b (UnpreparedValue b) -> [Text]
getPathFromOrderBy AnnotatedOrderByElement b (UnpreparedValue b)
obCol
IR.AOCArrayAggregation RelInfo b
relInfo AnnBoolExp b (UnpreparedValue b)
_ AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb ->
let fieldName :: Text
fieldName = RelName -> Text
relNameToTxt (RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
relInfo) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_aggregate"
in Text
fieldName Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: AnnotatedAggregateOrderBy b (UnpreparedValue b) -> [Text]
forall {v}. AnnotatedAggregateOrderBy b v -> [Text]
mkAggregateOrderByPath AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb
IR.AOCComputedField ComputedFieldOrderBy b (UnpreparedValue b)
cfob ->
let fieldNameText :: Text
fieldNameText = ComputedFieldName -> Text
computedFieldNameToText (ComputedFieldName -> Text) -> ComputedFieldName -> Text
forall a b. (a -> b) -> a -> b
$ ComputedFieldOrderBy b (UnpreparedValue b) -> ComputedFieldName
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> ComputedFieldName
IR._cfobName ComputedFieldOrderBy b (UnpreparedValue b)
cfob
in case ComputedFieldOrderBy b (UnpreparedValue b)
-> ComputedFieldOrderByElement b (UnpreparedValue b)
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> ComputedFieldOrderByElement b v
IR._cfobOrderByElement ComputedFieldOrderBy b (UnpreparedValue b)
cfob of
IR.CFOBEScalar ScalarType b
_ AnnRedactionExp b (UnpreparedValue b)
_redactionExp -> [Text
fieldNameText]
IR.CFOBETableAggregation TableName b
_ AnnBoolExp b (UnpreparedValue b)
_ AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb ->
(Text
fieldNameText Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_aggregate") Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: AnnotatedAggregateOrderBy b (UnpreparedValue b) -> [Text]
forall {v}. AnnotatedAggregateOrderBy b v -> [Text]
mkAggregateOrderByPath AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb
getOrderByColumnType :: AnnotatedOrderByElement b (UnpreparedValue b) -> ColumnType b
getOrderByColumnType = \case
IR.AOCColumn ColumnInfo b
columnInfo AnnRedactionExp b (UnpreparedValue b)
_redactionExp -> ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo
IR.AOCObjectRelation RelInfo b
_ AnnBoolExp b (UnpreparedValue b)
_ AnnotatedOrderByElement b (UnpreparedValue b)
obCol -> AnnotatedOrderByElement b (UnpreparedValue b) -> ColumnType b
getOrderByColumnType AnnotatedOrderByElement b (UnpreparedValue b)
obCol
IR.AOCArrayAggregation RelInfo b
_ AnnBoolExp b (UnpreparedValue b)
_ AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb -> AnnotatedAggregateOrderBy b (UnpreparedValue b) -> ColumnType b
aggregateOrderByColumnType AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb
IR.AOCComputedField ComputedFieldOrderBy b (UnpreparedValue b)
cfob ->
case ComputedFieldOrderBy b (UnpreparedValue b)
-> ComputedFieldOrderByElement b (UnpreparedValue b)
forall (b :: BackendType) v.
ComputedFieldOrderBy b v -> ComputedFieldOrderByElement b v
IR._cfobOrderByElement ComputedFieldOrderBy b (UnpreparedValue b)
cfob of
IR.CFOBEScalar ScalarType b
scalarType AnnRedactionExp b (UnpreparedValue b)
_redactionExp -> ScalarType b -> ColumnType b
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType b
scalarType
IR.CFOBETableAggregation TableName b
_ AnnBoolExp b (UnpreparedValue b)
_ AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb -> AnnotatedAggregateOrderBy b (UnpreparedValue b) -> ColumnType b
aggregateOrderByColumnType AnnotatedAggregateOrderBy b (UnpreparedValue b)
aggOb
where
aggregateOrderByColumnType :: AnnotatedAggregateOrderBy b (UnpreparedValue b) -> ColumnType b
aggregateOrderByColumnType = \case
AnnotatedAggregateOrderBy b (UnpreparedValue b)
IR.AAOCount -> ScalarType b -> ColumnType b
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar (forall (b :: BackendType). BackendSchema b => ScalarType b
aggregateOrderByCountType @b)
IR.AAOOp IR.AggregateOrderByColumn {Text
ColumnType b
ColumnInfo b
AnnRedactionExp b (UnpreparedValue b)
$sel:_aobcAggregateFunctionName:AggregateOrderByColumn :: forall (b :: BackendType) v. AggregateOrderByColumn b v -> Text
$sel:_aobcAggregateFunctionReturnType:AggregateOrderByColumn :: forall (b :: BackendType) v.
AggregateOrderByColumn b v -> ColumnType b
$sel:_aobcColumn:AggregateOrderByColumn :: forall (b :: BackendType) v.
AggregateOrderByColumn b v -> ColumnInfo b
$sel:_aobcRedactionExpression:AggregateOrderByColumn :: forall (b :: BackendType) v.
AggregateOrderByColumn b v -> AnnRedactionExp b v
_aobcAggregateFunctionName :: Text
_aobcAggregateFunctionReturnType :: ColumnType b
_aobcColumn :: ColumnInfo b
_aobcRedactionExpression :: AnnRedactionExp b (UnpreparedValue b)
..} -> ColumnType b
_aobcAggregateFunctionReturnType
tableAggregationFields ::
forall b r m n.
(MonadBuildSchema b r m n) =>
TableInfo b ->
SchemaT r m (Parser 'Output n (IR.AggregateFields b (IR.UnpreparedValue b)))
tableAggregationFields :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
tableAggregationFields TableInfo b
tableInfo = 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 sourceName :: SourceName
sourceName = SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
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 :: MkTypename
mkTypename = ResolvedSourceCustomization -> MkTypename
_rscTypeNames ResolvedSourceCustomization
customization
Name
-> (SourceName, TableName b)
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
-> SchemaT
r m (Parser 'Output n (AggregateFields 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 'tableAggregationFields (SourceName
sourceName, TableName b
tableName) do
GQLNameIdentifier
tableGQLName <- TableInfo b -> SchemaT r m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
[(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
allScalarColumns <- ((StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Maybe (ColumnInfo b, AnnRedactionExpUnpreparedValue b))
-> [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe (\(StructuredColumnInfo b
column, AnnRedactionExpUnpreparedValue b
redactionExp) -> StructuredColumnInfo b
column StructuredColumnInfo b
-> Getting
(First (ColumnInfo b)) (StructuredColumnInfo b) (ColumnInfo b)
-> Maybe (ColumnInfo b)
forall s a. s -> Getting (First a) s a -> Maybe a
^? Getting
(First (ColumnInfo b)) (StructuredColumnInfo b) (ColumnInfo b)
forall (b :: BackendType) (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (ColumnInfo b) (f (ColumnInfo b))
-> p (StructuredColumnInfo b) (f (StructuredColumnInfo b))
_SCIScalarColumn Maybe (ColumnInfo b)
-> (ColumnInfo b
-> (ColumnInfo b, AnnRedactionExpUnpreparedValue b))
-> Maybe (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (,AnnRedactionExpUnpreparedValue b
redactionExp)) ([(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)])
-> SchemaT
r m [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT r m [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b
-> SchemaT
r m [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
forall (b :: BackendType) r (m :: * -> *).
(Backend b, MonadError QErr m, MonadReader r m,
Has SchemaContext r, Has (SourceInfo b) r) =>
TableInfo b
-> m [(StructuredColumnInfo b, AnnRedactionExpUnpreparedValue b)]
tableSelectColumns TableInfo b
tableInfo
[ComputedFieldInfo b]
allComputedFields <-
if forall (b :: BackendType). Backend b => Bool
supportsAggregateComputedFields @b
then TableInfo b -> SchemaT r m [ComputedFieldInfo b]
forall (b :: BackendType) r (m :: * -> *).
(Backend b, MonadError QErr m, MonadReader r m,
Has SchemaContext r, Has (SourceInfo b) r) =>
TableInfo b -> m [ComputedFieldInfo b]
tableSelectComputedFields TableInfo b
tableInfo
else [ComputedFieldInfo b] -> SchemaT r m [ComputedFieldInfo b]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
let numericColumns :: [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
numericColumns = ((ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> Bool)
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
forall a. (a -> Bool) -> [a] -> [a]
filter (ColumnInfo b -> Bool
forall (b :: BackendType). Backend b => ColumnInfo b -> Bool
isNumCol (ColumnInfo b -> Bool)
-> ((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ColumnInfo b)
-> (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> ColumnInfo b
forall a b. (a, b) -> a
fst) [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
allScalarColumns
numericComputedFields :: [ComputedFieldInfo b]
numericComputedFields = [ComputedFieldInfo b] -> [ComputedFieldInfo b]
forall (b :: BackendType).
Backend b =>
[ComputedFieldInfo b] -> [ComputedFieldInfo b]
onlyNumComputedFields [ComputedFieldInfo b]
allComputedFields
comparableColumns :: [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
comparableColumns = ((ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> Bool)
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
forall a. (a -> Bool) -> [a] -> [a]
filter (ColumnInfo b -> Bool
forall (b :: BackendType). Backend b => ColumnInfo b -> Bool
isComparableCol (ColumnInfo b -> Bool)
-> ((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ColumnInfo b)
-> (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> ColumnInfo b
forall a b. (a, b) -> a
fst) [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
allScalarColumns
comparableComputedFields :: [ComputedFieldInfo b]
comparableComputedFields = [ComputedFieldInfo b] -> [ComputedFieldInfo b]
forall (b :: BackendType).
Backend b =>
[ComputedFieldInfo b] -> [ComputedFieldInfo b]
onlyComparableComputedFields [ComputedFieldInfo b]
allComputedFields
customOperatorsAndColumns :: [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
customOperatorsAndColumns =
HashMap
Name
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
-> [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
forall k v. HashMap k v -> [(k, v)]
HashMap.toList (HashMap
Name
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
-> [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))])
-> HashMap
Name
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
-> [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
forall a b. (a -> b) -> a -> b
$ (HashMap (ScalarType b) (ScalarType b)
-> Maybe
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)))
-> HashMap Name (HashMap (ScalarType b) (ScalarType b))
-> HashMap
Name
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
forall v1 v2 k. (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
HashMap.mapMaybe ([(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> HashMap (ScalarType b) (ScalarType b)
-> Maybe
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
getCustomAggOpsColumns [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
allScalarColumns) (HashMap Name (HashMap (ScalarType b) (ScalarType b))
-> HashMap
Name
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)))
-> HashMap Name (HashMap (ScalarType b) (ScalarType b))
-> HashMap
Name
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
Backend b =>
SourceConfig b
-> HashMap Name (HashMap (ScalarType b) (ScalarType b))
getCustomAggregateOperators @b (SourceInfo b -> SourceConfig b
forall (b :: BackendType). SourceInfo b -> SourceConfig b
_siConfiguration SourceInfo b
sourceInfo)
description :: Description
description = Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"aggregate fields of " Text -> TableName b -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
selectName :: Name
selectName = MkTypename -> Name -> Name
runMkTypename MkTypename
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
mkTableAggregateFieldTypeName GQLNameIdentifier
tableGQLName
FieldParser n (AggregateField b (UnpreparedValue b))
count <- SchemaT r m (FieldParser n (AggregateField b (UnpreparedValue b)))
countField
HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
nonCountComputedFieldsMap <-
([[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
forall a b. (a -> b) -> SchemaT r m a -> SchemaT r m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))])
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k (t :: * -> *) v.
(Hashable k, Foldable t) =>
(v -> v -> v) -> t (HashMap k v) -> HashMap k v
HashMap.unionsWith [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
forall a. [a] -> [a] -> [a]
(++) ([HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
-> ([[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
-> [[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat)
(SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
forall a b. (a -> b) -> a -> b
$ [SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (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
([SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]])
-> [SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
forall a b. (a -> b) -> a -> b
$ [Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])]
-> [SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[
if [ComputedFieldInfo b] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ComputedFieldInfo b]
numericComputedFields
then Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. Maybe a
Nothing
else SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. a -> Maybe a
Just
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a b. (a -> b) -> a -> b
$ [GQLNameIdentifier]
-> (GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [GQLNameIdentifier]
numericAggOperators
((GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
-> (GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall a b. (a -> b) -> a -> b
$ \GQLNameIdentifier
operator -> do
[FieldParser n (SelectionField b (UnpreparedValue b))]
numFields <- TableName b
-> [ComputedFieldInfo b]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
mkColumnAggComputedFields TableName b
tableName [ComputedFieldInfo b]
numericComputedFields
pure $ GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton GQLNameIdentifier
operator [FieldParser n (SelectionField b (UnpreparedValue b))]
numFields,
if [ComputedFieldInfo b] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ComputedFieldInfo b]
comparableComputedFields
then Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. Maybe a
Nothing
else SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. a -> Maybe a
Just
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a b. (a -> b) -> a -> b
$ [GQLNameIdentifier]
-> (GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [GQLNameIdentifier]
comparisonAggOperators
((GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
-> (GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall a b. (a -> b) -> a -> b
$ \GQLNameIdentifier
operator -> do
[FieldParser n (SelectionField b (UnpreparedValue b))]
comparableFields <- TableName b
-> [ComputedFieldInfo b]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
mkColumnAggComputedFields TableName b
tableName [ComputedFieldInfo b]
comparableComputedFields
pure $ GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton GQLNameIdentifier
operator [FieldParser n (SelectionField b (UnpreparedValue b))]
comparableFields
]
HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
nonCountFieldsMap <-
([[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
forall a b. (a -> b) -> SchemaT r m a -> SchemaT r m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (([FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))])
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k (t :: * -> *) v.
(Hashable k, Foldable t) =>
(v -> v -> v) -> t (HashMap k v) -> HashMap k v
HashMap.unionsWith [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
forall a. [a] -> [a] -> [a]
(++) ([HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
-> ([[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
-> [[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat)
(SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
forall a b. (a -> b) -> a -> b
$ [SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (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
([SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]])
-> [SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
-> SchemaT
r
m
[[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
forall a b. (a -> b) -> a -> b
$ [Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])]
-> [SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[
if [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
numericColumns
then Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. Maybe a
Nothing
else SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. a -> Maybe a
Just
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a b. (a -> b) -> a -> b
$ [GQLNameIdentifier]
-> (GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [GQLNameIdentifier]
numericAggOperators
((GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
-> (GQLNameIdentifier
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall a b. (a -> b) -> a -> b
$ \GQLNameIdentifier
operator -> do
[FieldParser n (SelectionField b (UnpreparedValue b))]
numFields <- GQLNameIdentifier
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
mkNumericAggFields GQLNameIdentifier
operator [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
numericColumns
pure $ GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton GQLNameIdentifier
operator [FieldParser n (SelectionField b (UnpreparedValue b))]
numFields,
if [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
comparableColumns
then Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. Maybe a
Nothing
else SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. a -> Maybe a
Just (SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a b. (a -> b) -> a -> b
$ do
[FieldParser n (SelectionField b (UnpreparedValue b))]
comparableFields <- ((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkColumnAggField [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
comparableColumns
pure
$ [GQLNameIdentifier]
comparisonAggOperators
[GQLNameIdentifier]
-> ([GQLNameIdentifier]
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall a b. a -> (a -> b) -> b
& (GQLNameIdentifier
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))])
-> [GQLNameIdentifier]
-> [HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall a b. (a -> b) -> [a] -> [b]
map \GQLNameIdentifier
operator ->
GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton GQLNameIdentifier
operator [FieldParser n (SelectionField b (UnpreparedValue b))]
comparableFields,
if [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
-> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
customOperatorsAndColumns
then Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. Maybe a
Nothing
else SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a. a -> Maybe a
Just
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
-> Maybe
(SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]])
forall a b. (a -> b) -> a -> b
$ [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
-> ((Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
-> SchemaT
r
m
(HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]))
-> SchemaT
r
m
[HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [(Name,
NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))]
customOperatorsAndColumns \(Name
operator, NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
columnTypes) -> do
[FieldParser n (SelectionField b (UnpreparedValue b))]
customFields <- (((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> [((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b)]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ScalarType b
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> ((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ScalarType b
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkNullableScalarTypeAggField) (NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
-> [((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b)]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
columnTypes)
pure $ GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k v. Hashable k => k -> v -> HashMap k v
HashMap.singleton (Name -> GQLNameIdentifier
C.fromCustomName Name
operator) [FieldParser n (SelectionField b (UnpreparedValue b))]
customFields
]
let nonCountFields :: HashMap
GQLNameIdentifier
(FieldParser n (AggregateField b (UnpreparedValue b)))
nonCountFields =
(GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> FieldParser n (AggregateField b (UnpreparedValue b)))
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
(FieldParser n (AggregateField b (UnpreparedValue b)))
forall k v1 v2. (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
HashMap.mapWithKey
( \GQLNameIdentifier
operator [FieldParser n (SelectionField b (UnpreparedValue b))]
fields -> MkTypename
-> GQLNameIdentifier
-> NamingCase
-> GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> FieldParser n (AggregateField b (UnpreparedValue b))
parseAggOperator MkTypename
mkTypename GQLNameIdentifier
operator NamingCase
tCase GQLNameIdentifier
tableGQLName [FieldParser n (SelectionField b (UnpreparedValue b))]
fields
)
(([FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))])
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
-> HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HashMap.unionWith [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
forall a. [a] -> [a] -> [a]
(++) HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
nonCountFieldsMap HashMap
GQLNameIdentifier
[FieldParser n (SelectionField b (UnpreparedValue b))]
nonCountComputedFieldsMap)
aggregateFields :: [FieldParser n (IR.AggregateField b (IR.UnpreparedValue b))]
aggregateFields :: [FieldParser n (AggregateField b (UnpreparedValue b))]
aggregateFields = FieldParser n (AggregateField b (UnpreparedValue b))
count FieldParser n (AggregateField b (UnpreparedValue b))
-> [FieldParser n (AggregateField b (UnpreparedValue b))]
-> [FieldParser n (AggregateField b (UnpreparedValue b))]
forall a. a -> [a] -> [a]
: HashMap
GQLNameIdentifier
(FieldParser n (AggregateField b (UnpreparedValue b)))
-> [FieldParser n (AggregateField b (UnpreparedValue b))]
forall k v. HashMap k v -> [v]
HashMap.elems HashMap
GQLNameIdentifier
(FieldParser n (AggregateField b (UnpreparedValue b)))
nonCountFields
Parser 'Output n (AggregateFields b (UnpreparedValue b))
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Parser 'Output n (AggregateFields b (UnpreparedValue b))
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b))))
-> Parser 'Output n (AggregateFields b (UnpreparedValue b))
-> SchemaT
r m (Parser 'Output n (AggregateFields b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser n (AggregateField b (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name (ParsedSelection (AggregateField b (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
selectName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
description) [FieldParser n (AggregateField b (UnpreparedValue b))]
aggregateFields
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name (ParsedSelection (AggregateField b (UnpreparedValue b))))
-> (InsOrdHashMap
Name (ParsedSelection (AggregateField b (UnpreparedValue b)))
-> AggregateFields b (UnpreparedValue b))
-> Parser 'Output n (AggregateFields b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> AggregateField b (UnpreparedValue b))
-> InsOrdHashMap
Name (ParsedSelection (AggregateField b (UnpreparedValue b)))
-> AggregateFields b (UnpreparedValue b)
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> AggregateField b (UnpreparedValue b)
forall (b :: BackendType) v. Text -> AggregateField b v
IR.AFExp
where
getCustomAggOpsColumns :: [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)] -> HashMap (ScalarType b) (ScalarType b) -> Maybe (NonEmpty ((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
getCustomAggOpsColumns :: [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> HashMap (ScalarType b) (ScalarType b)
-> Maybe
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
getCustomAggOpsColumns [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
columnInfos HashMap (ScalarType b) (ScalarType b)
typeMap =
[(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
columnInfos
[(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> ([(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b)])
-> [((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b)]
forall a b. a -> (a -> b) -> b
& ((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> Maybe
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> [((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b)]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe
( \(ci :: ColumnInfo b
ci@ColumnInfo {Bool
Int
Maybe Description
Name
Column b
ColumnType b
ColumnMutability
ciColumn :: forall (b :: BackendType). ColumnInfo b -> Column b
ciType :: forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciIsNullable :: forall (b :: BackendType). ColumnInfo b -> Bool
ciName :: forall (b :: BackendType). ColumnInfo b -> Name
ciDescription :: forall (b :: BackendType). ColumnInfo b -> Maybe Description
ciColumn :: Column b
ciName :: Name
ciPosition :: Int
ciType :: ColumnType b
ciIsNullable :: Bool
ciDescription :: Maybe Description
ciMutability :: ColumnMutability
ciPosition :: forall (b :: BackendType). ColumnInfo b -> Int
ciMutability :: forall (b :: BackendType). ColumnInfo b -> ColumnMutability
..}, AnnRedactionExpUnpreparedValue b
redactionExp) ->
case ColumnType b
ciType of
ColumnEnumReference EnumReference b
_ -> Maybe
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
forall a. Maybe a
Nothing
ColumnScalar ScalarType b
scalarType ->
((ColumnInfo b
ci, AnnRedactionExpUnpreparedValue b
redactionExp),) (ScalarType b
-> ((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b))
-> Maybe (ScalarType b)
-> Maybe
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScalarType b
-> HashMap (ScalarType b) (ScalarType b) -> Maybe (ScalarType b)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup ScalarType b
scalarType HashMap (ScalarType b) (ScalarType b)
typeMap
)
[((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)]
-> ([((ColumnInfo b, AnnRedactionExpUnpreparedValue b),
ScalarType b)]
-> Maybe
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)))
-> Maybe
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
forall a b. a -> (a -> b) -> b
& [((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b)]
-> Maybe
(NonEmpty
((ColumnInfo b, AnnRedactionExpUnpreparedValue b), ScalarType b))
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty
mkColumnAggComputedFields :: TableName b -> [ComputedFieldInfo b] -> SchemaT r m [FieldParser n (IR.SelectionField b (IR.UnpreparedValue b))]
mkColumnAggComputedFields :: TableName b
-> [ComputedFieldInfo b]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
mkColumnAggComputedFields TableName b
tableName [ComputedFieldInfo b]
computedFieldInfos =
(ComputedFieldInfo b
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))))
-> [ComputedFieldInfo b]
-> SchemaT
r m [Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (TableName b
-> ComputedFieldInfo b
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
mkColumnAggComputedField TableName b
tableName) [ComputedFieldInfo b]
computedFieldInfos SchemaT
r m [Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))]
-> ([Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))])
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> [Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))]
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
mkColumnAggComputedField :: TableName b -> ComputedFieldInfo b -> SchemaT r m (Maybe (FieldParser n (IR.SelectionField b (IR.UnpreparedValue b))))
mkColumnAggComputedField :: TableName b
-> ComputedFieldInfo b
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
mkColumnAggComputedField TableName b
tableName ComputedFieldInfo b
computedFieldInfo = do
let annotatedFieldToSelectionField :: AnnotatedField b -> n (IR.SelectionField b (IR.UnpreparedValue b))
annotatedFieldToSelectionField :: AnnotatedField b -> n (SelectionField b (UnpreparedValue b))
annotatedFieldToSelectionField = \case
IR.AFComputedField XComputedField b
_ ComputedFieldName
computedFieldName (IR.CFSScalar ComputedFieldScalarSelect b (UnpreparedValue b)
computedFieldScalarSelect) ->
SelectionField b (UnpreparedValue b)
-> n (SelectionField b (UnpreparedValue b))
forall a. a -> n a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SelectionField b (UnpreparedValue b)
-> n (SelectionField b (UnpreparedValue b)))
-> SelectionField b (UnpreparedValue b)
-> n (SelectionField b (UnpreparedValue b))
forall a b. (a -> b) -> a -> b
$ ComputedFieldName
-> ComputedFieldScalarSelect b (UnpreparedValue b)
-> SelectionField b (UnpreparedValue b)
forall (b :: BackendType) v.
ComputedFieldName
-> ComputedFieldScalarSelect b v -> SelectionField b v
IR.SFComputedField ComputedFieldName
computedFieldName ComputedFieldScalarSelect b (UnpreparedValue b)
computedFieldScalarSelect
AnnotatedField b
_ -> ErrorMessage -> n (SelectionField b (UnpreparedValue b))
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
parseError ErrorMessage
"Only computed fields that return scalar types are supported"
ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
computedField ComputedFieldInfo b
computedFieldInfo TableName b
tableName TableInfo b
tableInfo
SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
-> (Maybe (FieldParser n (AnnotatedField b))
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))))
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
forall a b. SchemaT r m a -> (a -> SchemaT r m b) -> SchemaT r m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
(Just FieldParser n (AnnotatedField b)
fieldParser) -> (Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))))
-> (FieldParser n (SelectionField b (UnpreparedValue b))
-> Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
-> FieldParser n (SelectionField b (UnpreparedValue b))
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldParser n (SelectionField b (UnpreparedValue b))
-> Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))
forall a. a -> Maybe a
Just) (FieldParser n (AnnotatedField b)
fieldParser FieldParser n (AnnotatedField b)
-> (AnnotatedField b -> n (SelectionField b (UnpreparedValue b)))
-> FieldParser n (SelectionField b (UnpreparedValue b))
forall (m :: * -> *) origin a b.
Monad m =>
FieldParser origin m a -> (a -> m b) -> FieldParser origin m b
`P.bindField` AnnotatedField b -> n (SelectionField b (UnpreparedValue b))
annotatedFieldToSelectionField)
Maybe (FieldParser n (AnnotatedField b))
Nothing -> Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))
-> SchemaT
r m (Maybe (FieldParser n (SelectionField b (UnpreparedValue b))))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (FieldParser n (SelectionField b (UnpreparedValue b)))
forall a. Maybe a
Nothing
mkNumericAggFields :: GQLNameIdentifier -> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)] -> SchemaT r m [FieldParser n (IR.SelectionField b (IR.UnpreparedValue b))]
mkNumericAggFields :: GQLNameIdentifier
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
mkNumericAggFields GQLNameIdentifier
name
| (GQLNameIdentifier -> Name
C.toSnakeG GQLNameIdentifier
name) Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
Name._sum = ((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkColumnAggField
| Bool
otherwise = ((ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> [(ColumnInfo b, AnnRedactionExpUnpreparedValue b)]
-> SchemaT
r m [FieldParser n (SelectionField b (UnpreparedValue b))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse \(ColumnInfo b
columnInfo, AnnRedactionExpUnpreparedValue b
redactionExp) ->
Name
-> (Text, ColumnInfo b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
-> SchemaT
r m (FieldParser n (SelectionField 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 'tableAggregationFields (Text
"mkNumericAggFields" :: Text, ColumnInfo b
columnInfo)
(SchemaT r m (FieldParser n (SelectionField b (UnpreparedValue b)))
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$
FieldParser n (SelectionField b (UnpreparedValue b))
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(FieldParser n (SelectionField b (UnpreparedValue b))
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b))))
-> FieldParser n (SelectionField b (UnpreparedValue b))
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$! do
let !cfcol :: SelectionField b (UnpreparedValue b)
cfcol = Column b
-> ColumnType b
-> AnnRedactionExpUnpreparedValue b
-> SelectionField b (UnpreparedValue b)
forall (b :: BackendType) v.
Column b
-> ColumnType b -> AnnRedactionExp b v -> SelectionField b v
IR.SFCol (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo) (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) AnnRedactionExpUnpreparedValue b
redactionExp
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (Maybe Double)
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
(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 MetadataObjId 'Both n Double
-> Parser MetadataObjId 'Both n (Maybe Double)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable Parser MetadataObjId 'Both n Double
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Double
P.float)
FieldParser MetadataObjId n ()
-> SelectionField b (UnpreparedValue b)
-> FieldParser n (SelectionField b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SelectionField b (UnpreparedValue b)
cfcol
mkColumnAggField :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> SchemaT r m (FieldParser n (IR.SelectionField b (IR.UnpreparedValue b)))
mkColumnAggField :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkColumnAggField columnAndRedactionExp :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
columnAndRedactionExp@(ColumnInfo b
columnInfo, AnnRedactionExpUnpreparedValue b
_redactionExp) =
(ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ColumnType b
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkColumnAggField' (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
columnAndRedactionExp (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo)
mkColumnAggField' :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> ColumnType b -> SchemaT r m (FieldParser n (IR.SelectionField b (IR.UnpreparedValue b)))
mkColumnAggField' :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ColumnType b
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkColumnAggField' (ColumnInfo b
columnInfo, AnnRedactionExpUnpreparedValue b
redactionExp) ColumnType b
resultType = do
Parser 'Both n (ValueWithOrigin (ColumnValue b))
field <- ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser ColumnType b
resultType (Bool -> Nullability
G.Nullability Bool
True)
pure
$ Name
-> Maybe Description
-> Parser 'Both n (ValueWithOrigin (ColumnValue b))
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_
(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
FieldParser MetadataObjId n ()
-> SelectionField b (UnpreparedValue b)
-> FieldParser n (SelectionField b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Column b
-> ColumnType b
-> AnnRedactionExpUnpreparedValue b
-> SelectionField b (UnpreparedValue b)
forall (b :: BackendType) v.
Column b
-> ColumnType b -> AnnRedactionExp b v -> SelectionField b v
IR.SFCol (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo) (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) AnnRedactionExpUnpreparedValue b
redactionExp
mkNullableScalarTypeAggField :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b) -> ScalarType b -> SchemaT r m (FieldParser n (IR.SelectionField b (IR.UnpreparedValue b)))
mkNullableScalarTypeAggField :: (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ScalarType b
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkNullableScalarTypeAggField (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
columnInfo ScalarType b
resultType =
(ColumnInfo b, AnnRedactionExpUnpreparedValue b)
-> ColumnType b
-> SchemaT
r m (FieldParser n (SelectionField b (UnpreparedValue b)))
mkColumnAggField' (ColumnInfo b, AnnRedactionExpUnpreparedValue b)
columnInfo (ScalarType b -> ColumnType b
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType b
resultType)
countField :: SchemaT r m (FieldParser n (IR.AggregateField b (IR.UnpreparedValue b)))
countField :: SchemaT r m (FieldParser n (AggregateField b (UnpreparedValue b)))
countField = do
Maybe (Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b))
columnsEnum <- TableInfo b
-> SchemaT
r
m
(Maybe
(Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
TableInfo b
-> SchemaT
r
m
(Maybe
(Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b)))
tableSelectColumnsEnum TableInfo b
tableInfo
let distinctName :: Name
distinctName = Name
Name._distinct
args :: InputFieldsParser MetadataObjId n (CountType b (UnpreparedValue b))
args = do
Maybe Bool
distinct <- Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Bool
-> InputFieldsParser MetadataObjId n (Maybe Bool)
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
distinctName Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Both n Bool
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Bool
P.boolean
CountDistinct -> CountType b (UnpreparedValue b)
mkCountType <- forall (b :: BackendType) (n :: * -> *).
(BackendSchema b, MonadParse n) =>
Maybe (Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b))
-> InputFieldsParser
n (CountDistinct -> CountType b (UnpreparedValue b))
countTypeInput @b Maybe (Parser 'Both n (Column b, AnnRedactionExpUnpreparedValue b))
columnsEnum
pure
$ CountDistinct -> CountType b (UnpreparedValue b)
mkCountType
(CountDistinct -> CountType b (UnpreparedValue b))
-> CountDistinct -> CountType b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ CountDistinct
-> (Bool -> CountDistinct) -> Maybe Bool -> CountDistinct
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
CountDistinct
IR.SelectCountNonDistinct
(CountDistinct -> CountDistinct -> Bool -> CountDistinct
forall a. a -> a -> Bool -> a
bool CountDistinct
IR.SelectCountNonDistinct CountDistinct
IR.SelectCountDistinct)
Maybe Bool
distinct
FieldParser n (AggregateField b (UnpreparedValue b))
-> SchemaT
r m (FieldParser n (AggregateField b (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser n (AggregateField b (UnpreparedValue b))
-> SchemaT
r m (FieldParser n (AggregateField b (UnpreparedValue b))))
-> FieldParser n (AggregateField b (UnpreparedValue b))
-> SchemaT
r m (FieldParser n (AggregateField b (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ CountType b (UnpreparedValue b)
-> AggregateField b (UnpreparedValue b)
forall (b :: BackendType) v. CountType b v -> AggregateField b v
IR.AFCount (CountType b (UnpreparedValue b)
-> AggregateField b (UnpreparedValue b))
-> FieldParser MetadataObjId n (CountType b (UnpreparedValue b))
-> FieldParser n (AggregateField b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (CountType b (UnpreparedValue b))
-> Parser MetadataObjId 'Both n Int32
-> FieldParser MetadataObjId n (CountType b (UnpreparedValue b))
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Both m b
-> FieldParser origin m a
P.selection Name
Name._count Maybe Description
forall a. Maybe a
Nothing InputFieldsParser MetadataObjId n (CountType b (UnpreparedValue b))
args Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int
parseAggOperator ::
MkTypename ->
GQLNameIdentifier ->
NamingCase ->
GQLNameIdentifier ->
[FieldParser n (IR.SelectionField b (IR.UnpreparedValue b))] ->
FieldParser n (IR.AggregateField b (IR.UnpreparedValue b))
parseAggOperator :: MkTypename
-> GQLNameIdentifier
-> NamingCase
-> GQLNameIdentifier
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> FieldParser n (AggregateField b (UnpreparedValue b))
parseAggOperator MkTypename
makeTypename GQLNameIdentifier
operator NamingCase
tCase GQLNameIdentifier
tableGQLName [FieldParser n (SelectionField b (UnpreparedValue b))]
columns =
let opFieldName :: Name
opFieldName = NamingCase -> GQLNameIdentifier -> Name
applyFieldNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
operator
opText :: Text
opText = Name -> Text
G.unName Name
opFieldName
setName :: Name
setName = MkTypename -> Name -> Name
runMkTypename MkTypename
makeTypename (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 -> GQLNameIdentifier
mkTableAggOperatorTypeName GQLNameIdentifier
tableGQLName GQLNameIdentifier
operator
setDesc :: Maybe Description
setDesc = 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
"aggregate " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
opText Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" on columns"
subselectionParser :: Parser
MetadataObjId
'Output
n
(Fields (SelectionField b (UnpreparedValue b)))
subselectionParser =
Name
-> Maybe Description
-> [FieldParser n (SelectionField b (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name (ParsedSelection (SelectionField b (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
setName Maybe Description
setDesc [FieldParser n (SelectionField b (UnpreparedValue b))]
columns
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name (ParsedSelection (SelectionField b (UnpreparedValue b))))
-> (InsOrdHashMap
Name (ParsedSelection (SelectionField b (UnpreparedValue b)))
-> Fields (SelectionField b (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(Fields (SelectionField b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> SelectionField b (UnpreparedValue b))
-> InsOrdHashMap
Name (ParsedSelection (SelectionField b (UnpreparedValue b)))
-> Fields (SelectionField b (UnpreparedValue b))
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> SelectionField b (UnpreparedValue b)
forall (b :: BackendType) v. Text -> SelectionField b v
IR.SFExp
in Name
-> Maybe Description
-> Parser
MetadataObjId
'Output
n
(Fields (SelectionField b (UnpreparedValue b)))
-> FieldParser
MetadataObjId n (Fields (SelectionField b (UnpreparedValue b)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
opFieldName Maybe Description
forall a. Maybe a
Nothing Parser
MetadataObjId
'Output
n
(Fields (SelectionField b (UnpreparedValue b)))
subselectionParser
FieldParser
MetadataObjId n (Fields (SelectionField b (UnpreparedValue b)))
-> (Fields (SelectionField b (UnpreparedValue b))
-> AggregateField b (UnpreparedValue b))
-> FieldParser n (AggregateField b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> AggregateOp b (UnpreparedValue b)
-> AggregateField b (UnpreparedValue b)
forall (b :: BackendType) v. AggregateOp b v -> AggregateField b v
IR.AFOp (AggregateOp b (UnpreparedValue b)
-> AggregateField b (UnpreparedValue b))
-> (Fields (SelectionField b (UnpreparedValue b))
-> AggregateOp b (UnpreparedValue b))
-> Fields (SelectionField b (UnpreparedValue b))
-> AggregateField b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> Fields (SelectionField b (UnpreparedValue b))
-> AggregateOp b (UnpreparedValue b)
forall (b :: BackendType) v.
Text -> SelectionFields b v -> AggregateOp b v
IR.AggregateOp Text
opText
defaultArgsParser ::
forall b r m n.
( MonadBuildSchema b r m n
) =>
InputFieldsParser n (Maybe (AnnBoolExp b (IR.UnpreparedValue b))) ->
InputFieldsParser n (Maybe (NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b)))) ->
InputFieldsParser n (Maybe (NonEmpty (IR.AnnDistinctColumn b (IR.UnpreparedValue b)))) ->
SchemaT r m (InputFieldsParser n (SelectArgs b))
defaultArgsParser :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
-> SchemaT r m (InputFieldsParser n (SelectArgs b))
defaultArgsParser InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
distinctParser = do
let result :: InputFieldsParser n (SelectArgs b)
result = do
Maybe (AnnBoolExp b (UnpreparedValue b))
whereArg <- InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser
Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
orderByArg <- InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser
Maybe Int
limitArg <- InputFieldsParser n (Maybe Int)
forall (n :: * -> *).
MonadParse n =>
InputFieldsParser n (Maybe Int)
tableLimitArg
Maybe Int64
offsetArg <- InputFieldsParser n (Maybe Int64)
forall (n :: * -> *).
MonadParse n =>
InputFieldsParser n (Maybe Int64)
tableOffsetArg
Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
distinctArg <- InputFieldsParser
n (Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b))))
distinctParser
pure
$ IR.SelectArgs
{ $sel:_saWhere:SelectArgs :: Maybe (AnnBoolExp b (UnpreparedValue b))
IR._saWhere = Maybe (AnnBoolExp b (UnpreparedValue b))
whereArg,
$sel:_saOrderBy:SelectArgs :: Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
IR._saOrderBy = Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
orderByArg,
$sel:_saLimit:SelectArgs :: Maybe Int
IR._saLimit = Maybe Int
limitArg,
$sel:_saOffset:SelectArgs :: Maybe Int64
IR._saOffset = Maybe Int64
offsetArg,
$sel:_saDistinct:SelectArgs :: Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
IR._saDistinct = Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
distinctArg
}
InputFieldsParser n (SelectArgs b)
-> SchemaT r m (InputFieldsParser n (SelectArgs b))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(InputFieldsParser n (SelectArgs b)
-> SchemaT r m (InputFieldsParser n (SelectArgs b)))
-> InputFieldsParser n (SelectArgs b)
-> SchemaT r m (InputFieldsParser n (SelectArgs b))
forall a b. (a -> b) -> a -> b
$ InputFieldsParser n (SelectArgs b)
result
InputFieldsParser n (SelectArgs b)
-> (SelectArgs b -> n (SelectArgs b))
-> InputFieldsParser n (SelectArgs b)
forall (m :: * -> *) origin a b.
Monad m =>
InputFieldsParser origin m a
-> (a -> m b) -> InputFieldsParser origin m b
`P.bindFields` \SelectArgs b
args -> do
Maybe (n ()) -> n ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ do
NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBy <- SelectArgs b
-> Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
forall (b :: BackendType) v.
SelectArgsG b v -> Maybe (NonEmpty (AnnotatedOrderByItemG b v))
IR._saOrderBy SelectArgs b
args
NonEmpty (AnnDistinctColumn b (UnpreparedValue b))
distinct <- SelectArgs b
-> Maybe (NonEmpty (AnnDistinctColumn b (UnpreparedValue b)))
forall (b :: BackendType) v.
SelectArgsG b v -> Maybe (NonEmpty (AnnDistinctColumn b v))
IR._saDistinct SelectArgs b
args
n () -> Maybe (n ())
forall a. a -> Maybe a
Just (n () -> Maybe (n ())) -> n () -> Maybe (n ())
forall a b. (a -> b) -> a -> b
$ NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> NonEmpty (AnnDistinctColumn b (UnpreparedValue b)) -> n ()
forall {b :: BackendType} {b :: BackendType} {t :: * -> *}
{f :: * -> *} {b :: BackendType} {v} {v}.
(Column b ~ Column b, Foldable t, Eq (Column b), MonadParse f) =>
NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
-> t (AnnDistinctColumn b v) -> f ()
validateArgs NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBy NonEmpty (AnnDistinctColumn b (UnpreparedValue b))
distinct
pure SelectArgs b
args
where
validateArgs :: NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
-> t (AnnDistinctColumn b v) -> f ()
validateArgs NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
orderByCols t (AnnDistinctColumn b v)
distinctCols = do
let colsLen :: Int
colsLen = t (AnnDistinctColumn b v) -> Int
forall a. t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t (AnnDistinctColumn b v)
distinctCols
initOrderBys :: [OrderByItemG b (AnnotatedOrderByElement b v)]
initOrderBys = Int
-> [OrderByItemG b (AnnotatedOrderByElement b v)]
-> [OrderByItemG b (AnnotatedOrderByElement b v)]
forall a. Int -> [a] -> [a]
take Int
colsLen ([OrderByItemG b (AnnotatedOrderByElement b v)]
-> [OrderByItemG b (AnnotatedOrderByElement b v)])
-> [OrderByItemG b (AnnotatedOrderByElement b v)]
-> [OrderByItemG b (AnnotatedOrderByElement b v)]
forall a b. (a -> b) -> a -> b
$ NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
-> [OrderByItemG b (AnnotatedOrderByElement b v)]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
orderByCols
initOrdByCols :: [Column b]
initOrdByCols = ((OrderByItemG b (AnnotatedOrderByElement b v) -> Maybe (Column b))
-> [OrderByItemG b (AnnotatedOrderByElement b v)] -> [Column b])
-> [OrderByItemG b (AnnotatedOrderByElement b v)]
-> (OrderByItemG b (AnnotatedOrderByElement b v)
-> Maybe (Column b))
-> [Column b]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (OrderByItemG b (AnnotatedOrderByElement b v) -> Maybe (Column b))
-> [OrderByItemG b (AnnotatedOrderByElement b v)] -> [Column b]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe [OrderByItemG b (AnnotatedOrderByElement b v)]
initOrderBys ((OrderByItemG b (AnnotatedOrderByElement b v) -> Maybe (Column b))
-> [Column b])
-> (OrderByItemG b (AnnotatedOrderByElement b v)
-> Maybe (Column b))
-> [Column b]
forall a b. (a -> b) -> a -> b
$ \OrderByItemG b (AnnotatedOrderByElement b v)
ob ->
case OrderByItemG b (AnnotatedOrderByElement b v)
-> AnnotatedOrderByElement b v
forall (b :: BackendType) a. OrderByItemG b a -> a
IR.obiColumn OrderByItemG b (AnnotatedOrderByElement b v)
ob of
IR.AOCColumn ColumnInfo b
columnInfo AnnRedactionExp b v
_redactionExp -> Column b -> Maybe (Column b)
forall a. a -> Maybe a
Just (Column b -> Maybe (Column b)) -> Column b -> Maybe (Column b)
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo
AnnotatedOrderByElement b v
_ -> Maybe (Column b)
forall a. Maybe a
Nothing
isValid :: Bool
isValid =
(Int
colsLen Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [Column b] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Column b]
initOrdByCols)
Bool -> Bool -> Bool
&& (Column b -> Bool) -> [Column b] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Column b -> [Column b] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Column b]
initOrdByCols) (AnnDistinctColumn b v -> Column b
AnnDistinctColumn b v -> Column b
forall (b :: BackendType) v. AnnDistinctColumn b v -> Column b
IR._adcColumn (AnnDistinctColumn b v -> Column b)
-> [AnnDistinctColumn b v] -> [Column b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t (AnnDistinctColumn b v) -> [AnnDistinctColumn b v]
forall a. t a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList t (AnnDistinctColumn b v)
distinctCols)
Bool -> f () -> f ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
isValid
(f () -> f ()) -> f () -> f ()
forall a b. (a -> b) -> a -> b
$ ErrorMessage -> f ()
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
parseError
ErrorMessage
"\"distinct_on\" columns must match initial \"order_by\" columns"
fieldSelection ::
forall b r m n.
( AggregationPredicatesSchema b,
BackendTableSelectSchema b,
Eq (AnnBoolExp b (IR.UnpreparedValue b)),
MonadBuildSchema b r m n
) =>
LogicalModelCache b ->
TableName b ->
TableInfo b ->
FieldInfo b ->
SchemaT r m [FieldParser n (AnnotatedField b)]
fieldSelection :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
LogicalModelCache b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> SchemaT r m [FieldParser n (AnnotatedField b)]
fieldSelection LogicalModelCache b
logicalModelCache TableName b
table TableInfo b
tableInfo = \case
FIColumn (SCIScalarColumn ColumnInfo b
columnInfo) ->
Maybe (FieldParser n (AnnotatedField b))
-> [FieldParser n (AnnotatedField b)]
forall a. Maybe a -> [a]
maybeToList (Maybe (FieldParser n (AnnotatedField b))
-> [FieldParser n (AnnotatedField b)])
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MaybeT (SchemaT r m) (FieldParser n (AnnotatedField b))
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SchemaKind
schemaKind <- (SchemaContext -> SchemaKind) -> MaybeT (SchemaT r m) SchemaKind
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> SchemaKind
scSchemaKind
let fieldName :: Name
fieldName = ColumnInfo b -> Name
forall (b :: BackendType). ColumnInfo b -> Name
ciName ColumnInfo b
columnInfo
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
$ SchemaKind -> Bool
isHasuraSchema SchemaKind
schemaKind Bool -> Bool -> Bool
|| Name
fieldName Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
/= Name
Name._id
let columnName :: Column b
columnName = ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo
SelPermInfo b
selectPermissions <- 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
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
$ Column b
columnName Column b
-> HashMap (Column b) (AnnRedactionExpPartialSQL b) -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`HashMap.member` SelPermInfo b -> HashMap (Column b) (AnnRedactionExpPartialSQL b)
forall (b :: BackendType).
SelPermInfo b -> HashMap (Column b) (AnnRedactionExpPartialSQL b)
spiCols SelPermInfo b
selectPermissions
let redactionExp :: AnnRedactionExp b (UnpreparedValue b)
redactionExp = AnnRedactionExp b (UnpreparedValue b)
-> Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b)
forall a. a -> Maybe a -> a
fromMaybe AnnRedactionExp b (UnpreparedValue b)
forall (b :: BackendType) v. AnnRedactionExp b v
NoRedaction (Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b))
-> Maybe (AnnRedactionExp b (UnpreparedValue b))
-> AnnRedactionExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SelPermInfo b
-> Column b -> Maybe (AnnRedactionExp b (UnpreparedValue b))
forall (b :: BackendType).
Backend b =>
SelPermInfo b
-> Column b -> Maybe (AnnRedactionExpUnpreparedValue b)
getRedactionExprForColumn SelPermInfo b
selectPermissions Column b
columnName
pathArg :: InputFieldsParser n (Maybe (ScalarSelectionArguments b))
pathArg = ColumnType b
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b))
forall (b :: BackendType) (n :: * -> *).
(BackendSchema b, MonadParse n) =>
ColumnType b
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b))
forall (n :: * -> *).
MonadParse n =>
ColumnType b
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b))
scalarSelectionArgumentsParser (ColumnType b
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b)))
-> ColumnType b
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b))
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo
nullability :: Bool
nullability = ColumnInfo b -> Bool
forall (b :: BackendType). ColumnInfo b -> Bool
ciIsNullable ColumnInfo b
columnInfo Bool -> Bool -> Bool
|| AnnRedactionExp b (UnpreparedValue b)
redactionExp AnnRedactionExp b (UnpreparedValue b)
-> AnnRedactionExp b (UnpreparedValue b) -> Bool
forall a. Eq a => a -> a -> Bool
/= AnnRedactionExp b (UnpreparedValue b)
forall (b :: BackendType) v. AnnRedactionExp b v
NoRedaction
Parser 'Both n (ValueWithOrigin (ColumnValue b))
field <- SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT
(SchemaT r m) (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT
(SchemaT r m) (Parser 'Both n (ValueWithOrigin (ColumnValue b))))
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT
(SchemaT r m) (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall a b. (a -> b) -> a -> b
$ ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
ColumnType b
-> Nullability
-> SchemaT r m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
ColumnType b
-> Nullability
-> SchemaT r 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)
FieldParser n (AnnotatedField b)
-> MaybeT (SchemaT r m) (FieldParser n (AnnotatedField b))
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(FieldParser n (AnnotatedField b)
-> MaybeT (SchemaT r m) (FieldParser n (AnnotatedField b)))
-> FieldParser n (AnnotatedField b)
-> MaybeT (SchemaT r m) (FieldParser n (AnnotatedField b))
forall a b. (a -> b) -> a -> b
$! Name
-> Maybe Description
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b))
-> Parser 'Both n (ValueWithOrigin (ColumnValue b))
-> FieldParser MetadataObjId n (Maybe (ScalarSelectionArguments b))
forall (m :: * -> *) origin a b.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Both m b
-> FieldParser origin m a
P.selection Name
fieldName (ColumnInfo b -> Maybe Description
forall (b :: BackendType). ColumnInfo b -> Maybe Description
ciDescription ColumnInfo b
columnInfo) InputFieldsParser n (Maybe (ScalarSelectionArguments b))
pathArg Parser 'Both n (ValueWithOrigin (ColumnValue b))
field
FieldParser MetadataObjId n (Maybe (ScalarSelectionArguments b))
-> (Maybe (ScalarSelectionArguments b) -> AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> Column b
-> ColumnType b
-> AnnRedactionExp b (UnpreparedValue b)
-> Maybe (ScalarSelectionArguments b)
-> AnnotatedField b
forall (backend :: BackendType) v r.
Column backend
-> ColumnType backend
-> AnnRedactionExp backend v
-> Maybe (ScalarSelectionArguments backend)
-> AnnFieldG backend r v
IR.mkAnnColumnField (ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
columnInfo) (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) AnnRedactionExp b (UnpreparedValue b)
redactionExp
FIColumn (SCIObjectColumn NestedObjectInfo b
nestedObjectInfo) ->
FieldParser n (AnnotatedField b)
-> [FieldParser n (AnnotatedField b)]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser n (AnnotatedField b)
-> [FieldParser n (AnnotatedField b)])
-> (FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (AnnotatedField b))
-> FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> [FieldParser n (AnnotatedField b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b)
-> FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser n (AnnotatedField b)
forall a b.
(a -> b)
-> FieldParser MetadataObjId n a -> FieldParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall (b :: BackendType) r v.
AnnNestedObjectSelectG b r v -> AnnFieldG b r v
IR.AFNestedObject (FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> [FieldParser n (AnnotatedField b)])
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NestedObjectInfo b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
nestedObjectFieldParser NestedObjectInfo b
nestedObjectInfo
FIColumn (SCIArrayColumn NestedArrayInfo {Bool
XNestedObjects b
StructuredColumnInfo b
_naiSupportsNestedArrays :: XNestedObjects b
_naiIsNullable :: Bool
_naiColumnInfo :: StructuredColumnInfo b
_naiSupportsNestedArrays :: forall (b :: BackendType). NestedArrayInfo b -> XNestedObjects b
_naiIsNullable :: forall (b :: BackendType). NestedArrayInfo b -> Bool
_naiColumnInfo :: forall (b :: BackendType).
NestedArrayInfo b -> StructuredColumnInfo b
..}) ->
(FieldParser n (AnnotatedField b)
-> FieldParser n (AnnotatedField b))
-> [FieldParser n (AnnotatedField b)]
-> [FieldParser n (AnnotatedField b)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (XNestedObjects b
-> Bool
-> FieldParser n (AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall origin (m :: * -> *) (b :: BackendType) r v.
Functor m =>
XNestedObjects b
-> Bool
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
nestedArrayFieldParser XNestedObjects b
_naiSupportsNestedArrays Bool
_naiIsNullable) ([FieldParser n (AnnotatedField b)]
-> [FieldParser n (AnnotatedField b)])
-> SchemaT r m [FieldParser n (AnnotatedField b)]
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LogicalModelCache b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
LogicalModelCache b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> SchemaT r m [FieldParser n (AnnotatedField b)]
fieldSelection LogicalModelCache b
logicalModelCache TableName b
table TableInfo b
tableInfo (StructuredColumnInfo b -> FieldInfo b
forall (b :: BackendType). StructuredColumnInfo b -> FieldInfo b
FIColumn StructuredColumnInfo b
_naiColumnInfo)
FIRelationship RelInfo b
relationshipInfo ->
[[FieldParser n (AnnotatedField b)]]
-> [FieldParser n (AnnotatedField b)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser n (AnnotatedField b)]]
-> [FieldParser n (AnnotatedField b)])
-> (Maybe [FieldParser n (AnnotatedField b)]
-> [[FieldParser n (AnnotatedField b)]])
-> Maybe [FieldParser n (AnnotatedField b)]
-> [FieldParser n (AnnotatedField b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe [FieldParser n (AnnotatedField b)]
-> [[FieldParser n (AnnotatedField b)]]
forall a. Maybe a -> [a]
maybeToList (Maybe [FieldParser n (AnnotatedField b)]
-> [FieldParser n (AnnotatedField b)])
-> SchemaT r m (Maybe [FieldParser n (AnnotatedField b)])
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableName b
-> RelInfo b
-> SchemaT r m (Maybe [FieldParser n (AnnotatedField b)])
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
TableName b
-> RelInfo b
-> SchemaT r m (Maybe [FieldParser n (AnnotatedField b)])
relationshipField TableName b
table RelInfo b
relationshipInfo
FIComputedField ComputedFieldInfo b
computedFieldInfo ->
Maybe (FieldParser n (AnnotatedField b))
-> [FieldParser n (AnnotatedField b)]
forall a. Maybe a -> [a]
maybeToList (Maybe (FieldParser n (AnnotatedField b))
-> [FieldParser n (AnnotatedField b)])
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> SchemaT r m (Maybe (FieldParser n (AnnotatedField b)))
computedField ComputedFieldInfo b
computedFieldInfo TableName b
table TableInfo b
tableInfo
FIRemoteRelationship RemoteFieldInfo (DBJoinField b)
remoteFieldInfo -> do
SchemaKind
schemaKind <- (SchemaContext -> SchemaKind) -> SchemaT r m SchemaKind
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> SchemaKind
scSchemaKind
case (SchemaKind
schemaKind, RemoteFieldInfo (DBJoinField b) -> RemoteFieldInfoRHS
forall lhsJoinField.
RemoteFieldInfo lhsJoinField -> RemoteFieldInfoRHS
_rfiRHS RemoteFieldInfo (DBJoinField b)
remoteFieldInfo) of
(RelaySchema NodeInterfaceParserBuilder
_, RFISchema RemoteSchemaFieldInfo
_) ->
[FieldParser n (AnnotatedField b)]
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
(SchemaKind, RemoteFieldInfoRHS)
_ -> do
RemoteRelationshipParserBuilder forall lhsJoinField r (n :: * -> *) (m :: * -> *).
MonadBuildSchemaBase m n =>
RemoteFieldInfo lhsJoinField
-> SchemaT
r
m
(Maybe [FieldParser n (RemoteRelationshipField UnpreparedValue)])
remoteRelationshipField <- (SchemaContext -> RemoteRelationshipParserBuilder)
-> SchemaT r m RemoteRelationshipParserBuilder
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RemoteRelationshipParserBuilder
scRemoteRelationshipParserBuilder
[FieldParser n (RemoteRelationshipField UnpreparedValue)]
relationshipFields <- [FieldParser n (RemoteRelationshipField UnpreparedValue)]
-> Maybe [FieldParser n (RemoteRelationshipField UnpreparedValue)]
-> [FieldParser n (RemoteRelationshipField UnpreparedValue)]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [FieldParser n (RemoteRelationshipField UnpreparedValue)]
-> [FieldParser n (RemoteRelationshipField UnpreparedValue)])
-> SchemaT
r
m
(Maybe [FieldParser n (RemoteRelationshipField UnpreparedValue)])
-> SchemaT
r m [FieldParser n (RemoteRelationshipField UnpreparedValue)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RemoteFieldInfo (DBJoinField b)
-> SchemaT
r
m
(Maybe [FieldParser n (RemoteRelationshipField UnpreparedValue)])
forall lhsJoinField r (n :: * -> *) (m :: * -> *).
MonadBuildSchemaBase m n =>
RemoteFieldInfo lhsJoinField
-> SchemaT
r
m
(Maybe [FieldParser n (RemoteRelationshipField UnpreparedValue)])
remoteRelationshipField RemoteFieldInfo (DBJoinField b)
remoteFieldInfo
let lhsFields :: HashMap FieldName (DBJoinField b)
lhsFields = RemoteFieldInfo (DBJoinField b)
-> HashMap FieldName (DBJoinField b)
forall lhsJoinField.
RemoteFieldInfo lhsJoinField -> HashMap FieldName lhsJoinField
_rfiLHS RemoteFieldInfo (DBJoinField b)
remoteFieldInfo
[FieldParser n (AnnotatedField b)]
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser n (AnnotatedField b)]
-> SchemaT r m [FieldParser n (AnnotatedField b)])
-> [FieldParser n (AnnotatedField b)]
-> SchemaT r m [FieldParser n (AnnotatedField b)]
forall a b. (a -> b) -> a -> b
$ (FieldParser n (RemoteRelationshipField UnpreparedValue)
-> FieldParser n (AnnotatedField b))
-> [FieldParser n (RemoteRelationshipField UnpreparedValue)]
-> [FieldParser n (AnnotatedField b)]
forall a b. (a -> b) -> [a] -> [b]
map ((RemoteRelationshipField UnpreparedValue -> AnnotatedField b)
-> FieldParser n (RemoteRelationshipField UnpreparedValue)
-> FieldParser n (AnnotatedField b)
forall a b.
(a -> b)
-> FieldParser MetadataObjId n a -> FieldParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (RemoteRelationshipSelect
b (RemoteRelationshipField UnpreparedValue)
-> AnnotatedField b
forall (b :: BackendType) r v.
RemoteRelationshipSelect b r -> AnnFieldG b r v
IR.AFRemote (RemoteRelationshipSelect
b (RemoteRelationshipField UnpreparedValue)
-> AnnotatedField b)
-> (RemoteRelationshipField UnpreparedValue
-> RemoteRelationshipSelect
b (RemoteRelationshipField UnpreparedValue))
-> RemoteRelationshipField UnpreparedValue
-> AnnotatedField b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HashMap FieldName (DBJoinField b)
-> RemoteRelationshipField UnpreparedValue
-> RemoteRelationshipSelect
b (RemoteRelationshipField UnpreparedValue)
forall (b :: BackendType) r.
HashMap FieldName (DBJoinField b)
-> r -> RemoteRelationshipSelect b r
IR.RemoteRelationshipSelect HashMap FieldName (DBJoinField b)
lhsFields)) [FieldParser n (RemoteRelationshipField UnpreparedValue)]
relationshipFields
where
nestedObjectFieldParser :: NestedObjectInfo b -> SchemaT r m (FieldParser n (AnnotatedNestedObjectSelect b))
nestedObjectFieldParser :: NestedObjectInfo b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
nestedObjectFieldParser NestedObjectInfo {Bool
Maybe Description
Name
Column b
XNestedObjects b
LogicalModelName
ColumnMutability
_noiSupportsNestedObjects :: XNestedObjects b
_noiColumn :: Column b
_noiName :: Name
_noiType :: LogicalModelName
_noiIsNullable :: Bool
_noiDescription :: Maybe Description
_noiMutability :: ColumnMutability
_noiSupportsNestedObjects :: forall (b :: BackendType). NestedObjectInfo b -> XNestedObjects b
_noiColumn :: forall (b :: BackendType). NestedObjectInfo b -> Column b
_noiName :: forall (b :: BackendType). NestedObjectInfo b -> Name
_noiType :: forall (b :: BackendType). NestedObjectInfo b -> LogicalModelName
_noiIsNullable :: forall (b :: BackendType). NestedObjectInfo b -> Bool
_noiDescription :: forall (b :: BackendType). NestedObjectInfo b -> Maybe Description
_noiMutability :: forall (b :: BackendType). NestedObjectInfo b -> ColumnMutability
..} = do
case LogicalModelName
-> LogicalModelCache b -> Maybe (LogicalModelInfo b)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup LogicalModelName
_noiType LogicalModelCache b
logicalModelCache of
Just LogicalModelInfo b
objectType -> do
Parser
'Output
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
parser <- XNestedObjects b
-> LogicalModelCache b
-> LogicalModelInfo b
-> Column b
-> Bool
-> SchemaT
r
m
(Parser
'Output
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
XNestedObjects b
-> LogicalModelCache b
-> LogicalModelInfo b
-> Column b
-> Bool
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
nestedObjectParser XNestedObjects b
_noiSupportsNestedObjects LogicalModelCache b
logicalModelCache LogicalModelInfo b
objectType Column b
_noiColumn Bool
_noiIsNullable
pure $ Name
-> Maybe Description
-> Parser
'Output
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
_noiName Maybe Description
_noiDescription Parser
'Output
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
parser
Maybe (LogicalModelInfo b)
_ -> Text
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 (Text
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> Text
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnNestedObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Text
"fieldSelection: object type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> LogicalModelName
_noiType LogicalModelName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" not found"
outputParserModifier :: Bool -> IP.Parser origin 'Output m a -> IP.Parser origin 'Output m a
outputParserModifier :: forall origin (m :: * -> *) a.
Bool -> Parser origin 'Output m a -> Parser origin 'Output m a
outputParserModifier Bool
True = Parser origin 'Output m a -> Parser origin 'Output m a
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nullableParser
outputParserModifier Bool
False = Parser origin 'Output m a -> Parser origin 'Output m a
forall (m :: * -> *) origin (k :: Kind) a.
Parser origin k m a -> Parser origin k m a
P.nonNullableParser
nestedArrayFieldParser :: forall origin m b r v. (Functor m) => XNestedObjects b -> Bool -> IP.FieldParser origin m (IR.AnnFieldG b r v) -> IP.FieldParser origin m (IR.AnnFieldG b r v)
nestedArrayFieldParser :: forall origin (m :: * -> *) (b :: BackendType) r v.
Functor m =>
XNestedObjects b
-> Bool
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
nestedArrayFieldParser XNestedObjects b
supportsNestedArrays Bool
isNullable =
Bool
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
forall origin (m :: * -> *) a.
Bool -> FieldParser origin m a -> FieldParser origin m a
wrapNullable Bool
isNullable (FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v))
-> (FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v))
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
forall (m :: * -> *) origin a.
FieldParser origin m a -> FieldParser origin m a
IP.multipleField (FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v))
-> (FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v))
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnFieldG b r v -> AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
forall a b.
(a -> b) -> FieldParser origin m a -> FieldParser origin m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (b :: BackendType) r v.
XNestedObjects b -> AnnNestedArraySelectG b r v -> AnnFieldG b r v
IR.AFNestedArray @b XNestedObjects b
supportsNestedArrays (AnnNestedArraySelectG b r v -> AnnFieldG b r v)
-> (AnnFieldG b r v -> AnnNestedArraySelectG b r v)
-> AnnFieldG b r v
-> AnnFieldG b r v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnnFieldG b r v -> AnnNestedArraySelectG b r v
forall (b :: BackendType) r v.
AnnFieldG b r v -> AnnNestedArraySelectG b r v
IR.ANASSimple)
wrapNullable :: Bool -> IP.FieldParser origin m a -> IP.FieldParser origin m a
wrapNullable :: forall origin (m :: * -> *) a.
Bool -> FieldParser origin m a -> FieldParser origin m a
wrapNullable Bool
isNullable = if Bool
isNullable then FieldParser origin m a -> FieldParser origin m a
forall (m :: * -> *) origin a.
FieldParser origin m a -> FieldParser origin m a
IP.nullableField else FieldParser origin m a -> FieldParser origin m a
forall (m :: * -> *) origin a.
FieldParser origin m a -> FieldParser origin m a
IP.nonNullableField
nestedObjectParser ::
forall b r m n.
(MonadBuildSchema b r m n) =>
XNestedObjects b ->
LogicalModelCache b ->
LogicalModelInfo b ->
Column b ->
Bool ->
SchemaT r m (P.Parser 'Output n (AnnotatedNestedObjectSelect b))
nestedObjectParser :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
XNestedObjects b
-> LogicalModelCache b
-> LogicalModelInfo b
-> Column b
-> Bool
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
nestedObjectParser XNestedObjects b
supportsNestedObjects LogicalModelCache b
objectTypes LogicalModelInfo {Maybe Text
RolePermInfoMap b
InsOrdHashMap (Column b) (LogicalModelField b)
LogicalModelName
_lmiName :: LogicalModelName
_lmiFields :: InsOrdHashMap (Column b) (LogicalModelField b)
_lmiDescription :: Maybe Text
_lmiPermissions :: RolePermInfoMap b
_lmiName :: forall (b :: BackendType). LogicalModelInfo b -> LogicalModelName
_lmiFields :: forall (b :: BackendType).
LogicalModelInfo b
-> InsOrdHashMap (Column b) (LogicalModelField b)
_lmiDescription :: forall (b :: BackendType). LogicalModelInfo b -> Maybe Text
_lmiPermissions :: forall (b :: BackendType). LogicalModelInfo b -> RolePermInfoMap b
..} Column b
column Bool
isNullable = do
[FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
allFieldParsers <- [LogicalModelField b]
-> (LogicalModelField b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> SchemaT
r
m
[FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for (InsOrdHashMap (Column b) (LogicalModelField b)
-> [LogicalModelField b]
forall a. InsOrdHashMap (Column b) a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (InsOrdHashMap (Column b) (LogicalModelField b)
-> [LogicalModelField b])
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> [LogicalModelField b]
forall a b. (a -> b) -> a -> b
$ InsOrdHashMap (Column b) (LogicalModelField b)
_lmiFields) LogicalModelField b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
outputFieldParser
let LogicalModelName Name
gqlName = LogicalModelName
_lmiName
Parser 'Output n (AnnotatedNestedObjectSelect b)
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Parser 'Output n (AnnotatedNestedObjectSelect b)
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b)))
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
forall a b. (a -> b) -> a -> b
$ Bool
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
forall origin (m :: * -> *) a.
Bool -> Parser origin 'Output m a -> Parser origin 'Output m a
outputParserModifier Bool
isNullable
(Parser 'Output n (AnnotatedNestedObjectSelect b)
-> Parser 'Output n (AnnotatedNestedObjectSelect b))
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(AnnFieldG
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
gqlName (Text -> Description
G.Description (Text -> Description) -> Maybe Text -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
_lmiDescription) [FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
allFieldParsers
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> (InsOrdHashMap
Name
(ParsedSelection
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> AnnotatedNestedObjectSelect b)
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> XNestedObjects b
-> Column b
-> AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedNestedObjectSelect b
forall (b :: BackendType) r v.
XNestedObjects b
-> Column b -> AnnFieldsG b r v -> AnnNestedObjectSelectG b r v
IR.AnnNestedObjectSelectG XNestedObjects b
supportsNestedObjects Column b
column (AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedNestedObjectSelect b)
-> (InsOrdHashMap
Name
(ParsedSelection
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> AnnotatedNestedObjectSelect b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text
-> AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> InsOrdHashMap
Name
(ParsedSelection
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> AnnFieldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v. Text -> AnnFieldG b r v
IR.AFExpression
where
outputFieldParser ::
LogicalModelField b ->
SchemaT r m (IP.FieldParser MetadataObjId n (IR.AnnFieldG b (IR.RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue b)))
outputFieldParser :: LogicalModelField b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
outputFieldParser LogicalModelField {Maybe Text
Column b
LogicalModelType b
lmfName :: Column b
lmfType :: LogicalModelType b
lmfDescription :: Maybe Text
lmfName :: forall (b :: BackendType). LogicalModelField b -> Column b
lmfType :: forall (b :: BackendType).
LogicalModelField b -> LogicalModelType b
lmfDescription :: forall (b :: BackendType). LogicalModelField b -> Maybe Text
..} =
Name
-> (LogicalModelName, Column b)
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
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 'nestedObjectParser (LogicalModelName
_lmiName, Column b
lmfName) do
Name
name <- Text -> SchemaT r m Name
forall (m :: * -> *). MonadError QErr m => Text -> m Name
textToName (Text -> SchemaT r m Name) -> Text -> SchemaT r m Name
forall a b. (a -> b) -> a -> b
$ Column b -> Text
forall a. ToTxt a => a -> Text
toTxt Column b
lmfName
let go :: LogicalModelType b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
go = \case
LogicalModelTypeScalar LogicalModelTypeScalarC {Bool
ScalarType b
lmtsScalar :: ScalarType b
lmtsNullable :: Bool
lmtsScalar :: forall (b :: BackendType). LogicalModelTypeScalar b -> ScalarType b
lmtsNullable :: forall (b :: BackendType). LogicalModelTypeScalar b -> Bool
..} -> do
Name
fieldTypeName <- Text -> SchemaT r m Name
forall (m :: * -> *). MonadError QErr m => Text -> m Name
textToName (Text -> SchemaT r m Name) -> Text -> SchemaT r m Name
forall a b. (a -> b) -> a -> b
$ ScalarType b -> Text
forall a. ToTxt a => a -> Text
toTxt ScalarType b
lmtsScalar
Bool
-> Name
-> ScalarType b
-> Parser MetadataObjId 'Both n Value
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
wrapScalar Bool
lmtsNullable Name
name ScalarType b
lmtsScalar (Parser MetadataObjId 'Both n Value
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> Parser MetadataObjId 'Both n Value
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Bool -> Name -> Parser MetadataObjId 'Both n Value
forall {m :: * -> *} {origin}.
MonadParse m =>
Bool -> Name -> Parser origin 'Both m Value
customScalarParser Bool
lmtsNullable Name
fieldTypeName
LogicalModelTypeReference LogicalModelTypeReferenceC {Bool
LogicalModelName
lmtrReference :: LogicalModelName
lmtrNullable :: Bool
lmtrReference :: LogicalModelTypeReference -> LogicalModelName
lmtrNullable :: LogicalModelTypeReference -> Bool
..} -> do
LogicalModelInfo b
objectType' <- LogicalModelName
-> LogicalModelCache b -> Maybe (LogicalModelInfo b)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup LogicalModelName
lmtrReference LogicalModelCache b
objectTypes Maybe (LogicalModelInfo b)
-> SchemaT r m (LogicalModelInfo b)
-> SchemaT r m (LogicalModelInfo b)
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Text -> SchemaT r m (LogicalModelInfo b)
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 (Text
"Custom logical model type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> LogicalModelName
lmtrReference LogicalModelName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" not found")
Parser
MetadataObjId
'Output
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
parser <- (AnnotatedNestedObjectSelect b
-> AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> Parser 'Output n (AnnotatedNestedObjectSelect b)
-> Parser
MetadataObjId
'Output
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall a b.
(a -> b)
-> Parser MetadataObjId 'Output n a
-> Parser MetadataObjId 'Output n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (b :: BackendType) r v.
AnnNestedObjectSelectG b r v -> AnnFieldG b r v
IR.AFNestedObject @b) (Parser 'Output n (AnnotatedNestedObjectSelect b)
-> Parser
MetadataObjId
'Output
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
-> SchemaT
r
m
(Parser
MetadataObjId
'Output
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> XNestedObjects b
-> LogicalModelCache b
-> LogicalModelInfo b
-> Column b
-> Bool
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
XNestedObjects b
-> LogicalModelCache b
-> LogicalModelInfo b
-> Column b
-> Bool
-> SchemaT r m (Parser 'Output n (AnnotatedNestedObjectSelect b))
nestedObjectParser XNestedObjects b
supportsNestedObjects LogicalModelCache b
objectTypes LogicalModelInfo b
objectType' Column b
lmfName Bool
lmtrNullable
pure $ Name
-> Maybe Description
-> Parser
MetadataObjId
'Output
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
name (Text -> Description
G.Description (Text -> Description) -> Maybe Text -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
lmfDescription) Parser
MetadataObjId
'Output
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
parser
LogicalModelTypeArray LogicalModelTypeArrayC {Bool
LogicalModelType b
lmtaArray :: LogicalModelType b
lmtaNullable :: Bool
lmtaArray :: forall (b :: BackendType).
LogicalModelTypeArray b -> LogicalModelType b
lmtaNullable :: forall (b :: BackendType). LogicalModelTypeArray b -> Bool
..} -> do
XNestedObjects b
-> Bool
-> FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall origin (m :: * -> *) (b :: BackendType) r v.
Functor m =>
XNestedObjects b
-> Bool
-> FieldParser origin m (AnnFieldG b r v)
-> FieldParser origin m (AnnFieldG b r v)
nestedArrayFieldParser XNestedObjects b
supportsNestedObjects Bool
lmtaNullable (FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LogicalModelType b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
go LogicalModelType b
lmtaArray
LogicalModelType b
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
go LogicalModelType b
lmfType
where
wrapScalar :: Bool
-> Name
-> ScalarType b
-> Parser MetadataObjId 'Both n Value
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
wrapScalar Bool
isNullable' Name
name ScalarType b
scalarType Parser MetadataObjId 'Both n Value
parser =
FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a. a -> SchemaT r m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SchemaT
r
m
(FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall a b. (a -> b) -> a -> b
$ Bool
-> FieldParser MetadataObjId n () -> FieldParser MetadataObjId n ()
forall origin (m :: * -> *) a.
Bool -> FieldParser origin m a -> FieldParser origin m a
wrapNullable Bool
isNullable' (Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Value
-> FieldParser MetadataObjId n ()
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Both m a
-> FieldParser origin m ()
P.selection_ Name
name (Text -> Description
G.Description (Text -> Description) -> Maybe Text -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
lmfDescription) Parser MetadataObjId 'Both n Value
parser)
FieldParser MetadataObjId n ()
-> AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> FieldParser
MetadataObjId
n
(AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Column b
-> ColumnType b
-> AnnRedactionExp b (UnpreparedValue b)
-> Maybe (ScalarSelectionArguments b)
-> AnnFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (backend :: BackendType) v r.
Column backend
-> ColumnType backend
-> AnnRedactionExp backend v
-> Maybe (ScalarSelectionArguments backend)
-> AnnFieldG backend r v
IR.mkAnnColumnField Column b
lmfName (ScalarType b -> ColumnType b
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType b
scalarType) AnnRedactionExp b (UnpreparedValue b)
forall (b :: BackendType) v. AnnRedactionExp b v
NoRedaction Maybe (ScalarSelectionArguments b)
forall a. Maybe a
Nothing
customScalarParser :: Bool -> Name -> Parser origin 'Both m Value
customScalarParser Bool
isNullable' Name
fieldTypeName =
let nullable :: Nullability
nullable = if Bool
isNullable' then Nullability
P.Nullable else Nullability
P.NonNullable
schemaType :: Type origin 'Both
schemaType = Nullability
-> Definition origin (TypeInfo origin 'Both) -> Type origin 'Both
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
nullable (Definition origin (TypeInfo origin 'Both) -> Type origin 'Both)
-> Definition origin (TypeInfo origin 'Both) -> Type origin 'Both
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> TypeInfo origin 'Both
-> Definition origin (TypeInfo origin 'Both)
forall origin a.
Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> a
-> Definition origin a
P.Definition Name
fieldTypeName Maybe Description
forall a. Maybe a
Nothing Maybe origin
forall a. Maybe a
Nothing [] TypeInfo origin 'Both
forall origin. TypeInfo origin 'Both
P.TIScalar
in P.Parser
{ pType :: Type origin 'Both
pType = Type origin 'Both
schemaType,
pParser :: ParserInput 'Both -> m Value
pParser = GType -> InputValue Variable -> m Value
forall (m :: * -> *).
MonadParse m =>
GType -> InputValue Variable -> m Value
P.valueToJSON (Type origin 'Both -> GType
forall origin (k :: Kind). Type origin k -> GType
P.toGraphQLType Type origin 'Both
schemaType)
}
relationshipField ::
forall b r m n.
( AggregationPredicatesSchema b,
BackendTableSelectSchema b,
Eq (AnnBoolExp b (IR.UnpreparedValue b)),
MonadBuildSchema b r m n
) =>
TableName b ->
RelInfo b ->
SchemaT r m (Maybe [FieldParser n (AnnotatedField b)])
relationshipField :: forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
TableName b
-> RelInfo b
-> SchemaT r m (Maybe [FieldParser n (AnnotatedField b)])
relationshipField TableName b
table RelInfo b
ri = MaybeT (SchemaT r m) [FieldParser n (AnnotatedField b)]
-> SchemaT r m (Maybe [FieldParser n (AnnotatedField b)])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
NamingCase
tCase <- (SourceInfo b -> NamingCase) -> MaybeT (SchemaT r m) NamingCase
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve ((SourceInfo b -> NamingCase) -> MaybeT (SchemaT r m) NamingCase)
-> (SourceInfo b -> NamingCase) -> MaybeT (SchemaT r m) NamingCase
forall a b. (a -> b) -> a -> b
$ ResolvedSourceCustomization -> NamingCase
_rscNamingConvention (ResolvedSourceCustomization -> NamingCase)
-> (SourceInfo b -> ResolvedSourceCustomization)
-> SourceInfo b
-> NamingCase
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
SourceInfo b -> ResolvedSourceCustomization
_siCustomization @b
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT (SchemaT r m) RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
OptimizePermissionFilters
optimizePermissionFilters <- (SchemaOptions -> OptimizePermissionFilters)
-> MaybeT (SchemaT r m) OptimizePermissionFilters
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> OptimizePermissionFilters
Options.soOptimizePermissionFilters
TableInfo b
tableInfo <- SchemaT r m (TableInfo b) -> MaybeT (SchemaT r m) (TableInfo b)
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (TableInfo b) -> MaybeT (SchemaT r m) (TableInfo b))
-> SchemaT r m (TableInfo b) -> MaybeT (SchemaT r m) (TableInfo b)
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType) r (m :: * -> *).
(Backend b, MonadError QErr m, MonadReader r m,
Has (SourceInfo b) r) =>
TableName b -> m (TableInfo b)
askTableInfo @b TableName b
table
TableName b
otherTableName <- case RelInfo b -> RelTarget b
forall (b :: BackendType). RelInfo b -> RelTarget b
riTarget RelInfo b
ri of
RelTargetNativeQuery NativeQueryName
_ -> String -> MaybeT (SchemaT r m) (TableName b)
forall a. HasCallStack => String -> a
error String
"relationshipField RelTargetNativeQuery"
RelTargetTable TableName b
tn -> TableName b -> MaybeT (SchemaT r m) (TableName b)
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TableName b
tn
TableInfo b
otherTableInfo <- SchemaT r m (TableInfo b) -> MaybeT (SchemaT r m) (TableInfo b)
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (TableInfo b) -> MaybeT (SchemaT r m) (TableInfo b))
-> SchemaT r m (TableInfo b) -> MaybeT (SchemaT r m) (TableInfo b)
forall a b. (a -> b) -> a -> b
$ TableName b -> SchemaT r m (TableInfo b)
forall (b :: BackendType) r (m :: * -> *).
(Backend b, MonadError QErr m, MonadReader r m,
Has (SourceInfo b) r) =>
TableName b -> m (TableInfo b)
askTableInfo TableName b
otherTableName
SelPermInfo b
tablePerms <- 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
SelPermInfo b
remotePerms <- 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
otherTableInfo
Name
relFieldName <- SchemaT r m Name -> MaybeT (SchemaT r m) Name
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m Name -> MaybeT (SchemaT r m) Name)
-> SchemaT r m Name -> MaybeT (SchemaT r m) Name
forall a b. (a -> b) -> a -> b
$ Text -> SchemaT r m Name
forall (m :: * -> *). MonadError QErr m => Text -> m Name
textToName (Text -> SchemaT r m Name) -> Text -> SchemaT r m Name
forall a b. (a -> b) -> a -> b
$ RelName -> Text
relNameToTxt (RelName -> Text) -> RelName -> Text
forall a b. (a -> b) -> a -> b
$ RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
ri
let thisTablePerm :: AnnBoolExp b (UnpreparedValue b)
thisTablePerm = TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall (b :: BackendType) v. TablePermG b v -> AnnBoolExp b v
IR._tpFilter (TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b))
-> TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SelPermInfo b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
tablePerms
deduplicatePermissions :: AnnBoolExp b (IR.UnpreparedValue b) -> AnnBoolExp b (IR.UnpreparedValue b)
deduplicatePermissions :: AnnBoolExp b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
deduplicatePermissions AnnBoolExp b (UnpreparedValue b)
x =
case (OptimizePermissionFilters
optimizePermissionFilters, AnnBoolExp b (UnpreparedValue b)
x) of
( OptimizePermissionFilters
OptimizePermissionFilters,
BoolAnd
[ BoolField
( AVRelationship
RelInfo b
remoteRI
RelationshipFilters
{ rfTargetTablePermissions :: forall (backend :: BackendType) leaf.
RelationshipFilters backend leaf -> AnnBoolExp backend leaf
rfTargetTablePermissions = BoolAnd [],
AnnBoolExp b (UnpreparedValue b)
rfFilter :: AnnBoolExp b (UnpreparedValue b)
rfFilter :: forall (backend :: BackendType) leaf.
RelationshipFilters backend leaf -> AnnBoolExp backend leaf
rfFilter
}
)
]
) ->
let remoteTableName :: Maybe (TableName b)
remoteTableName = case RelInfo b -> RelTarget b
forall (b :: BackendType). RelInfo b -> RelTarget b
riTarget RelInfo b
remoteRI of
RelTargetTable TableName b
tn -> TableName b -> Maybe (TableName b)
forall a. a -> Maybe a
Just TableName b
tn
RelTarget b
_ -> Maybe (TableName b)
forall a. Maybe a
Nothing
in if (Maybe (TableName b)
remoteTableName Maybe (TableName b) -> Maybe (TableName b) -> Bool
forall a. Eq a => a -> a -> Bool
== TableName b -> Maybe (TableName b)
forall a. a -> Maybe a
Just TableName b
table)
Bool -> Bool -> Bool
&& (RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
remoteRI HashMap (Column b) (Column b)
-> HashMap (Column b) (Column b) -> Bool
forall k v.
(Hashable k, Hashable v) =>
HashMap k v -> HashMap v k -> Bool
`HashMap.isInverseOf` RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
ri)
Bool -> Bool -> Bool
&& (AnnBoolExp b (UnpreparedValue b)
thisTablePerm AnnBoolExp b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b) -> Bool
forall a. Eq a => a -> a -> Bool
== AnnBoolExp b (UnpreparedValue b)
rfFilter)
then [AnnBoolExp b (UnpreparedValue b)]
-> AnnBoolExp b (UnpreparedValue b)
forall (backend :: BackendType) field.
[GBoolExp backend field] -> GBoolExp backend field
BoolAnd []
else AnnBoolExp b (UnpreparedValue b)
x
(OptimizePermissionFilters, AnnBoolExp b (UnpreparedValue b))
_ -> AnnBoolExp b (UnpreparedValue b)
x
deduplicatePermissions' :: SelectExp b -> SelectExp b
deduplicatePermissions' :: SelectExp b -> SelectExp b
deduplicatePermissions' SelectExp b
expr =
let newFilter :: AnnBoolExp b (UnpreparedValue b)
newFilter = AnnBoolExp b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
deduplicatePermissions (TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall (b :: BackendType) v. TablePermG b v -> AnnBoolExp b v
IR._tpFilter (SelectExp b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType) (f :: * -> *) v.
AnnSelectG b f v -> TablePermG b v
IR._asnPerm SelectExp b
expr))
in SelectExp b
expr {$sel:_asnPerm:AnnSelectG :: TablePermG b (UnpreparedValue b)
IR._asnPerm = (SelectExp b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType) (f :: * -> *) v.
AnnSelectG b f v -> TablePermG b v
IR._asnPerm SelectExp b
expr) {$sel:_tpFilter:TablePerm :: AnnBoolExp b (UnpreparedValue b)
IR._tpFilter = AnnBoolExp b (UnpreparedValue b)
newFilter}}
case RelInfo b -> RelType
forall (b :: BackendType). RelInfo b -> RelType
riType RelInfo b
ri of
RelType
ObjRel -> do
let desc :: Maybe Description
desc = 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
"An object relationship"
Parser 'Output n (AnnotatedFields b)
selectionSetParser <- 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
otherTableInfo
Nullable
nullable <- case (RelInfo b -> Bool
forall (b :: BackendType). RelInfo b -> Bool
riIsManual RelInfo b
ri, RelInfo b -> InsertOrder
forall (b :: BackendType). RelInfo b -> InsertOrder
riInsertOrder RelInfo b
ri) of
(Bool
False, InsertOrder
BeforeParent) -> do
let columns :: [Column b]
columns = HashMap (Column b) (Column b) -> [Column b]
forall k v. HashMap k v -> [k]
HashMap.keys (HashMap (Column b) (Column b) -> [Column b])
-> HashMap (Column b) (Column b) -> [Column b]
forall a b. (a -> b) -> a -> b
$ RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
ri
fieldInfoMap :: FieldInfoMap (FieldInfo b)
fieldInfoMap = TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> FieldInfoMap (FieldInfo b)
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> FieldInfoMap field
_tciFieldInfoMap (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> FieldInfoMap (FieldInfo b))
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> FieldInfoMap (FieldInfo 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
findColumn :: Column b -> Maybe (ColumnInfo b)
findColumn Column b
col = FieldName -> FieldInfoMap (FieldInfo b) -> Maybe (FieldInfo b)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (forall (b :: BackendType). Backend b => Column b -> FieldName
fromCol @b Column b
col) FieldInfoMap (FieldInfo b)
fieldInfoMap Maybe (FieldInfo b)
-> Getting
(First (ColumnInfo b)) (Maybe (FieldInfo b)) (ColumnInfo b)
-> Maybe (ColumnInfo b)
forall s a. s -> Getting (First a) s a -> Maybe a
^? (FieldInfo b -> Const (First (ColumnInfo b)) (FieldInfo b))
-> Maybe (FieldInfo b)
-> Const (First (ColumnInfo b)) (Maybe (FieldInfo b))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((FieldInfo b -> Const (First (ColumnInfo b)) (FieldInfo b))
-> Maybe (FieldInfo b)
-> Const (First (ColumnInfo b)) (Maybe (FieldInfo b)))
-> ((ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> FieldInfo b -> Const (First (ColumnInfo b)) (FieldInfo b))
-> Getting
(First (ColumnInfo b)) (Maybe (FieldInfo b)) (ColumnInfo b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b))
-> FieldInfo b -> Const (First (ColumnInfo b)) (FieldInfo b)
forall (b :: BackendType) (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (StructuredColumnInfo b) (f (StructuredColumnInfo b))
-> p (FieldInfo b) (f (FieldInfo b))
_FIColumn ((StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b))
-> FieldInfo b -> Const (First (ColumnInfo b)) (FieldInfo b))
-> ((ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b))
-> (ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> FieldInfo b
-> Const (First (ColumnInfo b)) (FieldInfo b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> StructuredColumnInfo b
-> Const (First (ColumnInfo b)) (StructuredColumnInfo b)
forall (b :: BackendType) (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (ColumnInfo b) (f (ColumnInfo b))
-> p (StructuredColumnInfo b) (f (StructuredColumnInfo b))
_SCIScalarColumn
[ColumnInfo b]
colInfo <-
(Column b -> Maybe (ColumnInfo b))
-> [Column b] -> Maybe [ColumnInfo b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Column b -> Maybe (ColumnInfo b)
findColumn [Column b]
columns
Maybe [ColumnInfo b]
-> MaybeT (SchemaT r m) [ColumnInfo b]
-> MaybeT (SchemaT r m) [ColumnInfo b]
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Text -> MaybeT (SchemaT r m) [ColumnInfo b]
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 Text
"could not find column info in schema cache"
pure $ Bool -> Nullable
boolToNullable (Bool -> Nullable) -> Bool -> Nullable
forall a b. (a -> b) -> a -> b
$ (ColumnInfo b -> Bool) -> [ColumnInfo b] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ColumnInfo b -> Bool
forall (b :: BackendType). ColumnInfo b -> Bool
ciIsNullable [ColumnInfo b]
colInfo
(Bool, InsertOrder)
_ -> Nullable -> MaybeT (SchemaT r m) Nullable
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Nullable
Nullable
pure
$ FieldParser n (AnnotatedField b)
-> [FieldParser n (AnnotatedField b)]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(FieldParser n (AnnotatedField b)
-> [FieldParser n (AnnotatedField b)])
-> FieldParser n (AnnotatedField b)
-> [FieldParser n (AnnotatedField b)]
forall a b. (a -> b) -> a -> b
$ case Nullable
nullable of Nullable
Nullable -> FieldParser n (AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall a. a -> a
id; Nullable
NotNullable -> FieldParser n (AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall (m :: * -> *) origin a.
FieldParser origin m a -> FieldParser origin m a
IP.nonNullableField
(FieldParser n (AnnotatedField b)
-> FieldParser n (AnnotatedField b))
-> FieldParser n (AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall a b. (a -> b) -> a -> 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
relFieldName Maybe Description
desc Parser 'Output n (AnnotatedFields b)
selectionSetParser
FieldParser MetadataObjId n (AnnotatedFields b)
-> (AnnotatedFields b -> AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \AnnotatedFields b
fields ->
ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall (b :: BackendType) r v.
ObjectRelationSelectG b r v -> AnnFieldG b r v
IR.AFObjectRelation
(ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b)
-> ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall a b. (a -> b) -> a -> b
$ RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> a
-> AnnRelationSelectG b a
IR.AnnRelationSelectG (RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
ri) (RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
ri) Nullable
Nullable
(AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ AnnotatedFields b
-> SelectFromG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnFieldsG b r v
-> SelectFromG b v -> AnnBoolExp b v -> AnnObjectSelectG b r v
IR.AnnObjectSelectG AnnotatedFields b
fields (TableName b -> SelectFromG b (UnpreparedValue b)
forall (b :: BackendType) v. TableName b -> SelectFromG b v
IR.FromTable TableName b
otherTableName)
(AnnBoolExp b (UnpreparedValue b)
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ AnnBoolExp b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
deduplicatePermissions
(AnnBoolExp b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b))
-> AnnBoolExp b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall (b :: BackendType) v. TablePermG b v -> AnnBoolExp b v
IR._tpFilter
(TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b))
-> TablePermG b (UnpreparedValue b)
-> AnnBoolExp b (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SelPermInfo b -> TablePermG b (UnpreparedValue b)
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
remotePerms
RelType
ArrRel -> do
let arrayRelDesc :: Maybe Description
arrayRelDesc = 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
"An array relationship"
FieldParser n (SelectExp b)
otherTableParser <- SchemaT r m (Maybe (FieldParser n (SelectExp b)))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (SchemaT r m (Maybe (FieldParser n (SelectExp b)))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b)))
-> SchemaT r m (Maybe (FieldParser n (SelectExp b)))
-> MaybeT (SchemaT r m) (FieldParser n (SelectExp b))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (SelectExp b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (SelectExp 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
otherTableInfo Name
relFieldName Maybe Description
arrayRelDesc
let arrayRelField :: FieldParser n (AnnotatedField b)
arrayRelField =
FieldParser n (SelectExp b)
otherTableParser FieldParser n (SelectExp b)
-> (SelectExp b -> AnnotatedField b)
-> FieldParser n (AnnotatedField b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \SelectExp b
selectExp ->
ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall (b :: BackendType) r v.
ArraySelectG b r v -> AnnFieldG b r v
IR.AFArrayRelation
(ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall a b. (a -> b) -> a -> b
$ ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
ArrayRelationSelectG b r v -> ArraySelectG b r v
IR.ASSimple
(ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> SelectExp b
-> ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> a
-> AnnRelationSelectG b a
IR.AnnRelationSelectG (RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
ri) (RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
ri) Nullable
Nullable
(SelectExp b
-> ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> SelectExp b
-> ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall a b. (a -> b) -> a -> b
$ SelectExp b -> SelectExp b
deduplicatePermissions' SelectExp b
selectExp
relAggFieldName :: Name
relAggFieldName = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
tCase (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Name
relFieldName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__aggregate
relAggDesc :: Maybe Description
relAggDesc = 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
"An aggregate relationship"
Maybe (FieldParser n (AggSelectExp b))
remoteAggField <- SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
-> MaybeT (SchemaT r m) (Maybe (FieldParser n (AggSelectExp b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
-> MaybeT (SchemaT r m) (Maybe (FieldParser n (AggSelectExp b))))
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
-> MaybeT (SchemaT r m) (Maybe (FieldParser n (AggSelectExp b)))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp b)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSourceSchema b r m n =>
TableInfo b
-> Name
-> Maybe Description
-> SchemaT r m (Maybe (FieldParser n (AggSelectExp 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
otherTableInfo Name
relAggFieldName Maybe Description
relAggDesc
Maybe (FieldParser n (ConnectionSelectExp b))
remoteConnectionField <- MaybeT
(MaybeT (SchemaT r m)) (FieldParser n (ConnectionSelectExp b))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT
(MaybeT (SchemaT r m)) (FieldParser n (ConnectionSelectExp b))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b))))
-> MaybeT
(MaybeT (SchemaT r m)) (FieldParser n (ConnectionSelectExp b))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
forall a b. (a -> b) -> a -> b
$ do
RelaySchema NodeInterfaceParserBuilder
_ <- (SchemaContext -> SchemaKind)
-> MaybeT (MaybeT (SchemaT r m)) SchemaKind
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> SchemaKind
scSchemaKind
XRelay b
_xRelayInfo <- Maybe (XRelay b) -> MaybeT (MaybeT (SchemaT r m)) (XRelay b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (XRelay b) -> MaybeT (MaybeT (SchemaT r m)) (XRelay b))
-> Maybe (XRelay b) -> MaybeT (MaybeT (SchemaT r m)) (XRelay b)
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b
NESeq (ColumnInfo b)
pkeyColumns <-
MaybeT (SchemaT r m) (Maybe (NESeq (ColumnInfo b)))
-> MaybeT (MaybeT (SchemaT r m)) (NESeq (ColumnInfo b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT
(MaybeT (SchemaT r m) (Maybe (NESeq (ColumnInfo b)))
-> MaybeT (MaybeT (SchemaT r m)) (NESeq (ColumnInfo b)))
-> MaybeT (SchemaT r m) (Maybe (NESeq (ColumnInfo b)))
-> MaybeT (MaybeT (SchemaT r m)) (NESeq (ColumnInfo b))
forall a b. (a -> b) -> a -> b
$ (TableInfo b
-> Getting
(First (NESeq (ColumnInfo b))) (TableInfo b) (NESeq (ColumnInfo b))
-> Maybe (NESeq (ColumnInfo b))
forall s a. s -> Getting (First a) s a -> Maybe a
^? (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b)))
(TableCoreInfoG b (FieldInfo b) (ColumnInfo b)))
-> TableInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableInfo b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(TableCoreInfo b -> f (TableCoreInfo b))
-> TableInfo b -> f (TableInfo b)
tiCoreInfo ((TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b)))
(TableCoreInfoG b (FieldInfo b) (ColumnInfo b)))
-> TableInfo b
-> Const (First (NESeq (ColumnInfo b))) (TableInfo b))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b)))
(TableCoreInfoG b (FieldInfo b) (ColumnInfo b)))
-> Getting
(First (NESeq (ColumnInfo b))) (TableInfo b) (NESeq (ColumnInfo b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b)))
(TableCoreInfoG b (FieldInfo b) (ColumnInfo b))
forall (b :: BackendType) field primaryKeyColumn1 primaryKeyColumn2
(f :: * -> *).
Functor f =>
(Maybe (PrimaryKey b primaryKeyColumn1)
-> f (Maybe (PrimaryKey b primaryKeyColumn2)))
-> TableCoreInfoG b field primaryKeyColumn1
-> f (TableCoreInfoG b field primaryKeyColumn2)
tciPrimaryKey ((Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b)))
(TableCoreInfoG b (FieldInfo b) (ColumnInfo b)))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b)))
(TableCoreInfoG b (FieldInfo b) (ColumnInfo b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b)))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b))))
-> ((NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b)))
-> (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> Maybe (PrimaryKey b (ColumnInfo b))
-> Const
(First (NESeq (ColumnInfo b)))
(Maybe (PrimaryKey b (ColumnInfo b)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NESeq (ColumnInfo b)
-> Const (First (NESeq (ColumnInfo b))) (NESeq (ColumnInfo b)))
-> PrimaryKey b (ColumnInfo b)
-> Const
(First (NESeq (ColumnInfo b))) (PrimaryKey b (ColumnInfo b))
forall (b :: BackendType) a1 a2 (f :: * -> *).
Functor f =>
(NESeq a1 -> f (NESeq a2))
-> PrimaryKey b a1 -> f (PrimaryKey b a2)
pkColumns)
(TableInfo b -> Maybe (NESeq (ColumnInfo b)))
-> MaybeT (SchemaT r m) (TableInfo b)
-> MaybeT (SchemaT r m) (Maybe (NESeq (ColumnInfo b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b -> MaybeT (SchemaT r m) (TableInfo b)
forall a. a -> MaybeT (SchemaT r m) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TableInfo b
otherTableInfo
let relConnectionName :: Name
relConnectionName = Name
relFieldName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__connection
relConnectionDesc :: Maybe Description
relConnectionDesc = 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
"An array relationship connection"
MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(MaybeT (SchemaT r m)) (FieldParser n (ConnectionSelectExp b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(MaybeT (SchemaT r m)) (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(MaybeT (SchemaT r m)) (FieldParser n (ConnectionSelectExp b))
forall a b. (a -> b) -> a -> b
$ SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (m :: * -> *) a. Monad m => m a -> MaybeT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b))))
-> SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT
(SchemaT r m) (Maybe (FieldParser n (ConnectionSelectExp b)))
forall a b. (a -> b) -> a -> b
$ TableInfo b
-> Name
-> Maybe Description
-> NESeq (ColumnInfo b)
-> SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b,
AggregationPredicatesSchema b) =>
TableInfo b
-> Name
-> Maybe Description
-> PrimaryKeyColumns b
-> SchemaT r m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection TableInfo b
otherTableInfo Name
relConnectionName Maybe Description
relConnectionDesc NESeq (ColumnInfo b)
pkeyColumns
pure
$ [Maybe (FieldParser n (AnnotatedField b))]
-> [FieldParser n (AnnotatedField b)]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[ FieldParser n (AnnotatedField b)
-> Maybe (FieldParser n (AnnotatedField b))
forall a. a -> Maybe a
Just FieldParser n (AnnotatedField b)
arrayRelField,
(AggSelectExp b -> AnnotatedField b)
-> FieldParser n (AggSelectExp b)
-> FieldParser n (AnnotatedField b)
forall a b.
(a -> b)
-> FieldParser MetadataObjId n a -> FieldParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall (b :: BackendType) r v.
ArraySelectG b r v -> AnnFieldG b r v
IR.AFArrayRelation (ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b)
-> (AggSelectExp b
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AggSelectExp b
-> AnnotatedField b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
ArrayAggregateSelectG b r v -> ArraySelectG b r v
IR.ASAggregate (ArrayAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (AggSelectExp b
-> ArrayAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AggSelectExp b
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> AggSelectExp b
-> ArrayAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> a
-> AnnRelationSelectG b a
IR.AnnRelationSelectG (RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
ri) (RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
ri) Nullable
Nullable) (FieldParser n (AggSelectExp b)
-> FieldParser n (AnnotatedField b))
-> Maybe (FieldParser n (AggSelectExp b))
-> Maybe (FieldParser n (AnnotatedField b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (FieldParser n (AggSelectExp b))
remoteAggField,
(ConnectionSelectExp b -> AnnotatedField b)
-> FieldParser n (ConnectionSelectExp b)
-> FieldParser n (AnnotatedField b)
forall a b.
(a -> b)
-> FieldParser MetadataObjId n a -> FieldParser MetadataObjId n b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b
forall (b :: BackendType) r v.
ArraySelectG b r v -> AnnFieldG b r v
IR.AFArrayRelation (ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> AnnotatedField b)
-> (ConnectionSelectExp b
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ConnectionSelectExp b
-> AnnotatedField b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArrayConnectionSelect
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
ArrayConnectionSelect b r v -> ArraySelectG b r v
IR.ASConnection (ArrayConnectionSelect
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> (ConnectionSelectExp b
-> ArrayConnectionSelect
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> ConnectionSelectExp b
-> ArraySelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> ConnectionSelectExp b
-> ArrayConnectionSelect
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b)
-> Nullable
-> a
-> AnnRelationSelectG b a
IR.AnnRelationSelectG (RelInfo b -> RelName
forall (b :: BackendType). RelInfo b -> RelName
riName RelInfo b
ri) (RelInfo b -> HashMap (Column b) (Column b)
forall (b :: BackendType).
RelInfo b -> HashMap (Column b) (Column b)
riMapping RelInfo b
ri) Nullable
Nullable) (FieldParser n (ConnectionSelectExp b)
-> FieldParser n (AnnotatedField b))
-> Maybe (FieldParser n (ConnectionSelectExp b))
-> Maybe (FieldParser n (AnnotatedField b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (FieldParser n (ConnectionSelectExp b))
remoteConnectionField
]
tablePermissionsInfo :: (Backend b) => SelPermInfo b -> TablePerms b
tablePermissionsInfo :: forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions =
IR.TablePerm
{ $sel:_tpFilter:TablePerm :: AnnBoolExp b (UnpreparedValue b)
IR._tpFilter = (PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b)
forall a b. (a -> b) -> AnnBoolExpFld b a -> AnnBoolExpFld b b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PartialSQLExp b -> UnpreparedValue b
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue (AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SelPermInfo b -> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
forall (b :: BackendType). SelPermInfo b -> AnnBoolExpPartialSQL b
spiFilter SelPermInfo b
selectPermissions,
$sel:_tpLimit:TablePerm :: Maybe Int
IR._tpLimit = SelPermInfo b -> Maybe Int
forall (b :: BackendType). SelPermInfo b -> Maybe Int
spiLimit SelPermInfo b
selectPermissions
}