2021-09-24 01:56:37 +03:00
|
|
|
-- |
|
|
|
|
-- Description: Create/delete SQL functions to/from Hasura metadata.
|
2019-01-25 06:31:54 +03:00
|
|
|
module Hasura.RQL.DDL.Schema.Function where
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
import Control.Lens ((^.))
|
|
|
|
import Data.Aeson
|
|
|
|
import Data.HashMap.Strict qualified as Map
|
|
|
|
import Data.HashMap.Strict.InsOrd qualified as OMap
|
|
|
|
import Data.Text.Extended
|
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
|
|
|
import Hasura.SQL.Tag
|
|
|
|
import Hasura.Session
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype TrackFunction b = TrackFunction {tfName :: FunctionName b}
|
2021-03-15 16:02:58 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
deriving instance (Backend b) => FromJSON (TrackFunction b)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
deriving instance (Backend b) => ToJSON (TrackFunction b)
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2019-07-11 10:41:20 +03:00
|
|
|
-- | Track function, Phase 1:
|
|
|
|
-- Validate function tracking operation. Fails if function is already being
|
|
|
|
-- tracked, or if a table with the same name is being tracked.
|
2021-09-24 01:56:37 +03:00
|
|
|
trackFunctionP1 ::
|
|
|
|
forall b m.
|
|
|
|
(CacheRM m, QErrM m, Backend b) =>
|
|
|
|
SourceName ->
|
|
|
|
FunctionName b ->
|
|
|
|
m ()
|
2020-12-28 15:56:00 +03:00
|
|
|
trackFunctionP1 sourceName qf = do
|
2019-01-25 06:31:54 +03:00
|
|
|
rawSchemaCache <- askSchemaCache
|
2021-05-27 15:08:21 +03:00
|
|
|
unless (isJust $ AB.unpackAnyBackend @b =<< Map.lookup sourceName (scSources rawSchemaCache)) $
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
throw400 NotExists $ sourceName <<> " is not a known " <> reify (backendTag @b) <<> " source"
|
2021-02-23 20:37:27 +03:00
|
|
|
when (isJust $ unsafeFunctionInfo @b sourceName qf $ scSources rawSchemaCache) $
|
2019-01-25 06:31:54 +03:00
|
|
|
throw400 AlreadyTracked $ "function already tracked : " <>> qf
|
2021-04-22 00:44:37 +03:00
|
|
|
let qt = functionToTable @b qf
|
2021-02-23 20:37:27 +03:00
|
|
|
when (isJust $ unsafeTableInfo @b sourceName qt $ scSources rawSchemaCache) $
|
2019-07-11 10:41:20 +03:00
|
|
|
throw400 NotSupported $ "table with name " <> qf <<> " already exists"
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
trackFunctionP2 ::
|
|
|
|
forall b m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
|
|
SourceName ->
|
|
|
|
FunctionName b ->
|
|
|
|
FunctionConfig ->
|
|
|
|
m EncJSON
|
2020-12-28 15:56:00 +03:00
|
|
|
trackFunctionP2 sourceName qf config = do
|
2021-03-15 16:02:58 +03:00
|
|
|
buildSchemaCacheFor
|
2021-04-22 00:44:37 +03:00
|
|
|
(MOSourceObjId sourceName $ AB.mkAnyBackend $ SMOFunction @b qf)
|
2021-09-24 01:56:37 +03:00
|
|
|
$ MetadataModifier $
|
|
|
|
metaSources . ix sourceName . toSourceMetadata . (smFunctions @b)
|
|
|
|
%~ OMap.insert qf (FunctionMetadata qf config mempty)
|
2020-12-08 17:22:31 +03:00
|
|
|
pure successMsg
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
handleMultipleFunctions ::
|
|
|
|
forall b m a.
|
|
|
|
(QErrM m, Backend b) =>
|
|
|
|
FunctionName b ->
|
|
|
|
[a] ->
|
|
|
|
m a
|
2019-10-18 11:29:47 +03:00
|
|
|
handleMultipleFunctions qf = \case
|
|
|
|
[fi] -> return fi
|
2021-09-24 01:56:37 +03:00
|
|
|
[] -> throw400 NotExists $ "no such function exists: " <>> qf
|
|
|
|
_ -> throw400 NotSupported $ "function " <> qf <<> " is overloaded. Overloaded functions are not supported"
|
2019-10-18 11:29:47 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runTrackFunc ::
|
|
|
|
forall b m.
|
|
|
|
(MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b) =>
|
|
|
|
TrackFunction b ->
|
|
|
|
m EncJSON
|
2021-04-22 00:44:37 +03:00
|
|
|
runTrackFunc (TrackFunction qf) = do
|
2020-12-28 15:56:00 +03:00
|
|
|
-- v1 track_function lacks a means to take extra arguments
|
2021-04-22 00:44:37 +03:00
|
|
|
trackFunctionP1 @b defaultSource qf
|
|
|
|
trackFunctionP2 @b defaultSource qf emptyFunctionConfig
|
2019-11-20 09:47:06 +03:00
|
|
|
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
-- | JSON API payload for v2 of 'track_function':
|
|
|
|
--
|
|
|
|
-- https://hasura.io/docs/latest/graphql/core/api-reference/schema-metadata-api/custom-functions.html#track-function-v2
|
|
|
|
data TrackFunctionV2 (b :: BackendType) = TrackFunctionV2
|
2021-09-24 01:56:37 +03:00
|
|
|
{ _tfv2Source :: !SourceName,
|
|
|
|
_tfv2Function :: !(FunctionName b),
|
|
|
|
_tfv2Configuration :: !FunctionConfig
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
instance Backend b => FromJSON (TrackFunctionV2 b) where
|
2021-09-20 22:49:33 +03:00
|
|
|
parseJSON = withObject "TrackFunctionV2" $ \o ->
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
TrackFunctionV2
|
2021-09-24 01:56:37 +03:00
|
|
|
<$> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "function"
|
|
|
|
<*> o .:? "configuration" .!= emptyFunctionConfig
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runTrackFunctionV2 ::
|
|
|
|
forall b m.
|
|
|
|
(BackendMetadata b, QErrM m, CacheRWM m, MetadataM m) =>
|
|
|
|
TrackFunctionV2 b ->
|
|
|
|
m EncJSON
|
2020-12-28 15:56:00 +03:00
|
|
|
runTrackFunctionV2 (TrackFunctionV2 source qf config) = do
|
2021-04-22 00:44:37 +03:00
|
|
|
trackFunctionP1 @b source qf
|
|
|
|
trackFunctionP2 @b source qf config
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2020-11-18 21:04:57 +03:00
|
|
|
-- | JSON API payload for 'untrack_function':
|
|
|
|
--
|
2021-03-01 21:50:24 +03:00
|
|
|
-- https://hasura.io/docs/latest/graphql/core/api-reference/schema-metadata-api/custom-functions.html#untrack-function
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
data UnTrackFunction b = UnTrackFunction
|
2021-09-24 01:56:37 +03:00
|
|
|
{ _utfFunction :: !(FunctionName b),
|
|
|
|
_utfSource :: !SourceName
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
2020-12-28 15:56:00 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
instance (Backend b) => FromJSON (UnTrackFunction b) where
|
2021-05-24 18:56:32 +03:00
|
|
|
-- Following was the previous implementation, which while seems to be correct,
|
|
|
|
-- has an unexpected behaviour. In the case when @source@ key is present but
|
|
|
|
-- @function@ key is absent, it would silently coerce it into a @default@
|
|
|
|
-- source. The culprint being the _alternative_ operator, which silently fails
|
|
|
|
-- the first parse. This note exists so that we don't try to simplify using
|
|
|
|
-- the _alternative_ pattern here.
|
|
|
|
-- Previous implementation :-
|
|
|
|
-- Consider the following JSON -
|
|
|
|
-- {
|
|
|
|
-- "source": "custom_source",
|
|
|
|
-- "schema": "public",
|
|
|
|
-- "name": "my_function"
|
|
|
|
-- }
|
|
|
|
-- it silently fails parsing the source here because @function@ key is not
|
|
|
|
-- present, and proceeds to parse using @withoutSource@ as default source. Now
|
|
|
|
-- this is surprising for the user, because they mention @source@ key
|
|
|
|
-- explicitly. A better behaviour is to explicitly look for @function@ key if
|
|
|
|
-- a @source@ key is present.
|
|
|
|
-- >>
|
|
|
|
-- parseJSON v = withSource <|> withoutSource
|
|
|
|
-- where
|
|
|
|
-- withoutSource = UnTrackFunction <$> parseJSON v <*> pure defaultSource
|
|
|
|
-- withSource = flip (withObject "UnTrackFunction") v \o -> do
|
|
|
|
-- UnTrackFunction <$> o .: "function"
|
|
|
|
-- <*> o .:? "source" .!= defaultSource
|
|
|
|
parseJSON v = flip (withObject "UnTrackFunction") v $ \o -> do
|
|
|
|
source <- o .:? "source"
|
|
|
|
case source of
|
|
|
|
Just src -> flip UnTrackFunction src <$> o .: "function"
|
2021-09-24 01:56:37 +03:00
|
|
|
Nothing -> UnTrackFunction <$> parseJSON v <*> pure defaultSource
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
askFunctionInfo ::
|
|
|
|
forall b m.
|
|
|
|
(CacheRM m, MonadError QErr m, Backend b) =>
|
|
|
|
SourceName ->
|
|
|
|
FunctionName b ->
|
|
|
|
m (FunctionInfo b)
|
2021-02-14 09:07:52 +03:00
|
|
|
askFunctionInfo source functionName = do
|
2021-02-23 20:37:27 +03:00
|
|
|
sourceCache <- scSources <$> askSchemaCache
|
2021-02-14 09:07:52 +03:00
|
|
|
unsafeFunctionInfo @b source functionName sourceCache
|
2021-01-29 08:48:17 +03:00
|
|
|
`onNothing` throw400 NotExists ("function " <> functionName <<> " not found in the cache")
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runUntrackFunc ::
|
|
|
|
forall b m.
|
|
|
|
(CacheRWM m, MonadError QErr m, MetadataM m, BackendMetadata b) =>
|
|
|
|
UnTrackFunction b ->
|
|
|
|
m EncJSON
|
2021-01-20 03:31:53 +03:00
|
|
|
runUntrackFunc (UnTrackFunction functionName sourceName) = do
|
2021-04-22 00:44:37 +03:00
|
|
|
void $ askFunctionInfo @b sourceName functionName
|
2021-09-24 01:56:37 +03:00
|
|
|
withNewInconsistentObjsCheck $
|
|
|
|
buildSchemaCache $
|
|
|
|
dropFunctionInMetadata @b sourceName functionName
|
2020-12-08 17:22:31 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
dropFunctionInMetadata ::
|
|
|
|
forall b.
|
|
|
|
(BackendMetadata b) =>
|
|
|
|
SourceName ->
|
|
|
|
FunctionName b ->
|
|
|
|
MetadataModifier
|
|
|
|
dropFunctionInMetadata source function =
|
|
|
|
MetadataModifier $
|
|
|
|
metaSources . ix source . toSourceMetadata . (smFunctions @b) %~ OMap.delete function
|
2021-01-29 08:48:17 +03:00
|
|
|
|
|
|
|
{- Note [Function Permissions]
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
Before we started supporting tracking volatile functions, permissions
|
|
|
|
for a function was inferred from the target table of the function.
|
|
|
|
The rationale behind this is that a stable/immutable function does not
|
|
|
|
modify the database and the data returned by the function is filtered using
|
|
|
|
the permissions that are specified precisely for that data.
|
|
|
|
Now consider mutable/volatile functions, we can't automatically infer whether or
|
|
|
|
not these functions should be exposed for the sole reason that they can modify
|
|
|
|
the database. This necessitates a permission system for functions.
|
|
|
|
So, we introduce a new API `pg_create_function_permission` which will
|
|
|
|
explicitly grant permission to a function to a role. For creating a
|
|
|
|
function permission, the role must have select permissions configured
|
|
|
|
for the target table.
|
|
|
|
Since, this is a breaking change, we enable it only when the graphql-engine
|
|
|
|
is started with
|
|
|
|
`--infer-function-permissions`/HASURA_GRAPHQL_INFER_FUNCTION_PERMISSIONS set
|
|
|
|
to false (by default, it's set to true).
|
|
|
|
-}
|
|
|
|
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
data FunctionPermissionArgument b = FunctionPermissionArgument
|
2021-09-24 01:56:37 +03:00
|
|
|
{ _afpFunction :: !(FunctionName b),
|
|
|
|
_afpSource :: !SourceName,
|
|
|
|
_afpRole :: !RoleName
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
}
|
2021-01-29 08:48:17 +03:00
|
|
|
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
instance (Backend b) => FromJSON (FunctionPermissionArgument b) where
|
2021-01-29 08:48:17 +03:00
|
|
|
parseJSON v =
|
2021-09-20 22:49:33 +03:00
|
|
|
flip (withObject "FunctionPermissionArgument") v $ \o ->
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
FunctionPermissionArgument
|
2021-09-24 01:56:37 +03:00
|
|
|
<$> o .: "function"
|
|
|
|
<*> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "role"
|
2021-01-29 08:48:17 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runCreateFunctionPermission ::
|
|
|
|
forall b m.
|
|
|
|
( CacheRWM m,
|
|
|
|
MonadError QErr m,
|
|
|
|
MetadataM m,
|
|
|
|
BackendMetadata b
|
|
|
|
) =>
|
|
|
|
FunctionPermissionArgument b ->
|
|
|
|
m EncJSON
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
runCreateFunctionPermission (FunctionPermissionArgument functionName source role) = do
|
2021-08-09 13:20:04 +03:00
|
|
|
metadata <- getMetadata
|
2021-02-23 20:37:27 +03:00
|
|
|
sourceCache <- scSources <$> askSchemaCache
|
2021-04-22 00:44:37 +03:00
|
|
|
functionInfo <- askFunctionInfo @b source functionName
|
2021-08-09 13:20:04 +03:00
|
|
|
when (doesFunctionPermissionExist @b metadata source functionName role) $
|
2021-01-29 08:48:17 +03:00
|
|
|
throw400 AlreadyExists $
|
2021-09-24 01:56:37 +03:00
|
|
|
"permission of role "
|
|
|
|
<> role <<> " already exists for function "
|
|
|
|
<> functionName <<> " in source: " <>> source
|
2021-01-29 08:48:17 +03:00
|
|
|
functionTableInfo <-
|
2021-02-14 09:07:52 +03:00
|
|
|
unsafeTableInfo @b source (_fiReturnType functionInfo) sourceCache
|
2021-09-24 01:56:37 +03:00
|
|
|
`onNothing` throw400 NotExists ("function's return table " <> _fiReturnType functionInfo <<> " not found in the cache")
|
2021-01-29 08:48:17 +03:00
|
|
|
unless (role `Map.member` _tiRolePermInfoMap functionTableInfo) $
|
|
|
|
throw400 NotSupported $
|
2021-09-24 01:56:37 +03:00
|
|
|
"function permission can only be added when the function's return table "
|
|
|
|
<> _fiReturnType functionInfo <<> " has select permission configured for role: " <>> role
|
2021-03-15 16:02:58 +03:00
|
|
|
buildSchemaCacheFor
|
2021-09-24 01:56:37 +03:00
|
|
|
( MOSourceObjId source $
|
|
|
|
AB.mkAnyBackend (SMOFunctionPermission @b functionName role)
|
|
|
|
)
|
|
|
|
$ MetadataModifier $
|
|
|
|
metaSources
|
|
|
|
. ix
|
|
|
|
source
|
|
|
|
. toSourceMetadata
|
|
|
|
. (smFunctions @b)
|
|
|
|
. ix functionName
|
|
|
|
. fmPermissions
|
|
|
|
%~ (:) (FunctionPermissionInfo role)
|
2021-01-29 08:48:17 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
dropFunctionPermissionInMetadata ::
|
|
|
|
forall b.
|
|
|
|
(BackendMetadata b) =>
|
|
|
|
SourceName ->
|
|
|
|
FunctionName b ->
|
|
|
|
RoleName ->
|
|
|
|
MetadataModifier
|
|
|
|
dropFunctionPermissionInMetadata source function role =
|
|
|
|
MetadataModifier $
|
|
|
|
metaSources . ix source . toSourceMetadata . (smFunctions @b) . ix function . fmPermissions %~ filter ((/=) role . _fpmRole)
|
2021-01-29 08:48:17 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
doesFunctionPermissionExist :: forall b. (BackendMetadata b) => Metadata -> SourceName -> FunctionName b -> RoleName -> Bool
|
2021-08-09 13:20:04 +03:00
|
|
|
doesFunctionPermissionExist metadata sourceName functionName roleName =
|
2021-09-24 01:56:37 +03:00
|
|
|
any ((== roleName) . _fpmRole) $ metadata ^. (metaSources . ix sourceName . toSourceMetadata . (smFunctions @b) . ix functionName . fmPermissions)
|
2021-08-09 13:20:04 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runDropFunctionPermission ::
|
|
|
|
forall m b.
|
|
|
|
( CacheRWM m,
|
|
|
|
MonadError QErr m,
|
|
|
|
MetadataM m,
|
|
|
|
BackendMetadata b
|
|
|
|
) =>
|
|
|
|
FunctionPermissionArgument b ->
|
|
|
|
m EncJSON
|
Clean metadata arguments
## Description
Thanks to #1664, the Metadata API types no longer require a `ToJSON` instance. This PR follows up with a cleanup of the types of the arguments to the metadata API:
- whenever possible, it moves those argument types to where they're used (RQL.DDL.*)
- it removes all unrequired instances (mostly `ToJSON`)
This PR does not attempt to do it for _all_ such argument types. For some of the metadata operations, the type used to describe the argument to the API and used to represent the value in the metadata are one and the same (like for `CreateEndpoint`). Sometimes, the two types are intertwined in complex ways (`RemoteRelationship` and `RemoteRelationshipDef`). In the spirit of only doing uncontroversial cleaning work, this PR only moves types that are not used outside of RQL.DDL.
Furthermore, this is a small step towards separating the different types all jumbled together in RQL.Types.
## Notes
This PR also improves several `FromJSON` instances to make use of `withObject`, and to use a human readable string instead of a type name in error messages whenever possible. For instance:
- before: `expected Object for Object, but encountered X`
after: `expected Object for add computed field, but encountered X`
- before: `Expecting an object for update query`
after: `expected Object for update query, but encountered X`
This PR also renames `CreateFunctionPermission` to `FunctionPermissionArgument`, to remove the quite surprising `type DropFunctionPermission = CreateFunctionPermission`.
This PR also deletes some dead code, mostly in RQL.DML.
This PR also moves a PG-specific source resolving function from DDL.Schema.Source to the only place where it is used: App.hs.
https://github.com/hasura/graphql-engine-mono/pull/1844
GitOrigin-RevId: a594521194bb7fe6a111b02a9e099896f9fed59c
2021-07-27 13:41:42 +03:00
|
|
|
runDropFunctionPermission (FunctionPermissionArgument functionName source role) = do
|
2021-08-09 13:20:04 +03:00
|
|
|
metadata <- getMetadata
|
|
|
|
unless (doesFunctionPermissionExist @b metadata source functionName role) $
|
2021-01-29 08:48:17 +03:00
|
|
|
throw400 NotExists $
|
2021-09-24 01:56:37 +03:00
|
|
|
"permission of role "
|
|
|
|
<> role <<> " does not exist for function "
|
|
|
|
<> functionName <<> " in source: " <>> source
|
2021-03-15 16:02:58 +03:00
|
|
|
buildSchemaCacheFor
|
2021-09-24 01:56:37 +03:00
|
|
|
( MOSourceObjId source $
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
SMOFunctionPermission @b functionName role
|
|
|
|
)
|
2021-04-22 00:44:37 +03:00
|
|
|
$ dropFunctionPermissionInMetadata @b source functionName role
|
2021-01-29 08:48:17 +03:00
|
|
|
pure successMsg
|