graphql-engine/server/src-lib/Hasura/GraphQL/Schema/Parser.hs
Auke Booij 1007ea27ae server: refactor MonadSchema into MonadMemoize
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
2022-08-04 13:45:53 +00:00

168 lines
5.9 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE PatternSynonyms #-}
-- | In 'Hasura.GraphQL.Parser', the 'Definition' type has a 'dOrigin' field
-- that allows to track where a fragment of GraphQL type information comes from.
-- This is useful for error reporting and internal repair mechanisms such as
-- inconsistency tracking.
--
-- Morally, within the HGE codebase, this origin is always 'MetadataObjId'.
-- However, in order to avoid an import of 'Hasura.RQL' from
-- 'Hasura.GraphQL.Parser', the 'dOrigin' has been defined through a type
-- parameter of 'Definition'. This type parameter then has to get threaded
-- through throughout the 'Hasura.GraphQL.Parser' module hierarchy, so that it
-- ends up in a lot of types. This is very noisy.
--
-- In order to avoid the noise of this type parameter, which really only has one
-- value, and is really only used in one type, this module erases the type
-- parameter by filling in the desired value, exporting type synonyms of the
-- now-fixed notion of "origin". So most modules in the HGE codebase should
-- import this module rather than 'Hasura.GraphQL.Parser'.
module Hasura.GraphQL.Schema.Parser
( -- The pattern is as follows:
-- 1. Export a type synonym which has the origin type parameter set to
-- 'MetadataObjId'
FieldParser,
-- 2. Export the constructor of the type. Note that despite the use of
-- 'PatternSynonyms', there is no pattern being defined. The reason for
-- using 'PatternSynonyms' is that that extension (and the 'pattern'
-- syntax) allows re-exporting a constructor of a type, without
-- re-exporting its original associated type. This is not possible in
-- plain Haskell2010.
pattern P.FieldParser,
InputFieldsParser,
pattern P.InputFieldsParser,
Parser,
pattern P.Parser,
Schema,
pattern P.Schema,
ConflictingDefinitions,
pattern P.ConflictingDefinitions,
Definition,
pattern P.Definition,
Type,
Directive,
pattern P.Directive,
DirectiveInfo,
pattern P.DirectiveInfo,
FieldInfo,
pattern P.FieldInfo,
InputFieldInfo,
pattern P.InputFieldInfo,
HasTypeDefinitions,
SomeDefinitionTypeInfo,
pattern P.SomeDefinitionTypeInfo,
TypeDefinitionsWrapper,
pattern TypeDefinitionsWrapper,
P.ParseErrorCode (..),
toQErr,
module Hasura.GraphQL.Parser,
Memoize.MonadMemoize,
memoizeOn,
memoize,
)
where
-- Re-export everything, except types whose type parameter we want to fill in in
-- this module.
import Control.Monad.Error.Class
import Control.Monad.Memoize qualified as Memoize
import Data.Typeable
import Hasura.Base.Error
import Hasura.Base.ErrorMessage (ErrorMessage (fromErrorMessage))
import Hasura.GraphQL.Parser hiding
( ConflictingDefinitions (..),
Definition,
Directive,
DirectiveInfo,
FieldInfo,
FieldParser,
HasTypeDefinitions,
InputFieldInfo,
InputFieldsParser,
ParseErrorCode (..),
Parser,
Schema,
SomeDefinitionTypeInfo,
Type,
TypeDefinitionsWrapper,
)
import Hasura.GraphQL.Parser qualified as P
import Hasura.Prelude
import Hasura.RQL.Types.Metadata.Object
import Language.Haskell.TH qualified as TH
type FieldParser = P.FieldParser MetadataObjId
type Parser = P.Parser MetadataObjId
type Schema = P.Schema MetadataObjId
type ConflictingDefinitions = P.ConflictingDefinitions MetadataObjId
type Type = P.Type MetadataObjId
type InputFieldsParser = P.InputFieldsParser MetadataObjId
type Definition = P.Definition MetadataObjId
type Directive = P.Directive MetadataObjId
type DirectiveInfo = P.DirectiveInfo MetadataObjId
type FieldInfo = P.FieldInfo MetadataObjId
type InputFieldInfo = P.InputFieldInfo MetadataObjId
type HasTypeDefinitions = P.HasTypeDefinitions MetadataObjId
type SomeDefinitionTypeInfo = P.SomeDefinitionTypeInfo MetadataObjId
type TypeDefinitionsWrapper = P.TypeDefinitionsWrapper MetadataObjId
-- | In order to aid type inference and type checking, we define this pattern
-- synonym (an actual one) which restricts 'P.TypeDefinitionsWrapper' to have
-- 'MetadataObjId' set for its origin type parameter.
pattern TypeDefinitionsWrapper :: () => forall a. HasTypeDefinitions a => a -> TypeDefinitionsWrapper
pattern TypeDefinitionsWrapper typeDef = P.TypeDefinitionsWrapper typeDef
toQErr :: (MonadError QErr m) => Either ParseError a -> m a
toQErr = either (throwError . parseErrorToQErr) pure
where
parseErrorToQErr :: ParseError -> QErr
parseErrorToQErr ParseError {pePath, peMessage, peCode} =
(err400 (parseErrorCodeToCode peCode) (fromErrorMessage peMessage)) {qePath = pePath}
parseErrorCodeToCode :: P.ParseErrorCode -> Code
parseErrorCodeToCode P.ValidationFailed = ValidationFailed
parseErrorCodeToCode P.ParseFailed = ParseFailed
parseErrorCodeToCode P.ConflictingDefinitionsError = Unexpected
parseErrorCodeToCode P.NotSupported = NotSupported
memoizeOn ::
(Memoize.MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n, Typeable b) =>
-- | A unique name used to identify the function being memoized. There isnt
-- really any metaprogramming going on here, we just use a Template Haskell
-- 'TH.Name' as a convenient source for a static, unique identifier.
TH.Name ->
-- | The value to use as the memoization key. Its the callers
-- responsibility to ensure multiple calls to the same function dont use
-- the same key.
a ->
-- | The value to be memoized. 'p' is intended to be either 'Parser k' or
-- 'FieldParser'.
m (p n b) ->
m (p n b)
memoizeOn = Memoize.memoizeOn
-- | A wrapper around 'memoizeOn' that memoizes a function by using its argument
-- as the key.
memoize ::
(Memoize.MonadMemoize m, Ord a, Typeable a, Typeable p, MonadParse n, Typeable b) =>
TH.Name ->
-- | A function generating something to be memoized. 'p' is intended to be
-- either 'Parser k' or 'FieldParser'.
(a -> m (p n b)) ->
(a -> m (p n b))
memoize = Memoize.memoize