graphql-engine/server/src-lib/Hasura/RQL/DML/Internal.hs
Vamshi Surabhi b84db36ebb
allow custom mutations through actions (#3042)
* basic doc for actions

* custom_types, sync and async actions

* switch to graphql-parser-hs on github

* update docs

* metadata import/export

* webhook calls are now supported

* relationships in sync actions

* initialise.sql is now in sync with the migration file

* fix metadata tests

* allow specifying arguments of actions

* fix blacklist check on check_build_worthiness job

* track custom_types and actions related tables

* handlers are now triggered on async actions

* default to pgjson unless a field is involved in relationships, for generating definition list

* use 'true' for action filter for non admin role

* fix create_action_permission sql query

* drop permissions when dropping an action

* add a hdb_role view (and relationships) to fetch all roles in the system

* rename 'webhook' key in action definition to 'handler'

* allow templating actions wehook URLs with env vars

* add 'update_action' /v1/query type

* allow forwarding client headers by setting `forward_client_headers` in action definition

* add 'headers' configuration in action definition

* handle webhook error response based on status codes

* support array relationships for custom types

* implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731

* single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor

* use top level primary key inputs for delete_by_pk & account select permissions for single row mutations

* use only REST semantics to resolve the webhook response

* use 'pk_columns' instead of 'columns' for update_by_pk input

* add python basic tests for single row mutations

* add action context (name) in webhook payload

* Async action response is accessible for non admin roles only if
  the request session vars equals to action's

* clean nulls, empty arrays for actions, custom types in export metadata

* async action mutation returns only the UUID of the action

* unit tests for URL template parser

* Basic sync actions python tests

* fix output in async query & add async tests

* add admin secret header in async actions python test

* document async action architecture in Resolve/Action.hs file

* support actions returning array of objects

* tests for list type response actions

* update docs with actions and custom types metadata API reference

* update actions python tests as per #f8e1330

Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com>
Co-authored-by: Aravind Shankar <face11301@gmail.com>
Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 23:08:23 +05:30

290 lines
8.9 KiB
Haskell

module Hasura.RQL.DML.Internal where
import qualified Database.PG.Query as Q
import qualified Hasura.SQL.DML as S
import Hasura.Prelude
import Hasura.RQL.GBoolExp
import Hasura.RQL.Types
import Hasura.SQL.Error
import Hasura.SQL.Types
import Hasura.SQL.Value
import Control.Lens
import Data.Aeson.Types
import qualified Data.HashMap.Strict as M
import qualified Data.HashSet as HS
import qualified Data.Sequence as DS
import qualified Data.Text as T
newtype DMLP1T m a
= DMLP1T { unDMLP1T :: StateT (DS.Seq Q.PrepArg) m a }
deriving ( Functor, Applicative, Monad, MonadTrans
, MonadState (DS.Seq Q.PrepArg), MonadError e
, TableCoreInfoRM, CacheRM, UserInfoM, HasSQLGenCtx
)
runDMLP1T :: DMLP1T m a -> m (a, DS.Seq Q.PrepArg)
runDMLP1T = flip runStateT DS.empty . unDMLP1T
mkAdminRolePermInfo :: TableCoreInfo -> RolePermInfo
mkAdminRolePermInfo ti =
RolePermInfo (Just i) (Just s) (Just u) (Just d)
where
fields = _tciFieldInfoMap ti
pgCols = map pgiColumn $ getCols fields
scalarComputedFields = map _cfiName $ onlyScalarComputedFields $
getComputedFieldInfos fields
tn = _tciName ti
i = InsPermInfo (HS.fromList pgCols) annBoolExpTrue M.empty []
s = SelPermInfo (HS.fromList pgCols) (HS.fromList scalarComputedFields) tn annBoolExpTrue
Nothing True []
u = UpdPermInfo (HS.fromList pgCols) tn annBoolExpTrue Nothing M.empty []
d = DelPermInfo tn annBoolExpTrue []
askPermInfo'
:: (UserInfoM m)
=> PermAccessor c
-> TableInfo
-> m (Maybe c)
askPermInfo' pa tableInfo = do
roleName <- askCurRole
let mrpi = getRolePermInfo roleName
return $ mrpi >>= (^. permAccToLens pa)
where
rpim = _tiRolePermInfoMap tableInfo
getRolePermInfo roleName
| roleName == adminRole = Just $ mkAdminRolePermInfo (_tiCoreInfo tableInfo)
| otherwise = M.lookup roleName rpim
askPermInfo
:: (UserInfoM m, QErrM m)
=> PermAccessor c
-> TableInfo
-> m c
askPermInfo pa tableInfo = do
roleName <- askCurRole
mPermInfo <- askPermInfo' pa tableInfo
case mPermInfo of
Just c -> return c
Nothing -> throw400 PermissionDenied $ mconcat
[ pt <> " on " <>> _tciName (_tiCoreInfo tableInfo)
, " for role " <>> roleName
, " is not allowed. "
]
where
pt = permTypeToCode $ permAccToType pa
isTabUpdatable :: RoleName -> TableInfo -> Bool
isTabUpdatable role ti
| role == adminRole = True
| otherwise = isJust $ M.lookup role rpim >>= _permUpd
where
rpim = _tiRolePermInfoMap ti
askInsPermInfo
:: (UserInfoM m, QErrM m)
=> TableInfo -> m InsPermInfo
askInsPermInfo = askPermInfo PAInsert
askSelPermInfo
:: (UserInfoM m, QErrM m)
=> TableInfo -> m SelPermInfo
askSelPermInfo = askPermInfo PASelect
askUpdPermInfo
:: (UserInfoM m, QErrM m)
=> TableInfo -> m UpdPermInfo
askUpdPermInfo = askPermInfo PAUpdate
askDelPermInfo
:: (UserInfoM m, QErrM m)
=> TableInfo -> m DelPermInfo
askDelPermInfo = askPermInfo PADelete
verifyAsrns :: (MonadError QErr m) => [a -> m ()] -> [a] -> m ()
verifyAsrns preds xs = indexedForM_ xs $ \a -> mapM_ ($ a) preds
checkSelOnCol :: (UserInfoM m, QErrM m)
=> SelPermInfo -> PGCol -> m ()
checkSelOnCol selPermInfo =
checkPermOnCol PTSelect (spiCols selPermInfo)
checkPermOnCol
:: (UserInfoM m, QErrM m)
=> PermType
-> HS.HashSet PGCol
-> PGCol
-> m ()
checkPermOnCol pt allowedCols pgCol = do
roleName <- askCurRole
unless (HS.member pgCol allowedCols) $
throw400 PermissionDenied $ permErrMsg roleName
where
permErrMsg roleName
| roleName == adminRole = "no such column exists : " <>> pgCol
| otherwise = mconcat
[ "role " <>> roleName
, " does not have permission to "
, permTypeToCode pt <> " column " <>> pgCol
]
binRHSBuilder :: (QErrM m) => PGColumnType -> Value -> DMLP1T m S.SQLExp
binRHSBuilder colType val = do
preparedArgs <- get
scalarValue <- parsePGScalarValue colType val
put (preparedArgs DS.|> toBinaryValue scalarValue)
return $ toPrepParam (DS.length preparedArgs + 1) (pstType scalarValue)
fetchRelTabInfo
:: (QErrM m, CacheRM m)
=> QualifiedTable
-> m TableInfo
fetchRelTabInfo refTabName =
-- Internal error
modifyErrAndSet500 ("foreign " <> ) $ askTabInfo refTabName
type SessVarBldr m = PGType PGScalarType -> SessVar -> m S.SQLExp
fetchRelDet
:: (UserInfoM m, QErrM m, CacheRM m)
=> RelName -> QualifiedTable
-> m (FieldInfoMap FieldInfo, SelPermInfo)
fetchRelDet relName refTabName = do
roleName <- askCurRole
-- Internal error
refTabInfo <- fetchRelTabInfo refTabName
-- Get the correct constraint that applies to the given relationship
refSelPerm <- modifyErr (relPermErr refTabName roleName) $
askSelPermInfo refTabInfo
return (_tciFieldInfoMap $ _tiCoreInfo refTabInfo, refSelPerm)
where
relPermErr rTable roleName _ =
mconcat
[ "role " <>> roleName
, " does not have permission to read relationship " <>> relName
, "; no permission on"
, " table " <>> rTable
]
checkOnColExp
:: (UserInfoM m, QErrM m, CacheRM m)
=> SelPermInfo
-> SessVarBldr m
-> AnnBoolExpFldSQL
-> m AnnBoolExpFldSQL
checkOnColExp spi sessVarBldr annFld = case annFld of
AVCol colInfo _ -> do
let cn = pgiColumn colInfo
checkSelOnCol spi cn
return annFld
AVRel relInfo nesAnn -> do
relSPI <- snd <$> fetchRelDet (riName relInfo) (riRTable relInfo)
modAnn <- checkSelPerm relSPI sessVarBldr nesAnn
resolvedFltr <- convAnnBoolExpPartialSQL sessVarBldr $ spiFilter relSPI
return $ AVRel relInfo $ andAnnBoolExps modAnn resolvedFltr
convAnnBoolExpPartialSQL
:: (Applicative f)
=> SessVarBldr f
-> AnnBoolExpPartialSQL
-> f AnnBoolExpSQL
convAnnBoolExpPartialSQL f =
traverseAnnBoolExp (convPartialSQLExp f)
convPartialSQLExp
:: (Applicative f)
=> SessVarBldr f
-> PartialSQLExp
-> f S.SQLExp
convPartialSQLExp f = \case
PSESQLExp sqlExp -> pure sqlExp
PSESessVar colTy sessionVariable -> f colTy sessionVariable
sessVarFromCurrentSetting
:: (Applicative f) => PGType PGScalarType -> SessVar -> f S.SQLExp
sessVarFromCurrentSetting pgType sessVar =
pure $ sessVarFromCurrentSetting' pgType sessVar
sessVarFromCurrentSetting' :: PGType PGScalarType -> SessVar -> S.SQLExp
sessVarFromCurrentSetting' ty sessVar =
flip S.SETyAnn (S.mkTypeAnn ty) $
case ty of
PGTypeScalar baseTy -> withConstructorFn baseTy sessVarVal
PGTypeArray _ -> sessVarVal
where
sessVarVal = S.SEOpApp (S.SQLOp "->>")
[currentSession, S.SELit $ T.toLower sessVar]
currentSession :: S.SQLExp
currentSession = S.SEUnsafe "current_setting('hasura.user')::json"
checkSelPerm
:: (UserInfoM m, QErrM m, CacheRM m)
=> SelPermInfo
-> SessVarBldr m
-> AnnBoolExpSQL
-> m AnnBoolExpSQL
checkSelPerm spi sessVarBldr =
traverse (checkOnColExp spi sessVarBldr)
convBoolExp
:: (UserInfoM m, QErrM m, CacheRM m)
=> FieldInfoMap FieldInfo
-> SelPermInfo
-> BoolExp
-> SessVarBldr m
-> (PGColumnType -> Value -> m S.SQLExp)
-> m AnnBoolExpSQL
convBoolExp cim spi be sessVarBldr prepValBldr = do
abe <- annBoolExp rhsParser cim $ unBoolExp be
checkSelPerm spi sessVarBldr abe
where
rhsParser pgType val = case pgType of
PGTypeScalar ty -> prepValBldr ty val
PGTypeArray ofTy -> do
-- for arrays, we don't use the prepared builder
vals <- runAesonParser parseJSON val
WithScalarType scalarType scalarValues <- parsePGScalarValues ofTy vals
return $ S.SETyAnn
(S.SEArray $ map (toTxtValue . WithScalarType scalarType) scalarValues)
(S.mkTypeAnn $ PGTypeArray scalarType)
dmlTxErrorHandler :: Q.PGTxErr -> QErr
dmlTxErrorHandler = mkTxErrorHandler $ \case
PGIntegrityConstraintViolation _ -> True
PGDataException _ -> True
PGSyntaxErrorOrAccessRuleViolation (Just (PGErrorSpecific code)) -> code `elem`
[ PGUndefinedObject
, PGInvalidColumnReference ]
_ -> False
toJSONableExp :: Bool -> PGColumnType -> Bool -> S.SQLExp -> S.SQLExp
toJSONableExp strfyNum colTy asText expn
| asText || (isScalarColumnWhere isBigNum colTy && strfyNum) =
expn `S.SETyAnn` S.textTypeAnn
| isScalarColumnWhere isGeoType colTy =
S.SEFnApp "ST_AsGeoJSON"
[ expn
, S.SEUnsafe "15" -- max decimal digits
, S.SEUnsafe "4" -- to print out crs
] Nothing
`S.SETyAnn` S.jsonTypeAnn
| otherwise = expn
-- validate headers
validateHeaders :: (UserInfoM m, QErrM m) => [T.Text] -> m ()
validateHeaders depHeaders = do
headers <- getVarNames . userVars <$> askUserInfo
forM_ depHeaders $ \hdr ->
unless (hdr `elem` map T.toLower headers) $
throw400 NotFound $ hdr <<> " header is expected but not found"
-- validate limit and offset int values
onlyPositiveInt :: MonadError QErr m => Int -> m ()
onlyPositiveInt i = when (i < 0) $ throw400 NotSupported
"unexpected negative value"