graphql-engine/server/src-lib/Hasura/RQL/DML/Select.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

306 lines
10 KiB
Haskell

module Hasura.RQL.DML.Select
( selectP2
, selectQuerySQL
, selectAggQuerySQL
, convSelectQuery
, asSingleRowJsonResp
, module Hasura.RQL.DML.Select.Internal
, runSelect
)
where
import Data.Aeson.Types
import Instances.TH.Lift ()
import qualified Data.HashSet as HS
import qualified Data.List.NonEmpty as NE
import qualified Data.Sequence as DS
import Hasura.EncJSON
import Hasura.Prelude
import Hasura.RQL.DML.Internal
import Hasura.RQL.DML.Select.Internal
import Hasura.RQL.Types
import Hasura.SQL.Types
import qualified Database.PG.Query as Q
import qualified Hasura.SQL.DML as S
convSelCol :: (UserInfoM m, QErrM m, CacheRM m)
=> FieldInfoMap FieldInfo
-> SelPermInfo
-> SelCol
-> m [ExtCol]
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, CacheRM m)
=> FieldInfoMap FieldInfo
-> SelPermInfo
-> Wildcard
-> m [ExtCol]
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 (`HS.member` cols) pgCols
mkRelCol wc relInfo = do
let relName = riName relInfo
relTab = riRTable relInfo
relTabInfo <- fetchRelTabInfo relTab
mRelSelPerm <- askPermInfo' PASelect relTabInfo
forM mRelSelPerm $ \rspi -> do
rExtCols <- convWildcard (_tciFieldInfoMap $ _tiCoreInfo relTabInfo) rspi wc
return $ ECRel relName Nothing $
SelectG rExtCols Nothing Nothing Nothing Nothing
relExtCols wc = mapM (mkRelCol wc) relColInfos
resolveStar :: (UserInfoM m, QErrM m, CacheRM m)
=> FieldInfoMap FieldInfo
-> SelPermInfo
-> SelectQ
-> m SelectQExt
resolveStar fim spi (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 spi selCol
everything <- case wildcards of
[] -> return []
_ -> convWildcard fim spi $ 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, CacheRM m)
=> SessVarBldr m
-> (FieldInfoMap FieldInfo, SelPermInfo)
-> OrderByCol
-> m AnnObCol
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 $ AOCPG $ pgiColumn 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'"
]
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, relSpi) <- fetchRelDet (riName relInfo) (riRTable relInfo)
resolvedSelFltr <- convAnnBoolExpPartialSQL sessVarBldr $ spiFilter relSpi
AOCObj relInfo resolvedSelFltr <$>
convOrderByElem sessVarBldr (relFim, relSpi) rest
convSelectQ
:: (UserInfoM m, QErrM m, CacheRM m, HasSQLGenCtx m)
=> FieldInfoMap FieldInfo -- Table information of current table
-> SelPermInfo -- Additional select permission info
-> SelectQExt -- Given Select Query
-> SessVarBldr m
-> (PGColumnType -> Value -> m S.SQLExp)
-> m AnnSimpleSel
convSelectQ fieldInfoMap selPermInfo selQ sessVarBldr prepValBldr = do
annFlds <- withPathK "columns" $
indexedForM (sqColumns selQ) $ \case
(ECSimple pgCol) -> do
colInfo <- convExtSimple fieldInfoMap selPermInfo pgCol
return (fromPGCol pgCol, mkAnnColField colInfo Nothing)
(ECRel relName mAlias relSelQ) -> do
annRel <- convExtRel fieldInfoMap relName mAlias
relSelQ sessVarBldr prepValBldr
return ( fromRel $ fromMaybe relName mAlias
, either FObj FArr annRel
)
-- let spiT = spiTable selPermInfo
-- Convert where clause
wClause <- forM (sqWhere selQ) $ \be ->
withPathK "where" $
convBoolExp fieldInfoMap selPermInfo be sessVarBldr prepValBldr
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 $ spiTable selPermInfo
tabPerm = TablePerm resolvedSelFltr mPermLimit
tabArgs = TableArgs wClause annOrdByM mQueryLimit
(S.intToSQLExp <$> mQueryOffset) Nothing
strfyNum <- stringifyNum <$> askSQLGenCtx
return $ AnnSelG annFlds tabFrom tabPerm tabArgs strfyNum
where
mQueryOffset = sqOffset selQ
mQueryLimit = sqLimit selQ
mPermLimit = spiLimit selPermInfo
convExtSimple
:: (UserInfoM m, QErrM m)
=> FieldInfoMap FieldInfo
-> SelPermInfo
-> PGCol
-> m PGColumnInfo
convExtSimple fieldInfoMap selPermInfo pgCol = do
checkSelOnCol selPermInfo pgCol
askPGColInfo fieldInfoMap pgCol relWhenPGErr
where
relWhenPGErr = "relationships have to be expanded"
convExtRel
:: (UserInfoM m, QErrM m, CacheRM m, HasSQLGenCtx m)
=> FieldInfoMap FieldInfo
-> RelName
-> Maybe RelName
-> SelectQExt
-> SessVarBldr m
-> (PGColumnType -> Value -> m S.SQLExp)
-> m (Either ObjSel ArrSel)
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 relCIM relSPI selQ sessVarBldr prepValBldr
case relTy of
ObjRel -> do
when misused $ throw400 UnexpectedPayload objRelMisuseMsg
return $ Left $ AnnRelG (fromMaybe relName mAlias) colMapping annSel
ArrRel ->
return $ Right $ ASSimple $ AnnRelG (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, CacheRM m, HasSQLGenCtx m)
=> SessVarBldr m
-> (PGColumnType -> Value -> m S.SQLExp)
-> SelectQuery
-> m AnnSimpleSel
convSelectQuery sessVarBldr prepArgBuilder (DMLQuery qt selQ) = do
tabInfo <- withPathK "table" $ askTabInfo qt
selPermInfo <- askSelPermInfo tabInfo
let fieldInfo = _tciFieldInfoMap $ _tiCoreInfo tabInfo
extSelQ <- resolveStar fieldInfo selPermInfo selQ
validateHeaders $ spiRequiredHeaders selPermInfo
convSelectQ fieldInfo selPermInfo
extSelQ sessVarBldr prepArgBuilder
selectP2 :: JsonAggSelect -> (AnnSimpleSel, 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
selectQuerySQL :: JsonAggSelect -> AnnSimpleSel -> Q.Query
selectQuerySQL jsonAggSelect sel =
Q.fromBuilder $ toSQL $ mkSQLSelect jsonAggSelect sel
selectAggQuerySQL :: AnnAggSel -> Q.Query
selectAggQuerySQL =
Q.fromBuilder . toSQL . mkAggSelect
asSingleRowJsonResp :: Q.Query -> [Q.PrepArg] -> Q.TxE QErr EncJSON
asSingleRowJsonResp query args =
encJFromBS . runIdentity . Q.getRow
<$> Q.rawQE dmlTxErrorHandler query args True
phaseOne
:: (QErrM m, UserInfoM m, CacheRM m, HasSQLGenCtx m)
=> SelectQuery -> m (AnnSimpleSel, DS.Seq Q.PrepArg)
phaseOne =
runDMLP1T . convSelectQuery sessVarFromCurrentSetting binRHSBuilder
phaseTwo :: (MonadTx m) => (AnnSimpleSel, DS.Seq Q.PrepArg) -> m EncJSON
phaseTwo =
liftTx . selectP2 JASMultipleRows
runSelect
:: (QErrM m, UserInfoM m, CacheRM m, HasSQLGenCtx m, MonadTx m)
=> SelectQuery -> m EncJSON
runSelect q =
phaseOne q >>= phaseTwo