2021-07-08 23:49:10 +03:00
|
|
|
{-# LANGUAGE ViewPatterns #-}
|
2021-02-23 20:37:27 +03:00
|
|
|
-- | Translate from the DML to the TSql dialect.
|
|
|
|
|
|
|
|
module Hasura.Backends.MSSQL.FromIr
|
|
|
|
( fromSelectRows
|
|
|
|
, mkSQLSelect
|
|
|
|
, fromRootField
|
|
|
|
, fromSelectAggregate
|
|
|
|
, fromAnnBoolExp
|
|
|
|
, Error(..)
|
|
|
|
, runFromIr
|
|
|
|
, FromIr
|
|
|
|
, jsonFieldName
|
|
|
|
, fromDelete
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
|
|
|
import qualified Data.HashMap.Strict as HM
|
|
|
|
import qualified Data.Map.Strict as M
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import qualified Database.ODBC.SQLServer as ODBC
|
|
|
|
|
|
|
|
import Control.Monad.Validate
|
|
|
|
import Data.Map.Strict (Map)
|
|
|
|
import Data.Proxy
|
|
|
|
|
2021-06-11 06:26:50 +03:00
|
|
|
import qualified Hasura.RQL.IR as IR
|
2021-02-23 20:37:27 +03:00
|
|
|
import qualified Hasura.RQL.Types.Column as IR
|
|
|
|
import qualified Hasura.RQL.Types.Common as IR
|
|
|
|
import qualified Hasura.RQL.Types.Relationship as IR
|
|
|
|
|
|
|
|
import Hasura.Backends.MSSQL.Instances.Types ()
|
|
|
|
import Hasura.Backends.MSSQL.Types as TSQL
|
|
|
|
import Hasura.SQL.Backend
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Types
|
|
|
|
|
|
|
|
-- | Most of these errors should be checked for legitimacy.
|
|
|
|
data Error
|
|
|
|
= UnsupportedOpExpG (IR.OpExpG 'MSSQL Expression)
|
|
|
|
| FunctionNotSupported
|
2021-04-28 14:05:33 +03:00
|
|
|
| NodesUnsupportedForNow
|
2021-06-11 06:26:50 +03:00
|
|
|
| ConnectionsNotSupported
|
2021-02-23 20:37:27 +03:00
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
|
|
-- | The base monad used throughout this module for all conversion
|
|
|
|
-- functions.
|
|
|
|
--
|
|
|
|
-- It's a Validate, so it'll continue going when it encounters errors
|
|
|
|
-- to accumulate as many as possible.
|
|
|
|
--
|
|
|
|
-- It also contains a mapping from entity prefixes to counters. So if
|
|
|
|
-- my prefix is "table" then there'll be a counter that lets me
|
|
|
|
-- generate table1, table2, etc. Same for any other prefix needed
|
|
|
|
-- (e.g. names for joins).
|
|
|
|
--
|
|
|
|
-- A ReaderT is used around this in most of the module too, for
|
|
|
|
-- setting the current entity that a given field name refers to. See
|
|
|
|
-- @fromPGCol@.
|
|
|
|
newtype FromIr a = FromIr
|
|
|
|
{ unFromIr :: StateT (Map Text Int) (Validate (NonEmpty Error)) a
|
|
|
|
} deriving (Functor, Applicative, Monad, MonadValidate (NonEmpty Error))
|
|
|
|
|
|
|
|
data StringifyNumbers
|
|
|
|
= StringifyNumbers
|
|
|
|
| LeaveNumbersAlone
|
|
|
|
deriving (Eq)
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Runners
|
|
|
|
|
|
|
|
runFromIr :: FromIr a -> Validate (NonEmpty Error) a
|
|
|
|
runFromIr fromIr = evalStateT (unFromIr fromIr) mempty
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Similar rendition of old API
|
|
|
|
|
2021-07-08 18:41:59 +03:00
|
|
|
mkSQLSelect
|
|
|
|
:: IR.JsonAggSelect
|
|
|
|
-> IR.AnnSelectG 'MSSQL (Const Void) (IR.AnnFieldG 'MSSQL (Const Void)) Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
-> FromIr TSQL.Select
|
|
|
|
mkSQLSelect jsonAggSelect annSimpleSel =
|
|
|
|
case jsonAggSelect of
|
|
|
|
IR.JASMultipleRows -> fromSelectRows annSimpleSel
|
2021-06-08 06:50:24 +03:00
|
|
|
IR.JASSingleObject ->
|
|
|
|
fromSelectRows annSimpleSel <&> \sel ->
|
|
|
|
sel
|
2021-02-23 20:37:27 +03:00
|
|
|
{ selectFor =
|
|
|
|
JsonFor
|
|
|
|
ForJson {jsonCardinality = JsonSingleton, jsonRoot = NoRoot}
|
|
|
|
, selectTop = Top 1
|
|
|
|
}
|
|
|
|
|
|
|
|
-- | Convert from the IR database query into a select.
|
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
|
|
|
fromRootField :: IR.QueryDB 'MSSQL (Const Void) Expression -> FromIr Select
|
2021-02-23 20:37:27 +03:00
|
|
|
fromRootField =
|
|
|
|
\case
|
2021-06-11 06:26:50 +03:00
|
|
|
(IR.QDBSingleRow s) -> mkSQLSelect IR.JASSingleObject s
|
|
|
|
(IR.QDBMultipleRows s) -> mkSQLSelect IR.JASMultipleRows s
|
2021-07-08 23:49:10 +03:00
|
|
|
(IR.QDBAggregation s) -> fromSelectAggregate Nothing s
|
2021-06-11 06:26:50 +03:00
|
|
|
(IR.QDBConnection _) -> refute $ pure ConnectionsNotSupported
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Top-level exported functions
|
|
|
|
|
2021-07-08 18:41:59 +03:00
|
|
|
fromSelectRows :: IR.AnnSelectG 'MSSQL (Const Void) (IR.AnnFieldG 'MSSQL (Const Void)) Expression -> FromIr TSQL.Select
|
2021-02-23 20:37:27 +03:00
|
|
|
fromSelectRows annSelectG = do
|
|
|
|
selectFrom <-
|
|
|
|
case from of
|
|
|
|
IR.FromTable qualifiedObject -> fromQualifiedTable qualifiedObject
|
[Preview] Inherited roles for postgres read queries
fixes #3868
docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de`
Note:
To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`.
Introduction
------------
This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`.
How are select permissions of different roles are combined?
------------------------------------------------------------
A select permission includes 5 things:
1. Columns accessible to the role
2. Row selection filter
3. Limit
4. Allow aggregation
5. Scalar computed fields accessible to the role
Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`.
Let's say the following GraphQL query is queried with the `combined_roles` role.
```graphql
query {
employees {
address
phone
}
}
```
This will translate to the following SQL query:
```sql
select
(case when (P1 or P2) then address else null end) as address,
(case when P2 then phone else null end) as phone
from employee
where (P1 or P2)
```
The other parameters of the select permission will be combined in the following manner:
1. Limit - Minimum of the limits will be the limit of the inherited role
2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation
3. Scalar computed fields - same as table column fields, as in the above example
APIs for inherited roles:
----------------------
1. `add_inherited_role`
`add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments
`role_name`: the name of the inherited role to be added (String)
`role_set`: list of roles that need to be combined (Array of Strings)
Example:
```json
{
"type": "add_inherited_role",
"args": {
"role_name":"combined_user",
"role_set":[
"user",
"user1"
]
}
}
```
After adding the inherited role, the inherited role can be used like single roles like earlier
Note:
An inherited role can only be created with non-inherited/singular roles.
2. `drop_inherited_role`
The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument:
`role_name`: name of the inherited role to be dropped
Example:
```json
{
"type": "drop_inherited_role",
"args": {
"role_name":"combined_user"
}
}
```
Metadata
---------
The derived roles metadata will be included under the `experimental_features` key while exporting the metadata.
```json
{
"experimental_features": {
"derived_roles": [
{
"role_name": "manager_is_employee_too",
"role_set": [
"employee",
"manager"
]
}
]
}
}
```
Scope
------
Only postgres queries and subscriptions are supported in this PR.
Important points:
-----------------
1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done.
TODOs
-------
- [ ] Tests
- [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features
- [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?)
- [ ] Introspection test with a inherited role (nullability changes in a inherited role)
- [ ] Docs
- [ ] Changelog
Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com>
GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
|
|
|
IR.FromFunction {} -> refute $ pure FunctionNotSupported
|
2021-02-23 20:37:27 +03:00
|
|
|
Args { argsOrderBy
|
|
|
|
, argsWhere
|
|
|
|
, argsJoins
|
|
|
|
, argsTop
|
|
|
|
, argsDistinct = Proxy
|
|
|
|
, argsOffset
|
|
|
|
, argsExistingJoins
|
|
|
|
} <- runReaderT (fromSelectArgsG args) (fromAlias selectFrom)
|
|
|
|
fieldSources <-
|
|
|
|
runReaderT
|
|
|
|
(traverse (fromAnnFieldsG argsExistingJoins stringifyNumbers) fields)
|
|
|
|
(fromAlias selectFrom)
|
|
|
|
filterExpression <-
|
|
|
|
runReaderT (fromAnnBoolExp permFilter) (fromAlias selectFrom)
|
|
|
|
let selectProjections =
|
|
|
|
concatMap (toList . fieldSourceProjections) fieldSources
|
|
|
|
pure
|
|
|
|
Select
|
|
|
|
{ selectOrderBy = argsOrderBy
|
|
|
|
, selectTop = permissionBasedTop <> argsTop
|
|
|
|
, selectProjections
|
2021-06-08 06:50:24 +03:00
|
|
|
, selectFrom = Just selectFrom
|
2021-02-23 20:37:27 +03:00
|
|
|
, selectJoins = argsJoins <> mapMaybe fieldSourceJoin fieldSources
|
|
|
|
, selectWhere = argsWhere <> Where [filterExpression]
|
|
|
|
, selectFor =
|
|
|
|
JsonFor ForJson {jsonCardinality = JsonArray, jsonRoot = NoRoot}
|
|
|
|
, selectOffset = argsOffset
|
|
|
|
}
|
|
|
|
where
|
|
|
|
IR.AnnSelectG { _asnFields = fields
|
|
|
|
, _asnFrom = from
|
|
|
|
, _asnPerm = perm
|
|
|
|
, _asnArgs = args
|
|
|
|
, _asnStrfyNum = num
|
|
|
|
} = annSelectG
|
|
|
|
IR.TablePerm {_tpLimit = mPermLimit, _tpFilter = permFilter} = perm
|
|
|
|
permissionBasedTop =
|
[Preview] Inherited roles for postgres read queries
fixes #3868
docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de`
Note:
To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`.
Introduction
------------
This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`.
How are select permissions of different roles are combined?
------------------------------------------------------------
A select permission includes 5 things:
1. Columns accessible to the role
2. Row selection filter
3. Limit
4. Allow aggregation
5. Scalar computed fields accessible to the role
Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`.
Let's say the following GraphQL query is queried with the `combined_roles` role.
```graphql
query {
employees {
address
phone
}
}
```
This will translate to the following SQL query:
```sql
select
(case when (P1 or P2) then address else null end) as address,
(case when P2 then phone else null end) as phone
from employee
where (P1 or P2)
```
The other parameters of the select permission will be combined in the following manner:
1. Limit - Minimum of the limits will be the limit of the inherited role
2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation
3. Scalar computed fields - same as table column fields, as in the above example
APIs for inherited roles:
----------------------
1. `add_inherited_role`
`add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments
`role_name`: the name of the inherited role to be added (String)
`role_set`: list of roles that need to be combined (Array of Strings)
Example:
```json
{
"type": "add_inherited_role",
"args": {
"role_name":"combined_user",
"role_set":[
"user",
"user1"
]
}
}
```
After adding the inherited role, the inherited role can be used like single roles like earlier
Note:
An inherited role can only be created with non-inherited/singular roles.
2. `drop_inherited_role`
The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument:
`role_name`: name of the inherited role to be dropped
Example:
```json
{
"type": "drop_inherited_role",
"args": {
"role_name":"combined_user"
}
}
```
Metadata
---------
The derived roles metadata will be included under the `experimental_features` key while exporting the metadata.
```json
{
"experimental_features": {
"derived_roles": [
{
"role_name": "manager_is_employee_too",
"role_set": [
"employee",
"manager"
]
}
]
}
}
```
Scope
------
Only postgres queries and subscriptions are supported in this PR.
Important points:
-----------------
1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done.
TODOs
-------
- [ ] Tests
- [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features
- [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?)
- [ ] Introspection test with a inherited role (nullability changes in a inherited role)
- [ ] Docs
- [ ] Changelog
Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com>
GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
|
|
|
maybe NoTop Top mPermLimit
|
2021-02-23 20:37:27 +03:00
|
|
|
stringifyNumbers =
|
|
|
|
if num
|
|
|
|
then StringifyNumbers
|
|
|
|
else LeaveNumbersAlone
|
|
|
|
|
2021-07-08 23:49:10 +03:00
|
|
|
|
|
|
|
mkNodesSelect :: Args -> Where -> Expression -> Top -> From -> [(Int, (IR.FieldName, [Projection]))] -> [(Int, [Projection])]
|
|
|
|
mkNodesSelect Args{..} foreignKeyConditions filterExpression permissionBasedTop selectFrom nodes =
|
|
|
|
[ (index,
|
|
|
|
[ ExpressionProjection $ Aliased
|
|
|
|
{ aliasedThing = SelectExpression $ Select
|
|
|
|
{ selectProjections = projections
|
|
|
|
, selectTop = permissionBasedTop <> argsTop
|
|
|
|
, selectFrom = pure selectFrom
|
|
|
|
, selectJoins = argsJoins
|
|
|
|
, selectWhere = argsWhere <> Where [filterExpression] <> foreignKeyConditions
|
|
|
|
, selectFor =
|
|
|
|
JsonFor ForJson {jsonCardinality = JsonArray, jsonRoot = NoRoot}
|
|
|
|
, selectOrderBy = argsOrderBy
|
|
|
|
, selectOffset = argsOffset
|
|
|
|
}
|
|
|
|
, aliasedAlias = IR.getFieldNameTxt fieldName
|
|
|
|
}
|
|
|
|
] -- singleton
|
|
|
|
)
|
|
|
|
| (index, (fieldName, projections)) <- nodes ]
|
|
|
|
|
|
|
|
|
|
|
|
--
|
|
|
|
-- The idea here is that LIMIT/OFFSET and aggregates don't mix
|
|
|
|
-- well. Therefore we have a nested query:
|
|
|
|
--
|
|
|
|
-- select sum(*), .. FROM (select * from x offset o limit l) p
|
|
|
|
--
|
|
|
|
-- That's why @projections@ appears on the outer, and is a
|
|
|
|
-- @StarProjection@ for the inner. But the joins, conditions, top,
|
|
|
|
-- offset are on the inner.
|
|
|
|
--
|
|
|
|
mkAggregateSelect :: Args -> Where -> From -> [(Int, (IR.FieldName, [Projection]))] -> [(Int, [Projection])]
|
|
|
|
mkAggregateSelect Args {..} foreignKeyConditions selectFrom aggregates =
|
|
|
|
[ ( index
|
|
|
|
, [ ExpressionProjection $
|
|
|
|
Aliased
|
|
|
|
{ aliasedThing =
|
|
|
|
JsonQueryExpression $
|
|
|
|
SelectExpression $
|
|
|
|
Select
|
|
|
|
{ selectProjections = reproject aggSubselectName <$> projections
|
|
|
|
, selectTop = NoTop
|
|
|
|
, selectFrom = pure $
|
|
|
|
FromSelect
|
|
|
|
Aliased
|
|
|
|
{ aliasedAlias = aggSubselectName
|
|
|
|
, aliasedThing =
|
|
|
|
Select
|
|
|
|
{ selectProjections = pure StarProjection
|
|
|
|
, selectTop = argsTop
|
|
|
|
, selectFrom = pure selectFrom
|
|
|
|
, selectJoins = argsJoins
|
|
|
|
, selectWhere = argsWhere <> foreignKeyConditions
|
|
|
|
, selectFor = NoFor
|
|
|
|
, selectOrderBy = mempty
|
|
|
|
, selectOffset = argsOffset
|
|
|
|
}
|
|
|
|
}
|
|
|
|
, selectJoins = mempty
|
|
|
|
, selectWhere = mempty
|
|
|
|
, selectFor =
|
|
|
|
JsonFor
|
|
|
|
ForJson
|
|
|
|
{jsonCardinality = JsonSingleton, jsonRoot = NoRoot}
|
|
|
|
, selectOrderBy = mempty
|
|
|
|
, selectOffset = Nothing
|
|
|
|
}
|
|
|
|
, aliasedAlias = IR.getFieldNameTxt fieldName
|
|
|
|
}
|
|
|
|
] -- singleton
|
|
|
|
)
|
|
|
|
| (index, (fieldName, projections)) <- aggregates
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
-- | Re-project projections in the aggSubselectName scope
|
|
|
|
--
|
|
|
|
-- For example,
|
|
|
|
--
|
|
|
|
-- [ AggregateProjection
|
|
|
|
-- (Aliased {aliasedThing = CountAggregate StarCountable, aliasedAlias = "count"})
|
|
|
|
-- , AggregateProjection
|
|
|
|
-- (Aliased
|
|
|
|
-- { aliasedThing = OpAggregate "sum"
|
|
|
|
-- [ ColumnExpression
|
|
|
|
-- (FieldName
|
|
|
|
-- { fieldName = "id"
|
|
|
|
-- , fieldNameEntity = "t_person1" -- <<<<< This needs to be `aggSubselectName`
|
|
|
|
-- })
|
|
|
|
-- ]
|
|
|
|
-- , aliasedAlias = "sum"
|
|
|
|
-- })
|
|
|
|
--
|
|
|
|
reproject :: Text -> Projection -> Projection
|
|
|
|
reproject label = \case
|
|
|
|
AggregateProjection (Aliased {aliasedThing = OpAggregate aggName expressions, ..}) ->
|
|
|
|
AggregateProjection (Aliased {aliasedThing = OpAggregate aggName (fixColumnEntity label <$> expressions), ..})
|
|
|
|
AggregateProjection (Aliased {aliasedThing = CountAggregate countableFieldnames, ..}) ->
|
|
|
|
AggregateProjection (Aliased {aliasedThing = CountAggregate $ fixEntity label <$> countableFieldnames, ..})
|
2021-07-30 12:02:38 +03:00
|
|
|
AggregateProjection (Aliased {aliasedThing = JsonQueryOpAggregate aggName expressions, ..}) ->
|
|
|
|
AggregateProjection (Aliased {aliasedThing = JsonQueryOpAggregate aggName (fixColumnEntity label <$> expressions), ..})
|
2021-07-08 23:49:10 +03:00
|
|
|
x -> x
|
|
|
|
where
|
2021-07-30 12:02:38 +03:00
|
|
|
fixColumnEntity :: Text -> Expression -> Expression
|
2021-07-08 23:49:10 +03:00
|
|
|
fixColumnEntity entity = \case
|
|
|
|
ColumnExpression fName ->
|
|
|
|
ColumnExpression $ fixEntity entity fName
|
2021-07-30 12:02:38 +03:00
|
|
|
JsonQueryExpression expression ->
|
|
|
|
JsonQueryExpression $ fixColumnEntity entity expression
|
|
|
|
SelectExpression Select{..} ->
|
|
|
|
SelectExpression $ Select {selectProjections = reproject entity <$> selectProjections, ..}
|
2021-07-08 23:49:10 +03:00
|
|
|
x -> x
|
2021-07-30 12:02:38 +03:00
|
|
|
fixEntity :: Text -> FieldName -> FieldName
|
2021-07-08 23:49:10 +03:00
|
|
|
fixEntity entity FieldName{..} = FieldName {fieldNameEntity = entity, ..}
|
|
|
|
|
|
|
|
|
2021-07-08 18:41:59 +03:00
|
|
|
fromSelectAggregate
|
2021-07-08 23:49:10 +03:00
|
|
|
:: Maybe (EntityAlias, HashMap ColumnName ColumnName)
|
|
|
|
-> IR.AnnSelectG 'MSSQL (Const Void) (IR.TableAggregateFieldG 'MSSQL (Const Void)) Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
-> FromIr TSQL.Select
|
2021-07-08 23:49:10 +03:00
|
|
|
fromSelectAggregate
|
|
|
|
mparentRelationship
|
|
|
|
IR.AnnSelectG
|
|
|
|
{ _asnFields = (zip [0..] -> fields)
|
|
|
|
, _asnFrom = from
|
|
|
|
, _asnPerm = IR.TablePerm {_tpLimit = (maybe NoTop Top -> permissionBasedTop), _tpFilter = permFilter}
|
|
|
|
, _asnArgs = args
|
|
|
|
, _asnStrfyNum = (bool LeaveNumbersAlone StringifyNumbers -> stringifyNumbers)
|
|
|
|
}
|
|
|
|
= do
|
|
|
|
selectFrom <- case from of
|
|
|
|
IR.FromTable qualifiedObject -> fromQualifiedTable qualifiedObject
|
|
|
|
IR.FromFunction {} -> refute $ pure FunctionNotSupported
|
|
|
|
-- Below: When we're actually a RHS of a query (of CROSS APPLY),
|
|
|
|
-- then we'll have a LHS table that we're joining on. So we get the
|
|
|
|
-- conditions expressions from the field mappings. The LHS table is
|
|
|
|
-- the entityAlias, and the RHS table is selectFrom.
|
|
|
|
mforeignKeyConditions <- fmap (Where . fromMaybe []) $ for mparentRelationship $
|
|
|
|
\(entityAlias, mapping) ->
|
|
|
|
runReaderT (fromMapping selectFrom mapping) entityAlias
|
|
|
|
filterExpression <- runReaderT (fromAnnBoolExp permFilter) (fromAlias selectFrom)
|
|
|
|
args'@Args{argsExistingJoins} <-
|
|
|
|
runReaderT (fromSelectArgsG args) (fromAlias selectFrom)
|
|
|
|
-- Although aggregates, exps and nodes could be handled in one list,
|
|
|
|
-- we need to separately treat the subselect expressions
|
|
|
|
expss :: [(Int, [Projection])] <- flip runReaderT (fromAlias selectFrom) $ sequence $ mapMaybe fromTableExpFieldG fields
|
|
|
|
nodes :: [(Int, (IR.FieldName, [Projection]))] <-
|
|
|
|
flip runReaderT (fromAlias selectFrom) $ sequence $ mapMaybe (fromTableNodesFieldG argsExistingJoins stringifyNumbers) fields
|
|
|
|
aggregates :: [(Int, (IR.FieldName, [Projection]))] <-
|
|
|
|
flip runReaderT (fromAlias selectFrom) $ sequence $ mapMaybe fromTableAggFieldG fields
|
2021-02-23 20:37:27 +03:00
|
|
|
pure
|
|
|
|
Select
|
2021-07-08 23:49:10 +03:00
|
|
|
{ selectProjections =
|
|
|
|
concatMap snd $ sortBy (comparing fst) $
|
|
|
|
expss
|
|
|
|
<> mkNodesSelect args' mforeignKeyConditions filterExpression permissionBasedTop selectFrom nodes
|
|
|
|
<> mkAggregateSelect args' mforeignKeyConditions selectFrom aggregates
|
|
|
|
, selectTop = NoTop
|
|
|
|
, selectFrom = pure $ FromOpenJson $ Aliased
|
|
|
|
{ aliasedThing = OpenJson
|
|
|
|
{ openJsonExpression = ValueExpression $ ODBC.TextValue "[0]"
|
|
|
|
, openJsonWith = Nothing
|
|
|
|
}
|
|
|
|
, aliasedAlias = existsFieldName
|
|
|
|
}
|
|
|
|
, selectJoins = mempty -- JOINs and WHEREs are only relevant in subselects
|
|
|
|
, selectWhere = mempty
|
|
|
|
, selectFor = JsonFor ForJson {jsonCardinality = JsonSingleton, jsonRoot = NoRoot}
|
|
|
|
, selectOrderBy = Nothing
|
|
|
|
, selectOffset = Nothing
|
2021-02-23 20:37:27 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- GraphQL Args
|
|
|
|
|
|
|
|
data Args = Args
|
|
|
|
{ argsWhere :: Where
|
|
|
|
, argsOrderBy :: Maybe (NonEmpty OrderBy)
|
|
|
|
, argsJoins :: [Join]
|
|
|
|
, argsTop :: Top
|
|
|
|
, argsOffset :: Maybe Expression
|
|
|
|
, argsDistinct :: Proxy (Maybe (NonEmpty FieldName))
|
|
|
|
, argsExistingJoins :: Map TableName EntityAlias
|
|
|
|
} deriving (Show)
|
|
|
|
|
|
|
|
data UnfurledJoin = UnfurledJoin
|
|
|
|
{ unfurledJoin :: Join
|
|
|
|
, unfurledObjectTableAlias :: Maybe (TableName, EntityAlias)
|
|
|
|
-- ^ Recorded if we joined onto an object relation.
|
|
|
|
} deriving (Show)
|
|
|
|
|
|
|
|
fromSelectArgsG :: IR.SelectArgsG 'MSSQL Expression -> ReaderT EntityAlias FromIr Args
|
|
|
|
fromSelectArgsG selectArgsG = do
|
2021-06-10 19:13:20 +03:00
|
|
|
let argsOffset = ValueExpression . ODBC.IntValue . fromIntegral <$> moffset
|
2021-02-23 20:37:27 +03:00
|
|
|
argsWhere <-
|
|
|
|
maybe (pure mempty) (fmap (Where . pure) . fromAnnBoolExp) mannBoolExp
|
2021-06-10 19:13:20 +03:00
|
|
|
argsTop <-
|
|
|
|
maybe (pure mempty) (pure . Top) mlimit
|
2021-02-23 20:37:27 +03:00
|
|
|
-- Not supported presently, per Vamshi:
|
|
|
|
--
|
|
|
|
-- > It is hardly used and we don't have to go to great lengths to support it.
|
|
|
|
--
|
|
|
|
-- But placeholdering the code so that when it's ready to be used,
|
|
|
|
-- you can just drop the Proxy wrapper.
|
2021-06-15 18:53:20 +03:00
|
|
|
let argsDistinct = Proxy
|
2021-02-23 20:37:27 +03:00
|
|
|
(argsOrderBy, joins) <-
|
2021-07-27 19:27:28 +03:00
|
|
|
runWriterT (traverse fromAnnotatedOrderByItemG (maybe [] toList orders))
|
2021-02-23 20:37:27 +03:00
|
|
|
-- Any object-relation joins that we generated, we record their
|
|
|
|
-- generated names into a mapping.
|
|
|
|
let argsExistingJoins =
|
|
|
|
M.fromList (mapMaybe unfurledObjectTableAlias (toList joins))
|
|
|
|
pure
|
|
|
|
Args
|
|
|
|
{ argsJoins = toList (fmap unfurledJoin joins)
|
|
|
|
, argsOrderBy = nonEmpty argsOrderBy
|
|
|
|
, ..
|
|
|
|
}
|
|
|
|
where
|
|
|
|
IR.SelectArgs { _saWhere = mannBoolExp
|
|
|
|
, _saLimit = mlimit
|
|
|
|
, _saOffset = moffset
|
|
|
|
, _saOrderBy = orders
|
|
|
|
} = selectArgsG
|
|
|
|
|
|
|
|
-- | Produce a valid ORDER BY construct, telling about any joins
|
|
|
|
-- needed on the side.
|
2021-07-27 19:27:28 +03:00
|
|
|
fromAnnotatedOrderByItemG
|
|
|
|
:: IR.AnnotatedOrderByItemG 'MSSQL Expression
|
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
|
|
|
-> WriterT (Seq UnfurledJoin) (ReaderT EntityAlias FromIr) OrderBy
|
2021-07-27 19:27:28 +03:00
|
|
|
fromAnnotatedOrderByItemG IR.OrderByItemG {obiType, obiColumn = obiColumn, obiNulls} = do
|
|
|
|
(orderByFieldName, orderByType) <- unfurlAnnotatedOrderByElement obiColumn
|
2021-02-23 20:37:27 +03:00
|
|
|
let orderByNullsOrder = fromMaybe NullsAnyOrder obiNulls
|
|
|
|
orderByOrder = fromMaybe AscOrder obiType
|
|
|
|
pure OrderBy {..}
|
|
|
|
|
|
|
|
-- | Unfurl the nested set of object relations (tell'd in the writer)
|
|
|
|
-- that are terminated by field name (IR.AOCColumn and
|
|
|
|
-- IR.AOCArrayAggregation).
|
2021-07-27 19:27:28 +03:00
|
|
|
unfurlAnnotatedOrderByElement
|
|
|
|
:: IR.AnnotatedOrderByElement 'MSSQL Expression
|
2021-05-21 15:27:44 +03:00
|
|
|
-> WriterT (Seq UnfurledJoin) (ReaderT EntityAlias FromIr) (FieldName, Maybe TSQL.ScalarType)
|
2021-07-27 19:27:28 +03:00
|
|
|
unfurlAnnotatedOrderByElement =
|
2021-02-23 20:37:27 +03:00
|
|
|
\case
|
2021-05-21 15:27:44 +03:00
|
|
|
IR.AOCColumn pgColumnInfo -> do
|
|
|
|
fieldName <- lift (fromPGColumnInfo pgColumnInfo)
|
|
|
|
pure
|
|
|
|
( fieldName
|
|
|
|
, case (IR.pgiType pgColumnInfo) of
|
|
|
|
IR.ColumnScalar t -> Just t
|
|
|
|
-- Above: It is of interest to us whether the type is
|
|
|
|
-- text/ntext/image. See ToQuery for more explanation.
|
|
|
|
_ -> Nothing)
|
|
|
|
IR.AOCObjectRelation IR.RelInfo {riMapping = mapping, riRTable = table} annBoolExp annOrderByElementG -> do
|
|
|
|
selectFrom <- lift (lift (fromQualifiedTable table))
|
2021-02-23 20:37:27 +03:00
|
|
|
joinAliasEntity <-
|
2021-05-21 15:27:44 +03:00
|
|
|
lift (lift (generateEntityAlias (ForOrderAlias (tableNameText table))))
|
2021-02-23 20:37:27 +03:00
|
|
|
foreignKeyConditions <- lift (fromMapping selectFrom mapping)
|
|
|
|
-- TODO: Because these object relations are re-used by regular
|
|
|
|
-- object mapping queries, this WHERE may be unnecessarily
|
|
|
|
-- restrictive. But I actually don't know from where such an
|
|
|
|
-- expression arises in the source GraphQL syntax.
|
|
|
|
--
|
|
|
|
-- Worst case scenario, we could put the WHERE in the key of the
|
|
|
|
-- Map in 'argsExistingJoins'. That would guarantee only equal
|
|
|
|
-- selects are re-used.
|
|
|
|
whereExpression <-
|
|
|
|
lift (local (const (fromAlias selectFrom)) (fromAnnBoolExp annBoolExp))
|
|
|
|
tell
|
|
|
|
(pure
|
|
|
|
UnfurledJoin
|
|
|
|
{ unfurledJoin =
|
|
|
|
Join
|
|
|
|
{ joinSource =
|
|
|
|
JoinSelect
|
|
|
|
Select
|
|
|
|
{ selectTop = NoTop
|
|
|
|
, selectProjections = [StarProjection]
|
2021-06-08 06:50:24 +03:00
|
|
|
, selectFrom = Just selectFrom
|
2021-02-23 20:37:27 +03:00
|
|
|
, selectJoins = []
|
|
|
|
, selectWhere =
|
|
|
|
Where (foreignKeyConditions <> [whereExpression])
|
|
|
|
, selectFor = NoFor
|
|
|
|
, selectOrderBy = Nothing
|
|
|
|
, selectOffset = Nothing
|
|
|
|
}
|
|
|
|
, joinJoinAlias =
|
|
|
|
JoinAlias {joinAliasEntity, joinAliasField = Nothing}
|
|
|
|
}
|
2021-05-21 15:27:44 +03:00
|
|
|
, unfurledObjectTableAlias = Just (table, EntityAlias joinAliasEntity)
|
2021-02-23 20:37:27 +03:00
|
|
|
})
|
|
|
|
local
|
|
|
|
(const (EntityAlias joinAliasEntity))
|
2021-07-27 19:27:28 +03:00
|
|
|
(unfurlAnnotatedOrderByElement annOrderByElementG)
|
2021-05-18 16:06:42 +03:00
|
|
|
IR.AOCArrayAggregation IR.RelInfo {riMapping = mapping, riRTable = tableName} annBoolExp annAggregateOrderBy -> do
|
|
|
|
selectFrom <- lift (lift (fromQualifiedTable tableName))
|
2021-02-23 20:37:27 +03:00
|
|
|
let alias = aggFieldName
|
|
|
|
joinAliasEntity <-
|
2021-05-18 16:06:42 +03:00
|
|
|
lift (lift (generateEntityAlias (ForOrderAlias (tableNameText tableName))))
|
2021-02-23 20:37:27 +03:00
|
|
|
foreignKeyConditions <- lift (fromMapping selectFrom mapping)
|
|
|
|
whereExpression <-
|
|
|
|
lift (local (const (fromAlias selectFrom)) (fromAnnBoolExp annBoolExp))
|
|
|
|
aggregate <-
|
|
|
|
lift
|
|
|
|
(local
|
|
|
|
(const (fromAlias selectFrom))
|
|
|
|
(case annAggregateOrderBy of
|
|
|
|
IR.AAOCount -> pure (CountAggregate StarCountable)
|
|
|
|
IR.AAOOp text pgColumnInfo -> do
|
|
|
|
fieldName <- fromPGColumnInfo pgColumnInfo
|
|
|
|
pure (OpAggregate text (pure (ColumnExpression fieldName)))))
|
|
|
|
tell
|
|
|
|
(pure
|
|
|
|
(UnfurledJoin
|
|
|
|
{ unfurledJoin =
|
|
|
|
Join
|
|
|
|
{ joinSource =
|
|
|
|
JoinSelect
|
|
|
|
Select
|
|
|
|
{ selectTop = NoTop
|
|
|
|
, selectProjections =
|
|
|
|
[ AggregateProjection
|
|
|
|
Aliased
|
|
|
|
{ aliasedThing = aggregate
|
|
|
|
, aliasedAlias = alias
|
|
|
|
}
|
|
|
|
]
|
2021-06-08 06:50:24 +03:00
|
|
|
, selectFrom = Just selectFrom
|
2021-02-23 20:37:27 +03:00
|
|
|
, selectJoins = []
|
|
|
|
, selectWhere =
|
|
|
|
Where
|
|
|
|
(foreignKeyConditions <> [whereExpression])
|
|
|
|
, selectFor = NoFor
|
|
|
|
, selectOrderBy = Nothing
|
|
|
|
, selectOffset = Nothing
|
|
|
|
}
|
|
|
|
, joinJoinAlias =
|
|
|
|
JoinAlias {joinAliasEntity, joinAliasField = Nothing}
|
|
|
|
}
|
|
|
|
, unfurledObjectTableAlias = Nothing
|
|
|
|
}))
|
2021-05-21 15:27:44 +03:00
|
|
|
pure
|
|
|
|
( FieldName {fieldNameEntity = joinAliasEntity, fieldName = alias}
|
|
|
|
, Nothing)
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Conversion functions
|
|
|
|
|
2021-07-08 23:49:10 +03:00
|
|
|
tableNameText :: TableName -> Text
|
2021-02-23 20:37:27 +03:00
|
|
|
tableNameText (TableName {tableName}) = tableName
|
|
|
|
|
|
|
|
-- | This is really the start where you query the base table,
|
|
|
|
-- everything else is joins attached to it.
|
|
|
|
fromQualifiedTable :: TableName -> FromIr From
|
|
|
|
fromQualifiedTable schemadTableName@(TableName{tableName}) = do
|
|
|
|
alias <- generateEntityAlias (TableTemplate tableName)
|
|
|
|
pure
|
|
|
|
(FromQualifiedTable
|
|
|
|
(Aliased
|
2021-07-08 23:49:10 +03:00
|
|
|
{ aliasedThing = schemadTableName
|
2021-02-23 20:37:27 +03:00
|
|
|
, aliasedAlias = alias
|
|
|
|
}))
|
|
|
|
|
|
|
|
fromTableName :: TableName -> FromIr EntityAlias
|
|
|
|
fromTableName TableName{tableName} = do
|
|
|
|
alias <- generateEntityAlias (TableTemplate tableName)
|
|
|
|
pure (EntityAlias alias)
|
|
|
|
|
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
|
|
|
fromAnnBoolExp
|
|
|
|
:: IR.GBoolExp 'MSSQL (IR.AnnBoolExpFld 'MSSQL Expression)
|
2021-02-23 20:37:27 +03:00
|
|
|
-> ReaderT EntityAlias FromIr Expression
|
|
|
|
fromAnnBoolExp = traverse fromAnnBoolExpFld >=> fromGBoolExp
|
|
|
|
|
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
|
|
|
fromAnnBoolExpFld
|
|
|
|
:: IR.AnnBoolExpFld 'MSSQL Expression
|
|
|
|
-> ReaderT EntityAlias FromIr Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
fromAnnBoolExpFld =
|
|
|
|
\case
|
2021-07-07 14:58:37 +03:00
|
|
|
IR.AVColumn pgColumnInfo opExpGs -> do
|
2021-05-21 15:27:44 +03:00
|
|
|
expression <- fromColumnInfoForBoolExp pgColumnInfo
|
2021-02-23 20:37:27 +03:00
|
|
|
expressions <- traverse (lift . fromOpExpG expression) opExpGs
|
|
|
|
pure (AndExpression expressions)
|
2021-07-07 14:58:37 +03:00
|
|
|
IR.AVRelationship IR.RelInfo {riMapping = mapping, riRTable = table} annBoolExp -> do
|
2021-02-23 20:37:27 +03:00
|
|
|
selectFrom <- lift (fromQualifiedTable table)
|
|
|
|
foreignKeyConditions <- fromMapping selectFrom mapping
|
|
|
|
whereExpression <-
|
|
|
|
local (const (fromAlias selectFrom)) (fromAnnBoolExp annBoolExp)
|
|
|
|
pure
|
|
|
|
(ExistsExpression
|
|
|
|
Select
|
|
|
|
{ selectOrderBy = Nothing
|
|
|
|
, selectProjections =
|
|
|
|
[ ExpressionProjection
|
|
|
|
(Aliased
|
|
|
|
{ aliasedThing = trueExpression
|
|
|
|
, aliasedAlias = existsFieldName
|
|
|
|
})
|
|
|
|
]
|
2021-06-08 06:50:24 +03:00
|
|
|
, selectFrom = Just selectFrom
|
2021-02-23 20:37:27 +03:00
|
|
|
, selectJoins = mempty
|
|
|
|
, selectWhere = Where (foreignKeyConditions <> [whereExpression])
|
|
|
|
, selectTop = NoTop
|
|
|
|
, selectFor = NoFor
|
|
|
|
, selectOffset = Nothing
|
|
|
|
})
|
|
|
|
|
2021-05-21 15:27:44 +03:00
|
|
|
-- | For boolean operators, various comparison operators used need
|
|
|
|
-- special handling to ensure that SQL Server won't outright reject
|
|
|
|
-- the comparison. See also 'shouldCastToVarcharMax'.
|
|
|
|
fromColumnInfoForBoolExp :: IR.ColumnInfo 'MSSQL -> ReaderT EntityAlias FromIr Expression
|
|
|
|
fromColumnInfoForBoolExp IR.ColumnInfo {pgiColumn = pgCol, pgiType} = do
|
|
|
|
fieldName <- columnNameToFieldName pgCol <$> ask
|
|
|
|
if shouldCastToVarcharMax pgiType -- See function commentary.
|
|
|
|
then pure (CastExpression (ColumnExpression fieldName) "VARCHAR(MAX)")
|
|
|
|
else pure (ColumnExpression fieldName)
|
|
|
|
|
|
|
|
-- | There's a problem of comparing text fields with =, <, etc. that
|
|
|
|
-- SQL Server completely refuses to do so. So one way to workaround
|
|
|
|
-- this restriction is to automatically cast such text fields to
|
|
|
|
-- varchar(max).
|
|
|
|
shouldCastToVarcharMax :: IR.ColumnType 'MSSQL -> Bool
|
|
|
|
shouldCastToVarcharMax typ =
|
|
|
|
typ == IR.ColumnScalar TextType || typ == IR.ColumnScalar WtextType
|
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
fromPGColumnInfo :: IR.ColumnInfo 'MSSQL -> ReaderT EntityAlias FromIr FieldName
|
|
|
|
fromPGColumnInfo IR.ColumnInfo {pgiColumn = pgCol} =
|
|
|
|
columnNameToFieldName pgCol <$> ask
|
|
|
|
-- entityAlias <- ask
|
|
|
|
-- pure
|
|
|
|
-- (columnNameToFieldName pgCol entityAlias
|
|
|
|
-- FieldName
|
|
|
|
-- {fieldName = PG.getPGColTxt pgCol, fieldNameEntity = entityAliasText})
|
|
|
|
|
|
|
|
fromGExists :: IR.GExists 'MSSQL Expression -> ReaderT EntityAlias FromIr Select
|
|
|
|
fromGExists IR.GExists {_geTable, _geWhere} = do
|
|
|
|
selectFrom <- lift (fromQualifiedTable _geTable)
|
|
|
|
whereExpression <-
|
|
|
|
local (const (fromAlias selectFrom)) (fromGBoolExp _geWhere)
|
|
|
|
pure
|
|
|
|
Select
|
|
|
|
{ selectOrderBy = Nothing
|
|
|
|
, selectProjections =
|
|
|
|
[ ExpressionProjection
|
|
|
|
(Aliased
|
|
|
|
{ aliasedThing = trueExpression
|
|
|
|
, aliasedAlias = existsFieldName
|
|
|
|
})
|
|
|
|
]
|
2021-06-08 06:50:24 +03:00
|
|
|
, selectFrom = Just selectFrom
|
2021-02-23 20:37:27 +03:00
|
|
|
, selectJoins = mempty
|
|
|
|
, selectWhere = Where [whereExpression]
|
|
|
|
, selectTop = NoTop
|
|
|
|
, selectFor = NoFor
|
|
|
|
, selectOffset = Nothing
|
|
|
|
}
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Sources of projected fields
|
|
|
|
--
|
|
|
|
-- Because in the IR, a field projected can be a foreign object, we
|
|
|
|
-- have to both generate a projection AND on the side generate a join.
|
|
|
|
--
|
|
|
|
-- So a @FieldSource@ couples the idea of the projected thing and the
|
|
|
|
-- source of it (via 'Aliased').
|
|
|
|
|
|
|
|
data FieldSource
|
|
|
|
= ExpressionFieldSource (Aliased Expression)
|
|
|
|
| JoinFieldSource (Aliased Join)
|
|
|
|
| AggregateFieldSource [Aliased Aggregate]
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2021-07-08 23:49:10 +03:00
|
|
|
-- | Get FieldSource from a TAFExp type table aggregate field
|
|
|
|
fromTableExpFieldG :: -- TODO: Convert function to be similar to Nodes function
|
|
|
|
(Int, (IR.FieldName, IR.TableAggregateFieldG 'MSSQL (Const Void) Expression)) ->
|
|
|
|
Maybe (ReaderT EntityAlias FromIr (Int, [Projection]))
|
|
|
|
fromTableExpFieldG = \case
|
|
|
|
(index, (IR.FieldName name, IR.TAFExp text)) -> Just $
|
|
|
|
pure $
|
|
|
|
(index, fieldSourceProjections $
|
|
|
|
ExpressionFieldSource
|
|
|
|
Aliased
|
|
|
|
{ aliasedThing = TSQL.ValueExpression (ODBC.TextValue text)
|
|
|
|
, aliasedAlias = name
|
|
|
|
})
|
|
|
|
_ -> Nothing
|
|
|
|
|
|
|
|
fromTableAggFieldG ::
|
|
|
|
(Int, (IR.FieldName, IR.TableAggregateFieldG 'MSSQL (Const Void) Expression)) ->
|
|
|
|
Maybe (ReaderT EntityAlias FromIr (Int, (IR.FieldName, [Projection])))
|
|
|
|
fromTableAggFieldG = \case
|
|
|
|
(index, (fieldName, IR.TAFAgg (aggregateFields :: [(IR.FieldName, IR.AggregateField 'MSSQL)]))) -> Just do
|
|
|
|
aggregates <-
|
|
|
|
for aggregateFields \(fieldName', aggregateField) ->
|
|
|
|
fromAggregateField aggregateField <&> \aliasedThing ->
|
|
|
|
Aliased {aliasedAlias = IR.getFieldNameTxt fieldName', ..}
|
|
|
|
pure (index, (fieldName, fieldSourceProjections $ AggregateFieldSource aggregates))
|
|
|
|
_ -> Nothing
|
|
|
|
|
|
|
|
|
|
|
|
fromTableNodesFieldG ::
|
|
|
|
Map TableName EntityAlias ->
|
|
|
|
StringifyNumbers ->
|
|
|
|
(Int, (IR.FieldName, IR.TableAggregateFieldG 'MSSQL (Const Void) Expression)) ->
|
|
|
|
Maybe (ReaderT EntityAlias FromIr (Int, (IR.FieldName, [Projection])))
|
|
|
|
fromTableNodesFieldG argsExistingJoins stringifyNumbers = \case
|
|
|
|
(index, (fieldName, IR.TAFNodes () (annFieldsG :: [(IR.FieldName, IR.AnnFieldG 'MSSQL (Const Void) Expression)]))) -> Just do
|
|
|
|
fieldSources' <- fromAnnFieldsG argsExistingJoins stringifyNumbers `traverse` annFieldsG
|
|
|
|
let nodesProjections' :: [Projection] = concatMap fieldSourceProjections fieldSources'
|
|
|
|
pure (index, (fieldName, nodesProjections'))
|
|
|
|
_ -> Nothing
|
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
fromAggregateField :: IR.AggregateField 'MSSQL -> ReaderT EntityAlias FromIr Aggregate
|
|
|
|
fromAggregateField aggregateField =
|
|
|
|
case aggregateField of
|
|
|
|
IR.AFExp text -> pure (TextAggregate text)
|
|
|
|
IR.AFCount countType -> CountAggregate <$> case countType of
|
|
|
|
StarCountable -> pure StarCountable
|
|
|
|
NonNullFieldCountable names -> NonNullFieldCountable <$> traverse fromPGCol names
|
|
|
|
DistinctCountable names -> DistinctCountable <$> traverse fromPGCol names
|
|
|
|
IR.AFOp IR.AggregateOp {_aoOp = op, _aoFields = fields} -> do
|
2021-07-30 12:02:38 +03:00
|
|
|
projections :: [Projection] <- for fields \(fieldName, pgColFld) ->
|
2021-02-23 20:37:27 +03:00
|
|
|
case pgColFld of
|
2021-07-30 12:02:38 +03:00
|
|
|
IR.CFCol pgCol _pgType -> do
|
|
|
|
fname <- fromPGCol pgCol
|
|
|
|
pure $ AggregateProjection $ Aliased (JsonQueryOpAggregate op [ColumnExpression fname]) (IR.getFieldNameTxt fieldName)
|
|
|
|
IR.CFExp text -> do
|
|
|
|
pure $ ExpressionProjection $ Aliased (ValueExpression (ODBC.TextValue text)) (IR.getFieldNameTxt fieldName)
|
|
|
|
pure $ OpAggregate op $
|
|
|
|
[ JsonQueryExpression $ SelectExpression $
|
|
|
|
emptySelect
|
|
|
|
{ selectProjections = projections
|
|
|
|
, selectFor = JsonFor $ ForJson JsonSingleton NoRoot
|
|
|
|
}
|
|
|
|
]
|
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
-- | The main sources of fields, either constants, fields or via joins.
|
|
|
|
fromAnnFieldsG ::
|
|
|
|
Map TableName EntityAlias
|
|
|
|
-> StringifyNumbers
|
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
|
|
|
-> (IR.FieldName, IR.AnnFieldG 'MSSQL (Const Void) Expression)
|
2021-02-23 20:37:27 +03:00
|
|
|
-> ReaderT EntityAlias FromIr FieldSource
|
|
|
|
fromAnnFieldsG existingJoins stringifyNumbers (IR.FieldName name, field) =
|
|
|
|
case field of
|
|
|
|
IR.AFColumn annColumnField -> do
|
|
|
|
expression <- fromAnnColumnField stringifyNumbers annColumnField
|
|
|
|
pure
|
|
|
|
(ExpressionFieldSource
|
|
|
|
Aliased {aliasedThing = expression, aliasedAlias = name})
|
|
|
|
IR.AFExpression text ->
|
|
|
|
pure
|
|
|
|
(ExpressionFieldSource
|
|
|
|
Aliased
|
|
|
|
{ aliasedThing = TSQL.ValueExpression (ODBC.TextValue text)
|
|
|
|
, aliasedAlias = name
|
|
|
|
})
|
|
|
|
IR.AFObjectRelation objectRelationSelectG ->
|
|
|
|
fmap
|
|
|
|
(\aliasedThing ->
|
|
|
|
JoinFieldSource (Aliased {aliasedThing, aliasedAlias = name}))
|
|
|
|
(fromObjectRelationSelectG existingJoins objectRelationSelectG)
|
|
|
|
IR.AFArrayRelation arraySelectG ->
|
|
|
|
fmap
|
|
|
|
(\aliasedThing ->
|
|
|
|
JoinFieldSource (Aliased {aliasedThing, aliasedAlias = name}))
|
|
|
|
(fromArraySelectG arraySelectG)
|
|
|
|
|
|
|
|
-- | Here is where we project a field as a column expression. If
|
|
|
|
-- number stringification is on, then we wrap it in a
|
|
|
|
-- 'ToStringExpression' so that it's casted when being projected.
|
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
|
|
|
fromAnnColumnField
|
|
|
|
:: StringifyNumbers
|
[Preview] Inherited roles for postgres read queries
fixes #3868
docker image - `hasura/graphql-engine:inherited-roles-preview-48b73a2de`
Note:
To be able to use the inherited roles feature, the graphql-engine should be started with the env variable `HASURA_GRAPHQL_EXPERIMENTAL_FEATURES` set to `inherited_roles`.
Introduction
------------
This PR implements the idea of multiple roles as presented in this [paper](https://www.microsoft.com/en-us/research/wp-content/uploads/2016/02/FGALanguageICDE07.pdf). The multiple roles feature in this PR can be used via inherited roles. An inherited role is a role which can be created by combining multiple singular roles. For example, if there are two roles `author` and `editor` configured in the graphql-engine, then we can create a inherited role with the name of `combined_author_editor` role which will combine the select permissions of the `author` and `editor` roles and then make GraphQL queries using the `combined_author_editor`.
How are select permissions of different roles are combined?
------------------------------------------------------------
A select permission includes 5 things:
1. Columns accessible to the role
2. Row selection filter
3. Limit
4. Allow aggregation
5. Scalar computed fields accessible to the role
Suppose there are two roles, `role1` gives access to the `address` column with row filter `P1` and `role2` gives access to both the `address` and the `phone` column with row filter `P2` and we create a new role `combined_roles` which combines `role1` and `role2`.
Let's say the following GraphQL query is queried with the `combined_roles` role.
```graphql
query {
employees {
address
phone
}
}
```
This will translate to the following SQL query:
```sql
select
(case when (P1 or P2) then address else null end) as address,
(case when P2 then phone else null end) as phone
from employee
where (P1 or P2)
```
The other parameters of the select permission will be combined in the following manner:
1. Limit - Minimum of the limits will be the limit of the inherited role
2. Allow aggregations - If any of the role allows aggregation, then the inherited role will allow aggregation
3. Scalar computed fields - same as table column fields, as in the above example
APIs for inherited roles:
----------------------
1. `add_inherited_role`
`add_inherited_role` is the [metadata API](https://hasura.io/docs/1.0/graphql/core/api-reference/index.html#schema-metadata-api) to create a new inherited role. It accepts two arguments
`role_name`: the name of the inherited role to be added (String)
`role_set`: list of roles that need to be combined (Array of Strings)
Example:
```json
{
"type": "add_inherited_role",
"args": {
"role_name":"combined_user",
"role_set":[
"user",
"user1"
]
}
}
```
After adding the inherited role, the inherited role can be used like single roles like earlier
Note:
An inherited role can only be created with non-inherited/singular roles.
2. `drop_inherited_role`
The `drop_inherited_role` API accepts the name of the inherited role and drops it from the metadata. It accepts a single argument:
`role_name`: name of the inherited role to be dropped
Example:
```json
{
"type": "drop_inherited_role",
"args": {
"role_name":"combined_user"
}
}
```
Metadata
---------
The derived roles metadata will be included under the `experimental_features` key while exporting the metadata.
```json
{
"experimental_features": {
"derived_roles": [
{
"role_name": "manager_is_employee_too",
"role_set": [
"employee",
"manager"
]
}
]
}
}
```
Scope
------
Only postgres queries and subscriptions are supported in this PR.
Important points:
-----------------
1. All columns exposed to an inherited role will be marked as `nullable`, this is done so that cell value nullification can be done.
TODOs
-------
- [ ] Tests
- [ ] Test a GraphQL query running with a inherited role without enabling inherited roles in experimental features
- [] Tests for aggregate queries, limit, computed fields, functions, subscriptions (?)
- [ ] Introspection test with a inherited role (nullability changes in a inherited role)
- [ ] Docs
- [ ] Changelog
Co-authored-by: Vamshi Surabhi <6562944+0x777@users.noreply.github.com>
GitOrigin-RevId: 3b8ee1e11f5ceca80fe294f8c074d42fbccfec63
2021-03-08 14:14:13 +03:00
|
|
|
-> IR.AnnColumnField 'MSSQL Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
-> ReaderT EntityAlias FromIr Expression
|
|
|
|
fromAnnColumnField _stringifyNumbers annColumnField = do
|
|
|
|
fieldName <- fromPGCol pgCol
|
2021-02-24 15:52:21 +03:00
|
|
|
-- TODO: Handle stringifying large numbers
|
|
|
|
{-(IR.isScalarColumnWhere PG.isBigNum typ && stringifyNumbers == StringifyNumbers)-}
|
|
|
|
|
|
|
|
-- for geometry and geography values, the automatic json encoding on sql
|
|
|
|
-- server would fail. So we need to convert it to a format the json encoding
|
|
|
|
-- handles. Ideally we want this representation to be GeoJSON but sql server
|
|
|
|
-- doesn't have any functions to convert to GeoJSON format. So we return it in
|
|
|
|
-- WKT format
|
|
|
|
if typ == (IR.ColumnScalar GeometryType) || typ == (IR.ColumnScalar GeographyType)
|
|
|
|
then pure $ MethodExpression (ColumnExpression fieldName) "STAsText" []
|
2021-07-08 23:49:10 +03:00
|
|
|
else case caseBoolExpMaybe of
|
|
|
|
Nothing -> pure (ColumnExpression fieldName)
|
|
|
|
Just ex -> do
|
|
|
|
ex' <- (traverse fromAnnBoolExpFld >=> fromGBoolExp) (coerce ex)
|
|
|
|
pure (ConditionalProjection ex' fieldName)
|
2021-02-23 20:37:27 +03:00
|
|
|
where
|
2021-02-24 15:52:21 +03:00
|
|
|
IR.AnnColumnField { _acfInfo = IR.ColumnInfo{pgiColumn=pgCol,pgiType=typ}
|
|
|
|
, _acfAsText = _asText :: Bool
|
2021-02-23 20:37:27 +03:00
|
|
|
, _acfOp = _ :: Maybe (IR.ColumnOp 'MSSQL) -- TODO: What's this?
|
2021-07-08 23:49:10 +03:00
|
|
|
, _acfCaseBoolExpression = caseBoolExpMaybe
|
2021-02-23 20:37:27 +03:00
|
|
|
} = annColumnField
|
|
|
|
|
|
|
|
-- | This is where a field name "foo" is resolved to a fully qualified
|
|
|
|
-- field name [table].[foo]. The table name comes from EntityAlias in
|
|
|
|
-- the ReaderT.
|
|
|
|
fromPGCol :: ColumnName -> ReaderT EntityAlias FromIr FieldName
|
|
|
|
fromPGCol pgCol = columnNameToFieldName pgCol <$> ask
|
|
|
|
-- entityAlias <- ask
|
|
|
|
-- pure (columnNameToFieldName pgCol entityAlias -- FieldName {fieldName = PG.getPGColTxt pgCol, fieldNameEntity = entityAliasText}
|
|
|
|
-- )
|
|
|
|
|
|
|
|
fieldSourceProjections :: FieldSource -> [Projection]
|
|
|
|
fieldSourceProjections =
|
|
|
|
\case
|
|
|
|
ExpressionFieldSource aliasedExpression ->
|
|
|
|
pure (ExpressionProjection aliasedExpression)
|
|
|
|
JoinFieldSource aliasedJoin ->
|
|
|
|
pure
|
|
|
|
(ExpressionProjection
|
|
|
|
(aliasedJoin
|
|
|
|
{ aliasedThing =
|
|
|
|
-- Basically a cast, to ensure that SQL Server won't
|
|
|
|
-- double-encode the JSON but will "pass it through"
|
|
|
|
-- untouched.
|
|
|
|
JsonQueryExpression
|
|
|
|
(ColumnExpression
|
|
|
|
(joinAliasToField
|
|
|
|
(joinJoinAlias (aliasedThing aliasedJoin))))
|
|
|
|
}))
|
|
|
|
AggregateFieldSource aggregates -> fmap AggregateProjection aggregates
|
|
|
|
|
|
|
|
joinAliasToField :: JoinAlias -> FieldName
|
|
|
|
joinAliasToField JoinAlias {..} =
|
|
|
|
FieldName
|
|
|
|
{ fieldNameEntity = joinAliasEntity
|
|
|
|
, fieldName = fromMaybe (error "TODO: Eliminate this case. joinAliasToField") joinAliasField
|
|
|
|
}
|
|
|
|
|
|
|
|
fieldSourceJoin :: FieldSource -> Maybe Join
|
|
|
|
fieldSourceJoin =
|
|
|
|
\case
|
|
|
|
JoinFieldSource aliasedJoin -> pure (aliasedThing aliasedJoin)
|
|
|
|
ExpressionFieldSource {} -> Nothing
|
|
|
|
AggregateFieldSource {} -> Nothing
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Joins
|
|
|
|
|
|
|
|
fromObjectRelationSelectG ::
|
|
|
|
Map TableName {-PG.QualifiedTable-} EntityAlias
|
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
|
|
|
-> IR.ObjectRelationSelectG 'MSSQL (Const Void) Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
-> ReaderT EntityAlias FromIr Join
|
|
|
|
fromObjectRelationSelectG existingJoins annRelationSelectG = do
|
|
|
|
eitherAliasOrFrom <- lift (lookupTableFrom existingJoins tableFrom)
|
|
|
|
let entityAlias :: EntityAlias = either id fromAlias eitherAliasOrFrom
|
|
|
|
fieldSources <-
|
|
|
|
local
|
|
|
|
(const entityAlias)
|
|
|
|
(traverse (fromAnnFieldsG mempty LeaveNumbersAlone) fields)
|
|
|
|
let selectProjections =
|
|
|
|
concatMap (toList . fieldSourceProjections) fieldSources
|
|
|
|
joinJoinAlias <-
|
|
|
|
do fieldName <- lift (fromRelName aarRelationshipName)
|
|
|
|
alias <- lift (generateEntityAlias (ObjectRelationTemplate fieldName))
|
|
|
|
pure
|
|
|
|
JoinAlias
|
|
|
|
{joinAliasEntity = alias, joinAliasField = pure jsonFieldName}
|
|
|
|
let selectFor =
|
|
|
|
JsonFor ForJson {jsonCardinality = JsonSingleton, jsonRoot = NoRoot}
|
|
|
|
filterExpression <- local (const entityAlias) (fromAnnBoolExp tableFilter)
|
|
|
|
case eitherAliasOrFrom of
|
|
|
|
Right selectFrom -> do
|
|
|
|
foreignKeyConditions <- fromMapping selectFrom mapping
|
|
|
|
pure
|
|
|
|
Join
|
|
|
|
{ joinJoinAlias
|
|
|
|
, joinSource =
|
|
|
|
JoinSelect
|
|
|
|
Select
|
|
|
|
{ selectOrderBy = Nothing
|
|
|
|
, selectTop = NoTop
|
|
|
|
, selectProjections
|
2021-06-08 06:50:24 +03:00
|
|
|
, selectFrom = Just selectFrom
|
2021-02-23 20:37:27 +03:00
|
|
|
, selectJoins = mapMaybe fieldSourceJoin fieldSources
|
|
|
|
, selectWhere =
|
|
|
|
Where (foreignKeyConditions <> [filterExpression])
|
|
|
|
, selectFor
|
|
|
|
, selectOffset = Nothing
|
|
|
|
}
|
|
|
|
}
|
|
|
|
Left _entityAlias ->
|
|
|
|
pure
|
|
|
|
Join
|
|
|
|
{ joinJoinAlias
|
|
|
|
, joinSource =
|
|
|
|
JoinReselect
|
|
|
|
Reselect
|
|
|
|
{ reselectProjections = selectProjections
|
|
|
|
, reselectFor = selectFor
|
|
|
|
, reselectWhere = Where [filterExpression]
|
|
|
|
}
|
|
|
|
}
|
|
|
|
where
|
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
|
|
|
IR.AnnObjectSelectG { _aosFields = fields :: IR.AnnFieldsG 'MSSQL (Const Void) Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
, _aosTableFrom = tableFrom :: TableName{-PG.QualifiedTable-}
|
|
|
|
, _aosTableFilter = tableFilter :: IR.AnnBoolExp 'MSSQL Expression
|
|
|
|
} = annObjectSelectG
|
|
|
|
IR.AnnRelationSelectG { aarRelationshipName
|
|
|
|
, aarColumnMapping = mapping :: HashMap ColumnName ColumnName -- PG.PGCol PG.PGCol
|
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
|
|
|
, aarAnnSelect = annObjectSelectG :: IR.AnnObjectSelectG 'MSSQL (Const Void) Expression
|
2021-02-23 20:37:27 +03:00
|
|
|
} = annRelationSelectG
|
|
|
|
|
|
|
|
lookupTableFrom ::
|
|
|
|
Map TableName {-PG.QualifiedTable-} EntityAlias
|
|
|
|
-> {-PG.QualifiedTable-}TableName
|
|
|
|
-> FromIr (Either EntityAlias From)
|
|
|
|
lookupTableFrom existingJoins tableFrom = do
|
|
|
|
case M.lookup tableFrom existingJoins of
|
|
|
|
Just entityAlias -> pure (Left entityAlias)
|
|
|
|
Nothing -> fmap Right (fromQualifiedTable tableFrom)
|
|
|
|
|
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
|
|
|
fromArraySelectG :: IR.ArraySelectG 'MSSQL (Const Void) Expression -> ReaderT EntityAlias FromIr Join
|
2021-02-23 20:37:27 +03:00
|
|
|
fromArraySelectG =
|
|
|
|
\case
|
|
|
|
IR.ASSimple arrayRelationSelectG ->
|
|
|
|
fromArrayRelationSelectG arrayRelationSelectG
|
|
|
|
IR.ASAggregate arrayAggregateSelectG ->
|
|
|
|
fromArrayAggregateSelectG arrayAggregateSelectG
|
|
|
|
|
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
|
|
|
fromArrayAggregateSelectG
|
|
|
|
:: IR.AnnRelationSelectG 'MSSQL (IR.AnnAggregateSelectG 'MSSQL (Const Void) Expression)
|
2021-02-23 20:37:27 +03:00
|
|
|
-> ReaderT EntityAlias FromIr Join
|
|
|
|
fromArrayAggregateSelectG annRelationSelectG = do
|
|
|
|
fieldName <- lift (fromRelName aarRelationshipName)
|
2021-07-08 23:49:10 +03:00
|
|
|
joinSelect <- do
|
|
|
|
lhsEntityAlias <- ask
|
|
|
|
-- With this, the foreign key relations are injected automatically
|
|
|
|
-- at the right place by fromSelectAggregate.
|
|
|
|
lift (fromSelectAggregate (pure (lhsEntityAlias, mapping)) annSelectG)
|
2021-02-23 20:37:27 +03:00
|
|
|
alias <- lift (generateEntityAlias (ArrayAggregateTemplate fieldName))
|
|
|
|
pure
|
|
|
|
Join
|
|
|
|
{ joinJoinAlias =
|
|
|
|
JoinAlias
|
|
|
|
{joinAliasEntity = alias, joinAliasField = pure jsonFieldName}
|
|
|
|
, joinSource = JoinSelect joinSelect
|
|
|
|
}
|
|
|
|
where
|
|
|
|
IR.AnnRelationSelectG { aarRelationshipName
|
2021-07-08 23:49:10 +03:00
|
|
|
, aarColumnMapping = mapping :: HashMap ColumnName ColumnName
|
2021-02-23 20:37:27 +03:00
|
|
|
, aarAnnSelect = annSelectG
|
|
|
|
} = annRelationSelectG
|
|
|
|
|
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
|
|
|
fromArrayRelationSelectG :: IR.ArrayRelationSelectG 'MSSQL (Const Void) Expression -> ReaderT EntityAlias FromIr Join
|
2021-02-23 20:37:27 +03:00
|
|
|
fromArrayRelationSelectG annRelationSelectG = do
|
|
|
|
fieldName <- lift (fromRelName aarRelationshipName)
|
2021-06-08 06:50:24 +03:00
|
|
|
sel <- lift (fromSelectRows annSelectG)
|
2021-02-23 20:37:27 +03:00
|
|
|
joinSelect <-
|
2021-06-08 06:50:24 +03:00
|
|
|
do foreignKeyConditions <- selectFromMapping sel mapping
|
2021-02-23 20:37:27 +03:00
|
|
|
pure
|
2021-06-08 06:50:24 +03:00
|
|
|
sel {selectWhere = Where foreignKeyConditions <> selectWhere sel}
|
2021-02-23 20:37:27 +03:00
|
|
|
alias <- lift (generateEntityAlias (ArrayRelationTemplate fieldName))
|
|
|
|
pure
|
|
|
|
Join
|
|
|
|
{ joinJoinAlias =
|
|
|
|
JoinAlias
|
|
|
|
{joinAliasEntity = alias, joinAliasField = pure jsonFieldName}
|
|
|
|
, joinSource = JoinSelect joinSelect
|
|
|
|
}
|
|
|
|
where
|
|
|
|
IR.AnnRelationSelectG { aarRelationshipName
|
|
|
|
, aarColumnMapping = mapping :: HashMap ColumnName ColumnName-- PG.PGCol PG.PGCol
|
|
|
|
, aarAnnSelect = annSelectG
|
|
|
|
} = annRelationSelectG
|
|
|
|
|
|
|
|
fromRelName :: IR.RelName -> FromIr Text
|
|
|
|
fromRelName relName =
|
|
|
|
pure (IR.relNameToTxt relName)
|
|
|
|
|
|
|
|
-- | The context given by the reader is of the previous/parent
|
|
|
|
-- "remote" table. The WHERE that we're generating goes in the child,
|
|
|
|
-- "local" query. The @From@ passed in as argument is the local table.
|
|
|
|
--
|
|
|
|
-- We should hope to see e.g. "post.category = category.id" for a
|
|
|
|
-- local table of post and a remote table of category.
|
|
|
|
--
|
|
|
|
-- The left/right columns in @HashMap PG.PGCol PG.PGCol@ corresponds
|
|
|
|
-- to the left/right of @select ... join ...@. Therefore left=remote,
|
|
|
|
-- right=local in this context.
|
|
|
|
fromMapping ::
|
|
|
|
From
|
|
|
|
-> HashMap ColumnName ColumnName-- PG.PGCol PG.PGCol
|
|
|
|
-> ReaderT EntityAlias FromIr [Expression]
|
|
|
|
fromMapping localFrom =
|
|
|
|
traverse
|
|
|
|
(\(remotePgCol, localPgCol) -> do
|
|
|
|
localFieldName <- local (const (fromAlias localFrom)) (fromPGCol localPgCol)
|
|
|
|
remoteFieldName <- fromPGCol remotePgCol
|
|
|
|
pure
|
2021-05-21 15:27:44 +03:00
|
|
|
(OpExpression TSQL.EQ'
|
2021-02-23 20:37:27 +03:00
|
|
|
(ColumnExpression localFieldName)
|
|
|
|
(ColumnExpression remoteFieldName))) .
|
|
|
|
HM.toList
|
|
|
|
|
2021-06-08 06:50:24 +03:00
|
|
|
selectFromMapping :: Select
|
|
|
|
-> HashMap ColumnName ColumnName
|
|
|
|
-> ReaderT EntityAlias FromIr [Expression]
|
|
|
|
selectFromMapping Select {selectFrom = Nothing } = const (pure [])
|
|
|
|
selectFromMapping Select {selectFrom = Just from} = fromMapping from
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Basic SQL expression types
|
|
|
|
|
|
|
|
fromOpExpG :: Expression -> IR.OpExpG 'MSSQL Expression -> FromIr Expression
|
|
|
|
fromOpExpG expression op =
|
|
|
|
case op of
|
2021-03-25 20:50:08 +03:00
|
|
|
IR.ANISNULL -> pure $ TSQL.IsNullExpression expression
|
|
|
|
IR.ANISNOTNULL -> pure $ TSQL.IsNotNullExpression expression
|
|
|
|
IR.AEQ False val -> pure $ nullableBoolEquality expression val
|
2021-05-21 15:27:44 +03:00
|
|
|
IR.AEQ True val -> pure $ OpExpression TSQL.EQ' expression val
|
2021-03-25 20:50:08 +03:00
|
|
|
IR.ANE False val -> pure $ nullableBoolInequality expression val
|
2021-05-21 15:27:44 +03:00
|
|
|
IR.ANE True val -> pure $ OpExpression TSQL.NEQ' expression val
|
2021-03-25 20:50:08 +03:00
|
|
|
IR.AGT val -> pure $ OpExpression TSQL.GT expression val
|
|
|
|
IR.ALT val -> pure $ OpExpression TSQL.LT expression val
|
|
|
|
IR.AGTE val -> pure $ OpExpression TSQL.GTE expression val
|
|
|
|
IR.ALTE val -> pure $ OpExpression TSQL.LTE expression val
|
|
|
|
IR.AIN val -> pure $ OpExpression TSQL.IN expression val
|
|
|
|
IR.ANIN val -> pure $ OpExpression TSQL.NIN expression val
|
|
|
|
IR.ALIKE val -> pure $ OpExpression TSQL.LIKE expression val
|
|
|
|
IR.ANLIKE val -> pure $ OpExpression TSQL.NLIKE expression val
|
|
|
|
|
|
|
|
IR.ABackendSpecific o -> case o of
|
|
|
|
ASTContains val -> pure $ TSQL.STOpExpression TSQL.STContains expression val
|
|
|
|
ASTCrosses val -> pure $ TSQL.STOpExpression TSQL.STCrosses expression val
|
|
|
|
ASTEquals val -> pure $ TSQL.STOpExpression TSQL.STEquals expression val
|
|
|
|
ASTIntersects val -> pure $ TSQL.STOpExpression TSQL.STIntersects expression val
|
|
|
|
ASTOverlaps val -> pure $ TSQL.STOpExpression TSQL.STOverlaps expression val
|
|
|
|
ASTTouches val -> pure $ TSQL.STOpExpression TSQL.STTouches expression val
|
|
|
|
ASTWithin val -> pure $ TSQL.STOpExpression TSQL.STWithin expression val
|
|
|
|
|
|
|
|
-- As of March 2021, only geometry/geography casts are supported
|
|
|
|
IR.ACast _casts -> refute (pure (UnsupportedOpExpG op)) -- mkCastsExp casts
|
|
|
|
|
|
|
|
-- We do not yet support column names in permissions
|
|
|
|
IR.CEQ _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SEQ lhs $ mkQCol rhsCol
|
|
|
|
IR.CNE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SNE lhs $ mkQCol rhsCol
|
|
|
|
IR.CGT _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SGT lhs $ mkQCol rhsCol
|
|
|
|
IR.CLT _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SLT lhs $ mkQCol rhsCol
|
|
|
|
IR.CGTE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SGTE lhs $ mkQCol rhsCol
|
|
|
|
IR.CLTE _rhsCol -> refute (pure (UnsupportedOpExpG op)) -- S.BECompare S.SLTE lhs $ mkQCol rhsCol
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
nullableBoolEquality :: Expression -> Expression -> Expression
|
|
|
|
nullableBoolEquality x y =
|
|
|
|
OrExpression
|
2021-05-21 15:27:44 +03:00
|
|
|
[ OpExpression TSQL.EQ' x y
|
2021-02-23 20:37:27 +03:00
|
|
|
, AndExpression [IsNullExpression x, IsNullExpression y]
|
|
|
|
]
|
|
|
|
|
|
|
|
nullableBoolInequality :: Expression -> Expression -> Expression
|
|
|
|
nullableBoolInequality x y =
|
|
|
|
OrExpression
|
2021-05-21 15:27:44 +03:00
|
|
|
[ OpExpression TSQL.NEQ' x y
|
2021-02-23 20:37:27 +03:00
|
|
|
, AndExpression [IsNotNullExpression x, IsNullExpression y]
|
|
|
|
]
|
|
|
|
|
|
|
|
fromGBoolExp :: IR.GBoolExp 'MSSQL Expression -> ReaderT EntityAlias FromIr Expression
|
|
|
|
fromGBoolExp =
|
|
|
|
\case
|
|
|
|
IR.BoolAnd expressions ->
|
|
|
|
fmap AndExpression (traverse fromGBoolExp expressions)
|
|
|
|
IR.BoolOr expressions ->
|
|
|
|
fmap OrExpression (traverse fromGBoolExp expressions)
|
|
|
|
IR.BoolNot expression -> fmap NotExpression (fromGBoolExp expression)
|
|
|
|
IR.BoolExists gExists -> fmap ExistsExpression (fromGExists gExists)
|
|
|
|
IR.BoolFld expression -> pure expression
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Delete
|
|
|
|
|
|
|
|
fromDelete :: IR.AnnDel 'MSSQL -> FromIr Delete
|
|
|
|
fromDelete (IR.AnnDel tableName (permFilter, whereClause) _ _) = do
|
|
|
|
tableAlias <- fromTableName tableName
|
|
|
|
runReaderT
|
|
|
|
(do permissionsFilter <- fromAnnBoolExp permFilter
|
|
|
|
whereExpression <- fromAnnBoolExp whereClause
|
|
|
|
pure
|
|
|
|
Delete
|
|
|
|
{ deleteTable =
|
|
|
|
Aliased
|
|
|
|
{ aliasedAlias = entityAliasText tableAlias
|
|
|
|
, aliasedThing = tableName
|
|
|
|
}
|
|
|
|
, deleteWhere = Where [permissionsFilter, whereExpression]
|
|
|
|
})
|
|
|
|
tableAlias
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Misc combinators
|
|
|
|
|
|
|
|
trueExpression :: Expression
|
|
|
|
trueExpression = ValueExpression (ODBC.BoolValue True)
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Constants
|
|
|
|
|
|
|
|
jsonFieldName :: Text
|
|
|
|
jsonFieldName = "json"
|
|
|
|
|
|
|
|
aggFieldName :: Text
|
|
|
|
aggFieldName = "agg"
|
|
|
|
|
2021-07-08 23:49:10 +03:00
|
|
|
aggSubselectName :: Text
|
|
|
|
aggSubselectName = "agg_sub"
|
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
existsFieldName :: Text
|
|
|
|
existsFieldName = "exists_placeholder"
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Name generation
|
|
|
|
|
|
|
|
data NameTemplate
|
|
|
|
= ArrayRelationTemplate Text
|
|
|
|
| ArrayAggregateTemplate Text
|
|
|
|
| ObjectRelationTemplate Text
|
|
|
|
| TableTemplate Text
|
|
|
|
| ForOrderAlias Text
|
|
|
|
|
|
|
|
generateEntityAlias :: NameTemplate -> FromIr Text
|
|
|
|
generateEntityAlias template = do
|
|
|
|
FromIr (modify' (M.insertWith (+) prefix start))
|
|
|
|
i <- FromIr get
|
|
|
|
pure (prefix <> tshow (fromMaybe start (M.lookup prefix i)))
|
|
|
|
where
|
|
|
|
start = 1
|
|
|
|
prefix = T.take 20 rendered
|
|
|
|
rendered =
|
|
|
|
case template of
|
|
|
|
ArrayRelationTemplate sample -> "ar_" <> sample
|
|
|
|
ArrayAggregateTemplate sample -> "aa_" <> sample
|
|
|
|
ObjectRelationTemplate sample -> "or_" <> sample
|
|
|
|
TableTemplate sample -> "t_" <> sample
|
|
|
|
ForOrderAlias sample -> "order_" <> sample
|
|
|
|
|
|
|
|
fromAlias :: From -> EntityAlias
|
|
|
|
fromAlias (FromQualifiedTable Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
|
|
|
fromAlias (FromOpenJson Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
2021-07-08 23:49:10 +03:00
|
|
|
fromAlias (FromSelect Aliased {aliasedAlias}) = EntityAlias aliasedAlias
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
columnNameToFieldName :: ColumnName -> EntityAlias -> FieldName
|
|
|
|
columnNameToFieldName (ColumnName fieldName) EntityAlias {entityAliasText = fieldNameEntity} =
|
|
|
|
FieldName {fieldName, fieldNameEntity}
|