happstack-ixset-0.2.1: Efficient relational queries on Haskell sets.Source codeContentsIndex
Happstack.Data.IxSet
Description

Assume you have a type like:

data Entry = Entry Author [Author] Updated Id Content
  newtype Updated = Updated EpochTime
  newtype Id = Id Int64
  newtype Content = Content String
  newtype Author = Author Email
  type Email = String

1. Decide what parts of your type you want indexed, and make your type an instance of Indexable

instance Indexable Entry () where
    empty = IxSet[
                ,Ix (Map.empty::Map Author (Set Entry)) --out of order
                ,Ix (Map.empty::Map Id (Set Entry))
                ,Ix (Map.empty::Map Updated (Set Entry))
                ,Ix (Map.empty::Map Test (Set Entry)) -- bogus index
                ,Ix (Map.empty::Map Word (Set Entry)) -- text index
                ]
    calcs entry = () -- words for text indexing purposes

3. Use insert,delete,replace and empty to build up an IxSet collection

entries = foldr insert empty [e1,e2,e3,e4] entries' = foldr delete entries [e1,e3] entries'' = update e4 e5 entries

4. Use the query functions below to grab data from it. e.g.

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

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

5. Text Index

If you want to do add a text index extract the words in entry and pass them in the calc method of the Indexable class. Then if you want all entries with either word1 or word2, you change the instance to

getWords entry = let Just (Content s) =
                                     gGet entry in map Word $ words s
instance Indexable Entry [Word] where
    ....
    calcs entry = getWords entry

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"]

6. Find the only the first author

If an Entry has multiple authors and you want to be able to query on the first author, define a FirstAuthor datatype and add it to the result of calc. calc e=(toWords e,getFirstAuthor e) and now you can do

newtype FirstAuthor = FirstAuthor Email getFirstAuthor = let Just (Author a)=gGet Entry in FirstAuthor a

instance Indexable Entry ([Word],FirstAuthor)
    ...
    empty = ....
             Ix (Map.empty::Map FirstAuthor (Set Entry))]
    calcs entry = (getWords Entry,getFirstAuthor entry)

entries @= (FirstAuthor "john@doe.com")  -- guess what this does
Synopsis
data IxSet a
= ISet [a]
| IxSet [Ix a]
iSetConstr :: Constr
ixSetConstr :: Constr
ixSetDataType :: DataType
class Data b => Indexable a b | a -> b where
empty :: IxSet a
calcs :: a -> b
noCalcs :: t -> ()
inferIxSet :: String -> Name -> Name -> [Name] -> Q [Dec]
flatten :: (Typeable a, Data a) => a -> [Dynamic]
type IndexOp = forall k a. (Ord k, Ord a) => k -> a -> Map k (Set a) -> Map k (Set a)
change :: (Data a, Ord a, Data b, Indexable a b) => IndexOp -> a -> IxSet a -> IxSet a
insert :: (Data a, Ord a, Data b, Indexable a b) => a -> IxSet a -> IxSet a
delete :: (Data a, Ord a, Data b, Indexable a b) => a -> IxSet a -> IxSet a
updateIx :: (Indexable a b, Ord a, Data a, Typeable k) => k -> a -> IxSet a -> IxSet a
toSet :: Ord a => IxSet a -> Set a
toSet' :: Ord a => [Ix a] -> Set a
fromSet :: (Indexable a b, Ord a, Data a) => Set a -> IxSet a
fromSet' :: (Indexable a b, Ord a, Data a) => Set a -> IxSet a
fromList :: (Indexable a b, Ord a, Data a) => [a] -> IxSet a
size :: Ord a => IxSet a -> Int
toList :: Ord a => IxSet a -> [a]
toList' :: Ord a => [Ix a] -> [a]
getOne :: Ord a => IxSet a -> Maybe a
getOneOr :: Ord a => a -> IxSet a -> a
(&&&) :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet a
(|||) :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet a
union :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet a
intersection :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet a
(@=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet a
(@<) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet a
(@>) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet a
(@<=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet a
(@>=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet a
(@><) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet a
(@>=<) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet a
(@><=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet a
(@>=<=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet a
(@+) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> [k] -> IxSet a
(@*) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> [k] -> IxSet a
getEQ :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet a
getLT :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet a
getGT :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet a
getLTE :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet a
getGTE :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet a
getRange :: (Indexable a b, Typeable k, Ord a, Data a) => k -> k -> IxSet a -> IxSet a
groupBy :: (Typeable k, Typeable t) => IxSet t -> [(k, [t])]
rGroupBy :: (Typeable k, Typeable t) => IxSet t -> [(k, [t])]
getOrd :: (Indexable a b, Ord a, Data a, Typeable k) => Ordering -> k -> IxSet a -> IxSet a
module Ix
Documentation
data IxSet a Source
Constructors
ISet [a]
IxSet [Ix a]
show/hide Instances
Typeable1 IxSet
(Data ctx a, Sat (ctx (IxSet a)), Sat (ctx ([] a)), Indexable a b, Data a, Ord a) => Data ctx (IxSet a)
Data a => Data (IxSet a)
(Ord a, Read a, Data a, Indexable a b) => Read (IxSet a)
(Ord a, Show a) => Show (IxSet a)
(Show a, Indexable a b, Data a, Ord a) => Monoid (IxSet a)
Version (IxSet a)
(Serialize a, Ord a, Data a, Indexable a b) => Serialize (IxSet a)
(Indexable a b, Data a, Ord a, Default a) => Default (IxSet a)
iSetConstr :: ConstrSource
ixSetConstr :: ConstrSource
ixSetDataType :: DataTypeSource
class Data b => Indexable a b | a -> b whereSource
empty defines what an empty IxSet for this particular type should look like. calcs adds indexable values not found in the type. If you don't want calculated values use Indexable a ().
Methods
empty :: IxSet aSource
calcs :: a -> bSource
show/hide Instances
noCalcs :: t -> ()Source
Function to be used for calcs in the case of an Indexable a () instance
inferIxSet :: String -> Name -> Name -> [Name] -> Q [Dec]Source
flatten :: (Typeable a, Data a) => a -> [Dynamic]Source
Generically traverses the argument and converts all data in it to Dynamic and returns all the iternal data as a list of Dynamic
type IndexOp = forall k a. (Ord k, Ord a) => k -> a -> Map k (Set a) -> Map k (Set a)Source
change :: (Data a, Ord a, Data b, Indexable a b) => IndexOp -> a -> IxSet a -> IxSet aSource
Higher order operator for modifying IxSets. Use this when your final function should have the form a->IxSet a->IxSet a, e.g. insert.
insert :: (Data a, Ord a, Data b, Indexable a b) => a -> IxSet a -> IxSet aSource
Inserts an item into the IxSet
delete :: (Data a, Ord a, Data b, Indexable a b) => a -> IxSet a -> IxSet aSource
Removes an item from the IxSet
updateIx :: (Indexable a b, Ord a, Data a, Typeable k) => k -> a -> IxSet a -> IxSet aSource
Will replace the item with index k. Only works if there is at most one item with that index in the IxSet.
toSet :: Ord a => IxSet a -> Set aSource
Converts an IxSet to a Set of its elements
toSet' :: Ord a => [Ix a] -> Set aSource
Takes a list of Ixs and converts it into a Set
fromSet :: (Indexable a b, Ord a, Data a) => Set a -> IxSet aSource
Converts a Set to an IxSet
fromSet' :: (Indexable a b, Ord a, Data a) => Set a -> IxSet aSource
Converts a Set to an IxSet
fromList :: (Indexable a b, Ord a, Data a) => [a] -> IxSet aSource
Converts a list to an IxSet
size :: Ord a => IxSet a -> IntSource
Returns the number of unique items in the IxSet
toList :: Ord a => IxSet a -> [a]Source
Converts an IxSet to its list of elements.
toList' :: Ord a => [Ix a] -> [a]Source
Converts a list of Ix's
getOne :: Ord a => IxSet a -> Maybe aSource
If the IxSet is a singleton it will return the one item stored, else Nothing.
getOneOr :: Ord a => a -> IxSet a -> aSource
getOne with a user provided default
(&&&) :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet aSource
An infix intersection operation
(|||) :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet aSource
An infix union operation
union :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet aSource
Takes the union of the two IxSets
intersection :: (Ord a, Data a, Indexable a b) => IxSet a -> IxSet a -> IxSet aSource
Takes the intersection of the two IxSets
(@=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet aSource
Infix version of getEQ
(@<) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet aSource
Infix version of getLT
(@>) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet aSource
Infix version of getGT
(@<=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet aSource
Infix version of getLTE
(@>=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> k -> IxSet aSource
Infix version of getGTE
(@><) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet aSource
Returns the subset with indices in the open interval (k,k)
(@>=<) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet aSource
Returns the subset with indices in [k,k)
(@><=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet aSource
Returns the subset with indices in (k,k]
(@>=<=) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> (k, k) -> IxSet aSource
Returns the subset with indices in [k,k]
(@+) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> [k] -> IxSet aSource
Creates the subset that has an index in the provided list.
(@*) :: (Indexable a b, Data a, Ord a, Typeable k) => IxSet a -> [k] -> IxSet aSource
Creates the subset that matches all the provided indices.
getEQ :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet aSource
Returns the subset with an index equal to the provided key. It is possible to provide a key of a type not indexed in the IxSet. In this case the function returns the empty IxSet for this type.
getLT :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet aSource
Returns the subset with an index less than the provided key. It is possible to provide a key of a type not indexed in the IxSet. In this case the function returns the empty IxSet for this type.
getGT :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet aSource
Returns the subset with an index greater than the provided key. It is possible to provide a key of a type not indexed in the IxSet. In this case the function returns the empty IxSet for this type.
getLTE :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet aSource
Returns the subset with an index less than or equal to the provided key. It is possible to provide a key of a type not indexed in the IxSet. In this case the function returns the empty IxSet for this type.
getGTE :: (Indexable a b, Data a, Ord a, Typeable k) => k -> IxSet a -> IxSet aSource
Returns the subset with an index greater than or equal to the provided key. It is possible to provide a key of a type not indexed in the IxSet. In this case the function returns the empty IxSet for this type.
getRange :: (Indexable a b, Typeable k, Ord a, Data a) => k -> k -> IxSet a -> IxSet aSource
Returns the subset with an index within the interval provided. The top of the interval is closed and the bottom is open. It is possible to provide a key of a type not indexed in the IxSet. In this case the function returns the empty IxSet for this type.
groupBy :: (Typeable k, Typeable t) => IxSet t -> [(k, [t])]Source
Returns lists of elements paired with the indices determined by type inference.
rGroupBy :: (Typeable k, Typeable t) => IxSet t -> [(k, [t])]Source
A reversed groupBy
getOrd :: (Indexable a b, Ord a, Data a, Typeable k) => Ordering -> k -> IxSet a -> IxSet aSource
A function for building up selectors on IxSets. Used in the various get* functions.
module Ix
Produced by Haddock version 2.4.2