module Data.SplayTree.Set (
module S
,Set
,empty
,null
,size
,member
,memberSplay
,insert
,delete
,union
,difference
,intersection
,map
,fromList
)
where
import Prelude hiding (null, map)
import qualified Prelude as P
import Data.SplayTree (SplayTree (..), Measure (..), (|>), (<|), (><), query, fmap')
import qualified Data.SplayTree as S
import Control.Applicative hiding (empty)
import Data.Maybe
import Data.Monoid
import Data.Foldable
import Data.Traversable
data Elem a = None | Elem a
deriving (Show, Ord, Eq, Functor, Foldable, Traversable)
instance (Ord a) => Monoid (Elem a) where
mempty = None
mappend None b = b
mappend a None = a
mappend a b = max a b
instance (Ord a) => Measured (Elem a) where
type Measure (Elem a) = Elem a
measure a = a
newtype Set a = Set { unSet :: SplayTree (Elem a) }
deriving (Eq, Show, Ord, Foldable)
instance Ord a => Monoid (Set a) where
mempty = Set mempty
mappend = union
empty :: (Ord a) => Set a
empty = Set S.empty
singleton :: (Ord a) => a -> Set a
singleton = Set . S.singleton . Elem
null :: (Ord a) => Set a -> Bool
null = S.null . unSet
size :: (Ord a) => Set a -> Int
size = S.size . unSet
member :: (Ord a) => a -> Set a -> Bool
member a set = fst $ memberSplay a set
memberSplay :: (Ord a) => a -> Set a -> (Bool, Set a)
memberSplay a (Set tree) = fmap Set $ S.memberSplay (Elem a) tree
fromList :: (Ord a) => [a] -> Set a
fromList = Set . S.fromListBalance . P.map Elem
insert :: (Ord a) => a -> Set a -> Set a
insert a = Set . S.insert (Elem a) . unSet
delete :: (Ord a) => a -> Set a -> Set a
delete a (Set tree) = Set $ S.delete (Elem a) tree
union :: (Ord a) => Set a -> Set a -> Set a
union l = foldl' (flip insert) l
map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
map f = fromList . P.map f . toList
difference :: (Ord a) => Set a -> Set a -> Set a
difference (Set l) (Set r) = Set (S.difference l r)
intersection :: (Ord a) => Set a -> Set a -> Set a
intersection (Set l) (Set r) = Set (S.intersection l r)