2019-07-11 10:41:20 +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
|
|
|
|
|
|
|
|
import Hasura.Prelude
|
2020-08-27 19:36:39 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
import qualified Data.HashMap.Strict as Map
|
|
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
2019-01-25 06:31:54 +03:00
|
|
|
|
|
|
|
import Data.Aeson
|
2020-10-27 16:53:49 +03:00
|
|
|
import Data.Text.Extended
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2021-03-15 16:02:58 +03:00
|
|
|
import qualified Hasura.SQL.AnyBackend as AB
|
|
|
|
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2020-08-27 19:36:39 +03:00
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.RQL.Types
|
2021-01-29 08:48:17 +03:00
|
|
|
import Hasura.Session
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2021-05-11 18:18:31 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
newtype TrackFunction b
|
2019-01-25 06:31:54 +03:00
|
|
|
= TrackFunction
|
2021-03-15 16:02:58 +03:00
|
|
|
{ tfName :: FunctionName b }
|
2021-02-14 09:07:52 +03:00
|
|
|
deriving instance (Backend b) => Show (TrackFunction b)
|
|
|
|
deriving instance (Backend b) => Eq (TrackFunction b)
|
|
|
|
deriving instance (Backend b) => FromJSON (TrackFunction b)
|
|
|
|
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.
|
2019-01-25 06:31:54 +03:00
|
|
|
trackFunctionP1
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall b m
|
2021-02-14 09:07:52 +03:00
|
|
|
. (CacheRM m, QErrM m, Backend b)
|
2021-04-22 00:44:37 +03:00
|
|
|
=> 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-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
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
trackFunctionP2
|
2021-03-15 16:02:58 +03:00
|
|
|
:: forall b m
|
|
|
|
. (MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b)
|
2021-02-14 09:07:52 +03:00
|
|
|
=> 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)
|
2020-12-08 17:22:31 +03:00
|
|
|
$ MetadataModifier
|
2021-04-22 00:44:37 +03:00
|
|
|
$ metaSources.ix sourceName.toSourceMetadata.(smFunctions @b)
|
2021-01-29 08:48:17 +03:00
|
|
|
%~ 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-04-22 00:44: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
|
|
|
|
[] ->
|
|
|
|
throw400 NotExists $ "no such function exists in postgres : " <>> qf
|
|
|
|
[fi] -> return fi
|
|
|
|
_ ->
|
|
|
|
throw400 NotSupported $
|
|
|
|
"function " <> qf <<> " is overloaded. Overloaded functions are not supported"
|
|
|
|
|
2019-01-25 06:31:54 +03:00
|
|
|
runTrackFunc
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall b m
|
|
|
|
. (MonadError QErr m, CacheRWM m, MetadataM m, BackendMetadata b)
|
|
|
|
=> TrackFunction b
|
|
|
|
-> m EncJSON
|
|
|
|
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
|
|
|
|
|
|
|
runTrackFunctionV2
|
2021-04-22 00:44:37 +03:00
|
|
|
:: 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
|
2021-02-14 09:07:52 +03:00
|
|
|
data UnTrackFunction b
|
2019-01-25 06:31:54 +03:00
|
|
|
= UnTrackFunction
|
2021-02-14 09:07:52 +03:00
|
|
|
{ _utfFunction :: !(FunctionName b)
|
2020-12-28 15:56:00 +03:00
|
|
|
, _utfSource :: !SourceName
|
2021-02-14 09:07:52 +03:00
|
|
|
} deriving (Generic)
|
|
|
|
deriving instance (Backend b) => Show (UnTrackFunction b)
|
|
|
|
deriving instance (Backend b) => Eq (UnTrackFunction b)
|
|
|
|
instance (Backend b) => ToJSON (UnTrackFunction b) where
|
|
|
|
toJSON = genericToJSON hasuraJSON
|
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"
|
|
|
|
Nothing -> UnTrackFunction <$> parseJSON v <*> pure defaultSource
|
|
|
|
|
2019-01-25 06:31:54 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
askFunctionInfo
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall b m
|
2021-02-14 09:07:52 +03:00
|
|
|
. (CacheRM m, MonadError QErr m, Backend b)
|
|
|
|
=> SourceName -> FunctionName b -> m (FunctionInfo b)
|
|
|
|
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")
|
|
|
|
|
2019-01-25 06:31:54 +03:00
|
|
|
runUntrackFunc
|
2021-04-22 00:44:37 +03:00
|
|
|
:: 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
|
2020-12-08 17:22:31 +03:00
|
|
|
withNewInconsistentObjsCheck
|
|
|
|
$ buildSchemaCache
|
2021-04-22 00:44:37 +03:00
|
|
|
$ dropFunctionInMetadata @b defaultSource functionName
|
2020-12-08 17:22:31 +03:00
|
|
|
pure successMsg
|
|
|
|
|
2021-04-22 00:44:37 +03:00
|
|
|
dropFunctionInMetadata
|
|
|
|
:: forall b
|
|
|
|
. (BackendMetadata b)
|
|
|
|
=> SourceName
|
|
|
|
-> FunctionName b
|
|
|
|
-> MetadataModifier
|
2020-12-28 15:56:00 +03:00
|
|
|
dropFunctionInMetadata source function = MetadataModifier $
|
2021-04-22 00:44:37 +03:00
|
|
|
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).
|
|
|
|
-}
|
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
data CreateFunctionPermission b
|
2021-01-29 08:48:17 +03:00
|
|
|
= CreateFunctionPermission
|
2021-02-14 09:07:52 +03:00
|
|
|
{ _afpFunction :: !(FunctionName b)
|
2021-01-29 08:48:17 +03:00
|
|
|
, _afpSource :: !SourceName
|
|
|
|
, _afpRole :: !RoleName
|
2021-02-14 09:07:52 +03:00
|
|
|
} deriving (Generic)
|
|
|
|
deriving instance (Backend b) => Show (CreateFunctionPermission b)
|
|
|
|
deriving instance (Backend b) => Eq (CreateFunctionPermission b)
|
|
|
|
instance (Backend b) => ToJSON (CreateFunctionPermission b) where
|
|
|
|
toJSON = genericToJSON hasuraJSON
|
2021-01-29 08:48:17 +03:00
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
instance (Backend b) => FromJSON (CreateFunctionPermission b) where
|
2021-01-29 08:48:17 +03:00
|
|
|
parseJSON v =
|
|
|
|
flip (withObject "CreateFunctionPermission") v $ \o ->
|
|
|
|
CreateFunctionPermission
|
|
|
|
<$> o .: "function"
|
|
|
|
<*> o .:? "source" .!= defaultSource
|
|
|
|
<*> o .: "role"
|
|
|
|
|
|
|
|
runCreateFunctionPermission
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall b m
|
2021-02-14 09:07:52 +03:00
|
|
|
. ( CacheRWM m
|
2021-01-29 08:48:17 +03:00
|
|
|
, MonadError QErr m
|
|
|
|
, MetadataM m
|
2021-02-14 09:07:52 +03:00
|
|
|
, BackendMetadata b
|
2021-01-29 08:48:17 +03:00
|
|
|
)
|
2021-02-14 09:07:52 +03:00
|
|
|
=> CreateFunctionPermission b
|
2021-01-29 08:48:17 +03:00
|
|
|
-> m EncJSON
|
|
|
|
runCreateFunctionPermission (CreateFunctionPermission functionName source role) = do
|
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-01-29 08:48:17 +03:00
|
|
|
when (role `elem` _fiPermissions functionInfo) $
|
|
|
|
throw400 AlreadyExists $
|
|
|
|
"permission of role "
|
|
|
|
<> role <<> " already exists for function " <> functionName <<> " in source: " <>> source
|
|
|
|
functionTableInfo <-
|
2021-02-14 09:07:52 +03:00
|
|
|
unsafeTableInfo @b source (_fiReturnType functionInfo) sourceCache
|
2021-03-15 16:02:58 +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 $
|
|
|
|
"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
|
|
|
|
(MOSourceObjId source
|
2021-04-22 00:44:37 +03:00
|
|
|
$ AB.mkAnyBackend (SMOFunctionPermission @b functionName role))
|
2021-01-29 08:48:17 +03:00
|
|
|
$ MetadataModifier
|
2021-03-15 16:02:58 +03:00
|
|
|
$ metaSources.ix
|
2021-04-22 00:44:37 +03:00
|
|
|
source.toSourceMetadata.(smFunctions @b).ix functionName.fmPermissions
|
2021-01-29 08:48:17 +03:00
|
|
|
%~ (:) (FunctionPermissionMetadata role)
|
|
|
|
pure successMsg
|
|
|
|
|
2021-02-14 09:07:52 +03:00
|
|
|
dropFunctionPermissionInMetadata
|
2021-04-22 00:44:37 +03:00
|
|
|
:: forall b
|
|
|
|
. (BackendMetadata b)
|
|
|
|
=> SourceName
|
|
|
|
-> FunctionName b
|
|
|
|
-> RoleName
|
|
|
|
-> MetadataModifier
|
2021-01-29 08:48:17 +03:00
|
|
|
dropFunctionPermissionInMetadata source function role = MetadataModifier $
|
2021-04-22 00:44:37 +03:00
|
|
|
metaSources.ix source.toSourceMetadata.(smFunctions @b).ix function.fmPermissions %~ filter ((/=) role . _fpmRole)
|
2021-01-29 08:48:17 +03:00
|
|
|
|
|
|
|
type DropFunctionPermission = CreateFunctionPermission
|
|
|
|
|
|
|
|
runDropFunctionPermission
|
2021-03-15 16:02:58 +03:00
|
|
|
:: forall m b
|
|
|
|
. ( CacheRWM m
|
2021-01-29 08:48:17 +03:00
|
|
|
, MonadError QErr m
|
|
|
|
, MetadataM m
|
2021-02-14 09:07:52 +03:00
|
|
|
, BackendMetadata b
|
2021-01-29 08:48:17 +03:00
|
|
|
)
|
2021-02-14 09:07:52 +03:00
|
|
|
=> DropFunctionPermission b
|
2021-01-29 08:48:17 +03:00
|
|
|
-> m EncJSON
|
|
|
|
runDropFunctionPermission (CreateFunctionPermission functionName source role) = do
|
2021-04-22 00:44:37 +03:00
|
|
|
functionInfo <- askFunctionInfo @b source functionName
|
2021-01-29 08:48:17 +03:00
|
|
|
unless (role `elem` _fiPermissions functionInfo) $
|
|
|
|
throw400 NotExists $
|
|
|
|
"permission of role "
|
|
|
|
<> role <<> " does not exist for function " <> functionName <<> " in source: " <>> source
|
2021-03-15 16:02:58 +03:00
|
|
|
buildSchemaCacheFor
|
|
|
|
(MOSourceObjId source
|
|
|
|
$ AB.mkAnyBackend
|
2021-04-22 00:44:37 +03:00
|
|
|
$ SMOFunctionPermission @b functionName role)
|
|
|
|
$ dropFunctionPermissionInMetadata @b source functionName role
|
2021-01-29 08:48:17 +03:00
|
|
|
pure successMsg
|