ixset-typed-0.4.0.1: Efficient relational queries on Haskell sets.

Safe HaskellNone
LanguageHaskell2010

Data.IxSet.Typed.Ix

Description

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

Synopsis

Documentation

data Ix (ix :: *) (a :: *) where Source #

Ix is a Map from some key (of type ix) to a Set of values (of type a) for that key.

Constructors

Ix :: !(Map ix (Set a)) -> (a -> [ix]) -> Ix ix a 
Instances
(NFData ix, NFData a) => NFData (Ix ix a) Source # 
Instance details

Defined in Data.IxSet.Typed.Ix

Methods

rnf :: Ix ix a -> () #

MkIxList ixs ixs' a r => MkIxList (ix ': ixs) ixs' a (Ix ix a -> r) Source # 
Instance details

Defined in Data.IxSet.Typed

Methods

ixList' :: (IxList (ix ': ixs) a -> IxList ixs' a) -> Ix ix a -> r

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.

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

Helper function to create a new index from a list.

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.