bloodhound-0.5.0.0: ElasticSearch client library for Haskell

Copyright(C) 2014 Chris Allen
LicenseBSD-style (see the file LICENSE)
MaintainerChris Allen <cma@bitemyapp.com
Stabilityprovisional
PortabilityDeriveGeneric, RecordWildCards
Safe HaskellNone
LanguageHaskell2010

Database.Bloodhound.Types

Description

Data types for describing actions and data structures performed to interact with Elasticsearch. The two main buckets your queries against Elasticsearch will fall into are Querys and Filters. Filters are more like traditional database constraints and often have preferable performance properties. Querys support human-written textual queries, such as fuzzy queries.

Synopsis

Documentation

mkSort :: FieldName -> SortOrder -> DefaultSort Source

mkSort defaults everything but the FieldName and the SortOrder so that you can concisely describe the usual kind of SortSpecs you want.

showText :: Show a => a -> Text Source

unpackId :: DocId -> String Source

unpackId is a silly convenience function that gets used once.

mkMatchQuery :: FieldName -> QueryString -> MatchQuery Source

mkMatchQuery is a convenience function that defaults the less common parameters, enabling you to provide only the FieldName and QueryString to make a MatchQuery

mkMultiMatchQuery :: [FieldName] -> QueryString -> MultiMatchQuery Source

mkMultiMatchQuery is a convenience function that defaults the less common parameters, enabling you to provide only the list of FieldNames and QueryString to make a MultiMatchQuery.

data Status Source

Status is a data type for describing the JSON body returned by Elasticsearch when you query its status. This was deprecated in 1.2.0.

http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/indices-status.html#indices-status

Constructors

Status 

Fields

ok :: Maybe Bool
 
status :: Int
 
name :: Text
 
version :: Version
 
tagline :: Text
 

newtype Existence Source

Constructors

Existence Bool 

newtype NullValue Source

Constructors

NullValue Bool 

newtype Server Source

Server is used with the client functions to point at the ES instance

Constructors

Server String 

Instances

type Reply = Response ByteString Source

Reply and Method are type synonyms from Method

data EsResult a Source

EsResult describes the standard wrapper JSON document that you see in successful Elasticsearch responses.

Constructors

EsResult 

Fields

_index :: Text
 
_type :: Text
 
_id :: Text
 
_version :: Int
 
found :: Maybe Bool
 
_source :: a
 

Instances

Eq a => Eq (EsResult a) 
Show a => Show (EsResult a) 
FromJSON a => FromJSON (EsResult a) 

data Search Source

Constructors

Search 

data SearchHits a Source

Constructors

SearchHits 

Fields

hitsTotal :: Int
 
maxScore :: Score
 
hits :: [Hit a]
 

Instances

Eq a => Eq (SearchHits a) 
Show a => Show (SearchHits a) 
FromJSON a => FromJSON (SearchHits a) 

data Hit a Source

Instances

Eq a => Eq (Hit a) 
Show a => Show (Hit a) 
FromJSON a => FromJSON (Hit a) 

class Monoid a => Seminearring a where Source

Minimal complete definition

(<||>)

Methods

(<||>) :: a -> a -> a infixr 5 Source

(<&&>) :: a -> a -> a infixr 5 Source

Instances

data Term Source

Constructors

Term 

Fields

termField :: Text
 
termValue :: Text
 

Instances

data LatLon Source

Constructors

LatLon 

Fields

lat :: Double
 
lon :: Double
 

newtype LessThan Source

Constructors

LessThan Double 

Instances

newtype LessThanEq Source

Constructors

LessThanEq Double 

newtype Regexp Source

Constructors

Regexp Text 

Instances

newtype FieldName Source

FieldName is used all over the place wherever a specific field within a document needs to be specified, usually in Querys or Filters.

Constructors

FieldName Text 

newtype IndexName Source

IndexName is used to describe which index to querycreatedelete

Constructors

IndexName String 

newtype MappingName Source

MappingName is part of mappings which are how ES describes and schematizes the data in the indices.

Constructors

MappingName String 

newtype DocId Source

DocId is a generic wrapper value for expressing unique Document IDs. Can be set by the user or created by ES itself. Often used in client functions for poking at specific documents.

Constructors

DocId String 

newtype CacheName Source

CacheName is used in RegexpFilter for describing the CacheKey keyed caching behavior.

Constructors

CacheName Text 

newtype CacheKey Source

CacheKey is used in RegexpFilter to key regex caching.

Constructors

CacheKey Text 

Instances

data BulkOperation Source

BulkOperation is a sum type for expressing the four kinds of bulk operation index, create, delete, and update. BulkIndex behaves like an "upsert", BulkCreate will fail if a document already exists at the DocId.

http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/docs-bulk.html#docs-bulk

type Sort = [SortSpec] Source

Sort is a synonym for a list of SortSpecs. Sort behavior is order dependent with later sorts acting as tie-breakers for earlier sorts.

data Missing Source

Missing prescribes how to handle missing fields. A missing field can be sorted last, first, or using a custom value as a substitute.

http://www.elasticsearch.org/guide/en/elasticsearch/reference/current/search-request-sort.html#_missing_values

newtype Boost Source

Constructors

Boost Double 

newtype QueryString Source

QueryString is used to wrap query text bodies, be they human written or not.

Constructors

QueryString Text 

data BooleanOperator Source

BooleanOperator is the usual And/Or operators with an ES compatible JSON encoding baked in. Used all over the place.

Constructors

And 
Or 

newtype Lenient Source

Lenient, if set to true, will cause format based failures to be ignored. I don't know what the bloody default is, Elasticsearch documentation didn't say what it was. Let me know if you figure it out.

Constructors

Lenient Bool 

newtype MinimumMatch Source

MinimumMatch controls how many should clauses in the bool query should match. Can be an absolute value (2) or a percentage (30%) or a combination of both.

Constructors

MinimumMatch Int 

newtype PrefixLength Source

PrefixLength is the prefix length used in queries, defaults to 0.

Constructors

PrefixLength Int 

newtype PhraseSlop Source

PhraseSlop sets the default slop for phrases, 0 means exact phrase matches. Default is 0.

Constructors

PhraseSlop Int 

data FieldDefinition Source

Constructors

FieldDefinition 

Fields

fieldType :: FieldType
 

data Mapping Source

Support for type reification of Mappings is currently incomplete, for now the mapping API verbiage expects a ToJSONable blob.

Indexes have mappings, mappings are schemas for the documents contained in the index. I'd recommend having only one mapping per index, always having a mapping, and keeping different kinds of documents separated if possible.

Constructors

Mapping 

Instances

newtype AllowLeadingWildcard Source

Allowing a wildcard at the beginning of a word (eg "*ing") is particularly heavy, because all terms in the index need to be examined, just in case they match. Leading wildcards can be disabled by setting AllowLeadingWildcard to false.

newtype Locale Source

Locale is used for string conversions - defaults to ROOT.

Constructors

Locale Text 

newtype AnalyzeWildcard Source

By default, wildcard terms in a query are not analyzed. Setting AnalyzeWildcard to true enables best-effort analysis.

Constructors

AnalyzeWildcard Bool 

class Monoid a where

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Minimal complete definition: mempty and mappend.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Minimal complete definition

mempty, mappend

Methods

mempty :: a

Identity of mappend

mappend :: a -> a -> a

An associative operation

mconcat :: [a] -> a

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 
Monoid ByteString 
Monoid Builder 
Monoid ByteString 
Monoid Text 
Monoid More 
Monoid Buffer 
Monoid Buffer 
Monoid All 
Monoid Any 
Monoid Text 
Monoid Builder 
Monoid IntSet 
Monoid CookieJar

Since 1.9

Monoid RequestBody 
Monoid Filter 
Monoid [a] 
Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Monoid (Result a) 
Monoid (Parser a) 
Monoid a => Monoid (Dual a) 
Monoid (Endo a) 
Num a => Monoid (Sum a) 
Num a => Monoid (Product a) 
Monoid (First a) 
Monoid (Last a) 
Monoid (IntMap a) 
Ord a => Monoid (Set a) 
Monoid (DList a) 
(Hashable a, Eq a) => Monoid (HashSet a) 
Monoid (Vector a) 
Unbox a => Monoid (Vector a) 
Storable a => Monoid (Vector a) 
Prim a => Monoid (Vector a) 
Monoid b => Monoid (a -> b) 
(Monoid a, Monoid b) => Monoid (a, b) 
(Eq k, Hashable k) => Monoid (HashMap k v) 
Ord k => Monoid (Map k v) 
Monoid (Parser i a) 
Monoid a => Monoid (Const a b) 
Monoid (Proxy * s) 
Typeable (* -> Constraint) Monoid 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

class ToJSON a where

A type that can be converted to JSON.

An example type and instance:

@{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance ToJSON Coord where toJSON (Coord x y) = object ["x" .= x, "y" .= y] @

Note the use of the OverloadedStrings language extension which enables Text values to be written as string literals.

Instead of manually writing your ToJSON instance, there are three options to do it automatically:

  • Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • Data.Aeson.Generic provides a generic toJSON function that accepts any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions (GHC 7.2 and newer), toJSON will have a default generic implementation.

To use the latter option, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving a definition for toJSON.

For example the previous example can be simplified to just:

@{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord = Coord { x :: Double, y :: Double } deriving Generic

instance ToJSON Coord @

Note that, instead of using DefaultSignatures, it's also possible to parameterize the generic encoding using genericToJSON applied to your encoding/decoding Options:

instance ToJSON Coord where
    toJSON = genericToJSON defaultOptions

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value

Instances

ToJSON Bool 
ToJSON Char 
ToJSON Double 
ToJSON Float 
ToJSON Int 
ToJSON Int8 
ToJSON Int16 
ToJSON Int32 
ToJSON Int64 
ToJSON Integer 
ToJSON Word 
ToJSON Word8 
ToJSON Word16 
ToJSON Word32 
ToJSON Word64 
ToJSON () 
ToJSON Scientific 
ToJSON Number 
ToJSON Text 
ToJSON UTCTime 
ToJSON Value 
ToJSON DotNetTime 
ToJSON Text 
ToJSON IntSet 
ToJSON ZonedTime 
ToJSON Aggregation 
ToJSON Interval 
ToJSON ExecutionHint 
ToJSON CollectionMode 
ToJSON TermInclusion 
ToJSON TermOrder 
ToJSON Distance 
ToJSON OptimizeBbox 
ToJSON DistanceType 
ToJSON DistanceUnit 
ToJSON GeoPoint 
ToJSON GeoBoundingBoxConstraint 
ToJSON GeoBoundingBox 
ToJSON LatLon 
ToJSON GeoFilterType 
ToJSON BoolMatch 
ToJSON Term 
ToJSON RegexpFlags 
ToJSON RangeExecution 
ToJSON ZeroTermsQuery 
ToJSON Filter 
ToJSON CommonMinimumMatch 
ToJSON CommonTermsQuery 
ToJSON BoostingQuery 
ToJSON BoolQuery 
ToJSON MultiMatchQueryType 
ToJSON MultiMatchQuery 
ToJSON MatchQueryType 
ToJSON MatchQuery 
ToJSON DisMaxQuery 
ToJSON FilteredQuery 
ToJSON FuzzyLikeThisQuery 
ToJSON FuzzyLikeFieldQuery 
ToJSON FuzzyQuery 
ToJSON ScoreType 
ToJSON HasChildQuery 
ToJSON HasParentQuery 
ToJSON IndicesQuery 
ToJSON MoreLikeThisQuery 
ToJSON MoreLikeThisFieldQuery 
ToJSON NestedQuery 
ToJSON PrefixQuery 
ToJSON FieldOrFields 
ToJSON QueryStringQuery 
ToJSON SimpleQueryFlag 
ToJSON SimpleQueryStringQuery 
ToJSON RangeQuery 
ToJSON RegexpQuery 
ToJSON Query 
ToJSON HighlightEncoder 
ToJSON HighlightSettings 
ToJSON FieldHighlight 
ToJSON Highlights 
ToJSON Search 
ToJSON MaxDocFrequency 
ToJSON MinDocFrequency 
ToJSON PhraseSlop 
ToJSON MinWordLength 
ToJSON MaxWordLength 
ToJSON Locale 
ToJSON GeneratePhraseQueries 
ToJSON AnalyzeWildcard 
ToJSON EnablePositionIncrements 
ToJSON LowercaseExpanded 
ToJSON AllowLeadingWildcard 
ToJSON QueryPath 
ToJSON StopWord 
ToJSON PercentMatch 
ToJSON TypeName 
ToJSON PrefixLength 
ToJSON Fuzziness 
ToJSON MaxQueryTerms 
ToJSON MinimumTermFrequency 
ToJSON IgnoreTermFrequency 
ToJSON DisableCoord 
ToJSON MinimumMatch 
ToJSON BoostTerms 
ToJSON Boost 
ToJSON Tiebreaker 
ToJSON Lenient 
ToJSON MaxExpansions 
ToJSON Analyzer 
ToJSON CutoffFrequency 
ToJSON FieldName 
ToJSON QueryString 
ToJSON DocId 
ToJSON MappingName 
ToJSON IndexName 
ToJSON ReplicaCount 
ToJSON ShardCount 
ToJSON BooleanOperator 
ToJSON SortMode 
ToJSON Missing 
ToJSON SortOrder 
ToJSON SortSpec 
ToJSON IndexSettings 
ToJSON Version 
ToJSON [Char] 
ToJSON a => ToJSON [a] 
ToJSON (Ratio Integer) 
ToJSON a => ToJSON (Maybe a) 
HasResolution a => ToJSON (Fixed a) 
ToJSON a => ToJSON (Dual a) 
ToJSON a => ToJSON (First a) 
ToJSON a => ToJSON (Last a) 
ToJSON a => ToJSON (IntMap a) 
ToJSON a => ToJSON (Set a) 
ToJSON v => ToJSON (Tree v) 
ToJSON a => ToJSON (HashSet a) 
ToJSON a => ToJSON (Vector a) 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
(Storable a, ToJSON a) => ToJSON (Vector a) 
(Prim a, ToJSON a) => ToJSON (Vector a) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 
(ToJSON a, ToJSON b) => ToJSON (a, b) 
ToJSON v => ToJSON (HashMap String v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (Map String v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (Map Text v) 
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

data Bucket a Source

Constructors

Bucket 

Fields

buckets :: [a]
 

Instances