2019-12-09 01:17:39 +03:00
|
|
|
|
{-# LANGUAGE Arrows #-}
|
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
module Hasura.RQL.DDL.Schema.Cache.Fields (addNonColumnFields) where
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
import Control.Arrow.Extended
|
|
|
|
|
import Control.Lens ((^.), _3, _4)
|
|
|
|
|
import Data.Aeson
|
|
|
|
|
import Data.Align (align)
|
|
|
|
|
import Data.HashMap.Strict.Extended qualified as M
|
|
|
|
|
import Data.HashSet qualified as HS
|
|
|
|
|
import Data.Sequence qualified as Seq
|
|
|
|
|
import Data.Text.Extended
|
|
|
|
|
import Data.These (These (..))
|
|
|
|
|
import Hasura.Base.Error
|
|
|
|
|
import Hasura.Incremental qualified as Inc
|
|
|
|
|
import Hasura.Prelude
|
|
|
|
|
import Hasura.RQL.DDL.ComputedField
|
|
|
|
|
import Hasura.RQL.DDL.Relationship
|
|
|
|
|
import Hasura.RQL.DDL.RemoteRelationship
|
|
|
|
|
import Hasura.RQL.DDL.Schema.Cache.Common
|
|
|
|
|
import Hasura.RQL.DDL.Schema.Function
|
|
|
|
|
import Hasura.RQL.Types
|
|
|
|
|
import Hasura.SQL.AnyBackend qualified as AB
|
|
|
|
|
import Language.GraphQL.Draft.Syntax qualified as G
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
addNonColumnFields ::
|
|
|
|
|
forall b arr m.
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
Inc.ArrowDistribute arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
ArrowKleisli m arr,
|
|
|
|
|
MonadError QErr m,
|
|
|
|
|
BackendMetadata b
|
|
|
|
|
) =>
|
|
|
|
|
( HashMap SourceName (AB.AnyBackend PartiallyResolvedSource),
|
|
|
|
|
SourceName,
|
|
|
|
|
HashMap (TableName b) (TableCoreInfoG b (ColumnInfo b) (ColumnInfo b)),
|
|
|
|
|
FieldInfoMap (ColumnInfo b),
|
|
|
|
|
RemoteSchemaMap,
|
|
|
|
|
DBFunctionsMetadata b,
|
|
|
|
|
NonColumnTableInputs b
|
|
|
|
|
)
|
|
|
|
|
`arr` FieldInfoMap (FieldInfo b)
|
|
|
|
|
addNonColumnFields =
|
|
|
|
|
proc
|
|
|
|
|
( allSources,
|
|
|
|
|
source,
|
|
|
|
|
rawTableInfo,
|
|
|
|
|
columns,
|
|
|
|
|
remoteSchemaMap,
|
|
|
|
|
pgFunctions,
|
|
|
|
|
NonColumnTableInputs {..}
|
|
|
|
|
)
|
|
|
|
|
-> do
|
|
|
|
|
objectRelationshipInfos <-
|
|
|
|
|
buildInfoMapPreservingMetadata
|
|
|
|
|
(_rdName . (^. _3))
|
|
|
|
|
(\(s, t, c) -> mkRelationshipMetadataObject @b ObjRel (s, t, c))
|
|
|
|
|
buildObjectRelationship
|
|
|
|
|
-<
|
|
|
|
|
(_tciForeignKeys <$> rawTableInfo, map (source,_nctiTable,) _nctiObjectRelationships)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
arrayRelationshipInfos <-
|
|
|
|
|
buildInfoMapPreservingMetadata
|
|
|
|
|
(_rdName . (^. _3))
|
|
|
|
|
(mkRelationshipMetadataObject @b ArrRel)
|
|
|
|
|
buildArrayRelationship
|
|
|
|
|
-<
|
|
|
|
|
(_tciForeignKeys <$> rawTableInfo, map (source,_nctiTable,) _nctiArrayRelationships)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
let relationshipInfos = objectRelationshipInfos <> arrayRelationshipInfos
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
computedFieldInfos <-
|
|
|
|
|
buildInfoMapPreservingMetadata
|
|
|
|
|
(_cfmName . (^. _4))
|
|
|
|
|
(\(s, _, t, c) -> mkComputedFieldMetadataObject (s, t, c))
|
|
|
|
|
buildComputedField
|
|
|
|
|
-<
|
|
|
|
|
(HS.fromList $ M.keys rawTableInfo, map (source,pgFunctions,_nctiTable,) _nctiComputedFields)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
let columnsAndComputedFields =
|
|
|
|
|
let columnFields = columns <&> FIColumn
|
|
|
|
|
computedFields = M.fromList $
|
|
|
|
|
flip map (M.toList computedFieldInfos) $
|
|
|
|
|
\(cfName, (cfInfo, _)) -> (fromComputedField cfName, FIComputedField cfInfo)
|
|
|
|
|
in M.union columnFields computedFields
|
2021-04-22 00:44:37 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
rawRemoteRelationshipInfos <-
|
|
|
|
|
buildInfoMapPreservingMetadata
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(_rrName . (^. _3))
|
2021-09-24 01:56:37 +03:00
|
|
|
|
(mkRemoteRelationshipMetadataObject @b)
|
|
|
|
|
buildRemoteRelationship
|
|
|
|
|
-<
|
|
|
|
|
((allSources, columnsAndComputedFields, remoteSchemaMap), map (source,_nctiTable,) _nctiRemoteRelationships)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
let relationshipFields = mapKeys fromRel relationshipInfos
|
|
|
|
|
computedFieldFields = mapKeys fromComputedField computedFieldInfos
|
|
|
|
|
remoteRelationshipFields = mapKeys fromRemoteRelationship rawRemoteRelationshipInfos
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +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.
|
|
|
|
|
(align relationshipFields computedFieldFields >- returnA)
|
|
|
|
|
>-> (| Inc.keyed (\fieldName fields -> (fieldName, fields) >- noFieldConflicts FIRelationship FIComputedField) |)
|
|
|
|
|
-- Second, align with remote relationship fields
|
|
|
|
|
>-> (\fields -> align (M.catMaybes fields) remoteRelationshipFields >- returnA)
|
|
|
|
|
>-> (| Inc.keyed (\fieldName fields -> (fieldName, fields) >- noFieldConflicts id FIRemoteRelationship) |)
|
|
|
|
|
-- 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!).
|
|
|
|
|
>-> (\fields -> (columns, M.catMaybes fields) >- noCustomFieldConflicts)
|
|
|
|
|
-- Finally, check for conflicts with the columns themselves.
|
|
|
|
|
>-> (\fields -> align columns (M.catMaybes fields) >- returnA)
|
|
|
|
|
>-> (| 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
|
2021-09-24 01:56:37 +03:00
|
|
|
|
tellA
|
|
|
|
|
-<
|
|
|
|
|
Seq.singleton $
|
|
|
|
|
CIInconsistency $
|
|
|
|
|
ConflictingObjects
|
|
|
|
|
("conflicting definitions for field " <>> fieldName)
|
|
|
|
|
[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
|
|
|
|
|
let columnsByGQLName = mapFromL pgiName $ M.elems columns
|
2021-09-24 01:56:37 +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.
|
|
|
|
|
Just columnInfo
|
|
|
|
|
| toTxt (pgiColumn columnInfo) /= G.unName fieldGQLName ->
|
|
|
|
|
throwA
|
|
|
|
|
-<
|
|
|
|
|
err400 AlreadyExists $
|
|
|
|
|
"field definition conflicts with custom field name for postgres column "
|
|
|
|
|
<>> pgiColumn columnInfo
|
|
|
|
|
_ -> returnA -< ()
|
|
|
|
|
)
|
|
|
|
|
|) (fieldInfoGraphQLNames fieldInfo)
|
|
|
|
|
returnA -< (fieldInfo, metadata)
|
|
|
|
|
)
|
|
|
|
|
|) metadata
|
|
|
|
|
)
|
|
|
|
|
|) nonColumnFields
|
2019-12-13 10:47:28 +03:00
|
|
|
|
|
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
|
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
mkRelationshipMetadataObject ::
|
|
|
|
|
forall b a.
|
|
|
|
|
(ToJSON a, Backend b) =>
|
|
|
|
|
RelType ->
|
|
|
|
|
(SourceName, TableName b, RelDef a) ->
|
|
|
|
|
MetadataObject
|
2020-12-28 15:56:00 +03:00
|
|
|
|
mkRelationshipMetadataObject relType (source, table, relDef) =
|
2021-09-24 01:56:37 +03:00
|
|
|
|
let objectId =
|
|
|
|
|
MOSourceObjId source $
|
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
|
SMOTableObj @b table $
|
|
|
|
|
MTORel (_rdName relDef) relType
|
|
|
|
|
in MetadataObject objectId $ toJSON $ WithTable @b source table relDef
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
buildObjectRelationship ::
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
Backend b
|
|
|
|
|
) =>
|
|
|
|
|
( HashMap (TableName b) (HashSet (ForeignKey b)),
|
|
|
|
|
( SourceName,
|
|
|
|
|
TableName b,
|
|
|
|
|
ObjRelDef b
|
|
|
|
|
)
|
|
|
|
|
)
|
|
|
|
|
`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
|
2020-12-28 15:56:00 +03:00
|
|
|
|
buildRelationship -< (source, table, buildRelInfo, ObjRel, relDef)
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
buildArrayRelationship ::
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
Backend b
|
|
|
|
|
) =>
|
|
|
|
|
( HashMap (TableName b) (HashSet (ForeignKey b)),
|
|
|
|
|
( SourceName,
|
|
|
|
|
TableName b,
|
|
|
|
|
ArrRelDef b
|
|
|
|
|
)
|
|
|
|
|
)
|
|
|
|
|
`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
|
|
|
|
|
buildRelationship -< (source, table, buildRelInfo, ArrRel, relDef)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
buildRelationship ::
|
|
|
|
|
forall b arr a.
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
ToJSON a,
|
|
|
|
|
Backend b
|
|
|
|
|
) =>
|
|
|
|
|
( SourceName,
|
|
|
|
|
TableName b,
|
|
|
|
|
RelDef a -> Either QErr (RelInfo b, [SchemaDependency]),
|
|
|
|
|
RelType,
|
|
|
|
|
RelDef a
|
|
|
|
|
)
|
|
|
|
|
`arr` Maybe (RelInfo b)
|
2020-12-28 15:56:00 +03:00
|
|
|
|
buildRelationship = proc (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-09-24 01:56:37 +03:00
|
|
|
|
schemaObject =
|
|
|
|
|
SOSourceObj source $
|
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
|
SOITableObj @b table $
|
|
|
|
|
TORel relName
|
2020-12-08 17:22:31 +03:00
|
|
|
|
addRelationshipContext e = "in relationship " <> relName <<> ": " <> e
|
2021-09-24 01:56:37 +03:00
|
|
|
|
(|
|
|
|
|
|
withRecordInconsistency
|
|
|
|
|
( (|
|
|
|
|
|
modifyErrA
|
|
|
|
|
( do
|
|
|
|
|
(info, dependencies) <- liftEitherA -< buildRelInfo relDef
|
|
|
|
|
recordDependencies -< (metadataObject, schemaObject, dependencies)
|
|
|
|
|
returnA -< info
|
|
|
|
|
)
|
|
|
|
|
|) (addTableContext @b table . addRelationshipContext)
|
|
|
|
|
)
|
|
|
|
|
|) metadataObject
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
mkComputedFieldMetadataObject ::
|
|
|
|
|
forall b.
|
|
|
|
|
(Backend b) =>
|
|
|
|
|
(SourceName, TableName b, ComputedFieldMetadata b) ->
|
|
|
|
|
MetadataObject
|
|
|
|
|
mkComputedFieldMetadataObject (source, table, ComputedFieldMetadata {..}) =
|
|
|
|
|
let objectId =
|
|
|
|
|
MOSourceObjId source $
|
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
|
SMOTableObj @b table $
|
|
|
|
|
MTOComputedField _cfmName
|
2020-12-28 15:56:00 +03:00
|
|
|
|
definition = AddComputedField source table _cfmName _cfmDefinition _cfmComment
|
2021-09-24 01:56:37 +03:00
|
|
|
|
in MetadataObject objectId (toJSON definition)
|
2019-12-09 01:17:39 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
buildComputedField ::
|
|
|
|
|
forall b arr m.
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
ArrowKleisli m arr,
|
|
|
|
|
MonadError QErr m,
|
|
|
|
|
BackendMetadata b
|
|
|
|
|
) =>
|
|
|
|
|
( HashSet (TableName b),
|
|
|
|
|
(SourceName, DBFunctionsMetadata b, TableName b, ComputedFieldMetadata b)
|
|
|
|
|
)
|
|
|
|
|
`arr` Maybe (ComputedFieldInfo b)
|
|
|
|
|
buildComputedField = proc (trackedTableNames, (source, pgFunctions, table, cf@ComputedFieldMetadata {..})) -> do
|
2020-12-08 17:22:31 +03:00
|
|
|
|
let addComputedFieldContext e = "in computed field " <> _cfmName <<> ": " <> e
|
|
|
|
|
function = _cfdFunction _cfmDefinition
|
|
|
|
|
funcDefs = fromMaybe [] $ M.lookup function pgFunctions
|
2021-09-24 01:56:37 +03:00
|
|
|
|
(|
|
|
|
|
|
withRecordInconsistency
|
|
|
|
|
( (|
|
|
|
|
|
modifyErrA
|
|
|
|
|
( do
|
|
|
|
|
rawfi <- bindErrorA -< handleMultipleFunctions @b (_cfdFunction _cfmDefinition) funcDefs
|
|
|
|
|
bindErrorA -< buildComputedFieldInfo trackedTableNames table _cfmName _cfmDefinition rawfi _cfmComment
|
|
|
|
|
)
|
|
|
|
|
|) (addTableContext @b table . addComputedFieldContext)
|
|
|
|
|
)
|
|
|
|
|
|) (mkComputedFieldMetadataObject (source, table, cf))
|
2020-12-08 17:22:31 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
mkRemoteRelationshipMetadataObject ::
|
|
|
|
|
forall b.
|
|
|
|
|
Backend b =>
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(SourceName, TableName b, RemoteRelationship) ->
|
2021-09-24 01:56:37 +03:00
|
|
|
|
MetadataObject
|
2021-12-01 07:53:34 +03:00
|
|
|
|
mkRemoteRelationshipMetadataObject (source, table, rr@RemoteRelationship {..}) =
|
2021-09-24 01:56:37 +03:00
|
|
|
|
let objectId =
|
|
|
|
|
MOSourceObjId source $
|
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
|
SMOTableObj @b table $
|
2021-12-01 07:53:34 +03:00
|
|
|
|
MTORemoteRelationship _rrName
|
2021-09-24 01:56:37 +03:00
|
|
|
|
in MetadataObject objectId $
|
|
|
|
|
toJSON $
|
2021-12-01 07:53:34 +03:00
|
|
|
|
CreateFromSourceRelationship @b source table rr
|
2020-05-27 18:02:58 +03:00
|
|
|
|
|
2021-09-24 01:56:37 +03:00
|
|
|
|
buildRemoteRelationship ::
|
|
|
|
|
forall b arr m.
|
|
|
|
|
( ArrowChoice arr,
|
|
|
|
|
ArrowWriter (Seq CollectedInfo) arr,
|
|
|
|
|
ArrowKleisli m arr,
|
|
|
|
|
MonadError QErr m,
|
|
|
|
|
BackendMetadata b
|
|
|
|
|
) =>
|
|
|
|
|
( (HashMap SourceName (AB.AnyBackend PartiallyResolvedSource), FieldInfoMap (FieldInfo b), RemoteSchemaMap),
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(SourceName, TableName b, RemoteRelationship)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
|
|
|
|
`arr` Maybe (RemoteFieldInfo b)
|
|
|
|
|
buildRemoteRelationship =
|
|
|
|
|
proc
|
|
|
|
|
( (allSources, allColumns, remoteSchemaMap),
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(source, table, rr@RemoteRelationship {..})
|
2021-09-24 01:56:37 +03:00
|
|
|
|
)
|
|
|
|
|
-> do
|
2021-12-01 07:53:34 +03:00
|
|
|
|
let metadataObject = mkRemoteRelationshipMetadataObject @b (source, table, rr)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
schemaObj =
|
|
|
|
|
SOSourceObj source $
|
|
|
|
|
AB.mkAnyBackend $
|
|
|
|
|
SOITableObj @b table $
|
2021-12-01 07:53:34 +03:00
|
|
|
|
TORemoteRel _rrName
|
|
|
|
|
addRemoteRelationshipContext e = "in remote relationship" <> _rrName <<> ": " <> e
|
2021-09-24 01:56:37 +03:00
|
|
|
|
(|
|
|
|
|
|
withRecordInconsistency
|
|
|
|
|
( (|
|
|
|
|
|
modifyErrA
|
|
|
|
|
( do
|
2021-12-01 07:53:34 +03:00
|
|
|
|
(remoteField, dependencies) <- bindErrorA -< buildRemoteFieldInfo source table allColumns rr allSources remoteSchemaMap
|
2021-09-24 01:56:37 +03:00
|
|
|
|
recordDependencies -< (metadataObject, schemaObj, dependencies)
|
|
|
|
|
returnA -< remoteField
|
|
|
|
|
)
|
|
|
|
|
|) (addTableContext @b table . addRemoteRelationshipContext)
|
|
|
|
|
)
|
|
|
|
|
|) metadataObject
|