bloodhound-0.11.0.0: ElasticSearch client library for Haskell

Copyright(C) 2014, 2015, 2016 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

defaultIndexDocumentSettings :: IndexDocumentSettings Source

Reasonable default settings. Chooses no version control and no parent.

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 -> Text 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.

mkDocVersion :: Int -> Maybe DocVersion Source

Smart constructor for in-range doc version

runBH :: BHEnv -> BH m a -> m a Source

data BHEnv Source

Common environment for Elasticsearch calls. Connections will be pipelined according to the provided HTTP connection manager.

Instances

bhRequestHook :: BHEnv -> Request -> IO Request Source

Low-level hook that is run before every request is sent. Used to implement custom authentication strategies. Defaults to return with mkBHEnv.

mkBHEnv :: Server -> Manager -> BHEnv Source

Create a BHEnv with all optional fields defaulted. HTTP hook will be a noop. You can use the exported fields to customize it further, e.g.:

> (mkBHEnv myServer myManager) { bhRequestHook = customHook }

class (Functor m, Applicative m, MonadIO m) => MonadBH m where Source

All API calls to Elasticsearch operate within MonadBH . The idea is that it can be easily embedded in your own monad transformer stack. A default instance for a ReaderT and alias BH is provided for the simple case.

Methods

getBHEnv :: m BHEnv Source

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
 

data UpdatableIndexSetting Source

Constructors

NumberOfReplicas ReplicaCount

The number of replicas each shard has.

AutoExpandReplicas ReplicaBounds 
BlocksReadOnly Bool

Set to True to have the index read only. False to allow writes and metadata changes.

BlocksRead Bool

Set to True to disable read operations against the index.

BlocksWrite Bool

Set to True to disable write operations against the index.

BlocksMetaData Bool

Set to True to disable metadata operations against the index.

RefreshInterval NominalDiffTime

The async refresh interval of a shard

IndexConcurrency Int 
FailOnMergeFailure Bool 
TranslogFlushThresholdOps Int

When to flush on operations.

TranslogFlushThresholdSize Bytes

When to flush based on translog (bytes) size.

TranslogFlushThresholdPeriod NominalDiffTime

When to flush based on a period of not flushing.

TranslogDisableFlush Bool

Disables flushing. Note, should be set for a short interval and then enabled.

CacheFilterMaxSize (Maybe Bytes)

The maximum size of filter cache (per segment in shard).

CacheFilterExpire (Maybe NominalDiffTime)

The expire after access time for filter cache.

GatewaySnapshotInterval NominalDiffTime

The gateway snapshot interval (only applies to shared gateways).

RoutingAllocationInclude (NonEmpty NodeAttrFilter)

A node matching any rule will be allowed to host shards from the index.

RoutingAllocationExclude (NonEmpty NodeAttrFilter)

A node matching any rule will NOT be allowed to host shards from the index.

RoutingAllocationRequire (NonEmpty NodeAttrFilter)

Only nodes matching all rules will be allowed to host shards from the index.

RoutingAllocationEnable AllocationPolicy

Enables shard allocation for a specific index.

RoutingAllocationShardsPerNode ShardCount

Controls the total number of shards (replicas and primaries) allowed to be allocated on a single node.

RecoveryInitialShards InitialShardCount

When using local gateway a particular shard is recovered only if there can be allocated quorum shards in the cluster.

GCDeletes NominalDiffTime 
TTLDisablePurge Bool

Disables temporarily the purge of expired docs.

TranslogFSType FSType 
IndexCompoundFormat CompoundFormat 
IndexCompoundOnFlush Bool 
WarmerEnabled Bool 

data AllocationPolicy Source

Constructors

AllocAll

Allows shard allocation for all shards.

AllocPrimaries

Allows shard allocation only for primary shards.

AllocNewPrimaries

Allows shard allocation only for primary shards for new indices.

AllocNone

No shard allocation is allowed

data IndexTemplate Source

An IndexTemplate defines a template that will automatically be applied to new indices created. The templates include both IndexSettings and mappings, and a simple TemplatePattern that controls if the template will be applied to the index created. Specify mappings as follows: [toJSON TweetMapping, ...]

https://www.elastic.co/guide/en/elasticsearch/reference/1.7/indices-templates.html

newtype Server Source

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

Constructors

Server Text 

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 lookups or lookups that couldn't find the document.

Constructors

EsResult 

Instances

data EsResultFound a Source

EsResultFound contains the document and its metadata inside of an EsResult when the document was successfully found.

Constructors

EsResultFound 

Fields

_version :: DocVersion
 
_source :: a
 

data EsError Source

EsError is the generic type that will be returned when there was a problem. If you can't parse the expected response, its a good idea to try parsing this.

Constructors

EsError 

data EsProtocolException Source

EsProtocolException will be thrown if Bloodhound cannot parse a response returned by the ElasticSearch server. If you encounter this error, please verify that your domain data types and FromJSON instances are working properly (for example, the a of '[Hit a]' in 'SearchResult.searchHits.hits'). If you're sure that your mappings are correct, then this error may be an indication of an incompatibility between Bloodhound and ElasticSearch. Please open a bug report and be sure to include the exception body.

data VersionControl Source

VersionControl is specified when indexing documents as a optimistic concurrency control.

Constructors

NoVersionControl

Don't send a version. This is a pure overwrite.

InternalVersion DocVersion

Use the default ES versioning scheme. Only index the document if the version is the same as the one specified. Only applicable to updates, as you should be getting Version from a search result.

ExternalGT ExternalDocVersion

Use your own version numbering. Only index the document if the version is strictly higher OR the document doesn't exist. The given version will be used as the new version number for the stored document. N.B. All updates must increment this number, meaning there is some global, external ordering of updates.

ExternalGTE ExternalDocVersion

Use your own version numbering. Only index the document if the version is equal or higher than the stored version. Will succeed if there is no existing document. The given version will be used as the new version number for the stored document. Use with care, as this could result in data loss.

ForceVersion ExternalDocVersion

The document will always be indexed and the given version will be the new version. This is typically used for correcting errors. Use with care, as this could result in data loss.

data IndexDocumentSettings Source

IndexDocumentSettings are special settings supplied when indexing a document. For the best backwards compatiblity when new fields are added, you should probably prefer to start with defaultIndexDocumentSettings

data Hit a Source

Instances

Eq a => Eq (Hit a) Source 
Show a => Show (Hit a) Source 
Generic (Hit a) Source 
FromJSON a => FromJSON (Hit a) Source 
type Rep (Hit a) Source 

class Monoid a => Seminearring a where Source

Minimal complete definition

(<||>)

Methods

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

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

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 Script Source

Script is often used in place of FieldName to specify more complex ways of extracting a value from a document.

Constructors

Script 

Fields

scriptText :: Text
 

newtype IndexName Source

IndexName is used to describe which index to querycreatedelete

Constructors

IndexName Text 

data IndexSelection Source

IndexSelection is used for APIs which take a single index, a list of indexes, or the special _all index.

data IndexOptimizationSettings Source

Constructors

IndexOptimizationSettings 

Fields

maxNumSegments :: Maybe Int

Number of segments to optimize to. 1 will fully optimize the index. If omitted, the default behavior is to only optimize if the server deems it necessary.

onlyExpungeDeletes :: Bool

Should the optimize process only expunge segments with deletes in them? If the purpose of the optimization is to free disk space, this should be set to True.

flushAfterOptimize :: Bool

Should a flush be performed after the optimize.

defaultIndexOptimizationSettings :: IndexOptimizationSettings Source

defaultIndexOptimizationSettings implements the default settings that ElasticSearch uses for index optimization. maxNumSegments is Nothing, onlyExpungeDeletes is False, and flushAfterOptimize is True.

newtype MappingName Source

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

Constructors

MappingName Text 

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 Text 

newtype CacheName Source

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

Constructors

CacheName Text 

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

type Cache = Bool Source

Cache is for telling ES whether it should cache a Filter not. Querys cannot be cached.

newtype PhraseSlop Source

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

Constructors

PhraseSlop Int 

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 

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.

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 ByteString 
Monoid Builder 
Monoid Encoding 
Monoid Series 
Monoid Buffer 
Monoid Buffer 
Monoid More 
Monoid All 
Monoid Any 
Monoid ShortByteString 
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 (IResult a) 
Monoid (Result a) 
Monoid (Parser a) 
Ord a => Monoid (Max a) 
Ord a => Monoid (Min 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 (Seq a) 
Monoid (DList a) 
(Ord a, Bounded a) => Monoid (Min a) 
(Ord a, Bounded a) => Monoid (Max a) 
Monoid m => Monoid (WrappedMonoid m) 
Semigroup a => Monoid (Option a) 
(Hashable a, Eq a) => Monoid (HashSet a) 
Monoid (Vector a) 
Storable a => Monoid (Vector a) 
Prim a => Monoid (Vector a) 
Monoid (SearchHits 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 k s) 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
Alternative f => Monoid (Alt * f a) 
Monoid a => Monoid (Tagged k s a) 
(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:

-- Allow ourselves to write Text literals.
{-# LANGUAGE OverloadedStrings #-}

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

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

  toEncoding (Coord x y) = pairs ("x" .= x <> "y" .= y)

Instead of manually writing your ToJSON instance, there are two 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:
  • The compiler can provide a default generic implementation for toJSON.

To use the second, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving definitions for toJSON or toEncoding.

For example, the previous example can be simplified to a more minimal instance:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

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

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

Why do we provide an implementation for toEncoding here? The toEncoding function is a relatively new addition to this class. To allow users of older versions of this library to upgrade without having to edit all of their instances or encounter surprising incompatibilities, the default implementation of toEncoding uses toJSON. This produces correct results, but since it performs an intermediate conversion to a Value, it will be less efficient than directly emitting an Encoding. Our one-liner definition of toEncoding above bypasses the intermediate Value.

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic encoding with only a tiny amount of effort, using genericToJSON and genericToEncoding with your preferred Options:

instance ToJSON Coord where
    toJSON     = genericToJSON defaultOptions
    toEncoding = genericToEncoding defaultOptions

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value

Convert a Haskell value to a JSON-friendly intermediate type.

toEncoding :: a -> Encoding

Encode a Haskell value as JSON.

The default implementation of this method creates an intermediate Value using toJSON. This provides source-level compatibility for people upgrading from older versions of this library, but obviously offers no performance advantage.

To benefit from direct encoding, you must provide an implementation for this method. The easiest way to do so is by having your types implement Generic using the DeriveGeneric extension, and then have GHC generate a method body as follows.

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

Instances

ToJSON DateMathExpr 
ToJSON DateRangeAggRange 
ToJSON DateRangeAggregation 
ToJSON Aggregation 
ToJSON Interval 
ToJSON ExecutionHint 
ToJSON CollectionMode 
ToJSON TermInclusion 
ToJSON TermOrder 
ToJSON ScrollId 
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 Pattern 
ToJSON Exclude 
ToJSON Include 
ToJSON PatternOrPatterns 
ToJSON Source 
ToJSON Search 
ToJSON Size 
ToJSON From 
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 NullValue 
ToJSON Existence 
ToJSON CacheKey 
ToJSON CacheName 
ToJSON FieldName 
ToJSON QueryString 
ToJSON DocId 
ToJSON MappingName 
ToJSON TemplatePattern 
ToJSON TemplateName 
ToJSON IndexName 
ToJSON ReplicaCount 
ToJSON ShardCount 
ToJSON BooleanOperator 
ToJSON SortMode 
ToJSON Missing 
ToJSON SortOrder 
ToJSON SortSpec 
ToJSON ExternalDocVersion 
ToJSON DocVersion 
ToJSON RoutingValue 
ToJSON IndexAliasRouting 
ToJSON SearchAliasRouting 
ToJSON AliasRouting 
ToJSON IndexAliasCreate 
ToJSON IndexAliasAction 
ToJSON IndexAliasName 
ToJSON IndexAlias 
ToJSON IndexTemplate 
ToJSON CompoundFormat 
ToJSON InitialShardCount 
ToJSON FSType 
ToJSON Bytes 
ToJSON ReplicaBounds 
ToJSON AllocationPolicy 
ToJSON UpdatableIndexSetting 
ToJSON IndexSettings 
ToJSON Version 

data Bucket a Source

Constructors

Bucket 

Fields

buckets :: [a]
 

data DateMathAnchor Source

Starting point for a date range. This along with the DateMathModifiers gets you the date ES will start from.

Constructors

DMNow 
DMDate Day 

newtype EsUsername Source

Username type used for HTTP Basic authentication. See basicAuthHook.

Constructors

EsUsername 

Fields

esUsername :: Text
 

newtype EsPassword Source

Password type used for HTTP Basic authentication. See basicAuthHook.

Constructors

EsPassword 

Fields

esPassword :: Text