graphql-engine/server/src-lib/Hasura/RQL/DDL/Webhook/Transform/Request.hs

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

200 lines
6.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveAnyClass #-}
-- | Types and subroutines related to constructing transformations on
-- HTTP requests.
module Hasura.RQL.DDL.Webhook.Transform.Request
( -- ** Request Transformation Context
RequestTransformCtx (..),
mkReqTransformCtx,
-- * Templating
TemplatingEngine (..),
Template (..),
Version (..),
runRequestTemplateTransform,
validateRequestTemplateTransform,
validateRequestTemplateTransform',
-- * Unescaped
runUnescapedRequestTemplateTransform,
runUnescapedRequestTemplateTransform',
validateRequestUnescapedTemplateTransform,
validateRequestUnescapedTemplateTransform',
)
where
-------------------------------------------------------------------------------
import Control.Arrow (left)
import Control.Lens qualified as Lens
import Data.Aeson (FromJSON, ToJSON, (.=))
import Data.Aeson qualified as Aeson
import Data.Aeson.Kriti.Functions qualified as KFunc
import Data.Bifunctor
import Data.ByteString (ByteString)
import Data.Text.Encoding qualified as TE
import Data.Validation (Validation, fromEither)
import Hasura.Prelude
import Hasura.RQL.DDL.Webhook.Transform.Class (Template (..), TemplatingEngine (..), TransformErrorBundle (..), UnescapedTemplate, encodeScalar, wrapUnescapedTemplate)
import Hasura.Session (SessionVariables)
import Kriti.Error qualified as Kriti
import Kriti.Parser qualified as Kriti
import Network.HTTP.Client.Transformable qualified as HTTP
-------------------------------------------------------------------------------
-- | Common context that is made available to all request transformations.
data RequestTransformCtx = RequestTransformCtx
{ rtcBaseUrl :: Maybe Aeson.Value,
rtcBody :: Aeson.Value,
rtcSessionVariables :: Maybe SessionVariables,
rtcQueryParams :: Maybe Aeson.Value,
rtcEngine :: TemplatingEngine
}
instance ToJSON RequestTransformCtx where
toJSON RequestTransformCtx {..} =
let required =
[ "body" .= rtcBody,
"session_variables" .= rtcSessionVariables
]
optional =
[ ("base_url" .=) <$> rtcBaseUrl,
("query_params" .=) <$> rtcQueryParams
]
in Aeson.object (required <> catMaybes optional)
-- | A smart constructor for constructing the 'RequestTransformCtx'
--
-- XXX: This function makes internal usage of 'TE.decodeUtf8', which throws an
-- impure exception when the supplied 'ByteString' cannot be decoded into valid
-- UTF8 text!
mkReqTransformCtx ::
Text ->
Maybe SessionVariables ->
TemplatingEngine ->
HTTP.Request ->
RequestTransformCtx
mkReqTransformCtx url sessionVars rtcEngine reqData =
let rtcBaseUrl = Just $ Aeson.toJSON url
rtcBody =
let mBody = Lens.preview (HTTP.body . HTTP._RequestBodyLBS) reqData >>= Aeson.decode @Aeson.Value
in fromMaybe Aeson.Null mBody
rtcSessionVariables = sessionVars
rtcQueryParams =
let queryParams =
Lens.view HTTP.queryParams reqData & fmap \(key, val) ->
(TE.decodeUtf8 key, fmap TE.decodeUtf8 val)
in Just $ Aeson.toJSON queryParams
in RequestTransformCtx {..}
-------------------------------------------------------------------------------
-- | A helper function for executing transformations from a 'Template'
-- and a 'RequestTransformCtx'.
--
-- NOTE: This and all related funtions are hard-coded to Kriti at the
-- moment. When we add additional template engines this function will
-- need to take a 'TemplatingEngine' parameter.
runRequestTemplateTransform ::
Template ->
RequestTransformCtx ->
Either TransformErrorBundle Aeson.Value
runRequestTemplateTransform template RequestTransformCtx {rtcEngine = Kriti, ..} =
let context =
[ ("$body", rtcBody),
("$session_variables", Aeson.toJSON rtcSessionVariables)
]
<> catMaybes
[ ("$query_params",) <$> rtcQueryParams,
("$base_url",) <$> rtcBaseUrl
]
kritiFuncs = KFunc.sessionFunctions rtcSessionVariables
eResult = KFunc.runKritiWith (unTemplate $ template) context kritiFuncs
in eResult & left \kritiErr ->
let renderedErr = Aeson.toJSON kritiErr
in TransformErrorBundle [renderedErr]
-- TODO: Should this live in 'Hasura.RQL.DDL.Webhook.Transform.Validation'?
validateRequestTemplateTransform ::
TemplatingEngine ->
Template ->
Either TransformErrorBundle ()
validateRequestTemplateTransform Kriti (Template template) =
bimap packBundle (const ()) $ Kriti.parser $ TE.encodeUtf8 template
where
packBundle = TransformErrorBundle . pure . Aeson.toJSON . Kriti.serialize
validateRequestTemplateTransform' ::
TemplatingEngine ->
Template ->
Validation TransformErrorBundle ()
validateRequestTemplateTransform' engine =
fromEither . validateRequestTemplateTransform engine
-------------------------------------------------------------------------------
-- | 'RequestTransform' Versioning
data Version
= V1
| V2
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 anyclass (Hashable, NFData)
instance FromJSON Version where
parseJSON v = do
version :: Int <- Aeson.parseJSON v
case version of
1 -> pure V1
2 -> pure V2
i -> fail $ "expected 1 or 2, encountered " ++ show i
instance ToJSON Version where
toJSON = \case
V1 -> Aeson.toJSON @Int 1
V2 -> Aeson.toJSON @Int 2
-------------------------------------------------------------------------------
-- | A helper function for executing Kriti transformations from a
-- 'UnescapedTemplate' and a 'RequestTrasformCtx'.
--
-- The difference from 'runRequestTemplateTransform' is that this
-- function will wrap the template text in double quotes before
-- running Kriti.
runUnescapedRequestTemplateTransform ::
RequestTransformCtx ->
UnescapedTemplate ->
Either TransformErrorBundle ByteString
runUnescapedRequestTemplateTransform context unescapedTemplate = do
result <-
runRequestTemplateTransform
(wrapUnescapedTemplate unescapedTemplate)
context
encodeScalar result
-- | Run a Kriti transformation with an unescaped template in
-- 'Validation' instead of 'Either'.
runUnescapedRequestTemplateTransform' ::
RequestTransformCtx ->
UnescapedTemplate ->
Validation TransformErrorBundle ByteString
runUnescapedRequestTemplateTransform' context unescapedTemplate =
fromEither $
runUnescapedRequestTemplateTransform context unescapedTemplate
-- TODO: Should this live in 'Hasura.RQL.DDL.Webhook.Transform.Validation'?
validateRequestUnescapedTemplateTransform ::
TemplatingEngine ->
UnescapedTemplate ->
Either TransformErrorBundle ()
validateRequestUnescapedTemplateTransform engine =
validateRequestTemplateTransform engine . wrapUnescapedTemplate
validateRequestUnescapedTemplateTransform' ::
TemplatingEngine ->
UnescapedTemplate ->
Validation TransformErrorBundle ()
validateRequestUnescapedTemplateTransform' engine =
fromEither . validateRequestUnescapedTemplateTransform engine