module Data.List.Set( Set, singleton
                    , insert, delete
                    , union, intersection, difference
                    , fromList, insertAll
                    ) where
import qualified Data.List as List
newtype Set a = Set { Set a -> [a]
toList :: [a] }
              deriving (Int -> Set a -> ShowS
[Set a] -> ShowS
Set a -> String
(Int -> Set a -> ShowS)
-> (Set a -> String) -> ([Set a] -> ShowS) -> Show (Set a)
forall a. Show a => Int -> Set a -> ShowS
forall a. Show a => [Set a] -> ShowS
forall a. Show a => Set a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Set a] -> ShowS
$cshowList :: forall a. Show a => [Set a] -> ShowS
show :: Set a -> String
$cshow :: forall a. Show a => Set a -> String
showsPrec :: Int -> Set a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Set a -> ShowS
Show,ReadPrec [Set a]
ReadPrec (Set a)
Int -> ReadS (Set a)
ReadS [Set a]
(Int -> ReadS (Set a))
-> ReadS [Set a]
-> ReadPrec (Set a)
-> ReadPrec [Set a]
-> Read (Set a)
forall a. Read a => ReadPrec [Set a]
forall a. Read a => ReadPrec (Set a)
forall a. Read a => Int -> ReadS (Set a)
forall a. Read a => ReadS [Set a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Set a]
$creadListPrec :: forall a. Read a => ReadPrec [Set a]
readPrec :: ReadPrec (Set a)
$creadPrec :: forall a. Read a => ReadPrec (Set a)
readList :: ReadS [Set a]
$creadList :: forall a. Read a => ReadS [Set a]
readsPrec :: Int -> ReadS (Set a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Set a)
Read,a -> Set b -> Set a
(a -> b) -> Set a -> Set b
(forall a b. (a -> b) -> Set a -> Set b)
-> (forall a b. a -> Set b -> Set a) -> Functor Set
forall a b. a -> Set b -> Set a
forall a b. (a -> b) -> Set a -> Set b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Set b -> Set a
$c<$ :: forall a b. a -> Set b -> Set a
fmap :: (a -> b) -> Set a -> Set b
$cfmap :: forall a b. (a -> b) -> Set a -> Set b
Functor,a -> Set a -> Bool
Set m -> m
Set a -> [a]
Set a -> Bool
Set a -> Int
Set a -> a
Set a -> a
Set a -> a
Set a -> a
(a -> m) -> Set a -> m
(a -> m) -> Set a -> m
(a -> b -> b) -> b -> Set a -> b
(a -> b -> b) -> b -> Set a -> b
(b -> a -> b) -> b -> Set a -> b
(b -> a -> b) -> b -> Set a -> b
(a -> a -> a) -> Set a -> a
(a -> a -> a) -> Set a -> a
(forall m. Monoid m => Set m -> m)
-> (forall m a. Monoid m => (a -> m) -> Set a -> m)
-> (forall m a. Monoid m => (a -> m) -> Set a -> m)
-> (forall a b. (a -> b -> b) -> b -> Set a -> b)
-> (forall a b. (a -> b -> b) -> b -> Set a -> b)
-> (forall b a. (b -> a -> b) -> b -> Set a -> b)
-> (forall b a. (b -> a -> b) -> b -> Set a -> b)
-> (forall a. (a -> a -> a) -> Set a -> a)
-> (forall a. (a -> a -> a) -> Set a -> a)
-> (forall a. Set a -> [a])
-> (forall a. Set a -> Bool)
-> (forall a. Set a -> Int)
-> (forall a. Eq a => a -> Set a -> Bool)
-> (forall a. Ord a => Set a -> a)
-> (forall a. Ord a => Set a -> a)
-> (forall a. Num a => Set a -> a)
-> (forall a. Num a => Set a -> a)
-> Foldable Set
forall a. Eq a => a -> Set a -> Bool
forall a. Num a => Set a -> a
forall a. Ord a => Set a -> a
forall m. Monoid m => Set m -> m
forall a. Set a -> Bool
forall a. Set a -> Int
forall a. Set a -> [a]
forall a. (a -> a -> a) -> Set a -> a
forall m a. Monoid m => (a -> m) -> Set a -> m
forall b a. (b -> a -> b) -> b -> Set a -> b
forall a b. (a -> b -> b) -> b -> Set a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Set a -> a
$cproduct :: forall a. Num a => Set a -> a
sum :: Set a -> a
$csum :: forall a. Num a => Set a -> a
minimum :: Set a -> a
$cminimum :: forall a. Ord a => Set a -> a
maximum :: Set a -> a
$cmaximum :: forall a. Ord a => Set a -> a
elem :: a -> Set a -> Bool
$celem :: forall a. Eq a => a -> Set a -> Bool
length :: Set a -> Int
$clength :: forall a. Set a -> Int
null :: Set a -> Bool
$cnull :: forall a. Set a -> Bool
toList :: Set a -> [a]
$ctoList :: forall a. Set a -> [a]
foldl1 :: (a -> a -> a) -> Set a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Set a -> a
foldr1 :: (a -> a -> a) -> Set a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Set a -> a
foldl' :: (b -> a -> b) -> b -> Set a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Set a -> b
foldl :: (b -> a -> b) -> b -> Set a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Set a -> b
foldr' :: (a -> b -> b) -> b -> Set a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Set a -> b
foldr :: (a -> b -> b) -> b -> Set a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Set a -> b
foldMap' :: (a -> m) -> Set a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Set a -> m
foldMap :: (a -> m) -> Set a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Set a -> m
fold :: Set m -> m
$cfold :: forall m. Monoid m => Set m -> m
Foldable,Functor Set
Foldable Set
Functor Set
-> Foldable Set
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Set a -> f (Set b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Set (f a) -> f (Set a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Set a -> m (Set b))
-> (forall (m :: * -> *) a. Monad m => Set (m a) -> m (Set a))
-> Traversable Set
(a -> f b) -> Set a -> f (Set b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Set (m a) -> m (Set a)
forall (f :: * -> *) a. Applicative f => Set (f a) -> f (Set a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Set a -> m (Set b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Set a -> f (Set b)
sequence :: Set (m a) -> m (Set a)
$csequence :: forall (m :: * -> *) a. Monad m => Set (m a) -> m (Set a)
mapM :: (a -> m b) -> Set a -> m (Set b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Set a -> m (Set b)
sequenceA :: Set (f a) -> f (Set a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Set (f a) -> f (Set a)
traverse :: (a -> f b) -> Set a -> f (Set b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Set a -> f (Set b)
$cp2Traversable :: Foldable Set
$cp1Traversable :: Functor Set
Traversable)
instance Eq a => Eq (Set a) where
  (Set [a]
xs) == :: Set a -> Set a -> Bool
== (Set [a]
ys) = (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
ys) [a]
xs Bool -> Bool -> Bool
&&  (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
xs) [a]
ys
instance Eq a => Semigroup (Set a) where
  (Set [a]
xs) <> :: Set a -> Set a -> Set a
<> Set a
s = [a] -> Set a -> Set a
forall a. Eq a => [a] -> Set a -> Set a
insertAll [a]
xs Set a
s
instance Eq a => Monoid (Set a) where
  mempty :: Set a
mempty = [a] -> Set a
forall a. [a] -> Set a
Set []
singleton   :: a -> Set a
singleton :: a -> Set a
singleton a
x = [a] -> Set a
forall a. [a] -> Set a
Set [a
x]
insert                           :: Eq a => a -> Set a -> Set a
insert :: a -> Set a -> Set a
insert a
x s :: Set a
s@(Set [a]
xs) | a
x a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set a
s = Set a
s
                    | Bool
otherwise  = [a] -> Set a
forall a. [a] -> Set a
Set (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
xs)
insertAll      :: Eq a => [a] -> Set a -> Set a
insertAll :: [a] -> Set a -> Set a
insertAll [a]
xs Set a
s = (Set a -> a -> Set a) -> Set a -> [a] -> Set a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' ((a -> Set a -> Set a) -> Set a -> a -> Set a
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> Set a -> Set a
forall a. Eq a => a -> Set a -> Set a
insert) Set a
s [a]
xs
fromList :: Eq a => [a] -> Set a
fromList :: [a] -> Set a
fromList = ([a] -> Set a -> Set a) -> Set a -> [a] -> Set a
forall a b c. (a -> b -> c) -> b -> a -> c
flip [a] -> Set a -> Set a
forall a. Eq a => [a] -> Set a -> Set a
insertAll Set a
forall a. Monoid a => a
mempty
delete            :: Eq a => a -> Set a -> Set a
delete :: a -> Set a -> Set a
delete a
x (Set [a]
xs) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ [a] -> [a]
go [a]
xs
  where
    go :: [a] -> [a]
go = \case
      [] -> []
      (a
y:[a]
ys) | a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y    -> [a]
ys 
             | Bool
otherwise -> a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a] -> [a]
go [a]
ys
union :: Eq a => Set a -> Set a -> Set a
union :: Set a -> Set a -> Set a
union = Set a -> Set a -> Set a
forall a. Semigroup a => a -> a -> a
(<>)
intersection                     :: Eq a => Set a -> Set a -> Set a
(Set [a]
xs) intersection :: Set a -> Set a -> Set a
`intersection` (Set [a]
ys) = [a] -> Set a
forall a. [a] -> Set a
Set ([a]
xs [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
`List.intersect` [a]
ys)
difference :: Eq a => Set a -> Set a -> Set a
(Set [a]
xs) difference :: Set a -> Set a -> Set a
`difference` (Set [a]
ys) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ [a]
xs [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
List.\\ [a]
ys