{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.DDL.Schema.Source
( AddSource,
DropSource (..),
RenameSource,
UpdateSource,
runAddSource,
runDropSource,
runRenameSource,
dropSource,
runPostDropSourceHook,
runUpdateSource,
)
where
import Control.Lens (at, (.~), (^.))
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson.Extended
import Data.Aeson.Extended qualified as J
import Data.Aeson.TH
import Data.Has
import Data.HashMap.Strict qualified as HM
import Data.HashMap.Strict.InsOrd qualified as OMap
import Data.Text.Extended
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.Logging qualified as L
import Hasura.Prelude
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Metadata.Backend
import Hasura.RQL.Types.Metadata.Instances ()
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.SchemaCache.Build
import Hasura.RQL.Types.SchemaCacheTypes
import Hasura.RQL.Types.Source
import Hasura.RQL.Types.SourceCustomization
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.SQL.Backend
import Hasura.Server.Logging (MetadataLog (..))
data AddSource b = AddSource
{ AddSource b -> SourceName
_asName :: SourceName,
AddSource b -> BackendSourceKind b
_asBackendKind :: BackendSourceKind b,
AddSource b -> SourceConnConfiguration b
_asConfiguration :: SourceConnConfiguration b,
AddSource b -> Bool
_asReplaceConfiguration :: Bool,
AddSource b -> SourceCustomization
_asCustomization :: SourceCustomization
}
instance (Backend b) => FromJSONWithContext (BackendSourceKind b) (AddSource b) where
parseJSONWithContext :: BackendSourceKind b -> Value -> Parser (AddSource b)
parseJSONWithContext BackendSourceKind b
backendKind = String
-> (Object -> Parser (AddSource b))
-> Value
-> Parser (AddSource b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"AddSource" ((Object -> Parser (AddSource b)) -> Value -> Parser (AddSource b))
-> (Object -> Parser (AddSource b))
-> Value
-> Parser (AddSource b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
SourceName
-> BackendSourceKind b
-> SourceConnConfiguration b
-> Bool
-> SourceCustomization
-> AddSource b
forall (b :: BackendType).
SourceName
-> BackendSourceKind b
-> SourceConnConfiguration b
-> Bool
-> SourceCustomization
-> AddSource b
AddSource
(SourceName
-> BackendSourceKind b
-> SourceConnConfiguration b
-> Bool
-> SourceCustomization
-> AddSource b)
-> Parser SourceName
-> Parser
(BackendSourceKind b
-> SourceConnConfiguration b
-> Bool
-> SourceCustomization
-> AddSource b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser
(BackendSourceKind b
-> SourceConnConfiguration b
-> Bool
-> SourceCustomization
-> AddSource b)
-> Parser (BackendSourceKind b)
-> Parser
(SourceConnConfiguration b
-> Bool -> SourceCustomization -> AddSource b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> BackendSourceKind b -> Parser (BackendSourceKind b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure BackendSourceKind b
backendKind
Parser
(SourceConnConfiguration b
-> Bool -> SourceCustomization -> AddSource b)
-> Parser (SourceConnConfiguration b)
-> Parser (Bool -> SourceCustomization -> AddSource b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (SourceConnConfiguration b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"configuration"
Parser (Bool -> SourceCustomization -> AddSource b)
-> Parser Bool -> Parser (SourceCustomization -> AddSource b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"replace_configuration" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Parser (SourceCustomization -> AddSource b)
-> Parser SourceCustomization -> Parser (AddSource b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe SourceCustomization)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"customization" Parser (Maybe SourceCustomization)
-> SourceCustomization -> Parser SourceCustomization
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceCustomization
emptySourceCustomization
runAddSource ::
forall m b.
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
AddSource b ->
m EncJSON
runAddSource :: AddSource b -> m EncJSON
runAddSource (AddSource SourceName
name BackendSourceKind b
backendKind SourceConnConfiguration b
sourceConfig Bool
replaceConfiguration SourceCustomization
sourceCustomization) = do
SourceCache
sources <- SchemaCache -> SourceCache
scSources (SchemaCache -> SourceCache) -> m SchemaCache -> m SourceCache
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m SchemaCache
forall (m :: * -> *). CacheRM m => m SchemaCache
askSchemaCache
MetadataModifier
metadataModifier <-
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier
((Metadata -> Metadata) -> MetadataModifier)
-> m (Metadata -> Metadata) -> m MetadataModifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> if SourceName -> SourceCache -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
HM.member SourceName
name SourceCache
sources
then
if Bool
replaceConfiguration
then do
let sMetadata :: (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata
sMetadata = (Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((SourceMetadata b -> Identity (SourceMetadata b))
-> Sources -> Identity Sources)
-> (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
name ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (SourceMetadata b -> Identity (SourceMetadata b))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backend b => Prism' BackendSourceMetadata (SourceMetadata b)
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b
updateConfig :: Metadata -> Metadata
updateConfig = (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata
sMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata)
-> ((SourceConnConfiguration b
-> Identity (SourceConnConfiguration b))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (SourceConnConfiguration b
-> Identity (SourceConnConfiguration b))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceConnConfiguration b -> Identity (SourceConnConfiguration b))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType).
Lens' (SourceMetadata b) (SourceConnConfiguration b)
smConfiguration ((SourceConnConfiguration b
-> Identity (SourceConnConfiguration b))
-> Metadata -> Identity Metadata)
-> SourceConnConfiguration b -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> b -> s -> t
.~ SourceConnConfiguration b
sourceConfig
updateCustomization :: Metadata -> Metadata
updateCustomization = (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata
sMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata)
-> ((SourceCustomization -> Identity SourceCustomization)
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (SourceCustomization -> Identity SourceCustomization)
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceCustomization -> Identity SourceCustomization)
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType).
Lens' (SourceMetadata b) SourceCustomization
smCustomization ((SourceCustomization -> Identity SourceCustomization)
-> Metadata -> Identity Metadata)
-> SourceCustomization -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> b -> s -> t
.~ SourceCustomization
sourceCustomization
(Metadata -> Metadata) -> m (Metadata -> Metadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Metadata -> Metadata) -> m (Metadata -> Metadata))
-> (Metadata -> Metadata) -> m (Metadata -> Metadata)
forall a b. (a -> b) -> a -> b
$ Metadata -> Metadata
updateConfig (Metadata -> Metadata)
-> (Metadata -> Metadata) -> Metadata -> Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> Metadata
updateCustomization
else Code -> Text -> m (Metadata -> Metadata)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
AlreadyExists (Text -> m (Metadata -> Metadata))
-> Text -> m (Metadata -> Metadata)
forall a b. (a -> b) -> a -> b
$ Text
"source with name " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
name SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" already exists"
else do
let sourceMetadata :: BackendSourceMetadata
sourceMetadata =
SourceName
-> BackendSourceKind b
-> SourceConnConfiguration b
-> SourceCustomization
-> BackendSourceMetadata
forall (b :: BackendType).
Backend b =>
SourceName
-> BackendSourceKind b
-> SourceConnConfiguration b
-> SourceCustomization
-> BackendSourceMetadata
mkSourceMetadata @b SourceName
name BackendSourceKind b
backendKind SourceConnConfiguration b
sourceConfig SourceCustomization
sourceCustomization
(Metadata -> Metadata) -> m (Metadata -> Metadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Metadata -> Metadata) -> m (Metadata -> Metadata))
-> (Metadata -> Metadata) -> m (Metadata -> Metadata)
forall a b. (a -> b) -> a -> b
$ (Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> (Sources -> Sources) -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ SourceName -> BackendSourceMetadata -> Sources -> Sources
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.insert SourceName
name BackendSourceMetadata
sourceMetadata
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor (SourceName -> MetadataObjId
MOSource SourceName
name) MetadataModifier
metadataModifier
EncJSON -> m EncJSON
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
data RenameSource = RenameSource
{ RenameSource -> SourceName
_rmName :: SourceName,
RenameSource -> SourceName
_rmNewName :: SourceName
}
$(deriveFromJSON hasuraJSON ''RenameSource)
runRenameSource ::
forall m.
(MonadError QErr m, CacheRWM m, MetadataM m) =>
RenameSource ->
m EncJSON
runRenameSource :: RenameSource -> m EncJSON
runRenameSource RenameSource {SourceName
_rmNewName :: SourceName
_rmName :: SourceName
_rmNewName :: RenameSource -> SourceName
_rmName :: RenameSource -> SourceName
..} = do
SourceCache
sources <- SchemaCache -> SourceCache
scSources (SchemaCache -> SourceCache) -> m SchemaCache -> m SourceCache
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m SchemaCache
forall (m :: * -> *). CacheRM m => m SchemaCache
askSchemaCache
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SourceName -> SourceCache -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
HM.member SourceName
_rmName SourceCache
sources) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotExists (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Could not find source with name " Text -> SourceName -> Text
forall t. ToTxt t => Text -> t -> Text
<>> SourceName
_rmName
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SourceName -> SourceCache -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
HM.member SourceName
_rmNewName SourceCache
sources) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
AlreadyExists (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Source with name " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
_rmNewName SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" already exists"
let metadataModifier :: MetadataModifier
metadataModifier =
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$
(Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> (Sources -> Sources) -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ SourceName -> SourceName -> Sources -> Sources
renameBackendSourceMetadata SourceName
_rmName SourceName
_rmNewName
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor (SourceName -> MetadataObjId
MOSource SourceName
_rmNewName) MetadataModifier
metadataModifier
EncJSON -> m EncJSON
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
where
renameBackendSourceMetadata ::
SourceName ->
SourceName ->
OMap.InsOrdHashMap SourceName BackendSourceMetadata ->
OMap.InsOrdHashMap SourceName BackendSourceMetadata
renameBackendSourceMetadata :: SourceName -> SourceName -> Sources -> Sources
renameBackendSourceMetadata SourceName
oldKey SourceName
newKey Sources
m =
case SourceName -> Sources -> Maybe BackendSourceMetadata
forall k v. (Eq k, Hashable k) => k -> InsOrdHashMap k v -> Maybe v
OMap.lookup SourceName
oldKey Sources
m of
Just BackendSourceMetadata
val ->
let renamedSource :: BackendSourceMetadata
renamedSource = AnyBackend SourceMetadata -> BackendSourceMetadata
BackendSourceMetadata (AnyBackend SourceMetadata
-> (forall (b :: BackendType).
SourceMetadata b -> SourceMetadata b)
-> AnyBackend SourceMetadata
forall (i :: BackendType -> *) (j :: BackendType -> *).
AnyBackend i
-> (forall (b :: BackendType). i b -> j b) -> AnyBackend j
AB.mapBackend (BackendSourceMetadata -> AnyBackend SourceMetadata
unBackendSourceMetadata BackendSourceMetadata
val) (SourceName -> SourceMetadata b -> SourceMetadata b
forall (b :: BackendType).
SourceName -> SourceMetadata b -> SourceMetadata b
renameSource SourceName
newKey))
in SourceName -> BackendSourceMetadata -> Sources -> Sources
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.insert SourceName
newKey BackendSourceMetadata
renamedSource (Sources -> Sources) -> Sources -> Sources
forall a b. (a -> b) -> a -> b
$ SourceName -> Sources -> Sources
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.delete SourceName
oldKey (Sources -> Sources) -> Sources -> Sources
forall a b. (a -> b) -> a -> b
$ Sources
m
Maybe BackendSourceMetadata
Nothing -> Sources
m
renameSource :: forall b. SourceName -> SourceMetadata b -> SourceMetadata b
renameSource :: SourceName -> SourceMetadata b -> SourceMetadata b
renameSource SourceName
newName SourceMetadata b
metadata = SourceMetadata b
metadata {_smName :: SourceName
_smName = SourceName
newName}
data DropSource = DropSource
{ DropSource -> SourceName
_dsName :: SourceName,
DropSource -> Bool
_dsCascade :: Bool
}
deriving (Int -> DropSource -> ShowS
[DropSource] -> ShowS
DropSource -> String
(Int -> DropSource -> ShowS)
-> (DropSource -> String)
-> ([DropSource] -> ShowS)
-> Show DropSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DropSource] -> ShowS
$cshowList :: [DropSource] -> ShowS
show :: DropSource -> String
$cshow :: DropSource -> String
showsPrec :: Int -> DropSource -> ShowS
$cshowsPrec :: Int -> DropSource -> ShowS
Show, DropSource -> DropSource -> Bool
(DropSource -> DropSource -> Bool)
-> (DropSource -> DropSource -> Bool) -> Eq DropSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DropSource -> DropSource -> Bool
$c/= :: DropSource -> DropSource -> Bool
== :: DropSource -> DropSource -> Bool
$c== :: DropSource -> DropSource -> Bool
Eq)
instance FromJSON DropSource where
parseJSON :: Value -> Parser DropSource
parseJSON = String
-> (Object -> Parser DropSource) -> Value -> Parser DropSource
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"DropSource" ((Object -> Parser DropSource) -> Value -> Parser DropSource)
-> (Object -> Parser DropSource) -> Value -> Parser DropSource
forall a b. (a -> b) -> a -> b
$ \Object
o ->
SourceName -> Bool -> DropSource
DropSource (SourceName -> Bool -> DropSource)
-> Parser SourceName -> Parser (Bool -> DropSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name" Parser (Bool -> DropSource) -> Parser Bool -> Parser DropSource
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"cascade" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
runDropSource ::
forall m r.
( MonadError QErr m,
CacheRWM m,
MonadIO m,
MonadBaseControl IO m,
MetadataM m,
MonadReader r m,
Has (L.Logger L.Hasura) r
) =>
DropSource ->
m EncJSON
runDropSource :: DropSource -> m EncJSON
runDropSource dropSourceInfo :: DropSource
dropSourceInfo@(DropSource SourceName
name Bool
cascade) = do
SchemaCache
schemaCache <- m SchemaCache
forall (m :: * -> *). CacheRM m => m SchemaCache
askSchemaCache
let sources :: SourceCache
sources = SchemaCache -> SourceCache
scSources SchemaCache
schemaCache
case SourceName -> SourceCache -> Maybe BackendSourceInfo
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup SourceName
name SourceCache
sources of
Just BackendSourceInfo
backendSourceInfo ->
BackendSourceInfo
-> (forall (b :: BackendType).
BackendMetadata b =>
SourceInfo b -> m ())
-> m ()
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @BackendMetadata BackendSourceInfo
backendSourceInfo ((forall (b :: BackendType).
BackendMetadata b =>
SourceInfo b -> m ())
-> m ())
-> (forall (b :: BackendType).
BackendMetadata b =>
SourceInfo b -> m ())
-> m ()
forall a b. (a -> b) -> a -> b
$ SchemaCache -> DropSource -> SourceInfo b -> m ()
forall (m :: * -> *) r (b :: BackendType).
(MonadError QErr m, CacheRWM m, MonadIO m, MonadBaseControl IO m,
MetadataM m, MonadReader r m, Has (Logger Hasura) r,
BackendMetadata b) =>
SchemaCache -> DropSource -> SourceInfo b -> m ()
dropSource SchemaCache
schemaCache DropSource
dropSourceInfo
Maybe BackendSourceInfo
Nothing -> do
Metadata
metadata <- m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
m BackendSourceMetadata -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m BackendSourceMetadata -> m ())
-> m BackendSourceMetadata -> m ()
forall a b. (a -> b) -> a -> b
$
Maybe BackendSourceMetadata
-> m BackendSourceMetadata -> m BackendSourceMetadata
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing (Metadata
metadata Metadata
-> Getting
(Maybe BackendSourceMetadata)
Metadata
(Maybe BackendSourceMetadata)
-> Maybe BackendSourceMetadata
forall s a. s -> Getting a s a -> a
^. (Sources -> Const (Maybe BackendSourceMetadata) Sources)
-> Metadata -> Const (Maybe BackendSourceMetadata) Metadata
Lens' Metadata Sources
metaSources ((Sources -> Const (Maybe BackendSourceMetadata) Sources)
-> Metadata -> Const (Maybe BackendSourceMetadata) Metadata)
-> ((Maybe BackendSourceMetadata
-> Const
(Maybe BackendSourceMetadata) (Maybe BackendSourceMetadata))
-> Sources -> Const (Maybe BackendSourceMetadata) Sources)
-> Getting
(Maybe BackendSourceMetadata)
Metadata
(Maybe BackendSourceMetadata)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Lens' Sources (Maybe (IxValue Sources))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Index Sources
SourceName
name) (m BackendSourceMetadata -> m BackendSourceMetadata)
-> m BackendSourceMetadata -> m BackendSourceMetadata
forall a b. (a -> b) -> a -> b
$
Code -> Text -> m BackendSourceMetadata
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotExists (Text -> m BackendSourceMetadata)
-> Text -> m BackendSourceMetadata
forall a b. (a -> b) -> a -> b
$ Text
"source with name " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
name SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" does not exist"
if Bool
cascade
then
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
Unexpected (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"source with name " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
name SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" is inconsistent"
else
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor (SourceName -> MetadataObjId
MOSource SourceName
name) (SourceName -> MetadataModifier
dropSourceMetadataModifier SourceName
name)
EncJSON -> m EncJSON
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
dropSourceMetadataModifier :: SourceName -> MetadataModifier
dropSourceMetadataModifier :: SourceName -> MetadataModifier
dropSourceMetadataModifier SourceName
sourceName = (Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ (Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> (Sources -> Sources) -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ SourceName -> Sources -> Sources
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OMap.delete SourceName
sourceName
dropSource ::
forall m r b.
( MonadError QErr m,
CacheRWM m,
MonadIO m,
MonadBaseControl IO m,
MetadataM m,
MonadReader r m,
Has (L.Logger L.Hasura) r,
BackendMetadata b
) =>
SchemaCache ->
DropSource ->
SourceInfo b ->
m ()
dropSource :: SchemaCache -> DropSource -> SourceInfo b -> m ()
dropSource SchemaCache
_schemaCache (DropSource SourceName
sourceName Bool
cascade) SourceInfo b
sourceInfo = do
SchemaCache
schemaCache <- m SchemaCache
forall (m :: * -> *). CacheRM m => m SchemaCache
askSchemaCache
let remoteDeps :: [SchemaObjId]
remoteDeps = SchemaCache -> SourceName -> [SchemaObjId]
getRemoteDependencies SchemaCache
schemaCache SourceName
sourceName
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Bool
cascade Bool -> Bool -> Bool
|| [SchemaObjId] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SchemaObjId]
remoteDeps) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
[SchemaObjId] -> m ()
forall (m :: * -> *). MonadError QErr m => [SchemaObjId] -> m ()
reportDependentObjectsExist [SchemaObjId]
remoteDeps
MetadataModifier
metadataModifier <- WriterT MetadataModifier m () -> m MetadataModifier
forall (m :: * -> *) w a. Monad m => WriterT w m a -> m w
execWriterT (WriterT MetadataModifier m () -> m MetadataModifier)
-> WriterT MetadataModifier m () -> m MetadataModifier
forall a b. (a -> b) -> a -> b
$ do
(SchemaObjId -> WriterT MetadataModifier m ())
-> [SchemaObjId] -> WriterT MetadataModifier m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ SchemaObjId -> WriterT MetadataModifier m ()
forall (m :: * -> *).
MonadError QErr m =>
SchemaObjId -> WriterT MetadataModifier m ()
purgeSourceAndSchemaDependencies [SchemaObjId]
remoteDeps
MetadataModifier -> WriterT MetadataModifier m ()
forall w (m :: * -> *). MonadWriter w m => w -> m ()
tell (MetadataModifier -> WriterT MetadataModifier m ())
-> MetadataModifier -> WriterT MetadataModifier m ()
forall a b. (a -> b) -> a -> b
$ SourceName -> MetadataModifier
dropSourceMetadataModifier SourceName
sourceName
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor (SourceName -> MetadataObjId
MOSource SourceName
sourceName) MetadataModifier
metadataModifier
SourceName -> SourceInfo b -> m ()
forall (m :: * -> *) r (b :: BackendType).
(MonadError QErr m, MonadIO m, MonadBaseControl IO m,
MonadReader r m, Has (Logger Hasura) r, BackendMetadata b) =>
SourceName -> SourceInfo b -> m ()
runPostDropSourceHook SourceName
sourceName SourceInfo b
sourceInfo
runPostDropSourceHook ::
forall m r b.
( MonadError QErr m,
MonadIO m,
MonadBaseControl IO m,
MonadReader r m,
Has (L.Logger L.Hasura) r,
BackendMetadata b
) =>
SourceName ->
SourceInfo b ->
m ()
runPostDropSourceHook :: SourceName -> SourceInfo b -> m ()
runPostDropSourceHook SourceName
sourceName SourceInfo b
sourceInfo = do
Logger Hasura
logger :: (L.Logger L.Hasura) <- (r -> Logger Hasura) -> m (Logger Hasura)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks r -> Logger Hasura
forall a t. Has a t => t -> a
getter
let sourceConfig :: SourceConfig b
sourceConfig = SourceInfo b -> SourceConfig b
forall (b :: BackendType). SourceInfo b -> SourceConfig b
_siConfiguration SourceInfo b
sourceInfo
let tableTriggersMap :: HashMap (TableName b) [TriggerName]
tableTriggersMap = (TableInfo b -> [TriggerName])
-> HashMap (TableName b) (TableInfo b)
-> HashMap (TableName b) [TriggerName]
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map (HashMap TriggerName (EventTriggerInfo b) -> [TriggerName]
forall k v. HashMap k v -> [k]
HM.keys (HashMap TriggerName (EventTriggerInfo b) -> [TriggerName])
-> (TableInfo b -> HashMap TriggerName (EventTriggerInfo b))
-> TableInfo b
-> [TriggerName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TableInfo b -> HashMap TriggerName (EventTriggerInfo b)
forall (b :: BackendType). TableInfo b -> EventTriggerInfoMap b
_tiEventTriggerInfoMap) (SourceInfo b -> HashMap (TableName b) (TableInfo b)
forall (b :: BackendType). SourceInfo b -> TableCache b
_siTables SourceInfo b
sourceInfo)
ExceptT QErr m () -> m (Either QErr ())
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (SourceConfig b
-> HashMap (TableName b) [TriggerName] -> ExceptT QErr m ()
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, MonadIO m,
MonadBaseControl IO m) =>
SourceConfig b -> TableEventTriggers b -> m ()
postDropSourceHook @b SourceConfig b
sourceConfig HashMap (TableName b) [TriggerName]
tableTriggersMap) m (Either QErr ()) -> (Either QErr () -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (QErr -> m ()) -> (() -> m ()) -> Either QErr () -> m ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Logger Hasura -> QErr -> m ()
logDropSourceHookError Logger Hasura
logger) () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure
where
logDropSourceHookError :: Logger Hasura -> QErr -> m ()
logDropSourceHookError Logger Hasura
logger QErr
err =
let msg :: Text
msg =
Text
"Error executing cleanup actions after removing source '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName -> Text
forall a. ToTxt a => a -> Text
toTxt SourceName
sourceName
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'. Consider cleaning up tables in hdb_catalog schema manually."
in Logger Hasura
-> forall a (m :: * -> *).
(ToEngineLog a Hasura, MonadIO m) =>
a -> m ()
forall impl.
Logger impl
-> forall a (m :: * -> *).
(ToEngineLog a impl, MonadIO m) =>
a -> m ()
L.unLogger Logger Hasura
logger (MetadataLog -> m ()) -> MetadataLog -> m ()
forall a b. (a -> b) -> a -> b
$ LogLevel -> Text -> Value -> MetadataLog
MetadataLog LogLevel
L.LevelWarn Text
msg (QErr -> Value
forall a. ToJSON a => a -> Value
J.toJSON QErr
err)
data UpdateSource b = UpdateSource
{ UpdateSource b -> SourceName
_usName :: SourceName,
UpdateSource b -> Maybe (SourceConnConfiguration b)
_usConfiguration :: Maybe (SourceConnConfiguration b),
UpdateSource b -> Maybe SourceCustomization
_usCustomization :: Maybe SourceCustomization
}
instance (Backend b) => FromJSONWithContext (BackendSourceKind b) (UpdateSource b) where
parseJSONWithContext :: BackendSourceKind b -> Value -> Parser (UpdateSource b)
parseJSONWithContext BackendSourceKind b
_ = String
-> (Object -> Parser (UpdateSource b))
-> Value
-> Parser (UpdateSource b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UpdateSource" ((Object -> Parser (UpdateSource b))
-> Value -> Parser (UpdateSource b))
-> (Object -> Parser (UpdateSource b))
-> Value
-> Parser (UpdateSource b)
forall a b. (a -> b) -> a -> b
$ \Object
o ->
SourceName
-> Maybe (SourceConnConfiguration b)
-> Maybe SourceCustomization
-> UpdateSource b
forall (b :: BackendType).
SourceName
-> Maybe (SourceConnConfiguration b)
-> Maybe SourceCustomization
-> UpdateSource b
UpdateSource
(SourceName
-> Maybe (SourceConnConfiguration b)
-> Maybe SourceCustomization
-> UpdateSource b)
-> Parser SourceName
-> Parser
(Maybe (SourceConnConfiguration b)
-> Maybe SourceCustomization -> UpdateSource b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Parser
(Maybe (SourceConnConfiguration b)
-> Maybe SourceCustomization -> UpdateSource b)
-> Parser (Maybe (SourceConnConfiguration b))
-> Parser (Maybe SourceCustomization -> UpdateSource b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe (SourceConnConfiguration b))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"configuration"
Parser (Maybe SourceCustomization -> UpdateSource b)
-> Parser (Maybe SourceCustomization) -> Parser (UpdateSource b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe SourceCustomization)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"customization"
runUpdateSource ::
forall m b.
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
UpdateSource b ->
m EncJSON
runUpdateSource :: UpdateSource b -> m EncJSON
runUpdateSource (UpdateSource SourceName
name Maybe (SourceConnConfiguration b)
sourceConfig Maybe SourceCustomization
sourceCustomization) = do
SourceCache
sources <- SchemaCache -> SourceCache
scSources (SchemaCache -> SourceCache) -> m SchemaCache -> m SourceCache
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m SchemaCache
forall (m :: * -> *). CacheRM m => m SchemaCache
askSchemaCache
MetadataModifier
metadataModifier <-
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier
((Metadata -> Metadata) -> MetadataModifier)
-> m (Metadata -> Metadata) -> m MetadataModifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> if SourceName -> SourceCache -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
HM.member SourceName
name SourceCache
sources
then do
let sMetadata :: (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata
sMetadata = (Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((SourceMetadata b -> Identity (SourceMetadata b))
-> Sources -> Identity Sources)
-> (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
name ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (SourceMetadata b -> Identity (SourceMetadata b))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Backend b => Prism' BackendSourceMetadata (SourceMetadata b)
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b
updateConfig :: Metadata -> Metadata
updateConfig = (Metadata -> Metadata)
-> (SourceConnConfiguration b -> Metadata -> Metadata)
-> Maybe (SourceConnConfiguration b)
-> Metadata
-> Metadata
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Metadata -> Metadata
forall a. a -> a
id (\SourceConnConfiguration b
scc -> (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata
sMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata)
-> ((SourceConnConfiguration b
-> Identity (SourceConnConfiguration b))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (SourceConnConfiguration b
-> Identity (SourceConnConfiguration b))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceConnConfiguration b -> Identity (SourceConnConfiguration b))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType).
Lens' (SourceMetadata b) (SourceConnConfiguration b)
smConfiguration ((SourceConnConfiguration b
-> Identity (SourceConnConfiguration b))
-> Metadata -> Identity Metadata)
-> SourceConnConfiguration b -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> b -> s -> t
.~ SourceConnConfiguration b
scc) Maybe (SourceConnConfiguration b)
sourceConfig
updateCustomization :: Metadata -> Metadata
updateCustomization = (Metadata -> Metadata)
-> (SourceCustomization -> Metadata -> Metadata)
-> Maybe SourceCustomization
-> Metadata
-> Metadata
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Metadata -> Metadata
forall a. a -> a
id (\SourceCustomization
scc -> (SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata
sMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> Metadata -> Identity Metadata)
-> ((SourceCustomization -> Identity SourceCustomization)
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (SourceCustomization -> Identity SourceCustomization)
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceCustomization -> Identity SourceCustomization)
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType).
Lens' (SourceMetadata b) SourceCustomization
smCustomization ((SourceCustomization -> Identity SourceCustomization)
-> Metadata -> Identity Metadata)
-> SourceCustomization -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> b -> s -> t
.~ SourceCustomization
scc) Maybe SourceCustomization
sourceCustomization
(Metadata -> Metadata) -> m (Metadata -> Metadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Metadata -> Metadata) -> m (Metadata -> Metadata))
-> (Metadata -> Metadata) -> m (Metadata -> Metadata)
forall a b. (a -> b) -> a -> b
$ Metadata -> Metadata
updateConfig (Metadata -> Metadata)
-> (Metadata -> Metadata) -> Metadata -> Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> Metadata
updateCustomization
else do
Code -> Text -> m (Metadata -> Metadata)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotExists (Text -> m (Metadata -> Metadata))
-> Text -> m (Metadata -> Metadata)
forall a b. (a -> b) -> a -> b
$ Text
"source with name " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
name SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" does not exist"
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor (SourceName -> MetadataObjId
MOSource SourceName
name) MetadataModifier
metadataModifier
EncJSON -> m EncJSON
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg