2022-06-27 19:32:25 +03:00
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
|
|
|
|
module Hasura.Metadata.DTO.MetadataDTOSpec (spec) where
|
|
|
|
|
server: polymorphic codec for metadata sources
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
2022-08-25 21:34:44 +03:00
|
|
|
import Data.Aeson (ToJSON (toJSON), eitherDecode)
|
2022-06-27 19:32:25 +03:00
|
|
|
import Data.Aeson.QQ.Simple (aesonQQ)
|
server: polymorphic codec for metadata sources
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
2022-08-25 21:34:44 +03:00
|
|
|
import Data.Either (isLeft)
|
2022-06-27 19:32:25 +03:00
|
|
|
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.Metadata.DTO.Placeholder (PlaceholderArray (PlaceholderArray))
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Test.Hspec
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = describe "MetadataDTO" $ do
|
|
|
|
describe "distinguishing metadata revisions" $ do
|
|
|
|
it "serializes v1" $ do
|
|
|
|
let output = V1 $ emptyMetadataV1
|
|
|
|
let expected = [aesonQQ|{ "version": 1, "tables": [] }|]
|
|
|
|
toJSON output `shouldBe` expected
|
|
|
|
|
|
|
|
it "serializes v2" $ do
|
|
|
|
let output = V2 $ emptyMetadataV2
|
|
|
|
let expected = [aesonQQ|{ "version": 2, "tables": [] }|]
|
|
|
|
toJSON output `shouldBe` expected
|
|
|
|
|
|
|
|
it "serializes v3" $ do
|
|
|
|
let output = V3 $ emptyMetadataV3
|
|
|
|
let expected = [aesonQQ|{ "version": 3, "sources": [] }|]
|
|
|
|
toJSON output `shouldBe` expected
|
|
|
|
|
|
|
|
it "parses v2" $ do
|
|
|
|
let input = "{ \"version\": 2, \"tables\": [] }"
|
|
|
|
let expected = V2 $ emptyMetadataV2
|
|
|
|
let actual = eitherDecode input :: Either String MetadataDTO
|
|
|
|
actual `shouldBe` Right expected
|
|
|
|
|
|
|
|
it "parses v3" $ do
|
|
|
|
let input = "{\"version\": 3, \"sources\": [] }"
|
|
|
|
let expected = V3 $ emptyMetadataV3
|
|
|
|
let actual = eitherDecode input :: Either String MetadataDTO
|
|
|
|
actual `shouldBe` Right expected
|
|
|
|
|
|
|
|
it "fails parsing v3 on version mismatch" $ do
|
|
|
|
let input = "{\"version\": 3, \"tables\": [] }"
|
|
|
|
let actual = eitherDecode input :: Either String MetadataDTO
|
|
|
|
actual `shouldSatisfy` isLeft
|
|
|
|
|
|
|
|
it "assumes v1 if version field is absent" $ do
|
|
|
|
let input = "{\"tables\": [] }"
|
|
|
|
let expected = V1 $ emptyMetadataV1
|
|
|
|
let actual = eitherDecode input :: Either String MetadataDTO
|
|
|
|
actual `shouldBe` Right expected
|
|
|
|
|
|
|
|
it "fails parsing if input is not v1-compatible, and version is absent" $ do
|
|
|
|
let input = "{\"sources\": [] }"
|
|
|
|
let actual = eitherDecode input :: Either String MetadataDTO
|
|
|
|
actual `shouldSatisfy` isLeft
|
|
|
|
|
server: polymorphic codec for metadata sources
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
2022-08-25 21:34:44 +03:00
|
|
|
-- TODO: Currently there are discrepancies between Metadata and DTO
|
|
|
|
-- serialization. These tests are disabled until those discrepancies are
|
|
|
|
-- resolved.
|
|
|
|
-- beforeAll getMetadataFixture $ do
|
|
|
|
-- describe "v3" $ do
|
|
|
|
-- it "deserializes and re-serializes equivalently to Metadata" $ \metadataFixture -> do
|
|
|
|
-- let dto = parseEither parseJSON =<< metadataFixture :: Either String MetadataDTO
|
|
|
|
-- let fromDto = toJSON <$> dto
|
|
|
|
-- fromDto `shouldSatisfy` isRight
|
|
|
|
-- fromDto `shouldBe` metadataFixture
|
|
|
|
|
|
|
|
-- it "converts metadata to DTO to JSON to metadata" $ \metadataFixture -> do
|
|
|
|
-- let origMetadata = parseEither (parseJSON @Metadata) =<< metadataFixture
|
|
|
|
-- let dto = metadataToDTO <$> origMetadata
|
|
|
|
-- let json = toJSON <$> dto
|
|
|
|
-- let metadata = parseEither (parseJSON @Metadata) =<< json
|
|
|
|
-- metadata `shouldSatisfy` isRight
|
|
|
|
-- metadata `shouldBe` origMetadata
|
2022-08-01 15:48:40 +03:00
|
|
|
|
2022-06-27 19:32:25 +03:00
|
|
|
emptyMetadataV3 :: MetadataV3
|
|
|
|
emptyMetadataV3 =
|
|
|
|
MetadataV3
|
server: polymorphic codec for metadata sources
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
2022-08-25 21:34:44 +03:00
|
|
|
{ metaV3Sources = mempty,
|
2022-08-01 15:48:40 +03:00
|
|
|
metaV3RemoteSchemas = Nothing,
|
|
|
|
metaV3QueryCollections = Nothing,
|
2022-06-27 19:32:25 +03:00
|
|
|
metaV3Allowlist = Nothing,
|
2022-08-01 15:48:40 +03:00
|
|
|
metaV3Actions = Nothing,
|
2022-06-27 19:32:25 +03:00
|
|
|
metaV3CustomTypes = Nothing,
|
2022-08-01 15:48:40 +03:00
|
|
|
metaV3CronTriggers = Nothing,
|
2022-06-27 19:32:25 +03:00
|
|
|
metaV3RestEndpoints = Nothing,
|
2022-08-01 15:48:40 +03:00
|
|
|
metaV3ApiLimits = Nothing,
|
|
|
|
metaV3MetricsConfig = Nothing,
|
|
|
|
metaV3InheritedRoles = Nothing,
|
|
|
|
metaV3GraphqlSchemaIntrospection = Nothing,
|
|
|
|
metaV3Network = Nothing,
|
|
|
|
metaV3BackendConfigs = Nothing
|
2022-06-27 19:32:25 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
emptyMetadataV2 :: MetadataV2
|
|
|
|
emptyMetadataV2 =
|
|
|
|
MetadataV2
|
|
|
|
{ metaV2Actions = Nothing,
|
|
|
|
metaV2Allowlist = Nothing,
|
|
|
|
metaV2CronTriggers = Nothing,
|
|
|
|
metaV2CustomTypes = Nothing,
|
|
|
|
metaV2Functions = Nothing,
|
|
|
|
metaV2QueryCollections = Nothing,
|
|
|
|
metaV2RemoteSchemas = Nothing,
|
|
|
|
metaV2Tables = PlaceholderArray mempty
|
|
|
|
}
|
|
|
|
|
|
|
|
emptyMetadataV1 :: MetadataV1
|
|
|
|
emptyMetadataV1 =
|
|
|
|
MetadataV1
|
|
|
|
{ metaV1Functions = Nothing,
|
|
|
|
metaV1RemoteSchemas = Nothing,
|
|
|
|
metaV1Tables = PlaceholderArray mempty
|
|
|
|
}
|
|
|
|
|
server: polymorphic codec for metadata sources
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
2022-08-25 21:34:44 +03:00
|
|
|
-- getMetadataFixture :: IO (Either String Value)
|
|
|
|
-- getMetadataFixture = do
|
|
|
|
-- let filePath = $(strToExp =<< makeRelativeToProject "../cli/internal/metadatautil/testdata/json/t2/metadata.json")
|
|
|
|
-- -- Round-trip fixture data through the server's old serialization so that we
|
|
|
|
-- -- will get consistent results on the next round-trip.
|
|
|
|
-- metadata <- eitherDecodeFileStrict' filePath :: IO (Either String Metadata)
|
|
|
|
-- return $ toJSON <$> metadata
|