module Language.Parser.Ptera.Data.Alignable.Set ( T, Set, empty, singleton, insert, delete, fromList, toList, null, intersection, union, difference, length, member, ) where import Language.Parser.Ptera.Prelude hiding (empty, length, null, toList) import qualified Data.IntSet as IntSet import qualified Language.Parser.Ptera.Data.Alignable as Alignable type T = Set newtype Set n = Set IntSet.IntSet deriving (Set n -> Set n -> Bool (Set n -> Set n -> Bool) -> (Set n -> Set n -> Bool) -> Eq (Set n) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall k (n :: k). Set n -> Set n -> Bool /= :: Set n -> Set n -> Bool $c/= :: forall k (n :: k). Set n -> Set n -> Bool == :: Set n -> Set n -> Bool $c== :: forall k (n :: k). Set n -> Set n -> Bool Eq, Int -> Set n -> ShowS [Set n] -> ShowS Set n -> String (Int -> Set n -> ShowS) -> (Set n -> String) -> ([Set n] -> ShowS) -> Show (Set n) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall k (n :: k). Int -> Set n -> ShowS forall k (n :: k). [Set n] -> ShowS forall k (n :: k). Set n -> String showList :: [Set n] -> ShowS $cshowList :: forall k (n :: k). [Set n] -> ShowS show :: Set n -> String $cshow :: forall k (n :: k). Set n -> String showsPrec :: Int -> Set n -> ShowS $cshowsPrec :: forall k (n :: k). Int -> Set n -> ShowS Show) deriving b -> Set n -> Set n NonEmpty (Set n) -> Set n Set n -> Set n -> Set n (Set n -> Set n -> Set n) -> (NonEmpty (Set n) -> Set n) -> (forall b. Integral b => b -> Set n -> Set n) -> Semigroup (Set n) forall b. Integral b => b -> Set n -> Set n forall a. (a -> a -> a) -> (NonEmpty a -> a) -> (forall b. Integral b => b -> a -> a) -> Semigroup a forall k (n :: k). NonEmpty (Set n) -> Set n forall k (n :: k). Set n -> Set n -> Set n forall k (n :: k) b. Integral b => b -> Set n -> Set n stimes :: b -> Set n -> Set n $cstimes :: forall k (n :: k) b. Integral b => b -> Set n -> Set n sconcat :: NonEmpty (Set n) -> Set n $csconcat :: forall k (n :: k). NonEmpty (Set n) -> Set n <> :: Set n -> Set n -> Set n $c<> :: forall k (n :: k). Set n -> Set n -> Set n Semigroup via IntSet.IntSet empty :: Set n empty :: Set n empty = IntSet -> Set n coerce IntSet IntSet.empty singleton :: Alignable.T n => n -> Set n singleton :: n -> Set n singleton = (Int -> IntSet) -> n -> Set n coerce Int -> IntSet IntSet.singleton insert :: Alignable.T n => n -> Set n -> Set n insert :: n -> Set n -> Set n insert = (Int -> IntSet -> IntSet) -> n -> Set n -> Set n coerce Int -> IntSet -> IntSet IntSet.insert delete :: Alignable.T n => n -> Set n -> Set n delete :: n -> Set n -> Set n delete = (Int -> IntSet -> IntSet) -> n -> Set n -> Set n coerce Int -> IntSet -> IntSet IntSet.delete fromList :: Alignable.T n => [n] -> Set n fromList :: [n] -> Set n fromList = ([Int] -> IntSet) -> [n] -> Set n coerce [Int] -> IntSet IntSet.fromList toList :: Alignable.T n => Set n -> [n] toList :: Set n -> [n] toList = (IntSet -> [Int]) -> Set n -> [n] coerce IntSet -> [Int] IntSet.toList null :: Set n -> Bool null :: Set n -> Bool null = (IntSet -> Bool) -> Set n -> Bool coerce IntSet -> Bool IntSet.null intersection :: Set n -> Set n -> Set n intersection :: Set n -> Set n -> Set n intersection = (IntSet -> IntSet -> IntSet) -> Set n -> Set n -> Set n coerce IntSet -> IntSet -> IntSet IntSet.intersection difference :: Set n -> Set n -> Set n difference :: Set n -> Set n -> Set n difference = (IntSet -> IntSet -> IntSet) -> Set n -> Set n -> Set n coerce IntSet -> IntSet -> IntSet IntSet.difference union :: Set n -> Set n -> Set n union :: Set n -> Set n -> Set n union = (IntSet -> IntSet -> IntSet) -> Set n -> Set n -> Set n coerce IntSet -> IntSet -> IntSet IntSet.union length :: Set n -> Int length :: Set n -> Int length = (IntSet -> Int) -> Set n -> Int coerce IntSet -> Int IntSet.size member :: Alignable.T n => n -> Set n -> Bool member :: n -> Set n -> Bool member = (Int -> IntSet -> Bool) -> n -> Set n -> Bool coerce Int -> IntSet -> Bool IntSet.member