module Language.Parser.Ptera.Data.Symbolic.IntSet where import Language.Parser.Ptera.Prelude hiding (empty) import qualified Data.IntSet as DataIntSet type T = IntSet type Key = Int data IntSet = StraightSet DataIntSet.IntSet | NegativeSet DataIntSet.IntSet deriving (IntSet -> IntSet -> Bool (IntSet -> IntSet -> Bool) -> (IntSet -> IntSet -> Bool) -> Eq IntSet forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: IntSet -> IntSet -> Bool $c/= :: IntSet -> IntSet -> Bool == :: IntSet -> IntSet -> Bool $c== :: IntSet -> IntSet -> Bool Eq, Int -> IntSet -> ShowS [IntSet] -> ShowS IntSet -> String (Int -> IntSet -> ShowS) -> (IntSet -> String) -> ([IntSet] -> ShowS) -> Show IntSet forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [IntSet] -> ShowS $cshowList :: [IntSet] -> ShowS show :: IntSet -> String $cshow :: IntSet -> String showsPrec :: Int -> IntSet -> ShowS $cshowsPrec :: Int -> IntSet -> ShowS Show) instance Semigroup IntSet where <> :: IntSet -> IntSet -> IntSet (<>) = IntSet -> IntSet -> IntSet union instance Monoid IntSet where mempty :: IntSet mempty = IntSet -> IntSet StraightSet IntSet DataIntSet.empty full :: IntSet full :: IntSet full = IntSet -> IntSet NegativeSet IntSet DataIntSet.empty singleton :: Key -> IntSet singleton :: Int -> IntSet singleton Int k = IntSet -> IntSet StraightSet do Int -> IntSet DataIntSet.singleton Int k invert :: IntSet -> IntSet invert :: IntSet -> IntSet invert = \case StraightSet IntSet s -> IntSet -> IntSet NegativeSet IntSet s NegativeSet IntSet s -> IntSet -> IntSet StraightSet IntSet s fromList :: [Key] -> IntSet fromList :: [Int] -> IntSet fromList [Int] ks = IntSet -> IntSet StraightSet do [Int] -> IntSet DataIntSet.fromList [Int] ks insert :: Key -> IntSet -> IntSet insert :: Int -> IntSet -> IntSet insert Int k = \case StraightSet IntSet s -> IntSet -> IntSet StraightSet do Int -> IntSet -> IntSet DataIntSet.insert Int k IntSet s NegativeSet IntSet s -> IntSet -> IntSet NegativeSet do Int -> IntSet -> IntSet DataIntSet.delete Int k IntSet s delete :: Key -> IntSet -> IntSet delete :: Int -> IntSet -> IntSet delete Int k = \case StraightSet IntSet s -> IntSet -> IntSet StraightSet do Int -> IntSet -> IntSet DataIntSet.delete Int k IntSet s NegativeSet IntSet s -> IntSet -> IntSet NegativeSet do Int -> IntSet -> IntSet DataIntSet.insert Int k IntSet s member :: Key -> IntSet -> Bool member :: Int -> IntSet -> Bool member Int k = \case StraightSet IntSet s -> Int -> IntSet -> Bool DataIntSet.member Int k IntSet s NegativeSet IntSet s -> Bool -> Bool not do Int -> IntSet -> Bool DataIntSet.member Int k IntSet s union :: IntSet -> IntSet -> IntSet union :: IntSet -> IntSet -> IntSet union (StraightSet IntSet s1) (StraightSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.union IntSet s1 IntSet s2 union (StraightSet IntSet s1) (NegativeSet IntSet s2) = IntSet -> IntSet NegativeSet do IntSet -> IntSet -> IntSet DataIntSet.difference IntSet s2 IntSet s1 union (NegativeSet IntSet s1) (StraightSet IntSet s2) = IntSet -> IntSet NegativeSet do IntSet -> IntSet -> IntSet DataIntSet.difference IntSet s1 IntSet s2 union (NegativeSet IntSet s1) (NegativeSet IntSet s2) = IntSet -> IntSet NegativeSet do IntSet -> IntSet -> IntSet DataIntSet.intersection IntSet s1 IntSet s2 intersection :: IntSet -> IntSet -> IntSet intersection :: IntSet -> IntSet -> IntSet intersection (StraightSet IntSet s1) (StraightSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.intersection IntSet s1 IntSet s2 intersection (StraightSet IntSet s1) (NegativeSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.difference IntSet s1 IntSet s2 intersection (NegativeSet IntSet s1) (StraightSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.difference IntSet s2 IntSet s1 intersection (NegativeSet IntSet s1) (NegativeSet IntSet s2) = IntSet -> IntSet NegativeSet do IntSet -> IntSet -> IntSet DataIntSet.union IntSet s1 IntSet s2 difference :: IntSet -> IntSet -> IntSet difference :: IntSet -> IntSet -> IntSet difference (StraightSet IntSet s1) (StraightSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.difference IntSet s1 IntSet s2 difference (StraightSet IntSet s1) (NegativeSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.intersection IntSet s1 IntSet s2 difference (NegativeSet IntSet s1) (StraightSet IntSet s2) = IntSet -> IntSet NegativeSet do IntSet -> IntSet -> IntSet DataIntSet.union IntSet s1 IntSet s2 difference (NegativeSet IntSet s1) (NegativeSet IntSet s2) = IntSet -> IntSet StraightSet do IntSet -> IntSet -> IntSet DataIntSet.difference IntSet s2 IntSet s1