2018-12-13 10:26:15 +03:00
|
|
|
module Hasura.RQL.DML.Count
|
2021-09-24 01:56:37 +03:00
|
|
|
( CountQueryP1 (..),
|
|
|
|
validateCountQWith,
|
|
|
|
validateCountQ,
|
|
|
|
runCount,
|
|
|
|
countQToTx,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Monad.Trans.Control (MonadBaseControl)
|
|
|
|
import Data.Aeson
|
|
|
|
import Data.ByteString.Builder qualified as BB
|
|
|
|
import Data.Sequence qualified as DS
|
|
|
|
import Database.PG.Query qualified as Q
|
|
|
|
import Hasura.Backends.Postgres.SQL.DML qualified as S
|
|
|
|
import Hasura.Backends.Postgres.SQL.Types
|
|
|
|
import Hasura.Backends.Postgres.Translate.BoolExp
|
|
|
|
import Hasura.Base.Error
|
|
|
|
import Hasura.EncJSON
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DML.Internal
|
|
|
|
import Hasura.RQL.DML.Types
|
|
|
|
import Hasura.RQL.IR.BoolExp
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
import Hasura.SQL.Types
|
|
|
|
import Hasura.Session
|
|
|
|
import Hasura.Tracing qualified as Tracing
|
|
|
|
|
|
|
|
data CountQueryP1 = CountQueryP1
|
|
|
|
{ cqp1Table :: !QualifiedTable,
|
|
|
|
cqp1Where :: !(AnnBoolExpSQL ('Postgres 'Vanilla), Maybe (AnnBoolExpSQL ('Postgres 'Vanilla))),
|
|
|
|
cqp1Distinct :: !(Maybe [PGCol])
|
|
|
|
}
|
|
|
|
deriving (Eq)
|
|
|
|
|
|
|
|
mkSQLCount ::
|
|
|
|
CountQueryP1 -> S.Select
|
2018-06-27 16:11:32 +03:00
|
|
|
mkSQLCount (CountQueryP1 tn (permFltr, mWc) mDistCols) =
|
|
|
|
S.mkSelect
|
2021-09-24 01:56:37 +03:00
|
|
|
{ S.selExtr = [S.Extractor S.countStar Nothing],
|
|
|
|
S.selFrom =
|
|
|
|
Just $
|
|
|
|
S.FromExp
|
|
|
|
[S.mkSelFromExp False innerSel $ TableName "r"]
|
2018-06-27 16:11:32 +03:00
|
|
|
}
|
|
|
|
where
|
|
|
|
finalWC =
|
2018-11-16 15:40:23 +03:00
|
|
|
toSQLBoolExp (S.QualTable tn) $
|
2021-09-24 01:56:37 +03:00
|
|
|
maybe permFltr (andAnnBoolExps permFltr) mWc
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
innerSel =
|
|
|
|
partSel
|
|
|
|
{ S.selFrom = Just $ S.mkSimpleFromExp tn,
|
|
|
|
S.selWhere = S.WhereFrag <$> Just finalWC
|
|
|
|
}
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
|
|
partSel = case mDistCols of
|
|
|
|
Just distCols ->
|
|
|
|
let extrs = flip map distCols $ \c -> S.Extractor (S.mkSIdenExp c) Nothing
|
2021-09-24 01:56:37 +03:00
|
|
|
in S.mkSelect
|
|
|
|
{ S.selDistinct = Just S.DistinctSimple,
|
|
|
|
S.selExtr = extrs
|
|
|
|
}
|
|
|
|
Nothing ->
|
|
|
|
S.mkSelect
|
|
|
|
{ S.selExtr = [S.Extractor (S.SEStar Nothing) Nothing]
|
2018-06-27 16:11:32 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
-- SELECT count(*) FROM (SELECT DISTINCT c1, .. cn FROM .. WHERE ..) r;
|
|
|
|
-- SELECT count(*) FROM (SELECT * FROM .. WHERE ..) r;
|
2021-09-24 01:56:37 +03:00
|
|
|
validateCountQWith ::
|
|
|
|
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
|
|
|
|
SessionVariableBuilder ('Postgres 'Vanilla) m ->
|
|
|
|
(ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp) ->
|
|
|
|
CountQuery ->
|
|
|
|
m CountQueryP1
|
2021-01-07 12:04:22 +03:00
|
|
|
validateCountQWith sessVarBldr prepValBldr (CountQuery qt _ mDistCols mWhere) = do
|
2020-12-28 15:56:00 +03:00
|
|
|
tableInfo <- askTabInfoSource qt
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
|
|
-- Check if select is allowed
|
2021-09-24 01:56:37 +03:00
|
|
|
selPerm <-
|
|
|
|
modifyErr (<> selNecessaryMsg) $
|
|
|
|
askSelPermInfo tableInfo
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2019-11-20 21:21:30 +03:00
|
|
|
let colInfoMap = _tciFieldInfoMap $ _tiCoreInfo tableInfo
|
2018-06-27 16:11:32 +03:00
|
|
|
|
|
|
|
forM_ mDistCols $ \distCols -> do
|
2021-09-24 01:56:37 +03:00
|
|
|
let distColAsrns =
|
|
|
|
[ checkSelOnCol selPerm,
|
|
|
|
assertColumnExists colInfoMap relInDistColsErr
|
|
|
|
]
|
2018-06-27 16:11:32 +03:00
|
|
|
withPathK "distinct" $ verifyAsrns distColAsrns distCols
|
|
|
|
|
|
|
|
-- convert the where clause
|
|
|
|
annSQLBoolExp <- forM mWhere $ \be ->
|
|
|
|
withPathK "where" $
|
2021-09-24 01:56:37 +03:00
|
|
|
convBoolExp colInfoMap selPerm be sessVarBldr qt (valueParserWithCollectableType prepValBldr)
|
2019-04-17 12:48:41 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
resolvedSelFltr <-
|
|
|
|
convAnnBoolExpPartialSQL sessVarBldr $
|
|
|
|
spiFilter selPerm
|
2018-06-27 16:11:32 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
return $
|
|
|
|
CountQueryP1
|
|
|
|
qt
|
|
|
|
(resolvedSelFltr, annSQLBoolExp)
|
|
|
|
mDistCols
|
2018-06-27 16:11:32 +03:00
|
|
|
where
|
|
|
|
selNecessaryMsg =
|
|
|
|
"; \"count\" is only allowed if the role "
|
2021-09-24 01:56:37 +03:00
|
|
|
<> "has \"select\" permissions on the table"
|
2018-06-27 16:11:32 +03:00
|
|
|
relInDistColsErr =
|
|
|
|
"Relationships can't be used in \"distinct\"."
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
validateCountQ ::
|
|
|
|
(QErrM m, UserInfoM m, CacheRM m) =>
|
|
|
|
CountQuery ->
|
|
|
|
m (CountQueryP1, DS.Seq Q.PrepArg)
|
2021-01-07 12:04:22 +03:00
|
|
|
validateCountQ query = do
|
|
|
|
let source = cqSource query
|
2021-04-22 00:44:37 +03:00
|
|
|
tableCache :: TableCache ('Postgres 'Vanilla) <- askTableCache source
|
2021-09-24 01:56:37 +03:00
|
|
|
flip runTableCacheRT (source, tableCache) $
|
|
|
|
runDMLP1T $
|
|
|
|
validateCountQWith sessVarFromCurrentSetting binRHSBuilder query
|
|
|
|
|
|
|
|
countQToTx ::
|
|
|
|
(QErrM m, MonadTx m) =>
|
|
|
|
(CountQueryP1, DS.Seq Q.PrepArg) ->
|
|
|
|
m EncJSON
|
2018-12-13 10:26:15 +03:00
|
|
|
countQToTx (u, p) = do
|
2021-09-24 01:56:37 +03:00
|
|
|
qRes <-
|
|
|
|
liftTx $
|
|
|
|
Q.rawQE
|
|
|
|
dmlTxErrorHandler
|
|
|
|
(Q.fromBuilder countSQL)
|
|
|
|
(toList p)
|
|
|
|
True
|
2019-03-18 19:22:21 +03:00
|
|
|
return $ encJFromBuilder $ encodeCount qRes
|
2018-06-27 16:11:32 +03:00
|
|
|
where
|
|
|
|
countSQL = toSQL $ mkSQLCount u
|
|
|
|
encodeCount (Q.SingleRow (Identity c)) =
|
|
|
|
BB.byteString "{\"count\":" <> BB.intDec c <> BB.char7 '}'
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
runCount ::
|
|
|
|
( QErrM m,
|
|
|
|
UserInfoM m,
|
|
|
|
CacheRM m,
|
|
|
|
MonadIO m,
|
|
|
|
MonadBaseControl IO m,
|
|
|
|
Tracing.MonadTrace m,
|
|
|
|
MetadataM m
|
|
|
|
) =>
|
|
|
|
CountQuery ->
|
|
|
|
m EncJSON
|
2021-01-07 12:04:22 +03:00
|
|
|
runCount q = do
|
2021-04-22 00:44:37 +03:00
|
|
|
sourceConfig <- askSourceConfig @('Postgres 'Vanilla) (cqSource q)
|
2021-09-15 23:45:49 +03:00
|
|
|
validateCountQ q >>= runTxWithCtx (_pscExecCtx sourceConfig) Q.ReadOnly . countQToTx
|