hunt-searchengine-0.3.0.0: A search and indexing engine.

LicenseMIT
MaintainerUwe Schmidt
Stabilityexperimental
Portabilitynone portable
Safe HaskellNone
LanguageHaskell98

Hunt.ClientInterface

Contents

Description

Common data types and and smart constructors for calling a hunt server from a client.

Values of the Command datatype and its component types, e.g Query, ApiDocument, and others can be constructed with the "smart" construtors defined in this module

The module is intended to be imported qualified, eg like import qualified Hunt.ClientInterface as HI.

Synopsis

types used in commands

data Command Source

The "high-level" commands accepted by the Interpreter / JSON API. These are translated to BasicCommands.

data ApiDocument Source

The document accepted by the interpreter and JSON API.

Constructors

ApiDocument 

Fields

adUri :: URI

The unique identifier.

adIndex :: IndexMap

The data to index according to schema associated with the context.

adDescr :: Description

The document description (a simple key-value map).

adWght :: Score

An optional document boost, (internal default is 1.0).

class Huntable x where Source

Minimal complete definition

huntURI

type Content = Text Source

The content of a document.

type Context = Text Source

The name of a context.

data ContextSchema Source

The context schema information. Every context schema has a type and additional to adjust the behavior.

The regular expression splits the text into words which are then transformed by the given normalizations functions (e.g. to lower case).

type Description = DocDesc Source

The description of a document is a generic key value map.

type IndexMap = Map Context Content Source

Context map

type RegEx = Text Source

Regular expression.

data StatusCmd Source

Available status commands.

type URI = Text Source

The URI describing the location of the original document.

type Weight = Score Source

Weight (for ranking).

types used in results

data CmdError Source

An error during processing of the command. This includes a error code and a message.

Constructors

ResError 

Fields

ceCode :: Int

Error code.

ceMsg :: Text

Message describing the error.

newtype CmdRes a Source

auxiliary type for parsing JSON CmdResult's of various kinds

usefull in hunt applications, not used within the hunt server

Constructors

CmdRes 

Fields

unCmdRes :: a
 

Instances

Show a => Show (CmdRes a) 
FromJSON a => FromJSON (CmdRes a) 

data CmdResult Source

The result of an interpreted command.

Constructors

ResOK

The command was processed successfully.

ResSearch

The search results.

ResCompletion

The auto-completion results.

Fields

crWords :: [(Text, [Text])]
 
ResSuggestion

The simplified completion result

Fields

crSugg :: [(Text, Score)]
 
ResGeneric

A generic JSON result.

Fields

crGen :: Value
 

data LimitedResult x Source

Paginated result with an offset and chunk size.

Constructors

LimitedResult 

Fields

lrResult :: [x]

The list with at most lrMax elements.

lrOffset :: Int

The offset of the result.

lrMax :: Int

The limit for the result.

lrCount :: Int

The size of the complete result.

data Score Source

The score of a hit (either a document hit or a word hit). type Score = Float

Weight or score of a documents, 0.0 indicates: not set, so there is no need to work with Maybe's wrapped in newtype to not mix up with Score's and Weight's in documents

Instances

Eq Score 
Fractional Score 
Num Score 
Ord Score 
Show Score 
ToJSON Score 
FromJSON Score 
Monoid Score 
Binary Score 
NFData Score 
Aggregate ScoredOccs Score

aggregate scored occurences to a score by aggregating first the positions and snd the doc ids

used in computing the score of word in completion search

Aggregate ScoredDocs Score

aggregate scored docs to a single score by summing up the scores and throw away the DocIds

command construction

cmdSearch :: Query -> Command Source

create simple search command

cmdCompletion :: Query -> Command Source

Create simple completion command

cmdInsertDoc :: ApiDocument -> Command Source

insert document

cmdUpdateDoc :: ApiDocument -> Command Source

update document

cmdDeleteDoc :: URI -> Command Source

delete document identified by an URI

cmdDeleteDocsByQuery :: Query -> Command Source

delete all documents idenitfied by a query

configuration options for search and completion

setSelectedFields :: [Text] -> Command -> Command Source

configure search command: set the list of attributes of the document decription to be included in the result list

example: setSelectedFields ["title", "date"] restricts the documents attributes to these to fields

setMaxResults :: Int -> Command -> Command Source

configure search and completion command: set the max # of results

setResultOffset :: Int -> Command -> Command Source

configure search command: set the starting offset of the result list

setWeightIncluded :: Command -> Command Source

configure search command: include document weight in result list

Misc

createContextCommands :: [ApiDocument] -> Command Source

create InsertContext Commands by a list of Insert Commands These contexts are not optimized and shoudn't be used in production code.

ApiDocument construction, configuration and access

mkApiDoc :: URI -> ApiDocument Source

build an api document with an uri as key and a description map as contents

setDescription :: Description -> ApiDocument -> ApiDocument Source

add an index map containing the text parts to be indexed

setIndex :: IndexMap -> ApiDocument -> ApiDocument Source

add an index map containing the text parts to be indexed

setDocWeight :: Score -> ApiDocument -> ApiDocument Source

add a document weight

Misc

listToApiDoc Source

Arguments

:: Text

The uri

-> [(Text, Text)]

The index

-> [(Text, Text)]

The description

-> ApiDocument 

wrapper for building an ApiDocument by lists

description construction

Queries

data Query Source

The query language.

query parsing

parseQuery :: String -> Either Text Query Source

Parse a query using the default syntax provided by the Hunt framework.

query construction

pretty printing

printQuery :: Query -> Text Source

Renders a text representation of a Query.

query completion

schema definition

mkSchema :: ContextSchema Source

the default schema: context type is text, no normalizers, weigth is 1.0, context is always searched by queries without context spec

setCxNoDefault :: ContextSchema -> ContextSchema Source

prevent searching in context, when not explicitly set in query

setCxWeight :: Float -> ContextSchema -> ContextSchema Source

set the regex for splitting a text into words

setCxRegEx :: RegEx -> ContextSchema -> ContextSchema Source

set the regex for splitting a text into words

setCxUpperCase :: ContextSchema -> ContextSchema Source

add a text normalizer for transformation into uppercase

setCxLowerCase :: ContextSchema -> ContextSchema Source

add a text normalizer for transformation into lowercase

setCxZeroFill :: ContextSchema -> ContextSchema Source

add a text normalizer for transformation into lowercase

setCxText :: ContextSchema -> ContextSchema Source

set the type of a context to text

setCxInt :: ContextSchema -> ContextSchema Source

set the type of a context to Int

setCxDate :: ContextSchema -> ContextSchema Source

set the type of a context to Date

setCxPosition :: ContextSchema -> ContextSchema Source

set the type of a context to Int

Weights and Scores

sendCmdToFile :: String -> Command -> IO () Source

send command as JSON into a file

the JSON is pretty printed with aeson-pretty, "" and "-" are used for output to stdout