{-# LANGUAGE PartialTypeSignatures #-} -- | Postgres Translate BoolExp -- -- Convert IR boolean expressions to Postgres-specific SQL expressions. module Hasura.Backends.Postgres.Translate.BoolExp ( toSQLBoolExp, ) where import Data.HashMap.Strict qualified as M import Data.Text.Extended (ToTxt) import Hasura.Backends.Postgres.SQL.DML qualified as S import Hasura.Backends.Postgres.SQL.Types hiding (TableName) import Hasura.Backends.Postgres.Types.BoolExp import Hasura.Backends.Postgres.Types.Function (onArgumentExp) import Hasura.Function.Cache import Hasura.Prelude import Hasura.RQL.IR.BoolExp import Hasura.RQL.IR.BoolExp.AggregationPredicates (AggregationPredicate (..), AggregationPredicateArguments (..), AggregationPredicatesImplementation (..)) import Hasura.RQL.Types.Backend import Hasura.RQL.Types.Column import Hasura.RQL.Types.Common import Hasura.RQL.Types.Relationships.Local import Hasura.RQL.Types.Table () import Hasura.SQL.Backend import Hasura.SQL.Types -- This convoluted expression instead of col = val -- to handle the case of col : null equalsBoolExpBuilder :: SQLExpression ('Postgres pgKind) -> SQLExpression ('Postgres pgKind) -> S.BoolExp equalsBoolExpBuilder qualColExp rhsExp = S.BEBin S.OrOp (S.BECompare S.SEQ qualColExp rhsExp) ( S.BEBin S.AndOp (S.BENull qualColExp) (S.BENull rhsExp) ) notEqualsBoolExpBuilder :: SQLExpression ('Postgres pgKind) -> SQLExpression ('Postgres pgKind) -> S.BoolExp notEqualsBoolExpBuilder qualColExp rhsExp = S.BEBin S.OrOp (S.BECompare S.SNE qualColExp rhsExp) ( S.BEBin S.AndOp (S.BENotNull qualColExp) (S.BENull rhsExp) ) -- | Translate an IR boolean expression to an SQL boolean expression. References -- to columns etc are relative to the given 'rootReference'. toSQLBoolExp :: forall pgKind. Backend ('Postgres pgKind) => -- | The name of the tabular value in query scope that the boolean expression -- applies to S.Qual -> -- | The boolean expression to translate AnnBoolExpSQL ('Postgres pgKind) -> S.BoolExp toSQLBoolExp rootReference e = evalState ( runReaderT (unBoolExpM (translateBoolExp e)) initialCtx ) 0 where initialCtx = BoolExpCtx { currTableReference = rootReference, rootReference = rootReference } -- | The table context of boolean expression translation. This is used to -- resolve references to fields, as those may refer to the so-called 'root -- table' (identified by a '$'-sign in the expression input syntax) or the -- 'current' table. data BoolExpCtx = BoolExpCtx { -- | Reference to the current tabular value. currTableReference :: S.Qual, -- | Reference to the root tabular value. rootReference :: S.Qual } -- | The monad that carries the translation of boolean expressions. This -- supports the generation of fresh names for aliasing sub-expressions and -- maintains the table context of the expressions being translated. newtype BoolExpM a = BoolExpM {unBoolExpM :: ReaderT BoolExpCtx (State Word64) a} deriving (Functor, Applicative, Monad, MonadReader BoolExpCtx, MonadState Word64) -- | Translate a 'GBoolExp' with annotated SQLExpressions in the leaves into a -- bare SQL Boolean Expression. translateBoolExp :: forall pgKind. (Backend ('Postgres pgKind)) => AnnBoolExpSQL ('Postgres pgKind) -> BoolExpM S.BoolExp translateBoolExp = \case BoolAnd bes -> do sqlBExps <- mapM translateBoolExp bes return $ sqlAnd sqlBExps BoolOr bes -> do sqlBExps <- mapM translateBoolExp bes return $ foldr (S.BEBin S.OrOp) (S.BELit False) sqlBExps BoolNot notExp -> S.BENot <$> translateBoolExp notExp BoolExists (GExists currTableReference wh) -> do fresh <- state \identifier -> (identifier, identifier + 1) let alias :: S.TableAlias alias = S.toTableAlias (Identifier ("_exists_table_" <> tshow fresh)) identifier :: TableIdentifier identifier = S.tableAliasToIdentifier alias whereExp <- withCurrentTable (S.QualifiedIdentifier identifier Nothing) (translateBoolExp wh) return $ S.mkExists (S.FISimple currTableReference (Just alias)) whereExp BoolField boolExp -> case boolExp of AVColumn colInfo opExps -> do BoolExpCtx {rootReference, currTableReference} <- ask let colFld = fromCol @('Postgres pgKind) $ ciColumn colInfo bExps = map (mkFieldCompExp rootReference currTableReference $ LColumn colFld) opExps return $ sqlAnd bExps AVRelationship (RelInfo _ _ colMapping relTN _ _) nesAnn -> do -- Convert the where clause on the relationship relTNAlias <- S.toTableAlias <$> freshIdentifier relTN let relTNIdentifier = S.tableAliasToIdentifier relTNAlias annRelBoolExp <- withCurrentTable (S.QualifiedIdentifier relTNIdentifier Nothing) (translateBoolExp nesAnn) tableRelExp <- translateTableRelationship colMapping relTNIdentifier let innerBoolExp = S.BEBin S.AndOp tableRelExp annRelBoolExp return $ S.mkExists (S.FISimple relTN $ Just $ relTNAlias) innerBoolExp AVComputedField (AnnComputedFieldBoolExp _ _ function sessionArgPresence cfBoolExp) -> do case cfBoolExp of CFBEScalar opExps -> do BoolExpCtx {rootReference, currTableReference} <- ask -- Convert the where clause on scalar computed field let bExps = map (mkFieldCompExp rootReference currTableReference $ LComputedField function sessionArgPresence) opExps pure $ sqlAnd bExps CFBETable _ be -> do -- Convert the where clause on table computed field BoolExpCtx {currTableReference} <- ask functionAlias <- S.toTableAlias <$> freshIdentifier function let functionIdentifier = S.tableAliasToIdentifier functionAlias functionExp = mkComputedFieldFunctionExp currTableReference function sessionArgPresence $ Just $ functionAlias S.mkExists (S.FIFunc functionExp) <$> withCurrentTable (S.QualifiedIdentifier functionIdentifier Nothing) (translateBoolExp be) AVAggregationPredicates aggPreds -> translateAVAggregationPredicates aggPreds -- | Call a given translation action recursively using the given identifier for the 'current' table. withCurrentTable :: forall a. S.Qual -> BoolExpM a -> BoolExpM a withCurrentTable curr = local (\e -> e {currTableReference = curr}) -- | Draw a fresh identifier intended to alias the given object. freshIdentifier :: forall a. ToTxt a => QualifiedObject a -> BoolExpM Identifier freshIdentifier obj = do curVarNum <- get put $ curVarNum + 1 let newIdentifier = Identifier $ "_be_" <> tshow curVarNum <> "_" <> snakeCaseQualifiedObject obj return newIdentifier identifierWithSuffix :: ToTxt a => QualifiedObject a -> Text -> Identifier identifierWithSuffix relTableName name = Identifier (snakeCaseQualifiedObject relTableName <> "_" <> name) -- | Given a GraphQL aggregation filter of the form: -- > { where: {