module ProjectM36.TupleSet where
import ProjectM36.Base
import ProjectM36.Tuple
import ProjectM36.Error
import qualified Data.HashSet as HS
import qualified Data.Vector as V
import qualified Control.Parallel.Strategies as P
import Data.Either
emptyTupleSet :: RelationTupleSet
emptyTupleSet :: RelationTupleSet
emptyTupleSet = [RelationTuple] -> RelationTupleSet
RelationTupleSet []
singletonTupleSet :: RelationTupleSet
singletonTupleSet :: RelationTupleSet
singletonTupleSet = [RelationTuple] -> RelationTupleSet
RelationTupleSet [RelationTuple
emptyTuple]
verifyTupleSet :: Attributes -> RelationTupleSet -> Either RelationalError RelationTupleSet
verifyTupleSet :: Attributes
-> RelationTupleSet -> Either RelationalError RelationTupleSet
verifyTupleSet Attributes
attrs RelationTupleSet
tupleSet = do
let tupleList :: [Either RelationalError RelationTuple]
tupleList = forall a b. (a -> b) -> [a] -> [b]
map (Attributes -> RelationTuple -> Either RelationalError RelationTuple
verifyTuple Attributes
attrs) (RelationTupleSet -> [RelationTuple]
asList RelationTupleSet
tupleSet) forall a. a -> Strategy a -> a
`P.using` forall a. Int -> Strategy a -> Strategy [a]
P.parListChunk Int
chunkSize forall a. Strategy a
P.r0
chunkSize :: Int
chunkSize = (forall (t :: * -> *) a. Foldable t => t a -> Int
length forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationTupleSet -> [RelationTuple]
asList) RelationTupleSet
tupleSet forall a. Integral a => a -> a -> a
`div` Int
24
case forall a b. [Either a b] -> [a]
lefts [Either RelationalError RelationTuple]
tupleList of
RelationalError
x : [RelationalError]
_ -> forall a b. a -> Either a b
Left RelationalError
x
[RelationalError]
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ [RelationTuple] -> RelationTupleSet
RelationTupleSet forall a b. (a -> b) -> a -> b
$ (forall a. HashSet a -> [a]
HS.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList) (forall a b. [Either a b] -> [b]
rights [Either RelationalError RelationTuple]
tupleList)
mkTupleSet :: Attributes -> [RelationTuple] -> Either RelationalError RelationTupleSet
mkTupleSet :: Attributes
-> [RelationTuple] -> Either RelationalError RelationTupleSet
mkTupleSet Attributes
attrs [RelationTuple]
tuples = Attributes
-> RelationTupleSet -> Either RelationalError RelationTupleSet
verifyTupleSet Attributes
attrs ([RelationTuple] -> RelationTupleSet
RelationTupleSet [RelationTuple]
tuples)
mkTupleSetFromList :: Attributes -> [[Atom]] -> Either RelationalError RelationTupleSet
mkTupleSetFromList :: Attributes -> [[Atom]] -> Either RelationalError RelationTupleSet
mkTupleSetFromList Attributes
attrs [[Atom]]
atomMatrix = Attributes
-> [RelationTuple] -> Either RelationalError RelationTupleSet
mkTupleSet Attributes
attrs forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (Attributes -> Vector Atom -> RelationTuple
mkRelationTuple Attributes
attrs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Vector a
V.fromList) [[Atom]]
atomMatrix
tupleSetUnion :: Attributes -> RelationTupleSet -> RelationTupleSet -> RelationTupleSet
tupleSetUnion :: Attributes
-> RelationTupleSet -> RelationTupleSet -> RelationTupleSet
tupleSetUnion Attributes
targetAttrs RelationTupleSet
tupSet1 RelationTupleSet
tupSet2 = [RelationTuple] -> RelationTupleSet
RelationTupleSet forall a b. (a -> b) -> a -> b
$ forall a. HashSet a -> [a]
HS.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList forall a b. (a -> b) -> a -> b
$ [RelationTuple] -> [RelationTuple]
reorder (RelationTupleSet -> [RelationTuple]
asList RelationTupleSet
tupSet1) forall a. [a] -> [a] -> [a]
++ [RelationTuple] -> [RelationTuple]
reorder (RelationTupleSet -> [RelationTuple]
asList RelationTupleSet
tupSet2)
where
reorder :: [RelationTuple] -> [RelationTuple]
reorder = forall a b. (a -> b) -> [a] -> [b]
map (Attributes -> RelationTuple -> RelationTuple
reorderTuple Attributes
targetAttrs)