module Hasura.RQL.DDL.ConnectionTemplate
( runTestConnectionTemplate,
TestConnectionTemplate (..),
BackendResolvedConnectionTemplate (..),
ResolvedConnectionTemplateWrapper (..),
)
where
import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON))
import Data.Aeson qualified as J
import Hasura.Backends.Postgres.Connection.Settings (ConnectionTemplate (..))
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Metadata (MetadataM)
import Hasura.RQL.Types.SchemaCache (CacheRM, askSourceConfig)
import Hasura.SQL.AnyBackend qualified as AB
data TestConnectionTemplate b = TestConnectionTemplate
{ forall (b :: BackendType). TestConnectionTemplate b -> SourceName
_tctSourceName :: SourceName,
forall (b :: BackendType).
TestConnectionTemplate b -> ConnectionTemplateRequestContext b
_tctRequestContext :: ConnectionTemplateRequestContext b,
forall (b :: BackendType).
TestConnectionTemplate b -> Maybe ConnectionTemplate
_tctConnectionTemplate :: (Maybe ConnectionTemplate)
}
instance (Backend b) => FromJSON (TestConnectionTemplate b) where
parseJSON :: Value -> Parser (TestConnectionTemplate b)
parseJSON Value
v =
((Object -> Parser (TestConnectionTemplate b))
-> Value -> Parser (TestConnectionTemplate b))
-> Value
-> (Object -> Parser (TestConnectionTemplate b))
-> Parser (TestConnectionTemplate b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (String
-> (Object -> Parser (TestConnectionTemplate b))
-> Value
-> Parser (TestConnectionTemplate b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"TestConnectionTemplate") Value
v ((Object -> Parser (TestConnectionTemplate b))
-> Parser (TestConnectionTemplate b))
-> (Object -> Parser (TestConnectionTemplate b))
-> Parser (TestConnectionTemplate b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
SourceName
-> ConnectionTemplateRequestContext b
-> Maybe ConnectionTemplate
-> TestConnectionTemplate b
forall (b :: BackendType).
SourceName
-> ConnectionTemplateRequestContext b
-> Maybe ConnectionTemplate
-> TestConnectionTemplate b
TestConnectionTemplate
(SourceName
-> ConnectionTemplateRequestContext b
-> Maybe ConnectionTemplate
-> TestConnectionTemplate b)
-> Parser SourceName
-> Parser
(ConnectionTemplateRequestContext b
-> Maybe ConnectionTemplate -> TestConnectionTemplate b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o
Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"source_name"
Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
J..!= SourceName
defaultSource
Parser
(ConnectionTemplateRequestContext b
-> Maybe ConnectionTemplate -> TestConnectionTemplate b)
-> Parser (ConnectionTemplateRequestContext b)
-> Parser (Maybe ConnectionTemplate -> TestConnectionTemplate b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (ConnectionTemplateRequestContext b)
forall a. FromJSON a => Object -> Key -> Parser a
J..: Key
"request_context"
Parser (Maybe ConnectionTemplate -> TestConnectionTemplate b)
-> Parser (Maybe ConnectionTemplate)
-> Parser (TestConnectionTemplate b)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o
Object -> Key -> Parser (Maybe ConnectionTemplate)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"connection_template"
runTestConnectionTemplate ::
forall b m.
(MonadError QErr m, CacheRM m, Backend b, MetadataM m) =>
TestConnectionTemplate b ->
m EncJSON
runTestConnectionTemplate :: forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRM m, Backend b, MetadataM m) =>
TestConnectionTemplate b -> m EncJSON
runTestConnectionTemplate (TestConnectionTemplate SourceName
sourceName ConnectionTemplateRequestContext b
requestContext Maybe ConnectionTemplate
connectionTemplateMaybe) = do
SourceConfig b
sourceConfig <- forall (b :: BackendType) (m :: * -> *).
(CacheRM m, MonadError QErr m, Backend b, MetadataM m) =>
SourceName -> m (SourceConfig b)
askSourceConfig @b SourceName
sourceName
Either QErr EncJSON -> m EncJSON
forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither (Either QErr EncJSON -> m EncJSON)
-> Either QErr EncJSON -> m EncJSON
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
Backend b =>
SourceConfig b
-> ConnectionTemplateRequestContext b
-> Maybe ConnectionTemplate
-> Either QErr EncJSON
resolveConnectionTemplate @b SourceConfig b
sourceConfig ConnectionTemplateRequestContext b
requestContext Maybe ConnectionTemplate
connectionTemplateMaybe
newtype ResolvedConnectionTemplateWrapper b = ResolvedConnectionTemplateWrapper
{ forall (b :: BackendType).
ResolvedConnectionTemplateWrapper b -> ResolvedConnectionTemplate b
getResolvedConnectionTemplateWrapper :: ResolvedConnectionTemplate b
}
newtype BackendResolvedConnectionTemplate = BackendResolvedConnectionTemplate
{ BackendResolvedConnectionTemplate
-> AnyBackend ResolvedConnectionTemplateWrapper
getBackendResolvedConnectionTemplate :: AB.AnyBackend ResolvedConnectionTemplateWrapper
}
instance ToJSON BackendResolvedConnectionTemplate where
toJSON :: BackendResolvedConnectionTemplate -> Value
toJSON BackendResolvedConnectionTemplate
resolvedConnectionTemplate =
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend
@Backend
(BackendResolvedConnectionTemplate
-> AnyBackend ResolvedConnectionTemplateWrapper
getBackendResolvedConnectionTemplate BackendResolvedConnectionTemplate
resolvedConnectionTemplate)
((forall (b :: BackendType).
Backend b =>
ResolvedConnectionTemplateWrapper b -> Value)
-> Value)
-> (forall (b :: BackendType).
Backend b =>
ResolvedConnectionTemplateWrapper b -> Value)
-> Value
forall a b. (a -> b) -> a -> b
$ \(ResolvedConnectionTemplateWrapper b
resolvedConnectionTemplate' :: ResolvedConnectionTemplateWrapper b) ->
[Pair] -> Value
J.object
[ Key
"result" Key -> ResolvedConnectionTemplate b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
J..= ResolvedConnectionTemplateWrapper b -> ResolvedConnectionTemplate b
forall (b :: BackendType).
ResolvedConnectionTemplateWrapper b -> ResolvedConnectionTemplate b
getResolvedConnectionTemplateWrapper ResolvedConnectionTemplateWrapper b
resolvedConnectionTemplate'
]