module ProjectM36.AttributeNames where
import qualified ProjectM36.Attribute as A
import ProjectM36.Base
import ProjectM36.Error
import qualified Data.Set as S
empty :: AttributeNames
empty = AttributeNames S.empty
all :: AttributeNames
all = InvertedAttributeNames S.empty
projectionAttributesForAttributeNames :: Attributes -> AttributeNames -> Either RelationalError Attributes
projectionAttributesForAttributeNames attrs (AttributeNames attrNameSet) = do
let nonExistentAttributeNames = A.attributeNamesNotContained attrNameSet (A.attributeNameSet attrs)
if not $ S.null nonExistentAttributeNames then
Left $ AttributeNamesMismatchError nonExistentAttributeNames
else
return $ A.attributesForNames attrNameSet attrs
projectionAttributesForAttributeNames attrs (InvertedAttributeNames unselectedAttrNameSet) = do
let nonExistentAttributeNames = A.attributeNamesNotContained unselectedAttrNameSet (A.attributeNameSet attrs)
if not $ S.null nonExistentAttributeNames then
Left $ AttributeNamesMismatchError nonExistentAttributeNames
else
return $ A.attributesForNames (A.nonMatchingAttributeNameSet unselectedAttrNameSet (A.attributeNameSet attrs)) attrs
projectionAttributesForAttributeNames attrs (UnionAttributeNames namesA namesB) = do
attrsA <- projectionAttributesForAttributeNames attrs namesA
attrsB <- projectionAttributesForAttributeNames attrs namesB
pure (A.union attrsA attrsB)
projectionAttributesForAttributeNames attrs (IntersectAttributeNames namesA namesB) = A.intersection <$> projectionAttributesForAttributeNames attrs namesA <*> projectionAttributesForAttributeNames attrs namesB
invertAttributeNames :: AttributeNames -> AttributeNames
invertAttributeNames (AttributeNames names) = InvertedAttributeNames names
invertAttributeNames (InvertedAttributeNames names) = AttributeNames names
invertAttributeNames (UnionAttributeNames namesA namesB) = IntersectAttributeNames (invertAttributeNames namesA) (invertAttributeNames namesB)
invertAttributeNames (IntersectAttributeNames namesA namesB) = UnionAttributeNames (invertAttributeNames namesA) (invertAttributeNames namesB)