| Safe Haskell | None |
|---|
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)
- Decide what parts of your type you want indexed and make your type
an instance of
Indexable. UseixFunandixGento 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.
entries = insertList [e1, e2, e3, e4] (empty :: IxEntry) entries1 = foldr delete entries [e1, e3] entries2 = updateIx (Id 4) e5 entries
- 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.
- 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"]
- 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
- data IxSet ixs a
- data IxList ixs a
- class (All Ord ixs, Ord a) => Indexable ixs a where
- class Ord ix => IsIndexOf ix ixs
- type family All c xs :: Constraint
- data Ix ix a
- ixList :: MkIxList ixs ixs a r => r
- class MkIxList ixs ixs' a r | r -> a ixs ixs'
- ixFun :: Ord ix => (a -> [ix]) -> Ix ix a
- ixGen :: forall proxy a ix. (Ord ix, Data a, Typeable ix) => proxy ix -> Ix ix a
- noCalcs :: t -> ()
- inferIxSet :: String -> Name -> Name -> [Name] -> Q [Dec]
- type IndexOp = forall k a. (Ord k, Ord a) => k -> a -> Map k (Set a) -> Map k (Set a)
- type SetOp = forall a. Ord a => a -> Set a -> Set a
- change :: forall ixs a. Indexable ixs a => SetOp -> IndexOp -> a -> IxSet ixs a -> IxSet ixs a
- insert :: Indexable ixs a => a -> IxSet ixs a -> IxSet ixs a
- insertList :: forall ixs a. Indexable ixs a => [a] -> IxSet ixs a -> IxSet ixs a
- delete :: Indexable ixs a => a -> IxSet ixs a -> IxSet ixs a
- updateIx :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> a -> IxSet ixs a -> IxSet ixs a
- deleteIx :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a
- empty :: Indexable ixs a => IxSet ixs a
- fromSet :: Indexable ixs a => Set a -> IxSet ixs a
- fromList :: Indexable ixs a => [a] -> IxSet ixs a
- toSet :: IxSet ixs a -> Set a
- toList :: IxSet ixs a -> [a]
- toAscList :: forall proxy ix ixs a. IsIndexOf ix ixs => proxy ix -> IxSet ixs a -> [a]
- toDescList :: forall proxy ix ixs a. IsIndexOf ix ixs => proxy ix -> IxSet ixs a -> [a]
- getOne :: Ord a => IxSet ixs a -> Maybe a
- getOneOr :: Ord a => a -> IxSet ixs a -> a
- size :: IxSet ixs a -> Int
- null :: IxSet ixs a -> Bool
- (&&&) :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a
- (|||) :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a
- union :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a
- intersection :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs a
- (@=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a
- (@<) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a
- (@>) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a
- (@<=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a
- (@>=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs a
- (@><) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a
- (@>=<) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a
- (@><=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a
- (@>=<=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs a
- (@+) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> [ix] -> IxSet ixs a
- (@*) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> [ix] -> IxSet ixs a
- getEQ :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a
- getLT :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a
- getGT :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a
- getLTE :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a
- getGTE :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs a
- getRange :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> ix -> IxSet ixs a -> IxSet ixs a
- groupBy :: forall ix ixs a. IsIndexOf ix ixs => IxSet ixs a -> [(ix, [a])]
- groupAscBy :: forall ix ixs a. IsIndexOf ix ixs => IxSet ixs a -> [(ix, [a])]
- groupDescBy :: IsIndexOf ix ixs => IxSet ixs a -> [(ix, [a])]
- flatten :: (Typeable a, Data a, Typeable b) => a -> [b]
- flattenWithCalcs :: (Data c, Typeable a, Data a, Typeable b) => (a -> c) -> a -> [b]
- stats :: Indexable ixs a => IxSet ixs a -> (Int, Int, Int, Int)
Set type
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) | |
| Indexable ixs a => Eq (IxSet ixs a) | |
| Indexable ixs a => Ord (IxSet ixs a) | |
| (Indexable ixs a, Read a) => Read (IxSet ixs a) | |
| (Indexable ixs a, Show a) => Show (IxSet ixs a) | |
| Indexable ixs a => Monoid (IxSet ixs a) | |
| (All NFData ixs, NFData a) => NFData (IxSet ixs a) | |
| (Indexable ixs a, SafeCopy a) => SafeCopy (IxSet ixs a) |
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.
type family All c xs :: ConstraintSource
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)
Declaring indices
ixList :: MkIxList ixs ixs a r => rSource
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.
ixFun :: Ord ix => (a -> [ix]) -> Ix ix aSource
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 aSource
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
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
change :: forall ixs a. Indexable ixs a => SetOp -> IndexOp -> a -> IxSet ixs a -> IxSet ixs aSource
insertList :: forall ixs a. Indexable ixs a => [a] -> IxSet ixs a -> IxSet ixs aSource
Creation
Conversion
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.
Size checking
Set operations
(&&&) :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs aSource
An infix intersection operation.
(|||) :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs aSource
An infix union operation.
union :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs aSource
Takes the union of the two IxSets.
intersection :: Indexable ixs a => IxSet ixs a -> IxSet ixs a -> IxSet ixs aSource
Takes the intersection of the two IxSets.
Indexing
(@=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs aSource
Infix version of getEQ.
(@<) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs aSource
Infix version of getLT.
(@>) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs aSource
Infix version of getGT.
(@<=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs aSource
Infix version of getLTE.
(@>=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> ix -> IxSet ixs aSource
Infix version of getGTE.
(@><) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs aSource
Returns the subset with indices in the open interval (k,k).
(@>=<) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs aSource
Returns the subset with indices in [k,k).
(@><=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs aSource
Returns the subset with indices in (k,k].
(@>=<=) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> (ix, ix) -> IxSet ixs aSource
Returns the subset with indices in [k,k].
(@+) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> [ix] -> IxSet ixs aSource
Creates the subset that has an index in the provided list.
(@*) :: (Indexable ixs a, IsIndexOf ix ixs) => IxSet ixs a -> [ix] -> IxSet ixs aSource
Creates the subset that matches all the provided indices.
getEQ :: (Indexable ixs a, IsIndexOf ix ixs) => ix -> IxSet ixs a -> IxSet ixs aSource
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 aSource
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 aSource
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 aSource
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 aSource
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 aSource
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
Debugging and optimization
stats :: Indexable ixs a => IxSet ixs a -> (Int, Int, Int, Int)Source
Statistics about IxSet. This function returns quadruple
consisting of
- 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.