module Data.List.Set( Set, singleton
                    , insert, delete
                    , union, intersection, difference
                    , fromList, insertAll
                    ) where
import qualified Data.List as List
newtype Set a = Set { toList :: [a] }
              deriving (Show,Read,Functor,Foldable,Traversable)
instance Eq a => Eq (Set a) where
  (Set xs) == (Set ys) = all (`elem` ys) xs &&  all (`elem` xs) ys
instance Eq a => Semigroup (Set a) where
  (Set xs) <> s = insertAll xs s
instance Eq a => Monoid (Set a) where
  mempty = Set []
singleton   :: a -> Set a
singleton x = Set [x]
insert                           :: Eq a => a -> Set a -> Set a
insert x s@(Set xs) | x `elem` s = s
                    | otherwise  = Set (x:xs)
insertAll      :: Eq a => [a] -> Set a -> Set a
insertAll xs s = List.foldl' (flip insert) s xs
fromList :: Eq a => [a] -> Set a
fromList = flip insertAll mempty
delete            :: Eq a => a -> Set a -> Set a
delete x (Set xs) = Set $ go xs
  where
    go = \case
      [] -> []
      (y:ys) | x == y    -> ys 
             | otherwise -> y:go ys
union :: Eq a => Set a -> Set a -> Set a
union = (<>)
intersection                     :: Eq a => Set a -> Set a -> Set a
(Set xs) `intersection` (Set ys) = Set (xs `List.intersect` ys)
difference :: Eq a => Set a -> Set a -> Set a
(Set xs) `difference` (Set ys) = Set $ xs List.\\ ys