2021-09-24 01:56:37 +03:00
|
|
|
{-# LANGUAGE Arrows #-}
|
2021-03-15 16:02:58 +03:00
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
|
|
|
|
module Hasura.SQL.AnyBackend
|
2021-09-24 01:56:37 +03:00
|
|
|
( AnyBackend,
|
|
|
|
liftTag,
|
|
|
|
mkAnyBackend,
|
|
|
|
mapBackend,
|
|
|
|
traverseBackend,
|
|
|
|
dispatchAnyBackend,
|
|
|
|
dispatchAnyBackend',
|
|
|
|
dispatchAnyBackendArrow,
|
|
|
|
dispatchAnyBackendWithTwoConstraints,
|
|
|
|
unpackAnyBackend,
|
|
|
|
composeAnyBackend,
|
|
|
|
runBackend,
|
|
|
|
parseAnyBackendFromJSON,
|
|
|
|
debugAnyBackendToJSON,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Arrow.Extended (ArrowChoice, arr, (|||))
|
|
|
|
import Data.Aeson
|
|
|
|
import Data.Aeson.Types (Parser)
|
|
|
|
import Data.Kind (Constraint, Type)
|
|
|
|
import Hasura.Incremental (Cacheable)
|
|
|
|
import Hasura.Prelude
|
|
|
|
import Hasura.SQL.Backend
|
|
|
|
import Hasura.SQL.TH
|
|
|
|
import Hasura.SQL.Tag
|
|
|
|
import Language.Haskell.TH hiding (Type)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Types and constraints
|
2021-03-15 16:02:58 +03:00
|
|
|
|
|
|
|
-- | This type is essentially an unlabeled box for types indexed by BackendType.
|
|
|
|
-- Given some type defined as 'data T (b :: BackendType) = ...', we can define
|
|
|
|
-- 'AnyBackend T' without mentioning any 'BackendType'.
|
|
|
|
--
|
|
|
|
-- This is useful for having generic containers of potentially different types
|
2021-03-18 23:34:11 +03:00
|
|
|
-- of T. For instance, @SourceCache@ is defined as a
|
|
|
|
-- @HashMap SourceName (AnyBackend SourceInfo)@.
|
|
|
|
--
|
|
|
|
-- This type is generated with Template Haskell to have one constructor per
|
|
|
|
-- backend. This declaration generates the following type:
|
|
|
|
--
|
|
|
|
-- data AnyBackend (i :: BackendType -> Type)
|
2022-03-11 02:22:54 +03:00
|
|
|
-- = PostgresVanillaValue (i '(Postgres Vanilla))
|
|
|
|
-- | PostgresCitusValue (i '(Postgres Citus))
|
|
|
|
-- | BigQueryValue (i 'BigQuery)
|
|
|
|
-- | MySQLValue (i 'MySQL)
|
|
|
|
-- | MSSQLValue (i 'MSSQL)
|
|
|
|
-- | ExperimentalValue (i 'Experimental)
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- the kind of the type variable, expressed with a quote
|
|
|
|
varKind <- [t|BackendType -> Type|]
|
|
|
|
-- how to build a basic type: no UNPACK, no strict!, just a name
|
|
|
|
let normalType = (Bang NoSourceUnpackedness NoSourceStrictness,)
|
|
|
|
-- the name of the type variable
|
|
|
|
let typeVarName = mkName "i"
|
|
|
|
backendData
|
|
|
|
-- the name of the type
|
|
|
|
(mkName "AnyBackend")
|
|
|
|
-- the type variable
|
|
|
|
[KindedTV typeVarName varKind]
|
|
|
|
-- the constructor for each backend
|
|
|
|
( \b ->
|
|
|
|
pure $
|
|
|
|
NormalC
|
|
|
|
-- the name of the constructor: `FooValue`
|
|
|
|
(getBackendValueName b)
|
|
|
|
-- one argument: `i 'Foo`
|
|
|
|
-- (we Apply a type Variable to a Promoted name)
|
|
|
|
[normalType $ AppT (VarT typeVarName) (getBackendTypeValue b)]
|
|
|
|
)
|
|
|
|
-- classes in the deriving clause
|
|
|
|
[''Generic]
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
-- | Generates a constraint for all backends.
|
|
|
|
-- This Template Haskell expression generates the following constraint type:
|
|
|
|
--
|
|
|
|
-- type AllBackendsSatisfy (c :: BackendType -> Constraint) =
|
|
|
|
-- ( c 'Postgres
|
|
|
|
-- , c 'MSSQL
|
|
|
|
-- , ...
|
|
|
|
-- )
|
|
|
|
--
|
|
|
|
-- That is, given a class C, this creates the constraint that dictates that all
|
|
|
|
-- backend must satisfy C.
|
|
|
|
type AllBackendsSatisfy (c :: BackendType -> Constraint) =
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- the constraint for each backend: `c 'Foo`
|
|
|
|
-- (we Apply a type Variable to a Promoted name)
|
|
|
|
constraints <- forEachBackend \b ->
|
|
|
|
pure $ AppT (VarT $ mkName "c") (getBackendTypeValue b)
|
|
|
|
-- transforms a list of constraints into a tuple of constraints
|
|
|
|
-- by folding the "type application" constructor:
|
|
|
|
--
|
|
|
|
-- > apply (,,) [c 'Foo, c 'Bar, c 'Baz]
|
|
|
|
-- > apply (c 'Foo,,) [c 'Bar, c 'Baz]
|
|
|
|
-- > apply (c 'Foo, c 'Bar,) [c 'Baz]
|
|
|
|
-- > apply (c 'Foo, c 'Bar, c 'Baz) []
|
|
|
|
-- = (c 'Foo, c 'Bar, c 'Baz)
|
|
|
|
let tupleConstructor = TupleT $ length constraints
|
|
|
|
pure $ foldl AppT tupleConstructor constraints
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
-- | Generates a constraint for a generic type over all backends.
|
|
|
|
-- This Template Haskell expression generates the following constraint type:
|
|
|
|
--
|
|
|
|
-- type SatisfiesForAllBackends
|
|
|
|
-- (i :: BackendType -> Type)
|
|
|
|
-- (c :: Type -> Constraint)
|
|
|
|
-- = ( c (i 'Postgres)
|
|
|
|
-- , c (i 'MSSQL)
|
|
|
|
-- , ...
|
|
|
|
-- )
|
|
|
|
--
|
|
|
|
-- That is, given a type I and a class C, this creates the constraint that
|
|
|
|
-- dictates that for all backends b, @I b@ must satisfy C.
|
|
|
|
type SatisfiesForAllBackends
|
|
|
|
(i :: BackendType -> Type)
|
2021-09-24 01:56:37 +03:00
|
|
|
(c :: Type -> Constraint) =
|
|
|
|
$( do
|
|
|
|
-- the constraint for each backend: `c (i 'Foo)`
|
|
|
|
constraints <- forEachBackend \b ->
|
|
|
|
pure $ AppT (VarT $ mkName "c") $ AppT (VarT $ mkName "i") (getBackendTypeValue b)
|
|
|
|
-- transforms a list of constraints into a tuple of constraints
|
|
|
|
-- by folding the type application constructor
|
|
|
|
-- by folding the "type application" constructor:
|
|
|
|
--
|
|
|
|
-- > apply (,,) [c (i 'Foo), c (i 'Bar), c (i 'Baz)]
|
|
|
|
-- > apply (c (i 'Foo),,) [c (i 'Bar), c (i 'Baz)]
|
|
|
|
-- > apply (c (i 'Foo), c (i 'Bar),) [c (i 'Baz)]
|
|
|
|
-- > apply (c (i 'Foo), c (i 'Bar), c (i 'Baz)) []
|
|
|
|
-- = (c (i 'Foo), c (i 'Bar), c (i 'Baz))
|
|
|
|
let tupleConstructor = TupleT $ length constraints
|
|
|
|
pure $ foldl AppT tupleConstructor constraints
|
|
|
|
)
|
2021-03-18 23:34:11 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Functions on AnyBackend
|
|
|
|
|
2021-07-07 04:43:42 +03:00
|
|
|
-- | How to obtain a tag from a runtime value. This function is generated with
|
|
|
|
-- Template Haskell for each 'Backend'. The case switch looks like this:
|
|
|
|
--
|
|
|
|
-- Postgres -> PostgresValue PostgresTag
|
|
|
|
-- MSSQL -> MSSQLValue MSSQLTag
|
|
|
|
-- ...
|
|
|
|
liftTag :: BackendType -> AnyBackend BackendTag
|
2021-09-24 01:56:37 +03:00
|
|
|
liftTag t =
|
|
|
|
$( backendCase
|
|
|
|
-- the expression on which we do the case switch
|
|
|
|
[|t|]
|
|
|
|
-- the pattern for a given backend: the backend type itself
|
|
|
|
(\(con :| args) -> pure $ ConP con [ConP a [] | a <- args])
|
|
|
|
-- the body for a given backend: creating and wrapping the tag
|
|
|
|
(\b -> [|$(pure $ ConE $ getBackendValueName b) $(pure $ ConE $ getBackendTagName b)|])
|
|
|
|
-- no default case: every constructor should be handled
|
|
|
|
Nothing
|
|
|
|
)
|
2021-07-07 04:43:42 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
-- | Transforms an `AnyBackend i` into an `AnyBackend j`.
|
2021-09-24 01:56:37 +03:00
|
|
|
mapBackend ::
|
|
|
|
forall
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(j :: BackendType -> Type).
|
|
|
|
AnyBackend i ->
|
|
|
|
(forall b. i b -> j b) ->
|
|
|
|
AnyBackend j
|
2021-03-18 23:34:11 +03:00
|
|
|
mapBackend e f =
|
|
|
|
-- generates a case switch that, for each constructor, applies the provided function
|
|
|
|
-- case e of
|
|
|
|
-- FooValue x -> FooValue (f x)
|
|
|
|
-- BarValue x -> BarValue (f x)
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- we create a case match for each backend
|
|
|
|
matches <- forEachBackend \b -> do
|
|
|
|
-- the name of the constructor
|
|
|
|
let consName = getBackendValueName b
|
|
|
|
-- the patterrn we match: `FooValue x`
|
|
|
|
let matchPattern = ConP consName [VarP $ mkName "x"]
|
|
|
|
-- the body of the match: `FooValue (f x)`
|
|
|
|
matchBody <- [|$(pure $ ConE consName) (f x)|]
|
|
|
|
pure $ Match matchPattern (NormalB matchBody) []
|
|
|
|
-- the expression on which we do the case
|
|
|
|
caseExpr <- [|e|]
|
|
|
|
-- return the the expression of the case switch
|
|
|
|
pure $ CaseE caseExpr matches
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
-- | Traverse an `AnyBackend i` into an `f (AnyBackend j)`.
|
2021-09-24 01:56:37 +03:00
|
|
|
traverseBackend ::
|
|
|
|
forall
|
|
|
|
(c :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(j :: BackendType -> Type)
|
|
|
|
f.
|
|
|
|
(AllBackendsSatisfy c, Applicative f) =>
|
|
|
|
AnyBackend i ->
|
|
|
|
(forall b. c b => i b -> f (j b)) ->
|
|
|
|
f (AnyBackend j)
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
traverseBackend e f =
|
|
|
|
-- generates a case switch that, for each constructor, applies the provided function
|
|
|
|
-- case e of
|
|
|
|
-- FooValue x -> FooValue <$> f x
|
|
|
|
-- BarValue x -> BarValue <$> f x
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- we create a case match for each backend
|
|
|
|
matches <- forEachBackend \b -> do
|
|
|
|
-- the name of the constructor
|
|
|
|
let consName = getBackendValueName b
|
|
|
|
-- the patterrn we match: `FooValue x`
|
|
|
|
let matchPattern = ConP consName [VarP $ mkName "x"]
|
|
|
|
-- the body of the match: `FooValue <$> f x`
|
|
|
|
matchBody <- [|$(pure $ ConE consName) <$> f x|]
|
|
|
|
pure $ Match matchPattern (NormalB matchBody) []
|
|
|
|
-- the expression on which we do the case
|
|
|
|
caseExpr <- [|e|]
|
|
|
|
-- return the the expression of the case switch
|
|
|
|
pure $ CaseE caseExpr matches
|
server: IR for DB-DB joins
### Description
This PR adds the required IR for DB to DB joins, based on @paf31 and @0x777 's `feature/db-to-db` branch.
To do so, it also refactors the IR to introduce a new type parameter, `r`, which is used to recursively constructs the `v` parameter of remote QueryDBs. When collecting remote joins, we replace `r` with `Const Void`, indicating at the type level that there cannot be any leftover remote join.
Furthermore, this PR refactors IR.Select for readability, moves some code from IR.Root to IR.Select to avoid having to deal with circular dependencies, and makes it compile by adding `error` in all new cases in the execution pipeline.
The diff doesn't make it clear, but most of Select.hs is actually unchanged. Declarations have just been reordered by topic, in the following order:
- type declarations
- instance declarations
- type aliases
- constructor functions
- traverse functions
https://github.com/hasura/graphql-engine-mono/pull/1580
Co-authored-by: Phil Freeman <630306+paf31@users.noreply.github.com>
GitOrigin-RevId: bbdcb4119cec8bb3fc32f1294f91b8dea0728721
2021-06-18 02:12:11 +03:00
|
|
|
)
|
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
-- | Creates a new @AnyBackend i@ for a given backend @b@ by wrapping the given @i b@.
|
2021-09-24 01:56:37 +03:00
|
|
|
mkAnyBackend ::
|
|
|
|
forall
|
|
|
|
(b :: BackendType)
|
|
|
|
(i :: BackendType -> Type).
|
|
|
|
HasTag b =>
|
|
|
|
i b ->
|
|
|
|
AnyBackend i
|
2021-03-15 16:02:58 +03:00
|
|
|
mkAnyBackend =
|
2021-03-18 23:34:11 +03:00
|
|
|
-- generates a case switch that associates a tag constructor to a value constructor
|
|
|
|
-- case backendTag @b of
|
2021-07-07 04:43:42 +03:00
|
|
|
-- FooTag -> FooValue
|
2021-03-18 23:34:11 +03:00
|
|
|
-- BarTag -> BarValue
|
2021-09-24 01:56:37 +03:00
|
|
|
$( backendCase
|
|
|
|
[|backendTag @b|]
|
|
|
|
-- the pattern for a backend
|
|
|
|
(\b -> pure $ ConP (getBackendTagName b) [])
|
|
|
|
-- the body for a backend
|
|
|
|
(pure . ConE . getBackendValueName)
|
|
|
|
-- no default case
|
|
|
|
Nothing
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
-- | Dispatch a function to the value inside the @AnyBackend@, that does not
|
|
|
|
-- require bringing into scope a new class constraint.
|
2021-09-24 01:56:37 +03:00
|
|
|
runBackend ::
|
|
|
|
forall
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type).
|
|
|
|
AnyBackend i ->
|
|
|
|
(forall (b :: BackendType). i b -> r) ->
|
|
|
|
r
|
2021-03-18 23:34:11 +03:00
|
|
|
runBackend b f = $(mkDispatch 'f 'b)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
|
|
|
-- | Dispatch an existential using an universally quantified function while
|
|
|
|
-- also resolving a different constraint.
|
|
|
|
-- Use this to dispatch Backend* instances.
|
|
|
|
-- This is essentially a wrapper around 'runAnyBackend f . repackAnyBackend @c'.
|
2021-09-24 01:56:37 +03:00
|
|
|
dispatchAnyBackend ::
|
|
|
|
forall
|
|
|
|
(c :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type).
|
|
|
|
AllBackendsSatisfy c =>
|
|
|
|
AnyBackend i ->
|
|
|
|
(forall (b :: BackendType). c b => i b -> r) ->
|
|
|
|
r
|
2021-03-18 23:34:11 +03:00
|
|
|
dispatchAnyBackend e f = $(mkDispatch 'f 'e)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
dispatchAnyBackendWithTwoConstraints ::
|
|
|
|
forall
|
|
|
|
(c1 :: BackendType -> Constraint)
|
|
|
|
(c2 :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type).
|
|
|
|
AllBackendsSatisfy c1 =>
|
|
|
|
AllBackendsSatisfy c2 =>
|
|
|
|
AnyBackend i ->
|
|
|
|
(forall (b :: BackendType). c1 b => c2 b => i b -> r) ->
|
|
|
|
r
|
2021-09-09 14:54:19 +03:00
|
|
|
dispatchAnyBackendWithTwoConstraints e f = $(mkDispatch 'f 'e)
|
|
|
|
|
2021-03-15 16:02:58 +03:00
|
|
|
-- | Unlike 'dispatchAnyBackend', the expected constraint has a different kind.
|
|
|
|
-- Use for classes like 'Show', 'ToJSON', etc.
|
2021-09-24 01:56:37 +03:00
|
|
|
dispatchAnyBackend' ::
|
|
|
|
forall
|
|
|
|
(c :: Type -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type).
|
|
|
|
i `SatisfiesForAllBackends` c =>
|
|
|
|
AnyBackend i ->
|
|
|
|
(forall (b :: BackendType). c (i b) => i b -> r) ->
|
|
|
|
r
|
2021-03-18 23:34:11 +03:00
|
|
|
dispatchAnyBackend' e f = $(mkDispatch 'f 'e)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
|
|
|
-- | Sometimes we need to run operations on two backends of the same type.
|
|
|
|
-- If the backends don't contain the same type, the given 'r' value is returned.
|
|
|
|
-- Otherwise, the function is called with the two wrapped values.
|
2021-09-24 01:56:37 +03:00
|
|
|
composeAnyBackend ::
|
|
|
|
forall
|
|
|
|
(c :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type).
|
|
|
|
AllBackendsSatisfy c =>
|
|
|
|
(forall (b :: BackendType). c b => i b -> i b -> r) ->
|
|
|
|
AnyBackend i ->
|
|
|
|
AnyBackend i ->
|
|
|
|
r ->
|
|
|
|
r
|
2021-03-15 16:02:58 +03:00
|
|
|
composeAnyBackend f e1 e2 owise =
|
2021-03-18 23:34:11 +03:00
|
|
|
-- generates the following case expression for all backends:
|
|
|
|
-- (FooValue a, FooValue b) -> f a b
|
|
|
|
-- (BarValue a, BarValue b) -> f a b
|
|
|
|
-- ...
|
|
|
|
-- _ -> owise
|
2021-09-24 01:56:37 +03:00
|
|
|
$( backendCase
|
|
|
|
[|(e1, e2)|]
|
|
|
|
-- the pattern for a given backend: `(FooValue a, FooValue b)`
|
|
|
|
( \b -> do
|
|
|
|
let valueCon n = pure $ ConP (getBackendValueName b) [VarP $ mkName n]
|
|
|
|
[p|($(valueCon "a"), $(valueCon "b"))|]
|
|
|
|
)
|
|
|
|
-- the body for each backend: `f a b`
|
|
|
|
(const [|f a b|])
|
|
|
|
-- the default case
|
|
|
|
(Just [|owise|])
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
-- | Try to unpack the type of an existential.
|
|
|
|
-- Returns @Just x@ upon a succesful match, @Nothing@ otherwise.
|
2021-09-24 01:56:37 +03:00
|
|
|
unpackAnyBackend ::
|
|
|
|
forall
|
|
|
|
(b :: BackendType)
|
|
|
|
(i :: BackendType -> Type).
|
|
|
|
HasTag b =>
|
|
|
|
AnyBackend i ->
|
|
|
|
Maybe (i b)
|
2021-03-18 23:34:11 +03:00
|
|
|
unpackAnyBackend exists =
|
|
|
|
-- generates the following case expression for all backends:
|
|
|
|
-- (FooTag, FooValue a) -> Just a
|
|
|
|
-- ...
|
|
|
|
-- _ -> Nothing
|
2021-09-24 01:56:37 +03:00
|
|
|
$( backendCase
|
|
|
|
[|(backendTag @b, exists)|]
|
|
|
|
-- the pattern for a given backend
|
|
|
|
( \b -> do
|
|
|
|
let tagConstructor = pure $ ConP (getBackendTagName b) []
|
|
|
|
valConstructor = pure $ ConP (getBackendValueName b) [VarP $ mkName "a"]
|
|
|
|
[p|($tagConstructor, $valConstructor)|]
|
|
|
|
)
|
|
|
|
-- the body for each backend
|
|
|
|
(const [|Just a|])
|
|
|
|
-- the default case
|
|
|
|
(Just [|Nothing|])
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Special case for arrows
|
|
|
|
|
|
|
|
-- Sadly, we CAN'T mix template haskell and arrow syntax... Meaning we can't
|
|
|
|
-- generate a `backendCase` within proc syntax. What we have to do instead is to
|
|
|
|
-- MANUALLY DESUGAR the arrow code, to manually construct the following
|
|
|
|
-- pipeline.
|
|
|
|
--
|
|
|
|
-- ┌────────────┐ ┌────────────────────┐ ┌───┐
|
|
|
|
-- │ AnyBackend ├─┬──────►│ Left PostgresValue ├───────────────►│ f ├────────┐
|
|
|
|
-- └────────────┘ │ └────────────────────┘ └───┘ │
|
|
|
|
-- │ │
|
|
|
|
-- │ ┌─────────────────────────┐ ┌───┐ │
|
|
|
|
-- └─┬────►│ Right (Left MSSQLValue) ├──────────►│ f ├─────┐ │
|
|
|
|
-- │ └─────────────────────────┘ └───┘ │ │
|
|
|
|
-- │ │ │
|
|
|
|
-- │ ┌─────────────────────────────────┐ ┌───┐ │ │
|
|
|
|
-- └─┬──►│ Right (Right (Left MongoValue)) ├───┤ f ├──┐ │ │
|
|
|
|
-- │ └─────────────────────────────────┘ └───┘ │ │ │
|
|
|
|
-- │ │ │ │
|
|
|
|
-- │ ┌───────────────────────────┐ ┌───┐ │ │ │ ┌───┐
|
|
|
|
-- └──►│ Right (Right (Right ...)) ├─────────┤ f ├──┴──┴──┴─►│ r │
|
|
|
|
-- └───────────────────────────┘ └───┘ └───┘
|
|
|
|
--
|
|
|
|
-- This is what, internally, GHC would translate an arrow case-switch into: the
|
|
|
|
-- only tool it has is:
|
|
|
|
-- (|||) :: a b d -> a c d -> a (Either b c) d
|
|
|
|
--
|
|
|
|
-- It must therefore encode the case switch as an arrow from the original value
|
|
|
|
-- to this tree of Either, and then coalesce them using (|||). This is what we
|
|
|
|
-- do here.
|
|
|
|
|
|
|
|
-- | First, we create a type to represent our complicated Either type. We use
|
|
|
|
-- `Void` as a terminating case for our recursion. This declaration creates the
|
|
|
|
-- following type:
|
|
|
|
--
|
|
|
|
-- type BackendChoice (i :: BackendType -> Type)
|
|
|
|
-- = Either (i 'Postgres)
|
|
|
|
-- ( Either (i 'MSSQL)
|
|
|
|
-- ( Either ...
|
|
|
|
-- Void
|
|
|
|
type BackendChoice (i :: BackendType -> Type) =
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- creates the type (i b) for each backend b
|
|
|
|
types <- forEachBackend \b ->
|
|
|
|
pure $ AppT (VarT $ mkName "i") (getBackendTypeValue b)
|
|
|
|
-- generate the either type by folding over that list
|
|
|
|
let appEither l r = [t|Either $(pure l) $(pure r)|]
|
|
|
|
foldrM appEither (ConT ''Void) types
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
-- | Spread a 'AnyBackend' into a 'BackendChoice'.
|
|
|
|
--
|
|
|
|
-- Given backends Foo, Bar, Baz, the type of `BackendChoice c` will be:
|
|
|
|
-- ( Either (c 'Foo)
|
|
|
|
-- ( Either (c 'Bar)
|
|
|
|
-- ( Either (c 'Baz)
|
|
|
|
-- Void )))
|
|
|
|
--
|
|
|
|
-- Accordingly, the following Template Haskell splice generates the following code:
|
|
|
|
--
|
|
|
|
-- case e of
|
|
|
|
-- FooValue x -> Left x
|
|
|
|
-- BarValue x -> Right (Left x)
|
|
|
|
-- BazValue x -> Right (Right (Left x))
|
2021-09-24 01:56:37 +03:00
|
|
|
spreadChoice ::
|
|
|
|
forall
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(arr :: Type -> Type -> Type).
|
|
|
|
(ArrowChoice arr) =>
|
|
|
|
arr (AnyBackend i) (BackendChoice i)
|
2021-03-18 23:34:11 +03:00
|
|
|
spreadChoice = arr $ \e ->
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- to each backend we match a 'BackendChoice' constructor
|
|
|
|
-- in order: Left, Right . Left, Right . Right . Left...
|
|
|
|
let choiceCons = iterate (UInfixE (ConE 'Right) (VarE '(.))) (ConE 'Left)
|
|
|
|
backendCons <- backendConstructors
|
|
|
|
-- we then construct the case match for each of them
|
|
|
|
matches <- for (zip backendCons choiceCons) \(b, c) -> do
|
|
|
|
-- name of the constructor: FooValue
|
|
|
|
let consName = getBackendValueName b
|
|
|
|
-- pattern of the match: `FooValue x`
|
|
|
|
let matchPattern = ConP consName [VarP $ mkName "x"]
|
|
|
|
-- expression of the match: applying the 'BackendChoice' constructor to x
|
|
|
|
matchBody <- [|$(pure c) x|]
|
|
|
|
pure $ Match matchPattern (NormalB matchBody) []
|
|
|
|
-- the expression on which we do the case
|
|
|
|
caseExpr <- [|e|]
|
|
|
|
-- we return the case expression
|
|
|
|
pure $ CaseE caseExpr matches
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
-- | Coalesce a 'BackendChoice' into a result, given an arrow from each
|
|
|
|
-- possibilty to a common result.
|
|
|
|
--
|
|
|
|
-- Given backends Foo, Bar, Baz, the type of `BackendChoice c` will be:
|
|
|
|
-- ( Either (c 'Foo)
|
|
|
|
-- ( Either (c 'Bar)
|
|
|
|
-- ( Either (c 'Baz)
|
|
|
|
-- Void )))
|
|
|
|
--
|
|
|
|
-- Accordingly, the following Template Haskell splice generates the following code:
|
|
|
|
--
|
|
|
|
-- ( arrow |||
|
|
|
|
-- ( arrow |||
|
|
|
|
-- ( arrow |||
|
|
|
|
-- absurd )))
|
2021-09-24 01:56:37 +03:00
|
|
|
coalesceChoice ::
|
|
|
|
forall
|
|
|
|
(c1 :: BackendType -> Constraint)
|
|
|
|
(c2 :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type)
|
|
|
|
(arr :: Type -> Type -> Type).
|
|
|
|
(ArrowChoice arr, AllBackendsSatisfy c1, AllBackendsSatisfy c2) =>
|
|
|
|
(forall b. c1 b => c2 b => arr (i b) r) ->
|
|
|
|
arr (BackendChoice i) r
|
2021-03-18 23:34:11 +03:00
|
|
|
coalesceChoice arrow =
|
2021-09-24 01:56:37 +03:00
|
|
|
$( do
|
|
|
|
-- associate the arrow to each type
|
|
|
|
arrows <- forEachBackend $ const [|arrow|]
|
|
|
|
-- the default case of our fold is `arr absurd` for the terminating Void
|
|
|
|
baseCase <- [|arr absurd|]
|
|
|
|
-- how to combine two arrows using (|||)
|
|
|
|
let combine = \l r -> [|$(pure l) ||| $(pure r)|]
|
|
|
|
foldrM combine baseCase arrows
|
2021-03-18 23:34:11 +03:00
|
|
|
)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
|
|
|
-- | Dispatch variant for use with arrow syntax. The universally quantified
|
2021-03-18 23:34:11 +03:00
|
|
|
-- dispatch function is an arrow instead. Since we can't express this using
|
|
|
|
-- Template Haskell, we instead generate the arrow by combining `spreadChoice`
|
|
|
|
-- and `coalesceChoice`.
|
2021-09-24 01:56:37 +03:00
|
|
|
dispatchAnyBackendArrow' ::
|
|
|
|
forall
|
|
|
|
(c1 :: BackendType -> Constraint)
|
|
|
|
(c2 :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type)
|
|
|
|
(arr :: Type -> Type -> Type).
|
|
|
|
(ArrowChoice arr, AllBackendsSatisfy c1, AllBackendsSatisfy c2) =>
|
|
|
|
(forall b. c1 b => c2 b => arr (i b) r) ->
|
|
|
|
arr (AnyBackend i) r
|
2021-09-20 10:34:59 +03:00
|
|
|
dispatchAnyBackendArrow' arrow = spreadChoice >>> coalesceChoice @c1 @c2 arrow
|
2021-03-18 23:34:11 +03:00
|
|
|
|
|
|
|
-- | While dispatchAnyBackendArrow' is expressed over an `AnyBackend`, in
|
|
|
|
-- practice we need slightly more complex types. Specifically: the only call
|
|
|
|
-- site for 'dispatchAnyBackendArrow' uses a four element tuple containing an
|
|
|
|
-- 'AnyBackend'.
|
2021-09-24 01:56:37 +03:00
|
|
|
newtype BackendArrowTuple x i (b :: BackendType) = BackendArrowTuple {unTuple :: (i b, x)}
|
2021-03-18 23:34:11 +03:00
|
|
|
|
|
|
|
-- | Finally, we can do the dispatch on the four-elements tuple.
|
|
|
|
-- Here's what happens, step by step:
|
|
|
|
--
|
|
|
|
-- ┌─────────────────────────┐
|
|
|
|
-- │ (x, y, AnyBackend i, z) │
|
|
|
|
-- └─┬───────────────────────┘
|
|
|
|
-- │
|
|
|
|
-- │ cons
|
|
|
|
-- ▼
|
|
|
|
-- ┌────────────────────────────────────────┐ ┌─────────────────────────────┐
|
|
|
|
-- │ AnyBackend (BackendArrowTuple x y z i) │ ┌───► │ BackendArrowTuple x y z i b │
|
|
|
|
-- └─┬──────────────────────────────────────┘ │ └─┬───────────────────────────┘
|
|
|
|
-- │ │ │
|
|
|
|
-- │ spreadChoice │ │ arr unTuple
|
|
|
|
-- ▼ │ ▼
|
|
|
|
-- ┌───────────────────────────────────────────┐ │ ┌────────────────┐
|
|
|
|
-- │ BackendChoice (BackendArrowTuple x y z i) │ │ │ (x, y, i b, z) │
|
|
|
|
-- └─┬─────────────────────────────────────────┘ │ └─┬──────────────┘
|
|
|
|
-- │ │ │
|
|
|
|
-- │ coalesceChoice (arr unTuple >>> arrow) ◄─────┘ │ arrow
|
|
|
|
-- ▼ ▼
|
|
|
|
-- ┌───┐ ┌───┐
|
|
|
|
-- │ r │ │ r │
|
|
|
|
-- └───┘ └───┘
|
|
|
|
--
|
2021-09-20 10:34:59 +03:00
|
|
|
-- NOTE: The below function accepts two constraints, if the arrow
|
|
|
|
-- you want to dispatch only has one constraint then repeat the constraint twice.
|
|
|
|
-- For example:
|
|
|
|
-- ```AB.dispatchAnyBackendArrow @BackendMetadata @BackendMetadata (proc (sourceMetadata, invalidationKeys)```
|
2021-09-24 01:56:37 +03:00
|
|
|
dispatchAnyBackendArrow ::
|
|
|
|
forall
|
|
|
|
(c1 :: BackendType -> Constraint)
|
|
|
|
(c2 :: BackendType -> Constraint)
|
|
|
|
(i :: BackendType -> Type)
|
|
|
|
(r :: Type)
|
|
|
|
(arr :: Type -> Type -> Type)
|
|
|
|
x.
|
|
|
|
(ArrowChoice arr, AllBackendsSatisfy c1, AllBackendsSatisfy c2) =>
|
|
|
|
(forall b. c1 b => c2 b => arr (i b, x) r) ->
|
|
|
|
arr (AnyBackend i, x) r
|
2021-03-18 23:34:11 +03:00
|
|
|
dispatchAnyBackendArrow arrow =
|
2021-09-20 10:34:59 +03:00
|
|
|
arr cons >>> dispatchAnyBackendArrow' @c1 @c2 (arr unTuple >>> arrow)
|
2021-03-18 23:34:11 +03:00
|
|
|
where
|
2021-07-23 02:06:10 +03:00
|
|
|
cons :: (AnyBackend i, x) -> AnyBackend (BackendArrowTuple x i)
|
|
|
|
cons (e, x) = mapBackend e \ib -> BackendArrowTuple (ib, x)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
2021-03-18 23:34:11 +03:00
|
|
|
--------------------------------------------------------------------------------
|
server: fix major issue with JSON instances of AnyBackend
### Description
This PR fixes a major issue in the JSON instances of `AnyBackend`: they were not symmetrical! `FromJSON` always made the assumption that the value was an object, and that it contained a "kind" field if it happened to not be a Postgres value. `ToJSON` did NOT insert said field in the output, and did not enforce that the output was an object.
....however, it worked, because nowhere in the code did we yet rely on those being symmetrical. They are both used only once:
- `parseJSON` was used to decode a `Metadata` object, but the matching `toJSON` instance, which is heavily customized, does insert the "kind" field properly
- `toJSON` was only used on the `SchemaCache`, which has no corresponding `FromJSON` instance, since we only serialize it in debug endpoints
This PR makes no attempt at making the instances symmetrical. Instead, it implements simpler functions, and pushes the problem of identifying the proper backend (if any) to the call sites.
### Notes
Additionally, it cleans up some instances that were manually written where they could be auto-generated. In the process, this PR changes the semantics of `Show`, since the stock derived instance will include the constructor name, where before it was skipped. I think it is preferable.
https://github.com/hasura/graphql-engine-mono/pull/1672
GitOrigin-RevId: 0a1580a0e0f01c25b8c9fee7612dba6e7de055d5
2021-06-28 21:38:12 +03:00
|
|
|
-- JSON functions
|
|
|
|
|
|
|
|
-- | Attempts to parse an 'AnyBackend' from a JSON value, using the provided
|
|
|
|
-- backend information.
|
2021-09-24 01:56:37 +03:00
|
|
|
parseAnyBackendFromJSON ::
|
|
|
|
i `SatisfiesForAllBackends` FromJSON =>
|
|
|
|
BackendType ->
|
|
|
|
Value ->
|
|
|
|
Parser (AnyBackend i)
|
server: fix major issue with JSON instances of AnyBackend
### Description
This PR fixes a major issue in the JSON instances of `AnyBackend`: they were not symmetrical! `FromJSON` always made the assumption that the value was an object, and that it contained a "kind" field if it happened to not be a Postgres value. `ToJSON` did NOT insert said field in the output, and did not enforce that the output was an object.
....however, it worked, because nowhere in the code did we yet rely on those being symmetrical. They are both used only once:
- `parseJSON` was used to decode a `Metadata` object, but the matching `toJSON` instance, which is heavily customized, does insert the "kind" field properly
- `toJSON` was only used on the `SchemaCache`, which has no corresponding `FromJSON` instance, since we only serialize it in debug endpoints
This PR makes no attempt at making the instances symmetrical. Instead, it implements simpler functions, and pushes the problem of identifying the proper backend (if any) to the call sites.
### Notes
Additionally, it cleans up some instances that were manually written where they could be auto-generated. In the process, this PR changes the semantics of `Show`, since the stock derived instance will include the constructor name, where before it was skipped. I think it is preferable.
https://github.com/hasura/graphql-engine-mono/pull/1672
GitOrigin-RevId: 0a1580a0e0f01c25b8c9fee7612dba6e7de055d5
2021-06-28 21:38:12 +03:00
|
|
|
parseAnyBackendFromJSON backendKind value = do
|
|
|
|
-- generates the following case for all backends:
|
|
|
|
-- Foo -> FooValue <$> parseJSON value
|
|
|
|
-- Bar -> BarValue <$> parseJSON value
|
|
|
|
-- ...
|
2021-09-24 01:56:37 +03:00
|
|
|
$( backendCase
|
|
|
|
[|backendKind|]
|
|
|
|
-- the pattern for a given backend
|
|
|
|
(\(con :| args) -> pure $ ConP con [ConP arg [] | arg <- args])
|
|
|
|
-- the body for each backend
|
|
|
|
( \b -> do
|
|
|
|
let valueCon = pure $ ConE $ getBackendValueName b
|
|
|
|
[|$valueCon <$> parseJSON value|]
|
|
|
|
)
|
|
|
|
-- no default case
|
|
|
|
Nothing
|
server: fix major issue with JSON instances of AnyBackend
### Description
This PR fixes a major issue in the JSON instances of `AnyBackend`: they were not symmetrical! `FromJSON` always made the assumption that the value was an object, and that it contained a "kind" field if it happened to not be a Postgres value. `ToJSON` did NOT insert said field in the output, and did not enforce that the output was an object.
....however, it worked, because nowhere in the code did we yet rely on those being symmetrical. They are both used only once:
- `parseJSON` was used to decode a `Metadata` object, but the matching `toJSON` instance, which is heavily customized, does insert the "kind" field properly
- `toJSON` was only used on the `SchemaCache`, which has no corresponding `FromJSON` instance, since we only serialize it in debug endpoints
This PR makes no attempt at making the instances symmetrical. Instead, it implements simpler functions, and pushes the problem of identifying the proper backend (if any) to the call sites.
### Notes
Additionally, it cleans up some instances that were manually written where they could be auto-generated. In the process, this PR changes the semantics of `Show`, since the stock derived instance will include the constructor name, where before it was skipped. I think it is preferable.
https://github.com/hasura/graphql-engine-mono/pull/1672
GitOrigin-RevId: 0a1580a0e0f01c25b8c9fee7612dba6e7de055d5
2021-06-28 21:38:12 +03:00
|
|
|
)
|
|
|
|
|
|
|
|
-- | Outputs a debug JSON value from an 'AnyBackend'. This function must only be
|
|
|
|
-- used for debug purposes, as it has no way of inserting the backend kind in
|
|
|
|
-- the output, since there's no guarantee that the output will be an object.
|
2021-09-24 01:56:37 +03:00
|
|
|
debugAnyBackendToJSON ::
|
|
|
|
i `SatisfiesForAllBackends` ToJSON =>
|
|
|
|
AnyBackend i ->
|
|
|
|
Value
|
server: fix major issue with JSON instances of AnyBackend
### Description
This PR fixes a major issue in the JSON instances of `AnyBackend`: they were not symmetrical! `FromJSON` always made the assumption that the value was an object, and that it contained a "kind" field if it happened to not be a Postgres value. `ToJSON` did NOT insert said field in the output, and did not enforce that the output was an object.
....however, it worked, because nowhere in the code did we yet rely on those being symmetrical. They are both used only once:
- `parseJSON` was used to decode a `Metadata` object, but the matching `toJSON` instance, which is heavily customized, does insert the "kind" field properly
- `toJSON` was only used on the `SchemaCache`, which has no corresponding `FromJSON` instance, since we only serialize it in debug endpoints
This PR makes no attempt at making the instances symmetrical. Instead, it implements simpler functions, and pushes the problem of identifying the proper backend (if any) to the call sites.
### Notes
Additionally, it cleans up some instances that were manually written where they could be auto-generated. In the process, this PR changes the semantics of `Show`, since the stock derived instance will include the constructor name, where before it was skipped. I think it is preferable.
https://github.com/hasura/graphql-engine-mono/pull/1672
GitOrigin-RevId: 0a1580a0e0f01c25b8c9fee7612dba6e7de055d5
2021-06-28 21:38:12 +03:00
|
|
|
debugAnyBackendToJSON e = dispatchAnyBackend' @ToJSON e toJSON
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Instances for 'AnyBackend'
|
|
|
|
|
|
|
|
deriving instance i `SatisfiesForAllBackends` Show => Show (AnyBackend i)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
server: fix major issue with JSON instances of AnyBackend
### Description
This PR fixes a major issue in the JSON instances of `AnyBackend`: they were not symmetrical! `FromJSON` always made the assumption that the value was an object, and that it contained a "kind" field if it happened to not be a Postgres value. `ToJSON` did NOT insert said field in the output, and did not enforce that the output was an object.
....however, it worked, because nowhere in the code did we yet rely on those being symmetrical. They are both used only once:
- `parseJSON` was used to decode a `Metadata` object, but the matching `toJSON` instance, which is heavily customized, does insert the "kind" field properly
- `toJSON` was only used on the `SchemaCache`, which has no corresponding `FromJSON` instance, since we only serialize it in debug endpoints
This PR makes no attempt at making the instances symmetrical. Instead, it implements simpler functions, and pushes the problem of identifying the proper backend (if any) to the call sites.
### Notes
Additionally, it cleans up some instances that were manually written where they could be auto-generated. In the process, this PR changes the semantics of `Show`, since the stock derived instance will include the constructor name, where before it was skipped. I think it is preferable.
https://github.com/hasura/graphql-engine-mono/pull/1672
GitOrigin-RevId: 0a1580a0e0f01c25b8c9fee7612dba6e7de055d5
2021-06-28 21:38:12 +03:00
|
|
|
deriving instance i `SatisfiesForAllBackends` Eq => Eq (AnyBackend i)
|
2021-03-18 23:34:11 +03:00
|
|
|
|
server: fix major issue with JSON instances of AnyBackend
### Description
This PR fixes a major issue in the JSON instances of `AnyBackend`: they were not symmetrical! `FromJSON` always made the assumption that the value was an object, and that it contained a "kind" field if it happened to not be a Postgres value. `ToJSON` did NOT insert said field in the output, and did not enforce that the output was an object.
....however, it worked, because nowhere in the code did we yet rely on those being symmetrical. They are both used only once:
- `parseJSON` was used to decode a `Metadata` object, but the matching `toJSON` instance, which is heavily customized, does insert the "kind" field properly
- `toJSON` was only used on the `SchemaCache`, which has no corresponding `FromJSON` instance, since we only serialize it in debug endpoints
This PR makes no attempt at making the instances symmetrical. Instead, it implements simpler functions, and pushes the problem of identifying the proper backend (if any) to the call sites.
### Notes
Additionally, it cleans up some instances that were manually written where they could be auto-generated. In the process, this PR changes the semantics of `Show`, since the stock derived instance will include the constructor name, where before it was skipped. I think it is preferable.
https://github.com/hasura/graphql-engine-mono/pull/1672
GitOrigin-RevId: 0a1580a0e0f01c25b8c9fee7612dba6e7de055d5
2021-06-28 21:38:12 +03:00
|
|
|
instance i `SatisfiesForAllBackends` Hashable => Hashable (AnyBackend i)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-07-23 02:06:10 +03:00
|
|
|
instance i `SatisfiesForAllBackends` Cacheable => Cacheable (AnyBackend i)
|