2022-04-29 05:13:13 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
|
2021-03-15 16:02:58 +03:00
|
|
|
module Hasura.SQL.Backend
|
2021-04-22 00:44:37 +03:00
|
|
|
( PostgresKind (..),
|
|
|
|
BackendType (..),
|
2022-04-29 05:13:13 +03:00
|
|
|
BackendSourceKind (..),
|
2021-07-07 04:43:42 +03:00
|
|
|
backendShortName,
|
2021-03-15 16:02:58 +03:00
|
|
|
supportedBackends,
|
2022-04-29 05:13:13 +03:00
|
|
|
backendTextNames,
|
|
|
|
backendTypeFromText,
|
|
|
|
parseBackendTypeFromText,
|
|
|
|
backendTypeFromBackendSourceKind,
|
2021-03-15 16:02:58 +03:00
|
|
|
)
|
|
|
|
where
|
2021-04-22 00:44:37 +03:00
|
|
|
|
2022-11-03 16:56:35 +03:00
|
|
|
import Autodocodec (Codec (StringCodec), HasCodec (codec), JSONCodec, bimapCodec, literalTextCodec, parseAlternatives, (<?>))
|
2022-10-18 07:17:57 +03:00
|
|
|
import Data.Aeson hiding ((<?>))
|
2022-04-29 05:13:13 +03:00
|
|
|
import Data.Aeson.Types (Parser)
|
2021-03-18 23:34:11 +03:00
|
|
|
import Data.Text (unpack)
|
|
|
|
import Data.Text.Extended
|
2022-10-18 07:17:57 +03:00
|
|
|
import Data.Text.NonEmpty (NonEmptyText, nonEmptyTextQQ)
|
2022-11-03 16:56:35 +03:00
|
|
|
import Hasura.Backends.DataConnector.Adapter.Types (DataConnectorName (..), mkDataConnectorName)
|
2021-02-03 19:17:20 +03:00
|
|
|
import Hasura.Prelude
|
2022-10-18 07:17:57 +03:00
|
|
|
import Language.GraphQL.Draft.Syntax qualified as GQL
|
2022-04-29 05:13:13 +03:00
|
|
|
import Witch qualified
|
2021-04-22 00:44:37 +03:00
|
|
|
|
|
|
|
-- | Argument to Postgres; we represent backends which are variations on Postgres as sub-types of
|
|
|
|
-- Postgres. This value indicates which "flavour" of Postgres a backend is.
|
|
|
|
data PostgresKind
|
|
|
|
= Vanilla
|
2021-05-21 05:46:58 +03:00
|
|
|
| Citus
|
2022-08-19 17:19:54 +03:00
|
|
|
| Cockroach
|
2022-04-29 05:13:13 +03:00
|
|
|
deriving stock (Show, Eq, Ord, Generic)
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving anyclass (Hashable)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
|
|
|
-- | An enum that represents each backend we support.
|
2021-03-18 23:34:11 +03:00
|
|
|
data BackendType
|
2021-04-22 00:44:37 +03:00
|
|
|
= Postgres PostgresKind
|
2021-03-18 23:34:11 +03:00
|
|
|
| MSSQL
|
2021-04-12 13:18:29 +03:00
|
|
|
| BigQuery
|
2021-07-15 15:44:26 +03:00
|
|
|
| MySQL
|
2022-05-02 08:03:12 +03:00
|
|
|
| DataConnector
|
2022-04-29 05:13:13 +03:00
|
|
|
deriving stock (Show, Eq, Ord, Generic)
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving anyclass (Hashable)
|
2021-04-22 00:44:37 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
-- | The name of the backend, as we expect it to appear in our metadata and API.
|
2022-04-29 05:13:13 +03:00
|
|
|
instance Witch.From BackendType NonEmptyText where
|
|
|
|
from (Postgres Vanilla) = [nonEmptyTextQQ|postgres|]
|
|
|
|
from (Postgres Citus) = [nonEmptyTextQQ|citus|]
|
2022-08-19 17:19:54 +03:00
|
|
|
from (Postgres Cockroach) = [nonEmptyTextQQ|cockroach|]
|
2022-04-29 05:13:13 +03:00
|
|
|
from MSSQL = [nonEmptyTextQQ|mssql|]
|
|
|
|
from BigQuery = [nonEmptyTextQQ|bigquery|]
|
|
|
|
from MySQL = [nonEmptyTextQQ|mysql|]
|
2022-05-02 08:03:12 +03:00
|
|
|
from DataConnector = [nonEmptyTextQQ|dataconnector|]
|
2022-04-29 05:13:13 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
instance ToTxt BackendType where
|
2022-04-29 05:13:13 +03:00
|
|
|
toTxt = toTxt . Witch.into @NonEmptyText
|
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
instance FromJSON BackendType where
|
2022-04-29 05:13:13 +03:00
|
|
|
parseJSON = withText "backend type" parseBackendTypeFromText
|
2021-03-18 23:34:11 +03:00
|
|
|
|
|
|
|
instance ToJSON BackendType where
|
|
|
|
toJSON = String . toTxt
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
-- | Similar to 'BackendType', however, in the case of 'DataConnectorKind' we need to be able
|
|
|
|
-- capture the name of the data connector that should be used by the DataConnector backend.
|
2022-04-29 05:13:13 +03:00
|
|
|
-- This type correlates to the kind property of 'SourceMetadata', which is usually just
|
2022-05-02 08:03:12 +03:00
|
|
|
-- postgres, mssql, etc for static backends, but can be a configurable value for DataConnector
|
|
|
|
-- hence requiring 'DataConnectorName' for 'DataConnectorKind'
|
2022-04-29 05:13:13 +03:00
|
|
|
--
|
|
|
|
-- This type cannot entirely replace 'BackendType' because 'BackendType' has a fixed number of
|
|
|
|
-- possible values which can be enumerated over at compile time, but 'BackendSourceKind' does
|
2022-05-02 08:03:12 +03:00
|
|
|
-- not because DataConnector fundamentally is configured at runtime with 'DataConnectorName'.
|
2022-04-29 05:13:13 +03:00
|
|
|
data BackendSourceKind (b :: BackendType) where
|
|
|
|
PostgresVanillaKind :: BackendSourceKind ('Postgres 'Vanilla)
|
|
|
|
PostgresCitusKind :: BackendSourceKind ('Postgres 'Citus)
|
2022-08-19 17:19:54 +03:00
|
|
|
PostgresCockroachKind :: BackendSourceKind ('Postgres 'Cockroach)
|
2022-04-29 05:13:13 +03:00
|
|
|
MSSQLKind :: BackendSourceKind 'MSSQL
|
|
|
|
BigQueryKind :: BackendSourceKind 'BigQuery
|
|
|
|
MySQLKind :: BackendSourceKind 'MySQL
|
2022-05-02 08:03:12 +03:00
|
|
|
DataConnectorKind :: DataConnectorName -> BackendSourceKind 'DataConnector
|
2022-04-29 05:13:13 +03:00
|
|
|
|
|
|
|
deriving instance Show (BackendSourceKind b)
|
|
|
|
|
|
|
|
deriving instance Eq (BackendSourceKind b)
|
|
|
|
|
|
|
|
deriving instance Ord (BackendSourceKind b)
|
|
|
|
|
|
|
|
instance Witch.From (BackendSourceKind b) NonEmptyText where
|
|
|
|
-- All cases are specified explicitly here to ensure compiler warnings highlight
|
|
|
|
-- this area for consideration and update if another BackendType is added
|
|
|
|
from k@PostgresVanillaKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
|
|
from k@PostgresCitusKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
2022-08-19 17:19:54 +03:00
|
|
|
from k@PostgresCockroachKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
2022-04-29 05:13:13 +03:00
|
|
|
from k@MSSQLKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
|
|
from k@BigQueryKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
|
|
from k@MySQLKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
2022-05-02 08:03:12 +03:00
|
|
|
from (DataConnectorKind dataConnectorName) = Witch.into @NonEmptyText dataConnectorName
|
2022-04-29 05:13:13 +03:00
|
|
|
|
|
|
|
instance ToTxt (BackendSourceKind b) where
|
|
|
|
toTxt = toTxt . Witch.into @NonEmptyText
|
|
|
|
|
|
|
|
-- If you need to parse an arbitrary string into a BackendSourceKind, you can't because of the
|
|
|
|
-- b type parameter. You actually want to parse into 'AnyBackend BackendSourceKind'.
|
|
|
|
-- See 'backendSourceKindFromText' from the AnyBackend module for that.
|
|
|
|
|
|
|
|
instance ToJSON (BackendSourceKind b) where
|
|
|
|
toJSON = String . toTxt
|
|
|
|
|
|
|
|
instance FromJSON (BackendSourceKind ('Postgres 'Vanilla)) where
|
|
|
|
parseJSON = mkParseStaticBackendSourceKind PostgresVanillaKind
|
|
|
|
|
|
|
|
instance FromJSON (BackendSourceKind ('Postgres 'Citus)) where
|
|
|
|
parseJSON = mkParseStaticBackendSourceKind PostgresCitusKind
|
|
|
|
|
2022-08-19 17:19:54 +03:00
|
|
|
instance FromJSON (BackendSourceKind ('Postgres 'Cockroach)) where
|
|
|
|
parseJSON = mkParseStaticBackendSourceKind PostgresCockroachKind
|
|
|
|
|
2022-04-29 05:13:13 +03:00
|
|
|
instance FromJSON (BackendSourceKind ('MSSQL)) where
|
|
|
|
parseJSON = mkParseStaticBackendSourceKind MSSQLKind
|
|
|
|
|
|
|
|
instance FromJSON (BackendSourceKind ('BigQuery)) where
|
|
|
|
parseJSON = mkParseStaticBackendSourceKind BigQueryKind
|
|
|
|
|
|
|
|
instance FromJSON (BackendSourceKind ('MySQL)) where
|
|
|
|
parseJSON = mkParseStaticBackendSourceKind MySQLKind
|
|
|
|
|
2022-05-02 08:03:12 +03:00
|
|
|
instance FromJSON (BackendSourceKind ('DataConnector)) where
|
2022-11-03 16:56:35 +03:00
|
|
|
parseJSON v = DataConnectorKind <$> parseJSON v
|
2022-04-29 05:13:13 +03:00
|
|
|
|
|
|
|
mkParseStaticBackendSourceKind :: BackendSourceKind b -> (Value -> Parser (BackendSourceKind b))
|
|
|
|
mkParseStaticBackendSourceKind backendSourceKind =
|
|
|
|
withText "BackendSourceKind" $ \text ->
|
|
|
|
if text `elem` validValues
|
|
|
|
then pure backendSourceKind
|
|
|
|
else fail ("got: " <> unpack text <> ", expected one of: " <> unpack (commaSeparated validValues))
|
|
|
|
where
|
|
|
|
validValues = backendTextNames $ backendTypeFromBackendSourceKind backendSourceKind
|
|
|
|
|
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
|
|
|
instance HasCodec (BackendSourceKind ('Postgres 'Vanilla)) where
|
|
|
|
codec = mkCodecStaticBackendSourceKind PostgresVanillaKind
|
|
|
|
|
|
|
|
instance HasCodec (BackendSourceKind ('Postgres 'Citus)) where
|
|
|
|
codec = mkCodecStaticBackendSourceKind PostgresCitusKind
|
|
|
|
|
|
|
|
instance HasCodec (BackendSourceKind ('Postgres 'Cockroach)) where
|
|
|
|
codec = mkCodecStaticBackendSourceKind PostgresCockroachKind
|
|
|
|
|
|
|
|
instance HasCodec (BackendSourceKind ('MSSQL)) where
|
|
|
|
codec = mkCodecStaticBackendSourceKind MSSQLKind
|
|
|
|
|
|
|
|
instance HasCodec (BackendSourceKind ('BigQuery)) where
|
|
|
|
codec = mkCodecStaticBackendSourceKind BigQueryKind
|
|
|
|
|
|
|
|
instance HasCodec (BackendSourceKind ('MySQL)) where
|
|
|
|
codec = mkCodecStaticBackendSourceKind MySQLKind
|
|
|
|
|
|
|
|
instance HasCodec (BackendSourceKind ('DataConnector)) where
|
2022-11-03 16:56:35 +03:00
|
|
|
codec = bimapCodec dec enc gqlNameCodec
|
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
|
|
|
where
|
2022-11-03 16:56:35 +03:00
|
|
|
dec :: GQL.Name -> Either String (BackendSourceKind 'DataConnector)
|
|
|
|
dec n = DataConnectorKind <$> mkDataConnectorName n
|
|
|
|
|
2022-10-18 07:17:57 +03:00
|
|
|
enc :: BackendSourceKind ('DataConnector) -> GQL.Name
|
2022-11-03 16:56:35 +03:00
|
|
|
enc (DataConnectorKind dcName) = unDataConnectorName dcName
|
2022-10-18 07:17:57 +03:00
|
|
|
|
|
|
|
gqlNameCodec :: JSONCodec GQL.Name
|
|
|
|
gqlNameCodec =
|
|
|
|
bimapCodec
|
|
|
|
parseName
|
|
|
|
GQL.unName
|
|
|
|
(StringCodec (Just "GraphQLName"))
|
|
|
|
<?> "A valid GraphQL name"
|
|
|
|
|
|
|
|
parseName text = GQL.mkName text `onNothing` Left (unpack text <> " is not a valid GraphQL name")
|
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
|
|
|
|
|
|
|
mkCodecStaticBackendSourceKind :: BackendSourceKind b -> JSONCodec (BackendSourceKind b)
|
|
|
|
mkCodecStaticBackendSourceKind backendSourceKind =
|
|
|
|
bimapCodec dec enc $
|
|
|
|
parseAlternatives (literalTextCodec longName) (literalTextCodec <$> aliases)
|
|
|
|
where
|
|
|
|
dec text =
|
|
|
|
if text `elem` validValues
|
|
|
|
then Right backendSourceKind
|
|
|
|
else Left ("got: " <> unpack text <> ", expected one of: " <> unpack (commaSeparated validValues))
|
|
|
|
|
|
|
|
enc = toTxt
|
|
|
|
|
|
|
|
validValues = backendTextNames $ backendTypeFromBackendSourceKind backendSourceKind
|
|
|
|
longName = head validValues
|
|
|
|
aliases = tail validValues
|
|
|
|
|
2021-07-07 04:43:42 +03:00
|
|
|
-- | Some generated APIs use a shortened version of the backend's name rather than its full
|
|
|
|
-- name. This function returns the "short form" of a backend, if any.
|
2022-04-29 05:13:13 +03:00
|
|
|
backendShortName :: BackendType -> Maybe Text
|
2021-07-07 04:43:42 +03:00
|
|
|
backendShortName = \case
|
2022-04-29 05:13:13 +03:00
|
|
|
Postgres Vanilla -> Just "pg"
|
|
|
|
_ -> Nothing
|
2021-07-07 04:43:42 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
supportedBackends :: [BackendType]
|
2021-04-22 00:44:37 +03:00
|
|
|
supportedBackends =
|
|
|
|
[ Postgres Vanilla,
|
2021-05-21 05:46:58 +03:00
|
|
|
Postgres Citus,
|
2022-08-19 17:19:54 +03:00
|
|
|
Postgres Cockroach,
|
2021-04-22 00:44:37 +03:00
|
|
|
MSSQL,
|
|
|
|
BigQuery,
|
2021-12-22 03:10:28 +03:00
|
|
|
MySQL,
|
2022-05-02 08:03:12 +03:00
|
|
|
DataConnector
|
2021-04-22 00:44:37 +03:00
|
|
|
]
|
2022-04-29 05:13:13 +03:00
|
|
|
|
|
|
|
backendTextNames :: BackendType -> [Text]
|
|
|
|
backendTextNames b =
|
|
|
|
catMaybes
|
|
|
|
[ Just (toTxt b), -- long form
|
|
|
|
backendShortName b -- short form
|
|
|
|
]
|
|
|
|
|
|
|
|
backendTextNameLookup :: [(Text, BackendType)]
|
|
|
|
backendTextNameLookup =
|
|
|
|
supportedBackends >>= (\b -> (,b) <$> backendTextNames b)
|
|
|
|
|
|
|
|
-- | This uses this lookup mechanism to avoid having to duplicate and hardcode the
|
|
|
|
-- backend string. We accept both the short form and the long form of the backend's name.
|
|
|
|
backendTypeFromText :: Text -> Maybe BackendType
|
|
|
|
backendTypeFromText txt =
|
|
|
|
lookup txt backendTextNameLookup
|
|
|
|
|
|
|
|
parseBackendTypeFromText :: Text -> Parser BackendType
|
|
|
|
parseBackendTypeFromText txt =
|
|
|
|
let uniqueBackends = commaSeparated $ fst <$> backendTextNameLookup
|
|
|
|
in backendTypeFromText txt
|
|
|
|
`onNothing` fail ("got: " <> unpack txt <> ", expected one of: " <> unpack uniqueBackends)
|
|
|
|
|
|
|
|
backendTypeFromBackendSourceKind :: BackendSourceKind b -> BackendType
|
|
|
|
backendTypeFromBackendSourceKind = \case
|
|
|
|
PostgresVanillaKind -> Postgres Vanilla
|
|
|
|
PostgresCitusKind -> Postgres Citus
|
2022-08-19 17:19:54 +03:00
|
|
|
PostgresCockroachKind -> Postgres Cockroach
|
2022-04-29 05:13:13 +03:00
|
|
|
MSSQLKind -> MSSQL
|
|
|
|
BigQueryKind -> BigQuery
|
|
|
|
MySQLKind -> MySQL
|
2022-05-02 08:03:12 +03:00
|
|
|
DataConnectorKind _ -> DataConnector
|