mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-17 12:31:52 +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
147 lines
5.7 KiB
Haskell
147 lines
5.7 KiB
Haskell
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
|
|
|
|
-- | This module defines the monads required to run parser tests.
|
|
--
|
|
-- Warning: a lot of the implementations are currently 'undefined'. As we write
|
|
-- more advanced tests, they might require implementations.
|
|
module Test.Parser.Monad
|
|
( ParserTestT (..),
|
|
SchemaEnvironment,
|
|
SchemaTestT (..),
|
|
)
|
|
where
|
|
|
|
import Control.Monad.Memoize
|
|
import Data.Aeson.Internal (JSONPathElement)
|
|
import Data.Has (Has (..))
|
|
import Data.Text qualified as T
|
|
import Hasura.Base.Error (QErr)
|
|
import Hasura.Base.ErrorMessage
|
|
import Hasura.GraphQL.Parser.Class
|
|
import Hasura.GraphQL.Parser.ErrorCode
|
|
import Hasura.GraphQL.Schema.Common (SchemaContext (..), SchemaKind (..), ignoreRemoteRelationship)
|
|
import Hasura.GraphQL.Schema.NamingCase
|
|
import Hasura.GraphQL.Schema.Options (SchemaOptions (..))
|
|
import Hasura.GraphQL.Schema.Options qualified as Options
|
|
import Hasura.GraphQL.Schema.Typename
|
|
import Hasura.Prelude
|
|
import Hasura.RQL.Types.SourceCustomization (CustomizeRemoteFieldName, MkRootFieldName)
|
|
import Hasura.Session (adminRoleName)
|
|
import Language.Haskell.TH.Syntax qualified as TH
|
|
import Test.Hspec
|
|
|
|
notImplemented :: String -> a
|
|
notImplemented location =
|
|
error $ "Not implemented: Test.Parser.Monad." <> location
|
|
|
|
-- | Monad builder environment.
|
|
--
|
|
-- Parser functions generally have a return type of @m (Parser n)@. The @m@
|
|
-- parameter is mocked through 'SchemaTestT', which requires a bunch of 'Has'
|
|
-- instances, as well as a 'ReaderT' instance for environment
|
|
-- settings/configurations. This type repesents these settings.
|
|
--
|
|
-- SchemaEnvironment: currently void. This is subject to change if we require
|
|
-- more complex setup.
|
|
data SchemaEnvironment
|
|
|
|
instance Has NamingCase SchemaEnvironment where
|
|
getter :: SchemaEnvironment -> NamingCase
|
|
getter = const HasuraCase
|
|
|
|
modifier :: (NamingCase -> NamingCase) -> SchemaEnvironment -> SchemaEnvironment
|
|
modifier = notImplemented "modifier<Has NamingCase SchemaEnvironment>"
|
|
|
|
instance Has SchemaOptions SchemaEnvironment where
|
|
getter :: SchemaEnvironment -> SchemaOptions
|
|
getter =
|
|
const
|
|
SchemaOptions
|
|
{ soStringifyNumbers = Options.Don'tStringifyNumbers,
|
|
soDangerousBooleanCollapse = Options.Don'tDangerouslyCollapseBooleans,
|
|
soInferFunctionPermissions = Options.InferFunctionPermissions,
|
|
soOptimizePermissionFilters = Options.Don'tOptimizePermissionFilters
|
|
}
|
|
|
|
modifier :: (SchemaOptions -> SchemaOptions) -> SchemaEnvironment -> SchemaEnvironment
|
|
modifier = notImplemented "modifier<Has SchemaOptions SchemaEnvironment>"
|
|
|
|
instance Has SchemaContext SchemaEnvironment where
|
|
getter :: SchemaEnvironment -> SchemaContext
|
|
getter =
|
|
const
|
|
SchemaContext
|
|
{ scSchemaKind = HasuraSchema,
|
|
scRemoteRelationshipParserBuilder = ignoreRemoteRelationship,
|
|
scRole = adminRoleName
|
|
}
|
|
|
|
modifier :: (SchemaContext -> SchemaContext) -> SchemaEnvironment -> SchemaEnvironment
|
|
modifier = notImplemented "modifier<Has SchemaContext SchemaEnvironment>"
|
|
|
|
instance Has MkTypename SchemaEnvironment where
|
|
getter :: SchemaEnvironment -> MkTypename
|
|
getter = const (MkTypename id)
|
|
|
|
modifier :: (MkTypename -> MkTypename) -> SchemaEnvironment -> SchemaEnvironment
|
|
modifier = notImplemented "modifier<Has MkTypeName SchemaEnvironment>"
|
|
|
|
instance Has MkRootFieldName SchemaEnvironment where
|
|
getter :: SchemaEnvironment -> MkRootFieldName
|
|
getter = const mempty
|
|
|
|
modifier :: (MkRootFieldName -> MkRootFieldName) -> SchemaEnvironment -> SchemaEnvironment
|
|
modifier = notImplemented "modifier<Has MkRootFieldName SchemaEnvironment>"
|
|
|
|
instance Has CustomizeRemoteFieldName SchemaEnvironment where
|
|
getter :: SchemaEnvironment -> CustomizeRemoteFieldName
|
|
getter = notImplemented "getter<Has CustomizeRemoteFieldName SchemaEnvironment>"
|
|
|
|
modifier :: (CustomizeRemoteFieldName -> CustomizeRemoteFieldName) -> SchemaEnvironment -> SchemaEnvironment
|
|
modifier = notImplemented "modifier<Has CustomizeRemoteFieldName SchemaEnvironment>"
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
-- | SchemaTestT
|
|
newtype SchemaTestT a = SchemaTestT a
|
|
deriving stock (Functor)
|
|
deriving (Applicative, Monad) via Identity
|
|
|
|
instance MonadError QErr SchemaTestT where
|
|
throwError :: forall a. QErr -> SchemaTestT a
|
|
throwError = notImplemented "throwError<MonadError QErr SchemaTestT>"
|
|
|
|
catchError :: forall a. SchemaTestT a -> (QErr -> SchemaTestT a) -> SchemaTestT a
|
|
catchError = notImplemented "catchError<MonadError QErr SchemaTestT>"
|
|
|
|
-- | Note this is not used because all the actual getters/setters for
|
|
-- SchemaEnvironment are @const X@, so these bottoms never actually get
|
|
-- evaluated.
|
|
instance MonadReader SchemaEnvironment SchemaTestT where
|
|
ask :: SchemaTestT SchemaEnvironment
|
|
ask = notImplemented "ask<MonadReader SchemaEnvironment SchemaTestT>"
|
|
|
|
local :: (SchemaEnvironment -> SchemaEnvironment) -> SchemaTestT a -> SchemaTestT a
|
|
local = notImplemented "local<MonadReader SchemaEnvironment SchemaTestT>"
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
-- | ParserTestT
|
|
--
|
|
-- Encodes an assertion error (as `Left`) or a value as `Right`.
|
|
newtype ParserTestT a = ParserTestT (Either (IO ()) a)
|
|
deriving stock (Functor)
|
|
deriving (Applicative, Monad) via (Either (IO ()))
|
|
|
|
instance MonadMemoize SchemaTestT where
|
|
memoizeOn :: TH.Name -> a -> SchemaTestT p -> SchemaTestT p
|
|
memoizeOn _ _ = id
|
|
|
|
instance MonadParse ParserTestT where
|
|
withKey :: JSONPathElement -> ParserTestT a -> ParserTestT a
|
|
withKey = const id
|
|
|
|
parseErrorWith :: ParseErrorCode -> ErrorMessage -> ParserTestT a
|
|
parseErrorWith code text =
|
|
ParserTestT . Left . expectationFailure $ show code <> ": " <> T.unpack (fromErrorMessage text)
|