{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Backends.MSSQL.Instances.Schema () where
import Data.Char qualified as Char
import Data.Has
import Data.HashMap.Strict qualified as Map
import Data.List.NonEmpty qualified as NE
import Data.Text qualified as T
import Data.Text.Casing qualified as C
import Data.Text.Encoding as TE
import Data.Text.Extended
import Database.ODBC.SQLServer qualified as ODBC
import Hasura.Backends.MSSQL.Schema.IfMatched
import Hasura.Backends.MSSQL.Types.Insert (BackendInsert (..))
import Hasura.Backends.MSSQL.Types.Internal qualified as MSSQL
import Hasura.Backends.MSSQL.Types.Update (BackendUpdate (..), UpdateOperator (..))
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (toErrorMessage)
import Hasura.GraphQL.Schema.Backend
import Hasura.GraphQL.Schema.BoolExp
import Hasura.GraphQL.Schema.Build qualified as GSB
import Hasura.GraphQL.Schema.Common
import Hasura.GraphQL.Schema.NamingCase
import Hasura.GraphQL.Schema.Options (SchemaOptions)
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.GraphQL.Schema.Parser
( FieldParser,
InputFieldsParser,
Kind (..),
MonadMemoize,
MonadParse,
Parser,
)
import Hasura.GraphQL.Schema.Parser qualified as P
import Hasura.GraphQL.Schema.Select
import Hasura.GraphQL.Schema.Typename (MkTypename)
import Hasura.GraphQL.Schema.Update qualified as SU
import Hasura.Name qualified as Name
import Hasura.Prelude
import Hasura.RQL.IR
import Hasura.RQL.IR.Select qualified as IR
import Hasura.RQL.Types.Backend hiding (BackendInsert)
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization (MkRootFieldName (..))
import Hasura.RQL.Types.Table
import Hasura.SQL.Backend
import Language.GraphQL.Draft.Syntax qualified as G
instance BackendSchema 'MSSQL where
buildTableQueryAndSubscriptionFields :: MkRootFieldName
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))],
[FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))],
Maybe (Name, Parser 'Output n (ApolloFederationParserFunction n)))
buildTableQueryAndSubscriptionFields = MkRootFieldName
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m ([FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))],
[FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))],
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 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> NESeq (ColumnInfo 'MSSQL)
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildTableRelayQueryFields MkRootFieldName
_ SourceInfo 'MSSQL
_ TableName 'MSSQL
_ TableInfo 'MSSQL
_ GQLNameIdentifier
_ NESeq (ColumnInfo 'MSSQL)
_ = [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
buildTableStreamingSubscriptionFields :: MkRootFieldName
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildTableStreamingSubscriptionFields = MkRootFieldName
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
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 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildTableInsertMutationFields = (SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (BackendInsert 'MSSQL (UnpreparedValue 'MSSQL))))
-> MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedInsert
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
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 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (BackendInsert 'MSSQL (UnpreparedValue 'MSSQL)))
forall (m :: * -> *) r (n :: * -> *).
MonadBuildSchema 'MSSQL r m n =>
SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL)))
backendInsertParser
buildTableDeleteMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildTableDeleteMutationFields = MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnDelG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
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
buildTableUpdateMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildTableUpdateMutationFields = MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
msBuildTableUpdateMutationFields
buildFunctionQueryFields :: MkRootFieldName
-> SourceInfo 'MSSQL
-> FunctionName 'MSSQL
-> FunctionInfo 'MSSQL
-> TableName 'MSSQL
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildFunctionQueryFields MkRootFieldName
_ SourceInfo 'MSSQL
_ FunctionName 'MSSQL
_ FunctionInfo 'MSSQL
_ TableName 'MSSQL
_ = [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
buildFunctionRelayQueryFields :: MkRootFieldName
-> SourceInfo 'MSSQL
-> FunctionName 'MSSQL
-> FunctionInfo 'MSSQL
-> TableName 'MSSQL
-> NESeq (ColumnInfo 'MSSQL)
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildFunctionRelayQueryFields MkRootFieldName
_ SourceInfo 'MSSQL
_ FunctionName 'MSSQL
_ FunctionInfo 'MSSQL
_ TableName 'MSSQL
_ NESeq (ColumnInfo 'MSSQL)
_ = [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(QueryDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
buildFunctionMutationFields :: MkRootFieldName
-> SourceInfo 'MSSQL
-> FunctionName 'MSSQL
-> FunctionInfo 'MSSQL
-> TableName 'MSSQL
-> m [FieldParser
n
(MutationDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
buildFunctionMutationFields MkRootFieldName
_ SourceInfo 'MSSQL
_ FunctionName 'MSSQL
_ FunctionInfo 'MSSQL
_ TableName 'MSSQL
_ = [FieldParser
n
(MutationDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(MutationDB
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
relayExtension :: Maybe (XRelay 'MSSQL)
relayExtension = Maybe (XRelay 'MSSQL)
forall a. Maybe a
Nothing
nodesAggExtension :: Maybe (XNodesAgg 'MSSQL)
nodesAggExtension = () -> Maybe ()
forall a. a -> Maybe a
Just ()
streamSubscriptionExtension :: Maybe (XStreamingSubscription 'MSSQL)
streamSubscriptionExtension = Maybe (XStreamingSubscription 'MSSQL)
forall a. Maybe a
Nothing
mkRelationshipParser :: SourceInfo 'MSSQL
-> RelInfo 'MSSQL
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField 'MSSQL (UnpreparedValue 'MSSQL)))))
mkRelationshipParser SourceInfo 'MSSQL
_ RelInfo 'MSSQL
_ = Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField 'MSSQL (UnpreparedValue 'MSSQL))))
-> m (Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField 'MSSQL (UnpreparedValue 'MSSQL)))))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe
(InputFieldsParser
n (Maybe (AnnotatedInsertField 'MSSQL (UnpreparedValue 'MSSQL))))
forall a. Maybe a
Nothing
columnParser :: ColumnType 'MSSQL
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
columnParser = ColumnType 'MSSQL
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
forall (n :: * -> *) (m :: * -> *) r.
(MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType 'MSSQL
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
msColumnParser
scalarSelectionArgumentsParser :: ColumnType 'MSSQL
-> InputFieldsParser n (Maybe (ScalarSelectionArguments 'MSSQL))
scalarSelectionArgumentsParser ColumnType 'MSSQL
_ = Maybe Void -> InputFieldsParser MetadataObjId n (Maybe Void)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Void
forall a. Maybe a
Nothing
orderByOperators :: SourceInfo 'MSSQL
-> NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType 'MSSQL, NullsOrderType 'MSSQL)))
orderByOperators SourceInfo 'MSSQL
_sourceInfo = NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType 'MSSQL, NullsOrderType 'MSSQL)))
msOrderByOperators
comparisonExps :: ColumnType 'MSSQL -> m (Parser 'Input n [ComparisonExp 'MSSQL])
comparisonExps = ColumnType 'MSSQL -> m (Parser 'Input n [ComparisonExp 'MSSQL])
forall (m :: * -> *) (n :: * -> *) r.
(BackendSchema 'MSSQL, MonadMemoize m, MonadParse n,
MonadError QErr m, MonadReader r m, Has SchemaOptions r,
Has MkTypename r, Has NamingCase r) =>
ColumnType 'MSSQL -> m (Parser 'Input n [ComparisonExp 'MSSQL])
msComparisonExps
countTypeInput :: Maybe (Parser 'Both n (Column 'MSSQL))
-> InputFieldsParser n (CountDistinct -> CountType 'MSSQL)
countTypeInput = Maybe (Parser 'Both n (Column 'MSSQL))
-> InputFieldsParser n (CountDistinct -> CountType 'MSSQL)
forall (n :: * -> *).
MonadParse n =>
Maybe (Parser 'Both n (Column 'MSSQL))
-> InputFieldsParser n (CountDistinct -> CountType 'MSSQL)
msCountTypeInput
aggregateOrderByCountType :: ScalarType 'MSSQL
aggregateOrderByCountType = ScalarType 'MSSQL
ScalarType
MSSQL.IntegerType
computedField :: SourceInfo 'MSSQL
-> ComputedFieldInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> m (Maybe (FieldParser n (AnnotatedField 'MSSQL)))
computedField SourceInfo 'MSSQL
_ ComputedFieldInfo 'MSSQL
_ TableName 'MSSQL
_ TableInfo 'MSSQL
_ = Maybe (FieldParser n (AnnotatedField 'MSSQL))
-> m (Maybe (FieldParser n (AnnotatedField 'MSSQL)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (FieldParser n (AnnotatedField 'MSSQL))
forall a. Maybe a
Nothing
instance BackendTableSelectSchema 'MSSQL where
tableArguments :: SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (SelectArgsG 'MSSQL (UnpreparedValue 'MSSQL)))
tableArguments = SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (SelectArgsG 'MSSQL (UnpreparedValue 'MSSQL)))
forall r (m :: * -> *) (n :: * -> *).
MonadBuildSchema 'MSSQL r m n =>
SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (SelectArgsG 'MSSQL (UnpreparedValue 'MSSQL)))
msTableArgs
selectTable :: SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp 'MSSQL)))
selectTable = SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (SelectExp 'MSSQL)))
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 'MSSQL
-> TableInfo 'MSSQL
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp 'MSSQL)))
selectTableAggregate = SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> Name
-> Maybe Description
-> m (Maybe (FieldParser n (AggSelectExp 'MSSQL)))
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 'MSSQL
-> TableInfo 'MSSQL
-> m (Maybe (Parser 'Output n (AnnotatedFields 'MSSQL)))
tableSelectionSet = SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (Maybe (Parser 'Output n (AnnotatedFields 'MSSQL)))
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
backendInsertParser ::
forall m r n.
MonadBuildSchema 'MSSQL r m n =>
SourceInfo 'MSSQL ->
TableInfo 'MSSQL ->
m (InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL)))
backendInsertParser :: SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL)))
backendInsertParser SourceInfo 'MSSQL
sourceName TableInfo 'MSSQL
tableInfo = do
InputFieldsParser n (Maybe (IfMatched (UnpreparedValue 'MSSQL)))
ifMatched <- SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (Maybe (IfMatched (UnpreparedValue 'MSSQL))))
forall r (m :: * -> *) (n :: * -> *).
(MonadBuildSchema 'MSSQL r m n,
AggregationPredicatesSchema 'MSSQL) =>
SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (Maybe (IfMatched (UnpreparedValue 'MSSQL))))
ifMatchedFieldParser SourceInfo 'MSSQL
sourceName TableInfo 'MSSQL
tableInfo
let _biIdentityColumns :: ExtraTableMetadata 'MSSQL
_biIdentityColumns = TableCoreInfoG 'MSSQL (FieldInfo 'MSSQL) (ColumnInfo 'MSSQL)
-> ExtraTableMetadata 'MSSQL
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> ExtraTableMetadata b
_tciExtraTableMetadata (TableCoreInfoG 'MSSQL (FieldInfo 'MSSQL) (ColumnInfo 'MSSQL)
-> ExtraTableMetadata 'MSSQL)
-> TableCoreInfoG 'MSSQL (FieldInfo 'MSSQL) (ColumnInfo 'MSSQL)
-> ExtraTableMetadata 'MSSQL
forall a b. (a -> b) -> a -> b
$ TableInfo 'MSSQL
-> TableCoreInfoG 'MSSQL (FieldInfo 'MSSQL) (ColumnInfo 'MSSQL)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo 'MSSQL
tableInfo
InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL))
-> m (InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL))
-> m (InputFieldsParser
n (BackendInsert (UnpreparedValue 'MSSQL))))
-> InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL))
-> m (InputFieldsParser n (BackendInsert (UnpreparedValue 'MSSQL)))
forall a b. (a -> b) -> a -> b
$ do
Maybe (IfMatched (UnpreparedValue 'MSSQL))
_biIfMatched <- InputFieldsParser n (Maybe (IfMatched (UnpreparedValue 'MSSQL)))
ifMatched
pure $ BackendInsert :: forall v. Maybe (IfMatched v) -> BackendInsert v
BackendInsert {Maybe (IfMatched (UnpreparedValue 'MSSQL))
_biIfMatched :: Maybe (IfMatched (UnpreparedValue 'MSSQL))
_biIfMatched :: Maybe (IfMatched (UnpreparedValue 'MSSQL))
..}
msBuildTableUpdateMutationFields ::
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName ->
Scenario ->
SourceInfo 'MSSQL ->
TableName 'MSSQL ->
TableInfo 'MSSQL ->
C.GQLNameIdentifier ->
m [FieldParser n (AnnotatedUpdateG 'MSSQL (RemoteRelationshipField UnpreparedValue) (UnpreparedValue 'MSSQL))]
msBuildTableUpdateMutationFields :: MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
msBuildTableUpdateMutationFields MkRootFieldName
mkRootFieldName Scenario
scenario SourceInfo 'MSSQL
sourceName TableName 'MSSQL
tableName TableInfo 'MSSQL
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
Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
fieldParsers <- MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m (Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))])
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT do
UpdPermInfo 'MSSQL
updatePerms <- Maybe (UpdPermInfo 'MSSQL) -> MaybeT m (UpdPermInfo 'MSSQL)
forall (m :: * -> *) b. Applicative m => Maybe b -> MaybeT m b
hoistMaybe (Maybe (UpdPermInfo 'MSSQL) -> MaybeT m (UpdPermInfo 'MSSQL))
-> Maybe (UpdPermInfo 'MSSQL) -> MaybeT m (UpdPermInfo 'MSSQL)
forall a b. (a -> b) -> a -> b
$ RolePermInfo 'MSSQL -> Maybe (UpdPermInfo 'MSSQL)
forall (b :: BackendType). RolePermInfo b -> Maybe (UpdPermInfo b)
_permUpd (RolePermInfo 'MSSQL -> Maybe (UpdPermInfo 'MSSQL))
-> RolePermInfo 'MSSQL -> Maybe (UpdPermInfo 'MSSQL)
forall a b. (a -> b) -> a -> b
$ RoleName -> TableInfo 'MSSQL -> RolePermInfo 'MSSQL
forall (b :: BackendType).
RoleName -> TableInfo b -> RolePermInfo b
getRolePermInfo RoleName
roleName TableInfo 'MSSQL
tableInfo
let mkBackendUpdate :: TableInfo 'MSSQL
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
mkBackendUpdate TableInfo 'MSSQL
backendUpdateTableInfo =
((InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL)))
-> InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))))
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL)))
-> InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))))
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL))))
-> ((HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))
-> BackendUpdate (UnpreparedValue 'MSSQL))
-> InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL)))
-> InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
-> (HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))
-> BackendUpdate (UnpreparedValue 'MSSQL))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))))
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))
-> BackendUpdate (UnpreparedValue 'MSSQL))
-> InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL)))
-> InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))
-> BackendUpdate (UnpreparedValue 'MSSQL)
forall v. HashMap ColumnName (UpdateOperator v) -> BackendUpdate v
BackendUpdate (m (InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))))
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL))))
-> m (InputFieldsParser
MetadataObjId
n
(HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))))
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
forall a b. (a -> b) -> a -> b
$
HashMap (Column 'MSSQL) (UpdateOperator (UnpreparedValue 'MSSQL))
-> [UpdateOperator
'MSSQL m n (UpdateOperator (UnpreparedValue 'MSSQL))]
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n
(HashMap
(Column 'MSSQL) (UpdateOperator (UnpreparedValue 'MSSQL))))
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 'MSSQL -> UpdateOperator (UnpreparedValue 'MSSQL)
forall v. v -> UpdateOperator v
UpdateSet (UnpreparedValue 'MSSQL -> UpdateOperator (UnpreparedValue 'MSSQL))
-> HashMap ColumnName (UnpreparedValue 'MSSQL)
-> HashMap ColumnName (UpdateOperator (UnpreparedValue 'MSSQL))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdPermInfo 'MSSQL
-> HashMap (Column 'MSSQL) (UnpreparedValue 'MSSQL)
forall (b :: BackendType).
UpdPermInfo b -> HashMap (Column b) (UnpreparedValue b)
SU.presetColumns UpdPermInfo 'MSSQL
updatePerms)
[ UnpreparedValue 'MSSQL -> UpdateOperator (UnpreparedValue 'MSSQL)
forall v. v -> UpdateOperator v
UpdateSet (UnpreparedValue 'MSSQL -> UpdateOperator (UnpreparedValue 'MSSQL))
-> UpdateOperator 'MSSQL m n (UnpreparedValue 'MSSQL)
-> UpdateOperator
'MSSQL m n (UpdateOperator (UnpreparedValue 'MSSQL))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator 'MSSQL m n (UnpreparedValue 'MSSQL)
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 'MSSQL -> UpdateOperator (UnpreparedValue 'MSSQL)
forall v. v -> UpdateOperator v
UpdateInc (UnpreparedValue 'MSSQL -> UpdateOperator (UnpreparedValue 'MSSQL))
-> UpdateOperator 'MSSQL m n (UnpreparedValue 'MSSQL)
-> UpdateOperator
'MSSQL m n (UpdateOperator (UnpreparedValue 'MSSQL))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> UpdateOperator 'MSSQL m n (UnpreparedValue 'MSSQL)
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
]
TableInfo 'MSSQL
backendUpdateTableInfo
m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))])
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> MaybeT
m
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall a b. (a -> b) -> a -> b
$
(TableInfo 'MSSQL
-> m (InputFieldsParser
n (BackendUpdate 'MSSQL (UnpreparedValue 'MSSQL))))
-> MkRootFieldName
-> Scenario
-> SourceInfo 'MSSQL
-> TableName 'MSSQL
-> TableInfo 'MSSQL
-> GQLNameIdentifier
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
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 'MSSQL
-> m (InputFieldsParser
n (BackendUpdate 'MSSQL (UnpreparedValue 'MSSQL)))
TableInfo 'MSSQL
-> m (InputFieldsParser
MetadataObjId n (BackendUpdate (UnpreparedValue 'MSSQL)))
mkBackendUpdate
MkRootFieldName
mkRootFieldName
Scenario
scenario
SourceInfo 'MSSQL
sourceName
TableName 'MSSQL
tableName
TableInfo 'MSSQL
tableInfo
GQLNameIdentifier
gqlName
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))])
-> (Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))])
-> Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Monoid
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))] =>
Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold @Maybe @[_] (Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))])
-> Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
-> m [FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
forall a b. (a -> b) -> a -> b
$ Maybe
[FieldParser
n
(AnnotatedUpdateG
'MSSQL
(RemoteRelationshipField UnpreparedValue)
(UnpreparedValue 'MSSQL))]
fieldParsers
msTableArgs ::
forall r m n.
MonadBuildSchema 'MSSQL r m n =>
SourceInfo 'MSSQL ->
TableInfo 'MSSQL ->
m (InputFieldsParser n (IR.SelectArgsG 'MSSQL (UnpreparedValue 'MSSQL)))
msTableArgs :: SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (SelectArgsG 'MSSQL (UnpreparedValue 'MSSQL)))
msTableArgs SourceInfo 'MSSQL
sourceName TableInfo 'MSSQL
tableInfo = do
InputFieldsParser
n (Maybe (AnnBoolExp 'MSSQL (UnpreparedValue 'MSSQL)))
whereParser <- SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n (Maybe (AnnBoolExp 'MSSQL (UnpreparedValue 'MSSQL))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
(AggregationPredicatesSchema b, MonadBuildSchema b r m n) =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (AnnBoolExp b (UnpreparedValue b))))
tableWhereArg SourceInfo 'MSSQL
sourceName TableInfo 'MSSQL
tableInfo
InputFieldsParser
n
(Maybe
(NonEmpty (AnnotatedOrderByItemG 'MSSQL (UnpreparedValue 'MSSQL))))
orderByParser <- SourceInfo 'MSSQL
-> TableInfo 'MSSQL
-> m (InputFieldsParser
n
(Maybe
(NonEmpty
(AnnotatedOrderByItemG 'MSSQL (UnpreparedValue 'MSSQL)))))
forall (b :: BackendType) r (m :: * -> *) (n :: * -> *).
MonadBuildSchema b r m n =>
SourceInfo b
-> TableInfo b
-> m (InputFieldsParser
n (Maybe (NonEmpty (AnnotatedOrderByItemG b (UnpreparedValue b)))))
tableOrderByArg SourceInfo 'MSSQL
sourceName TableInfo 'MSSQL
tableInfo
pure do
Maybe (AnnBoolExp 'MSSQL (UnpreparedValue 'MSSQL))
whereArg <- InputFieldsParser
n (Maybe (AnnBoolExp 'MSSQL (UnpreparedValue 'MSSQL)))
whereParser
Maybe
(NonEmpty (AnnotatedOrderByItemG 'MSSQL (UnpreparedValue 'MSSQL)))
orderByArg <- InputFieldsParser
n
(Maybe
(NonEmpty (AnnotatedOrderByItemG 'MSSQL (UnpreparedValue 'MSSQL))))
orderByParser
Maybe Int
limitArg <- InputFieldsParser n (Maybe Int)
forall (n :: * -> *).
MonadParse n =>
InputFieldsParser n (Maybe Int)
tableLimitArg
Maybe Int64
offsetArg <- InputFieldsParser n (Maybe Int64)
forall (n :: * -> *).
MonadParse n =>
InputFieldsParser n (Maybe Int64)
tableOffsetArg
pure $
SelectArgs :: forall (b :: BackendType) v.
Maybe (AnnBoolExp b v)
-> Maybe (NonEmpty (AnnotatedOrderByItemG b v))
-> Maybe Int
-> Maybe Int64
-> Maybe (NonEmpty (Column b))
-> SelectArgsG b v
IR.SelectArgs
{ $sel:_saWhere:SelectArgs :: Maybe (AnnBoolExp 'MSSQL (UnpreparedValue 'MSSQL))
IR._saWhere = Maybe (AnnBoolExp 'MSSQL (UnpreparedValue 'MSSQL))
whereArg,
$sel:_saOrderBy:SelectArgs :: Maybe
(NonEmpty (AnnotatedOrderByItemG 'MSSQL (UnpreparedValue 'MSSQL)))
IR._saOrderBy = Maybe
(NonEmpty (AnnotatedOrderByItemG 'MSSQL (UnpreparedValue 'MSSQL)))
orderByArg,
$sel:_saLimit:SelectArgs :: Maybe Int
IR._saLimit = Maybe Int
limitArg,
$sel:_saOffset:SelectArgs :: Maybe Int64
IR._saOffset = Maybe Int64
offsetArg,
$sel:_saDistinct:SelectArgs :: Maybe (NonEmpty (Column 'MSSQL))
IR._saDistinct = Maybe (NonEmpty (Column 'MSSQL))
forall a. Maybe a
Nothing
}
msColumnParser ::
(MonadParse n, MonadError QErr m, MonadReader r m, Has MkTypename r, Has NamingCase r) =>
ColumnType 'MSSQL ->
G.Nullability ->
m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
msColumnParser :: ColumnType 'MSSQL
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
msColumnParser ColumnType 'MSSQL
columnType (G.Nullability Bool
isNullable) =
Parser 'Both n (ColumnValue 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
forall (m :: * -> *) a.
MonadParse m =>
Parser 'Both m a -> Parser 'Both m (ValueWithOrigin a)
peelWithOrigin (Parser 'Both n (ColumnValue 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
-> (Parser MetadataObjId 'Both n Value
-> Parser 'Both n (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n Value
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> ColumnValue 'MSSQL)
-> Parser MetadataObjId 'Both n Value
-> Parser 'Both n (ColumnValue 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ColumnType 'MSSQL -> ScalarValue 'MSSQL -> ColumnValue 'MSSQL
forall (b :: BackendType).
ColumnType b -> ScalarValue b -> ColumnValue b
ColumnValue ColumnType 'MSSQL
columnType) (Parser MetadataObjId 'Both n Value
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
-> m (Parser MetadataObjId 'Both n Value)
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ColumnType 'MSSQL
columnType of
ColumnScalar ScalarType 'MSSQL
scalarType ->
ScalarType
-> Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value
possiblyNullable ScalarType 'MSSQL
ScalarType
scalarType (Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value)
-> m (Parser MetadataObjId 'Both n Value)
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> case ScalarType 'MSSQL
scalarType of
ScalarType 'MSSQL
MSSQL.CharType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Text -> Value
mkCharValue (Text -> Value)
-> Parser MetadataObjId 'Both n Text
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
ScalarType 'MSSQL
MSSQL.VarcharType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Text -> Value
mkCharValue (Text -> Value)
-> Parser MetadataObjId 'Both n Text
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
ScalarType 'MSSQL
MSSQL.WcharType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Text -> Value
ODBC.TextValue (Text -> Value)
-> Parser MetadataObjId 'Both n Text
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
ScalarType 'MSSQL
MSSQL.WvarcharType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Text -> Value
ODBC.TextValue (Text -> Value)
-> Parser MetadataObjId 'Both n Text
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
ScalarType 'MSSQL
MSSQL.WtextType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Text -> Value
ODBC.TextValue (Text -> Value)
-> Parser MetadataObjId 'Both n Text
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
ScalarType 'MSSQL
MSSQL.TextType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Text -> Value
ODBC.TextValue (Text -> Value)
-> Parser MetadataObjId 'Both n Text
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Text
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Text
P.string
ScalarType 'MSSQL
MSSQL.IntegerType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Int -> Value
ODBC.IntValue (Int -> Value) -> (Int32 -> Int) -> Int32 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Value)
-> Parser MetadataObjId 'Both n Int32
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int
ScalarType 'MSSQL
MSSQL.SmallintType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Int -> Value
ODBC.IntValue (Int -> Value) -> (Int32 -> Int) -> Int32 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Value)
-> Parser MetadataObjId 'Both n Int32
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int
ScalarType 'MSSQL
MSSQL.BigintType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Int -> Value
ODBC.IntValue (Int -> Value) -> (Int32 -> Int) -> Int32 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Value)
-> Parser MetadataObjId 'Both n Int32
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int
ScalarType 'MSSQL
MSSQL.TinyintType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Int -> Value
ODBC.IntValue (Int -> Value) -> (Int32 -> Int) -> Int32 -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int32 -> Value)
-> Parser MetadataObjId 'Both n Int32
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Int32
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Int32
P.int
ScalarType 'MSSQL
MSSQL.NumericType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Double -> Value
ODBC.DoubleValue (Double -> Value)
-> Parser MetadataObjId 'Both n Double
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Double
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Double
P.float
ScalarType 'MSSQL
MSSQL.DecimalType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Double -> Value
ODBC.DoubleValue (Double -> Value)
-> Parser MetadataObjId 'Both n Double
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Double
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Double
P.float
ScalarType 'MSSQL
MSSQL.FloatType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Double -> Value
ODBC.DoubleValue (Double -> Value)
-> Parser MetadataObjId 'Both n Double
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Double
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Double
P.float
ScalarType 'MSSQL
MSSQL.RealType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Double -> Value
ODBC.DoubleValue (Double -> Value)
-> Parser MetadataObjId 'Both n Double
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Double
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Double
P.float
ScalarType 'MSSQL
MSSQL.BitType -> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
forall a b. (a -> b) -> a -> b
$ Bool -> Value
ODBC.BoolValue (Bool -> Value)
-> Parser MetadataObjId 'Both n Bool
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n Bool
forall (m :: * -> *) origin.
MonadParse m =>
Parser origin 'Both m Bool
P.boolean
ScalarType 'MSSQL
_ -> do
Name
name <- ScalarType -> m Name
forall (m :: * -> *). MonadError QErr m => ScalarType -> m Name
MSSQL.mkMSSQLScalarTypeName ScalarType 'MSSQL
ScalarType
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 Value
-> m (Parser MetadataObjId 'Both n Value)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value))
-> Parser MetadataObjId 'Both n Value
-> m (Parser MetadataObjId 'Both n Value)
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 Value
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 Value) -> InputValue Variable -> n Value
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (QErr -> n Value)
-> (Value -> n Value) -> Either QErr Value -> n Value
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (ParseErrorCode -> ErrorMessage -> n Value
forall (m :: * -> *) a.
MonadParse m =>
ParseErrorCode -> ErrorMessage -> m a
P.parseErrorWith ParseErrorCode
P.ParseFailed (ErrorMessage -> n Value)
-> (QErr -> ErrorMessage) -> QErr -> n Value
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) Value -> n Value
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either QErr Value -> n Value)
-> (Value -> Either QErr Value) -> Value -> n Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScalarType -> Value -> Either QErr Value
MSSQL.parseScalarValue ScalarType 'MSSQL
ScalarType
scalarType)
}
ColumnEnumReference enumRef :: EnumReference 'MSSQL
enumRef@(EnumReference TableName 'MSSQL
_ EnumValues
enumValues Maybe Name
_) ->
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
Name
enumName <- EnumReference 'MSSQL -> m Name
forall (b :: BackendType) (m :: * -> *) r.
(Backend b, MonadReader r m, Has MkTypename r, MonadError QErr m,
Has NamingCase r) =>
EnumReference b -> m Name
mkEnumTypeName EnumReference 'MSSQL
enumRef
pure $ ScalarType
-> Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value
possiblyNullable ScalarType
MSSQL.VarcharType (Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value)
-> Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value
forall a b. (a -> b) -> a -> b
$ Name
-> Maybe Description
-> NonEmpty (Definition EnumValueInfo, Value)
-> Parser MetadataObjId 'Both n Value
forall (m :: * -> *) origin a.
MonadParse m =>
Name
-> Maybe Description
-> NonEmpty (Definition origin EnumValueInfo, a)
-> Parser origin 'Both m a
P.enum Name
enumName Maybe Description
forall a. Maybe a
Nothing ((EnumValue, EnumValueInfo) -> (Definition EnumValueInfo, Value)
(EnumValue, EnumValueInfo)
-> (Definition EnumValueInfo, ScalarValue 'MSSQL)
mkEnumValue ((EnumValue, EnumValueInfo) -> (Definition EnumValueInfo, Value))
-> NonEmpty (EnumValue, EnumValueInfo)
-> NonEmpty (Definition EnumValueInfo, Value)
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 Value)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
ValidationFailed Text
"empty enum values"
where
possiblyNullable :: ScalarType
-> Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value
possiblyNullable ScalarType
_scalarType
| Bool
isNullable = (Maybe Value -> Value)
-> Parser MetadataObjId 'Both n (Maybe Value)
-> Parser MetadataObjId 'Both n Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
ODBC.NullValue) (Parser MetadataObjId 'Both n (Maybe Value)
-> Parser MetadataObjId 'Both n Value)
-> (Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n (Maybe Value))
-> Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser MetadataObjId 'Both n Value
-> Parser MetadataObjId 'Both n (Maybe Value)
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 Value
-> Parser MetadataObjId 'Both n Value
forall a. a -> a
id
mkEnumValue :: (EnumValue, EnumValueInfo) -> (P.Definition P.EnumValueInfo, ScalarValue 'MSSQL)
mkEnumValue :: (EnumValue, EnumValueInfo)
-> (Definition EnumValueInfo, ScalarValue 'MSSQL)
mkEnumValue (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 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 -> Value
ODBC.TextValue (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Name -> Text
G.unName Name
value
)
mkCharValue :: Text -> ODBC.Value
mkCharValue :: Text -> Value
mkCharValue Text
txt =
if (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
Char.isAscii Text
txt
then ByteString -> Value
ODBC.ByteStringValue (Text -> ByteString
TE.encodeUtf8 Text
txt)
else Text -> Value
ODBC.TextValue Text
txt
msOrderByOperators ::
NamingCase ->
( G.Name,
NonEmpty
( P.Definition P.EnumValueInfo,
(BasicOrderType 'MSSQL, NullsOrderType 'MSSQL)
)
)
msOrderByOperators :: NamingCase
-> (Name,
NonEmpty
(Definition EnumValueInfo,
(BasicOrderType 'MSSQL, NullsOrderType 'MSSQL)))
msOrderByOperators NamingCase
_tCase =
(Name
Name._order_by,) (NonEmpty (Definition EnumValueInfo, (Order, NullsOrder))
-> (Name,
NonEmpty (Definition EnumValueInfo, (Order, NullsOrder))))
-> NonEmpty (Definition EnumValueInfo, (Order, NullsOrder))
-> (Name, NonEmpty (Definition EnumValueInfo, (Order, NullsOrder)))
forall a b. (a -> b) -> a -> b
$
[(Definition EnumValueInfo, (Order, NullsOrder))]
-> NonEmpty (Definition EnumValueInfo, (Order, NullsOrder))
forall a. [a] -> NonEmpty a
NE.fromList
[ ( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define Name
Name._asc Description
"in ascending order, nulls first",
(Order
MSSQL.AscOrder, NullsOrder
MSSQL.NullsFirst)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define Name
Name._asc_nulls_first Description
"in ascending order, nulls first",
(Order
MSSQL.AscOrder, NullsOrder
MSSQL.NullsFirst)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define Name
Name._asc_nulls_last Description
"in ascending order, nulls last",
(Order
MSSQL.AscOrder, NullsOrder
MSSQL.NullsLast)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define Name
Name._desc Description
"in descending order, nulls last",
(Order
MSSQL.DescOrder, NullsOrder
MSSQL.NullsLast)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define Name
Name._desc_nulls_first Description
"in descending order, nulls first",
(Order
MSSQL.DescOrder, NullsOrder
MSSQL.NullsFirst)
),
( Name -> Description -> Definition EnumValueInfo
forall origin.
Name -> Description -> Definition origin EnumValueInfo
define Name
Name._desc_nulls_last Description
"in descending order, nulls last",
(Order
MSSQL.DescOrder, NullsOrder
MSSQL.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
msComparisonExps ::
forall m n r.
( BackendSchema 'MSSQL,
MonadMemoize m,
MonadParse n,
MonadError QErr m,
MonadReader r m,
Has SchemaOptions r,
Has MkTypename r,
Has NamingCase r
) =>
ColumnType 'MSSQL ->
m (Parser 'Input n [ComparisonExp 'MSSQL])
msComparisonExps :: ColumnType 'MSSQL -> m (Parser 'Input n [ComparisonExp 'MSSQL])
msComparisonExps = Name
-> (ColumnType 'MSSQL
-> m (Parser 'Input n [ComparisonExp 'MSSQL]))
-> ColumnType 'MSSQL
-> m (Parser 'Input n [ComparisonExp 'MSSQL])
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)
P.memoize 'comparisonExps \ColumnType 'MSSQL
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 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser <- ColumnType 'MSSQL
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)))
forall (b :: BackendType) (n :: * -> *) (m :: * -> *) r.
(BackendSchema b, MonadParse n, MonadError QErr m, MonadReader r m,
Has MkTypename r, Has NamingCase r) =>
ColumnType b
-> Nullability
-> m (Parser 'Both n (ValueWithOrigin (ColumnValue b)))
columnParser ColumnType 'MSSQL
columnType (Bool -> Nullability
G.Nullability Bool
False)
let columnListParser :: Parser MetadataObjId 'Both n [ColumnValue 'MSSQL]
columnListParser = (ValueWithOrigin (ColumnValue 'MSSQL) -> ColumnValue 'MSSQL)
-> [ValueWithOrigin (ColumnValue 'MSSQL)] -> [ColumnValue 'MSSQL]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ValueWithOrigin (ColumnValue 'MSSQL) -> ColumnValue 'MSSQL
forall a. ValueWithOrigin a -> a
openValueOrigin ([ValueWithOrigin (ColumnValue 'MSSQL)] -> [ColumnValue 'MSSQL])
-> Parser
MetadataObjId 'Both n [ValueWithOrigin (ColumnValue 'MSSQL)]
-> Parser MetadataObjId 'Both n [ColumnValue 'MSSQL]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser
MetadataObjId 'Both n [ValueWithOrigin (ColumnValue 'MSSQL)]
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 'MSSQL))
typedParser
let name :: Name
name = Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL)) -> Name
forall a. HasName a => a -> Name
P.getName Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser Name -> Name -> Name
forall a. Semigroup a => a -> a -> a
<> Name
Name.__MSSQL_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 'MSSQL)) -> Name
forall a. HasName a => a -> Name
P.getName Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser
Name -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
". All fields are combined with logical 'AND'."
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
pure $
Name
-> Maybe Description
-> InputFieldsParser MetadataObjId n [ComparisonExp 'MSSQL]
-> Parser 'Input n [ComparisonExp 'MSSQL]
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 'MSSQL]
-> Parser 'Input n [ComparisonExp 'MSSQL])
-> InputFieldsParser MetadataObjId n [ComparisonExp 'MSSQL]
-> Parser 'Input n [ComparisonExp 'MSSQL]
forall a b. (a -> b) -> a -> b
$
([Maybe (ComparisonExp 'MSSQL)] -> [ComparisonExp 'MSSQL])
-> InputFieldsParser MetadataObjId n [Maybe (ComparisonExp 'MSSQL)]
-> InputFieldsParser MetadataObjId n [ComparisonExp 'MSSQL]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Maybe (ComparisonExp 'MSSQL)] -> [ComparisonExp 'MSSQL]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes (InputFieldsParser MetadataObjId n [Maybe (ComparisonExp 'MSSQL)]
-> InputFieldsParser MetadataObjId n [ComparisonExp 'MSSQL])
-> InputFieldsParser MetadataObjId n [Maybe (ComparisonExp 'MSSQL)]
-> InputFieldsParser MetadataObjId n [ComparisonExp 'MSSQL]
forall a b. (a -> b) -> a -> b
$
[InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
-> InputFieldsParser MetadataObjId n [Maybe (ComparisonExp 'MSSQL)]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA ([InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
-> InputFieldsParser
MetadataObjId n [Maybe (ComparisonExp 'MSSQL)])
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
-> InputFieldsParser MetadataObjId n [Maybe (ComparisonExp 'MSSQL)]
forall a b. (a -> b) -> a -> b
$
[[InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[
NamingCase
-> DangerouslyCollapseBooleans
-> Parser 'Both n (UnpreparedValue 'MSSQL)
-> Parser 'Both n (UnpreparedValue 'MSSQL)
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
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 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser 'Both n (UnpreparedValue 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser)
([ColumnValue 'MSSQL] -> UnpreparedValue 'MSSQL
mkListLiteral ([ColumnValue 'MSSQL] -> UnpreparedValue 'MSSQL)
-> Parser MetadataObjId 'Both n [ColumnValue 'MSSQL]
-> Parser 'Both n (UnpreparedValue 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetadataObjId 'Both n [ColumnValue 'MSSQL]
columnListParser),
NamingCase
-> DangerouslyCollapseBooleans
-> Parser 'Both n (UnpreparedValue 'MSSQL)
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
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 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser 'Both n (UnpreparedValue 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType 'MSSQL -> Bool) -> ColumnType 'MSSQL -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (ScalarType -> [ScalarType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ScalarType]
MSSQL.stringTypes) ColumnType 'MSSQL
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__like
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column match the given pattern")
(UnpreparedValue 'MSSQL -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
field -> OpExpG backend field
ALIKE (UnpreparedValue 'MSSQL -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__nlike
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column NOT match the given pattern")
(UnpreparedValue 'MSSQL -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
field -> OpExpG backend field
ANLIKE (UnpreparedValue 'MSSQL -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType 'MSSQL -> Bool) -> ColumnType 'MSSQL -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (ScalarType -> [ScalarType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ScalarType]
MSSQL.geoTypes) ColumnType 'MSSQL
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_contains
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column contain the given value")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTContains (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_equals
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column equal to given value (directionality is ignored)")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTEquals (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_intersects
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column spatially intersect the given value")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTIntersects (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_overlaps
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column 'spatially overlap' (intersect but not completely contain) the given value")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTOverlaps (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_within
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"is the column contained in the given value")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTWithin (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser)
],
Bool -> [()]
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((ScalarType 'MSSQL -> Bool) -> ColumnType 'MSSQL -> Bool
forall (b :: BackendType).
(ScalarType b -> Bool) -> ColumnType b -> Bool
isScalarColumnWhere (ScalarType
MSSQL.GeometryType ScalarType -> ScalarType -> Bool
forall a. Eq a => a -> a -> Bool
==) ColumnType 'MSSQL
columnType)
[()]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
-> [InputFieldsParser
MetadataObjId n (Maybe (ComparisonExp 'MSSQL))]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> [ Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_crosses
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column cross the given geometry value")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTCrosses (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser),
Name
-> Maybe Description
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
-> InputFieldsParser MetadataObjId n (Maybe (ComparisonExp 'MSSQL))
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.__st_touches
(Description -> Maybe Description
forall a. a -> Maybe a
Just Description
"does the column have at least one point in common with the given geometry value")
(BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL
forall (backend :: BackendType) field.
BooleanOperators backend field -> OpExpG backend field
ABackendSpecific (BooleanOperators (UnpreparedValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> (ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> ComparisonExp 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnpreparedValue 'MSSQL -> BooleanOperators (UnpreparedValue 'MSSQL)
forall a. a -> BooleanOperators a
MSSQL.ASTTouches (UnpreparedValue 'MSSQL
-> BooleanOperators (UnpreparedValue 'MSSQL))
-> (ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL)
-> ValueWithOrigin (ColumnValue 'MSSQL)
-> BooleanOperators (UnpreparedValue 'MSSQL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueWithOrigin (ColumnValue 'MSSQL) -> UnpreparedValue 'MSSQL
forall (b :: BackendType).
ValueWithOrigin (ColumnValue b) -> UnpreparedValue b
mkParameter (ValueWithOrigin (ColumnValue 'MSSQL) -> ComparisonExp 'MSSQL)
-> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
-> Parser MetadataObjId 'Both n (ComparisonExp 'MSSQL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser 'Both n (ValueWithOrigin (ColumnValue 'MSSQL))
typedParser)
]
]
where
mkListLiteral :: [ColumnValue 'MSSQL] -> UnpreparedValue 'MSSQL
mkListLiteral :: [ColumnValue 'MSSQL] -> UnpreparedValue 'MSSQL
mkListLiteral =
Expression -> UnpreparedValue 'MSSQL
forall (b :: BackendType). SQLExpression b -> UnpreparedValue b
UVLiteral (Expression -> UnpreparedValue 'MSSQL)
-> ([ColumnValue 'MSSQL] -> Expression)
-> [ColumnValue 'MSSQL]
-> UnpreparedValue 'MSSQL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Expression] -> Expression
MSSQL.ListExpression ([Expression] -> Expression)
-> ([ColumnValue 'MSSQL] -> [Expression])
-> [ColumnValue 'MSSQL]
-> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ColumnValue 'MSSQL -> Expression)
-> [ColumnValue 'MSSQL] -> [Expression]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Value -> Expression
MSSQL.ValueExpression (Value -> Expression)
-> (ColumnValue 'MSSQL -> Value)
-> ColumnValue 'MSSQL
-> Expression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnValue 'MSSQL -> Value
forall (b :: BackendType). ColumnValue b -> ScalarValue b
cvValue)
msCountTypeInput ::
MonadParse n =>
Maybe (Parser 'Both n (Column 'MSSQL)) ->
InputFieldsParser n (IR.CountDistinct -> CountType 'MSSQL)
msCountTypeInput :: Maybe (Parser 'Both n (Column 'MSSQL))
-> InputFieldsParser n (CountDistinct -> CountType 'MSSQL)
msCountTypeInput = \case
Just Parser 'Both n (Column 'MSSQL)
columnEnum -> do
Maybe ColumnName
column <- Name
-> Maybe Description
-> Parser MetadataObjId 'Both n ColumnName
-> InputFieldsParser MetadataObjId n (Maybe ColumnName)
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._column Maybe Description
forall a. Maybe a
Nothing Parser 'Both n (Column 'MSSQL)
Parser MetadataObjId 'Both n ColumnName
columnEnum
pure $ (CountDistinct -> Maybe ColumnName -> Countable ColumnName)
-> Maybe ColumnName -> CountDistinct -> Countable ColumnName
forall a b c. (a -> b -> c) -> b -> a -> c
flip CountDistinct -> Maybe (Column 'MSSQL) -> CountType 'MSSQL
CountDistinct -> Maybe ColumnName -> Countable ColumnName
mkCountType Maybe ColumnName
column
Maybe (Parser 'Both n (Column 'MSSQL))
Nothing -> (CountDistinct -> Countable ColumnName)
-> InputFieldsParser
MetadataObjId n (CountDistinct -> Countable ColumnName)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((CountDistinct -> Countable ColumnName)
-> InputFieldsParser
MetadataObjId n (CountDistinct -> Countable ColumnName))
-> (CountDistinct -> Countable ColumnName)
-> InputFieldsParser
MetadataObjId n (CountDistinct -> Countable ColumnName)
forall a b. (a -> b) -> a -> b
$ (CountDistinct -> Maybe ColumnName -> Countable ColumnName)
-> Maybe ColumnName -> CountDistinct -> Countable ColumnName
forall a b c. (a -> b -> c) -> b -> a -> c
flip CountDistinct -> Maybe (Column 'MSSQL) -> CountType 'MSSQL
CountDistinct -> Maybe ColumnName -> Countable ColumnName
mkCountType Maybe ColumnName
forall a. Maybe a
Nothing
where
mkCountType :: IR.CountDistinct -> Maybe (Column 'MSSQL) -> CountType 'MSSQL
mkCountType :: CountDistinct -> Maybe (Column 'MSSQL) -> CountType 'MSSQL
mkCountType CountDistinct
_ Maybe (Column 'MSSQL)
Nothing = CountType 'MSSQL
forall name. Countable name
MSSQL.StarCountable
mkCountType CountDistinct
IR.SelectCountDistinct (Just Column 'MSSQL
col) = ColumnName -> Countable ColumnName
forall name. name -> Countable name
MSSQL.DistinctCountable Column 'MSSQL
ColumnName
col
mkCountType CountDistinct
IR.SelectCountNonDistinct (Just Column 'MSSQL
col) = ColumnName -> Countable ColumnName
forall name. name -> Countable name
MSSQL.NonNullFieldCountable Column 'MSSQL
ColumnName
col