graphql-engine/server/src-lib/Hasura/RQL/DML/Count.hs
Antoine Leblanc cdf5e3b5f0 Specialize RQL.DML to postgres.
### Description

When generalizing the code, back in late 2020, we over-eagerly generalized parts of the code that are specific to RQL's DML. This was in part due to the fact that, at the time, the DML types were all mixed alongside other types in `RQL.Types`. As a result, a lot of `RQL.DML.Internal` was generic over the backend type, instead of being specialized to `'Postgres 'Vanilla`.

A consequence of this is that, before this PR, `DML.Internal` ended up having a dependency on non-Postgres backends, due to the use of `annBoolExp`, which requires a `BackendMetadata` instance. Since the code was written in a generic manner, `DML.Internal` in turn depended on having the metadata instances in scope... This PR changes that to, instead, explicitly import the Postgres instance.

(Note that this module didn't import `RQL.Types.Metadata.Instances`, but depends on a module that imports it, and **orphan instances are transitively imported**, as evidenced by the need for that explicit import in #4568.)

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4573
GitOrigin-RevId: 7b82b5d7c23c03654518a1816802d400f37c3c64
2022-05-27 18:23:19 +00:00

164 lines
4.6 KiB
Haskell

module Hasura.RQL.DML.Count
( 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.Connection.MonadTx
import Hasura.Backends.Postgres.Execute.Types
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.Column
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.SchemaCache
import Hasura.RQL.Types.Table
import Hasura.SQL.Backend
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
mkSQLCount (CountQueryP1 tn (permFltr, mWc) mDistCols) =
S.mkSelect
{ S.selExtr = [S.Extractor S.countStar Nothing],
S.selFrom =
Just $
S.FromExp
[S.mkSelFromExp False innerSel $ TableName "r"]
}
where
finalWC =
toSQLBoolExp (S.QualTable tn) $
maybe permFltr (andAnnBoolExps permFltr) mWc
innerSel =
partSel
{ S.selFrom = Just $ S.mkSimpleFromExp tn,
S.selWhere = S.WhereFrag <$> Just finalWC
}
partSel = case mDistCols of
Just distCols ->
let extrs = flip map distCols $ \c -> S.Extractor (S.mkSIdenExp c) Nothing
in S.mkSelect
{ S.selDistinct = Just S.DistinctSimple,
S.selExtr = extrs
}
Nothing ->
S.mkSelect
{ S.selExtr = [S.Extractor (S.SEStar Nothing) Nothing]
}
-- SELECT count(*) FROM (SELECT DISTINCT c1, .. cn FROM .. WHERE ..) r;
-- SELECT count(*) FROM (SELECT * FROM .. WHERE ..) r;
validateCountQWith ::
(UserInfoM m, QErrM m, TableInfoRM ('Postgres 'Vanilla) m) =>
SessionVariableBuilder m ->
(ColumnType ('Postgres 'Vanilla) -> Value -> m S.SQLExp) ->
CountQuery ->
m CountQueryP1
validateCountQWith sessVarBldr prepValBldr (CountQuery qt _ mDistCols mWhere) = do
tableInfo <- askTableInfoSource qt
-- Check if select is allowed
selPerm <-
modifyErr (<> selNecessaryMsg) $
askSelPermInfo tableInfo
let colInfoMap = _tciFieldInfoMap $ _tiCoreInfo tableInfo
forM_ mDistCols $ \distCols -> do
let distColAsrns =
[ checkSelOnCol selPerm,
assertColumnExists colInfoMap relInDistColsErr
]
withPathK "distinct" $ verifyAsrns distColAsrns distCols
-- convert the where clause
annSQLBoolExp <- forM mWhere $ \be ->
withPathK "where" $
convBoolExp colInfoMap selPerm be sessVarBldr qt (valueParserWithCollectableType prepValBldr)
resolvedSelFltr <-
convAnnBoolExpPartialSQL sessVarBldr $
spiFilter selPerm
return $
CountQueryP1
qt
(resolvedSelFltr, annSQLBoolExp)
mDistCols
where
selNecessaryMsg =
"; \"count\" is only allowed if the role "
<> "has \"select\" permissions on the table"
relInDistColsErr =
"Relationships can't be used in \"distinct\"."
validateCountQ ::
(QErrM m, UserInfoM m, CacheRM m) =>
CountQuery ->
m (CountQueryP1, DS.Seq Q.PrepArg)
validateCountQ query = do
let source = cqSource query
tableCache :: TableCache ('Postgres 'Vanilla) <- fold <$> askTableCache source
flip runTableCacheRT (source, tableCache) $
runDMLP1T $
validateCountQWith sessVarFromCurrentSetting binRHSBuilder query
countQToTx ::
(QErrM m, MonadTx m) =>
(CountQueryP1, DS.Seq Q.PrepArg) ->
m EncJSON
countQToTx (u, p) = do
qRes <-
liftTx $
Q.rawQE
dmlTxErrorHandler
(Q.fromBuilder countSQL)
(toList p)
True
return $ encJFromBuilder $ encodeCount qRes
where
countSQL = toSQL $ mkSQLCount u
encodeCount (Q.SingleRow (Identity c)) =
BB.byteString "{\"count\":" <> BB.intDec c <> BB.char7 '}'
runCount ::
( QErrM m,
UserInfoM m,
CacheRM m,
MonadIO m,
MonadBaseControl IO m,
Tracing.MonadTrace m,
MetadataM m
) =>
CountQuery ->
m EncJSON
runCount q = do
sourceConfig <- askSourceConfig @('Postgres 'Vanilla) (cqSource q)
validateCountQ q >>= runTxWithCtx (_pscExecCtx sourceConfig) Q.ReadOnly . countQToTx