{-# LANGUAGE TemplateHaskell #-}
module Hasura.Server.API.Query
( RQLQuery,
queryModifiesSchemaCache,
requiresAdmin,
runQuery,
)
where
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson
import Data.Aeson.Casing
import Data.Aeson.TH
import Data.Environment qualified as Env
import Data.Has (Has)
import Hasura.Backends.Postgres.DDL.RunSQL
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.GraphQL.Execute.Backend
import Hasura.Logging qualified as L
import Hasura.Metadata.Class
import Hasura.Prelude
import Hasura.RQL.DDL.Action
import Hasura.RQL.DDL.ComputedField
import Hasura.RQL.DDL.CustomTypes
import Hasura.RQL.DDL.Endpoint
import Hasura.RQL.DDL.EventTrigger
import Hasura.RQL.DDL.Metadata
import Hasura.RQL.DDL.Permission
import Hasura.RQL.DDL.QueryCollection
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.DML.Count
import Hasura.RQL.DML.Delete
import Hasura.RQL.DML.Insert
import Hasura.RQL.DML.Select
import Hasura.RQL.DML.Types
import Hasura.RQL.DML.Update
import Hasura.RQL.Types.Allowlist
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.CustomTypes
import Hasura.RQL.Types.Endpoint
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.QueryCollection
import Hasura.RQL.Types.RemoteSchema
import Hasura.RQL.Types.Run
import Hasura.RQL.Types.ScheduledTrigger
import Hasura.RQL.Types.SchemaCache.Build
import Hasura.RQL.Types.Source
import Hasura.SQL.Backend
import Hasura.Server.Types
import Hasura.Server.Utils
import Hasura.Session
import Hasura.Tracing qualified as Tracing
import Network.HTTP.Client qualified as HTTP
import Network.HTTP.Client.Manager (HasHttpManagerM (..))
data RQLQueryV1
= RQAddExistingTableOrView !(TrackTable ('Postgres 'Vanilla))
| RQTrackTable !(TrackTable ('Postgres 'Vanilla))
| RQUntrackTable !(UntrackTable ('Postgres 'Vanilla))
| RQSetTableIsEnum !SetTableIsEnum
| RQSetTableCustomization !(SetTableCustomization ('Postgres 'Vanilla))
| RQTrackFunction !(TrackFunction ('Postgres 'Vanilla))
| RQUntrackFunction !(UnTrackFunction ('Postgres 'Vanilla))
| RQCreateObjectRelationship !(CreateObjRel ('Postgres 'Vanilla))
| RQCreateArrayRelationship !(CreateArrRel ('Postgres 'Vanilla))
| RQDropRelationship !(DropRel ('Postgres 'Vanilla))
| !(SetRelComment ('Postgres 'Vanilla))
| RQRenameRelationship !(RenameRel ('Postgres 'Vanilla))
|
RQAddComputedField !(AddComputedField ('Postgres 'Vanilla))
| RQDropComputedField !(DropComputedField ('Postgres 'Vanilla))
| RQCreateRemoteRelationship !(CreateFromSourceRelationship ('Postgres 'Vanilla))
| RQUpdateRemoteRelationship !(CreateFromSourceRelationship ('Postgres 'Vanilla))
| RQDeleteRemoteRelationship !(DeleteFromSourceRelationship ('Postgres 'Vanilla))
| RQCreateInsertPermission !(CreatePerm InsPerm ('Postgres 'Vanilla))
| RQCreateSelectPermission !(CreatePerm SelPerm ('Postgres 'Vanilla))
| RQCreateUpdatePermission !(CreatePerm UpdPerm ('Postgres 'Vanilla))
| RQCreateDeletePermission !(CreatePerm DelPerm ('Postgres 'Vanilla))
| RQDropInsertPermission !(DropPerm ('Postgres 'Vanilla))
| RQDropSelectPermission !(DropPerm ('Postgres 'Vanilla))
| RQDropUpdatePermission !(DropPerm ('Postgres 'Vanilla))
| RQDropDeletePermission !(DropPerm ('Postgres 'Vanilla))
| !(SetPermComment ('Postgres 'Vanilla))
| RQGetInconsistentMetadata !GetInconsistentMetadata
| RQDropInconsistentMetadata !DropInconsistentMetadata
| RQInsert !InsertQuery
| RQSelect !SelectQuery
| RQUpdate !UpdateQuery
| RQDelete !DeleteQuery
| RQCount !CountQuery
| RQBulk ![RQLQuery]
|
RQAddRemoteSchema !AddRemoteSchemaQuery
| RQUpdateRemoteSchema !AddRemoteSchemaQuery
| RQRemoveRemoteSchema !RemoteSchemaNameQuery
| RQReloadRemoteSchema !RemoteSchemaNameQuery
| RQIntrospectRemoteSchema !RemoteSchemaNameQuery
| RQCreateEventTrigger !(CreateEventTriggerQuery ('Postgres 'Vanilla))
| RQDeleteEventTrigger !(DeleteEventTriggerQuery ('Postgres 'Vanilla))
| RQRedeliverEvent !(RedeliverEventQuery ('Postgres 'Vanilla))
| RQInvokeEventTrigger !(InvokeEventTriggerQuery ('Postgres 'Vanilla))
|
RQCreateCronTrigger !CreateCronTrigger
| RQDeleteCronTrigger !ScheduledTriggerName
| RQCreateScheduledEvent !CreateScheduledEvent
|
RQCreateQueryCollection !CreateCollection
| RQRenameQueryCollection !RenameCollection
| RQDropQueryCollection !DropCollection
| RQAddQueryToCollection !AddQueryToCollection
| RQDropQueryFromCollection !DropQueryFromCollection
| RQAddCollectionToAllowlist !AllowlistEntry
| RQDropCollectionFromAllowlist !DropCollectionFromAllowlist
| RQRunSql !RunSQL
| RQReplaceMetadata !ReplaceMetadata
| RQExportMetadata !ExportMetadata
| RQClearMetadata !ClearMetadata
| RQReloadMetadata !ReloadMetadata
| RQCreateAction !CreateAction
| RQDropAction !DropAction
| RQUpdateAction !UpdateAction
| RQCreateActionPermission !CreateActionPermission
| RQDropActionPermission !DropActionPermission
| RQCreateRestEndpoint !CreateEndpoint
| RQDropRestEndpoint !DropEndpoint
| RQDumpInternalState !DumpInternalState
| RQSetCustomTypes !CustomTypes
data RQLQueryV2
= RQV2TrackTable !(TrackTableV2 ('Postgres 'Vanilla))
| RQV2SetTableCustomFields !SetTableCustomFields
| RQV2TrackFunction !(TrackFunctionV2 ('Postgres 'Vanilla))
| RQV2ReplaceMetadata !ReplaceMetadataV2
data RQLQuery
= RQV1 !RQLQueryV1
| RQV2 !RQLQueryV2
$( concat
<$> sequence
[ [d|
instance FromJSON RQLQuery where
parseJSON = withObject "Object" $ \o -> do
mVersion <- o .:? "version"
let version = fromMaybe VIVersion1 mVersion
val = Object o
case version of
VIVersion1 -> RQV1 <$> parseJSON val
VIVersion2 -> RQV2 <$> parseJSON val
|],
deriveFromJSON
defaultOptions
{ constructorTagModifier = snakeCase . drop 2,
sumEncoding = TaggedObject "type" "args"
}
''RQLQueryV1,
deriveFromJSON
defaultOptions
{ constructorTagModifier = snakeCase . drop 4,
sumEncoding = TaggedObject "type" "args",
tagSingleConstructors = True
}
''RQLQueryV2
]
)
runQuery ::
( MonadIO m,
Tracing.MonadTrace m,
MonadBaseControl IO m,
MonadMetadataStorage m,
MonadResolveSource m,
MonadQueryTags m
) =>
Env.Environment ->
L.Logger L.Hasura ->
InstanceId ->
UserInfo ->
RebuildableSchemaCache ->
HTTP.Manager ->
ServerConfigCtx ->
RQLQuery ->
m (EncJSON, RebuildableSchemaCache)
runQuery :: Environment
-> Logger Hasura
-> InstanceId
-> UserInfo
-> RebuildableSchemaCache
-> Manager
-> ServerConfigCtx
-> RQLQuery
-> m (EncJSON, RebuildableSchemaCache)
runQuery Environment
env Logger Hasura
logger InstanceId
instanceId UserInfo
userInfo RebuildableSchemaCache
sc Manager
hMgr ServerConfigCtx
serverConfigCtx RQLQuery
query = do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ((ServerConfigCtx -> ReadOnlyMode
_sccReadOnlyMode ServerConfigCtx
serverConfigCtx ReadOnlyMode -> ReadOnlyMode -> Bool
forall a. Eq a => a -> a -> Bool
== ReadOnlyMode
ReadOnlyModeEnabled) Bool -> Bool -> Bool
&& RQLQuery -> Bool
queryModifiesUserDB RQLQuery
query) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotSupported Text
"Cannot run write queries when read-only mode is enabled"
(Metadata
metadata, MetadataResourceVersion
currentResourceVersion) <- m (Metadata, MetadataResourceVersion)
forall (m :: * -> *).
MonadMetadataStorage m =>
m (Metadata, MetadataResourceVersion)
fetchMetadata
(EncJSON, RebuildableSchemaCache, CacheInvalidations, Metadata)
result <-
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 (Environment
-> RQLQuery
-> ReaderT (Logger Hasura) (MetadataT (CacheRWT (RunT m))) EncJSON
forall (m :: * -> *) r.
(CacheRWM m, UserInfoM m, MonadBaseControl IO m, MonadIO m,
HasHttpManagerM m, HasServerConfigCtx m, MonadTrace m, MetadataM m,
MonadMetadataStorageQueryAPI m, MonadQueryTags m, MonadReader r m,
Has (Logger Hasura) r) =>
Environment -> RQLQuery -> m EncJSON
runQueryM Environment
env RQLQuery
query) Logger Hasura
logger MetadataT (CacheRWT (RunT m)) EncJSON
-> (MetadataT (CacheRWT (RunT m)) EncJSON
-> m (EncJSON, RebuildableSchemaCache, CacheInvalidations,
Metadata))
-> m (EncJSON, RebuildableSchemaCache, CacheInvalidations,
Metadata)
forall a b. a -> (a -> b) -> b
& \MetadataT (CacheRWT (RunT m)) EncJSON
x -> do
((EncJSON
js, Metadata
meta), RebuildableSchemaCache
rsc, CacheInvalidations
ci) <-
MetadataT (CacheRWT (RunT m)) EncJSON
x 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
sc
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 RunCtx
runCtx
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
(EncJSON, RebuildableSchemaCache, CacheInvalidations, Metadata)
-> m (EncJSON, RebuildableSchemaCache, CacheInvalidations,
Metadata)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EncJSON
js, RebuildableSchemaCache
rsc, CacheInvalidations
ci, Metadata
meta)
MetadataResourceVersion
-> (EncJSON, RebuildableSchemaCache, CacheInvalidations, Metadata)
-> m (EncJSON, RebuildableSchemaCache)
withReload MetadataResourceVersion
currentResourceVersion (EncJSON, RebuildableSchemaCache, CacheInvalidations, Metadata)
result
where
runCtx :: RunCtx
runCtx = UserInfo -> Manager -> ServerConfigCtx -> RunCtx
RunCtx UserInfo
userInfo Manager
hMgr ServerConfigCtx
serverConfigCtx
withReload :: MetadataResourceVersion
-> (EncJSON, RebuildableSchemaCache, CacheInvalidations, Metadata)
-> m (EncJSON, RebuildableSchemaCache)
withReload MetadataResourceVersion
currentResourceVersion (EncJSON
result, RebuildableSchemaCache
updatedCache, CacheInvalidations
invalidations, Metadata
updatedMetadata) = do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (RQLQuery -> Bool
queryModifiesSchemaCache RQLQuery
query) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
case (ServerConfigCtx -> MaintenanceMode ()
_sccMaintenanceMode ServerConfigCtx
serverConfigCtx) of
MaintenanceMode ()
MaintenanceModeDisabled -> do
MetadataResourceVersion
newResourceVersion <- MetadataResourceVersion -> Metadata -> m MetadataResourceVersion
forall (m :: * -> *).
MonadMetadataStorage m =>
MetadataResourceVersion -> Metadata -> m MetadataResourceVersion
setMetadata MetadataResourceVersion
currentResourceVersion Metadata
updatedMetadata
MetadataResourceVersion -> InstanceId -> CacheInvalidations -> m ()
forall (m :: * -> *).
MonadMetadataStorage m =>
MetadataResourceVersion -> InstanceId -> CacheInvalidations -> m ()
notifySchemaCacheSync MetadataResourceVersion
newResourceVersion InstanceId
instanceId CacheInvalidations
invalidations
MaintenanceModeEnabled () ->
Text -> m ()
forall (m :: * -> *) a. QErrM m => Text -> m a
throw500 Text
"metadata cannot be modified in maintenance mode"
(EncJSON, RebuildableSchemaCache)
-> m (EncJSON, RebuildableSchemaCache)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EncJSON
result, RebuildableSchemaCache
updatedCache)
queryModifiesSchemaCache :: RQLQuery -> Bool
queryModifiesSchemaCache :: RQLQuery -> Bool
queryModifiesSchemaCache (RQV1 RQLQueryV1
qi) = case RQLQueryV1
qi of
RQAddExistingTableOrView TrackTable ('Postgres 'Vanilla)
_ -> Bool
True
RQTrackTable TrackTable ('Postgres 'Vanilla)
_ -> Bool
True
RQUntrackTable UntrackTable ('Postgres 'Vanilla)
_ -> Bool
True
RQTrackFunction TrackFunction ('Postgres 'Vanilla)
_ -> Bool
True
RQUntrackFunction UnTrackFunction ('Postgres 'Vanilla)
_ -> Bool
True
RQSetTableIsEnum SetTableIsEnum
_ -> Bool
True
RQCreateObjectRelationship CreateObjRel ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateArrayRelationship CreateArrRel ('Postgres 'Vanilla)
_ -> Bool
True
RQDropRelationship DropRel ('Postgres 'Vanilla)
_ -> Bool
True
RQSetRelationshipComment SetRelComment ('Postgres 'Vanilla)
_ -> Bool
False
RQRenameRelationship RenameRel ('Postgres 'Vanilla)
_ -> Bool
True
RQAddComputedField AddComputedField ('Postgres 'Vanilla)
_ -> Bool
True
RQDropComputedField DropComputedField ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
True
RQUpdateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
True
RQDeleteRemoteRelationship DeleteFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateInsertPermission CreatePerm InsPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateSelectPermission CreatePerm SelPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateUpdatePermission CreatePerm UpdPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateDeletePermission CreatePerm DelPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropInsertPermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropSelectPermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropUpdatePermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropDeletePermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQSetPermissionComment SetPermComment ('Postgres 'Vanilla)
_ -> Bool
False
RQGetInconsistentMetadata GetInconsistentMetadata
_ -> Bool
False
RQDropInconsistentMetadata DropInconsistentMetadata
_ -> Bool
True
RQInsert InsertQuery
_ -> Bool
False
RQSelect SelectQuery
_ -> Bool
False
RQUpdate UpdateQuery
_ -> Bool
False
RQDelete DeleteQuery
_ -> Bool
False
RQCount CountQuery
_ -> Bool
False
RQAddRemoteSchema AddRemoteSchemaQuery
_ -> Bool
True
RQUpdateRemoteSchema AddRemoteSchemaQuery
_ -> Bool
True
RQRemoveRemoteSchema RemoteSchemaNameQuery
_ -> Bool
True
RQReloadRemoteSchema RemoteSchemaNameQuery
_ -> Bool
True
RQIntrospectRemoteSchema RemoteSchemaNameQuery
_ -> Bool
False
RQCreateEventTrigger CreateEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQDeleteEventTrigger DeleteEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQRedeliverEvent RedeliverEventQuery ('Postgres 'Vanilla)
_ -> Bool
False
RQInvokeEventTrigger InvokeEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateCronTrigger CreateCronTrigger
_ -> Bool
True
RQDeleteCronTrigger ScheduledTriggerName
_ -> Bool
True
RQCreateScheduledEvent CreateScheduledEvent
_ -> Bool
False
RQCreateQueryCollection CreateCollection
_ -> Bool
True
RQRenameQueryCollection RenameCollection
_ -> Bool
True
RQDropQueryCollection DropCollection
_ -> Bool
True
RQAddQueryToCollection AddQueryToCollection
_ -> Bool
True
RQDropQueryFromCollection DropQueryFromCollection
_ -> Bool
True
RQAddCollectionToAllowlist AllowlistEntry
_ -> Bool
True
RQDropCollectionFromAllowlist DropCollectionFromAllowlist
_ -> Bool
True
RQRunSql RunSQL
q -> RunSQL -> Bool
isSchemaCacheBuildRequiredRunSQL RunSQL
q
RQReplaceMetadata ReplaceMetadata
_ -> Bool
True
RQExportMetadata ExportMetadata
_ -> Bool
False
RQClearMetadata ClearMetadata
_ -> Bool
True
RQReloadMetadata ReloadMetadata
_ -> Bool
True
RQCreateRestEndpoint CreateEndpoint
_ -> Bool
True
RQDropRestEndpoint DropEndpoint
_ -> Bool
True
RQCreateAction CreateAction
_ -> Bool
True
RQDropAction DropAction
_ -> Bool
True
RQUpdateAction UpdateAction
_ -> Bool
True
RQCreateActionPermission CreateActionPermission
_ -> Bool
True
RQDropActionPermission DropActionPermission
_ -> Bool
True
RQDumpInternalState DumpInternalState
_ -> Bool
False
RQSetCustomTypes CustomTypes
_ -> Bool
True
RQSetTableCustomization SetTableCustomization ('Postgres 'Vanilla)
_ -> Bool
True
RQBulk [RQLQuery]
qs -> (RQLQuery -> Bool) -> [RQLQuery] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any RQLQuery -> Bool
queryModifiesSchemaCache [RQLQuery]
qs
queryModifiesSchemaCache (RQV2 RQLQueryV2
qi) = case RQLQueryV2
qi of
RQV2TrackTable TrackTableV2 ('Postgres 'Vanilla)
_ -> Bool
True
RQV2SetTableCustomFields SetTableCustomFields
_ -> Bool
True
RQV2TrackFunction TrackFunctionV2 ('Postgres 'Vanilla)
_ -> Bool
True
RQV2ReplaceMetadata ReplaceMetadataV2
_ -> Bool
True
queryModifiesUserDB :: RQLQuery -> Bool
queryModifiesUserDB :: RQLQuery -> Bool
queryModifiesUserDB (RQV1 RQLQueryV1
qi) = case RQLQueryV1
qi of
RQAddExistingTableOrView TrackTable ('Postgres 'Vanilla)
_ -> Bool
False
RQTrackTable TrackTable ('Postgres 'Vanilla)
_ -> Bool
False
RQUntrackTable UntrackTable ('Postgres 'Vanilla)
_ -> Bool
False
RQTrackFunction TrackFunction ('Postgres 'Vanilla)
_ -> Bool
False
RQUntrackFunction UnTrackFunction ('Postgres 'Vanilla)
_ -> Bool
False
RQSetTableIsEnum SetTableIsEnum
_ -> Bool
False
RQCreateObjectRelationship CreateObjRel ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateArrayRelationship CreateArrRel ('Postgres 'Vanilla)
_ -> Bool
False
RQDropRelationship DropRel ('Postgres 'Vanilla)
_ -> Bool
False
RQSetRelationshipComment SetRelComment ('Postgres 'Vanilla)
_ -> Bool
False
RQRenameRelationship RenameRel ('Postgres 'Vanilla)
_ -> Bool
False
RQAddComputedField AddComputedField ('Postgres 'Vanilla)
_ -> Bool
False
RQDropComputedField DropComputedField ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
False
RQUpdateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
False
RQDeleteRemoteRelationship DeleteFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateInsertPermission CreatePerm InsPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateSelectPermission CreatePerm SelPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateUpdatePermission CreatePerm UpdPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateDeletePermission CreatePerm DelPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQDropInsertPermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQDropSelectPermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQDropUpdatePermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQDropDeletePermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
False
RQSetPermissionComment SetPermComment ('Postgres 'Vanilla)
_ -> Bool
False
RQGetInconsistentMetadata GetInconsistentMetadata
_ -> Bool
False
RQDropInconsistentMetadata DropInconsistentMetadata
_ -> Bool
False
RQInsert InsertQuery
_ -> Bool
True
RQSelect SelectQuery
_ -> Bool
False
RQUpdate UpdateQuery
_ -> Bool
True
RQDelete DeleteQuery
_ -> Bool
True
RQCount CountQuery
_ -> Bool
False
RQAddRemoteSchema AddRemoteSchemaQuery
_ -> Bool
False
RQUpdateRemoteSchema AddRemoteSchemaQuery
_ -> Bool
False
RQRemoveRemoteSchema RemoteSchemaNameQuery
_ -> Bool
False
RQReloadRemoteSchema RemoteSchemaNameQuery
_ -> Bool
False
RQIntrospectRemoteSchema RemoteSchemaNameQuery
_ -> Bool
False
RQCreateEventTrigger CreateEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQDeleteEventTrigger DeleteEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQRedeliverEvent RedeliverEventQuery ('Postgres 'Vanilla)
_ -> Bool
False
RQInvokeEventTrigger InvokeEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
False
RQCreateCronTrigger CreateCronTrigger
_ -> Bool
False
RQDeleteCronTrigger ScheduledTriggerName
_ -> Bool
False
RQCreateScheduledEvent CreateScheduledEvent
_ -> Bool
False
RQCreateQueryCollection CreateCollection
_ -> Bool
False
RQRenameQueryCollection RenameCollection
_ -> Bool
False
RQDropQueryCollection DropCollection
_ -> Bool
False
RQAddQueryToCollection AddQueryToCollection
_ -> Bool
False
RQDropQueryFromCollection DropQueryFromCollection
_ -> Bool
False
RQAddCollectionToAllowlist AllowlistEntry
_ -> Bool
False
RQDropCollectionFromAllowlist DropCollectionFromAllowlist
_ -> Bool
False
RQRunSql RunSQL
_ -> Bool
True
RQReplaceMetadata ReplaceMetadata
_ -> Bool
True
RQExportMetadata ExportMetadata
_ -> Bool
False
RQClearMetadata ClearMetadata
_ -> Bool
False
RQReloadMetadata ReloadMetadata
_ -> Bool
False
RQCreateRestEndpoint CreateEndpoint
_ -> Bool
False
RQDropRestEndpoint DropEndpoint
_ -> Bool
False
RQCreateAction CreateAction
_ -> Bool
False
RQDropAction DropAction
_ -> Bool
False
RQUpdateAction UpdateAction
_ -> Bool
False
RQCreateActionPermission CreateActionPermission
_ -> Bool
False
RQDropActionPermission DropActionPermission
_ -> Bool
False
RQDumpInternalState DumpInternalState
_ -> Bool
False
RQSetCustomTypes CustomTypes
_ -> Bool
False
RQSetTableCustomization SetTableCustomization ('Postgres 'Vanilla)
_ -> Bool
False
RQBulk [RQLQuery]
qs -> (RQLQuery -> Bool) -> [RQLQuery] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any RQLQuery -> Bool
queryModifiesUserDB [RQLQuery]
qs
queryModifiesUserDB (RQV2 RQLQueryV2
qi) = case RQLQueryV2
qi of
RQV2TrackTable TrackTableV2 ('Postgres 'Vanilla)
_ -> Bool
False
RQV2SetTableCustomFields SetTableCustomFields
_ -> Bool
False
RQV2TrackFunction TrackFunctionV2 ('Postgres 'Vanilla)
_ -> Bool
False
RQV2ReplaceMetadata ReplaceMetadataV2
_ -> Bool
True
runQueryM ::
( CacheRWM m,
UserInfoM m,
MonadBaseControl IO m,
MonadIO m,
HasHttpManagerM m,
HasServerConfigCtx m,
Tracing.MonadTrace m,
MetadataM m,
MonadMetadataStorageQueryAPI m,
MonadQueryTags m,
MonadReader r m,
Has (L.Logger L.Hasura) r
) =>
Env.Environment ->
RQLQuery ->
m EncJSON
runQueryM :: Environment -> RQLQuery -> m EncJSON
runQueryM Environment
env RQLQuery
rq = Text -> m EncJSON -> m EncJSON
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"args" (m EncJSON -> m EncJSON) -> m EncJSON -> m EncJSON
forall a b. (a -> b) -> a -> b
$ case RQLQuery
rq of
RQV1 RQLQueryV1
q -> RQLQueryV1 -> m EncJSON
runQueryV1M RQLQueryV1
q
RQV2 RQLQueryV2
q -> RQLQueryV2 -> m EncJSON
runQueryV2M RQLQueryV2
q
where
runQueryV1M :: RQLQueryV1 -> m EncJSON
runQueryV1M = \case
RQAddExistingTableOrView TrackTable ('Postgres 'Vanilla)
q -> TrackTable ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
TrackTable b -> m EncJSON
runTrackTableQ TrackTable ('Postgres 'Vanilla)
q
RQTrackTable TrackTable ('Postgres 'Vanilla)
q -> TrackTable ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
TrackTable b -> m EncJSON
runTrackTableQ TrackTable ('Postgres 'Vanilla)
q
RQUntrackTable UntrackTable ('Postgres 'Vanilla)
q -> UntrackTable ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(CacheRWM m, QErrM m, MetadataM m, BackendMetadata b,
BackendEventTrigger b, MonadIO m) =>
UntrackTable b -> m EncJSON
runUntrackTableQ UntrackTable ('Postgres 'Vanilla)
q
RQSetTableIsEnum SetTableIsEnum
q -> SetTableIsEnum -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
SetTableIsEnum -> m EncJSON
runSetExistingTableIsEnumQ SetTableIsEnum
q
RQSetTableCustomization SetTableCustomization ('Postgres 'Vanilla)
q -> SetTableCustomization ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
SetTableCustomization b -> m EncJSON
runSetTableCustomization SetTableCustomization ('Postgres 'Vanilla)
q
RQTrackFunction TrackFunction ('Postgres 'Vanilla)
q -> TrackFunction ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
TrackFunction b -> m EncJSON
runTrackFunc TrackFunction ('Postgres 'Vanilla)
q
RQUntrackFunction UnTrackFunction ('Postgres 'Vanilla)
q -> UnTrackFunction ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
UnTrackFunction b -> m EncJSON
runUntrackFunc UnTrackFunction ('Postgres 'Vanilla)
q
RQCreateObjectRelationship CreateObjRel ('Postgres 'Vanilla)
q -> RelType
-> WithTable
('Postgres 'Vanilla) (RelDef (ObjRelUsing ('Postgres 'Vanilla)))
-> 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
('Postgres 'Vanilla) (RelDef (ObjRelUsing ('Postgres 'Vanilla)))
-> m EncJSON)
-> WithTable
('Postgres 'Vanilla) (RelDef (ObjRelUsing ('Postgres 'Vanilla)))
-> m EncJSON
forall a b. (a -> b) -> a -> b
$ CreateObjRel ('Postgres 'Vanilla)
-> WithTable
('Postgres 'Vanilla) (RelDef (ObjRelUsing ('Postgres 'Vanilla)))
forall (b :: BackendType).
CreateObjRel b -> WithTable b (ObjRelDef b)
unCreateObjRel CreateObjRel ('Postgres 'Vanilla)
q
RQCreateArrayRelationship CreateArrRel ('Postgres 'Vanilla)
q -> RelType
-> WithTable
('Postgres 'Vanilla) (RelDef (ArrRelUsing ('Postgres 'Vanilla)))
-> 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
('Postgres 'Vanilla) (RelDef (ArrRelUsing ('Postgres 'Vanilla)))
-> m EncJSON)
-> WithTable
('Postgres 'Vanilla) (RelDef (ArrRelUsing ('Postgres 'Vanilla)))
-> m EncJSON
forall a b. (a -> b) -> a -> b
$ CreateArrRel ('Postgres 'Vanilla)
-> WithTable
('Postgres 'Vanilla) (RelDef (ArrRelUsing ('Postgres 'Vanilla)))
forall (b :: BackendType).
CreateArrRel b -> WithTable b (ArrRelDef b)
unCreateArrRel CreateArrRel ('Postgres 'Vanilla)
q
RQDropRelationship DropRel ('Postgres 'Vanilla)
q -> DropRel ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
DropRel b -> m EncJSON
runDropRel DropRel ('Postgres 'Vanilla)
q
RQSetRelationshipComment SetRelComment ('Postgres 'Vanilla)
q -> SetRelComment ('Postgres 'Vanilla) -> m EncJSON
forall (m :: * -> *) (b :: BackendType).
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
SetRelComment b -> m EncJSON
runSetRelComment SetRelComment ('Postgres 'Vanilla)
q
RQRenameRelationship RenameRel ('Postgres 'Vanilla)
q -> RenameRel ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
RenameRel b -> m EncJSON
runRenameRel RenameRel ('Postgres 'Vanilla)
q
RQAddComputedField AddComputedField ('Postgres 'Vanilla)
q -> AddComputedField ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
AddComputedField b -> m EncJSON
runAddComputedField AddComputedField ('Postgres 'Vanilla)
q
RQDropComputedField DropComputedField ('Postgres 'Vanilla)
q -> DropComputedField ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, BackendMetadata b) =>
DropComputedField b -> m EncJSON
runDropComputedField DropComputedField ('Postgres 'Vanilla)
q
RQCreateInsertPermission CreatePerm InsPerm ('Postgres 'Vanilla)
q -> CreatePerm InsPerm ('Postgres 'Vanilla) -> 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 CreatePerm InsPerm ('Postgres 'Vanilla)
q
RQCreateSelectPermission CreatePerm SelPerm ('Postgres 'Vanilla)
q -> CreatePerm SelPerm ('Postgres 'Vanilla) -> 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 CreatePerm SelPerm ('Postgres 'Vanilla)
q
RQCreateUpdatePermission CreatePerm UpdPerm ('Postgres 'Vanilla)
q -> CreatePerm UpdPerm ('Postgres 'Vanilla) -> 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 CreatePerm UpdPerm ('Postgres 'Vanilla)
q
RQCreateDeletePermission CreatePerm DelPerm ('Postgres 'Vanilla)
q -> CreatePerm DelPerm ('Postgres 'Vanilla) -> 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 CreatePerm DelPerm ('Postgres 'Vanilla)
q
RQDropInsertPermission DropPerm ('Postgres 'Vanilla)
q -> PermType -> DropPerm ('Postgres 'Vanilla) -> 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 DropPerm ('Postgres 'Vanilla)
q
RQDropSelectPermission DropPerm ('Postgres 'Vanilla)
q -> PermType -> DropPerm ('Postgres 'Vanilla) -> 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 DropPerm ('Postgres 'Vanilla)
q
RQDropUpdatePermission DropPerm ('Postgres 'Vanilla)
q -> PermType -> DropPerm ('Postgres 'Vanilla) -> 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 DropPerm ('Postgres 'Vanilla)
q
RQDropDeletePermission DropPerm ('Postgres 'Vanilla)
q -> PermType -> DropPerm ('Postgres 'Vanilla) -> 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 DropPerm ('Postgres 'Vanilla)
q
RQSetPermissionComment SetPermComment ('Postgres 'Vanilla)
q -> SetPermComment ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m, BackendMetadata b) =>
SetPermComment b -> m EncJSON
runSetPermComment SetPermComment ('Postgres 'Vanilla)
q
RQGetInconsistentMetadata GetInconsistentMetadata
q -> GetInconsistentMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRM m) =>
GetInconsistentMetadata -> m EncJSON
runGetInconsistentMetadata GetInconsistentMetadata
q
RQDropInconsistentMetadata DropInconsistentMetadata
q -> DropInconsistentMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
DropInconsistentMetadata -> m EncJSON
runDropInconsistentMetadata DropInconsistentMetadata
q
RQInsert InsertQuery
q -> InsertQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m, HasServerConfigCtx m, MonadIO m,
MonadTrace m, MonadBaseControl IO m, MetadataM m) =>
InsertQuery -> m EncJSON
runInsert InsertQuery
q
RQSelect SelectQuery
q -> SelectQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m, HasServerConfigCtx m, MonadIO m,
MonadBaseControl IO m, MonadTrace m, MetadataM m) =>
SelectQuery -> m EncJSON
runSelect SelectQuery
q
RQUpdate UpdateQuery
q -> UpdateQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m, HasServerConfigCtx m,
MonadBaseControl IO m, MonadIO m, MonadTrace m, MetadataM m) =>
UpdateQuery -> m EncJSON
runUpdate UpdateQuery
q
RQDelete DeleteQuery
q -> DeleteQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m, HasServerConfigCtx m, MonadIO m,
MonadTrace m, MonadBaseControl IO m, MetadataM m) =>
DeleteQuery -> m EncJSON
runDelete DeleteQuery
q
RQCount CountQuery
q -> CountQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m, MonadIO m, MonadBaseControl IO m,
MonadTrace m, MetadataM m) =>
CountQuery -> m EncJSON
runCount CountQuery
q
RQAddRemoteSchema 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
RQUpdateRemoteSchema 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
RQRemoveRemoteSchema RemoteSchemaNameQuery
q -> RemoteSchemaNameQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRWM m, MetadataM m) =>
RemoteSchemaNameQuery -> m EncJSON
runRemoveRemoteSchema RemoteSchemaNameQuery
q
RQReloadRemoteSchema RemoteSchemaNameQuery
q -> RemoteSchemaNameQuery -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
RemoteSchemaNameQuery -> m EncJSON
runReloadRemoteSchema RemoteSchemaNameQuery
q
RQIntrospectRemoteSchema RemoteSchemaNameQuery
q -> RemoteSchemaNameQuery -> m EncJSON
forall (m :: * -> *).
(CacheRM m, QErrM m) =>
RemoteSchemaNameQuery -> m EncJSON
runIntrospectRemoteSchema RemoteSchemaNameQuery
q
RQCreateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
q -> CreateFromSourceRelationship ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
CreateFromSourceRelationship b -> m EncJSON
runCreateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
q
RQUpdateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
q -> CreateFromSourceRelationship ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
CreateFromSourceRelationship b -> m EncJSON
runUpdateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
q
RQDeleteRemoteRelationship DeleteFromSourceRelationship ('Postgres 'Vanilla)
q -> DeleteFromSourceRelationship ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
DeleteFromSourceRelationship b -> m EncJSON
runDeleteRemoteRelationship DeleteFromSourceRelationship ('Postgres 'Vanilla)
q
RQCreateEventTrigger CreateEventTriggerQuery ('Postgres 'Vanilla)
q -> CreateEventTriggerQuery ('Postgres 'Vanilla) -> 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 ('Postgres 'Vanilla)
q
RQDeleteEventTrigger DeleteEventTriggerQuery ('Postgres 'Vanilla)
q -> DeleteEventTriggerQuery ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendEventTrigger b, MonadError QErr m, CacheRWM m, MonadIO m,
MetadataM m) =>
DeleteEventTriggerQuery b -> m EncJSON
runDeleteEventTriggerQuery DeleteEventTriggerQuery ('Postgres 'Vanilla)
q
RQRedeliverEvent RedeliverEventQuery ('Postgres 'Vanilla)
q -> RedeliverEventQuery ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendEventTrigger b, MonadIO m, CacheRM m, QErrM m,
MetadataM m) =>
RedeliverEventQuery b -> m EncJSON
runRedeliverEvent RedeliverEventQuery ('Postgres 'Vanilla)
q
RQInvokeEventTrigger InvokeEventTriggerQuery ('Postgres 'Vanilla)
q -> InvokeEventTriggerQuery ('Postgres 'Vanilla) -> 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 InvokeEventTriggerQuery ('Postgres 'Vanilla)
q
RQCreateCronTrigger CreateCronTrigger
q -> CreateCronTrigger -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MonadIO m, MetadataM m,
MonadMetadataStorageQueryAPI m) =>
CreateCronTrigger -> m EncJSON
runCreateCronTrigger CreateCronTrigger
q
RQDeleteCronTrigger ScheduledTriggerName
q -> ScheduledTriggerName -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
ScheduledTriggerName -> m EncJSON
runDeleteCronTrigger ScheduledTriggerName
q
RQCreateScheduledEvent CreateScheduledEvent
q -> CreateScheduledEvent -> m EncJSON
forall (m :: * -> *).
MonadMetadataStorageQueryAPI m =>
CreateScheduledEvent -> m EncJSON
runCreateScheduledEvent CreateScheduledEvent
q
RQCreateQueryCollection CreateCollection
q -> CreateCollection -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
CreateCollection -> m EncJSON
runCreateCollection CreateCollection
q
RQRenameQueryCollection RenameCollection
q -> RenameCollection -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
RenameCollection -> m EncJSON
runRenameCollection RenameCollection
q
RQDropQueryCollection DropCollection
q -> DropCollection -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
DropCollection -> m EncJSON
runDropCollection DropCollection
q
RQAddQueryToCollection AddQueryToCollection
q -> AddQueryToCollection -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m) =>
AddQueryToCollection -> m EncJSON
runAddQueryToCollection AddQueryToCollection
q
RQDropQueryFromCollection DropQueryFromCollection
q -> DropQueryFromCollection -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MonadError QErr m, MetadataM m) =>
DropQueryFromCollection -> m EncJSON
runDropQueryFromCollection DropQueryFromCollection
q
RQAddCollectionToAllowlist AllowlistEntry
q -> AllowlistEntry -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
AllowlistEntry -> m EncJSON
runAddCollectionToAllowlist AllowlistEntry
q
RQDropCollectionFromAllowlist DropCollectionFromAllowlist
q -> DropCollectionFromAllowlist -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, MetadataM m, CacheRWM m) =>
DropCollectionFromAllowlist -> m EncJSON
runDropCollectionFromAllowlist DropCollectionFromAllowlist
q
RQReplaceMetadata 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
RQClearMetadata 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
RQExportMetadata ExportMetadata
q -> ExportMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, MetadataM m) =>
ExportMetadata -> m EncJSON
runExportMetadata ExportMetadata
q
RQReloadMetadata ReloadMetadata
q -> ReloadMetadata -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
ReloadMetadata -> m EncJSON
runReloadMetadata ReloadMetadata
q
RQCreateAction CreateAction
q -> CreateAction -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
CreateAction -> m EncJSON
runCreateAction CreateAction
q
RQDropAction DropAction
q -> DropAction -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
DropAction -> m EncJSON
runDropAction DropAction
q
RQUpdateAction UpdateAction
q -> UpdateAction -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
UpdateAction -> m EncJSON
runUpdateAction UpdateAction
q
RQCreateActionPermission CreateActionPermission
q -> CreateActionPermission -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
CreateActionPermission -> m EncJSON
runCreateActionPermission CreateActionPermission
q
RQDropActionPermission DropActionPermission
q -> DropActionPermission -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
DropActionPermission -> m EncJSON
runDropActionPermission DropActionPermission
q
RQCreateRestEndpoint CreateEndpoint
q -> CreateEndpoint -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
CreateEndpoint -> m EncJSON
runCreateEndpoint CreateEndpoint
q
RQDropRestEndpoint DropEndpoint
q -> DropEndpoint -> m EncJSON
forall (m :: * -> *).
(CacheRWM m, MetadataM m, MonadMetadataStorageQueryAPI m) =>
DropEndpoint -> m EncJSON
runDropEndpoint DropEndpoint
q
RQDumpInternalState DumpInternalState
q -> DumpInternalState -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRM m) =>
DumpInternalState -> m EncJSON
runDumpInternalState DumpInternalState
q
RQRunSql RunSQL
q -> RunSQL -> m EncJSON
forall (pgKind :: PostgresKind) (m :: * -> *).
(BackendMetadata ('Postgres pgKind), ToMetadataFetchQuery pgKind,
FetchTableMetadata pgKind, FetchFunctionMetadata pgKind,
CacheRWM m, HasServerConfigCtx m, MetadataM m,
MonadBaseControl IO m, MonadError QErr m, MonadIO m, MonadTrace m,
UserInfoM m) =>
RunSQL -> m EncJSON
runRunSQL @'Vanilla RunSQL
q
RQSetCustomTypes CustomTypes
q -> CustomTypes -> m EncJSON
forall (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m) =>
CustomTypes -> m EncJSON
runSetCustomTypes CustomTypes
q
RQBulk [RQLQuery]
qs -> [EncJSON] -> EncJSON
encJFromList ([EncJSON] -> EncJSON) -> m [EncJSON] -> m EncJSON
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (RQLQuery -> m EncJSON) -> [RQLQuery] -> m [EncJSON]
forall (m :: * -> *) a b. QErrM m => (a -> m b) -> [a] -> m [b]
indexedMapM (Environment -> RQLQuery -> m EncJSON
forall (m :: * -> *) r.
(CacheRWM m, UserInfoM m, MonadBaseControl IO m, MonadIO m,
HasHttpManagerM m, HasServerConfigCtx m, MonadTrace m, MetadataM m,
MonadMetadataStorageQueryAPI m, MonadQueryTags m, MonadReader r m,
Has (Logger Hasura) r) =>
Environment -> RQLQuery -> m EncJSON
runQueryM Environment
env) [RQLQuery]
qs
runQueryV2M :: RQLQueryV2 -> m EncJSON
runQueryV2M = \case
RQV2TrackTable TrackTableV2 ('Postgres 'Vanilla)
q -> TrackTableV2 ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
TrackTableV2 b -> m EncJSON
runTrackTableV2Q TrackTableV2 ('Postgres 'Vanilla)
q
RQV2SetTableCustomFields SetTableCustomFields
q -> SetTableCustomFields -> m EncJSON
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
SetTableCustomFields -> m EncJSON
runSetTableCustomFieldsQV2 SetTableCustomFields
q
RQV2TrackFunction TrackFunctionV2 ('Postgres 'Vanilla)
q -> TrackFunctionV2 ('Postgres 'Vanilla) -> m EncJSON
forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, QErrM m, CacheRWM m, MetadataM m) =>
TrackFunctionV2 b -> m EncJSON
runTrackFunctionV2 TrackFunctionV2 ('Postgres 'Vanilla)
q
RQV2ReplaceMetadata 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
requiresAdmin :: RQLQuery -> Bool
requiresAdmin :: RQLQuery -> Bool
requiresAdmin = \case
RQV1 RQLQueryV1
q -> case RQLQueryV1
q of
RQAddExistingTableOrView TrackTable ('Postgres 'Vanilla)
_ -> Bool
True
RQTrackTable TrackTable ('Postgres 'Vanilla)
_ -> Bool
True
RQUntrackTable UntrackTable ('Postgres 'Vanilla)
_ -> Bool
True
RQSetTableIsEnum SetTableIsEnum
_ -> Bool
True
RQSetTableCustomization SetTableCustomization ('Postgres 'Vanilla)
_ -> Bool
True
RQTrackFunction TrackFunction ('Postgres 'Vanilla)
_ -> Bool
True
RQUntrackFunction UnTrackFunction ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateObjectRelationship CreateObjRel ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateArrayRelationship CreateArrRel ('Postgres 'Vanilla)
_ -> Bool
True
RQDropRelationship DropRel ('Postgres 'Vanilla)
_ -> Bool
True
RQSetRelationshipComment SetRelComment ('Postgres 'Vanilla)
_ -> Bool
True
RQRenameRelationship RenameRel ('Postgres 'Vanilla)
_ -> Bool
True
RQAddComputedField AddComputedField ('Postgres 'Vanilla)
_ -> Bool
True
RQDropComputedField DropComputedField ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
True
RQUpdateRemoteRelationship CreateFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
True
RQDeleteRemoteRelationship DeleteFromSourceRelationship ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateInsertPermission CreatePerm InsPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateSelectPermission CreatePerm SelPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateUpdatePermission CreatePerm UpdPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateDeletePermission CreatePerm DelPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropInsertPermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropSelectPermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropUpdatePermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQDropDeletePermission DropPerm ('Postgres 'Vanilla)
_ -> Bool
True
RQSetPermissionComment SetPermComment ('Postgres 'Vanilla)
_ -> Bool
True
RQGetInconsistentMetadata GetInconsistentMetadata
_ -> Bool
True
RQDropInconsistentMetadata DropInconsistentMetadata
_ -> Bool
True
RQInsert InsertQuery
_ -> Bool
False
RQSelect SelectQuery
_ -> Bool
False
RQUpdate UpdateQuery
_ -> Bool
False
RQDelete DeleteQuery
_ -> Bool
False
RQCount CountQuery
_ -> Bool
False
RQAddRemoteSchema AddRemoteSchemaQuery
_ -> Bool
True
RQUpdateRemoteSchema AddRemoteSchemaQuery
_ -> Bool
True
RQRemoveRemoteSchema RemoteSchemaNameQuery
_ -> Bool
True
RQReloadRemoteSchema RemoteSchemaNameQuery
_ -> Bool
True
RQIntrospectRemoteSchema RemoteSchemaNameQuery
_ -> Bool
True
RQCreateEventTrigger CreateEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQDeleteEventTrigger DeleteEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQRedeliverEvent RedeliverEventQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQInvokeEventTrigger InvokeEventTriggerQuery ('Postgres 'Vanilla)
_ -> Bool
True
RQCreateCronTrigger CreateCronTrigger
_ -> Bool
True
RQDeleteCronTrigger ScheduledTriggerName
_ -> Bool
True
RQCreateScheduledEvent CreateScheduledEvent
_ -> Bool
True
RQCreateQueryCollection CreateCollection
_ -> Bool
True
RQRenameQueryCollection RenameCollection
_ -> Bool
True
RQDropQueryCollection DropCollection
_ -> Bool
True
RQAddQueryToCollection AddQueryToCollection
_ -> Bool
True
RQDropQueryFromCollection DropQueryFromCollection
_ -> Bool
True
RQAddCollectionToAllowlist AllowlistEntry
_ -> Bool
True
RQDropCollectionFromAllowlist DropCollectionFromAllowlist
_ -> Bool
True
RQReplaceMetadata ReplaceMetadata
_ -> Bool
True
RQClearMetadata ClearMetadata
_ -> Bool
True
RQExportMetadata ExportMetadata
_ -> Bool
True
RQReloadMetadata ReloadMetadata
_ -> Bool
True
RQCreateRestEndpoint CreateEndpoint
_ -> Bool
True
RQDropRestEndpoint DropEndpoint
_ -> Bool
True
RQCreateAction CreateAction
_ -> Bool
True
RQDropAction DropAction
_ -> Bool
True
RQUpdateAction UpdateAction
_ -> Bool
True
RQCreateActionPermission CreateActionPermission
_ -> Bool
True
RQDropActionPermission DropActionPermission
_ -> Bool
True
RQDumpInternalState DumpInternalState
_ -> Bool
True
RQSetCustomTypes CustomTypes
_ -> Bool
True
RQRunSql RunSQL
_ -> Bool
True
RQBulk [RQLQuery]
qs -> (RQLQuery -> Bool) -> [RQLQuery] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any RQLQuery -> Bool
requiresAdmin [RQLQuery]
qs
RQV2 RQLQueryV2
q -> case RQLQueryV2
q of
RQV2TrackTable TrackTableV2 ('Postgres 'Vanilla)
_ -> Bool
True
RQV2SetTableCustomFields SetTableCustomFields
_ -> Bool
True
RQV2TrackFunction TrackFunctionV2 ('Postgres 'Vanilla)
_ -> Bool
True
RQV2ReplaceMetadata ReplaceMetadataV2
_ -> Bool
True