{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE QuasiQuotes #-}
module Hasura.RQL.Types.BackendType
( PostgresKind (..),
BackendType (..),
BackendSourceKind (..),
backendShortName,
supportedBackends,
backendTextNames,
backendTypeFromText,
parseBackendTypeFromText,
backendTypeFromBackendSourceKind,
)
where
import Autodocodec (Codec (StringCodec), HasCodec (codec), JSONCodec, bimapCodec, literalTextCodec, parseAlternatives, (<?>))
import Data.Aeson hiding ((<?>))
import Data.Aeson.Types (Parser)
import Data.Text (unpack)
import Data.Text.Extended
import Data.Text.NonEmpty (NonEmptyText, nonEmptyTextQQ)
import Hasura.Prelude
import Hasura.RQL.Types.DataConnector (DataConnectorName (..), mkDataConnectorName)
import Language.GraphQL.Draft.Syntax qualified as GQL
import Witch qualified
data PostgresKind
= Vanilla
| Citus
| Cockroach
deriving stock (Int -> PostgresKind -> ShowS
[PostgresKind] -> ShowS
PostgresKind -> String
(Int -> PostgresKind -> ShowS)
-> (PostgresKind -> String)
-> ([PostgresKind] -> ShowS)
-> Show PostgresKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PostgresKind -> ShowS
showsPrec :: Int -> PostgresKind -> ShowS
$cshow :: PostgresKind -> String
show :: PostgresKind -> String
$cshowList :: [PostgresKind] -> ShowS
showList :: [PostgresKind] -> ShowS
Show, PostgresKind -> PostgresKind -> Bool
(PostgresKind -> PostgresKind -> Bool)
-> (PostgresKind -> PostgresKind -> Bool) -> Eq PostgresKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PostgresKind -> PostgresKind -> Bool
== :: PostgresKind -> PostgresKind -> Bool
$c/= :: PostgresKind -> PostgresKind -> Bool
/= :: PostgresKind -> PostgresKind -> Bool
Eq, Eq PostgresKind
Eq PostgresKind
-> (PostgresKind -> PostgresKind -> Ordering)
-> (PostgresKind -> PostgresKind -> Bool)
-> (PostgresKind -> PostgresKind -> Bool)
-> (PostgresKind -> PostgresKind -> Bool)
-> (PostgresKind -> PostgresKind -> Bool)
-> (PostgresKind -> PostgresKind -> PostgresKind)
-> (PostgresKind -> PostgresKind -> PostgresKind)
-> Ord PostgresKind
PostgresKind -> PostgresKind -> Bool
PostgresKind -> PostgresKind -> Ordering
PostgresKind -> PostgresKind -> PostgresKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PostgresKind -> PostgresKind -> Ordering
compare :: PostgresKind -> PostgresKind -> Ordering
$c< :: PostgresKind -> PostgresKind -> Bool
< :: PostgresKind -> PostgresKind -> Bool
$c<= :: PostgresKind -> PostgresKind -> Bool
<= :: PostgresKind -> PostgresKind -> Bool
$c> :: PostgresKind -> PostgresKind -> Bool
> :: PostgresKind -> PostgresKind -> Bool
$c>= :: PostgresKind -> PostgresKind -> Bool
>= :: PostgresKind -> PostgresKind -> Bool
$cmax :: PostgresKind -> PostgresKind -> PostgresKind
max :: PostgresKind -> PostgresKind -> PostgresKind
$cmin :: PostgresKind -> PostgresKind -> PostgresKind
min :: PostgresKind -> PostgresKind -> PostgresKind
Ord, (forall x. PostgresKind -> Rep PostgresKind x)
-> (forall x. Rep PostgresKind x -> PostgresKind)
-> Generic PostgresKind
forall x. Rep PostgresKind x -> PostgresKind
forall x. PostgresKind -> Rep PostgresKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PostgresKind -> Rep PostgresKind x
from :: forall x. PostgresKind -> Rep PostgresKind x
$cto :: forall x. Rep PostgresKind x -> PostgresKind
to :: forall x. Rep PostgresKind x -> PostgresKind
Generic)
deriving anyclass (Eq PostgresKind
Eq PostgresKind
-> (Int -> PostgresKind -> Int)
-> (PostgresKind -> Int)
-> Hashable PostgresKind
Int -> PostgresKind -> Int
PostgresKind -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> PostgresKind -> Int
hashWithSalt :: Int -> PostgresKind -> Int
$chash :: PostgresKind -> Int
hash :: PostgresKind -> Int
Hashable)
data BackendType
= Postgres PostgresKind
| MSSQL
| BigQuery
| DataConnector
deriving stock (Int -> BackendType -> ShowS
[BackendType] -> ShowS
BackendType -> String
(Int -> BackendType -> ShowS)
-> (BackendType -> String)
-> ([BackendType] -> ShowS)
-> Show BackendType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BackendType -> ShowS
showsPrec :: Int -> BackendType -> ShowS
$cshow :: BackendType -> String
show :: BackendType -> String
$cshowList :: [BackendType] -> ShowS
showList :: [BackendType] -> ShowS
Show, BackendType -> BackendType -> Bool
(BackendType -> BackendType -> Bool)
-> (BackendType -> BackendType -> Bool) -> Eq BackendType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BackendType -> BackendType -> Bool
== :: BackendType -> BackendType -> Bool
$c/= :: BackendType -> BackendType -> Bool
/= :: BackendType -> BackendType -> Bool
Eq, Eq BackendType
Eq BackendType
-> (BackendType -> BackendType -> Ordering)
-> (BackendType -> BackendType -> Bool)
-> (BackendType -> BackendType -> Bool)
-> (BackendType -> BackendType -> Bool)
-> (BackendType -> BackendType -> Bool)
-> (BackendType -> BackendType -> BackendType)
-> (BackendType -> BackendType -> BackendType)
-> Ord BackendType
BackendType -> BackendType -> Bool
BackendType -> BackendType -> Ordering
BackendType -> BackendType -> BackendType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BackendType -> BackendType -> Ordering
compare :: BackendType -> BackendType -> Ordering
$c< :: BackendType -> BackendType -> Bool
< :: BackendType -> BackendType -> Bool
$c<= :: BackendType -> BackendType -> Bool
<= :: BackendType -> BackendType -> Bool
$c> :: BackendType -> BackendType -> Bool
> :: BackendType -> BackendType -> Bool
$c>= :: BackendType -> BackendType -> Bool
>= :: BackendType -> BackendType -> Bool
$cmax :: BackendType -> BackendType -> BackendType
max :: BackendType -> BackendType -> BackendType
$cmin :: BackendType -> BackendType -> BackendType
min :: BackendType -> BackendType -> BackendType
Ord, (forall x. BackendType -> Rep BackendType x)
-> (forall x. Rep BackendType x -> BackendType)
-> Generic BackendType
forall x. Rep BackendType x -> BackendType
forall x. BackendType -> Rep BackendType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BackendType -> Rep BackendType x
from :: forall x. BackendType -> Rep BackendType x
$cto :: forall x. Rep BackendType x -> BackendType
to :: forall x. Rep BackendType x -> BackendType
Generic)
deriving anyclass (Eq BackendType
Eq BackendType
-> (Int -> BackendType -> Int)
-> (BackendType -> Int)
-> Hashable BackendType
Int -> BackendType -> Int
BackendType -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> BackendType -> Int
hashWithSalt :: Int -> BackendType -> Int
$chash :: BackendType -> Int
hash :: BackendType -> Int
Hashable)
instance Witch.From BackendType NonEmptyText where
from :: BackendType -> NonEmptyText
from (Postgres PostgresKind
Vanilla) = [nonEmptyTextQQ|postgres|]
from (Postgres PostgresKind
Citus) = [nonEmptyTextQQ|citus|]
from (Postgres PostgresKind
Cockroach) = [nonEmptyTextQQ|cockroach|]
from BackendType
MSSQL = [nonEmptyTextQQ|mssql|]
from BackendType
BigQuery = [nonEmptyTextQQ|bigquery|]
from BackendType
DataConnector = [nonEmptyTextQQ|dataconnector|]
instance ToTxt BackendType where
toTxt :: BackendType -> Text
toTxt = NonEmptyText -> Text
forall a. ToTxt a => a -> Text
toTxt (NonEmptyText -> Text)
-> (BackendType -> NonEmptyText) -> BackendType -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Witch.into @NonEmptyText
instance FromJSON BackendType where
parseJSON :: Value -> Parser BackendType
parseJSON = String
-> (Text -> Parser BackendType) -> Value -> Parser BackendType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"backend type" Text -> Parser BackendType
parseBackendTypeFromText
instance ToJSON BackendType where
toJSON :: BackendType -> Value
toJSON = Text -> Value
String (Text -> Value) -> (BackendType -> Text) -> BackendType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BackendType -> Text
forall a. ToTxt a => a -> Text
toTxt
data BackendSourceKind (b :: BackendType) where
PostgresVanillaKind :: BackendSourceKind ('Postgres 'Vanilla)
PostgresCitusKind :: BackendSourceKind ('Postgres 'Citus)
PostgresCockroachKind :: BackendSourceKind ('Postgres 'Cockroach)
MSSQLKind :: BackendSourceKind 'MSSQL
BigQueryKind :: BackendSourceKind 'BigQuery
DataConnectorKind :: DataConnectorName -> BackendSourceKind 'DataConnector
deriving instance Show (BackendSourceKind b)
deriving instance Eq (BackendSourceKind b)
deriving instance Ord (BackendSourceKind b)
instance Witch.From (BackendSourceKind b) NonEmptyText where
from :: BackendSourceKind b -> NonEmptyText
from k :: BackendSourceKind b
k@BackendSourceKind b
PostgresVanillaKind = forall target source. From source target => source -> target
Witch.into @NonEmptyText (BackendType -> NonEmptyText) -> BackendType -> NonEmptyText
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
k
from k :: BackendSourceKind b
k@BackendSourceKind b
PostgresCitusKind = forall target source. From source target => source -> target
Witch.into @NonEmptyText (BackendType -> NonEmptyText) -> BackendType -> NonEmptyText
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
k
from k :: BackendSourceKind b
k@BackendSourceKind b
PostgresCockroachKind = forall target source. From source target => source -> target
Witch.into @NonEmptyText (BackendType -> NonEmptyText) -> BackendType -> NonEmptyText
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
k
from k :: BackendSourceKind b
k@BackendSourceKind b
MSSQLKind = forall target source. From source target => source -> target
Witch.into @NonEmptyText (BackendType -> NonEmptyText) -> BackendType -> NonEmptyText
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
k
from k :: BackendSourceKind b
k@BackendSourceKind b
BigQueryKind = forall target source. From source target => source -> target
Witch.into @NonEmptyText (BackendType -> NonEmptyText) -> BackendType -> NonEmptyText
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
k
from (DataConnectorKind DataConnectorName
dataConnectorName) = forall target source. From source target => source -> target
Witch.into @NonEmptyText DataConnectorName
dataConnectorName
instance ToTxt (BackendSourceKind b) where
toTxt :: BackendSourceKind b -> Text
toTxt = NonEmptyText -> Text
forall a. ToTxt a => a -> Text
toTxt (NonEmptyText -> Text)
-> (BackendSourceKind b -> NonEmptyText)
-> BackendSourceKind b
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall target source. From source target => source -> target
Witch.into @NonEmptyText
instance ToJSON (BackendSourceKind b) where
toJSON :: BackendSourceKind b -> Value
toJSON = Text -> Value
String (Text -> Value)
-> (BackendSourceKind b -> Text) -> BackendSourceKind b -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BackendSourceKind b -> Text
forall a. ToTxt a => a -> Text
toTxt
instance FromJSON (BackendSourceKind ('Postgres 'Vanilla)) where
parseJSON :: Value -> Parser (BackendSourceKind ('Postgres 'Vanilla))
parseJSON = BackendSourceKind ('Postgres 'Vanilla)
-> Value -> Parser (BackendSourceKind ('Postgres 'Vanilla))
forall (b :: BackendType).
BackendSourceKind b -> Value -> Parser (BackendSourceKind b)
mkParseStaticBackendSourceKind BackendSourceKind ('Postgres 'Vanilla)
PostgresVanillaKind
instance FromJSON (BackendSourceKind ('Postgres 'Citus)) where
parseJSON :: Value -> Parser (BackendSourceKind ('Postgres 'Citus))
parseJSON = BackendSourceKind ('Postgres 'Citus)
-> Value -> Parser (BackendSourceKind ('Postgres 'Citus))
forall (b :: BackendType).
BackendSourceKind b -> Value -> Parser (BackendSourceKind b)
mkParseStaticBackendSourceKind BackendSourceKind ('Postgres 'Citus)
PostgresCitusKind
instance FromJSON (BackendSourceKind ('Postgres 'Cockroach)) where
parseJSON :: Value -> Parser (BackendSourceKind ('Postgres 'Cockroach))
parseJSON = BackendSourceKind ('Postgres 'Cockroach)
-> Value -> Parser (BackendSourceKind ('Postgres 'Cockroach))
forall (b :: BackendType).
BackendSourceKind b -> Value -> Parser (BackendSourceKind b)
mkParseStaticBackendSourceKind BackendSourceKind ('Postgres 'Cockroach)
PostgresCockroachKind
instance FromJSON (BackendSourceKind ('MSSQL)) where
parseJSON :: Value -> Parser (BackendSourceKind 'MSSQL)
parseJSON = BackendSourceKind 'MSSQL
-> Value -> Parser (BackendSourceKind 'MSSQL)
forall (b :: BackendType).
BackendSourceKind b -> Value -> Parser (BackendSourceKind b)
mkParseStaticBackendSourceKind BackendSourceKind 'MSSQL
MSSQLKind
instance FromJSON (BackendSourceKind ('BigQuery)) where
parseJSON :: Value -> Parser (BackendSourceKind 'BigQuery)
parseJSON = BackendSourceKind 'BigQuery
-> Value -> Parser (BackendSourceKind 'BigQuery)
forall (b :: BackendType).
BackendSourceKind b -> Value -> Parser (BackendSourceKind b)
mkParseStaticBackendSourceKind BackendSourceKind 'BigQuery
BigQueryKind
instance FromJSON (BackendSourceKind ('DataConnector)) where
parseJSON :: Value -> Parser (BackendSourceKind 'DataConnector)
parseJSON Value
v = DataConnectorName -> BackendSourceKind 'DataConnector
DataConnectorKind (DataConnectorName -> BackendSourceKind 'DataConnector)
-> Parser DataConnectorName
-> Parser (BackendSourceKind 'DataConnector)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser DataConnectorName
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
mkParseStaticBackendSourceKind :: BackendSourceKind b -> (Value -> Parser (BackendSourceKind b))
mkParseStaticBackendSourceKind :: forall (b :: BackendType).
BackendSourceKind b -> Value -> Parser (BackendSourceKind b)
mkParseStaticBackendSourceKind BackendSourceKind b
backendSourceKind =
String
-> (Text -> Parser (BackendSourceKind b))
-> Value
-> Parser (BackendSourceKind b)
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"BackendSourceKind" ((Text -> Parser (BackendSourceKind b))
-> Value -> Parser (BackendSourceKind b))
-> (Text -> Parser (BackendSourceKind b))
-> Value
-> Parser (BackendSourceKind b)
forall a b. (a -> b) -> a -> b
$ \Text
text ->
if Text
text Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
validValues
then BackendSourceKind b -> Parser (BackendSourceKind b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure BackendSourceKind b
backendSourceKind
else String -> Parser (BackendSourceKind b)
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"got: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
text String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", expected one of: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack ([Text] -> Text
forall t (f :: * -> *). (ToTxt t, Foldable f) => f t -> Text
commaSeparated [Text]
validValues))
where
validValues :: [Text]
validValues = BackendType -> [Text]
backendTextNames (BackendType -> [Text]) -> BackendType -> [Text]
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
backendSourceKind
instance HasCodec (BackendSourceKind ('Postgres 'Vanilla)) where
codec :: JSONCodec (BackendSourceKind ('Postgres 'Vanilla))
codec = BackendSourceKind ('Postgres 'Vanilla)
-> JSONCodec (BackendSourceKind ('Postgres 'Vanilla))
forall (b :: BackendType).
BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind BackendSourceKind ('Postgres 'Vanilla)
PostgresVanillaKind
instance HasCodec (BackendSourceKind ('Postgres 'Citus)) where
codec :: JSONCodec (BackendSourceKind ('Postgres 'Citus))
codec = BackendSourceKind ('Postgres 'Citus)
-> JSONCodec (BackendSourceKind ('Postgres 'Citus))
forall (b :: BackendType).
BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind BackendSourceKind ('Postgres 'Citus)
PostgresCitusKind
instance HasCodec (BackendSourceKind ('Postgres 'Cockroach)) where
codec :: JSONCodec (BackendSourceKind ('Postgres 'Cockroach))
codec = BackendSourceKind ('Postgres 'Cockroach)
-> JSONCodec (BackendSourceKind ('Postgres 'Cockroach))
forall (b :: BackendType).
BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind BackendSourceKind ('Postgres 'Cockroach)
PostgresCockroachKind
instance HasCodec (BackendSourceKind ('MSSQL)) where
codec :: JSONCodec (BackendSourceKind 'MSSQL)
codec = BackendSourceKind 'MSSQL -> JSONCodec (BackendSourceKind 'MSSQL)
forall (b :: BackendType).
BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind BackendSourceKind 'MSSQL
MSSQLKind
instance HasCodec (BackendSourceKind ('BigQuery)) where
codec :: JSONCodec (BackendSourceKind 'BigQuery)
codec = BackendSourceKind 'BigQuery
-> JSONCodec (BackendSourceKind 'BigQuery)
forall (b :: BackendType).
BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind BackendSourceKind 'BigQuery
BigQueryKind
instance HasCodec (BackendSourceKind ('DataConnector)) where
codec :: JSONCodec (BackendSourceKind 'DataConnector)
codec = (Name -> Either String (BackendSourceKind 'DataConnector))
-> (BackendSourceKind 'DataConnector -> Name)
-> Codec Value Name Name
-> JSONCodec (BackendSourceKind 'DataConnector)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> Either String newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
bimapCodec Name -> Either String (BackendSourceKind 'DataConnector)
dec BackendSourceKind 'DataConnector -> Name
enc Codec Value Name Name
gqlNameCodec
where
dec :: GQL.Name -> Either String (BackendSourceKind 'DataConnector)
dec :: Name -> Either String (BackendSourceKind 'DataConnector)
dec Name
n = DataConnectorName -> BackendSourceKind 'DataConnector
DataConnectorKind (DataConnectorName -> BackendSourceKind 'DataConnector)
-> Either String DataConnectorName
-> Either String (BackendSourceKind 'DataConnector)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Either String DataConnectorName
mkDataConnectorName Name
n
enc :: BackendSourceKind ('DataConnector) -> GQL.Name
enc :: BackendSourceKind 'DataConnector -> Name
enc (DataConnectorKind DataConnectorName
dcName) = DataConnectorName -> Name
unDataConnectorName DataConnectorName
dcName
gqlNameCodec :: JSONCodec GQL.Name
gqlNameCodec :: Codec Value Name Name
gqlNameCodec =
(Text -> Either String Name)
-> (Name -> Text) -> Codec Value Text Text -> Codec Value Name Name
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> Either String newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
bimapCodec
Text -> Either String Name
parseName
Name -> Text
GQL.unName
(Maybe Text -> Codec Value Text Text
StringCodec (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"GraphQLName"))
Codec Value Name Name -> Text -> Codec Value Name Name
forall input output.
ValueCodec input output -> Text -> ValueCodec input output
<?> Text
"A valid GraphQL name"
parseName :: Text -> Either String Name
parseName Text
text = Text -> Maybe Name
GQL.mkName Text
text Maybe Name -> Either String Name -> Either String Name
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` String -> Either String Name
forall a b. a -> Either a b
Left (Text -> String
unpack Text
text String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" is not a valid GraphQL name")
mkCodecStaticBackendSourceKind :: BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind :: forall (b :: BackendType).
BackendSourceKind b -> JSONCodec (BackendSourceKind b)
mkCodecStaticBackendSourceKind BackendSourceKind b
backendSourceKind =
(Text -> Either String (BackendSourceKind b))
-> (BackendSourceKind b -> Text)
-> Codec Value Text Text
-> Codec Value (BackendSourceKind b) (BackendSourceKind b)
forall oldOutput newOutput newInput oldInput context.
(oldOutput -> Either String newOutput)
-> (newInput -> oldInput)
-> Codec context oldInput oldOutput
-> Codec context newInput newOutput
bimapCodec Text -> Either String (BackendSourceKind b)
dec BackendSourceKind b -> Text
enc
(Codec Value Text Text
-> Codec Value (BackendSourceKind b) (BackendSourceKind b))
-> Codec Value Text Text
-> Codec Value (BackendSourceKind b) (BackendSourceKind b)
forall a b. (a -> b) -> a -> b
$ Codec Value Text Text
-> [Codec Value Text Text] -> Codec Value Text Text
forall context input output.
Codec context input output
-> [Codec context input output] -> Codec context input output
parseAlternatives (Text -> Codec Value Text Text
literalTextCodec Text
longName) (Text -> Codec Value Text Text
literalTextCodec (Text -> Codec Value Text Text)
-> [Text] -> [Codec Value Text Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
aliases)
where
dec :: Text -> Either String (BackendSourceKind b)
dec Text
text =
if Text
text Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
validValues
then BackendSourceKind b -> Either String (BackendSourceKind b)
forall a b. b -> Either a b
Right BackendSourceKind b
backendSourceKind
else String -> Either String (BackendSourceKind b)
forall a b. a -> Either a b
Left (String
"got: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
text String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", expected one of: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack ([Text] -> Text
forall t (f :: * -> *). (ToTxt t, Foldable f) => f t -> Text
commaSeparated [Text]
validValues))
enc :: BackendSourceKind b -> Text
enc = BackendSourceKind b -> Text
forall a. ToTxt a => a -> Text
toTxt
validValues :: [Text]
validValues = BackendType -> [Text]
backendTextNames (BackendType -> [Text]) -> BackendType -> [Text]
forall a b. (a -> b) -> a -> b
$ BackendSourceKind b -> BackendType
forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind BackendSourceKind b
backendSourceKind
longName :: Text
longName = [Text] -> Text
forall a. HasCallStack => [a] -> a
head [Text]
validValues
aliases :: [Text]
aliases = [Text] -> [Text]
forall a. HasCallStack => [a] -> [a]
tail [Text]
validValues
backendShortName :: BackendType -> Maybe Text
backendShortName :: BackendType -> Maybe Text
backendShortName = \case
Postgres PostgresKind
Vanilla -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"pg"
BackendType
_ -> Maybe Text
forall a. Maybe a
Nothing
supportedBackends :: [BackendType]
supportedBackends :: [BackendType]
supportedBackends =
[ PostgresKind -> BackendType
Postgres PostgresKind
Vanilla,
PostgresKind -> BackendType
Postgres PostgresKind
Citus,
PostgresKind -> BackendType
Postgres PostgresKind
Cockroach,
BackendType
MSSQL,
BackendType
BigQuery,
BackendType
DataConnector
]
backendTextNames :: BackendType -> [Text]
backendTextNames :: BackendType -> [Text]
backendTextNames BackendType
b =
[Maybe Text] -> [Text]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[ Text -> Maybe Text
forall a. a -> Maybe a
Just (BackendType -> Text
forall a. ToTxt a => a -> Text
toTxt BackendType
b),
BackendType -> Maybe Text
backendShortName BackendType
b
]
backendTextNameLookup :: [(Text, BackendType)]
backendTextNameLookup :: [(Text, BackendType)]
backendTextNameLookup =
[BackendType]
supportedBackends [BackendType]
-> (BackendType -> [(Text, BackendType)]) -> [(Text, BackendType)]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (\BackendType
b -> (,BackendType
b) (Text -> (Text, BackendType)) -> [Text] -> [(Text, BackendType)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BackendType -> [Text]
backendTextNames BackendType
b)
backendTypeFromText :: Text -> Maybe BackendType
backendTypeFromText :: Text -> Maybe BackendType
backendTypeFromText Text
txt =
Text -> [(Text, BackendType)] -> Maybe BackendType
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
txt [(Text, BackendType)]
backendTextNameLookup
parseBackendTypeFromText :: Text -> Parser BackendType
parseBackendTypeFromText :: Text -> Parser BackendType
parseBackendTypeFromText Text
txt =
let uniqueBackends :: Text
uniqueBackends = [Text] -> Text
forall t (f :: * -> *). (ToTxt t, Foldable f) => f t -> Text
commaSeparated ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Text, BackendType) -> Text
forall a b. (a, b) -> a
fst ((Text, BackendType) -> Text) -> [(Text, BackendType)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, BackendType)]
backendTextNameLookup
in Text -> Maybe BackendType
backendTypeFromText Text
txt
Maybe BackendType -> Parser BackendType -> Parser BackendType
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` String -> Parser BackendType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String
"got: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
txt String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
", expected one of: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
unpack Text
uniqueBackends)
backendTypeFromBackendSourceKind :: BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind :: forall (b :: BackendType). BackendSourceKind b -> BackendType
backendTypeFromBackendSourceKind = \case
BackendSourceKind b
PostgresVanillaKind -> PostgresKind -> BackendType
Postgres PostgresKind
Vanilla
BackendSourceKind b
PostgresCitusKind -> PostgresKind -> BackendType
Postgres PostgresKind
Citus
BackendSourceKind b
PostgresCockroachKind -> PostgresKind -> BackendType
Postgres PostgresKind
Cockroach
BackendSourceKind b
MSSQLKind -> BackendType
MSSQL
BackendSourceKind b
BigQueryKind -> BackendType
BigQuery
DataConnectorKind DataConnectorName
_ -> BackendType
DataConnector