| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Hunt.ContextIndex
Description
The context index introduces contexts and combines the index, document table and schema.
- empty :: DocTable dt => ContextIndex dt
- insertContext :: Context -> IndexImpl -> ContextSchema -> ContextIndex dt -> ContextIndex dt
- deleteContext :: Context -> ContextIndex dt -> ContextIndex dt
- foreachContext :: (Functor m, Monad m) => [Context] -> (Context -> m res) -> m [(Context, res)]
- contexts :: ContextMap -> [Context]
- contextsM :: (Monad m, DocTable dt) => ContextIndex dt -> m [Context]
- hasContext :: Context -> ContextMap -> Bool
- hasContextM :: (Monad m, DocTable dt) => Context -> ContextIndex dt -> m Bool
- lookupRangeCx :: Monad m => Context -> Text -> Text -> ContextMap -> m [(Text, IntermediateValue)]
- lookupAllWithCx :: Monad m => Context -> ContextMap -> m [(Text, IntermediateValue)]
- searchWithCx :: Monad m => TextSearchOp -> Context -> Text -> ContextMap -> m [(Text, IntermediateValue)]
- searchWithCxsNormalized :: (Functor m, Monad m) => TextSearchOp -> [(Context, Text)] -> ContextMap -> m [(Context, [(Text, IntermediateValue)])]
- searchWithCxSc :: Monad m => TextSearchOp -> Context -> Text -> ContextMap -> m [(Text, (Score, Occurrences))]
- lookupRangeCxSc :: Monad m => Context -> Text -> Text -> ContextMap -> m [(Text, (Score, Occurrences))]
- insertList :: (MonadParallel m, Applicative m, DocTable dt) => [(DValue dt, Words)] -> ContextIndex dt -> m (ContextIndex dt)
- createDocTableFromPartition :: (MonadParallel m, DocTable dt) => [(DValue dt, Words)] -> m (dt, [(DocId, Words)])
- unionDocTables :: (DocTable dt, MonadParallel m) => [(dt, [(DocId, Words)])] -> dt -> m (dt, [(DocId, Words)])
- modifyWithDescription :: (MonadParallel m, Applicative m, DocTable dt) => Score -> Description -> Words -> DocId -> ContextIndex dt -> m (ContextIndex dt)
- delete :: (MonadParallel m, Applicative m, DocTable dt) => DocIdSet -> ContextIndex dt -> m (ContextIndex dt)
- deleteDocsByURI :: (MonadParallel m, Applicative m, DocTable dt) => Set URI -> ContextIndex dt -> m (ContextIndex dt)
- decodeCxIx :: (Binary dt, DocTable dt) => [IndexImpl] -> ByteString -> ContextIndex dt
- member :: (Monad m, Applicative m, DocTable dt) => URI -> ContextIndex dt -> m Bool
- data ContextIndex dt = ContextIndex {
- ciIndex :: !ContextMap
- ciDocs :: !dt
- newtype ContextMap = ContextMap {}
- type IndexRep = (ContextSchema, IndexImpl)
- mkContextMap :: Map Context IndexRep -> ContextMap
- mapToSchema :: ContextMap -> Schema
Construction
empty :: DocTable dt => ContextIndex dt Source
Contexts and Schema
insertContext :: Context -> IndexImpl -> ContextSchema -> ContextIndex dt -> ContextIndex dt Source
Inserts a new context.
deleteContext :: Context -> ContextIndex dt -> ContextIndex dt Source
Removes context (including the index and the schema).
foreachContext :: (Functor m, Monad m) => [Context] -> (Context -> m res) -> m [(Context, res)] Source
contexts :: ContextMap -> [Context] Source
Contexts/keys of ContextMap.
contextsM :: (Monad m, DocTable dt) => ContextIndex dt -> m [Context] Source
All contexts of the index.
hasContext :: Context -> ContextMap -> Bool Source
Check if the context exists.
hasContextM :: (Monad m, DocTable dt) => Context -> ContextIndex dt -> m Bool Source
Does the context exist?
Queries
lookupRangeCx :: Monad m => Context -> Text -> Text -> ContextMap -> m [(Text, IntermediateValue)] Source
Range query in a context between first and second key.
lookupAllWithCx :: Monad m => Context -> ContextMap -> m [(Text, IntermediateValue)] Source
Dump a context
searchWithCx :: Monad m => TextSearchOp -> Context -> Text -> ContextMap -> m [(Text, IntermediateValue)] Source
Search query in a context.
searchWithCxsNormalized :: (Functor m, Monad m) => TextSearchOp -> [(Context, Text)] -> ContextMap -> m [(Context, [(Text, IntermediateValue)])] Source
Search over a list of contexts and words
searchWithCxSc :: Monad m => TextSearchOp -> Context -> Text -> ContextMap -> m [(Text, (Score, Occurrences))] Source
Search query with scored results XXX TODO: this function should return intermediates and query processor should work with those
lookupRangeCxSc :: Monad m => Context -> Text -> Text -> ContextMap -> m [(Text, (Score, Occurrences))] Source
Range query in a context between first and second key. XXX TODO: this function should return intermediates and query processor should work with those
Insert/Delete Documents
insertList :: (MonadParallel m, Applicative m, DocTable dt) => [(DValue dt, Words)] -> ContextIndex dt -> m (ContextIndex dt) Source
Insert multiple documents and words.
createDocTableFromPartition :: (MonadParallel m, DocTable dt) => [(DValue dt, Words)] -> m (dt, [(DocId, Words)]) Source
unionDocTables :: (DocTable dt, MonadParallel m) => [(dt, [(DocId, Words)])] -> dt -> m (dt, [(DocId, Words)]) Source
modifyWithDescription :: (MonadParallel m, Applicative m, DocTable dt) => Score -> Description -> Words -> DocId -> ContextIndex dt -> m (ContextIndex dt) Source
Modify the description of a document and add words (occurrences for that document) to the index.
delete :: (MonadParallel m, Applicative m, DocTable dt) => DocIdSet -> ContextIndex dt -> m (ContextIndex dt) Source
Delete a set of documents by DocId.
deleteDocsByURI :: (MonadParallel m, Applicative m, DocTable dt) => Set URI -> ContextIndex dt -> m (ContextIndex dt) Source
Delete a set of documents by URI.
decodeCxIx :: (Binary dt, DocTable dt) => [IndexImpl] -> ByteString -> ContextIndex dt Source
Deserialize a ContextIndex with the list of available index implementations and a
map of available ContextSchema.
Note: The serialized index implementations have to be in the list of available types,
otherwise this will fail. The serialized schemas have to be in the list of
available ContextSchema, otherwise this will fail as well.
member :: (Monad m, Applicative m, DocTable dt) => URI -> ContextIndex dt -> m Bool Source
Is the document part of the index?
Types
data ContextIndex dt Source
Context index introduces contexts and combines the major components of Hunt.
Constructors
| ContextIndex | |
Fields
| |
Instances
| Binary dt => Binary (ContextIndex dt) |
type IndexRep = (ContextSchema, IndexImpl) Source
Contexts with associated heterogeneous index implementations.
mkContextMap :: Map Context IndexRep -> ContextMap Source
Strict smart constructor for the ContextMap.
mapToSchema :: ContextMap -> Schema Source
Get Schema from ContextMap