{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE ViewPatterns #-}
module Hasura.Backends.Postgres.Schema.Select
( selectFunction,
selectFunctionAggregate,
selectFunctionConnection,
computedFieldPG,
buildFunctionQueryFieldsPG,
buildFunctionMutationFieldsPG,
)
where
import Control.Lens hiding (index)
import Data.Has (getter)
import Data.HashMap.Strict.Extended qualified as Map
import Data.Sequence qualified as Seq
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Data.Traversable (mapAccumL)
import Hasura.Backends.Postgres.SQL.Types qualified as PG
import Hasura.Backends.Postgres.Types.ComputedField qualified as PG
import Hasura.Backends.Postgres.Types.Function qualified as PG
import Hasura.Base.Error
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser
( FieldParser,
InputFieldsParser,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.Table
import Hasura.GraphQL.Schema.Typename (mkTypename)
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.IR qualified as IR
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table
import Hasura.SQL.Backend
import Language.GraphQL.Draft.Syntax qualified as G
selectFunction ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
Maybe G.Description ->
m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
selectFunction :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
selectFunction MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo fi :: FunctionInfo ('Postgres pgKind)
fi@FunctionInfo {Maybe Text
Seq (FunctionInputArgument ('Postgres pgKind))
FunctionPermissionsMap
Name
SystemDefined
JsonAggSelect
TableName ('Postgres pgKind)
FunctionName ('Postgres pgKind)
FunctionVolatility
FunctionExposedAs
_fiComment :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiJsonAggSelect :: forall (b :: BackendType). FunctionInfo b -> JsonAggSelect
_fiPermissions :: forall (b :: BackendType). FunctionInfo b -> FunctionPermissionsMap
_fiDescription :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiReturnType :: forall (b :: BackendType). FunctionInfo b -> TableName b
_fiInputArgs :: forall (b :: BackendType).
FunctionInfo b -> Seq (FunctionInputArgument b)
_fiExposedAs :: forall (b :: BackendType). FunctionInfo b -> FunctionExposedAs
_fiVolatility :: forall (b :: BackendType). FunctionInfo b -> FunctionVolatility
_fiSystemDefined :: forall (b :: BackendType). FunctionInfo b -> SystemDefined
_fiGQLAggregateName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLArgsName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiSQLName :: forall (b :: BackendType). FunctionInfo b -> FunctionName b
_fiComment :: Maybe Text
_fiJsonAggSelect :: JsonAggSelect
_fiPermissions :: FunctionPermissionsMap
_fiDescription :: Maybe Text
_fiReturnType :: TableName ('Postgres pgKind)
_fiInputArgs :: Seq (FunctionInputArgument ('Postgres pgKind))
_fiExposedAs :: FunctionExposedAs
_fiVolatility :: FunctionVolatility
_fiSystemDefined :: SystemDefined
_fiGQLAggregateName :: Name
_fiGQLArgsName :: Name
_fiGQLName :: Name
_fiSQLName :: FunctionName ('Postgres pgKind)
..} Maybe Description
description = MaybeT m (FieldParser n (SelectExp ('Postgres pgKind)))
-> m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
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
TableInfo ('Postgres pgKind)
tableInfo <- m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind)))
-> m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind) -> m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
_fiReturnType
SelPermInfo ('Postgres pgKind)
selectPermissions <- Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind)))
-> Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind)
-> Maybe (SelPermInfo ('Postgres pgKind))
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo ('Postgres pgKind)
tableInfo
Parser 'Output n (AnnotatedFields ('Postgres pgKind))
selectionSetParser <- m (Maybe (Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT m (Parser 'Output n (AnnotatedFields ('Postgres pgKind)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT
m (Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT m (Parser 'Output n (AnnotatedFields ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
returnFunctionParser SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
m (FieldParser n (SelectExp ('Postgres pgKind)))
-> MaybeT m (FieldParser n (SelectExp ('Postgres pgKind)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift 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
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
tableArgsParser <- SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
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 ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser <- SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
customSQLFunctionArgs SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo ('Postgres pgKind)
fi Name
_fiGQLName Name
_fiGQLArgsName
let argsParser :: InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
argsParser = (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
tableArgsParser
functionFieldName :: Name
functionFieldName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName Name
_fiGQLName
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> Parser 'Output n (AnnotatedFields ('Postgres pgKind))
-> FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
AnnotatedFields ('Postgres pgKind))
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
functionFieldName Maybe Description
description InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
argsParser Parser 'Output n (AnnotatedFields ('Postgres pgKind))
selectionSetParser
FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
AnnotatedFields ('Postgres pgKind))
-> (((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
AnnotatedFields ('Postgres pgKind))
-> SelectExp ('Postgres pgKind))
-> FieldParser n (SelectExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \((FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
funcArgs, SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
tableArgs'), AnnotatedFields ('Postgres pgKind)
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 ('Postgres pgKind)
IR._asnFields = AnnotatedFields ('Postgres pgKind)
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnFrom = FunctionName ('Postgres pgKind)
-> FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> Maybe
[(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
-> SelectFromG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) v.
FunctionName b
-> FunctionArgsExp b v
-> Maybe [(Column b, ScalarType b)]
-> SelectFromG b v
IR.FromFunction FunctionName ('Postgres pgKind)
_fiSQLName FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
funcArgs Maybe [(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
forall a. Maybe a
Nothing,
$sel:_asnPerm:AnnSelectG :: TablePermG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnPerm = SelPermInfo ('Postgres pgKind)
-> TablePermG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo ('Postgres pgKind)
selectPermissions,
$sel:_asnArgs:AnnSelectG :: SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnArgs = SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
tableArgs',
$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
returnFunctionParser :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
returnFunctionParser =
case JsonAggSelect
_fiJsonAggSelect of
JsonAggSelect
JASSingleObject -> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(BackendTableSelectSchema b, MonadBuildSchemaBase r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionSet
JsonAggSelect
JASMultipleRows -> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
forall r (m :: * -> *) (n :: * -> *) (b :: BackendType).
(MonadBuildSchemaBase r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
tableSelectionList
selectFunctionAggregate ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
Maybe G.Description ->
m (Maybe (FieldParser n (AggSelectExp ('Postgres pgKind))))
selectFunctionAggregate :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp ('Postgres pgKind))))
selectFunctionAggregate MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo fi :: FunctionInfo ('Postgres pgKind)
fi@FunctionInfo {Maybe Text
Seq (FunctionInputArgument ('Postgres pgKind))
FunctionPermissionsMap
Name
SystemDefined
JsonAggSelect
TableName ('Postgres pgKind)
FunctionName ('Postgres pgKind)
FunctionVolatility
FunctionExposedAs
_fiComment :: Maybe Text
_fiJsonAggSelect :: JsonAggSelect
_fiPermissions :: FunctionPermissionsMap
_fiDescription :: Maybe Text
_fiReturnType :: TableName ('Postgres pgKind)
_fiInputArgs :: Seq (FunctionInputArgument ('Postgres pgKind))
_fiExposedAs :: FunctionExposedAs
_fiVolatility :: FunctionVolatility
_fiSystemDefined :: SystemDefined
_fiGQLAggregateName :: Name
_fiGQLArgsName :: Name
_fiGQLName :: Name
_fiSQLName :: FunctionName ('Postgres pgKind)
_fiComment :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiJsonAggSelect :: forall (b :: BackendType). FunctionInfo b -> JsonAggSelect
_fiPermissions :: forall (b :: BackendType). FunctionInfo b -> FunctionPermissionsMap
_fiDescription :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiReturnType :: forall (b :: BackendType). FunctionInfo b -> TableName b
_fiInputArgs :: forall (b :: BackendType).
FunctionInfo b -> Seq (FunctionInputArgument b)
_fiExposedAs :: forall (b :: BackendType). FunctionInfo b -> FunctionExposedAs
_fiVolatility :: forall (b :: BackendType). FunctionInfo b -> FunctionVolatility
_fiSystemDefined :: forall (b :: BackendType). FunctionInfo b -> SystemDefined
_fiGQLAggregateName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLArgsName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiSQLName :: forall (b :: BackendType). FunctionInfo b -> FunctionName b
..} Maybe Description
description = MaybeT m (FieldParser n (AggSelectExp ('Postgres pgKind)))
-> m (Maybe (FieldParser n (AggSelectExp ('Postgres pgKind))))
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
TableInfo ('Postgres pgKind)
targetTableInfo <- SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> MaybeT m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
_fiReturnType
SelPermInfo ('Postgres pgKind)
selectPermissions <- Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind)))
-> Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind)
-> Maybe (SelPermInfo ('Postgres pgKind))
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo ('Postgres pgKind)
targetTableInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ SelPermInfo ('Postgres pgKind) -> Bool
forall (b :: BackendType). SelPermInfo b -> Bool
spiAllowAgg SelPermInfo ('Postgres pgKind)
selectPermissions
()
xNodesAgg <- Maybe () -> MaybeT m ()
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe () -> MaybeT m ()) -> Maybe () -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ BackendSchema ('Postgres pgKind) =>
Maybe (XNodesAgg ('Postgres pgKind))
forall (b :: BackendType). BackendSchema b => Maybe (XNodesAgg b)
nodesAggExtension @('Postgres pgKind)
TableInfo ('Postgres pgKind)
tableInfo <- SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> MaybeT m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
_fiReturnType
Parser 'Output n (AnnotatedFields ('Postgres pgKind))
nodesParser <- m (Maybe (Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT m (Parser 'Output n (AnnotatedFields ('Postgres pgKind)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT
m (Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT m (Parser 'Output n (AnnotatedFields ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
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 ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
m (FieldParser n (AggSelectExp ('Postgres pgKind)))
-> MaybeT m (FieldParser n (AggSelectExp ('Postgres pgKind)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift 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 ('Postgres pgKind) -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo ('Postgres pgKind)
tableInfo
InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
tableArgsParser <- SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
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 ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser <- SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
customSQLFunctionArgs SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo ('Postgres pgKind)
fi Name
_fiGQLAggregateName Name
_fiGQLArgsName
Parser 'Output n (AggregateFields ('Postgres pgKind))
aggregateParser <- SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Parser 'Output n (AggregateFields ('Postgres pgKind)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b -> m (Parser 'Output n (AggregateFields b))
tableAggregationFields SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
Name
selectionName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> m Name -> m Name
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Name -> m Name
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkTableAggregateTypeName GQLNameIdentifier
tableGQLName)
let aggregateFieldName :: Name
aggregateFieldName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName Name
_fiGQLAggregateName
argsParser :: InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
argsParser = (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
tableArgsParser
aggregationParser :: Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
aggregationParser =
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Text
-> TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
forall a.
(Text -> a) -> InsOrdHashMap Name (ParsedSelection a) -> Fields a
parsedSelectionsToFields Text
-> TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v. Text -> TableAggregateFieldG b r v
IR.TAFExp) (Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$
Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.nonNullableParser (Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$
Name
-> Maybe Description
-> [FieldParser
MetadataObjId
n
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> Parser
MetadataObjId
'Output
n
(InsOrdHashMap
Name
(ParsedSelection
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
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
Maybe Description
forall a. Maybe a
Nothing
[ XNodesAgg ('Postgres pgKind)
-> AnnotatedFields ('Postgres pgKind)
-> TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
XNodesAgg b -> AnnFieldsG b r v -> TableAggregateFieldG b r v
IR.TAFNodes ()
XNodesAgg ('Postgres pgKind)
xNodesAgg (AnnotatedFields ('Postgres pgKind)
-> TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> FieldParser MetadataObjId n (AnnotatedFields ('Postgres pgKind))
-> FieldParser
MetadataObjId
n
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Output n (AnnotatedFields ('Postgres pgKind))
-> FieldParser MetadataObjId n (AnnotatedFields ('Postgres pgKind))
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 ('Postgres pgKind))
nodesParser,
AggregateFields ('Postgres pgKind)
-> TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
AggregateFields b -> TableAggregateFieldG b r v
IR.TAFAgg (AggregateFields ('Postgres pgKind)
-> TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> FieldParser MetadataObjId n (AggregateFields ('Postgres pgKind))
-> FieldParser
MetadataObjId
n
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser 'Output n (AggregateFields ('Postgres pgKind))
-> FieldParser MetadataObjId n (AggregateFields ('Postgres pgKind))
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 ('Postgres pgKind))
aggregateParser
]
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
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
aggregateFieldName Maybe Description
description InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
argsParser Parser
MetadataObjId
'Output
n
(Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
aggregationParser
FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> (((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> AggSelectExp ('Postgres pgKind))
-> FieldParser n (AggSelectExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \((FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
funcArgs, SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
tableArgs'), Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
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
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
IR._asnFields = Fields
(TableAggregateFieldG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnFrom = FunctionName ('Postgres pgKind)
-> FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> Maybe
[(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
-> SelectFromG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) v.
FunctionName b
-> FunctionArgsExp b v
-> Maybe [(Column b, ScalarType b)]
-> SelectFromG b v
IR.FromFunction FunctionName ('Postgres pgKind)
_fiSQLName FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
funcArgs Maybe [(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
forall a. Maybe a
Nothing,
$sel:_asnPerm:AnnSelectG :: TablePermG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnPerm = SelPermInfo ('Postgres pgKind)
-> TablePermG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo ('Postgres pgKind)
selectPermissions,
$sel:_asnArgs:AnnSelectG :: SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnArgs = SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
tableArgs',
$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
}
selectFunctionConnection ::
forall pgKind r m n.
( MonadBuildSchema ('Postgres pgKind) r m n,
AggregationPredicatesSchema ('Postgres pgKind),
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
Maybe G.Description ->
PrimaryKeyColumns ('Postgres pgKind) ->
m (Maybe (FieldParser n (ConnectionSelectExp ('Postgres pgKind))))
selectFunctionConnection :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> PrimaryKeyColumns ('Postgres pgKind)
-> m (Maybe
(FieldParser n (ConnectionSelectExp ('Postgres pgKind))))
selectFunctionConnection MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo fi :: FunctionInfo ('Postgres pgKind)
fi@FunctionInfo {Maybe Text
Seq (FunctionInputArgument ('Postgres pgKind))
FunctionPermissionsMap
Name
SystemDefined
JsonAggSelect
TableName ('Postgres pgKind)
FunctionName ('Postgres pgKind)
FunctionVolatility
FunctionExposedAs
_fiComment :: Maybe Text
_fiJsonAggSelect :: JsonAggSelect
_fiPermissions :: FunctionPermissionsMap
_fiDescription :: Maybe Text
_fiReturnType :: TableName ('Postgres pgKind)
_fiInputArgs :: Seq (FunctionInputArgument ('Postgres pgKind))
_fiExposedAs :: FunctionExposedAs
_fiVolatility :: FunctionVolatility
_fiSystemDefined :: SystemDefined
_fiGQLAggregateName :: Name
_fiGQLArgsName :: Name
_fiGQLName :: Name
_fiSQLName :: FunctionName ('Postgres pgKind)
_fiComment :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiJsonAggSelect :: forall (b :: BackendType). FunctionInfo b -> JsonAggSelect
_fiPermissions :: forall (b :: BackendType). FunctionInfo b -> FunctionPermissionsMap
_fiDescription :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiReturnType :: forall (b :: BackendType). FunctionInfo b -> TableName b
_fiInputArgs :: forall (b :: BackendType).
FunctionInfo b -> Seq (FunctionInputArgument b)
_fiExposedAs :: forall (b :: BackendType). FunctionInfo b -> FunctionExposedAs
_fiVolatility :: forall (b :: BackendType). FunctionInfo b -> FunctionVolatility
_fiSystemDefined :: forall (b :: BackendType). FunctionInfo b -> SystemDefined
_fiGQLAggregateName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLArgsName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiSQLName :: forall (b :: BackendType). FunctionInfo b -> FunctionName b
..} Maybe Description
description PrimaryKeyColumns ('Postgres pgKind)
pkeyColumns = MaybeT m (FieldParser n (ConnectionSelectExp ('Postgres pgKind)))
-> m (Maybe
(FieldParser n (ConnectionSelectExp ('Postgres pgKind))))
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
TableInfo ('Postgres pgKind)
returnTableInfo <- m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind)))
-> m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind) -> m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
_fiReturnType
SelPermInfo ('Postgres pgKind)
selectPermissions <- Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind)))
-> Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind)
-> Maybe (SelPermInfo ('Postgres pgKind))
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo ('Postgres pgKind)
returnTableInfo
()
xRelayInfo <- Maybe () -> MaybeT m ()
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe () -> MaybeT m ()) -> Maybe () -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ BackendSchema ('Postgres pgKind) =>
Maybe (XRelay ('Postgres pgKind))
forall (b :: BackendType). BackendSchema b => Maybe (XRelay b)
relayExtension @('Postgres pgKind)
TableInfo ('Postgres pgKind)
tableInfo <- m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind)))
-> m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind) -> m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
_fiReturnType
Parser 'Output n (ConnectionFields ('Postgres pgKind))
selectionSetParser <- m (Maybe (Parser 'Output n (ConnectionFields ('Postgres pgKind))))
-> MaybeT
m (Parser 'Output n (ConnectionFields ('Postgres pgKind)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT (m (Maybe (Parser 'Output n (ConnectionFields ('Postgres pgKind))))
-> MaybeT
m (Parser 'Output n (ConnectionFields ('Postgres pgKind))))
-> m (Maybe
(Parser 'Output n (ConnectionFields ('Postgres pgKind))))
-> MaybeT
m (Parser 'Output n (ConnectionFields ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (ConnectionFields ('Postgres pgKind))))
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 ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
m (FieldParser n (ConnectionSelectExp ('Postgres pgKind)))
-> MaybeT
m (FieldParser n (ConnectionSelectExp ('Postgres pgKind)))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift do
let fieldName :: Name
fieldName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Name
_fiGQLName Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__connection
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 ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)
tableConnectionArgsParser <- PrimaryKeyColumns ('Postgres pgKind)
-> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
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 ('Postgres pgKind)
pkeyColumns SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser <- SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
customSQLFunctionArgs SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo ('Postgres pgKind)
fi Name
_fiGQLName Name
_fiGQLArgsName
let argsParser :: InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice))
argsParser = (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> (SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)
-> (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice))
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser InputFieldsParser
n
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)
tableConnectionArgsParser
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice))
-> Parser 'Output n (ConnectionFields ('Postgres pgKind))
-> FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)),
ConnectionFields ('Postgres pgKind))
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
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice))
argsParser Parser 'Output n (ConnectionFields ('Postgres pgKind))
selectionSetParser
FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)),
ConnectionFields ('Postgres pgKind))
-> (((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
(SelectArgs ('Postgres pgKind),
Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))),
Maybe ConnectionSlice)),
ConnectionFields ('Postgres pgKind))
-> ConnectionSelectExp ('Postgres pgKind))
-> FieldParser n (ConnectionSelectExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \((FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
funcArgs, (SelectArgs ('Postgres pgKind)
args, Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
split, Maybe ConnectionSlice
slice)), ConnectionFields ('Postgres pgKind)
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 ('Postgres pgKind)
IR._csXRelay = ()
XRelay ('Postgres pgKind)
xRelayInfo,
$sel:_csPrimaryKeyColumns:ConnectionSelect :: PrimaryKeyColumns ('Postgres pgKind)
IR._csPrimaryKeyColumns = PrimaryKeyColumns ('Postgres pgKind)
pkeyColumns,
$sel:_csSplit:ConnectionSelect :: Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
IR._csSplit = Maybe
(NonEmpty
(ConnectionSplit
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
split,
$sel:_csSlice:ConnectionSelect :: Maybe ConnectionSlice
IR._csSlice = Maybe ConnectionSlice
slice,
$sel:_csSelect:ConnectionSelect :: AnnSelectG
('Postgres pgKind)
(ConnectionField
('Postgres pgKind) (RemoteRelationshipField UnpreparedValue))
(UnpreparedValue ('Postgres pgKind))
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 :: ConnectionFields ('Postgres pgKind)
IR._asnFields = ConnectionFields ('Postgres pgKind)
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnFrom = FunctionName ('Postgres pgKind)
-> FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> Maybe
[(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
-> SelectFromG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) v.
FunctionName b
-> FunctionArgsExp b v
-> Maybe [(Column b, ScalarType b)]
-> SelectFromG b v
IR.FromFunction FunctionName ('Postgres pgKind)
_fiSQLName FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
funcArgs Maybe [(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
forall a. Maybe a
Nothing,
$sel:_asnPerm:AnnSelectG :: TablePermG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnPerm = SelPermInfo ('Postgres pgKind)
-> TablePermG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo ('Postgres pgKind)
selectPermissions,
$sel:_asnArgs:AnnSelectG :: SelectArgs ('Postgres pgKind)
IR._asnArgs = SelectArgs ('Postgres pgKind)
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
}
}
computedFieldPG ::
forall pgKind r m n.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
SourceInfo ('Postgres pgKind) ->
ComputedFieldInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
m (Maybe (FieldParser n (AnnotatedField ('Postgres pgKind))))
computedFieldPG :: SourceInfo ('Postgres pgKind)
-> ComputedFieldInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe (FieldParser n (AnnotatedField ('Postgres pgKind))))
computedFieldPG SourceInfo ('Postgres pgKind)
sourceInfo ComputedFieldInfo {Maybe Text
ComputedFieldReturn ('Postgres pgKind)
XComputedField ('Postgres pgKind)
ComputedFieldFunction ('Postgres pgKind)
ComputedFieldName
_cfiDescription :: forall (b :: BackendType). ComputedFieldInfo b -> Maybe Text
_cfiReturnType :: forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldReturn b
_cfiFunction :: forall (b :: BackendType).
ComputedFieldInfo b -> ComputedFieldFunction b
_cfiName :: forall (b :: BackendType). ComputedFieldInfo b -> ComputedFieldName
_cfiXComputedFieldInfo :: forall (b :: BackendType). ComputedFieldInfo b -> XComputedField b
_cfiDescription :: Maybe Text
_cfiReturnType :: ComputedFieldReturn ('Postgres pgKind)
_cfiFunction :: ComputedFieldFunction ('Postgres pgKind)
_cfiName :: ComputedFieldName
_cfiXComputedFieldInfo :: XComputedField ('Postgres pgKind)
..} TableName ('Postgres pgKind)
parentTable TableInfo ('Postgres pgKind)
tableInfo = MaybeT m (FieldParser n (AnnotatedField ('Postgres pgKind)))
-> m (Maybe (FieldParser n (AnnotatedField ('Postgres pgKind))))
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
StringifyNumbers
stringifyNumbers <- (SchemaOptions -> StringifyNumbers) -> MaybeT m StringifyNumbers
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> StringifyNumbers
Options.soStringifyNumbers
SelPermInfo ('Postgres pgKind)
selectPermissions <- Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind)))
-> Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind)
-> Maybe (SelPermInfo ('Postgres pgKind))
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo ('Postgres pgKind)
tableInfo
Name
fieldName <- 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
$ ComputedFieldName -> Text
computedFieldNameToText ComputedFieldName
_cfiName
InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser <- m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> MaybeT
m
(InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> MaybeT
m
(InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> MaybeT
m
(InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ ComputedFieldFunction ('Postgres pgKind)
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
computedFieldFunctionArgs ComputedFieldFunction ('Postgres pgKind)
_cfiFunction
case ComputedFieldReturn ('Postgres pgKind)
_cfiReturnType of
PG.CFRScalar scalarReturnType -> do
Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind))
caseBoolExpMaybe <-
Maybe (Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)))
-> MaybeT
m (Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (ComputedFieldName
-> HashMap
ComputedFieldName
(Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)))
-> Maybe
(Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)))
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup ComputedFieldName
_cfiName (SelPermInfo ('Postgres pgKind)
-> HashMap
ComputedFieldName
(Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)))
forall (b :: BackendType).
SelPermInfo b
-> HashMap
ComputedFieldName (Maybe (AnnColumnCaseBoolExpPartialSQL b))
spiComputedFields SelPermInfo ('Postgres pgKind)
selectPermissions))
let caseBoolExpUnpreparedValue :: Maybe
(GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
caseBoolExpUnpreparedValue =
((AnnColumnCaseBoolExpField
('Postgres pgKind) (PartialSQLExp ('Postgres pgKind))
-> AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)
-> GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((AnnColumnCaseBoolExpField
('Postgres pgKind) (PartialSQLExp ('Postgres pgKind))
-> AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)
-> GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> ((PartialSQLExp ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind))
-> AnnColumnCaseBoolExpField
('Postgres pgKind) (PartialSQLExp ('Postgres pgKind))
-> AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> (PartialSQLExp ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind))
-> AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)
-> GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PartialSQLExp ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind))
-> AnnColumnCaseBoolExpField
('Postgres pgKind) (PartialSQLExp ('Postgres pgKind))
-> AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) PartialSQLExp ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType). PartialSQLExp b -> UnpreparedValue b
partialSQLExpToUnpreparedValue (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind)
-> GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind))
-> Maybe
(GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (AnnColumnCaseBoolExpPartialSQL ('Postgres pgKind))
caseBoolExpMaybe
fieldArgsParser :: InputFieldsParser
MetadataObjId n (AnnotatedField ('Postgres pgKind))
fieldArgsParser = do
FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
args <- InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser
Maybe ColumnOp
colOp <- forall (n :: * -> *).
(BackendSchema ('Postgres pgKind), MonadParse n) =>
ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
forall (b :: BackendType) (n :: * -> *).
(BackendSchema b, MonadParse n) =>
ColumnType b
-> InputFieldsParser n (Maybe (ScalarSelectionArguments b))
scalarSelectionArgumentsParser @('Postgres pgKind) (ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind))))
-> ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$ ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
scalarReturnType
pure $
XComputedField ('Postgres pgKind)
-> ComputedFieldName
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> AnnotatedField ('Postgres pgKind)
forall (b :: BackendType) r v.
XComputedField b
-> ComputedFieldName
-> ComputedFieldSelect b r v
-> AnnFieldG b r v
IR.AFComputedField
XComputedField ('Postgres pgKind)
_cfiXComputedFieldInfo
ComputedFieldName
_cfiName
( ComputedFieldScalarSelect
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> Maybe
(GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
ComputedFieldScalarSelect b v
-> Maybe (AnnColumnCaseBoolExp b v) -> ComputedFieldSelect b r v
IR.CFSScalar
( ComputedFieldScalarSelect :: forall (b :: BackendType) v.
FunctionName b
-> FunctionArgsExp b v
-> ScalarType b
-> Maybe (ScalarSelectionArguments b)
-> ComputedFieldScalarSelect b v
IR.ComputedFieldScalarSelect
{ $sel:_cfssFunction:ComputedFieldScalarSelect :: FunctionName ('Postgres pgKind)
IR._cfssFunction = ComputedFieldFunction ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
forall (b :: BackendType).
ComputedFieldFunction b -> FunctionName b
_cffName ComputedFieldFunction ('Postgres pgKind)
_cfiFunction,
$sel:_cfssType:ComputedFieldScalarSelect :: ScalarType ('Postgres pgKind)
IR._cfssType = ScalarType ('Postgres pgKind)
PGScalarType
scalarReturnType,
$sel:_cfssScalarArguments:ComputedFieldScalarSelect :: Maybe (ScalarSelectionArguments ('Postgres pgKind))
IR._cfssScalarArguments = Maybe (ScalarSelectionArguments ('Postgres pgKind))
Maybe ColumnOp
colOp,
$sel:_cfssArguments:ComputedFieldScalarSelect :: FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._cfssArguments = FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
args
}
)
Maybe
(GBoolExp
('Postgres pgKind)
(AnnColumnCaseBoolExpField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
caseBoolExpUnpreparedValue
)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
dummyParser <- m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> MaybeT
m
(Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> MaybeT
m
(Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))))
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> MaybeT
m
(Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
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 @('Postgres pgKind) (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
scalarReturnType) (Bool -> Nullability
G.Nullability Bool
True)
pure $ Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n (AnnotatedField ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> FieldParser n (AnnotatedField ('Postgres pgKind))
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 Maybe Description
fieldDescription InputFieldsParser
MetadataObjId n (AnnotatedField ('Postgres pgKind))
fieldArgsParser Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
dummyParser
PG.CFRSetofTable tableName -> do
TableInfo ('Postgres pgKind)
otherTableInfo <- m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind)))
-> m (TableInfo ('Postgres pgKind))
-> MaybeT m (TableInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind) -> m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
QualifiedTable
tableName
SelPermInfo ('Postgres pgKind)
remotePerms <- Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind)))
-> Maybe (SelPermInfo ('Postgres pgKind))
-> MaybeT m (SelPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind)
-> Maybe (SelPermInfo ('Postgres pgKind))
forall (b :: BackendType).
RoleName -> TableInfo b -> Maybe (SelPermInfo b)
tableSelectPermissions RoleName
roleName TableInfo ('Postgres pgKind)
otherTableInfo
Parser MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
selectionSetParser <- m (Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))))
-> MaybeT
m
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT ((Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
-> Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
-> Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Parser MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.multiple (Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
-> (Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.nonNullableParser) (Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind)))
-> Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))))
-> m (Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))))
-> m (Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))))
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 ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
otherTableInfo)
InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
selectArgsParser <- m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
-> m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$ SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
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 ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
otherTableInfo
let fieldArgsParser :: InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
fieldArgsParser = (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
functionArgsParser InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
selectArgsParser
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
-> FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
AnnotatedFields ('Postgres pgKind))
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
fieldDescription InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
fieldArgsParser Parser MetadataObjId 'Output n (AnnotatedFields ('Postgres pgKind))
selectionSetParser
FieldParser
MetadataObjId
n
((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
AnnotatedFields ('Postgres pgKind))
-> (((FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))),
SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
AnnotatedFields ('Postgres pgKind))
-> AnnotatedField ('Postgres pgKind))
-> FieldParser n (AnnotatedField ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \((FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
functionArgs', SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
args), AnnotatedFields ('Postgres pgKind)
fields) ->
XComputedField ('Postgres pgKind)
-> ComputedFieldName
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> AnnotatedField ('Postgres pgKind)
forall (b :: BackendType) r v.
XComputedField b
-> ComputedFieldName
-> ComputedFieldSelect b r v
-> AnnFieldG b r v
IR.AFComputedField XComputedField ('Postgres pgKind)
_cfiXComputedFieldInfo ComputedFieldName
_cfiName (ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> AnnotatedField ('Postgres pgKind))
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> AnnotatedField ('Postgres pgKind)
forall a b. (a -> b) -> a -> b
$
JsonAggSelect
-> AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
JsonAggSelect
-> AnnSimpleSelectG b r v -> ComputedFieldSelect b r v
IR.CFSTable JsonAggSelect
JASMultipleRows (AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> ComputedFieldSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$
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 ('Postgres pgKind)
IR._asnFields = AnnotatedFields ('Postgres pgKind)
fields,
$sel:_asnFrom:AnnSelectG :: SelectFromG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnFrom = FunctionName ('Postgres pgKind)
-> FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> Maybe
[(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
-> SelectFromG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) v.
FunctionName b
-> FunctionArgsExp b v
-> Maybe [(Column b, ScalarType b)]
-> SelectFromG b v
IR.FromFunction (ComputedFieldFunction ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
forall (b :: BackendType).
ComputedFieldFunction b -> FunctionName b
_cffName ComputedFieldFunction ('Postgres pgKind)
_cfiFunction) FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
functionArgs' Maybe [(Column ('Postgres pgKind), ScalarType ('Postgres pgKind))]
forall a. Maybe a
Nothing,
$sel:_asnPerm:AnnSelectG :: TablePermG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnPerm = SelPermInfo ('Postgres pgKind)
-> TablePermG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType).
Backend b =>
SelPermInfo b -> TablePerms b
tablePermissionsInfo SelPermInfo ('Postgres pgKind)
remotePerms,
$sel:_asnArgs:AnnSelectG :: SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
IR._asnArgs = SelectArgsG ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
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
fieldDescription :: Maybe G.Description
fieldDescription :: Maybe Description
fieldDescription = Text -> Description
G.Description (Text -> Description) -> Maybe Text -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
_cfiDescription
computedFieldFunctionArgs ::
ComputedFieldFunction ('Postgres pgKind) ->
m (InputFieldsParser n (FunctionArgsExp ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind))))
computedFieldFunctionArgs :: ComputedFieldFunction ('Postgres pgKind)
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
computedFieldFunctionArgs ComputedFieldFunction {Maybe PGDescription
Seq (FunctionArgument ('Postgres pgKind))
FunctionName ('Postgres pgKind)
ComputedFieldImplicitArguments ('Postgres pgKind)
_cffDescription :: forall (b :: BackendType).
ComputedFieldFunction b -> Maybe PGDescription
_cffComputedFieldImplicitArgs :: forall (b :: BackendType).
ComputedFieldFunction b -> ComputedFieldImplicitArguments b
_cffInputArgs :: forall (b :: BackendType).
ComputedFieldFunction b -> Seq (FunctionArgument b)
_cffDescription :: Maybe PGDescription
_cffComputedFieldImplicitArgs :: ComputedFieldImplicitArguments ('Postgres pgKind)
_cffInputArgs :: Seq (FunctionArgument ('Postgres pgKind))
_cffName :: FunctionName ('Postgres pgKind)
_cffName :: forall (b :: BackendType).
ComputedFieldFunction b -> FunctionName b
..} =
SourceInfo ('Postgres pgKind)
-> FunctionTrackedAs ('Postgres pgKind)
-> Seq (FunctionInputArgument ('Postgres pgKind))
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> FunctionTrackedAs ('Postgres pgKind)
-> Seq (FunctionInputArgument ('Postgres pgKind))
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
functionArgs SourceInfo ('Postgres pgKind)
sourceInfo (ComputedFieldName
-> SourceName
-> TableName ('Postgres pgKind)
-> FunctionTrackedAs ('Postgres pgKind)
forall (b :: BackendType).
ComputedFieldName
-> SourceName -> TableName b -> FunctionTrackedAs b
FTAComputedField ComputedFieldName
_cfiName (SourceInfo ('Postgres pgKind) -> SourceName
forall (b :: BackendType). SourceInfo b -> SourceName
_siName SourceInfo ('Postgres pgKind)
sourceInfo) TableName ('Postgres pgKind)
parentTable) (FunctionArg -> InputArgument FunctionArg
forall a. a -> InputArgument a
IAUserProvided (FunctionArg -> InputArgument FunctionArg)
-> Seq FunctionArg -> Seq (InputArgument FunctionArg)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Seq (FunctionArgument ('Postgres pgKind))
Seq FunctionArg
_cffInputArgs)
m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
addTableAndSessionArgument
where
addTableAndSessionArgument :: FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
addTableAndSessionArgument args :: FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
args@(FunctionArgsExp [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
positional HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
named) =
let withTable :: FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
withTable = case ComputedFieldImplicitArguments -> FunctionTableArgument
PG._cffaTableArgument ComputedFieldImplicitArguments ('Postgres pgKind)
ComputedFieldImplicitArguments
_cffComputedFieldImplicitArgs of
FunctionTableArgument
PG.FTAFirst -> [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a. [a] -> HashMap Text a -> FunctionArgsExpG a
FunctionArgsExp (ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall a. ArgumentExp a
PG.AETableRow ArgumentExp (UnpreparedValue ('Postgres pgKind))
-> [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
-> [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
forall a. a -> [a] -> [a]
: [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
positional) HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
named
PG.FTANamed FunctionArgName
argName Int
index -> FunctionArgName
-> Int
-> ArgumentExp (UnpreparedValue ('Postgres pgKind))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a.
FunctionArgName
-> Int -> a -> FunctionArgsExpG a -> FunctionArgsExpG a
IR.insertFunctionArg FunctionArgName
argName Int
index ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall a. ArgumentExp a
PG.AETableRow FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
args
sessionArgVal :: ArgumentExp (UnpreparedValue b)
sessionArgVal = UnpreparedValue b -> ArgumentExp (UnpreparedValue b)
forall a. a -> ArgumentExp a
PG.AESession UnpreparedValue b
forall (b :: BackendType). UnpreparedValue b
IR.UVSession
in case ComputedFieldImplicitArguments -> Maybe FunctionSessionArgument
PG._cffaSessionArgument ComputedFieldImplicitArguments ('Postgres pgKind)
ComputedFieldImplicitArguments
_cffComputedFieldImplicitArgs of
Maybe FunctionSessionArgument
Nothing -> FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
withTable
Just (PG.FunctionSessionArgument FunctionArgName
argName Int
index) ->
FunctionArgName
-> Int
-> ArgumentExp (UnpreparedValue ('Postgres pgKind))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a.
FunctionArgName
-> Int -> a -> FunctionArgsExpG a -> FunctionArgsExpG a
IR.insertFunctionArg FunctionArgName
argName Int
index ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType). ArgumentExp (UnpreparedValue b)
sessionArgVal FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
withTable
customSQLFunctionArgs ::
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
G.Name ->
G.Name ->
m (InputFieldsParser n (FunctionArgsExp ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind))))
customSQLFunctionArgs :: SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Name
-> Name
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
customSQLFunctionArgs SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo {Maybe Text
Seq (FunctionInputArgument ('Postgres pgKind))
FunctionPermissionsMap
Name
SystemDefined
JsonAggSelect
TableName ('Postgres pgKind)
FunctionName ('Postgres pgKind)
FunctionVolatility
FunctionExposedAs
_fiComment :: Maybe Text
_fiJsonAggSelect :: JsonAggSelect
_fiPermissions :: FunctionPermissionsMap
_fiDescription :: Maybe Text
_fiReturnType :: TableName ('Postgres pgKind)
_fiInputArgs :: Seq (FunctionInputArgument ('Postgres pgKind))
_fiExposedAs :: FunctionExposedAs
_fiVolatility :: FunctionVolatility
_fiSystemDefined :: SystemDefined
_fiGQLAggregateName :: Name
_fiGQLArgsName :: Name
_fiGQLName :: Name
_fiSQLName :: FunctionName ('Postgres pgKind)
_fiComment :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiJsonAggSelect :: forall (b :: BackendType). FunctionInfo b -> JsonAggSelect
_fiPermissions :: forall (b :: BackendType). FunctionInfo b -> FunctionPermissionsMap
_fiDescription :: forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiReturnType :: forall (b :: BackendType). FunctionInfo b -> TableName b
_fiInputArgs :: forall (b :: BackendType).
FunctionInfo b -> Seq (FunctionInputArgument b)
_fiExposedAs :: forall (b :: BackendType). FunctionInfo b -> FunctionExposedAs
_fiVolatility :: forall (b :: BackendType). FunctionInfo b -> FunctionVolatility
_fiSystemDefined :: forall (b :: BackendType). FunctionInfo b -> SystemDefined
_fiGQLAggregateName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLArgsName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiGQLName :: forall (b :: BackendType). FunctionInfo b -> Name
_fiSQLName :: forall (b :: BackendType). FunctionInfo b -> FunctionName b
..} Name
functionName Name
functionArgsName =
SourceInfo ('Postgres pgKind)
-> FunctionTrackedAs ('Postgres pgKind)
-> Seq (FunctionInputArgument ('Postgres pgKind))
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> FunctionTrackedAs ('Postgres pgKind)
-> Seq (FunctionInputArgument ('Postgres pgKind))
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
functionArgs
SourceInfo ('Postgres pgKind)
sourceInfo
( CustomFunctionNames -> FunctionTrackedAs ('Postgres pgKind)
forall (b :: BackendType).
CustomFunctionNames -> FunctionTrackedAs b
FTACustomFunction (CustomFunctionNames -> FunctionTrackedAs ('Postgres pgKind))
-> CustomFunctionNames -> FunctionTrackedAs ('Postgres pgKind)
forall a b. (a -> b) -> a -> b
$
CustomFunctionNames :: Name -> Name -> CustomFunctionNames
CustomFunctionNames
{ cfnFunctionName :: Name
cfnFunctionName = Name
functionName,
cfnArgsName :: Name
cfnArgsName = Name
functionArgsName
}
)
Seq (FunctionInputArgument ('Postgres pgKind))
_fiInputArgs
functionArgs ::
forall r m n pgKind.
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind) ->
FunctionTrackedAs ('Postgres pgKind) ->
Seq.Seq (FunctionInputArgument ('Postgres pgKind)) ->
m (InputFieldsParser n (FunctionArgsExp ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind))))
functionArgs :: SourceInfo ('Postgres pgKind)
-> FunctionTrackedAs ('Postgres pgKind)
-> Seq (FunctionInputArgument ('Postgres pgKind))
-> m (InputFieldsParser
n
(FunctionArgsExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
functionArgs SourceInfo ('Postgres pgKind)
sourceInfo FunctionTrackedAs ('Postgres pgKind)
functionTrackedAs (Seq (FunctionInputArgument ('Postgres pgKind))
-> [InputArgument FunctionArg]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList -> [InputArgument FunctionArg]
inputArgs) = 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
let ([Text]
names, [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
session, [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
optional, [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
mandatory) = [([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])]
-> ([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])
forall a. Monoid a => [a] -> a
mconcat ([([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])]
-> ([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]))
-> [([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])]
-> ([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])
forall a b. (a -> b) -> a -> b
$ (Int,
[([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])])
-> [([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])]
forall a b. (a, b) -> b
snd ((Int,
[([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])])
-> [([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])])
-> (Int,
[([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])])
-> [([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])]
forall a b. (a -> b) -> a -> b
$ (Int
-> InputArgument FunctionArg
-> (Int,
([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])))
-> Int
-> [InputArgument FunctionArg]
-> (Int,
[([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))])])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL Int
-> FunctionInputArgument ('Postgres pgKind)
-> (Int,
([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]))
Int
-> InputArgument FunctionArg
-> (Int,
([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]))
splitArguments Int
1 [InputArgument FunctionArg]
inputArgs
defaultArguments :: FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
defaultArguments = [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a. [a] -> HashMap Text a -> FunctionArgsExpG a
FunctionArgsExp ((Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall a b. (a, b) -> b
snd ((Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
session) HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall k v. HashMap k v
Map.empty
if
| [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
session Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 ->
Text
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 Text
"there shouldn't be more than one session argument"
| [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
optional Bool -> Bool -> Bool
&& [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
mandatory ->
InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure FunctionArgsExpG (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
defaultArguments
| Bool
otherwise -> do
[InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))]
argumentParsers <- [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> m [InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> m [InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))])
-> [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> m [InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))]
forall a b. (a -> b) -> a -> b
$ [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
optional [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
-> [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
forall a. Semigroup a => a -> a -> a
<> [m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]
mandatory
Name
objectName <-
Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name)
-> (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> m Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase
(GQLNameIdentifier -> m Name) -> m GQLNameIdentifier -> m Name
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< case FunctionTrackedAs ('Postgres pgKind)
functionTrackedAs of
FTAComputedField ComputedFieldName
computedFieldName SourceName
_sourceName TableName ('Postgres pgKind)
tableName -> do
TableInfo ('Postgres pgKind)
tableInfo <- SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind) -> m (TableInfo ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceInfo b -> TableName b -> m (TableInfo b)
askTableInfo SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
tableName
Name
computedFieldGQLName <- 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
$ ComputedFieldName -> Text
computedFieldNameToText ComputedFieldName
computedFieldName
GQLNameIdentifier
tableGQLName <- TableInfo ('Postgres pgKind) -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName @('Postgres pgKind) TableInfo ('Postgres pgKind)
tableInfo
pure $ Name -> GQLNameIdentifier -> GQLNameIdentifier
mkFunctionArgsTypeName Name
computedFieldGQLName GQLNameIdentifier
tableGQLName
FTACustomFunction (CustomFunctionNames {Name
cfnArgsName :: Name
cfnArgsName :: CustomFunctionNames -> Name
cfnArgsName}) ->
GQLNameIdentifier -> m GQLNameIdentifier
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GQLNameIdentifier -> m GQLNameIdentifier)
-> GQLNameIdentifier -> m GQLNameIdentifier
forall a b. (a -> b) -> a -> b
$ Name -> GQLNameIdentifier
C.fromCustomName Name
cfnArgsName
let fieldName :: Name
fieldName = Name
Name._args
fieldDesc :: Description
fieldDesc =
case FunctionTrackedAs ('Postgres pgKind)
functionTrackedAs of
FTAComputedField ComputedFieldName
computedFieldName SourceName
_sourceName TableName ('Postgres pgKind)
tableName ->
Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$
Text
"input parameters for computed field "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ComputedFieldName
computedFieldName ComputedFieldName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" defined on table " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
FTACustomFunction (CustomFunctionNames {Name
cfnFunctionName :: Name
cfnFunctionName :: CustomFunctionNames -> Name
cfnFunctionName}) ->
Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"input parameters for function " Text -> Name -> Text
forall t. ToTxt t => Text -> t -> Text
<>> Name
cfnFunctionName
objectParser :: Parser
MetadataObjId
'Input
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
objectParser =
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
[Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> Parser
MetadataObjId
'Input
n
[Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
objectName Maybe Description
forall a. Maybe a
Nothing ([InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))]
-> InputFieldsParser
MetadataObjId
n
[Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA [InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))]
argumentParsers) Parser
MetadataObjId
'Input
n
[Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> ([Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> n (FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> Parser
MetadataObjId
'Input
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (m :: * -> *) origin (k :: Kind) a b.
Monad m =>
Parser origin k m a -> (a -> m b) -> Parser origin k m b
`P.bind` \[Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
arguments -> do
let foundArguments :: HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
foundArguments = [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$ [Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
arguments [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
forall a. Semigroup a => a -> a -> a
<> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
session
argsWithNames :: [(Text, InputArgument FunctionArg)]
argsWithNames = [Text]
-> [InputArgument FunctionArg]
-> [(Text, InputArgument FunctionArg)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
names [InputArgument FunctionArg]
inputArgs
([ArgumentExp (UnpreparedValue ('Postgres pgKind))]
positional, [(Text, InputArgument FunctionArg)]
left) <- ((Text, InputArgument FunctionArg)
-> n (Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> [(Text, InputArgument FunctionArg)]
-> n ([ArgumentExp (UnpreparedValue ('Postgres pgKind))],
[(Text, InputArgument FunctionArg)])
forall (f :: * -> *) (m :: * -> *) a b.
(Foldable f, Monad m) =>
(a -> m (Maybe b)) -> f a -> m ([b], [a])
spanMaybeM (\(Text
name, InputArgument FunctionArg
_) -> Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$ Text
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup Text
name HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
foundArguments) [(Text, InputArgument FunctionArg)]
argsWithNames
HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
named <- [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
Map.fromList ([(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> ([Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))])
-> [Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> [(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes ([Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> n [Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
-> n (HashMap
Text (ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text, InputArgument FunctionArg)
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> [(Text, InputArgument FunctionArg)]
-> n [Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> (Text, FunctionInputArgument ('Postgres pgKind))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
namedArgument HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
foundArguments) [(Text, InputArgument FunctionArg)]
left
pure $ [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a. [a] -> HashMap Text a -> FunctionArgsExpG a
FunctionArgsExp [ArgumentExp (UnpreparedValue ('Postgres pgKind))]
positional HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
named
InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m a
P.field Name
fieldName (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
fieldDesc) Parser
MetadataObjId
'Input
n
(FunctionArgsExpG
(ArgumentExp (UnpreparedValue ('Postgres pgKind))))
objectParser
where
sessionPlaceholder :: PG.ArgumentExp (IR.UnpreparedValue b)
sessionPlaceholder :: ArgumentExp (UnpreparedValue b)
sessionPlaceholder = UnpreparedValue b -> ArgumentExp (UnpreparedValue b)
forall a. a -> ArgumentExp a
PG.AEInput UnpreparedValue b
forall (b :: BackendType). UnpreparedValue b
IR.UVSession
splitArguments ::
Int ->
FunctionInputArgument ('Postgres pgKind) ->
( Int,
( [Text],
[(Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))]
)
)
splitArguments :: Int
-> FunctionInputArgument ('Postgres pgKind)
-> (Int,
([Text],
[(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))],
[m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))],
[m (InputFieldsParser
n
(Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))]))
splitArguments Int
positionalIndex (IASessionVariables FunctionArgName
name) =
let argName :: Text
argName = FunctionArgName -> Text
getFuncArgNameTxt FunctionArgName
name
in (Int
positionalIndex, ([Text
argName], [(Text
argName, ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType). ArgumentExp (UnpreparedValue b)
sessionPlaceholder)], [], []))
splitArguments Int
positionalIndex (IAUserProvided FunctionArgument ('Postgres pgKind)
arg) =
let (Text
argName, Int
newIndex) = case FunctionArg -> Maybe FunctionArgName
PG.faName FunctionArgument ('Postgres pgKind)
FunctionArg
arg of
Maybe FunctionArgName
Nothing -> (Text
"arg_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
positionalIndex, Int
positionalIndex Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
Just FunctionArgName
name -> (FunctionArgName -> Text
getFuncArgNameTxt FunctionArgName
name, Int
positionalIndex)
in if HasDefault -> Bool
PG.unHasDefault (HasDefault -> Bool) -> HasDefault -> Bool
forall a b. (a -> b) -> a -> b
$ FunctionArg -> HasDefault
PG.faHasDefault FunctionArgument ('Postgres pgKind)
FunctionArg
arg
then (Int
newIndex, ([Text
argName], [], [FunctionArgument ('Postgres pgKind)
-> Text
-> m (InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
parseArgument FunctionArgument ('Postgres pgKind)
arg Text
argName], []))
else (Int
newIndex, ([Text
argName], [], [], [FunctionArgument ('Postgres pgKind)
-> Text
-> m (InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
parseArgument FunctionArgument ('Postgres pgKind)
arg Text
argName]))
parseArgument :: FunctionArgument ('Postgres pgKind) -> Text -> m (InputFieldsParser n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind)))))
parseArgument :: FunctionArgument ('Postgres pgKind)
-> Text
-> m (InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
parseArgument FunctionArgument ('Postgres pgKind)
arg Text
name = do
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
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 (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind))
-> ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall a b. (a -> b) -> a -> b
$ QualifiedPGType -> PGScalarType
PG.mkFunctionArgScalarType (QualifiedPGType -> PGScalarType)
-> QualifiedPGType -> PGScalarType
forall a b. (a -> b) -> a -> b
$ FunctionArg -> QualifiedPGType
PG.faType FunctionArgument ('Postgres pgKind)
FunctionArg
arg) (Bool -> Nullability
G.Nullability Bool
True)
Name
fieldName <- Text -> m Name
forall (m :: * -> *). MonadError QErr m => Text -> m Name
textToName Text
name
let argParser :: InputFieldsParser
MetadataObjId
n
(Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
argParser = Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
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
fieldName Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser
InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
n
(Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))))
-> InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ InputFieldsParser
MetadataObjId
n
(Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
argParser InputFieldsParser
MetadataObjId
n
(Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (m :: * -> *) a b.
Functor m =>
InputFieldsParser m (Maybe a)
-> (a -> b) -> InputFieldsParser m (Maybe b)
`mapField` ((Text
name,) (ArgumentExp (UnpreparedValue ('Postgres pgKind))
-> (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall a. a -> ArgumentExp a
PG.AEInput (UnpreparedValue ('Postgres pgKind)
-> ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter)
namedArgument ::
HashMap Text (PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind))) ->
(Text, FunctionInputArgument ('Postgres pgKind)) ->
n (Maybe (Text, PG.ArgumentExp (IR.UnpreparedValue ('Postgres pgKind))))
namedArgument :: HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> (Text, FunctionInputArgument ('Postgres pgKind))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
namedArgument HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
dictionary (Text
name, FunctionInputArgument ('Postgres pgKind)
inputArgument) = case FunctionInputArgument ('Postgres pgKind)
inputArgument of
IASessionVariables FunctionArgName
_ -> Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$ (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a. a -> Maybe a
Just (Text
name, ArgumentExp (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType). ArgumentExp (UnpreparedValue b)
sessionPlaceholder)
IAUserProvided FunctionArgument ('Postgres pgKind)
arg -> case Text
-> HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup Text
name HashMap Text (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
dictionary of
Just ArgumentExp (UnpreparedValue ('Postgres pgKind))
parsedValue -> case FunctionArg -> Maybe FunctionArgName
PG.faName FunctionArgument ('Postgres pgKind)
FunctionArg
arg of
Just FunctionArgName
_ -> Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$ (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> Maybe (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall a. a -> Maybe a
Just (Text
name, ArgumentExp (UnpreparedValue ('Postgres pgKind))
parsedValue)
Maybe FunctionArgName
Nothing -> ParseErrorCode
-> ErrorMessage
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (m :: * -> *) a.
MonadParse m =>
ParseErrorCode -> ErrorMessage -> m a
P.parseErrorWith ParseErrorCode
P.NotSupported ErrorMessage
"Only last set of positional arguments can be omitted"
Maybe (ArgumentExp (UnpreparedValue ('Postgres pgKind)))
Nothing ->
Bool
-> n (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall (m :: * -> *) a. Applicative m => Bool -> m a -> m (Maybe a)
whenMaybe (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ HasDefault -> Bool
PG.unHasDefault (HasDefault -> Bool) -> HasDefault -> Bool
forall a b. (a -> b) -> a -> b
$ FunctionArg -> HasDefault
PG.faHasDefault FunctionArgument ('Postgres pgKind)
FunctionArg
arg) (n (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))))
-> n (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
-> n (Maybe
(Text, ArgumentExp (UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$
ParseErrorCode
-> ErrorMessage
-> n (Text, ArgumentExp (UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) a.
MonadParse m =>
ParseErrorCode -> ErrorMessage -> m a
P.parseErrorWith ParseErrorCode
P.NotSupported ErrorMessage
"Non default arguments cannot be omitted"
buildFunctionQueryFieldsPG ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
FunctionName ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
m [FieldParser n (QueryDB ('Postgres pgKind) (RemoteRelationshipField UnpreparedValue) (UnpreparedValue ('Postgres pgKind)))]
buildFunctionQueryFieldsPG :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionQueryFieldsPG MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo FunctionName ('Postgres pgKind)
functionName FunctionInfo ('Postgres pgKind)
functionInfo TableName ('Postgres pgKind)
tableName = do
let
funcDesc :: Maybe Description
funcDesc =
Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> (Text -> Description) -> Text -> Maybe Description
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Description
G.Description (Text -> Maybe Description) -> Text -> Maybe Description
forall a b. (a -> b) -> a -> b
$
(Text -> Maybe Text -> Text) -> Maybe Text -> Text -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (FunctionInfo ('Postgres pgKind) -> Maybe Text
forall (b :: BackendType). FunctionInfo b -> Maybe Text
_fiComment FunctionInfo ('Postgres pgKind)
functionInfo) (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
"execute function " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FunctionName ('Postgres pgKind)
QualifiedFunction
functionName QualifiedFunction -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" which returns " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
funcAggDesc :: Maybe Description
funcAggDesc =
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
"execute function " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FunctionName ('Postgres pgKind)
QualifiedFunction
functionName QualifiedFunction -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" and query aggregates on result of table type " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
queryResultType :: AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
queryResultType =
case FunctionInfo ('Postgres pgKind) -> JsonAggSelect
forall (b :: BackendType). FunctionInfo b -> JsonAggSelect
_fiJsonAggSelect FunctionInfo ('Postgres pgKind)
functionInfo of
JsonAggSelect
JASMultipleRows -> AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
AnnSimpleSelectG b r v -> QueryDB b r v
QDBMultipleRows
JsonAggSelect
JASSingleObject -> AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
AnnSimpleSelectG b r v -> QueryDB b r v
QDBSingleRow
[Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
-> [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
([Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
-> [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
-> m [Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))]
-> m [Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA
[ (AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser (AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
queryResultType) (m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))))
-> m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
selectFunction MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo ('Postgres pgKind)
functionInfo Maybe Description
funcDesc,
(AnnAggregateSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> m (Maybe
(FieldParser
n
(AnnAggregateSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser (AnnAggregateSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
AnnAggregateSelectG b r v -> QueryDB b r v
QDBAggregation) (m (Maybe
(FieldParser
n
(AnnAggregateSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))))
-> m (Maybe
(FieldParser
n
(AnnAggregateSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnAggregateSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp ('Postgres pgKind))))
selectFunctionAggregate MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo ('Postgres pgKind)
functionInfo Maybe Description
funcAggDesc
]
buildFunctionMutationFieldsPG ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
FunctionName ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
m [FieldParser n (MutationDB ('Postgres pgKind) (RemoteRelationshipField UnpreparedValue) (UnpreparedValue ('Postgres pgKind)))]
buildFunctionMutationFieldsPG :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionMutationFieldsPG MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo FunctionName ('Postgres pgKind)
functionName FunctionInfo ('Postgres pgKind)
functionInfo TableName ('Postgres pgKind)
tableName = do
let funcDesc :: Maybe Description
funcDesc = 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
"execute VOLATILE function " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FunctionName ('Postgres pgKind)
QualifiedFunction
functionName QualifiedFunction -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" which returns " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
jsonAggSelect :: JsonAggSelect
jsonAggSelect = FunctionInfo ('Postgres pgKind) -> JsonAggSelect
forall (b :: BackendType). FunctionInfo b -> JsonAggSelect
_fiJsonAggSelect FunctionInfo ('Postgres pgKind)
functionInfo
[Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
-> [FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
([Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
-> [FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
-> m [Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
-> m [FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [m (Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))]
-> m [Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA
[ (AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall (n :: * -> *) (m :: * -> *) a b.
(Functor n, Functor m) =>
(a -> b)
-> m (Maybe (FieldParser n a)) -> m (Maybe (FieldParser n b))
optionalFieldParser (JsonAggSelect
-> AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
JsonAggSelect -> AnnSimpleSelectG b r v -> MutationDB b r v
MDBFunction JsonAggSelect
jsonAggSelect) (m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))))
-> m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall a b. (a -> b) -> a -> b
$ MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe
(FieldParser
n
(AnnSimpleSelectG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
selectFunction MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceInfo FunctionInfo ('Postgres pgKind)
functionInfo Maybe Description
funcDesc
]