sphinx-0.6.1: Haskell bindings to the Sphinx full-text searching daemon.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Search.Sphinx.Types

Synopsis

Documentation

data Result a Source #

a result returned from searchd

Constructors

Ok a 
Warning Text a 
Error Int Text 
Retry Text 

Instances

Instances details
Show a => Show (Result a) Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

data Match Source #

Constructors

Match 

Instances

Instances details
Show Match Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Eq Match Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

(==) :: Match -> Match -> Bool #

(/=) :: Match -> Match -> Bool #

data Attr Source #

Instances

Instances details
Show Attr Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

data Query Source #

Data structure representing one query. It can be sent with runQueries or runQueries' to the server in batch mode.

Constructors

Query 

Fields

Instances

Instances details
Show Query Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

data VerCommand Source #

Current client-side command implementation versions

Instances

Instances details
Show VerCommand Source # 
Instance details

Defined in Text.Search.Sphinx.Types

data Filter Source #

Filter types

Instances

Instances details
Show Filter Source # 
Instance details

Defined in Text.Search.Sphinx.Types

data QueryStatus Source #

status from an individual query

Instances

Instances details
Show QueryStatus Source # 
Instance details

Defined in Text.Search.Sphinx.Types

data Status Source #

Searchd status codes

Constructors

OK 
RETRY 
WARNING 
ERROR Int 

Instances

Instances details
Show Status Source # 
Instance details

Defined in Text.Search.Sphinx.Types

data SingleResult Source #

a single query result, runQueries returns a list of these

Instances

Instances details
Show SingleResult Source # 
Instance details

Defined in Text.Search.Sphinx.Types

data QueryResult Source #

The result of a query

Constructors

QueryResult 

Fields

  • matches :: [Match]

    The matches

  • total :: Int

    Total amount of matches retrieved on server by this query.

  • totalFound :: Int

    Total amount of matching documents in index.

  • words :: [(Text, Int, Int)]

    processed words with the number of docs and the number of hits.

  • attributeNames :: [ByteString]

    List of attribute names returned in the result. | The Match will contain just the attribute values in the same order.

Instances

Instances details
Show QueryResult Source # 
Instance details

Defined in Text.Search.Sphinx.Types

data Rank Source #

Ranking modes (ext2 only)

Instances

Instances details
Enum Rank Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

succ :: Rank -> Rank #

pred :: Rank -> Rank #

toEnum :: Int -> Rank #

fromEnum :: Rank -> Int #

enumFrom :: Rank -> [Rank] #

enumFromThen :: Rank -> Rank -> [Rank] #

enumFromTo :: Rank -> Rank -> [Rank] #

enumFromThenTo :: Rank -> Rank -> Rank -> [Rank] #

Show Rank Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

data Sort Source #

Sort modes

Instances

Instances details
Enum Sort Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

succ :: Sort -> Sort #

pred :: Sort -> Sort #

toEnum :: Int -> Sort #

fromEnum :: Sort -> Int #

enumFrom :: Sort -> [Sort] #

enumFromThen :: Sort -> Sort -> [Sort] #

enumFromTo :: Sort -> Sort -> [Sort] #

enumFromThenTo :: Sort -> Sort -> Sort -> [Sort] #

Show Sort Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> Sort -> ShowS #

show :: Sort -> String #

showList :: [Sort] -> ShowS #

data AttrT Source #

Attribute types

Instances

Instances details
Enum AttrT Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Show AttrT Source # 
Instance details

Defined in Text.Search.Sphinx.Types

Methods

showsPrec :: Int -> AttrT -> ShowS #

show :: AttrT -> String #

showList :: [AttrT] -> ShowS #

verCommand :: Num a => VerCommand -> a Source #

Important! 2.0 compatible

exclude :: Filter -> Filter Source #

shortcut for creating an exclusion filter

toAttrT :: (Eq a, Num a) => a -> AttrT Source #

attrT :: Num a => AttrT -> a Source #

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A lazy ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Lazy.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Data ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Lazy.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Lazy.Internal

Associated Types

type Item ByteString #

Read ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

NFData ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

rnf :: ByteString -> () #

Eq ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Ord ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Lift ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

lift :: Quote m => ByteString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString #

type Item ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal