{-# LANGUAGE ViewPatterns #-}
module Hasura.Server.API.Metadata
( RQLMetadata,
RQLMetadataV1 (..),
runMetadataQuery,
)
where
import Control.Lens (_Just)
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson
import Data.Aeson.Casing
import Data.Aeson.Types qualified as A
import Data.Environment qualified as Env
import Data.Has (Has)
import Data.Text qualified as T
import Data.Text.Extended qualified as T
import GHC.Generics.Extended (constrName)
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.Logging qualified as L
import Hasura.Metadata.Class
import Hasura.Prelude hiding (first)
import Hasura.RQL.DDL.Action
import Hasura.RQL.DDL.ApiLimit
import Hasura.RQL.DDL.ComputedField
import Hasura.RQL.DDL.CustomTypes
import Hasura.RQL.DDL.DataConnector
import Hasura.RQL.DDL.Endpoint
import Hasura.RQL.DDL.EventTrigger
import Hasura.RQL.DDL.GraphqlSchemaIntrospection
import Hasura.RQL.DDL.InheritedRoles
import Hasura.RQL.DDL.Metadata
import Hasura.RQL.DDL.Network
import Hasura.RQL.DDL.Permission
import Hasura.RQL.DDL.QueryCollection
import Hasura.RQL.DDL.QueryTags
import Hasura.RQL.DDL.Relationship
import Hasura.RQL.DDL.Relationship.Rename
import Hasura.RQL.DDL.RemoteRelationship
import Hasura.RQL.DDL.RemoteSchema
import Hasura.RQL.DDL.ScheduledTrigger
import Hasura.RQL.DDL.Schema
import Hasura.RQL.DDL.Schema.Source
import Hasura.RQL.DDL.SourceKinds
import Hasura.RQL.DDL.Webhook.Transform.Validation
import Hasura.RQL.Types.Action
import Hasura.RQL.Types.Allowlist
import Hasura.RQL.Types.ApiLimit
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.CustomTypes
import Hasura.RQL.Types.Endpoint
import Hasura.RQL.Types.Eventing.Backend
import Hasura.RQL.Types.GraphqlSchemaIntrospection
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Metadata.Backend
import Hasura.RQL.Types.Network
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.QueryCollection
import Hasura.RQL.Types.RemoteSchema
import Hasura.RQL.Types.Roles
import Hasura.RQL.Types.Run
import Hasura.RQL.Types.ScheduledTrigger
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.SchemaCache.Build
import Hasura.RQL.Types.Source
import Hasura.SQL.AnyBackend
import Hasura.SQL.Backend
import Hasura.Server.API.Backend
import Hasura.Server.API.Instances ()
import Hasura.Server.Types
import Hasura.Server.Utils (APIVersion (..))
import Hasura.Session
import Hasura.Tracing qualified as Tracing
import Network.HTTP.Client.Manager qualified as HTTP
data RQLMetadataV1
=
RMAddSource !(AnyBackend AddSource)
| RMDropSource DropSource
| RMRenameSource !RenameSource
| RMUpdateSource !(AnyBackend UpdateSource)
|
RMTrackTable !(AnyBackend TrackTableV2)
| RMUntrackTable !(AnyBackend UntrackTable)
| RMSetTableCustomization !(AnyBackend SetTableCustomization)
| RMSetApolloFederationConfig (AnyBackend SetApolloFederationConfig)
|
RMPgSetTableIsEnum !SetTableIsEnum
|
RMCreateInsertPermission !(AnyBackend (CreatePerm InsPerm))
| RMCreateSelectPermission !(AnyBackend (CreatePerm SelPerm))
| RMCreateUpdatePermission !(AnyBackend (CreatePerm UpdPerm))
| RMCreateDeletePermission !(AnyBackend (CreatePerm DelPerm))
| RMDropInsertPermission !(AnyBackend DropPerm)
| RMDropSelectPermission !(AnyBackend DropPerm)
| RMDropUpdatePermission !(AnyBackend DropPerm)
| RMDropDeletePermission !(AnyBackend DropPerm)
| !(AnyBackend SetPermComment)
|
RMCreateObjectRelationship !(AnyBackend CreateObjRel)
| RMCreateArrayRelationship !(AnyBackend CreateArrRel)
| RMDropRelationship !(AnyBackend DropRel)
| !(AnyBackend SetRelComment)
| RMRenameRelationship !(AnyBackend RenameRel)
|
RMCreateRemoteRelationship !(AnyBackend CreateFromSourceRelationship)
| RMUpdateRemoteRelationship !(AnyBackend CreateFromSourceRelationship)
| RMDeleteRemoteRelationship !(AnyBackend DeleteFromSourceRelationship)
|
RMTrackFunction !(AnyBackend TrackFunctionV2)
| RMUntrackFunction !(AnyBackend UnTrackFunction)
| RMSetFunctionCustomization (AnyBackend SetFunctionCustomization)
|
RMCreateFunctionPermission !(AnyBackend FunctionPermissionArgument)
| RMDropFunctionPermission !(AnyBackend FunctionPermissionArgument)
|
RMAddComputedField !(AnyBackend AddComputedField)
| RMDropComputedField !(AnyBackend DropComputedField)
|
RMCreateEventTrigger !(AnyBackend (Unvalidated1 CreateEventTriggerQuery))
| RMDeleteEventTrigger !(AnyBackend DeleteEventTriggerQuery)
| RMRedeliverEvent !(AnyBackend RedeliverEventQuery)
| RMInvokeEventTrigger !(AnyBackend InvokeEventTriggerQuery)
|
RMAddRemoteSchema !AddRemoteSchemaQuery
| RMUpdateRemoteSchema !AddRemoteSchemaQuery
| RMRemoveRemoteSchema !RemoteSchemaNameQuery
| RMReloadRemoteSchema !RemoteSchemaNameQuery
| RMIntrospectRemoteSchema !RemoteSchemaNameQuery
|
RMAddRemoteSchemaPermissions !AddRemoteSchemaPermission
| RMDropRemoteSchemaPermissions !DropRemoteSchemaPermissions
|
RMCreateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship
| RMUpdateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship
| RMDeleteRemoteSchemaRemoteRelationship DeleteRemoteSchemaRemoteRelationship
|
RMCreateCronTrigger !(Unvalidated CreateCronTrigger)
| RMDeleteCronTrigger !ScheduledTriggerName
| RMCreateScheduledEvent !CreateScheduledEvent
| RMDeleteScheduledEvent !DeleteScheduledEvent
| RMGetScheduledEvents !GetScheduledEvents
| RMGetEventInvocations !GetEventInvocations
| RMGetCronTriggers
|
RMCreateAction !(Unvalidated CreateAction)
| RMDropAction !DropAction
| RMUpdateAction !(Unvalidated UpdateAction)
| RMCreateActionPermission !CreateActionPermission
| RMDropActionPermission !DropActionPermission
|
RMCreateQueryCollection !CreateCollection
| RMRenameQueryCollection !RenameCollection
| RMDropQueryCollection !DropCollection
| RMAddQueryToCollection !AddQueryToCollection
| RMDropQueryFromCollection !DropQueryFromCollection
| RMAddCollectionToAllowlist !AllowlistEntry
| RMDropCollectionFromAllowlist !DropCollectionFromAllowlist
| RMUpdateScopeOfCollectionInAllowlist !UpdateScopeOfCollectionInAllowlist
|
RMCreateRestEndpoint !CreateEndpoint
| RMDropRestEndpoint !DropEndpoint
|
RMDCAddAgent !DCAddAgent
| RMDCDeleteAgent !DCDeleteAgent
| RMListSourceKinds !ListSourceKinds
|
RMSetCustomTypes !CustomTypes
|
RMSetApiLimits !ApiLimit
| RMRemoveApiLimits
|
RMSetMetricsConfig !MetricsConfig
| RMRemoveMetricsConfig
|
RMAddInheritedRole !InheritedRole
| RMDropInheritedRole !DropInheritedRole
|
RMReplaceMetadata !ReplaceMetadata
| RMExportMetadata !ExportMetadata
| RMClearMetadata !ClearMetadata
| RMReloadMetadata !ReloadMetadata
| RMGetInconsistentMetadata !GetInconsistentMetadata
| RMDropInconsistentMetadata !DropInconsistentMetadata
|
RMSetGraphqlSchemaIntrospectionOptions !SetGraphqlIntrospectionOptions
|
RMAddHostToTLSAllowlist !AddHostToTLSAllowlist
| RMDropHostFromTLSAllowlist !DropHostFromTLSAllowlist
|
RMSetQueryTagsConfig !SetQueryTagsConfig
|
RMDumpInternalState !DumpInternalState
| RMGetCatalogState !GetCatalogState
| RMSetCatalogState !SetCatalogState
| RMTestWebhookTransform !(Unvalidated TestWebhookTransform)
|
RMBulk [RQLMetadataRequest]
deriving ((forall x. RQLMetadataV1 -> Rep RQLMetadataV1 x)
-> (forall x. Rep RQLMetadataV1 x -> RQLMetadataV1)
-> Generic RQLMetadataV1
forall x. Rep RQLMetadataV1 x -> RQLMetadataV1
forall x. RQLMetadataV1 -> Rep RQLMetadataV1 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RQLMetadataV1 x -> RQLMetadataV1
$cfrom :: forall x. RQLMetadataV1 -> Rep RQLMetadataV1 x
Generic)
instance FromJSON RQLMetadataV1 where
parseJSON :: Value -> Parser RQLMetadataV1
parseJSON = String
-> (Object -> Parser RQLMetadataV1)
-> Value
-> Parser RQLMetadataV1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RQLMetadataV1" \Object
o -> do
Text
queryType <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
let args :: forall a. FromJSON a => A.Parser a
args :: Parser a
args = Object
o Object -> Key -> Parser a
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"args"
case Text
queryType of
Text
"rename_source" -> RenameSource -> RQLMetadataV1
RMRenameSource (RenameSource -> RQLMetadataV1)
-> Parser RenameSource -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser RenameSource
forall a. FromJSON a => Parser a
args
Text
"add_remote_schema" -> AddRemoteSchemaQuery -> RQLMetadataV1
RMAddRemoteSchema (AddRemoteSchemaQuery -> RQLMetadataV1)
-> Parser AddRemoteSchemaQuery -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AddRemoteSchemaQuery
forall a. FromJSON a => Parser a
args
Text
"update_remote_schema" -> AddRemoteSchemaQuery -> RQLMetadataV1
RMUpdateRemoteSchema (AddRemoteSchemaQuery -> RQLMetadataV1)
-> Parser AddRemoteSchemaQuery -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AddRemoteSchemaQuery
forall a. FromJSON a => Parser a
args
Text
"remove_remote_schema" -> RemoteSchemaNameQuery -> RQLMetadataV1
RMRemoveRemoteSchema (RemoteSchemaNameQuery -> RQLMetadataV1)
-> Parser RemoteSchemaNameQuery -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser RemoteSchemaNameQuery
forall a. FromJSON a => Parser a
args
Text
"reload_remote_schema" -> RemoteSchemaNameQuery -> RQLMetadataV1
RMReloadRemoteSchema (RemoteSchemaNameQuery -> RQLMetadataV1)
-> Parser RemoteSchemaNameQuery -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser RemoteSchemaNameQuery
forall a. FromJSON a => Parser a
args
Text
"introspect_remote_schema" -> RemoteSchemaNameQuery -> RQLMetadataV1
RMIntrospectRemoteSchema (RemoteSchemaNameQuery -> RQLMetadataV1)
-> Parser RemoteSchemaNameQuery -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser RemoteSchemaNameQuery
forall a. FromJSON a => Parser a
args
Text
"add_remote_schema_permissions" -> AddRemoteSchemaPermission -> RQLMetadataV1
RMAddRemoteSchemaPermissions (AddRemoteSchemaPermission -> RQLMetadataV1)
-> Parser AddRemoteSchemaPermission -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AddRemoteSchemaPermission
forall a. FromJSON a => Parser a
args
Text
"drop_remote_schema_permissions" -> DropRemoteSchemaPermissions -> RQLMetadataV1
RMDropRemoteSchemaPermissions (DropRemoteSchemaPermissions -> RQLMetadataV1)
-> Parser DropRemoteSchemaPermissions -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropRemoteSchemaPermissions
forall a. FromJSON a => Parser a
args
Text
"create_remote_schema_remote_relationship" -> CreateRemoteSchemaRemoteRelationship -> RQLMetadataV1
RMCreateRemoteSchemaRemoteRelationship (CreateRemoteSchemaRemoteRelationship -> RQLMetadataV1)
-> Parser CreateRemoteSchemaRemoteRelationship
-> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CreateRemoteSchemaRemoteRelationship
forall a. FromJSON a => Parser a
args
Text
"update_remote_schema_remote_relationship" -> CreateRemoteSchemaRemoteRelationship -> RQLMetadataV1
RMUpdateRemoteSchemaRemoteRelationship (CreateRemoteSchemaRemoteRelationship -> RQLMetadataV1)
-> Parser CreateRemoteSchemaRemoteRelationship
-> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CreateRemoteSchemaRemoteRelationship
forall a. FromJSON a => Parser a
args
Text
"delete_remote_schema_remote_relationship" -> DeleteRemoteSchemaRemoteRelationship -> RQLMetadataV1
RMDeleteRemoteSchemaRemoteRelationship (DeleteRemoteSchemaRemoteRelationship -> RQLMetadataV1)
-> Parser DeleteRemoteSchemaRemoteRelationship
-> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DeleteRemoteSchemaRemoteRelationship
forall a. FromJSON a => Parser a
args
Text
"create_cron_trigger" -> Unvalidated CreateCronTrigger -> RQLMetadataV1
RMCreateCronTrigger (Unvalidated CreateCronTrigger -> RQLMetadataV1)
-> Parser (Unvalidated CreateCronTrigger) -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Unvalidated CreateCronTrigger)
forall a. FromJSON a => Parser a
args
Text
"delete_cron_trigger" -> ScheduledTriggerName -> RQLMetadataV1
RMDeleteCronTrigger (ScheduledTriggerName -> RQLMetadataV1)
-> Parser ScheduledTriggerName -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ScheduledTriggerName
forall a. FromJSON a => Parser a
args
Text
"create_scheduled_event" -> CreateScheduledEvent -> RQLMetadataV1
RMCreateScheduledEvent (CreateScheduledEvent -> RQLMetadataV1)
-> Parser CreateScheduledEvent -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CreateScheduledEvent
forall a. FromJSON a => Parser a
args
Text
"delete_scheduled_event" -> DeleteScheduledEvent -> RQLMetadataV1
RMDeleteScheduledEvent (DeleteScheduledEvent -> RQLMetadataV1)
-> Parser DeleteScheduledEvent -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DeleteScheduledEvent
forall a. FromJSON a => Parser a
args
Text
"get_scheduled_events" -> GetScheduledEvents -> RQLMetadataV1
RMGetScheduledEvents (GetScheduledEvents -> RQLMetadataV1)
-> Parser GetScheduledEvents -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GetScheduledEvents
forall a. FromJSON a => Parser a
args
Text
"get_event_invocations" -> GetEventInvocations -> RQLMetadataV1
RMGetEventInvocations (GetEventInvocations -> RQLMetadataV1)
-> Parser GetEventInvocations -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GetEventInvocations
forall a. FromJSON a => Parser a
args
Text
"get_cron_triggers" -> RQLMetadataV1 -> Parser RQLMetadataV1
forall (f :: * -> *) a. Applicative f => a -> f a
pure RQLMetadataV1
RMGetCronTriggers
Text
"create_action" -> Unvalidated CreateAction -> RQLMetadataV1
RMCreateAction (Unvalidated CreateAction -> RQLMetadataV1)
-> Parser (Unvalidated CreateAction) -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Unvalidated CreateAction)
forall a. FromJSON a => Parser a
args
Text
"drop_action" -> DropAction -> RQLMetadataV1
RMDropAction (DropAction -> RQLMetadataV1)
-> Parser DropAction -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropAction
forall a. FromJSON a => Parser a
args
Text
"update_action" -> Unvalidated UpdateAction -> RQLMetadataV1
RMUpdateAction (Unvalidated UpdateAction -> RQLMetadataV1)
-> Parser (Unvalidated UpdateAction) -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Unvalidated UpdateAction)
forall a. FromJSON a => Parser a
args
Text
"create_action_permission" -> CreateActionPermission -> RQLMetadataV1
RMCreateActionPermission (CreateActionPermission -> RQLMetadataV1)
-> Parser CreateActionPermission -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CreateActionPermission
forall a. FromJSON a => Parser a
args
Text
"drop_action_permission" -> DropActionPermission -> RQLMetadataV1
RMDropActionPermission (DropActionPermission -> RQLMetadataV1)
-> Parser DropActionPermission -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropActionPermission
forall a. FromJSON a => Parser a
args
Text
"create_query_collection" -> CreateCollection -> RQLMetadataV1
RMCreateQueryCollection (CreateCollection -> RQLMetadataV1)
-> Parser CreateCollection -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CreateCollection
forall a. FromJSON a => Parser a
args
Text
"rename_query_collection" -> RenameCollection -> RQLMetadataV1
RMRenameQueryCollection (RenameCollection -> RQLMetadataV1)
-> Parser RenameCollection -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser RenameCollection
forall a. FromJSON a => Parser a
args
Text
"drop_query_collection" -> DropCollection -> RQLMetadataV1
RMDropQueryCollection (DropCollection -> RQLMetadataV1)
-> Parser DropCollection -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropCollection
forall a. FromJSON a => Parser a
args
Text
"add_query_to_collection" -> AddQueryToCollection -> RQLMetadataV1
RMAddQueryToCollection (AddQueryToCollection -> RQLMetadataV1)
-> Parser AddQueryToCollection -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AddQueryToCollection
forall a. FromJSON a => Parser a
args
Text
"drop_query_from_collection" -> DropQueryFromCollection -> RQLMetadataV1
RMDropQueryFromCollection (DropQueryFromCollection -> RQLMetadataV1)
-> Parser DropQueryFromCollection -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropQueryFromCollection
forall a. FromJSON a => Parser a
args
Text
"add_collection_to_allowlist" -> AllowlistEntry -> RQLMetadataV1
RMAddCollectionToAllowlist (AllowlistEntry -> RQLMetadataV1)
-> Parser AllowlistEntry -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AllowlistEntry
forall a. FromJSON a => Parser a
args
Text
"drop_collection_from_allowlist" -> DropCollectionFromAllowlist -> RQLMetadataV1
RMDropCollectionFromAllowlist (DropCollectionFromAllowlist -> RQLMetadataV1)
-> Parser DropCollectionFromAllowlist -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropCollectionFromAllowlist
forall a. FromJSON a => Parser a
args
Text
"update_scope_of_collection_in_allowlist" -> UpdateScopeOfCollectionInAllowlist -> RQLMetadataV1
RMUpdateScopeOfCollectionInAllowlist (UpdateScopeOfCollectionInAllowlist -> RQLMetadataV1)
-> Parser UpdateScopeOfCollectionInAllowlist
-> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser UpdateScopeOfCollectionInAllowlist
forall a. FromJSON a => Parser a
args
Text
"create_rest_endpoint" -> CreateEndpoint -> RQLMetadataV1
RMCreateRestEndpoint (CreateEndpoint -> RQLMetadataV1)
-> Parser CreateEndpoint -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CreateEndpoint
forall a. FromJSON a => Parser a
args
Text
"drop_rest_endpoint" -> DropEndpoint -> RQLMetadataV1
RMDropRestEndpoint (DropEndpoint -> RQLMetadataV1)
-> Parser DropEndpoint -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropEndpoint
forall a. FromJSON a => Parser a
args
Text
"dc_add_agent" -> DCAddAgent -> RQLMetadataV1
RMDCAddAgent (DCAddAgent -> RQLMetadataV1)
-> Parser DCAddAgent -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DCAddAgent
forall a. FromJSON a => Parser a
args
Text
"dc_delete_agent" -> DCDeleteAgent -> RQLMetadataV1
RMDCDeleteAgent (DCDeleteAgent -> RQLMetadataV1)
-> Parser DCDeleteAgent -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DCDeleteAgent
forall a. FromJSON a => Parser a
args
Text
"list_source_kinds" -> ListSourceKinds -> RQLMetadataV1
RMListSourceKinds (ListSourceKinds -> RQLMetadataV1)
-> Parser ListSourceKinds -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ListSourceKinds
forall a. FromJSON a => Parser a
args
Text
"set_custom_types" -> CustomTypes -> RQLMetadataV1
RMSetCustomTypes (CustomTypes -> RQLMetadataV1)
-> Parser CustomTypes -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CustomTypes
forall a. FromJSON a => Parser a
args
Text
"set_api_limits" -> ApiLimit -> RQLMetadataV1
RMSetApiLimits (ApiLimit -> RQLMetadataV1)
-> Parser ApiLimit -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ApiLimit
forall a. FromJSON a => Parser a
args
Text
"remove_api_limits" -> RQLMetadataV1 -> Parser RQLMetadataV1
forall (f :: * -> *) a. Applicative f => a -> f a
pure RQLMetadataV1
RMRemoveApiLimits
Text
"set_metrics_config" -> MetricsConfig -> RQLMetadataV1
RMSetMetricsConfig (MetricsConfig -> RQLMetadataV1)
-> Parser MetricsConfig -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MetricsConfig
forall a. FromJSON a => Parser a
args
Text
"remove_metrics_config" -> RQLMetadataV1 -> Parser RQLMetadataV1
forall (f :: * -> *) a. Applicative f => a -> f a
pure RQLMetadataV1
RMRemoveMetricsConfig
Text
"add_inherited_role" -> InheritedRole -> RQLMetadataV1
RMAddInheritedRole (InheritedRole -> RQLMetadataV1)
-> Parser InheritedRole -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser InheritedRole
forall a. FromJSON a => Parser a
args
Text
"drop_inherited_role" -> DropInheritedRole -> RQLMetadataV1
RMDropInheritedRole (DropInheritedRole -> RQLMetadataV1)
-> Parser DropInheritedRole -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropInheritedRole
forall a. FromJSON a => Parser a
args
Text
"replace_metadata" -> ReplaceMetadata -> RQLMetadataV1
RMReplaceMetadata (ReplaceMetadata -> RQLMetadataV1)
-> Parser ReplaceMetadata -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ReplaceMetadata
forall a. FromJSON a => Parser a
args
Text
"export_metadata" -> ExportMetadata -> RQLMetadataV1
RMExportMetadata (ExportMetadata -> RQLMetadataV1)
-> Parser ExportMetadata -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ExportMetadata
forall a. FromJSON a => Parser a
args
Text
"clear_metadata" -> ClearMetadata -> RQLMetadataV1
RMClearMetadata (ClearMetadata -> RQLMetadataV1)
-> Parser ClearMetadata -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ClearMetadata
forall a. FromJSON a => Parser a
args
Text
"reload_metadata" -> ReloadMetadata -> RQLMetadataV1
RMReloadMetadata (ReloadMetadata -> RQLMetadataV1)
-> Parser ReloadMetadata -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ReloadMetadata
forall a. FromJSON a => Parser a
args
Text
"get_inconsistent_metadata" -> GetInconsistentMetadata -> RQLMetadataV1
RMGetInconsistentMetadata (GetInconsistentMetadata -> RQLMetadataV1)
-> Parser GetInconsistentMetadata -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GetInconsistentMetadata
forall a. FromJSON a => Parser a
args
Text
"drop_inconsistent_metadata" -> DropInconsistentMetadata -> RQLMetadataV1
RMDropInconsistentMetadata (DropInconsistentMetadata -> RQLMetadataV1)
-> Parser DropInconsistentMetadata -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropInconsistentMetadata
forall a. FromJSON a => Parser a
args
Text
"add_host_to_tls_allowlist" -> AddHostToTLSAllowlist -> RQLMetadataV1
RMAddHostToTLSAllowlist (AddHostToTLSAllowlist -> RQLMetadataV1)
-> Parser AddHostToTLSAllowlist -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AddHostToTLSAllowlist
forall a. FromJSON a => Parser a
args
Text
"drop_host_from_tls_allowlist" -> DropHostFromTLSAllowlist -> RQLMetadataV1
RMDropHostFromTLSAllowlist (DropHostFromTLSAllowlist -> RQLMetadataV1)
-> Parser DropHostFromTLSAllowlist -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DropHostFromTLSAllowlist
forall a. FromJSON a => Parser a
args
Text
"dump_internal_state" -> DumpInternalState -> RQLMetadataV1
RMDumpInternalState (DumpInternalState -> RQLMetadataV1)
-> Parser DumpInternalState -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DumpInternalState
forall a. FromJSON a => Parser a
args
Text
"get_catalog_state" -> GetCatalogState -> RQLMetadataV1
RMGetCatalogState (GetCatalogState -> RQLMetadataV1)
-> Parser GetCatalogState -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GetCatalogState
forall a. FromJSON a => Parser a
args
Text
"set_catalog_state" -> SetCatalogState -> RQLMetadataV1
RMSetCatalogState (SetCatalogState -> RQLMetadataV1)
-> Parser SetCatalogState -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser SetCatalogState
forall a. FromJSON a => Parser a
args
Text
"set_graphql_schema_introspection_options" -> SetGraphqlIntrospectionOptions -> RQLMetadataV1
RMSetGraphqlSchemaIntrospectionOptions (SetGraphqlIntrospectionOptions -> RQLMetadataV1)
-> Parser SetGraphqlIntrospectionOptions -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser SetGraphqlIntrospectionOptions
forall a. FromJSON a => Parser a
args
Text
"test_webhook_transform" -> Unvalidated TestWebhookTransform -> RQLMetadataV1
RMTestWebhookTransform (Unvalidated TestWebhookTransform -> RQLMetadataV1)
-> Parser (Unvalidated TestWebhookTransform)
-> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Unvalidated TestWebhookTransform)
forall a. FromJSON a => Parser a
args
Text
"set_query_tags" -> SetQueryTagsConfig -> RQLMetadataV1
RMSetQueryTagsConfig (SetQueryTagsConfig -> RQLMetadataV1)
-> Parser SetQueryTagsConfig -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser SetQueryTagsConfig
forall a. FromJSON a => Parser a
args
Text
"bulk" -> [RQLMetadataRequest] -> RQLMetadataV1
RMBulk ([RQLMetadataRequest] -> RQLMetadataV1)
-> Parser [RQLMetadataRequest] -> Parser RQLMetadataV1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [RQLMetadataRequest]
forall a. FromJSON a => Parser a
args
Text
_ -> do
(AnyBackend BackendSourceKind
backendSourceKind, Text
cmd) <- Text -> Parser (AnyBackend BackendSourceKind, Text)
forall (m :: * -> *).
MonadFail m =>
Text -> m (AnyBackend BackendSourceKind, Text)
parseQueryType Text
queryType
AnyBackend BackendSourceKind
-> (forall (b :: BackendType).
BackendAPI b =>
BackendSourceKind b -> Parser RQLMetadataV1)
-> Parser RQLMetadataV1
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
dispatchAnyBackend @BackendAPI AnyBackend BackendSourceKind
backendSourceKind \(BackendSourceKind b
backendSourceKind' :: BackendSourceKind b) -> do
Value
argValue <- Parser Value
forall a. FromJSON a => Parser a
args
Maybe RQLMetadataV1
command <- [Maybe RQLMetadataV1] -> Maybe RQLMetadataV1
forall (f :: * -> *) a. Alternative f => [f a] -> f a
choice ([Maybe RQLMetadataV1] -> Maybe RQLMetadataV1)
-> Parser [Maybe RQLMetadataV1] -> Parser (Maybe RQLMetadataV1)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Parser (Maybe RQLMetadataV1)] -> Parser [Maybe RQLMetadataV1]
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA [CommandParser b
p BackendSourceKind b
backendSourceKind' Text
cmd Value
argValue | CommandParser b
p <- BackendAPI b => [CommandParser b]
forall (b :: BackendType). BackendAPI b => [CommandParser b]
metadataV1CommandParsers @b]
Maybe RQLMetadataV1 -> Parser RQLMetadataV1 -> Parser RQLMetadataV1
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing Maybe RQLMetadataV1
command (Parser RQLMetadataV1 -> Parser RQLMetadataV1)
-> Parser RQLMetadataV1 -> Parser RQLMetadataV1
forall a b. (a -> b) -> a -> b
$
String -> Parser RQLMetadataV1
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser RQLMetadataV1) -> String -> Parser RQLMetadataV1
forall a b. (a -> b) -> a -> b
$
String
"unknown metadata command \"" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
cmd
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\" for backend "
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack (BackendSourceKind b -> Text
forall a. ToTxt a => a -> Text
T.toTxt BackendSourceKind b
backendSourceKind')
parseQueryType :: MonadFail m => Text -> m (AnyBackend BackendSourceKind, Text)
parseQueryType :: Text -> m (AnyBackend BackendSourceKind, Text)
parseQueryType Text
queryType =
let (Text
prefix, Int -> Text -> Text
T.drop Int
1 -> Text
cmd) = Text -> Text -> (Text, Text)
T.breakOn Text
"_" Text
queryType
in (,Text
cmd) (AnyBackend BackendSourceKind
-> (AnyBackend BackendSourceKind, Text))
-> m (AnyBackend BackendSourceKind)
-> m (AnyBackend BackendSourceKind, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe (AnyBackend BackendSourceKind)
backendSourceKindFromText Text
prefix
Maybe (AnyBackend BackendSourceKind)
-> m (AnyBackend BackendSourceKind)
-> m (AnyBackend BackendSourceKind)
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` String -> m (AnyBackend BackendSourceKind)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
( String
"unknown metadata command \"" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
queryType
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\"; \""
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
prefix
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\" was not recognized as a valid backend name"
)
data RQLMetadataV2
= RMV2ReplaceMetadata !ReplaceMetadataV2
| RMV2ExportMetadata !ExportMetadata
deriving ((forall x. RQLMetadataV2 -> Rep RQLMetadataV2 x)
-> (forall x. Rep RQLMetadataV2 x -> RQLMetadataV2)
-> Generic RQLMetadataV2
forall x. Rep RQLMetadataV2 x -> RQLMetadataV2
forall x. RQLMetadataV2 -> Rep RQLMetadataV2 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RQLMetadataV2 x -> RQLMetadataV2
$cfrom :: forall x. RQLMetadataV2 -> Rep RQLMetadataV2 x
Generic)
instance FromJSON RQLMetadataV2 where
parseJSON :: Value -> Parser RQLMetadataV2
parseJSON =
Options -> Value -> Parser RQLMetadataV2
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON (Options -> Value -> Parser RQLMetadataV2)
-> Options -> Value -> Parser RQLMetadataV2
forall a b. (a -> b) -> a -> b
$
Options
defaultOptions
{ constructorTagModifier :: String -> String
constructorTagModifier = String -> String
snakeCase (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
4,
sumEncoding :: SumEncoding
sumEncoding = String -> String -> SumEncoding
TaggedObject String
"type" String
"args"
}
data RQLMetadataRequest
= RMV1 !RQLMetadataV1
| RMV2 !RQLMetadataV2
instance FromJSON RQLMetadataRequest where
parseJSON :: Value -> Parser RQLMetadataRequest
parseJSON = String
-> (Object -> Parser RQLMetadataRequest)
-> Value
-> Parser RQLMetadataRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RQLMetadataRequest" ((Object -> Parser RQLMetadataRequest)
-> Value -> Parser RQLMetadataRequest)
-> (Object -> Parser RQLMetadataRequest)
-> Value
-> Parser RQLMetadataRequest
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
APIVersion
version <- Object
o Object -> Key -> Parser (Maybe APIVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"version" Parser (Maybe APIVersion) -> APIVersion -> Parser APIVersion
forall a. Parser (Maybe a) -> a -> Parser a
.!= APIVersion
VIVersion1
let val :: Value
val = Object -> Value
Object Object
o
case APIVersion
version of
APIVersion
VIVersion1 -> RQLMetadataV1 -> RQLMetadataRequest
RMV1 (RQLMetadataV1 -> RQLMetadataRequest)
-> Parser RQLMetadataV1 -> Parser RQLMetadataRequest
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser RQLMetadataV1
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
APIVersion
VIVersion2 -> RQLMetadataV2 -> RQLMetadataRequest
RMV2 (RQLMetadataV2 -> RQLMetadataRequest)
-> Parser RQLMetadataV2 -> Parser RQLMetadataRequest
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser RQLMetadataV2
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
data RQLMetadata = RQLMetadata
{ RQLMetadata -> Maybe MetadataResourceVersion
_rqlMetadataResourceVersion :: !(Maybe MetadataResourceVersion),
RQLMetadata -> RQLMetadataRequest
_rqlMetadata :: !RQLMetadataRequest
}
instance FromJSON RQLMetadata where
parseJSON :: Value -> Parser RQLMetadata
parseJSON = String
-> (Object -> Parser RQLMetadata) -> Value -> Parser RQLMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RQLMetadata" ((Object -> Parser RQLMetadata) -> Value -> Parser RQLMetadata)
-> (Object -> Parser RQLMetadata) -> Value -> Parser RQLMetadata
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe MetadataResourceVersion
_rqlMetadataResourceVersion <- Object
o Object -> Key -> Parser (Maybe MetadataResourceVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"resource_version"
RQLMetadataRequest
_rqlMetadata <- Value -> Parser RQLMetadataRequest
forall a. FromJSON a => Value -> Parser a
parseJSON (Value -> Parser RQLMetadataRequest)
-> Value -> Parser RQLMetadataRequest
forall a b. (a -> b) -> a -> b
$ Object -> Value
Object Object
o
RQLMetadata -> Parser RQLMetadata
forall (f :: * -> *) a. Applicative f => a -> f a
pure RQLMetadata :: Maybe MetadataResourceVersion -> RQLMetadataRequest -> RQLMetadata
RQLMetadata {Maybe MetadataResourceVersion
RQLMetadataRequest
_rqlMetadata :: RQLMetadataRequest
_rqlMetadataResourceVersion :: Maybe MetadataResourceVersion
_rqlMetadata :: RQLMetadataRequest
_rqlMetadataResourceVersion :: Maybe MetadataResourceVersion
..}
runMetadataQuery ::
( MonadIO m,
MonadBaseControl IO m,
Tracing.MonadTrace m,
MonadMetadataStorage m,
MonadResolveSource m
) =>
Env.Environment ->
L.Logger L.Hasura ->
InstanceId ->
UserInfo ->
HTTP.Manager ->
ServerConfigCtx ->
RebuildableSchemaCache ->
RQLMetadata ->
m (EncJSON, RebuildableSchemaCache)
runMetadataQuery :: Environment
-> Logger Hasura
-> InstanceId
-> UserInfo
-> Manager
-> ServerConfigCtx
-> RebuildableSchemaCache
-> RQLMetadata
-> m (EncJSON, RebuildableSchemaCache)
runMetadataQuery Environment
env Logger Hasura
logger InstanceId
instanceId UserInfo
userInfo Manager
httpManager ServerConfigCtx
serverConfigCtx RebuildableSchemaCache
schemaCache RQLMetadata {Maybe MetadataResourceVersion
RQLMetadataRequest
_rqlMetadata :: RQLMetadataRequest
_rqlMetadataResourceVersion :: Maybe MetadataResourceVersion
_rqlMetadata :: RQLMetadata -> RQLMetadataRequest
_rqlMetadataResourceVersion :: RQLMetadata -> Maybe MetadataResourceVersion
..} = do
(Metadata
metadata, MetadataResourceVersion
currentResourceVersion) <- Text
-> m (Metadata, MetadataResourceVersion)
-> m (Metadata, MetadataResourceVersion)
forall (m :: * -> *) a. MonadTrace m => Text -> m a -> m a
Tracing.trace Text
"fetchMetadata" m (Metadata, MetadataResourceVersion)
forall (m :: * -> *).
MonadMetadataStorage m =>
m (Metadata, MetadataResourceVersion)
fetchMetadata
((EncJSON
r, Metadata
modMetadata), RebuildableSchemaCache
modSchemaCache, CacheInvalidations
cacheInvalidations) <-
Environment
-> MetadataResourceVersion
-> RQLMetadataRequest
-> ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
forall (m :: * -> *) r.
(MonadIO m, MonadBaseControl IO m, CacheRWM m, MonadTrace m,
UserInfoM m, HasHttpManagerM m, MetadataM m,
MonadMetadataStorageQueryAPI m, HasServerConfigCtx m,
MonadReader r m, Has (Logger Hasura) r) =>
Environment
-> MetadataResourceVersion -> RQLMetadataRequest -> m EncJSON
runMetadataQueryM Environment
env MetadataResourceVersion
currentResourceVersion RQLMetadataRequest
_rqlMetadata
ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
-> (ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
-> MetadataT (CacheRWT (RunT m)) EncJSON)
-> MetadataT (CacheRWT (RunT m)) EncJSON
forall a b. a -> (a -> b) -> b
& (ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
-> Logger Hasura -> MetadataT (CacheRWT (RunT m)) EncJSON)
-> Logger Hasura
-> ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
-> MetadataT (CacheRWT (RunT m)) EncJSON
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
-> Logger Hasura -> MetadataT (CacheRWT (RunT m)) EncJSON
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT Logger Hasura
logger
MetadataT (CacheRWT (RunT m)) EncJSON
-> (MetadataT (CacheRWT (RunT m)) EncJSON
-> CacheRWT (RunT m) (EncJSON, Metadata))
-> CacheRWT (RunT m) (EncJSON, Metadata)
forall a b. a -> (a -> b) -> b
& Metadata
-> MetadataT (CacheRWT (RunT m)) EncJSON
-> CacheRWT (RunT m) (EncJSON, Metadata)
forall (m :: * -> *) a.
Metadata -> MetadataT m a -> m (a, Metadata)
runMetadataT Metadata
metadata
CacheRWT (RunT m) (EncJSON, Metadata)
-> (CacheRWT (RunT m) (EncJSON, Metadata)
-> RunT
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
-> RunT
m ((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
forall a b. a -> (a -> b) -> b
& RebuildableSchemaCache
-> CacheRWT (RunT m) (EncJSON, Metadata)
-> RunT
m ((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
forall (m :: * -> *) a.
Functor m =>
RebuildableSchemaCache
-> CacheRWT m a
-> m (a, RebuildableSchemaCache, CacheInvalidations)
runCacheRWT RebuildableSchemaCache
schemaCache
RunT
m ((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
-> (RunT
m ((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
-> ExceptT
QErr
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
-> ExceptT
QErr
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
forall a b. a -> (a -> b) -> b
& RunCtx
-> RunT
m ((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
-> ExceptT
QErr
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
forall (m :: * -> *) a. RunCtx -> RunT m a -> ExceptT QErr m a
peelRun (UserInfo -> Manager -> ServerConfigCtx -> RunCtx
RunCtx UserInfo
userInfo Manager
httpManager ServerConfigCtx
serverConfigCtx)
ExceptT
QErr
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
-> (ExceptT
QErr
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
-> m (Either
QErr
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)))
-> m (Either
QErr
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
forall a b. a -> (a -> b) -> b
& ExceptT
QErr
m
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations)
-> m (Either
QErr
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
m (Either
QErr
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
-> (m (Either
QErr
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
-> m ((EncJSON, Metadata), RebuildableSchemaCache,
CacheInvalidations))
-> m ((EncJSON, Metadata), RebuildableSchemaCache,
CacheInvalidations)
forall a b. a -> (a -> b) -> b
& m (Either
QErr
((EncJSON, Metadata), RebuildableSchemaCache, CacheInvalidations))
-> m ((EncJSON, Metadata), RebuildableSchemaCache,
CacheInvalidations)
forall e (m :: * -> *) a. MonadError e m => m (Either e a) -> m a
liftEitherM
if RQLMetadataRequest -> Bool
queryModifiesMetadata RQLMetadataRequest
_rqlMetadata
then case (ServerConfigCtx -> MaintenanceMode ()
_sccMaintenanceMode ServerConfigCtx
serverConfigCtx, ServerConfigCtx -> ReadOnlyMode
_sccReadOnlyMode ServerConfigCtx
serverConfigCtx) of
(MaintenanceMode ()
MaintenanceModeDisabled, ReadOnlyMode
ReadOnlyModeDisabled) -> do
MetadataResourceVersion
newResourceVersion <-
Text -> m MetadataResourceVersion -> m MetadataResourceVersion
forall (m :: * -> *) a. MonadTrace m => Text -> m a -> m a
Tracing.trace Text
"setMetadata" (m MetadataResourceVersion -> m MetadataResourceVersion)
-> m MetadataResourceVersion -> m MetadataResourceVersion
forall a b. (a -> b) -> a -> b
$
MetadataResourceVersion -> Metadata -> m MetadataResourceVersion
forall (m :: * -> *).
MonadMetadataStorage m =>
MetadataResourceVersion -> Metadata -> m MetadataResourceVersion
setMetadata (MetadataResourceVersion
-> Maybe MetadataResourceVersion -> MetadataResourceVersion
forall a. a -> Maybe a -> a
fromMaybe MetadataResourceVersion
currentResourceVersion Maybe MetadataResourceVersion
_rqlMetadataResourceVersion) Metadata
modMetadata
Text -> m () -> m ()
forall (m :: * -> *) a. MonadTrace m => Text -> m a -> m a
Tracing.trace Text
"notifySchemaCacheSync" (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
MetadataResourceVersion -> InstanceId -> CacheInvalidations -> m ()
forall (m :: * -> *).
MonadMetadataStorage m =>
MetadataResourceVersion -> InstanceId -> CacheInvalidations -> m ()
notifySchemaCacheSync MetadataResourceVersion
newResourceVersion InstanceId
instanceId CacheInvalidations
cacheInvalidations
(()
_, RebuildableSchemaCache
modSchemaCache', CacheInvalidations
_) <-
Text
-> m ((), RebuildableSchemaCache, CacheInvalidations)
-> m ((), RebuildableSchemaCache, CacheInvalidations)
forall (m :: * -> *) a. MonadTrace m => Text -> m a -> m a
Tracing.trace Text
"setMetadataResourceVersionInSchemaCache" (m ((), RebuildableSchemaCache, CacheInvalidations)
-> m ((), RebuildableSchemaCache, CacheInvalidations))
-> m ((), RebuildableSchemaCache, CacheInvalidations)
-> m ((), RebuildableSchemaCache, CacheInvalidations)
forall a b. (a -> b) -> a -> b
$
MetadataResourceVersion -> CacheRWT (RunT m) ()
forall (m :: * -> *). CacheRWM m => MetadataResourceVersion -> m ()
setMetadataResourceVersionInSchemaCache MetadataResourceVersion
newResourceVersion
CacheRWT (RunT m) ()
-> (CacheRWT (RunT m) ()
-> RunT m ((), RebuildableSchemaCache, CacheInvalidations))
-> RunT m ((), RebuildableSchemaCache, CacheInvalidations)
forall a b. a -> (a -> b) -> b
& RebuildableSchemaCache
-> CacheRWT (RunT m) ()
-> RunT m ((), RebuildableSchemaCache, CacheInvalidations)
forall (m :: * -> *) a.
Functor m =>
RebuildableSchemaCache
-> CacheRWT m a
-> m (a, RebuildableSchemaCache, CacheInvalidations)
runCacheRWT RebuildableSchemaCache
modSchemaCache
RunT m ((), RebuildableSchemaCache, CacheInvalidations)
-> (RunT m ((), RebuildableSchemaCache, CacheInvalidations)
-> ExceptT QErr m ((), RebuildableSchemaCache, CacheInvalidations))
-> ExceptT QErr m ((), RebuildableSchemaCache, CacheInvalidations)
forall a b. a -> (a -> b) -> b
& RunCtx
-> RunT m ((), RebuildableSchemaCache, CacheInvalidations)
-> ExceptT QErr m ((), RebuildableSchemaCache, CacheInvalidations)
forall (m :: * -> *) a. RunCtx -> RunT m a -> ExceptT QErr m a
peelRun (UserInfo -> Manager -> ServerConfigCtx -> RunCtx
RunCtx UserInfo
userInfo Manager
httpManager ServerConfigCtx
serverConfigCtx)
ExceptT QErr m ((), RebuildableSchemaCache, CacheInvalidations)
-> (ExceptT QErr m ((), RebuildableSchemaCache, CacheInvalidations)
-> m (Either
QErr ((), RebuildableSchemaCache, CacheInvalidations)))
-> m (Either QErr ((), RebuildableSchemaCache, CacheInvalidations))
forall a b. a -> (a -> b) -> b
& ExceptT QErr m ((), RebuildableSchemaCache, CacheInvalidations)
-> m (Either QErr ((), RebuildableSchemaCache, CacheInvalidations))
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
m (Either QErr ((), RebuildableSchemaCache, CacheInvalidations))
-> (m (Either
QErr ((), RebuildableSchemaCache, CacheInvalidations))
-> m ((), RebuildableSchemaCache, CacheInvalidations))
-> m ((), RebuildableSchemaCache, CacheInvalidations)
forall a b. a -> (a -> b) -> b
& m (Either QErr ((), RebuildableSchemaCache, CacheInvalidations))
-> m ((), RebuildableSchemaCache, CacheInvalidations)
forall e (m :: * -> *) a. MonadError e m => m (Either e a) -> m a
liftEitherM
(EncJSON, RebuildableSchemaCache)
-> m (EncJSON, RebuildableSchemaCache)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EncJSON
r, RebuildableSchemaCache
modSchemaCache')
(MaintenanceModeEnabled (), ReadOnlyMode
ReadOnlyModeDisabled) ->
Text -> m (EncJSON, RebuildableSchemaCache)
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 Text
"metadata cannot be modified in maintenance mode"
(MaintenanceMode ()
MaintenanceModeDisabled, ReadOnlyMode
ReadOnlyModeEnabled) ->
Code -> Text -> m (EncJSON, RebuildableSchemaCache)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotSupported Text
"metadata cannot be modified in read-only mode"
(MaintenanceModeEnabled (), ReadOnlyMode
ReadOnlyModeEnabled) ->
Text -> m (EncJSON, RebuildableSchemaCache)
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 Text
"metadata cannot be modified in maintenance mode"
else (EncJSON, RebuildableSchemaCache)
-> m (EncJSON, RebuildableSchemaCache)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EncJSON
r, RebuildableSchemaCache
modSchemaCache)
queryModifiesMetadata :: RQLMetadataRequest -> Bool
queryModifiesMetadata :: RQLMetadataRequest -> Bool
queryModifiesMetadata = \case
RMV1 RQLMetadataV1
q ->
case RQLMetadataV1
q of
RMRedeliverEvent AnyBackend RedeliverEventQuery
_ -> Bool
False
RMInvokeEventTrigger AnyBackend InvokeEventTriggerQuery
_ -> Bool
False
RMGetInconsistentMetadata GetInconsistentMetadata
_ -> Bool
False
RMIntrospectRemoteSchema RemoteSchemaNameQuery
_ -> Bool
False
RMDumpInternalState DumpInternalState
_ -> Bool
False
RMSetCatalogState SetCatalogState
_ -> Bool
False
RMGetCatalogState GetCatalogState
_ -> Bool
False
RMExportMetadata ExportMetadata
_ -> Bool
False
RMGetEventInvocations GetEventInvocations
_ -> Bool
False
RQLMetadataV1
RMGetCronTriggers -> Bool
False
RMGetScheduledEvents GetScheduledEvents
_ -> Bool
False
RMCreateScheduledEvent CreateScheduledEvent
_ -> Bool
False
RMDeleteScheduledEvent DeleteScheduledEvent
_ -> Bool
False
RMTestWebhookTransform Unvalidated TestWebhookTransform
_ -> Bool
False
RMBulk [RQLMetadataRequest]
qs -> (RQLMetadataRequest -> Bool) -> [RQLMetadataRequest] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any RQLMetadataRequest -> Bool
queryModifiesMetadata [RQLMetadataRequest]
qs
RQLMetadataV1
_ -> Bool
True
RMV2 RQLMetadataV2
q ->
case RQLMetadataV2
q of
RMV2ExportMetadata ExportMetadata
_ -> Bool
False
RQLMetadataV2
_ -> Bool
True
runMetadataQueryM ::
( MonadIO m,
MonadBaseControl IO m,
CacheRWM m,
Tracing.MonadTrace m,
UserInfoM m,
HTTP.HasHttpManagerM m,
MetadataM m,
MonadMetadataStorageQueryAPI m,
HasServerConfigCtx m,
MonadReader r m,
Has (L.Logger L.Hasura) r
) =>
Env.Environment ->
MetadataResourceVersion ->
RQLMetadataRequest ->
m EncJSON
runMetadataQueryM :: Environment
-> MetadataResourceVersion -> RQLMetadataRequest -> m EncJSON
runMetadataQueryM Environment
env MetadataResourceVersion
currentResourceVersion =
Text -> m EncJSON -> m EncJSON
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"args" (m EncJSON -> m EncJSON)
-> (RQLMetadataRequest -> m EncJSON)
-> RQLMetadataRequest
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
RMV1 RQLMetadataV1
q ->
Text -> m EncJSON -> m EncJSON
forall (m :: * -> *) a. MonadTrace m => Text -> m a -> m a
Tracing.trace (Text
"v1 " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (RQLMetadataV1 -> String
forall a. (HasConstructor (Rep a), Generic a) => a -> String
constrName RQLMetadataV1
q)) (m EncJSON -> m EncJSON) -> m EncJSON -> m EncJSON
forall a b. (a -> b) -> a -> b
$
Environment
-> MetadataResourceVersion -> RQLMetadataV1 -> m EncJSON
forall (m :: * -> *) r.
(MonadIO m, MonadBaseControl IO m, CacheRWM m, MonadTrace m,
UserInfoM m, HasHttpManagerM m, MetadataM m,
MonadMetadataStorageQueryAPI m, HasServerConfigCtx m,
MonadReader r m, Has (Logger Hasura) r) =>
Environment
-> MetadataResourceVersion -> RQLMetadataV1 -> m EncJSON
runMetadataQueryV1M Environment
env MetadataResourceVersion
currentResourceVersion RQLMetadataV1
q
RMV2 RQLMetadataV2
q ->
Text -> m EncJSON -> m EncJSON
forall (m :: * -> *) a. MonadTrace m => Text -> m a -> m a
Tracing.trace (Text
"v2 " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (RQLMetadataV2 -> String
forall a. (HasConstructor (Rep a), Generic a) => a -> String
constrName RQLMetadataV2
q)) (m EncJSON -> m EncJSON) -> m EncJSON -> m EncJSON
forall a b. (a -> b) -> a -> b
$
MetadataResourceVersion -> RQLMetadataV2 -> m EncJSON
forall (m :: * -> *) r.
(MonadIO m, CacheRWM m, MetadataM m,
MonadMetadataStorageQueryAPI m, MonadReader r m,
Has (Logger Hasura) r) =>
MetadataResourceVersion -> RQLMetadataV2 -> m EncJSON
runMetadataQueryV2M MetadataResourceVersion
currentResourceVersion RQLMetadataV2
q
runMetadataQueryV1M ::
forall m r.
( MonadIO m,
MonadBaseControl IO m,
CacheRWM m,
Tracing.MonadTrace m,
UserInfoM m,
HTTP.HasHttpManagerM m,
MetadataM m,
MonadMetadataStorageQueryAPI m,
HasServerConfigCtx m,
MonadReader r m,
Has (L.Logger L.Hasura) r
) =>
Env.Environment ->
MetadataResourceVersion ->
RQLMetadataV1 ->
m EncJSON
runMetadataQueryV1M :: Environment
-> MetadataResourceVersion -> RQLMetadataV1 -> m EncJSON
runMetadataQueryV1M Environment
env MetadataResourceVersion
currentResourceVersion = \case
RMAddSource AnyBackend AddSource
q -> (forall (b :: BackendType).
BackendMetadata b =>
AddSource b -> m EncJSON)
-> AnyBackend AddSource -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
AddSource b -> m EncJSON
forall (m :: * -> *) (b :: BackendType).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
AddSource b -> m EncJSON
runAddSource AnyBackend AddSource
q
RMDropSource DropSource
q -> DropSource -> m EncJSON
forall (m :: * -> *) r.
(MonadError QErr m, CacheRWM m, MonadIO m, MonadBaseControl IO m,
MetadataM m, MonadReader r m, Has (Logger Hasura) r) =>
DropSource -> m EncJSON
runDropSource DropSource
q
RMRenameSource RenameSource
q -> RenameSource -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
RenameSource -> m EncJSON
runRenameSource RenameSource
q
RMUpdateSource AnyBackend UpdateSource
q -> (forall (b :: BackendType).
BackendMetadata b =>
UpdateSource b -> m EncJSON)
-> AnyBackend UpdateSource -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
UpdateSource b -> m EncJSON
forall (m :: * -> *) (b :: BackendType).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
UpdateSource b -> m EncJSON
runUpdateSource AnyBackend UpdateSource
q
RMTrackTable AnyBackend TrackTableV2
q -> (forall (b :: BackendType).
BackendMetadata b =>
TrackTableV2 b -> m EncJSON)
-> AnyBackend TrackTableV2 -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
TrackTableV2 b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
TrackTableV2 b -> m EncJSON
runTrackTableV2Q AnyBackend TrackTableV2
q
RMUntrackTable AnyBackend UntrackTable
q -> (forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
UntrackTable b -> m EncJSON)
-> AnyBackend UntrackTable -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a)
-> AnyBackend i -> a
dispatchMetadataAndEventTrigger forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
UntrackTable b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(CacheRWM m, QErrM m, MetadataM m, BackendMetadata b,
BackendEventTrigger b, MonadIO m) =>
UntrackTable b -> m EncJSON
runUntrackTableQ AnyBackend UntrackTable
q
RMSetFunctionCustomization AnyBackend SetFunctionCustomization
q -> (forall (b :: BackendType).
BackendMetadata b =>
SetFunctionCustomization b -> m EncJSON)
-> AnyBackend SetFunctionCustomization -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
SetFunctionCustomization b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
SetFunctionCustomization b -> m EncJSON
runSetFunctionCustomization AnyBackend SetFunctionCustomization
q
RMSetTableCustomization AnyBackend SetTableCustomization
q -> (forall (b :: BackendType).
BackendMetadata b =>
SetTableCustomization b -> m EncJSON)
-> AnyBackend SetTableCustomization -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
SetTableCustomization b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
SetTableCustomization b -> m EncJSON
runSetTableCustomization AnyBackend SetTableCustomization
q
RMSetApolloFederationConfig AnyBackend SetApolloFederationConfig
q -> (forall (b :: BackendType).
BackendMetadata b =>
SetApolloFederationConfig b -> m EncJSON)
-> AnyBackend SetApolloFederationConfig -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
SetApolloFederationConfig b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
SetApolloFederationConfig b -> m EncJSON
runSetApolloFederationConfig AnyBackend SetApolloFederationConfig
q
RMPgSetTableIsEnum SetTableIsEnum
q -> SetTableIsEnum -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
SetTableIsEnum -> m EncJSON
runSetExistingTableIsEnumQ SetTableIsEnum
q
RMCreateInsertPermission AnyBackend (CreatePerm InsPerm)
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreatePerm InsPerm b -> m EncJSON)
-> AnyBackend (CreatePerm InsPerm) -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
CreatePerm InsPerm b -> m EncJSON
forall (m :: * -> *) (b :: BackendType) (a :: BackendType -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
CreatePerm a b -> m EncJSON
runCreatePerm AnyBackend (CreatePerm InsPerm)
q
RMCreateSelectPermission AnyBackend (CreatePerm SelPerm)
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreatePerm SelPerm b -> m EncJSON)
-> AnyBackend (CreatePerm SelPerm) -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
CreatePerm SelPerm b -> m EncJSON
forall (m :: * -> *) (b :: BackendType) (a :: BackendType -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
CreatePerm a b -> m EncJSON
runCreatePerm AnyBackend (CreatePerm SelPerm)
q
RMCreateUpdatePermission AnyBackend (CreatePerm UpdPerm)
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreatePerm UpdPerm b -> m EncJSON)
-> AnyBackend (CreatePerm UpdPerm) -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
CreatePerm UpdPerm b -> m EncJSON
forall (m :: * -> *) (b :: BackendType) (a :: BackendType -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
CreatePerm a b -> m EncJSON
runCreatePerm AnyBackend (CreatePerm UpdPerm)
q
RMCreateDeletePermission AnyBackend (CreatePerm DelPerm)
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreatePerm DelPerm b -> m EncJSON)
-> AnyBackend (CreatePerm DelPerm) -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
CreatePerm DelPerm b -> m EncJSON
forall (m :: * -> *) (b :: BackendType) (a :: BackendType -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
CreatePerm a b -> m EncJSON
runCreatePerm AnyBackend (CreatePerm DelPerm)
q
RMDropInsertPermission AnyBackend DropPerm
q -> (forall (b :: BackendType).
BackendMetadata b =>
DropPerm b -> m EncJSON)
-> AnyBackend DropPerm -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata (PermType -> DropPerm b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
PermType -> DropPerm b -> m EncJSON
runDropPerm PermType
PTInsert) AnyBackend DropPerm
q
RMDropSelectPermission AnyBackend DropPerm
q -> (forall (b :: BackendType).
BackendMetadata b =>
DropPerm b -> m EncJSON)
-> AnyBackend DropPerm -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata (PermType -> DropPerm b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
PermType -> DropPerm b -> m EncJSON
runDropPerm PermType
PTSelect) AnyBackend DropPerm
q
RMDropUpdatePermission AnyBackend DropPerm
q -> (forall (b :: BackendType).
BackendMetadata b =>
DropPerm b -> m EncJSON)
-> AnyBackend DropPerm -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata (PermType -> DropPerm b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
PermType -> DropPerm b -> m EncJSON
runDropPerm PermType
PTUpdate) AnyBackend DropPerm
q
RMDropDeletePermission AnyBackend DropPerm
q -> (forall (b :: BackendType).
BackendMetadata b =>
DropPerm b -> m EncJSON)
-> AnyBackend DropPerm -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata (PermType -> DropPerm b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(UserInfoM m, CacheRWM m, MonadError QErr m, MetadataM m,
BackendMetadata b) =>
PermType -> DropPerm b -> m EncJSON
runDropPerm PermType
PTDelete) AnyBackend DropPerm
q
RMSetPermissionComment AnyBackend SetPermComment
q -> (forall (b :: BackendType).
BackendMetadata b =>
SetPermComment b -> m EncJSON)
-> AnyBackend SetPermComment -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
SetPermComment b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, BackendMetadata b) =>
SetPermComment b -> m EncJSON
runSetPermComment AnyBackend SetPermComment
q
RMCreateObjectRelationship AnyBackend CreateObjRel
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreateObjRel b -> m EncJSON)
-> AnyBackend CreateObjRel -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata (RelType -> WithTable b (RelDef (ObjRelUsing b)) -> m EncJSON
forall (m :: * -> *) (b :: BackendType) a.
(MonadError QErr m, CacheRWM m, ToJSON a, MetadataM m, Backend b,
BackendMetadata b) =>
RelType -> WithTable b (RelDef a) -> m EncJSON
runCreateRelationship RelType
ObjRel (WithTable b (RelDef (ObjRelUsing b)) -> m EncJSON)
-> (CreateObjRel b -> WithTable b (RelDef (ObjRelUsing b)))
-> CreateObjRel b
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateObjRel b -> WithTable b (RelDef (ObjRelUsing b))
forall (b :: BackendType).
CreateObjRel b -> WithTable b (ObjRelDef b)
unCreateObjRel) AnyBackend CreateObjRel
q
RMCreateArrayRelationship AnyBackend CreateArrRel
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreateArrRel b -> m EncJSON)
-> AnyBackend CreateArrRel -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata (RelType -> WithTable b (RelDef (ArrRelUsing b)) -> m EncJSON
forall (m :: * -> *) (b :: BackendType) a.
(MonadError QErr m, CacheRWM m, ToJSON a, MetadataM m, Backend b,
BackendMetadata b) =>
RelType -> WithTable b (RelDef a) -> m EncJSON
runCreateRelationship RelType
ArrRel (WithTable b (RelDef (ArrRelUsing b)) -> m EncJSON)
-> (CreateArrRel b -> WithTable b (RelDef (ArrRelUsing b)))
-> CreateArrRel b
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CreateArrRel b -> WithTable b (RelDef (ArrRelUsing b))
forall (b :: BackendType).
CreateArrRel b -> WithTable b (ArrRelDef b)
unCreateArrRel) AnyBackend CreateArrRel
q
RMDropRelationship AnyBackend DropRel
q -> (forall (b :: BackendType).
BackendMetadata b =>
DropRel b -> m EncJSON)
-> AnyBackend DropRel -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
DropRel b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
DropRel b -> m EncJSON
runDropRel AnyBackend DropRel
q
RMSetRelationshipComment AnyBackend SetRelComment
q -> (forall (b :: BackendType).
BackendMetadata b =>
SetRelComment b -> m EncJSON)
-> AnyBackend SetRelComment -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
SetRelComment b -> m EncJSON
forall (m :: * -> *) (b :: BackendType).
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
SetRelComment b -> m EncJSON
runSetRelComment AnyBackend SetRelComment
q
RMRenameRelationship AnyBackend RenameRel
q -> (forall (b :: BackendType).
BackendMetadata b =>
RenameRel b -> m EncJSON)
-> AnyBackend RenameRel -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
RenameRel b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
RenameRel b -> m EncJSON
runRenameRel AnyBackend RenameRel
q
RMCreateRemoteRelationship AnyBackend CreateFromSourceRelationship
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreateFromSourceRelationship b -> m EncJSON)
-> AnyBackend CreateFromSourceRelationship -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
CreateFromSourceRelationship b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
CreateFromSourceRelationship b -> m EncJSON
runCreateRemoteRelationship AnyBackend CreateFromSourceRelationship
q
RMUpdateRemoteRelationship AnyBackend CreateFromSourceRelationship
q -> (forall (b :: BackendType).
BackendMetadata b =>
CreateFromSourceRelationship b -> m EncJSON)
-> AnyBackend CreateFromSourceRelationship -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
CreateFromSourceRelationship b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
CreateFromSourceRelationship b -> m EncJSON
runUpdateRemoteRelationship AnyBackend CreateFromSourceRelationship
q
RMDeleteRemoteRelationship AnyBackend DeleteFromSourceRelationship
q -> (forall (b :: BackendType).
BackendMetadata b =>
DeleteFromSourceRelationship b -> m EncJSON)
-> AnyBackend DeleteFromSourceRelationship -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
DeleteFromSourceRelationship b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
DeleteFromSourceRelationship b -> m EncJSON
runDeleteRemoteRelationship AnyBackend DeleteFromSourceRelationship
q
RMTrackFunction AnyBackend TrackFunctionV2
q -> (forall (b :: BackendType).
BackendMetadata b =>
TrackFunctionV2 b -> m EncJSON)
-> AnyBackend TrackFunctionV2 -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
TrackFunctionV2 b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, QErrM m, CacheRWM m, MetadataM m) =>
TrackFunctionV2 b -> m EncJSON
runTrackFunctionV2 AnyBackend TrackFunctionV2
q
RMUntrackFunction AnyBackend UnTrackFunction
q -> (forall (b :: BackendType).
BackendMetadata b =>
UnTrackFunction b -> m EncJSON)
-> AnyBackend UnTrackFunction -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
UnTrackFunction b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
UnTrackFunction b -> m EncJSON
runUntrackFunc AnyBackend UnTrackFunction
q
RMCreateFunctionPermission AnyBackend FunctionPermissionArgument
q -> (forall (b :: BackendType).
BackendMetadata b =>
FunctionPermissionArgument b -> m EncJSON)
-> AnyBackend FunctionPermissionArgument -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
FunctionPermissionArgument b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
FunctionPermissionArgument b -> m EncJSON
runCreateFunctionPermission AnyBackend FunctionPermissionArgument
q
RMDropFunctionPermission AnyBackend FunctionPermissionArgument
q -> (forall (b :: BackendType).
BackendMetadata b =>
FunctionPermissionArgument b -> m EncJSON)
-> AnyBackend FunctionPermissionArgument -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
FunctionPermissionArgument b -> m EncJSON
forall (m :: * -> *) (b :: BackendType).
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
FunctionPermissionArgument b -> m EncJSON
runDropFunctionPermission AnyBackend FunctionPermissionArgument
q
RMAddComputedField AnyBackend AddComputedField
q -> (forall (b :: BackendType).
BackendMetadata b =>
AddComputedField b -> m EncJSON)
-> AnyBackend AddComputedField -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
AddComputedField b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
AddComputedField b -> m EncJSON
runAddComputedField AnyBackend AddComputedField
q
RMDropComputedField AnyBackend DropComputedField
q -> (forall (b :: BackendType).
BackendMetadata b =>
DropComputedField b -> m EncJSON)
-> AnyBackend DropComputedField -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType).
BackendMetadata b =>
DropComputedField b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, BackendMetadata b) =>
DropComputedField b -> m EncJSON
runDropComputedField AnyBackend DropComputedField
q
RMCreateEventTrigger AnyBackend (Unvalidated1 CreateEventTriggerQuery)
q ->
(forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
Unvalidated1 CreateEventTriggerQuery b -> m EncJSON)
-> AnyBackend (Unvalidated1 CreateEventTriggerQuery) -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a)
-> AnyBackend i -> a
dispatchMetadataAndEventTrigger
( LensLike
(Either TransformErrorBundle)
(Unvalidated1 CreateEventTriggerQuery b)
(Unvalidated1 CreateEventTriggerQuery b)
RequestTransform
RequestTransform
-> (Unvalidated1 CreateEventTriggerQuery b -> m EncJSON)
-> Unvalidated1 CreateEventTriggerQuery b
-> m EncJSON
forall (m :: * -> *) api.
MonadError QErr m =>
LensLike
(Either TransformErrorBundle)
api
api
RequestTransform
RequestTransform
-> (api -> m EncJSON) -> api -> m EncJSON
validateTransforms
((CreateEventTriggerQuery b
-> Either TransformErrorBundle (CreateEventTriggerQuery b))
-> Unvalidated1 CreateEventTriggerQuery b
-> Either
TransformErrorBundle (Unvalidated1 CreateEventTriggerQuery b)
forall k (f :: k -> *) (a :: k). Lens' (Unvalidated1 f a) (f a)
unUnvalidate1 ((CreateEventTriggerQuery b
-> Either TransformErrorBundle (CreateEventTriggerQuery b))
-> Unvalidated1 CreateEventTriggerQuery b
-> Either
TransformErrorBundle (Unvalidated1 CreateEventTriggerQuery b))
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> CreateEventTriggerQuery b
-> Either TransformErrorBundle (CreateEventTriggerQuery b))
-> LensLike
(Either TransformErrorBundle)
(Unvalidated1 CreateEventTriggerQuery b)
(Unvalidated1 CreateEventTriggerQuery b)
RequestTransform
RequestTransform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> CreateEventTriggerQuery b
-> Either TransformErrorBundle (CreateEventTriggerQuery b)
forall (b :: BackendType).
Lens' (CreateEventTriggerQuery b) (Maybe RequestTransform)
cetqRequestTransform ((Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> CreateEventTriggerQuery b
-> Either TransformErrorBundle (CreateEventTriggerQuery b))
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> (RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> CreateEventTriggerQuery b
-> Either TransformErrorBundle (CreateEventTriggerQuery b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestTransform -> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just)
(CreateEventTriggerQuery b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, BackendEventTrigger b, QErrM m, UserInfoM m,
CacheRWM m, MetadataM m, MonadIO m) =>
CreateEventTriggerQuery b -> m EncJSON
runCreateEventTriggerQuery (CreateEventTriggerQuery b -> m EncJSON)
-> (Unvalidated1 CreateEventTriggerQuery b
-> CreateEventTriggerQuery b)
-> Unvalidated1 CreateEventTriggerQuery b
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unvalidated1 CreateEventTriggerQuery b -> CreateEventTriggerQuery b
forall k (f :: k -> *) (a :: k). Unvalidated1 f a -> f a
_unUnvalidate1)
)
AnyBackend (Unvalidated1 CreateEventTriggerQuery)
q
RMDeleteEventTrigger AnyBackend DeleteEventTriggerQuery
q -> (forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
DeleteEventTriggerQuery b -> m EncJSON)
-> AnyBackend DeleteEventTriggerQuery -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a)
-> AnyBackend i -> a
dispatchMetadataAndEventTrigger forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
DeleteEventTriggerQuery b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendEventTrigger b, MonadError QErr m, CacheRWM m, MonadIO m,
MetadataM m) =>
DeleteEventTriggerQuery b -> m EncJSON
runDeleteEventTriggerQuery AnyBackend DeleteEventTriggerQuery
q
RMRedeliverEvent AnyBackend RedeliverEventQuery
q -> (forall (b :: BackendType).
BackendEventTrigger b =>
RedeliverEventQuery b -> m EncJSON)
-> AnyBackend RedeliverEventQuery -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendEventTrigger b => i b -> a)
-> AnyBackend i -> a
dispatchEventTrigger forall (b :: BackendType).
BackendEventTrigger b =>
RedeliverEventQuery b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendEventTrigger b, MonadIO m, CacheRM m, QErrM m,
MetadataM m) =>
RedeliverEventQuery b -> m EncJSON
runRedeliverEvent AnyBackend RedeliverEventQuery
q
RMInvokeEventTrigger AnyBackend InvokeEventTriggerQuery
q -> (forall (b :: BackendType).
BackendEventTrigger b =>
InvokeEventTriggerQuery b -> m EncJSON)
-> AnyBackend InvokeEventTriggerQuery -> m EncJSON
forall (i :: BackendType -> *) a.
(forall (b :: BackendType). BackendEventTrigger b => i b -> a)
-> AnyBackend i -> a
dispatchEventTrigger forall (b :: BackendType).
BackendEventTrigger b =>
InvokeEventTriggerQuery b -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadIO m, QErrM m, CacheRM m, MetadataM m, MonadTrace m,
UserInfoM m, BackendEventTrigger b) =>
InvokeEventTriggerQuery b -> m EncJSON
runInvokeEventTrigger AnyBackend InvokeEventTriggerQuery
q
RMAddRemoteSchema AddRemoteSchemaQuery
q -> Environment -> AddRemoteSchemaQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MonadIO m, HasHttpManagerM m, MetadataM m,
MonadTrace m) =>
Environment -> AddRemoteSchemaQuery -> m EncJSON
runAddRemoteSchema Environment
env AddRemoteSchemaQuery
q
RMUpdateRemoteSchema AddRemoteSchemaQuery
q -> Environment -> AddRemoteSchemaQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MonadIO m, HasHttpManagerM m, MetadataM m,
MonadTrace m) =>
Environment -> AddRemoteSchemaQuery -> m EncJSON
runUpdateRemoteSchema Environment
env AddRemoteSchemaQuery
q
RMRemoveRemoteSchema RemoteSchemaNameQuery
q -> RemoteSchemaNameQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRWM m, MetadataM m) =>
RemoteSchemaNameQuery -> m EncJSON
runRemoveRemoteSchema RemoteSchemaNameQuery
q
RMReloadRemoteSchema RemoteSchemaNameQuery
q -> RemoteSchemaNameQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
RemoteSchemaNameQuery -> m EncJSON
runReloadRemoteSchema RemoteSchemaNameQuery
q
RMIntrospectRemoteSchema RemoteSchemaNameQuery
q -> RemoteSchemaNameQuery -> m EncJSON
forall (m :: * -> *).
(CacheRM m, QErrM m) =>
RemoteSchemaNameQuery -> m EncJSON
runIntrospectRemoteSchema RemoteSchemaNameQuery
q
RMAddRemoteSchemaPermissions AddRemoteSchemaPermission
q -> AddRemoteSchemaPermission -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, HasServerConfigCtx m, MetadataM m) =>
AddRemoteSchemaPermission -> m EncJSON
runAddRemoteSchemaPermissions AddRemoteSchemaPermission
q
RMDropRemoteSchemaPermissions DropRemoteSchemaPermissions
q -> DropRemoteSchemaPermissions -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
DropRemoteSchemaPermissions -> m EncJSON
runDropRemoteSchemaPermissions DropRemoteSchemaPermissions
q
RMCreateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship
q -> CreateRemoteSchemaRemoteRelationship -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
CreateRemoteSchemaRemoteRelationship -> m EncJSON
runCreateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship
q
RMUpdateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship
q -> CreateRemoteSchemaRemoteRelationship -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
CreateRemoteSchemaRemoteRelationship -> m EncJSON
runUpdateRemoteSchemaRemoteRelationship CreateRemoteSchemaRemoteRelationship
q
RMDeleteRemoteSchemaRemoteRelationship DeleteRemoteSchemaRemoteRelationship
q -> DeleteRemoteSchemaRemoteRelationship -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
DeleteRemoteSchemaRemoteRelationship -> m EncJSON
runDeleteRemoteSchemaRemoteRelationship DeleteRemoteSchemaRemoteRelationship
q
RMCreateCronTrigger Unvalidated CreateCronTrigger
q ->
LensLike
(Either TransformErrorBundle)
(Unvalidated CreateCronTrigger)
(Unvalidated CreateCronTrigger)
RequestTransform
RequestTransform
-> (Unvalidated CreateCronTrigger -> m EncJSON)
-> Unvalidated CreateCronTrigger
-> m EncJSON
forall (m :: * -> *) api.
MonadError QErr m =>
LensLike
(Either TransformErrorBundle)
api
api
RequestTransform
RequestTransform
-> (api -> m EncJSON) -> api -> m EncJSON
validateTransforms
((CreateCronTrigger
-> Either TransformErrorBundle CreateCronTrigger)
-> Unvalidated CreateCronTrigger
-> Either TransformErrorBundle (Unvalidated CreateCronTrigger)
forall a. Lens' (Unvalidated a) a
unUnvalidate ((CreateCronTrigger
-> Either TransformErrorBundle CreateCronTrigger)
-> Unvalidated CreateCronTrigger
-> Either TransformErrorBundle (Unvalidated CreateCronTrigger))
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> CreateCronTrigger
-> Either TransformErrorBundle CreateCronTrigger)
-> LensLike
(Either TransformErrorBundle)
(Unvalidated CreateCronTrigger)
(Unvalidated CreateCronTrigger)
RequestTransform
RequestTransform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> CreateCronTrigger
-> Either TransformErrorBundle CreateCronTrigger
Lens' CreateCronTrigger (Maybe RequestTransform)
cctRequestTransform ((Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> CreateCronTrigger
-> Either TransformErrorBundle CreateCronTrigger)
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> (RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> CreateCronTrigger
-> Either TransformErrorBundle CreateCronTrigger
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestTransform -> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just)
(CreateCronTrigger -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MonadIO m, MetadataM m,
MonadMetadataStorageQueryAPI m) =>
CreateCronTrigger -> m EncJSON
runCreateCronTrigger (CreateCronTrigger -> m EncJSON)
-> (Unvalidated CreateCronTrigger -> CreateCronTrigger)
-> Unvalidated CreateCronTrigger
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unvalidated CreateCronTrigger -> CreateCronTrigger
forall a. Unvalidated a -> a
_unUnvalidate)
Unvalidated CreateCronTrigger
q
RMDeleteCronTrigger ScheduledTriggerName
q -> ScheduledTriggerName -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
ScheduledTriggerName -> m EncJSON
runDeleteCronTrigger ScheduledTriggerName
q
RMCreateScheduledEvent CreateScheduledEvent
q -> CreateScheduledEvent -> m EncJSON
forall (m :: * -> *).
MonadMetadataStorageQueryAPI m =>
CreateScheduledEvent -> m EncJSON
runCreateScheduledEvent CreateScheduledEvent
q
RMDeleteScheduledEvent DeleteScheduledEvent
q -> DeleteScheduledEvent -> m EncJSON
forall (m :: * -> *).
MonadMetadataStorageQueryAPI m =>
DeleteScheduledEvent -> m EncJSON
runDeleteScheduledEvent DeleteScheduledEvent
q
RMGetScheduledEvents GetScheduledEvents
q -> GetScheduledEvents -> m EncJSON
forall (m :: * -> *).
(CacheRM m, MonadMetadataStorageQueryAPI m) =>
GetScheduledEvents -> m EncJSON
runGetScheduledEvents GetScheduledEvents
q
RMGetEventInvocations GetEventInvocations
q -> GetEventInvocations -> m EncJSON
forall (m :: * -> *).
(CacheRM m, MonadMetadataStorageQueryAPI m) =>
GetEventInvocations -> m EncJSON
runGetEventInvocations GetEventInvocations
q
RQLMetadataV1
RMGetCronTriggers -> m EncJSON
forall (m :: * -> *). MetadataM m => m EncJSON
runGetCronTriggers
RMCreateAction Unvalidated CreateAction
q ->
LensLike
(Either TransformErrorBundle)
(Unvalidated CreateAction)
(Unvalidated CreateAction)
RequestTransform
RequestTransform
-> (Unvalidated CreateAction -> m EncJSON)
-> Unvalidated CreateAction
-> m EncJSON
forall (m :: * -> *) api.
MonadError QErr m =>
LensLike
(Either TransformErrorBundle)
api
api
RequestTransform
RequestTransform
-> (api -> m EncJSON) -> api -> m EncJSON
validateTransforms
((CreateAction -> Either TransformErrorBundle CreateAction)
-> Unvalidated CreateAction
-> Either TransformErrorBundle (Unvalidated CreateAction)
forall a. Lens' (Unvalidated a) a
unUnvalidate ((CreateAction -> Either TransformErrorBundle CreateAction)
-> Unvalidated CreateAction
-> Either TransformErrorBundle (Unvalidated CreateAction))
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> CreateAction -> Either TransformErrorBundle CreateAction)
-> LensLike
(Either TransformErrorBundle)
(Unvalidated CreateAction)
(Unvalidated CreateAction)
RequestTransform
RequestTransform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> CreateAction -> Either TransformErrorBundle CreateAction
Lens' CreateAction ActionDefinitionInput
caDefinition ((ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> CreateAction -> Either TransformErrorBundle CreateAction)
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> (RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> CreateAction
-> Either TransformErrorBundle CreateAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput
forall arg webhook.
Lens' (ActionDefinition arg webhook) (Maybe RequestTransform)
adRequestTransform ((Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> (RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestTransform -> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just)
(CreateAction -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
CreateAction -> m EncJSON
runCreateAction (CreateAction -> m EncJSON)
-> (Unvalidated CreateAction -> CreateAction)
-> Unvalidated CreateAction
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unvalidated CreateAction -> CreateAction
forall a. Unvalidated a -> a
_unUnvalidate)
Unvalidated CreateAction
q
RMDropAction DropAction
q -> DropAction -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
DropAction -> m EncJSON
runDropAction DropAction
q
RMUpdateAction Unvalidated UpdateAction
q ->
LensLike
(Either TransformErrorBundle)
(Unvalidated UpdateAction)
(Unvalidated UpdateAction)
RequestTransform
RequestTransform
-> (Unvalidated UpdateAction -> m EncJSON)
-> Unvalidated UpdateAction
-> m EncJSON
forall (m :: * -> *) api.
MonadError QErr m =>
LensLike
(Either TransformErrorBundle)
api
api
RequestTransform
RequestTransform
-> (api -> m EncJSON) -> api -> m EncJSON
validateTransforms
((UpdateAction -> Either TransformErrorBundle UpdateAction)
-> Unvalidated UpdateAction
-> Either TransformErrorBundle (Unvalidated UpdateAction)
forall a. Lens' (Unvalidated a) a
unUnvalidate ((UpdateAction -> Either TransformErrorBundle UpdateAction)
-> Unvalidated UpdateAction
-> Either TransformErrorBundle (Unvalidated UpdateAction))
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> UpdateAction -> Either TransformErrorBundle UpdateAction)
-> LensLike
(Either TransformErrorBundle)
(Unvalidated UpdateAction)
(Unvalidated UpdateAction)
RequestTransform
RequestTransform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> UpdateAction -> Either TransformErrorBundle UpdateAction
Lens' UpdateAction ActionDefinitionInput
uaDefinition ((ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> UpdateAction -> Either TransformErrorBundle UpdateAction)
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> (RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> UpdateAction
-> Either TransformErrorBundle UpdateAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput
forall arg webhook.
Lens' (ActionDefinition arg webhook) (Maybe RequestTransform)
adRequestTransform ((Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput)
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform))
-> (RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> ActionDefinitionInput
-> Either TransformErrorBundle ActionDefinitionInput
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestTransform -> Either TransformErrorBundle RequestTransform)
-> Maybe RequestTransform
-> Either TransformErrorBundle (Maybe RequestTransform)
forall a b. Prism (Maybe a) (Maybe b) a b
_Just)
(UpdateAction -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
UpdateAction -> m EncJSON
runUpdateAction (UpdateAction -> m EncJSON)
-> (Unvalidated UpdateAction -> UpdateAction)
-> Unvalidated UpdateAction
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unvalidated UpdateAction -> UpdateAction
forall a. Unvalidated a -> a
_unUnvalidate)
Unvalidated UpdateAction
q
RMCreateActionPermission CreateActionPermission
q -> CreateActionPermission -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
CreateActionPermission -> m EncJSON
runCreateActionPermission CreateActionPermission
q
RMDropActionPermission DropActionPermission
q -> DropActionPermission -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
DropActionPermission -> m EncJSON
runDropActionPermission DropActionPermission
q
RMCreateQueryCollection CreateCollection
q -> CreateCollection -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
CreateCollection -> m EncJSON
runCreateCollection CreateCollection
q
RMRenameQueryCollection RenameCollection
q -> RenameCollection -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
RenameCollection -> m EncJSON
runRenameCollection RenameCollection
q
RMDropQueryCollection DropCollection
q -> DropCollection -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
DropCollection -> m EncJSON
runDropCollection DropCollection
q
RMAddQueryToCollection AddQueryToCollection
q -> AddQueryToCollection -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m) =>
AddQueryToCollection -> m EncJSON
runAddQueryToCollection AddQueryToCollection
q
RMDropQueryFromCollection DropQueryFromCollection
q -> DropQueryFromCollection -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m) =>
DropQueryFromCollection -> m EncJSON
runDropQueryFromCollection DropQueryFromCollection
q
RMAddCollectionToAllowlist AllowlistEntry
q -> AllowlistEntry -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
AllowlistEntry -> m EncJSON
runAddCollectionToAllowlist AllowlistEntry
q
RMDropCollectionFromAllowlist DropCollectionFromAllowlist
q -> DropCollectionFromAllowlist -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
DropCollectionFromAllowlist -> m EncJSON
runDropCollectionFromAllowlist DropCollectionFromAllowlist
q
RMUpdateScopeOfCollectionInAllowlist UpdateScopeOfCollectionInAllowlist
q -> UpdateScopeOfCollectionInAllowlist -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
UpdateScopeOfCollectionInAllowlist -> m EncJSON
runUpdateScopeOfCollectionInAllowlist UpdateScopeOfCollectionInAllowlist
q
RMCreateRestEndpoint CreateEndpoint
q -> CreateEndpoint -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
CreateEndpoint -> m EncJSON
runCreateEndpoint CreateEndpoint
q
RMDropRestEndpoint DropEndpoint
q -> DropEndpoint -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
DropEndpoint -> m EncJSON
runDropEndpoint DropEndpoint
q
RMDCAddAgent DCAddAgent
q -> DCAddAgent -> m EncJSON
forall (m :: * -> *). MetadataM m => DCAddAgent -> m EncJSON
runAddDataConnectorAgent DCAddAgent
q
RMDCDeleteAgent DCDeleteAgent
q -> DCDeleteAgent -> m EncJSON
forall (m :: * -> *).
(MetadataM m, MonadError QErr m) =>
DCDeleteAgent -> m EncJSON
runDeleteDataConnectorAgent DCDeleteAgent
q
RMListSourceKinds ListSourceKinds
q -> ListSourceKinds -> m EncJSON
forall (m :: * -> *). MetadataM m => ListSourceKinds -> m EncJSON
runListSourceKinds ListSourceKinds
q
RMSetCustomTypes CustomTypes
q -> CustomTypes -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
CustomTypes -> m EncJSON
runSetCustomTypes CustomTypes
q
RMSetApiLimits ApiLimit
q -> ApiLimit -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
ApiLimit -> m EncJSON
runSetApiLimits ApiLimit
q
RQLMetadataV1
RMRemoveApiLimits -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
m EncJSON
runRemoveApiLimits
RMSetMetricsConfig MetricsConfig
q -> MetricsConfig -> m EncJSON
forall (m :: * -> *).
(MonadIO m, CacheRWM m, MetadataM m, MonadError QErr m) =>
MetricsConfig -> m EncJSON
runSetMetricsConfig MetricsConfig
q
RQLMetadataV1
RMRemoveMetricsConfig -> m EncJSON
forall (m :: * -> *).
(MonadIO m, CacheRWM m, MetadataM m, MonadError QErr m) =>
m EncJSON
runRemoveMetricsConfig
RMAddInheritedRole InheritedRole
q -> InheritedRole -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
InheritedRole -> m EncJSON
runAddInheritedRole InheritedRole
q
RMDropInheritedRole DropInheritedRole
q -> DropInheritedRole -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
DropInheritedRole -> m EncJSON
runDropInheritedRole DropInheritedRole
q
RMReplaceMetadata ReplaceMetadata
q -> ReplaceMetadata -> m EncJSON
forall (m :: * -> *) r.
(CacheRWM m, MetadataM m, MonadIO m,
MonadMetadataStorageQueryAPI m, MonadReader r m,
Has (Logger Hasura) r) =>
ReplaceMetadata -> m EncJSON
runReplaceMetadata ReplaceMetadata
q
RMExportMetadata ExportMetadata
q -> ExportMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, MetadataM m) =>
ExportMetadata -> m EncJSON
runExportMetadata ExportMetadata
q
RMClearMetadata ClearMetadata
q -> ClearMetadata -> m EncJSON
forall (m :: * -> *) r.
(QErrM m, MonadIO m, CacheRWM m, MetadataM m,
MonadMetadataStorageQueryAPI m, MonadBaseControl IO m,
MonadReader r m, Has (Logger Hasura) r) =>
ClearMetadata -> m EncJSON
runClearMetadata ClearMetadata
q
RMReloadMetadata ReloadMetadata
q -> ReloadMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
ReloadMetadata -> m EncJSON
runReloadMetadata ReloadMetadata
q
RMGetInconsistentMetadata GetInconsistentMetadata
q -> GetInconsistentMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRM m) =>
GetInconsistentMetadata -> m EncJSON
runGetInconsistentMetadata GetInconsistentMetadata
q
RMDropInconsistentMetadata DropInconsistentMetadata
q -> DropInconsistentMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
DropInconsistentMetadata -> m EncJSON
runDropInconsistentMetadata DropInconsistentMetadata
q
RMSetGraphqlSchemaIntrospectionOptions SetGraphqlIntrospectionOptions
q -> SetGraphqlIntrospectionOptions -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
SetGraphqlIntrospectionOptions -> m EncJSON
runSetGraphqlSchemaIntrospectionOptions SetGraphqlIntrospectionOptions
q
RMAddHostToTLSAllowlist AddHostToTLSAllowlist
q -> AddHostToTLSAllowlist -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
AddHostToTLSAllowlist -> m EncJSON
runAddHostToTLSAllowlist AddHostToTLSAllowlist
q
RMDropHostFromTLSAllowlist DropHostFromTLSAllowlist
q -> DropHostFromTLSAllowlist -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
DropHostFromTLSAllowlist -> m EncJSON
runDropHostFromTLSAllowlist DropHostFromTLSAllowlist
q
RMDumpInternalState DumpInternalState
q -> DumpInternalState -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRM m) =>
DumpInternalState -> m EncJSON
runDumpInternalState DumpInternalState
q
RMGetCatalogState GetCatalogState
q -> GetCatalogState -> m EncJSON
forall (m :: * -> *).
MonadMetadataStorageQueryAPI m =>
GetCatalogState -> m EncJSON
runGetCatalogState GetCatalogState
q
RMSetCatalogState SetCatalogState
q -> SetCatalogState -> m EncJSON
forall (m :: * -> *).
MonadMetadataStorageQueryAPI m =>
SetCatalogState -> m EncJSON
runSetCatalogState SetCatalogState
q
RMTestWebhookTransform Unvalidated TestWebhookTransform
q ->
LensLike
(Either TransformErrorBundle)
(Unvalidated TestWebhookTransform)
(Unvalidated TestWebhookTransform)
RequestTransform
RequestTransform
-> (Unvalidated TestWebhookTransform -> m EncJSON)
-> Unvalidated TestWebhookTransform
-> m EncJSON
forall (m :: * -> *) api.
MonadError QErr m =>
LensLike
(Either TransformErrorBundle)
api
api
RequestTransform
RequestTransform
-> (api -> m EncJSON) -> api -> m EncJSON
validateTransforms
((TestWebhookTransform
-> Either TransformErrorBundle TestWebhookTransform)
-> Unvalidated TestWebhookTransform
-> Either TransformErrorBundle (Unvalidated TestWebhookTransform)
forall a. Lens' (Unvalidated a) a
unUnvalidate ((TestWebhookTransform
-> Either TransformErrorBundle TestWebhookTransform)
-> Unvalidated TestWebhookTransform
-> Either TransformErrorBundle (Unvalidated TestWebhookTransform))
-> ((RequestTransform
-> Either TransformErrorBundle RequestTransform)
-> TestWebhookTransform
-> Either TransformErrorBundle TestWebhookTransform)
-> LensLike
(Either TransformErrorBundle)
(Unvalidated TestWebhookTransform)
(Unvalidated TestWebhookTransform)
RequestTransform
RequestTransform
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RequestTransform -> Either TransformErrorBundle RequestTransform)
-> TestWebhookTransform
-> Either TransformErrorBundle TestWebhookTransform
Lens' TestWebhookTransform RequestTransform
twtTransformer)
(TestWebhookTransform -> m EncJSON
forall (m :: * -> *). QErrM m => TestWebhookTransform -> m EncJSON
runTestWebhookTransform (TestWebhookTransform -> m EncJSON)
-> (Unvalidated TestWebhookTransform -> TestWebhookTransform)
-> Unvalidated TestWebhookTransform
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unvalidated TestWebhookTransform -> TestWebhookTransform
forall a. Unvalidated a -> a
_unUnvalidate)
Unvalidated TestWebhookTransform
q
RMSetQueryTagsConfig SetQueryTagsConfig
q -> SetQueryTagsConfig -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
SetQueryTagsConfig -> m EncJSON
runSetQueryTagsConfig SetQueryTagsConfig
q
RMBulk [RQLMetadataRequest]
q -> [EncJSON] -> EncJSON
encJFromList ([EncJSON] -> EncJSON) -> m [EncJSON] -> m EncJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (RQLMetadataRequest -> m EncJSON)
-> [RQLMetadataRequest] -> m [EncJSON]
forall (m :: * -> *) a b. QErrM m => (a -> m b) -> [a] -> m [b]
indexedMapM (Environment
-> MetadataResourceVersion -> RQLMetadataRequest -> m EncJSON
forall (m :: * -> *) r.
(MonadIO m, MonadBaseControl IO m, CacheRWM m, MonadTrace m,
UserInfoM m, HasHttpManagerM m, MetadataM m,
MonadMetadataStorageQueryAPI m, HasServerConfigCtx m,
MonadReader r m, Has (Logger Hasura) r) =>
Environment
-> MetadataResourceVersion -> RQLMetadataRequest -> m EncJSON
runMetadataQueryM Environment
env MetadataResourceVersion
currentResourceVersion) [RQLMetadataRequest]
q
where
dispatchMetadata ::
(forall b. BackendMetadata b => i b -> a) ->
AnyBackend i ->
a
dispatchMetadata :: (forall (b :: BackendType). BackendMetadata b => i b -> a)
-> AnyBackend i -> a
dispatchMetadata forall (b :: BackendType). BackendMetadata b => i b -> a
f AnyBackend i
x = AnyBackend i
-> (forall (b :: BackendType). BackendMetadata b => i b -> a) -> a
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
dispatchAnyBackend @BackendMetadata AnyBackend i
x forall (b :: BackendType). BackendMetadata b => i b -> a
f
dispatchEventTrigger :: (forall b. BackendEventTrigger b => i b -> a) -> AnyBackend i -> a
dispatchEventTrigger :: (forall (b :: BackendType). BackendEventTrigger b => i b -> a)
-> AnyBackend i -> a
dispatchEventTrigger forall (b :: BackendType). BackendEventTrigger b => i b -> a
f AnyBackend i
x = AnyBackend i
-> (forall (b :: BackendType). BackendEventTrigger b => i b -> a)
-> a
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
dispatchAnyBackend @BackendEventTrigger AnyBackend i
x forall (b :: BackendType). BackendEventTrigger b => i b -> a
f
dispatchMetadataAndEventTrigger ::
(forall b. (BackendMetadata b, BackendEventTrigger b) => i b -> a) ->
AnyBackend i ->
a
dispatchMetadataAndEventTrigger :: (forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a)
-> AnyBackend i -> a
dispatchMetadataAndEventTrigger forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a
f AnyBackend i
x = AnyBackend i
-> (forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a)
-> a
forall (c1 :: BackendType -> Constraint)
(c2 :: BackendType -> Constraint) (i :: BackendType -> *) r.
(AllBackendsSatisfy c1, AllBackendsSatisfy c2) =>
AnyBackend i
-> (forall (b :: BackendType). (c1 b, c2 b) => i b -> r) -> r
dispatchAnyBackendWithTwoConstraints @BackendMetadata @BackendEventTrigger AnyBackend i
x forall (b :: BackendType).
(BackendMetadata b, BackendEventTrigger b) =>
i b -> a
f
runMetadataQueryV2M ::
( MonadIO m,
CacheRWM m,
MetadataM m,
MonadMetadataStorageQueryAPI m,
MonadReader r m,
Has (L.Logger L.Hasura) r
) =>
MetadataResourceVersion ->
RQLMetadataV2 ->
m EncJSON
runMetadataQueryV2M :: MetadataResourceVersion -> RQLMetadataV2 -> m EncJSON
runMetadataQueryV2M MetadataResourceVersion
currentResourceVersion = \case
RMV2ReplaceMetadata ReplaceMetadataV2
q -> ReplaceMetadataV2 -> m EncJSON
forall (m :: * -> *) r.
(QErrM m, CacheRWM m, MetadataM m, MonadIO m,
MonadMetadataStorageQueryAPI m, MonadReader r m,
Has (Logger Hasura) r) =>
ReplaceMetadataV2 -> m EncJSON
runReplaceMetadataV2 ReplaceMetadataV2
q
RMV2ExportMetadata ExportMetadata
q -> MetadataResourceVersion -> ExportMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, MetadataM m) =>
MetadataResourceVersion -> ExportMetadata -> m EncJSON
runExportMetadataV2 MetadataResourceVersion
currentResourceVersion ExportMetadata
q