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

Safe HaskellNone
LanguageHaskell2010

Data.IxSet.Typed

Contents

Description

An efficient implementation of queryable sets.

Assume you have a family of types such as:

data Entry      = Entry Author [Author] Updated Id Content
  deriving (Show, Eq, Ord, Data, Typeable)
newtype Updated = Updated UTCTime
  deriving (Show, Eq, Ord, Data, Typeable)
newtype Id      = Id Int64
  deriving (Show, Eq, Ord, Data, Typeable)
newtype Content = Content String
  deriving (Show, Eq, Ord, Data, Typeable)
newtype Author  = Author Email
  deriving (Show, Eq, Ord, Data, Typeable)
type Email      = String
data Test = Test
  deriving (Show, Eq, Ord, Data, Typeable)
  1. Decide what parts of your type you want indexed and make your type an instance of Indexable. Use ixFun and ixGen to build indices:

    type EntryIxs = '[Author, Id, Updated, Test]
    type IxEntry  = IxSet EntryIxs Entry
    
    instance Indexable EntryIxs Entry where
      indices = ixList
                  (ixGen (Proxy :: Proxy Author))        -- out of order
                  (ixGen (Proxy :: Proxy Id))
                  (ixGen (Proxy :: Proxy Updated))
                  (ixGen (Proxy :: Proxy Test))          -- bogus index

    The use of ixGen requires the Data and Typeable instances above. You can build indices manually using ixFun. You can also use the Template Haskell function inferIxSet to generate an Indexable instance automatically.

  2. Use insert, insertList, delete, updateIx, deleteIx and empty to build up an IxSet collection:

    entries  = insertList [e1, e2, e3, e4] (empty :: IxEntry)
    entries1 = foldr delete entries [e1, e3]
    entries2 = updateIx (Id 4) e5 entries
  3. Use the query functions below to grab data from it:

    entries @= Author "john@doe.com" @< Updated t1

    Statement above will find all items in entries updated earlier than t1 by john@doe.com.

  4. Text index

    If you want to do add a text index create a calculated index. Then if you want all entries with either word1 or word2, you change the instance to:

    newtype Word = Word String
      deriving (Show, Eq, Ord)
    
    getWords (Entry _ _ _ _ (Content s)) = map Word $ words s
    
    type EntryIxs = '[..., Word]
    instance Indexable EntryIxs Entry where
        indices = ixList
                    ...
                    (ixFun getWords)

    Now you can do this query to find entries with any of the words:

    entries @+ [Word "word1", Word "word2"]

    And if you want all entries with both:

    entries @* [Word "word1", Word "word2"]
  5. Find only the first author

    If an Entry has multiple authors and you want to be able to query on the first author only, define a FirstAuthor datatype and create an index with this type. Now you can do:

    newtype FirstAuthor = FirstAuthor Email
      deriving (Show, Eq, Ord)
    
    getFirstAuthor (Entry author _ _ _ _) = [FirstAuthor author]
    
    type EntryIxs = '[..., FirstAuthor]
    instance Indexable EntryIxs Entry where
        indices = ixList
                    ...
                    (ixFun getFirstAuthor)
    entries @= (FirstAuthor "john@doe.com")  -- guess what this does

Synopsis

Set type

data IxSet ixs a Source #

Set with associated indices.

The type-level list ixs contains all types that are valid index keys. The type a is the type of elements in the indexed set.

On strictness: An IxSet is "mostly" spine-strict. It is generally spine-strict in the set itself. All operations on IxSet with the exception of queries are spine-strict in the indices as well. Query operations, however, are lazy in the indices, so querying a number of times and subsequently selecting the result will not unnecessarily rebuild all indices.

Instances

Foldable (IxSet ixs) Source # 

Methods

fold :: Monoid m => IxSet ixs m -> m #

foldMap :: Monoid m => (a -> m) -> IxSet ixs a -> m #

foldr :: (a -> b -> b) -> b -> IxSet ixs a -> b #

foldr' :: (a -> b -> b) -> b -> IxSet ixs a -> b #

foldl :: (b -> a -> b) -> b -> IxSet ixs a -> b #

foldl' :: (b -> a -> b) -> b -> IxSet ixs a -> b #

foldr1 :: (a -> a -> a) -> IxSet ixs a -> a #

foldl1 :: (a -> a -> a) -> IxSet ixs a -> a #

toList :: IxSet ixs a -> [a] #

null :: IxSet ixs a -> Bool #

length :: IxSet ixs a -> Int #

elem :: Eq a => a -> IxSet ixs a -> Bool #

maximum :: Ord a => IxSet ixs a -> a #

minimum :: Ord a => IxSet ixs a -> a #

sum :: Num a => IxSet ixs a -> a #

product :: Num a => IxSet ixs a -> a #

Indexable ixs a => Eq (IxSet ixs a) Source # 

Methods

(==) :: IxSet ixs a -> IxSet ixs a -> Bool #

(/=) :: IxSet ixs a -> IxSet ixs a -> Bool #

Indexable ixs a => Ord (IxSet ixs a) Source # 

Methods

compare :: IxSet ixs a -> IxSet ixs a -> Ordering #

(<) :: IxSet ixs a -> IxSet ixs a -> Bool #

(<=) :: IxSet ixs a -> IxSet ixs a -> Bool #

(>) :: IxSet ixs a -> IxSet ixs a -> Bool #

(>=) :: IxSet ixs a -> IxSet ixs a -> Bool #

max :: IxSet ixs a -> IxSet ixs a -> IxSet ixs a #

min :: IxSet ixs a -> IxSet ixs a -> IxSet ixs a #

(Indexable ixs a, Read a) => Read (IxSet ixs a) Source # 

Methods

readsPrec :: Int -> ReadS (IxSet ixs a) #

readList :: ReadS [IxSet ixs a] #

readPrec :: ReadPrec (IxSet ixs a) #

readListPrec :: ReadPrec [IxSet ixs a] #

(Indexable ixs a, Show a) => Show (IxSet ixs a) Source # 

Methods

showsPrec :: Int -> IxSet ixs a -> ShowS #

show :: IxSet ixs a -> String #

showList :: [IxSet ixs a] -> ShowS #

Indexable ixs a => Monoid (IxSet ixs a) Source # 

Methods

mempty :: IxSet ixs a #

mappend :: IxSet ixs a -> IxSet ixs a -> IxSet ixs a #

mconcat :: [IxSet ixs a] -> IxSet ixs a #

(All NFData ixs, NFData a) => NFData (IxSet ixs a) Source # 

Methods

rnf :: IxSet ixs a -> () #

(Indexable ixs a, SafeCopy a) => SafeCopy (IxSet ixs a) Source # 

data IxList ixs a Source #

Instances

MkIxList ([] *) ixs a (IxList ixs a) Source # 

Methods

ixList' :: (IxList [*] a -> IxList ixs a) -> IxList ixs a

(All NFData ixs, NFData a) => NFData (IxList ixs a) Source # 

Methods

rnf :: IxList ixs a -> () #

class (All Ord ixs, Ord a) => Indexable ixs a where Source #

Associate indices with a given type. The constraint Indexable ixs a says that we know how to build index sets of type IxSet ixs a.

In order to use an IxSet on a particular type, you have to make it an instance of Indexable yourself. There are no predefined instances of IxSet.

Minimal complete definition

indices

Methods

indices :: IxList ixs a Source #

Define how the indices for this particular type should look like.

Use the ixList function to construct the list of indices, and use ixFun (or ixGen) for individual indices.

class Ord ix => IsIndexOf ix ixs Source #

Constraint for membership in the type-level list. Says that ix is contained in the index list ixs.

Minimal complete definition

access, mapAt

Instances

IsIndexOf ix ixs => IsIndexOf ix ((:) * ix' ixs) Source # 

Methods

access :: IxList ((* ': ix') ixs) a -> Ix ix a

mapAt :: All Ord ((* ': ix') ixs) => (Ix ix a -> Ix ix a) -> (forall ix'0. Ord ix'0 => Ix ix'0 a -> Ix ix'0 a) -> IxList ((* ': ix') ixs) a -> IxList ((* ': ix') ixs) a

Ord ix => IsIndexOf ix ((:) * ix ixs) Source # 

Methods

access :: IxList ((* ': ix) ixs) a -> Ix ix a

mapAt :: All Ord ((* ': ix) ixs) => (Ix ix a -> Ix ix a) -> (forall ix'. Ord ix' => Ix ix' a -> Ix ix' a) -> IxList ((* ': ix) ixs) a -> IxList ((* ': ix) ixs) a

type family All (c :: * -> Constraint) (xs :: [*]) :: Constraint Source #

The constraint All c xs says the c has to hold for all elements in the type-level list xs.

Example:

All Ord '[Int, Char, Bool]

is equivalent to

(Ord Int, Ord Char, Ord Bool)

Instances

type All c ([] *) Source # 
type All c ([] *) = ()
type All c ((:) * x xs) Source # 
type All c ((:) * x xs) = (c x, All c xs)

Declaring indices

data Ix ix a Source #

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

Instances

(NFData ix, NFData a) => NFData (Ix ix a) Source # 

Methods

rnf :: Ix ix a -> () #

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

Methods

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

ixList :: MkIxList ixs ixs a r => r Source #

Create an (empty) IxList from a number of indices. Useful in the Indexable indices method. Use ixFun and ixGen for the individual indices.

Note that this function takes a variable number of arguments. Here are some example types at which the function can be used:

ixList :: Ix ix1 a -> IxList '[ix1] a
ixList :: Ix ix1 a -> Ix ix2 a -> IxList '[ix1, ix2] a
ixList :: Ix ix1 a -> Ix ix2 a -> Ix ix3 a -> IxList '[ix1, ix2, ix3] a
ixList :: ...

Concrete example use:

instance Indexable '[..., Index1Type, Index2Type] Type where
    indices = ixList
                ...
                (ixFun getIndex1)
                (ixGen (Proxy :: Proxy Index2Type))

class MkIxList ixs ixs' a r | r -> a ixs ixs' Source #

Class that allows a variable number of arguments to be passed to the ixSet and mkEmpty functions. See the documentation of these functions for more information.

Minimal complete definition

ixList'

Instances

MkIxList ([] *) ixs a (IxList ixs a) Source # 

Methods

ixList' :: (IxList [*] a -> IxList ixs a) -> IxList ixs a

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

Methods

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

ixFun :: Ord ix => (a -> [ix]) -> Ix ix a Source #

Create a functional index. Provided function should return a list of indices where the value should be found.

getIndices :: Type -> [IndexType]
getIndices value = [...indices...]
instance Indexable '[IndexType] Type where
    indices = ixList (ixFun getIndices)

This is the recommended way to create indices.

ixGen :: forall proxy a ix. (Ord ix, Data a, Typeable ix) => proxy ix -> Ix ix a Source #

Create a generic index. Provided example is used only as type source so you may use a Proxy. This uses flatten to traverse values using their Data instances.

instance Indexable '[IndexType] Type where
    indices = ixList (ixGen (Proxy :: Proxy Type))

In production systems consider using ixFun in place of ixGen as the former one is much faster.

TH derivation of indices

noCalcs :: t -> () Source #

Function to be used as third argument in inferIxSet when you don't want any calculated values.

inferIxSet :: String -> Name -> Name -> [Name] -> Q [Dec] Source #

Template Haskell helper function for automatically building an Indexable instance from a data type, e.g.

data Foo = Foo Int String
  deriving (Eq, Ord, Data, Typeable)

and

inferIxSet "FooDB" ''Foo 'noCalcs [''Int, ''String]

will define:

type FooDB = IxSet '[Int, String] Foo
instance Indexable '[Int, String] Foo where
  ...

with Int and String as indices defined via

  ixFun (flattenWithCalcs noCalcs)

each.

WARNING: This function uses flattenWithCalcs for index generation, which in turn uses an SYB type-based traversal. It is often more efficient (and sometimes more correct) to explicitly define the indices using ixFun.

Changes to set

type IndexOp = forall k a. (Ord k, Ord a) => k -> a -> Map k (Set a) -> Map k (Set a) Source #

type SetOp = forall a. Ord a => a -> Set a -> Set a Source #

change :: forall ixs a. Indexable ixs a => SetOp -> IndexOp -> a -> IxSet ixs a -> IxSet ixs a Source #

Higher order operator for modifying IxSets. Use this when your final function should have the form a -> IxSet a -> IxSet a, e.g. insert or delete.

insert :: Indexable ixs a => a -> IxSet ixs a -> IxSet ixs a Source #

Inserts an item into the IxSet. If your data happens to have a primary key this function might not be what you want. See updateIx.

insertList :: forall ixs a. Indexable ixs a => [a] -> IxSet ixs a -> IxSet ixs a Source #

delete :: Indexable ixs a => a -> IxSet ixs a -> IxSet ixs a Source #

Removes an item from the IxSet.

updateIx :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> a -> IxSet ixs a -> IxSet ixs a Source #

Will replace the item with the given index of type ix. Only works if there is at most one item with that index in the IxSet. Will not change IxSet if you have more than one item with given index.

deleteIx :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a Source #

Will delete the item with the given index of type ix. Only works if there is at most one item with that index in the IxSet. Will not change IxSet if you have more than one item with given index.

Creation

empty :: Indexable ixs a => IxSet ixs a Source #

An empty IxSet.

fromSet :: Indexable ixs a => Set a -> IxSet ixs a Source #

Converts a Set to an IxSet.

fromList :: Indexable ixs a => [a] -> IxSet ixs a Source #

Converts a list to an IxSet.

Conversion

toSet :: IxSet ixs a -> Set a Source #

Converts an IxSet to a Set of its elements.

toList :: IxSet ixs a -> [a] Source #

Converts an IxSet to its list of elements.

toAscList :: forall proxy ix ixs a. IsIndexOf ix ixs => proxy ix -> IxSet ixs a -> [a] Source #

Converts an IxSet to its list of elements.

List will be sorted in ascending order by the index ix.

The list may contain duplicate entries if a single value produces multiple keys.

toDescList :: forall proxy ix ixs a. IsIndexOf ix ixs => proxy ix -> IxSet ixs a -> [a] Source #

Converts an IxSet to its list of elements.

List will be sorted in descending order by the index ix.

The list may contain duplicate entries if a single value produces multiple keys.

getOne :: Ord a => IxSet ixs a -> Maybe a Source #

If the IxSet is a singleton it will return the one item stored in it. If IxSet is empty or has many elements this function returns Nothing.

getOneOr :: Ord a => a -> IxSet ixs a -> a Source #

Like getOne with a user-provided default.

Size checking

size :: IxSet ixs a -> Int Source #

Returns the number of unique items in the IxSet.

null :: IxSet ixs a -> Bool Source #

Return True if the IxSet is empty, False otherwise.

Set operations

(&&&) :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a infixr 5 Source #

An infix intersection operation.

(|||) :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a infixr 5 Source #

An infix union operation.

union :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a Source #

Takes the union of the two IxSets.

intersection :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a Source #

Takes the intersection of the two IxSets.

Indexing

(@=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a Source #

Infix version of getEQ.

(@<) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a Source #

Infix version of getLT.

(@>) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a Source #

Infix version of getGT.

(@<=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a Source #

Infix version of getLTE.

(@>=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a Source #

Infix version of getGTE.

(@><) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a Source #

Returns the subset with indices in the open interval (k,k).

(@>=<) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a Source #

Returns the subset with indices in [k,k).

(@><=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a Source #

Returns the subset with indices in (k,k].

(@>=<=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a Source #

Returns the subset with indices in [k,k].

(@+) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> [ix] -> IxSet ixs a Source #

Creates the subset that has an index in the provided list.

(@*) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> [ix] -> IxSet ixs a Source #

Creates the subset that matches all the provided indices.

getEQ :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a Source #

Returns the subset with an index equal to the provided key. The set must be indexed over key type, doing otherwise results in runtime error.

getLT :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a Source #

Returns the subset with an index less than the provided key. The set must be indexed over key type, doing otherwise results in runtime error.

getGT :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a Source #

Returns the subset with an index greater than the provided key. The set must be indexed over key type, doing otherwise results in runtime error.

getLTE :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a Source #

Returns the subset with an index less than or equal to the provided key. The set must be indexed over key type, doing otherwise results in runtime error.

getGTE :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a Source #

Returns the subset with an index greater than or equal to the provided key. The set must be indexed over key type, doing otherwise results in runtime error.

getRange :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> ix -> IxSet ixs a -> IxSet ixs a Source #

Returns the subset with an index within the interval provided. The bottom of the interval is closed and the top is open, i. e. [k1;k2). The set must be indexed over key type, doing otherwise results in runtime error.

groupBy :: forall ix ixs a. IsIndexOf ix ixs => IxSet ixs a -> [(ix, [a])] Source #

Returns lists of elements paired with the indices determined by type inference.

groupAscBy :: forall ix ixs a. IsIndexOf ix ixs => IxSet ixs a -> [(ix, [a])] Source #

Returns lists of elements paired with the indices determined by type inference.

The resulting list will be sorted in ascending order by ix. The values in [a] will be sorted in ascending order as well.

groupDescBy :: IsIndexOf ix ixs => IxSet ixs a -> [(ix, [a])] Source #

Returns lists of elements paired with the indices determined by type inference.

The resulting list will be sorted in descending order by ix.

NOTE: The values in [a] are currently sorted in ascending order. But this may change if someone bothers to add toDescList. So do not rely on the sort order of the resulting list.

Index creation helpers

flatten :: (Typeable a, Data a, Typeable b) => a -> [b] Source #

Generically traverses the argument to find all occurences of values of type b and returns them as a list.

This function properly handles String as String not as [Char].

flattenWithCalcs :: (Data c, Typeable a, Data a, Typeable b) => (a -> c) -> a -> [b] Source #

Generically traverses the argument and calculated values to find all occurences of values of type b and returns them as a list. Equivalent to:

flatten (x,calcs x)

This function properly handles String as String not as [Char].

Debugging and optimization

stats :: Indexable ixs a => IxSet ixs a -> (Int, Int, Int, Int) Source #

Statistics about IxSet. This function returns quadruple consisting of

  1. total number of elements in the set
  2. number of declared indices
  3. number of keys in all indices
  4. number of values in all keys in all indices.

This can aid you in debugging and optimisation.