{-# LANGUAGE ExistentialQuantification
, ScopedTypeVariables
, TypeOperators
#-}
module Data.HtsSet ( HtsSet
, empty, singleton
, null, size, member, notMember
, insert
, lookup, lookupWithDefault
, update
, existTypeOf, existTypeOfP
, (:+) (..), Append (..), fill
) where
import qualified Data.Map as M
import Data.Typeable
import Prelude hiding (lookup, null)
data CastBox = forall a. (Typeable a) => CastBox { unBox :: a }
newtype HtsSet = HtsSet { unHS :: M.Map TypeRep CastBox }
data P a = P
mapCastBox :: forall a. Typeable a => (a -> a) -> CastBox -> CastBox
mapCastBox f o@(CastBox e) = case cast e of
(Just e') -> CastBox (f e')
Nothing -> o
empty :: HtsSet
empty = HtsSet M.empty
singleton :: forall a. Typeable a => a -> HtsSet
singleton a = HtsSet (M.singleton (typeRep (Proxy :: Proxy a)) (CastBox a))
null :: HtsSet -> Bool
null = M.null . unHS
size :: HtsSet -> Int
size = M.size . unHS
member :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool
member _ = M.member (typeRep (Proxy :: Proxy a)) . unHS
notMember :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool
notMember p = not . member p
insert :: forall a. Typeable a => a -> HtsSet -> HtsSet
insert a (HtsSet hs) = HtsSet (M.insert (typeRep (Proxy :: Proxy a)) (CastBox a) hs)
lookup :: forall a. Typeable a => HtsSet -> Maybe a
lookup (HtsSet hs) = case M.lookup (typeRep (Proxy :: Proxy a)) hs of
(Just (CastBox a)) -> cast a
_ -> Nothing
lookupWithDefault :: forall a. Typeable a => a -> HtsSet -> a
lookupWithDefault a hs = case lookup hs of
Nothing -> a
(Just a') -> a'
update :: forall a. Typeable a => (a -> a) -> HtsSet -> HtsSet
update f = HtsSet . M.adjust (mapCastBox f) (typeRep (Proxy :: Proxy a)) . unHS
existTypeOf :: forall a. Typeable a => a -> HtsSet -> Bool
existTypeOf _ (HtsSet hs) = case M.lookup (typeRep (Proxy :: Proxy a)) hs of
(Just _) -> True
_ -> False
existTypeOfP :: forall proxy a. Typeable a => proxy a -> HtsSet -> Bool
existTypeOfP _ (HtsSet hs) = case M.lookup (typeRep (Proxy :: Proxy a)) hs of
(Just _) -> True
_ -> False
data a :+ b = a :+ b
infixr 5 :+
class Append a where
append :: a -> HtsSet -> HtsSet
fill :: (Append a) => a -> HtsSet
fill = flip append empty
instance (Typeable a, Append b) => Append (a :+ b) where
append (a :+ b) = insert a . (append b)
instance Append () where
append _ hs = hs