{-# LANGUAGE UndecidableInstances #-}
module Hasura.LogicalModel.API
( GetLogicalModel (..),
TrackLogicalModel (..),
UntrackLogicalModel (..),
runGetLogicalModel,
execTrackLogicalModel,
execUntrackLogicalModel,
dropLogicalModelInMetadata,
CreateLogicalModelPermission (..),
DropLogicalModelPermission (..),
runCreateSelectLogicalModelPermission,
runDropSelectLogicalModelPermission,
module Hasura.LogicalModel.Types,
)
where
import Autodocodec (HasCodec)
import Autodocodec qualified as AC
import Control.Lens (Traversal', has, preview, (^?))
import Data.Aeson
import Data.HashMap.Strict.InsOrd.Extended qualified as InsOrdHashMap
import Data.Text.Extended (toTxt, (<<>))
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.LogicalModel.Lenses (lmmSelectPermissions)
import Hasura.LogicalModel.Metadata (LogicalModelMetadata (..))
import Hasura.LogicalModel.Types (LogicalModelField, LogicalModelName, logicalModelFieldMapCodec)
import Hasura.Prelude
import Hasura.RQL.Types.Backend (Backend (..))
import Hasura.RQL.Types.BackendTag (backendPrefix, backendTag, reify)
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Common (SourceName, defaultSource, sourceNameToText, successMsg)
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Metadata.Backend
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.Permission (PermDef (_pdRole), SelPerm)
import Hasura.RQL.Types.Roles (RoleName)
import Hasura.RQL.Types.SchemaCache.Build
import Hasura.SQL.AnyBackend qualified as AB
data TrackLogicalModel (b :: BackendType) = TrackLogicalModel
{ forall (b :: BackendType). TrackLogicalModel b -> SourceName
tlmSource :: SourceName,
forall (b :: BackendType). TrackLogicalModel b -> LogicalModelName
tlmName :: LogicalModelName,
forall (b :: BackendType). TrackLogicalModel b -> Maybe Text
tlmDescription :: Maybe Text,
forall (b :: BackendType).
TrackLogicalModel b
-> InsOrdHashMap (Column b) (LogicalModelField b)
tlmFields :: InsOrdHashMap.InsOrdHashMap (Column b) (LogicalModelField b)
}
instance (Backend b) => HasCodec (TrackLogicalModel b) where
codec :: JSONCodec (TrackLogicalModel b)
codec =
Text
-> JSONCodec (TrackLogicalModel b)
-> JSONCodec (TrackLogicalModel b)
forall input output.
Text -> ValueCodec input output -> ValueCodec input output
AC.CommentCodec
(Text
"A request to track a logical model")
(JSONCodec (TrackLogicalModel b)
-> JSONCodec (TrackLogicalModel b))
-> JSONCodec (TrackLogicalModel b)
-> JSONCodec (TrackLogicalModel b)
forall a b. (a -> b) -> a -> b
$ Text
-> ObjectCodec (TrackLogicalModel b) (TrackLogicalModel b)
-> JSONCodec (TrackLogicalModel b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"TrackLogicalModel")
(ObjectCodec (TrackLogicalModel b) (TrackLogicalModel b)
-> JSONCodec (TrackLogicalModel b))
-> ObjectCodec (TrackLogicalModel b) (TrackLogicalModel b)
-> JSONCodec (TrackLogicalModel b)
forall a b. (a -> b) -> a -> b
$ SourceName
-> LogicalModelName
-> Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b
forall (b :: BackendType).
SourceName
-> LogicalModelName
-> Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b
TrackLogicalModel
(SourceName
-> LogicalModelName
-> Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
-> Codec Object (TrackLogicalModel b) SourceName
-> Codec
Object
(TrackLogicalModel b)
(LogicalModelName
-> Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ObjectCodec SourceName SourceName
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
AC.requiredField Text
"source" Text
sourceDoc
ObjectCodec SourceName SourceName
-> (TrackLogicalModel b -> SourceName)
-> Codec Object (TrackLogicalModel b) SourceName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackLogicalModel b -> SourceName
forall (b :: BackendType). TrackLogicalModel b -> SourceName
tlmSource
Codec
Object
(TrackLogicalModel b)
(LogicalModelName
-> Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
-> Codec Object (TrackLogicalModel b) LogicalModelName
-> Codec
Object
(TrackLogicalModel b)
(Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
forall a b.
Codec Object (TrackLogicalModel b) (a -> b)
-> Codec Object (TrackLogicalModel b) a
-> Codec Object (TrackLogicalModel b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec LogicalModelName LogicalModelName
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
AC.requiredField Text
"name" Text
nameDoc
ObjectCodec LogicalModelName LogicalModelName
-> (TrackLogicalModel b -> LogicalModelName)
-> Codec Object (TrackLogicalModel b) LogicalModelName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackLogicalModel b -> LogicalModelName
forall (b :: BackendType). TrackLogicalModel b -> LogicalModelName
tlmName
Codec
Object
(TrackLogicalModel b)
(Maybe Text
-> InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
-> Codec Object (TrackLogicalModel b) (Maybe Text)
-> Codec
Object
(TrackLogicalModel b)
(InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
forall a b.
Codec Object (TrackLogicalModel b) (a -> b)
-> Codec Object (TrackLogicalModel b) a
-> Codec Object (TrackLogicalModel b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
AC.optionalField Text
"description" Text
descriptionDoc
ObjectCodec (Maybe Text) (Maybe Text)
-> (TrackLogicalModel b -> Maybe Text)
-> Codec Object (TrackLogicalModel b) (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackLogicalModel b -> Maybe Text
forall (b :: BackendType). TrackLogicalModel b -> Maybe Text
tlmDescription
Codec
Object
(TrackLogicalModel b)
(InsOrdHashMap (Column b) (LogicalModelField b)
-> TrackLogicalModel b)
-> Codec
Object
(TrackLogicalModel b)
(InsOrdHashMap (Column b) (LogicalModelField b))
-> ObjectCodec (TrackLogicalModel b) (TrackLogicalModel b)
forall a b.
Codec Object (TrackLogicalModel b) (a -> b)
-> Codec Object (TrackLogicalModel b) a
-> Codec Object (TrackLogicalModel b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> ValueCodec
(InsOrdHashMap (Column b) (LogicalModelField b))
(InsOrdHashMap (Column b) (LogicalModelField b))
-> Text
-> ObjectCodec
(InsOrdHashMap (Column b) (LogicalModelField b))
(InsOrdHashMap (Column b) (LogicalModelField b))
forall input output.
Text -> ValueCodec input output -> Text -> ObjectCodec input output
AC.requiredFieldWith Text
"fields" ValueCodec
(InsOrdHashMap (Column b) (LogicalModelField b))
(InsOrdHashMap (Column b) (LogicalModelField b))
forall (b :: BackendType).
Backend b =>
Codec
Value
(InsOrdHashMap (Column b) (LogicalModelField b))
(InsOrdHashMap (Column b) (LogicalModelField b))
logicalModelFieldMapCodec Text
fieldsDoc
ObjectCodec
(InsOrdHashMap (Column b) (LogicalModelField b))
(InsOrdHashMap (Column b) (LogicalModelField b))
-> (TrackLogicalModel b
-> InsOrdHashMap (Column b) (LogicalModelField b))
-> Codec
Object
(TrackLogicalModel b)
(InsOrdHashMap (Column b) (LogicalModelField b))
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackLogicalModel b
-> InsOrdHashMap (Column b) (LogicalModelField b)
forall (b :: BackendType).
TrackLogicalModel b
-> InsOrdHashMap (Column b) (LogicalModelField b)
tlmFields
where
sourceDoc :: Text
sourceDoc = Text
"The source in which this logical model should be tracked"
nameDoc :: Text
nameDoc = Text
"Root field name for the logical model"
fieldsDoc :: Text
fieldsDoc = Text
"Return type of the expression"
descriptionDoc :: Text
descriptionDoc = Text
"A description of the query which appears in the graphql schema"
deriving via
(AC.Autodocodec (TrackLogicalModel b))
instance
(Backend b) => FromJSON (TrackLogicalModel b)
deriving via
(AC.Autodocodec (TrackLogicalModel b))
instance
(Backend b) => ToJSON (TrackLogicalModel b)
logicalModelTrackToMetadata ::
forall b.
TrackLogicalModel b ->
LogicalModelMetadata b
logicalModelTrackToMetadata :: forall (b :: BackendType).
TrackLogicalModel b -> LogicalModelMetadata b
logicalModelTrackToMetadata TrackLogicalModel {Maybe Text
InsOrdHashMap (Column b) (LogicalModelField b)
SourceName
LogicalModelName
tlmSource :: forall (b :: BackendType). TrackLogicalModel b -> SourceName
tlmName :: forall (b :: BackendType). TrackLogicalModel b -> LogicalModelName
tlmDescription :: forall (b :: BackendType). TrackLogicalModel b -> Maybe Text
tlmFields :: forall (b :: BackendType).
TrackLogicalModel b
-> InsOrdHashMap (Column b) (LogicalModelField b)
tlmSource :: SourceName
tlmName :: LogicalModelName
tlmDescription :: Maybe Text
tlmFields :: InsOrdHashMap (Column b) (LogicalModelField b)
..} =
LogicalModelMetadata
{ _lmmName :: LogicalModelName
_lmmName = LogicalModelName
tlmName,
_lmmFields :: InsOrdHashMap (Column b) (LogicalModelField b)
_lmmFields = InsOrdHashMap (Column b) (LogicalModelField b)
tlmFields,
_lmmSelectPermissions :: InsOrdHashMap RoleName (SelPermDef b)
_lmmSelectPermissions = InsOrdHashMap RoleName (SelPermDef b)
forall a. Monoid a => a
mempty,
_lmmDescription :: Maybe Text
_lmmDescription = Maybe Text
tlmDescription
}
data GetLogicalModel (b :: BackendType) = GetLogicalModel
{ forall (b :: BackendType). GetLogicalModel b -> SourceName
glmSource :: SourceName
}
deriving instance (Backend b) => Show (GetLogicalModel b)
deriving instance (Backend b) => Eq (GetLogicalModel b)
instance (Backend b) => FromJSON (GetLogicalModel b) where
parseJSON :: Value -> Parser (GetLogicalModel b)
parseJSON = String
-> (Object -> Parser (GetLogicalModel b))
-> Value
-> Parser (GetLogicalModel b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetLogicalModel" ((Object -> Parser (GetLogicalModel b))
-> Value -> Parser (GetLogicalModel b))
-> (Object -> Parser (GetLogicalModel b))
-> Value
-> Parser (GetLogicalModel b)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
SourceName
glmSource <- Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"source"
GetLogicalModel b -> Parser (GetLogicalModel b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure GetLogicalModel {SourceName
glmSource :: SourceName
glmSource :: SourceName
..}
instance (Backend b) => ToJSON (GetLogicalModel b) where
toJSON :: GetLogicalModel b -> Value
toJSON GetLogicalModel {SourceName
glmSource :: forall (b :: BackendType). GetLogicalModel b -> SourceName
glmSource :: SourceName
..} =
[Pair] -> Value
object
[ Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
glmSource
]
runGetLogicalModel ::
forall b m.
( BackendMetadata b,
MonadError QErr m,
MetadataM m
) =>
GetLogicalModel b ->
m EncJSON
runGetLogicalModel :: forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, MetadataM m) =>
GetLogicalModel b -> m EncJSON
runGetLogicalModel GetLogicalModel b
q = do
m ()
-> (SourceMetadata b -> m ()) -> Maybe (SourceMetadata b) -> m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
( Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound
(Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Source '"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName -> Text
sourceNameToText (GetLogicalModel b -> SourceName
forall (b :: BackendType). GetLogicalModel b -> SourceName
glmSource GetLogicalModel b
q)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' of kind "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BackendType -> Text
forall a. ToTxt a => a -> Text
toTxt (BackendTag b -> BackendType
forall (b :: BackendType). BackendTag b -> BackendType
reify (forall (b :: BackendType). HasTag b => BackendTag b
backendTag @b))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" not found."
)
(m () -> SourceMetadata b -> m ()
forall a b. a -> b -> a
const (m () -> SourceMetadata b -> m ())
-> m () -> SourceMetadata b -> m ()
forall a b. (a -> b) -> a -> b
$ () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
(Maybe (SourceMetadata b) -> m ())
-> (Metadata -> Maybe (SourceMetadata b)) -> Metadata -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
-> Metadata -> Maybe (SourceMetadata b)
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Sources -> Const (First (SourceMetadata b)) Sources)
-> Metadata -> Const (First (SourceMetadata b)) Metadata
Lens' Metadata Sources
metaSources ((Sources -> Const (First (SourceMetadata b)) Sources)
-> Metadata -> Const (First (SourceMetadata b)) Metadata)
-> ((SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> Sources -> Const (First (SourceMetadata b)) Sources)
-> Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
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 (GetLogicalModel b -> SourceName
forall (b :: BackendType). GetLogicalModel b -> SourceName
glmSource GetLogicalModel b
q) ((BackendSourceMetadata
-> Const (First (SourceMetadata b)) BackendSourceMetadata)
-> Sources -> Const (First (SourceMetadata b)) Sources)
-> ((SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> BackendSourceMetadata
-> Const (First (SourceMetadata b)) BackendSourceMetadata)
-> (SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> Sources
-> Const (First (SourceMetadata b)) Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b)
(Metadata -> m ()) -> m Metadata -> m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
Metadata
metadata <- m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
let logicalModels :: Maybe (LogicalModels b)
logicalModels :: Maybe (LogicalModels b)
logicalModels = Metadata
metadata Metadata
-> Getting (First (LogicalModels b)) Metadata (LogicalModels b)
-> Maybe (LogicalModels b)
forall s a. s -> Getting (First a) s a -> Maybe a
^? SourceName -> Traversal' Metadata (LogicalModels b)
forall (b :: BackendType).
Backend b =>
SourceName -> Traversal' Metadata (LogicalModels b)
getLogicalModels (GetLogicalModel b -> SourceName
forall (b :: BackendType). GetLogicalModel b -> SourceName
glmSource GetLogicalModel b
q)
EncJSON -> m EncJSON
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe [LogicalModelMetadata b] -> EncJSON
forall a. ToJSON a => a -> EncJSON
encJFromJValue (LogicalModels b -> [LogicalModelMetadata b]
forall k v. InsOrdHashMap k v -> [v]
InsOrdHashMap.elems (LogicalModels b -> [LogicalModelMetadata b])
-> Maybe (LogicalModels b) -> Maybe [LogicalModelMetadata b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (LogicalModels b)
logicalModels))
getLogicalModels :: forall b. (Backend b) => SourceName -> Traversal' Metadata (LogicalModels b)
getLogicalModels :: forall (b :: BackendType).
Backend b =>
SourceName -> Traversal' Metadata (LogicalModels b)
getLogicalModels SourceName
sourceName =
(Sources -> f Sources) -> Metadata -> f Metadata
Lens' Metadata Sources
metaSources ((Sources -> f Sources) -> Metadata -> f Metadata)
-> ((LogicalModels b -> f (LogicalModels b))
-> Sources -> f Sources)
-> (LogicalModels b -> f (LogicalModels b))
-> Metadata
-> f 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
sourceName ((BackendSourceMetadata -> f BackendSourceMetadata)
-> Sources -> f Sources)
-> ((LogicalModels b -> f (LogicalModels b))
-> BackendSourceMetadata -> f BackendSourceMetadata)
-> (LogicalModels b -> f (LogicalModels b))
-> Sources
-> f Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceMetadata b -> f (SourceMetadata b))
-> BackendSourceMetadata -> f BackendSourceMetadata
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata ((SourceMetadata b -> f (SourceMetadata b))
-> BackendSourceMetadata -> f BackendSourceMetadata)
-> ((LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b))
-> (LogicalModels b -> f (LogicalModels b))
-> BackendSourceMetadata
-> f BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType) (f :: * -> *).
Functor f =>
(LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b)
smLogicalModels @b
execTrackLogicalModel ::
forall b m.
( BackendMetadata b,
MonadError QErr m
) =>
TrackLogicalModel b ->
Metadata ->
m (MetadataObjId, MetadataModifier)
execTrackLogicalModel :: forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m) =>
TrackLogicalModel b
-> Metadata -> m (MetadataObjId, MetadataModifier)
execTrackLogicalModel TrackLogicalModel b
trackLogicalModelRequest Metadata
metadata = do
SourceMetadata b
sourceMetadata <-
m (SourceMetadata b)
-> (SourceMetadata b -> m (SourceMetadata b))
-> Maybe (SourceMetadata b)
-> m (SourceMetadata b)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Code -> Text -> m (SourceMetadata b)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound (Text -> m (SourceMetadata b)) -> Text -> m (SourceMetadata b)
forall a b. (a -> b) -> a -> b
$ Text
"Source " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName -> Text
sourceNameToText SourceName
source Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" not found.") SourceMetadata b -> m (SourceMetadata b)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe (SourceMetadata b) -> m (SourceMetadata b))
-> (Metadata -> Maybe (SourceMetadata b))
-> Metadata
-> m (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
-> Metadata -> Maybe (SourceMetadata b)
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Sources -> Const (First (SourceMetadata b)) Sources)
-> Metadata -> Const (First (SourceMetadata b)) Metadata
Lens' Metadata Sources
metaSources ((Sources -> Const (First (SourceMetadata b)) Sources)
-> Metadata -> Const (First (SourceMetadata b)) Metadata)
-> ((SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> Sources -> Const (First (SourceMetadata b)) Sources)
-> Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
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
source ((BackendSourceMetadata
-> Const (First (SourceMetadata b)) BackendSourceMetadata)
-> Sources -> Const (First (SourceMetadata b)) Sources)
-> ((SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> BackendSourceMetadata
-> Const (First (SourceMetadata b)) BackendSourceMetadata)
-> (SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> Sources
-> Const (First (SourceMetadata b)) Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b)
(Metadata -> m (SourceMetadata b))
-> Metadata -> m (SourceMetadata b)
forall a b. (a -> b) -> a -> b
$ Metadata
metadata
let (LogicalModelMetadata b
lmMetadata :: LogicalModelMetadata b) = TrackLogicalModel b -> LogicalModelMetadata b
forall (b :: BackendType).
TrackLogicalModel b -> LogicalModelMetadata b
logicalModelTrackToMetadata TrackLogicalModel b
trackLogicalModelRequest
fieldName :: LogicalModelName
fieldName = LogicalModelMetadata b -> LogicalModelName
forall (b :: BackendType).
LogicalModelMetadata b -> LogicalModelName
_lmmName LogicalModelMetadata b
lmMetadata
existingLogicalModels :: [LogicalModelName]
existingLogicalModels = InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> [LogicalModelName]
forall k v. InsOrdHashMap k v -> [k]
InsOrdHashMap.keys (SourceMetadata b
-> InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
forall (b :: BackendType). SourceMetadata b -> LogicalModels b
_smLogicalModels SourceMetadata b
sourceMetadata)
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (LogicalModelName
fieldName LogicalModelName -> [LogicalModelName] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [LogicalModelName]
existingLogicalModels) do
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
AlreadyTracked (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Logical model '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> LogicalModelName -> Text
forall a. ToTxt a => a -> Text
toTxt LogicalModelName
fieldName Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' is already tracked."
let metadataObj :: MetadataObjId
metadataObj =
SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
source
(AnyBackend SourceMetadataObjId -> MetadataObjId)
-> AnyBackend SourceMetadataObjId -> MetadataObjId
forall a b. (a -> b) -> a -> b
$ SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend
(SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
LogicalModelName -> SourceMetadataObjId b
SMOLogicalModel @b LogicalModelName
fieldName
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)
-> ((InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> Sources -> Identity Sources)
-> (InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata 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
source ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b)
smLogicalModels)
((InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> Identity
(InsOrdHashMap LogicalModelName (LogicalModelMetadata b)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> InsOrdHashMap LogicalModelName (LogicalModelMetadata b))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ LogicalModelName
-> LogicalModelMetadata b
-> InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
-> InsOrdHashMap LogicalModelName (LogicalModelMetadata b)
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.insert LogicalModelName
fieldName LogicalModelMetadata b
lmMetadata
(MetadataObjId, MetadataModifier)
-> m (MetadataObjId, MetadataModifier)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MetadataObjId
metadataObj, MetadataModifier
metadataModifier)
where
source :: SourceName
source = TrackLogicalModel b -> SourceName
forall (b :: BackendType). TrackLogicalModel b -> SourceName
tlmSource TrackLogicalModel b
trackLogicalModelRequest
data UntrackLogicalModel (b :: BackendType) = UntrackLogicalModel
{ forall (b :: BackendType). UntrackLogicalModel b -> SourceName
utlmSource :: SourceName,
forall (b :: BackendType).
UntrackLogicalModel b -> LogicalModelName
utlmName :: LogicalModelName
}
deriving instance Show (UntrackLogicalModel b)
deriving instance Eq (UntrackLogicalModel b)
instance FromJSON (UntrackLogicalModel b) where
parseJSON :: Value -> Parser (UntrackLogicalModel b)
parseJSON = String
-> (Object -> Parser (UntrackLogicalModel b))
-> Value
-> Parser (UntrackLogicalModel b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UntrackLogicalModel" ((Object -> Parser (UntrackLogicalModel b))
-> Value -> Parser (UntrackLogicalModel b))
-> (Object -> Parser (UntrackLogicalModel b))
-> Value
-> Parser (UntrackLogicalModel b)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
SourceName
utlmSource <- Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"source"
LogicalModelName
utlmName <- Object
o Object -> Key -> Parser LogicalModelName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
UntrackLogicalModel b -> Parser (UntrackLogicalModel b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure UntrackLogicalModel {SourceName
LogicalModelName
utlmSource :: SourceName
utlmName :: LogicalModelName
utlmSource :: SourceName
utlmName :: LogicalModelName
..}
instance ToJSON (UntrackLogicalModel b) where
toJSON :: UntrackLogicalModel b -> Value
toJSON UntrackLogicalModel {SourceName
LogicalModelName
utlmSource :: forall (b :: BackendType). UntrackLogicalModel b -> SourceName
utlmName :: forall (b :: BackendType).
UntrackLogicalModel b -> LogicalModelName
utlmSource :: SourceName
utlmName :: LogicalModelName
..} =
[Pair] -> Value
object
[ Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
utlmSource,
Key
"name" Key -> LogicalModelName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= LogicalModelName
utlmName
]
execUntrackLogicalModel ::
forall b m.
( BackendMetadata b,
MonadError QErr m
) =>
UntrackLogicalModel b ->
Metadata ->
m (MetadataObjId, MetadataModifier)
execUntrackLogicalModel :: forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m) =>
UntrackLogicalModel b
-> Metadata -> m (MetadataObjId, MetadataModifier)
execUntrackLogicalModel UntrackLogicalModel b
q Metadata
metadata = do
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceName -> LogicalModelName -> Metadata -> m ()
assertLogicalModelExists @b SourceName
source LogicalModelName
fieldName Metadata
metadata
let metadataObj :: MetadataObjId
metadataObj =
SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
source
(AnyBackend SourceMetadataObjId -> MetadataObjId)
-> AnyBackend SourceMetadataObjId -> MetadataObjId
forall a b. (a -> b) -> a -> b
$ SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend
(SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
LogicalModelName -> SourceMetadataObjId b
SMOLogicalModel @b LogicalModelName
fieldName
(MetadataObjId, MetadataModifier)
-> m (MetadataObjId, MetadataModifier)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MetadataObjId
metadataObj, forall (b :: BackendType).
BackendMetadata b =>
SourceName -> LogicalModelName -> MetadataModifier
dropLogicalModelInMetadata @b SourceName
source LogicalModelName
fieldName)
where
source :: SourceName
source = UntrackLogicalModel b -> SourceName
forall (b :: BackendType). UntrackLogicalModel b -> SourceName
utlmSource UntrackLogicalModel b
q
fieldName :: LogicalModelName
fieldName = UntrackLogicalModel b -> LogicalModelName
forall (b :: BackendType).
UntrackLogicalModel b -> LogicalModelName
utlmName UntrackLogicalModel b
q
data CreateLogicalModelPermission a (b :: BackendType) = CreateLogicalModelPermission
{ forall (a :: BackendType -> *) (b :: BackendType).
CreateLogicalModelPermission a b -> SourceName
clmpSource :: SourceName,
forall (a :: BackendType -> *) (b :: BackendType).
CreateLogicalModelPermission a b -> LogicalModelName
clmpName :: LogicalModelName,
forall (a :: BackendType -> *) (b :: BackendType).
CreateLogicalModelPermission a b -> PermDef b a
clmpInfo :: PermDef b a
}
deriving stock ((forall x.
CreateLogicalModelPermission a b
-> Rep (CreateLogicalModelPermission a b) x)
-> (forall x.
Rep (CreateLogicalModelPermission a b) x
-> CreateLogicalModelPermission a b)
-> Generic (CreateLogicalModelPermission a b)
forall x.
Rep (CreateLogicalModelPermission a b) x
-> CreateLogicalModelPermission a b
forall x.
CreateLogicalModelPermission a b
-> Rep (CreateLogicalModelPermission a b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (a :: BackendType -> *) (b :: BackendType) x.
Rep (CreateLogicalModelPermission a b) x
-> CreateLogicalModelPermission a b
forall (a :: BackendType -> *) (b :: BackendType) x.
CreateLogicalModelPermission a b
-> Rep (CreateLogicalModelPermission a b) x
$cfrom :: forall (a :: BackendType -> *) (b :: BackendType) x.
CreateLogicalModelPermission a b
-> Rep (CreateLogicalModelPermission a b) x
from :: forall x.
CreateLogicalModelPermission a b
-> Rep (CreateLogicalModelPermission a b) x
$cto :: forall (a :: BackendType -> *) (b :: BackendType) x.
Rep (CreateLogicalModelPermission a b) x
-> CreateLogicalModelPermission a b
to :: forall x.
Rep (CreateLogicalModelPermission a b) x
-> CreateLogicalModelPermission a b
Generic)
instance
(FromJSON (PermDef b a)) =>
FromJSON (CreateLogicalModelPermission a b)
where
parseJSON :: Value -> Parser (CreateLogicalModelPermission a b)
parseJSON = String
-> (Object -> Parser (CreateLogicalModelPermission a b))
-> Value
-> Parser (CreateLogicalModelPermission a b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CreateLogicalModelPermission" \Object
obj -> do
SourceName
clmpSource <- Object
obj Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source" Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
defaultSource
LogicalModelName
clmpName <- Object
obj Object -> Key -> Parser LogicalModelName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
PermDef b a
clmpInfo <- Value -> Parser (PermDef b a)
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
obj)
CreateLogicalModelPermission a b
-> Parser (CreateLogicalModelPermission a b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CreateLogicalModelPermission {SourceName
LogicalModelName
PermDef b a
clmpSource :: SourceName
clmpName :: LogicalModelName
clmpInfo :: PermDef b a
clmpSource :: SourceName
clmpName :: LogicalModelName
clmpInfo :: PermDef b a
..}
runCreateSelectLogicalModelPermission ::
forall b m.
(Backend b, CacheRWM m, MetadataM m, MonadError QErr m) =>
CreateLogicalModelPermission SelPerm b ->
m EncJSON
runCreateSelectLogicalModelPermission :: forall (b :: BackendType) (m :: * -> *).
(Backend b, CacheRWM m, MetadataM m, MonadError QErr m) =>
CreateLogicalModelPermission SelPerm b -> m EncJSON
runCreateSelectLogicalModelPermission CreateLogicalModelPermission {SourceName
LogicalModelName
PermDef b SelPerm
clmpSource :: forall (a :: BackendType -> *) (b :: BackendType).
CreateLogicalModelPermission a b -> SourceName
clmpName :: forall (a :: BackendType -> *) (b :: BackendType).
CreateLogicalModelPermission a b -> LogicalModelName
clmpInfo :: forall (a :: BackendType -> *) (b :: BackendType).
CreateLogicalModelPermission a b -> PermDef b a
clmpSource :: SourceName
clmpName :: LogicalModelName
clmpInfo :: PermDef b SelPerm
..} = do
Metadata
metadata <- m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceName -> LogicalModelName -> Metadata -> m ()
assertLogicalModelExists @b SourceName
clmpSource LogicalModelName
clmpName Metadata
metadata
let metadataObj :: MetadataObjId
metadataObj :: MetadataObjId
metadataObj =
SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
clmpSource
(AnyBackend SourceMetadataObjId -> MetadataObjId)
-> AnyBackend SourceMetadataObjId -> MetadataObjId
forall a b. (a -> b) -> a -> b
$ SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend
(SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
LogicalModelName -> SourceMetadataObjId b
SMOLogicalModel @b LogicalModelName
clmpName
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor MetadataObjId
metadataObj
(MetadataModifier -> m ()) -> MetadataModifier -> m ()
forall a b. (a -> b) -> a -> b
$ (Metadata -> Metadata) -> MetadataModifier
MetadataModifier
((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
Backend b =>
SourceName
-> LogicalModelName -> ASetter' Metadata (LogicalModelMetadata b)
logicalModelMetadataSetter @b SourceName
clmpSource LogicalModelName
clmpName
ASetter' Metadata (LogicalModelMetadata b)
-> ((InsOrdHashMap RoleName (PermDef b SelPerm)
-> Identity (InsOrdHashMap RoleName (PermDef b SelPerm)))
-> LogicalModelMetadata b -> Identity (LogicalModelMetadata b))
-> (InsOrdHashMap RoleName (PermDef b SelPerm)
-> Identity (InsOrdHashMap RoleName (PermDef b SelPerm)))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap RoleName (PermDef b SelPerm)
-> Identity (InsOrdHashMap RoleName (PermDef b SelPerm)))
-> LogicalModelMetadata b -> Identity (LogicalModelMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(InsOrdHashMap RoleName (SelPermDef b)
-> f (InsOrdHashMap RoleName (SelPermDef b)))
-> LogicalModelMetadata b -> f (LogicalModelMetadata b)
lmmSelectPermissions
((InsOrdHashMap RoleName (PermDef b SelPerm)
-> Identity (InsOrdHashMap RoleName (PermDef b SelPerm)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap RoleName (PermDef b SelPerm)
-> InsOrdHashMap RoleName (PermDef b SelPerm))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RoleName
-> PermDef b SelPerm
-> InsOrdHashMap RoleName (PermDef b SelPerm)
-> InsOrdHashMap RoleName (PermDef b SelPerm)
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.insert (PermDef b SelPerm -> RoleName
forall (b :: BackendType) (perm :: BackendType -> *).
PermDef b perm -> RoleName
_pdRole PermDef b SelPerm
clmpInfo) PermDef b SelPerm
clmpInfo
EncJSON -> m EncJSON
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
data DropLogicalModelPermission (b :: BackendType) = DropLogicalModelPermission
{ forall (b :: BackendType).
DropLogicalModelPermission b -> SourceName
dlmpSource :: SourceName,
forall (b :: BackendType).
DropLogicalModelPermission b -> LogicalModelName
dlmpName :: LogicalModelName,
forall (b :: BackendType). DropLogicalModelPermission b -> RoleName
dlmpRole :: RoleName
}
deriving stock ((forall x.
DropLogicalModelPermission b
-> Rep (DropLogicalModelPermission b) x)
-> (forall x.
Rep (DropLogicalModelPermission b) x
-> DropLogicalModelPermission b)
-> Generic (DropLogicalModelPermission b)
forall x.
Rep (DropLogicalModelPermission b) x
-> DropLogicalModelPermission b
forall x.
DropLogicalModelPermission b
-> Rep (DropLogicalModelPermission b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (b :: BackendType) x.
Rep (DropLogicalModelPermission b) x
-> DropLogicalModelPermission b
forall (b :: BackendType) x.
DropLogicalModelPermission b
-> Rep (DropLogicalModelPermission b) x
$cfrom :: forall (b :: BackendType) x.
DropLogicalModelPermission b
-> Rep (DropLogicalModelPermission b) x
from :: forall x.
DropLogicalModelPermission b
-> Rep (DropLogicalModelPermission b) x
$cto :: forall (b :: BackendType) x.
Rep (DropLogicalModelPermission b) x
-> DropLogicalModelPermission b
to :: forall x.
Rep (DropLogicalModelPermission b) x
-> DropLogicalModelPermission b
Generic)
instance FromJSON (DropLogicalModelPermission b) where
parseJSON :: Value -> Parser (DropLogicalModelPermission b)
parseJSON = String
-> (Object -> Parser (DropLogicalModelPermission b))
-> Value
-> Parser (DropLogicalModelPermission b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"DropLogicalModelPermission" \Object
obj -> do
SourceName
dlmpSource <- Object
obj Object -> Key -> Parser (Maybe SourceName)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"source" Parser (Maybe SourceName) -> SourceName -> Parser SourceName
forall a. Parser (Maybe a) -> a -> Parser a
.!= SourceName
defaultSource
LogicalModelName
dlmpName <- Object
obj Object -> Key -> Parser LogicalModelName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
RoleName
dlmpRole <- Object
obj Object -> Key -> Parser RoleName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"role"
DropLogicalModelPermission b
-> Parser (DropLogicalModelPermission b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DropLogicalModelPermission {RoleName
SourceName
LogicalModelName
dlmpSource :: SourceName
dlmpName :: LogicalModelName
dlmpRole :: RoleName
dlmpSource :: SourceName
dlmpName :: LogicalModelName
dlmpRole :: RoleName
..}
runDropSelectLogicalModelPermission ::
forall b m.
(Backend b, CacheRWM m, MetadataM m, MonadError QErr m) =>
DropLogicalModelPermission b ->
m EncJSON
runDropSelectLogicalModelPermission :: forall (b :: BackendType) (m :: * -> *).
(Backend b, CacheRWM m, MetadataM m, MonadError QErr m) =>
DropLogicalModelPermission b -> m EncJSON
runDropSelectLogicalModelPermission DropLogicalModelPermission {RoleName
SourceName
LogicalModelName
dlmpSource :: forall (b :: BackendType).
DropLogicalModelPermission b -> SourceName
dlmpName :: forall (b :: BackendType).
DropLogicalModelPermission b -> LogicalModelName
dlmpRole :: forall (b :: BackendType). DropLogicalModelPermission b -> RoleName
dlmpSource :: SourceName
dlmpName :: LogicalModelName
dlmpRole :: RoleName
..} = do
Metadata
metadata <- m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceName -> LogicalModelName -> Metadata -> m ()
assertLogicalModelExists @b SourceName
dlmpSource LogicalModelName
dlmpName Metadata
metadata
let metadataObj :: MetadataObjId
metadataObj :: MetadataObjId
metadataObj =
SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
dlmpSource
(AnyBackend SourceMetadataObjId -> MetadataObjId)
-> AnyBackend SourceMetadataObjId -> MetadataObjId
forall a b. (a -> b) -> a -> b
$ SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend
(SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
LogicalModelName -> SourceMetadataObjId b
SMOLogicalModel @b LogicalModelName
dlmpName
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor MetadataObjId
metadataObj
(MetadataModifier -> m ()) -> MetadataModifier -> m ()
forall a b. (a -> b) -> a -> b
$ (Metadata -> Metadata) -> MetadataModifier
MetadataModifier
((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
Backend b =>
SourceName
-> LogicalModelName -> ASetter' Metadata (LogicalModelMetadata b)
logicalModelMetadataSetter @b SourceName
dlmpSource LogicalModelName
dlmpName
ASetter' Metadata (LogicalModelMetadata b)
-> ((InsOrdHashMap RoleName (SelPermDef b)
-> Identity (InsOrdHashMap RoleName (SelPermDef b)))
-> LogicalModelMetadata b -> Identity (LogicalModelMetadata b))
-> (InsOrdHashMap RoleName (SelPermDef b)
-> Identity (InsOrdHashMap RoleName (SelPermDef b)))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap RoleName (SelPermDef b)
-> Identity (InsOrdHashMap RoleName (SelPermDef b)))
-> LogicalModelMetadata b -> Identity (LogicalModelMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(InsOrdHashMap RoleName (SelPermDef b)
-> f (InsOrdHashMap RoleName (SelPermDef b)))
-> LogicalModelMetadata b -> f (LogicalModelMetadata b)
lmmSelectPermissions
((InsOrdHashMap RoleName (SelPermDef b)
-> Identity (InsOrdHashMap RoleName (SelPermDef b)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap RoleName (SelPermDef b)
-> InsOrdHashMap RoleName (SelPermDef b))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RoleName
-> InsOrdHashMap RoleName (SelPermDef b)
-> InsOrdHashMap RoleName (SelPermDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.delete RoleName
dlmpRole
EncJSON -> m EncJSON
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
dropLogicalModelInMetadata :: forall b. (BackendMetadata b) => SourceName -> LogicalModelName -> MetadataModifier
dropLogicalModelInMetadata :: forall (b :: BackendType).
BackendMetadata b =>
SourceName -> LogicalModelName -> MetadataModifier
dropLogicalModelInMetadata SourceName
source LogicalModelName
name = do
(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)
-> ((LogicalModels b -> Identity (LogicalModels b))
-> Sources -> Identity Sources)
-> (LogicalModels b -> Identity (LogicalModels 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
source
((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((LogicalModels b -> Identity (LogicalModels b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (LogicalModels b -> Identity (LogicalModels b))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b
((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((LogicalModels b -> Identity (LogicalModels b))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (LogicalModels b -> Identity (LogicalModels b))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LogicalModels b -> Identity (LogicalModels b))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b)
smLogicalModels
((LogicalModels b -> Identity (LogicalModels b))
-> Metadata -> Identity Metadata)
-> (LogicalModels b -> LogicalModels b) -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ LogicalModelName -> LogicalModels b -> LogicalModels b
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.delete LogicalModelName
name
assertLogicalModelExists ::
forall b m. (Backend b, MonadError QErr m) => SourceName -> LogicalModelName -> Metadata -> m ()
assertLogicalModelExists :: forall (b :: BackendType) (m :: * -> *).
(Backend b, MonadError QErr m) =>
SourceName -> LogicalModelName -> Metadata -> m ()
assertLogicalModelExists SourceName
sourceName LogicalModelName
name Metadata
metadata = do
let sourceMetadataTraversal :: Traversal' Metadata (SourceMetadata b)
sourceMetadataTraversal :: Traversal' Metadata (SourceMetadata b)
sourceMetadataTraversal = (Sources -> f Sources) -> Metadata -> f Metadata
Lens' Metadata Sources
metaSources ((Sources -> f Sources) -> Metadata -> f Metadata)
-> ((SourceMetadata b -> f (SourceMetadata b))
-> Sources -> f Sources)
-> (SourceMetadata b -> f (SourceMetadata b))
-> Metadata
-> f 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
sourceName ((BackendSourceMetadata -> f BackendSourceMetadata)
-> Sources -> f Sources)
-> ((SourceMetadata b -> f (SourceMetadata b))
-> BackendSourceMetadata -> f BackendSourceMetadata)
-> (SourceMetadata b -> f (SourceMetadata b))
-> Sources
-> f Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b
SourceMetadata b
sourceMetadata <-
Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
-> Metadata -> Maybe (SourceMetadata b)
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
Traversal' Metadata (SourceMetadata b)
sourceMetadataTraversal Metadata
metadata
Maybe (SourceMetadata b)
-> m (SourceMetadata b) -> m (SourceMetadata b)
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> m (SourceMetadata b)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound (Text
"Source " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
sourceName SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" not found.")
let desiredLogicalModel :: Traversal' (SourceMetadata b) (LogicalModelMetadata b)
desiredLogicalModel :: Traversal' (SourceMetadata b) (LogicalModelMetadata b)
desiredLogicalModel = (LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b)
smLogicalModels ((LogicalModels b -> f (LogicalModels b))
-> SourceMetadata b -> f (SourceMetadata b))
-> ((LogicalModelMetadata b -> f (LogicalModelMetadata b))
-> LogicalModels b -> f (LogicalModels b))
-> (LogicalModelMetadata b -> f (LogicalModelMetadata b))
-> SourceMetadata b
-> f (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (LogicalModels b)
-> Traversal' (LogicalModels b) (IxValue (LogicalModels b))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (LogicalModels b)
LogicalModelName
name
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Getting Any (SourceMetadata b) (LogicalModelMetadata b)
-> SourceMetadata b -> Bool
forall s a. Getting Any s a -> s -> Bool
has Getting Any (SourceMetadata b) (LogicalModelMetadata b)
Traversal' (SourceMetadata b) (LogicalModelMetadata b)
desiredLogicalModel SourceMetadata b
sourceMetadata) do
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound (Text
"Logical model " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> LogicalModelName
name LogicalModelName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" not found in source " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
sourceName SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
".")