mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 03:09:21 +03:00
84fd5910b0
This PR expands the OpenAPI specification generated for metadata to include separate definitions for `SourceMetadata` for each native database type, and for DataConnector. For the most part the changes add `HasCodec` implementations, and don't modify existing code otherwise. The generated OpenAPI spec can be used to generate TypeScript definitions that distinguish different source metadata types based on the value of the `kind` properly. There is a problem: because the specified `kind` value for a data connector source is any string, when TypeScript gets a source with a `kind` value of, say, `"postgres"`, it cannot unambiguously determine whether the source is postgres, or a data connector. For example, ```ts function consumeSourceMetadata(source: SourceMetadata) { if (source.kind === "postgres" || source.kind === "pg") { // At this point TypeScript infers that `source` is either an instance // of `PostgresSourceMetadata`, or `DataconnectorSourceMetadata`. It // can't narrow further. source } if (source.kind === "something else") { // TypeScript infers that this `source` must be an instance of // `DataconnectorSourceMetadata` because `source.kind` does not match // any of the other options. source } } ``` The simplest way I can think of to fix this would be to add a boolean property to the `SourceMetadata` type along the lines of `isNative` or `isDataConnector`. This could be a field that only exists in serialized data, like the metadata version field. The combination of one of the native database names for `kind`, and a true value for `isNative` would be enough for TypeScript to unambiguously distinguish the source kinds. But note that in the current state TypeScript is able to reference the short `"pg"` name correctly! ~~Tests are not passing yet due to some discrepancies in DTO serialization vs existing Metadata serialization. I'm working on that.~~ The placeholders that I used for table and function metadata are not compatible with the ordered JSON serialization in use. I think the best solution is to write compatible codecs for those types in another PR. For now I have disabled some DTO tests for this PR. Here are the generated [OpenAPI spec](https://github.com/hasura/graphql-engine-mono/files/9397333/openapi.tar.gz) based on these changes, and the generated [TypeScript client code](https://github.com/hasura/graphql-engine-mono/files/9397339/client-typescript.tar.gz) based on that spec. Ticket: [MM-66](https://hasurahq.atlassian.net/browse/MM-66) PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5582 GitOrigin-RevId: e1446191c6c832879db04f129daa397a3be03f62
133 lines
5.9 KiB
Haskell
133 lines
5.9 KiB
Haskell
-- | This module exports an OpenAPI specification for the GraphQL Engine
|
|
-- metadata API.
|
|
--
|
|
-- The OpenAPI specification for metadata is experimental and incomplete. Please
|
|
-- do not incorporate it into essential workflows at this time.
|
|
module Hasura.Server.MetadataOpenAPI (metadataOpenAPI) where
|
|
|
|
import Autodocodec (HasCodec, JSONCodec)
|
|
import Autodocodec.OpenAPI (declareNamedSchemaVia, declareNamedSchemaViaCodec)
|
|
import Control.Lens ((.~), (^.))
|
|
import Data.Data (Proxy)
|
|
import Data.HashMap.Strict.InsOrd qualified as HM
|
|
import Data.OpenApi
|
|
( HasComponents (components),
|
|
HasName (name),
|
|
HasSchema (schema),
|
|
HasSchemas (schemas),
|
|
OpenApi,
|
|
)
|
|
import Data.OpenApi qualified as OpenApi
|
|
import Data.OpenApi.Declare (undeclare)
|
|
import Data.Proxy (Proxy (..))
|
|
import Hasura.Backends.BigQuery.Source (BigQueryConnSourceConfig)
|
|
import Hasura.Backends.DataConnector.Adapter.Types qualified as DataConnector
|
|
import Hasura.Backends.MSSQL.Connection (MSSQLConnConfiguration)
|
|
import Hasura.Backends.MySQL.Types qualified as MySQL
|
|
import Hasura.Backends.Postgres.Connection.Settings (PostgresConnConfiguration)
|
|
import Hasura.Metadata.DTO.Metadata (MetadataDTO)
|
|
import Hasura.Metadata.DTO.MetadataV1 (MetadataV1)
|
|
import Hasura.Metadata.DTO.MetadataV2 (MetadataV2)
|
|
import Hasura.Metadata.DTO.MetadataV3 (MetadataV3)
|
|
import Hasura.Prelude
|
|
import Hasura.RQL.Types.Metadata.Common
|
|
( BackendSourceMetadata,
|
|
FunctionMetadata,
|
|
SourceMetadata,
|
|
TableMetadata,
|
|
backendSourceMetadataCodec,
|
|
)
|
|
import Hasura.RQL.Types.SourceCustomization (SourceCustomization)
|
|
import Hasura.SQL.Backend (BackendType (..), PostgresKind (..))
|
|
|
|
-- | An OpenApi document includes \"schemas\" that describe the data that may be
|
|
-- produced or consumed by an API. It can also include \"paths\" which describe
|
|
-- REST endpoints, and the document can include other API metadata. This example
|
|
-- only includes schemas.
|
|
--
|
|
-- Throws an error if any schema listed in 'openApiSchemas' does not have
|
|
-- a name.
|
|
--
|
|
-- The OpenAPI specification for metadata is experimental and incomplete. Please
|
|
-- do not incorporate it into essential workflows at this time.
|
|
metadataOpenAPI :: OpenApi
|
|
metadataOpenAPI =
|
|
(mempty :: OpenApi)
|
|
& components . schemas .~ HM.fromList (applySchemaName <$> openApiSchemas)
|
|
|
|
-- | All metadata DTOs should be listed here. Schemas in this list must be
|
|
-- named! Some autodocodec combinators apply names for you, like 'object'.
|
|
-- Otherwise you can use the 'named' combinator to apply a name.
|
|
--
|
|
-- As far as I can tell it is necessary to explicitly list all of the data
|
|
-- types that should be included in the OpenApi document with their names. It
|
|
-- would be nice to provide only a top-level type ('Metadata' in this case), and
|
|
-- have all of the types referenced by that type included automatically; but
|
|
-- I haven't seen a way to do that.
|
|
openApiSchemas :: [OpenApi.NamedSchema]
|
|
openApiSchemas =
|
|
[ toNamedSchema (Proxy @MetadataDTO),
|
|
toNamedSchema (Proxy @MetadataV1),
|
|
toNamedSchema (Proxy @MetadataV2),
|
|
toNamedSchema (Proxy @MetadataV3),
|
|
toNamedSchemaVia backendSourceMetadataCodec (Proxy @BackendSourceMetadata),
|
|
toNamedSchema (Proxy @SourceCustomization),
|
|
-- SourceMetadata
|
|
toNamedSchema (Proxy @(SourceMetadata ('Postgres 'Vanilla))),
|
|
toNamedSchema (Proxy @(SourceMetadata ('Postgres 'Citus))),
|
|
toNamedSchema (Proxy @(SourceMetadata ('Postgres 'Cockroach))),
|
|
toNamedSchema (Proxy @(SourceMetadata ('MSSQL))),
|
|
toNamedSchema (Proxy @(SourceMetadata ('BigQuery))),
|
|
toNamedSchema (Proxy @(SourceMetadata ('MySQL))),
|
|
toNamedSchema (Proxy @(SourceMetadata ('DataConnector))),
|
|
-- FunctionMetadata
|
|
toNamedSchema (Proxy @(FunctionMetadata ('Postgres 'Vanilla))),
|
|
toNamedSchema (Proxy @(FunctionMetadata ('Postgres 'Citus))),
|
|
toNamedSchema (Proxy @(FunctionMetadata ('Postgres 'Cockroach))),
|
|
toNamedSchema (Proxy @(FunctionMetadata ('MSSQL))),
|
|
toNamedSchema (Proxy @(FunctionMetadata ('BigQuery))),
|
|
toNamedSchema (Proxy @(FunctionMetadata ('MySQL))),
|
|
toNamedSchema (Proxy @(FunctionMetadata ('DataConnector))),
|
|
-- TableMetadata
|
|
toNamedSchema (Proxy @(TableMetadata ('Postgres 'Vanilla))),
|
|
toNamedSchema (Proxy @(TableMetadata ('Postgres 'Citus))),
|
|
toNamedSchema (Proxy @(TableMetadata ('Postgres 'Cockroach))),
|
|
toNamedSchema (Proxy @(TableMetadata ('MSSQL))),
|
|
toNamedSchema (Proxy @(TableMetadata ('BigQuery))),
|
|
toNamedSchema (Proxy @(TableMetadata ('MySQL))),
|
|
toNamedSchema (Proxy @(TableMetadata ('DataConnector))),
|
|
-- Postgres-specific types
|
|
toNamedSchema (Proxy @PostgresConnConfiguration),
|
|
-- MSSQL-specific types
|
|
toNamedSchema (Proxy @MSSQLConnConfiguration),
|
|
-- BigQuery-specific types
|
|
toNamedSchema (Proxy @BigQueryConnSourceConfig),
|
|
-- MySQL-specific types
|
|
toNamedSchema (Proxy @MySQL.ConnSourceConfig),
|
|
-- DataConnector-specific types
|
|
toNamedSchema (Proxy @DataConnector.ConnSourceConfig)
|
|
]
|
|
|
|
-- | Introspect a given 'OpenApi.NamedSchema' to get its name, and return the
|
|
-- name with the unwrapped schema. (NamedSchema wraps a pair of an
|
|
-- 'OpenApi.Schema' and an optional name.)
|
|
--
|
|
-- Throws an exception if the named schema has no name. If this happens to you
|
|
-- then use autodocodec's 'named' combinator to apply a name to your codec.
|
|
applySchemaName :: OpenApi.NamedSchema -> (Text, OpenApi.Schema)
|
|
applySchemaName givenSchema = (schemaName, givenSchema ^. schema)
|
|
where
|
|
schemaName = case givenSchema ^. name of
|
|
Just n -> n
|
|
Nothing ->
|
|
error $
|
|
"a codec listed in 'openApiSchemas' does not have a name; "
|
|
<> "use the 'named' combinator from autodocodec to apply a name "
|
|
<> "to any codec in that list that does not already have one"
|
|
|
|
toNamedSchema :: HasCodec a => Proxy a -> OpenApi.NamedSchema
|
|
toNamedSchema proxy = undeclare $ declareNamedSchemaViaCodec proxy
|
|
|
|
toNamedSchemaVia :: JSONCodec a -> Proxy a -> OpenApi.NamedSchema
|
|
toNamedSchemaVia codec proxy = undeclare $ declareNamedSchemaVia codec proxy
|