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

218 lines
8.3 KiB
Haskell
Raw Normal View History

2018-06-27 16:11:32 +03:00
module Hasura.GraphQL.Resolve.Mutation
( convertUpdate
, convertDelete
, convertMutResp
, buildEmptyMutResp
2018-06-27 16:11:32 +03:00
) where
import Data.Has
2018-06-27 16:11:32 +03:00
import Hasura.Prelude
import qualified Data.Aeson as J
import qualified Data.HashMap.Strict as Map
import qualified Data.HashMap.Strict.InsOrd as OMap
2018-06-27 16:11:32 +03:00
import qualified Language.GraphQL.Draft.Syntax as G
import qualified Hasura.RQL.DML.Delete as RD
import qualified Hasura.RQL.DML.Returning as RR
import qualified Hasura.RQL.DML.Update as RU
2019-04-17 12:48:41 +03:00
import qualified Hasura.RQL.DML.Select as RS
import qualified Hasura.SQL.DML as S
2018-06-27 16:11:32 +03:00
import Hasura.EncJSON
2018-06-27 16:11:32 +03:00
import Hasura.GraphQL.Resolve.BoolExp
import Hasura.GraphQL.Resolve.Context
import Hasura.GraphQL.Resolve.InputValue
2019-04-17 12:48:41 +03:00
import Hasura.GraphQL.Resolve.Select (fromSelSet)
2018-06-27 16:11:32 +03:00
import Hasura.GraphQL.Validate.Field
import Hasura.GraphQL.Validate.Types
import Hasura.RQL.Types
import Hasura.SQL.Types
import Hasura.SQL.Value
2018-06-27 16:11:32 +03:00
convertMutResp
:: ( MonadReusability m, MonadError QErr m, MonadReader r m, Has FieldMap r
, Has OrdByCtx r, Has SQLGenCtx r
)
2019-04-17 12:48:41 +03:00
=> G.NamedType -> SelSet -> m (RR.MutFldsG UnresolvedVal)
convertMutResp ty selSet =
withSelSet selSet $ \fld -> case _fName fld of
"__typename" -> return $ RR.MExp $ G.unName $ G.unNamedType ty
"affected_rows" -> return RR.MCount
2019-04-17 12:48:41 +03:00
"returning" -> do
annFlds <- fromSelSet (_fType fld) $ _fSelSet fld
annFldsResolved <- traverse
(traverse (RS.traverseAnnFld convertUnresolvedVal)) annFlds
return $ RR.MRet annFldsResolved
G.Name t -> throw500 $ "unexpected field in mutation resp : " <> t
2019-04-17 12:48:41 +03:00
where
convertUnresolvedVal = \case
UVPG annPGVal -> UVSQL <$> txtConverter annPGVal
UVSessVar colTy sessVar -> pure $ UVSessVar colTy sessVar
UVSQL sqlExp -> pure $ UVSQL sqlExp
2018-06-27 16:11:32 +03:00
convertRowObj
:: (MonadReusability m, MonadError QErr m)
=> PGColGNameMap
-> AnnInpVal
2019-04-17 12:48:41 +03:00
-> m [(PGCol, UnresolvedVal)]
convertRowObj colGNameMap val =
flip withObject val $ \_ obj ->
forM (OMap.toList obj) $ \(k, v) -> do
prepExpM <- fmap mkParameterizablePGValue <$> asPGColumnValueM v
pgCol <- pgiColumn <$> resolvePGCol colGNameMap k
let prepExp = fromMaybe (UVSQL S.SENull) prepExpM
return (pgCol, prepExp)
2018-06-27 16:11:32 +03:00
type ApplySQLOp = (PGCol, S.SQLExp) -> S.SQLExp
rhsExpOp :: S.SQLOp -> S.TypeAnn -> ApplySQLOp
rhsExpOp op annTy (col, e) =
S.mkSQLOpExp op (S.SEIden $ toIden col) annExp
where
annExp = S.SETyAnn e annTy
lhsExpOp :: S.SQLOp -> S.TypeAnn -> ApplySQLOp
lhsExpOp op annTy (col, e) =
S.mkSQLOpExp op annExp $ S.SEIden $ toIden col
where
annExp = S.SETyAnn e annTy
convObjWithOp
:: (MonadReusability m, MonadError QErr m)
=> PGColGNameMap -> ApplySQLOp -> AnnInpVal -> m [(PGCol, UnresolvedVal)]
convObjWithOp colGNameMap opFn val =
flip withObject val $ \_ obj -> forM (OMap.toList obj) $ \(k, v) -> do
colVal <- openOpaqueValue =<< asPGColumnValue v
pgCol <- pgiColumn <$> resolvePGCol colGNameMap k
-- TODO: why are we using txtEncoder here?
let encVal = txtEncoder $ pstValue $ _apvValue colVal
sqlExp = opFn (pgCol, encVal)
2019-04-17 12:48:41 +03:00
return (pgCol, UVSQL sqlExp)
convDeleteAtPathObj
:: (MonadReusability m, MonadError QErr m)
=> PGColGNameMap -> AnnInpVal -> m [(PGCol, UnresolvedVal)]
convDeleteAtPathObj colGNameMap val =
flip withObject val $ \_ obj -> forM (OMap.toList obj) $ \(k, v) -> do
vals <- traverse (openOpaqueValue <=< asPGColumnValue) =<< asArray v
pgCol <- pgiColumn <$> resolvePGCol colGNameMap k
let valExps = map (txtEncoder . pstValue . _apvValue) vals
annEncVal = S.SETyAnn (S.SEArray valExps) S.textArrTypeAnn
sqlExp = S.SEOpApp S.jsonbDeleteAtPathOp
[S.SEIden $ toIden pgCol, annEncVal]
2019-04-17 12:48:41 +03:00
return (pgCol, UVSQL sqlExp)
convertUpdateP1
:: ( MonadReusability m, MonadError QErr m
, MonadReader r m, Has FieldMap r
, Has OrdByCtx r, Has SQLGenCtx r
)
=> UpdOpCtx -- the update context
2018-06-27 16:11:32 +03:00
-> Field -- the mutation field
2019-04-17 12:48:41 +03:00
-> m (RU.AnnUpdG UnresolvedVal)
convertUpdateP1 opCtx fld = do
2018-06-27 16:11:32 +03:00
-- a set expression is same as a row object
setExpM <- withArgM args "_set" $ convertRowObj colGNameMap
-- where bool expression to filter column
2019-04-17 12:48:41 +03:00
whereExp <- withArg args "where" parseBoolExp
-- increment operator on integer columns
incExpM <- withArgM args "_inc" $
convObjWithOp' $ rhsExpOp S.incOp S.intTypeAnn
-- append jsonb value
appendExpM <- withArgM args "_append" $
convObjWithOp' $ rhsExpOp S.jsonbConcatOp S.jsonbTypeAnn
-- prepend jsonb value
prependExpM <- withArgM args "_prepend" $
convObjWithOp' $ lhsExpOp S.jsonbConcatOp S.jsonbTypeAnn
-- delete a key in jsonb object
deleteKeyExpM <- withArgM args "_delete_key" $
convObjWithOp' $ rhsExpOp S.jsonbDeleteOp S.textTypeAnn
-- delete an element in jsonb array
deleteElemExpM <- withArgM args "_delete_elem" $
convObjWithOp' $ rhsExpOp S.jsonbDeleteOp S.intTypeAnn
-- delete at path in jsonb value
deleteAtPathExpM <- withArgM args "_delete_at_path" $ convDeleteAtPathObj colGNameMap
2019-04-17 12:48:41 +03:00
mutFlds <- convertMutResp (_fType fld) $ _fSelSet fld
let resolvedPreSetItems =
Map.toList $ fmap partialSQLExpToUnresolvedVal preSetCols
let updExpsM = [ setExpM, incExpM, appendExpM, prependExpM
, deleteKeyExpM, deleteElemExpM, deleteAtPathExpM
]
2019-04-17 12:48:41 +03:00
setItems = resolvedPreSetItems ++ concat (catMaybes updExpsM)
-- atleast one of update operators is expected
-- or preSetItems shouldn't be empty
-- this is not equivalent to (null setItems)
2019-04-17 12:48:41 +03:00
unless (any isJust updExpsM || not (null resolvedPreSetItems)) $ throwVE $
"atleast any one of _set, _inc, _append, _prepend, "
<> "_delete_key, _delete_elem and "
<> "_delete_at_path operator is expected"
2019-04-17 12:48:41 +03:00
let unresolvedPermFltr = fmapAnnBoolExp partialSQLExpToUnresolvedVal filterExp
return $ RU.AnnUpd tn setItems
(unresolvedPermFltr, whereExp) mutFlds allCols
2018-06-27 16:11:32 +03:00
where
convObjWithOp' = convObjWithOp colGNameMap
allCols = Map.elems colGNameMap
UpdOpCtx tn _ colGNameMap filterExp preSetCols = opCtx
2018-06-27 16:11:32 +03:00
args = _fArguments fld
convertUpdate
:: ( MonadReusability m, MonadError QErr m
2019-04-17 12:48:41 +03:00
, MonadReader r m, Has FieldMap r
, Has OrdByCtx r, Has SQLGenCtx r
)
=> UpdOpCtx -- the update context
-> Field -- the mutation field
2019-04-17 12:48:41 +03:00
-> m RespTx
convertUpdate opCtx fld = do
2019-04-17 12:48:41 +03:00
annUpdUnresolved <- convertUpdateP1 opCtx fld
(annUpdResolved, prepArgs) <- withPrepArgs $ RU.traverseAnnUpd
resolveValPrep annUpdUnresolved
strfyNum <- stringifyNum <$> asks getter
2019-04-17 12:48:41 +03:00
let whenNonEmptyItems = return $ RU.updateQueryToTx strfyNum
(annUpdResolved, prepArgs)
whenEmptyItems = return $ return $
2019-04-17 12:48:41 +03:00
buildEmptyMutResp $ RU.uqp1MutFlds annUpdResolved
-- if there are not set items then do not perform
-- update and return empty mutation response
2019-04-17 12:48:41 +03:00
bool whenNonEmptyItems whenEmptyItems $ null $ RU.uqp1SetExps annUpdResolved
2018-06-27 16:11:32 +03:00
convertDelete
:: ( MonadReusability m, MonadError QErr m
2019-04-17 12:48:41 +03:00
, MonadReader r m, Has FieldMap r
, Has OrdByCtx r, Has SQLGenCtx r
)
=> DelOpCtx -- the delete context
2018-06-27 16:11:32 +03:00
-> Field -- the mutation field
2019-04-17 12:48:41 +03:00
-> m RespTx
convertDelete opCtx fld = do
2019-04-17 12:48:41 +03:00
whereExp <- withArg (_fArguments fld) "where" parseBoolExp
mutFlds <- convertMutResp (_fType fld) $ _fSelSet fld
let unresolvedPermFltr =
fmapAnnBoolExp partialSQLExpToUnresolvedVal filterExp
annDelUnresolved = RD.AnnDel tn (unresolvedPermFltr, whereExp)
mutFlds allCols
(annDelResolved, prepArgs) <- withPrepArgs $ RD.traverseAnnDel
resolveValPrep annDelUnresolved
strfyNum <- stringifyNum <$> asks getter
2019-04-17 12:48:41 +03:00
return $ RD.deleteQueryToTx strfyNum (annDelResolved, prepArgs)
where
DelOpCtx tn _ filterExp allCols = opCtx
-- | build mutation response for empty objects
buildEmptyMutResp :: RR.MutFlds -> EncJSON
buildEmptyMutResp = mkTx
where
mkTx = encJFromJValue . OMap.fromList . map (second convMutFld)
-- generate empty mutation response
convMutFld = \case
RR.MCount -> J.toJSON (0 :: Int)
RR.MExp e -> J.toJSON e
RR.MRet _ -> J.toJSON ([] :: [J.Value])