mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-11-10 10:29:12 +03:00
server/postgres: Support computed fields in permission check/filter
https://github.com/hasura/graphql-engine-mono/pull/1697 GitOrigin-RevId: 6cdf8acc90d3fd97d20a3ee68c84306c3f589370
This commit is contained in:
parent
ca567bf8cb
commit
a63fa18d9c
@ -3,6 +3,7 @@
|
||||
## Next release
|
||||
(Add entries below in the order of server, console, cli, docs, others)
|
||||
|
||||
- server: Support computed fields in permission check/filter (close #7102)
|
||||
- server: support computed fields in query 'order_by' (close #7103)
|
||||
- server: log warning if there are errors while executing clean up actions after "drop source" (previously it would throw an error)
|
||||
- server: Fixed a bug where MSSQL and BigQuery would ignore environment variables set from the console
|
||||
|
@ -5,6 +5,8 @@ import Hasura.Prelude
|
||||
import qualified Data.Aeson as J
|
||||
import qualified Data.HashMap.Strict as Map
|
||||
|
||||
import Data.Text.Extended
|
||||
|
||||
import Hasura.Backends.BigQuery.Types
|
||||
import Hasura.Base.Error
|
||||
import Hasura.RQL.IR.BoolExp
|
||||
@ -20,12 +22,11 @@ parseBoolExpOperations
|
||||
=> ValueParser 'BigQuery m v
|
||||
-> TableName
|
||||
-> FieldInfoMap (FieldInfo 'BigQuery)
|
||||
-> ColumnInfo 'BigQuery
|
||||
-> ColumnReference 'BigQuery
|
||||
-> J.Value
|
||||
-> m [OpExpG 'BigQuery v]
|
||||
parseBoolExpOperations rhsParser _table _fields columnInfo value =
|
||||
withPathK (columnName $ pgiColumn columnInfo) $
|
||||
parseOperations (pgiType columnInfo) value
|
||||
parseBoolExpOperations rhsParser _table _fields columnRef value =
|
||||
withPathK (toTxt columnRef) $ parseOperations (columnReferenceType columnRef) value
|
||||
where
|
||||
parseWithTy ty = rhsParser (CollectableTypeScalar ty)
|
||||
|
||||
|
@ -6,7 +6,7 @@ import qualified Data.Aeson as J
|
||||
import qualified Data.HashMap.Strict as Map
|
||||
import qualified Data.Text as T
|
||||
|
||||
import Data.Text.Extended (dquote, (<<>))
|
||||
import Data.Text.Extended (dquote, toTxt, (<<>))
|
||||
|
||||
import Hasura.Backends.MSSQL.Types hiding (ColumnType)
|
||||
import Hasura.Base.Error
|
||||
@ -22,12 +22,11 @@ parseBoolExpOperations
|
||||
=> ValueParser 'MSSQL m v
|
||||
-> TableName
|
||||
-> FieldInfoMap (FieldInfo 'MSSQL)
|
||||
-> ColumnInfo 'MSSQL
|
||||
-> ColumnReference 'MSSQL
|
||||
-> J.Value
|
||||
-> m [OpExpG 'MSSQL v]
|
||||
parseBoolExpOperations rhsParser _table _fields columnInfo value =
|
||||
withPathK (columnNameText $ pgiColumn columnInfo) $
|
||||
parseOperations (pgiType columnInfo) value
|
||||
parseBoolExpOperations rhsParser _table _fields columnRef value =
|
||||
withPathK (toTxt columnRef) $ parseOperations (columnReferenceType columnRef) value
|
||||
where
|
||||
parseWithTy ty = rhsParser (CollectableTypeScalar ty)
|
||||
|
||||
@ -88,7 +87,7 @@ parseBoolExpOperations rhsParser _table _fields columnInfo value =
|
||||
x -> throw400 UnexpectedPayload $ "Unknown operator : " <> x
|
||||
|
||||
where
|
||||
colTy = pgiType columnInfo
|
||||
colTy = columnReferenceType columnRef
|
||||
|
||||
parseOne = parseWithTy columnType val
|
||||
parseManyWithType ty = rhsParser (CollectableTypeArray ty) val
|
||||
|
@ -22,23 +22,6 @@ import Hasura.SQL.Backend
|
||||
import Hasura.SQL.Types
|
||||
|
||||
|
||||
-- | Represents a reference to a Postgres column, possibly casted an arbitrary
|
||||
-- number of times. Used within 'parseOperationsExpression' for bookkeeping.
|
||||
data ColumnReference (b :: BackendType)
|
||||
= ColumnReferenceColumn !(ColumnInfo b)
|
||||
| ColumnReferenceCast !(ColumnReference b) !(ColumnType b)
|
||||
|
||||
columnReferenceType :: ColumnReference backend -> ColumnType backend
|
||||
columnReferenceType = \case
|
||||
ColumnReferenceColumn column -> pgiType column
|
||||
ColumnReferenceCast _ targetType -> targetType
|
||||
|
||||
instance Backend b => ToTxt (ColumnReference b) where
|
||||
toTxt = \case
|
||||
ColumnReferenceColumn column -> toTxt $ pgiColumn column
|
||||
ColumnReferenceCast reference targetType ->
|
||||
toTxt reference <> "::" <> toTxt targetType
|
||||
|
||||
parseBoolExpOperations
|
||||
:: forall pgKind m v
|
||||
. ( Backend ('Postgres pgKind)
|
||||
@ -48,19 +31,18 @@ parseBoolExpOperations
|
||||
=> ValueParser ('Postgres pgKind) m v
|
||||
-> QualifiedTable
|
||||
-> FieldInfoMap (FieldInfo ('Postgres pgKind))
|
||||
-> ColumnInfo ('Postgres pgKind)
|
||||
-> ColumnReference ('Postgres pgKind)
|
||||
-> Value
|
||||
-> m [OpExpG ('Postgres pgKind) v]
|
||||
parseBoolExpOperations rhsParser rootTable fim columnInfo value = do
|
||||
parseBoolExpOperations rhsParser rootTable fim columnRef value = do
|
||||
restrictJSONColumn
|
||||
withPathK (getPGColTxt $ pgiColumn columnInfo) $
|
||||
parseOperations (ColumnReferenceColumn columnInfo) value
|
||||
withPathK (toTxt columnRef) $ parseOperations columnRef value
|
||||
where
|
||||
restrictJSONColumn :: m ()
|
||||
restrictJSONColumn = case columnInfo of
|
||||
ColumnInfo _ _ _ (ColumnScalar PGJSON) _ _ ->
|
||||
restrictJSONColumn = case columnReferenceType columnRef of
|
||||
ColumnScalar PGJSON ->
|
||||
throwError (err400 UnexpectedPayload "JSON column can not be part of boolean expression")
|
||||
_ -> pure ()
|
||||
_ -> pure ()
|
||||
|
||||
parseOperations :: ColumnReference ('Postgres pgKind) -> Value -> m [OpExpG ('Postgres pgKind) v]
|
||||
parseOperations column = \case
|
||||
|
@ -3,6 +3,7 @@ module Hasura.Backends.Postgres.Translate.BoolExp
|
||||
( toSQLBoolExp
|
||||
, getBoolExpDeps
|
||||
, annBoolExp
|
||||
, BoolExpRHSParser(..)
|
||||
) where
|
||||
|
||||
import Hasura.Prelude
|
||||
@ -18,6 +19,13 @@ import Hasura.RQL.Types
|
||||
import Hasura.SQL.Types
|
||||
|
||||
|
||||
-- | Context to parse a RHS value in a boolean expression
|
||||
data BoolExpRHSParser (b :: BackendType) m v
|
||||
= BoolExpRHSParser
|
||||
{ _berpValueParser :: !(ValueParser b m v) -- ^ Parse a JSON value with enforcing a column type
|
||||
, _berpSessionValue :: !v -- ^ Required for a computed field SQL function with session argument
|
||||
}
|
||||
|
||||
-- This convoluted expression instead of col = val
|
||||
-- to handle the case of col : null
|
||||
equalsBoolExpBuilder :: SQLExpression ('Postgres pgKind) -> SQLExpression ('Postgres pgKind) -> S.BoolExp
|
||||
@ -36,7 +44,7 @@ notEqualsBoolExpBuilder qualColExp rhsExp =
|
||||
|
||||
annBoolExp
|
||||
:: (QErrM m, TableCoreInfoRM b m, BackendMetadata b)
|
||||
=> ValueParser b m v
|
||||
=> BoolExpRHSParser b m v
|
||||
-> TableName b
|
||||
-> FieldInfoMap (FieldInfo b)
|
||||
-> GBoolExp b ColExp
|
||||
@ -49,8 +57,7 @@ annBoolExp rhsParser rootTable fim boolExp =
|
||||
BoolExists (GExists refqt whereExp) ->
|
||||
withPathK "_exists" $ do
|
||||
refFields <- withPathK "_table" $ askFieldInfoMapSource refqt
|
||||
annWhereExp <- withPathK "_where" $
|
||||
annBoolExp rhsParser rootTable refFields whereExp
|
||||
annWhereExp <- withPathK "_where" $ annBoolExp rhsParser rootTable refFields whereExp
|
||||
return $ BoolExists $ GExists refqt annWhereExp
|
||||
BoolFld fld -> BoolFld <$> annColExp rhsParser rootTable fim fld
|
||||
where
|
||||
@ -58,7 +65,7 @@ annBoolExp rhsParser rootTable fim boolExp =
|
||||
|
||||
annColExp
|
||||
:: (QErrM m, TableCoreInfoRM b m, BackendMetadata b)
|
||||
=> ValueParser b m v
|
||||
=> BoolExpRHSParser b m v
|
||||
-> TableName b
|
||||
-> FieldInfoMap (FieldInfo b)
|
||||
-> ColExp
|
||||
@ -66,15 +73,33 @@ annColExp
|
||||
annColExp rhsParser rootTable colInfoMap (ColExp fieldName colVal) = do
|
||||
colInfo <- askFieldInfo colInfoMap fieldName
|
||||
case colInfo of
|
||||
FIColumn pgi -> AVColumn pgi <$> parseBoolExpOperations rhsParser rootTable colInfoMap pgi colVal
|
||||
FIColumn pgi -> AVColumn pgi <$> parseBoolExpOperations (_berpValueParser rhsParser) rootTable colInfoMap (ColumnReferenceColumn pgi) colVal
|
||||
|
||||
FIRelationship relInfo -> do
|
||||
relBoolExp <- decodeValue colVal
|
||||
relFieldInfoMap <- askFieldInfoMapSource $ riRTable relInfo
|
||||
annRelBoolExp <- annBoolExp rhsParser rootTable relFieldInfoMap $
|
||||
unBoolExp relBoolExp
|
||||
annRelBoolExp <- annBoolExp rhsParser rootTable relFieldInfoMap $ unBoolExp relBoolExp
|
||||
return $ AVRelationship relInfo annRelBoolExp
|
||||
FIComputedField _ ->
|
||||
throw400 UnexpectedPayload "Computed columns can not be part of the where clause"
|
||||
|
||||
FIComputedField ComputedFieldInfo{..} -> do
|
||||
let ComputedFieldFunction{..} = _cfiFunction
|
||||
case toList _cffInputArgs of
|
||||
[] -> do
|
||||
let hasuraSession = _berpSessionValue rhsParser
|
||||
sessionArgPresence = mkSessionArgumentPresence hasuraSession _cffSessionArgument _cffTableArgument
|
||||
AVComputedField . AnnComputedFieldBoolExp _cfiXComputedFieldInfo _cfiName _cffName sessionArgPresence
|
||||
<$> case _cfiReturnType of
|
||||
CFRScalar scalarType -> CFBEScalar
|
||||
<$> parseBoolExpOperations (_berpValueParser rhsParser) rootTable colInfoMap (ColumnReferenceComputedField _cfiName scalarType) colVal
|
||||
CFRSetofTable table -> do
|
||||
tableBoolExp <- decodeValue colVal
|
||||
tableFieldInfoMap <- askFieldInfoMapSource table
|
||||
annTableBoolExp <- annBoolExp rhsParser table tableFieldInfoMap $ unBoolExp tableBoolExp
|
||||
pure $ CFBETable table annTableBoolExp
|
||||
|
||||
_ -> throw400 UnexpectedPayload
|
||||
"Computed columns with input arguments can not be part of the where clause"
|
||||
|
||||
-- TODO Rakesh (from master)
|
||||
FIRemoteRelationship{} ->
|
||||
throw400 UnexpectedPayload "remote field unsupported"
|
||||
|
@ -86,13 +86,8 @@ boolExp sourceName tableInfo selectPermissions = memoizeOn 'boolExp (sourceName,
|
||||
-- For a computed field to qualify in boolean expression it shouldn't have any input arguments
|
||||
case toList _cffInputArgs of
|
||||
[] -> do
|
||||
let sessionArgPresence = case _cffSessionArgument of
|
||||
Nothing -> SAPNotPresent
|
||||
Just _ -> case _cffTableArgument of
|
||||
FTAFirst -> SAPSecond P.UVSession -- If table argument is first, then session argument will be second
|
||||
FTANamed _ 0 -> SAPSecond P.UVSession -- Index 0 => table argument is first
|
||||
FTANamed{} -> SAPFirst P.UVSession -- If table argument is second, then session argument will be firest
|
||||
|
||||
let sessionArgPresence =
|
||||
mkSessionArgumentPresence P.UVSession _cffSessionArgument _cffTableArgument
|
||||
fmap (AVComputedField . AnnComputedFieldBoolExp _cfiXComputedFieldInfo _cfiName _cffName sessionArgPresence)
|
||||
<$> case _cfiReturnType of
|
||||
CFRScalar scalarType -> lift $ fmap CFBEScalar <$> comparisonExps @b (ColumnScalar scalarType)
|
||||
|
@ -47,6 +47,7 @@ textToName textName = G.mkName textName `onNothing` throw400 ValidationFailed
|
||||
|
||||
partialSQLExpToUnpreparedValue :: PartialSQLExp b -> P.UnpreparedValue b
|
||||
partialSQLExpToUnpreparedValue (PSESessVar pftype var) = P.UVSessionVar pftype var
|
||||
partialSQLExpToUnpreparedValue PSESession = P.UVSession
|
||||
partialSQLExpToUnpreparedValue (PSESQLExp sqlExp) = P.UVLiteral sqlExp
|
||||
|
||||
mapField
|
||||
|
@ -79,7 +79,8 @@ procBoolExp
|
||||
-> BoolExp b
|
||||
-> m (AnnBoolExpPartialSQL b, [SchemaDependency])
|
||||
procBoolExp source tn fieldInfoMap be = do
|
||||
abe <- annBoolExp parseCollectableType tn fieldInfoMap $ unBoolExp be
|
||||
let rhsParser = BoolExpRHSParser parseCollectableType PSESession
|
||||
abe <- annBoolExp rhsParser tn fieldInfoMap $ unBoolExp be
|
||||
let deps = getBoolExpDeps source tn abe
|
||||
return (abe, deps)
|
||||
|
||||
|
@ -71,7 +71,7 @@ mkSQLCount (CountQueryP1 tn (permFltr, mWc) mDistCols) =
|
||||
-- SELECT count(*) FROM (SELECT * FROM .. WHERE ..) r;
|
||||
validateCountQWith
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m)
|
||||
=> SessVarBldr ('Postgres 'Vanilla) m
|
||||
=> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> (ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp)
|
||||
-> CountQuery
|
||||
-> m CountQueryP1
|
||||
|
@ -34,7 +34,7 @@ import Hasura.Session
|
||||
|
||||
validateDeleteQWith
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m)
|
||||
=> SessVarBldr ('Postgres 'Vanilla) m
|
||||
=> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> (ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp)
|
||||
-> DeleteQuery
|
||||
-> m (AnnDel ('Postgres 'Vanilla))
|
||||
|
@ -68,7 +68,7 @@ validateInpCols inpCols updColsPerm = forM_ inpCols $ \inpCol ->
|
||||
|
||||
buildConflictClause
|
||||
:: (UserInfoM m, QErrM m)
|
||||
=> SessVarBldr ('Postgres 'Vanilla) m
|
||||
=> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> TableInfo ('Postgres 'Vanilla)
|
||||
-> [PGCol]
|
||||
-> OnConflict
|
||||
@ -129,7 +129,7 @@ buildConflictClause sessVarBldr tableInfo inpCols (OnConflict mTCol mTCons act)
|
||||
convInsertQuery
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m)
|
||||
=> (Value -> m [InsObj ('Postgres 'Vanilla)])
|
||||
-> SessVarBldr ('Postgres 'Vanilla) m
|
||||
-> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> (ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp)
|
||||
-> InsertQuery
|
||||
-> m (InsertQueryP1 ('Postgres 'Vanilla))
|
||||
|
@ -1,7 +1,4 @@
|
||||
module Hasura.RQL.DML.Internal where
|
||||
-- ( mkAdminRolePermInfo
|
||||
-- , SessVarBldr
|
||||
-- ) where
|
||||
|
||||
import Hasura.Prelude
|
||||
|
||||
@ -207,7 +204,11 @@ fetchRelTabInfo refTabName =
|
||||
modifyErrAndSet500 ("foreign " <> ) $
|
||||
askTabInfoSource refTabName
|
||||
|
||||
type SessVarBldr b m = SessionVarType b -> SessionVariable -> m (SQLExpression b)
|
||||
data SessionVariableBuilder b m
|
||||
= SessionVariableBuilder
|
||||
{ _svbCurrentSession :: !(SQLExpression b)
|
||||
, _svbVariableParser :: !(SessionVarType b -> SessionVariable -> m (SQLExpression b))
|
||||
}
|
||||
|
||||
fetchRelDet
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM b m, Backend b)
|
||||
@ -234,7 +235,7 @@ fetchRelDet relName refTabName = do
|
||||
checkOnColExp
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM b m, Backend b)
|
||||
=> SelPermInfo b
|
||||
-> SessVarBldr b m
|
||||
-> SessionVariableBuilder b m
|
||||
-> AnnBoolExpFldSQL b
|
||||
-> m (AnnBoolExpFldSQL b)
|
||||
checkOnColExp spi sessVarBldr annFld = case annFld of
|
||||
@ -267,7 +268,7 @@ checkOnColExp spi sessVarBldr annFld = case annFld of
|
||||
|
||||
convAnnBoolExpPartialSQL
|
||||
:: (Applicative f, Backend backend)
|
||||
=> SessVarBldr backend f
|
||||
=> SessionVariableBuilder backend f
|
||||
-> AnnBoolExpPartialSQL backend
|
||||
-> f (AnnBoolExpSQL backend)
|
||||
convAnnBoolExpPartialSQL f =
|
||||
@ -275,7 +276,7 @@ convAnnBoolExpPartialSQL f =
|
||||
|
||||
convAnnColumnCaseBoolExpPartialSQL
|
||||
:: (Applicative f, Backend backend)
|
||||
=> SessVarBldr backend f
|
||||
=> SessionVariableBuilder backend f
|
||||
-> AnnColumnCaseBoolExpPartialSQL backend
|
||||
-> f (AnnColumnCaseBoolExp backend (SQLExpression backend))
|
||||
convAnnColumnCaseBoolExpPartialSQL f =
|
||||
@ -283,17 +284,18 @@ convAnnColumnCaseBoolExpPartialSQL f =
|
||||
|
||||
convPartialSQLExp
|
||||
:: (Applicative f)
|
||||
=> SessVarBldr backend f
|
||||
=> SessionVariableBuilder backend f
|
||||
-> PartialSQLExp backend
|
||||
-> f (SQLExpression backend)
|
||||
convPartialSQLExp f = \case
|
||||
convPartialSQLExp sessVarBldr = \case
|
||||
PSESQLExp sqlExp -> pure sqlExp
|
||||
PSESessVar colTy sessionVariable -> f colTy sessionVariable
|
||||
PSESession -> pure $ _svbCurrentSession sessVarBldr
|
||||
PSESessVar colTy sessionVariable -> (_svbVariableParser sessVarBldr) colTy sessionVariable
|
||||
|
||||
sessVarFromCurrentSetting
|
||||
:: (Applicative f) => CollectableType PGScalarType -> SessionVariable -> f S.SQLExp
|
||||
sessVarFromCurrentSetting pgType sessVar =
|
||||
pure $ sessVarFromCurrentSetting' pgType sessVar
|
||||
:: (Applicative f) => SessionVariableBuilder ('Postgres pgKind) f
|
||||
sessVarFromCurrentSetting =
|
||||
SessionVariableBuilder currentSession $ \ty var -> pure $ sessVarFromCurrentSetting' ty var
|
||||
|
||||
sessVarFromCurrentSetting' :: CollectableType PGScalarType -> SessionVariable -> S.SQLExp
|
||||
sessVarFromCurrentSetting' ty sessVar =
|
||||
@ -329,7 +331,7 @@ currentSession = S.SEUnsafe "current_setting('hasura.user')::json"
|
||||
checkSelPerm
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM b m, Backend b)
|
||||
=> SelPermInfo b
|
||||
-> SessVarBldr b m
|
||||
-> SessionVariableBuilder b m
|
||||
-> AnnBoolExpSQL b
|
||||
-> m (AnnBoolExpSQL b)
|
||||
checkSelPerm spi sessVarBldr =
|
||||
@ -340,12 +342,13 @@ convBoolExp
|
||||
=> FieldInfoMap (FieldInfo b)
|
||||
-> SelPermInfo b
|
||||
-> BoolExp b
|
||||
-> SessVarBldr b m
|
||||
-> SessionVariableBuilder b m
|
||||
-> TableName b
|
||||
-> ValueParser b m (SQLExpression b)
|
||||
-> m (AnnBoolExpSQL b)
|
||||
convBoolExp cim spi be sessVarBldr rootTable rhsParser = do
|
||||
abe <- annBoolExp rhsParser rootTable cim $ unBoolExp be
|
||||
let boolExpRHSParser = BoolExpRHSParser rhsParser $ _svbCurrentSession sessVarBldr
|
||||
abe <- annBoolExp boolExpRHSParser rootTable cim $ unBoolExp be
|
||||
checkSelPerm spi sessVarBldr abe
|
||||
|
||||
dmlTxErrorHandler :: Q.PGTxErr -> QErr
|
||||
|
@ -118,7 +118,7 @@ resolveStar fim selPermInfo (SelectG selCols mWh mOb mLt mOf) = do
|
||||
|
||||
convOrderByElem
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m)
|
||||
=> SessVarBldr ('Postgres 'Vanilla) m
|
||||
=> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> (FieldInfoMap (FieldInfo ('Postgres 'Vanilla)), SelPermInfo ('Postgres 'Vanilla))
|
||||
-> OrderByCol
|
||||
-> m (AnnotatedOrderByElement ('Postgres 'Vanilla) S.SQLExp)
|
||||
@ -179,7 +179,7 @@ convSelectQ
|
||||
-> FieldInfoMap (FieldInfo ('Postgres 'Vanilla)) -- Table information of current table
|
||||
-> SelPermInfo ('Postgres 'Vanilla) -- Additional select permission info
|
||||
-> SelectQExt ('Postgres 'Vanilla) -- Given Select Query
|
||||
-> SessVarBldr ('Postgres 'Vanilla) m
|
||||
-> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> ValueParser ('Postgres 'Vanilla) m S.SQLExp
|
||||
-> m (AnnSimpleSelect ('Postgres 'Vanilla))
|
||||
convSelectQ table fieldInfoMap selPermInfo selQ sessVarBldr prepValBldr = do
|
||||
@ -250,7 +250,7 @@ convExtRel
|
||||
-> RelName
|
||||
-> Maybe RelName
|
||||
-> SelectQExt ('Postgres 'Vanilla)
|
||||
-> SessVarBldr ('Postgres 'Vanilla) m
|
||||
-> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> ValueParser ('Postgres 'Vanilla) m S.SQLExp
|
||||
-> m (Either (ObjectRelationSelect ('Postgres 'Vanilla)) (ArraySelect ('Postgres 'Vanilla)))
|
||||
convExtRel fieldInfoMap relName mAlias selQ sessVarBldr prepValBldr = do
|
||||
@ -288,7 +288,7 @@ convSelectQuery
|
||||
, TableInfoRM ('Postgres 'Vanilla) m
|
||||
, HasServerConfigCtx m
|
||||
)
|
||||
=> SessVarBldr ('Postgres 'Vanilla) m
|
||||
=> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> ValueParser ('Postgres 'Vanilla) m S.SQLExp
|
||||
-> SelectQuery
|
||||
-> m (AnnSimpleSelect ('Postgres 'Vanilla))
|
||||
|
@ -95,7 +95,7 @@ convOp fieldInfoMap preSetCols updPerm objs conv =
|
||||
|
||||
validateUpdateQueryWith
|
||||
:: (UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m)
|
||||
=> SessVarBldr ('Postgres 'Vanilla) m
|
||||
=> SessionVariableBuilder ('Postgres 'Vanilla) m
|
||||
-> ValueParser ('Postgres 'Vanilla) m S.SQLExp
|
||||
-> UpdateQuery
|
||||
-> m (AnnUpd ('Postgres 'Vanilla))
|
||||
|
@ -20,6 +20,7 @@ module Hasura.RQL.IR.BoolExp
|
||||
, STIntersectsGeomminNband(..)
|
||||
|
||||
, SessionArgumentPresence(..)
|
||||
, mkSessionArgumentPresence
|
||||
, ComputedFieldBoolExp(..)
|
||||
, AnnComputedFieldBoolExp(..)
|
||||
, AnnBoolExpFld(..)
|
||||
@ -186,6 +187,7 @@ makePrisms ''GBoolExp
|
||||
-- inline the session variables.
|
||||
data PartialSQLExp (b :: BackendType)
|
||||
= PSESessVar !(SessionVarType b) !SessionVariable
|
||||
| PSESession
|
||||
| PSESQLExp !(SQLExpression b)
|
||||
deriving (Generic)
|
||||
deriving instance (Backend b) => Eq (PartialSQLExp b)
|
||||
@ -196,11 +198,13 @@ instance (Backend b, Hashable (BooleanOperators b (PartialSQLExp b))) => Cachea
|
||||
instance Backend b => ToJSON (PartialSQLExp b) where
|
||||
toJSON = \case
|
||||
PSESessVar colTy sessVar -> toJSON (colTy, sessVar)
|
||||
PSESession -> String "hasura_session"
|
||||
PSESQLExp e -> toJSON e
|
||||
|
||||
isStaticValue :: PartialSQLExp backend -> Bool
|
||||
isStaticValue = \case
|
||||
PSESessVar _ _ -> False
|
||||
PSESession -> False
|
||||
PSESQLExp _ -> True
|
||||
|
||||
hasStaticExp :: Backend b => OpExpG b (PartialSQLExp b) -> Bool
|
||||
@ -297,8 +301,8 @@ opExpDepCol = \case
|
||||
_ -> Nothing
|
||||
|
||||
-- | The presence of session argument in the SQL function of a computed field.
|
||||
-- Since we only support maximum of 2 arguments in boolean expression, the position
|
||||
-- (if present) is either first or second. The other mandatory argument is table row input.
|
||||
-- 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.
|
||||
data SessionArgumentPresence a
|
||||
= SAPNotPresent
|
||||
| SAPFirst a
|
||||
@ -308,6 +312,18 @@ instance (NFData a) => NFData (SessionArgumentPresence a)
|
||||
instance (Cacheable a) => Cacheable (SessionArgumentPresence a)
|
||||
instance (Hashable a) => Hashable (SessionArgumentPresence a)
|
||||
|
||||
-- | 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
|
||||
FTAFirst -> SAPSecond sessionValue
|
||||
-- Argument index 0 implies it is first
|
||||
FTANamed _ 0 -> SAPSecond sessionValue
|
||||
-- If table argument is second, then session argument will be first
|
||||
FTANamed{} -> SAPFirst sessionValue
|
||||
|
||||
-- | 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
|
||||
@ -336,7 +352,7 @@ instance (Backend b, Hashable (BooleanOperators b a), Hashable a) => Hashable
|
||||
data AnnComputedFieldBoolExp (b :: BackendType) a
|
||||
= AnnComputedFieldBoolExp
|
||||
{ _acfbXFieldInfo :: !(XComputedField b)
|
||||
, _acfbName :: !(ComputedFieldName)
|
||||
, _acfbName :: !ComputedFieldName
|
||||
, _acfbFunction :: !(FunctionName b)
|
||||
, _acfbSessionArgumentPresence :: !(SessionArgumentPresence a)
|
||||
, _acfbBoolExp :: !(ComputedFieldBoolExp b a)
|
||||
|
@ -25,12 +25,15 @@ module Hasura.RQL.Types.Column
|
||||
|
||||
, fromCol
|
||||
, ColumnValues
|
||||
|
||||
, ColumnReference(..)
|
||||
, columnReferenceType
|
||||
) where
|
||||
|
||||
import Hasura.Prelude
|
||||
|
||||
import qualified Data.HashMap.Strict as M
|
||||
import qualified Language.GraphQL.Draft.Syntax as G
|
||||
import qualified Data.HashMap.Strict as M
|
||||
import qualified Language.GraphQL.Draft.Syntax as G
|
||||
|
||||
import Control.Lens.TH
|
||||
import Data.Aeson
|
||||
@ -38,9 +41,10 @@ import Data.Aeson.TH
|
||||
import Data.Text.Extended
|
||||
|
||||
import Hasura.Base.Error
|
||||
import Hasura.Incremental (Cacheable)
|
||||
import Hasura.Incremental (Cacheable)
|
||||
import Hasura.RQL.Types.Backend
|
||||
import Hasura.RQL.Types.Common
|
||||
import Hasura.RQL.Types.ComputedField
|
||||
import Hasura.SQL.Backend
|
||||
import Hasura.SQL.Types
|
||||
|
||||
@ -201,3 +205,23 @@ fromCol :: Backend b => Column b -> FieldName
|
||||
fromCol = FieldName . toTxt
|
||||
|
||||
type ColumnValues b a = HashMap (Column b) a
|
||||
|
||||
-- | Represents a reference to a source column, possibly casted an arbitrary
|
||||
-- number of times. Used within 'parseBoolExpOperations' for bookkeeping.
|
||||
data ColumnReference (b :: BackendType)
|
||||
= ColumnReferenceColumn !(ColumnInfo b)
|
||||
| ColumnReferenceComputedField !ComputedFieldName !(ScalarType b)
|
||||
| ColumnReferenceCast !(ColumnReference b) !(ColumnType b)
|
||||
|
||||
columnReferenceType :: ColumnReference backend -> ColumnType backend
|
||||
columnReferenceType = \case
|
||||
ColumnReferenceColumn column -> pgiType column
|
||||
ColumnReferenceComputedField _ scalarType -> ColumnScalar scalarType
|
||||
ColumnReferenceCast _ targetType -> targetType
|
||||
|
||||
instance Backend b => ToTxt (ColumnReference b) where
|
||||
toTxt = \case
|
||||
ColumnReferenceColumn column -> toTxt $ pgiColumn column
|
||||
ColumnReferenceComputedField name _ -> toTxt name
|
||||
ColumnReferenceCast reference targetType ->
|
||||
toTxt reference <> "::" <> toTxt targetType
|
||||
|
@ -82,7 +82,7 @@ class (Backend b) => BackendMetadata (b :: BackendType) where
|
||||
=> ValueParser b m v
|
||||
-> TableName b
|
||||
-> FieldInfoMap (FieldInfo b)
|
||||
-> ColumnInfo b
|
||||
-> ColumnReference b
|
||||
-> Value
|
||||
-> m [OpExpG b v]
|
||||
|
||||
|
@ -0,0 +1,17 @@
|
||||
description: A reader fetch authors with atleast one published article
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
headers:
|
||||
X-Hasura-Role: reader
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
author{
|
||||
name
|
||||
}
|
||||
}
|
||||
response:
|
||||
data:
|
||||
author:
|
||||
- name: Author 1
|
||||
- name: Author 2
|
@ -26,6 +26,11 @@ args:
|
||||
published_on TIMESTAMP
|
||||
);
|
||||
|
||||
CREATE FUNCTION get_articles(author_row author)
|
||||
RETURNS SETOF article as $$
|
||||
SELECT * FROM article WHERE author_id = author_row.id
|
||||
$$ LANGUAGE SQL STABLE;
|
||||
|
||||
INSERT INTO article (title, content, author_id, is_published)
|
||||
VALUES
|
||||
('Article 1', 'Sample article content 1', 1, false),
|
||||
@ -126,6 +131,7 @@ args:
|
||||
SELECT * FROM gpa WHERE
|
||||
gpa_score >= pass_gpa
|
||||
$$ language SQL STABLE;
|
||||
|
||||
CREATE TABLE auction (
|
||||
id serial primary key,
|
||||
price integer not null DEFAULT 250,
|
||||
@ -138,6 +144,28 @@ args:
|
||||
(100), (120), (300), (260)
|
||||
;
|
||||
|
||||
CREATE TABLE student_marks (
|
||||
id SERIAL PRIMARY KEY,
|
||||
name TEXT UNIQUE NOT NULL,
|
||||
physics INTEGER,
|
||||
chemistry INTEGER,
|
||||
mathematics INTEGER
|
||||
);
|
||||
|
||||
INSERT INTO student_marks (name, physics, chemistry, mathematics) VALUES
|
||||
('clarke', 84, 67, 70), ('george', 56, 79, 70),
|
||||
('blake', 66, 89, 78), ('leonel', 90, 93, 85);
|
||||
|
||||
CREATE FUNCTION student_total_marks (student_row student_marks)
|
||||
RETURNS INTEGER AS $$
|
||||
SELECT student_row.physics + student_row.chemistry + student_row.mathematics
|
||||
$$ LANGUAGE SQL STABLE;
|
||||
|
||||
CREATE FUNCTION student_total_marks_offset (hasura_session json, student_row student_marks)
|
||||
RETURNS INTEGER AS $$
|
||||
SELECT student_row.physics + student_row.chemistry + student_row.mathematics - (hasura_session ->> 'x-hasura-offset-marks')::integer
|
||||
$$ LANGUAGE SQL STABLE;
|
||||
|
||||
- type: track_table
|
||||
args:
|
||||
schema: public
|
||||
@ -149,6 +177,16 @@ args:
|
||||
schema: public
|
||||
name: article
|
||||
|
||||
# Add computed field to author table
|
||||
- type: add_computed_field
|
||||
args:
|
||||
table: author
|
||||
name: get_articles
|
||||
definition:
|
||||
function: get_articles
|
||||
table_argument: author_row
|
||||
|
||||
|
||||
#Object relationship
|
||||
- type: create_object_relationship
|
||||
args:
|
||||
@ -224,6 +262,18 @@ args:
|
||||
_eq: true
|
||||
limit: 10
|
||||
|
||||
#Author select permission for reader
|
||||
- type: create_select_permission
|
||||
args:
|
||||
table: author
|
||||
role: reader
|
||||
permission:
|
||||
columns:
|
||||
- name
|
||||
filter:
|
||||
get_articles:
|
||||
is_published: true
|
||||
|
||||
#Author select permission for anonymous users
|
||||
#Only authors with atleast one article will be shown
|
||||
- type: create_select_permission
|
||||
@ -495,3 +545,50 @@ args:
|
||||
permission:
|
||||
columns: [name]
|
||||
filter: {}
|
||||
|
||||
# Track student_marks table
|
||||
- type: track_table
|
||||
args:
|
||||
table: student_marks
|
||||
|
||||
- type: add_computed_field
|
||||
args:
|
||||
table: student_marks
|
||||
name: total_marks
|
||||
definition:
|
||||
function: student_total_marks
|
||||
table_argument: student_row
|
||||
|
||||
- type: add_computed_field
|
||||
args:
|
||||
table: student_marks
|
||||
name: total_marks_offset
|
||||
definition:
|
||||
function: student_total_marks_offset
|
||||
table_argument: student_row
|
||||
session_argument: hasura_session
|
||||
|
||||
- type: create_select_permission
|
||||
args:
|
||||
table: student_marks
|
||||
role: tutor
|
||||
permission:
|
||||
columns:
|
||||
- name
|
||||
filter:
|
||||
total_marks:
|
||||
_gte: 220
|
||||
|
||||
- type: create_select_permission
|
||||
args:
|
||||
table: student_marks
|
||||
role: tutor_session
|
||||
permission:
|
||||
columns:
|
||||
- name
|
||||
computed_fields:
|
||||
- total_marks
|
||||
- total_marks_offset
|
||||
filter:
|
||||
total_marks_offset:
|
||||
_gte: 220
|
||||
|
@ -3,6 +3,7 @@ args:
|
||||
- type: run_sql
|
||||
args:
|
||||
sql: |
|
||||
DROP FUNCTION get_articles(author);
|
||||
DROP TABLE article;
|
||||
DROP TABLE author;
|
||||
DROP TABLE "Track" cascade;
|
||||
@ -12,4 +13,7 @@ args:
|
||||
DROP TABLE jsonb_table;
|
||||
DROP TABLE gpa cascade;
|
||||
DROP TABLE auction;
|
||||
DROP FUNCTION student_total_marks(student_marks);
|
||||
DROP FUNCTION student_total_marks_offset(json, student_marks);
|
||||
DROP TABLE student_marks;
|
||||
cascade: true
|
||||
|
@ -0,0 +1,18 @@
|
||||
description: Fetch student names with tutor role
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
headers:
|
||||
X-Hasura-Role: tutor
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
student_marks{
|
||||
name
|
||||
}
|
||||
}
|
||||
response:
|
||||
data:
|
||||
student_marks:
|
||||
- name: clarke
|
||||
- name: blake
|
||||
- name: leonel
|
@ -0,0 +1,24 @@
|
||||
description: Fetch student names with tutor role with an offset given via hasura session
|
||||
url: /v1/graphql
|
||||
status: 200
|
||||
headers:
|
||||
X-Hasura-Role: tutor_session
|
||||
X-Hasura-Offset-Marks: '10'
|
||||
query:
|
||||
query: |
|
||||
query {
|
||||
student_marks{
|
||||
name
|
||||
total_marks
|
||||
total_marks_offset
|
||||
}
|
||||
}
|
||||
response:
|
||||
data:
|
||||
student_marks:
|
||||
- name: blake
|
||||
total_marks: 233
|
||||
total_marks_offset: 223
|
||||
- name: leonel
|
||||
total_marks: 268
|
||||
total_marks_offset: 258
|
@ -602,6 +602,15 @@ class TestGraphqlQueryPermissions:
|
||||
def test_author_articles_without_required_headers_set(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/select_articles_without_required_headers.yaml', transport)
|
||||
|
||||
def test_reader_author(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/reader_author.yaml', transport)
|
||||
|
||||
def test_tutor_get_students(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/tutor_get_students.yaml', transport)
|
||||
|
||||
def test_tutor_get_students_session(self, hge_ctx, transport):
|
||||
check_query_f(hge_ctx, self.dir() + '/tutor_get_students_session.yaml', transport)
|
||||
|
||||
@classmethod
|
||||
def dir(cls):
|
||||
return 'queries/graphql_query/permissions'
|
||||
|
Loading…
Reference in New Issue
Block a user