Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
ProjectM36.IsomorphicSchema
Synopsis
- data SchemaExpr
- isomorphs :: Schema -> SchemaIsomorphs
- validateSchema :: Schema -> DatabaseContext -> Maybe SchemaError
- invert :: SchemaIsomorph -> SchemaIsomorph
- isomorphInRelVarNames :: SchemaIsomorph -> [RelVarName]
- isomorphsInRelVarNames :: SchemaIsomorphs -> Set RelVarName
- isomorphOutRelVarNames :: SchemaIsomorph -> [RelVarName]
- isomorphsOutRelVarNames :: SchemaIsomorphs -> Set RelVarName
- validateRelationalExprInSchema :: Schema -> RelationalExpr -> Either RelationalError ()
- processRelationalExprInSchema :: Schema -> RelationalExpr -> Either RelationalError RelationalExpr
- validateDatabaseContextExprInSchema :: Schema -> DatabaseContextExpr -> Either RelationalError ()
- processDatabaseContextExprInSchema :: Schema -> DatabaseContextExpr -> Either RelationalError DatabaseContextExpr
- processDatabaseContextExprSchemaUpdate :: Schema -> DatabaseContextExpr -> Schema
- processDatabaseContextExprSchemasUpdate :: Subschemas -> DatabaseContextExpr -> Subschemas
- relExprMorph :: SchemaIsomorph -> RelationalExpr -> Either RelationalError RelationalExpr
- relExprMogrify :: (RelationalExprBase a -> Either RelationalError (RelationalExprBase a)) -> RelationalExprBase a -> Either RelationalError (RelationalExprBase a)
- databaseContextExprMorph :: SchemaIsomorph -> (RelationalExpr -> Either RelationalError RelationalExpr) -> DatabaseContextExpr -> Either RelationalError DatabaseContextExpr
- applyRelationalExprSchemaIsomorphs :: SchemaIsomorphs -> RelationalExpr -> Either RelationalError RelationalExpr
- inclusionDependencyInSchema :: Schema -> InclusionDependency -> Either RelationalError InclusionDependency
- inclusionDependenciesInSchema :: Schema -> InclusionDependencies -> Either RelationalError InclusionDependencies
- relationVariablesInSchema :: Schema -> Either RelationalError RelationVariables
- relationVariablesAsRelationInSchema :: DatabaseContext -> Schema -> TransactionGraph -> Either RelationalError Relation
- createIncDepsForIsomorph :: SchemaName -> SchemaIsomorph -> InclusionDependencies
- evalSchemaExpr :: SchemaExpr -> DatabaseContext -> TransactionId -> TransactionGraph -> Subschemas -> Either RelationalError (Subschemas, DatabaseContext)
- class Morph a where
- morphToSchema :: Schema -> TransactionGraph -> a -> Either RelationalError a
- notificationsAsRelationInSchema :: Notifications -> Schema -> Either RelationalError Relation
- notificationsAsData :: Notifications -> [(Text, RelationalExpr, RelationalExpr, RelationalExpr)]
Documentation
data SchemaExpr Source #
Constructors
AddSubschema SchemaName SchemaIsomorphs | |
RemoveSubschema SchemaName |
Instances
Generic SchemaExpr Source # | |
Defined in ProjectM36.IsomorphicSchema | |
Show SchemaExpr Source # | |
Defined in ProjectM36.IsomorphicSchema | |
Serialise SchemaExpr Source # | |
Defined in ProjectM36.Serialise.IsomorphicSchema Methods schemaGen :: Proxy SchemaExpr -> SchemaGen Schema Source # toBuilder :: SchemaExpr -> Builder Source # extractor :: Extractor SchemaExpr Source # | |
type Rep SchemaExpr Source # | |
Defined in ProjectM36.IsomorphicSchema type Rep SchemaExpr = D1 ('MetaData "SchemaExpr" "ProjectM36.IsomorphicSchema" "project-m36-1.1.1-inplace" 'False) (C1 ('MetaCons "AddSubschema" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SchemaName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SchemaIsomorphs)) :+: C1 ('MetaCons "RemoveSubschema" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SchemaName))) |
isomorphs :: Schema -> SchemaIsomorphs Source #
validateSchema :: Schema -> DatabaseContext -> Maybe SchemaError Source #
Return an error if the schema is not isomorphic to the base database context. A schema is fully isomorphic iff all relvars in the base context are in the "out" relvars, but only once. TODO: add relvar must appear exactly once constraint
isomorphsInRelVarNames :: SchemaIsomorphs -> Set RelVarName Source #
Relation variables names represented in the virtual schema space. Useful for determining if a relvar name is valid in the schema.
validateRelationalExprInSchema :: Schema -> RelationalExpr -> Either RelationalError () Source #
Check that all mentioned relvars are actually present in the current schema.
processRelationalExprInSchema :: Schema -> RelationalExpr -> Either RelationalError RelationalExpr Source #
validateDatabaseContextExprInSchema :: Schema -> DatabaseContextExpr -> Either RelationalError () Source #
processDatabaseContextExprInSchema :: Schema -> DatabaseContextExpr -> Either RelationalError DatabaseContextExpr Source #
processDatabaseContextExprSchemaUpdate :: Schema -> DatabaseContextExpr -> Schema Source #
If the database context expression adds or removes a relvar, we need to update the isomorphs to create a passthrough Isomorph.
relExprMorph :: SchemaIsomorph -> RelationalExpr -> Either RelationalError RelationalExpr Source #
Morph a relational expression in one schema to another isomorphic schema.
Returns a function which can be used to morph a GraphRefRelationalExpr
. Here, we naively apply the morphs in the current context ignoring past contexts because:
* the current schema may not exist in past
* this function should only be used for showing DDL, not for expression evaluation.
* if a schema were renamed, then the path to past isomorphisms in the transaction graph tree would be lost.
relExprMogrify :: (RelationalExprBase a -> Either RelationalError (RelationalExprBase a)) -> RelationalExprBase a -> Either RelationalError (RelationalExprBase a) Source #
databaseContextExprMorph :: SchemaIsomorph -> (RelationalExpr -> Either RelationalError RelationalExpr) -> DatabaseContextExpr -> Either RelationalError DatabaseContextExpr Source #
applyRelationalExprSchemaIsomorphs :: SchemaIsomorphs -> RelationalExpr -> Either RelationalError RelationalExpr Source #
Apply the isomorphism transformations to the relational expression to convert the relational expression from operating on one schema to a disparate, isomorphic schema.
inclusionDependencyInSchema :: Schema -> InclusionDependency -> Either RelationalError InclusionDependency Source #
inclusionDependenciesInSchema :: Schema -> InclusionDependencies -> Either RelationalError InclusionDependencies Source #
relationVariablesAsRelationInSchema :: DatabaseContext -> Schema -> TransactionGraph -> Either RelationalError Relation Source #
Show metadata about the relation variables in the isomorphic schema.
createIncDepsForIsomorph :: SchemaName -> SchemaIsomorph -> InclusionDependencies Source #
Create inclusion dependencies mainly for IsoRestrict because the predicate should hold in the base schema.
evalSchemaExpr :: SchemaExpr -> DatabaseContext -> TransactionId -> TransactionGraph -> Subschemas -> Either RelationalError (Subschemas, DatabaseContext) Source #
Apply SchemaIsomorphs to database context data.
Methods
morphToSchema :: Schema -> TransactionGraph -> a -> Either RelationalError a Source #
Instances
Morph InclusionDependencies Source # | |
Defined in ProjectM36.IsomorphicSchema Methods morphToSchema :: Schema -> TransactionGraph -> InclusionDependencies -> Either RelationalError InclusionDependencies Source # | |
Morph InclusionDependency Source # | The names of inclusion dependencies might leak context about a different schema, but that's arbitrary and cannot be altered without having the user provide a renaming function or a new set of incDep names- seems extraneous. |
Defined in ProjectM36.IsomorphicSchema Methods morphToSchema :: Schema -> TransactionGraph -> InclusionDependency -> Either RelationalError InclusionDependency Source # | |
Morph RelationalExpr Source # | |
Defined in ProjectM36.IsomorphicSchema Methods morphToSchema :: Schema -> TransactionGraph -> RelationalExpr -> Either RelationalError RelationalExpr Source # |