graphql-engine/server/src-lib/Hasura/RemoteSchema/Metadata/RemoteRelationship.hs
Auke Booij cdac24c79f 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 16:35:37 +00:00

250 lines
9.4 KiB
Haskell

{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
module Hasura.RemoteSchema.Metadata.RemoteRelationship
( ToSchemaRelationshipDef (..),
trrdRemoteField,
trrdLhsFields,
trrdRemoteSchema,
FieldCall (..),
RemoteArguments (..),
RemoteFields (..),
SchemaRemoteRelationships,
RemoteSchemaTypeRelationships (..),
rstrsName,
rstrsRelationships,
)
where
import Autodocodec
import Autodocodec.Extended (graphQLValueCodec, hashSetCodec)
import Control.Lens (makeLenses)
import Data.Aeson qualified as J
import Data.Aeson.Key qualified as K
import Data.Aeson.KeyMap qualified as KM
import Data.Aeson.TH qualified as J
import Data.Aeson.Types (prependFailure)
import Data.Bifunctor (bimap)
import Data.HashMap.Strict qualified as HM
import Data.HashMap.Strict.InsOrd.Extended qualified as OM
import Data.Scientific (floatingOrInteger)
import Data.Text qualified as T
import Hasura.Prelude
import Hasura.RQL.Types.Common
import Hasura.RemoteSchema.Metadata.Base
import Language.GraphQL.Draft.Syntax qualified as G
-- | Metadata representation of a relationship to a remote schema.
data ToSchemaRelationshipDef = ToSchemaRelationshipDef
{ -- | Identifier for this mapping.
_trrdRemoteSchema :: RemoteSchemaName,
-- | The lhs fields that must be forwarded to the remote schema.
_trrdLhsFields :: HashSet FieldName,
_trrdRemoteField :: RemoteFields
}
deriving stock (Show, Eq, Generic)
instance NFData ToSchemaRelationshipDef
instance HasCodec ToSchemaRelationshipDef where
codec =
object "ToSchemaRelationshipDef" $
ToSchemaRelationshipDef
<$> requiredField' "remote_schema" .= _trrdRemoteSchema
<*> requiredFieldWith' "lhs_fields" hashSetCodec .= _trrdLhsFields
<*> requiredField' "remote_field" .= _trrdRemoteField
-- | Targeted field in a remote schema relationship.
-- TODO: explain about subfields and why this is a container
newtype RemoteFields = RemoteFields {unRemoteFields :: NonEmpty FieldCall}
deriving (Show, Eq, Generic)
instance NFData RemoteFields
instance HasCodec RemoteFields where
codec =
named "RemoteFields" $
bimapCodec dec enc $
hashMapCodec argumentsCodec
<?> "Remote fields are represented by an object that maps each field name to its arguments."
where
argumentsCodec :: JSONCodec (RemoteArguments, Maybe RemoteFields)
argumentsCodec =
object "FieldCall" $
(,)
<$> requiredField' "arguments"
.= fst
<*> optionalField' "field"
.= snd
dec :: HashMap G.Name (RemoteArguments, Maybe RemoteFields) -> Either String RemoteFields
dec hashmap = case HM.toList hashmap of
[(fieldName, (arguments, maybeSubField))] ->
let subfields = maybe [] (toList . unRemoteFields) maybeSubField
in Right $
RemoteFields $
FieldCall {fcName = fieldName, fcArguments = arguments} :| subfields
[] -> Left "Expecting one single mapping, received none."
_ -> Left "Expecting one single mapping, received too many."
enc :: RemoteFields -> HashMap G.Name (RemoteArguments, Maybe RemoteFields)
enc (RemoteFields (field :| subfields)) =
HM.singleton (fcName field) (fcArguments field, RemoteFields <$> nonEmpty subfields)
instance J.FromJSON RemoteFields where
parseJSON = prependFailure details . fmap RemoteFields . parseRemoteFields
where
details = "Remote fields are represented by an object that maps each field name to its arguments."
parseRemoteFields = J.withObject "RemoteFields" \hashmap -> case KM.toList hashmap of
[(fieldNameKey, callValue)] -> do
fieldName <- J.parseJSON $ J.String $ K.toText fieldNameKey
callObject <- J.parseJSON callValue
arguments <- callObject J..: "arguments"
maybeSubField <- callObject J..:? "field"
subFields <-
fromMaybe [] <$> for maybeSubField \fieldValue -> do
remoteFields <- parseRemoteFields fieldValue
pure (toList remoteFields)
pure $ FieldCall {fcName = fieldName, fcArguments = arguments} :| subFields
[] -> fail "Expecting one single mapping, received none."
_ -> fail "Expecting one single mapping, received too many."
instance J.ToJSON RemoteFields where
toJSON (RemoteFields fields) = remoteFieldsJson fields
where
remoteFieldsJson (field :| subfields) =
J.object
[ K.fromText (G.unName (fcName field))
J..= J.object
( catMaybes
[ Just $ "arguments" J..= fcArguments field,
nonEmpty subfields <&> \sf -> "field" J..= remoteFieldsJson sf
]
)
]
-- | Associates a field name with the arguments it will be passed in the query.
--
-- https://graphql.github.io/graphql-spec/June2018/#sec-Language.Arguments
data FieldCall = FieldCall
{ fcName :: G.Name,
fcArguments :: RemoteArguments
}
deriving (Show, Eq, Generic)
instance NFData FieldCall
instance Hashable FieldCall
-- | Arguments to a remote GraphQL fields, represented as a mapping from name to
-- GraphQL Value. Said values can be variable names, in which case they'll be
-- referring to values we're closed over.
-- TODO: expand on this
newtype RemoteArguments = RemoteArguments
{ getRemoteArguments :: HashMap G.Name (G.Value G.Name)
}
deriving (Show, Eq, Generic, NFData)
instance Hashable RemoteArguments
instance HasCodec RemoteArguments where
codec =
named "RemoteArguments" $
CommentCodec "Remote arguments are represented by an object that maps each argument name to its value." $
dimapCodec RemoteArguments getRemoteArguments $
hashMapCodec (graphQLValueCodec varCodec)
where
varCodec = bimapCodec decodeVariable encodeVariable textCodec
decodeVariable text = case T.uncons text of
Just ('$', rest)
| T.null rest -> Left $ "Empty variable name"
| otherwise ->
onNothing
(G.mkName rest)
(Left $ "Invalid variable name '" <> T.unpack rest <> "'")
_ -> Left $ "Variable name must start with $"
encodeVariable name = "$" <> G.unName name
instance J.FromJSON RemoteArguments where
parseJSON = prependFailure details . fmap RemoteArguments . J.withObject "RemoteArguments" parseObjectFieldsToGValue
where
details = "Remote arguments are represented by an object that maps each argument name to its value."
parseObjectFieldsToGValue keyMap =
HM.fromList <$> for (KM.toList keyMap) \(K.toText -> key, value) -> do
name <- G.mkName key `onNothing` fail (T.unpack key <> " is an invalid key name")
parsedValue <- parseValueAsGValue value
pure (name, parsedValue)
parseValueAsGValue = \case
J.Object obj ->
G.VObject <$> parseObjectFieldsToGValue obj
J.Array array ->
G.VList . toList <$> traverse parseValueAsGValue array
J.String text ->
case T.uncons text of
Just ('$', rest)
| T.null rest -> fail $ "Empty variable name"
| otherwise -> case G.mkName rest of
Nothing -> fail $ "Invalid variable name '" <> T.unpack rest <> "'"
Just name' -> pure $ G.VVariable name'
_ -> pure (G.VString text)
J.Number !scientificNum ->
pure $ case floatingOrInteger scientificNum of
-- this number couldn't be interpreted as an integer
Left (_ :: Float) -> G.VFloat scientificNum
-- this number was successfully interpreted as an integer
Right n -> G.VInt n
J.Bool !boolean ->
pure $ G.VBoolean boolean
J.Null ->
pure G.VNull
instance J.ToJSON RemoteArguments where
toJSON (RemoteArguments fields) = fieldsToObject fields
where
fieldsToObject =
J.Object . KM.fromList . map (bimap (K.fromText . G.unName) gValueToValue) . HM.toList
gValueToValue =
\case
G.VVariable v -> J.toJSON ("$" <> G.unName v)
G.VInt i -> J.toJSON i
G.VFloat f -> J.toJSON f
G.VString s -> J.toJSON s
G.VBoolean b -> J.toJSON b
G.VNull -> J.Null
G.VEnum s -> J.toJSON s
G.VList list -> J.toJSON (map gValueToValue list)
G.VObject obj -> fieldsToObject obj
type RemoteRelationships r = InsOrdHashMap RelName (RemoteRelationshipG r)
data RemoteSchemaTypeRelationships r = RemoteSchemaTypeRelationships
{ _rstrsName :: G.Name,
_rstrsRelationships :: RemoteRelationships r
}
deriving (Show, Eq, Generic)
instance J.FromJSON (RemoteRelationshipG r) => J.FromJSON (RemoteSchemaTypeRelationships r) where
parseJSON = J.withObject "RemoteSchemaMetadata" \obj ->
RemoteSchemaTypeRelationships
<$> obj J..: "type_name"
<*> (oMapFromL _rrName <$> obj J..:? "relationships" J..!= [])
instance J.ToJSON (RemoteRelationshipG r) => J.ToJSON (RemoteSchemaTypeRelationships r) where
toJSON RemoteSchemaTypeRelationships {..} =
J.object
[ "type_name" J..= _rstrsName,
"relationships" J..= OM.elems _rstrsRelationships
]
type SchemaRemoteRelationships r = InsOrdHashMap G.Name (RemoteSchemaTypeRelationships r)
$(J.deriveJSON hasuraJSON ''ToSchemaRelationshipDef)
$(makeLenses ''RemoteSchemaTypeRelationships)
$(makeLenses ''ToSchemaRelationshipDef)