Inline a whole bunch of nothing for BackendSchema

This makes it easier to refactor `BackendSchema`, because if the type of a type class method is changed, it's easier to update the corresponding dummy implementations.

Partially addresses hasura/graphql-engine-mono#2971, in the sense that this aids refactors.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5443
GitOrigin-RevId: 65e169d01415a04e7c419a628cf32e743448543d
This commit is contained in:
Auke Booij 2022-08-11 13:57:06 +02:00 committed by hasura-bot
parent c41fbfbb49
commit 4d5ee4c17e
3 changed files with 33 additions and 322 deletions

View File

@ -44,7 +44,6 @@ import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Function import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Source (SourceInfo) import Hasura.RQL.Types.Source (SourceInfo)
import Hasura.RQL.Types.SourceCustomization (MkRootFieldName)
import Hasura.RQL.Types.Table import Hasura.RQL.Types.Table
import Hasura.SQL.Backend import Hasura.SQL.Backend
import Language.GraphQL.Draft.Syntax qualified as G import Language.GraphQL.Draft.Syntax qualified as G
@ -55,14 +54,14 @@ import Language.GraphQL.Draft.Syntax qualified as G
instance BackendSchema 'BigQuery where instance BackendSchema 'BigQuery where
-- top level parsers -- top level parsers
buildTableQueryAndSubscriptionFields = GSB.buildTableQueryAndSubscriptionFields buildTableQueryAndSubscriptionFields = GSB.buildTableQueryAndSubscriptionFields
buildTableRelayQueryFields = bqBuildTableRelayQueryFields buildTableRelayQueryFields _ _ _ _ _ _ = pure []
buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields = bqBuildTableInsertMutationFields buildTableInsertMutationFields _ _ _ _ _ _ = pure []
buildTableUpdateMutationFields = bqBuildTableUpdateMutationFields buildTableUpdateMutationFields _ _ _ _ _ _ = pure []
buildTableDeleteMutationFields = bqBuildTableDeleteMutationFields buildTableDeleteMutationFields _ _ _ _ _ _ = pure []
buildFunctionQueryFields = bqBuildFunctionQueryFields buildFunctionQueryFields _ _ _ _ _ = pure []
buildFunctionRelayQueryFields = bqBuildFunctionRelayQueryFields buildFunctionRelayQueryFields _ _ _ _ _ _ = pure []
buildFunctionMutationFields = bqBuildFunctionMutationFields buildFunctionMutationFields _ _ _ _ _ = pure []
-- backend extensions -- backend extensions
relayExtension = Nothing relayExtension = Nothing
@ -71,7 +70,7 @@ instance BackendSchema 'BigQuery where
-- individual components -- individual components
columnParser = bqColumnParser columnParser = bqColumnParser
scalarSelectionArgumentsParser = bqScalarSelectionArgumentsParser scalarSelectionArgumentsParser _ = pure Nothing
orderByOperators _sourceInfo = bqOrderByOperators orderByOperators _sourceInfo = bqOrderByOperators
comparisonExps = bqComparisonExps comparisonExps = bqComparisonExps
countTypeInput = bqCountTypeInput countTypeInput = bqCountTypeInput
@ -84,91 +83,6 @@ instance BackendTableSelectSchema 'BigQuery where
selectTableAggregate = defaultSelectTableAggregate selectTableAggregate = defaultSelectTableAggregate
tableSelectionSet = defaultTableSelectionSet tableSelectionSet = defaultTableSelectionSet
----------------------------------------------------------------
-- Top level parsers
bqBuildTableRelayQueryFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
SourceInfo 'BigQuery ->
TableName 'BigQuery ->
TableInfo 'BigQuery ->
C.GQLNameIdentifier ->
NESeq (ColumnInfo 'BigQuery) ->
m [P.FieldParser n a]
bqBuildTableRelayQueryFields _mkRootFieldName _sourceName _tableName _tableInfo _gqlName _pkeyColumns =
pure []
bqBuildTableInsertMutationFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
Scenario ->
SourceInfo 'BigQuery ->
TableName 'BigQuery ->
TableInfo 'BigQuery ->
C.GQLNameIdentifier ->
m [P.FieldParser n a]
bqBuildTableInsertMutationFields _mkRootFieldName _scenario _sourceName _tableName _tableInfo _gqlName =
pure []
bqBuildTableUpdateMutationFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
Scenario ->
SourceInfo 'BigQuery ->
TableName 'BigQuery ->
TableInfo 'BigQuery ->
C.GQLNameIdentifier ->
m [P.FieldParser n a]
bqBuildTableUpdateMutationFields _mkRootFieldName _scenario _sourceName _tableName _tableInfo _gqlName =
pure []
bqBuildTableDeleteMutationFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
Scenario ->
SourceInfo 'BigQuery ->
TableName 'BigQuery ->
TableInfo 'BigQuery ->
C.GQLNameIdentifier ->
m [P.FieldParser n a]
bqBuildTableDeleteMutationFields _mkRootFieldName _scenario _sourceName _tableName _tableInfo _gqlName =
pure []
bqBuildFunctionQueryFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
SourceInfo 'BigQuery ->
FunctionName 'BigQuery ->
FunctionInfo 'BigQuery ->
TableName 'BigQuery ->
m [P.FieldParser n a]
bqBuildFunctionQueryFields _ _ _ _ _ =
pure []
bqBuildFunctionRelayQueryFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
SourceInfo 'BigQuery ->
FunctionName 'BigQuery ->
FunctionInfo 'BigQuery ->
TableName 'BigQuery ->
NESeq (ColumnInfo 'BigQuery) ->
m [P.FieldParser n a]
bqBuildFunctionRelayQueryFields _mkRootFieldName _sourceName _functionName _functionInfo _tableName _pkeyColumns =
pure []
bqBuildFunctionMutationFields ::
MonadBuildSchema 'BigQuery r m n =>
MkRootFieldName ->
SourceInfo 'BigQuery ->
FunctionName 'BigQuery ->
FunctionInfo 'BigQuery ->
TableName 'BigQuery ->
m [P.FieldParser n a]
bqBuildFunctionMutationFields _ _ _ _ _ =
pure []
---------------------------------------------------------------- ----------------------------------------------------------------
-- Individual components -- Individual components
@ -231,12 +145,6 @@ bqColumnParser columnType (G.Nullability isNullable) =
stringBased scalarName = stringBased scalarName =
P.string {P.pType = P.TNamed P.NonNullable $ P.Definition scalarName Nothing Nothing [] P.TIScalar} P.string {P.pType = P.TNamed P.NonNullable $ P.Definition scalarName Nothing Nothing [] P.TIScalar}
bqScalarSelectionArgumentsParser ::
MonadParse n =>
ColumnType 'BigQuery ->
InputFieldsParser n (Maybe (ScalarSelectionArguments 'BigQuery))
bqScalarSelectionArgumentsParser _columnType = pure Nothing
bqOrderByOperators :: bqOrderByOperators ::
NamingCase -> NamingCase ->
( G.Name, ( G.Name,
@ -524,14 +432,3 @@ bqComputedField sourceName ComputedFieldInfo {..} tableName tableInfo = runMaybe
fieldName <- textToName argumentName fieldName <- textToName argumentName
let argParser = P.field fieldName Nothing typedParser let argParser = P.field fieldName Nothing typedParser
pure $ argParser `P.bindFields` \inputValue -> pure ((argumentName, BigQuery.AEInput $ IR.mkParameter inputValue)) pure $ argParser `P.bindFields` \inputValue -> pure ((argumentName, BigQuery.AEInput $ IR.mkParameter inputValue))
{-
NOTE: Unused. Should we remove?
-- | Remote join field parser.
-- Currently unsupported: returns Nothing for now.
bqRemoteRelationshipField ::
MonadBuildSchema 'BigQuery r m n =>
RemoteFieldInfo (DBJoinField 'BigQuery) ->
m (Maybe [FieldParser n (AnnotatedField 'BigQuery)])
bqRemoteRelationshipField _remoteFieldInfo = pure Nothing
-}

View File

@ -41,13 +41,9 @@ import Hasura.GraphQL.Schema.Update qualified as SU
import Hasura.Name qualified as Name import Hasura.Name qualified as Name
import Hasura.Prelude import Hasura.Prelude
import Hasura.RQL.IR import Hasura.RQL.IR
import Hasura.RQL.IR.Insert qualified as IR
import Hasura.RQL.IR.Select qualified as IR import Hasura.RQL.IR.Select qualified as IR
import Hasura.RQL.Types.Backend hiding (BackendInsert) import Hasura.RQL.Types.Backend hiding (BackendInsert)
import Hasura.RQL.Types.Column import Hasura.RQL.Types.Column
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.Relationships.Local
import Hasura.RQL.Types.SchemaCache import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.Source import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization (MkRootFieldName (..)) import Hasura.RQL.Types.SourceCustomization (MkRootFieldName (..))
@ -62,31 +58,41 @@ import Language.GraphQL.Draft.Syntax qualified as G
instance BackendSchema 'MSSQL where instance BackendSchema 'MSSQL where
-- top level parsers -- top level parsers
buildTableQueryAndSubscriptionFields = GSB.buildTableQueryAndSubscriptionFields buildTableQueryAndSubscriptionFields = GSB.buildTableQueryAndSubscriptionFields
buildTableRelayQueryFields = msBuildTableRelayQueryFields buildTableRelayQueryFields _ _ _ _ _ _ = pure []
buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields = GSB.buildTableInsertMutationFields backendInsertParser buildTableInsertMutationFields = GSB.buildTableInsertMutationFields backendInsertParser
buildTableDeleteMutationFields = GSB.buildTableDeleteMutationFields buildTableDeleteMutationFields = GSB.buildTableDeleteMutationFields
buildTableUpdateMutationFields = msBuildTableUpdateMutationFields buildTableUpdateMutationFields = msBuildTableUpdateMutationFields
buildFunctionQueryFields = msBuildFunctionQueryFields buildFunctionQueryFields _ _ _ _ _ = pure []
buildFunctionRelayQueryFields = msBuildFunctionRelayQueryFields buildFunctionRelayQueryFields _ _ _ _ _ _ = pure []
buildFunctionMutationFields = msBuildFunctionMutationFields buildFunctionMutationFields _ _ _ _ _ = pure []
-- backend extensions -- backend extensions
relayExtension = Nothing relayExtension = Nothing
nodesAggExtension = Just () nodesAggExtension = Just ()
streamSubscriptionExtension = Nothing streamSubscriptionExtension = Nothing
mkRelationshipParser = msMkRelationshipParser -- When we support nested inserts, we also need to ensure we limit ourselves
-- to inserting into tables whch supports inserts:
{-
import Hasura.GraphQL.Schema.Mutation qualified as GSB
runMaybeT $ do
let otherTableName = riRTable relationshipInfo
otherTableInfo <- lift $ askTableInfo sourceName otherTableName
guard (supportsInserts otherTableInfo)
-}
mkRelationshipParser _ _ = pure Nothing
-- individual components -- individual components
columnParser = msColumnParser columnParser = msColumnParser
scalarSelectionArgumentsParser = msScalarSelectionArgumentsParser scalarSelectionArgumentsParser _ = pure Nothing
orderByOperators _sourceInfo = msOrderByOperators orderByOperators _sourceInfo = msOrderByOperators
comparisonExps = msComparisonExps comparisonExps = msComparisonExps
countTypeInput = msCountTypeInput countTypeInput = msCountTypeInput
aggregateOrderByCountType = MSSQL.IntegerType aggregateOrderByCountType = MSSQL.IntegerType
computedField = msComputedField computedField _ _ _ _ = pure Nothing
instance BackendTableSelectSchema 'MSSQL where instance BackendTableSelectSchema 'MSSQL where
tableArguments = msTableArgs tableArguments = msTableArgs
@ -98,18 +104,6 @@ instance BackendTableSelectSchema 'MSSQL where
-- * Top level parsers -- * Top level parsers
msBuildTableRelayQueryFields ::
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName ->
SourceInfo 'MSSQL ->
TableName 'MSSQL ->
TableInfo 'MSSQL ->
C.GQLNameIdentifier ->
NESeq (ColumnInfo 'MSSQL) ->
m [P.FieldParser n a]
msBuildTableRelayQueryFields _mkRootFieldName _sourceName _tableName _tableInfo _gqlName _pkeyColumns =
pure []
backendInsertParser :: backendInsertParser ::
forall m r n. forall m r n.
MonadBuildSchema 'MSSQL r m n => MonadBuildSchema 'MSSQL r m n =>
@ -155,40 +149,6 @@ msBuildTableUpdateMutationFields mkRootFieldName scenario sourceName tableName t
gqlName gqlName
pure . fold @Maybe @[_] $ fieldParsers pure . fold @Maybe @[_] $ fieldParsers
msBuildFunctionQueryFields ::
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName ->
SourceInfo 'MSSQL ->
FunctionName 'MSSQL ->
FunctionInfo 'MSSQL ->
TableName 'MSSQL ->
m [P.FieldParser n a]
msBuildFunctionQueryFields _ _ _ _ _ =
pure []
msBuildFunctionRelayQueryFields ::
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName ->
SourceInfo 'MSSQL ->
FunctionName 'MSSQL ->
FunctionInfo 'MSSQL ->
TableName 'MSSQL ->
NESeq (ColumnInfo 'MSSQL) ->
m [P.FieldParser n a]
msBuildFunctionRelayQueryFields _mkRootFieldName _sourceName _functionName _functionInfo _tableName _pkeyColumns =
pure []
msBuildFunctionMutationFields ::
MonadBuildSchema 'MSSQL r m n =>
MkRootFieldName ->
SourceInfo 'MSSQL ->
FunctionName 'MSSQL ->
FunctionInfo 'MSSQL ->
TableName 'MSSQL ->
m [P.FieldParser n a]
msBuildFunctionMutationFields _ _ _ _ _ =
pure []
---------------------------------------------------------------- ----------------------------------------------------------------
-- * Table arguments -- * Table arguments
@ -217,25 +177,6 @@ msTableArgs sourceName tableInfo = do
IR._saDistinct = Nothing IR._saDistinct = Nothing
} }
msMkRelationshipParser ::
forall r m n.
MonadBuildSchema 'MSSQL r m n =>
SourceInfo 'MSSQL ->
RelInfo 'MSSQL ->
m (Maybe (InputFieldsParser n (Maybe (IR.AnnotatedInsertField 'MSSQL (UnpreparedValue 'MSSQL)))))
msMkRelationshipParser _sourceName _relationshipInfo = do
-- When we support nested inserts, we also need to ensure we limit ourselves
-- to inserting into tables whch supports inserts:
{-
import Hasura.GraphQL.Schema.Mutation qualified as GSB
runMaybeT $ do
let otherTableName = riRTable relationshipInfo
otherTableInfo <- lift $ askTableInfo sourceName otherTableName
guard (supportsInserts otherTableInfo)
-}
return Nothing
---------------------------------------------------------------- ----------------------------------------------------------------
-- * Individual components -- * Individual components
@ -297,12 +238,6 @@ msColumnParser columnType (G.Nullability isNullable) =
ODBC.TextValue $ G.unName value ODBC.TextValue $ G.unName value
) )
msScalarSelectionArgumentsParser ::
MonadParse n =>
ColumnType 'MSSQL ->
InputFieldsParser n (Maybe (ScalarSelectionArguments 'MSSQL))
msScalarSelectionArgumentsParser _columnType = pure Nothing
msOrderByOperators :: msOrderByOperators ::
NamingCase -> NamingCase ->
( G.Name, ( G.Name,
@ -449,26 +384,3 @@ msCountTypeInput = \case
mkCountType _ Nothing = MSSQL.StarCountable mkCountType _ Nothing = MSSQL.StarCountable
mkCountType IR.SelectCountDistinct (Just col) = MSSQL.DistinctCountable col mkCountType IR.SelectCountDistinct (Just col) = MSSQL.DistinctCountable col
mkCountType IR.SelectCountNonDistinct (Just col) = MSSQL.NonNullFieldCountable col mkCountType IR.SelectCountNonDistinct (Just col) = MSSQL.NonNullFieldCountable col
-- | Computed field parser.
-- Currently unsupported: returns Nothing for now.
msComputedField ::
MonadBuildSchema 'MSSQL r m n =>
SourceInfo 'MSSQL ->
ComputedFieldInfo 'MSSQL ->
TableName 'MSSQL ->
TableInfo 'MSSQL ->
m (Maybe (FieldParser n (AnnotatedField 'MSSQL)))
msComputedField _sourceName _fieldInfo _table _tableInfo = pure Nothing
{-
NOTE: Unused, should we remove?
-- | Remote join field parser.
-- Currently unsupported: returns Nothing for now.
msRemoteRelationshipField ::
MonadBuildSchema 'MSSQL r m n =>
RemoteFieldInfo (DBJoinField 'MSSQL) ->
m (Maybe [FieldParser n (AnnotatedField 'MSSQL)])
msRemoteRelationshipField _remoteFieldInfo = pure Nothing
-}

View File

@ -8,7 +8,6 @@ import Data.ByteString (ByteString)
import Data.Has import Data.Has
import Data.HashMap.Strict qualified as HM import Data.HashMap.Strict qualified as HM
import Data.List.NonEmpty qualified as NE import Data.List.NonEmpty qualified as NE
import Data.Text.Casing qualified as C
import Data.Text.Encoding (encodeUtf8) import Data.Text.Encoding (encodeUtf8)
import Data.Text.Extended import Data.Text.Extended
import Database.MySQL.Base.Types qualified as MySQL import Database.MySQL.Base.Types qualified as MySQL
@ -35,28 +34,26 @@ import Hasura.RQL.IR
import Hasura.RQL.IR.Select qualified as IR import Hasura.RQL.IR.Select qualified as IR
import Hasura.RQL.Types.Backend as RQL import Hasura.RQL.Types.Backend as RQL
import Hasura.RQL.Types.Column as RQL import Hasura.RQL.Types.Column as RQL
import Hasura.RQL.Types.Function as RQL
import Hasura.RQL.Types.SchemaCache as RQL import Hasura.RQL.Types.SchemaCache as RQL
import Hasura.RQL.Types.Source as RQL import Hasura.RQL.Types.Source as RQL
import Hasura.RQL.Types.SourceCustomization as RQL
import Hasura.SQL.Backend import Hasura.SQL.Backend
import Language.GraphQL.Draft.Syntax qualified as GQL import Language.GraphQL.Draft.Syntax qualified as GQL
instance BackendSchema 'MySQL where instance BackendSchema 'MySQL where
buildTableQueryAndSubscriptionFields = GSB.buildTableQueryAndSubscriptionFields buildTableQueryAndSubscriptionFields = GSB.buildTableQueryAndSubscriptionFields
buildTableRelayQueryFields = buildTableRelayQueryFields' buildTableRelayQueryFields _ _ _ _ _ _ = pure []
buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields buildTableStreamingSubscriptionFields = GSB.buildTableStreamingSubscriptionFields
buildTableInsertMutationFields = buildTableInsertMutationFields' buildTableInsertMutationFields _ _ _ _ _ _ = pure []
buildTableUpdateMutationFields = buildTableUpdateMutationFields' buildTableUpdateMutationFields _ _ _ _ _ _ = pure []
buildTableDeleteMutationFields = buildTableDeleteMutationFields' buildTableDeleteMutationFields _ _ _ _ _ _ = pure []
buildFunctionQueryFields = buildFunctionQueryFields' buildFunctionQueryFields _ _ _ _ _ = pure []
buildFunctionRelayQueryFields = buildFunctionRelayQueryFields' buildFunctionRelayQueryFields _ _ _ _ _ _ = pure []
buildFunctionMutationFields = buildFunctionMutationFields' buildFunctionMutationFields _ _ _ _ _ = pure []
relayExtension = Nothing relayExtension = Nothing
nodesAggExtension = Just () nodesAggExtension = Just ()
streamSubscriptionExtension = Nothing streamSubscriptionExtension = Nothing
columnParser = columnParser' columnParser = columnParser'
scalarSelectionArgumentsParser = scalarSelectionArgumentsParser' scalarSelectionArgumentsParser _ = pure Nothing
orderByOperators _sourceInfo = orderByOperators' orderByOperators _sourceInfo = orderByOperators'
comparisonExps = comparisonExps' comparisonExps = comparisonExps'
countTypeInput = mysqlCountTypeInput countTypeInput = mysqlCountTypeInput
@ -92,88 +89,6 @@ mysqlTableArgs sourceInfo tableInfo = do
IR._saDistinct = Nothing IR._saDistinct = Nothing
} }
buildTableRelayQueryFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
RQL.SourceInfo 'MySQL ->
RQL.TableName 'MySQL ->
TableInfo 'MySQL ->
C.GQLNameIdentifier ->
NESeq (ColumnInfo 'MySQL) ->
m [P.FieldParser n a]
buildTableRelayQueryFields' _mkRootFieldName _sourceInfo _tableName _tableInfo _gqlName _pkeyColumns =
pure []
buildTableInsertMutationFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
Scenario ->
RQL.SourceInfo 'MySQL ->
RQL.TableName 'MySQL ->
TableInfo 'MySQL ->
C.GQLNameIdentifier ->
m [P.FieldParser n a]
buildTableInsertMutationFields' _mkRootFieldName _scenario _sourceInfo _tableName _tableInfo _gqlName =
pure []
buildTableUpdateMutationFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
Scenario ->
RQL.SourceInfo 'MySQL ->
RQL.TableName 'MySQL ->
TableInfo 'MySQL ->
C.GQLNameIdentifier ->
m [P.FieldParser n a]
buildTableUpdateMutationFields' _mkRootFieldName _scenario _sourceInfo _tableName _tableInfo _gqlName =
pure []
buildTableDeleteMutationFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
Scenario ->
RQL.SourceInfo 'MySQL ->
RQL.TableName 'MySQL ->
TableInfo 'MySQL ->
C.GQLNameIdentifier ->
m [P.FieldParser n a]
buildTableDeleteMutationFields' _mkRootFieldName _scenario _sourceInfo _tableName _tableInfo _gqlName =
pure []
buildFunctionQueryFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
RQL.SourceInfo 'MySQL ->
FunctionName 'MySQL ->
FunctionInfo 'MySQL ->
RQL.TableName 'MySQL ->
m [P.FieldParser n a]
buildFunctionQueryFields' _ _ _ _ _ =
pure []
buildFunctionRelayQueryFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
RQL.SourceInfo 'MySQL ->
FunctionName 'MySQL ->
FunctionInfo 'MySQL ->
RQL.TableName 'MySQL ->
NESeq (ColumnInfo 'MySQL) ->
m [P.FieldParser n a]
buildFunctionRelayQueryFields' _mkRootFieldName _sourceInfo _functionName _functionInfo _tableName _pkeyColumns =
pure []
buildFunctionMutationFields' ::
MonadBuildSchema 'MySQL r m n =>
RQL.MkRootFieldName ->
RQL.SourceInfo 'MySQL ->
FunctionName 'MySQL ->
FunctionInfo 'MySQL ->
RQL.TableName 'MySQL ->
m [P.FieldParser n a]
buildFunctionMutationFields' _ _ _ _ _ =
pure []
bsParser :: MonadParse m => Parser 'Both m ByteString bsParser :: MonadParse m => Parser 'Both m ByteString
bsParser = encodeUtf8 <$> P.string bsParser = encodeUtf8 <$> P.string
@ -229,12 +144,6 @@ columnParser' columnType (GQL.Nullability isNullable) =
MySQL.VarcharValue $ GQL.unName value MySQL.VarcharValue $ GQL.unName value
) )
scalarSelectionArgumentsParser' ::
MonadParse n =>
ColumnType 'MySQL ->
InputFieldsParser n (Maybe (ScalarSelectionArguments 'MySQL))
scalarSelectionArgumentsParser' _columnType = pure Nothing
orderByOperators' :: NamingCase -> (GQL.Name, NonEmpty (P.Definition P.EnumValueInfo, (BasicOrderType 'MySQL, NullsOrderType 'MySQL))) orderByOperators' :: NamingCase -> (GQL.Name, NonEmpty (P.Definition P.EnumValueInfo, (BasicOrderType 'MySQL, NullsOrderType 'MySQL)))
orderByOperators' _tCase = orderByOperators' _tCase =
(Name._order_by,) $ (Name._order_by,) $
@ -290,13 +199,6 @@ comparisonExps' = P.memoize 'comparisonExps $ \columnType -> do
P.fieldOptional Name.__lte Nothing (ALTE . mkParameter <$> typedParser) P.fieldOptional Name.__lte Nothing (ALTE . mkParameter <$> typedParser)
] ]
{-
NOTE: Should this be removed?
offsetParser' :: MonadParse n => Parser 'Both n (SQLExpression 'MySQL)
offsetParser' =
MySQL.ValueExpression . MySQL.BigValue . fromIntegral <$> P.int
-}
mysqlCountTypeInput :: mysqlCountTypeInput ::
MonadParse n => MonadParse n =>
Maybe (Parser 'Both n (Column 'MySQL)) -> Maybe (Parser 'Both n (Column 'MySQL)) ->