2021-06-11 06:26:50 +03:00
|
|
|
module Hasura.GraphQL.Execute.RemoteJoin.Collect
|
|
|
|
( RemoteJoins
|
|
|
|
, RemoteJoinMap
|
|
|
|
, FieldPath(..)
|
|
|
|
, appendPath
|
|
|
|
, getRemoteJoins
|
|
|
|
, getRemoteJoinsSelect
|
|
|
|
, getRemoteJoinsMutationDB
|
|
|
|
, getRemoteJoinsActionQuery
|
|
|
|
, getRemoteJoinsActionMutation
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
|
|
import qualified Data.HashMap.Strict as Map
|
|
|
|
import qualified Data.HashSet as HS
|
|
|
|
import qualified Data.List.NonEmpty as NE
|
|
|
|
|
|
|
|
import Control.Lens
|
|
|
|
|
|
|
|
import Hasura.GraphQL.Execute.RemoteJoin.Types
|
|
|
|
import Hasura.RQL.IR
|
|
|
|
import Hasura.RQL.IR.Returning
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
|
|
|
|
{- Note: [Remote Joins Architecture]
|
|
|
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
|
|
|
|
|
|
Unparsed Incoming GraphQL +------------------------------+
|
|
|
|
--------------------------> | Parsing of the GraphQL query |-----+
|
|
|
|
+------------------------------+ |
|
|
|
|
| DB Query and remote joins (if any)
|
|
|
|
|
|
|
|
|
V
|
|
|
|
+----------------------------------+ SQL query response +----------------------------+
|
|
|
|
| Traverse the DB response to | <------------------- | Execution of the DB query |
|
|
|
|
| get the values of the arguments | +----------------------------+
|
|
|
|
| of the remote field |
|
|
|
|
+----------------------------------+
|
|
|
|
|
|
|
|
|
| Remote field arguments
|
|
|
|
V
|
|
|
|
+--------------------------+ Remote schema response +----------------------------------------+
|
|
|
|
| Query the remote schema | ------------------------> | Replace the remote join fields in |
|
|
|
|
| with the remote field | | the SQL query response (JSON) with |
|
|
|
|
| arguments to the remote | | the response obtained from the remote |
|
|
|
|
| field configured in the | | schema at appropriate places. |
|
|
|
|
| remote join. | +----------------------------------------+
|
|
|
|
+--------------------------+
|
|
|
|
-}
|
|
|
|
|
|
|
|
-- | Collects remote joins from the AST and also adds the necessary join fields
|
|
|
|
getRemoteJoins
|
|
|
|
:: Backend b
|
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
|
|
|
=> QueryDB b r u
|
|
|
|
-> (QueryDB b (Const Void) u, Maybe RemoteJoins)
|
2021-06-11 06:26:50 +03:00
|
|
|
getRemoteJoins = \case
|
|
|
|
QDBMultipleRows s -> first QDBMultipleRows $ getRemoteJoinsSelect s
|
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
|
|
|
QDBSingleRow s -> first QDBSingleRow $ getRemoteJoinsSelect s
|
|
|
|
QDBAggregation s -> first QDBAggregation $ getRemoteJoinsAggregateSelect s
|
|
|
|
QDBConnection s -> first QDBConnection $ getRemoteJoinsConnectionSelect s
|
2021-06-11 06:26:50 +03:00
|
|
|
|
|
|
|
-- | Traverse through 'AnnSimpleSel' and collect remote join fields (if any).
|
|
|
|
getRemoteJoinsSelect
|
|
|
|
:: Backend b
|
2021-07-08 18:41:59 +03:00
|
|
|
=> AnnSimpleSelectG b r u
|
|
|
|
-> (AnnSimpleSelectG b (Const Void) u, Maybe RemoteJoins)
|
2021-06-11 06:26:50 +03:00
|
|
|
getRemoteJoinsSelect =
|
|
|
|
second mapToNonEmpty . flip runState mempty . transformSelect mempty
|
|
|
|
|
|
|
|
-- | Traverse through @'AnnAggregateSelect' and collect remote join fields (if any).
|
|
|
|
getRemoteJoinsAggregateSelect
|
|
|
|
:: Backend b
|
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
|
|
|
=> AnnAggregateSelectG b r u
|
|
|
|
-> (AnnAggregateSelectG b (Const Void) u, Maybe RemoteJoins)
|
2021-06-11 06:26:50 +03:00
|
|
|
getRemoteJoinsAggregateSelect =
|
|
|
|
second mapToNonEmpty . flip runState mempty . transformAggregateSelect mempty
|
|
|
|
|
|
|
|
-- | Traverse through @'ConnectionSelect' and collect remote join fields (if any).
|
|
|
|
getRemoteJoinsConnectionSelect
|
|
|
|
:: Backend b
|
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
|
|
|
=> ConnectionSelect b r u
|
|
|
|
-> (ConnectionSelect b (Const Void) u, Maybe RemoteJoins)
|
2021-06-11 06:26:50 +03:00
|
|
|
getRemoteJoinsConnectionSelect =
|
|
|
|
second mapToNonEmpty . flip runState mempty . transformConnectionSelect mempty
|
|
|
|
|
|
|
|
-- | Traverse through 'MutationOutput' and collect remote join fields (if any)
|
|
|
|
getRemoteJoinsMutationOutput
|
|
|
|
:: Backend b
|
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
|
|
|
=> MutationOutputG b r u
|
|
|
|
-> (MutationOutputG b (Const Void) u, Maybe RemoteJoins)
|
2021-06-11 06:26:50 +03:00
|
|
|
getRemoteJoinsMutationOutput =
|
|
|
|
second mapToNonEmpty . flip runState mempty . transformMutationOutput mempty
|
|
|
|
where
|
|
|
|
transformMutationOutput path = \case
|
|
|
|
MOutMultirowFields mutationFields ->
|
|
|
|
MOutMultirowFields <$> transfromMutationFields mutationFields
|
|
|
|
MOutSinglerowObject annFields ->
|
|
|
|
MOutSinglerowObject <$> transformAnnFields path annFields
|
|
|
|
where
|
|
|
|
transfromMutationFields fields =
|
|
|
|
forM fields $ \(fieldName, field') -> do
|
|
|
|
let fieldPath = appendPath fieldName path
|
|
|
|
(fieldName,) <$> case field' of
|
|
|
|
MCount -> pure MCount
|
|
|
|
MExp t -> pure $ MExp t
|
|
|
|
MRet annFields -> MRet <$> transformAnnFields fieldPath annFields
|
|
|
|
|
|
|
|
|
|
|
|
-- local helpers
|
|
|
|
|
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
|
|
|
getRemoteJoinsAnnFields
|
|
|
|
:: Backend b
|
|
|
|
=> AnnFieldsG b r u
|
|
|
|
-> (AnnFieldsG b (Const Void) u, Maybe RemoteJoins)
|
|
|
|
getRemoteJoinsAnnFields =
|
|
|
|
second mapToNonEmpty . flip runState mempty . transformAnnFields mempty
|
|
|
|
|
|
|
|
getRemoteJoinsMutationDB
|
|
|
|
:: Backend b
|
|
|
|
=> MutationDB b r u
|
|
|
|
-> (MutationDB b (Const Void) u, Maybe RemoteJoins)
|
|
|
|
getRemoteJoinsMutationDB = \case
|
|
|
|
MDBInsert insert ->
|
|
|
|
first MDBInsert $ getRemoteJoinsInsert insert
|
|
|
|
MDBUpdate update ->
|
|
|
|
first MDBUpdate $ getRemoteJoinsUpdate update
|
|
|
|
MDBDelete delete ->
|
|
|
|
first MDBDelete $ getRemoteJoinsDelete delete
|
|
|
|
MDBFunction aggSelect select ->
|
|
|
|
first (MDBFunction aggSelect) $ getRemoteJoinsSelect select
|
|
|
|
where
|
|
|
|
getRemoteJoinsInsert insert =
|
|
|
|
let (output', remoteJoins) = getRemoteJoinsMutationOutput $ _aiOutput insert
|
|
|
|
in (insert{ _aiOutput = output'}, remoteJoins)
|
|
|
|
|
|
|
|
getRemoteJoinsUpdate update =
|
|
|
|
let (output', remoteJoins) = getRemoteJoinsMutationOutput $ uqp1Output update
|
|
|
|
in (update{ uqp1Output = output'}, remoteJoins)
|
|
|
|
|
|
|
|
getRemoteJoinsDelete delete =
|
|
|
|
let (output', remoteJoins) = getRemoteJoinsMutationOutput $ dqp1Output delete
|
|
|
|
in (delete{ dqp1Output = output'}, remoteJoins)
|
|
|
|
|
|
|
|
getRemoteJoinsSyncAction
|
|
|
|
:: (Backend b)
|
|
|
|
=> AnnActionExecution b r v
|
|
|
|
-> (AnnActionExecution b (Const Void) v, Maybe RemoteJoins)
|
|
|
|
getRemoteJoinsSyncAction actionExecution =
|
|
|
|
let (fields', remoteJoins) = getRemoteJoinsAnnFields $ _aaeFields actionExecution
|
|
|
|
in (actionExecution { _aaeFields = fields' }, remoteJoins)
|
|
|
|
|
|
|
|
getRemoteJoinsActionQuery
|
|
|
|
:: (Backend b)
|
|
|
|
=> ActionQuery b r v
|
|
|
|
-> (ActionQuery b (Const Void) v, Maybe RemoteJoins)
|
|
|
|
getRemoteJoinsActionQuery = \case
|
|
|
|
AQQuery sync ->
|
|
|
|
first AQQuery $ getRemoteJoinsSyncAction sync
|
|
|
|
AQAsync async ->
|
|
|
|
first AQAsync $ getRemoteJoinsAsyncQuery async
|
|
|
|
where
|
|
|
|
getRemoteJoinsAsyncQuery async =
|
|
|
|
let (fields', remoteJoins) =
|
|
|
|
second mapToNonEmpty . flip runState mempty . transformAsyncFields mempty $
|
|
|
|
_aaaqFields async
|
|
|
|
in (async { _aaaqFields = fields' }, remoteJoins)
|
|
|
|
|
|
|
|
transformAsyncFields path fields =
|
|
|
|
forM fields $ \(fieldName, field) -> do
|
|
|
|
let fieldPath = appendPath fieldName path
|
|
|
|
(fieldName,) <$> case field of
|
|
|
|
AsyncTypename t -> pure $ AsyncTypename t
|
|
|
|
AsyncOutput outputFields ->
|
|
|
|
AsyncOutput <$> transformAnnFields fieldPath outputFields
|
|
|
|
AsyncId -> pure AsyncId
|
|
|
|
AsyncCreatedAt -> pure AsyncCreatedAt
|
|
|
|
AsyncErrors -> pure AsyncErrors
|
|
|
|
|
|
|
|
getRemoteJoinsActionMutation
|
|
|
|
:: (Backend b)
|
|
|
|
=> ActionMutation b r v
|
|
|
|
-> (ActionMutation b (Const Void) v, Maybe RemoteJoins)
|
|
|
|
getRemoteJoinsActionMutation = \case
|
|
|
|
AMSync sync ->
|
|
|
|
first AMSync $ getRemoteJoinsSyncAction sync
|
|
|
|
AMAsync async -> (AMAsync async, Nothing)
|
|
|
|
|
|
|
|
|
2021-06-11 06:26:50 +03:00
|
|
|
transformSelect
|
|
|
|
:: Backend b
|
|
|
|
=> FieldPath
|
2021-07-08 18:41:59 +03:00
|
|
|
-> AnnSimpleSelectG b r u
|
|
|
|
-> State RemoteJoinMap (AnnSimpleSelectG b (Const Void) u)
|
2021-06-11 06:26:50 +03:00
|
|
|
transformSelect path sel = do
|
|
|
|
let fields = _asnFields sel
|
|
|
|
-- Transform selects in array, object and computed fields
|
|
|
|
transformedFields <- transformAnnFields path fields
|
|
|
|
pure sel{_asnFields = transformedFields}
|
|
|
|
|
|
|
|
transformAggregateSelect
|
|
|
|
:: Backend b
|
|
|
|
=> FieldPath
|
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
|
|
|
-> AnnAggregateSelectG b r u
|
|
|
|
-> State RemoteJoinMap (AnnAggregateSelectG b (Const Void) u)
|
2021-06-11 06:26:50 +03:00
|
|
|
transformAggregateSelect path sel = do
|
|
|
|
let aggFields = _asnFields sel
|
|
|
|
transformedFields <- forM aggFields $ \(fieldName, aggField) ->
|
|
|
|
(fieldName,) <$> case aggField of
|
|
|
|
TAFAgg agg -> pure $ TAFAgg agg
|
|
|
|
TAFNodes x annFields -> TAFNodes x <$> transformAnnFields (appendPath fieldName path) annFields
|
|
|
|
TAFExp t -> pure $ TAFExp t
|
|
|
|
pure sel{_asnFields = transformedFields}
|
|
|
|
|
|
|
|
transformConnectionSelect
|
|
|
|
:: Backend b
|
|
|
|
=> FieldPath
|
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
|
|
|
-> ConnectionSelect b r u
|
|
|
|
-> State RemoteJoinMap (ConnectionSelect b (Const Void) u)
|
2021-06-11 06:26:50 +03:00
|
|
|
transformConnectionSelect path ConnectionSelect{..} = do
|
|
|
|
let connectionFields = _asnFields _csSelect
|
|
|
|
transformedFields <- forM connectionFields $ \(fieldName, field) ->
|
|
|
|
(fieldName,) <$> case field of
|
|
|
|
ConnectionTypename t -> pure $ ConnectionTypename t
|
|
|
|
ConnectionPageInfo p -> pure $ ConnectionPageInfo p
|
|
|
|
ConnectionEdges edges -> ConnectionEdges <$> transformEdges (appendPath fieldName path) edges
|
|
|
|
let select = _csSelect{_asnFields = transformedFields}
|
|
|
|
pure $ ConnectionSelect _csXRelay _csPrimaryKeyColumns _csSplit _csSlice select
|
|
|
|
where
|
|
|
|
transformEdges edgePath edgeFields =
|
|
|
|
forM edgeFields $ \(fieldName, edgeField) ->
|
|
|
|
(fieldName,) <$> case edgeField of
|
|
|
|
EdgeTypename t -> pure $ EdgeTypename t
|
|
|
|
EdgeCursor -> pure EdgeCursor
|
|
|
|
EdgeNode annFields ->
|
|
|
|
EdgeNode <$> transformAnnFields (appendPath fieldName edgePath) annFields
|
|
|
|
|
|
|
|
transformObjectSelect
|
|
|
|
:: Backend b
|
|
|
|
=> FieldPath
|
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
|
|
|
-> AnnObjectSelectG b r u
|
|
|
|
-> State RemoteJoinMap (AnnObjectSelectG b (Const Void) u)
|
2021-06-11 06:26:50 +03:00
|
|
|
transformObjectSelect path sel = do
|
|
|
|
let fields = _aosFields sel
|
|
|
|
transformedFields <- transformAnnFields path fields
|
|
|
|
pure sel{_aosFields = transformedFields}
|
|
|
|
|
|
|
|
transformAnnFields
|
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
|
|
|
:: forall b r u
|
2021-06-11 06:26:50 +03:00
|
|
|
. Backend b
|
|
|
|
=> FieldPath
|
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
|
|
|
-> AnnFieldsG b r u
|
|
|
|
-> State RemoteJoinMap (AnnFieldsG b (Const Void) u)
|
2021-06-11 06:26:50 +03:00
|
|
|
transformAnnFields path fields = do
|
|
|
|
|
|
|
|
-- TODO: Check for correctness. I think this entire function seems to be
|
|
|
|
-- assuming that the column names will appear as is in the response from the
|
|
|
|
-- server, which is incorrect as they can be aliased. Similarly, the phantom
|
|
|
|
-- columns are being added without checking for overlap with aliases
|
|
|
|
|
|
|
|
let pgColumnFields = HS.fromList $ map (pgiColumn . _acfInfo . snd) $
|
|
|
|
getFields _AFColumn fields
|
|
|
|
remoteSelects = getFields (_AFRemote) fields
|
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
|
|
|
remoteJoins = remoteSelects <&> \(fieldName, remoteSelect) ->
|
2021-06-11 06:26:50 +03:00
|
|
|
let RemoteSelect argsMap selSet hasuraColumns remoteFields rsi = remoteSelect
|
|
|
|
hasuraColumnFields = HS.map (fromCol @b . pgiColumn) hasuraColumns
|
|
|
|
phantomColumns = HS.filter ((`notElem` pgColumnFields) . pgiColumn) hasuraColumns
|
|
|
|
in (phantomColumns, RemoteJoin fieldName argsMap selSet hasuraColumnFields remoteFields rsi $
|
|
|
|
map (fromCol @b . pgiColumn) $ toList phantomColumns)
|
|
|
|
|
|
|
|
transformedFields <- forM fields $ \(fieldName, field') -> do
|
|
|
|
let fieldPath = appendPath fieldName path
|
|
|
|
(fieldName,) <$> case field' of
|
|
|
|
AFNodeId x qt pkeys -> pure $ AFNodeId x qt pkeys
|
|
|
|
AFColumn c -> pure $ AFColumn c
|
|
|
|
AFObjectRelation annRel ->
|
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
|
|
|
AFObjectRelation <$> transformAnnRelation (transformObjectSelect fieldPath) annRel
|
2021-06-11 06:26:50 +03:00
|
|
|
AFArrayRelation (ASSimple annRel) ->
|
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
|
|
|
AFArrayRelation . ASSimple <$> transformAnnRelation (transformSelect fieldPath) annRel
|
2021-06-11 06:26:50 +03:00
|
|
|
AFArrayRelation (ASAggregate aggRel) ->
|
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
|
|
|
AFArrayRelation . ASAggregate <$> transformAnnRelation (transformAggregateSelect fieldPath) aggRel
|
2021-06-11 06:26:50 +03:00
|
|
|
AFArrayRelation (ASConnection annRel) ->
|
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
|
|
|
AFArrayRelation . ASConnection <$> transformAnnRelation (transformConnectionSelect fieldPath) annRel
|
2021-06-11 06:26:50 +03:00
|
|
|
AFComputedField x computedField ->
|
|
|
|
AFComputedField x <$> case computedField of
|
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
|
|
|
CFSScalar cfss cbe -> pure $ CFSScalar cfss cbe
|
2021-06-11 06:26:50 +03:00
|
|
|
CFSTable jas annSel -> CFSTable jas <$> transformSelect fieldPath annSel
|
|
|
|
AFRemote rs -> pure $ AFRemote rs
|
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
|
|
|
AFExpression t -> pure $ AFExpression t
|
|
|
|
-- TODO: implement this
|
|
|
|
AFDBRemote _ -> error "FIXME"
|
2021-06-11 06:26:50 +03:00
|
|
|
|
|
|
|
case NE.nonEmpty remoteJoins of
|
|
|
|
Nothing -> pure transformedFields
|
|
|
|
Just nonEmptyRemoteJoins -> do
|
|
|
|
let phantomColumns = map (\ci -> (fromCol @b $ pgiColumn ci, AFColumn $ AnnColumnField ci False Nothing Nothing)) $ toList $ HS.unions $ map fst $ remoteJoins
|
|
|
|
modify (Map.insert path $ fmap snd nonEmptyRemoteJoins)
|
|
|
|
pure $ transformedFields <> phantomColumns
|
|
|
|
|
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
|
|
|
where
|
|
|
|
getFields f = mapMaybe (sequence . second (^? f))
|
2021-06-11 06:26:50 +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
|
|
|
transformAnnRelation f (AnnRelationSelectG name maps select) = do
|
|
|
|
transformedSelect <- f select
|
|
|
|
pure $ AnnRelationSelectG name maps transformedSelect
|
2021-06-11 06:26:50 +03:00
|
|
|
|
|
|
|
|
|
|
|
mapToNonEmpty :: RemoteJoinMap -> Maybe RemoteJoins
|
|
|
|
mapToNonEmpty = NE.nonEmpty . Map.toList
|