mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 20:41:49 +03:00
1007ea27ae
Followup to hasura/graphql-engine-mono#4713. The `memoizeOn` method, part of `MonadSchema`, originally had the following type: ```haskell memoizeOn :: (HasCallStack, Ord a, Typeable a, Typeable b, Typeable k) => TH.Name -> a -> m (Parser k n b) -> m (Parser k n b) ``` The reason for operating on `Parser`s specifically was that the `MonadSchema` effect would additionally initialize certain `Unique` values, which appear (nested in) the type of `Parser`. hasura/graphql-engine-mono#518 changed the type of `memoizeOn`, to additionally allow memoizing `FieldParser`s. These also contained a `Unique` value, which was similarly initialized by the `MonadSchema` effect. The new type of `memoizeOn` was as follows: ```haskell memoizeOn :: forall p d a b . (HasCallStack, HasDefinition (p n b) d, Ord a, Typeable p, Typeable a, Typeable b) => TH.Name -> a -> m (p n b) -> m (p n b) ``` Note the type `p n b` of the value being memoized: by choosing `p` to be either `Parser k` or `FieldParser`, both can be memoized. Also note the new `HasDefinition (p n b) d` constraint, which provided a `Lens` for accessing the `Unique` value to be initialized. A quick simplification is that the `HasCallStack` constraint has never been used by any code. This was realized in hasura/graphql-engine-mono#4713, by removing that constraint. hasura/graphql-engine-mono#2980 removed the `Unique` value from our GraphQL-related types entirely, as their original purpose was never truly realized. One part of removing `Unique` consisted of dropping the `HasDefinition (p n b) d` constraint from `memoizeOn`. What I didn't realize at the time was that this meant that the type of `memoizeOn` could be generalized and simplified much further. This PR finally implements that generalization. The new type is as follows: ```haskell memoizeOn :: forall a p. (Ord a, Typeable a, Typeable p) => TH.Name -> a -> m p -> m p ``` This change has a couple of consequences. 1. While constructing the schema, we often output `Maybe (Parser ...)`, to model that the existence of certain pieces of GraphQL schema sometimes depends on the permissions that a certain role has. The previous versions of `memoizeOn` were not able to handle this, as the only thing they could memoize was fully-defined (if not yet fully-evaluated) `(Field)Parser`s. This much more general API _would_ allow memoizing `Maybe (Parser ...)`s. However, we probably have to be continue being cautious with this: if we blindly memoize all `Maybe (Parser ...)`s, the resulting code may never be able to decide whether the value is `Just` or `Nothing` - i.e. it never commits to the existence-or-not of a GraphQL schema fragment. This would manifest as a non-well-founded knot tying, and this would get reported as an error by the implementation of `memoizeOn`. tl;dr: This generalization _technically_ allows for memoizing `Maybe` values, but we probably still want to avoid doing so. For this reason, the PR adds a specialized version of `memoizeOn` to `Hasura.GraphQL.Schema.Parser`. 2. There is no longer any need to connect the `MonadSchema` knot-tying effect with the `MonadParse` effect. In fact, after this PR, the `memoizeOn` method is completely GraphQL-agnostic, and so we implement hasura/graphql-engine-mono#4726, separating `memoizeOn` from `MonadParse` entirely - `memoizeOn` can be defined and implemented as a general Haskell typeclass method. Since `MonadSchema` has been made into a single-type-parameter type class, it has been renamed to something more general, namely `MonadMemoize`. Its only task is to memoize arbitrary `Typeable p` objects under a combined key consisting of a `TH.Name` and a `Typeable a`. Also for this reason, the new `MonadMemoize` has been moved to the more general `Control.Monad.Memoize`. 3. After this change, it's somewhat clearer what `memoizeOn` does: it memoizes an arbitrary value of a `Typeable` type. The only thing that needs to be understood in its implementation is how the manual blackholing works. There is no more semantic interaction with _any_ GraphQL code. PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4725 Co-authored-by: Daniel Harvey <4729125+danieljharvey@users.noreply.github.com> GitOrigin-RevId: 089fa2e82c2ce29da76850e994eabb1e261f9c92
238 lines
9.9 KiB
Haskell
238 lines
9.9 KiB
Haskell
{-# LANGUAGE ApplicativeDo #-}
|
||
{-# LANGUAGE TemplateHaskell #-}
|
||
|
||
module Hasura.GraphQL.Schema.BoolExp
|
||
( boolExp,
|
||
mkBoolOperator,
|
||
equalityOperators,
|
||
comparisonOperators,
|
||
)
|
||
where
|
||
|
||
import Data.Text.Casing (GQLNameIdentifier)
|
||
import Data.Text.Casing qualified as C
|
||
import Data.Text.Extended
|
||
import Hasura.GraphQL.Parser.Class
|
||
import Hasura.GraphQL.Schema.Backend
|
||
import Hasura.GraphQL.Schema.Common (SchemaContext (..), askTableInfo, partialSQLExpToUnpreparedValue, retrieve)
|
||
import Hasura.GraphQL.Schema.NamingCase
|
||
import Hasura.GraphQL.Schema.Options qualified as Options
|
||
import Hasura.GraphQL.Schema.Parser
|
||
( InputFieldsParser,
|
||
Kind (..),
|
||
Parser,
|
||
)
|
||
import Hasura.GraphQL.Schema.Parser qualified as P
|
||
import Hasura.GraphQL.Schema.Table
|
||
import Hasura.GraphQL.Schema.Typename (mkTypename)
|
||
import Hasura.Name qualified as Name
|
||
import Hasura.Prelude
|
||
import Hasura.RQL.IR.BoolExp
|
||
import Hasura.RQL.IR.Value
|
||
import Hasura.RQL.Types.Backend
|
||
import Hasura.RQL.Types.Column
|
||
import Hasura.RQL.Types.ComputedField
|
||
import Hasura.RQL.Types.Function
|
||
import Hasura.RQL.Types.Relationships.Local
|
||
import Hasura.RQL.Types.SchemaCache hiding (askTableInfo)
|
||
import Hasura.RQL.Types.Source
|
||
import Hasura.RQL.Types.SourceCustomization (applyFieldNameCaseIdentifier)
|
||
import Hasura.RQL.Types.Table
|
||
import Language.GraphQL.Draft.Syntax qualified as G
|
||
|
||
-- |
|
||
-- > input type_bool_exp {
|
||
-- > _or: [type_bool_exp!]
|
||
-- > _and: [type_bool_exp!]
|
||
-- > _not: type_bool_exp
|
||
-- > column: type_comparison_exp
|
||
-- > ...
|
||
-- > }
|
||
boolExp ::
|
||
forall b r m n.
|
||
MonadBuildSchema b r m n =>
|
||
SourceInfo b ->
|
||
TableInfo b ->
|
||
m (Parser 'Input n (AnnBoolExp b (UnpreparedValue b)))
|
||
boolExp sourceInfo tableInfo = P.memoizeOn 'boolExp (_siName sourceInfo, tableName) $ do
|
||
tableGQLName <- getTableGQLName tableInfo
|
||
name <- mkTypename $ tableGQLName <> Name.__bool_exp
|
||
let description =
|
||
G.Description $
|
||
"Boolean expression to filter rows from the table " <> tableName
|
||
<<> ". All fields are combined with a logical 'AND'."
|
||
|
||
fieldInfos <- tableSelectFields sourceInfo tableInfo
|
||
tableFieldParsers <- catMaybes <$> traverse mkField fieldInfos
|
||
recur <- boolExp sourceInfo tableInfo
|
||
-- Bafflingly, ApplicativeDo doesn’t work if we inline this definition (I
|
||
-- think the TH splices throw it off), so we have to define it separately.
|
||
let specialFieldParsers =
|
||
[ P.fieldOptional Name.__or Nothing (BoolOr <$> P.list recur),
|
||
P.fieldOptional Name.__and Nothing (BoolAnd <$> P.list recur),
|
||
P.fieldOptional Name.__not Nothing (BoolNot <$> recur)
|
||
]
|
||
|
||
pure $
|
||
BoolAnd <$> P.object name (Just description) do
|
||
tableFields <- map BoolField . catMaybes <$> sequenceA tableFieldParsers
|
||
specialFields <- catMaybes <$> sequenceA specialFieldParsers
|
||
pure (tableFields ++ specialFields)
|
||
where
|
||
tableName = tableInfoName tableInfo
|
||
|
||
mkField ::
|
||
FieldInfo b ->
|
||
m (Maybe (InputFieldsParser n (Maybe (AnnBoolExpFld b (UnpreparedValue b)))))
|
||
mkField fieldInfo = runMaybeT do
|
||
roleName <- retrieve scRole
|
||
fieldName <- hoistMaybe $ fieldInfoGraphQLName fieldInfo
|
||
P.fieldOptional fieldName Nothing <$> case fieldInfo of
|
||
-- field_name: field_type_comparison_exp
|
||
FIColumn columnInfo ->
|
||
lift $ fmap (AVColumn columnInfo) <$> comparisonExps @b (ciType columnInfo)
|
||
-- field_name: field_type_bool_exp
|
||
FIRelationship relationshipInfo -> do
|
||
remoteTableInfo <- askTableInfo sourceInfo $ riRTable relationshipInfo
|
||
let remoteTableFilter =
|
||
(fmap . fmap) partialSQLExpToUnpreparedValue $
|
||
maybe annBoolExpTrue spiFilter $
|
||
tableSelectPermissions roleName remoteTableInfo
|
||
remoteBoolExp <- lift $ boolExp sourceInfo remoteTableInfo
|
||
pure $ fmap (AVRelationship relationshipInfo . andAnnBoolExps remoteTableFilter) remoteBoolExp
|
||
FIComputedField ComputedFieldInfo {..} -> do
|
||
let ComputedFieldFunction {..} = _cfiFunction
|
||
-- For a computed field to qualify in boolean expression it shouldn't have any input arguments
|
||
case toList _cffInputArgs of
|
||
[] -> do
|
||
let functionArgs =
|
||
flip FunctionArgsExp mempty $
|
||
fromComputedFieldImplicitArguments @b UVSession _cffComputedFieldImplicitArgs
|
||
|
||
fmap (AVComputedField . AnnComputedFieldBoolExp _cfiXComputedFieldInfo _cfiName _cffName functionArgs)
|
||
<$> case computedFieldReturnType @b _cfiReturnType of
|
||
ReturnsScalar scalarType -> lift $ fmap CFBEScalar <$> comparisonExps @b (ColumnScalar scalarType)
|
||
ReturnsTable table -> do
|
||
info <- askTableInfo sourceInfo table
|
||
lift $ fmap (CFBETable table) <$> boolExp sourceInfo info
|
||
ReturnsOthers -> hoistMaybe Nothing
|
||
_ -> hoistMaybe Nothing
|
||
|
||
-- Using remote relationship fields in boolean expressions is not supported.
|
||
FIRemoteRelationship _ -> empty
|
||
|
||
{- Note [Nullability in comparison operators]
|
||
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
||
|
||
In comparisonExps, we hardcode most operators with `Nullability False` when
|
||
calling `column`, which might seem a bit sketchy. Shouldn’t the nullability
|
||
depend on the nullability of the underlying Postgres column?
|
||
|
||
No. If we did that, then we would allow boolean expressions like this:
|
||
|
||
delete_users(where: {status: {eq: null}})
|
||
|
||
which in turn would generate a SQL query along the lines of:
|
||
|
||
DELETE FROM users WHERE users.status = NULL
|
||
|
||
but `= NULL` might not do what they expect. For instance, on Postgres, it always
|
||
evaluates to False!
|
||
|
||
Even operators for which `null` is a valid value must be careful in their
|
||
implementation. An explicit `null` must always be handled explicitly! If,
|
||
instead, an explicit null is ignored:
|
||
|
||
foo <- fmap join $ fieldOptional "_foo_level" $ nullable int
|
||
|
||
then
|
||
|
||
delete_users(where: {_foo_level: null})
|
||
=> delete_users(where: {})
|
||
=> delete_users()
|
||
|
||
Now we’ve gone and deleted every user in the database. Whoops! Hopefully the
|
||
user had backups!
|
||
|
||
In most cases, as mentioned above, we avoid this problem by making the column
|
||
value non-nullable (which is correct, since we never treat a null value as a SQL
|
||
NULL), then creating the field using 'fieldOptional'. This creates a parser that
|
||
rejects nulls, but won’t be called at all if the field is not specified, which
|
||
is permitted by the GraphQL specification. See Note [The value of omitted
|
||
fields] in Hasura.GraphQL.Parser.Internal.Parser for more details.
|
||
|
||
Additionally, it is worth nothing that the `column` parser *does* handle
|
||
explicit nulls, by creating a Null column value.
|
||
|
||
But... the story doesn't end there. Some of our users WANT this peculiar
|
||
behaviour. For instance, they want to be able to express the following:
|
||
|
||
query($isVerified: Boolean) {
|
||
users(where: {_isVerified: {_eq: $isVerified}}) {
|
||
name
|
||
}
|
||
}
|
||
|
||
$isVerified is True -> return users who are verified
|
||
$isVerified is False -> return users who aren't
|
||
$isVerified is null -> return all users
|
||
|
||
In the future, we will likely introduce a separate group of operators that do
|
||
implement this particular behaviour explicitly; but for now we have an option that
|
||
reverts to the previous behaviour.
|
||
|
||
To do so, we have to treat explicit nulls as implicit one: this is what the
|
||
'nullable' combinator does: it treats an explicit null as if the field has never
|
||
been called at all.
|
||
-}
|
||
|
||
-- This is temporary, and should be removed as soon as possible.
|
||
mkBoolOperator ::
|
||
(MonadParse n, 'Input P.<: k) =>
|
||
-- | Naming convention for the field
|
||
NamingCase ->
|
||
-- | shall this be collapsed to True when null is given?
|
||
Options.DangerouslyCollapseBooleans ->
|
||
-- | name of this operator
|
||
GQLNameIdentifier ->
|
||
-- | optional description
|
||
Maybe G.Description ->
|
||
-- | parser for the underlying value
|
||
Parser k n a ->
|
||
InputFieldsParser n (Maybe a)
|
||
mkBoolOperator tCase Options.DangerouslyCollapseBooleans name desc = fmap join . P.fieldOptional (applyFieldNameCaseIdentifier tCase name) desc . P.nullable
|
||
mkBoolOperator tCase Options.Don'tDangerouslyCollapseBooleans name desc = P.fieldOptional (applyFieldNameCaseIdentifier tCase name) desc
|
||
|
||
equalityOperators ::
|
||
(MonadParse n, 'Input P.<: k) =>
|
||
NamingCase ->
|
||
-- | shall this be collapsed to True when null is given?
|
||
Options.DangerouslyCollapseBooleans ->
|
||
-- | parser for one column value
|
||
Parser k n (UnpreparedValue b) ->
|
||
-- | parser for a list of column values
|
||
Parser k n (UnpreparedValue b) ->
|
||
[InputFieldsParser n (Maybe (OpExpG b (UnpreparedValue b)))]
|
||
equalityOperators tCase collapseIfNull valueParser valueListParser =
|
||
[ mkBoolOperator tCase collapseIfNull (C.fromTuple $$(G.litGQLIdentifier ["_is", "null"])) Nothing $ bool ANISNOTNULL ANISNULL <$> P.boolean,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__eq) Nothing $ AEQ True <$> valueParser,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__neq) Nothing $ ANE True <$> valueParser,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__in) Nothing $ AIN <$> valueListParser,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__nin) Nothing $ ANIN <$> valueListParser
|
||
]
|
||
|
||
comparisonOperators ::
|
||
(MonadParse n, 'Input P.<: k) =>
|
||
NamingCase ->
|
||
-- | shall this be collapsed to True when null is given?
|
||
Options.DangerouslyCollapseBooleans ->
|
||
-- | parser for one column value
|
||
Parser k n (UnpreparedValue b) ->
|
||
[InputFieldsParser n (Maybe (OpExpG b (UnpreparedValue b)))]
|
||
comparisonOperators tCase collapseIfNull valueParser =
|
||
[ mkBoolOperator tCase collapseIfNull (C.fromName Name.__gt) Nothing $ AGT <$> valueParser,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__lt) Nothing $ ALT <$> valueParser,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__gte) Nothing $ AGTE <$> valueParser,
|
||
mkBoolOperator tCase collapseIfNull (C.fromName Name.__lte) Nothing $ ALTE <$> valueParser
|
||
]
|