{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE ViewPatterns #-}
module Hasura.GraphQL.Schema.Select
( selectTableByPk,
selectTableConnection,
defaultSelectTable,
defaultSelectTableAggregate,
defaultTableArgs,
defaultTableSelectionSet,
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.Internal qualified as J
import Data.Aeson.Key qualified as K
import Data.ByteString.Lazy qualified as BL
import Data.Has
import Data.HashMap.Strict.Extended qualified as Map
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.Extended
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (toErrorMessage)
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Internal.Parser qualified as P
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options (OptimizePermissionFilters (..))
import Hasura.GraphQL.Schema.Options qualified as Options
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.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR qualified as IR
import Hasura.RQL.IR.BoolExp
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.Relationships.Local
import Hasura.RQL.Types.Relationships.Remote
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.Server.Utils (executeJSONPath)
import Language.GraphQL.Draft.Syntax qualified as G
defaultSelectTable ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (SelectExp b)))
defaultSelectTable :: SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp b)))
defaultSelectTable SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT m (FieldParser n (SelectExp b))
-> m (Maybe (FieldParser n (SelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPermissions <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
Parser 'Output n (AnnotatedFields b)
selectionSetParser <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall r (m :: * -> *) (n :: * -> *) (b :: BackendType).
(MonadBuildSchemaBase r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList SourceInfo b
sourceInfo TableInfo b
tableInfo
m (FieldParser n (SelectExp b))
-> MaybeT m (FieldParser n (SelectExp b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (FieldParser n (SelectExp b))
-> MaybeT m (FieldParser n (SelectExp b)))
-> m (FieldParser n (SelectExp b))
-> MaybeT m (FieldParser n (SelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> m (FieldParser n (SelectExp b))
-> 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 (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> 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 <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
tableArguments SourceInfo b
sourceInfo 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 -> MetadataObjId
MOSource (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo)) (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) ->
AnnSelectG :: forall (b :: BackendType) (f :: * -> *) v.
Fields (f v)
-> SelectFromG b v
-> TablePermG b v
-> SelectArgsG b v
-> StringifyNumbers
-> Maybe NamingCase
-> AnnSelectG b f v
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
}
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
selectTableConnection ::
forall b r m n.
( MonadBuildSchema b r m n,
BackendTableSelectSchema b,
AggregationPredicatesSchema b
) =>
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
PrimaryKeyColumns b ->
m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection :: SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> PrimaryKeyColumns b
-> m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description PrimaryKeyColumns b
pkeyColumns = MaybeT m (FieldParser n (ConnectionSelectExp b))
-> m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
XRelay b
xRelayInfo <- Maybe (XRelay b) -> MaybeT m (XRelay b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (XRelay b) -> MaybeT m (XRelay b))
-> Maybe (XRelay b) -> MaybeT m (XRelay b)
forall a b. (a -> b) -> a -> b
$ BackendSchema b => Maybe (XRelay b)
forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b
SelPermInfo b
selectPermissions <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectionSetParser <- (Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.nonNullableParser (MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> (m (Maybe
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> m (Maybe
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (Maybe
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> m (Maybe
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b
-> m (Maybe
(Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
m (FieldParser n (ConnectionSelectExp b))
-> MaybeT m (FieldParser n (ConnectionSelectExp b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (FieldParser n (ConnectionSelectExp b))
-> MaybeT m (FieldParser n (ConnectionSelectExp b)))
-> m (FieldParser n (ConnectionSelectExp b))
-> MaybeT m (FieldParser n (ConnectionSelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> m (FieldParser n (ConnectionSelectExp b))
-> 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) -> 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
-> SourceInfo b
-> TableInfo b
-> 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
-> SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice))
tableConnectionArgs PrimaryKeyColumns b
pkeyColumns SourceInfo b
sourceInfo TableInfo b
tableInfo
pure $
Name
-> Maybe Description
-> InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice)
-> Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> FieldParser
MetadataObjId
n
((SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice),
Fields
(ConnectionField
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
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice)
selectArgsParser Parser
MetadataObjId
'Output
n
(Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
selectionSetParser
FieldParser
MetadataObjId
n
((SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice),
Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
-> (((SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice),
Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue 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), Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
fields) ->
ConnectionSelect :: forall (b :: BackendType) r v.
XRelay b
-> PrimaryKeyColumns b
-> Maybe (NonEmpty (ConnectionSplit b v))
-> Maybe ConnectionSlice
-> AnnSelectG b (ConnectionField b r) v
-> ConnectionSelect b r v
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 =
AnnSelectG :: forall (b :: BackendType) (f :: * -> *) v.
Fields (f v)
-> SelectFromG b v
-> TablePermG b v
-> SelectArgsG b v
-> StringifyNumbers
-> Maybe NamingCase
-> AnnSelectG b f v
IR.AnnSelectG
{ $sel:_asnFields:AnnSelectG :: Fields
(ConnectionField
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
IR._asnFields = Fields
(ConnectionField
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 :: 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
}
}
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
selectTableByPk ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (SelectExp b)))
selectTableByPk :: SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp b)))
selectTableByPk SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT m (FieldParser n (SelectExp b))
-> m (Maybe (FieldParser n (SelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPermissions <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
NESeq (ColumnInfo b)
primaryKeys <- Maybe (NESeq (ColumnInfo b)) -> MaybeT m (NESeq (ColumnInfo b))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (NESeq (ColumnInfo b)) -> MaybeT m (NESeq (ColumnInfo b)))
-> Maybe (NESeq (ColumnInfo b)) -> MaybeT 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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b)
forall (b :: BackendType) a1. PrimaryKey b a1 -> NESeq a1
_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 primaryKeyColumn1.
TableCoreInfoG b field primaryKeyColumn1
-> Maybe (PrimaryKey b primaryKeyColumn1)
_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 <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ColumnInfo b -> Bool) -> NESeq (ColumnInfo b) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\ColumnInfo b
c -> ColumnInfo b -> Column b
forall (b :: BackendType). ColumnInfo b -> Column b
ciColumn ColumnInfo b
c Column b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`Map.member` SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
forall (b :: BackendType).
SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiCols SelPermInfo b
selectPermissions) NESeq (ColumnInfo b)
primaryKeys
m (FieldParser n (SelectExp b))
-> MaybeT m (FieldParser n (SelectExp b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (FieldParser n (SelectExp b))
-> MaybeT m (FieldParser n (SelectExp b)))
-> m (FieldParser n (SelectExp b))
-> MaybeT m (FieldParser n (SelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> m (FieldParser n (SelectExp b))
-> 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 (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> 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)
sequenceA (NESeq
(InputFieldsParser
MetadataObjId n (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
-> m (NESeq
(InputFieldsParser
MetadataObjId
n
(GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
-> 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
-> m (InputFieldsParser
MetadataObjId
n
(GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))))
-> 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
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) (Bool -> Nullability
G.Nullability (Bool -> Nullability) -> Bool -> Nullability
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Bool
forall (b :: BackendType). ColumnInfo b -> Bool
ciIsNullable ColumnInfo b
columnInfo)
pure $
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 (f :: * -> *) a. Applicative f => a -> f a
pure (OpExpG b (UnpreparedValue b) -> [OpExpG b (UnpreparedValue b)])
-> (ValueWithOrigin (ColumnValue b)
-> OpExpG b (UnpreparedValue b))
-> ValueWithOrigin (ColumnValue b)
-> [OpExpG b (UnpreparedValue b)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> UnpreparedValue b -> OpExpG b (UnpreparedValue b)
forall (backend :: BackendType) field.
Bool -> field -> OpExpG backend field
AEQ Bool
True (UnpreparedValue b -> OpExpG b (UnpreparedValue b))
-> (ValueWithOrigin (ColumnValue b) -> UnpreparedValue b)
-> ValueWithOrigin (ColumnValue b)
-> OpExpG b (UnpreparedValue b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter
(ValueWithOrigin (ColumnValue b)
-> 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 -> MetadataObjId
MOSource (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo)) (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 :: TablePerms b
defaultPerms = SelPermInfo b -> TablePerms b
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions
permissions :: TablePerms b
permissions = TablePerms 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 (t :: * -> *) a. Foldable t => t a -> [a]
toList NESeq (GBoolExp b (AnnBoolExpFld b (UnpreparedValue b)))
boolExpr
in AnnSelectG :: forall (b :: BackendType) (f :: * -> *) v.
Fields (f v)
-> SelectFromG b v
-> TablePermG b v
-> SelectArgsG b v
-> StringifyNumbers
-> Maybe NamingCase
-> AnnSelectG b f v
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 :: TablePerms b
IR._asnPerm = TablePerms 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
}
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
defaultSelectTableAggregate ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b ->
TableInfo b ->
G.Name ->
Maybe G.Description ->
m (Maybe (FieldParser n (AggSelectExp b)))
defaultSelectTableAggregate :: SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp b)))
defaultSelectTableAggregate SourceInfo b
sourceInfo TableInfo b
tableInfo Name
fieldName Maybe Description
description = MaybeT m (FieldParser n (AggSelectExp b))
-> m (Maybe (FieldParser n (AggSelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT m (FieldParser n (AggSelectExp b))
-> m (Maybe (FieldParser n (AggSelectExp b))))
-> MaybeT m (FieldParser n (AggSelectExp b))
-> m (Maybe (FieldParser n (AggSelectExp b)))
forall a b. (a -> b) -> a -> b
$ do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SelPermInfo b
selectPermissions <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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 m (XNodesAgg b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (XNodesAgg b) -> MaybeT m (XNodesAgg b))
-> Maybe (XNodesAgg b) -> MaybeT m (XNodesAgg b)
forall a b. (a -> b) -> a -> b
$ BackendSchema b => Maybe (XNodesAgg b)
forall (b :: BackendType). BackendSchema b => Maybe (XNodesAgg b)
nodesAggExtension @b
Parser 'Output n (AnnotatedFields b)
nodesParser <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall r (m :: * -> *) (n :: * -> *) (b :: BackendType).
(MonadBuildSchemaBase r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList SourceInfo b
sourceInfo TableInfo b
tableInfo
m (FieldParser n (AggSelectExp b))
-> MaybeT m (FieldParser n (AggSelectExp b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (FieldParser n (AggSelectExp b))
-> MaybeT m (FieldParser n (AggSelectExp b)))
-> m (FieldParser n (AggSelectExp b))
-> MaybeT m (FieldParser n (AggSelectExp b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b, Name)
-> m (FieldParser n (AggSelectExp b))
-> 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 (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName, Name
fieldName) do
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> 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 -> 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 <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (SelectArgsG b (UnpreparedValue b)))
tableArguments SourceInfo b
sourceInfo TableInfo b
tableInfo
Parser 'Output n (AggregateFields b)
aggregateParser <- SourceInfo b
-> TableInfo b -> m (Parser 'Output n (AggregateFields b))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b -> m (Parser 'Output n (AggregateFields b))
tableAggregationFields SourceInfo b
sourceInfo TableInfo b
tableInfo
Name
selectionName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateTypeName GQLNameIdentifier
tableGQLName
let 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 a.
Parser origin 'Output m a -> Parser origin 'Output 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)
[ 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
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AggregateFields b -> TableAggregateFieldG b r v
IR.TAFAgg (AggregateFields b
-> TableAggregateFieldG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> FieldParser MetadataObjId n (AggregateFields 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)
-> FieldParser MetadataObjId n (AggregateFields 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)
aggregateParser
]
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 -> MetadataObjId
MOSource (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo)) (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) ->
AnnSelectG :: forall (b :: BackendType) (f :: * -> *) v.
Fields (f v)
-> SelectFromG b v
-> TablePermG b v
-> SelectArgsG b v
-> StringifyNumbers
-> Maybe NamingCase
-> AnnSelectG b f v
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
}
where
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
defaultTableSelectionSet ::
forall b r m n.
( AggregationPredicatesSchema b,
BackendTableSelectSchema b,
Eq (AnnBoolExp b (IR.UnpreparedValue b)),
MonadBuildSchema b r m n
) =>
SourceInfo b ->
TableInfo b ->
m (Maybe (Parser 'Output n (AnnotatedFields b)))
defaultTableSelectionSet :: SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
defaultTableSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo = MaybeT m (Parser 'Output n (AnnotatedFields b))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
SelPermInfo b
_selectPermissions <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
SchemaKind
schemaKind <- m SchemaKind -> MaybeT m SchemaKind
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m SchemaKind -> MaybeT m SchemaKind)
-> m SchemaKind -> MaybeT m SchemaKind
forall a b. (a -> b) -> a -> b
$ (SchemaContext -> SchemaKind) -> m SchemaKind
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> SchemaKind
scSchemaKind
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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 (BackendSchema b => Maybe (XRelay b)
forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b)
m (Parser 'Output n (AnnotatedFields b))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Output n (AnnotatedFields b))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Parser 'Output n (AnnotatedFields b))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b)
-> m (Parser 'Output n (AnnotatedFields b))
-> 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 -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
Name
objectTypename <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase GQLNameIdentifier
tableGQLName
let xRelay :: Maybe (XRelay b)
xRelay = BackendSchema b => Maybe (XRelay b)
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]
Map.elems (HashMap FieldName (FieldInfo b) -> [FieldInfo b])
-> HashMap FieldName (FieldInfo b) -> [FieldInfo b]
forall a b. (a -> b) -> a -> b
$ TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> HashMap FieldName (FieldInfo b)
forall (b :: BackendType) field primaryKeyColumn1.
TableCoreInfoG b field primaryKeyColumn1 -> FieldInfoMap field
_tciFieldInfoMap TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
tableCoreInfo
tablePkeyColumns :: Maybe (NESeq (ColumnInfo b))
tablePkeyColumns = PrimaryKey b (ColumnInfo b) -> NESeq (ColumnInfo b)
forall (b :: BackendType) a1. PrimaryKey b a1 -> NESeq a1
_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
<$> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Maybe (PrimaryKey b (ColumnInfo b))
forall (b :: BackendType) field primaryKeyColumn1.
TableCoreInfoG b field primaryKeyColumn1
-> Maybe (PrimaryKey b primaryKeyColumn1)
_tciPrimaryKey TableCoreInfoG b (FieldInfo b) (ColumnInfo 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 (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 (TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Maybe ApolloFederationConfig
forall (b :: BackendType) field primaryKeyColumn1.
TableCoreInfoG b field primaryKeyColumn1
-> Maybe ApolloFederationConfig
_tciApolloFederationConfig TableCoreInfoG b (FieldInfo b) (ColumnInfo 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 (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
Map.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
PG.getPGDescription (PGDescription -> Description)
-> Maybe PGDescription -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
-> Maybe PGDescription
forall (b :: BackendType) field primaryKeyColumn1.
TableCoreInfoG b field primaryKeyColumn1 -> Maybe PGDescription
_tciDescription TableCoreInfoG b (FieldInfo b) (ColumnInfo 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)])
-> m [[FieldParser n (AnnotatedField b)]]
-> m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FieldInfo b]
-> (FieldInfo b -> m [FieldParser n (AnnotatedField b)])
-> 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
(SourceInfo b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> 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) =>
SourceInfo b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> m [FieldParser n (AnnotatedField b)]
fieldSelection SourceInfo b
sourceInfo 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]
Parser 'Output n NodeMap
nodeInterface <- NodeInterfaceParserBuilder
-> forall r (n :: * -> *) (m :: * -> *).
MonadBuildSchemaBase r m n =>
m (Parser 'Output n NodeMap)
runNodeBuilder NodeInterfaceParserBuilder
nodeBuilder
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)
-> m (Parser 'Output n (AnnotatedFields b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser 'Output n (AnnotatedFields b)
-> m (Parser 'Output n (AnnotatedFields b)))
-> Parser 'Output n (AnnotatedFields b)
-> 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
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 :: TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
tableCoreInfo = TableInfo b -> TableCoreInfoG b (FieldInfo b) (ColumnInfo b)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo b
tableInfo
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
P.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 ::
(MonadBuildSchemaBase r m n, BackendTableSelectSchema b) =>
SourceInfo b ->
TableInfo b ->
m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList :: SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList SourceInfo b
sourceInfo 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 (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)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
nonNullableObjectList :: Parser 'Output m a -> Parser 'Output m a
nonNullableObjectList :: Parser 'Output m a -> Parser 'Output m a
nonNullableObjectList =
Parser 'Output m a -> Parser 'Output m a
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.nonNullableParser (Parser 'Output m a -> Parser 'Output m a)
-> (Parser 'Output m a -> Parser 'Output m a)
-> Parser 'Output m a
-> Parser 'Output m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser 'Output m a -> Parser 'Output m a
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.multiple (Parser 'Output m a -> Parser 'Output m a)
-> (Parser 'Output m a -> Parser 'Output m a)
-> Parser 'Output m a
-> Parser 'Output m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser 'Output m a -> Parser 'Output m a
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.nonNullableParser
tableConnectionSelectionSet ::
forall b r m n.
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b ->
TableInfo b ->
m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet :: SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (ConnectionFields b)))
tableConnectionSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo = MaybeT m (Parser 'Output n (ConnectionFields b))
-> m (Maybe (Parser 'Output n (ConnectionFields b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
GQLNameIdentifier
tableIdentifierName <- m GQLNameIdentifier -> MaybeT m GQLNameIdentifier
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m GQLNameIdentifier -> MaybeT m GQLNameIdentifier)
-> m GQLNameIdentifier -> MaybeT m GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ TableInfo b -> 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 m (SelPermInfo b) -> MaybeT m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MaybeT m (SelPermInfo b) -> MaybeT m ())
-> MaybeT m (SelPermInfo b) -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
Parser 'Output n (EdgeFields b)
edgesParser <- m (Maybe (Parser 'Output n (EdgeFields b)))
-> MaybeT m (Parser 'Output n (EdgeFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (EdgeFields b)))
-> MaybeT m (Parser 'Output n (EdgeFields b)))
-> m (Maybe (Parser 'Output n (EdgeFields b)))
-> MaybeT m (Parser 'Output n (EdgeFields b))
forall a b. (a -> b) -> a -> b
$ Name -> m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet Name
tableGQLName
m (Parser 'Output n (ConnectionFields b))
-> MaybeT m (Parser 'Output n (ConnectionFields b))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Output n (ConnectionFields b))
-> MaybeT m (Parser 'Output n (ConnectionFields b)))
-> m (Parser 'Output n (ConnectionFields b))
-> MaybeT m (Parser 'Output n (ConnectionFields b))
forall a b. (a -> b) -> a -> b
$ Name
-> (SourceName, TableName b)
-> m (Parser 'Output n (ConnectionFields b))
-> 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 (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableName b
tableName) do
Name
connectionTypeName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m Name
forall a b. (a -> b) -> a -> b
$ Name
tableGQLName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name._Connection
let 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)
-> m (Parser 'Output n (ConnectionFields b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser 'Output n (ConnectionFields b)
-> m (Parser 'Output n (ConnectionFields b)))
-> Parser 'Output n (ConnectionFields b)
-> 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 a.
Parser origin 'Output m a -> Parser origin 'Output 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
tableName :: TableName b
tableName = TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo
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 a.
Parser origin 'Output m a -> Parser origin 'Output 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 -> m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet :: Name -> m (Maybe (Parser 'Output n (EdgeFields b)))
tableEdgesSelectionSet Name
tableGQLName = MaybeT m (Parser 'Output n (EdgeFields b))
-> 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 <- m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser MetadataObjId 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> MaybeT 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 (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 a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.nonNullableParser (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b))
-> Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo b
-> TableInfo b
-> m (Maybe (Parser MetadataObjId 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet SourceInfo b
sourceInfo TableInfo b
tableInfo
Name
edgesType <- m Name -> MaybeT m Name
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m Name -> MaybeT m Name) -> m Name -> MaybeT m Name
forall a b. (a -> b) -> a -> b
$ Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m Name
forall a b. (a -> b) -> a -> b
$ Name
tableGQLName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name._Edge
let 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 m (Parser 'Output n (EdgeFields b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser 'Output n (EdgeFields b)
-> MaybeT m (Parser 'Output n (EdgeFields b)))
-> Parser 'Output n (EdgeFields b)
-> MaybeT 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) =>
SourceInfo b ->
TableInfo b ->
m (InputFieldsParser n (SelectArgs b))
defaultTableArgs :: SourceInfo b
-> TableInfo b -> m (InputFieldsParser n (SelectArgs b))
defaultTableArgs SourceInfo b
sourceInfo TableInfo b
tableInfo = do
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (AnnBoolExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, MonadBuildSchema b r m n) =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser MetadataObjId n (Maybe (NonEmpty (Column b)))
distinctParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
MetadataObjId n (Maybe (NonEmpty (Column b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (Maybe (NonEmpty (Column b))))
tableDistinctArg SourceInfo b
sourceInfo TableInfo b
tableInfo
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 (Column b))
distinctArg <- InputFieldsParser MetadataObjId n (Maybe (NonEmpty (Column b)))
distinctParser
pure $
SelectArgs :: forall (b :: BackendType) v.
Maybe (AnnBoolExp b v)
-> Maybe (NonEmpty (AnnotatedOrderByItemG b v))
-> Maybe Int
-> Maybe Int64
-> Maybe (NonEmpty (Column b))
-> SelectArgsG b v
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 (Column b))
IR._saDistinct = Maybe (NonEmpty (Column b))
distinctArg
}
InputFieldsParser n (SelectArgs b)
-> m (InputFieldsParser n (SelectArgs b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser n (SelectArgs b)
-> m (InputFieldsParser n (SelectArgs b)))
-> InputFieldsParser n (SelectArgs b)
-> 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 (Column b)
distinct <- SelectArgs b -> Maybe (NonEmpty (Column b))
forall (b :: BackendType) v.
SelectArgsG b v -> Maybe (NonEmpty (Column b))
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 (Column b) -> n ()
forall (t :: * -> *) (b :: BackendType) (f :: * -> *)
(b :: BackendType) v.
(Foldable t, Eq (Column b), MonadParse f) =>
NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
-> t (Column b) -> f ()
validateArgs NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
orderBy NonEmpty (Column b)
distinct
pure SelectArgs b
args
where
validateArgs :: NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
-> t (Column b) -> f ()
validateArgs NonEmpty (OrderByItemG b (AnnotatedOrderByElement b v))
orderByCols t (Column b)
distinctCols = do
let colsLen :: Int
colsLen = t (Column b) -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t (Column b)
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 (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 -> 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 (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 (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Column b]
initOrdByCols) (t (Column b) -> [Column b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList t (Column b)
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"
tableWhereArg ::
forall b r m n.
( AggregationPredicatesSchema b,
MonadBuildSchema b r m n
) =>
SourceInfo b ->
TableInfo b ->
m (InputFieldsParser n (Maybe (IR.AnnBoolExp b (IR.UnpreparedValue b))))
tableWhereArg :: SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg SourceInfo b
sourceInfo TableInfo b
tableInfo = do
Parser 'Input n (AnnBoolExp b (UnpreparedValue b))
boolExpParser <- SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
boolExp SourceInfo b
sourceInfo TableInfo b
tableInfo
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 (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 =>
SourceInfo b ->
TableInfo b ->
m (InputFieldsParser n (Maybe (NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b)))))
tableOrderByArg :: SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg SourceInfo b
sourceInfo TableInfo b
tableInfo = do
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
Parser 'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)]
orderByParser <- SourceInfo b
-> TableInfo b
-> m (Parser
'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)])
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (Parser
'Input n [AnnotatedOrderByItemG b (UnpreparedValue b)])
orderByExp SourceInfo b
sourceInfo 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))))
-> m (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> m (InputFieldsParser
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))))
-> InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> 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 (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 (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 =>
SourceInfo b ->
TableInfo b ->
m (InputFieldsParser n (Maybe (NonEmpty (Column b))))
tableDistinctArg :: SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (Maybe (NonEmpty (Column b))))
tableDistinctArg SourceInfo b
sourceInfo TableInfo b
tableInfo = do
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
Maybe (Parser MetadataObjId 'Both n (Column b))
columnsEnum <- SourceInfo b
-> TableInfo b
-> m (Maybe (Parser MetadataObjId 'Both n (Column b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(Backend b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Both n (Column b)))
tableSelectColumnsEnum SourceInfo b
sourceInfo 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 (Column b)))
-> m (InputFieldsParser n (Maybe (NonEmpty (Column b))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure do
Maybe [Column b]
maybeDistinctOnColumns <-
Maybe (Maybe [Column b]) -> Maybe [Column b]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Maybe (Maybe [Column b]) -> Maybe [Column b])
-> (Maybe (Maybe (Maybe [Column b])) -> Maybe (Maybe [Column b]))
-> Maybe (Maybe (Maybe [Column b]))
-> Maybe [Column b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Maybe (Maybe [Column b])) -> Maybe (Maybe [Column b])
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
(Maybe (Maybe (Maybe [Column b])) -> Maybe [Column b])
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (Maybe [Column b])))
-> InputFieldsParser MetadataObjId n (Maybe [Column b])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Parser MetadataObjId 'Both n (Column b))
-> (Parser MetadataObjId 'Both n (Column b)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe [Column b])))
-> InputFieldsParser
MetadataObjId n (Maybe (Maybe (Maybe [Column b])))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for
Maybe (Parser MetadataObjId 'Both n (Column b))
columnsEnum
(Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (Maybe [Column b])
-> InputFieldsParser MetadataObjId n (Maybe (Maybe [Column 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 [Column b])
-> InputFieldsParser MetadataObjId n (Maybe (Maybe [Column b])))
-> (Parser MetadataObjId 'Both n (Column b)
-> Parser MetadataObjId 'Both n (Maybe [Column b]))
-> Parser MetadataObjId 'Both n (Column b)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe [Column b]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Both n [Column b]
-> Parser MetadataObjId 'Both n (Maybe [Column 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 [Column b]
-> Parser MetadataObjId 'Both n (Maybe [Column b]))
-> (Parser MetadataObjId 'Both n (Column b)
-> Parser MetadataObjId 'Both n [Column b])
-> Parser MetadataObjId 'Both n (Column b)
-> Parser MetadataObjId 'Both n (Maybe [Column b])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Both n (Column b)
-> Parser MetadataObjId 'Both n [Column 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 [Column b]
maybeDistinctOnColumns Maybe [Column b]
-> ([Column b] -> Maybe (NonEmpty (Column b)))
-> Maybe (NonEmpty (Column b))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Column b] -> Maybe (NonEmpty (Column b))
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty
tableLimitArg ::
forall n.
MonadParse n =>
InputFieldsParser n (Maybe Int)
tableLimitArg :: InputFieldsParser n (Maybe Int)
tableLimitArg =
(Maybe (Maybe Int32) -> Maybe Int)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
-> InputFieldsParser n (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int32 -> Int) -> Maybe Int32 -> Maybe Int
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 n (Maybe Int))
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int32))
-> InputFieldsParser 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 :: InputFieldsParser n (Maybe Int64)
tableOffsetArg =
(Maybe (Maybe Int64) -> Maybe Int64)
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
-> InputFieldsParser n (Maybe Int64)
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 n (Maybe Int64))
-> InputFieldsParser MetadataObjId n (Maybe (Maybe Int64))
-> InputFieldsParser 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 ->
SourceInfo b ->
TableInfo b ->
m
( InputFieldsParser
n
( SelectArgs b,
Maybe (NonEmpty (IR.ConnectionSplit b (IR.UnpreparedValue b))),
Maybe IR.ConnectionSlice
)
)
tableConnectionArgs :: PrimaryKeyColumns b
-> SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n
(SelectArgs b,
Maybe (NonEmpty (ConnectionSplit b (UnpreparedValue b))),
Maybe ConnectionSlice))
tableConnectionArgs PrimaryKeyColumns b
pkeyColumns SourceInfo b
sourceInfo TableInfo b
tableInfo = do
InputFieldsParser n (Maybe (AnnBoolExp b (UnpreparedValue b)))
whereParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (AnnBoolExp b (UnpreparedValue b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, MonadBuildSchema b r m n) =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg SourceInfo b
sourceInfo 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 (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 (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
-> NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))
forall v.
NonEmpty (AnnotatedOrderByItemG b v)
-> NonEmpty (AnnotatedOrderByItemG b v)
appendPrimaryKeyOrderBy) (InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
-> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> m (InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
-> m (InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg SourceInfo b
sourceInfo TableInfo b
tableInfo
InputFieldsParser MetadataObjId n (Maybe (NonEmpty (Column b)))
distinctParser <- SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
MetadataObjId n (Maybe (NonEmpty (Column b))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (Maybe (NonEmpty (Column b))))
tableDistinctArg SourceInfo b
sourceInfo 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 (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 (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 (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 (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 (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 (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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser
MetadataObjId
n
(Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b))))
orderByParser
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 (Column b))
distinct <- InputFieldsParser MetadataObjId n (Maybe (NonEmpty (Column 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 (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 (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 (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 (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> ConnectionSplitKind
-> ByteString
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
parseConnectionSplit 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 (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 (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 (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 (Column b))
-> SelectArgs b
forall (b :: BackendType) v.
Maybe (AnnBoolExp b v)
-> Maybe (NonEmpty (AnnotatedOrderByItemG b v))
-> Maybe Int
-> Maybe Int64
-> Maybe (NonEmpty (Column b))
-> 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 (Column 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 v) -> NonEmpty (IR.AnnotatedOrderByItemG b v)
appendPrimaryKeyOrderBy :: NonEmpty (AnnotatedOrderByItemG b v)
-> NonEmpty (AnnotatedOrderByItemG b v)
appendPrimaryKeyOrderBy orderBys :: NonEmpty (AnnotatedOrderByItemG b v)
orderBys@(AnnotatedOrderByItemG b v
h NE.:| [AnnotatedOrderByItemG b v]
t) =
let orderByColumnNames :: [Column b]
orderByColumnNames =
NonEmpty (AnnotatedOrderByItemG b v)
orderBys NonEmpty (AnnotatedOrderByItemG b v)
-> Getting
(Endo [Column b]) (NonEmpty (AnnotatedOrderByItemG b v)) (Column b)
-> [Column b]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (AnnotatedOrderByItemG b v
-> Const (Endo [Column b]) (AnnotatedOrderByItemG b v))
-> NonEmpty (AnnotatedOrderByItemG b v)
-> Const (Endo [Column b]) (NonEmpty (AnnotatedOrderByItemG b v))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((AnnotatedOrderByItemG b v
-> Const (Endo [Column b]) (AnnotatedOrderByItemG b v))
-> NonEmpty (AnnotatedOrderByItemG b v)
-> Const (Endo [Column b]) (NonEmpty (AnnotatedOrderByItemG b v)))
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByItemG b v
-> Const (Endo [Column b]) (AnnotatedOrderByItemG b v))
-> Getting
(Endo [Column b]) (NonEmpty (AnnotatedOrderByItemG b v)) (Column b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnotatedOrderByItemG b v -> AnnotatedOrderByElement b v)
-> Optic'
(->)
(Const (Endo [Column b]))
(AnnotatedOrderByItemG b v)
(AnnotatedOrderByElement b v)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to AnnotatedOrderByItemG b v -> AnnotatedOrderByElement b v
forall (b :: BackendType) a. OrderByItemG b a -> a
IR.obiColumn Optic'
(->)
(Const (Endo [Column b]))
(AnnotatedOrderByItemG b v)
(AnnotatedOrderByElement b v)
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByElement b v
-> Const (Endo [Column b]) (AnnotatedOrderByElement b v))
-> (Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByItemG b v
-> Const (Endo [Column b]) (AnnotatedOrderByItemG b v)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnInfo b -> Const (Endo [Column b]) (ColumnInfo b))
-> AnnotatedOrderByElement b v
-> Const (Endo [Column b]) (AnnotatedOrderByElement b v)
forall (b :: BackendType) v.
Prism' (AnnotatedOrderByElement b v) (ColumnInfo b)
IR._AOCColumn ((ColumnInfo b -> Const (Endo [Column b]) (ColumnInfo b))
-> AnnotatedOrderByElement b v
-> Const (Endo [Column b]) (AnnotatedOrderByElement b v))
-> ((Column b -> Const (Endo [Column b]) (Column b))
-> ColumnInfo b -> Const (Endo [Column b]) (ColumnInfo b))
-> (Column b -> Const (Endo [Column b]) (Column b))
-> AnnotatedOrderByElement b v
-> Const (Endo [Column b]) (AnnotatedOrderByElement b v)
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 v]
pkeyOrderBys = ((ColumnInfo b -> Maybe (AnnotatedOrderByItemG b v))
-> [ColumnInfo b] -> [AnnotatedOrderByItemG b v])
-> [ColumnInfo b]
-> (ColumnInfo b -> Maybe (AnnotatedOrderByItemG b v))
-> [AnnotatedOrderByItemG b v]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ColumnInfo b -> Maybe (AnnotatedOrderByItemG b v))
-> [ColumnInfo b] -> [AnnotatedOrderByItemG b v]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe (PrimaryKeyColumns b -> [ColumnInfo b]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList PrimaryKeyColumns b
pkeyColumns) ((ColumnInfo b -> Maybe (AnnotatedOrderByItemG b v))
-> [AnnotatedOrderByItemG b v])
-> (ColumnInfo b -> Maybe (AnnotatedOrderByItemG b v))
-> [AnnotatedOrderByItemG b v]
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 (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Column b]
orderByColumnNames
then Maybe (AnnotatedOrderByItemG b v)
forall a. Maybe a
Nothing
else AnnotatedOrderByItemG b v -> Maybe (AnnotatedOrderByItemG b v)
forall a. a -> Maybe a
Just (AnnotatedOrderByItemG b v -> Maybe (AnnotatedOrderByItemG b v))
-> AnnotatedOrderByItemG b v -> Maybe (AnnotatedOrderByItemG b v)
forall a b. (a -> b) -> a -> b
$ Maybe (BasicOrderType b)
-> AnnotatedOrderByElement b v
-> Maybe (NullsOrderType b)
-> AnnotatedOrderByItemG b v
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 -> AnnotatedOrderByElement b v
forall (b :: BackendType) v.
ColumnInfo b -> AnnotatedOrderByElement b v
IR.AOCColumn ColumnInfo b
columnInfo) Maybe (NullsOrderType b)
forall a. Maybe a
Nothing
in AnnotatedOrderByItemG b v
h AnnotatedOrderByItemG b v
-> [AnnotatedOrderByItemG b v]
-> NonEmpty (AnnotatedOrderByItemG b v)
forall a. a -> [a] -> NonEmpty a
NE.:| ([AnnotatedOrderByItemG b v]
t [AnnotatedOrderByItemG b v]
-> [AnnotatedOrderByItemG b v] -> [AnnotatedOrderByItemG b v]
forall a. Semigroup a => a -> a -> a
<> [AnnotatedOrderByItemG b v]
pkeyOrderBys)
parseConnectionSplit ::
Maybe (NonEmpty (IR.AnnotatedOrderByItemG b (IR.UnpreparedValue b))) ->
IR.ConnectionSplitKind ->
BL.ByteString ->
n (NonEmpty (IR.ConnectionSplit b (IR.UnpreparedValue b)))
parseConnectionSplit :: Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))
-> ConnectionSplitKind
-> ByteString
-> n (NonEmpty (ConnectionSplit b (UnpreparedValue b)))
parseConnectionSplit 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
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
$ ColumnType b -> Value -> Except QErr (ScalarValue b)
forall (m :: * -> *) (b :: BackendType).
(MonadError QErr m, Backend b) =>
ColumnType b -> Value -> m (ScalarValue b)
parseScalarValueColumnType ColumnType b
columnType Value
columnValue
let unresolvedValue :: UnpreparedValue b
unresolvedValue = Maybe VariableInfo -> ColumnValue b -> UnpreparedValue b
forall (b :: BackendType).
Maybe VariableInfo -> ColumnValue b -> UnpreparedValue b
IR.UVParameter Maybe VariableInfo
forall a. Maybe a
Nothing (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 (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 -> AnnotatedOrderByElement b (UnpreparedValue b)
forall (b :: BackendType) v.
ColumnInfo b -> AnnotatedOrderByElement b v
IR.AOCColumn ColumnInfo b
columnInfo) 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
$ ColumnType b -> Value -> Except QErr (ScalarValue b)
forall (m :: * -> *) (b :: BackendType).
(MonadError QErr m, Backend b) =>
ColumnType b -> Value -> m (ScalarValue b)
parseScalarValueColumnType ColumnType b
columnType Value
orderByItemValue
let unresolvedValue :: UnpreparedValue b
unresolvedValue = Maybe VariableInfo -> ColumnValue b -> UnpreparedValue b
forall (b :: BackendType).
Maybe VariableInfo -> ColumnValue b -> UnpreparedValue b
IR.UVParameter Maybe VariableInfo
forall a. Maybe a
Nothing (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 (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 (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 -> [Text]
mkAggregateOrderByPath = \case
AnnotatedAggregateOrderBy b
IR.AAOCount -> [Text
"count"]
IR.AAOOp Text
t ColumnInfo b
col -> [Text
t, 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
col]
getPathFromOrderBy :: AnnotatedOrderByElement b (UnpreparedValue b) -> [Text]
getPathFromOrderBy = \case
IR.AOCColumn ColumnInfo b
columnInfo ->
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
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 -> [Text]
mkAggregateOrderByPath AnnotatedAggregateOrderBy 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
_ -> [Text
fieldNameText]
IR.CFOBETableAggregation TableName b
_ AnnBoolExp b (UnpreparedValue b)
_ AnnotatedAggregateOrderBy 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 -> [Text]
mkAggregateOrderByPath AnnotatedAggregateOrderBy b
aggOb
getOrderByColumnType :: AnnotatedOrderByElement b (UnpreparedValue b) -> ColumnType b
getOrderByColumnType = \case
IR.AOCColumn ColumnInfo b
columnInfo -> 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
aggOb -> AnnotatedAggregateOrderBy b -> ColumnType b
aggregateOrderByColumnType AnnotatedAggregateOrderBy 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 -> 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
aggOb -> AnnotatedAggregateOrderBy b -> ColumnType b
aggregateOrderByColumnType AnnotatedAggregateOrderBy b
aggOb
where
aggregateOrderByColumnType :: AnnotatedAggregateOrderBy b -> ColumnType b
aggregateOrderByColumnType = \case
AnnotatedAggregateOrderBy b
IR.AAOCount -> ScalarType b -> ColumnType b
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar (BackendSchema b => ScalarType b
forall (b :: BackendType). BackendSchema b => ScalarType b
aggregateOrderByCountType @b)
IR.AAOOp Text
_ ColumnInfo b
colInfo -> ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
colInfo
tableAggregationFields ::
forall b r m n.
MonadBuildSchema b r m n =>
SourceInfo b ->
TableInfo b ->
m (Parser 'Output n (IR.AggregateFields b))
tableAggregationFields :: SourceInfo b
-> TableInfo b -> m (Parser 'Output n (AggregateFields b))
tableAggregationFields SourceInfo b
sourceInfo TableInfo b
tableInfo =
Name
-> (SourceName, TableName b)
-> m (Parser 'Output n (AggregateFields b))
-> m (Parser 'Output n (AggregateFields 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 (SourceInfo b -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo b
sourceInfo, TableInfo b -> TableName b
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo b
tableInfo) do
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
GQLNameIdentifier
tableGQLName <- TableInfo b -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo b
tableInfo
[ColumnInfo b]
allColumns <- SourceInfo b -> TableInfo b -> m [ColumnInfo b]
forall (b :: BackendType) r (m :: * -> *).
(Backend b, MonadError QErr m, MonadReader r m,
Has SchemaContext r) =>
SourceInfo b -> TableInfo b -> m [ColumnInfo b]
tableSelectColumns SourceInfo b
sourceInfo TableInfo b
tableInfo
let numericColumns :: [ColumnInfo b]
numericColumns = [ColumnInfo b] -> [ColumnInfo b]
forall (b :: BackendType).
Backend b =>
[ColumnInfo b] -> [ColumnInfo b]
onlyNumCols [ColumnInfo b]
allColumns
comparableColumns :: [ColumnInfo b]
comparableColumns = [ColumnInfo b] -> [ColumnInfo b]
forall (b :: BackendType).
Backend b =>
[ColumnInfo b] -> [ColumnInfo b]
onlyComparableCols [ColumnInfo b]
allColumns
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
Name
selectName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateFieldTypeName GQLNameIdentifier
tableGQLName
FieldParser n (AggregateField b)
count <- m (FieldParser n (AggregateField b))
countField
MkTypename
makeTypename <- (r -> MkTypename) -> m MkTypename
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> MkTypename
forall a t. Has a t => t -> a
getter
[FieldParser n (AggregateField b)]
numericAndComparable <-
([[FieldParser n (AggregateField b)]]
-> [FieldParser n (AggregateField b)])
-> m [[FieldParser n (AggregateField b)]]
-> m [FieldParser n (AggregateField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[FieldParser n (AggregateField b)]]
-> [FieldParser n (AggregateField b)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (m [[FieldParser n (AggregateField b)]]
-> m [FieldParser n (AggregateField b)])
-> m [[FieldParser n (AggregateField b)]]
-> m [FieldParser n (AggregateField b)]
forall a b. (a -> b) -> a -> b
$
[m [FieldParser n (AggregateField b)]]
-> m [[FieldParser n (AggregateField b)]]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([m [FieldParser n (AggregateField b)]]
-> m [[FieldParser n (AggregateField b)]])
-> [m [FieldParser n (AggregateField b)]]
-> m [[FieldParser n (AggregateField b)]]
forall a b. (a -> b) -> a -> b
$
[Maybe (m [FieldParser n (AggregateField b)])]
-> [m [FieldParser n (AggregateField b)]]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[
if [ColumnInfo b] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ColumnInfo b]
numericColumns
then Maybe (m [FieldParser n (AggregateField b)])
forall a. Maybe a
Nothing
else m [FieldParser n (AggregateField b)]
-> Maybe (m [FieldParser n (AggregateField b)])
forall a. a -> Maybe a
Just (m [FieldParser n (AggregateField b)]
-> Maybe (m [FieldParser n (AggregateField b)]))
-> m [FieldParser n (AggregateField b)]
-> Maybe (m [FieldParser n (AggregateField b)])
forall a b. (a -> b) -> a -> b
$
[Name]
-> (Name -> m (FieldParser n (AggregateField b)))
-> m [FieldParser n (AggregateField b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a -> (a -> f b) -> f (t b)
for [Name]
numericAggOperators ((Name -> m (FieldParser n (AggregateField b)))
-> m [FieldParser n (AggregateField b)])
-> (Name -> m (FieldParser n (AggregateField b)))
-> m [FieldParser n (AggregateField b)]
forall a b. (a -> b) -> a -> b
$ \Name
operator -> do
let fieldNameCase :: Name
fieldNameCase = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
tCase Name
operator
[FieldParser n (ColFld b)]
numFields <- Name -> [ColumnInfo b] -> m [FieldParser n (ColFld b)]
mkNumericAggFields Name
operator [ColumnInfo b]
numericColumns
pure $ MkTypename
-> Name
-> Name
-> NamingCase
-> GQLNameIdentifier
-> [FieldParser n (ColFld b)]
-> FieldParser n (AggregateField b)
parseAggOperator MkTypename
makeTypename Name
operator Name
fieldNameCase NamingCase
tCase GQLNameIdentifier
tableGQLName [FieldParser n (ColFld b)]
numFields,
if [ColumnInfo b] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ColumnInfo b]
comparableColumns
then Maybe (m [FieldParser n (AggregateField b)])
forall a. Maybe a
Nothing
else m [FieldParser n (AggregateField b)]
-> Maybe (m [FieldParser n (AggregateField b)])
forall a. a -> Maybe a
Just (m [FieldParser n (AggregateField b)]
-> Maybe (m [FieldParser n (AggregateField b)]))
-> m [FieldParser n (AggregateField b)]
-> Maybe (m [FieldParser n (AggregateField b)])
forall a b. (a -> b) -> a -> b
$ do
[FieldParser n (ColFld b)]
comparableFields <- (ColumnInfo b -> m (FieldParser n (ColFld b)))
-> [ColumnInfo b] -> m [FieldParser n (ColFld b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ColumnInfo b -> m (FieldParser n (ColFld b))
mkColumnAggField [ColumnInfo b]
comparableColumns
pure $
[Name]
comparisonAggOperators [Name]
-> ([Name] -> [FieldParser n (AggregateField b)])
-> [FieldParser n (AggregateField b)]
forall a b. a -> (a -> b) -> b
& (Name -> FieldParser n (AggregateField b))
-> [Name] -> [FieldParser n (AggregateField b)]
forall a b. (a -> b) -> [a] -> [b]
map \Name
operator ->
let fieldNameCase :: Name
fieldNameCase = NamingCase -> Name -> Name
applyFieldNameCaseCust NamingCase
tCase Name
operator
in MkTypename
-> Name
-> Name
-> NamingCase
-> GQLNameIdentifier
-> [FieldParser n (ColFld b)]
-> FieldParser n (AggregateField b)
parseAggOperator MkTypename
makeTypename Name
operator Name
fieldNameCase NamingCase
tCase GQLNameIdentifier
tableGQLName [FieldParser n (ColFld b)]
comparableFields
]
let aggregateFields :: [FieldParser n (AggregateField b)]
aggregateFields = FieldParser n (AggregateField b)
count FieldParser n (AggregateField b)
-> [FieldParser n (AggregateField b)]
-> [FieldParser n (AggregateField b)]
forall a. a -> [a] -> [a]
: [FieldParser n (AggregateField b)]
numericAndComparable
pure $
Name
-> Maybe Description
-> [FieldParser n (AggregateField b)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (AggregateField 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)]
aggregateFields
Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (AggregateField b)))
-> (InsOrdHashMap Name (ParsedSelection (AggregateField b))
-> AggregateFields b)
-> Parser 'Output n (AggregateFields b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> AggregateField b)
-> InsOrdHashMap Name (ParsedSelection (AggregateField b))
-> AggregateFields b
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> AggregateField b
forall (b :: BackendType). Text -> AggregateField b
IR.AFExp
where
mkNumericAggFields :: G.Name -> [ColumnInfo b] -> m [FieldParser n (IR.ColFld b)]
mkNumericAggFields :: Name -> [ColumnInfo b] -> m [FieldParser n (ColFld b)]
mkNumericAggFields Name
name
| Name
name Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
Name._sum = (ColumnInfo b -> m (FieldParser n (ColFld b)))
-> [ColumnInfo b] -> m [FieldParser n (ColFld b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ColumnInfo b -> m (FieldParser n (ColFld b))
mkColumnAggField
| Bool
otherwise = (ColumnInfo b -> m (FieldParser n (ColFld b)))
-> [ColumnInfo b] -> m [FieldParser n (ColFld b)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse \ColumnInfo b
columnInfo ->
FieldParser n (ColFld b) -> m (FieldParser n (ColFld b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser n (ColFld b) -> m (FieldParser n (ColFld b)))
-> FieldParser n (ColFld b) -> m (FieldParser n (ColFld b))
forall a b. (a -> b) -> a -> b
$
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 ()
-> ColFld b -> FieldParser n (ColFld b)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Column b -> ColumnType b -> ColFld b
forall (b :: BackendType). Column b -> ColumnType b -> ColFld b
IR.CFCol (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)
mkColumnAggField :: ColumnInfo b -> m (FieldParser n (IR.ColFld b))
mkColumnAggField :: ColumnInfo b -> m (FieldParser n (ColFld b))
mkColumnAggField ColumnInfo b
columnInfo = do
Parser 'Both n (ValueWithOrigin (ColumnValue b))
field <- ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) (Bool -> Nullability
G.Nullability Bool
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 ()
-> ColFld b -> FieldParser n (ColFld b)
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> Column b -> ColumnType b -> ColFld b
forall (b :: BackendType). Column b -> ColumnType b -> ColFld b
IR.CFCol (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)
countField :: m (FieldParser n (IR.AggregateField b))
countField :: m (FieldParser n (AggregateField b))
countField = do
Maybe (Parser 'Both n (Column b))
columnsEnum <- SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Both n (Column b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(Backend b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Both n (Column b)))
tableSelectColumnsEnum SourceInfo b
sourceInfo TableInfo b
tableInfo
let distinctName :: Name
distinctName = Name
Name._distinct
args :: InputFieldsParser MetadataObjId n (CountType 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
mkCountType <- Maybe (Parser 'Both n (Column b))
-> InputFieldsParser MetadataObjId n (CountDistinct -> CountType b)
forall (b :: BackendType) (n :: * -> *).
(BackendSchema b, MonadParse n) =>
Maybe (Parser 'Both n (Column b))
-> InputFieldsParser n (CountDistinct -> CountType b)
countTypeInput @b Maybe (Parser 'Both n (Column b))
columnsEnum
pure $
CountDistinct -> CountType b
mkCountType (CountDistinct -> CountType b) -> CountDistinct -> CountType 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)
-> m (FieldParser n (AggregateField b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FieldParser n (AggregateField b)
-> m (FieldParser n (AggregateField b)))
-> FieldParser n (AggregateField b)
-> m (FieldParser n (AggregateField b))
forall a b. (a -> b) -> a -> b
$ CountType b -> AggregateField b
forall (b :: BackendType). CountType b -> AggregateField b
IR.AFCount (CountType b -> AggregateField b)
-> FieldParser MetadataObjId n (CountType b)
-> FieldParser n (AggregateField b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> InputFieldsParser MetadataObjId n (CountType b)
-> Parser MetadataObjId 'Both n Int32
-> FieldParser MetadataObjId n (CountType 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)
args Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int
parseAggOperator ::
MkTypename ->
G.Name ->
G.Name ->
NamingCase ->
GQLNameIdentifier ->
[FieldParser n (IR.ColFld b)] ->
FieldParser n (IR.AggregateField b)
parseAggOperator :: MkTypename
-> Name
-> Name
-> NamingCase
-> GQLNameIdentifier
-> [FieldParser n (ColFld b)]
-> FieldParser n (AggregateField b)
parseAggOperator MkTypename
makeTypename Name
operator Name
fieldName NamingCase
tCase GQLNameIdentifier
tableGQLName [FieldParser n (ColFld b)]
columns =
let opText :: Text
opText = Name -> Text
G.unName Name
operator
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 -> Name -> GQLNameIdentifier
mkTableAggOperatorTypeName GQLNameIdentifier
tableGQLName Name
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 (ColFld b))
subselectionParser =
Name
-> Maybe Description
-> [FieldParser n (ColFld b)]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (ColFld 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 (ColFld b)]
columns
Parser
MetadataObjId
'Output
n
(InsOrdHashMap Name (ParsedSelection (ColFld b)))
-> (InsOrdHashMap Name (ParsedSelection (ColFld b))
-> Fields (ColFld b))
-> Parser MetadataObjId 'Output n (Fields (ColFld b))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> ColFld b)
-> InsOrdHashMap Name (ParsedSelection (ColFld b))
-> Fields (ColFld b)
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text -> ColFld b
forall (b :: BackendType). Text -> ColFld b
IR.CFExp
in Name
-> Maybe Description
-> Parser MetadataObjId 'Output n (Fields (ColFld b))
-> FieldParser MetadataObjId n (Fields (ColFld b))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> Parser origin 'Output m a
-> FieldParser origin m a
P.subselection_ Name
fieldName Maybe Description
forall a. Maybe a
Nothing Parser MetadataObjId 'Output n (Fields (ColFld b))
subselectionParser
FieldParser MetadataObjId n (Fields (ColFld b))
-> (Fields (ColFld b) -> AggregateField b)
-> FieldParser n (AggregateField b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> AggregateOp b -> AggregateField b
forall (b :: BackendType). AggregateOp b -> AggregateField b
IR.AFOp (AggregateOp b -> AggregateField b)
-> (Fields (ColFld b) -> AggregateOp b)
-> Fields (ColFld b)
-> AggregateField b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Fields (ColFld b) -> AggregateOp b
forall (b :: BackendType). Text -> ColumnFields b -> AggregateOp b
IR.AggregateOp Text
opText
fieldSelection ::
forall b r m n.
( AggregationPredicatesSchema b,
BackendTableSelectSchema b,
Eq (AnnBoolExp b (IR.UnpreparedValue b)),
MonadBuildSchema b r m n
) =>
SourceInfo b ->
TableName b ->
TableInfo b ->
FieldInfo b ->
m [FieldParser n (AnnotatedField b)]
fieldSelection :: SourceInfo b
-> TableName b
-> TableInfo b
-> FieldInfo b
-> m [FieldParser n (AnnotatedField b)]
fieldSelection SourceInfo b
sourceInfo TableName b
table TableInfo b
tableInfo = \case
FIColumn 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)])
-> m (Maybe (FieldParser n (AnnotatedField b)))
-> m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MaybeT m (FieldParser n (AnnotatedField b))
-> m (Maybe (FieldParser n (AnnotatedField b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
SchemaKind
schemaKind <- (SchemaContext -> SchemaKind) -> MaybeT 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 m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT 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 m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ Column b
columnName Column b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
`Map.member` SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
forall (b :: BackendType).
SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiCols SelPermInfo b
selectPermissions
let caseBoolExp :: Maybe (AnnColumnCaseBoolExpPartialSQL b)
caseBoolExp = Maybe (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Maybe (AnnColumnCaseBoolExpPartialSQL b)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Maybe (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Maybe (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Maybe (AnnColumnCaseBoolExpPartialSQL b)
forall a b. (a -> b) -> a -> b
$ Column b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
-> Maybe (Maybe (AnnColumnCaseBoolExpPartialSQL b))
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup Column b
columnName (SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
forall (b :: BackendType).
SelPermInfo b
-> HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiCols SelPermInfo b
selectPermissions)
caseBoolExpUnpreparedValue :: Maybe
(GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b)))
caseBoolExpUnpreparedValue =
((AnnColumnCaseBoolExpField b (PartialSQLExp b)
-> AnnColumnCaseBoolExpField b (UnpreparedValue b))
-> AnnColumnCaseBoolExpPartialSQL b
-> GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((AnnColumnCaseBoolExpField b (PartialSQLExp b)
-> AnnColumnCaseBoolExpField b (UnpreparedValue b))
-> AnnColumnCaseBoolExpPartialSQL b
-> GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b)))
-> ((PartialSQLExp b -> UnpreparedValue b)
-> AnnColumnCaseBoolExpField b (PartialSQLExp b)
-> AnnColumnCaseBoolExpField b (UnpreparedValue b))
-> (PartialSQLExp b -> UnpreparedValue b)
-> AnnColumnCaseBoolExpPartialSQL b
-> GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartialSQLExp b -> UnpreparedValue b)
-> AnnColumnCaseBoolExpField b (PartialSQLExp b)
-> AnnColumnCaseBoolExpField b (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) PartialSQLExp b -> UnpreparedValue b
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue (AnnColumnCaseBoolExpPartialSQL b
-> GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b)))
-> Maybe (AnnColumnCaseBoolExpPartialSQL b)
-> Maybe
(GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (AnnColumnCaseBoolExpPartialSQL b)
caseBoolExp
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))
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
|| Maybe (AnnColumnCaseBoolExpPartialSQL b) -> Bool
forall a. Maybe a -> Bool
isJust Maybe (AnnColumnCaseBoolExpPartialSQL b)
caseBoolExp
Parser 'Both n (ValueWithOrigin (ColumnValue b))
field <- m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT m (Parser 'Both n (ValueWithOrigin (ColumnValue b))))
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
-> MaybeT m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall a b. (a -> b) -> a -> b
$ ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser (ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo) (Bool -> Nullability
G.Nullability Bool
nullability)
pure $
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
-> Maybe
(GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b)))
-> Maybe (ScalarSelectionArguments b)
-> AnnotatedField b
forall (backend :: BackendType) v r.
Column backend
-> ColumnType backend
-> Maybe (AnnColumnCaseBoolExp 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) Maybe
(GBoolExp b (AnnColumnCaseBoolExpField b (UnpreparedValue b)))
caseBoolExpUnpreparedValue
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)])
-> m (Maybe [FieldParser n (AnnotatedField b)])
-> m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo b
-> TableName b
-> RelInfo b
-> 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) =>
SourceInfo b
-> TableName b
-> RelInfo b
-> m (Maybe [FieldParser n (AnnotatedField b)])
relationshipField SourceInfo b
sourceInfo 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)])
-> m (Maybe (FieldParser n (AnnotatedField b)))
-> m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo b
-> ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> m (Maybe (FieldParser n (AnnotatedField b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendSchema b, MonadBuildSchema b r m n) =>
SourceInfo b
-> ComputedFieldInfo b
-> TableName b
-> TableInfo b
-> m (Maybe (FieldParser n (AnnotatedField b)))
computedField SourceInfo b
sourceInfo ComputedFieldInfo b
computedFieldInfo TableName b
table TableInfo b
tableInfo
FIRemoteRelationship RemoteFieldInfo (DBJoinField b)
remoteFieldInfo -> do
SchemaKind
schemaKind <- (SchemaContext -> SchemaKind) -> 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)]
-> m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
(SchemaKind, RemoteFieldInfoRHS)
_ -> do
RemoteRelationshipParserBuilder forall lhsJoinField r (n :: * -> *) (m :: * -> *).
MonadBuildSchemaBase r m n =>
RemoteFieldInfo lhsJoinField
-> m (Maybe
[FieldParser n (RemoteRelationshipField UnpreparedValue)])
remoteRelationshipField <- (SchemaContext -> RemoteRelationshipParserBuilder)
-> 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)])
-> m (Maybe
[FieldParser n (RemoteRelationshipField UnpreparedValue)])
-> m [FieldParser n (RemoteRelationshipField UnpreparedValue)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RemoteFieldInfo (DBJoinField b)
-> m (Maybe
[FieldParser n (RemoteRelationshipField UnpreparedValue)])
forall lhsJoinField r (n :: * -> *) (m :: * -> *).
MonadBuildSchemaBase r m n =>
RemoteFieldInfo lhsJoinField
-> 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)]
-> m [FieldParser n (AnnotatedField b)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser n (AnnotatedField b)]
-> m [FieldParser n (AnnotatedField b)])
-> [FieldParser n (AnnotatedField b)]
-> 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 (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
relationshipField ::
forall b r m n.
( AggregationPredicatesSchema b,
BackendTableSelectSchema b,
Eq (AnnBoolExp b (IR.UnpreparedValue b)),
MonadBuildSchema b r m n
) =>
SourceInfo b ->
TableName b ->
RelInfo b ->
m (Maybe [FieldParser n (AnnotatedField b)])
relationshipField :: SourceInfo b
-> TableName b
-> RelInfo b
-> m (Maybe [FieldParser n (AnnotatedField b)])
relationshipField SourceInfo b
sourceInfo TableName b
table RelInfo b
ri = MaybeT m [FieldParser n (AnnotatedField b)]
-> m (Maybe [FieldParser n (AnnotatedField b)])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
NamingCase
tCase <- (r -> NamingCase) -> MaybeT m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
RoleName
roleName <- (SchemaContext -> RoleName) -> MaybeT m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
OptimizePermissionFilters
optimizePermissionFilters <- (SchemaOptions -> OptimizePermissionFilters)
-> MaybeT 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 <- m (TableInfo b) -> MaybeT m (TableInfo b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo b) -> MaybeT m (TableInfo b))
-> m (TableInfo b) -> MaybeT m (TableInfo b)
forall a b. (a -> b) -> a -> b
$ SourceInfo b -> TableName b -> m (TableInfo b)
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo b
sourceInfo TableName b
table
TableInfo b
otherTableInfo <- m (TableInfo b) -> MaybeT m (TableInfo b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo b) -> MaybeT m (TableInfo b))
-> m (TableInfo b) -> MaybeT m (TableInfo b)
forall a b. (a -> b) -> a -> b
$ SourceInfo b -> TableName b -> m (TableInfo b)
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo b
sourceInfo (TableName b -> m (TableInfo b)) -> TableName b -> m (TableInfo b)
forall a b. (a -> b) -> a -> b
$ RelInfo b -> TableName b
forall (b :: BackendType). RelInfo b -> TableName b
riRTable RelInfo b
ri
SelPermInfo b
tablePerms <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
tableInfo
SelPermInfo b
remotePerms <- Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b))
-> Maybe (SelPermInfo b) -> MaybeT m (SelPermInfo b)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo b -> Maybe (SelPermInfo b)
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo b
otherTableInfo
Name
relFieldName <- m Name -> MaybeT m Name
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m Name -> MaybeT m Name) -> m Name -> MaybeT m Name
forall a b. (a -> b) -> a -> b
$ Text -> m Name
forall (m :: * -> *). MonadError QErr m => Text -> m Name
textToName (Text -> m Name) -> Text -> m Name
forall a b. (a -> b) -> a -> b
$ RelName -> Text
relNameToTxt (RelName -> 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 AnnBoolExp b (UnpreparedValue b)
remoteTablePerm)]) ->
if RelInfo b -> TableName b
forall (b :: BackendType). RelInfo b -> TableName b
riRTable RelInfo b
remoteRI TableName b -> TableName b -> Bool
forall a. Eq a => a -> a -> Bool
== 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.
(Eq k, Hashable k, Eq v, Hashable v) =>
HashMap k v -> HashMap v k -> Bool
`Map.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)
remoteTablePerm
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 <- m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b)))
-> m (Maybe (Parser 'Output n (AnnotatedFields b)))
-> MaybeT m (Parser 'Output n (AnnotatedFields b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet SourceInfo b
sourceInfo TableInfo b
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]
Map.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 primaryKeyColumn1.
TableCoreInfoG b field primaryKeyColumn1 -> 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
Map.lookup (Column b -> FieldName
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. Prism (Maybe a) (Maybe b) a 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
. (ColumnInfo b -> Const (First (ColumnInfo b)) (ColumnInfo b))
-> FieldInfo b -> Const (First (ColumnInfo b)) (FieldInfo b)
forall (b :: BackendType). Prism' (FieldInfo b) (ColumnInfo b)
_FIColumn
[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)
traverse Column b -> Maybe (ColumnInfo b)
findColumn [Column b]
columns
Maybe [ColumnInfo b]
-> MaybeT m [ColumnInfo b] -> MaybeT m [ColumnInfo b]
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Text -> MaybeT 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 m Nullable
forall (f :: * -> *) a. Applicative f => a -> f a
pure Nullable
Nullable
pure $
FieldParser n (AnnotatedField b)
-> [FieldParser n (AnnotatedField b)]
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
P.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)
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
-> ObjectRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b) -> 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) (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
-> TableName b
-> AnnBoolExp b (UnpreparedValue b)
-> AnnObjectSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) r v.
AnnFieldsG b r v
-> TableName b -> AnnBoolExp b v -> AnnObjectSelectG b r v
IR.AnnObjectSelectG AnnotatedFields b
fields (RelInfo b -> TableName b
forall (b :: BackendType). RelInfo b -> TableName b
riRTable RelInfo b
ri) (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 <- m (Maybe (FieldParser n (SelectExp b)))
-> MaybeT m (FieldParser n (SelectExp b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (FieldParser n (SelectExp b)))
-> MaybeT m (FieldParser n (SelectExp b)))
-> m (Maybe (FieldParser n (SelectExp b)))
-> MaybeT m (FieldParser n (SelectExp b))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp b)))
selectTable SourceInfo b
sourceInfo 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)
-> SelectExp b
-> ArrayRelationSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b) -> 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) (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 <- m (Maybe (FieldParser n (AggSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (AggSelectExp b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Maybe (FieldParser n (AggSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (AggSelectExp b))))
-> m (Maybe (FieldParser n (AggSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (AggSelectExp b)))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp b)))
selectTableAggregate SourceInfo b
sourceInfo TableInfo b
otherTableInfo Name
relAggFieldName Maybe Description
relAggDesc
Maybe (FieldParser n (ConnectionSelectExp b))
remoteConnectionField <- MaybeT (MaybeT m) (FieldParser n (ConnectionSelectExp b))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (MaybeT (MaybeT m) (FieldParser n (ConnectionSelectExp b))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b))))
-> MaybeT (MaybeT m) (FieldParser n (ConnectionSelectExp b))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall a b. (a -> b) -> a -> b
$ do
RelaySchema NodeInterfaceParserBuilder
_ <- (SchemaContext -> SchemaKind) -> MaybeT (MaybeT 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 m) (XRelay b)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (XRelay b) -> MaybeT (MaybeT m) (XRelay b))
-> Maybe (XRelay b) -> MaybeT (MaybeT m) (XRelay b)
forall a b. (a -> b) -> a -> b
$ BackendSchema b => Maybe (XRelay b)
forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @b
NESeq (ColumnInfo b)
pkeyColumns <-
MaybeT m (Maybe (NESeq (ColumnInfo b)))
-> MaybeT (MaybeT m) (NESeq (ColumnInfo b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (MaybeT m (Maybe (NESeq (ColumnInfo b)))
-> MaybeT (MaybeT m) (NESeq (ColumnInfo b)))
-> MaybeT m (Maybe (NESeq (ColumnInfo b)))
-> MaybeT (MaybeT 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). Lens' (TableInfo b) (TableCoreInfo 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.
Lens
(TableCoreInfoG b field primaryKeyColumn1)
(TableCoreInfoG b field primaryKeyColumn2)
(Maybe (PrimaryKey b primaryKeyColumn1))
(Maybe (PrimaryKey b 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. Prism (Maybe a) (Maybe b) a 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.
Lens (PrimaryKey b a1) (PrimaryKey b a2) (NESeq a1) (NESeq a2)
pkColumns)
(TableInfo b -> Maybe (NESeq (ColumnInfo b)))
-> MaybeT m (TableInfo b)
-> MaybeT m (Maybe (NESeq (ColumnInfo b)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo b -> MaybeT m (TableInfo b)
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 m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT (MaybeT m) (FieldParser n (ConnectionSelectExp b))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT (MaybeT m) (FieldParser n (ConnectionSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT (MaybeT m) (FieldParser n (ConnectionSelectExp b))
forall a b. (a -> b) -> a -> b
$ m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b))))
-> m (Maybe (FieldParser n (ConnectionSelectExp b)))
-> MaybeT m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall a b. (a -> b) -> a -> b
$ SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> NESeq (ColumnInfo b)
-> m (Maybe (FieldParser n (ConnectionSelectExp b)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b,
AggregationPredicatesSchema b) =>
SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> PrimaryKeyColumns b
-> m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection SourceInfo b
sourceInfo TableInfo b
otherTableInfo Name
relConnectionName Maybe Description
relConnectionDesc NESeq (ColumnInfo b)
pkeyColumns
pure $
[Maybe (FieldParser n (AnnotatedField b))]
-> [FieldParser n (AnnotatedField b)]
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 (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)
-> AggSelectExp b
-> ArrayAggregateSelectG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b) -> 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)) (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 (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)
-> ConnectionSelectExp b
-> ArrayConnectionSelect
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
forall (b :: BackendType) a.
RelName
-> HashMap (Column b) (Column b) -> 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)) (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 :: SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo b
selectPermissions =
TablePerm :: forall (b :: BackendType) v.
AnnBoolExp b v -> Maybe Int -> TablePermG b v
IR.TablePerm
{ $sel:_tpFilter:TablePerm :: AnnBoolExp b (UnpreparedValue b)
IR._tpFilter = (PartialSQLExp b -> UnpreparedValue b)
-> AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PartialSQLExp b -> UnpreparedValue b
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue (AnnBoolExpFld b (PartialSQLExp b)
-> AnnBoolExpFld b (UnpreparedValue b))
-> GBoolExp b (AnnBoolExpFld b (PartialSQLExp b))
-> AnnBoolExp b (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
}