2019-12-09 01:17:39 +03:00
|
|
|
|
{-# LANGUAGE Arrows #-}
|
|
|
|
|
|
|
|
|
|
module Hasura.RQL.DDL.Schema.Cache.Fields (addNonColumnFields) where
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2019-12-09 01:17:39 +03:00
|
|
|
|
import Control.Arrow.Extended
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
import Control.Arrow.Interpret
|
2021-01-20 03:31:53 +03:00
|
|
|
|
import Control.Lens ((^.), _3, _4)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
import Data.Aeson
|
2021-08-24 20:41:24 +03:00
|
|
|
|
import Data.Align (align)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
import Data.HashMap.Strict.Extended qualified as M
|
2019-12-13 00:46:33 +03:00
|
|
|
|
import Data.HashSet qualified as HS
|
2019-12-09 01:17:39 +03:00
|
|
|
|
import Data.Sequence qualified as Seq
|
2020-10-27 16:53:49 +03:00
|
|
|
|
import Data.Text.Extended
|
2021-08-24 20:41:24 +03:00
|
|
|
|
import Data.These (These (..))
|
2021-05-11 18:18:31 +03:00
|
|
|
|
import Hasura.Base.Error
|
2019-12-09 01:17:39 +03:00
|
|
|
|
import Hasura.Incremental qualified as Inc
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
import Hasura.RQL.DDL.ComputedField
|
|
|
|
|
import Hasura.RQL.DDL.Relationship
|
2021-06-11 06:26:50 +03:00
|
|
|
|
import Hasura.RQL.DDL.RemoteRelationship
|
2019-12-09 01:17:39 +03:00
|
|
|
|
import Hasura.RQL.DDL.Schema.Cache.Common
|
|
|
|
|
import Hasura.RQL.DDL.Schema.Function
|
2022-04-27 16:57:28 +03:00
|
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
|
import Hasura.RQL.Types.Column
|
|
|
|
|
import Hasura.RQL.Types.Common
|
|
|
|
|
import Hasura.RQL.Types.ComputedField
|
|
|
|
|
import Hasura.RQL.Types.Function
|
|
|
|
|
import Hasura.RQL.Types.Metadata
|
|
|
|
|
import Hasura.RQL.Types.Metadata.Backend
|
|
|
|
|
import Hasura.RQL.Types.Metadata.Object
|
|
|
|
|
import Hasura.RQL.Types.Relationships.Local
|
|
|
|
|
import Hasura.RQL.Types.Relationships.Remote
|
|
|
|
|
import Hasura.RQL.Types.SchemaCache
|
|
|
|
|
import Hasura.RQL.Types.SchemaCache.Build
|
|
|
|
|
import Hasura.RQL.Types.SchemaCacheTypes
|
|
|
|
|
import Hasura.RQL.Types.Table
|
2021-03-15 16:02:58 +03:00
|
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
2019-12-13 10:47:28 +03:00
|
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
|
|
|
|
addNonColumnFields ::
|
|
|
|
|
forall b arr m.
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
Inc.ArrowDistribute arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
ArrowKleisli m arr,
|
|
|
|
|
MonadError QErr m,
|
|
|
|
|
BackendMetadata b
|
2021-09-24 01:56:37 +03:00
|
|
|
|
) =>
|
2019-12-09 01:17:39 +03:00
|
|
|
|
( HashMap SourceName (AB.AnyBackend PartiallyResolvedSource),
|
2021-07-23 02:06:10 +03:00
|
|
|
|
SourceName,
|
2019-12-13 00:46:33 +03:00
|
|
|
|
HashMap (TableName b) (TableCoreInfoG b (ColumnInfo b) (ColumnInfo b)),
|
2021-02-14 09:07:52 +03:00
|
|
|
|
FieldInfoMap (ColumnInfo b),
|
scaffolding for remote-schemas module
The main aim of the PR is:
1. To set up a module structure for 'remote-schemas' package.
2. Move parts by the remote schema codebase into the new module structure to validate it.
## Notes to the reviewer
Why a PR with large-ish diff?
1. We've been making progress on the MM project but we don't yet know long it is going to take us to get to the first milestone. To understand this better, we need to figure out the unknowns as soon as possible. Hence I've taken a stab at the first two items in the [end-state](https://gist.github.com/0x777/ca2bdc4284d21c3eec153b51dea255c9) document to figure out the unknowns. Unsurprisingly, there are a bunch of issues that we haven't discussed earlier. These are documented in the 'open questions' section.
1. The diff is large but that is only code moved around and I've added a section that documents how things are moved. In addition, there are fair number of PR comments to help with the review process.
## Changes in the PR
### Module structure
Sets up the module structure as follows:
```
Hasura/
RemoteSchema/
Metadata/
Types.hs
SchemaCache/
Types.hs
Permission.hs
RemoteRelationship.hs
Build.hs
MetadataAPI/
Types.hs
Execute.hs
```
### 1. Types representing metadata are moved
Types that capture metadata information (currently scattered across several RQL modules) are moved into `Hasura.RemoteSchema.Metadata.Types`.
- This new module only depends on very 'core' modules such as
`Hasura.Session` for the notion of roles and `Hasura.Incremental` for `Cacheable` typeclass.
- The requirement on database modules is avoided by generalizing the remote schemas metadata to accept an arbitrary 'r' for a remote relationship
definition.
### 2. SchemaCache related types and build logic have been moved
Types that represent remote schemas information in SchemaCache are moved into `Hasura.RemoteSchema.SchemaCache.Types`.
Similar to `H.RS.Metadata.Types`, this module depends on 'core' modules except for `Hasura.GraphQL.Parser.Variable`. It has something to do with remote relationships but I haven't spent time looking into it. The validation of 'remote relationships to remote schema' is also something that needs to be looked at.
Rips out the logic that builds remote schema's SchemaCache information from the monolithic `buildSchemaCacheRule` and moves it into `Hasura.RemoteSchema.SchemaCache.Build`. Further, the `.SchemaCache.Permission` and `.SchemaCache.RemoteRelationship` have been created from existing modules that capture schema cache building logic for those two components.
This was a fair amount of work. On main, currently remote schema's SchemaCache information is built in two phases - in the first phase, 'permissions' and 'remote relationships' are ignored and in the second phase they are filled in.
While remote relationships can only be resolved after partially resolving sources and other remote schemas, the same isn't true for permissions. Further, most of the work that is done to resolve remote relationships can be moved to the first phase so that the second phase can be a very simple traversal.
This is the approach that was taken - resolve permissions and as much as remote relationships information in the first phase.
### 3. Metadata APIs related types and build logic have been moved
The types that represent remote schema related metadata APIs and the execution logic have been moved to `Hasura.RemoteSchema.MetadataAPI.Types` and `.Execute` modules respectively.
## Open questions:
1. `Hasura.RemoteSchema.Metadata.Types` is so called because I was hoping that all of the metadata related APIs of remote schema can be brought in at `Hasura.RemoteSchema.Metadata.API`. However, as metadata APIs depended on functions from `SchemaCache` module (see [1](https://github.com/hasura/graphql-engine-mono/blob/ceba6d62264603ee5d279814677b29bcc43ecaea/server/src-lib/Hasura/RQL/DDL/RemoteSchema.hs#L55) and [2](https://github.com/hasura/graphql-engine-mono/blob/ceba6d62264603ee5d279814677b29bcc43ecaea/server/src-lib/Hasura/RQL/DDL/RemoteSchema.hs#L91), it made more sense to create a separate top-level module for `MetadataAPI`s.
Maybe we can just have `Hasura.RemoteSchema.Metadata` and get rid of the extra nesting or have `Hasura.RemoteSchema.Metadata.{Core,Permission,RemoteRelationship}` if we want to break them down further.
1. `buildRemoteSchemas` in `H.RS.SchemaCache.Build` has the following type:
```haskell
buildRemoteSchemas ::
( ArrowChoice arr,
Inc.ArrowDistribute arr,
ArrowWriter (Seq CollectedInfo) arr,
Inc.ArrowCache m arr,
MonadIO m,
HasHttpManagerM m,
Inc.Cacheable remoteRelationshipDefinition,
ToJSON remoteRelationshipDefinition,
MonadError QErr m
) =>
Env.Environment ->
( (Inc.Dependency (HashMap RemoteSchemaName Inc.InvalidationKey), OrderedRoles),
[RemoteSchemaMetadataG remoteRelationshipDefinition]
)
`arr` HashMap RemoteSchemaName (PartiallyResolvedRemoteSchemaCtxG remoteRelationshipDefinition, MetadataObject)
```
Note the dependence on `CollectedInfo` which is defined as
```haskell
data CollectedInfo
= CIInconsistency InconsistentMetadata
| CIDependency
MetadataObject
-- ^ for error reporting on missing dependencies
SchemaObjId
SchemaDependency
deriving (Eq)
```
this pretty much means that remote schemas is dependent on types from databases, actions, ....
How do we fix this? Maybe introduce a typeclass such as `ArrowCollectRemoteSchemaDependencies` which is defined in `Hasura.RemoteSchema` and then implemented in graphql-engine?
1. The dependency on `buildSchemaCacheFor` in `.MetadataAPI.Execute` which has the following signature:
```haskell
buildSchemaCacheFor ::
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId ->
MetadataModifier ->
```
This can be easily resolved if we restrict what the metadata APIs are allowed to do. Currently, they operate in an unfettered access to modify SchemaCache (the `CacheRWM` constraint):
```haskell
runAddRemoteSchema ::
( QErrM m,
CacheRWM m,
MonadIO m,
HasHttpManagerM m,
MetadataM m,
Tracing.MonadTrace m
) =>
Env.Environment ->
AddRemoteSchemaQuery ->
m EncJSON
```
This should instead be changed to restrict remote schema APIs to only modify remote schema metadata (but has access to the remote schemas part of the schema cache), this dependency is completely removed.
```haskell
runAddRemoteSchema ::
( QErrM m,
MonadIO m,
HasHttpManagerM m,
MonadReader RemoteSchemasSchemaCache m,
MonadState RemoteSchemaMetadata m,
Tracing.MonadTrace m
) =>
Env.Environment ->
AddRemoteSchemaQuery ->
m RemoteSchemeMetadataObjId
```
The idea is that the core graphql-engine would call these functions and then call
`buildSchemaCacheFor`.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6291
GitOrigin-RevId: 51357148c6404afe70219afa71bd1d59bdf4ffc6
2022-10-21 06:13:07 +03:00
|
|
|
|
PartiallyResolvedRemoteSchemaMap,
|
2019-12-13 00:46:33 +03:00
|
|
|
|
DBFunctionsMetadata b,
|
|
|
|
|
NonColumnTableInputs b
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
`arr` FieldInfoMap (FieldInfo b)
|
2019-12-13 00:46:33 +03:00
|
|
|
|
addNonColumnFields =
|
2021-09-24 01:56:37 +03:00
|
|
|
|
proc
|
2019-12-13 00:46:33 +03:00
|
|
|
|
( allSources,
|
2021-09-24 01:56:37 +03:00
|
|
|
|
source,
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
|
rawTableInfo,
|
2021-09-24 01:56:37 +03:00
|
|
|
|
columns,
|
2020-12-08 17:22:31 +03:00
|
|
|
|
remoteSchemaMap,
|
2020-12-28 15:56:00 +03:00
|
|
|
|
pgFunctions,
|
2020-12-08 17:22:31 +03:00
|
|
|
|
NonColumnTableInputs {..}
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
|
|
|
|
-> do
|
2020-12-08 17:22:31 +03:00
|
|
|
|
objectRelationshipInfos <-
|
2019-12-13 00:46:33 +03:00
|
|
|
|
buildInfoMapPreservingMetadata
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
|
(_rdName . (^. _3))
|
2019-12-13 00:46:33 +03:00
|
|
|
|
(\(s, t, c) -> mkRelationshipMetadataObject @b ObjRel (s, t, c))
|
2019-12-09 01:17:39 +03:00
|
|
|
|
buildObjectRelationship
|
2021-09-24 01:56:37 +03:00
|
|
|
|
-<
|
2019-12-13 10:47:28 +03:00
|
|
|
|
(_tciForeignKeys <$> rawTableInfo, map (source,_nctiTable,) _nctiObjectRelationships)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
|
|
|
|
arrayRelationshipInfos <-
|
2020-12-08 17:22:31 +03:00
|
|
|
|
buildInfoMapPreservingMetadata
|
2021-01-20 03:31:53 +03:00
|
|
|
|
(_rdName . (^. _3))
|
|
|
|
|
(mkRelationshipMetadataObject @b ArrRel)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
buildArrayRelationship
|
2021-09-24 01:56:37 +03:00
|
|
|
|
-<
|
2021-01-20 03:31:53 +03:00
|
|
|
|
(_tciForeignKeys <$> rawTableInfo, map (source,_nctiTable,) _nctiArrayRelationships)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
|
|
|
|
let relationshipInfos = objectRelationshipInfos <> arrayRelationshipInfos
|
|
|
|
|
|
2021-05-11 18:18:31 +03:00
|
|
|
|
computedFieldInfos <-
|
|
|
|
|
buildInfoMapPreservingMetadata
|
2020-12-28 15:56:00 +03:00
|
|
|
|
(_cfmName . (^. _4))
|
2019-12-09 01:17:39 +03:00
|
|
|
|
(\(s, _, t, c) -> mkComputedFieldMetadataObject (s, t, c))
|
2022-05-25 13:24:41 +03:00
|
|
|
|
( proc ((a, b), (c, d, e, f)) -> do
|
|
|
|
|
o <- interpretWriter -< buildComputedField a b c d e f
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
arrM liftEither -< o
|
|
|
|
|
)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
-<
|
2022-05-25 13:24:41 +03:00
|
|
|
|
( ( HS.fromList $ M.keys rawTableInfo,
|
|
|
|
|
HS.fromList $ map ciColumn $ M.elems columns
|
|
|
|
|
),
|
|
|
|
|
map (source,pgFunctions,_nctiTable,) _nctiComputedFields
|
|
|
|
|
)
|
2021-12-22 02:14:56 +03:00
|
|
|
|
-- the fields that can be used for defining join conditions to other sources/remote schemas:
|
|
|
|
|
-- 1. all columns
|
|
|
|
|
-- 2. computed fields which don't expect arguments other than the table row and user session
|
|
|
|
|
let lhsJoinFields =
|
2022-01-19 11:37:50 +03:00
|
|
|
|
let columnFields = columns <&> \columnInfo -> JoinColumn (ciColumn columnInfo) (ciType columnInfo)
|
2021-07-12 19:03:36 +03:00
|
|
|
|
computedFields = M.fromList $
|
2021-12-22 02:14:56 +03:00
|
|
|
|
flip mapMaybe (M.toList computedFieldInfos) $
|
|
|
|
|
\(cfName, (ComputedFieldInfo {..}, _)) -> do
|
2022-05-25 13:24:41 +03:00
|
|
|
|
scalarType <- case computedFieldReturnType @b _cfiReturnType of
|
|
|
|
|
ReturnsScalar ty -> pure ty
|
|
|
|
|
ReturnsTable {} -> Nothing
|
|
|
|
|
ReturnsOthers {} -> Nothing
|
2021-12-22 02:14:56 +03:00
|
|
|
|
let ComputedFieldFunction {..} = _cfiFunction
|
|
|
|
|
case toList _cffInputArgs of
|
|
|
|
|
[] ->
|
|
|
|
|
pure $
|
|
|
|
|
(fromComputedField cfName,) $
|
|
|
|
|
JoinComputedField $
|
|
|
|
|
ScalarComputedField
|
|
|
|
|
_cfiXComputedFieldInfo
|
|
|
|
|
_cfiName
|
|
|
|
|
_cffName
|
2022-05-25 13:24:41 +03:00
|
|
|
|
_cffComputedFieldImplicitArgs
|
2021-12-22 02:14:56 +03:00
|
|
|
|
scalarType
|
|
|
|
|
_ -> Nothing
|
2021-07-12 19:03:36 +03:00
|
|
|
|
in M.union columnFields computedFields
|
2021-04-22 00:44:37 +03:00
|
|
|
|
|
|
|
|
|
rawRemoteRelationshipInfos <-
|
2021-02-14 09:07:52 +03:00
|
|
|
|
buildInfoMapPreservingMetadata
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(_rrName . (^. _3))
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
|
(mkRemoteRelationshipMetadataObject @b)
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
( proc ((a, b, c), d) -> do
|
2022-04-04 15:35:10 +03:00
|
|
|
|
o <- interpretWriter -< buildRemoteRelationship a b c d
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
arrM liftEither -< o
|
|
|
|
|
)
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
|
-<
|
2021-12-22 02:14:56 +03:00
|
|
|
|
((allSources, lhsJoinFields, remoteSchemaMap), map (source,_nctiTable,) _nctiRemoteRelationships)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
|
|
|
|
let relationshipFields = mapKeys fromRel relationshipInfos
|
|
|
|
|
computedFieldFields = mapKeys fromComputedField computedFieldInfos
|
2020-12-28 15:56:00 +03:00
|
|
|
|
remoteRelationshipFields = mapKeys fromRemoteRelationship rawRemoteRelationshipInfos
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2020-12-28 15:56:00 +03:00
|
|
|
|
-- First, check for conflicts between non-column fields, since we can raise a better error
|
|
|
|
|
-- message in terms of the two metadata objects that define them.
|
2021-07-12 19:03:36 +03:00
|
|
|
|
(align relationshipFields computedFieldFields >- returnA)
|
|
|
|
|
>-> (| Inc.keyed (\fieldName fields -> (fieldName, fields) >- noFieldConflicts FIRelationship FIComputedField) |)
|
2020-05-27 18:02:58 +03:00
|
|
|
|
-- Second, align with remote relationship fields
|
2022-07-29 17:52:02 +03:00
|
|
|
|
>-> (\fields -> align (catMaybes fields) remoteRelationshipFields >- returnA)
|
2021-07-23 02:06:10 +03:00
|
|
|
|
>-> (| Inc.keyed (\fieldName fields -> (fieldName, fields) >- noFieldConflicts id FIRemoteRelationship) |)
|
2019-12-13 10:47:28 +03:00
|
|
|
|
-- Next, check for conflicts with custom field names. This is easiest to do before merging with
|
|
|
|
|
-- the column info itself because we have access to the information separately, and custom field
|
|
|
|
|
-- names are not currently stored as a separate map (but maybe should be!).
|
2022-07-29 17:52:02 +03:00
|
|
|
|
>-> (\fields -> (columns, catMaybes fields) >- noCustomFieldConflicts)
|
2019-12-13 10:47:28 +03:00
|
|
|
|
-- Finally, check for conflicts with the columns themselves.
|
2022-07-29 17:52:02 +03:00
|
|
|
|
>-> (\fields -> align columns (catMaybes fields) >- returnA)
|
2019-12-13 10:47:28 +03:00
|
|
|
|
>-> (| Inc.keyed (\_ fields -> fields >- noColumnConflicts) |)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
where
|
2020-05-27 18:02:58 +03:00
|
|
|
|
noFieldConflicts this that = proc (fieldName, fields) -> case fields of
|
|
|
|
|
This (thisField, metadata) -> returnA -< Just (this thisField, metadata)
|
|
|
|
|
That (thatField, metadata) -> returnA -< Just (that thatField, metadata)
|
|
|
|
|
These (_, thisMetadata) (_, thatMetadata) -> do
|
2019-12-09 01:17:39 +03:00
|
|
|
|
tellA
|
|
|
|
|
-<
|
|
|
|
|
Seq.singleton $
|
|
|
|
|
CIInconsistency $
|
|
|
|
|
ConflictingObjects
|
|
|
|
|
("conflicting definitions for field " <>> fieldName)
|
2020-05-27 18:02:58 +03:00
|
|
|
|
[thisMetadata, thatMetadata]
|
2019-12-09 01:17:39 +03:00
|
|
|
|
returnA -< Nothing
|
|
|
|
|
|
2019-12-13 10:47:28 +03:00
|
|
|
|
noCustomFieldConflicts = proc (columns, nonColumnFields) -> do
|
2022-01-19 11:37:50 +03:00
|
|
|
|
let columnsByGQLName = mapFromL ciName $ M.elems columns
|
2019-12-13 10:47:28 +03:00
|
|
|
|
(|
|
|
|
|
|
Inc.keyed
|
|
|
|
|
( \_ (fieldInfo, metadata) ->
|
|
|
|
|
(|
|
|
|
|
|
withRecordInconsistency
|
|
|
|
|
( do
|
|
|
|
|
(|
|
|
|
|
|
traverseA_
|
|
|
|
|
( \fieldGQLName -> case M.lookup fieldGQLName columnsByGQLName of
|
|
|
|
|
-- Only raise an error if the GQL name isn’t the same as the Postgres column name.
|
|
|
|
|
-- If they are the same, `noColumnConflicts` will catch it, and it will produce a
|
|
|
|
|
-- more useful error message.
|
2020-12-17 14:37:16 +03:00
|
|
|
|
Just columnInfo
|
2022-01-19 11:37:50 +03:00
|
|
|
|
| toTxt (ciColumn columnInfo) /= G.unName fieldGQLName ->
|
2019-12-13 10:47:28 +03:00
|
|
|
|
throwA
|
|
|
|
|
-<
|
|
|
|
|
err400 AlreadyExists $
|
|
|
|
|
"field definition conflicts with custom field name for postgres column "
|
2022-01-19 11:37:50 +03:00
|
|
|
|
<>> ciColumn columnInfo
|
2019-12-13 10:47:28 +03:00
|
|
|
|
_ -> returnA -< ()
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
2019-12-13 10:47:28 +03:00
|
|
|
|
|) (fieldInfoGraphQLNames fieldInfo)
|
|
|
|
|
returnA -< (fieldInfo, metadata)
|
|
|
|
|
)
|
|
|
|
|
|) metadata
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
2019-12-13 10:47:28 +03:00
|
|
|
|
|) nonColumnFields
|
|
|
|
|
|
2019-12-09 01:17:39 +03:00
|
|
|
|
noColumnConflicts = proc fields -> case fields of
|
|
|
|
|
This columnInfo -> returnA -< FIColumn columnInfo
|
|
|
|
|
That (fieldInfo, _) -> returnA -< fieldInfo
|
|
|
|
|
These columnInfo (_, fieldMetadata) -> do
|
2021-04-14 20:51:02 +03:00
|
|
|
|
recordInconsistency -< ((Nothing, fieldMetadata), "field definition conflicts with postgres column")
|
2019-12-09 01:17:39 +03:00
|
|
|
|
returnA -< FIColumn columnInfo
|
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
mkRelationshipMetadataObject ::
|
2021-04-22 00:44:37 +03:00
|
|
|
|
forall b a.
|
2021-03-15 16:02:58 +03:00
|
|
|
|
(ToJSON a, Backend b) =>
|
2021-04-22 00:44:37 +03:00
|
|
|
|
RelType ->
|
|
|
|
|
(SourceName, TableName b, RelDef a) ->
|
|
|
|
|
MetadataObject
|
2020-12-28 15:56:00 +03:00
|
|
|
|
mkRelationshipMetadataObject relType (source, table, relDef) =
|
2021-03-15 16:02:58 +03:00
|
|
|
|
let objectId =
|
|
|
|
|
MOSourceObjId source $
|
|
|
|
|
AB.mkAnyBackend $
|
2021-04-22 00:44:37 +03:00
|
|
|
|
SMOTableObj @b table $
|
2021-03-15 16:02:58 +03:00
|
|
|
|
MTORel (_rdName relDef) relType
|
2021-04-22 00:44:37 +03:00
|
|
|
|
in MetadataObject objectId $ toJSON $ WithTable @b source table relDef
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
|
|
|
|
buildObjectRelationship ::
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
Backend b
|
|
|
|
|
) =>
|
|
|
|
|
( HashMap (TableName b) (HashSet (ForeignKey b)),
|
2020-12-28 15:56:00 +03:00
|
|
|
|
( SourceName,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
TableName b,
|
|
|
|
|
ObjRelDef b
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
`arr` Maybe (RelInfo b)
|
server: fix the nullability of object relationships (fix hasura/graphql-engine#7201)
When adding object relationships, we set the nullability of the generated GraphQL field based on whether the database backend enforces that the referenced data always exists. For manual relationships (corresponding to `manual_configuration`), the database backend is unaware of any relationship between data, and hence such fields are always set to be nullable.
For relationships generated from foreign key constraints (corresponding to `foreign_key_constraint_on`), we distinguish between two cases:
1. The "forward" object relationship from a referencing table (i.e. which has the foreign key constraint) to a referenced table. This should be set to be non-nullable when all referencing columns are non-nullable. But in fact, it used to set it to be non-nullable if *any* referencing column is non-nullable, which is only correct in Postgres when `MATCH FULL` is set (a flag we don't consider). This fixes that by changing a boolean conjunction to a disjunction.
2. The "reverse" object relationship from a referenced table to a referencing table which has the foreign key constraint. This should always be set to be nullable. But in fact, it used to always be set to non-nullable, as was reported in hasura/graphql-engine#7201. This fixes that.
Moreover, we have moved the computation of the nullability from `Hasura.RQL.DDL.Relationship` to `Hasura.GraphQL.Schema.Select`: this nullability used to be passed through the `riIsNullable` field of `RelInfo`, but for array relationships this information is not actually used, and moreover the remaining fields of `RelInfo` are already enough to deduce the nullability.
This also adds regression tests for both (1) and (2) above.
https://github.com/hasura/graphql-engine-mono/pull/2159
GitOrigin-RevId: 617f12765614f49746d18d3368f41dfae2f3e6ca
2021-08-26 18:26:43 +03:00
|
|
|
|
buildObjectRelationship = proc (fkeysMap, (source, table, relDef)) -> do
|
|
|
|
|
let buildRelInfo def = objRelP2Setup source table fkeysMap def
|
2022-04-04 15:35:10 +03:00
|
|
|
|
interpretWriter -< buildRelationship source table buildRelInfo ObjRel relDef
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
|
|
|
|
buildArrayRelationship ::
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
Backend b
|
|
|
|
|
) =>
|
|
|
|
|
( HashMap (TableName b) (HashSet (ForeignKey b)),
|
2020-12-28 15:56:00 +03:00
|
|
|
|
( SourceName,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
TableName b,
|
|
|
|
|
ArrRelDef b
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
)
|
2021-02-14 09:07:52 +03:00
|
|
|
|
`arr` Maybe (RelInfo b)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
buildArrayRelationship = proc (fkeysMap, (source, table, relDef)) -> do
|
|
|
|
|
let buildRelInfo def = arrRelP2Setup fkeysMap source table def
|
2022-04-04 15:35:10 +03:00
|
|
|
|
interpretWriter -< buildRelationship source table buildRelInfo ArrRel relDef
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
|
|
|
|
buildRelationship ::
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
forall m b a.
|
|
|
|
|
( MonadWriter (Seq CollectedInfo) m,
|
2020-12-08 17:22:31 +03:00
|
|
|
|
ToJSON a,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
Backend b
|
2020-12-28 15:56:00 +03:00
|
|
|
|
) =>
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
SourceName ->
|
|
|
|
|
TableName b ->
|
|
|
|
|
(RelDef a -> Either QErr (RelInfo b, [SchemaDependency])) ->
|
|
|
|
|
RelType ->
|
|
|
|
|
RelDef a ->
|
|
|
|
|
m (Maybe (RelInfo b))
|
|
|
|
|
buildRelationship source table buildRelInfo relType relDef = do
|
2020-12-08 17:22:31 +03:00
|
|
|
|
let relName = _rdName relDef
|
2021-04-22 00:44:37 +03:00
|
|
|
|
metadataObject = mkRelationshipMetadataObject @b relType (source, table, relDef)
|
2021-03-15 16:02:58 +03:00
|
|
|
|
schemaObject =
|
|
|
|
|
SOSourceObj source $
|
|
|
|
|
AB.mkAnyBackend $
|
2021-04-22 00:44:37 +03:00
|
|
|
|
SOITableObj @b table $
|
2021-03-15 16:02:58 +03:00
|
|
|
|
TORel relName
|
2020-12-08 17:22:31 +03:00
|
|
|
|
addRelationshipContext e = "in relationship " <> relName <<> ": " <> e
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
withRecordInconsistencyM metadataObject $ do
|
|
|
|
|
modifyErr (addTableContext @b table . addRelationshipContext) $ do
|
|
|
|
|
(info, dependencies) <- liftEither $ buildRelInfo relDef
|
|
|
|
|
recordDependenciesM metadataObject schemaObject dependencies
|
|
|
|
|
return info
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
|
mkComputedFieldMetadataObject ::
|
2021-03-15 16:02:58 +03:00
|
|
|
|
forall b.
|
|
|
|
|
(Backend b) =>
|
|
|
|
|
(SourceName, TableName b, ComputedFieldMetadata b) ->
|
|
|
|
|
MetadataObject
|
2020-12-28 15:56:00 +03:00
|
|
|
|
mkComputedFieldMetadataObject (source, table, ComputedFieldMetadata {..}) =
|
2021-03-15 16:02:58 +03:00
|
|
|
|
let objectId =
|
|
|
|
|
MOSourceObjId source $
|
|
|
|
|
AB.mkAnyBackend $
|
2021-04-22 00:44:37 +03:00
|
|
|
|
SMOTableObj @b table $
|
2021-03-15 16:02:58 +03:00
|
|
|
|
MTOComputedField _cfmName
|
2022-05-04 17:52:29 +03:00
|
|
|
|
definition = AddComputedField @b source table _cfmName _cfmDefinition _cfmComment
|
2020-12-08 17:22:31 +03:00
|
|
|
|
in MetadataObject objectId (toJSON definition)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
|
|
|
|
buildComputedField ::
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
forall b m.
|
|
|
|
|
( MonadWriter (Seq CollectedInfo) m,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
BackendMetadata b
|
|
|
|
|
) =>
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
HashSet (TableName b) ->
|
2022-05-25 13:24:41 +03:00
|
|
|
|
HashSet (Column b) ->
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
SourceName ->
|
|
|
|
|
DBFunctionsMetadata b ->
|
|
|
|
|
TableName b ->
|
|
|
|
|
ComputedFieldMetadata b ->
|
|
|
|
|
m (Either QErr (Maybe (ComputedFieldInfo b)))
|
2022-05-25 13:24:41 +03:00
|
|
|
|
buildComputedField trackedTableNames tableColumns source pgFunctions table cf@ComputedFieldMetadata {..} = runExceptT do
|
2020-12-08 17:22:31 +03:00
|
|
|
|
let addComputedFieldContext e = "in computed field " <> _cfmName <<> ": " <> e
|
2022-05-04 17:52:29 +03:00
|
|
|
|
function = computedFieldFunction @b _cfmDefinition
|
2020-12-08 17:22:31 +03:00
|
|
|
|
funcDefs = fromMaybe [] $ M.lookup function pgFunctions
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
withRecordInconsistencyM (mkComputedFieldMetadataObject (source, table, cf)) $
|
|
|
|
|
modifyErr (addTableContext @b table . addComputedFieldContext) $ do
|
2022-05-04 17:52:29 +03:00
|
|
|
|
rawfi <- handleMultipleFunctions @b (computedFieldFunction @b _cfmDefinition) funcDefs
|
2022-05-25 13:24:41 +03:00
|
|
|
|
buildComputedFieldInfo trackedTableNames table tableColumns _cfmName _cfmDefinition rawfi _cfmComment
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
|
|
|
|
mkRemoteRelationshipMetadataObject ::
|
2021-03-15 16:02:58 +03:00
|
|
|
|
forall b.
|
|
|
|
|
Backend b =>
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(SourceName, TableName b, RemoteRelationship) ->
|
2021-03-15 16:02:58 +03:00
|
|
|
|
MetadataObject
|
2021-12-14 09:45:13 +03:00
|
|
|
|
mkRemoteRelationshipMetadataObject (source, table, RemoteRelationship {..}) =
|
2021-03-15 16:02:58 +03:00
|
|
|
|
let objectId =
|
|
|
|
|
MOSourceObjId source $
|
|
|
|
|
AB.mkAnyBackend $
|
2021-04-22 00:44:37 +03:00
|
|
|
|
SMOTableObj @b table $
|
2021-12-01 07:53:34 +03:00
|
|
|
|
MTORemoteRelationship _rrName
|
2021-07-23 02:06:10 +03:00
|
|
|
|
in MetadataObject objectId $
|
|
|
|
|
toJSON $
|
2021-12-14 09:45:13 +03:00
|
|
|
|
CreateFromSourceRelationship @b source table _rrName _rrDefinition
|
2020-05-27 18:02:58 +03:00
|
|
|
|
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
-- | This is a "thin" wrapper around 'buildRemoteFieldInfo', which only knows
|
|
|
|
|
-- how to construct dependencies on the RHS of the join condition, so the
|
|
|
|
|
-- dependencies on the remote relationship on the LHS entity are computed here
|
2020-05-27 18:02:58 +03:00
|
|
|
|
buildRemoteRelationship ::
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
forall b m.
|
|
|
|
|
( MonadWriter (Seq CollectedInfo) m,
|
2021-02-14 09:07:52 +03:00
|
|
|
|
BackendMetadata b
|
2021-07-23 02:06:10 +03:00
|
|
|
|
) =>
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
HashMap SourceName (AB.AnyBackend PartiallyResolvedSource) ->
|
|
|
|
|
M.HashMap FieldName (DBJoinField b) ->
|
scaffolding for remote-schemas module
The main aim of the PR is:
1. To set up a module structure for 'remote-schemas' package.
2. Move parts by the remote schema codebase into the new module structure to validate it.
## Notes to the reviewer
Why a PR with large-ish diff?
1. We've been making progress on the MM project but we don't yet know long it is going to take us to get to the first milestone. To understand this better, we need to figure out the unknowns as soon as possible. Hence I've taken a stab at the first two items in the [end-state](https://gist.github.com/0x777/ca2bdc4284d21c3eec153b51dea255c9) document to figure out the unknowns. Unsurprisingly, there are a bunch of issues that we haven't discussed earlier. These are documented in the 'open questions' section.
1. The diff is large but that is only code moved around and I've added a section that documents how things are moved. In addition, there are fair number of PR comments to help with the review process.
## Changes in the PR
### Module structure
Sets up the module structure as follows:
```
Hasura/
RemoteSchema/
Metadata/
Types.hs
SchemaCache/
Types.hs
Permission.hs
RemoteRelationship.hs
Build.hs
MetadataAPI/
Types.hs
Execute.hs
```
### 1. Types representing metadata are moved
Types that capture metadata information (currently scattered across several RQL modules) are moved into `Hasura.RemoteSchema.Metadata.Types`.
- This new module only depends on very 'core' modules such as
`Hasura.Session` for the notion of roles and `Hasura.Incremental` for `Cacheable` typeclass.
- The requirement on database modules is avoided by generalizing the remote schemas metadata to accept an arbitrary 'r' for a remote relationship
definition.
### 2. SchemaCache related types and build logic have been moved
Types that represent remote schemas information in SchemaCache are moved into `Hasura.RemoteSchema.SchemaCache.Types`.
Similar to `H.RS.Metadata.Types`, this module depends on 'core' modules except for `Hasura.GraphQL.Parser.Variable`. It has something to do with remote relationships but I haven't spent time looking into it. The validation of 'remote relationships to remote schema' is also something that needs to be looked at.
Rips out the logic that builds remote schema's SchemaCache information from the monolithic `buildSchemaCacheRule` and moves it into `Hasura.RemoteSchema.SchemaCache.Build`. Further, the `.SchemaCache.Permission` and `.SchemaCache.RemoteRelationship` have been created from existing modules that capture schema cache building logic for those two components.
This was a fair amount of work. On main, currently remote schema's SchemaCache information is built in two phases - in the first phase, 'permissions' and 'remote relationships' are ignored and in the second phase they are filled in.
While remote relationships can only be resolved after partially resolving sources and other remote schemas, the same isn't true for permissions. Further, most of the work that is done to resolve remote relationships can be moved to the first phase so that the second phase can be a very simple traversal.
This is the approach that was taken - resolve permissions and as much as remote relationships information in the first phase.
### 3. Metadata APIs related types and build logic have been moved
The types that represent remote schema related metadata APIs and the execution logic have been moved to `Hasura.RemoteSchema.MetadataAPI.Types` and `.Execute` modules respectively.
## Open questions:
1. `Hasura.RemoteSchema.Metadata.Types` is so called because I was hoping that all of the metadata related APIs of remote schema can be brought in at `Hasura.RemoteSchema.Metadata.API`. However, as metadata APIs depended on functions from `SchemaCache` module (see [1](https://github.com/hasura/graphql-engine-mono/blob/ceba6d62264603ee5d279814677b29bcc43ecaea/server/src-lib/Hasura/RQL/DDL/RemoteSchema.hs#L55) and [2](https://github.com/hasura/graphql-engine-mono/blob/ceba6d62264603ee5d279814677b29bcc43ecaea/server/src-lib/Hasura/RQL/DDL/RemoteSchema.hs#L91), it made more sense to create a separate top-level module for `MetadataAPI`s.
Maybe we can just have `Hasura.RemoteSchema.Metadata` and get rid of the extra nesting or have `Hasura.RemoteSchema.Metadata.{Core,Permission,RemoteRelationship}` if we want to break them down further.
1. `buildRemoteSchemas` in `H.RS.SchemaCache.Build` has the following type:
```haskell
buildRemoteSchemas ::
( ArrowChoice arr,
Inc.ArrowDistribute arr,
ArrowWriter (Seq CollectedInfo) arr,
Inc.ArrowCache m arr,
MonadIO m,
HasHttpManagerM m,
Inc.Cacheable remoteRelationshipDefinition,
ToJSON remoteRelationshipDefinition,
MonadError QErr m
) =>
Env.Environment ->
( (Inc.Dependency (HashMap RemoteSchemaName Inc.InvalidationKey), OrderedRoles),
[RemoteSchemaMetadataG remoteRelationshipDefinition]
)
`arr` HashMap RemoteSchemaName (PartiallyResolvedRemoteSchemaCtxG remoteRelationshipDefinition, MetadataObject)
```
Note the dependence on `CollectedInfo` which is defined as
```haskell
data CollectedInfo
= CIInconsistency InconsistentMetadata
| CIDependency
MetadataObject
-- ^ for error reporting on missing dependencies
SchemaObjId
SchemaDependency
deriving (Eq)
```
this pretty much means that remote schemas is dependent on types from databases, actions, ....
How do we fix this? Maybe introduce a typeclass such as `ArrowCollectRemoteSchemaDependencies` which is defined in `Hasura.RemoteSchema` and then implemented in graphql-engine?
1. The dependency on `buildSchemaCacheFor` in `.MetadataAPI.Execute` which has the following signature:
```haskell
buildSchemaCacheFor ::
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId ->
MetadataModifier ->
```
This can be easily resolved if we restrict what the metadata APIs are allowed to do. Currently, they operate in an unfettered access to modify SchemaCache (the `CacheRWM` constraint):
```haskell
runAddRemoteSchema ::
( QErrM m,
CacheRWM m,
MonadIO m,
HasHttpManagerM m,
MetadataM m,
Tracing.MonadTrace m
) =>
Env.Environment ->
AddRemoteSchemaQuery ->
m EncJSON
```
This should instead be changed to restrict remote schema APIs to only modify remote schema metadata (but has access to the remote schemas part of the schema cache), this dependency is completely removed.
```haskell
runAddRemoteSchema ::
( QErrM m,
MonadIO m,
HasHttpManagerM m,
MonadReader RemoteSchemasSchemaCache m,
MonadState RemoteSchemaMetadata m,
Tracing.MonadTrace m
) =>
Env.Environment ->
AddRemoteSchemaQuery ->
m RemoteSchemeMetadataObjId
```
The idea is that the core graphql-engine would call these functions and then call
`buildSchemaCacheFor`.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6291
GitOrigin-RevId: 51357148c6404afe70219afa71bd1d59bdf4ffc6
2022-10-21 06:13:07 +03:00
|
|
|
|
PartiallyResolvedRemoteSchemaMap ->
|
Avoid `Arrows` by interpreting monads
TL;DR
---
We go from this:
```haskell
(|
withRecordInconsistency
( (|
modifyErrA
( do
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
recordDependencies -< (metadataObject, schemaObject, dependencies)
returnA -< info
)
|) (addTableContext @b table . addRelationshipContext)
)
|) metadataObject
```
to this:
```haskell
withRecordInconsistencyM metadataObject $ do
modifyErr (addTableContext @b table . addRelationshipContext) $ do
(info, dependencies) <- liftEither $ buildRelInfo relDef
recordDependenciesM metadataObject schemaObject dependencies
return info
```
Background
---
We use Haskell's `Arrows` language extension to gain some syntactic sugar when working with `Arrow`s. `Arrow`s are a programming abstraction comparable to `Monad`s.
Unfortunately the syntactic sugar provided by this language extension is not very sweet.
This PR shows how we can sometimes avoid using `Arrow`s altogether, without loss of functionality or correctness. It is a demo of a technique that can be used to cut down the amount of `Arrows`-based code in our codebase by about half.
Approach
---
Although _in general_ not every `Monad` is an `Arrow`, specific `Arrow` instantiations are exactly as powerful as their `Monad` equivalents. Otherwise they wouldn't be very equivalent, would they?
Just like `liftEither` interprets the `Either e` monad into an arbitrary monad implementing `MonadError e`, we add `interpA` which interprets certain concrete monads such as `Writer w` into specific arrows, e.g. ones satisfying `ArrowWriter w`. This means that the part of the code that only uses such interpretable effects can be written _monadically_, and then used in _arrow_ constructions down the line.
This approach cannot be used for arrow effects which do not have a monadic equivalent. In our codebase, the only instance of this is `ArrowCache m`, implemented by the `Rule m` arrow. So code written with `ArrowCache m` in the context cannot be rewritten monadically using this technique.
See also
---
- #1827
- #2210
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3543
Co-authored-by: jkachmar <8461423+jkachmar@users.noreply.github.com>
GitOrigin-RevId: eb79619c95f7a571bce99bc144ce42ee65d08505
2022-02-22 21:08:54 +03:00
|
|
|
|
(SourceName, TableName b, RemoteRelationship) ->
|
|
|
|
|
m (Either QErr (Maybe (RemoteFieldInfo (DBJoinField b))))
|
|
|
|
|
buildRemoteRelationship allSources allColumns remoteSchemaMap (source, table, rr@RemoteRelationship {..}) = runExceptT $ do
|
|
|
|
|
let metadataObject = mkRemoteRelationshipMetadataObject @b (source, table, rr)
|
|
|
|
|
schemaObj =
|
|
|
|
|
SOSourceObj source $
|
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
|
SOITableObj @b table $
|
|
|
|
|
TORemoteRel _rrName
|
|
|
|
|
addRemoteRelationshipContext e = "in remote relationship" <> _rrName <<> ": " <> e
|
|
|
|
|
withRecordInconsistencyM metadataObject $
|
|
|
|
|
modifyErr (addTableContext @b table . addRemoteRelationshipContext) $ do
|
|
|
|
|
(remoteField, rhsDependencies) <-
|
|
|
|
|
buildRemoteFieldInfo (tableNameToLHSIdentifier @b table) allColumns rr allSources remoteSchemaMap
|
|
|
|
|
let lhsDependencies =
|
|
|
|
|
-- a direct dependency on the table on which this is defined
|
|
|
|
|
SchemaDependency (SOSourceObj source $ AB.mkAnyBackend $ SOITable @b table) DRTable
|
|
|
|
|
-- the relationship is also dependent on all the lhs
|
|
|
|
|
-- columns that are used in the join condition
|
|
|
|
|
: flip map (M.elems $ _rfiLHS remoteField) \case
|
|
|
|
|
JoinColumn column _ ->
|
|
|
|
|
-- TODO: shouldn't this be DRColumn??
|
|
|
|
|
mkColDep @b DRRemoteRelationship source table column
|
|
|
|
|
JoinComputedField computedFieldInfo ->
|
|
|
|
|
mkComputedFieldDep @b DRRemoteRelationship source table $ _scfName computedFieldInfo
|
|
|
|
|
-- Here is the essence of the function: construct dependencies on the RHS
|
|
|
|
|
-- of the join condition.
|
|
|
|
|
recordDependenciesM metadataObject schemaObj (lhsDependencies <> rhsDependencies)
|
|
|
|
|
return remoteField
|