mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 04:24:35 +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
239 lines
9.1 KiB
Haskell
239 lines
9.1 KiB
Haskell
{-# LANGUAGE DeriveAnyClass #-}
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
module Hasura.SQL.Backend
|
|
( PostgresKind (..),
|
|
BackendType (..),
|
|
BackendSourceKind (..),
|
|
backendShortName,
|
|
supportedBackends,
|
|
backendTextNames,
|
|
backendTypeFromText,
|
|
parseBackendTypeFromText,
|
|
backendTypeFromBackendSourceKind,
|
|
)
|
|
where
|
|
|
|
import Autodocodec (HasCodec (codec), JSONCodec, bimapCodec, dimapCodec, literalTextCodec, parseAlternatives)
|
|
import Data.Aeson
|
|
import Data.Aeson.Types (Parser)
|
|
import Data.Proxy
|
|
import Data.Text (unpack)
|
|
import Data.Text.Extended
|
|
import Data.Text.NonEmpty (NonEmptyText, mkNonEmptyText, nonEmptyTextCodec, nonEmptyTextQQ)
|
|
import Hasura.Backends.DataConnector.Adapter.Types (DataConnectorName (..))
|
|
import Hasura.Incremental
|
|
import Hasura.Prelude
|
|
import Witch qualified
|
|
|
|
-- | 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
|
|
| Citus
|
|
| Cockroach
|
|
deriving stock (Show, Eq, Ord, Generic)
|
|
deriving anyclass (Hashable, Cacheable)
|
|
|
|
-- | An enum that represents each backend we support.
|
|
data BackendType
|
|
= Postgres PostgresKind
|
|
| MSSQL
|
|
| BigQuery
|
|
| MySQL
|
|
| DataConnector
|
|
deriving stock (Show, Eq, Ord, Generic)
|
|
deriving anyclass (Hashable, Cacheable)
|
|
|
|
-- | The name of the backend, as we expect it to appear in our metadata and API.
|
|
instance Witch.From BackendType NonEmptyText where
|
|
from (Postgres Vanilla) = [nonEmptyTextQQ|postgres|]
|
|
from (Postgres Citus) = [nonEmptyTextQQ|citus|]
|
|
from (Postgres Cockroach) = [nonEmptyTextQQ|cockroach|]
|
|
from MSSQL = [nonEmptyTextQQ|mssql|]
|
|
from BigQuery = [nonEmptyTextQQ|bigquery|]
|
|
from MySQL = [nonEmptyTextQQ|mysql|]
|
|
from DataConnector = [nonEmptyTextQQ|dataconnector|]
|
|
|
|
instance ToTxt BackendType where
|
|
toTxt = toTxt . Witch.into @NonEmptyText
|
|
|
|
instance FromJSON BackendType where
|
|
parseJSON = withText "backend type" parseBackendTypeFromText
|
|
|
|
instance ToJSON BackendType where
|
|
toJSON = String . toTxt
|
|
|
|
instance Cacheable (Proxy (b :: BackendType))
|
|
|
|
-- | 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.
|
|
-- This type correlates to the kind property of 'SourceMetadata', which is usually just
|
|
-- postgres, mssql, etc for static backends, but can be a configurable value for DataConnector
|
|
-- hence requiring 'DataConnectorName' for 'DataConnectorKind'
|
|
--
|
|
-- 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
|
|
-- not because DataConnector fundamentally is configured at runtime with 'DataConnectorName'.
|
|
data BackendSourceKind (b :: BackendType) where
|
|
PostgresVanillaKind :: BackendSourceKind ('Postgres 'Vanilla)
|
|
PostgresCitusKind :: BackendSourceKind ('Postgres 'Citus)
|
|
PostgresCockroachKind :: BackendSourceKind ('Postgres 'Cockroach)
|
|
MSSQLKind :: BackendSourceKind 'MSSQL
|
|
BigQueryKind :: BackendSourceKind 'BigQuery
|
|
MySQLKind :: BackendSourceKind 'MySQL
|
|
DataConnectorKind :: DataConnectorName -> BackendSourceKind 'DataConnector
|
|
|
|
deriving instance Show (BackendSourceKind b)
|
|
|
|
deriving instance Eq (BackendSourceKind b)
|
|
|
|
deriving instance Ord (BackendSourceKind b)
|
|
|
|
instance Cacheable (BackendSourceKind b) where
|
|
unchanged _ = (==)
|
|
|
|
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
|
|
from k@PostgresCockroachKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
from k@MSSQLKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
from k@BigQueryKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
from k@MySQLKind = Witch.into @NonEmptyText $ backendTypeFromBackendSourceKind k
|
|
from (DataConnectorKind dataConnectorName) = Witch.into @NonEmptyText dataConnectorName
|
|
|
|
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
|
|
|
|
instance FromJSON (BackendSourceKind ('Postgres 'Cockroach)) where
|
|
parseJSON = mkParseStaticBackendSourceKind PostgresCockroachKind
|
|
|
|
instance FromJSON (BackendSourceKind ('MSSQL)) where
|
|
parseJSON = mkParseStaticBackendSourceKind MSSQLKind
|
|
|
|
instance FromJSON (BackendSourceKind ('BigQuery)) where
|
|
parseJSON = mkParseStaticBackendSourceKind BigQueryKind
|
|
|
|
instance FromJSON (BackendSourceKind ('MySQL)) where
|
|
parseJSON = mkParseStaticBackendSourceKind MySQLKind
|
|
|
|
instance FromJSON (BackendSourceKind ('DataConnector)) where
|
|
parseJSON = withText "BackendSourceKind" $ \text ->
|
|
DataConnectorKind . DataConnectorName <$> mkNonEmptyText text
|
|
`onNothing` fail "Cannot be empty string"
|
|
|
|
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
|
|
|
|
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
|
|
codec = dimapCodec dec enc nonEmptyTextCodec
|
|
where
|
|
dec = DataConnectorKind . DataConnectorName
|
|
enc = Witch.into
|
|
|
|
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
|
|
|
|
-- | 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.
|
|
backendShortName :: BackendType -> Maybe Text
|
|
backendShortName = \case
|
|
Postgres Vanilla -> Just "pg"
|
|
_ -> Nothing
|
|
|
|
supportedBackends :: [BackendType]
|
|
supportedBackends =
|
|
[ Postgres Vanilla,
|
|
Postgres Citus,
|
|
Postgres Cockroach,
|
|
MSSQL,
|
|
BigQuery,
|
|
MySQL,
|
|
DataConnector
|
|
]
|
|
|
|
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
|
|
PostgresCockroachKind -> Postgres Cockroach
|
|
MSSQLKind -> MSSQL
|
|
BigQueryKind -> BigQuery
|
|
MySQLKind -> MySQL
|
|
DataConnectorKind _ -> DataConnector
|