2022-03-08 03:42:06 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
2022-12-15 23:37:00 +03:00
|
|
|
{-# LANGUAGE OverloadedLists #-}
|
2022-03-08 03:42:06 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
|
2022-03-11 02:22:54 +03:00
|
|
|
-- | The 'Transform' typeclass with various types and helper functions
|
|
|
|
-- for evaluating transformations.
|
2022-03-08 03:42:06 +03:00
|
|
|
module Hasura.RQL.DDL.Webhook.Transform.Class
|
|
|
|
( -- * Transformation Interface and Utilities
|
|
|
|
Transform (..),
|
|
|
|
|
|
|
|
-- ** Error Context
|
|
|
|
TransformErrorBundle (..),
|
|
|
|
throwErrorBundle,
|
|
|
|
|
|
|
|
-- * Templating
|
|
|
|
TemplatingEngine (..),
|
|
|
|
Template (..),
|
|
|
|
|
|
|
|
-- * Unescaped
|
|
|
|
UnescapedTemplate (..),
|
|
|
|
wrapUnescapedTemplate,
|
2022-10-16 06:53:13 +03:00
|
|
|
encodeScalar,
|
2022-03-08 03:42:06 +03:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
2022-12-15 23:37:00 +03:00
|
|
|
import Autodocodec (HasCodec (codec), dimapCodec, stringConstCodec)
|
2022-03-08 03:42:06 +03:00
|
|
|
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
|
|
|
|
import Data.Aeson qualified as J
|
|
|
|
import Data.ByteString (ByteString)
|
2022-12-07 08:59:52 +03:00
|
|
|
import Data.ByteString.Builder.Extra (toLazyByteStringWith, untrimmedStrategy)
|
2022-03-08 03:42:06 +03:00
|
|
|
import Data.ByteString.Builder.Scientific (scientificBuilder)
|
|
|
|
import Data.ByteString.Lazy qualified as LBS
|
2023-01-09 18:29:04 +03:00
|
|
|
import Data.Kind (Type)
|
2022-03-08 03:42:06 +03:00
|
|
|
import Data.Text.Encoding (encodeUtf8)
|
2022-10-16 06:53:13 +03:00
|
|
|
import Data.Validation (Validation)
|
2022-03-08 03:42:06 +03:00
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | 'Transform' describes how to reify a defunctionalized transformation for
|
|
|
|
-- a particular request field.
|
|
|
|
class Transform a where
|
|
|
|
-- | The associated type 'TransformFn a' is the defunctionalized version
|
|
|
|
-- of some transformation that should be applied to a given request field.
|
|
|
|
--
|
|
|
|
-- In most cases it is some variation on a piece of template text describing
|
|
|
|
-- the transformation.
|
|
|
|
data TransformFn a :: Type
|
|
|
|
|
2022-10-16 06:53:13 +03:00
|
|
|
data TransformCtx a :: Type
|
|
|
|
|
2022-03-08 03:42:06 +03:00
|
|
|
-- | 'transform' is a function which takes 'TransformFn' of @a@ and reifies
|
|
|
|
-- it into a function of the form:
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- ReqTransformCtx -> a -> m a
|
|
|
|
-- @
|
|
|
|
transform ::
|
|
|
|
MonadError TransformErrorBundle m =>
|
|
|
|
TransformFn a ->
|
2022-10-16 06:53:13 +03:00
|
|
|
TransformCtx a ->
|
2022-03-08 03:42:06 +03:00
|
|
|
a ->
|
|
|
|
m a
|
|
|
|
|
2022-03-11 02:22:54 +03:00
|
|
|
-- | Validate a 'TransformFn' of @a@.
|
|
|
|
validate ::
|
|
|
|
TemplatingEngine ->
|
|
|
|
TransformFn a ->
|
|
|
|
Validation TransformErrorBundle ()
|
|
|
|
|
2022-03-08 03:42:06 +03:00
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | We use collect all transformation failures as a '[J.Value]'.
|
|
|
|
newtype TransformErrorBundle = TransformErrorBundle
|
|
|
|
{ tebMessages :: [J.Value]
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Generic, Show)
|
|
|
|
deriving newtype (Monoid, Semigroup, FromJSON, ToJSON)
|
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
|
|
|
|
|
|
|
-- | A helper function for serializing transformation errors to JSON.
|
|
|
|
throwErrorBundle ::
|
|
|
|
MonadError TransformErrorBundle m =>
|
|
|
|
Text ->
|
|
|
|
Maybe J.Value ->
|
|
|
|
m a
|
|
|
|
throwErrorBundle msg val = do
|
|
|
|
let requiredCtx =
|
|
|
|
[ "error_code" J..= ("TransformationError" :: Text),
|
|
|
|
"message" J..= msg
|
|
|
|
]
|
|
|
|
optionalCtx =
|
|
|
|
[ ("value" J..=) <$> val
|
|
|
|
]
|
|
|
|
err = J.object (requiredCtx <> catMaybes optionalCtx)
|
|
|
|
throwError $ TransformErrorBundle [err]
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | Available templating engines.
|
|
|
|
data TemplatingEngine
|
|
|
|
= Kriti
|
|
|
|
deriving stock (Bounded, Enum, 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 anyclass (NFData)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
2022-12-15 23:37:00 +03:00
|
|
|
instance HasCodec TemplatingEngine where
|
|
|
|
codec = stringConstCodec [(Kriti, "Kriti")]
|
|
|
|
|
2022-03-08 03:42:06 +03:00
|
|
|
-- XXX(jkachmar): We need roundtrip tests for these instances.
|
|
|
|
instance FromJSON TemplatingEngine where
|
|
|
|
parseJSON =
|
|
|
|
J.genericParseJSON
|
|
|
|
J.defaultOptions
|
|
|
|
{ J.tagSingleConstructors = True
|
|
|
|
}
|
|
|
|
|
|
|
|
-- XXX(jkachmar): We need roundtrip tests for these instances.
|
|
|
|
instance ToJSON TemplatingEngine where
|
|
|
|
toJSON =
|
|
|
|
J.genericToJSON
|
|
|
|
J.defaultOptions
|
|
|
|
{ J.tagSingleConstructors = True
|
|
|
|
}
|
|
|
|
|
|
|
|
toEncoding =
|
|
|
|
J.genericToEncoding
|
|
|
|
J.defaultOptions
|
|
|
|
{ J.tagSingleConstructors = True
|
|
|
|
}
|
|
|
|
|
2022-03-11 02:22:54 +03:00
|
|
|
-- | Textual transformation template.
|
2022-03-08 03:42:06 +03:00
|
|
|
newtype Template = Template
|
|
|
|
{ unTemplate :: Text
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Generic, Ord, Show)
|
|
|
|
deriving newtype (Hashable, FromJSONKey, ToJSONKey)
|
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
|
|
|
|
2022-12-15 23:37:00 +03:00
|
|
|
instance HasCodec Template where
|
|
|
|
codec = dimapCodec Template unTemplate codec
|
|
|
|
|
2022-03-08 03:42:06 +03:00
|
|
|
instance J.FromJSON Template where
|
2022-03-11 02:22:54 +03:00
|
|
|
parseJSON = J.withText "Template" (pure . Template)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
|
|
|
instance J.ToJSON Template where
|
|
|
|
toJSON = J.String . coerce
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
|
|
|
|
-- | Validated textual transformation template /for string
|
|
|
|
-- interpolation only/.
|
|
|
|
--
|
|
|
|
-- This is necessary due to Kriti not distinguishing between string
|
|
|
|
-- literals and string templates.
|
|
|
|
newtype UnescapedTemplate = UnescapedTemplate
|
|
|
|
{ getUnescapedTemplate :: Text
|
|
|
|
}
|
|
|
|
deriving stock (Eq, Generic, Ord, Show)
|
|
|
|
deriving newtype (Hashable, FromJSONKey, ToJSONKey)
|
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
|
|
|
|
2022-12-15 23:37:00 +03:00
|
|
|
instance HasCodec UnescapedTemplate where
|
|
|
|
codec = dimapCodec UnescapedTemplate getUnescapedTemplate codec
|
|
|
|
|
2022-03-08 03:42:06 +03:00
|
|
|
instance J.FromJSON UnescapedTemplate where
|
2022-03-11 02:22:54 +03:00
|
|
|
parseJSON = J.withText "Template" (pure . UnescapedTemplate)
|
2022-03-08 03:42:06 +03:00
|
|
|
|
|
|
|
instance J.ToJSON UnescapedTemplate where
|
|
|
|
toJSON = J.String . coerce
|
|
|
|
|
|
|
|
-- | Wrap an 'UnescapedTemplate' with escaped double quotes.
|
|
|
|
wrapUnescapedTemplate :: UnescapedTemplate -> Template
|
|
|
|
wrapUnescapedTemplate (UnescapedTemplate txt) = Template $ "\"" <> txt <> "\""
|
|
|
|
|
|
|
|
-------------------------------------------------------------------------------
|
|
|
|
-- Utility functions.
|
|
|
|
|
|
|
|
-- | Encode a JSON Scalar Value as a 'ByteString'.
|
|
|
|
-- If a non-Scalar value is provided, will return a 'TrnasformErrorBundle'
|
|
|
|
encodeScalar ::
|
|
|
|
MonadError TransformErrorBundle m =>
|
|
|
|
J.Value ->
|
|
|
|
m ByteString
|
|
|
|
encodeScalar = \case
|
|
|
|
J.String str -> pure $ encodeUtf8 str
|
|
|
|
J.Number num ->
|
2022-12-07 08:59:52 +03:00
|
|
|
-- like toLazyByteString, but tuned for output and for common small size:
|
|
|
|
pure . LBS.toStrict . toLazyByteStringWith (untrimmedStrategy 24 1024) "" $ scientificBuilder num
|
2022-03-08 03:42:06 +03:00
|
|
|
J.Bool True -> pure "true"
|
|
|
|
J.Bool False -> pure "false"
|
|
|
|
val ->
|
|
|
|
throwErrorBundle "Template must produce a String, Number, or Boolean value" (Just val)
|