2022-03-08 03:42:06 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
|
|
|
|
module Hasura.RQL.DDL.Webhook.Transform.Method
|
|
|
|
( -- * Method transformations
|
|
|
|
Method (..),
|
|
|
|
TransformFn (..),
|
2022-10-16 06:53:13 +03:00
|
|
|
TransformCtx (..),
|
2022-03-23 23:23:46 +03:00
|
|
|
MethodTransformFn (..),
|
2022-03-08 03:42:06 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
import Data.Aeson (FromJSON, ToJSON)
|
|
|
|
import Data.Aeson qualified as J
|
|
|
|
import Data.CaseInsensitive qualified as CI
|
|
|
|
import Data.Text qualified as T
|
2022-03-11 02:22:54 +03:00
|
|
|
import Data.Validation
|
2022-03-08 03:42:06 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.RQL.DDL.Webhook.Transform.Class
|
2022-10-16 06:53:13 +03:00
|
|
|
( TemplatingEngine,
|
2022-03-08 03:42:06 +03:00
|
|
|
Transform (..),
|
|
|
|
TransformErrorBundle (..),
|
|
|
|
)
|
2022-10-16 06:53:13 +03:00
|
|
|
import Hasura.RQL.DDL.Webhook.Transform.Request (RequestTransformCtx)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
2022-03-23 23:23:46 +03:00
|
|
|
-- | The actual request method we are transforming.
|
|
|
|
--
|
|
|
|
-- This newtype is necessary because otherwise we end up with an
|
|
|
|
-- orphan instance.
|
2022-03-08 03:42:06 +03:00
|
|
|
newtype Method = Method (CI.CI T.Text)
|
|
|
|
deriving stock (Generic)
|
|
|
|
deriving newtype (Show, Eq)
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving anyclass (NFData)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
|
|
|
instance J.ToJSON Method where
|
|
|
|
toJSON = J.String . CI.original . coerce
|
|
|
|
|
|
|
|
instance J.FromJSON Method where
|
|
|
|
parseJSON = J.withText "Method" (pure . coerce . CI.mk)
|
|
|
|
|
|
|
|
instance Transform Method where
|
2022-03-23 23:23:46 +03:00
|
|
|
-- NOTE: GHC does not let us attach Haddock documentation to data family
|
|
|
|
-- instances, so 'MethodTransformFn' is defined separately from this
|
|
|
|
-- wrapper.
|
|
|
|
newtype TransformFn Method = MethodTransformFn_ MethodTransformFn
|
2022-03-08 03:42:06 +03:00
|
|
|
deriving stock (Eq, Generic, Show)
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving newtype (NFData, FromJSON, ToJSON)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
2022-10-16 06:53:13 +03:00
|
|
|
newtype TransformCtx Method = TransformCtx RequestTransformCtx
|
|
|
|
|
2022-03-23 23:23:46 +03:00
|
|
|
-- NOTE: GHC does not let us attach Haddock documentation to typeclass
|
|
|
|
-- method implementations, so 'applyMethodTransformFn' is defined
|
|
|
|
-- separately.
|
2022-10-16 06:53:13 +03:00
|
|
|
transform (MethodTransformFn_ fn) (TransformCtx reqCtx) = applyMethodTransformFn fn reqCtx
|
2022-03-08 03:42:06 +03:00
|
|
|
|
2022-03-23 23:23:46 +03:00
|
|
|
-- NOTE: GHC does not let us attach Haddock documentation to typeclass
|
|
|
|
-- method implementations, so 'validateMethodTransformFn' is defined
|
|
|
|
-- separately.
|
|
|
|
validate engine (MethodTransformFn_ fn) = validateMethodTransformFn engine fn
|
2022-03-11 02:22:54 +03:00
|
|
|
|
2022-03-08 03:42:06 +03:00
|
|
|
-- | The defunctionalized transformation on 'Method'.
|
2022-03-23 23:23:46 +03:00
|
|
|
newtype MethodTransformFn
|
|
|
|
= -- | Replace the HTTP existing 'Method' with a new one.
|
|
|
|
Replace Method
|
|
|
|
deriving stock (Eq, Generic, Show)
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving newtype (NFData, FromJSON, ToJSON)
|
2022-03-23 23:23:46 +03:00
|
|
|
|
|
|
|
-- | Provide an implementation for the transformations defined by
|
|
|
|
-- 'MethodTransformFn'.
|
2022-03-08 03:42:06 +03:00
|
|
|
--
|
2022-03-23 23:23:46 +03:00
|
|
|
-- If one views 'MethodTransformFn' as an interface describing HTTP method
|
|
|
|
-- transformations, this can be seen as an implementation of these
|
|
|
|
-- transformations as normal Haskell functions.
|
|
|
|
applyMethodTransformFn ::
|
|
|
|
MonadError TransformErrorBundle m =>
|
|
|
|
MethodTransformFn ->
|
|
|
|
RequestTransformCtx ->
|
|
|
|
Method ->
|
|
|
|
m Method
|
|
|
|
applyMethodTransformFn fn _context _oldMethod = case fn of
|
|
|
|
Replace newMethod -> pure newMethod
|
|
|
|
|
|
|
|
-- | Validate that the provided 'MethodTransformFn' is correct in the context
|
|
|
|
-- of a particular 'TemplatingEngine'.
|
|
|
|
--
|
|
|
|
-- This is a product of the fact that the correctness of a given transformation
|
|
|
|
-- may be dependent on zero, one, or more of the templated transformations
|
|
|
|
-- encoded within the given 'MethodTransformFn'.
|
|
|
|
--
|
|
|
|
-- XXX: Do we want to validate the HTTP method verb?
|
|
|
|
validateMethodTransformFn ::
|
|
|
|
TemplatingEngine ->
|
|
|
|
MethodTransformFn ->
|
|
|
|
Validation TransformErrorBundle ()
|
|
|
|
validateMethodTransformFn _engine = \case
|
|
|
|
Replace _method -> pure ()
|