graphql-engine/server/src-lib/Hasura/GraphQL/Resolve/Insert.hs

593 lines
22 KiB
Haskell
Raw Normal View History

module Hasura.GraphQL.Resolve.Insert
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
( convertInsert
, convertInsertOne
)
where
import Data.Has
import Hasura.EncJSON
import Hasura.Prelude
backend only insert permissions (rfc #4120) (#4224) * move user info related code to Hasura.User module * the RFC #4120 implementation; insert permissions with admin secret * revert back to old RoleName based schema maps An attempt made to avoid duplication of schema contexts in types if any role doesn't possess any admin secret specific schema * fix compile errors in haskell test * keep 'user_vars' for session variables in http-logs * no-op refacto * tests for admin only inserts * update docs for admin only inserts * updated CHANGELOG.md * default behaviour when admin secret is not set * fix x-hasura-role to X-Hasura-Role in pytests * introduce effective timeout in actions async tests * update docs for admin-secret not configured case * Update docs/graphql/manual/api-reference/schema-metadata-api/permission.rst Co-Authored-By: Marion Schleifer <marion@hasura.io> * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * a complete iteration backend insert permissions accessable via 'x-hasura-backend-privilege' session variable * console changes for backend-only permissions * provide tooltip id; update labels and tooltips; * requested changes * requested changes - remove className from Toggle component - use appropriate function name (capitalizeFirstChar -> capitalize) * use toggle props from definitelyTyped * fix accidental commit * Revert "introduce effective timeout in actions async tests" This reverts commit b7a59c19d643520cfde6af579889e1038038438a. * generate complete schema for both 'default' and 'backend' sessions * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * remove unnecessary import, export Toggle as is * update session variable in tooltip * 'x-hasura-use-backend-only-permissions' variable to switch * update help texts * update docs * update docs * update console help text * regenerate package-lock * serve no backend schema when backend_only: false and header set to true - Few type name refactor as suggested by @0x777 * update CHANGELOG.md * Update CHANGELOG.md * Update CHANGELOG.md * fix a merge bug where a certain entity didn't get removed Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Rishichandra Wawhal <rishi@hasura.io> Co-authored-by: rikinsk <rikin.kachhia@gmail.com> Co-authored-by: Tirumarai Selvan <tiru@hasura.io>
2020-04-24 12:10:53 +03:00
import Hasura.Session
import qualified Data.Aeson as J
import qualified Data.Aeson.Casing as J
import qualified Data.Aeson.TH as J
import qualified Data.Environment as Env
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Data.Sequence as Seq
import qualified Data.Text as T
import qualified Database.PG.Query as Q
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Hasura.RQL.DML.Insert as RI
import qualified Hasura.RQL.DML.Returning as RR
import qualified Hasura.SQL.DML as S
import qualified Hasura.Tracing as Tracing
import Hasura.GraphQL.Resolve.BoolExp
import Hasura.GraphQL.Resolve.Context
import Hasura.GraphQL.Resolve.InputValue
import Hasura.GraphQL.Resolve.Mutation
import Hasura.GraphQL.Resolve.Select
import Hasura.GraphQL.Validate.SelectionSet
import Hasura.GraphQL.Validate.Types
import Hasura.RQL.DML.Insert (insertOrUpdateCheckExpr)
import Hasura.RQL.DML.Internal (convAnnBoolExpPartialSQL, convPartialSQLExp,
sessVarFromCurrentSetting)
import Hasura.RQL.DML.Mutation
import Hasura.RQL.DML.RemoteJoin
import Hasura.RQL.GBoolExp (toSQLBoolExp)
import Hasura.RQL.Types
import Hasura.Server.Version (HasVersion)
import Hasura.SQL.Types
import Hasura.SQL.Value
type ColumnValuesText = ColumnValues TxtEncodedPGVal
newtype InsResp
= InsResp
{ _irResponse :: Maybe J.Object
} deriving (Show, Eq)
$(J.deriveJSON (J.aesonDrop 3 J.snakeCase) ''InsResp)
data AnnIns a
= AnnIns
{ _aiInsObj :: !a
, _aiConflictClause :: !(Maybe RI.ConflictClauseP1)
, _aiCheckCond :: !(AnnBoolExpPartialSQL, Maybe AnnBoolExpPartialSQL)
, _aiTableCols :: ![PGColumnInfo]
, _aiDefVals :: !(Map.HashMap PGCol S.SQLExp)
} deriving (Show, Eq, Functor, Foldable, Traversable)
type SingleObjIns = AnnIns AnnInsObj
type MultiObjIns = AnnIns [AnnInsObj]
multiToSingles :: MultiObjIns -> [SingleObjIns]
multiToSingles = sequenceA
data RelIns a
= RelIns
{ _riAnnIns :: !a
, _riRelInfo :: !RelInfo
} deriving (Show, Eq)
type ObjRelIns = RelIns SingleObjIns
type ArrRelIns = RelIns MultiObjIns
type PGColWithValue = (PGCol, WithScalarType PGScalarValue)
data CTEExp
= CTEExp
{ _iweExp :: !S.CTE
, _iwePrepArgs :: !(Seq.Seq Q.PrepArg)
} deriving (Show, Eq)
data AnnInsObj
= AnnInsObj
{ _aioColumns :: ![PGColWithValue]
, _aioObjRels :: ![ObjRelIns]
, _aioArrRels :: ![ArrRelIns]
} deriving (Show, Eq)
mkAnnInsObj
:: (MonadReusability m, MonadError QErr m, Has InsCtxMap r, MonadReader r m, Has FieldMap r)
=> RelationInfoMap
-> PGColGNameMap
-> AnnGObject
-> m AnnInsObj
mkAnnInsObj relInfoMap allColMap annObj =
foldrM (traverseInsObj relInfoMap allColMap) emptyInsObj $ OMap.toList annObj
where
emptyInsObj = AnnInsObj [] [] []
traverseInsObj
:: (MonadReusability m, MonadError QErr m, Has InsCtxMap r, MonadReader r m, Has FieldMap r)
=> RelationInfoMap
-> PGColGNameMap
-> (G.Name, AnnInpVal)
-> AnnInsObj
-> m AnnInsObj
traverseInsObj rim allColMap (gName, annVal) defVal@(AnnInsObj cols objRels arrRels) =
case _aivValue annVal of
AGScalar{} -> parseValue
AGEnum{} -> parseValue
_ -> parseObject
where
parseValue = do
(_, WithScalarType scalarType maybeScalarValue) <- asPGColumnTypeAndValueM annVal
columnInfo <- onNothing (Map.lookup gName allColMap) $
throw500 "column not found in PGColGNameMap"
let columnName = pgiColumn columnInfo
scalarValue <- maybe (pure $ PGNull scalarType) openOpaqueValue maybeScalarValue
pure $ AnnInsObj ((columnName, WithScalarType scalarType scalarValue):cols) objRels arrRels
parseObject = do
objM <- asObjectM annVal
-- if relational insert input is 'null' then ignore
-- return default value
fmap (fromMaybe defVal) $ forM objM $ \obj -> do
let relNameM = RelName <$> mkNonEmptyText (G.unName gName)
onConflictM = OMap.lookup "on_conflict" obj
relName <- onNothing relNameM $ throw500 "found empty GName String"
dataVal <- onNothing (OMap.lookup "data" obj) $
throw500 "\"data\" object not found"
relInfo <- onNothing (Map.lookup relName rim) $
throw500 $ "relation " <> relName <<> " not found"
let rTable = riRTable relInfo
InsCtx rtColMap checkCond rtDefVals rtRelInfoMap rtUpdPerm <- getInsCtx rTable
let rtCols = Map.elems rtColMap
rtDefValsRes <- mapM (convPartialSQLExp sessVarFromCurrentSetting) rtDefVals
withPathK (G.unName gName) $ case riType relInfo of
ObjRel -> do
dataObj <- asObject dataVal
annDataObj <- mkAnnInsObj rtRelInfoMap rtColMap dataObj
ccM <- forM onConflictM $ parseOnConflict rTable rtUpdPerm rtColMap
let singleObjIns = AnnIns annDataObj ccM (checkCond, rtUpdPerm >>= upfiCheck) rtCols rtDefValsRes
objRelIns = RelIns singleObjIns relInfo
return (AnnInsObj cols (objRelIns:objRels) arrRels)
ArrRel -> do
arrDataVals <- asArray dataVal
let withNonEmptyArrData = do
annDataObjs <- forM arrDataVals $ \arrDataVal -> do
dataObj <- asObject arrDataVal
mkAnnInsObj rtRelInfoMap rtColMap dataObj
ccM <- forM onConflictM $ parseOnConflict rTable rtUpdPerm rtColMap
let multiObjIns = AnnIns annDataObjs ccM (checkCond, rtUpdPerm >>= upfiCheck) rtCols rtDefValsRes
arrRelIns = RelIns multiObjIns relInfo
return (AnnInsObj cols objRels (arrRelIns:arrRels))
-- if array relation insert input data has empty objects
-- then ignore and return default value
bool withNonEmptyArrData (return defVal) $ null arrDataVals
parseOnConflict
:: (MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r)
=> QualifiedTable
-> Maybe UpdPermForIns
-> PGColGNameMap
-> AnnInpVal
-> m RI.ConflictClauseP1
parseOnConflict tn updFiltrM allColMap val = withPathK "on_conflict" $
flip withObject val $ \_ obj -> do
constraint <- RI.CTConstraint <$> parseConstraint obj
updCols <- getUpdCols obj
case updCols of
[] -> return $ RI.CP1DoNothing $ Just constraint
_ -> do
UpdPermForIns _ _ updFiltr preSet <- onNothing updFiltrM $ throw500
"cannot update columns since update permission is not defined"
2019-04-17 12:48:41 +03:00
preSetRes <- mapM (convPartialSQLExp sessVarFromCurrentSetting) preSet
updFltrRes <- traverseAnnBoolExp
(convPartialSQLExp sessVarFromCurrentSetting)
updFiltr
whereExp <- parseWhereExp obj
let updateBoolExp = toSQLBoolExp (S.mkQual tn) updFltrRes
whereCondition = S.BEBin S.AndOp updateBoolExp whereExp
return $ RI.CP1Update constraint updCols preSetRes whereCondition
where
getUpdCols o = do
updColsVal <- onNothing (OMap.lookup "update_columns" o) $ throw500
"\"update_columns\" argument in expected in \"on_conflict\" field "
parseColumns allColMap updColsVal
parseConstraint o = do
v <- onNothing (OMap.lookup "constraint" o) $ throw500
"\"constraint\" is expected, but not found"
(_, enumVal) <- asEnumVal v
return $ ConstraintName $ G.unName $ G.unEnumValue enumVal
parseWhereExp =
OMap.lookup "where"
>>> traverse (parseBoolExp >=> traverse (traverse resolveValTxt))
>>> fmap (maybe (S.BELit True) (toSQLBoolExp (S.mkQual tn)))
toSQLExps
:: (MonadError QErr m, MonadState PrepArgs m)
=> [PGColWithValue]
-> m [(PGCol, S.SQLExp)]
toSQLExps cols =
forM cols $ \(c, v) -> do
prepExp <- prepareColVal v
return (c, prepExp)
mkSQLRow :: Map.HashMap PGCol S.SQLExp -> [(PGCol, S.SQLExp)] -> [S.SQLExp]
mkSQLRow defVals withPGCol = map snd $
flip map (Map.toList defVals) $
\(col, defVal) -> (col,) $ fromMaybe defVal $ Map.lookup col withPGColMap
where
withPGColMap = Map.fromList withPGCol
mkInsertQ
:: MonadError QErr m
=> QualifiedTable
-> Maybe RI.ConflictClauseP1
-> [PGColWithValue]
-> Map.HashMap PGCol S.SQLExp
-> RoleName
-> (AnnBoolExpSQL, Maybe AnnBoolExpSQL)
-> m CTEExp
mkInsertQ tn onConflictM insCols defVals role (insCheck, updCheck) = do
(givenCols, args) <- flip runStateT Seq.Empty $ toSQLExps insCols
let sqlConflict = RI.toSQLConflict <$> onConflictM
sqlExps = mkSQLRow defVals givenCols
valueExp = S.ValuesExp [S.TupleExp sqlExps]
tableCols = Map.keys defVals
sqlInsert =
S.SQLInsert tn tableCols valueExp sqlConflict
. Just
$ S.RetExp
[ S.selectStar
, S.Extractor
(insertOrUpdateCheckExpr tn onConflictM
(toSQLBoolExp (S.QualTable tn) insCheck)
(fmap (toSQLBoolExp (S.QualTable tn)) updCheck))
Nothing
]
adminIns = return (CTEExp (S.CTEInsert sqlInsert) args)
nonAdminInsert = do
let cteIns = S.CTEInsert sqlInsert
return (CTEExp cteIns args)
bool nonAdminInsert adminIns $ isAdmin role
fetchFromColVals
:: MonadError QErr m
=> ColumnValuesText
-> [PGColumnInfo]
-> m [(PGCol, WithScalarType PGScalarValue)]
fetchFromColVals colVal reqCols =
forM reqCols $ \ci -> do
let valM = Map.lookup (pgiColumn ci) colVal
val <- onNothing valM $ throw500 $ "column "
<> pgiColumn ci <<> " not found in given colVal"
pgColVal <- parseTxtEncodedPGValue (pgiType ci) val
return (pgiColumn ci, pgColVal)
-- | validate an insert object based on insert columns,
-- | insert object relations and additional columns from parent
validateInsert
:: (MonadError QErr m)
=> [PGCol] -- ^ inserting columns
-> [RelInfo] -- ^ object relation inserts
-> [PGCol] -- ^ additional fields from parent
-> m ()
validateInsert insCols objRels addCols = do
-- validate insertCols
unless (null insConflictCols) $ throwVE $
"cannot insert " <> showPGCols insConflictCols
<> " columns as their values are already being determined by parent insert"
forM_ objRels $ \relInfo -> do
let lCols = Map.keys $ riMapping relInfo
relName = riName relInfo
relNameTxt = relNameToTxt relName
lColConflicts = lCols `intersect` (addCols <> insCols)
withPathK relNameTxt $ unless (null lColConflicts) $ throwVE $
"cannot insert object relation ship " <> relName
<<> " as " <> showPGCols lColConflicts
<> " column values are already determined"
where
insConflictCols = insCols `intersect` addCols
-- | insert an object relationship and return affected rows
-- | and parent dependent columns
insertObjRel
:: (HasVersion, MonadTx m, MonadIO m, Tracing.MonadTrace m)
=> Env.Environment
-> Bool
-> MutationRemoteJoinCtx
-> RoleName
-> ObjRelIns
-> m (Int, [PGColWithValue])
insertObjRel env strfyNum rjCtx role objRelIns =
withPathK relNameTxt $ do
(affRows, colValM) <- withPathK "data" $ insertObj env strfyNum rjCtx role tn singleObjIns []
colVal <- onNothing colValM $ throw400 NotSupported errMsg
retColsWithVals <- fetchFromColVals colVal rColInfos
let c = mergeListsWith (Map.toList mapCols) retColsWithVals
(\(_, rCol) (col, _) -> rCol == col)
(\(lCol, _) (_, cVal) -> (lCol, cVal))
return (affRows, c)
where
RelIns singleObjIns relInfo = objRelIns
-- multiObjIns = singleToMulti singleObjIns
relName = riName relInfo
relNameTxt = relNameToTxt relName
mapCols = riMapping relInfo
tn = riRTable relInfo
allCols = _aiTableCols singleObjIns
rCols = Map.elems mapCols
rColInfos = getColInfos rCols allCols
errMsg = "cannot proceed to insert object relation "
<> relName <<> " since insert to table "
<> tn <<> " affects zero rows"
decodeEncJSON :: (J.FromJSON a, QErrM m) => EncJSON -> m a
decodeEncJSON =
either (throw500 . T.pack) decodeValue .
J.eitherDecode . encJToLBS
-- | insert an array relationship and return affected rows
insertArrRel
:: (HasVersion, MonadTx m, MonadIO m, Tracing.MonadTrace m)
=> Env.Environment
-> Bool
-> MutationRemoteJoinCtx
-> RoleName
-> [PGColWithValue]
-> ArrRelIns
-> m Int
insertArrRel env strfyNum rjCtx role resCols arrRelIns =
withPathK relNameTxt $ do
let addCols = mergeListsWith resCols (Map.toList colMapping)
(\(col, _) (lCol, _) -> col == lCol)
(\(_, colVal) (_, rCol) -> (rCol, colVal))
resBS <- insertMultipleObjects env strfyNum rjCtx role tn multiObjIns addCols mutOutput "data"
resObj <- decodeEncJSON resBS
onNothing (Map.lookup ("affected_rows" :: T.Text) resObj) $
throw500 "affected_rows not returned in array rel insert"
where
RelIns multiObjIns relInfo = arrRelIns
colMapping = riMapping relInfo
tn = riRTable relInfo
relNameTxt = relNameToTxt $ riName relInfo
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
mutOutput = RR.MOutMultirowFields [("affected_rows", RR.MCount)]
-- | insert an object with object and array relationships
insertObj
:: (HasVersion, MonadTx m, MonadIO m, Tracing.MonadTrace m)
=> Env.Environment
-> Bool
-> MutationRemoteJoinCtx
-> RoleName
-> QualifiedTable
-> SingleObjIns
-> [PGColWithValue] -- ^ additional fields
-> m (Int, Maybe ColumnValuesText)
insertObj env strfyNum rjCtx role tn singleObjIns addCols = do
-- validate insert
validateInsert (map fst cols) (map _riRelInfo objRels) $ map fst addCols
-- insert all object relations and fetch this insert dependent column values
objInsRes <- forM objRels $ insertObjRel env strfyNum rjCtx role
-- prepare final insert columns
let objRelAffRows = sum $ map fst objInsRes
objRelDeterminedCols = concatMap snd objInsRes
finalInsCols = cols <> objRelDeterminedCols <> addCols
-- prepare insert query as with expression
insCheck <- convAnnBoolExpPartialSQL sessVarFromCurrentSetting insCond
updCheck <- traverse (convAnnBoolExpPartialSQL sessVarFromCurrentSetting) updCond
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
CTEExp cte insPArgs <-
mkInsertQ tn onConflictM finalInsCols defVals role (insCheck, updCheck)
MutateResp affRows colVals <- liftTx $ mutateAndFetchCols tn allCols (cte, insPArgs) strfyNum
colValM <- asSingleObject colVals
arrRelAffRows <- bool (withArrRels colValM) (return 0) $ null arrRels
let totAffRows = objRelAffRows + affRows + arrRelAffRows
return (totAffRows, colValM)
where
AnnIns annObj onConflictM (insCond, updCond) allCols defVals = singleObjIns
AnnInsObj cols objRels arrRels = annObj
arrRelDepCols = flip getColInfos allCols $
concatMap (Map.keys . riMapping . _riRelInfo) arrRels
withArrRels colValM = do
colVal <- onNothing colValM $ throw400 NotSupported cannotInsArrRelErr
arrDepColsWithVal <- fetchFromColVals colVal arrRelDepCols
arrInsARows <- forM arrRels $ insertArrRel env strfyNum rjCtx role arrDepColsWithVal
return $ sum arrInsARows
asSingleObject = \case
[] -> pure Nothing
[r] -> pure $ Just r
_ -> throw500 "more than one row returned"
cannotInsArrRelErr =
"cannot proceed to insert array relations since insert to table "
<> tn <<> " affects zero rows"
-- | insert multiple Objects in postgres
insertMultipleObjects
:: ( HasVersion
, MonadTx m
, MonadIO m
, Tracing.MonadTrace m
)
=> Env.Environment
-> Bool
-> MutationRemoteJoinCtx
-> RoleName
-> QualifiedTable
-> MultiObjIns
-> [PGColWithValue] -- ^ additional fields
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
-> RR.MutationOutput
-> T.Text -- ^ error path
-> m EncJSON
insertMultipleObjects env strfyNum rjCtx role tn multiObjIns addCols mutOutput errP =
bool withoutRelsInsert withRelsInsert anyRelsToInsert
where
AnnIns insObjs onConflictM (insCond, updCond) tableColInfos defVals = multiObjIns
singleObjInserts = multiToSingles multiObjIns
insCols = map _aioColumns insObjs
allInsObjRels = concatMap _aioObjRels insObjs
allInsArrRels = concatMap _aioArrRels insObjs
anyRelsToInsert = not $ null allInsArrRels && null allInsObjRels
withErrPath = withPathK errP
-- insert all column rows at one go
withoutRelsInsert = withErrPath $ do
indexedForM_ insCols $ \insCol ->
validateInsert (map fst insCol) [] $ map fst addCols
let withAddCols = flip map insCols $ union addCols
tableCols = Map.keys defVals
(sqlRows, prepArgs) <- flip runStateT Seq.Empty $ do
rowsWithCol <- mapM toSQLExps withAddCols
return $ map (mkSQLRow defVals) rowsWithCol
insCheck <- convAnnBoolExpPartialSQL sessVarFromCurrentSetting insCond
updCheck <- traverse (convAnnBoolExpPartialSQL sessVarFromCurrentSetting) updCond
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
let insQP1 = RI.InsertQueryP1 tn tableCols sqlRows onConflictM
(insCheck, updCheck) mutOutput tableColInfos
p1 = (insQP1, prepArgs)
RI.execInsertQuery env strfyNum (Just rjCtx) p1
-- insert each object with relations
withRelsInsert = withErrPath $ do
insResps <- indexedForM singleObjInserts $ \objIns ->
insertObj env strfyNum rjCtx role tn objIns addCols
let affRows = sum $ map fst insResps
backend only insert permissions (rfc #4120) (#4224) * move user info related code to Hasura.User module * the RFC #4120 implementation; insert permissions with admin secret * revert back to old RoleName based schema maps An attempt made to avoid duplication of schema contexts in types if any role doesn't possess any admin secret specific schema * fix compile errors in haskell test * keep 'user_vars' for session variables in http-logs * no-op refacto * tests for admin only inserts * update docs for admin only inserts * updated CHANGELOG.md * default behaviour when admin secret is not set * fix x-hasura-role to X-Hasura-Role in pytests * introduce effective timeout in actions async tests * update docs for admin-secret not configured case * Update docs/graphql/manual/api-reference/schema-metadata-api/permission.rst Co-Authored-By: Marion Schleifer <marion@hasura.io> * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * a complete iteration backend insert permissions accessable via 'x-hasura-backend-privilege' session variable * console changes for backend-only permissions * provide tooltip id; update labels and tooltips; * requested changes * requested changes - remove className from Toggle component - use appropriate function name (capitalizeFirstChar -> capitalize) * use toggle props from definitelyTyped * fix accidental commit * Revert "introduce effective timeout in actions async tests" This reverts commit b7a59c19d643520cfde6af579889e1038038438a. * generate complete schema for both 'default' and 'backend' sessions * Apply suggestions from code review Co-Authored-By: Marion Schleifer <marion@hasura.io> * remove unnecessary import, export Toggle as is * update session variable in tooltip * 'x-hasura-use-backend-only-permissions' variable to switch * update help texts * update docs * update docs * update console help text * regenerate package-lock * serve no backend schema when backend_only: false and header set to true - Few type name refactor as suggested by @0x777 * update CHANGELOG.md * Update CHANGELOG.md * Update CHANGELOG.md * fix a merge bug where a certain entity didn't get removed Co-authored-by: Marion Schleifer <marion@hasura.io> Co-authored-by: Rishichandra Wawhal <rishi@hasura.io> Co-authored-by: rikinsk <rikin.kachhia@gmail.com> Co-authored-by: Tirumarai Selvan <tiru@hasura.io>
2020-04-24 12:10:53 +03:00
columnValues = mapMaybe snd insResps
cteExp <- mkSelCTEFromColVals tn tableColInfos columnValues
let (mutOutputRJ, remoteJoins) = getRemoteJoinsMutationOutput mutOutput
sqlQuery = Q.fromBuilder $ toSQL $
RR.mkMutationOutputExp tn tableColInfos (Just affRows) cteExp mutOutputRJ strfyNum
executeMutationOutputQuery env sqlQuery [] $ (,rjCtx) <$> remoteJoins
prefixErrPath :: (MonadError QErr m) => Field -> m a -> m a
prefixErrPath fld =
withPathK "selectionSet" . fieldAsPath fld . withPathK "args"
convertInsert
:: ( HasVersion
, MonadReusability m
, MonadError QErr m
, MonadReader r m
, Has FieldMap r
, Has OrdByCtx r
, Has SQLGenCtx r
, Has InsCtxMap r
, MonadIO tx
, MonadTx tx
, Tracing.MonadTrace tx
2019-04-17 12:48:41 +03:00
)
=> Env.Environment
-> MutationRemoteJoinCtx
-> RoleName
-> QualifiedTable -- table
-> Field -- the mutation field
-> m (tx EncJSON)
convertInsert env rjCtx role tn fld = prefixErrPath fld $ do
selSet <- asObjectSelectionSet $ _fSelSet fld
mutOutputUnres <- RR.MOutMultirowFields <$> resolveMutationFields (_fType fld) selSet
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
mutOutputRes <- RR.traverseMutationOutput resolveValTxt mutOutputUnres
annVals <- withArg arguments "objects" asArray
-- if insert input objects is empty array then
-- do not perform insert and return mutation response
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
bool (withNonEmptyObjs annVals mutOutputRes)
(withEmptyObjs mutOutputRes) $ null annVals
where
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
withNonEmptyObjs annVals mutOutput = do
InsCtx tableColMap checkCond defValMap relInfoMap updPerm <- getInsCtx tn
annObjs <- mapM asObject annVals
annInsObjs <- forM annObjs $ mkAnnInsObj relInfoMap tableColMap
conflictClauseM <- forM onConflictM $ parseOnConflict tn updPerm tableColMap
2019-04-17 12:48:41 +03:00
defValMapRes <- mapM (convPartialSQLExp sessVarFromCurrentSetting)
defValMap
let multiObjIns = AnnIns annInsObjs conflictClauseM (checkCond, updPerm >>= upfiCheck)
tableCols defValMapRes
tableCols = Map.elems tableColMap
strfyNum <- stringifyNum <$> asks getter
return $ prefixErrPath fld $ insertMultipleObjects env strfyNum rjCtx role tn
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
multiObjIns [] mutOutput "objects"
withEmptyObjs mutOutput =
return $ return $ buildEmptyMutResp mutOutput
arguments = _fArguments fld
onConflictM = Map.lookup "on_conflict" arguments
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
convertInsertOne
:: ( HasVersion
, MonadReusability m
, MonadError QErr m
, MonadReader r m
, Has FieldMap r
, Has OrdByCtx r
, Has SQLGenCtx r
, Has InsCtxMap r
, MonadIO tx
, MonadTx tx
, Tracing.MonadTrace tx
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
)
=> Env.Environment
-> MutationRemoteJoinCtx
-> RoleName
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
-> QualifiedTable -- table
-> Field -- the mutation field
-> m (tx EncJSON)
convertInsertOne env rjCtx role qt field = prefixErrPath field $ do
selSet <- asObjectSelectionSet $ _fSelSet field
tableSelFields <- processTableSelectionSet (_fType field) selSet
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
let mutationOutputUnresolved = RR.MOutSinglerowObject tableSelFields
mutationOutputResolved <- RR.traverseMutationOutput resolveValTxt mutationOutputUnresolved
annInputObj <- withArg arguments "object" asObject
InsCtx tableColMap checkCond defValMap relInfoMap updPerm <- getInsCtx qt
annInsertObj <- mkAnnInsObj relInfoMap tableColMap annInputObj
conflictClauseM <- forM (Map.lookup "on_conflict" arguments) $ parseOnConflict qt updPerm tableColMap
defValMapRes <- mapM (convPartialSQLExp sessVarFromCurrentSetting) defValMap
let multiObjIns = AnnIns [annInsertObj] conflictClauseM (checkCond, updPerm >>= upfiCheck)
tableCols defValMapRes
tableCols = Map.elems tableColMap
strfyNum <- stringifyNum <$> asks getter
pure $ prefixErrPath field $ insertMultipleObjects env strfyNum rjCtx role qt
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
multiObjIns [] mutationOutputResolved "object"
where
arguments = _fArguments field
-- helper functions
getInsCtx
:: (MonadError QErr m, MonadReader r m, Has InsCtxMap r)
=> QualifiedTable -> m InsCtx
getInsCtx tn = do
ctxMap <- asks getter
insCtx <- onNothing (Map.lookup tn ctxMap) $
throw500 $ "table " <> tn <<> " not found"
let defValMap = fmap PSESQLExp $ S.mkColDefValMap $ map pgiColumn $
Map.elems $ icAllCols insCtx
setCols = icSet insCtx
return $ insCtx {icSet = Map.union setCols defValMap}
mergeListsWith
:: [a] -> [b] -> (a -> b -> Bool) -> (a -> b -> c) -> [c]
mergeListsWith _ [] _ _ = []
mergeListsWith [] _ _ _ = []
mergeListsWith (x:xs) l b f = case find (b x) l of
Nothing -> mergeListsWith xs l b f
Just y -> f x y : mergeListsWith xs l b f