mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 08:02:15 +03:00
Add metadata commands for custom return type permissions
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8587 Co-authored-by: Daniel Harvey <4729125+danieljharvey@users.noreply.github.com> GitOrigin-RevId: 660f2eda9cf1c7c612d66745064b3998c77804e0
This commit is contained in:
parent
79682e0598
commit
7e06b30e4d
@ -39,10 +39,12 @@ spec = do
|
||||
]
|
||||
|
||||
Fixture.hgeWithEnv [(featureFlagForLogicalModels, "True")] do
|
||||
-- need to run isolated
|
||||
traverse_
|
||||
(Fixture.runClean fixtures)
|
||||
[testImplementation]
|
||||
[ testImplementation,
|
||||
testPermissions,
|
||||
testPermissionFailures
|
||||
]
|
||||
|
||||
-- ** Setup and teardown
|
||||
|
||||
@ -182,3 +184,243 @@ testImplementation = do
|
||||
error: Custom type "nice" still being used by logical model "logical_model".
|
||||
path: $.args
|
||||
|]
|
||||
|
||||
----------------------
|
||||
-- Test permissions --
|
||||
----------------------
|
||||
|
||||
testPermissions :: SpecWith TestEnvironment
|
||||
testPermissions = do
|
||||
let customReturnType :: Schema.CustomType
|
||||
customReturnType =
|
||||
(Schema.customType "divided_stuff")
|
||||
{ Schema.customTypeColumns =
|
||||
[ (Schema.logicalModelColumn "divided" Schema.TInt)
|
||||
{ Schema.logicalModelColumnDescription = Just "a divided thing"
|
||||
}
|
||||
]
|
||||
}
|
||||
|
||||
describe "Permissions" do
|
||||
it "Adds a custom return type with a select permission and returns a 200" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
sourceName = BackendType.backendSourceName backendTypeMetadata
|
||||
backendType = BackendType.backendTypeString backendTypeMetadata
|
||||
|
||||
Schema.trackCustomType sourceName customReturnType testEnvironment
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadata
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: #{backendType}_create_custom_return_type_select_permission
|
||||
args:
|
||||
source: #{sourceName}
|
||||
name: divided_stuff
|
||||
role: "test"
|
||||
permission:
|
||||
columns:
|
||||
- divided
|
||||
filter: {}
|
||||
|]
|
||||
)
|
||||
[yaml|
|
||||
- message: success
|
||||
|]
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadata
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: #{backendType}_get_custom_return_type
|
||||
args:
|
||||
source: #{sourceName}
|
||||
|]
|
||||
)
|
||||
[interpolateYaml|
|
||||
- name: divided_stuff
|
||||
description: ''
|
||||
fields:
|
||||
- description: a divided thing
|
||||
name: divided
|
||||
nullable: false
|
||||
type: integer
|
||||
select_permissions:
|
||||
- role: "test"
|
||||
permission:
|
||||
columns:
|
||||
- divided
|
||||
filter: {}
|
||||
|]
|
||||
|
||||
it "Adds a logical model, removes it, and returns 200" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
sourceName = BackendType.backendSourceName backendTypeMetadata
|
||||
backendType = BackendType.backendTypeString backendTypeMetadata
|
||||
|
||||
Schema.trackCustomType sourceName customReturnType testEnvironment
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadata
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: #{backendType}_create_custom_return_type_select_permission
|
||||
args:
|
||||
source: #{sourceName}
|
||||
name: divided_stuff
|
||||
role: "test"
|
||||
permission:
|
||||
columns:
|
||||
- divided
|
||||
filter: {}
|
||||
- type: #{backendType}_drop_custom_return_type_select_permission
|
||||
args:
|
||||
source: #{sourceName}
|
||||
name: divided_stuff
|
||||
role: "test"
|
||||
|]
|
||||
)
|
||||
[yaml|
|
||||
- message: success
|
||||
- message: success
|
||||
|]
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadata
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: #{backendType}_get_custom_return_type
|
||||
args:
|
||||
source: #{sourceName}
|
||||
|]
|
||||
)
|
||||
[interpolateYaml|
|
||||
- name: divided_stuff
|
||||
description: ''
|
||||
fields:
|
||||
- description: a divided thing
|
||||
name: divided
|
||||
nullable: false
|
||||
type: integer
|
||||
|]
|
||||
|
||||
testPermissionFailures :: SpecWith TestEnvironment
|
||||
testPermissionFailures = do
|
||||
describe "Permission failures" do
|
||||
it "Fails to adds a select permission to a nonexisting source" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
backendType = BackendType.backendTypeString backendTypeMetadata
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadataWithStatus
|
||||
400
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: #{backendType}_create_custom_return_type_select_permission
|
||||
args:
|
||||
source: made_up_source
|
||||
name: divided_stuff
|
||||
role: "test"
|
||||
permission:
|
||||
columns:
|
||||
- divided
|
||||
filter: {}
|
||||
|]
|
||||
)
|
||||
[yaml|
|
||||
code: not-found
|
||||
error: "Source \"made_up_source\" not found."
|
||||
path: "$.args[0].args"
|
||||
|]
|
||||
|
||||
it "Fails to adds a select permission to a nonexisting custom return type" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
sourceName = BackendType.backendSourceName backendTypeMetadata
|
||||
backendType = BackendType.backendTypeString backendTypeMetadata
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadataWithStatus
|
||||
400
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: bulk
|
||||
args:
|
||||
- type: #{backendType}_create_custom_return_type_select_permission
|
||||
args:
|
||||
source: #{sourceName}
|
||||
name: made_up_custom_return_type
|
||||
role: "test"
|
||||
permission:
|
||||
columns:
|
||||
- divided
|
||||
filter: {}
|
||||
|]
|
||||
)
|
||||
[interpolateYaml|
|
||||
code: "not-found"
|
||||
error: Custom return type "made_up_custom_return_type" not found in source "#{sourceName}".
|
||||
path: "$.args[0].args"
|
||||
|]
|
||||
|
||||
it "Fails to drop a select permission on a nonexisting source" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
backendType = BackendType.backendTypeString backendTypeMetadata
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadataWithStatus
|
||||
400
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: #{backendType}_drop_custom_return_type_select_permission
|
||||
args:
|
||||
source: made_up_source
|
||||
name: made_up_custom_return_type
|
||||
role: "test"
|
||||
permission:
|
||||
columns:
|
||||
- divided
|
||||
filter: {}
|
||||
|]
|
||||
)
|
||||
[interpolateYaml|
|
||||
code: not-found
|
||||
error: "Source \"made_up_source\" not found."
|
||||
path: "$.args"
|
||||
|]
|
||||
|
||||
it "Fails to drop a select permission from a nonexisting custom return type" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
sourceName = BackendType.backendSourceName backendTypeMetadata
|
||||
backendType = BackendType.backendTypeString backendTypeMetadata
|
||||
|
||||
shouldReturnYaml
|
||||
testEnvironment
|
||||
( GraphqlEngine.postMetadataWithStatus
|
||||
400
|
||||
testEnvironment
|
||||
[interpolateYaml|
|
||||
type: #{backendType}_drop_custom_return_type_select_permission
|
||||
args:
|
||||
source: #{sourceName}
|
||||
name: made_up_custom_return_type
|
||||
role: "test"
|
||||
|]
|
||||
)
|
||||
[interpolateYaml|
|
||||
code: "not-found"
|
||||
error: Custom return type "made_up_custom_return_type" not found in source "#{sourceName}".
|
||||
path: "$.args"
|
||||
|]
|
||||
|
@ -67,14 +67,13 @@ spec = do
|
||||
]
|
||||
|
||||
Fixture.hgeWithEnv [(featureFlagForLogicalModels, "True")] do
|
||||
-- do not need to run isolated
|
||||
traverse_
|
||||
(Fixture.runClean fixtures)
|
||||
[testAdminAccess, testPermissionFailures]
|
||||
-- need to run isolated
|
||||
traverse_
|
||||
(Fixture.runClean fixtures)
|
||||
[testImplementation, testPermissions]
|
||||
[ testAdminAccess,
|
||||
testImplementation,
|
||||
testPermissions,
|
||||
testPermissionFailures
|
||||
]
|
||||
|
||||
metadataHandlingWhenDisabledSpec
|
||||
|
||||
|
@ -164,7 +164,7 @@ logicalModelToPreparedStatement customReturnType model = do
|
||||
|
||||
returnedColumnNames :: Text
|
||||
returnedColumnNames =
|
||||
commaSeparated $ InsOrd.keys (_ctmFields customReturnType)
|
||||
commaSeparated $ InsOrd.keys (_crtmFields customReturnType)
|
||||
|
||||
wrapInCTE :: Text -> Text
|
||||
wrapInCTE query =
|
||||
|
@ -9,6 +9,10 @@ module Hasura.CustomReturnType.API
|
||||
runTrackCustomReturnType,
|
||||
runUntrackCustomReturnType,
|
||||
dropCustomReturnTypeInMetadata,
|
||||
CreateCustomReturnTypePermission (..),
|
||||
DropCustomReturnTypePermission (..),
|
||||
runCreateSelectCustomReturnTypePermission,
|
||||
runDropSelectCustomReturnTypePermission,
|
||||
getCustomTypes,
|
||||
module Hasura.CustomReturnType.Types,
|
||||
)
|
||||
@ -22,7 +26,7 @@ import Data.HashMap.Strict.InsOrd qualified as InsOrd
|
||||
import Data.HashMap.Strict.InsOrd.Extended qualified as OMap
|
||||
import Data.Text.Extended (toTxt, (<<>))
|
||||
import Hasura.Base.Error
|
||||
import Hasura.CustomReturnType.Metadata (CustomReturnTypeMetadata (..))
|
||||
import Hasura.CustomReturnType.Metadata (CustomReturnTypeMetadata (..), crtmSelectPermissions)
|
||||
import Hasura.CustomReturnType.Types (CustomReturnTypeName)
|
||||
import Hasura.EncJSON
|
||||
import Hasura.LogicalModel.Metadata (LogicalModelMetadata (..))
|
||||
@ -30,15 +34,17 @@ import Hasura.LogicalModel.Types (NullableScalarType, nullableScalarTypeMapCodec
|
||||
import Hasura.Metadata.DTO.Utils (codecNamePrefix)
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.Types.Backend (Backend (..))
|
||||
import Hasura.RQL.Types.Common (SourceName, sourceNameToText, successMsg)
|
||||
import Hasura.RQL.Types.Common (SourceName, defaultSource, sourceNameToText, successMsg)
|
||||
import Hasura.RQL.Types.Metadata
|
||||
import Hasura.RQL.Types.Metadata.Backend
|
||||
import Hasura.RQL.Types.Metadata.Object
|
||||
import Hasura.RQL.Types.Permission (PermDef (_pdRole), SelPerm)
|
||||
import Hasura.RQL.Types.SchemaCache.Build
|
||||
import Hasura.SQL.AnyBackend qualified as AB
|
||||
import Hasura.SQL.Backend
|
||||
import Hasura.Server.Init.FeatureFlag as FF
|
||||
import Hasura.Server.Types (HasServerConfigCtx (..), ServerConfigCtx (..))
|
||||
import Hasura.Session (RoleName)
|
||||
|
||||
-- | Default implementation of the 'track_custom_return_type' request payload.
|
||||
data TrackCustomReturnType (b :: BackendType) = TrackCustomReturnType
|
||||
@ -56,7 +62,7 @@ instance (Backend b) => HasCodec (TrackCustomReturnType b) where
|
||||
$ TrackCustomReturnType
|
||||
<$> AC.requiredField "source" sourceDoc
|
||||
AC..= tctSource
|
||||
<*> AC.requiredField "name" rootFieldDoc
|
||||
<*> AC.requiredField "name" nameDoc
|
||||
AC..= tctName
|
||||
<*> AC.optionalField "description" descriptionDoc
|
||||
AC..= tctDescription
|
||||
@ -64,7 +70,7 @@ instance (Backend b) => HasCodec (TrackCustomReturnType b) where
|
||||
AC..= tctFields
|
||||
where
|
||||
sourceDoc = "The source in which this custom return type should be tracked"
|
||||
rootFieldDoc = "Root field name for the custom return type"
|
||||
nameDoc = "Root field name for the custom return type"
|
||||
fieldsDoc = "Return type of the expression"
|
||||
descriptionDoc = "A description of the query which appears in the graphql schema"
|
||||
|
||||
@ -85,10 +91,10 @@ customTypeTrackToMetadata ::
|
||||
CustomReturnTypeMetadata b
|
||||
customTypeTrackToMetadata TrackCustomReturnType {..} =
|
||||
CustomReturnTypeMetadata
|
||||
{ _ctmName = tctName,
|
||||
_ctmFields = tctFields,
|
||||
_ctmSelectPermissions = mempty,
|
||||
_ctmDescription = tctDescription
|
||||
{ _crtmName = tctName,
|
||||
_crtmFields = tctFields,
|
||||
_crtmSelectPermissions = mempty,
|
||||
_crtmDescription = tctDescription
|
||||
}
|
||||
|
||||
-- | API payload for the 'get_custom_return_type' endpoint.
|
||||
@ -160,7 +166,7 @@ runTrackCustomReturnType trackCustomReturnTypeRequest = do
|
||||
|
||||
let (metadata :: CustomReturnTypeMetadata b) = customTypeTrackToMetadata trackCustomReturnTypeRequest
|
||||
|
||||
let fieldName = _ctmName metadata
|
||||
let fieldName = _crtmName metadata
|
||||
metadataObj =
|
||||
MOSourceObjId source $
|
||||
AB.mkAnyBackend $
|
||||
@ -244,12 +250,94 @@ runUntrackCustomReturnType q = do
|
||||
source = utctSource q
|
||||
fieldName = utctName q
|
||||
|
||||
-- | A permission for logical models is tied to a specific root field name and
|
||||
-- source. This wrapper adds both of those things to the JSON object that
|
||||
-- describes the permission.
|
||||
data CreateCustomReturnTypePermission a (b :: BackendType) = CreateCustomReturnTypePermission
|
||||
{ ccrtpSource :: SourceName,
|
||||
ccrtpName :: CustomReturnTypeName,
|
||||
ccrtpInfo :: PermDef b a
|
||||
}
|
||||
deriving stock (Generic)
|
||||
|
||||
instance
|
||||
FromJSON (PermDef b a) =>
|
||||
FromJSON (CreateCustomReturnTypePermission a b)
|
||||
where
|
||||
parseJSON = withObject "CreateCustomReturnTypePermission" \obj -> do
|
||||
ccrtpSource <- obj .:? "source" .!= defaultSource
|
||||
ccrtpName <- obj .: "name"
|
||||
ccrtpInfo <- parseJSON (Object obj)
|
||||
|
||||
pure CreateCustomReturnTypePermission {..}
|
||||
|
||||
runCreateSelectCustomReturnTypePermission ::
|
||||
forall b m.
|
||||
(Backend b, CacheRWM m, MetadataM m, MonadError QErr m, MonadIO m, HasServerConfigCtx m) =>
|
||||
CreateCustomReturnTypePermission SelPerm b ->
|
||||
m EncJSON
|
||||
runCreateSelectCustomReturnTypePermission CreateCustomReturnTypePermission {..} = do
|
||||
throwIfFeatureDisabled
|
||||
assertCustomReturnTypeExists @b ccrtpSource ccrtpName
|
||||
|
||||
let metadataObj :: MetadataObjId
|
||||
metadataObj =
|
||||
MOSourceObjId ccrtpSource $
|
||||
AB.mkAnyBackend $
|
||||
SMOCustomReturnType @b ccrtpName
|
||||
|
||||
buildSchemaCacheFor metadataObj $
|
||||
MetadataModifier $
|
||||
customReturnTypeMetadataSetter @b ccrtpSource ccrtpName . crtmSelectPermissions
|
||||
%~ OMap.insert (_pdRole ccrtpInfo) ccrtpInfo
|
||||
|
||||
pure successMsg
|
||||
|
||||
-- | To drop a permission, we need to know the source and root field name of
|
||||
-- the logical model, as well as the role whose permission we want to drop.
|
||||
data DropCustomReturnTypePermission (b :: BackendType) = DropCustomReturnTypePermission
|
||||
{ dcrtpSource :: SourceName,
|
||||
dcrtpName :: CustomReturnTypeName,
|
||||
dcrtpRole :: RoleName
|
||||
}
|
||||
deriving stock (Generic)
|
||||
|
||||
instance FromJSON (DropCustomReturnTypePermission b) where
|
||||
parseJSON = withObject "DropCustomReturnTypePermission" \obj -> do
|
||||
dcrtpSource <- obj .:? "source" .!= defaultSource
|
||||
dcrtpName <- obj .: "name"
|
||||
dcrtpRole <- obj .: "role"
|
||||
|
||||
pure DropCustomReturnTypePermission {..}
|
||||
|
||||
runDropSelectCustomReturnTypePermission ::
|
||||
forall b m.
|
||||
(Backend b, CacheRWM m, MetadataM m, MonadError QErr m, MonadIO m, HasServerConfigCtx m) =>
|
||||
DropCustomReturnTypePermission b ->
|
||||
m EncJSON
|
||||
runDropSelectCustomReturnTypePermission DropCustomReturnTypePermission {..} = do
|
||||
throwIfFeatureDisabled
|
||||
assertCustomReturnTypeExists @b dcrtpSource dcrtpName
|
||||
|
||||
let metadataObj :: MetadataObjId
|
||||
metadataObj =
|
||||
MOSourceObjId dcrtpSource $
|
||||
AB.mkAnyBackend $
|
||||
SMOCustomReturnType @b dcrtpName
|
||||
|
||||
buildSchemaCacheFor metadataObj $
|
||||
MetadataModifier $
|
||||
customReturnTypeMetadataSetter @b dcrtpSource dcrtpName . crtmSelectPermissions
|
||||
%~ OMap.delete dcrtpRole
|
||||
|
||||
pure successMsg
|
||||
|
||||
-- | TODO: should this cascade and also delete associated permissions?
|
||||
dropCustomReturnTypeInMetadata :: forall b. BackendMetadata b => SourceName -> CustomReturnTypeName -> MetadataModifier
|
||||
dropCustomReturnTypeInMetadata source rootFieldName = do
|
||||
dropCustomReturnTypeInMetadata source name = do
|
||||
MetadataModifier $
|
||||
metaSources . ix source . toSourceMetadata @b . smCustomReturnTypes
|
||||
%~ OMap.delete rootFieldName
|
||||
%~ OMap.delete name
|
||||
|
||||
-- | check feature flag is enabled before carrying out any actions
|
||||
throwIfFeatureDisabled :: (HasServerConfigCtx m, MonadIO m, MonadError QErr m) => m ()
|
||||
@ -264,7 +352,7 @@ throwIfFeatureDisabled = do
|
||||
-- | Check whether a custom return type with the given root field name exists for
|
||||
-- the given source.
|
||||
assertCustomReturnTypeExists :: forall b m. (Backend b, MetadataM m, MonadError QErr m) => SourceName -> CustomReturnTypeName -> m ()
|
||||
assertCustomReturnTypeExists sourceName rootFieldName = do
|
||||
assertCustomReturnTypeExists sourceName name = do
|
||||
metadata <- getMetadata
|
||||
|
||||
let sourceMetadataTraversal :: Traversal' Metadata (SourceMetadata b)
|
||||
@ -275,7 +363,7 @@ assertCustomReturnTypeExists sourceName rootFieldName = do
|
||||
`onNothing` throw400 NotFound ("Source " <> sourceName <<> " not found.")
|
||||
|
||||
let desiredCustomReturnType :: Traversal' (SourceMetadata b) (CustomReturnTypeMetadata b)
|
||||
desiredCustomReturnType = smCustomReturnTypes . ix rootFieldName
|
||||
desiredCustomReturnType = smCustomReturnTypes . ix name
|
||||
|
||||
unless (has desiredCustomReturnType sourceMetadata) do
|
||||
throw400 NotFound ("Custom return type " <> rootFieldName <<> " not found in source " <> sourceName <<> ".")
|
||||
throw400 NotFound ("Custom return type " <> name <<> " not found in source " <> sourceName <<> ".")
|
||||
|
@ -1,13 +1,19 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
|
||||
module Hasura.CustomReturnType.Metadata
|
||||
( CustomReturnTypeMetadata (..),
|
||||
CustomReturnTypeName (..),
|
||||
crtmName,
|
||||
crtmFields,
|
||||
crtmDescription,
|
||||
crtmSelectPermissions,
|
||||
)
|
||||
where
|
||||
|
||||
import Autodocodec (Autodocodec (Autodocodec), HasCodec)
|
||||
import Autodocodec qualified as AC
|
||||
import Control.Lens (makeLenses)
|
||||
import Data.Aeson (FromJSON, ToJSON)
|
||||
import Data.HashMap.Strict.InsOrd qualified as InsOrd
|
||||
import Data.HashMap.Strict.InsOrd.Autodocodec (sortedElemsCodec)
|
||||
@ -22,13 +28,15 @@ import Hasura.Session (RoleName)
|
||||
|
||||
-- | Description of a custom return type for use in metadata (before schema cache)
|
||||
data CustomReturnTypeMetadata (b :: BackendType) = CustomReturnTypeMetadata
|
||||
{ _ctmName :: CustomReturnTypeName,
|
||||
_ctmFields :: InsOrd.InsOrdHashMap (Column b) (NullableScalarType b),
|
||||
_ctmDescription :: Maybe Text,
|
||||
_ctmSelectPermissions :: InsOrdHashMap RoleName (SelPermDef b)
|
||||
{ _crtmName :: CustomReturnTypeName,
|
||||
_crtmFields :: InsOrd.InsOrdHashMap (Column b) (NullableScalarType b),
|
||||
_crtmDescription :: Maybe Text,
|
||||
_crtmSelectPermissions :: InsOrdHashMap RoleName (SelPermDef b)
|
||||
}
|
||||
deriving (Generic)
|
||||
|
||||
makeLenses ''CustomReturnTypeMetadata
|
||||
|
||||
instance (Backend b) => HasCodec (CustomReturnTypeMetadata b) where
|
||||
codec =
|
||||
AC.CommentCodec
|
||||
@ -36,13 +44,13 @@ instance (Backend b) => HasCodec (CustomReturnTypeMetadata b) where
|
||||
$ AC.object (codecNamePrefix @b <> "CustomReturnTypeMetadata")
|
||||
$ CustomReturnTypeMetadata
|
||||
<$> AC.requiredField "name" nameDoc
|
||||
AC..= _ctmName
|
||||
AC..= _crtmName
|
||||
<*> AC.requiredFieldWith "fields" nullableScalarTypeMapCodec fieldsDoc
|
||||
AC..= _ctmFields
|
||||
AC..= _crtmFields
|
||||
<*> AC.optionalField "description" descriptionDoc
|
||||
AC..= _ctmDescription
|
||||
AC..= _crtmDescription
|
||||
<*> optSortedList "select_permissions" _pdRole
|
||||
AC..= _ctmSelectPermissions
|
||||
AC..= _crtmSelectPermissions
|
||||
where
|
||||
nameDoc = "A name for a custom return type"
|
||||
fieldsDoc = "Return types for the custom return type"
|
||||
|
@ -736,30 +736,30 @@ buildSchemaCacheRule logger env = proc (MetadataWithResourceVersion metadataNoDe
|
||||
liftIO @m $ checkFeatureFlag FF.logicalModelInterface
|
||||
|
||||
let mkCustomReturnTypeMetadataObject :: CustomReturnTypeMetadata b -> MetadataObject
|
||||
mkCustomReturnTypeMetadataObject ctm =
|
||||
mkCustomReturnTypeMetadataObject crtm =
|
||||
( MetadataObject
|
||||
( MOSourceObjId sourceName $
|
||||
AB.mkAnyBackend $
|
||||
SMOCustomReturnType @b (_ctmName ctm)
|
||||
SMOCustomReturnType @b (_crtmName crtm)
|
||||
)
|
||||
(toJSON ctm)
|
||||
(toJSON crtm)
|
||||
)
|
||||
|
||||
customReturnTypeCacheMaybes <-
|
||||
interpretWriter
|
||||
-< for
|
||||
(OMap.elems customReturnTypes)
|
||||
\ctm@CustomReturnTypeMetadata {..} ->
|
||||
withRecordInconsistencyM (mkCustomReturnTypeMetadataObject ctm) $ do
|
||||
\crtm@CustomReturnTypeMetadata {..} ->
|
||||
withRecordInconsistencyM (mkCustomReturnTypeMetadataObject crtm) $ do
|
||||
unless areLogicalModelsEnabled $
|
||||
throw400 InvalidConfiguration "The Logical Models feature is disabled"
|
||||
|
||||
pure
|
||||
CustomReturnTypeInfo
|
||||
{ _ctiName = _ctmName,
|
||||
_ctiFields = _ctmFields,
|
||||
{ _ctiName = _crtmName,
|
||||
_ctiFields = _crtmFields,
|
||||
_ctiPermissions = mempty,
|
||||
_ctiDescription = _ctmDescription
|
||||
_ctiDescription = _crtmDescription
|
||||
}
|
||||
|
||||
let customReturnTypesCache :: CustomReturnTypeCache b
|
||||
|
@ -22,6 +22,7 @@ module Hasura.RQL.Types.Metadata
|
||||
emptyMetadata,
|
||||
emptyMetadataDefaults,
|
||||
functionMetadataSetter,
|
||||
customReturnTypeMetadataSetter,
|
||||
logicalModelMetadataSetter,
|
||||
metaActions,
|
||||
metaAllowlist,
|
||||
@ -54,6 +55,7 @@ import Data.Aeson.TH
|
||||
import Data.Aeson.Types
|
||||
import Data.HashMap.Strict.InsOrd.Extended qualified as OM
|
||||
import Data.Monoid (Dual (..), Endo (..))
|
||||
import Hasura.CustomReturnType.Metadata (CustomReturnTypeMetadata, CustomReturnTypeName)
|
||||
import Hasura.Incremental qualified as Inc
|
||||
import Hasura.LogicalModel.Metadata (LogicalModelMetadata, LogicalModelName, lmmSelectPermissions)
|
||||
import Hasura.Metadata.DTO.MetadataV3 (MetadataV3 (..))
|
||||
@ -276,6 +278,16 @@ functionMetadataSetter ::
|
||||
functionMetadataSetter source function =
|
||||
metaSources . ix source . toSourceMetadata . smFunctions . ix function
|
||||
|
||||
-- | A lens setter for the metadata of a custom return type as identified by the
|
||||
-- source name and root field name.
|
||||
customReturnTypeMetadataSetter ::
|
||||
(Backend b) =>
|
||||
SourceName ->
|
||||
CustomReturnTypeName ->
|
||||
ASetter' Metadata (CustomReturnTypeMetadata b)
|
||||
customReturnTypeMetadataSetter source name =
|
||||
metaSources . ix source . toSourceMetadata . smCustomReturnTypes . ix name
|
||||
|
||||
-- | A lens setter for the metadata of a logical model as identified by the
|
||||
-- source name and root field name.
|
||||
logicalModelMetadataSetter ::
|
||||
|
@ -443,7 +443,7 @@ instance (Backend b) => FromJSONWithContext (BackendSourceKind b) (SourceMetadat
|
||||
_smTables <- oMapFromL _tmTable <$> o .: "tables"
|
||||
_smFunctions <- oMapFromL _fmFunction <$> o .:? "functions" .!= []
|
||||
_smLogicalModels <- oMapFromL _lmmRootFieldName <$> o .:? "logical_models" .!= []
|
||||
_smCustomReturnTypes <- oMapFromL _ctmName <$> o .:? "custom_return_types" .!= []
|
||||
_smCustomReturnTypes <- oMapFromL _crtmName <$> o .:? "custom_return_types" .!= []
|
||||
_smConfiguration <- o .: "configuration"
|
||||
_smQueryTags <- o .:? "query_tags"
|
||||
_smCustomization <- o .:? "customization" .!= emptySourceCustomization
|
||||
@ -504,7 +504,7 @@ instance Backend b => HasCodec (SourceMetadata b) where
|
||||
.== _smFunctions
|
||||
<*> optionalFieldOrNullWithOmittedDefaultWith' "logical_models" (sortedElemsCodec _lmmRootFieldName) mempty
|
||||
.== _smLogicalModels
|
||||
<*> optionalFieldOrNullWithOmittedDefaultWith' "custom_return_types" (sortedElemsCodec _ctmName) mempty
|
||||
<*> optionalFieldOrNullWithOmittedDefaultWith' "custom_return_types" (sortedElemsCodec _crtmName) mempty
|
||||
.== _smCustomReturnTypes
|
||||
<*> requiredField' "configuration"
|
||||
.== _smConfiguration
|
||||
|
@ -122,7 +122,7 @@ sourcesToOrdJSONList sources =
|
||||
tablesPair = ("tables", AO.array $ map tableMetaToOrdJSON $ sortOn _tmTable $ OM.elems _smTables)
|
||||
functionsPair = listToMaybeOrdPairSort "functions" functionMetadataToOrdJSON _fmFunction _smFunctions
|
||||
logicalModelsPair = listToMaybeOrdPairSort "logical_models" AO.toOrdered _lmmRootFieldName (OM.elems _smLogicalModels)
|
||||
customReturnTypesPair = listToMaybeOrdPairSort "custom_return_types" AO.toOrdered _ctmName (OM.elems _smCustomReturnTypes)
|
||||
customReturnTypesPair = listToMaybeOrdPairSort "custom_return_types" AO.toOrdered _crtmName (OM.elems _smCustomReturnTypes)
|
||||
configurationPair = [("configuration", AO.toOrdered _smConfiguration)]
|
||||
queryTagsConfigPair = maybe [] (\queryTagsConfig -> [("query_tags", AO.toOrdered queryTagsConfig)]) _smQueryTags
|
||||
|
||||
|
@ -181,5 +181,7 @@ customReturnTypesCommands :: forall (b :: BackendType). Backend b => [CommandPar
|
||||
customReturnTypesCommands =
|
||||
[ commandParser "get_custom_return_type" $ RMGetCustomReturnType . mkAnyBackend @b,
|
||||
commandParser "track_custom_return_type" $ RMTrackCustomReturnType . mkAnyBackend @b,
|
||||
commandParser "untrack_custom_return_type" $ RMUntrackCustomReturnType . mkAnyBackend @b
|
||||
commandParser "untrack_custom_return_type" $ RMUntrackCustomReturnType . mkAnyBackend @b,
|
||||
commandParser "create_custom_return_type_select_permission" $ RMCreateSelectCustomReturnTypePermission . mkAnyBackend @b,
|
||||
commandParser "drop_custom_return_type_select_permission" $ RMDropSelectCustomReturnTypePermission . mkAnyBackend @b
|
||||
]
|
||||
|
@ -143,6 +143,8 @@ data RQLMetadataV1
|
||||
RMGetCustomReturnType !(AnyBackend CustomReturnType.GetCustomReturnType)
|
||||
| RMTrackCustomReturnType !(AnyBackend CustomReturnType.TrackCustomReturnType)
|
||||
| RMUntrackCustomReturnType !(AnyBackend CustomReturnType.UntrackCustomReturnType)
|
||||
| RMCreateSelectCustomReturnTypePermission !(AnyBackend (CustomReturnType.CreateCustomReturnTypePermission SelPerm))
|
||||
| RMDropSelectCustomReturnTypePermission !(AnyBackend CustomReturnType.DropCustomReturnTypePermission)
|
||||
| -- Tables event triggers
|
||||
RMCreateEventTrigger !(AnyBackend (Unvalidated1 CreateEventTriggerQuery))
|
||||
| RMDeleteEventTrigger !(AnyBackend DeleteEventTriggerQuery)
|
||||
@ -501,11 +503,13 @@ queryModifiesMetadata = \case
|
||||
RMGetLogicalModel _ -> False
|
||||
RMTrackLogicalModel _ -> True
|
||||
RMUntrackLogicalModel _ -> True
|
||||
RMCreateSelectLogicalModelPermission _ -> True
|
||||
RMDropSelectLogicalModelPermission _ -> True
|
||||
RMGetCustomReturnType _ -> False
|
||||
RMTrackCustomReturnType _ -> True
|
||||
RMUntrackCustomReturnType _ -> True
|
||||
RMCreateSelectLogicalModelPermission _ -> True
|
||||
RMDropSelectLogicalModelPermission _ -> True
|
||||
RMCreateSelectCustomReturnTypePermission _ -> True
|
||||
RMDropSelectCustomReturnTypePermission _ -> True
|
||||
RMBulk qs -> any queryModifiesMetadata qs
|
||||
-- We used to assume that the fallthrough was True,
|
||||
-- but it is better to be explicit here to warn when new constructors are added.
|
||||
@ -698,6 +702,8 @@ runMetadataQueryV1M env currentResourceVersion = \case
|
||||
RMGetCustomReturnType q -> dispatchMetadata CustomReturnType.runGetCustomReturnType q
|
||||
RMTrackCustomReturnType q -> dispatchMetadata CustomReturnType.runTrackCustomReturnType q
|
||||
RMUntrackCustomReturnType q -> dispatchMetadata CustomReturnType.runUntrackCustomReturnType q
|
||||
RMCreateSelectCustomReturnTypePermission q -> dispatchMetadata CustomReturnType.runCreateSelectCustomReturnTypePermission q
|
||||
RMDropSelectCustomReturnTypePermission q -> dispatchMetadata CustomReturnType.runDropSelectCustomReturnTypePermission q
|
||||
RMCreateEventTrigger q ->
|
||||
dispatchMetadataAndEventTrigger
|
||||
( validateTransforms
|
||||
|
@ -98,6 +98,8 @@ data RQLMetadataV1
|
||||
RMGetCustomReturnType !(AnyBackend CustomReturnType.GetCustomReturnType)
|
||||
| RMTrackCustomReturnType !(AnyBackend CustomReturnType.TrackCustomReturnType)
|
||||
| RMUntrackCustomReturnType !(AnyBackend CustomReturnType.UntrackCustomReturnType)
|
||||
| RMCreateSelectCustomReturnTypePermission !(AnyBackend (CustomReturnType.CreateCustomReturnTypePermission SelPerm))
|
||||
| RMDropSelectCustomReturnTypePermission !(AnyBackend CustomReturnType.DropCustomReturnTypePermission)
|
||||
| -- Tables event triggers
|
||||
RMCreateEventTrigger !(AnyBackend (Unvalidated1 CreateEventTriggerQuery))
|
||||
| RMDeleteEventTrigger !(AnyBackend DeleteEventTriggerQuery)
|
||||
|
@ -69,10 +69,10 @@ spec = do
|
||||
describe "Validation" do
|
||||
let crtm =
|
||||
CustomReturnTypeMetadata
|
||||
{ _ctmName = CustomReturnTypeName (G.unsafeMkName "custom_return_type_name"),
|
||||
_ctmFields = mempty,
|
||||
_ctmDescription = Nothing,
|
||||
_ctmSelectPermissions = mempty
|
||||
{ _crtmName = CustomReturnTypeName (G.unsafeMkName "custom_return_type_name"),
|
||||
_crtmFields = mempty,
|
||||
_crtmDescription = Nothing,
|
||||
_crtmSelectPermissions = mempty
|
||||
}
|
||||
|
||||
lmm =
|
||||
|
Loading…
Reference in New Issue
Block a user