graphql-engine/server/src-lib/Hasura/RQL/DML/Delete.hs
Robert fe035125f4 server: drop LazyTxT newtype
This is a follow-up to #1959.

Today, I spent a while in review figuring out that a harmless PR change didn't do anything,
because it was moving from a `runLazy...` to something without the `Lazy`. So let's get
that source of confusion removed.

This should be a bit easier to review commit by commit, since some of the functions had
confusing names. (E.g. there was a misnamed `Migrate.Internal.runTx` before.)

The change should be a no-op.

https://github.com/hasura/graphql-engine-mono/pull/2335

GitOrigin-RevId: 0f284c4c0f814482d7827e7732a6d49e7735b302
2021-09-15 20:46:45 +00:00

115 lines
3.9 KiB
Haskell

{-# LANGUAGE ScopedTypeVariables #-}
module Hasura.RQL.DML.Delete
( validateDeleteQWith
, validateDeleteQ
, AnnDelG(..)
, AnnDel
, execDeleteQuery
, runDelete
) where
import Hasura.Prelude
import qualified Data.Sequence as DS
import qualified Data.Tagged as Tagged
import qualified Database.PG.Query as Q
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson
import qualified Hasura.Backends.Postgres.SQL.DML as S
import qualified Hasura.Tracing as Tracing
import Hasura.Backends.Postgres.Connection
import Hasura.Backends.Postgres.Execute.Mutation
import Hasura.Backends.Postgres.Translate.Returning
import Hasura.Backends.Postgres.Types.Table
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.QueryTags
import Hasura.RQL.DML.Internal
import Hasura.RQL.DML.Types
import Hasura.RQL.IR.Delete
import Hasura.RQL.Types
import Hasura.Session
import Hasura.GraphQL.Execute.Backend
validateDeleteQWith
:: (UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m)
=> SessionVariableBuilder ('Postgres 'Vanilla) m
-> (ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp)
-> DeleteQuery
-> m (AnnDel ('Postgres 'Vanilla))
validateDeleteQWith sessVarBldr prepValBldr
(DeleteQuery tableName _ rqlBE mRetCols) = do
tableInfo <- askTabInfoSource tableName
let coreInfo = _tiCoreInfo tableInfo
-- If table is view then check if it deletable
mutableView tableName viIsDeletable
(_tciViewInfo coreInfo) "deletable"
-- Check if the role has delete permissions
delPerm <- askDelPermInfo tableInfo
-- Check if all dependent headers are present
validateHeaders $ dpiRequiredHeaders delPerm
-- Check if select is allowed
selPerm <- modifyErr (<> selNecessaryMsg) $
askSelPermInfo tableInfo
let fieldInfoMap = _tciFieldInfoMap coreInfo
allCols = getCols fieldInfoMap
-- convert the returning cols into sql returing exp
mAnnRetCols <- forM mRetCols $ \retCols ->
withPathK "returning" $ checkRetCols fieldInfoMap selPerm retCols
-- convert the where clause
annSQLBoolExp <- withPathK "where" $
convBoolExp fieldInfoMap selPerm rqlBE sessVarBldr tableName (valueParserWithCollectableType prepValBldr)
resolvedDelFltr <- convAnnBoolExpPartialSQL sessVarBldr $
dpiFilter delPerm
return $ AnnDel tableName
(resolvedDelFltr, annSQLBoolExp)
(mkDefaultMutFlds mAnnRetCols) allCols
where
selNecessaryMsg =
"; \"delete\" is only allowed if the role "
<> "has \"select\" permission as \"where\" can't be used "
<> "without \"select\" permission on the table"
validateDeleteQ
:: (QErrM m, UserInfoM m, CacheRM m)
=> DeleteQuery -> m (AnnDel ('Postgres 'Vanilla), DS.Seq Q.PrepArg)
validateDeleteQ query = do
let source = doSource query
tableCache :: TableCache ('Postgres 'Vanilla) <- askTableCache source
flip runTableCacheRT (source, tableCache) $ runDMLP1T $
validateDeleteQWith sessVarFromCurrentSetting binRHSBuilder query
runDelete
:: forall m
. ( QErrM m, UserInfoM m, CacheRM m
, HasServerConfigCtx m, MonadIO m
, Tracing.MonadTrace m, MonadBaseControl IO m
, MetadataM m, MonadQueryTags m)
=> DeleteQuery
-> m EncJSON
runDelete q = do
sourceConfig <- askSourceConfig @('Postgres 'Vanilla) (doSource q)
strfyNum <- stringifyNum . _sccSQLGenCtx <$> askServerConfigCtx
userInfo <- askUserInfo
let queryTags = QueryTagsComment $ Tagged.untag $ createQueryTags @m Nothing (encodeOptionalQueryTags Nothing)
validateDeleteQ q
>>= runTxWithCtx (_pscExecCtx sourceConfig) Q.ReadWrite
. flip runReaderT queryTags . execDeleteQuery strfyNum userInfo