2022-05-02 08:03:12 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
|
2022-10-20 06:23:37 +03:00
|
|
|
module Hasura.Backends.DataConnector.Adapter.Backend
|
|
|
|
( CustomBooleanOperator (..),
|
|
|
|
columnTypeToScalarType,
|
2022-12-01 03:07:16 +03:00
|
|
|
parseValue,
|
2022-10-20 06:23:37 +03:00
|
|
|
)
|
|
|
|
where
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2022-09-20 09:18:46 +03:00
|
|
|
import Data.Aeson qualified as J
|
2022-07-15 06:27:31 +03:00
|
|
|
import Data.Aeson.Extended (ToJSONKeyValue (..))
|
|
|
|
import Data.Aeson.Key (fromText)
|
2022-09-20 09:18:46 +03:00
|
|
|
import Data.Aeson.Types qualified as J
|
2022-10-27 03:42:49 +03:00
|
|
|
import Data.HashMap.Strict qualified as HashMap
|
2022-08-04 11:34:45 +03:00
|
|
|
import Data.List.NonEmpty qualified as NonEmpty
|
2023-03-30 18:52:20 +03:00
|
|
|
import Data.Map.Strict (Map)
|
2022-12-01 03:07:16 +03:00
|
|
|
import Data.Scientific (fromFloatDigits)
|
2022-08-04 11:34:45 +03:00
|
|
|
import Data.Text qualified as Text
|
2022-05-26 14:54:30 +03:00
|
|
|
import Data.Text.Casing qualified as C
|
2022-08-04 11:34:45 +03:00
|
|
|
import Data.Text.Extended ((<<>))
|
2022-10-27 03:42:49 +03:00
|
|
|
import Hasura.Backends.DataConnector.API qualified as API
|
2022-09-20 09:18:46 +03:00
|
|
|
import Hasura.Backends.DataConnector.Adapter.Types qualified as DC
|
2023-01-10 04:54:40 +03:00
|
|
|
import Hasura.Backends.DataConnector.Adapter.Types.Mutations qualified as DC
|
2022-06-02 05:06:45 +03:00
|
|
|
import Hasura.Base.Error (Code (ValidationFailed), QErr, runAesonParser, throw400)
|
2022-05-02 08:03:12 +03:00
|
|
|
import Hasura.Prelude
|
2022-07-15 06:27:31 +03:00
|
|
|
import Hasura.RQL.IR.BoolExp
|
2023-02-03 19:27:44 +03:00
|
|
|
import Hasura.RQL.Types.Backend (Backend (..), ComputedFieldReturnType, HasSourceConfiguration (..), SupportedNamingCase (..), XDisable, XEnable)
|
2023-04-24 21:35:48 +03:00
|
|
|
import Hasura.RQL.Types.BackendType (BackendType (DataConnector))
|
2022-10-20 06:23:37 +03:00
|
|
|
import Hasura.RQL.Types.Column (ColumnType (..))
|
2023-03-15 13:29:13 +03:00
|
|
|
import Hasura.RQL.Types.ResizePool
|
2022-05-02 08:03:12 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
|
|
|
|
|
|
|
-- | An alias for '()' indicating that a particular associated type has not yet
|
|
|
|
-- been implemented for the 'DataConnector' backend.
|
|
|
|
--
|
|
|
|
-- '()' is used (rather than a type with an empty data constructor) because it
|
|
|
|
-- comes with many of the instances that these associated types require.
|
|
|
|
--
|
|
|
|
-- This alias should /not/ be exported from this module, and it's only defined
|
|
|
|
-- for clarity.
|
|
|
|
type Unimplemented = ()
|
|
|
|
|
|
|
|
instance Backend 'DataConnector where
|
2023-03-30 18:52:20 +03:00
|
|
|
type BackendConfig 'DataConnector = Map DC.DataConnectorName DC.DataConnectorOptions
|
2022-09-20 09:18:46 +03:00
|
|
|
type BackendInfo 'DataConnector = HashMap DC.DataConnectorName DC.DataConnectorInfo
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2022-09-20 09:18:46 +03:00
|
|
|
type TableName 'DataConnector = DC.TableName
|
|
|
|
type FunctionName 'DataConnector = DC.FunctionName
|
2023-05-19 07:47:12 +03:00
|
|
|
type FunctionReturnType 'DataConnector = DC.FunctionReturnType
|
|
|
|
type RawFunctionInfo 'DataConnector = API.FunctionInfo
|
|
|
|
type FunctionArgument 'DataConnector = API.FunctionArg
|
2022-09-20 09:18:46 +03:00
|
|
|
type ConstraintName 'DataConnector = DC.ConstraintName
|
|
|
|
type BasicOrderType 'DataConnector = DC.OrderDirection
|
2022-05-02 08:03:12 +03:00
|
|
|
type NullsOrderType 'DataConnector = Unimplemented
|
2022-09-20 09:18:46 +03:00
|
|
|
type CountType 'DataConnector = DC.CountAggregate
|
|
|
|
type Column 'DataConnector = DC.ColumnName
|
2022-09-06 07:24:46 +03:00
|
|
|
type ScalarValue 'DataConnector = J.Value
|
2022-09-20 09:18:46 +03:00
|
|
|
type ScalarType 'DataConnector = DC.ScalarType
|
2022-06-02 05:06:45 +03:00
|
|
|
|
|
|
|
-- This does not actually have to be the full IR Expression, in fact it is only
|
|
|
|
-- required to represent literals, so we use a special type for that.
|
|
|
|
-- The 'SQLExpression' type family should be removed in a future refactor
|
2022-09-20 09:18:46 +03:00
|
|
|
type SQLExpression 'DataConnector = DC.Literal
|
2022-05-03 11:58:56 +03:00
|
|
|
type ScalarSelectionArguments 'DataConnector = Void
|
2022-07-15 06:27:31 +03:00
|
|
|
type BooleanOperators 'DataConnector = CustomBooleanOperator
|
2023-04-05 05:21:43 +03:00
|
|
|
type ExtraTableMetadata 'DataConnector = DC.ExtraTableMetadata
|
2022-05-04 17:52:29 +03:00
|
|
|
type ComputedFieldDefinition 'DataConnector = Unimplemented
|
2023-05-19 07:47:12 +03:00
|
|
|
type FunctionArgumentExp 'DataConnector = DC.ArgumentExp
|
2022-05-25 13:24:41 +03:00
|
|
|
type ComputedFieldImplicitArguments 'DataConnector = Unimplemented
|
|
|
|
type ComputedFieldReturn 'DataConnector = Unimplemented
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2023-01-10 04:54:40 +03:00
|
|
|
type UpdateVariant 'DataConnector = DC.DataConnectorUpdateVariant
|
2022-12-12 07:41:36 +03:00
|
|
|
type BackendInsert 'DataConnector = DC.BackendInsert
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
type XComputedField 'DataConnector = XDisable
|
|
|
|
type XRelay 'DataConnector = XDisable
|
2022-07-20 08:20:49 +03:00
|
|
|
type XNodesAgg 'DataConnector = XEnable
|
2022-12-21 20:14:07 +03:00
|
|
|
type XEventTriggers 'DataConnector = XDisable
|
2022-05-02 08:03:12 +03:00
|
|
|
type XNestedInserts 'DataConnector = XDisable
|
|
|
|
type XStreamingSubscription 'DataConnector = XDisable
|
2023-04-11 04:29:05 +03:00
|
|
|
type XNestedObjects 'DataConnector = XEnable
|
Nested array support for Data Connectors Backend and MongoDB
## Description
This change adds support for querying into nested arrays in Data Connector agents that support such a concept (currently MongoDB).
### DC API changes
- New API type `ColumnType` which allows representing the type of a "column" as either a scalar type, an object reference or an array of `ColumnType`s. This recursive definition allows arbitrary nesting of arrays of types.
- The `type` fields in the API types `ColumnInfo` and `ColumnInsertSchema` now take a `ColumnType` instead of a `ScalarType`.
- To ensure backwards compatibility, a `ColumnType` representing a scalar serialises and deserialises to the same representation as `ScalarType`.
- In queries, the `Field` type now has a new constructor `NestedArrayField`. This contains a nested `Field` along with optional `limit`, `offset`, `where` and `order_by` arguments. (These optional arguments are not yet used by either HGE or the MongoDB agent.)
### MongoDB Haskell agent changes
- The `/schema` endpoint will now recognise arrays within the JSON validation schema and generate corresponding arrays in the DC schema.
- The `/query` endpoint will now handle `NestedArrayField`s within queries (although it does not yet handle `limit`, `offset`, `where` and `order_by`).
### HGE server changes
- The `Backend` type class adds a new type family `XNestedArrays b` to enable nested arrays on a per-backend basis (currently enabled only for the `DataConnector` backend.
- Within `RawColumnInfo` the column type is now represented by a new type `RawColumnType b` which mirrors the shape of the DC API `ColumnType`, but uses `XNestedObjects b` and `XNestedArrays b` type families to allow turning nested object and array supports on or off for a particular backend. In the `DataConnector` backend `API.CustomType` is converted into `RawColumnInfo 'DataConnector` while building the schema.
- In the next stage of schema building, the `RawColumnInfo` is converted into a `StructuredColumnInfo` which allows us to represent the three different types of columns: scalar, object and array. TODO: the `StructuredColumnInfo` looks very similar to the Logical Model types. The main difference is that it uses the `XNestedObjects` and `XNestedArrays` type families. We should be able to combine these two representations.
- The `StructuredColumnInfo` is then placed into a `FIColumn` `FieldInfo`. This involved some refactoring of `FieldInfo` as I had previously split out `FINestedObject` into a separate constructor. However it works out better to represent all "column" fields (i.e. scalar, object and array) using `FIColumn` as this make it easier to implement permission checking correctly. This is the reason the `StructuredColumnInfo` was needed.
- Next, the `FieldInfo` are used to generate `FieldParser`s. We add a new constructor to `AnnFieldG` for `AFNestedArray`. An `AFNestedArray` field parser can contain either a simple array selection or an array aggregate. Simple array `FieldParsers` are currently limited to subfield selection. We will add support for limit, offset, where and order_by in a future PR. We also don't yet generate array aggregate `FieldParsers.
- The new `AFNestedArray` field is handled by the `QueryPlan` module in the `DataConnector` backend. There we generate an `API.NestedArrayField` from the AFNestedArray. We also handle nested arrays when reshaping the response from the DC agent.
## Limitations
- Support for limit, offset, filter (where) and order_by is not yet fully implemented, although it should not be hard to add this
- Support for aggregations on nested arrays is not yet fully implemented
- Permissions involving nested arrays (and objects) not yet implemented
- This should be integrated with Logical Model types, but that will happen in a separate PR
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/9149
GitOrigin-RevId: 0e7b71a994fc1d2ca1ef73bfe7b96e95b5328531
2023-05-24 11:00:59 +03:00
|
|
|
type XNestedArrays 'DataConnector = XEnable
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2022-09-02 09:33:21 +03:00
|
|
|
type HealthCheckTest 'DataConnector = Void
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
isComparableType :: ScalarType 'DataConnector -> Bool
|
2023-01-11 05:36:03 +03:00
|
|
|
isComparableType = const False
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
isNumType :: ScalarType 'DataConnector -> Bool
|
2023-01-11 05:36:03 +03:00
|
|
|
isNumType = const False
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2022-12-12 07:41:36 +03:00
|
|
|
getCustomAggregateOperators :: DC.SourceConfig -> HashMap G.Name (HashMap DC.ScalarType DC.ScalarType)
|
|
|
|
getCustomAggregateOperators DC.SourceConfig {..} =
|
2022-10-27 03:42:49 +03:00
|
|
|
HashMap.foldrWithKey insertOps mempty scalarTypesCapabilities
|
|
|
|
where
|
2022-10-28 04:12:54 +03:00
|
|
|
scalarTypesCapabilities = API.unScalarTypesCapabilities $ API._cScalarTypes _scCapabilities
|
2022-10-27 03:42:49 +03:00
|
|
|
insertOps typeName API.ScalarTypeCapabilities {..} m =
|
2023-05-24 16:51:56 +03:00
|
|
|
HashMap.foldrWithKey insertOp m
|
|
|
|
$ API.unAggregateFunctions _stcAggregateFunctions
|
2022-10-27 03:42:49 +03:00
|
|
|
where
|
|
|
|
insertOp funtionName resultTypeName =
|
2023-05-24 16:51:56 +03:00
|
|
|
HashMap.insertWith HashMap.union funtionName
|
|
|
|
$ HashMap.singleton
|
2022-12-01 03:07:16 +03:00
|
|
|
(DC.mkScalarType _scCapabilities typeName)
|
|
|
|
(DC.mkScalarType _scCapabilities resultTypeName)
|
2022-10-27 03:42:49 +03:00
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
textToScalarValue :: Maybe Text -> ScalarValue 'DataConnector
|
|
|
|
textToScalarValue = error "textToScalarValue: not implemented for the Data Connector backend."
|
|
|
|
|
|
|
|
parseScalarValue :: ScalarType 'DataConnector -> J.Value -> Either QErr (ScalarValue 'DataConnector)
|
2022-09-20 09:18:46 +03:00
|
|
|
parseScalarValue type' value = runAesonParser (parseValue type') value
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
scalarValueToJSON :: ScalarValue 'DataConnector -> J.Value
|
2022-12-01 03:07:16 +03:00
|
|
|
scalarValueToJSON = id
|
2022-05-02 08:03:12 +03:00
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
-- TODO: Fill in this definition for computed fields
|
2022-05-04 17:52:29 +03:00
|
|
|
computedFieldFunction :: ComputedFieldDefinition 'DataConnector -> FunctionName 'DataConnector
|
|
|
|
computedFieldFunction = error "computedFieldFunction: not implemented for the Data Connector backend"
|
|
|
|
|
2022-05-25 13:24:41 +03:00
|
|
|
computedFieldReturnType :: ComputedFieldReturn 'DataConnector -> ComputedFieldReturnType 'DataConnector
|
|
|
|
computedFieldReturnType = error "computedFieldReturnType: not implemented for the Data Connector backend"
|
|
|
|
|
|
|
|
fromComputedFieldImplicitArguments :: v -> ComputedFieldImplicitArguments 'DataConnector -> [FunctionArgumentExp 'DataConnector v]
|
|
|
|
fromComputedFieldImplicitArguments = error "fromComputedFieldImplicitArguments: not implemented for the Data Connector backend"
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
-- phil said this was cursed
|
|
|
|
tableToFunction :: TableName 'DataConnector -> FunctionName 'DataConnector
|
|
|
|
tableToFunction = coerce
|
|
|
|
|
2023-05-19 07:47:12 +03:00
|
|
|
functionToTable :: FunctionName 'DataConnector -> TableName 'DataConnector
|
|
|
|
functionToTable = coerce
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
tableGraphQLName :: TableName 'DataConnector -> Either QErr G.Name
|
2022-08-04 11:34:45 +03:00
|
|
|
tableGraphQLName name = do
|
|
|
|
let snakedName = snakeCaseTableName @'DataConnector name
|
|
|
|
G.mkName snakedName
|
|
|
|
`onNothing` throw400 ValidationFailed ("TableName " <> snakedName <> " is not a valid GraphQL identifier")
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
functionGraphQLName :: FunctionName 'DataConnector -> Either QErr G.Name
|
2023-05-19 07:47:12 +03:00
|
|
|
functionGraphQLName name = do
|
|
|
|
let snakedName = snakeCaseTableName @'DataConnector (coerce name)
|
|
|
|
G.mkName snakedName
|
|
|
|
`onNothing` throw400 ValidationFailed ("FunctionName " <> snakedName <> " is not a valid GraphQL name")
|
2022-05-02 08:03:12 +03:00
|
|
|
|
|
|
|
snakeCaseTableName :: TableName 'DataConnector -> Text
|
2022-09-20 09:18:46 +03:00
|
|
|
snakeCaseTableName = Text.intercalate "_" . NonEmpty.toList . DC.unTableName
|
2022-05-26 14:54:30 +03:00
|
|
|
|
|
|
|
getTableIdentifier :: TableName 'DataConnector -> Either QErr C.GQLNameIdentifier
|
2022-09-20 09:18:46 +03:00
|
|
|
getTableIdentifier name@(DC.TableName (prefix :| suffixes)) =
|
2022-08-17 15:46:36 +03:00
|
|
|
let identifier = do
|
|
|
|
namePrefix <- G.mkName prefix
|
|
|
|
nameSuffixes <- traverse G.mkNameSuffix suffixes
|
|
|
|
pure $ C.fromAutogeneratedTuple (namePrefix, nameSuffixes)
|
|
|
|
in identifier
|
|
|
|
`onNothing` throw400 ValidationFailed ("TableName " <> name <<> " is not a valid GraphQL identifier")
|
2022-05-26 14:54:30 +03:00
|
|
|
|
|
|
|
namingConventionSupport :: SupportedNamingCase
|
|
|
|
namingConventionSupport = OnlyHasuraCase
|
2022-07-15 06:27:31 +03:00
|
|
|
|
2023-03-15 13:29:13 +03:00
|
|
|
resizeSourcePools :: SourceConfig 'DataConnector -> ServerReplicas -> IO SourceResizePoolSummary
|
2022-10-17 11:04:54 +03:00
|
|
|
resizeSourcePools _sourceConfig _serverReplicas =
|
|
|
|
-- Data connectors do not have concept of connection pools
|
2023-03-15 13:29:13 +03:00
|
|
|
pure noPoolsResizedSummary
|
2022-10-17 11:04:54 +03:00
|
|
|
|
2022-12-21 20:14:07 +03:00
|
|
|
defaultTriggerOnReplication = Nothing
|
2022-11-29 20:41:41 +03:00
|
|
|
|
2023-02-03 19:27:44 +03:00
|
|
|
instance HasSourceConfiguration 'DataConnector where
|
|
|
|
type SourceConfig 'DataConnector = DC.SourceConfig
|
|
|
|
type SourceConnConfiguration 'DataConnector = DC.ConnSourceConfig
|
2023-04-05 11:57:19 +03:00
|
|
|
sourceConfigNumReadReplicas = const 0 -- not supported
|
|
|
|
sourceConfigConnectonTemplateEnabled = const False -- not supported
|
2023-02-03 19:27:44 +03:00
|
|
|
|
2022-07-15 06:27:31 +03:00
|
|
|
data CustomBooleanOperator a = CustomBooleanOperator
|
|
|
|
{ _cboName :: Text,
|
|
|
|
_cboRHS :: Maybe (Either (RootOrCurrentColumn 'DataConnector) a) -- TODO turn Either into a specific type
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Generic, Foldable, Functor, Traversable, Show)
|
|
|
|
|
2023-05-24 16:51:56 +03:00
|
|
|
instance (NFData a) => NFData (CustomBooleanOperator a)
|
2022-07-15 06:27:31 +03:00
|
|
|
|
2023-05-24 16:51:56 +03:00
|
|
|
instance (Hashable a) => Hashable (CustomBooleanOperator a)
|
2022-07-15 06:27:31 +03:00
|
|
|
|
2023-05-24 16:51:56 +03:00
|
|
|
instance (J.ToJSON a) => ToJSONKeyValue (CustomBooleanOperator a) where
|
2022-07-15 06:27:31 +03:00
|
|
|
toJSONKeyValue CustomBooleanOperator {..} = (fromText _cboName, J.toJSON _cboRHS)
|
2022-09-20 09:18:46 +03:00
|
|
|
|
|
|
|
parseValue :: DC.ScalarType -> J.Value -> J.Parser J.Value
|
|
|
|
parseValue type' val =
|
|
|
|
case (type', val) of
|
|
|
|
(_, J.Null) -> pure J.Null
|
2023-01-11 05:36:03 +03:00
|
|
|
(DC.ScalarType _ graphQLType, value) -> case graphQLType of
|
2022-12-01 03:07:16 +03:00
|
|
|
Nothing -> pure value
|
|
|
|
Just DC.GraphQLInt -> (J.Number . fromIntegral) <$> J.parseJSON @Int value
|
|
|
|
Just DC.GraphQLFloat -> (J.Number . fromFloatDigits) <$> J.parseJSON @Double value
|
|
|
|
Just DC.GraphQLString -> J.String <$> J.parseJSON value
|
|
|
|
Just DC.GraphQLBoolean -> J.Bool <$> J.parseJSON value
|
|
|
|
Just DC.GraphQLID -> J.String <$> parseID value
|
|
|
|
where
|
|
|
|
parseID value = J.parseJSON @Text value <|> tshow <$> J.parseJSON @Int value
|
2022-10-20 06:23:37 +03:00
|
|
|
|
|
|
|
columnTypeToScalarType :: ColumnType 'DataConnector -> DC.ScalarType
|
|
|
|
columnTypeToScalarType = \case
|
|
|
|
ColumnScalar scalarType -> scalarType
|
2023-01-11 05:36:03 +03:00
|
|
|
-- Data connectors does not yet support enum tables.
|
|
|
|
-- If/when we add this support, we probably want to
|
|
|
|
-- embed the enum scalar type name within the `EnumReference` record type
|
|
|
|
ColumnEnumReference _ -> error "columnTypeToScalarType got enum"
|