module ProjectM36.Key where
import ProjectM36.Base
import ProjectM36.Relation
import qualified Data.Set as S
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
inclusionDependencyForKey :: AttributeNames -> RelationalExpr -> InclusionDependency
inclusionDependencyForKey attrNames relExpr =
InclusionDependency equalityExpr (ExistingRelation relationFalse)
where
projectedOnKeys = Project attrNames
exprAsSubRelation expr = Extend (AttributeExtendTupleExpr "a" (RelationAtomExpr expr)) (ExistingRelation relationTrue)
exprCount expr = projectionForCount (Extend (AttributeExtendTupleExpr "b" (FunctionAtomExpr "count" [AttributeAtomExpr "a"] () )) (exprAsSubRelation expr))
projectionForCount = Project (AttributeNames $ S.fromList ["b"])
equalityExpr = NotEquals (exprCount relExpr) (exprCount (projectedOnKeys relExpr))
databaseContextExprForUniqueKey :: RelVarName -> [AttributeName] -> DatabaseContextExpr
databaseContextExprForUniqueKey rvName attrNames = AddInclusionDependency (rvName <> "_key") $ inclusionDependencyForKey (AttributeNames (S.fromList attrNames)) (RelationVariable rvName ())
databaseContextExprForForeignKey :: IncDepName -> (RelVarName, [AttributeName]) -> (RelVarName, [AttributeName]) -> DatabaseContextExpr
databaseContextExprForForeignKey fkName infoA infoB =
AddInclusionDependency fkName (inclusionDependencyForForeignKey infoA infoB)
inclusionDependencyForForeignKey :: (RelVarName, [AttributeName]) -> (RelVarName, [AttributeName]) -> InclusionDependency
inclusionDependencyForForeignKey (rvA, attrsA) (rvB, attrsB) =
InclusionDependency (
renameIfNecessary attrsB attrsA (Project (attrsL attrsA)
(RelationVariable rvA ()))) (
Project (attrsL attrsB) (RelationVariable rvB ()))
where
attrsL = AttributeNames . S.fromList
renameIfNecessary attrsExpected attrsExisting expr = foldr folder expr (zip attrsExpected attrsExisting)
folder (attrExpected, attrExisting) expr = if attrExpected == attrExisting then
expr
else
Rename attrExisting attrExpected expr
isForeignKeyFor :: InclusionDependency -> (RelVarName, [AttributeName]) -> (RelVarName, [AttributeName]) -> Bool
isForeignKeyFor incDep infoA infoB = incDep == checkIncDep
where
checkIncDep = inclusionDependencyForForeignKey infoA infoB