ixset-1.1.1: Efficient relational queries on Haskell sets.

Safe HaskellNone
LanguageHaskell2010

Data.IxSet.Ix

Description

This module defines Typeable indexes and convenience functions. Should probably be considered private to Data.IxSet.

Synopsis

Documentation

data Ix a Source #

Ix is a Map from some Typeable key to a Set of values for that key. Ix carries type information inside.

Constructors

(Typeable key, Ord key) => Ix (Map key (Set a)) (a -> [key]) 
Instances
(Typeable Ix, Data ctx a, Sat (ctx (Ix a))) => Data ctx (Ix a) Source # 
Instance details

Defined in Data.IxSet.Ix

Methods

gfoldl :: Proxy ctx -> (forall b c. Data ctx b => w (b -> c) -> b -> w c) -> (forall g. g -> w g) -> Ix a -> w (Ix a) #

gunfold :: Proxy ctx -> (forall b r. Data ctx b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ix a) #

toConstr :: Proxy ctx -> Ix a -> Constr #

dataTypeOf :: Proxy ctx -> Ix a -> DataType #

dataCast1 :: Typeable t => Proxy ctx -> (forall b. Data ctx b => w (t b)) -> Maybe (w (Ix a)) #

dataCast2 :: Typeable t => Proxy ctx -> (forall b c. (Data ctx b, Data ctx c) => w (t b c)) -> Maybe (w (Ix a)) #

Data a => Data (Ix a) Source # 
Instance details

Defined in Data.IxSet.Ix

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ix a -> c (Ix a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ix a) #

toConstr :: Ix a -> Constr #

dataTypeOf :: Ix a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ix a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ix a)) #

gmapT :: (forall b. Data b => b -> b) -> Ix a -> Ix a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ix a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ix a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ix a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ix a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ix a -> m (Ix a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ix a -> m (Ix a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ix a -> m (Ix a) #

insert :: (Ord a, Ord k) => k -> a -> Map k (Set a) -> Map k (Set a) Source #

Convenience function for inserting into Maps of Sets as in the case of an Ix. If they key did not already exist in the Map, then a new Set is added transparently.

delete :: (Ord a, Ord k) => k -> a -> Map k (Set a) -> Map k (Set a) Source #

Convenience function for deleting from Maps of Sets. If the resulting Set is empty, then the entry is removed from the Map.

insertList :: (Ord a, Ord k) => [(k, a)] -> Map k (Set a) -> Map k (Set a) Source #

Helper function to insert a list of elements into a set.

deleteList :: (Ord a, Ord k) => [(k, a)] -> Map k (Set a) -> Map k (Set a) Source #

Helper function to delete a list of elements from a set.

union :: (Ord a, Ord k) => Map k (Set a) -> Map k (Set a) -> Map k (Set a) Source #

Takes the union of two sets.

intersection :: (Ord a, Ord k) => Map k (Set a) -> Map k (Set a) -> Map k (Set a) Source #

Takes the intersection of two sets.