graphql-engine/server/src-lib/Hasura/RQL/DML/Mutation.hs

170 lines
6.0 KiB
Haskell
Raw Normal View History

module Hasura.RQL.DML.Mutation
( Mutation
, mkMutation
, MutationRemoteJoinCtx
, runMutation
, executeMutationOutputQuery
, mutateAndFetchCols
, mkSelCTEFromColVals
)
where
import Hasura.Prelude
import qualified Data.HashMap.Strict as Map
import qualified Data.Sequence as DS
import qualified Database.PG.Query as Q
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Types as N
import qualified Hasura.SQL.DML as S
import Hasura.EncJSON
import Hasura.RQL.DML.Internal
import Hasura.RQL.DML.RemoteJoin
import Hasura.RQL.DML.Returning
import Hasura.RQL.DML.Select
import Hasura.RQL.Instances ()
import Hasura.RQL.Types
import Hasura.Server.Version (HasVersion)
import Hasura.Session
import Hasura.SQL.Types
import Hasura.SQL.Value
type MutationRemoteJoinCtx = (HTTP.Manager, [N.Header], UserInfo)
data Mutation
= Mutation
{ _mTable :: !QualifiedTable
, _mQuery :: !(S.CTE, DS.Seq Q.PrepArg)
, _mOutput :: !MutationOutput
, _mCols :: ![PGColumnInfo]
, _mRemoteJoins :: !(Maybe (RemoteJoins, MutationRemoteJoinCtx))
, _mStrfyNum :: !Bool
}
mkMutation
:: Maybe MutationRemoteJoinCtx
-> QualifiedTable
-> (S.CTE, DS.Seq Q.PrepArg)
-> MutationOutput
-> [PGColumnInfo]
-> Bool
-> Mutation
mkMutation ctx table query output' allCols strfyNum =
let (output, remoteJoins) = getRemoteJoinsMutationOutput output'
remoteJoinsCtx = (,) <$> remoteJoins <*> ctx
in Mutation table query output allCols remoteJoinsCtx strfyNum
runMutation
:: (HasVersion, MonadTx m, MonadIO m)
=> Mutation -> m EncJSON
runMutation mut =
bool (mutateAndReturn mut) (mutateAndSel mut) $
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 20:38:23 +03:00
hasNestedFld $ _mOutput mut
mutateAndReturn
:: (HasVersion, MonadTx m, MonadIO m)
=> Mutation -> m EncJSON
mutateAndReturn (Mutation qt (cte, p) mutationOutput allCols remoteJoins strfyNum) =
executeMutationOutputQuery sqlQuery (toList p) remoteJoins
where
sqlQuery = Q.fromBuilder $ toSQL $
mkMutationOutputExp qt allCols Nothing cte mutationOutput strfyNum
mutateAndSel
:: (HasVersion, MonadTx m, MonadIO m)
=> Mutation -> m EncJSON
mutateAndSel (Mutation qt q mutationOutput allCols remoteJoins strfyNum) = do
-- Perform mutation and fetch unique columns
MutateResp _ columnVals <- liftTx $ mutateAndFetchCols qt allCols q strfyNum
selCTE <- mkSelCTEFromColVals qt allCols columnVals
let selWith = mkMutationOutputExp qt allCols Nothing selCTE mutationOutput strfyNum
-- Perform select query and fetch returning fields
executeMutationOutputQuery (Q.fromBuilder $ toSQL selWith) [] remoteJoins
executeMutationOutputQuery
:: (HasVersion, MonadTx m, MonadIO m)
=> Q.Query -- ^ SQL query
-> [Q.PrepArg] -- ^ Prepared params
-> Maybe (RemoteJoins, MutationRemoteJoinCtx) -- ^ Remote joins context
-> m EncJSON
executeMutationOutputQuery query prepArgs = \case
Nothing ->
runIdentity . Q.getRow
<$> liftTx (Q.rawQE dmlTxErrorHandler query prepArgs True)
Just (remoteJoins, (httpManager, reqHeaders, userInfo)) ->
executeQueryWithRemoteJoins httpManager reqHeaders userInfo query prepArgs remoteJoins
mutateAndFetchCols
:: QualifiedTable
-> [PGColumnInfo]
-> (S.CTE, DS.Seq Q.PrepArg)
-> Bool
-> Q.TxE QErr (MutateResp TxtEncodedPGVal)
mutateAndFetchCols qt cols (cte, p) strfyNum =
Q.getAltJ . runIdentity . Q.getRow
<$> Q.rawQE dmlTxErrorHandler (Q.fromBuilder sql) (toList p) True
where
aliasIden = Iden $ qualObjectToText qt <> "__mutation_result"
tabFrom = FromIden aliasIden
tabPerm = TablePerm annBoolExpTrue Nothing
selFlds = flip map cols $
\ci -> (fromPGCol $ pgiColumn ci, mkAnnColFieldAsText ci)
sql = toSQL selectWith
selectWith = S.SelectWith [(S.Alias aliasIden, cte)] select
select = S.mkSelect {S.selExtr = [S.Extractor extrExp Nothing]}
extrExp = S.applyJsonBuildObj
[ S.SELit "affected_rows", affRowsSel
, S.SELit "returning_columns", colSel
]
affRowsSel = S.SESelect $
S.mkSelect
{ S.selExtr = [S.Extractor S.countStar Nothing]
, S.selFrom = Just $ S.FromExp [S.FIIden aliasIden]
}
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 20:38:23 +03:00
colSel = S.SESelect $ mkSQLSelect JASMultipleRows $
AnnSelG selFlds tabFrom tabPerm noTableArgs strfyNum
-- | Note:- Using sorted columns is necessary to enable casting the rows returned by VALUES expression to table type.
-- For example, let's consider the table, `CREATE TABLE test (id serial primary key, name text not null, age int)`.
-- The generated values expression should be in order of columns;
-- `SELECT ("row"::table).* VALUES (1, 'Robert', 23) AS "row"`.
mkSelCTEFromColVals
:: (MonadError QErr m)
=> QualifiedTable -> [PGColumnInfo] -> [ColumnValues TxtEncodedPGVal] -> m S.CTE
mkSelCTEFromColVals qt allCols colVals =
S.CTESelect <$> case colVals of
[] -> return selNoRows
_ -> do
tuples <- mapM mkTupsFromColVal colVals
let fromItem = S.FIValues (S.ValuesExp tuples) (S.Alias rowAlias) Nothing
return S.mkSelect
{ S.selExtr = [extractor]
, S.selFrom = Just $ S.FromExp [fromItem]
}
where
rowAlias = Iden "row"
extractor = S.selectStar' $ S.QualIden rowAlias $ Just $ S.TypeAnn $ toSQLTxt qt
sortedCols = sortCols allCols
mkTupsFromColVal colVal =
fmap S.TupleExp $ forM sortedCols $ \ci -> do
let pgCol = pgiColumn ci
val <- onNothing (Map.lookup pgCol colVal) $
throw500 $ "column " <> pgCol <<> " not found in returning values"
pure $ txtEncodedToSQLExp (pgiType ci) val
selNoRows =
S.mkSelect { S.selExtr = [S.selectStar]
, S.selFrom = Just $ S.mkSimpleFromExp qt
, S.selWhere = Just $ S.WhereFrag $ S.BELit False
}
txtEncodedToSQLExp colTy = \case
TENull -> S.SENull
TELit textValue ->
S.withTyAnn (unsafePGColumnToRepresentation colTy) $ S.SELit textValue