mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-18 13:02:11 +03:00
92026b769f
fixes #3868 docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de` Note: To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`. Introduction ------------ This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`. How are select permissions of different roles are combined? ------------------------------------------------------------ A select permission includes 5 things: 1. Columns accessible to the role 2. Row selection filter 3. Limit 4. Allow aggregation 5. Scalar computed fields accessible to the role Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`. Let's say the following GraphQL query is queried with the `combined_roles` role. ```graphql query { employees { address phone } } ``` This will translate to the following SQL query: ```sql select (case when (P1 or P2) then address else null end) as address, (case when P2 then phone else null end) as phone from employee where (P1 or P2) ``` The other parameters of the select permission will be combined in the following manner: 1. Limit - Minimum of the limits will be the limit of the inherited role 2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation 3. Scalar computed fields - same as table column fields, as in the above example APIs for inherited roles: ---------------------- 1. `add_inherited_role` `add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments `role_name`: the name of the inherited role to be added (String) `role_set`: list of roles that need to be combined (Array of Strings) Example: ```json { "type": "add_inherited_role", "args": { "role_name":"combined_user", "role_set":[ "user", "user1" ] } } ``` After adding the inherited role, the inherited role can be used like single roles like earlier Note: An inherited role can only be created with non-inherited/singular roles. 2. `drop_inherited_role` The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument: `role_name`: name of the inherited role to be dropped Example: ```json { "type": "drop_inherited_role", "args": { "role_name":"combined_user" } } ``` Metadata --------- The derived roles metadata will be included under the `experimental_features` key while exporting the metadata. ```json { "experimental_features": { "derived_roles": [ { "role_name": "manager_is_employee_too", "role_set": [ "employee", "manager" ] } ] } } ``` Scope ------ Only postgres queries and subscriptions are supported in this PR. Important points: ----------------- 1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done. TODOs ------- - [ ] Tests - [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features - [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?) - [ ] Introspection test with a inherited role (nullability changes in a inherited role) - [ ] Docs - [ ] Changelog Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com> GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
259 lines
12 KiB
Haskell
259 lines
12 KiB
Haskell
{-# LANGUAGE Arrows #-}
|
|
{-# LANGUAGE ViewPatterns #-}
|
|
|
|
module Hasura.RQL.DDL.Schema.Cache.Permission
|
|
( buildTablePermissions
|
|
, mkPermissionMetadataObject
|
|
, mkRemoteSchemaPermissionMetadataObject
|
|
) where
|
|
|
|
import Hasura.Prelude
|
|
|
|
import qualified Data.HashMap.Strict as M
|
|
import qualified Data.HashMap.Strict.Extended as M
|
|
import qualified Data.HashMap.Strict.InsOrd as OMap
|
|
import qualified Data.HashSet as Set
|
|
import qualified Data.List.NonEmpty as NE
|
|
import qualified Data.Sequence as Seq
|
|
|
|
|
|
import Control.Arrow.Extended
|
|
import Data.Aeson
|
|
import Data.Text.Extended
|
|
|
|
import qualified Hasura.Incremental as Inc
|
|
|
|
import Hasura.RQL.DDL.Permission
|
|
import Hasura.RQL.DDL.Permission.Internal
|
|
import Hasura.RQL.DDL.Schema.Cache.Common
|
|
import Hasura.RQL.Types
|
|
import Hasura.Server.Types
|
|
import Hasura.Session
|
|
|
|
{- Note: [Inherited roles architecture for postgres read queries]
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
1. Schema generation
|
|
--------------------
|
|
|
|
Schema generation for inherited roles is similar to the schema
|
|
generation of non-inherited roles. In the case of inherited roles,
|
|
we combine the `SelectPermInfo`s (see `combineSelectPermInfos`) of the
|
|
inherited role's role set and a new `SelectPermInfo` will be generated
|
|
which will be the select permission of the inherited role.
|
|
|
|
2. SQL generation
|
|
-----------------
|
|
|
|
See note [SQL generation for inherited roles]
|
|
|
|
3. Introspection
|
|
----------------
|
|
|
|
The columns accessible to an inherited role are explicitly set to
|
|
nullable irrespective of the nullability of the DB column to accomodate
|
|
cell value nullification.
|
|
|
|
-}
|
|
|
|
-- | This type is only used in the `combineSelectPermInfos` for
|
|
-- combining select permissions efficiently
|
|
data CombinedSelPermInfo (b :: BackendType)
|
|
= CombinedSelPermInfo
|
|
{ cspiCols :: ![(M.HashMap (Column b) (Maybe (AnnColumnCaseBoolExpPartialSQL b)))]
|
|
, cspiScalarComputedFields :: ![(M.HashMap ComputedFieldName (Maybe (AnnColumnCaseBoolExpPartialSQL b)))]
|
|
, cspiFilter :: ![(AnnBoolExpPartialSQL b)]
|
|
, cspiLimit :: !(Maybe Int)
|
|
, cspiAllowAgg :: !Bool
|
|
, cspiRequiredHeaders :: !(Set.HashSet Text)
|
|
}
|
|
|
|
-- | combineSelectPermInfos combines multiple `SelPermInfo`s
|
|
-- into one `SelPermInfo`. Two `SelPermInfo` will
|
|
-- be combined in the following manner:
|
|
--
|
|
-- 1. Columns - The `SelPermInfo` contains a hashset of the columns that are
|
|
-- accessible to the role. To combine two `SelPermInfo`s, every column of the
|
|
-- hashset is coupled with the boolean expression (filter) of the `SelPermInfo`
|
|
-- and a hash map of all the columns is created out of it, this hashmap is
|
|
-- generated for the `SelPermInfo`s that are going to be combined. These hashmaps
|
|
-- are then unioned and the values of these hashmaps are `OR`ed. When a column
|
|
-- is accessible to all the select permissions then the nullability of the column
|
|
-- is inferred from the DB column otherwise the column is explicitly marked as
|
|
-- nullable to accomodate cell-value nullification.
|
|
-- 2. Scalar computed fields - Scalar computed fields work the same as Columns (#1)
|
|
-- 3. Filter / Boolean expression - The filters are combined using a `BoolOr`
|
|
-- 4. Limit - Limits are combined by taking the minimum of the two limits
|
|
-- 5. Allow Aggregation - Aggregation is allowed, if any of the permissions allow it.
|
|
-- 6. Request Headers - Request headers are concatenated
|
|
--
|
|
-- To maintain backwards compatibility, we handle the case of single select permission
|
|
-- differently i.e. we don't want the case statements that always evaluate to true with
|
|
-- the columns
|
|
--
|
|
combineSelectPermInfos
|
|
:: forall b
|
|
. (Backend b)
|
|
=> NE.NonEmpty (SelPermInfo b)
|
|
-> SelPermInfo b
|
|
combineSelectPermInfos (headSelPermInfo NE.:| []) = headSelPermInfo
|
|
combineSelectPermInfos selPermInfos@(headSelPermInfo NE.:| restSelPermInfos) =
|
|
let CombinedSelPermInfo {..}
|
|
= foldr combine (modifySingleSelectPerm headSelPermInfo) restSelPermInfos
|
|
mergeColumnsWithBoolExp xs
|
|
| length selPermInfos == length xs = Nothing
|
|
| otherwise = foldr combineCaseBoolExps Nothing xs
|
|
in SelPermInfo (mergeColumnsWithBoolExp <$> M.unionsAll cspiCols)
|
|
(mergeColumnsWithBoolExp <$> M.unionsAll cspiScalarComputedFields)
|
|
(BoolOr cspiFilter)
|
|
cspiLimit
|
|
cspiAllowAgg
|
|
(toList cspiRequiredHeaders)
|
|
where
|
|
modifySingleSelectPerm :: SelPermInfo b -> CombinedSelPermInfo b
|
|
modifySingleSelectPerm SelPermInfo {..} =
|
|
let columnCaseBoolExp = fmap AnnColumnCaseBoolExpField spiFilter
|
|
colsWithColCaseBoolExp = spiCols $> Just columnCaseBoolExp
|
|
scalarCompFieldsWithColCaseBoolExp = spiScalarComputedFields $> Just columnCaseBoolExp
|
|
in
|
|
CombinedSelPermInfo [colsWithColCaseBoolExp]
|
|
[scalarCompFieldsWithColCaseBoolExp]
|
|
[spiFilter]
|
|
spiLimit
|
|
spiAllowAgg
|
|
(Set.fromList spiRequiredHeaders)
|
|
|
|
combine :: SelPermInfo b -> CombinedSelPermInfo b -> CombinedSelPermInfo b
|
|
combine (modifySingleSelectPerm -> lSelPermInfo) accSelPermInfo =
|
|
CombinedSelPermInfo
|
|
{ cspiCols = (cspiCols lSelPermInfo) <> (cspiCols accSelPermInfo)
|
|
, cspiScalarComputedFields =
|
|
(cspiScalarComputedFields lSelPermInfo) <> (cspiScalarComputedFields accSelPermInfo)
|
|
, cspiFilter = (cspiFilter lSelPermInfo) <> (cspiFilter accSelPermInfo)
|
|
, cspiLimit =
|
|
case (cspiLimit lSelPermInfo, cspiLimit accSelPermInfo) of
|
|
(Nothing, Nothing) -> Nothing
|
|
(Just l, Nothing) -> Just l
|
|
(Nothing, Just r) -> Just r
|
|
(Just l , Just r) -> Just $ min l r
|
|
, cspiAllowAgg = cspiAllowAgg lSelPermInfo || cspiAllowAgg accSelPermInfo
|
|
, cspiRequiredHeaders = (cspiRequiredHeaders lSelPermInfo) <> (cspiRequiredHeaders accSelPermInfo)
|
|
}
|
|
|
|
combineCaseBoolExps l r =
|
|
case (l, r) of
|
|
(Nothing, Nothing) -> Nothing
|
|
(Just caseBoolExp, Nothing) -> Just caseBoolExp
|
|
(Nothing, Just caseBoolExp) -> Just caseBoolExp
|
|
(Just caseBoolExpL, Just caseBoolExpR) -> Just $ BoolOr [caseBoolExpL, caseBoolExpR]
|
|
|
|
buildTablePermissions
|
|
:: ( ArrowChoice arr, Inc.ArrowDistribute arr, Inc.ArrowCache m arr
|
|
, MonadError QErr m, ArrowWriter (Seq CollectedInfo) arr
|
|
, HasServerConfigCtx m
|
|
, BackendMetadata b)
|
|
=> ( SourceName
|
|
, Inc.Dependency (TableCoreCache b)
|
|
, FieldInfoMap (FieldInfo b)
|
|
, TablePermissionInputs b
|
|
, InheritedRoles
|
|
) `arr` (RolePermInfoMap b)
|
|
buildTablePermissions = Inc.cache proc (source, tableCache, tableFields, tablePermissions, inheritedRoles) -> do
|
|
let alignedPermissions = alignPermissions tablePermissions
|
|
table = _tpiTable tablePermissions
|
|
experimentalFeatures <- bindA -< _sccExperimentalFeatures <$> askServerConfigCtx
|
|
nonInheritedRolePermissions <-
|
|
(| Inc.keyed (\_ (insertPermission, selectPermission, updatePermission, deletePermission) -> do
|
|
insert <- buildPermission -< (tableCache, source, table, tableFields, listToMaybe insertPermission)
|
|
select <- buildPermission -< (tableCache, source, table, tableFields, listToMaybe selectPermission)
|
|
update <- buildPermission -< (tableCache, source, table, tableFields, listToMaybe updatePermission)
|
|
delete <- buildPermission -< (tableCache, source, table, tableFields, listToMaybe deletePermission)
|
|
returnA -< RolePermInfo insert select update delete)
|
|
|) alignedPermissions
|
|
-- build permissions for inherited roles only when inherited roles is enabled
|
|
let inheritedRolesMap =
|
|
bool mempty (OMap.toHashMap inheritedRoles) $ EFInheritedRoles `elem` experimentalFeatures
|
|
-- see [Inherited roles architecture for postgres read queries]
|
|
inheritedRolePermissions <-
|
|
(| Inc.keyed (\_ (AddInheritedRole _ roleSet) -> do
|
|
let singleRoleSelectPerms =
|
|
map ((_permSel =<<) . (`M.lookup` nonInheritedRolePermissions)) $
|
|
toList roleSet
|
|
nonEmptySelPerms = NE.nonEmpty =<< sequenceA singleRoleSelectPerms
|
|
combinedSelPermInfo = combineSelectPermInfos <$> nonEmptySelPerms
|
|
returnA -< RolePermInfo Nothing combinedSelPermInfo Nothing Nothing)
|
|
|) inheritedRolesMap
|
|
returnA -< nonInheritedRolePermissions <> inheritedRolePermissions
|
|
where
|
|
mkMap :: [PermDef a] -> HashMap RoleName (PermDef a)
|
|
mkMap = mapFromL _pdRole
|
|
|
|
alignPermissions TablePermissionInputs{..} =
|
|
let insertsMap = M.map (\a -> ([a], [], [], [])) (mkMap _tpiInsert)
|
|
selectsMap = M.map (\a -> ([], [a], [], [])) (mkMap _tpiSelect)
|
|
updatesMap = M.map (\a -> ([], [], [a], [])) (mkMap _tpiUpdate)
|
|
deletesMap = M.map (\a -> ([], [], [], [a])) (mkMap _tpiDelete)
|
|
unionMap = M.unionWith (<>)
|
|
in insertsMap `unionMap` selectsMap `unionMap` updatesMap `unionMap` deletesMap
|
|
|
|
mkPermissionMetadataObject
|
|
:: forall a b. (Backend b, IsPerm b a)
|
|
=> SourceName -> TableName b -> PermDef a -> MetadataObject
|
|
mkPermissionMetadataObject source table permDef =
|
|
let permType = permAccToType (permAccessor :: PermAccessor b (PermInfo b a))
|
|
objectId = MOSourceObjId source $
|
|
SMOTableObj table $ MTOPerm (_pdRole permDef) permType
|
|
definition = toJSON $ WithTable source table permDef
|
|
in MetadataObject objectId definition
|
|
|
|
mkRemoteSchemaPermissionMetadataObject
|
|
:: AddRemoteSchemaPermissions
|
|
-> MetadataObject
|
|
mkRemoteSchemaPermissionMetadataObject (AddRemoteSchemaPermissions rsName roleName defn _) =
|
|
let objectId = MORemoteSchemaPermissions rsName roleName
|
|
in MetadataObject objectId $ toJSON defn
|
|
|
|
withPermission
|
|
:: forall a b c s arr bknd. (ArrowChoice arr, ArrowWriter (Seq CollectedInfo) arr, IsPerm bknd c, Backend bknd)
|
|
=> WriterA (Seq SchemaDependency) (ErrorA QErr arr) (a, s) b
|
|
-> arr (a, ((SourceName, TableName bknd, PermDef c), s)) (Maybe b)
|
|
withPermission f = proc (e, ((source, table, permission), s)) -> do
|
|
let metadataObject = mkPermissionMetadataObject source table permission
|
|
permType = permAccToType (permAccessor :: PermAccessor bknd (PermInfo bknd c))
|
|
roleName = _pdRole permission
|
|
schemaObject = SOSourceObj source $
|
|
SOITableObj table $ TOPerm roleName permType
|
|
addPermContext err = "in permission for role " <> roleName <<> ": " <> err
|
|
(| withRecordInconsistency (
|
|
(| withRecordDependencies (
|
|
(| modifyErrA (f -< (e, s))
|
|
|) (addTableContext table . addPermContext))
|
|
|) metadataObject schemaObject)
|
|
|) metadataObject
|
|
|
|
buildPermission
|
|
:: ( ArrowChoice arr, Inc.ArrowCache m arr
|
|
, ArrowWriter (Seq CollectedInfo) arr
|
|
, MonadError QErr m, IsPerm b a
|
|
, Inc.Cacheable a
|
|
, BackendMetadata b
|
|
)
|
|
=> ( Inc.Dependency (TableCoreCache b)
|
|
, SourceName
|
|
, TableName b
|
|
, FieldInfoMap (FieldInfo b)
|
|
, Maybe (PermDef a)
|
|
) `arr` Maybe (PermInfo b a)
|
|
buildPermission = Inc.cache proc (tableCache, source, table, tableFields, maybePermission) -> do
|
|
(| traverseA ( \permission ->
|
|
(| withPermission (do
|
|
bindErrorA -< when (_pdRole permission == adminRoleName) $
|
|
throw400 ConstraintViolation "cannot define permission for admin role"
|
|
(info, dependencies) <- liftEitherA <<< Inc.bindDepend -< runExceptT $
|
|
runTableCoreCacheRT (buildPermInfo source table tableFields permission) (source, tableCache)
|
|
tellA -< Seq.fromList dependencies
|
|
returnA -< info)
|
|
|) (source, table, permission))
|
|
|) maybePermission
|
|
>-> (\info -> join info >- returnA)
|