{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Backends.Postgres.Instances.Schema
(
)
where
import Data.Aeson qualified as J
import Data.Aeson.Key qualified as K
import Data.Aeson.Types (JSONPathElement (..))
import Data.Has
import Data.HashMap.Strict qualified as Map
import Data.HashMap.Strict.Extended qualified as M
import Data.List.NonEmpty qualified as NE
import Data.Parser.JSONPath
import Data.Text.Casing qualified as C
import Data.Text.Extended
import Hasura.Backends.Postgres.SQL.DML as PG hiding (CountType, incOp)
import Hasura.Backends.Postgres.SQL.Types as PG hiding (FunctionName, TableName)
import Hasura.Backends.Postgres.SQL.Value as PG
import Hasura.Backends.Postgres.Schema.OnConflict
import Hasura.Backends.Postgres.Schema.Select
import Hasura.Backends.Postgres.Types.BoolExp
import Hasura.Backends.Postgres.Types.Column
import Hasura.Backends.Postgres.Types.Insert as PGIR
import Hasura.Backends.Postgres.Types.Update as PGIR
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (toErrorMessage)
import Hasura.Base.ToErrorValue
import Hasura.GraphQL.Schema.Backend
( BackendSchema,
BackendTableSelectSchema,
ComparisonExp,
MonadBuildSchema,
)
import Hasura.GraphQL.Schema.Backend qualified as BS
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.BoolExp.AggregationPredicates as Agg
import Hasura.GraphQL.Schema.Build qualified as GSB
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.Mutation qualified as GSB
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options (SchemaOptions)
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser
( Definition,
FieldParser,
InputFieldsParser,
Kind (..),
MonadMemoize,
MonadParse,
Parser,
memoize,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.Table (getTableIdentifierName, tableColumns)
import Hasura.GraphQL.Schema.Typename
import Hasura.GraphQL.Schema.Update qualified as SU
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR.BoolExp
import Hasura.RQL.IR.Returning (MutationOutputG (..))
import Hasura.RQL.IR.Root (RemoteRelationshipField)
import Hasura.RQL.IR.Select
( QueryDB (QDBConnection),
)
import Hasura.RQL.IR.Select qualified as IR
import Hasura.RQL.IR.Update qualified as IR
import Hasura.RQL.IR.Value qualified as IR
import Hasura.RQL.Types.Backend (Backend (..))
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Function (FunctionInfo)
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.RQL.Types.Table (CustomRootField (..), RolePermInfo (..), TableConfig (..), TableCoreInfoG (..), TableCustomRootFields (..), TableInfo (..), UpdPermInfo (..), ViewInfo (..), getRolePermInfo, isMutable, tableInfoName)
import Hasura.SQL.Backend (BackendType (Postgres), PostgresKind (Citus, Cockroach, Vanilla))
import Hasura.SQL.Tag (HasTag)
import Hasura.SQL.Types
import Language.GraphQL.Draft.Syntax qualified as G
import Language.GraphQL.Draft.Syntax.QQ qualified as G
class PostgresSchema (pgKind :: PostgresKind) where
pgkBuildTableRelayQueryFields ::
forall r m n.
MonadBuildSchema ('Postgres pgKind) r m n =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
C.GQLNameIdentifier ->
NESeq (ColumnInfo ('Postgres pgKind)) ->
m [FieldParser n (QueryDB ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
pgkBuildFunctionRelayQueryFields ::
forall r m n.
MonadBuildSchema ('Postgres pgKind) r m n =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
FunctionName ('Postgres pgKind) ->
FunctionInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
NESeq (ColumnInfo ('Postgres pgKind)) ->
m [FieldParser n (QueryDB ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
pgkRelayExtension ::
Maybe (XRelay ('Postgres pgKind))
instance PostgresSchema 'Vanilla where
pgkBuildTableRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres 'Vanilla)
-> TableName ('Postgres 'Vanilla)
-> TableInfo ('Postgres 'Vanilla)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres 'Vanilla))
-> m [FieldParser
n
(QueryDB
('Postgres 'Vanilla)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Vanilla)))]
pgkBuildTableRelayQueryFields = MkRootFieldName
-> SourceInfo ('Postgres 'Vanilla)
-> TableName ('Postgres 'Vanilla)
-> TableInfo ('Postgres 'Vanilla)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres 'Vanilla))
-> m [FieldParser
n
(QueryDB
('Postgres 'Vanilla)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Vanilla)))]
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableRelayQueryFields
pgkBuildFunctionRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres 'Vanilla)
-> FunctionName ('Postgres 'Vanilla)
-> FunctionInfo ('Postgres 'Vanilla)
-> TableName ('Postgres 'Vanilla)
-> NESeq (ColumnInfo ('Postgres 'Vanilla))
-> m [FieldParser
n
(QueryDB
('Postgres 'Vanilla)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Vanilla)))]
pgkBuildFunctionRelayQueryFields = MkRootFieldName
-> SourceInfo ('Postgres 'Vanilla)
-> FunctionName ('Postgres 'Vanilla)
-> FunctionInfo ('Postgres 'Vanilla)
-> TableName ('Postgres 'Vanilla)
-> NESeq (ColumnInfo ('Postgres 'Vanilla))
-> m [FieldParser
n
(QueryDB
('Postgres 'Vanilla)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Vanilla)))]
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionRelayQueryFields
pgkRelayExtension :: Maybe (XRelay ('Postgres 'Vanilla))
pgkRelayExtension = () -> Maybe ()
forall a. a -> Maybe a
Just ()
instance PostgresSchema 'Citus where
pgkBuildTableRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres 'Citus)
-> TableName ('Postgres 'Citus)
-> TableInfo ('Postgres 'Citus)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres 'Citus))
-> m [FieldParser
n
(QueryDB
('Postgres 'Citus)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Citus)))]
pgkBuildTableRelayQueryFields MkRootFieldName
_ SourceInfo ('Postgres 'Citus)
_ TableName ('Postgres 'Citus)
_ TableInfo ('Postgres 'Citus)
_ GQLNameIdentifier
_ NESeq (ColumnInfo ('Postgres 'Citus))
_ = [FieldParser
n
(QueryDB
('Postgres 'Citus)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Citus)))]
-> m [FieldParser
n
(QueryDB
('Postgres 'Citus)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Citus)))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
pgkBuildFunctionRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres 'Citus)
-> FunctionName ('Postgres 'Citus)
-> FunctionInfo ('Postgres 'Citus)
-> TableName ('Postgres 'Citus)
-> NESeq (ColumnInfo ('Postgres 'Citus))
-> m [FieldParser
n
(QueryDB
('Postgres 'Citus)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Citus)))]
pgkBuildFunctionRelayQueryFields MkRootFieldName
_ SourceInfo ('Postgres 'Citus)
_ FunctionName ('Postgres 'Citus)
_ FunctionInfo ('Postgres 'Citus)
_ TableName ('Postgres 'Citus)
_ NESeq (ColumnInfo ('Postgres 'Citus))
_ = [FieldParser
n
(QueryDB
('Postgres 'Citus)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Citus)))]
-> m [FieldParser
n
(QueryDB
('Postgres 'Citus)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Citus)))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
pgkRelayExtension :: Maybe (XRelay ('Postgres 'Citus))
pgkRelayExtension = Maybe (XRelay ('Postgres 'Citus))
forall a. Maybe a
Nothing
instance PostgresSchema 'Cockroach where
pgkBuildTableRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres 'Cockroach)
-> TableName ('Postgres 'Cockroach)
-> TableInfo ('Postgres 'Cockroach)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres 'Cockroach))
-> m [FieldParser
n
(QueryDB
('Postgres 'Cockroach)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Cockroach)))]
pgkBuildTableRelayQueryFields = MkRootFieldName
-> SourceInfo ('Postgres 'Cockroach)
-> TableName ('Postgres 'Cockroach)
-> TableInfo ('Postgres 'Cockroach)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres 'Cockroach))
-> m [FieldParser
n
(QueryDB
('Postgres 'Cockroach)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Cockroach)))]
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableRelayQueryFields
pgkBuildFunctionRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres 'Cockroach)
-> FunctionName ('Postgres 'Cockroach)
-> FunctionInfo ('Postgres 'Cockroach)
-> TableName ('Postgres 'Cockroach)
-> NESeq (ColumnInfo ('Postgres 'Cockroach))
-> m [FieldParser
n
(QueryDB
('Postgres 'Cockroach)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Cockroach)))]
pgkBuildFunctionRelayQueryFields = MkRootFieldName
-> SourceInfo ('Postgres 'Cockroach)
-> FunctionName ('Postgres 'Cockroach)
-> FunctionInfo ('Postgres 'Cockroach)
-> TableName ('Postgres 'Cockroach)
-> NESeq (ColumnInfo ('Postgres 'Cockroach))
-> m [FieldParser
n
(QueryDB
('Postgres 'Cockroach)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres 'Cockroach)))]
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionRelayQueryFields
pgkRelayExtension :: Maybe (XRelay ('Postgres 'Cockroach))
pgkRelayExtension = () -> Maybe ()
forall a. a -> Maybe a
Just ()
instance AggregationPredicatesSchema ('Postgres pgKind) where
aggregationPredicatesParser :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(InputFieldsParser
n
[AggregationPredicates
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))]))
aggregationPredicatesParser SourceInfo ('Postgres pgKind)
_ TableInfo ('Postgres pgKind)
_ = Maybe
(InputFieldsParser
n
[AggregationPredicatesImplementation
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))])
-> m (Maybe
(InputFieldsParser
n
[AggregationPredicatesImplementation
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))]))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe
(InputFieldsParser
n
[AggregationPredicatesImplementation
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))])
forall a. Maybe a
Nothing
_aggregationFunctions :: [Agg.FunctionSignature ('Postgres pgKind)]
_aggregationFunctions :: [FunctionSignature ('Postgres pgKind)]
_aggregationFunctions =
[ FunctionSignature :: forall (b :: BackendType).
Text
-> Name
-> ArgumentsSignature b
-> ScalarType b
-> FunctionSignature b
Agg.FunctionSignature
{ fnName :: Text
fnName = Text
"count",
fnGQLName :: Name
fnGQLName = [G.name|count|],
fnReturnType :: ScalarType ('Postgres pgKind)
fnReturnType = ScalarType ('Postgres pgKind)
PGScalarType
PGInteger,
fnArguments :: ArgumentsSignature ('Postgres pgKind)
fnArguments = ArgumentsSignature ('Postgres pgKind)
forall (b :: BackendType). ArgumentsSignature b
Agg.ArgumentsStar
},
FunctionSignature :: forall (b :: BackendType).
Text
-> Name
-> ArgumentsSignature b
-> ScalarType b
-> FunctionSignature b
Agg.FunctionSignature
{ fnName :: Text
fnName = Text
"bool_and",
fnGQLName :: Name
fnGQLName = [G.name|bool_and|],
fnReturnType :: ScalarType ('Postgres pgKind)
fnReturnType = ScalarType ('Postgres pgKind)
PGScalarType
PGBoolean,
fnArguments :: ArgumentsSignature ('Postgres pgKind)
fnArguments =
NonEmpty (ArgumentSignature ('Postgres pgKind))
-> ArgumentsSignature ('Postgres pgKind)
forall (b :: BackendType).
NonEmpty (ArgumentSignature b) -> ArgumentsSignature b
Agg.Arguments
( [ArgumentSignature ('Postgres pgKind)]
-> NonEmpty (ArgumentSignature ('Postgres pgKind))
forall a. [a] -> NonEmpty a
NE.fromList
[ ArgumentSignature :: forall (b :: BackendType).
ScalarType b -> Name -> ArgumentSignature b
Agg.ArgumentSignature
{ argType :: ScalarType ('Postgres pgKind)
argType = ScalarType ('Postgres pgKind)
PGScalarType
PGBoolean,
argName :: Name
argName = [G.name|arg0|]
}
]
)
},
FunctionSignature :: forall (b :: BackendType).
Text
-> Name
-> ArgumentsSignature b
-> ScalarType b
-> FunctionSignature b
Agg.FunctionSignature
{ fnName :: Text
fnName = Text
"corr",
fnGQLName :: Name
fnGQLName = [G.name|corr|],
fnReturnType :: ScalarType ('Postgres pgKind)
fnReturnType = ScalarType ('Postgres pgKind)
PGScalarType
PGDouble,
fnArguments :: ArgumentsSignature ('Postgres pgKind)
fnArguments =
NonEmpty (ArgumentSignature ('Postgres pgKind))
-> ArgumentsSignature ('Postgres pgKind)
forall (b :: BackendType).
NonEmpty (ArgumentSignature b) -> ArgumentsSignature b
Agg.Arguments
( [ArgumentSignature ('Postgres pgKind)]
-> NonEmpty (ArgumentSignature ('Postgres pgKind))
forall a. [a] -> NonEmpty a
NE.fromList
[ ArgumentSignature :: forall (b :: BackendType).
ScalarType b -> Name -> ArgumentSignature b
Agg.ArgumentSignature
{ argType :: ScalarType ('Postgres pgKind)
argType = ScalarType ('Postgres pgKind)
PGScalarType
PGDouble,
argName :: Name
argName = [G.name|Y|]
},
ArgumentSignature :: forall (b :: BackendType).
ScalarType b -> Name -> ArgumentSignature b
Agg.ArgumentSignature
{ argType :: ScalarType ('Postgres pgKind)
argType = ScalarType ('Postgres pgKind)
PGScalarType
PGDouble,
argName :: Name
argName = [G.name|X|]
}
]
)
}
]
instance
( PostgresSchema pgKind,
Backend ('Postgres pgKind),
HasTag ('Postgres pgKind)
) =>
BS.BackendTableSelectSchema ('Postgres pgKind)
where
tableArguments :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
tableArguments = SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(SelectArgsG
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
SourceInfo b
-> TableInfo b -> m (InputFieldsParser n (SelectArgs b))
defaultTableArgs
selectTable :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
selectTable = SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp b)))
defaultSelectTable
selectTableAggregate :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp ('Postgres pgKind))))
selectTableAggregate = SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp b)))
defaultSelectTableAggregate
tableSelectionSet :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
tableSelectionSet = SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe
(Parser 'Output n (AnnotatedFields ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, BackendTableSelectSchema b,
Eq (AnnBoolExp b (UnpreparedValue b)), MonadBuildSchema b r m n) =>
SourceInfo b
-> TableInfo b -> m (Maybe (Parser 'Output n (AnnotatedFields b)))
defaultTableSelectionSet
instance
( Backend ('Postgres pgKind),
PostgresSchema pgKind
) =>
BackendSchema ('Postgres pgKind)
where
buildTableQueryAndSubscriptionFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))],
[FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
buildTableQueryAndSubscriptionFields = MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))],
[FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
[FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
GSB.buildTableQueryAndSubscriptionFields
buildTableRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableRelayQueryFields = MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
(PostgresSchema pgKind,
MonadBuildSchema ('Postgres pgKind) r m n) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
pgkBuildTableRelayQueryFields
buildTableStreamingSubscriptionFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableStreamingSubscriptionFields = MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(QueryDB
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableInsertMutationFields = (SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(BackendInsert
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
-> MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
(SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
GSB.buildTableInsertMutationFields SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(BackendInsert
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) (m :: * -> *) r (n :: * -> *).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n (BackendInsert pgKind (UnpreparedValue ('Postgres pgKind))))
backendInsertParser
buildTableUpdateMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableUpdateMutationFields = MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
pgkBuildTableUpdateMutationFields
buildTableDeleteMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableDeleteMutationFields = MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
GSB.buildTableDeleteMutationFields
buildFunctionQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionQueryFields = MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(QueryDB
('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)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionQueryFieldsPG
buildFunctionRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionRelayQueryFields = MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
(PostgresSchema pgKind,
MonadBuildSchema ('Postgres pgKind) r m n) =>
MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
pgkBuildFunctionRelayQueryFields
buildFunctionMutationFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionMutationFields = MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(MutationDB
('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)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> m [FieldParser
n
(MutationDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionMutationFieldsPG
mkRelationshipParser :: SourceInfo ('Postgres pgKind)
-> RelInfo ('Postgres pgKind)
-> m (Maybe
(InputFieldsParser
n
(Maybe
(AnnotatedInsertField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))))
mkRelationshipParser = (SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(BackendInsert
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
-> XNestedInserts ('Postgres pgKind)
-> SourceInfo ('Postgres pgKind)
-> RelInfo ('Postgres pgKind)
-> m (Maybe
(InputFieldsParser
n
(Maybe
(AnnotatedInsertField
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
(SourceInfo b
-> TableInfo b
-> m (InputFieldsParser n (BackendInsert b (UnpreparedValue b))))
-> XNestedInserts b
-> SourceInfo b
-> RelInfo b
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField b (UnpreparedValue b)))))
GSB.mkDefaultRelationshipParser SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(BackendInsert
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) (m :: * -> *) r (n :: * -> *).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n (BackendInsert pgKind (UnpreparedValue ('Postgres pgKind))))
backendInsertParser ()
relayExtension :: Maybe (XRelay ('Postgres pgKind))
relayExtension = PostgresSchema pgKind => Maybe (XRelay ('Postgres pgKind))
forall (pgKind :: PostgresKind).
PostgresSchema pgKind =>
Maybe (XRelay ('Postgres pgKind))
pgkRelayExtension @pgKind
nodesAggExtension :: Maybe (XNodesAgg ('Postgres pgKind))
nodesAggExtension = () -> Maybe ()
forall a. a -> Maybe a
Just ()
streamSubscriptionExtension :: Maybe (XStreamingSubscription ('Postgres pgKind))
streamSubscriptionExtension = () -> Maybe ()
forall a. a -> Maybe a
Just ()
columnParser :: ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser = ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser
scalarSelectionArgumentsParser :: ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
scalarSelectionArgumentsParser = ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
forall (n :: * -> *) (pgKind :: PostgresKind).
MonadParse n =>
ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
pgScalarSelectionArgumentsParser
orderByOperators :: SourceInfo ('Postgres pgKind)
-> NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperators SourceInfo ('Postgres pgKind)
_sourceInfo = \case
NamingCase
HasuraCase -> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
forall (pgKind :: PostgresKind).
(Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperatorsHasuraCase
NamingCase
GraphqlCase -> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
forall (pgKind :: PostgresKind).
(Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperatorsGraphqlCase
comparisonExps :: ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
comparisonExps = ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadMemoize m, MonadParse n,
MonadError QErr m, MonadReader r m, Has SchemaOptions r,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
comparisonExps
countTypeInput :: Maybe (Parser 'Both n (Column ('Postgres pgKind)))
-> InputFieldsParser
n (CountDistinct -> CountType ('Postgres pgKind))
countTypeInput = Maybe (Parser 'Both n (Column ('Postgres pgKind)))
-> InputFieldsParser
n (CountDistinct -> CountType ('Postgres pgKind))
forall (n :: * -> *) (pgKind :: PostgresKind).
MonadParse n =>
Maybe (Parser 'Both n (Column ('Postgres pgKind)))
-> InputFieldsParser
n (CountDistinct -> CountType ('Postgres pgKind))
countTypeInput
aggregateOrderByCountType :: ScalarType ('Postgres pgKind)
aggregateOrderByCountType = ScalarType ('Postgres pgKind)
PGScalarType
PG.PGInteger
computedField :: SourceInfo ('Postgres pgKind)
-> ComputedFieldInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe (FieldParser n (AnnotatedField ('Postgres pgKind))))
computedField = SourceInfo ('Postgres pgKind)
-> ComputedFieldInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Maybe (FieldParser n (AnnotatedField ('Postgres pgKind))))
forall (pgKind :: PostgresKind) 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
backendInsertParser ::
forall pgKind m r n.
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
m (InputFieldsParser n (PGIR.BackendInsert pgKind (IR.UnpreparedValue ('Postgres pgKind))))
backendInsertParser :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n (BackendInsert pgKind (UnpreparedValue ('Postgres pgKind))))
backendInsertParser SourceInfo ('Postgres pgKind)
sourceName TableInfo ('Postgres pgKind)
tableInfo =
(Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> BackendInsert pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n (BackendInsert pgKind (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> BackendInsert pgKind (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) v.
Maybe (OnConflictClause ('Postgres pgKind) v)
-> BackendInsert pgKind v
BackendInsert (InputFieldsParser
MetadataObjId
n
(Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n (BackendInsert pgKind (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
-> m (InputFieldsParser
n (BackendInsert pgKind (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
MetadataObjId
n
(Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema ('Postgres pgKind) r m n,
AggregationPredicatesSchema ('Postgres pgKind)) =>
SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(Maybe
(OnConflictClause
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
onConflictFieldParser SourceInfo ('Postgres pgKind)
sourceName TableInfo ('Postgres pgKind)
tableInfo
buildTableRelayQueryFields ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
SourceInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
C.GQLNameIdentifier ->
NESeq (ColumnInfo ('Postgres pgKind)) ->
m [FieldParser n (QueryDB ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
buildTableRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildTableRelayQueryFields MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceName TableName ('Postgres pgKind)
tableName TableInfo ('Postgres pgKind)
tableInfo GQLNameIdentifier
gqlName NESeq (ColumnInfo ('Postgres pgKind))
pkeyColumns = 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 fieldDesc :: Maybe Description
fieldDesc = Description -> Maybe Description
forall a. a -> Maybe a
Just (Description -> Maybe Description)
-> Description -> Maybe Description
forall a b. (a -> b) -> a -> b
$ Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$ Text
"fetch data from the table: " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
rootFieldName :: Name
rootFieldName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyFieldNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> GQLNameIdentifier
mkRelayConnectionField GQLNameIdentifier
gqlName)
(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
fmap Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t a -> f a
afold (m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m [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 a b. (a -> b) -> a -> b
$
(ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> m (Maybe
(FieldParser
n
(ConnectionSelect
('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 ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
ConnectionSelect b r v -> QueryDB b r v
QDBConnection (m (Maybe
(FieldParser
n
(ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))))
-> m (Maybe
(FieldParser
n
(ConnectionSelect
('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
$
SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> Name
-> Maybe Description
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m (Maybe
(FieldParser
n
(ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b,
AggregationPredicatesSchema b) =>
SourceInfo b
-> TableInfo b
-> Name
-> Maybe Description
-> PrimaryKeyColumns b
-> m (Maybe (FieldParser n (ConnectionSelectExp b)))
selectTableConnection SourceInfo ('Postgres pgKind)
sourceName TableInfo ('Postgres pgKind)
tableInfo Name
rootFieldName Maybe Description
fieldDesc NESeq (ColumnInfo ('Postgres pgKind))
pkeyColumns
pgkBuildTableUpdateMutationFields ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
Scenario ->
SourceInfo ('Postgres pgKind) ->
TableName ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
C.GQLNameIdentifier ->
m [FieldParser n (IR.AnnotatedUpdateG ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
pgkBuildTableUpdateMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
pgkBuildTableUpdateMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo ('Postgres pgKind)
sourceInfo TableName ('Postgres pgKind)
tableName TableInfo ('Postgres pgKind)
tableInfo GQLNameIdentifier
gqlName = do
RoleName
roleName <- (SchemaContext -> RoleName) -> m RoleName
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaContext -> RoleName
scRole
[[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]]
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]]
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
-> (Maybe
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> [[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]])
-> Maybe
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> [[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]]
forall a. Maybe a -> [a]
maybeToList (Maybe
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
-> m (Maybe
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> m (Maybe
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
UpdPermInfo ('Postgres pgKind)
updatePerms <- Maybe (UpdPermInfo ('Postgres pgKind))
-> MaybeT m (UpdPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (UpdPermInfo ('Postgres pgKind))
-> MaybeT m (UpdPermInfo ('Postgres pgKind)))
-> Maybe (UpdPermInfo ('Postgres pgKind))
-> MaybeT m (UpdPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RolePermInfo ('Postgres pgKind)
-> Maybe (UpdPermInfo ('Postgres pgKind))
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd (RolePermInfo ('Postgres pgKind)
-> Maybe (UpdPermInfo ('Postgres pgKind)))
-> RolePermInfo ('Postgres pgKind)
-> Maybe (UpdPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind) -> RolePermInfo ('Postgres pgKind)
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo ('Postgres pgKind)
tableInfo
m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))])
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall a b. (a -> b) -> a -> b
$ do
[FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
singleUpdates <-
(TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(BackendUpdate
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
-> MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b,
BackendTableSelectSchema b) =>
(TableInfo b
-> m (InputFieldsParser n (BackendUpdate b (UnpreparedValue b))))
-> MkRootFieldName
-> Scenario
-> SourceInfo b
-> TableName b
-> TableInfo b
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))]
GSB.buildTableUpdateMutationFields
(\TableInfo ('Postgres pgKind)
ti -> (HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) v.
HashMap PGCol (UpdateOpExpression v) -> BackendUpdate pgKind v
BackendUpdate (InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
-> m (InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
MonadBuildSchema ('Postgres pgKind) r m n =>
TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
updateOperators TableInfo ('Postgres pgKind)
ti UpdPermInfo ('Postgres pgKind)
updatePerms)
MkRootFieldName
mkRootFieldName
Scenario
scenario
SourceInfo ('Postgres pgKind)
sourceInfo
TableName ('Postgres pgKind)
tableName
TableInfo ('Postgres pgKind)
tableInfo
GQLNameIdentifier
gqlName
Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
multiUpdate <-
MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m (Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall r (m :: * -> *) (n :: * -> *) (pgKind :: PostgresKind).
(MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)) =>
MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m (Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
updateTableMany
MkRootFieldName
mkRootFieldName
Scenario
scenario
SourceInfo ('Postgres pgKind)
sourceInfo
TableInfo ('Postgres pgKind)
tableInfo
GQLNameIdentifier
gqlName
pure $ [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
singleUpdates [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall a. [a] -> [a] -> [a]
++ Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> [FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall a. Maybe a -> [a]
maybeToList Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
multiUpdate
updateTableMany ::
forall r m n pgKind.
( MonadBuildSchema ('Postgres pgKind) r m n,
BackendTableSelectSchema ('Postgres pgKind)
) =>
MkRootFieldName ->
Scenario ->
SourceInfo ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
C.GQLNameIdentifier ->
m (Maybe (P.FieldParser n (IR.AnnotatedUpdateG ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))))
updateTableMany :: MkRootFieldName
-> Scenario
-> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> GQLNameIdentifier
-> m (Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
updateTableMany MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo GQLNameIdentifier
gqlName = MaybeT
m
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> m (Maybe
(FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('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
let columns :: [ColumnInfo ('Postgres pgKind)]
columns = TableInfo ('Postgres pgKind) -> [ColumnInfo ('Postgres pgKind)]
forall (b :: BackendType). TableInfo b -> [ColumnInfo b]
tableColumns TableInfo ('Postgres pgKind)
tableInfo
viewInfo :: Maybe ViewInfo
viewInfo = TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> Maybe ViewInfo
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> Maybe ViewInfo
_tciViewInfo (TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> Maybe ViewInfo)
-> TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> Maybe ViewInfo
forall a b. (a -> b) -> a -> b
$ TableInfo ('Postgres pgKind)
-> TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo ('Postgres pgKind)
tableInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ (ViewInfo -> Bool) -> Maybe ViewInfo -> Bool
isMutable ViewInfo -> Bool
viIsUpdatable Maybe ViewInfo
viewInfo
UpdPermInfo ('Postgres pgKind)
updatePerms <- Maybe (UpdPermInfo ('Postgres pgKind))
-> MaybeT m (UpdPermInfo ('Postgres pgKind))
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (UpdPermInfo ('Postgres pgKind))
-> MaybeT m (UpdPermInfo ('Postgres pgKind)))
-> Maybe (UpdPermInfo ('Postgres pgKind))
-> MaybeT m (UpdPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RolePermInfo ('Postgres pgKind)
-> Maybe (UpdPermInfo ('Postgres pgKind))
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd (RolePermInfo ('Postgres pgKind)
-> Maybe (UpdPermInfo ('Postgres pgKind)))
-> RolePermInfo ('Postgres pgKind)
-> Maybe (UpdPermInfo ('Postgres pgKind))
forall a b. (a -> b) -> a -> b
$ RoleName
-> TableInfo ('Postgres pgKind) -> RolePermInfo ('Postgres pgKind)
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo ('Postgres pgKind)
tableInfo
Bool -> MaybeT m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> MaybeT m ()) -> Bool -> MaybeT m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Scenario
scenario Scenario -> Scenario -> Bool
forall a. Eq a => a -> a -> Bool
== Scenario
Frontend Bool -> Bool -> Bool
&& UpdPermInfo ('Postgres pgKind) -> Bool
forall (b :: BackendType). UpdPermInfo b -> Bool
upiBackendOnly UpdPermInfo ('Postgres pgKind)
updatePerms
InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
updates <- m (InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
mkMultiRowUpdateParser SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo UpdPermInfo ('Postgres pgKind)
updatePerms)
Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
selection <- m (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> MaybeT
m
(Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
forall a b. (a -> b) -> a -> b
$ Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) origin a.
Parser origin 'Output m a -> Parser origin 'Output m a
P.multiple (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> m (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> m (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, BackendTableSelectSchema b) =>
SourceInfo b
-> TableInfo b
-> m (Parser
'Output
n
(MutFldsG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)))
GSB.mutationSelectionSet SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
let updateName :: Name
updateName = MkRootFieldName -> Name -> Name
runMkRootFieldName MkRootFieldName
mkRootFieldName (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ NamingCase
-> TableInfo ('Postgres pgKind)
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
forall (b :: BackendType).
NamingCase
-> TableInfo b
-> CustomRootField
-> (GQLNameIdentifier -> GQLNameIdentifier)
-> GQLNameIdentifier
-> Name
GSB.setFieldNameCase NamingCase
tCase TableInfo ('Postgres pgKind)
tableInfo CustomRootField
_tcrfUpdateMany GQLNameIdentifier -> GQLNameIdentifier
mkUpdateManyField GQLNameIdentifier
gqlName
argsParser :: InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
argsParser = (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))
-> AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
updates (AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
forall (backend :: BackendType) scalar. AnnBoolExp backend scalar
annBoolExpTrue)
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> FieldParser
MetadataObjId
n
((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutFldsG
('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
updateName Maybe Description
updateDesc InputFieldsParser
MetadataObjId
n
(BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
argsParser Parser
MetadataObjId
'Output
n
(MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
selection
FieldParser
MetadataObjId
n
((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> (((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> FieldParser
n
(AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> TableName ('Postgres pgKind)
-> [ColumnInfo ('Postgres pgKind)]
-> UpdPermInfo ('Postgres pgKind)
-> Maybe NamingCase
-> ((BackendUpdate
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutationOutputG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType).
Backend b =>
TableName b
-> [ColumnInfo b]
-> UpdPermInfo b
-> Maybe NamingCase
-> ((BackendUpdate b (UnpreparedValue b),
AnnBoolExp b (UnpreparedValue b)),
MutationOutputG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b))
-> AnnotatedUpdateG
b (RemoteRelationshipField UnpreparedValue) (UnpreparedValue b)
SU.mkUpdateObject TableName ('Postgres pgKind)
tableName [ColumnInfo ('Postgres pgKind)]
columns UpdPermInfo ('Postgres pgKind)
updatePerms (NamingCase -> Maybe NamingCase
forall a. a -> Maybe a
Just NamingCase
tCase) (((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutationOutputG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> (((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> ((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutationOutputG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> ((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> AnnotatedUpdateG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> MutationOutputG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> ((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> ((BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)),
AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))),
MutationOutputG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MutFldsG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> MutationOutputG
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
MutFldsG b r v -> MutationOutputG b r v
MOutMultirowFields
where
tableName :: TableName ('Postgres pgKind)
tableName = TableInfo ('Postgres pgKind) -> TableName ('Postgres pgKind)
forall (b :: BackendType). TableInfo b -> TableName b
tableInfoName TableInfo ('Postgres pgKind)
tableInfo
defaultUpdateDesc :: Text
defaultUpdateDesc = Text
"update multiples rows of table: " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
updateDesc :: Maybe Description
updateDesc = Text -> Comment -> Maybe Description
GSB.buildFieldDescription Text
defaultUpdateDesc (Comment -> Maybe Description) -> Comment -> Maybe Description
forall a b. (a -> b) -> a -> b
$ CustomRootField -> Comment
_crfComment CustomRootField
_tcrfUpdateMany
TableCustomRootFields {CustomRootField
_tcrfDeleteByPk :: TableCustomRootFields -> CustomRootField
_tcrfDelete :: TableCustomRootFields -> CustomRootField
_tcrfUpdateMany :: TableCustomRootFields -> CustomRootField
_tcrfUpdateByPk :: TableCustomRootFields -> CustomRootField
_tcrfUpdate :: TableCustomRootFields -> CustomRootField
_tcrfInsertOne :: TableCustomRootFields -> CustomRootField
_tcrfInsert :: TableCustomRootFields -> CustomRootField
_tcrfSelectStream :: TableCustomRootFields -> CustomRootField
_tcrfSelectAggregate :: TableCustomRootFields -> CustomRootField
_tcrfSelectByPk :: TableCustomRootFields -> CustomRootField
_tcrfSelect :: TableCustomRootFields -> CustomRootField
_tcrfDeleteByPk :: CustomRootField
_tcrfDelete :: CustomRootField
_tcrfUpdateByPk :: CustomRootField
_tcrfUpdate :: CustomRootField
_tcrfInsertOne :: CustomRootField
_tcrfInsert :: CustomRootField
_tcrfSelectStream :: CustomRootField
_tcrfSelectAggregate :: CustomRootField
_tcrfSelectByPk :: CustomRootField
_tcrfSelect :: CustomRootField
_tcrfUpdateMany :: CustomRootField
..} = TableConfig ('Postgres pgKind) -> TableCustomRootFields
forall (b :: BackendType). TableConfig b -> TableCustomRootFields
_tcCustomRootFields (TableConfig ('Postgres pgKind) -> TableCustomRootFields)
-> (TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> TableConfig ('Postgres pgKind))
-> TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> TableCustomRootFields
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> TableConfig ('Postgres pgKind)
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> TableConfig b
_tciCustomConfig (TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> TableCustomRootFields)
-> TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
-> TableCustomRootFields
forall a b. (a -> b) -> a -> b
$ TableInfo ('Postgres pgKind)
-> TableCoreInfoG
('Postgres pgKind)
(FieldInfo ('Postgres pgKind))
(ColumnInfo ('Postgres pgKind))
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo ('Postgres pgKind)
tableInfo
mkMultiRowUpdateParser ::
forall pgKind r m n.
MonadBuildSchema ('Postgres pgKind) r m n =>
SourceInfo ('Postgres pgKind) ->
TableInfo ('Postgres pgKind) ->
UpdPermInfo ('Postgres pgKind) ->
m (P.InputFieldsParser n (PGIR.BackendUpdate pgKind (IR.UnpreparedValue ('Postgres pgKind))))
mkMultiRowUpdateParser :: SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
mkMultiRowUpdateParser SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo UpdPermInfo ('Postgres pgKind)
updatePerms = do
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
GQLNameIdentifier
tableGQLName <- TableInfo ('Postgres pgKind) -> m GQLNameIdentifier
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
TableInfo b -> m GQLNameIdentifier
getTableIdentifierName TableInfo ('Postgres pgKind)
tableInfo
Name
updatesObjectName <- Name -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
Name -> m Name
mkTypename (Name -> m Name) -> Name -> m Name
forall a b. (a -> b) -> a -> b
$ NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier -> Name) -> GQLNameIdentifier -> Name
forall a b. (a -> b) -> a -> b
$ GQLNameIdentifier -> GQLNameIdentifier
mkMultiRowUpdateTypeName GQLNameIdentifier
tableGQLName
([MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
-> BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
-> InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
-> BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) v.
[MultiRowUpdate pgKind v] -> BackendUpdate pgKind v
BackendMultiRowUpdate
(InputFieldsParser
MetadataObjId
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
-> InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
-> (InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))])
-> InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
-> InputFieldsParser
MetadataObjId
n
[MultiRowUpdate pgKind (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
Name._updates (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
updatesDesc)
(Parser
MetadataObjId
'Input
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
-> InputFieldsParser
MetadataObjId
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))])
-> (InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Input
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))])
-> InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser
MetadataObjId
'Input
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Input
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list
(Parser
MetadataObjId
'Input
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Input
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))])
-> (InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Input
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Input
n
[MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Input
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
updatesObjectName Maybe Description
forall a. Maybe a
Nothing
(InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
n (BackendUpdate pgKind (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
mruWhere <- Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (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
Name._where Maybe Description
forall a. Maybe a
Nothing (Parser
MetadataObjId
'Input
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> m (Parser
MetadataObjId
'Input
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
-> m (InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceInfo ('Postgres pgKind)
-> TableInfo ('Postgres pgKind)
-> m (Parser
MetadataObjId
'Input
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema b r m n, AggregationPredicatesSchema b) =>
SourceInfo b
-> TableInfo b
-> m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
boolExp SourceInfo ('Postgres pgKind)
sourceInfo TableInfo ('Postgres pgKind)
tableInfo
InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind))))
mruExpression <- TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
MonadBuildSchema ('Postgres pgKind) r m n =>
TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
updateOperators TableInfo ('Postgres pgKind)
tableInfo UpdPermInfo ('Postgres pgKind)
updatePerms
pure $ AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) v.
AnnBoolExp ('Postgres pgKind) v
-> HashMap PGCol (UpdateOpExpression v) -> MultiRowUpdate pgKind v
MultiRowUpdate (AnnBoolExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind))
-> HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser
MetadataObjId
n
(AnnBoolExp
('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))
mruWhere InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(MultiRowUpdate pgKind (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> InputFieldsParser
MetadataObjId
n
(HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind))))
mruExpression
where
updatesDesc :: Description
updatesDesc = Description
"updates to execute, in order"
buildFunctionRelayQueryFields ::
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) ->
NESeq (ColumnInfo ('Postgres pgKind)) ->
m [FieldParser n (QueryDB ('Postgres pgKind) (RemoteRelationshipField IR.UnpreparedValue) (IR.UnpreparedValue ('Postgres pgKind)))]
buildFunctionRelayQueryFields :: MkRootFieldName
-> SourceInfo ('Postgres pgKind)
-> FunctionName ('Postgres pgKind)
-> FunctionInfo ('Postgres pgKind)
-> TableName ('Postgres pgKind)
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
buildFunctionRelayQueryFields MkRootFieldName
mkRootFieldName SourceInfo ('Postgres pgKind)
sourceName FunctionName ('Postgres pgKind)
functionName FunctionInfo ('Postgres pgKind)
functionInfo TableName ('Postgres pgKind)
tableName NESeq (ColumnInfo ('Postgres pgKind))
pkeyColumns = do
let fieldDesc :: Maybe Description
fieldDesc = 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
" which returns " Text -> QualifiedTable -> Text
forall t. ToTxt t => Text -> t -> Text
<>> TableName ('Postgres pgKind)
QualifiedTable
tableName
(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
fmap Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))
-> [FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))]
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t a -> f a
afold (m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m [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 a b. (a -> b) -> a -> b
$
(ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))
-> m (Maybe
(FieldParser
n
(ConnectionSelect
('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 ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
-> QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) r v.
ConnectionSelect b r v -> QueryDB b r v
QDBConnection (m (Maybe
(FieldParser
n
(ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
-> m (Maybe
(FieldParser
n
(QueryDB
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind))))))
-> m (Maybe
(FieldParser
n
(ConnectionSelect
('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
-> NESeq (ColumnInfo ('Postgres pgKind))
-> m (Maybe
(FieldParser
n
(ConnectionSelect
('Postgres pgKind)
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue ('Postgres pgKind)))))
forall (pgKind :: PostgresKind) r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema ('Postgres pgKind) r m n,
AggregationPredicatesSchema ('Postgres pgKind),
BackendTableSelectSchema ('Postgres pgKind)) =>
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)
sourceName FunctionInfo ('Postgres pgKind)
functionInfo Maybe Description
fieldDesc NESeq (ColumnInfo ('Postgres pgKind))
pkeyColumns
columnParser ::
(MonadParse n, MonadError QErr m, MonadReader r m, Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind) ->
G.Nullability ->
m (Parser 'Both n (IR.ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser :: ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser ColumnType ('Postgres pgKind)
columnType (G.Nullability Bool
isNullable) = do
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
Parser 'Both n (ColumnValue ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
forall (m :: * -> *) a.
MonadParse m =>
Parser 'Both m a -> Parser 'Both m (ValueWithOrigin a)
peelWithOrigin (Parser 'Both n (ColumnValue ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> (Parser MetadataObjId 'Both n PGScalarValue
-> Parser 'Both n (ColumnValue ('Postgres pgKind)))
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PGScalarValue -> ColumnValue ('Postgres pgKind))
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser 'Both n (ColumnValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ColumnType ('Postgres pgKind)
-> ScalarValue ('Postgres pgKind) -> ColumnValue ('Postgres pgKind)
forall (b :: BackendType).
ColumnType b -> ScalarValue b -> ColumnValue b
ColumnValue ColumnType ('Postgres pgKind)
columnType) (Parser MetadataObjId 'Both n PGScalarValue
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> m (Parser MetadataObjId 'Both n PGScalarValue)
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ColumnType ('Postgres pgKind)
columnType of
ColumnScalar ScalarType ('Postgres pgKind)
scalarType ->
PGScalarType
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue
possiblyNullable ScalarType ('Postgres pgKind)
PGScalarType
scalarType (Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue)
-> m (Parser MetadataObjId 'Both n PGScalarValue)
-> m (Parser MetadataObjId 'Both n PGScalarValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
Name
name <- PGScalarType -> m Name
forall (m :: * -> *). MonadError QErr m => PGScalarType -> m Name
mkScalarTypeName ScalarType ('Postgres pgKind)
PGScalarType
scalarType
let schemaType :: Type MetadataObjId 'Both
schemaType = Nullability
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Both)
-> Type MetadataObjId 'Both
forall origin (k :: Kind).
Nullability
-> Definition origin (TypeInfo origin k) -> Type origin k
P.TNamed Nullability
P.NonNullable (Definition MetadataObjId (TypeInfo MetadataObjId 'Both)
-> Type MetadataObjId 'Both)
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Both)
-> Type MetadataObjId 'Both
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> Maybe MetadataObjId
-> [Directive Void]
-> TypeInfo MetadataObjId 'Both
-> Definition MetadataObjId (TypeInfo MetadataObjId 'Both)
forall origin a.
Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> a
-> Definition origin a
P.Definition Name
name Maybe Description
forall a. Maybe a
Nothing Maybe MetadataObjId
forall a. Maybe a
Nothing [] TypeInfo MetadataObjId 'Both
forall origin. TypeInfo origin 'Both
P.TIScalar
Parser MetadataObjId 'Both n PGScalarValue
-> m (Parser MetadataObjId 'Both n PGScalarValue)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n PGScalarValue
-> m (Parser MetadataObjId 'Both n PGScalarValue))
-> Parser MetadataObjId 'Both n PGScalarValue
-> m (Parser MetadataObjId 'Both n PGScalarValue)
forall a b. (a -> b) -> a -> b
$
Parser :: forall origin (k :: Kind) (m :: * -> *) a.
Type origin k -> (ParserInput k -> m a) -> Parser origin k m a
P.Parser
{ pType :: Type MetadataObjId 'Both
pType = Type MetadataObjId 'Both
schemaType,
pParser :: ParserInput 'Both -> n PGScalarValue
pParser =
GType -> InputValue Variable -> n Value
forall (m :: * -> *).
MonadParse m =>
GType -> InputValue Variable -> m Value
P.valueToJSON (Type MetadataObjId 'Both -> GType
forall origin (k :: Kind). Type origin k -> GType
P.toGraphQLType Type MetadataObjId 'Both
schemaType) (InputValue Variable -> n Value)
-> (Value -> n PGScalarValue)
-> InputValue Variable
-> n PGScalarValue
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \case
Value
J.Null -> ErrorMessage -> n PGScalarValue
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
P.parseError (ErrorMessage -> n PGScalarValue)
-> ErrorMessage -> n PGScalarValue
forall a b. (a -> b) -> a -> b
$ ErrorMessage
"unexpected null value for type " ErrorMessage -> ErrorMessage -> ErrorMessage
forall a. Semigroup a => a -> a -> a
<> Name -> ErrorMessage
forall a. ToErrorValue a => a -> ErrorMessage
toErrorValue Name
name
Value
value ->
(Value -> Parser PGScalarValue)
-> Value -> Either QErr PGScalarValue
forall (m :: * -> *) v a. QErrM m => (v -> Parser a) -> v -> m a
runAesonParser (PGScalarType -> Value -> Parser PGScalarValue
parsePGValue ScalarType ('Postgres pgKind)
PGScalarType
scalarType) Value
value
Either QErr PGScalarValue
-> (QErr -> n PGScalarValue) -> n PGScalarValue
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` (ParseErrorCode -> ErrorMessage -> n PGScalarValue
forall (m :: * -> *) a.
MonadParse m =>
ParseErrorCode -> ErrorMessage -> m a
P.parseErrorWith ParseErrorCode
P.ParseFailed (ErrorMessage -> n PGScalarValue)
-> (QErr -> ErrorMessage) -> QErr -> n PGScalarValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ErrorMessage
toErrorMessage (Text -> ErrorMessage) -> (QErr -> Text) -> QErr -> ErrorMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QErr -> Text
qeError)
}
ColumnEnumReference (EnumReference TableName ('Postgres pgKind)
tableName EnumValues
enumValues Maybe Name
tableCustomName) ->
case [(EnumValue, EnumValueInfo)]
-> Maybe (NonEmpty (EnumValue, EnumValueInfo))
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty (EnumValues -> [(EnumValue, EnumValueInfo)]
forall k v. HashMap k v -> [(k, v)]
Map.toList EnumValues
enumValues) of
Just NonEmpty (EnumValue, EnumValueInfo)
enumValuesList -> do
GQLNameIdentifier
tableGQLName <- Either QErr GQLNameIdentifier -> m GQLNameIdentifier
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (QualifiedTable -> Either QErr GQLNameIdentifier
forall a.
ToTxt a =>
QualifiedObject a -> Either QErr GQLNameIdentifier
getIdentifierQualifiedObject TableName ('Postgres pgKind)
QualifiedTable
tableName)
Name
name <- GQLNameIdentifier -> Maybe Name -> NamingCase -> m Name
forall r (m :: * -> *).
(MonadReader r m, Has MkTypename r) =>
GQLNameIdentifier -> Maybe Name -> NamingCase -> m Name
addEnumSuffix GQLNameIdentifier
tableGQLName Maybe Name
tableCustomName NamingCase
tCase
pure $ PGScalarType
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue
possiblyNullable PGScalarType
PGText (Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue)
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> NonEmpty (Definition EnumValueInfo, PGScalarValue)
-> Parser MetadataObjId 'Both n PGScalarValue
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> NonEmpty (Definition origin EnumValueInfo, a)
-> Parser origin 'Both m a
P.enum Name
name Maybe Description
forall a. Maybe a
Nothing (NamingCase
-> (EnumValue, EnumValueInfo)
-> (Definition EnumValueInfo, PGScalarValue)
mkEnumValue NamingCase
tCase ((EnumValue, EnumValueInfo)
-> (Definition EnumValueInfo, PGScalarValue))
-> NonEmpty (EnumValue, EnumValueInfo)
-> NonEmpty (Definition EnumValueInfo, PGScalarValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (EnumValue, EnumValueInfo)
enumValuesList)
Maybe (NonEmpty (EnumValue, EnumValueInfo))
Nothing -> Code -> Text -> m (Parser MetadataObjId 'Both n PGScalarValue)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed Text
"empty enum values"
where
possiblyNullable :: PGScalarType
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue
possiblyNullable PGScalarType
scalarType
| Bool
isNullable = (Maybe PGScalarValue -> PGScalarValue)
-> Parser MetadataObjId 'Both n (Maybe PGScalarValue)
-> Parser MetadataObjId 'Both n PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (PGScalarValue -> Maybe PGScalarValue -> PGScalarValue
forall a. a -> Maybe a -> a
fromMaybe (PGScalarValue -> Maybe PGScalarValue -> PGScalarValue)
-> PGScalarValue -> Maybe PGScalarValue -> PGScalarValue
forall a b. (a -> b) -> a -> b
$ PGScalarType -> PGScalarValue
PGNull PGScalarType
scalarType) (Parser MetadataObjId 'Both n (Maybe PGScalarValue)
-> Parser MetadataObjId 'Both n PGScalarValue)
-> (Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n (Maybe PGScalarValue))
-> Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n (Maybe PGScalarValue)
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m (Maybe a)
P.nullable
| Bool
otherwise = Parser MetadataObjId 'Both n PGScalarValue
-> Parser MetadataObjId 'Both n PGScalarValue
forall a. a -> a
id
mkEnumValue :: NamingCase -> (EnumValue, EnumValueInfo) -> (P.Definition P.EnumValueInfo, PGScalarValue)
mkEnumValue :: NamingCase
-> (EnumValue, EnumValueInfo)
-> (Definition EnumValueInfo, PGScalarValue)
mkEnumValue NamingCase
tCase (EnumValue Name
value, EnumValueInfo Maybe Text
description) =
( Name
-> Maybe Description
-> Maybe MetadataObjId
-> [Directive Void]
-> EnumValueInfo
-> Definition EnumValueInfo
forall origin a.
Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> a
-> Definition origin a
P.Definition (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
value) (Text -> Description
G.Description (Text -> Description) -> Maybe Text -> Maybe Description
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
description) Maybe MetadataObjId
forall a. Maybe a
Nothing [] EnumValueInfo
P.EnumValueInfo,
Text -> PGScalarValue
PGValText (Text -> PGScalarValue) -> Text -> PGScalarValue
forall a b. (a -> b) -> a -> b
$ Name -> Text
G.unName Name
value
)
pgScalarSelectionArgumentsParser ::
MonadParse n =>
ColumnType ('Postgres pgKind) ->
InputFieldsParser n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
pgScalarSelectionArgumentsParser :: ColumnType ('Postgres pgKind)
-> InputFieldsParser
n (Maybe (ScalarSelectionArguments ('Postgres pgKind)))
pgScalarSelectionArgumentsParser ColumnType ('Postgres pgKind)
columnType
| (ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere ScalarType ('Postgres pgKind) -> Bool
PGScalarType -> Bool
PG.isJSONType ColumnType ('Postgres pgKind)
columnType =
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n Text
-> InputFieldsParser MetadataObjId n (Maybe Text)
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
description Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string InputFieldsParser MetadataObjId n (Maybe Text)
-> (Maybe Text -> n (Maybe ColumnOp))
-> InputFieldsParser MetadataObjId n (Maybe ColumnOp)
forall (m :: * -> *) origin a b.
Monad m =>
InputFieldsParser origin m a
-> (a -> m b) -> InputFieldsParser origin m b
`P.bindFields` (Maybe (Maybe ColumnOp) -> Maybe ColumnOp)
-> n (Maybe (Maybe ColumnOp)) -> n (Maybe ColumnOp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe ColumnOp) -> Maybe ColumnOp
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (n (Maybe (Maybe ColumnOp)) -> n (Maybe ColumnOp))
-> (Maybe Text -> n (Maybe (Maybe ColumnOp)))
-> Maybe Text
-> n (Maybe ColumnOp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> n (Maybe ColumnOp))
-> Maybe Text -> n (Maybe (Maybe ColumnOp))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Text -> n (Maybe ColumnOp)
forall (m :: * -> *). MonadParse m => Text -> m (Maybe ColumnOp)
toColExp
| Bool
otherwise = Maybe ColumnOp
-> InputFieldsParser MetadataObjId n (Maybe ColumnOp)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ColumnOp
forall a. Maybe a
Nothing
where
fieldName :: Name
fieldName = Name
Name._path
description :: Maybe Description
description = Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"JSON select path"
toColExp :: Text -> m (Maybe ColumnOp)
toColExp Text
textValue = case Text -> Either Text JSONPath
parseJSONPath Text
textValue of
Left Text
err -> ErrorMessage -> m (Maybe ColumnOp)
forall (m :: * -> *) a. MonadParse m => ErrorMessage -> m a
P.parseError (ErrorMessage -> m (Maybe ColumnOp))
-> ErrorMessage -> m (Maybe ColumnOp)
forall a b. (a -> b) -> a -> b
$ ErrorMessage
"parse json path error: " ErrorMessage -> ErrorMessage -> ErrorMessage
forall a. Semigroup a => a -> a -> a
<> Text -> ErrorMessage
toErrorMessage Text
err
Right [] -> Maybe ColumnOp -> m (Maybe ColumnOp)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ColumnOp
forall a. Maybe a
Nothing
Right JSONPath
jPaths -> Maybe ColumnOp -> m (Maybe ColumnOp)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ColumnOp -> m (Maybe ColumnOp))
-> Maybe ColumnOp -> m (Maybe ColumnOp)
forall a b. (a -> b) -> a -> b
$ ColumnOp -> Maybe ColumnOp
forall a. a -> Maybe a
Just (ColumnOp -> Maybe ColumnOp) -> ColumnOp -> Maybe ColumnOp
forall a b. (a -> b) -> a -> b
$ SQLOp -> SQLExp -> ColumnOp
PG.ColumnOp SQLOp
PG.jsonbPathOp (SQLExp -> ColumnOp) -> SQLExp -> ColumnOp
forall a b. (a -> b) -> a -> b
$ [SQLExp] -> SQLExp
PG.SEArray ([SQLExp] -> SQLExp) -> [SQLExp] -> SQLExp
forall a b. (a -> b) -> a -> b
$ (JSONPathElement -> SQLExp) -> JSONPath -> [SQLExp]
forall a b. (a -> b) -> [a] -> [b]
map JSONPathElement -> SQLExp
elToColExp JSONPath
jPaths
elToColExp :: JSONPathElement -> SQLExp
elToColExp (Key Key
k) = Text -> SQLExp
PG.SELit (Text -> SQLExp) -> Text -> SQLExp
forall a b. (a -> b) -> a -> b
$ Key -> Text
K.toText Key
k
elToColExp (Index Int
i) = Text -> SQLExp
PG.SELit (Text -> SQLExp) -> Text -> SQLExp
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. Show a => a -> Text
tshow Int
i
orderByOperatorsHasuraCase ::
(G.Name, NonEmpty (Definition P.EnumValueInfo, (BasicOrderType ('Postgres pgKind), NullsOrderType ('Postgres pgKind))))
orderByOperatorsHasuraCase :: (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperatorsHasuraCase = NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres Any), NullsOrderType ('Postgres Any))))
forall (pgKind :: PostgresKind).
NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperators NamingCase
HasuraCase
orderByOperatorsGraphqlCase ::
(G.Name, NonEmpty (Definition P.EnumValueInfo, (BasicOrderType ('Postgres pgKind), NullsOrderType ('Postgres pgKind))))
orderByOperatorsGraphqlCase :: (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperatorsGraphqlCase = NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres Any), NullsOrderType ('Postgres Any))))
forall (pgKind :: PostgresKind).
NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperators NamingCase
GraphqlCase
orderByOperators ::
NamingCase ->
(G.Name, NonEmpty (Definition P.EnumValueInfo, (BasicOrderType ('Postgres pgKind), NullsOrderType ('Postgres pgKind))))
orderByOperators :: NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType ('Postgres pgKind),
NullsOrderType ('Postgres pgKind))))
orderByOperators NamingCase
tCase =
(Name
Name._order_by,) (NonEmpty (Definition EnumValueInfo, (OrderType, NullsOrder))
-> (Name,
NonEmpty (Definition EnumValueInfo, (OrderType, NullsOrder))))
-> NonEmpty (Definition EnumValueInfo, (OrderType, NullsOrder))
-> (Name,
NonEmpty (Definition EnumValueInfo, (OrderType, NullsOrder)))
forall a b. (a -> b) -> a -> b
$
[(Definition EnumValueInfo, (OrderType, NullsOrder))]
-> NonEmpty (Definition EnumValueInfo, (OrderType, NullsOrder))
forall a. [a] -> NonEmpty a
NE.fromList
[ ( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
Name._asc) Description
"in ascending order, nulls last",
(OrderType
PG.OTAsc, NullsOrder
PG.NullsLast)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
Name._asc_nulls_first) Description
"in ascending order, nulls first",
(OrderType
PG.OTAsc, NullsOrder
PG.NullsFirst)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
Name._asc_nulls_last) Description
"in ascending order, nulls last",
(OrderType
PG.OTAsc, NullsOrder
PG.NullsLast)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
Name._desc) Description
"in descending order, nulls first",
(OrderType
PG.OTDesc, NullsOrder
PG.NullsFirst)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
Name._desc_nulls_first) Description
"in descending order, nulls first",
(OrderType
PG.OTDesc, NullsOrder
PG.NullsFirst)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define (NamingCase -> Name -> Name
applyEnumValueCase NamingCase
tCase Name
Name._desc_nulls_last) Description
"in descending order, nulls last",
(OrderType
PG.OTDesc, NullsOrder
PG.NullsLast)
)
]
where
define :: Name -> Description -> Definition origin EnumValueInfo
define Name
name Description
desc = Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> EnumValueInfo
-> Definition origin EnumValueInfo
forall origin a.
Name
-> Maybe Description
-> Maybe origin
-> [Directive Void]
-> a
-> Definition origin a
P.Definition Name
name (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
desc) Maybe origin
forall a. Maybe a
Nothing [] EnumValueInfo
P.EnumValueInfo
comparisonExps ::
forall pgKind m n r.
( BackendSchema ('Postgres pgKind),
MonadMemoize m,
MonadParse n,
MonadError QErr m,
MonadReader r m,
Has SchemaOptions r,
Has MkTypename r,
Has NamingCase r
) =>
ColumnType ('Postgres pgKind) ->
m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
comparisonExps :: ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
comparisonExps = Name
-> (ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)]))
-> ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
forall (m :: * -> *) a (p :: (* -> *) -> * -> *) (n :: * -> *) b.
(MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n,
Typeable b) =>
Name -> (a -> m (p n b)) -> a -> m (p n b)
memoize 'comparisonExps \ColumnType ('Postgres pgKind)
columnType -> do
DangerouslyCollapseBooleans
collapseIfNull <- (SchemaOptions -> DangerouslyCollapseBooleans)
-> m DangerouslyCollapseBooleans
forall r (m :: * -> *) a b.
(MonadReader r m, Has a r) =>
(a -> b) -> m b
retrieve SchemaOptions -> DangerouslyCollapseBooleans
Options.soDangerousBooleanCollapse
Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
geogInputParser <- m (Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
m (Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind))))
geographyWithinDistanceInput
Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
geomInputParser <- m (Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
m (Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))))
geometryWithinDistanceInput
Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
ignInputParser <- m (Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
m (Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))))
intersectsGeomNbandInput
Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
ingInputParser <- m (Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
m (Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))))
intersectsNbandGeomInput
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser ColumnType ('Postgres pgKind)
columnType (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
nullableTextParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText) (Bool -> Nullability
G.Nullability Bool
True)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
textParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText) (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
lqueryParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLquery) (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
ltxtqueryParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLtxtquery) (Bool -> Nullability
G.Nullability Bool
False)
NamingCase
tCase <- (r -> NamingCase) -> m NamingCase
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> NamingCase
forall a t. Has a t => t -> a
getter
Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
maybeCastParser <- ColumnType ('Postgres pgKind)
-> NamingCase
-> m (Maybe
(Parser
'Input
n
(CastExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
castExp ColumnType ('Postgres pgKind)
columnType NamingCase
tCase
let name :: Name
name = NamingCase -> Name -> Name
applyTypeNameCaseCust NamingCase
tCase (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$ Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Name
forall a. HasName a => a -> Name
P.getName Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__comparison_exp
desc :: Description
desc =
Text -> Description
G.Description (Text -> Description) -> Text -> Description
forall a b. (a -> b) -> a -> b
$
Text
"Boolean expression to compare columns of type "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Name
forall a. HasName a => a -> Name
P.getName Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser
Name -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
". All fields are combined with logical 'AND'."
textListParser :: Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
textListParser = (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ColumnValue ('Postgres pgKind))
-> [ValueWithOrigin (ColumnValue ('Postgres pgKind))]
-> [ColumnValue ('Postgres pgKind)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ColumnValue ('Postgres pgKind)
forall a. ValueWithOrigin a -> a
IR.openValueOrigin ([ValueWithOrigin (ColumnValue ('Postgres pgKind))]
-> [ColumnValue ('Postgres pgKind)])
-> Parser
MetadataObjId
'Both
n
[ValueWithOrigin (ColumnValue ('Postgres pgKind))]
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Both
n
[ValueWithOrigin (ColumnValue ('Postgres pgKind))]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
textParser
columnListParser :: Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
columnListParser = (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ColumnValue ('Postgres pgKind))
-> [ValueWithOrigin (ColumnValue ('Postgres pgKind))]
-> [ColumnValue ('Postgres pgKind)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ColumnValue ('Postgres pgKind)
forall a. ValueWithOrigin a -> a
IR.openValueOrigin ([ValueWithOrigin (ColumnValue ('Postgres pgKind))]
-> [ColumnValue ('Postgres pgKind)])
-> Parser
MetadataObjId
'Both
n
[ValueWithOrigin (ColumnValue ('Postgres pgKind))]
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Both
n
[ValueWithOrigin (ColumnValue ('Postgres pgKind))]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId n [ComparisonExp ('Postgres pgKind)]
-> Parser 'Input n [ComparisonExp ('Postgres pgKind)]
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
name (Description -> Maybe Description
forall a. a -> Maybe a
Just Description
desc) (InputFieldsParser
MetadataObjId n [ComparisonExp ('Postgres pgKind)]
-> Parser 'Input n [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId n [ComparisonExp ('Postgres pgKind)]
-> Parser 'Input n [ComparisonExp ('Postgres pgKind)]
forall a b. (a -> b) -> a -> b
$
([Maybe (ComparisonExp ('Postgres pgKind))]
-> [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp ('Postgres pgKind))]
-> InputFieldsParser
MetadataObjId n [ComparisonExp ('Postgres pgKind)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe (ComparisonExp ('Postgres pgKind))]
-> [ComparisonExp ('Postgres pgKind)]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp ('Postgres pgKind))]
-> InputFieldsParser
MetadataObjId n [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp ('Postgres pgKind))]
-> InputFieldsParser
MetadataObjId n [ComparisonExp ('Postgres pgKind)]
forall a b. (a -> b) -> a -> b
$
[InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp ('Postgres pgKind))]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp ('Postgres pgKind))])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp ('Postgres pgKind))]
forall a b. (a -> b) -> a -> b
$
[[InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ ((Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
-> (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ([InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe []) Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
maybeCastParser ((Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall a b. (a -> b) -> a -> b
$ \Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
castParser ->
[ Name
-> Maybe Description
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('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
Name.__cast Maybe Description
forall a. Maybe a
Nothing (HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
CastExp backend field -> OpExpG backend field
ACast (HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind))
-> Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
castParser)
],
NamingCase
-> DangerouslyCollapseBooleans
-> Parser 'Both n (UnpreparedValue ('Postgres pgKind))
-> Parser 'Both n (UnpreparedValue ('Postgres pgKind))
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (n :: * -> *) (k :: Kind) (b :: BackendType).
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> Parser k n (UnpreparedValue b)
-> Parser k n (UnpreparedValue b)
-> [InputFieldsParser n (Maybe (OpExpG b (UnpreparedValue b)))]
equalityOperators
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser)
(ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListParameter ColumnType ('Postgres pgKind)
columnType ([ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind))
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
-> Parser 'Both n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
columnListParser),
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
/= PGScalarType
PGRaster) ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> NamingCase
-> DangerouslyCollapseBooleans
-> Parser 'Both n (UnpreparedValue ('Postgres pgKind))
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (n :: * -> *) (k :: Kind) (b :: BackendType).
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> Parser k n (UnpreparedValue b)
-> [InputFieldsParser n (Maybe (OpExpG b (UnpreparedValue b)))]
comparisonOperators
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGRaster) ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "intersects", "rast"]))
Maybe Description
forall a. Maybe a
Nothing
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTIntersectsRast (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "intersects", "nband", "geom"]))
Maybe Description
forall a. Maybe a
Nothing
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. STIntersectsNbandGeommin a -> BooleanOperators a
ASTIntersectsNbandGeom (STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
ingInputParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "intersects", "geom", "nband"]))
Maybe Description
forall a. Maybe a
Nothing
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. STIntersectsGeomminNband a -> BooleanOperators a
ASTIntersectsGeomNband (STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
ignInputParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere ScalarType ('Postgres pgKind) -> Bool
PGScalarType -> Bool
isStringType ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__like)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column match the given pattern")
(UnpreparedValue ('Postgres pgKind)
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
field -> OpExpG backend field
ALIKE (UnpreparedValue ('Postgres pgKind)
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__nlike)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column NOT match the given pattern")
(UnpreparedValue ('Postgres pgKind)
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
field -> OpExpG backend field
ANLIKE (UnpreparedValue ('Postgres pgKind)
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__ilike)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column match the given case-insensitive pattern")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AILIKE (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__nilike)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column NOT match the given case-insensitive pattern")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ANILIKE (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__similar)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column match the given SQL regular expression")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASIMILAR (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__nsimilar)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column NOT match the given SQL regular expression")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ANSIMILAR (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__regex)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column match the given POSIX regular expression, case sensitive")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AREGEX (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__iregex)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column match the given POSIX regular expression, case insensitive")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AIREGEX (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__nregex)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column NOT match the given POSIX regular expression, case sensitive")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ANREGEX (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__niregex)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column NOT match the given POSIX regular expression, case insensitive")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ANIREGEX (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGJSONB) ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__contains)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column contain the given json value at the top level")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AContains (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_contained", "in"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column contained in the given json value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AContainedIn (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_has", "key"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the string exist as a top-level key in the column")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AHasKey (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
nullableTextParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_has", "keys", "any"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"do any of these strings exist as top-level keys in the column")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> ([ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> [ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AHasKeysAny (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ([ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind))
-> [ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListLiteral (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText) ([ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind))
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
textListParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_has", "keys", "all"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"do all of these strings exist as top-level keys in the column")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> ([ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> [ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AHasKeysAll (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ([ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind))
-> [ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListLiteral (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText) ([ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind))
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
textListParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGGeography) ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "intersects"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column spatially intersect the given geography value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTIntersects (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "d", "within"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column within a given distance from the given geography value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (DWithinGeogOp (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DWithinGeogOp (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. DWithinGeogOp a -> BooleanOperators a
ASTDWithinGeog (DWithinGeogOp (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
geogInputParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGGeometry) ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "contains"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column contain the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTContains (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "crosses"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column cross the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTCrosses (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "equals"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column equal to given geometry value (directionality is ignored)")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTEquals (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "overlaps"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column 'spatially overlap' (intersect but not completely contain) the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTOverlaps (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "touches"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column have atleast one point in common with the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTTouches (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "within"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column contained in the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTWithin (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "intersects"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column spatially intersect the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ASTIntersects (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "3d", "intersects"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column spatially intersect the given geometry value in 3D")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AST3DIntersects (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "d", "within"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column within a given distance from the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. DWithinGeomOp a -> BooleanOperators a
ASTDWithinGeom (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
geomInputParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_st", "3d", "d", "within"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column within a given 3D distance from the given geometry value")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. DWithinGeomOp a -> BooleanOperators a
AST3DDWithinGeom (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> Parser MetadataObjId 'Input n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
geomInputParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGLtree) ColumnType ('Postgres pgKind)
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__ancestor)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the left argument an ancestor of right (or equal)?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AAncestor (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_ancestor", "any"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does array contain an ancestor of `ltree`?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> ([ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> [ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AAncestorAny (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ([ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind))
-> [ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListLiteral ColumnType ('Postgres pgKind)
columnType ([ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind))
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
columnListParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__descendant)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the left argument a descendant of right (or equal)?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ADescendant (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
typedParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_descendant", "any"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does array contain a descendant of `ltree`?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> ([ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> [ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
ADescendantAny (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ([ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind))
-> [ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListLiteral ColumnType ('Postgres pgKind)
columnType ([ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind))
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
columnListParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
(Name -> GQLNameIdentifier
C.fromAutogeneratedName Name
Name.__matches)
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does `ltree` match `lquery`?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AMatches (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
lqueryParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_matches", "any"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does `ltree` match any `lquery` in array?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> ([ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> [ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AMatchesAny (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ([ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind))
-> [ColumnValue ('Postgres pgKind)]
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListLiteral (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGLquery) ([ColumnValue ('Postgres pgKind)]
-> ComparisonExp ('Postgres pgKind))
-> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue ('Postgres pgKind)]
textListParser),
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp ('Postgres pgKind)))
forall (n :: * -> *) (k :: Kind) a.
(MonadParse n, 'Input <: k) =>
NamingCase
-> DangerouslyCollapseBooleans
-> GQLNameIdentifier
-> Maybe Description
-> Parser k n a
-> InputFieldsParser n (Maybe a)
mkBoolOperator
NamingCase
tCase
DangerouslyCollapseBooleans
collapseIfNull
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_matches", "fulltext"]))
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does `ltree` match `ltxtquery`?")
(BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind))
forall a. a -> BooleanOperators a
AMatchesFulltext (UnpreparedValue ('Postgres pgKind)
-> BooleanOperators (UnpreparedValue ('Postgres pgKind)))
-> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> BooleanOperators (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 (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> ComparisonExp ('Postgres pgKind))
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser 'Both n (ComparisonExp ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
ltxtqueryParser)
]
]
where
mkListLiteral :: ColumnType ('Postgres pgKind) -> [ColumnValue ('Postgres pgKind)] -> IR.UnpreparedValue ('Postgres pgKind)
mkListLiteral :: ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListLiteral ColumnType ('Postgres pgKind)
columnType [ColumnValue ('Postgres pgKind)]
columnValues =
SQLExpression ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType). SQLExpression b -> UnpreparedValue b
IR.UVLiteral (SQLExpression ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind))
-> SQLExpression ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
forall a b. (a -> b) -> a -> b
$
SQLExp -> TypeAnn -> SQLExp
SETyAnn
([SQLExp] -> SQLExp
SEArray ([SQLExp] -> SQLExp) -> [SQLExp] -> SQLExp
forall a b. (a -> b) -> a -> b
$ PGScalarValue -> SQLExp
txtEncoder (PGScalarValue -> SQLExp)
-> (ColumnValue ('Postgres pgKind) -> PGScalarValue)
-> ColumnValue ('Postgres pgKind)
-> SQLExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnValue ('Postgres pgKind) -> PGScalarValue
forall (b :: BackendType). ColumnValue b -> ScalarValue b
cvValue (ColumnValue ('Postgres pgKind) -> SQLExp)
-> [ColumnValue ('Postgres pgKind)] -> [SQLExp]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ColumnValue ('Postgres pgKind)]
columnValues)
(CollectableType PGScalarType -> TypeAnn
mkTypeAnn (CollectableType PGScalarType -> TypeAnn)
-> CollectableType PGScalarType -> TypeAnn
forall a b. (a -> b) -> a -> b
$ PGScalarType -> CollectableType PGScalarType
forall a. a -> CollectableType a
CollectableTypeArray (PGScalarType -> CollectableType PGScalarType)
-> PGScalarType -> CollectableType PGScalarType
forall a b. (a -> b) -> a -> b
$ ColumnType ('Postgres pgKind) -> PGScalarType
forall (pgKind :: PostgresKind).
ColumnType ('Postgres pgKind) -> PGScalarType
unsafePGColumnToBackend ColumnType ('Postgres pgKind)
columnType)
mkListParameter :: ColumnType ('Postgres pgKind) -> [ColumnValue ('Postgres pgKind)] -> IR.UnpreparedValue ('Postgres pgKind)
mkListParameter :: ColumnType ('Postgres pgKind)
-> [ColumnValue ('Postgres pgKind)]
-> UnpreparedValue ('Postgres pgKind)
mkListParameter ColumnType ('Postgres pgKind)
columnType [ColumnValue ('Postgres pgKind)]
columnValues = do
let scalarType :: PGScalarType
scalarType = ColumnType ('Postgres pgKind) -> PGScalarType
forall (pgKind :: PostgresKind).
ColumnType ('Postgres pgKind) -> PGScalarType
unsafePGColumnToBackend ColumnType ('Postgres pgKind)
columnType
Maybe VariableInfo
-> ColumnValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
Maybe VariableInfo -> ColumnValue b -> UnpreparedValue b
IR.UVParameter Maybe VariableInfo
forall a. Maybe a
Nothing (ColumnValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind))
-> ColumnValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
forall a b. (a -> b) -> a -> b
$
ColumnType ('Postgres pgKind)
-> ScalarValue ('Postgres pgKind) -> ColumnValue ('Postgres pgKind)
forall (b :: BackendType).
ColumnType b -> ScalarValue b -> ColumnValue b
ColumnValue
(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
$ PGScalarType -> PGScalarType
PG.PGArray PGScalarType
scalarType)
([PGScalarValue] -> PGScalarValue
PG.PGValArray ([PGScalarValue] -> PGScalarValue)
-> [PGScalarValue] -> PGScalarValue
forall a b. (a -> b) -> a -> b
$ ColumnValue ('Postgres pgKind) -> PGScalarValue
forall (b :: BackendType). ColumnValue b -> ScalarValue b
cvValue (ColumnValue ('Postgres pgKind) -> PGScalarValue)
-> [ColumnValue ('Postgres pgKind)] -> [PGScalarValue]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ColumnValue ('Postgres pgKind)]
columnValues)
castExp :: ColumnType ('Postgres pgKind) -> NamingCase -> m (Maybe (Parser 'Input n (CastExp ('Postgres pgKind) (IR.UnpreparedValue ('Postgres pgKind)))))
castExp :: ColumnType ('Postgres pgKind)
-> NamingCase
-> m (Maybe
(Parser
'Input
n
(CastExp ('Postgres pgKind) (UnpreparedValue ('Postgres pgKind)))))
castExp ColumnType ('Postgres pgKind)
sourceType NamingCase
tCase = do
let maybeScalars :: Maybe (PGScalarType, PGScalarType)
maybeScalars = case ColumnType ('Postgres pgKind)
sourceType of
ColumnScalar ScalarType ('Postgres pgKind)
PGGeography -> (PGScalarType, PGScalarType) -> Maybe (PGScalarType, PGScalarType)
forall a. a -> Maybe a
Just (PGScalarType
PGGeography, PGScalarType
PGGeometry)
ColumnScalar ScalarType ('Postgres pgKind)
PGGeometry -> (PGScalarType, PGScalarType) -> Maybe (PGScalarType, PGScalarType)
forall a. a -> Maybe a
Just (PGScalarType
PGGeometry, PGScalarType
PGGeography)
ColumnScalar ScalarType ('Postgres pgKind)
PGJSONB -> (PGScalarType, PGScalarType) -> Maybe (PGScalarType, PGScalarType)
forall a. a -> Maybe a
Just (PGScalarType
PGJSONB, PGScalarType
PGText)
ColumnType ('Postgres pgKind)
_ -> Maybe (PGScalarType, PGScalarType)
forall a. Maybe a
Nothing
Maybe (PGScalarType, PGScalarType)
-> ((PGScalarType, PGScalarType)
-> m (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])))
-> m (Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM Maybe (PGScalarType, PGScalarType)
maybeScalars (((PGScalarType, PGScalarType)
-> m (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])))
-> m (Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))))
-> ((PGScalarType, PGScalarType)
-> m (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])))
-> m (Maybe
(Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])))
forall a b. (a -> b) -> a -> b
$ \(PGScalarType
sourceScalar, PGScalarType
targetScalar) -> do
GQLNameIdentifier
scalarTypeName <- Name -> GQLNameIdentifier
C.fromAutogeneratedName (Name -> GQLNameIdentifier) -> m Name -> m GQLNameIdentifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PGScalarType -> m Name
forall (m :: * -> *). MonadError QErr m => PGScalarType -> m Name
mkScalarTypeName PGScalarType
sourceScalar
Name
targetName <- PGScalarType -> m Name
forall (m :: * -> *). MonadError QErr m => PGScalarType -> m Name
mkScalarTypeName PGScalarType
targetScalar
Parser 'Input n [ComparisonExp ('Postgres pgKind)]
targetOpExps <- ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadMemoize m, MonadParse n,
MonadError QErr m, MonadReader r m, Has SchemaOptions r,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)])
comparisonExps (ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('Postgres pgKind)]))
-> ColumnType ('Postgres pgKind)
-> m (Parser 'Input n [ComparisonExp ('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
targetScalar
let field :: InputFieldsParser
MetadataObjId
n
(Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)]))
field = Name
-> Maybe Description
-> Parser
MetadataObjId
'Input
n
(PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (PGScalarType, [ComparisonExp ('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
targetName Maybe Description
forall a. Maybe a
Nothing (Parser
MetadataObjId
'Input
n
(PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)])))
-> Parser
MetadataObjId
'Input
n
(PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)]))
forall a b. (a -> b) -> a -> b
$ (PGScalarType
targetScalar,) ([ComparisonExp ('Postgres pgKind)]
-> (PGScalarType, [ComparisonExp ('Postgres pgKind)]))
-> Parser 'Input n [ComparisonExp ('Postgres pgKind)]
-> Parser
MetadataObjId
'Input
n
(PGScalarType, [ComparisonExp ('Postgres pgKind)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Input n [ComparisonExp ('Postgres pgKind)]
targetOpExps
sourceName :: Name
sourceName = NamingCase -> GQLNameIdentifier -> Name
applyTypeNameCaseIdentifier NamingCase
tCase (GQLNameIdentifier
scalarTypeName GQLNameIdentifier -> GQLNameIdentifier -> GQLNameIdentifier
forall a. Semigroup a => a -> a -> a
<> ((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["cast", "exp"])))
Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> m (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> m (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])))
-> Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> m (Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
sourceName Maybe Description
forall a. Maybe a
Nothing (InputFieldsParser
MetadataObjId
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]))
-> InputFieldsParser
MetadataObjId
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> Parser
MetadataObjId
'Input
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
forall a b. (a -> b) -> a -> b
$ [(PGScalarType, [ComparisonExp ('Postgres pgKind)])]
-> HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
M.fromList ([(PGScalarType, [ComparisonExp ('Postgres pgKind)])]
-> HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> (Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> [(PGScalarType, [ComparisonExp ('Postgres pgKind)])])
-> Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> HashMap PGScalarType [ComparisonExp ('Postgres pgKind)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> [(PGScalarType, [ComparisonExp ('Postgres pgKind)])]
forall a. Maybe a -> [a]
maybeToList (Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)])
-> HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
-> InputFieldsParser
MetadataObjId
n
(Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)]))
-> InputFieldsParser
MetadataObjId
n
(HashMap PGScalarType [ComparisonExp ('Postgres pgKind)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InputFieldsParser
MetadataObjId
n
(Maybe (PGScalarType, [ComparisonExp ('Postgres pgKind)]))
field
geographyWithinDistanceInput ::
forall pgKind m n r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m, Has MkTypename r, Has NamingCase r) =>
m (Parser 'Input n (DWithinGeogOp (IR.UnpreparedValue ('Postgres pgKind))))
geographyWithinDistanceInput :: m (Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind))))
geographyWithinDistanceInput = do
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geographyParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeography) (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
booleanParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGBoolean) (Bool -> Nullability
G.Nullability Bool
True)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
floatParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGFloat) (Bool -> Nullability
G.Nullability Bool
False)
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
Name._st_d_within_geography_input Maybe Description
forall a. Maybe a
Nothing (InputFieldsParser
MetadataObjId
n
(DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input n (DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$
UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind))
forall field. field -> field -> field -> DWithinGeogOp field
DWithinGeogOp (UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._distance Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
floatParser)
InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._from Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geographyParser)
InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(DWithinGeogOp (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Value Void
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Value Void
-> Parser origin k m a
-> InputFieldsParser origin m a
P.fieldWithDefault Name
Name._use_spheroid Maybe Description
forall a. Maybe a
Nothing (Bool -> Value Void
forall var. Bool -> Value var
G.VBoolean Bool
True) Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
booleanParser)
geometryWithinDistanceInput ::
forall pgKind m n r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m, Has MkTypename r, Has NamingCase r) =>
m (Parser 'Input n (DWithinGeomOp (IR.UnpreparedValue ('Postgres pgKind))))
geometryWithinDistanceInput :: m (Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))))
geometryWithinDistanceInput = do
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geometryParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeometry) (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
floatParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGFloat) (Bool -> Nullability
G.Nullability Bool
False)
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
Name._st_d_within_input Maybe Description
forall a. Maybe a
Nothing (InputFieldsParser
MetadataObjId
n
(DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input n (DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$
UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> DWithinGeomOp (UnpreparedValue ('Postgres pgKind))
forall field. field -> field -> DWithinGeomOp field
DWithinGeomOp (UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._distance Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
floatParser)
InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(DWithinGeomOp (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._from Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geometryParser)
intersectsNbandGeomInput ::
forall pgKind m n r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m, Has MkTypename r, Has NamingCase r) =>
m (Parser 'Input n (STIntersectsNbandGeommin (IR.UnpreparedValue ('Postgres pgKind))))
intersectsNbandGeomInput :: m (Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))))
intersectsNbandGeomInput = do
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geometryParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeometry) (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
integerParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGInteger) (Bool -> Nullability
G.Nullability Bool
False)
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
Name._st_intersects_nband_geom_input Maybe Description
forall a. Maybe a
Nothing (InputFieldsParser
MetadataObjId
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$
UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind))
forall field. field -> field -> STIntersectsNbandGeommin field
STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)
-> UnpreparedValue ('Postgres pgKind)
-> STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._nband Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
integerParser)
InputFieldsParser
MetadataObjId
n
(UnpreparedValue ('Postgres pgKind)
-> STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(STIntersectsNbandGeommin (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._geommin Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geometryParser)
intersectsGeomNbandInput ::
forall pgKind m n r.
(MonadMemoize m, MonadParse n, MonadError QErr m, MonadReader r m, Has MkTypename r, Has NamingCase r) =>
m (Parser 'Input n (STIntersectsGeomminNband (IR.UnpreparedValue ('Postgres pgKind))))
intersectsGeomNbandInput :: m (Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))))
intersectsGeomNbandInput = do
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geometryParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGGeometry) (Bool -> Nullability
G.Nullability Bool
False)
Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
integerParser <- ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGInteger) (Bool -> Nullability
G.Nullability Bool
False)
pure $
Name
-> Maybe Description
-> InputFieldsParser
MetadataObjId
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> InputFieldsParser origin m a
-> Parser origin 'Input m a
P.object Name
Name._st_intersects_geom_nband_input Maybe Description
forall a. Maybe a
Nothing (InputFieldsParser
MetadataObjId
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
-> Parser
'Input
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
forall a b. (a -> b) -> a -> b
$
UnpreparedValue ('Postgres pgKind)
-> Maybe (UnpreparedValue ('Postgres pgKind))
-> STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind))
forall field.
field -> Maybe field -> STIntersectsGeomminNband field
STIntersectsGeomminNband
(UnpreparedValue ('Postgres pgKind)
-> Maybe (UnpreparedValue ('Postgres pgKind))
-> STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId
n
(Maybe (UnpreparedValue ('Postgres pgKind))
-> STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> InputFieldsParser
MetadataObjId n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name
-> Maybe Description
-> Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (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 a
P.field Name
Name._geommin Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
geometryParser)
InputFieldsParser
MetadataObjId
n
(Maybe (UnpreparedValue ('Postgres pgKind))
-> STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId n (Maybe (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(STIntersectsGeomminNband (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Maybe (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Maybe (UnpreparedValue ('Postgres pgKind)))
-> InputFieldsParser
MetadataObjId
n
(Maybe (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> InputFieldsParser
MetadataObjId n (Maybe (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
Name._nband Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind)))
integerParser)
countTypeInput ::
MonadParse n =>
Maybe (Parser 'Both n (Column ('Postgres pgKind))) ->
InputFieldsParser n (IR.CountDistinct -> CountType ('Postgres pgKind))
countTypeInput :: Maybe (Parser 'Both n (Column ('Postgres pgKind)))
-> InputFieldsParser
n (CountDistinct -> CountType ('Postgres pgKind))
countTypeInput = \case
Just Parser 'Both n (Column ('Postgres pgKind))
columnEnum -> do
Maybe [PGCol]
columns <- Name
-> Maybe Description
-> Parser MetadataObjId 'Both n [PGCol]
-> InputFieldsParser MetadataObjId n (Maybe [PGCol])
forall (m :: * -> *) (k :: Kind) origin a.
(MonadParse m, 'Input <: k) =>
Name
-> Maybe Description
-> Parser origin k m a
-> InputFieldsParser origin m (Maybe a)
P.fieldOptional Name
Name._columns Maybe Description
forall a. Maybe a
Nothing (Parser MetadataObjId 'Both n PGCol
-> Parser MetadataObjId 'Both n [PGCol]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list Parser 'Both n (Column ('Postgres pgKind))
Parser MetadataObjId 'Both n PGCol
columnEnum)
pure $ (CountDistinct -> Maybe [PGCol] -> CountType)
-> Maybe [PGCol] -> CountDistinct -> CountType
forall a b c. (a -> b -> c) -> b -> a -> c
flip CountDistinct -> Maybe [PGCol] -> CountType
forall (pgKind :: PostgresKind).
CountDistinct
-> Maybe [Column ('Postgres pgKind)]
-> CountType ('Postgres pgKind)
mkCountType Maybe [PGCol]
columns
Maybe (Parser 'Both n (Column ('Postgres pgKind)))
Nothing -> (CountDistinct -> CountType)
-> InputFieldsParser MetadataObjId n (CountDistinct -> CountType)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((CountDistinct -> CountType)
-> InputFieldsParser MetadataObjId n (CountDistinct -> CountType))
-> (CountDistinct -> CountType)
-> InputFieldsParser MetadataObjId n (CountDistinct -> CountType)
forall a b. (a -> b) -> a -> b
$ (CountDistinct -> Maybe [PGCol] -> CountType)
-> Maybe [PGCol] -> CountDistinct -> CountType
forall a b c. (a -> b -> c) -> b -> a -> c
flip CountDistinct -> Maybe [PGCol] -> CountType
forall (pgKind :: PostgresKind).
CountDistinct
-> Maybe [Column ('Postgres pgKind)]
-> CountType ('Postgres pgKind)
mkCountType Maybe [PGCol]
forall a. Maybe a
Nothing
where
mkCountType :: IR.CountDistinct -> Maybe [Column ('Postgres pgKind)] -> CountType ('Postgres pgKind)
mkCountType :: CountDistinct
-> Maybe [Column ('Postgres pgKind)]
-> CountType ('Postgres pgKind)
mkCountType CountDistinct
_ Maybe [Column ('Postgres pgKind)]
Nothing = CountType ('Postgres pgKind)
CountType
PG.CTStar
mkCountType CountDistinct
IR.SelectCountDistinct (Just [Column ('Postgres pgKind)]
cols) = [PGCol] -> CountType
PG.CTDistinct [Column ('Postgres pgKind)]
[PGCol]
cols
mkCountType CountDistinct
IR.SelectCountNonDistinct (Just [Column ('Postgres pgKind)]
cols) = [PGCol] -> CountType
PG.CTSimple [Column ('Postgres pgKind)]
[PGCol]
cols
prependOp ::
forall pgKind m n r.
( BackendSchema ('Postgres pgKind),
MonadReader r m,
MonadError QErr m,
MonadParse n,
Has MkTypename r,
Has NamingCase r
) =>
SU.UpdateOperator ('Postgres pgKind) m n (IR.UnpreparedValue ('Postgres pgKind))
prependOp :: UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
prependOp = UpdateOperator :: forall (b :: BackendType) (m :: * -> *) (n :: * -> *) op.
(ColumnInfo b -> Bool)
-> (GQLNameIdentifier
-> TableName b
-> NonEmpty (ColumnInfo b)
-> m (InputFieldsParser n (HashMap (Column b) op)))
-> UpdateOperator b m n op
SU.UpdateOperator {GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
..}
where
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorApplicableColumn = (ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGJSONB) (ColumnType ('Postgres pgKind) -> Bool)
-> (ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind))
-> ColumnInfo ('Postgres pgKind)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorParser GQLNameIdentifier
tableGQLName QualifiedTable
_tableName NonEmpty (ColumnInfo ('Postgres pgKind))
columns = do
let typedParser :: ColumnInfo b
-> f (Parser MetadataObjId 'Both n (UnpreparedValue b))
typedParser ColumnInfo b
columnInfo =
(ValueWithOrigin (ColumnValue b) -> UnpreparedValue b)
-> Parser MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b))
-> Parser MetadataObjId 'Both n (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter
(Parser MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b))
-> Parser MetadataObjId 'Both n (UnpreparedValue b))
-> f (Parser
MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b)))
-> f (Parser MetadataObjId 'Both n (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType b
-> Nullability
-> f (Parser
MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
BS.columnParser
(ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo)
(Bool -> Nullability
G.Nullability (Bool -> Nullability) -> Bool -> Nullability
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Bool
forall (b :: BackendType). ColumnInfo b -> Bool
ciIsNullable ColumnInfo b
columnInfo)
desc :: Description
desc = Description
"prepend existing jsonb value of filtered columns with new jsonb value"
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind))))
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> Description
-> Description
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
forall (n :: * -> *) r (m :: * -> *) (b :: BackendType) a.
(MonadParse n, MonadReader r m, Has MkTypename r, Has NamingCase r,
Backend b) =>
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo b -> m (Parser 'Both n a))
-> NonEmpty (ColumnInfo b)
-> Description
-> Description
-> m (InputFieldsParser n (HashMap (Column b) a))
SU.updateOperator
GQLNameIdentifier
tableGQLName
(Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "prepend"))
(Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "_prepend"))
ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind)))
forall (b :: BackendType) (n :: * -> *) (f :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr f, MonadReader r f,
Has MkTypename r, Has NamingCase r) =>
ColumnInfo b
-> f (Parser MetadataObjId 'Both n (UnpreparedValue b))
typedParser
NonEmpty (ColumnInfo ('Postgres pgKind))
columns
Description
desc
Description
desc
appendOp ::
forall pgKind m n r.
( BackendSchema ('Postgres pgKind),
MonadReader r m,
MonadError QErr m,
MonadParse n,
Has MkTypename r,
Has NamingCase r
) =>
SU.UpdateOperator ('Postgres pgKind) m n (IR.UnpreparedValue ('Postgres pgKind))
appendOp :: UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
appendOp = UpdateOperator :: forall (b :: BackendType) (m :: * -> *) (n :: * -> *) op.
(ColumnInfo b -> Bool)
-> (GQLNameIdentifier
-> TableName b
-> NonEmpty (ColumnInfo b)
-> m (InputFieldsParser n (HashMap (Column b) op)))
-> UpdateOperator b m n op
SU.UpdateOperator {GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
..}
where
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorApplicableColumn = (ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGJSONB) (ColumnType ('Postgres pgKind) -> Bool)
-> (ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind))
-> ColumnInfo ('Postgres pgKind)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorParser GQLNameIdentifier
tableGQLName QualifiedTable
_tableName NonEmpty (ColumnInfo ('Postgres pgKind))
columns = do
let typedParser :: ColumnInfo b
-> f (Parser MetadataObjId 'Both n (UnpreparedValue b))
typedParser ColumnInfo b
columnInfo =
(ValueWithOrigin (ColumnValue b) -> UnpreparedValue b)
-> Parser MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b))
-> Parser MetadataObjId 'Both n (UnpreparedValue b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter
(Parser MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b))
-> Parser MetadataObjId 'Both n (UnpreparedValue b))
-> f (Parser
MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b)))
-> f (Parser MetadataObjId 'Both n (UnpreparedValue b))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType b
-> Nullability
-> f (Parser
MetadataObjId 'Both n (ValueWithOrigin (ColumnValue b)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
BS.columnParser
(ColumnInfo b -> ColumnType b
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType ColumnInfo b
columnInfo)
(Bool -> Nullability
G.Nullability (Bool -> Nullability) -> Bool -> Nullability
forall a b. (a -> b) -> a -> b
$ ColumnInfo b -> Bool
forall (b :: BackendType). ColumnInfo b -> Bool
ciIsNullable ColumnInfo b
columnInfo)
desc :: Description
desc = Description
"append existing jsonb value of filtered columns with new jsonb value"
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind))))
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> Description
-> Description
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
forall (n :: * -> *) r (m :: * -> *) (b :: BackendType) a.
(MonadParse n, MonadReader r m, Has MkTypename r, Has NamingCase r,
Backend b) =>
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo b -> m (Parser 'Both n a))
-> NonEmpty (ColumnInfo b)
-> Description
-> Description
-> m (InputFieldsParser n (HashMap (Column b) a))
SU.updateOperator
GQLNameIdentifier
tableGQLName
(Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "append"))
(Name -> GQLNameIdentifier
C.fromAutogeneratedName $$(G.litName "_append"))
ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind)))
forall (b :: BackendType) (n :: * -> *) (f :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr f, MonadReader r f,
Has MkTypename r, Has NamingCase r) =>
ColumnInfo b
-> f (Parser MetadataObjId 'Both n (UnpreparedValue b))
typedParser
NonEmpty (ColumnInfo ('Postgres pgKind))
columns
Description
desc
Description
desc
deleteKeyOp ::
forall pgKind m n r.
( BackendSchema ('Postgres pgKind),
MonadReader r m,
MonadError QErr m,
MonadParse n,
Has MkTypename r,
Has NamingCase r
) =>
SU.UpdateOperator ('Postgres pgKind) m n (IR.UnpreparedValue ('Postgres pgKind))
deleteKeyOp :: UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
deleteKeyOp = UpdateOperator :: forall (b :: BackendType) (m :: * -> *) (n :: * -> *) op.
(ColumnInfo b -> Bool)
-> (GQLNameIdentifier
-> TableName b
-> NonEmpty (ColumnInfo b)
-> m (InputFieldsParser n (HashMap (Column b) op)))
-> UpdateOperator b m n op
SU.UpdateOperator {GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
..}
where
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorApplicableColumn = (ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGJSONB) (ColumnType ('Postgres pgKind) -> Bool)
-> (ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind))
-> ColumnInfo ('Postgres pgKind)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorParser GQLNameIdentifier
tableGQLName QualifiedTable
_tableName NonEmpty (ColumnInfo ('Postgres pgKind))
columns = do
let nullableTextParser :: p
-> f (Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
nullableTextParser p
_ = (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
-> f (Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> f (Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind)
-> Nullability
-> f (Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText) (Bool -> Nullability
G.Nullability Bool
True)
desc :: Description
desc = Description
"delete key/value pair or string element. key/value pairs are matched based on their key value"
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind))))
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> Description
-> Description
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
forall (n :: * -> *) r (m :: * -> *) (b :: BackendType) a.
(MonadParse n, MonadReader r m, Has MkTypename r, Has NamingCase r,
Backend b) =>
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo b -> m (Parser 'Both n a))
-> NonEmpty (ColumnInfo b)
-> Description
-> Description
-> m (InputFieldsParser n (HashMap (Column b) a))
SU.updateOperator
GQLNameIdentifier
tableGQLName
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["delete", "key"]))
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_delete", "key"]))
ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) (n :: * -> *) r p (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr f, MonadReader r f,
Has MkTypename r, Has NamingCase r) =>
p
-> f (Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
nullableTextParser
NonEmpty (ColumnInfo ('Postgres pgKind))
columns
Description
desc
Description
desc
deleteElemOp ::
forall pgKind m n r.
( BackendSchema ('Postgres pgKind),
MonadReader r m,
MonadError QErr m,
MonadParse n,
Has MkTypename r,
Has NamingCase r
) =>
SU.UpdateOperator ('Postgres pgKind) m n (IR.UnpreparedValue ('Postgres pgKind))
deleteElemOp :: UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
deleteElemOp = UpdateOperator :: forall (b :: BackendType) (m :: * -> *) (n :: * -> *) op.
(ColumnInfo b -> Bool)
-> (GQLNameIdentifier
-> TableName b
-> NonEmpty (ColumnInfo b)
-> m (InputFieldsParser n (HashMap (Column b) op)))
-> UpdateOperator b m n op
SU.UpdateOperator {GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
..}
where
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorApplicableColumn = (ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGJSONB) (ColumnType ('Postgres pgKind) -> Bool)
-> (ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind))
-> ColumnInfo ('Postgres pgKind)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol (UnpreparedValue ('Postgres pgKind))))
updateOperatorParser GQLNameIdentifier
tableGQLName QualifiedTable
_tableName NonEmpty (ColumnInfo ('Postgres pgKind))
columns = do
let nonNullableIntParser :: p
-> f (Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
nonNullableIntParser p
_ = (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
-> f (Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> f (Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind)
-> Nullability
-> f (Parser
MetadataObjId
'Both
n
(ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGInteger) (Bool -> Nullability
G.Nullability Bool
False)
desc :: Description
desc =
Description
"delete the array element with specified index (negative integers count from the end). "
Description -> Description -> Description
forall a. Semigroup a => a -> a -> a
<> Description
"throws an error if top level container is not an array"
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind))))
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> Description
-> Description
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))))
forall (n :: * -> *) r (m :: * -> *) (b :: BackendType) a.
(MonadParse n, MonadReader r m, Has MkTypename r, Has NamingCase r,
Backend b) =>
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo b -> m (Parser 'Both n a))
-> NonEmpty (ColumnInfo b)
-> Description
-> Description
-> m (InputFieldsParser n (HashMap (Column b) a))
SU.updateOperator
GQLNameIdentifier
tableGQLName
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["delete", "elem"]))
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_delete", "elem"]))
ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) (n :: * -> *) r p (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr f, MonadReader r f,
Has MkTypename r, Has NamingCase r) =>
p
-> f (Parser
MetadataObjId 'Both n (UnpreparedValue ('Postgres pgKind)))
nonNullableIntParser
NonEmpty (ColumnInfo ('Postgres pgKind))
columns
Description
desc
Description
desc
deleteAtPathOp ::
forall pgKind m n r.
( BackendSchema ('Postgres pgKind),
MonadReader r m,
MonadError QErr m,
MonadParse n,
Has MkTypename r,
Has NamingCase r
) =>
SU.UpdateOperator ('Postgres pgKind) m n [IR.UnpreparedValue ('Postgres pgKind)]
deleteAtPathOp :: UpdateOperator
('Postgres pgKind) m n [UnpreparedValue ('Postgres pgKind)]
deleteAtPathOp = UpdateOperator :: forall (b :: BackendType) (m :: * -> *) (n :: * -> *) op.
(ColumnInfo b -> Bool)
-> (GQLNameIdentifier
-> TableName b
-> NonEmpty (ColumnInfo b)
-> m (InputFieldsParser n (HashMap (Column b) op)))
-> UpdateOperator b m n op
SU.UpdateOperator {GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) [UnpreparedValue ('Postgres pgKind)]))
GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol [UnpreparedValue ('Postgres pgKind)]))
ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol [UnpreparedValue ('Postgres pgKind)]))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorParser :: GQLNameIdentifier
-> TableName ('Postgres pgKind)
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) [UnpreparedValue ('Postgres pgKind)]))
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
..}
where
updateOperatorApplicableColumn :: ColumnInfo ('Postgres pgKind) -> Bool
updateOperatorApplicableColumn = (ScalarType ('Postgres pgKind) -> Bool)
-> ColumnType ('Postgres pgKind) -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGJSONB) (ColumnType ('Postgres pgKind) -> Bool)
-> (ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind))
-> ColumnInfo ('Postgres pgKind)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnInfo ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ColumnInfo b -> ColumnType b
ciType
updateOperatorParser :: GQLNameIdentifier
-> QualifiedTable
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> m (InputFieldsParser
n (HashMap PGCol [UnpreparedValue ('Postgres pgKind)]))
updateOperatorParser GQLNameIdentifier
tableGQLName QualifiedTable
_tableName NonEmpty (ColumnInfo ('Postgres pgKind))
columns = do
let nonNullableTextListParser :: p
-> f (Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)])
nonNullableTextListParser p
_ = Parser MetadataObjId 'Both m (UnpreparedValue ('Postgres pgKind))
-> Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)]
forall origin (k :: Kind) (m :: * -> *) a.
(MonadParse m, 'Input <: k) =>
Parser origin k m a -> Parser origin k m [a]
P.list (Parser MetadataObjId 'Both m (UnpreparedValue ('Postgres pgKind))
-> Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)])
-> (Parser
MetadataObjId
'Both
m
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both m (UnpreparedValue ('Postgres pgKind)))
-> Parser
MetadataObjId
'Both
m
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind))
-> Parser
MetadataObjId
'Both
m
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both m (UnpreparedValue ('Postgres pgKind))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue ('Postgres pgKind))
-> UnpreparedValue ('Postgres pgKind)
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
IR.mkParameter (Parser
MetadataObjId
'Both
m
(ValueWithOrigin (ColumnValue ('Postgres pgKind)))
-> Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)])
-> f (Parser
MetadataObjId
'Both
m
(ValueWithOrigin (ColumnValue ('Postgres pgKind))))
-> f (Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ColumnType ('Postgres pgKind)
-> Nullability
-> f (Parser
MetadataObjId
'Both
m
(ValueWithOrigin (ColumnValue ('Postgres pgKind))))
forall (n :: * -> *) (m :: * -> *) r (pgKind :: PostgresKind).
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType ('Postgres pgKind)
-> Nullability
-> m (Parser
'Both n (ValueWithOrigin (ColumnValue ('Postgres pgKind))))
columnParser (ScalarType ('Postgres pgKind) -> ColumnType ('Postgres pgKind)
forall (b :: BackendType). ScalarType b -> ColumnType b
ColumnScalar ScalarType ('Postgres pgKind)
PGScalarType
PGText) (Bool -> Nullability
G.Nullability Bool
False)
desc :: Description
desc = Description
"delete the field or element with specified path (for JSON arrays, negative integers count from the end)"
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n [UnpreparedValue ('Postgres pgKind)]))
-> NonEmpty (ColumnInfo ('Postgres pgKind))
-> Description
-> Description
-> m (InputFieldsParser
MetadataObjId
n
(HashMap
(Column ('Postgres pgKind)) [UnpreparedValue ('Postgres pgKind)]))
forall (n :: * -> *) r (m :: * -> *) (b :: BackendType) a.
(MonadParse n, MonadReader r m, Has MkTypename r, Has NamingCase r,
Backend b) =>
GQLNameIdentifier
-> GQLNameIdentifier
-> GQLNameIdentifier
-> (ColumnInfo b -> m (Parser 'Both n a))
-> NonEmpty (ColumnInfo b)
-> Description
-> Description
-> m (InputFieldsParser n (HashMap (Column b) a))
SU.updateOperator
GQLNameIdentifier
tableGQLName
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["delete", "at", "path"]))
((Name, [NameSuffix]) -> GQLNameIdentifier
C.fromAutogeneratedTuple $$(G.litGQLIdentifier ["_delete", "at", "path"]))
ColumnInfo ('Postgres pgKind)
-> m (Parser 'Both n [UnpreparedValue ('Postgres pgKind)])
forall (m :: * -> *) (f :: * -> *) r p (pgKind :: PostgresKind).
(MonadParse m, MonadError QErr f, MonadReader r f,
Has MkTypename r, Has NamingCase r) =>
p
-> f (Parser
MetadataObjId 'Both m [UnpreparedValue ('Postgres pgKind)])
nonNullableTextListParser
NonEmpty (ColumnInfo ('Postgres pgKind))
columns
Description
desc
Description
desc
updateOperators ::
forall pgKind m n r.
MonadBuildSchema ('Postgres pgKind) r m n =>
TableInfo ('Postgres pgKind) ->
UpdPermInfo ('Postgres pgKind) ->
m (InputFieldsParser n (HashMap (Column ('Postgres pgKind)) (UpdateOpExpression (IR.UnpreparedValue ('Postgres pgKind)))))
updateOperators :: TableInfo ('Postgres pgKind)
-> UpdPermInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
updateOperators TableInfo ('Postgres pgKind)
tableInfo UpdPermInfo ('Postgres pgKind)
updatePermissions = do
HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> [UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))]
-> TableInfo ('Postgres pgKind)
-> m (InputFieldsParser
n
(HashMap
(Column ('Postgres pgKind))
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *) op.
MonadBuildSchema b r m n =>
HashMap (Column b) op
-> [UpdateOperator b m n op]
-> TableInfo b
-> m (InputFieldsParser n (HashMap (Column b) op))
SU.buildUpdateOperators
(UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdateSet (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> HashMap PGCol (UnpreparedValue ('Postgres pgKind))
-> HashMap
PGCol (UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdPermInfo ('Postgres pgKind)
-> HashMap
(Column ('Postgres pgKind)) (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType).
UpdPermInfo b -> HashMap (Column b) (UnpreparedValue b)
SU.presetColumns UpdPermInfo ('Postgres pgKind)
updatePermissions)
[ UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdateSet (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) (n :: * -> *) r (m :: * -> *).
(BackendSchema b, MonadReader r m, Has MkTypename r,
Has NamingCase r, MonadError QErr m, MonadParse n) =>
UpdateOperator b m n (UnpreparedValue b)
SU.setOp,
UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdateInc (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
forall (b :: BackendType) (m :: * -> *) (n :: * -> *) r.
(Backend b, MonadReader r m, MonadError QErr m, MonadParse n,
BackendSchema b, Has MkTypename r, Has NamingCase r) =>
UpdateOperator b m n (UnpreparedValue b)
SU.incOp,
UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdatePrepend (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadReader r m,
MonadError QErr m, MonadParse n, Has MkTypename r,
Has NamingCase r) =>
UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
prependOp,
UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdateAppend (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadReader r m,
MonadError QErr m, MonadParse n, Has MkTypename r,
Has NamingCase r) =>
UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
appendOp,
UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdateDeleteKey (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadReader r m,
MonadError QErr m, MonadParse n, Has MkTypename r,
Has NamingCase r) =>
UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
deleteKeyOp,
UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. v -> UpdateOpExpression v
PGIR.UpdateDeleteElem (UnpreparedValue ('Postgres pgKind)
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadReader r m,
MonadError QErr m, MonadParse n, Has MkTypename r,
Has NamingCase r) =>
UpdateOperator
('Postgres pgKind) m n (UnpreparedValue ('Postgres pgKind))
deleteElemOp,
[UnpreparedValue ('Postgres pgKind)]
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind))
forall v. [v] -> UpdateOpExpression v
PGIR.UpdateDeleteAtPath ([UnpreparedValue ('Postgres pgKind)]
-> UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
-> UpdateOperator
('Postgres pgKind) m n [UnpreparedValue ('Postgres pgKind)]
-> UpdateOperator
('Postgres pgKind)
m
n
(UpdateOpExpression (UnpreparedValue ('Postgres pgKind)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator
('Postgres pgKind) m n [UnpreparedValue ('Postgres pgKind)]
forall (pgKind :: PostgresKind) (m :: * -> *) (n :: * -> *) r.
(BackendSchema ('Postgres pgKind), MonadReader r m,
MonadError QErr m, MonadParse n, Has MkTypename r,
Has NamingCase r) =>
UpdateOperator
('Postgres pgKind) m n [UnpreparedValue ('Postgres pgKind)]
deleteAtPathOp
]
TableInfo ('Postgres pgKind)
tableInfo