{-# LANGUAGE CPP #-}
module Data.HKeySet
(
HKeySet
, empty
, singleton
, union
, unions
, null
, size
, member
, insert
, delete
, difference
, intersection
, overlap
, sameKeys
, removeKeys
)
where
import Data.HKey
import Data.HMap (HMap)
import qualified Data.HMap as S
import qualified Data.List as List
import Data.Unique
import Prelude hiding (null)
newtype HKeySet = HKeySet HMap
empty :: HKeySet
empty = HKeySet S.empty
singleton :: HKey s a -> HKeySet
singleton x = HKeySet (S.singleton x undefined)
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE singleton #-}
#endif
union :: HKeySet -> HKeySet -> HKeySet
union (HKeySet s1) (HKeySet s2) = HKeySet (s1 `S.union` s2)
{-# INLINE union #-}
#if __GLASGOW_HASKELL__ >= 710
unions :: Foldable f => f HKeySet -> HKeySet
#endif
unions = List.foldl' union empty
{-# INLINE unions #-}
null :: HKeySet -> Bool
null (HKeySet x) = S.null x
{-# INLINE null #-}
size :: HKeySet -> Int
size (HKeySet x) = S.size x
{-# INLINE size #-}
member :: HKey s a -> HKeySet -> Bool
member x (HKeySet s) = x `S.member` s
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE member #-}
#endif
insert :: HKey x a -> HKeySet -> HKeySet
insert x (HKeySet s) = HKeySet (S.insert x undefined s)
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE insert #-}
#endif
delete :: HKey s a -> HKeySet -> HKeySet
delete x (HKeySet s) = HKeySet (S.delete x s)
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE delete #-}
#endif
difference :: HKeySet -> HKeySet -> HKeySet
difference (HKeySet a) (HKeySet b) = HKeySet (S.difference a b)
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE difference #-}
#endif
intersection :: HKeySet -> HKeySet -> HKeySet
intersection (HKeySet a) (HKeySet b) = HKeySet (S.intersection a b)
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE intersection #-}
#endif
overlap :: HMap -> HKeySet -> Bool
overlap h (HKeySet s) = not $ S.null (h `S.intersection` s)
sameKeys :: HMap -> HKeySet -> Bool
sameKeys h (HKeySet s) = S.null (h `S.difference` s)
removeKeys :: HMap -> HKeySet -> HMap
removeKeys h (HKeySet s) = h `S.difference` s