graphql-engine/server/src-lib/Hasura/Server/API/Query.hs

540 lines
20 KiB
Haskell
Raw Normal View History

-- | The RQL query ('/v1/query')
{-# LANGUAGE NamedFieldPuns #-}
module Hasura.Server.API.Query where
2018-06-27 16:11:32 +03:00
import Control.Lens
2018-06-27 16:11:32 +03:00
import Data.Aeson
import Data.Aeson.Casing
import Data.Aeson.TH
import Data.Time (UTCTime)
import qualified Data.Environment as Env
import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
import qualified Database.PG.Query as Q
import qualified Network.HTTP.Client as HTTP
2018-06-27 16:11:32 +03:00
import Hasura.EncJSON
2018-06-27 16:11:32 +03:00
import Hasura.Prelude
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
import Hasura.RQL.DDL.Action
import Hasura.RQL.DDL.ComputedField
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
import Hasura.RQL.DDL.CustomTypes
import Hasura.RQL.DDL.EventTrigger
2018-06-27 16:11:32 +03:00
import Hasura.RQL.DDL.Metadata
import Hasura.RQL.DDL.Permission
import Hasura.RQL.DDL.QueryCollection
2018-06-27 16:11:32 +03:00
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.Update
2018-06-27 16:11:32 +03:00
import Hasura.RQL.Types
import Hasura.RQL.Types.Run
import Hasura.Server.Init (InstanceId (..))
import Hasura.Server.Utils
import Hasura.Server.Version (HasVersion)
backend only insert permissions (rfc #4120) (#4224) * move user info related code to Hasura.User module * the RFC #4120 implementation; insert permissions with admin secret * revert back to old RoleName based schema maps An attempt made to avoid duplication of schema contexts in types if any role doesn't possess any admin secret specific schema * fix compile errors in haskell test * keep 'user_vars' for session variables in http-logs * no-op refacto * tests for admin only inserts * update docs for admin only inserts * updated CHANGELOG.md * default behaviour when admin secret is not set * fix x-hasura-role to X-Hasura-Role in pytests * introduce effective timeout in actions async tests * update docs for admin-secret not configured case * Update docs/graphql/manual/api-reference/schema-metadata-api/permission.rst Co-Authored-By: Marion Schleifer <marion@hasura.io> * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * a complete iteration backend insert permissions accessable via 'x-hasura-backend-privilege' session variable * console changes for backend-only permissions * provide tooltip id; update labels and tooltips; * requested changes * requested changes - remove className from Toggle component - use appropriate function name (capitalizeFirstChar -> capitalize) * use toggle props from definitelyTyped * fix accidental commit * Revert "introduce effective timeout in actions async tests" This reverts commit b7a59c19d643520cfde6af579889e1038038438a. * generate complete schema for both 'default' and 'backend' sessions * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * remove unnecessary import, export Toggle as is * update session variable in tooltip * 'x-hasura-use-backend-only-permissions' variable to switch * update help texts * update docs * update docs * update console help text * regenerate package-lock * serve no backend schema when backend_only: false and header set to true - Few type name refactor as suggested by @0x777 * update CHANGELOG.md * Update CHANGELOG.md * Update CHANGELOG.md * fix a merge bug where a certain entity didn't get removed Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Rishichandra Wawhal <rishi@hasura.io> Co-authored-by: rikinsk <rikin.kachhia@gmail.com> Co-authored-by: Tirumarai Selvan <tiru@hasura.io>
2020-04-24 12:10:53 +03:00
import Hasura.Session
2018-06-27 16:11:32 +03:00
import qualified Hasura.Tracing as Tracing
data RQLQueryV1
2018-06-27 16:11:32 +03:00
= RQAddExistingTableOrView !TrackTable
| RQTrackTable !TrackTable
| RQUntrackTable !UntrackTable
| RQSetTableIsEnum !SetTableIsEnum
2018-06-27 16:11:32 +03:00
| RQTrackFunction !TrackFunction
| RQUntrackFunction !UnTrackFunction
2018-06-27 16:11:32 +03:00
| RQCreateObjectRelationship !CreateObjRel
| RQCreateArrayRelationship !CreateArrRel
| RQDropRelationship !DropRel
| RQSetRelationshipComment !SetRelComment
| RQRenameRelationship !RenameRel
2018-06-27 16:11:32 +03:00
-- computed fields related
| RQAddComputedField !AddComputedField
| RQDropComputedField !DropComputedField
| RQCreateRemoteRelationship !RemoteRelationship
| RQUpdateRemoteRelationship !RemoteRelationship
| RQDeleteRemoteRelationship !DeleteRemoteRelationship
2018-06-27 16:11:32 +03:00
| RQCreateInsertPermission !CreateInsPerm
| RQCreateSelectPermission !CreateSelPerm
| RQCreateUpdatePermission !CreateUpdPerm
| RQCreateDeletePermission !CreateDelPerm
| RQDropInsertPermission !(DropPerm InsPerm)
| RQDropSelectPermission !(DropPerm SelPerm)
| RQDropUpdatePermission !(DropPerm UpdPerm)
| RQDropDeletePermission !(DropPerm DelPerm)
2018-06-27 16:11:32 +03:00
| RQSetPermissionComment !SetPermComment
| RQGetInconsistentMetadata !GetInconsistentMetadata
| RQDropInconsistentMetadata !DropInconsistentMetadata
2018-06-27 16:11:32 +03:00
| RQInsert !InsertQuery
| RQSelect !SelectQuery
| RQUpdate !UpdateQuery
| RQDelete !DeleteQuery
| RQCount !CountQuery
| RQBulk ![RQLQuery]
-- schema-stitching, custom resolver related
| RQAddRemoteSchema !AddRemoteSchemaQuery
| RQRemoveRemoteSchema !RemoteSchemaNameQuery
| RQReloadRemoteSchema !RemoteSchemaNameQuery
| RQIntrospectRemoteSchema !RemoteSchemaNameQuery
2018-09-05 14:26:46 +03:00
| RQCreateEventTrigger !CreateEventTriggerQuery
| RQDeleteEventTrigger !DeleteEventTriggerQuery
| RQRedeliverEvent !RedeliverEventQuery
| RQInvokeEventTrigger !InvokeEventTriggerQuery
2018-09-05 14:26:46 +03:00
-- scheduled triggers
| RQCreateCronTrigger !CreateCronTrigger
| RQDeleteCronTrigger !ScheduledTriggerName
| RQCreateScheduledEvent !CreateScheduledEvent
-- query collections, allow list related
| RQCreateQueryCollection !CreateCollection
| RQDropQueryCollection !DropCollection
| RQAddQueryToCollection !AddQueryToCollection
| RQDropQueryFromCollection !DropQueryFromCollection
| RQAddCollectionToAllowlist !CollectionReq
| RQDropCollectionFromAllowlist !CollectionReq
2018-06-27 16:11:32 +03:00
| RQRunSql !RunSQL
| RQReplaceMetadata !ReplaceMetadata
| RQExportMetadata !ExportMetadata
| RQClearMetadata !ClearMetadata
| RQReloadMetadata !ReloadMetadata
2018-06-27 16:11:32 +03:00
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
| RQCreateAction !CreateAction
| RQDropAction !DropAction
| RQUpdateAction !UpdateAction
| RQCreateActionPermission !CreateActionPermission
| RQDropActionPermission !DropActionPermission
2018-06-27 16:11:32 +03:00
| RQDumpInternalState !DumpInternalState
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
| RQSetCustomTypes !CustomTypes
deriving (Show, Eq)
2018-06-27 16:11:32 +03:00
data RQLQueryV2
= RQV2TrackTable !TrackTableV2
| RQV2SetTableCustomFields !SetTableCustomFields
| RQV2TrackFunction !TrackFunctionV2
deriving (Show, Eq)
data RQLQuery
= RQV1 !RQLQueryV1
| RQV2 !RQLQueryV2
deriving (Show, Eq)
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
instance ToJSON RQLQuery where
toJSON = \case
RQV1 q -> embedVersion VIVersion1 $ toJSON q
RQV2 q -> embedVersion VIVersion2 $ toJSON q
where
embedVersion version (Object o) =
Object $ HM.insert "version" (toJSON version) o
-- never happens since JSON value of RQL queries are always objects
embedVersion _ _ = error "Unexpected: toJSON of RQL queries are not objects"
2018-06-27 16:11:32 +03:00
$(deriveJSON
defaultOptions { constructorTagModifier = snakeCase . drop 2
, sumEncoding = TaggedObject "type" "args"
}
''RQLQueryV1)
$(deriveJSON
defaultOptions { constructorTagModifier = snakeCase . drop 4
, sumEncoding = TaggedObject "type" "args"
, tagSingleConstructors = True
}
''RQLQueryV2
)
2018-06-27 16:11:32 +03:00
fetchLastUpdate :: Q.TxE QErr (Maybe (InstanceId, UTCTime, CacheInvalidations))
fetchLastUpdate = over (_Just._3) Q.getAltJ <$> Q.withQE defaultTxErrorHandler [Q.sql|
SELECT instance_id::text, occurred_at, invalidations
FROM hdb_catalog.hdb_schema_update_event
ORDER BY occurred_at DESC LIMIT 1
|] () True
recordSchemaUpdate :: InstanceId -> CacheInvalidations -> Q.TxE QErr ()
recordSchemaUpdate instanceId invalidations =
liftTx $ Q.unitQE defaultTxErrorHandler [Q.sql|
INSERT INTO hdb_catalog.hdb_schema_update_event
(instance_id, occurred_at, invalidations) VALUES ($1::uuid, DEFAULT, $2::json)
ON CONFLICT ((occurred_at IS NOT NULL))
DO UPDATE SET instance_id = $1::uuid, occurred_at = DEFAULT, invalidations = $2::json
|] (instanceId, Q.AltJ invalidations) True
2018-06-27 16:11:32 +03:00
runQuery
:: (HasVersion, MonadIO m, MonadError QErr m, Tracing.MonadTrace m)
=> Env.Environment -> PGExecCtx -> InstanceId
-> UserInfo -> RebuildableSchemaCache Run -> HTTP.Manager
-> SQLGenCtx -> SystemDefined -> RQLQuery -> m (EncJSON, RebuildableSchemaCache Run)
runQuery env pgExecCtx instanceId userInfo sc hMgr sqlGenCtx systemDefined query = do
accessMode <- getQueryAccessMode query
traceCtx <- Tracing.currentContext
resE <- runQueryM env query & Tracing.interpTraceT \x -> do
a <- x & runHasSystemDefinedT systemDefined
& runCacheRWT sc
& peelRun runCtx pgExecCtx accessMode (Just traceCtx)
& runExceptT
& liftIO
pure (either
((, mempty) . Left)
(\((js, meta), rsc, ci) -> (Right (js, rsc, ci), meta)) a)
either throwError withReload resE
where
runCtx = RunCtx userInfo hMgr sqlGenCtx
withReload (result, updatedCache, invalidations) = do
when (queryModifiesSchemaCache query) $ do
e <- liftIO $ runExceptT $ runLazyTx pgExecCtx Q.ReadWrite $ liftTx $
recordSchemaUpdate instanceId invalidations
liftEither e
return (result, updatedCache)
2018-06-27 16:11:32 +03:00
-- | A predicate that determines whether the given query might modify/rebuild the schema cache. If
-- so, it needs to acquire the global lock on the schema cache so that other queries do not modify
-- it concurrently.
--
-- Ideally, we would enforce this using the type system — queries for which this function returns
-- 'False' should not be allowed to modify the schema cache. But for now we just ensure consistency
-- by hand.
queryModifiesSchemaCache :: RQLQuery -> Bool
queryModifiesSchemaCache (RQV1 qi) = case qi of
RQAddExistingTableOrView _ -> True
RQTrackTable _ -> True
RQUntrackTable _ -> True
RQTrackFunction _ -> True
RQUntrackFunction _ -> True
RQSetTableIsEnum _ -> True
RQCreateObjectRelationship _ -> True
RQCreateArrayRelationship _ -> True
RQDropRelationship _ -> True
RQSetRelationshipComment _ -> False
RQRenameRelationship _ -> True
RQAddComputedField _ -> True
RQDropComputedField _ -> True
RQCreateRemoteRelationship _ -> True
RQUpdateRemoteRelationship _ -> True
RQDeleteRemoteRelationship _ -> True
RQCreateInsertPermission _ -> True
RQCreateSelectPermission _ -> True
RQCreateUpdatePermission _ -> True
RQCreateDeletePermission _ -> True
RQDropInsertPermission _ -> True
RQDropSelectPermission _ -> True
RQDropUpdatePermission _ -> True
RQDropDeletePermission _ -> True
RQSetPermissionComment _ -> False
RQGetInconsistentMetadata _ -> False
RQDropInconsistentMetadata _ -> True
RQInsert _ -> False
RQSelect _ -> False
RQUpdate _ -> False
RQDelete _ -> False
RQCount _ -> False
RQAddRemoteSchema _ -> True
RQRemoveRemoteSchema _ -> True
RQReloadRemoteSchema _ -> True
RQIntrospectRemoteSchema _ -> False
RQCreateEventTrigger _ -> True
RQDeleteEventTrigger _ -> True
RQRedeliverEvent _ -> False
RQInvokeEventTrigger _ -> False
RQCreateCronTrigger _ -> True
RQDeleteCronTrigger _ -> True
RQCreateScheduledEvent _ -> False
RQCreateQueryCollection _ -> True
RQDropQueryCollection _ -> True
RQAddQueryToCollection _ -> True
RQDropQueryFromCollection _ -> True
RQAddCollectionToAllowlist _ -> True
RQDropCollectionFromAllowlist _ -> True
RQRunSql q -> isSchemaCacheBuildRequiredRunSQL q
RQReplaceMetadata _ -> True
RQExportMetadata _ -> False
RQClearMetadata _ -> True
RQReloadMetadata _ -> True
RQCreateAction _ -> True
RQDropAction _ -> True
RQUpdateAction _ -> True
RQCreateActionPermission _ -> True
RQDropActionPermission _ -> True
RQDumpInternalState _ -> False
RQSetCustomTypes _ -> True
RQBulk qs -> any queryModifiesSchemaCache qs
queryModifiesSchemaCache (RQV2 qi) = case qi of
RQV2TrackTable _ -> True
RQV2SetTableCustomFields _ -> True
RQV2TrackFunction _ -> True
2018-06-27 16:11:32 +03:00
getQueryAccessMode :: (MonadError QErr m) => RQLQuery -> m Q.TxAccess
getQueryAccessMode q = (fromMaybe Q.ReadOnly) <$> getQueryAccessMode' q
where
getQueryAccessMode' ::
(MonadError QErr m) => RQLQuery -> m (Maybe Q.TxAccess)
getQueryAccessMode' (RQV1 q') =
case q' of
RQSelect _ -> pure Nothing
RQCount _ -> pure Nothing
RQRunSql RunSQL {rTxAccessMode} -> pure $ Just rTxAccessMode
RQBulk qs -> foldM reconcileAccessModeWith Nothing (zip [0 :: Integer ..] qs)
_ -> pure $ Just Q.ReadWrite
where
reconcileAccessModeWith expectedMode (i, query) = do
queryMode <- getQueryAccessMode' query
onLeft (reconcileAccessModes expectedMode queryMode) $ \errMode ->
throw400 BadRequest $
"incompatible access mode requirements in bulk query, " <>
"expected access mode: " <>
(T.pack $ maybe "ANY" show expectedMode) <>
" but " <>
"$.args[" <>
(T.pack $ show i) <>
"] forces " <>
(T.pack $ show errMode)
getQueryAccessMode' (RQV2 _) = pure $ Just Q.ReadWrite
-- | onRight, return reconciled access mode. onLeft, return conflicting access mode
reconcileAccessModes :: Maybe Q.TxAccess -> Maybe Q.TxAccess -> Either Q.TxAccess (Maybe Q.TxAccess)
reconcileAccessModes Nothing mode = pure mode
reconcileAccessModes mode Nothing = pure mode
reconcileAccessModes (Just mode1) (Just mode2)
| mode1 == mode2 = pure $ Just mode1
| otherwise = Left mode2
runQueryM
:: ( HasVersion, QErrM m, CacheRWM m, UserInfoM m, MonadTx m
, MonadIO m, HasHttpManager m, HasSQLGenCtx m
, HasSystemDefined m
, Tracing.MonadTrace m
)
=> Env.Environment
-> RQLQuery
-> m EncJSON
runQueryM env rq = withPathK "args" $ case rq of
RQV1 q -> runQueryV1M q
RQV2 q -> runQueryV2M q
where
runQueryV1M = \case
RQAddExistingTableOrView q -> runTrackTableQ q
RQTrackTable q -> runTrackTableQ q
RQUntrackTable q -> runUntrackTableQ q
RQSetTableIsEnum q -> runSetExistingTableIsEnumQ q
RQTrackFunction q -> runTrackFunc q
RQUntrackFunction q -> runUntrackFunc q
RQCreateObjectRelationship q -> runCreateRelationship ObjRel q
RQCreateArrayRelationship q -> runCreateRelationship ArrRel q
RQDropRelationship q -> runDropRel q
RQSetRelationshipComment q -> runSetRelComment q
RQRenameRelationship q -> runRenameRel q
RQAddComputedField q -> runAddComputedField q
RQDropComputedField q -> runDropComputedField q
RQCreateInsertPermission q -> runCreatePerm q
RQCreateSelectPermission q -> runCreatePerm q
RQCreateUpdatePermission q -> runCreatePerm q
RQCreateDeletePermission q -> runCreatePerm q
RQDropInsertPermission q -> runDropPerm q
RQDropSelectPermission q -> runDropPerm q
RQDropUpdatePermission q -> runDropPerm q
RQDropDeletePermission q -> runDropPerm q
RQSetPermissionComment q -> runSetPermComment q
RQGetInconsistentMetadata q -> runGetInconsistentMetadata q
RQDropInconsistentMetadata q -> runDropInconsistentMetadata q
RQInsert q -> runInsert env q
RQSelect q -> runSelect q
RQUpdate q -> runUpdate env q
RQDelete q -> runDelete env q
RQCount q -> runCount q
RQAddRemoteSchema q -> runAddRemoteSchema env q
RQRemoveRemoteSchema q -> runRemoveRemoteSchema q
RQReloadRemoteSchema q -> runReloadRemoteSchema q
RQIntrospectRemoteSchema q -> runIntrospectRemoteSchema q
RQCreateRemoteRelationship q -> runCreateRemoteRelationship q
RQUpdateRemoteRelationship q -> runUpdateRemoteRelationship q
RQDeleteRemoteRelationship q -> runDeleteRemoteRelationship q
RQCreateEventTrigger q -> runCreateEventTriggerQuery q
RQDeleteEventTrigger q -> runDeleteEventTriggerQuery q
RQRedeliverEvent q -> runRedeliverEvent q
RQInvokeEventTrigger q -> runInvokeEventTrigger q
RQCreateCronTrigger q -> runCreateCronTrigger q
RQDeleteCronTrigger q -> runDeleteCronTrigger q
RQCreateScheduledEvent q -> runCreateScheduledEvent q
RQCreateQueryCollection q -> runCreateCollection q
RQDropQueryCollection q -> runDropCollection q
RQAddQueryToCollection q -> runAddQueryToCollection q
RQDropQueryFromCollection q -> runDropQueryFromCollection q
RQAddCollectionToAllowlist q -> runAddCollectionToAllowlist q
RQDropCollectionFromAllowlist q -> runDropCollectionFromAllowlist q
RQReplaceMetadata q -> runReplaceMetadata q
RQClearMetadata q -> runClearMetadata q
RQExportMetadata q -> runExportMetadata q
RQReloadMetadata q -> runReloadMetadata q
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
RQCreateAction q -> runCreateAction q
RQDropAction q -> runDropAction q
RQUpdateAction q -> runUpdateAction q
RQCreateActionPermission q -> runCreateActionPermission q
RQDropActionPermission q -> runDropActionPermission q
RQDumpInternalState q -> runDumpInternalState q
RQRunSql q -> runRunSQL q
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
RQSetCustomTypes q -> runSetCustomTypes q
RQBulk qs -> encJFromList <$> indexedMapM (runQueryM env) qs
runQueryV2M = \case
RQV2TrackTable q -> runTrackTableV2Q q
RQV2SetTableCustomFields q -> runSetTableCustomFieldsQV2 q
RQV2TrackFunction q -> runTrackFunctionV2 q
requiresAdmin :: RQLQuery -> Bool
requiresAdmin = \case
RQV1 q -> case q of
RQAddExistingTableOrView _ -> True
RQTrackTable _ -> True
RQUntrackTable _ -> True
RQSetTableIsEnum _ -> True
RQTrackFunction _ -> True
RQUntrackFunction _ -> True
RQCreateObjectRelationship _ -> True
RQCreateArrayRelationship _ -> True
RQDropRelationship _ -> True
RQSetRelationshipComment _ -> True
RQRenameRelationship _ -> True
RQAddComputedField _ -> True
RQDropComputedField _ -> True
RQCreateRemoteRelationship _ -> True
RQUpdateRemoteRelationship _ -> True
RQDeleteRemoteRelationship _ -> True
RQCreateInsertPermission _ -> True
RQCreateSelectPermission _ -> True
RQCreateUpdatePermission _ -> True
RQCreateDeletePermission _ -> True
RQDropInsertPermission _ -> True
RQDropSelectPermission _ -> True
RQDropUpdatePermission _ -> True
RQDropDeletePermission _ -> True
RQSetPermissionComment _ -> True
RQGetInconsistentMetadata _ -> True
RQDropInconsistentMetadata _ -> True
RQInsert _ -> False
RQSelect _ -> False
RQUpdate _ -> False
RQDelete _ -> False
RQCount _ -> False
RQAddRemoteSchema _ -> True
RQRemoveRemoteSchema _ -> True
RQReloadRemoteSchema _ -> True
RQIntrospectRemoteSchema _ -> True
RQCreateEventTrigger _ -> True
RQDeleteEventTrigger _ -> True
RQRedeliverEvent _ -> True
RQInvokeEventTrigger _ -> True
RQCreateCronTrigger _ -> True
RQDeleteCronTrigger _ -> True
RQCreateScheduledEvent _ -> True
RQCreateQueryCollection _ -> True
RQDropQueryCollection _ -> True
RQAddQueryToCollection _ -> True
RQDropQueryFromCollection _ -> True
RQAddCollectionToAllowlist _ -> True
RQDropCollectionFromAllowlist _ -> True
RQReplaceMetadata _ -> True
RQClearMetadata _ -> True
RQExportMetadata _ -> True
RQReloadMetadata _ -> True
RQCreateAction _ -> True
RQDropAction _ -> True
RQUpdateAction _ -> True
RQCreateActionPermission _ -> True
RQDropActionPermission _ -> True
RQDumpInternalState _ -> True
RQSetCustomTypes _ -> True
RQRunSql _ -> True
RQBulk qs -> any requiresAdmin qs
RQV2 q -> case q of
RQV2TrackTable _ -> True
RQV2SetTableCustomFields _ -> True
RQV2TrackFunction _ -> True