module Hasura.RQL.DML.Delete
( validateDeleteQWith,
validateDeleteQ,
AnnDelG (..),
AnnDel,
execDeleteQuery,
runDelete,
)
where
import Control.Lens ((^?))
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.Aeson
import Data.Sequence qualified as DS
import Database.PG.Query qualified as PG
import Hasura.Backends.Postgres.Connection
import Hasura.Backends.Postgres.Execute.Mutation
import Hasura.Backends.Postgres.SQL.DML qualified as S
import Hasura.Backends.Postgres.Translate.Returning
import Hasura.Backends.Postgres.Types.Table
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.Prelude
import Hasura.QueryTags
import Hasura.RQL.DML.Internal
import Hasura.RQL.DML.Types
import Hasura.RQL.IR.Delete
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Column
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.SchemaCache
import Hasura.Session
import Hasura.Tracing qualified as Tracing
validateDeleteQWith ::
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
SessionVariableBuilder m ->
(ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp) ->
DeleteQuery ->
m (AnnDel ('Postgres 'Vanilla))
validateDeleteQWith :: forall (m :: * -> *).
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
SessionVariableBuilder m
-> (ColumnType ('Postgres 'Vanilla) -> Value -> m SQLExp)
-> DeleteQuery
-> m (AnnDel ('Postgres 'Vanilla))
validateDeleteQWith
SessionVariableBuilder m
sessVarBldr
ColumnType ('Postgres 'Vanilla) -> Value -> m SQLExp
prepValBldr
(DeleteQuery QualifiedTable
tableName SourceName
_ BoolExp ('Postgres 'Vanilla)
rqlBE Maybe [PGCol]
mRetCols) = do
TableInfo ('Postgres 'Vanilla)
tableInfo <- TableName ('Postgres 'Vanilla)
-> m (TableInfo ('Postgres 'Vanilla))
forall (m :: * -> *).
(QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
TableName ('Postgres 'Vanilla)
-> m (TableInfo ('Postgres 'Vanilla))
askTableInfoSource TableName ('Postgres 'Vanilla)
QualifiedTable
tableName
let coreInfo :: TableCoreInfo ('Postgres 'Vanilla)
coreInfo = TableInfo ('Postgres 'Vanilla)
-> TableCoreInfo ('Postgres 'Vanilla)
forall (b :: BackendType). TableInfo b -> TableCoreInfo b
_tiCoreInfo TableInfo ('Postgres 'Vanilla)
tableInfo
QualifiedTable
-> (ViewInfo -> Bool) -> Maybe ViewInfo -> Text -> m ()
forall (m :: * -> *).
MonadError QErr m =>
QualifiedTable
-> (ViewInfo -> Bool) -> Maybe ViewInfo -> Text -> m ()
mutableView
QualifiedTable
tableName
ViewInfo -> Bool
viIsDeletable
(TableCoreInfo ('Postgres 'Vanilla) -> Maybe ViewInfo
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> Maybe ViewInfo
_tciViewInfo TableCoreInfo ('Postgres 'Vanilla)
coreInfo)
Text
"deletable"
DelPermInfo ('Postgres 'Vanilla)
delPerm <- TableInfo ('Postgres 'Vanilla)
-> m (DelPermInfo ('Postgres 'Vanilla))
forall (m :: * -> *).
(UserInfoM m, QErrM m) =>
TableInfo ('Postgres 'Vanilla)
-> m (DelPermInfo ('Postgres 'Vanilla))
askDelPermInfo TableInfo ('Postgres 'Vanilla)
tableInfo
HashSet Text -> m ()
forall (m :: * -> *).
(UserInfoM m, QErrM m) =>
HashSet Text -> m ()
validateHeaders (HashSet Text -> m ()) -> HashSet Text -> m ()
forall a b. (a -> b) -> a -> b
$ DelPermInfo ('Postgres 'Vanilla) -> HashSet Text
forall (b :: BackendType). DelPermInfo b -> HashSet Text
dpiRequiredHeaders DelPermInfo ('Postgres 'Vanilla)
delPerm
SelPermInfo ('Postgres 'Vanilla)
selPerm <-
(Text -> Text)
-> m (SelPermInfo ('Postgres 'Vanilla))
-> m (SelPermInfo ('Postgres 'Vanilla))
forall (m :: * -> *) a. QErrM m => (Text -> Text) -> m a -> m a
modifyErr (Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
selNecessaryMsg)
(m (SelPermInfo ('Postgres 'Vanilla))
-> m (SelPermInfo ('Postgres 'Vanilla)))
-> m (SelPermInfo ('Postgres 'Vanilla))
-> m (SelPermInfo ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ TableInfo ('Postgres 'Vanilla)
-> m (SelPermInfo ('Postgres 'Vanilla))
forall (m :: * -> *).
(UserInfoM m, QErrM m) =>
TableInfo ('Postgres 'Vanilla)
-> m (SelPermInfo ('Postgres 'Vanilla))
askSelPermInfo TableInfo ('Postgres 'Vanilla)
tableInfo
let fieldInfoMap :: FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
fieldInfoMap = TableCoreInfo ('Postgres 'Vanilla)
-> FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
forall (b :: BackendType) field primaryKeyColumn.
TableCoreInfoG b field primaryKeyColumn -> FieldInfoMap field
_tciFieldInfoMap TableCoreInfo ('Postgres 'Vanilla)
coreInfo
allCols :: [ColumnInfo ('Postgres 'Vanilla)]
allCols = (StructuredColumnInfo ('Postgres 'Vanilla)
-> Maybe (ColumnInfo ('Postgres 'Vanilla)))
-> [StructuredColumnInfo ('Postgres 'Vanilla)]
-> [ColumnInfo ('Postgres 'Vanilla)]
forall a b. (a -> Maybe b) -> [a] -> [b]
forall (f :: * -> *) a b.
Filterable f =>
(a -> Maybe b) -> f a -> f b
mapMaybe (StructuredColumnInfo ('Postgres 'Vanilla)
-> Getting
(First (ColumnInfo ('Postgres 'Vanilla)))
(StructuredColumnInfo ('Postgres 'Vanilla))
(ColumnInfo ('Postgres 'Vanilla))
-> Maybe (ColumnInfo ('Postgres 'Vanilla))
forall s a. s -> Getting (First a) s a -> Maybe a
^? Getting
(First (ColumnInfo ('Postgres 'Vanilla)))
(StructuredColumnInfo ('Postgres 'Vanilla))
(ColumnInfo ('Postgres 'Vanilla))
forall (b :: BackendType) (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p (ColumnInfo b) (f (ColumnInfo b))
-> p (StructuredColumnInfo b) (f (StructuredColumnInfo b))
_SCIScalarColumn) ([StructuredColumnInfo ('Postgres 'Vanilla)]
-> [ColumnInfo ('Postgres 'Vanilla)])
-> [StructuredColumnInfo ('Postgres 'Vanilla)]
-> [ColumnInfo ('Postgres 'Vanilla)]
forall a b. (a -> b) -> a -> b
$ FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> [StructuredColumnInfo ('Postgres 'Vanilla)]
forall (backend :: BackendType).
FieldInfoMap (FieldInfo backend) -> [StructuredColumnInfo backend]
getCols FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
fieldInfoMap
Maybe [ColumnInfo ('Postgres 'Vanilla)]
mAnnRetCols <- Maybe [PGCol]
-> ([PGCol] -> m [ColumnInfo ('Postgres 'Vanilla)])
-> m (Maybe [ColumnInfo ('Postgres 'Vanilla)])
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM Maybe [PGCol]
mRetCols (([PGCol] -> m [ColumnInfo ('Postgres 'Vanilla)])
-> m (Maybe [ColumnInfo ('Postgres 'Vanilla)]))
-> ([PGCol] -> m [ColumnInfo ('Postgres 'Vanilla)])
-> m (Maybe [ColumnInfo ('Postgres 'Vanilla)])
forall a b. (a -> b) -> a -> b
$ \[PGCol]
retCols ->
Text
-> m [ColumnInfo ('Postgres 'Vanilla)]
-> m [ColumnInfo ('Postgres 'Vanilla)]
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"returning" (m [ColumnInfo ('Postgres 'Vanilla)]
-> m [ColumnInfo ('Postgres 'Vanilla)])
-> m [ColumnInfo ('Postgres 'Vanilla)]
-> m [ColumnInfo ('Postgres 'Vanilla)]
forall a b. (a -> b) -> a -> b
$ FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> SelPermInfo ('Postgres 'Vanilla)
-> [PGCol]
-> m [ColumnInfo ('Postgres 'Vanilla)]
forall (m :: * -> *).
(UserInfoM m, QErrM m) =>
FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> SelPermInfo ('Postgres 'Vanilla)
-> [PGCol]
-> m [ColumnInfo ('Postgres 'Vanilla)]
checkRetCols FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
fieldInfoMap SelPermInfo ('Postgres 'Vanilla)
selPerm [PGCol]
retCols
AnnBoolExp ('Postgres 'Vanilla) SQLExp
annSQLBoolExp <-
Text
-> m (AnnBoolExp ('Postgres 'Vanilla) SQLExp)
-> m (AnnBoolExp ('Postgres 'Vanilla) SQLExp)
forall (m :: * -> *) a. QErrM m => Text -> m a -> m a
withPathK Text
"where"
(m (AnnBoolExp ('Postgres 'Vanilla) SQLExp)
-> m (AnnBoolExp ('Postgres 'Vanilla) SQLExp))
-> m (AnnBoolExp ('Postgres 'Vanilla) SQLExp)
-> m (AnnBoolExp ('Postgres 'Vanilla) SQLExp)
forall a b. (a -> b) -> a -> b
$ FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> SelPermInfo ('Postgres 'Vanilla)
-> BoolExp ('Postgres 'Vanilla)
-> SessionVariableBuilder m
-> FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> ValueParser
('Postgres 'Vanilla) m (SQLExpression ('Postgres 'Vanilla))
-> m (AnnBoolExpSQL ('Postgres 'Vanilla))
forall (m :: * -> *).
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> SelPermInfo ('Postgres 'Vanilla)
-> BoolExp ('Postgres 'Vanilla)
-> SessionVariableBuilder m
-> FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
-> ValueParser
('Postgres 'Vanilla) m (SQLExpression ('Postgres 'Vanilla))
-> m (AnnBoolExpSQL ('Postgres 'Vanilla))
convBoolExp FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
fieldInfoMap SelPermInfo ('Postgres 'Vanilla)
selPerm BoolExp ('Postgres 'Vanilla)
rqlBE SessionVariableBuilder m
sessVarBldr FieldInfoMap (FieldInfo ('Postgres 'Vanilla))
fieldInfoMap ((ColumnType ('Postgres 'Vanilla) -> Value -> m SQLExp)
-> CollectableType (ColumnType ('Postgres 'Vanilla))
-> Value
-> m SQLExp
forall (m :: * -> *).
MonadError QErr m =>
(ColumnType ('Postgres 'Vanilla) -> Value -> m SQLExp)
-> CollectableType (ColumnType ('Postgres 'Vanilla))
-> Value
-> m SQLExp
valueParserWithCollectableType ColumnType ('Postgres 'Vanilla) -> Value -> m SQLExp
prepValBldr)
AnnBoolExp ('Postgres 'Vanilla) SQLExp
resolvedDelFltr <-
SessionVariableBuilder m
-> AnnBoolExpPartialSQL ('Postgres 'Vanilla)
-> m (AnnBoolExpSQL ('Postgres 'Vanilla))
forall (f :: * -> *).
Applicative f =>
SessionVariableBuilder f
-> AnnBoolExpPartialSQL ('Postgres 'Vanilla)
-> f (AnnBoolExpSQL ('Postgres 'Vanilla))
convAnnBoolExpPartialSQL SessionVariableBuilder m
sessVarBldr
(AnnBoolExpPartialSQL ('Postgres 'Vanilla)
-> m (AnnBoolExpSQL ('Postgres 'Vanilla)))
-> AnnBoolExpPartialSQL ('Postgres 'Vanilla)
-> m (AnnBoolExpSQL ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$ DelPermInfo ('Postgres 'Vanilla)
-> AnnBoolExpPartialSQL ('Postgres 'Vanilla)
forall (b :: BackendType). DelPermInfo b -> AnnBoolExpPartialSQL b
dpiFilter DelPermInfo ('Postgres 'Vanilla)
delPerm
let validateInput :: Maybe (ValidateInput ResolvedWebhook)
validateInput = DelPermInfo ('Postgres 'Vanilla)
-> Maybe (ValidateInput ResolvedWebhook)
forall (b :: BackendType).
DelPermInfo b -> Maybe (ValidateInput ResolvedWebhook)
dpiValidateInput DelPermInfo ('Postgres 'Vanilla)
delPerm
AnnDelG ('Postgres 'Vanilla) Void SQLExp
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return
(AnnDelG ('Postgres 'Vanilla) Void SQLExp
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp))
-> AnnDelG ('Postgres 'Vanilla) Void SQLExp
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp)
forall a b. (a -> b) -> a -> b
$ TableName ('Postgres 'Vanilla)
-> (AnnBoolExp ('Postgres 'Vanilla) SQLExp,
AnnBoolExp ('Postgres 'Vanilla) SQLExp)
-> MutationOutputG ('Postgres 'Vanilla) Void SQLExp
-> [ColumnInfo ('Postgres 'Vanilla)]
-> Maybe NamingCase
-> Maybe (ValidateInput ResolvedWebhook)
-> Bool
-> AnnDelG ('Postgres 'Vanilla) Void SQLExp
forall (b :: BackendType) r v.
TableName b
-> (AnnBoolExp b v, AnnBoolExp b v)
-> MutationOutputG b r v
-> [ColumnInfo b]
-> Maybe NamingCase
-> Maybe (ValidateInput ResolvedWebhook)
-> Bool
-> AnnDelG b r v
AnnDel
TableName ('Postgres 'Vanilla)
QualifiedTable
tableName
(AnnBoolExp ('Postgres 'Vanilla) SQLExp
resolvedDelFltr, AnnBoolExp ('Postgres 'Vanilla) SQLExp
annSQLBoolExp)
(Maybe [ColumnInfo ('Postgres 'Vanilla)]
-> MutationOutput ('Postgres 'Vanilla)
forall (pgKind :: PostgresKind).
Backend ('Postgres pgKind) =>
Maybe [ColumnInfo ('Postgres pgKind)]
-> MutationOutput ('Postgres pgKind)
mkDefaultMutFlds Maybe [ColumnInfo ('Postgres 'Vanilla)]
mAnnRetCols)
[ColumnInfo ('Postgres 'Vanilla)]
allCols
Maybe NamingCase
forall a. Maybe a
Nothing
Maybe (ValidateInput ResolvedWebhook)
validateInput
Bool
False
where
selNecessaryMsg :: Text
selNecessaryMsg =
Text
"; \"delete\" is only allowed if the role "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"has \"select\" permission as \"where\" can't be used "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"without \"select\" permission on the table"
validateDeleteQ ::
(QErrM m, UserInfoM m, CacheRM m) =>
DeleteQuery ->
m (AnnDel ('Postgres 'Vanilla), DS.Seq PG.PrepArg)
validateDeleteQ :: forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m) =>
DeleteQuery -> m (AnnDel ('Postgres 'Vanilla), Seq PrepArg)
validateDeleteQ DeleteQuery
query = do
let source :: SourceName
source = DeleteQuery -> SourceName
doSource DeleteQuery
query
HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))
tableCache :: TableCache ('Postgres 'Vanilla) <- Maybe
(HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla)))
-> HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe
(HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla)))
-> HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla)))
-> m (Maybe
(HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))))
-> m (HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SourceName
-> m (Maybe
(HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))))
forall (b :: BackendType) (m :: * -> *).
(Backend b, CacheRM m) =>
SourceName -> m (Maybe (TableCache b))
askTableCache SourceName
source
(TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg))
-> HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))
-> TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
forall a b c. (a -> b -> c) -> b -> a -> c
flip TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
forall (b :: BackendType) (m :: * -> *) a.
TableCacheRT b m a -> TableCache b -> m a
runTableCacheRT HashMap
(TableName ('Postgres 'Vanilla)) (TableInfo ('Postgres 'Vanilla))
tableCache
(TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg))
-> TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> m (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
forall a b. (a -> b) -> a -> b
$ DMLP1T
(TableCacheRT ('Postgres 'Vanilla) m)
(AnnDelG ('Postgres 'Vanilla) Void SQLExp)
-> TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
forall (m :: * -> *) a. DMLP1T m a -> m (a, Seq PrepArg)
runDMLP1T
(DMLP1T
(TableCacheRT ('Postgres 'Vanilla) m)
(AnnDelG ('Postgres 'Vanilla) Void SQLExp)
-> TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg))
-> DMLP1T
(TableCacheRT ('Postgres 'Vanilla) m)
(AnnDelG ('Postgres 'Vanilla) Void SQLExp)
-> TableCacheRT
('Postgres 'Vanilla)
m
(AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
forall a b. (a -> b) -> a -> b
$ SessionVariableBuilder
(DMLP1T (TableCacheRT ('Postgres 'Vanilla) m))
-> (ColumnType ('Postgres 'Vanilla)
-> Value -> DMLP1T (TableCacheRT ('Postgres 'Vanilla) m) SQLExp)
-> DeleteQuery
-> DMLP1T
(TableCacheRT ('Postgres 'Vanilla) m) (AnnDel ('Postgres 'Vanilla))
forall (m :: * -> *).
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
SessionVariableBuilder m
-> (ColumnType ('Postgres 'Vanilla) -> Value -> m SQLExp)
-> DeleteQuery
-> m (AnnDel ('Postgres 'Vanilla))
validateDeleteQWith SessionVariableBuilder
(DMLP1T (TableCacheRT ('Postgres 'Vanilla) m))
forall (f :: * -> *). Applicative f => SessionVariableBuilder f
sessVarFromCurrentSetting ColumnType ('Postgres 'Vanilla)
-> Value -> DMLP1T (TableCacheRT ('Postgres 'Vanilla) m) SQLExp
forall (m :: * -> *).
QErrM m =>
ColumnType ('Postgres 'Vanilla) -> Value -> DMLP1T m SQLExp
binRHSBuilder DeleteQuery
query
runDelete ::
forall m.
( QErrM m,
UserInfoM m,
CacheRM m,
MonadIO m,
Tracing.MonadTrace m,
MonadBaseControl IO m,
MetadataM m
) =>
SQLGenCtx ->
DeleteQuery ->
m EncJSON
runDelete :: forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m, MonadIO m, MonadTrace m,
MonadBaseControl IO m, MetadataM m) =>
SQLGenCtx -> DeleteQuery -> m EncJSON
runDelete SQLGenCtx
sqlGen DeleteQuery
q = do
PGSourceConfig
sourceConfig <- forall (b :: BackendType) (m :: * -> *).
(CacheRM m, MonadError QErr m, Backend b, MetadataM m) =>
SourceName -> m (SourceConfig b)
askSourceConfig @('Postgres 'Vanilla) (DeleteQuery -> SourceName
doSource DeleteQuery
q)
let strfyNum :: StringifyNumbers
strfyNum = SQLGenCtx -> StringifyNumbers
stringifyNum SQLGenCtx
sqlGen
UserInfo
userInfo <- m UserInfo
forall (m :: * -> *). UserInfoM m => m UserInfo
askUserInfo
DeleteQuery -> m (AnnDel ('Postgres 'Vanilla), Seq PrepArg)
forall (m :: * -> *).
(QErrM m, UserInfoM m, CacheRM m) =>
DeleteQuery -> m (AnnDel ('Postgres 'Vanilla), Seq PrepArg)
validateDeleteQ DeleteQuery
q
m (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> ((AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> m EncJSON)
-> m EncJSON
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PGExecCtx
-> PGExecTxType -> PGExecFrom -> TxET QErr m EncJSON -> m EncJSON
forall (m :: * -> *) a.
(MonadIO m, MonadBaseControl IO m, MonadError QErr m, MonadTrace m,
UserInfoM m) =>
PGExecCtx -> PGExecTxType -> PGExecFrom -> TxET QErr m a -> m a
runTxWithCtx (PGSourceConfig -> PGExecCtx
_pscExecCtx PGSourceConfig
sourceConfig) (TxAccess -> Maybe TxIsolation -> PGExecTxType
Tx TxAccess
PG.ReadWrite Maybe TxIsolation
forall a. Maybe a
Nothing) PGExecFrom
LegacyRQLQuery
(TxET QErr m EncJSON -> m EncJSON)
-> ((AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> TxET QErr m EncJSON)
-> (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ReaderT QueryTagsComment (TxET QErr m) EncJSON
-> QueryTagsComment -> TxET QErr m EncJSON)
-> QueryTagsComment
-> ReaderT QueryTagsComment (TxET QErr m) EncJSON
-> TxET QErr m EncJSON
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT QueryTagsComment (TxET QErr m) EncJSON
-> QueryTagsComment -> TxET QErr m EncJSON
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT QueryTagsComment
emptyQueryTagsComment
(ReaderT QueryTagsComment (TxET QErr m) EncJSON
-> TxET QErr m EncJSON)
-> ((AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> ReaderT QueryTagsComment (TxET QErr m) EncJSON)
-> (AnnDelG ('Postgres 'Vanilla) Void SQLExp, Seq PrepArg)
-> TxET QErr m EncJSON
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StringifyNumbers
-> Maybe NamingCase
-> UserInfo
-> (AnnDel ('Postgres 'Vanilla), Seq PrepArg)
-> ReaderT QueryTagsComment (TxET QErr m) EncJSON
forall (pgKind :: PostgresKind) (m :: * -> *).
(MonadTx m, Backend ('Postgres pgKind),
PostgresAnnotatedFieldJSON pgKind,
MonadReader QueryTagsComment m) =>
StringifyNumbers
-> Maybe NamingCase
-> UserInfo
-> (AnnDel ('Postgres pgKind), Seq PrepArg)
-> m EncJSON
execDeleteQuery StringifyNumbers
strfyNum Maybe NamingCase
forall a. Maybe a
Nothing UserInfo
userInfo