graphql-engine/server/src-lib/Hasura/RQL/DML/Select.hs
Karthikeyan Chinnakonda 92026b769f [Preview] Inherited roles for postgres read queries
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
2021-03-08 11:15:10 +00:00

354 lines
13 KiB
Haskell

module Hasura.RQL.DML.Select
( runSelect
)
where
import Hasura.Prelude
import qualified Data.HashMap.Strict as HM
import qualified Data.List.NonEmpty as NE
import qualified Data.Sequence as DS
import qualified Database.PG.Query as Q
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson.Types
import Data.Text.Extended
import qualified Hasura.Backends.Postgres.SQL.DML as S
import qualified Hasura.Tracing as Tracing
import Hasura.Backends.Postgres.SQL.Types hiding (TableName)
import Hasura.Backends.Postgres.Translate.Select
import Hasura.EncJSON
import Hasura.RQL.DML.Internal
import Hasura.RQL.DML.Types
import Hasura.RQL.IR.OrderBy
import Hasura.RQL.IR.Select
import Hasura.RQL.Types
import Hasura.RQL.Types.Run
import Hasura.SQL.Types
import Hasura.Session
type SelectQExt b = SelectG (ExtCol b) (BoolExp b) Int
-- Columns in RQL
-- This technically doesn't need to be generalized to all backends as
-- it is specific to this module; however the generalization work was
-- already done, and there's no particular reason to force this to be
-- specific.
data ExtCol (b :: BackendType)
= ECSimple !(Column b)
| ECRel !RelName !(Maybe RelName) !(SelectQExt b)
instance Backend b => ToJSON (ExtCol b) where
toJSON (ECSimple s) = toJSON s
toJSON (ECRel rn mrn selq) =
object $ [ "name" .= rn
, "alias" .= mrn
] ++ selectGToPairs selq
instance Backend b => FromJSON (ExtCol b) where
parseJSON v@(Object o) =
ECRel
<$> o .: "name"
<*> o .:? "alias"
<*> parseJSON v
parseJSON v@(String _) =
ECSimple <$> parseJSON v
parseJSON _ =
fail $ mconcat
[ "A column should either be a string or an "
, "object (relationship)"
]
convSelCol :: (UserInfoM m, QErrM m, TableInfoRM 'Postgres m)
=> FieldInfoMap (FieldInfo 'Postgres)
-> SelPermInfo 'Postgres
-> SelCol 'Postgres
-> m [ExtCol 'Postgres]
convSelCol _ _ (SCExtSimple cn) =
return [ECSimple cn]
convSelCol fieldInfoMap _ (SCExtRel rn malias selQ) = do
-- Point to the name key
let pgWhenRelErr = "only relationships can be expanded"
relInfo <- withPathK "name" $
askRelType fieldInfoMap rn pgWhenRelErr
let (RelInfo _ _ _ relTab _ _ _) = relInfo
(rfim, rspi) <- fetchRelDet rn relTab
resolvedSelQ <- resolveStar rfim rspi selQ
return [ECRel rn malias resolvedSelQ]
convSelCol fieldInfoMap spi (SCStar wildcard) =
convWildcard fieldInfoMap spi wildcard
convWildcard
:: (UserInfoM m, QErrM m, TableInfoRM 'Postgres m)
=> FieldInfoMap (FieldInfo 'Postgres)
-> SelPermInfo 'Postgres
-> Wildcard
-> m [ExtCol 'Postgres]
convWildcard fieldInfoMap selPermInfo wildcard =
case wildcard of
Star -> return simpleCols
(StarDot wc) -> (simpleCols ++) <$> (catMaybes <$> relExtCols wc)
where
cols = spiCols selPermInfo
pgCols = map pgiColumn $ getCols fieldInfoMap
relColInfos = getRels fieldInfoMap
simpleCols = map ECSimple $ filter (`HM.member` cols) pgCols
mkRelCol wc relInfo = do
let relName = riName relInfo
relTab = riRTable relInfo
relTabInfo <- fetchRelTabInfo relTab
mRelSelPerm <- askPermInfo' PASelect relTabInfo
forM mRelSelPerm $ \relSelPermInfo -> do
rExtCols <- convWildcard (_tciFieldInfoMap $ _tiCoreInfo relTabInfo) relSelPermInfo wc
return $ ECRel relName Nothing $
SelectG rExtCols Nothing Nothing Nothing Nothing
relExtCols wc = mapM (mkRelCol wc) relColInfos
resolveStar :: (UserInfoM m, QErrM m, TableInfoRM 'Postgres m)
=> FieldInfoMap (FieldInfo 'Postgres)
-> SelPermInfo 'Postgres
-> SelectQ 'Postgres
-> m (SelectQExt 'Postgres)
resolveStar fim selPermInfo (SelectG selCols mWh mOb mLt mOf) = do
procOverrides <- fmap (concat . catMaybes) $ withPathK "columns" $
indexedForM selCols $ \selCol -> case selCol of
(SCStar _) -> return Nothing
_ -> Just <$> convSelCol fim selPermInfo selCol
everything <- case wildcards of
[] -> return []
_ -> convWildcard fim selPermInfo $ maximum wildcards
let extCols = unionBy equals procOverrides everything
return $ SelectG extCols mWh mOb mLt mOf
where
wildcards = lefts $ map mkEither selCols
mkEither (SCStar wc) = Left wc
mkEither selCol = Right selCol
equals (ECSimple x) (ECSimple y) = x == y
equals (ECRel x _ _) (ECRel y _ _) = x == y
equals _ _ = False
convOrderByElem
:: (UserInfoM m, QErrM m, TableInfoRM 'Postgres m)
=> SessVarBldr 'Postgres m
-> (FieldInfoMap (FieldInfo 'Postgres), SelPermInfo 'Postgres)
-> OrderByCol
-> m (AnnOrderByElement 'Postgres S.SQLExp)
convOrderByElem sessVarBldr (flds, spi) = \case
OCPG fldName -> do
fldInfo <- askFieldInfo flds fldName
case fldInfo of
FIColumn colInfo -> do
checkSelOnCol spi (pgiColumn colInfo)
let ty = pgiType colInfo
if isScalarColumnWhere isGeoType ty
then throw400 UnexpectedPayload $ mconcat
[ fldName <<> " has type 'geometry'"
, " and cannot be used in order_by"
]
else return $ AOCColumn colInfo
FIRelationship _ -> throw400 UnexpectedPayload $ mconcat
[ fldName <<> " is a"
, " relationship and should be expanded"
]
FIComputedField _ -> throw400 UnexpectedPayload $ mconcat
[ fldName <<> " is a"
, " computed field and can't be used in 'order_by'"
]
-- TODO Rakesh (from master)
FIRemoteRelationship {} ->
throw400 UnexpectedPayload (mconcat [ fldName <<> " is a remote field" ])
OCRel fldName rest -> do
fldInfo <- askFieldInfo flds fldName
case fldInfo of
FIColumn _ -> throw400 UnexpectedPayload $ mconcat
[ fldName <<> " is a Postgres column"
, " and cannot be chained further"
]
FIComputedField _ -> throw400 UnexpectedPayload $ mconcat
[ fldName <<> " is a"
, " computed field and can't be used in 'order_by'"
]
FIRelationship relInfo -> do
when (riType relInfo == ArrRel) $
throw400 UnexpectedPayload $ mconcat
[ fldName <<> " is an array relationship"
," and can't be used in 'order_by'"
]
(relFim, relSelPermInfo) <- fetchRelDet (riName relInfo) (riRTable relInfo)
resolvedSelFltr <- convAnnBoolExpPartialSQL sessVarBldr $ spiFilter relSelPermInfo
AOCObjectRelation relInfo resolvedSelFltr <$>
convOrderByElem sessVarBldr (relFim, relSelPermInfo) rest
FIRemoteRelationship {} ->
throw400 UnexpectedPayload (mconcat [ fldName <<> " is a remote field" ])
convSelectQ
:: ( UserInfoM m
, QErrM m
, TableInfoRM 'Postgres m
, HasServerConfigCtx m
)
=> TableName 'Postgres
-> FieldInfoMap (FieldInfo 'Postgres) -- Table information of current table
-> SelPermInfo 'Postgres -- Additional select permission info
-> SelectQExt 'Postgres -- Given Select Query
-> SessVarBldr 'Postgres m
-> ValueParser 'Postgres m S.SQLExp
-> m (AnnSimpleSel 'Postgres)
convSelectQ table fieldInfoMap selPermInfo selQ sessVarBldr prepValBldr = do
-- Convert where clause
wClause <- forM (sqWhere selQ) $ \boolExp ->
withPathK "where" $
convBoolExp fieldInfoMap selPermInfo boolExp sessVarBldr prepValBldr
annFlds <- withPathK "columns" $
indexedForM (sqColumns selQ) $ \case
(ECSimple pgCol) -> do
(colInfo, caseBoolExpMaybe) <- convExtSimple fieldInfoMap selPermInfo pgCol
resolvedCaseBoolExp <-
traverse (convAnnColumnCaseBoolExpPartialSQL sessVarBldr) caseBoolExpMaybe
return (fromCol @'Postgres pgCol, mkAnnColumnField colInfo resolvedCaseBoolExp Nothing)
(ECRel relName mAlias relSelQ) -> do
annRel <- convExtRel fieldInfoMap relName mAlias
relSelQ sessVarBldr prepValBldr
return ( fromRel $ fromMaybe relName mAlias
, either AFObjectRelation AFArrayRelation annRel
)
annOrdByML <- forM (sqOrderBy selQ) $ \(OrderByExp obItems) ->
withPathK "order_by" $ indexedForM obItems $ mapM $
convOrderByElem sessVarBldr (fieldInfoMap, selPermInfo)
let annOrdByM = NE.nonEmpty =<< annOrdByML
-- validate limit and offset values
withPathK "limit" $ mapM_ onlyPositiveInt mQueryLimit
withPathK "offset" $ mapM_ onlyPositiveInt mQueryOffset
resolvedSelFltr <- convAnnBoolExpPartialSQL sessVarBldr $
spiFilter selPermInfo
let tabFrom = FromTable table
tabPerm = TablePerm resolvedSelFltr mPermLimit
tabArgs = SelectArgs wClause annOrdByM mQueryLimit
(S.intToSQLExp <$> mQueryOffset) Nothing
strfyNum <- stringifyNum . _sccSQLGenCtx <$> askServerConfigCtx
return $ AnnSelectG annFlds tabFrom tabPerm tabArgs strfyNum
where
mQueryOffset = sqOffset selQ
mQueryLimit = sqLimit selQ
mPermLimit = spiLimit selPermInfo
convExtSimple
:: (UserInfoM m, QErrM m)
=> FieldInfoMap (FieldInfo 'Postgres)
-> SelPermInfo 'Postgres
-> PGCol
-> m (ColumnInfo 'Postgres, Maybe (AnnColumnCaseBoolExpPartialSQL 'Postgres))
convExtSimple fieldInfoMap selPermInfo pgCol = do
checkSelOnCol selPermInfo pgCol
colInfo <- askColInfo fieldInfoMap pgCol relWhenPGErr
pure (colInfo, join $ HM.lookup pgCol (spiCols selPermInfo))
where
relWhenPGErr = "relationships have to be expanded"
convExtRel
:: ( UserInfoM m
, QErrM m
, TableInfoRM 'Postgres m
, HasServerConfigCtx m
)
=> FieldInfoMap (FieldInfo 'Postgres)
-> RelName
-> Maybe RelName
-> SelectQExt 'Postgres
-> SessVarBldr 'Postgres m
-> ValueParser 'Postgres m S.SQLExp
-> m (Either (ObjectRelationSelect 'Postgres) (ArraySelect 'Postgres))
convExtRel fieldInfoMap relName mAlias selQ sessVarBldr prepValBldr = do
-- Point to the name key
relInfo <- withPathK "name" $
askRelType fieldInfoMap relName pgWhenRelErr
let (RelInfo _ relTy colMapping relTab _ _ _) = relInfo
(relCIM, relSPI) <- fetchRelDet relName relTab
annSel <- convSelectQ relTab relCIM relSPI selQ sessVarBldr prepValBldr
case relTy of
ObjRel -> do
when misused $ throw400 UnexpectedPayload objRelMisuseMsg
return $ Left $ AnnRelationSelectG (fromMaybe relName mAlias) colMapping $
AnnObjectSelectG (_asnFields annSel) relTab $ _tpFilter $ _asnPerm annSel
ArrRel ->
return $ Right $ ASSimple $ AnnRelationSelectG (fromMaybe relName mAlias)
colMapping annSel
where
pgWhenRelErr = "only relationships can be expanded"
misused =
or [ isJust (sqWhere selQ)
, isJust (sqLimit selQ)
, isJust (sqOffset selQ)
, isJust (sqOrderBy selQ)
]
objRelMisuseMsg =
mconcat [ "when selecting an 'obj_relationship' "
, "'where', 'order_by', 'limit' and 'offset' "
, " can't be used"
]
convSelectQuery
:: ( UserInfoM m
, QErrM m
, TableInfoRM 'Postgres m
, HasServerConfigCtx m
)
=> SessVarBldr 'Postgres m
-> ValueParser 'Postgres m S.SQLExp
-- -> (ColumnType 'Postgres -> Value -> m S.SQLExp)
-> SelectQuery
-> m (AnnSimpleSel 'Postgres)
convSelectQuery sessVarBldr prepArgBuilder (DMLQuery _ qt selQ) = do
tabInfo <- withPathK "table" $ askTabInfoSource qt
selPermInfo <- askSelPermInfo tabInfo
let fieldInfo = _tciFieldInfoMap $ _tiCoreInfo tabInfo
extSelQ <- resolveStar fieldInfo selPermInfo selQ
validateHeaders $ spiRequiredHeaders selPermInfo
convSelectQ qt fieldInfo selPermInfo extSelQ sessVarBldr prepArgBuilder
selectP2 :: JsonAggSelect -> (AnnSimpleSel 'Postgres, DS.Seq Q.PrepArg) -> Q.TxE QErr EncJSON
selectP2 jsonAggSelect (sel, p) =
encJFromBS . runIdentity . Q.getRow
<$> Q.rawQE dmlTxErrorHandler (Q.fromBuilder selectSQL) (toList p) True
where
selectSQL = toSQL $ mkSQLSelect jsonAggSelect sel
phaseOne
:: (QErrM m, UserInfoM m, CacheRM m, HasServerConfigCtx m)
=> SelectQuery -> m (AnnSimpleSel 'Postgres, DS.Seq Q.PrepArg)
phaseOne query = do
let sourceName = getSourceDMLQuery query
tableCache :: TableCache 'Postgres <- askTableCache sourceName
flip runTableCacheRT (sourceName, tableCache) $ runDMLP1T $
convSelectQuery sessVarFromCurrentSetting (valueParserWithCollectableType binRHSBuilder) query
phaseTwo :: (MonadTx m) => (AnnSimpleSel 'Postgres, DS.Seq Q.PrepArg) -> m EncJSON
phaseTwo =
liftTx . selectP2 JASMultipleRows
runSelect
:: ( QErrM m, UserInfoM m, CacheRM m
, HasServerConfigCtx m, MonadIO m, MonadBaseControl IO m
, Tracing.MonadTrace m, MetadataM m
)
=> SelectQuery -> m EncJSON
runSelect q = do
sourceConfig <- askSourceConfig (getSourceDMLQuery q)
phaseOne q >>= runQueryLazyTx (_pscExecCtx sourceConfig) Q.ReadOnly . phaseTwo