2020-10-22 23:42:27 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
2021-03-25 20:50:08 +03:00
|
|
|
|
2020-11-02 14:50:40 +03:00
|
|
|
module Hasura.RQL.IR.BoolExp
|
2021-09-24 01:56:37 +03:00
|
|
|
( BoolExp (..),
|
|
|
|
ColExp (..),
|
|
|
|
GBoolExp (..),
|
|
|
|
gBoolExpTrue,
|
|
|
|
GExists (..),
|
|
|
|
geWhere,
|
|
|
|
geTable,
|
|
|
|
_BoolExists,
|
|
|
|
DWithinGeomOp (..),
|
|
|
|
DWithinGeogOp (..),
|
|
|
|
CastExp,
|
|
|
|
OpExpG (..),
|
|
|
|
opExpDepCol,
|
|
|
|
STIntersectsNbandGeommin (..),
|
|
|
|
STIntersectsGeomminNband (..),
|
|
|
|
SessionArgumentPresence (..),
|
|
|
|
mkSessionArgumentPresence,
|
|
|
|
ComputedFieldBoolExp (..),
|
|
|
|
AnnComputedFieldBoolExp (..),
|
|
|
|
AnnBoolExpFld (..),
|
|
|
|
AnnBoolExp,
|
|
|
|
AnnColumnCaseBoolExpPartialSQL,
|
|
|
|
AnnColumnCaseBoolExp,
|
|
|
|
AnnColumnCaseBoolExpField (..),
|
|
|
|
annBoolExpTrue,
|
|
|
|
andAnnBoolExps,
|
|
|
|
AnnBoolExpFldSQL,
|
|
|
|
AnnBoolExpSQL,
|
|
|
|
PartialSQLExp (..),
|
|
|
|
isStaticValue,
|
|
|
|
hasStaticExp,
|
|
|
|
AnnBoolExpPartialSQL,
|
|
|
|
PreSetColsG,
|
|
|
|
PreSetColsPartial,
|
2021-10-18 12:16:38 +03:00
|
|
|
RootOrCurrentColumn (..),
|
|
|
|
RootOrCurrent (..),
|
2021-09-24 01:56:37 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Lens.Plated
|
|
|
|
import Control.Lens.TH
|
|
|
|
import Data.Aeson.Extended
|
|
|
|
import Data.Aeson.Internal
|
|
|
|
import Data.Aeson.TH
|
|
|
|
import Data.HashMap.Strict qualified as M
|
|
|
|
import Data.Monoid
|
|
|
|
import Data.Text.Extended
|
|
|
|
import Hasura.Incremental (Cacheable)
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
import Hasura.RQL.Types.Column
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
import Hasura.RQL.Types.ComputedField
|
2021-12-01 07:53:34 +03:00
|
|
|
import Hasura.RQL.Types.Relationships.Local
|
2021-09-24 01:56:37 +03:00
|
|
|
import Hasura.SQL.Backend
|
|
|
|
import Hasura.Session
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
----------------------------------------------------------------------------------------------------
|
|
|
|
-- Boolean structure
|
|
|
|
|
|
|
|
-- | This type represents a hierarchical boolean expression. It is parametric over the actual
|
|
|
|
-- implementation of the actual boolean term values. It nonetheless leaks some information:
|
|
|
|
-- "exists" is only used in permissions, to add conditions based on another table.
|
|
|
|
data GBoolExp (b :: BackendType) a
|
2021-09-24 01:56:37 +03:00
|
|
|
= BoolAnd ![GBoolExp b a]
|
|
|
|
| BoolOr ![GBoolExp b a]
|
|
|
|
| BoolNot !(GBoolExp b a)
|
|
|
|
| BoolExists !(GExists b a)
|
|
|
|
| BoolFld !a
|
2021-03-25 20:50:08 +03:00
|
|
|
deriving (Show, Eq, Functor, Foldable, Traversable, Data, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, NFData a) => NFData (GBoolExp b a)
|
|
|
|
|
|
|
|
instance (Backend b, Data a) => Plated (GBoolExp b a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, Cacheable a) => Cacheable (GBoolExp b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable a) => Hashable (GBoolExp b a)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
instance (Backend b, FromJSONKeyValue a) => FromJSON (GBoolExp b a) where
|
|
|
|
parseJSON = withObject "boolean expression" \o ->
|
|
|
|
BoolAnd <$> forM (M.toList o) \(k, v) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
if
|
|
|
|
| k == "$or" -> BoolOr <$> parseJSON v <?> Key k
|
|
|
|
| k == "_or" -> BoolOr <$> parseJSON v <?> Key k
|
|
|
|
| k == "$and" -> BoolAnd <$> parseJSON v <?> Key k
|
|
|
|
| k == "_and" -> BoolAnd <$> parseJSON v <?> Key k
|
|
|
|
| k == "$not" -> BoolNot <$> parseJSON v <?> Key k
|
|
|
|
| k == "_not" -> BoolNot <$> parseJSON v <?> Key k
|
|
|
|
| k == "$exists" -> BoolExists <$> parseJSON v <?> Key k
|
|
|
|
| k == "_exists" -> BoolExists <$> parseJSON v <?> Key k
|
|
|
|
| otherwise -> BoolFld <$> parseJSONKeyValue (k, v)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
instance (Backend b, ToJSONKeyValue a) => ToJSON (GBoolExp b a) where
|
|
|
|
toJSON be = case be of
|
|
|
|
-- special encoding for _and
|
|
|
|
BoolAnd bExps ->
|
|
|
|
let m = M.fromList $ map getKV bExps
|
2021-09-24 01:56:37 +03:00
|
|
|
in -- if the keys aren't repeated, then object encoding can be used
|
|
|
|
if length m == length bExps
|
|
|
|
then toJSON m
|
|
|
|
else object $ pure kv
|
2021-03-25 20:50:08 +03:00
|
|
|
_ -> object $ pure kv
|
|
|
|
where
|
|
|
|
kv = getKV be
|
|
|
|
getKV = \case
|
2021-09-24 01:56:37 +03:00
|
|
|
BoolAnd bExps -> "_and" .= map toJSON bExps
|
|
|
|
BoolOr bExps -> "_or" .= map toJSON bExps
|
|
|
|
BoolNot bExp -> "_not" .= toJSON bExp
|
2021-03-25 20:50:08 +03:00
|
|
|
BoolExists bExists -> "_exists" .= toJSON bExists
|
2021-09-24 01:56:37 +03:00
|
|
|
BoolFld a -> toJSONKeyValue a
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
gBoolExpTrue :: GBoolExp b a
|
|
|
|
gBoolExpTrue = BoolAnd []
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | Represents a condition on an aribtrary table. Used as part of our permissions boolean
|
|
|
|
-- expressions. See our documentation for more information:
|
|
|
|
-- https://hasura.io/docs/latest/graphql/core/auth/authorization/permission-rules.html#using-unrelated-tables-views
|
2021-09-24 01:56:37 +03:00
|
|
|
data GExists (b :: BackendType) a = GExists
|
|
|
|
{ _geTable :: !(TableName b),
|
|
|
|
_geWhere :: !(GBoolExp b a)
|
|
|
|
}
|
|
|
|
deriving (Functor, Foldable, Traversable, Generic)
|
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
deriving instance (Backend b, Show a) => Show (GExists b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
deriving instance (Backend b, Eq a) => Eq (GExists b a)
|
|
|
|
|
2021-07-27 16:51:30 +03:00
|
|
|
deriving instance (Backend b, Data a) => Data (GExists b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, NFData a) => NFData (GExists b a)
|
|
|
|
|
|
|
|
instance (Backend b, Data a) => Plated (GExists b a)
|
|
|
|
|
2020-11-12 12:25:48 +03:00
|
|
|
instance (Backend b, Cacheable a) => Cacheable (GExists b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable a) => Hashable (GExists b a)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
instance (Backend b, FromJSONKeyValue a) => FromJSON (GExists b a) where
|
|
|
|
parseJSON = withObject "_exists" \o -> do
|
2019-09-05 10:34:53 +03:00
|
|
|
qt <- o .: "_table"
|
|
|
|
wh <- o .: "_where"
|
2021-03-25 20:50:08 +03:00
|
|
|
pure $ GExists qt wh
|
2019-09-05 10:34:53 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, ToJSONKeyValue a) => ToJSON (GExists b a) where
|
|
|
|
toJSON (GExists gTable gWhere) =
|
2021-09-24 01:56:37 +03:00
|
|
|
object
|
|
|
|
[ "_table" .= gTable,
|
|
|
|
"_where" .= gWhere
|
|
|
|
]
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
makeLenses ''GExists
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
----------------------------------------------------------------------------------------------------
|
|
|
|
-- Boolean expressions in permissions
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | We don't allow conditions across relationships in permissions: the type we use as the terms in
|
|
|
|
-- GBoolExp is this one, ColExp, which only contains a FieldName and a JSON Value.
|
2021-09-24 01:56:37 +03:00
|
|
|
data ColExp = ColExp
|
|
|
|
{ ceCol :: !FieldName,
|
|
|
|
ceVal :: !Value
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Data, Generic)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance NFData ColExp
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance Cacheable ColExp
|
|
|
|
|
|
|
|
instance FromJSONKeyValue ColExp where
|
|
|
|
parseJSONKeyValue (k, v) = ColExp (FieldName k) <$> parseJSON v
|
|
|
|
|
|
|
|
instance ToJSONKeyValue ColExp where
|
|
|
|
toJSONKeyValue (ColExp k v) = (getFieldNameTxt k, v)
|
|
|
|
|
|
|
|
-- | This @BoolExp@ type is a simple alias for the boolean expressions used in permissions, that
|
|
|
|
-- uses 'ColExp' as the term in GBoolExp.
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype BoolExp (b :: BackendType) = BoolExp {unBoolExp :: GBoolExp b ColExp}
|
2021-03-25 20:50:08 +03:00
|
|
|
deriving newtype (Show, Eq, Generic, NFData, Cacheable, ToJSON, FromJSON)
|
2020-11-12 12:25:48 +03:00
|
|
|
|
|
|
|
$(makeWrapped ''BoolExp)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
makePrisms ''GBoolExp
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | Permissions get translated into boolean expressions that are threaded throuhgout the
|
|
|
|
-- parsers. For the leaf values of those permissions, we use this type, which references but doesn't
|
|
|
|
-- inline the session variables.
|
|
|
|
data PartialSQLExp (b :: BackendType)
|
|
|
|
= PSESessVar !(SessionVarType b) !SessionVariable
|
2021-07-28 11:09:32 +03:00
|
|
|
| PSESession
|
2021-03-25 20:50:08 +03:00
|
|
|
| PSESQLExp !(SQLExpression b)
|
|
|
|
deriving (Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-07-27 16:51:30 +03:00
|
|
|
deriving instance (Backend b) => Eq (PartialSQLExp b)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2022-01-11 16:36:02 +03:00
|
|
|
deriving instance (Backend b) => Show (PartialSQLExp b)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
instance (Backend b, NFData (BooleanOperators b (PartialSQLExp b))) => NFData (PartialSQLExp b)
|
|
|
|
|
|
|
|
instance (Backend b, Hashable (BooleanOperators b (PartialSQLExp b))) => Hashable (PartialSQLExp b)
|
|
|
|
|
2021-08-09 13:20:04 +03:00
|
|
|
instance (Backend b, Cacheable (BooleanOperators b (PartialSQLExp b))) => Cacheable (PartialSQLExp b)
|
2020-11-12 12:25:48 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance Backend b => ToJSON (PartialSQLExp b) where
|
|
|
|
toJSON = \case
|
|
|
|
PSESessVar colTy sessVar -> toJSON (colTy, sessVar)
|
2021-09-24 01:56:37 +03:00
|
|
|
PSESession -> String "hasura_session"
|
|
|
|
PSESQLExp e -> toJSON e
|
2019-03-25 15:29:52 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
isStaticValue :: PartialSQLExp backend -> Bool
|
|
|
|
isStaticValue = \case
|
|
|
|
PSESessVar _ _ -> False
|
2021-09-24 01:56:37 +03:00
|
|
|
PSESession -> False
|
|
|
|
PSESQLExp _ -> True
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
hasStaticExp :: Backend b => OpExpG b (PartialSQLExp b) -> Bool
|
|
|
|
hasStaticExp = getAny . foldMap (Any . isStaticValue)
|
2019-01-28 20:46:31 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
----------------------------------------------------------------------------------------------------
|
|
|
|
-- Boolean expressions in the schema
|
|
|
|
|
|
|
|
-- | Operand for cast operator
|
2020-10-22 23:42:27 +03:00
|
|
|
type CastExp b a = M.HashMap (ScalarType b) [OpExpG b a]
|
2019-07-15 11:52:45 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | This type represents the boolean operators that can be applied on values of a column. This type
|
|
|
|
-- only contains the common core, that we expect to be ultimately entirely supported in most if not
|
|
|
|
-- all backends. Backends can extend this with the @BooleanOperators@ type in @Backend@.
|
2020-11-12 12:25:48 +03:00
|
|
|
data OpExpG (b :: BackendType) a
|
2020-10-22 23:42:27 +03:00
|
|
|
= ACast !(CastExp b a)
|
2019-07-15 11:52:45 +03:00
|
|
|
| AEQ !Bool !a
|
2019-01-24 21:34:44 +03:00
|
|
|
| ANE !Bool !a
|
2021-09-24 01:56:37 +03:00
|
|
|
| AIN !a
|
2019-07-10 13:19:58 +03:00
|
|
|
| ANIN !a
|
2021-09-24 01:56:37 +03:00
|
|
|
| AGT !a
|
|
|
|
| ALT !a
|
2018-11-16 15:40:23 +03:00
|
|
|
| AGTE !a
|
|
|
|
| ALTE !a
|
2021-09-24 01:56:37 +03:00
|
|
|
| ALIKE !a -- LIKE
|
2018-11-16 15:40:23 +03:00
|
|
|
| ANLIKE !a -- NOT LIKE
|
2021-10-18 12:16:38 +03:00
|
|
|
| CEQ (RootOrCurrentColumn b)
|
|
|
|
| CNE (RootOrCurrentColumn b)
|
|
|
|
| CGT (RootOrCurrentColumn b)
|
|
|
|
| CLT (RootOrCurrentColumn b)
|
|
|
|
| CGTE (RootOrCurrentColumn b)
|
|
|
|
| CLTE (RootOrCurrentColumn b)
|
2021-09-24 01:56:37 +03:00
|
|
|
| ANISNULL -- IS NULL
|
2021-03-25 20:50:08 +03:00
|
|
|
| ANISNOTNULL -- IS NOT NULL
|
|
|
|
| ABackendSpecific !(BooleanOperators b a)
|
|
|
|
deriving (Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-10-18 12:16:38 +03:00
|
|
|
data RootOrCurrentColumn b = RootOrCurrentColumn RootOrCurrent (Column b)
|
|
|
|
deriving (Generic)
|
|
|
|
|
|
|
|
deriving instance Backend b => Show (RootOrCurrentColumn b)
|
|
|
|
|
|
|
|
deriving instance Backend b => Eq (RootOrCurrentColumn b)
|
|
|
|
|
|
|
|
instance Backend b => NFData (RootOrCurrentColumn b)
|
|
|
|
|
|
|
|
instance Backend b => Cacheable (RootOrCurrentColumn b)
|
|
|
|
|
|
|
|
instance Backend b => Hashable (RootOrCurrentColumn b)
|
|
|
|
|
|
|
|
instance Backend b => ToJSON (RootOrCurrentColumn b)
|
|
|
|
|
|
|
|
-- | The arguments of column-operators may refer to either the so-called 'root
|
|
|
|
-- tabular value' or 'current tabular value'.
|
|
|
|
data RootOrCurrent = IsRoot | IsCurrent
|
|
|
|
deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
instance NFData RootOrCurrent
|
|
|
|
|
|
|
|
instance Cacheable RootOrCurrent
|
|
|
|
|
|
|
|
instance Hashable RootOrCurrent
|
|
|
|
|
|
|
|
instance ToJSON RootOrCurrent
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
deriving instance (Backend b) => Functor (OpExpG b)
|
|
|
|
|
|
|
|
deriving instance (Backend b) => Foldable (OpExpG b)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
deriving instance (Backend b) => Traversable (OpExpG b)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
deriving instance (Backend b, Show (BooleanOperators b a), Show a) => Show (OpExpG b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
deriving instance (Backend b, Eq (BooleanOperators b a), Eq a) => Eq (OpExpG b a)
|
|
|
|
|
|
|
|
instance (Backend b, NFData (BooleanOperators b a), NFData a) => NFData (OpExpG b a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, Cacheable (BooleanOperators b a), Cacheable a) => Cacheable (OpExpG b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable (OpExpG b a)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
instance (Backend b, ToJSONKeyValue (BooleanOperators b a), ToJSON a) => ToJSONKeyValue (OpExpG b a) where
|
|
|
|
toJSONKeyValue = \case
|
2021-09-24 01:56:37 +03:00
|
|
|
ACast a -> ("_cast", toJSON $ object . map toJSONKeyValue <$> a)
|
|
|
|
AEQ _ a -> ("_eq", toJSON a)
|
|
|
|
ANE _ a -> ("_ne", toJSON a)
|
|
|
|
AIN a -> ("_in", toJSON a)
|
|
|
|
ANIN a -> ("_nin", toJSON a)
|
|
|
|
AGT a -> ("_gt", toJSON a)
|
|
|
|
ALT a -> ("_lt", toJSON a)
|
|
|
|
AGTE a -> ("_gte", toJSON a)
|
|
|
|
ALTE a -> ("_lte", toJSON a)
|
|
|
|
ALIKE a -> ("_like", toJSON a)
|
|
|
|
ANLIKE a -> ("_nlike", toJSON a)
|
|
|
|
CEQ a -> ("_ceq", toJSON a)
|
|
|
|
CNE a -> ("_cne", toJSON a)
|
|
|
|
CGT a -> ("_cgt", toJSON a)
|
|
|
|
CLT a -> ("_clt", toJSON a)
|
|
|
|
CGTE a -> ("_cgte", toJSON a)
|
|
|
|
CLTE a -> ("_clte", toJSON a)
|
|
|
|
ANISNULL -> ("_is_null", toJSON True)
|
|
|
|
ANISNOTNULL -> ("_is_null", toJSON False)
|
2021-03-25 20:50:08 +03:00
|
|
|
ABackendSpecific b -> toJSONKeyValue b
|
2020-11-25 17:18:58 +03:00
|
|
|
|
2021-10-18 12:16:38 +03:00
|
|
|
opExpDepCol :: OpExpG backend a -> Maybe (RootOrCurrentColumn backend)
|
2019-04-24 13:28:10 +03:00
|
|
|
opExpDepCol = \case
|
2021-09-24 01:56:37 +03:00
|
|
|
CEQ c -> Just c
|
|
|
|
CNE c -> Just c
|
|
|
|
CGT c -> Just c
|
|
|
|
CLT c -> Just c
|
2019-04-24 13:28:10 +03:00
|
|
|
CGTE c -> Just c
|
|
|
|
CLTE c -> Just c
|
2021-09-24 01:56:37 +03:00
|
|
|
_ -> Nothing
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
-- | The presence of session argument in the SQL function of a computed field.
|
2021-07-28 11:09:32 +03:00
|
|
|
-- Since we only support computed fields with SQL functions having maximum of 2 arguments in boolean expression,
|
|
|
|
-- the position (if present) is either first or second. The other mandatory argument is table row input.
|
2021-07-07 14:58:37 +03:00
|
|
|
data SessionArgumentPresence a
|
|
|
|
= SAPNotPresent
|
|
|
|
| SAPFirst a
|
|
|
|
| SAPSecond a
|
|
|
|
deriving (Show, Eq, Functor, Foldable, Traversable, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
instance (NFData a) => NFData (SessionArgumentPresence a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
instance (Cacheable a) => Cacheable (SessionArgumentPresence a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
instance (Hashable a) => Hashable (SessionArgumentPresence a)
|
|
|
|
|
2021-07-28 11:09:32 +03:00
|
|
|
-- | Determine the position of session argument
|
|
|
|
mkSessionArgumentPresence :: forall v a. v -> Maybe a -> FunctionTableArgument -> SessionArgumentPresence v
|
|
|
|
mkSessionArgumentPresence sessionValue = \case
|
|
|
|
Nothing -> const $ SAPNotPresent
|
|
|
|
Just _ -> \case
|
|
|
|
-- If table argument is first, then session argument will be second
|
2021-09-24 01:56:37 +03:00
|
|
|
FTAFirst -> SAPSecond sessionValue
|
2021-07-28 11:09:32 +03:00
|
|
|
-- Argument index 0 implies it is first
|
|
|
|
FTANamed _ 0 -> SAPSecond sessionValue
|
2021-09-24 01:56:37 +03:00
|
|
|
-- If table argument is second, then session argument will be first
|
|
|
|
FTANamed {} -> SAPFirst sessionValue
|
2021-07-28 11:09:32 +03:00
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
-- | This type is used to represent the kinds of boolean expression used for compouted fields
|
|
|
|
-- based on the return type of the SQL function
|
|
|
|
data ComputedFieldBoolExp (b :: BackendType) a
|
|
|
|
= CFBEScalar ![OpExpG b a] -- SQL function returning a scalar
|
|
|
|
| CFBETable !(TableName b) !(AnnBoolExp b a) -- SQL function returning SET OF table
|
|
|
|
deriving (Functor, Foldable, Traversable, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
deriving instance (Backend b, Eq (BooleanOperators b a), Eq a) => Eq (ComputedFieldBoolExp b a)
|
|
|
|
|
2021-09-22 13:43:05 +03:00
|
|
|
deriving instance (Backend b, Show (BooleanOperators b a), Show a) => Show (ComputedFieldBoolExp b a)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
instance (Backend b, NFData (BooleanOperators b a), NFData a) => NFData (ComputedFieldBoolExp b a)
|
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
instance (Backend b, Cacheable (BooleanOperators b a), Cacheable a) => Cacheable (ComputedFieldBoolExp b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable (ComputedFieldBoolExp b a)
|
2021-07-07 14:58:37 +03:00
|
|
|
|
|
|
|
-- | Using a computed field in boolean expression.
|
|
|
|
-- Example: A computed field "full_name" ("first_name" || "last_name") is defined to the "user"
|
|
|
|
-- table. Boolean expression to filter whose "full_name" is LIKE "%bob%"
|
|
|
|
-- query {
|
|
|
|
-- user(where: {full_name: {_like: "%bob%"}}){
|
|
|
|
-- id
|
|
|
|
-- first_name
|
|
|
|
-- last_name
|
|
|
|
-- full_name
|
|
|
|
-- }
|
|
|
|
-- }
|
|
|
|
-- Limitation: Computed field whose function with no input arguments are allowed in boolean
|
|
|
|
-- expression. It is complex to generate schema for `where` clause with functions having
|
|
|
|
-- input arguments.
|
2021-09-24 01:56:37 +03:00
|
|
|
data AnnComputedFieldBoolExp (b :: BackendType) a = AnnComputedFieldBoolExp
|
|
|
|
{ _acfbXFieldInfo :: !(XComputedField b),
|
|
|
|
_acfbName :: !ComputedFieldName,
|
|
|
|
_acfbFunction :: !(FunctionName b),
|
|
|
|
_acfbSessionArgumentPresence :: !(SessionArgumentPresence a),
|
|
|
|
_acfbBoolExp :: !(ComputedFieldBoolExp b a)
|
|
|
|
}
|
|
|
|
deriving (Functor, Foldable, Traversable, Generic)
|
|
|
|
|
|
|
|
deriving instance (Backend b, Eq (BooleanOperators b a), Eq a) => Eq (AnnComputedFieldBoolExp b a)
|
|
|
|
|
2021-09-22 13:43:05 +03:00
|
|
|
deriving instance (Backend b, Show (BooleanOperators b a), Show a) => Show (AnnComputedFieldBoolExp b a)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
instance (Backend b, NFData (BooleanOperators b a), NFData a) => NFData (AnnComputedFieldBoolExp b a)
|
|
|
|
|
2021-07-07 14:58:37 +03:00
|
|
|
instance (Backend b, Cacheable (BooleanOperators b a), Cacheable a) => Cacheable (AnnComputedFieldBoolExp b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable (AnnComputedFieldBoolExp b a)
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | This type is used for boolean terms in GBoolExp in the schema; there are two kinds boolean
|
|
|
|
-- terms:
|
|
|
|
-- - operators on a column of the current table, using the 'OpExpG' kind of operators
|
|
|
|
-- - arbitrary expressions on columns of tables in relationships (in the same source)
|
|
|
|
--
|
|
|
|
-- This type is parametric over the type of leaf values, the values on which we operate.
|
2020-11-12 12:25:48 +03:00
|
|
|
data AnnBoolExpFld (b :: BackendType) a
|
2021-07-07 14:58:37 +03:00
|
|
|
= AVColumn !(ColumnInfo b) ![OpExpG b a]
|
|
|
|
| AVRelationship !(RelInfo b) !(AnnBoolExp b a)
|
|
|
|
| AVComputedField !(AnnComputedFieldBoolExp b a)
|
2020-10-22 23:42:27 +03:00
|
|
|
deriving (Functor, Foldable, Traversable, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
deriving instance (Backend b, Eq (BooleanOperators b a), Eq a) => Eq (AnnBoolExpFld b a)
|
|
|
|
|
2021-09-22 13:43:05 +03:00
|
|
|
deriving instance (Backend b, Show (BooleanOperators b a), Show a) => Show (AnnBoolExpFld b a)
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
instance (Backend b, NFData (BooleanOperators b a), NFData a) => NFData (AnnBoolExpFld b a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, Cacheable (BooleanOperators b a), Cacheable a) => Cacheable (AnnBoolExpFld b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable (AnnBoolExpFld b a)
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, ToJSONKeyValue (BooleanOperators b a), ToJSON a) => ToJSONKeyValue (AnnBoolExpFld b a) where
|
|
|
|
toJSONKeyValue = \case
|
2021-07-07 14:58:37 +03:00
|
|
|
AVColumn pci opExps ->
|
2021-09-24 01:56:37 +03:00
|
|
|
( toTxt $ pgiColumn pci,
|
|
|
|
toJSON (pci, object . pure . toJSONKeyValue <$> opExps)
|
2021-03-25 20:50:08 +03:00
|
|
|
)
|
2021-07-07 14:58:37 +03:00
|
|
|
AVRelationship ri relBoolExp ->
|
2021-09-24 01:56:37 +03:00
|
|
|
( relNameToTxt $ riName ri,
|
|
|
|
toJSON (ri, toJSON relBoolExp)
|
2021-03-25 20:50:08 +03:00
|
|
|
)
|
2021-07-07 14:58:37 +03:00
|
|
|
AVComputedField cfBoolExp ->
|
2021-09-24 01:56:37 +03:00
|
|
|
( toTxt $ _acfbName cfBoolExp,
|
|
|
|
let function = _acfbFunction cfBoolExp
|
|
|
|
in case _acfbBoolExp cfBoolExp of
|
|
|
|
CFBEScalar opExps -> toJSON (function, object . pure . toJSONKeyValue <$> opExps)
|
|
|
|
CFBETable _ boolExp -> toJSON (function, toJSON boolExp)
|
2021-07-07 14:58:37 +03:00
|
|
|
)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
-- | A simple alias for the kind of boolean expressions used in the schema, that ties together
|
|
|
|
-- 'GBoolExp', 'OpExpG', and 'AnnBoolExpFld'.
|
|
|
|
type AnnBoolExp b a = GBoolExp b (AnnBoolExpFld b a)
|
[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 14:14:13 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- Type aliases for common use cases:
|
2021-09-24 01:56:37 +03:00
|
|
|
type AnnBoolExpFldSQL b = AnnBoolExpFld b (SQLExpression b)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
type AnnBoolExpSQL b = AnnBoolExp b (SQLExpression b)
|
|
|
|
|
|
|
|
type AnnBoolExpPartialSQL b = AnnBoolExp b (PartialSQLExp b)
|
2021-03-25 20:50:08 +03:00
|
|
|
|
|
|
|
annBoolExpTrue :: AnnBoolExp backend a
|
|
|
|
annBoolExpTrue = gBoolExpTrue
|
|
|
|
|
|
|
|
andAnnBoolExps :: AnnBoolExp backend a -> AnnBoolExp backend a -> AnnBoolExp backend a
|
2021-07-08 18:41:59 +03:00
|
|
|
andAnnBoolExps l r = BoolAnd [l, r]
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
----------------------------------------------------------------------------------------------------
|
|
|
|
-- Operands for specific operators
|
[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 14:14:13 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- Arguably, most of those should be moved elsewhere, since not all of the corresponding operators
|
|
|
|
-- are part of the common core of operators.
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | Operand for STDWithin opoerator
|
2021-09-24 01:56:37 +03:00
|
|
|
data DWithinGeomOp a = DWithinGeomOp
|
|
|
|
{ dwgeomDistance :: !a,
|
|
|
|
dwgeomFrom :: !a
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Functor, Foldable, Traversable, Generic, Data)
|
|
|
|
|
|
|
|
instance (NFData a) => NFData (DWithinGeomOp a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Cacheable a) => Cacheable (DWithinGeomOp a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Hashable a) => Hashable (DWithinGeomOp a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
$(deriveJSON hasuraJSON ''DWithinGeomOp)
|
|
|
|
|
|
|
|
-- | Operand for STDWithin opoerator
|
2021-09-24 01:56:37 +03:00
|
|
|
data DWithinGeogOp a = DWithinGeogOp
|
|
|
|
{ dwgeogDistance :: !a,
|
|
|
|
dwgeogFrom :: !a,
|
|
|
|
dwgeogUseSpheroid :: !a
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Functor, Foldable, Traversable, Generic, Data)
|
|
|
|
|
|
|
|
instance (NFData a) => NFData (DWithinGeogOp a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Cacheable a) => Cacheable (DWithinGeogOp a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Hashable a) => Hashable (DWithinGeogOp a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
$(deriveJSON hasuraJSON ''DWithinGeogOp)
|
|
|
|
|
|
|
|
-- | Operand for STIntersect
|
2021-09-24 01:56:37 +03:00
|
|
|
data STIntersectsNbandGeommin a = STIntersectsNbandGeommin
|
|
|
|
{ singNband :: !a,
|
|
|
|
singGeommin :: !a
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Functor, Foldable, Traversable, Generic, Data)
|
|
|
|
|
|
|
|
instance (NFData a) => NFData (STIntersectsNbandGeommin a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Cacheable a) => Cacheable (STIntersectsNbandGeommin a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Hashable a) => Hashable (STIntersectsNbandGeommin a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
$(deriveJSON hasuraJSON ''STIntersectsNbandGeommin)
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | Operand for STIntersect
|
2021-09-24 01:56:37 +03:00
|
|
|
data STIntersectsGeomminNband a = STIntersectsGeomminNband
|
|
|
|
{ signGeommin :: !a,
|
|
|
|
signNband :: !(Maybe a)
|
|
|
|
}
|
|
|
|
deriving (Show, Eq, Functor, Foldable, Traversable, Generic, Data)
|
|
|
|
|
|
|
|
instance (NFData a) => NFData (STIntersectsGeomminNband a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Cacheable a) => Cacheable (STIntersectsGeomminNband a)
|
2019-07-10 13:19:58 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
instance (Hashable a) => Hashable (STIntersectsGeomminNband a)
|
2019-04-17 12:48:41 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
$(deriveJSON hasuraJSON ''STIntersectsGeomminNband)
|
[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 14:14:13 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
----------------------------------------------------------------------------------------------------
|
|
|
|
-- Miscellaneous
|
2019-04-17 12:48:41 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | This is a simple newtype over AnnBoolExpFld. At time of writing, I do not know why we want
|
|
|
|
-- this, and why it exists. It might be a relic of a needed differentiation, now lost?
|
|
|
|
-- TODO: can this be removed?
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype AnnColumnCaseBoolExpField (b :: BackendType) a = AnnColumnCaseBoolExpField {_accColCaseBoolExpField :: AnnBoolExpFld b a}
|
2021-03-25 20:50:08 +03:00
|
|
|
deriving (Functor, Foldable, Traversable, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
deriving instance (Backend b, Eq (BooleanOperators b a), Eq a) => Eq (AnnColumnCaseBoolExpField b a)
|
|
|
|
|
2021-09-22 13:43:05 +03:00
|
|
|
deriving instance (Backend b, Show (BooleanOperators b a), Show a) => Show (AnnColumnCaseBoolExpField b a)
|
2021-05-21 05:46:58 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
instance (Backend b, NFData (BooleanOperators b a), NFData a) => NFData (AnnColumnCaseBoolExpField b a)
|
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, Cacheable (BooleanOperators b a), Cacheable a) => Cacheable (AnnColumnCaseBoolExpField b a)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
|
|
|
instance (Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable (AnnColumnCaseBoolExpField b a)
|
2019-04-17 12:48:41 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
instance (Backend b, ToJSONKeyValue (BooleanOperators b a), ToJSON a) => ToJSONKeyValue (AnnColumnCaseBoolExpField b a) where
|
|
|
|
toJSONKeyValue = toJSONKeyValue . _accColCaseBoolExpField
|
2018-11-16 15:40:23 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
-- | Similar to AnnBoolExp, this type alias ties together
|
|
|
|
-- 'GBoolExp', 'OpExpG', and 'AnnColumnCaseBoolExpFld'.
|
|
|
|
type AnnColumnCaseBoolExp b a = GBoolExp b (AnnColumnCaseBoolExpField b a)
|
|
|
|
|
|
|
|
-- misc type aliases
|
|
|
|
type AnnColumnCaseBoolExpPartialSQL b = AnnColumnCaseBoolExp b (PartialSQLExp b)
|
2019-09-05 10:34:53 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
type PreSetColsG b v = M.HashMap (Column b) v
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-03-25 20:50:08 +03:00
|
|
|
type PreSetColsPartial b = M.HashMap (Column b) (PartialSQLExp b)
|