{-# LANGUAGE GADTs,ExistentialQuantification #-}
module ProjectM36.Relation where
import qualified Data.Set as S
import qualified Data.HashSet as HS
import Control.Monad
import qualified Data.Vector as V
import qualified Data.Map as M
import ProjectM36.AtomType
import ProjectM36.Base
import ProjectM36.Tuple
import qualified ProjectM36.Attribute as A
import ProjectM36.TupleSet
import ProjectM36.Error
import ProjectM36.MiscUtils
import qualified ProjectM36.TypeConstructorDef as TCD
import qualified ProjectM36.DataConstructorDef as DCD
import qualified Data.Text as T
import Data.Either (isRight)
import System.Random.Shuffle
import Control.Monad.Random
import Data.List (sort)
attributes :: Relation -> Attributes
attributes (Relation attrs _ ) = attrs
attributeNames :: Relation -> S.Set AttributeName
attributeNames (Relation attrs _) = A.attributeNameSet attrs
attributeForName :: AttributeName -> Relation -> Either RelationalError Attribute
attributeForName attrName (Relation attrs _) = A.attributeForName attrName attrs
attributesForNames :: S.Set AttributeName -> Relation -> Attributes
attributesForNames attrNameSet (Relation attrs _) = A.attributesForNames attrNameSet attrs
atomTypeForName :: AttributeName -> Relation -> Either RelationalError AtomType
atomTypeForName attrName (Relation attrs _) = A.atomTypeForAttributeName attrName attrs
mkRelationFromList :: Attributes -> [[Atom]] -> Either RelationalError Relation
mkRelationFromList attrs atomMatrix =
Relation attrs <$> mkTupleSetFromList attrs atomMatrix
emptyRelationWithAttrs :: Attributes -> Relation
emptyRelationWithAttrs attrs = Relation attrs emptyTupleSet
mkRelation :: Attributes -> RelationTupleSet -> Either RelationalError Relation
mkRelation attrs tupleSet =
let duplicateAttrNames = dupes (sort (map A.attributeName (V.toList attrs))) in
if not (null duplicateAttrNames) then
Left (DuplicateAttributeNamesError (S.fromList duplicateAttrNames))
else
case verifyTupleSet attrs tupleSet of
Left err -> Left err
Right verifiedTupleSet -> return $ Relation attrs verifiedTupleSet
mkRelationDeferVerify :: Attributes -> RelationTupleSet -> Either RelationalError Relation
mkRelationDeferVerify attrs tupleSet = return $ Relation attrs (RelationTupleSet (filter tupleFilter (asList tupleSet)))
where
tupleFilter tuple = isRight (verifyTuple attrs tuple)
relationWithEmptyTupleSet :: Relation -> Relation
relationWithEmptyTupleSet (Relation attrs _) = emptyRelationWithAttrs attrs
mkRelationFromTuples :: Attributes -> [RelationTuple] -> Either RelationalError Relation
mkRelationFromTuples attrs tupleSetList = do
tupSet <- mkTupleSet attrs tupleSetList
mkRelation attrs tupSet
relationTrue :: Relation
relationTrue = Relation A.emptyAttributes singletonTupleSet
relationFalse :: Relation
relationFalse = Relation A.emptyAttributes emptyTupleSet
singletonTuple :: Relation -> Maybe RelationTuple
singletonTuple rel@(Relation _ tupleSet) = if cardinality rel == Finite 1 then
Just $ head $ asList tupleSet
else
Nothing
union :: Relation -> Relation -> Either RelationalError Relation
union (Relation attrs1 tupSet1) (Relation attrs2 tupSet2) =
if not (A.attributesEqual attrs1 attrs2)
then Left $ AttributeNamesMismatchError (A.attributeNameSet (A.attributesDifference attrs1 attrs2))
else
Right $ Relation attrs1 newtuples
where
newtuples = RelationTupleSet $ HS.toList . HS.fromList $ asList tupSet1 ++ map (reorderTuple attrs1) (asList tupSet2)
project :: S.Set AttributeName -> Relation -> Either RelationalError Relation
project attrNames rel@(Relation _ tupSet) = do
newAttrs <- A.projectionAttributesForNames attrNames (attributes rel)
let newAttrNameSet = A.attributeNameSet newAttrs
newTupleList = map (tupleProject newAttrNameSet) (asList tupSet)
pure (Relation newAttrs (RelationTupleSet (HS.toList (HS.fromList newTupleList))))
rename :: AttributeName -> AttributeName -> Relation -> Either RelationalError Relation
rename oldAttrName newAttrName rel@(Relation oldAttrs oldTupSet)
| not attributeValid = Left $ AttributeNamesMismatchError (S.singleton oldAttrName)
| newAttributeInUse = Left $ AttributeNameInUseError newAttrName
| otherwise = mkRelation newAttrs newTupSet
where
newAttributeInUse = A.attributeNamesContained (S.singleton newAttrName) (attributeNames rel)
attributeValid = A.attributeNamesContained (S.singleton oldAttrName) (attributeNames rel)
newAttrs = A.renameAttributes oldAttrName newAttrName oldAttrs
newTupSet = RelationTupleSet $ map tupsetmapper (asList oldTupSet)
tupsetmapper = tupleRenameAttribute oldAttrName newAttrName
arity :: Relation -> Int
arity (Relation attrs _) = A.arity attrs
degree :: Relation -> Int
degree = arity
cardinality :: Relation -> RelationCardinality
cardinality (Relation _ tupSet) = Finite (length (asList tupSet))
group :: S.Set AttributeName -> AttributeName -> Relation -> Either RelationalError Relation
group groupAttrNames newAttrName rel = do
let nonGroupAttrNames = A.nonMatchingAttributeNameSet groupAttrNames (S.fromList (V.toList (A.attributeNames (attributes rel))))
nonGroupProjectionAttributes <- A.projectionAttributesForNames nonGroupAttrNames (attributes rel)
groupProjectionAttributes <- A.projectionAttributesForNames groupAttrNames (attributes rel)
let groupAttr = Attribute newAttrName (RelationAtomType groupProjectionAttributes)
matchingRelTuple tupIn = case imageRelationFor tupIn rel of
Right rel2 -> RelationTuple (V.singleton groupAttr) (V.singleton (RelationAtom rel2))
Left _ -> undefined
mogrifier tupIn = pure (tupleExtend tupIn (matchingRelTuple tupIn))
newAttrs = A.addAttribute groupAttr nonGroupProjectionAttributes
nonGroupProjection <- project nonGroupAttrNames rel
relMogrify mogrifier newAttrs nonGroupProjection
restrictEq :: RelationTuple -> Relation -> Either RelationalError Relation
restrictEq tuple = restrict rfilter
where
rfilter :: RelationTuple -> Either RelationalError Bool
rfilter tupleIn = pure (tupleIntersection tuple tupleIn == tuple)
ungroup :: AttributeName -> Relation -> Either RelationalError Relation
ungroup relvalAttrName rel = case attributesForRelval relvalAttrName rel of
Left err -> Left err
Right relvalAttrs -> relFold relFolder (Right $ Relation newAttrs emptyTupleSet) rel
where
newAttrs = A.addAttributes relvalAttrs nonGroupAttrs
nonGroupAttrs = A.deleteAttributeName relvalAttrName (attributes rel)
relFolder :: RelationTuple -> Either RelationalError Relation -> Either RelationalError Relation
relFolder tupleIn acc = case acc of
Left err -> Left err
Right accRel -> do
ungrouped <- tupleUngroup relvalAttrName newAttrs tupleIn
accRel `union` ungrouped
tupleUngroup :: AttributeName -> Attributes -> RelationTuple -> Either RelationalError Relation
tupleUngroup relvalAttrName newAttrs tuple = do
relvalRelation <- relationForAttributeName relvalAttrName tuple
relFold folder (Right $ Relation newAttrs emptyTupleSet) relvalRelation
where
nonGroupTupleProjection = tupleProject nonGroupAttrNames tuple
nonGroupAttrNames = A.attributeNameSet newAttrs
folder tupleIn acc = case acc of
Left err -> Left err
Right accRel -> union accRel $ Relation newAttrs (RelationTupleSet [tupleExtend nonGroupTupleProjection tupleIn])
attributesForRelval :: AttributeName -> Relation -> Either RelationalError Attributes
attributesForRelval relvalAttrName (Relation attrs _) = do
atomType <- A.atomTypeForAttributeName relvalAttrName attrs
case atomType of
(RelationAtomType relAttrs) -> Right relAttrs
_ -> Left $ AttributeIsNotRelationValuedError relvalAttrName
type RestrictionFilter = RelationTuple -> Either RelationalError Bool
restrict :: RestrictionFilter -> Relation -> Either RelationalError Relation
restrict rfilter (Relation attrs tupset) = do
tuples <- filterM rfilter (asList tupset)
Right $ Relation attrs (RelationTupleSet tuples)
join :: Relation -> Relation -> Either RelationalError Relation
join (Relation attrs1 tupSet1) (Relation attrs2 tupSet2) = do
newAttrs <- A.joinAttributes attrs1 attrs2
let tupleSetJoiner accumulator tuple1 = do
joinedTupSet <- singleTupleSetJoin newAttrs tuple1 tupSet2
return $ joinedTupSet ++ accumulator
newTupSetList <- foldM tupleSetJoiner [] (asList tupSet1)
Relation newAttrs <$> mkTupleSet newAttrs newTupSetList
difference :: Relation -> Relation -> Either RelationalError Relation
difference relA relB =
if not (A.attributesEqual (attributes relA) (attributes relB))
then
Left $ AttributeNamesMismatchError (A.attributeNameSet (A.attributesDifference attrsA attrsB))
else
restrict rfilter relA
where
attrsA = attributes relA
attrsB = attributes relB
rfilter tupInA = relFold (\tupInB acc -> if acc == Right False then pure False else pure (tupInB /= tupInA)) (Right True) relB
relMap :: (RelationTuple -> Either RelationalError RelationTuple) -> Relation -> Either RelationalError Relation
relMap mapper (Relation attrs tupleSet) =
case forM (asList tupleSet) typeMapCheck of
Right remappedTupleSet -> mkRelation attrs (RelationTupleSet remappedTupleSet)
Left err -> Left err
where
typeMapCheck tupleIn = do
remappedTuple <- mapper tupleIn
if tupleAttributes remappedTuple == tupleAttributes tupleIn
then Right remappedTuple
else Left (TupleAttributeTypeMismatchError (A.attributesDifference (tupleAttributes tupleIn) attrs))
relMogrify :: (RelationTuple -> Either RelationalError RelationTuple) -> Attributes -> Relation -> Either RelationalError Relation
relMogrify mapper newAttributes (Relation _ tupSet) = do
newTuples <- mapM mapper (asList tupSet)
mkRelationFromTuples newAttributes newTuples
relFold :: (RelationTuple -> a -> a) -> a -> Relation -> a
relFold folder acc (Relation _ tupleSet) = foldr folder acc (asList tupleSet)
toList :: Relation -> IO [RelationTuple]
toList rel = do
gen <- newStdGen
let rel' = evalRand (randomizeTupleOrder rel) gen
pure (relFold (:) [] rel')
imageRelationFor :: RelationTuple -> Relation -> Either RelationalError Relation
imageRelationFor matchTuple rel = do
restricted <- restrictEq matchTuple rel
let projectionAttrNames = A.nonMatchingAttributeNameSet (attributeNames rel) (tupleAttributeNameSet matchTuple)
project projectionAttrNames restricted
typesAsRelation :: TypeConstructorMapping -> Either RelationalError Relation
typesAsRelation types = mkRelationFromTuples attrs tuples
where
attrs = A.attributesFromList [Attribute "TypeConstructor" TextAtomType,
Attribute "DataConstructors" dConsType]
subAttrs = A.attributesFromList [Attribute "DataConstructor" TextAtomType]
dConsType = RelationAtomType subAttrs
tuples = map mkTypeConsDescription types
mkTypeConsDescription (tCons, dConsList) = RelationTuple attrs (V.fromList [TextAtom (TCD.name tCons), mkDataConsRelation dConsList])
mkDataConsRelation dConsList = case mkRelationFromTuples subAttrs $ map (\dCons -> RelationTuple subAttrs (V.singleton $ TextAtom $ T.intercalate " " (DCD.name dCons:map (T.pack . show) (DCD.fields dCons)))) dConsList of
Left err -> error ("mkRelationFromTuples pooped " ++ show err)
Right rel -> RelationAtom rel
relationVariablesAsRelation :: M.Map RelVarName Relation -> Either RelationalError Relation
relationVariablesAsRelation relVarMap = mkRelationFromList attrs tups
where
subrelAttrs = A.attributesFromList [Attribute "attribute" TextAtomType, Attribute "type" TextAtomType]
attrs = A.attributesFromList [Attribute "name" TextAtomType,
Attribute "attributes" (RelationAtomType subrelAttrs)]
tups = map relVarToAtomList (M.toList relVarMap)
relVarToAtomList (rvName, rel) = [TextAtom rvName, attributesToRel (attributes rel)]
attributesToRel attrl = case mkRelationFromList subrelAttrs (map attrAtoms (V.toList attrl)) of
Left err -> error ("relationVariablesAsRelation pooped " ++ show err)
Right rel -> RelationAtom rel
attrAtoms a = [TextAtom (A.attributeName a), TextAtom (prettyAtomType (A.atomType a))]
randomizeTupleOrder :: MonadRandom m => Relation -> m Relation
randomizeTupleOrder (Relation attrs tupSet) =
Relation attrs . RelationTupleSet <$> shuffleM (asList tupSet)
oneTuple :: Relation -> Maybe RelationTuple
oneTuple (Relation _ (RelationTupleSet [])) = Nothing
oneTuple (Relation _ (RelationTupleSet (x:_))) = Just x
tuplesList :: Relation -> [RelationTuple]
tuplesList (Relation _ tupleSet) = asList tupleSet